Berk Özkütük pushed to branch wip/ozkutuk/sprint-fun at Glasgow Haskell Compiler / GHC
Commits:
-
73048fdf
by Berk Özkütük at 2025-06-08T15:16:27+02:00
12 changed files:
- compiler/GHC/Runtime/Heap/Inspect.hs
- testsuite/tests/ghci.debugger/scripts/T12449.stdout
- testsuite/tests/ghci.debugger/scripts/T19157.stdout
- testsuite/tests/ghci.debugger/scripts/T19355.stdout
- testsuite/tests/ghci.debugger/scripts/T19394.stdout
- testsuite/tests/ghci.debugger/scripts/break006.stdout
- testsuite/tests/ghci.debugger/scripts/break026.stdout
- testsuite/tests/ghci.debugger/scripts/hist001.stdout
- testsuite/tests/ghci.debugger/scripts/hist002.stdout
- testsuite/tests/ghci.debugger/scripts/print027.stdout
- testsuite/tests/ghci/scripts/T23507.script
- testsuite/tests/ghci/scripts/T23507.stdout
Changes:
1 | 1 | {-# LANGUAGE MagicHash #-}
|
2 | -{-# LANGUAGE ViewPatterns #-}
|
|
3 | - |
|
4 | 2 | {-# LANGUAGE CPP #-}
|
5 | 3 | |
6 | 4 | #if __GLASGOW_HASKELL__ > 912
|
... | ... | @@ -388,9 +386,7 @@ cPprTermBase y = |
388 | 386 | ifFunSuspension pred f prec t@Suspension{ctype = ctype}
|
389 | 387 | | ctype `elem` fun_ctype && pred t = f prec t
|
390 | 388 | where
|
391 | - -- TODO(ozkutuk): PAP _seems to be_ indicate a function closure,
|
|
392 | - -- I have no idea what AP is though
|
|
393 | - fun_ctype = [ FUN, FUN_1_0, FUN_0_1, FUN_2_0, FUN_1_1, FUN_0_2, FUN_STATIC, AP, PAP ]
|
|
389 | + fun_ctype = [ FUN, FUN_1_0, FUN_0_1, FUN_2_0, FUN_1_1, FUN_0_2, FUN_STATIC, PAP ]
|
|
394 | 390 | ifFunSuspension _ _ _ _ = return Nothing
|
395 | 391 | |
396 | 392 | isFunTy :: Type -> Bool
|
... | ... | @@ -513,8 +509,8 @@ cPprTermBase y = |
513 | 509 | ppr_list _ _ = panic "doList"
|
514 | 510 | |
515 | 511 | ppr_fun :: Precedence -> Term -> m (Maybe SDoc)
|
516 | - ppr_fun _ (ty -> fun_ty) = return $ Just $
|
|
517 | - angleBrackets (underscore <+> dcolon <+> pprType fun_ty)
|
|
512 | + ppr_fun _ t = return $ Just $
|
|
513 | + angleBrackets (underscore <+> dcolon <+> pprType (ty t))
|
|
518 | 514 | |
519 | 515 | |
520 | 516 | repPrim :: TyCon -> [Word] -> SDoc
|
1 | -fmap = (_t1::forall (f :: * -> *) a b.
|
|
1 | +fmap = <_ :: forall (f :: * -> *) a b.
|
|
2 | 2 | Functor f =>
|
3 | - (a -> b) -> f a -> f b)
|
|
3 | + (a -> b) -> f a -> f b>
|
|
4 | 4 | fmap
|
5 | 5 | :: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
|
6 | 6 | _t1
|
7 | 7 | :: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
|
8 | -show = (_t2::forall a. Show a => a -> String)
|
|
8 | +show = <_ :: forall a. Show a => a -> String>
|
|
9 | 9 | show :: forall a. Show a => a -> String
|
10 | 10 | _t2 :: forall a. Show a => a -> String
|
11 | 11 | "\"foo\""
|
12 | 12 | ["7","42"]
|
13 | -_t1 = (_t3::forall (f :: * -> *) a b.
|
|
13 | +_t1 = <_ :: forall (f :: * -> *) a b.
|
|
14 | 14 | Functor f =>
|
15 | - (a -> b) -> f a -> f b)
|
|
15 | + (a -> b) -> f a -> f b>
|
|
16 | 16 | _t3
|
17 | 17 | :: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
|
18 | -_t2 = (_t4::forall a. Show a => a -> String)
|
|
18 | +_t2 = <_ :: forall a. Show a => a -> String>
|
|
19 | 19 | _t4 :: forall a. Show a => a -> String
|
20 | 20 | ["7","42"]
|
21 | -id = (_t5::forall a. a -> a)
|
|
21 | +id = <_ :: forall a. a -> a>
|
|
22 | 22 | id :: forall a. a -> a
|
23 | 23 | _t5 :: forall a. a -> a
|
24 | -print = (_t6::forall a. Show a => a -> IO ())
|
|
24 | +print = <_ :: forall a. Show a => a -> IO ()>
|
|
25 | 25 | print :: forall a. Show a => a -> IO ()
|
26 | 26 | _t6 :: forall a. Show a => a -> IO () |
... | ... | @@ -3,19 +3,19 @@ Breakpoint 1 activated at T19157.hs:8:23-37 |
3 | 3 | ---------------------- Test 1
|
4 | 4 | Stopped in T19157.mySum.go, T19157.hs:8:23-37
|
5 | 5 | _result :: Int = _
|
6 | -go :: Int -> [Int] -> Int = _
|
|
6 | +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int>
|
|
7 | 7 | s :: Int = 1
|
8 | 8 | ss :: [Int] = [2,3,4,5,6]
|
9 | 9 | sum :: Int = 0
|
10 | 10 | Stopped in T19157.mySum.go, T19157.hs:8:23-37
|
11 | 11 | _result :: Int = _
|
12 | -go :: Int -> [Int] -> Int = _
|
|
12 | +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int>
|
|
13 | 13 | s :: Int = 4
|
14 | 14 | ss :: [Int] = [5,6]
|
15 | 15 | sum :: Int = _
|
16 | 16 | Stopped in T19157.mySum.go, T19157.hs:8:23-37
|
17 | 17 | _result :: Int = _
|
18 | -go :: Int -> [Int] -> Int = _
|
|
18 | +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int>
|
|
19 | 19 | s :: Int = 6
|
20 | 20 | ss :: [Int] = []
|
21 | 21 | sum :: Int = _
|
... | ... | @@ -26,7 +26,7 @@ sum :: Int = _ |
26 | 26 | ---------------------- Test 2
|
27 | 27 | Stopped in T19157.mySum.go, T19157.hs:8:23-37
|
28 | 28 | _result :: Int = _
|
29 | -go :: Int -> [Int] -> Int = _
|
|
29 | +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int>
|
|
30 | 30 | s :: Int = 1001
|
31 | 31 | ss :: [Int] = _
|
32 | 32 | sum :: Int = _
|
1 | -fmap = (_t1::Functor f => (a -> b) -> f a -> f b)
|
|
2 | -fmap = (_t2::forall (f :: * -> *) a b.
|
|
1 | +fmap = <_ :: forall (f :: * -> *) a b.
|
|
3 | 2 | Functor f =>
|
4 | - (a -> b) -> f a -> f b)
|
|
5 | -<*> = (_t3::forall (f :: * -> *) a b.
|
|
3 | + (a -> b) -> f a -> f b>
|
|
4 | +fmap = <_ :: forall (f :: * -> *) a b.
|
|
5 | + Functor f =>
|
|
6 | + (a -> b) -> f a -> f b>
|
|
7 | +<*> = <_ :: forall (f :: * -> *) a b.
|
|
8 | + Applicative f =>
|
|
9 | + f (a -> b) -> f a -> f b>
|
|
10 | +<*> = <_ :: forall (f :: * -> *) a b.
|
|
6 | 11 | Applicative f =>
|
7 | - f (a -> b) -> f a -> f b)
|
|
8 | -<*> = (_t4::Applicative f => f (a -> b) -> f a -> f b) |
|
12 | + f (a -> b) -> f a -> f b> |
... | ... | @@ -4,8 +4,10 @@ Identifier ‘realWorld#’ is not eligible for the :print, :sprint or :force co |
4 | 4 | Type constructor ‘Word8#’ is not eligible for the :print, :sprint or :force commands.
|
5 | 5 | Type constructor ‘Int’ is not eligible for the :print, :sprint or :force commands.
|
6 | 6 | Identifier ‘void#’ is not eligible for the :print, :sprint or :force commands.
|
7 | -error = (_t1::GHC.Internal.Stack.Types.HasCallStack => [Char] -> a)
|
|
8 | -oneShot = (_t2::(a -> b) -> a -> b)
|
|
9 | -xor# = (_t3::Word# -> Word# -> Word#)
|
|
10 | -seq# = (_t4::a -> State# s -> (# State# s, a #))
|
|
11 | -lazy = (_t5::a -> a) |
|
7 | +error = <_ :: forall a.
|
|
8 | + GHC.Internal.Stack.Types.HasCallStack =>
|
|
9 | + [Char] -> a>
|
|
10 | +oneShot = <_ :: forall a b. (a -> b) -> a -> b>
|
|
11 | +xor# = <_ :: Word# -> Word# -> Word#>
|
|
12 | +seq# = <_ :: forall a s. a -> State# s -> (# State# s, a #)>
|
|
13 | +lazy = <_ :: forall a. a -> a> |
1 | 1 | Stopped in Main.mymap, Test3.hs:2:18-31
|
2 | 2 | _result :: [a] = _
|
3 | -f :: Int -> a = _
|
|
3 | +f :: Int -> a = <_ :: Int -> a>
|
|
4 | 4 | x :: Int = 1
|
5 | 5 | xs :: [Int] = [2,3]
|
6 | 6 | xs :: [Int] = [2,3]
|
7 | -f :: Int -> a = _
|
|
7 | +f :: Int -> a = <_ :: Int -> a>
|
|
8 | 8 | x :: Int = 1
|
9 | 9 | _result :: [a] = _
|
10 | 10 | y = (_t1::a)
|
11 | 11 | y = 2
|
12 | 12 | xs :: [Int] = [2,3]
|
13 | -f :: Int -> Int = _
|
|
13 | +f :: Int -> Int = <_ :: Int -> Int>
|
|
14 | 14 | x :: Int = 1
|
15 | 15 | _result :: [Int] = _
|
16 | 16 | y :: Int = 2
|
1 | 1 | Stopped in Test.foldl, break026.hs:5:16-22
|
2 | 2 | _result :: Int = _
|
3 | 3 | c :: Int = 0
|
4 | -go :: Int -> [t1] -> Int = _
|
|
4 | +go :: Int -> [t1] -> Int = <_ :: Int -> [t1] -> Int>
|
|
5 | 5 | xs :: [t1] = _
|
6 | 6 | Stopped in Test.foldl.go, break026.hs:7:23-35
|
7 | 7 | _result :: Int = _
|
... | ... | @@ -19,7 +19,7 @@ c = 1 |
19 | 19 | Stopped in Test.foldl, break026.hs:5:16-22
|
20 | 20 | _result :: Int = _
|
21 | 21 | c :: Int = 0
|
22 | -go :: Int -> [t1] -> Int = _
|
|
22 | +go :: Int -> [t1] -> Int = <_ :: Int -> [t1] -> Int>
|
|
23 | 23 | xs :: [t1] = _
|
24 | 24 | Stopped in Test.foldl.go, break026.hs:7:23-35
|
25 | 25 | _result :: Int = _
|
... | ... | @@ -13,14 +13,14 @@ _result :: [a] |
13 | 13 | f :: t -> a
|
14 | 14 | xs :: [t]
|
15 | 15 | xs :: [t] = []
|
16 | -f :: t -> a = _
|
|
16 | +f :: t -> a = <_ :: t -> a>
|
|
17 | 17 | _result :: [a] = _
|
18 | 18 | Logged breakpoint at Test3.hs:2:18-20
|
19 | 19 | _result :: a
|
20 | 20 | f :: Integer -> a
|
21 | 21 | x :: Integer
|
22 | 22 | xs :: [t] = []
|
23 | -f :: Integer -> a = _
|
|
23 | +f :: Integer -> a = <_ :: Integer -> a>
|
|
24 | 24 | x :: Integer = 2
|
25 | 25 | _result :: a = _
|
26 | 26 | _result = 3
|
... | ... | @@ -13,14 +13,14 @@ _result :: [a] |
13 | 13 | f :: t -> a
|
14 | 14 | xs :: [t]
|
15 | 15 | xs :: [t] = []
|
16 | -f :: t -> a = _
|
|
16 | +f :: t -> a = <_ :: t -> a>
|
|
17 | 17 | _result :: [a] = _
|
18 | 18 | Logged breakpoint at Test3.hs:2:18-20
|
19 | 19 | _result :: a
|
20 | 20 | f :: Integer -> a
|
21 | 21 | x :: Integer
|
22 | 22 | xs :: [t] = []
|
23 | -f :: Integer -> a = _
|
|
23 | +f :: Integer -> a = <_ :: Integer -> a>
|
|
24 | 24 | x :: Integer = 2
|
25 | 25 | _result :: a = _
|
26 | 26 | _result = 3
|
1 | -+ = (_t1::Num a => a -> a -> a)
|
|
2 | -print = (_t2::Show a => a -> IO ())
|
|
3 | -log = (_t3::Floating a => a -> a)
|
|
4 | -head = (_t4::GHC.Internal.Stack.Types.HasCallStack => [a] -> a)
|
|
5 | -tail = (_t5::GHC.Internal.Stack.Types.HasCallStack => [a] -> [a])
|
|
6 | -fst = (_t6::(a, b) -> a) |
|
1 | ++ = <_ :: forall a. Num a => a -> a -> a>
|
|
2 | +print = <_ :: forall a. Show a => a -> IO ()>
|
|
3 | +log = <_ :: forall a. Floating a => a -> a>
|
|
4 | +head = <_ :: forall a.
|
|
5 | + GHC.Internal.Stack.Types.HasCallStack =>
|
|
6 | + [a] -> a>
|
|
7 | +tail = <_ :: forall a.
|
|
8 | + GHC.Internal.Stack.Types.HasCallStack =>
|
|
9 | + [a] -> [a]>
|
|
10 | +fst = <_ :: forall a b. (a, b) -> a> |
1 | 1 | let f () = ()
|
2 | 2 | :sprint f
|
3 | +f ()
|
|
4 | +:sprint f
|
|
5 | + |
|
3 | 6 | let x = 3
|
4 | 7 | :sprint x
|
8 | +x
|
|
9 | +:sprint x |
1 | +f = _
|
|
2 | +()
|
|
1 | 3 | f = <_ :: () -> ()>
|
4 | +x = _
|
|
5 | +3
|
|
2 | 6 | x = <_ :: forall {a}. Num a => a> |