[Git][ghc/ghc][wip/ozkutuk/sprint-fun] Accept the new test outputs

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 Accept the new test outputs - - - - - 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: ===================================== compiler/GHC/Runtime/Heap/Inspect.hs ===================================== @@ -1,6 +1,4 @@ {-# LANGUAGE MagicHash #-} -{-# LANGUAGE ViewPatterns #-} - {-# LANGUAGE CPP #-} #if __GLASGOW_HASKELL__ > 912 @@ -388,9 +386,7 @@ cPprTermBase y = ifFunSuspension pred f prec t@Suspension{ctype = ctype} | ctype `elem` fun_ctype && pred t = f prec t where - -- TODO(ozkutuk): PAP _seems to be_ indicate a function closure, - -- I have no idea what AP is though - fun_ctype = [ FUN, FUN_1_0, FUN_0_1, FUN_2_0, FUN_1_1, FUN_0_2, FUN_STATIC, AP, PAP ] + fun_ctype = [ FUN, FUN_1_0, FUN_0_1, FUN_2_0, FUN_1_1, FUN_0_2, FUN_STATIC, PAP ] ifFunSuspension _ _ _ _ = return Nothing isFunTy :: Type -> Bool @@ -513,8 +509,8 @@ cPprTermBase y = ppr_list _ _ = panic "doList" ppr_fun :: Precedence -> Term -> m (Maybe SDoc) - ppr_fun _ (ty -> fun_ty) = return $ Just $ - angleBrackets (underscore <+> dcolon <+> pprType fun_ty) + ppr_fun _ t = return $ Just $ + angleBrackets (underscore <+> dcolon <+> pprType (ty t)) repPrim :: TyCon -> [Word] -> SDoc ===================================== testsuite/tests/ghci.debugger/scripts/T12449.stdout ===================================== @@ -1,26 +1,26 @@ -fmap = (_t1::forall (f :: * -> *) a b. +fmap = <_ :: forall (f :: * -> *) a b. Functor f => - (a -> b) -> f a -> f b) + (a -> b) -> f a -> f b> fmap :: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b _t1 :: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b -show = (_t2::forall a. Show a => a -> String) +show = <_ :: forall a. Show a => a -> String> show :: forall a. Show a => a -> String _t2 :: forall a. Show a => a -> String "\"foo\"" ["7","42"] -_t1 = (_t3::forall (f :: * -> *) a b. +_t1 = <_ :: forall (f :: * -> *) a b. Functor f => - (a -> b) -> f a -> f b) + (a -> b) -> f a -> f b> _t3 :: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b -_t2 = (_t4::forall a. Show a => a -> String) +_t2 = <_ :: forall a. Show a => a -> String> _t4 :: forall a. Show a => a -> String ["7","42"] -id = (_t5::forall a. a -> a) +id = <_ :: forall a. a -> a> id :: forall a. a -> a _t5 :: forall a. a -> a -print = (_t6::forall a. Show a => a -> IO ()) +print = <_ :: forall a. Show a => a -> IO ()> print :: forall a. Show a => a -> IO () _t6 :: forall a. Show a => a -> IO () ===================================== testsuite/tests/ghci.debugger/scripts/T19157.stdout ===================================== @@ -3,19 +3,19 @@ Breakpoint 1 activated at T19157.hs:8:23-37 ---------------------- Test 1 Stopped in T19157.mySum.go, T19157.hs:8:23-37 _result :: Int = _ -go :: Int -> [Int] -> Int = _ +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int> s :: Int = 1 ss :: [Int] = [2,3,4,5,6] sum :: Int = 0 Stopped in T19157.mySum.go, T19157.hs:8:23-37 _result :: Int = _ -go :: Int -> [Int] -> Int = _ +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int> s :: Int = 4 ss :: [Int] = [5,6] sum :: Int = _ Stopped in T19157.mySum.go, T19157.hs:8:23-37 _result :: Int = _ -go :: Int -> [Int] -> Int = _ +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int> s :: Int = 6 ss :: [Int] = [] sum :: Int = _ @@ -26,7 +26,7 @@ sum :: Int = _ ---------------------- Test 2 Stopped in T19157.mySum.go, T19157.hs:8:23-37 _result :: Int = _ -go :: Int -> [Int] -> Int = _ +go :: Int -> [Int] -> Int = <_ :: Int -> [Int] -> Int> s :: Int = 1001 ss :: [Int] = _ sum :: Int = _ ===================================== testsuite/tests/ghci.debugger/scripts/T19355.stdout ===================================== @@ -1,8 +1,12 @@ -fmap = (_t1::Functor f => (a -> b) -> f a -> f b) -fmap = (_t2::forall (f :: * -> *) a b. +fmap = <_ :: forall (f :: * -> *) a b. Functor f => - (a -> b) -> f a -> f b) -<*> = (_t3::forall (f :: * -> *) a b. + (a -> b) -> f a -> f b> +fmap = <_ :: forall (f :: * -> *) a b. + Functor f => + (a -> b) -> f a -> f b> +<*> = <_ :: forall (f :: * -> *) a b. + Applicative f => + f (a -> b) -> f a -> f b> +<*> = <_ :: forall (f :: * -> *) a b. Applicative f => - f (a -> b) -> f a -> f b) -<*> = (_t4::Applicative f => f (a -> b) -> f a -> f b) + f (a -> b) -> f a -> f b> ===================================== testsuite/tests/ghci.debugger/scripts/T19394.stdout ===================================== @@ -4,8 +4,10 @@ Identifier ‘realWorld#’ is not eligible for the :print, :sprint or :force co Type constructor ‘Word8#’ is not eligible for the :print, :sprint or :force commands. Type constructor ‘Int’ is not eligible for the :print, :sprint or :force commands. Identifier ‘void#’ is not eligible for the :print, :sprint or :force commands. -error = (_t1::GHC.Internal.Stack.Types.HasCallStack => [Char] -> a) -oneShot = (_t2::(a -> b) -> a -> b) -xor# = (_t3::Word# -> Word# -> Word#) -seq# = (_t4::a -> State# s -> (# State# s, a #)) -lazy = (_t5::a -> a) +error = <_ :: forall a. + GHC.Internal.Stack.Types.HasCallStack => + [Char] -> a> +oneShot = <_ :: forall a b. (a -> b) -> a -> b> +xor# = <_ :: Word# -> Word# -> Word#> +seq# = <_ :: forall a s. a -> State# s -> (# State# s, a #)> +lazy = <_ :: forall a. a -> a> ===================================== testsuite/tests/ghci.debugger/scripts/break006.stdout ===================================== @@ -1,16 +1,16 @@ Stopped in Main.mymap, Test3.hs:2:18-31 _result :: [a] = _ -f :: Int -> a = _ +f :: Int -> a = <_ :: Int -> a> x :: Int = 1 xs :: [Int] = [2,3] xs :: [Int] = [2,3] -f :: Int -> a = _ +f :: Int -> a = <_ :: Int -> a> x :: Int = 1 _result :: [a] = _ y = (_t1::a) y = 2 xs :: [Int] = [2,3] -f :: Int -> Int = _ +f :: Int -> Int = <_ :: Int -> Int> x :: Int = 1 _result :: [Int] = _ y :: Int = 2 ===================================== testsuite/tests/ghci.debugger/scripts/break026.stdout ===================================== @@ -1,7 +1,7 @@ Stopped in Test.foldl, break026.hs:5:16-22 _result :: Int = _ c :: Int = 0 -go :: Int -> [t1] -> Int = _ +go :: Int -> [t1] -> Int = <_ :: Int -> [t1] -> Int> xs :: [t1] = _ Stopped in Test.foldl.go, break026.hs:7:23-35 _result :: Int = _ @@ -19,7 +19,7 @@ c = 1 Stopped in Test.foldl, break026.hs:5:16-22 _result :: Int = _ c :: Int = 0 -go :: Int -> [t1] -> Int = _ +go :: Int -> [t1] -> Int = <_ :: Int -> [t1] -> Int> xs :: [t1] = _ Stopped in Test.foldl.go, break026.hs:7:23-35 _result :: Int = _ ===================================== testsuite/tests/ghci.debugger/scripts/hist001.stdout ===================================== @@ -13,14 +13,14 @@ _result :: [a] f :: t -> a xs :: [t] xs :: [t] = [] -f :: t -> a = _ +f :: t -> a = <_ :: t -> a> _result :: [a] = _ Logged breakpoint at Test3.hs:2:18-20 _result :: a f :: Integer -> a x :: Integer xs :: [t] = [] -f :: Integer -> a = _ +f :: Integer -> a = <_ :: Integer -> a> x :: Integer = 2 _result :: a = _ _result = 3 ===================================== testsuite/tests/ghci.debugger/scripts/hist002.stdout ===================================== @@ -13,14 +13,14 @@ _result :: [a] f :: t -> a xs :: [t] xs :: [t] = [] -f :: t -> a = _ +f :: t -> a = <_ :: t -> a> _result :: [a] = _ Logged breakpoint at Test3.hs:2:18-20 _result :: a f :: Integer -> a x :: Integer xs :: [t] = [] -f :: Integer -> a = _ +f :: Integer -> a = <_ :: Integer -> a> x :: Integer = 2 _result :: a = _ _result = 3 ===================================== testsuite/tests/ghci.debugger/scripts/print027.stdout ===================================== @@ -1,6 +1,10 @@ -+ = (_t1::Num a => a -> a -> a) -print = (_t2::Show a => a -> IO ()) -log = (_t3::Floating a => a -> a) -head = (_t4::GHC.Internal.Stack.Types.HasCallStack => [a] -> a) -tail = (_t5::GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]) -fst = (_t6::(a, b) -> a) ++ = <_ :: forall a. Num a => a -> a -> a> +print = <_ :: forall a. Show a => a -> IO ()> +log = <_ :: forall a. Floating a => a -> a> +head = <_ :: forall a. + GHC.Internal.Stack.Types.HasCallStack => + [a] -> a> +tail = <_ :: forall a. + GHC.Internal.Stack.Types.HasCallStack => + [a] -> [a]> +fst = <_ :: forall a b. (a, b) -> a> ===================================== testsuite/tests/ghci/scripts/T23507.script ===================================== @@ -1,4 +1,9 @@ let f () = () :sprint f +f () +:sprint f + let x = 3 :sprint x +x +:sprint x ===================================== testsuite/tests/ghci/scripts/T23507.stdout ===================================== @@ -1,2 +1,6 @@ +f = _ +() f = <_ :: () -> ()> +x = _ +3 x = <_ :: forall {a}. Num a => a> View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73048fdfa048019a538eba811394e0c5... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73048fdfa048019a538eba811394e0c5... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Berk Özkütük (@ozkutuk)