Skip to content

Commit

Permalink
Trigger multiline mode in GHCi on '\case' (#13087)
Browse files Browse the repository at this point in the history
Summary:
In ALR, 'ITlcase' should expect an opening curly. This is probably a forgotten
edge case in ALR, since `maybe_layout` (which handles the non-ALR layout)
already deals with the 'ITlcase' token properly.

Test Plan: make TEST=T10453 && make TEST=T13087

Reviewers: bgamari, RyanGlScott

Reviewed By: RyanGlScott

Subscribers: RyanGlScott, rwbarton, carter

GHC Trac Issues: #10453, #13087

Differential Revision: https://phabricator.haskell.org/D5236
  • Loading branch information
harpocrates authored and RyanGlScott committed Oct 24, 2018
1 parent d65cbd6 commit eaf1593
Show file tree
Hide file tree
Showing 6 changed files with 31 additions and 0 deletions.
1 change: 1 addition & 0 deletions compiler/parser/Lexer.x
Original file line number Diff line number Diff line change
Expand Up @@ -2673,6 +2673,7 @@ lexTokenAlr = do mPending <- popPendingImplicitToken
ITwhere -> setAlrExpectingOCurly (Just ALRLayoutWhere)
ITlet -> setAlrExpectingOCurly (Just ALRLayoutLet)
ITof -> setAlrExpectingOCurly (Just ALRLayoutOf)
ITlcase -> setAlrExpectingOCurly (Just ALRLayoutOf)
ITdo -> setAlrExpectingOCurly (Just ALRLayoutDo)
ITmdo -> setAlrExpectingOCurly (Just ALRLayoutDo)
ITrec -> setAlrExpectingOCurly (Just ALRLayoutDo)
Expand Down
16 changes: 16 additions & 0 deletions testsuite/tests/ghci/scripts/T10453.script
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
:set +m
:set -XLambdaCase

foo1 x = case x of
1 -> "one"
_ -> "not one"

foo1 0
foo1 1

foo2 = \case
1 -> "one"
_ -> "not one"

foo2 0
foo2 1
4 changes: 4 additions & 0 deletions testsuite/tests/ghci/scripts/T10453.stdout
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
"not one"
"one"
"not one"
"one"
1 change: 1 addition & 0 deletions testsuite/tests/ghci/scripts/all.T
Original file line number Diff line number Diff line change
Expand Up @@ -224,6 +224,7 @@ test('T10248', normal, ghci_script, ['T10248.script'])
test('T10110', normal, ghci_script, ['T10110.script'])
test('T10322', normal, ghci_script, ['T10322.script'])
test('T10439', normal, ghci_script, ['T10439.script'])
test('T10453', normal, ghci_script, ['T10453.script'])
test('T10466', normal, ghci_script, ['T10466.script'])
test('T10501', normal, ghci_script, ['T10501.script'])
test('T10508', normal, ghci_script, ['T10508.script'])
Expand Down
8 changes: 8 additions & 0 deletions testsuite/tests/parser/should_compile/T13087.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
{-# LANGUAGE AlternativeLayoutRule #-}
{-# LANGUAGE LambdaCase #-}

isOne :: Int -> Bool
isOne = \case 1 -> True
_ -> False

main = return ()
1 change: 1 addition & 0 deletions testsuite/tests/parser/should_compile/all.T
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ test('T11622', normal, compile, [''])
test('DumpParsedAst', normal, compile, ['-dsuppress-uniques -ddump-parsed-ast'])
test('DumpRenamedAst', normal, compile, ['-dsuppress-uniques -ddump-rn-ast'])
test('DumpTypecheckedAst', normal, compile, ['-dsuppress-uniques -ddump-tc-ast'])
test('T13087', normal, compile, [''])
test('T13747', normal, compile, [''])
test('T14189', normal, compile, ['-dsuppress-uniques -ddump-rn-ast'])
test('T13986', normal, compile, [''])
Expand Down

0 comments on commit eaf1593

Please sign in to comment.