Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
-
81d9fe03
by Apoorv Ingle at 2025-11-02T21:39:48-06:00
-
e75752ed
by Apoorv Ingle at 2025-11-02T22:44:08-06:00
-
f556b226
by Apoorv Ingle at 2025-11-02T22:44:31-06:00
21 changed files:
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Head.hs
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/overloadedrecflds/should_fail/T26480b.stderr
- testsuite/tests/plugins/test-defaulting-plugin.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T10971d.stderr
- testsuite/tests/typecheck/should_fail/T13311.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- testsuite/tests/typecheck/should_fail/T3613.stderr
- testsuite/tests/typecheck/should_fail/T6069.stderr
- testsuite/tests/typecheck/should_fail/T7851.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail140.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/typecheck/should_fail/tcfail181.stderr
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
Changes:
| ... | ... | @@ -81,15 +81,15 @@ expand_do_stmts flav [stmt@(L sloc (LastStmt _ body@(L body_loc _) _ ret_expr))] |
| 81 | 81 | -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt`
|
| 82 | 82 | | NoSyntaxExprRn <- ret_expr
|
| 83 | 83 | -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt
|
| 84 | - = return $ L sloc (mkExpandedStmt stmt flav (HsPar noExtField body))
|
|
| 84 | + = return $ L sloc (mkExpandedStmt stmt flav (unLoc body))
|
|
| 85 | 85 | |
| 86 | 86 | | SyntaxExprRn ret <- ret_expr -- We have unfortunately lost the location on the return function :(
|
| 87 | 87 | --
|
| 88 | 88 | -- ------------------------------------------------
|
| 89 | 89 | -- return e ~~> return e
|
| 90 | 90 | -- to make T18324 work
|
| 91 | - = do let expansion = L body_loc (genHsApp ret body)
|
|
| 92 | - return $ L sloc (mkExpandedStmt stmt flav (HsPar noExtField expansion))
|
|
| 91 | + = do let expansion = HsApp noExtField (L body_loc ret) body
|
|
| 92 | + return $ L sloc (mkExpandedStmt stmt flav expansion)
|
|
| 93 | 93 | |
| 94 | 94 | expand_do_stmts doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
|
| 95 | 95 | -- See Note [Expanding HsDo with XXExprGhcRn] Equation (3) below
|
| ... | ... | @@ -1119,6 +1119,9 @@ addExprCtxt e thing_inside |
| 1119 | 1119 | |
| 1120 | 1120 | addLExprCtxt :: LHsExpr GhcRn -> TcRn a -> TcRn a
|
| 1121 | 1121 | addLExprCtxt (L lspan e) thing_inside
|
| 1122 | + | (RealSrcSpan{}) <- locA lspan
|
|
| 1123 | + , (HsPar _ e') <- e
|
|
| 1124 | + = addExprCtxt (unLoc e') thing_inside
|
|
| 1122 | 1125 | | (RealSrcSpan{}) <- locA lspan
|
| 1123 | 1126 | = addExprCtxt e thing_inside
|
| 1124 | 1127 | | otherwise
|
| ... | ... | @@ -11,7 +11,7 @@ default-fail05.hs:11:10: error: [GHC-39999] |
| 11 | 11 | (use -fprint-potential-instances to see them all)
|
| 12 | 12 | • In the first argument of ‘($)’, namely ‘toList’
|
| 13 | 13 | In the first argument of ‘print’, namely ‘(toList $ pure 21)’
|
| 14 | - In the expression: print (toList $ pure 21)
|
|
| 14 | + In a stmt of a 'do' block: print (toList $ pure 21)
|
|
| 15 | 15 | |
| 16 | 16 | default-fail05.hs:11:19: error: [GHC-39999]
|
| 17 | 17 | • Ambiguous type variable ‘t0’ arising from a use of ‘pure’
|
| ... | ... | @@ -25,10 +25,10 @@ default-fail05.hs:11:19: error: [GHC-39999] |
| 25 | 25 | (use -fprint-potential-instances to see them all)
|
| 26 | 26 | • In the second argument of ‘($)’, namely ‘pure 21’
|
| 27 | 27 | In the first argument of ‘print’, namely ‘(toList $ pure 21)’
|
| 28 | - In the expression: print (toList $ pure 21)
|
|
| 28 | + In a stmt of a 'do' block: print (toList $ pure 21)
|
|
| 29 | 29 | |
| 30 | 30 | default-fail05.hs:12:3: error: [GHC-39999]
|
| 31 | - • Ambiguous type variable ‘t1’ arising from a use of ‘traverse’
|
|
| 31 | + • Ambiguous type variable ‘t1’ arising from a do statement
|
|
| 32 | 32 | prevents the constraint ‘(Traversable t1)’ from being solved.
|
| 33 | 33 | Relevant bindings include
|
| 34 | 34 | main :: IO (t1 ()) (bound at default-fail05.hs:10:1)
|
| ... | ... | @@ -42,8 +42,5 @@ T2693.hs:29:20: error: [GHC-83865] |
| 42 | 42 | The type variable ‘a0’ is ambiguous
|
| 43 | 43 | • In the first argument of ‘mapM’, namely ‘g’
|
| 44 | 44 | In the expression: mapM g undefined
|
| 45 | - In the expression:
|
|
| 46 | - do pvs <- mapM g undefined
|
|
| 47 | - let n = (map ...) `min` (map ...)
|
|
| 48 | - undefined
|
|
| 45 | + In a stmt of a 'do' block: pvs <- mapM g undefined
|
|
| 49 | 46 |
| ... | ... | @@ -42,7 +42,7 @@ T26480b.hs:43:12: error: [GHC-39999] |
| 42 | 42 | |
| 43 | 43 | T26480b.hs:47:10: error: [GHC-39999]
|
| 44 | 44 | • No instance for ‘HasField "xyzzywyzzydyzzd" G H’
|
| 45 | - arising from the record selector ‘xyzzywyzzydyzzd’
|
|
| 45 | + arising from the expression (.xyzzywyzzydyzzd)
|
|
| 46 | 46 | NB: ‘G’ does not have a record field named ‘xyzzywyzzydyzzd’.
|
| 47 | 47 | • In the expression: (.xyzzywyzzydyzzd)
|
| 48 | 48 | In an equation for ‘test3a’: test3a = (.xyzzywyzzydyzzd)
|
| ... | ... | @@ -50,6 +50,7 @@ T26480b.hs:47:10: error: [GHC-39999] |
| 50 | 50 | |
| 51 | 51 | T26480b.hs:50:10: error: [GHC-39999]
|
| 52 | 52 | • No instance for ‘HasField "xyzzywyzzydyzze" G H’
|
| 53 | + arising from the expression (.field1.xyzzywyzzydyzze)
|
|
| 53 | 54 | NB: ‘G’ does not have a record field named ‘xyzzywyzzydyzze’.
|
| 54 | 55 | • In the expression: (.field1.xyzzywyzzydyzze)
|
| 55 | 56 | In an equation for ‘test3b’: test3b = (.field1.xyzzywyzzydyzze)
|
| ... | ... | @@ -66,6 +67,7 @@ T26480b.hs:54:12: error: [GHC-39999] |
| 66 | 67 | |
| 67 | 68 | T26480b.hs:57:12: error: [GHC-39999]
|
| 68 | 69 | • No instance for ‘HasField "xyzzywyzzydyzzg" G H’
|
| 70 | + arising from a record update
|
|
| 69 | 71 | NB: ‘G’ does not have a record field named ‘xyzzywyzzydyzzg’.
|
| 70 | 72 | • In the expression: d {field1.xyzzywyzzydyzzg = MkH 3}
|
| 71 | 73 | In an equation for ‘test4b’:
|
| ... | ... | @@ -3,7 +3,7 @@ test-defaulting-plugin.hs:28:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall |
| 3 | 3 | KnownNat a0 arising from a use of ‘q’
|
| 4 | 4 | • In the first argument of ‘(+)’, namely ‘q’
|
| 5 | 5 | In the second argument of ‘($)’, namely ‘q + w’
|
| 6 | - In the expression: print $ q + w
|
|
| 6 | + In a stmt of a 'do' block: print $ q + w
|
|
| 7 | 7 | |
| 8 | 8 | test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
|
| 9 | 9 | • Defaulting the type variable ‘a0’ to type ‘2’ in the following constraints
|
| ... | ... | @@ -15,7 +15,7 @@ test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall |
| 15 | 15 | arising from a use of ‘w’ at test-defaulting-plugin.hs:28:15
|
| 16 | 16 | • In the second argument of ‘(+)’, namely ‘w’
|
| 17 | 17 | In the second argument of ‘($)’, namely ‘q + w’
|
| 18 | - In the expression: print $ q + w
|
|
| 18 | + In a stmt of a 'do' block: print $ q + w
|
|
| 19 | 19 | |
| 20 | 20 | test-defaulting-plugin.hs:29:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
|
| 21 | 21 | • Defaulting the type variable ‘b0’ to type ‘0’ in the following constraint
|
| 1 | 1 | T13393.hs:61:3: error: [GHC-39999]
|
| 2 | - • Ambiguous type variable ‘t0’ arising from a use of ‘mapM’
|
|
| 2 | + • Ambiguous type variable ‘t0’ arising from a do statement
|
|
| 3 | 3 | prevents the constraint ‘(Traversable t0)’ from being solved.
|
| 4 | 4 | Probable fix: use a type annotation to specify what ‘t0’ should be.
|
| 5 | 5 | Potentially matching instances:
|
| 6 | - instance Traversable (Either a)
|
|
| 7 | - -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 8 | - instance Traversable Identity
|
|
| 9 | - -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 10 | - ...plus four others
|
|
| 11 | - ...plus 27 instances involving out-of-scope types
|
|
| 12 | - (use -fprint-potential-instances to see them all)
|
|
| 13 | - • In the expression:
|
|
| 14 | - mapM putBackLeftOverInputAndReturnOutput undefined
|
|
| 6 | + instance Traversable (Either a)
|
|
| 7 | + -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 8 | + instance Traversable Identity
|
|
| 9 | + -- Defined in ‘GHC.Internal.Data.Traversable’
|
|
| 10 | + ...plus four others
|
|
| 11 | + ...plus 27 instances involving out-of-scope types
|
|
| 12 | + (use -fprint-potential-instances to see them all)
|
|
| 13 | + • In a stmt of a 'do' block:
|
|
| 14 | + mapM putBackLeftOverInputAndReturnOutput undefined
|
|
| 15 | 15 | In the expression:
|
| 16 | - do mapM putBackLeftOverInputAndReturnOutput undefined
|
|
| 17 | - undefined
|
|
| 16 | + do mapM putBackLeftOverInputAndReturnOutput undefined
|
|
| 17 | + undefined
|
|
| 18 | 18 | In an equation for ‘encodeLinearToAac’:
|
| 19 | - encodeLinearToAac
|
|
| 20 | - = do mapM putBackLeftOverInputAndReturnOutput undefined
|
|
| 21 | - undefined
|
|
| 22 | - where
|
|
| 23 | - putBackLeftOverInputAndReturnOutput (MkEncodeResult x)
|
|
| 24 | - = do leftOvers .= x
|
|
| 25 | - undefined |
|
| 19 | + encodeLinearToAac
|
|
| 20 | + = do mapM putBackLeftOverInputAndReturnOutput undefined
|
|
| 21 | + undefined
|
|
| 22 | + where
|
|
| 23 | + putBackLeftOverInputAndReturnOutput (MkEncodeResult x)
|
|
| 24 | + = do leftOvers .= x
|
|
| 25 | + undefined
|
|
| 26 | + |
| ... | ... | @@ -12,15 +12,11 @@ valid_hole_fits.hs:9:6: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables |
| 12 | 12 | valid_hole_fits.hs:17:17: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
| 13 | 13 | • Found hole: _ :: Int -> IO Int
|
| 14 | 14 | • In the expression: _ x
|
| 15 | + In a stmt of a 'do' block: y <- _ x
|
|
| 15 | 16 | In the expression:
|
| 16 | 17 | do x <- a 0
|
| 17 | 18 | y <- _ x
|
| 18 | 19 | return y
|
| 19 | - In an equation for ‘c’:
|
|
| 20 | - c _
|
|
| 21 | - = do x <- a 0
|
|
| 22 | - y <- _ x
|
|
| 23 | - return y
|
|
| 24 | 20 | • Relevant bindings include
|
| 25 | 21 | x :: Int (bound at valid_hole_fits.hs:16:12)
|
| 26 | 22 | c :: Int -> IO Int (bound at valid_hole_fits.hs:16:1)
|
| ... | ... | @@ -3,14 +3,14 @@ T10971d.hs:4:14: error: [GHC-83865] |
| 3 | 3 | with actual type: Maybe a3
|
| 4 | 4 | • In the first argument of ‘f’, namely ‘(Just 1)’
|
| 5 | 5 | In the second argument of ‘($)’, namely ‘f (Just 1)’
|
| 6 | - In the expression: print $ f (Just 1)
|
|
| 6 | + In a stmt of a 'do' block: print $ f (Just 1)
|
|
| 7 | 7 | |
| 8 | 8 | T10971d.hs:5:19: error: [GHC-83865]
|
| 9 | 9 | • Couldn't match expected type: [b0]
|
| 10 | 10 | with actual type: Maybe a4
|
| 11 | 11 | • In the second argument of ‘g’, namely ‘(Just 5)’
|
| 12 | 12 | In the second argument of ‘($)’, namely ‘g (+ 1) (Just 5)’
|
| 13 | - In the expression: print $ g (+ 1) (Just 5)
|
|
| 13 | + In a stmt of a 'do' block: print $ g (+ 1) (Just 5)
|
|
| 14 | 14 | |
| 15 | 15 | T10971d.hs:6:23: error: [GHC-83865]
|
| 16 | 16 | • Couldn't match expected type: [a2]
|
| ... | ... | @@ -2,7 +2,7 @@ T13311.hs:9:3: error: [GHC-83865] |
| 2 | 2 | • Couldn't match expected type: IO a0
|
| 3 | 3 | with actual type: Maybe a1 -> Maybe b0
|
| 4 | 4 | • Probable cause: ‘f’ is applied to too few arguments
|
| 5 | - In the expression: f
|
|
| 5 | + In a stmt of a 'do' block: f
|
|
| 6 | 6 | In the expression:
|
| 7 | 7 | do f
|
| 8 | 8 | putChar 'a'
|
| ... | ... | @@ -10,7 +10,7 @@ T24064.hs:42:3: error: [GHC-25897] |
| 10 | 10 | the type signature for:
|
| 11 | 11 | test :: forall (m :: * -> *). (C2 m, F2 m ~ Y) => m ()
|
| 12 | 12 | at T24064.hs:40:1-32
|
| 13 | - • In the expression: fun1
|
|
| 13 | + • In a stmt of a 'do' block: fun1
|
|
| 14 | 14 | In the expression:
|
| 15 | 15 | do fun1
|
| 16 | 16 | fun2
|
| ... | ... | @@ -10,7 +10,7 @@ T3613.hs:17:24: error: [GHC-83865] |
| 10 | 10 | • Couldn't match type ‘IO’ with ‘Maybe’
|
| 11 | 11 | Expected: Maybe ()
|
| 12 | 12 | Actual: IO ()
|
| 13 | - • In the expression: bar
|
|
| 13 | + • In a stmt of a 'do' block: bar
|
|
| 14 | 14 | In the first argument of ‘fooThen’, namely
|
| 15 | 15 | ‘(do bar
|
| 16 | 16 | undefined)’
|
| 1 | - |
|
| 2 | 1 | T6069.hs:13:15: error: [GHC-83865]
|
| 3 | 2 | • Couldn't match type: forall s. ST s b0
|
| 4 | 3 | with: ST s0 Int
|
| ... | ... | @@ -24,4 +23,5 @@ T6069.hs:15:16: error: [GHC-83865] |
| 24 | 23 | Actual: (forall s. ST s b2) -> b2
|
| 25 | 24 | • In the second argument of ‘(.)’, namely ‘runST’
|
| 26 | 25 | In the expression: print . runST
|
| 27 | - In the expression: ((print . runST) $) fourty_two |
|
| 26 | + In the expression: (print . runST) $
|
|
| 27 | + |
| ... | ... | @@ -2,7 +2,7 @@ T7851.hs:5:10: error: [GHC-83865] |
| 2 | 2 | • Couldn't match expected type: IO a0
|
| 3 | 3 | with actual type: a1 -> IO ()
|
| 4 | 4 | • Probable cause: ‘print’ is applied to too few arguments
|
| 5 | - In the expression: print
|
|
| 5 | + In a stmt of a 'do' block: print
|
|
| 6 | 6 | In the expression:
|
| 7 | 7 | do print
|
| 8 | 8 | print "Hello"
|
| ... | ... | @@ -10,7 +10,5 @@ T8603.hs:33:17: error: [GHC-18872] |
| 10 | 10 | m a -> t m a’
|
| 11 | 11 | has only one
|
| 12 | 12 | In the expression: lift uniform [1, 2, 3]
|
| 13 | - In the expression:
|
|
| 14 | - do prize <- lift uniform [1, 2, 3]
|
|
| 15 | - return False
|
|
| 13 | + In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3]
|
|
| 16 | 14 |
| ... | ... | @@ -3,9 +3,9 @@ T9612.hs:16:9: error: [GHC-18872] |
| 3 | 3 | with: (Int, a)
|
| 4 | 4 | arising from a functional dependency between:
|
| 5 | 5 | constraint ‘MonadWriter (Int, a) (WriterT [(Int, a)] Identity)’
|
| 6 | - arising from a use of ‘tell’
|
|
| 6 | + arising from a do statement
|
|
| 7 | 7 | instance ‘MonadWriter w (WriterT w m)’ at T9612.hs:20:10-59
|
| 8 | - • In the expression: tell (n, x)
|
|
| 8 | + • In a stmt of a 'do' block: tell (n, x)
|
|
| 9 | 9 | In the expression:
|
| 10 | 10 | do tell (n, x)
|
| 11 | 11 | return (1, y)
|
| ... | ... | @@ -6,6 +6,7 @@ tcfail128.hs:18:16: error: [GHC-39999] |
| 6 | 6 | one instance involving out-of-scope types
|
| 7 | 7 | (use -fprint-potential-instances to see them all)
|
| 8 | 8 | • In the expression: thaw tmp
|
| 9 | + In a stmt of a 'do' block: v <- thaw tmp
|
|
| 9 | 10 | In the expression:
|
| 10 | 11 | do let sL = [...]
|
| 11 | 12 | dim = length sL
|
| ... | ... | @@ -13,11 +14,4 @@ tcfail128.hs:18:16: error: [GHC-39999] |
| 13 | 14 | ...
|
| 14 | 15 | v <- thaw tmp
|
| 15 | 16 | return ()
|
| 16 | - In an equation for ‘main’:
|
|
| 17 | - main
|
|
| 18 | - = do let sL = ...
|
|
| 19 | - dim = length sL
|
|
| 20 | - ...
|
|
| 21 | - v <- thaw tmp
|
|
| 22 | - return ()
|
|
| 23 | 17 |
| ... | ... | @@ -17,7 +17,8 @@ tcfail140.hs:13:10: error: [GHC-83865] |
| 17 | 17 | |
| 18 | 18 | tcfail140.hs:15:15: error: [GHC-83865]
|
| 19 | 19 | • Couldn't match expected type ‘t -> b’ with actual type ‘Int’
|
| 20 | - • In the first argument of ‘map’, namely ‘(3 `f`)’
|
|
| 20 | + • Possible cause: ‘f’ is applied to too many arguments
|
|
| 21 | + In the first argument of ‘map’, namely ‘(3 `f`)’
|
|
| 21 | 22 | In the expression: map (3 `f`) xs
|
| 22 | 23 | In an equation for ‘bot’: bot xs = map (3 `f`) xs
|
| 23 | 24 | • Relevant bindings include
|
| 1 | 1 | tcfail168.hs:7:11: error: [GHC-83865]
|
| 2 | 2 | • Couldn't match expected type: IO a0
|
| 3 | - with actual type: Char -> IO ()
|
|
| 3 | + with actual type: Char -> IO ()
|
|
| 4 | 4 | • Probable cause: ‘putChar’ is applied to too few arguments
|
| 5 | - In the expression: putChar
|
|
| 5 | + In a stmt of a 'do' block: putChar
|
|
| 6 | 6 | In the expression:
|
| 7 | - do putChar
|
|
| 8 | - putChar 'a'
|
|
| 9 | - putChar 'a'
|
|
| 10 | - putChar 'a'
|
|
| 11 | - putChar 'a'
|
|
| 12 | - ...
|
|
| 7 | + do putChar
|
|
| 8 | + putChar 'a'
|
|
| 9 | + putChar 'a'
|
|
| 10 | + putChar 'a'
|
|
| 11 | + putChar 'a'
|
|
| 12 | + ...
|
|
| 13 | 13 | In an equation for ‘foo’:
|
| 14 | - foo
|
|
| 15 | - = do putChar
|
|
| 16 | - putChar 'a'
|
|
| 17 | - putChar 'a'
|
|
| 18 | - putChar 'a'
|
|
| 19 | - ... |
|
| 14 | + foo
|
|
| 15 | + = do putChar
|
|
| 16 | + putChar 'a'
|
|
| 17 | + putChar 'a'
|
|
| 18 | + putChar 'a'
|
|
| 19 | + ...
|
|
| 20 | + |
| 1 | - |
|
| 2 | 1 | tcfail181.hs:17:9: error: [GHC-39999]
|
| 3 | - • Could not deduce ‘Monad m0’ arising from a use of ‘foo’
|
|
| 2 | + • Could not deduce ‘Monad m0’ arising from a record update
|
|
| 4 | 3 | from the context: Monad m
|
| 5 | 4 | bound by the inferred type of
|
| 6 | 5 | wog :: Monad m => p -> Something (m Bool) e
|
| ... | ... | @@ -12,8 +11,9 @@ tcfail181.hs:17:9: error: [GHC-39999] |
| 12 | 11 | ...plus six others
|
| 13 | 12 | ...plus one instance involving out-of-scope types
|
| 14 | 13 | (use -fprint-potential-instances to see them all)
|
| 15 | - • In the expression: foo
|
|
| 16 | - In a record update at field ‘bar’,
|
|
| 14 | + • In a record update at field ‘bar’,
|
|
| 17 | 15 | with type constructor ‘Something’
|
| 18 | 16 | and data constructor ‘Something’.
|
| 19 | 17 | In the expression: foo {bar = return True}
|
| 18 | + In an equation for ‘wog’: wog x = foo {bar = return True}
|
|
| 19 | + |
| 1 | 1 | CaretDiagnostics1.hs:7:8-15: error: [GHC-83865]
|
| 2 | 2 | • Couldn't match expected type ‘IO a0’ with actual type ‘Int’
|
| 3 | 3 | • In the second argument of ‘(+)’, namely ‘(3 :: Int)’
|
| 4 | - In the expression:
|
|
| 4 | + In a stmt of a 'do' block:
|
|
| 5 | 5 | 10000000000000000000000000000000000000 + 2 + (3 :: Int)
|
| 6 | 6 | In the expression:
|
| 7 | 7 | do 10000000000000000000000000000000000000 + 2 + (3 :: Int)
|