Skip to content

Commit

Permalink
feat: Make FC reporting in errors nicer (#39)
Browse files Browse the repository at this point in the history
  • Loading branch information
croyzor authored Oct 30, 2024
1 parent 8752f32 commit a77f82c
Show file tree
Hide file tree
Showing 73 changed files with 85 additions and 73 deletions.
10 changes: 9 additions & 1 deletion brat/Brat/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -191,9 +191,17 @@ addSrcContext _ _ (Right r) = Right r
addSrcContext fname cts (Left err@Err{fc=fc}) = Left (SrcErr msg err)
where
msg = case fc of
Just fc -> unlines (errHeader (fname ++ '@':show fc):showFileContext cts fc)
Just fc -> unlines (errHeader (fname ++ prettyFC fc)
:showFileContext cts fc
)
Nothing -> errHeader fname

prettyFC fc = let Pos startLine _ = start fc
Pos endLine _ = end fc
in if startLine == endLine
then " on line " ++ show startLine
else " on lines " ++ show startLine ++ "-" ++ show endLine

showFileContext :: String -> FC -> [String]
showFileContext contents fc = let
-- taking 1 off to convert 1-indexed user line numbers to 0-indexed list indices
Expand Down
6 changes: 5 additions & 1 deletion brat/Brat/FC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,11 @@ module Brat.FC where

data Pos = Pos { line :: Int
, col :: Int
} deriving (Eq, Show)
} deriving Eq

instance Show Pos where
show (Pos { .. }) = show line ++ ":" ++ show col


instance Ord Pos where
compare (Pos l c) (Pos l' c') | l == l' = compare c c'
Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/binding/cons.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/binding/cons.brat@FC {start = Pos {line = 7, col = 10}, end = Pos {line = 7, col = 23}}:
Error in test/golden/binding/cons.brat on line 7:
badUncons(cons(stuff)) = stuff
^^^^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/binding/let.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/binding/let.brat@FC {start = Pos {line = 7, col = 14}, end = Pos {line = 7, col = 36}}:
Error in test/golden/binding/let.brat on line 7:
badBinding = let x = twoThings in x
^^^^^^^^^^^^^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/apply_two_thunks.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/apply_two_thunks.brat@FC {start = Pos {line = 9, col = 9}, end = Pos {line = 9, col = 18}}:
Error in test/golden/error/apply_two_thunks.brat on line 9:
go(n) = thunks(n)
^^^^^^^^^

Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/arith_implicit_conversion.brat@FC {start = Pos {line = 2, col = 20}, end = Pos {line = 2, col = 21}}:
Error in test/golden/error/arith_implicit_conversion.brat on line 2:
f(x, y) = x + (x * y)
^

Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/arith_implicit_conversion2.brat@FC {start = Pos {line = 2, col = 16}, end = Pos {line = 2, col = 17}}:
Error in test/golden/error/arith_implicit_conversion2.brat on line 2:
f(x, y) = x + (y - x)
^

Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/arith_implicit_conversion3.brat@FC {start = Pos {line = 2, col = 11}, end = Pos {line = 2, col = 12}}:
Error in test/golden/error/arith_implicit_conversion3.brat on line 2:
f(x, y) = y + x
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/bad_rpat.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/bad_rpat.brat@FC {start = Pos {line = 2, col = 8}, end = Pos {line = 2, col = 19}}:
Error in test/golden/error/bad_rpat.brat on line 2:
test = cons(1, [])
^^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/bad_underscore.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/bad_underscore.brat@FC {start = Pos {line = 2, col = 12}, end = Pos {line = 2, col = 18}}:
Error in test/golden/error/bad_underscore.brat on line 2:
uscore = { i => _ }
^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/bad_underscore2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/bad_underscore2.brat@FC {start = Pos {line = 2, col = 13}, end = Pos {line = 2, col = 14}}:
Error in test/golden/error/bad_underscore2.brat on line 2:
uscore(i) = _
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/badvec.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/badvec.brat@FC {start = Pos {line = 2, col = 6}, end = Pos {line = 2, col = 9}}:
Error in test/golden/error/badvec.brat on line 2:
v3 = [1]
^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/badvec2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/badvec2.brat@FC {start = Pos {line = 2, col = 6}, end = Pos {line = 2, col = 9}}:
Error in test/golden/error/badvec2.brat on line 2:
v3 = nil
^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/badvec3.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/badvec3.brat@FC {start = Pos {line = 2, col = 6}, end = Pos {line = 2, col = 18}}:
Error in test/golden/error/badvec3.brat on line 2:
v3 = cons(1, nil)
^^^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/badvec4.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/badvec4.brat@FC {start = Pos {line = 2, col = 6}, end = Pos {line = 2, col = 11}}:
Error in test/golden/error/badvec4.brat on line 2:
v3 = [1,2]
^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/empty_into.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/empty_into.brat@FC {start = Pos {line = 5, col = 11}, end = Pos {line = 5, col = 21}}:
Error in test/golden/error/empty_into.brat on line 5:
intoErr = |> makeInt
^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanin-diff-types.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanin-diff-types.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanin-diff-types.brat on line 2:
f = { [\/] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanin-dynamic-length.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanin-dynamic-length.brat@FC {start = Pos {line = 2, col = 8}, end = Pos {line = 2, col = 16}}:
Error in test/golden/error/fanin-dynamic-length.brat on line 2:
f(n) = { [\/] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanin-list.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanin-list.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanin-list.brat on line 2:
f = { [\/] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanin-not-enough-overs.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanin-not-enough-overs.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanin-not-enough-overs.brat on line 2:
f = { [\/] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanin-too-many-overs.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanin-too-many-overs.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanin-too-many-overs.brat on line 2:
f = { [\/] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanout-diff-types.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanout-diff-types.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanout-diff-types.brat on line 2:
f = { [/\] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanout-dynamic-length.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanout-dynamic-length.brat@FC {start = Pos {line = 2, col = 8}, end = Pos {line = 2, col = 16}}:
Error in test/golden/error/fanout-dynamic-length.brat on line 2:
f(n) = { [/\] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanout-list.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanout-list.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanout-list.brat on line 2:
f = { [/\] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanout-not-enough-overs.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanout-not-enough-overs.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanout-not-enough-overs.brat on line 2:
f = { [/\] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/fanout-too-many-overs.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/fanout-too-many-overs.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/fanout-too-many-overs.brat on line 2:
f = { [/\] }
^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/inconsistentclauses.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/inconsistentclauses.brat@FC {start = Pos {line = 1, col = 1}, end = Pos {line = 3, col = 9}}:
Error in test/golden/error/inconsistentclauses.brat on lines 1-3:
f(Bool, Nat) -> Nat
^^^^^^^^^^^^^^^^^^^
f(true, n) = 1
Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/kbadvec.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/kbadvec.brat@FC {start = Pos {line = 2, col = 17}, end = Pos {line = 2, col = 20}}:
Error in test/golden/error/kbadvec.brat on line 2:
triple = { b => [b] }
^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/kbadvec2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/kbadvec2.brat@FC {start = Pos {line = 2, col = 17}, end = Pos {line = 2, col = 20}}:
Error in test/golden/error/kbadvec2.brat on line 2:
triple = { b => nil }
^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/kbadvec3.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/kbadvec3.brat@FC {start = Pos {line = 2, col = 19}, end = Pos {line = 2, col = 31}}:
Error in test/golden/error/kbadvec3.brat on line 2:
constNil = { b => cons(1, nil) }
^^^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/kbadvec4.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/kbadvec4.brat@FC {start = Pos {line = 2, col = 7}, end = Pos {line = 2, col = 12}}:
Error in test/golden/error/kbadvec4.brat on line 2:
f = { [1,2] => true }
^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/kvarnotfound.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/kvarnotfound.brat@FC {start = Pos {line = 2, col = 12}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/kvarnotfound.brat on line 2:
f = { x => y }
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/multilambda-id.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/multilambda-id.brat@FC {start = Pos {line = 2, col = 15}, end = Pos {line = 2, col = 16}}:
Error in test/golden/error/multilambda-id.brat on line 2:
f = { true => |
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/multilambda-id2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/multilambda-id2.brat@FC {start = Pos {line = 2, col = 12}, end = Pos {line = 2, col = 13}}:
Error in test/golden/error/multilambda-id2.brat on line 2:
g = { 0 => ||succ(n) => | }
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/multilambda-id3.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/multilambda-id3.brat@FC {start = Pos {line = 2, col = 15}, end = Pos {line = 2, col = 18}}:
Error in test/golden/error/multilambda-id3.brat on line 2:
f = { true => |;||false =>|;|;|}
^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/nameclash1.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/nameclash1.brat@FC {start = Pos {line = 1, col = 1}, end = Pos {line = 1, col = 16}}:
Error in test/golden/error/nameclash1.brat on line 1:
type Nat(x) = x
^^^^^^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/nameclash2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/nameclash2.brat@FC {start = Pos {line = 2, col = 1}, end = Pos {line = 2, col = 16}}:
Error in test/golden/error/nameclash2.brat on line 2:
type A(x,y) = y
^^^^^^^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/no_thunk.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/no_thunk.brat@FC {start = Pos {line = 8, col = 14}, end = Pos {line = 8, col = 15}}:
Error in test/golden/error/no_thunk.brat on line 8:
Rz(2.0 / n); X
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/noovers.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/noovers.brat@FC {start = Pos {line = 2, col = 2}, end = Pos {line = 2, col = 8}}:
Error in test/golden/error/noovers.brat on line 2:
f(a, b) = []
^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/pair.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/pair.brat@FC {start = Pos {line = 5, col = 8}, end = Pos {line = 5, col = 11}}:
Error in test/golden/error/pair.brat on line 5:
pair = row -- Distinct from a pair
^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/pass.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/pass.brat@FC {start = Pos {line = 5, col = 12}, end = Pos {line = 5, col = 13}}:
Error in test/golden/error/pass.brat on line 5:
f = { .., (x => x) }
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/pass_empty.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/pass_empty.brat@FC {start = Pos {line = 2, col = 17}, end = Pos {line = 2, col = 19}}:
Error in test/golden/error/pass_empty.brat on line 2:
f = { (x => x), .. }
^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/portpull-ambiguous.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/portpull-ambiguous.brat@FC {start = Pos {line = 6, col = 22}, end = Pos {line = 6, col = 31}}:
Error in test/golden/error/portpull-ambiguous.brat on line 6:
id2 = x, y => (id,id)(a1:x, y)
^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/portpull.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/portpull.brat@FC {start = Pos {line = 6, col = 22}, end = Pos {line = 6, col = 31}}:
Error in test/golden/error/portpull.brat on line 6:
id2 = x,y => (id, id)(a1:x, y)
^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/simpleterm.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/simpleterm.brat@FC {start = Pos {line = 2, col = 10}, end = Pos {line = 2, col = 14}}:
Error in test/golden/error/simpleterm.brat on line 2:
simple = true
^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/toplevel-leftovers.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/toplevel-leftovers.brat@FC {start = Pos {line = 2, col = 5}, end = Pos {line = 2, col = 7}}:
Error in test/golden/error/toplevel-leftovers.brat on line 2:
f = 42
^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/toplevel-leftovers2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/toplevel-leftovers2.brat@FC {start = Pos {line = 2, col = 8}, end = Pos {line = 2, col = 9}}:
Error in test/golden/error/toplevel-leftovers2.brat on line 2:
f(x) = x
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/toplevel-leftovers3.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/toplevel-leftovers3.brat@FC {start = Pos {line = 2, col = 2}, end = Pos {line = 2, col = 5}}:
Error in test/golden/error/toplevel-leftovers3.brat on line 2:
f(x) = x
^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/type-arith.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/type-arith.brat@FC {start = Pos {line = 1, col = 20}, end = Pos {line = 1, col = 25}}:
Error in test/golden/error/type-arith.brat on line 1:
f(n :: #, Vec(Nat, n ^ 3)) -> Bool
^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/type-arith2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/type-arith2.brat@FC {start = Pos {line = 1, col = 20}, end = Pos {line = 1, col = 25}}:
Error in test/golden/error/type-arith2.brat on line 1:
f(n :: #, Vec(Nat, n * n)) -> Bool
^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/unmatched_bracket.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/unmatched_bracket.brat@FC {start = Pos {line = 1, col = 17}, end = Pos {line = 1, col = 19}}:
Error in test/golden/error/unmatched_bracket.brat on line 1:
f(n, Vec([], n) -> Vec([], n) -- First bracket never closed
^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/varnotfound.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/varnotfound.brat@FC {start = Pos {line = 2, col = 8}, end = Pos {line = 2, col = 9}}:
Error in test/golden/error/varnotfound.brat on line 2:
f(x) = g(x)
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/vecpat.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/vecpat.brat@FC {start = Pos {line = 3, col = 5}, end = Pos {line = 3, col = 10}}:
Error in test/golden/error/vecpat.brat on line 3:
fst3(nil) = none
^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/vecpat2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/vecpat2.brat@FC {start = Pos {line = 3, col = 5}, end = Pos {line = 3, col = 14}}:
Error in test/golden/error/vecpat2.brat on line 3:
fst3(some(x)) = none
^^^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/error/vecpat3.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/error/vecpat3.brat@FC {start = Pos {line = 3, col = 5}, end = Pos {line = 3, col = 12}}:
Error in test/golden/error/vecpat3.brat on line 3:
fst3([a,b]) = none
^^^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/alias-clash.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in alias-clash@FC {start = Pos {line = 2, col = 15}, end = Pos {line = 2, col = 16}}:
Error in alias-clash on line 2:
import lib as A (z)
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/non-existent1.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in non-existent1@FC {start = Pos {line = 1, col = 16}, end = Pos {line = 1, col = 17}}:
Error in non-existent1 on line 1:
import lib (x, a)
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/non-existent2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in non-existent2@FC {start = Pos {line = 1, col = 23}, end = Pos {line = 1, col = 24}}:
Error in non-existent2 on line 1:
import lib hiding (y, a)
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/use-illegal-z.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/imports/use-illegal-z.brat@FC {start = Pos {line = 4, col = 14}, end = Pos {line = 4, col = 15}}:
Error in test/golden/imports/use-illegal-z.brat on line 4:
main = x, y, z
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/use-illegal-z2.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/imports/use-illegal-z2.brat@FC {start = Pos {line = 4, col = 22}, end = Pos {line = 4, col = 27}}:
Error in test/golden/imports/use-illegal-z2.brat on line 4:
main = lib.x, lib.y, lib.z
^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/use-illegal-z3.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/imports/use-illegal-z3.brat@FC {start = Pos {line = 4, col = 14}, end = Pos {line = 4, col = 15}}:
Error in test/golden/imports/use-illegal-z3.brat on line 4:
main = x, y, z
^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/use-illegal-z4.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/imports/use-illegal-z4.brat@FC {start = Pos {line = 4, col = 22}, end = Pos {line = 4, col = 27}}:
Error in test/golden/imports/use-illegal-z4.brat on line 4:
main = lib.x, lib.y, lib.z
^^^^^

Expand Down
2 changes: 1 addition & 1 deletion brat/test/golden/imports/use-unqualified.brat.golden
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Error in test/golden/imports/use-unqualified.brat@FC {start = Pos {line = 4, col = 8}, end = Pos {line = 4, col = 9}}:
Error in test/golden/imports/use-unqualified.brat on line 4:
main = x
^

Expand Down
Loading

0 comments on commit a77f82c

Please sign in to comment.