
#13481: T12622 fails in ghci way -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `T12622`, which is intended to test StaticPointers, fails in the GHCi way with a core lint warning, {{{ *** Core Lint errors : in result of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) *** <no location info>: warning: In the expression: >>= @ IO $fMonadIO @ (Bool -> Bool) @ () (break<10>(s_a1DF) lvl_s3bD) lvl_s3bE s_a1DF :: StaticPtr (Bool -> Bool) [LclId, Unf=Unf{Src=<vanilla>, TopLvl=False, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 70 0}] is out of scope *** Offending Program *** g :: Bool [LclIdX] g = break<15>() True $trModule_s3b7 :: Addr# [LclId] $trModule_s3b7 = "main"# $trModule_s3b6 :: TrName [LclId] $trModule_s3b6 = TrNameS $trModule_s3b7 $trModule_s3b9 :: Addr# [LclId] $trModule_s3b9 = "Main"# $trModule_s3b8 :: TrName [LclId] $trModule_s3b8 = TrNameS $trModule_s3b9 $trModule :: Module [LclIdX] $trModule = Module $trModule_s3b6 $trModule_s3b8 lvl_s3bj :: Addr# [LclId] lvl_s3bj = "error"# lvl_s3bk :: [Char] [LclId] lvl_s3bk = unpackCString# lvl_s3bj lvl_s3bl :: Addr# [LclId] lvl_s3bl = "main"# lvl_s3bm :: [Char] [LclId] lvl_s3bm = unpackCString# lvl_s3bl lvl_s3bn :: Addr# [LclId] lvl_s3bn = "Main"# lvl_s3bo :: [Char] [LclId] lvl_s3bo = unpackCString# lvl_s3bn lvl_s3bp :: Addr# [LclId] lvl_s3bp = "T12622.hs"# lvl_s3bq :: [Char] [LclId] lvl_s3bq = unpackCString# lvl_s3bp lvl_s3br :: Int [LclId] lvl_s3br = I# 21# lvl_s3bs :: Int [LclId] lvl_s3bs = I# 14# lvl_s3bt :: Int [LclId] lvl_s3bt = I# 21# lvl_s3bu :: Int [LclId] lvl_s3bu = I# 64# lvl_s3bv :: SrcLoc [LclId] lvl_s3bv = SrcLoc lvl_s3bm lvl_s3bo lvl_s3bq lvl_s3br lvl_s3bs lvl_s3bt lvl_s3bu lvl_s3bw :: ([Char], SrcLoc) [LclId] lvl_s3bw = (lvl_s3bk, lvl_s3bv) $dIP_s3bc :: CallStack [LclId] $dIP_s3bc = pushCallStack lvl_s3bw emptyCallStack lvl_s3bx :: Addr# [LclId] lvl_s3bx = "couldn't find "# lvl_s3by :: [Char] [LclId] lvl_s3by = unpackCString# lvl_s3bx lookupKey :: forall a. StaticPtr a -> IO a [LclIdX, Arity=1] lookupKey = \ (@ a_a23X) (p_X1DX :: StaticPtr a_a23X) -> break<8>(p_X1DX) >>= @ IO $fMonadIO @ (Maybe (StaticPtr a_a23X)) @ a_a23X (break<1>(p_X1DX) unsafeLookupStaticPtr @ a_a23X (break<0>(p_X1DX) staticKey @ a_a23X p_X1DX)) (\ (ds_d3as :: Maybe (StaticPtr a_a23X)) -> case ds_d3as of { Nothing -> break<7>(p_X1DX) error @ 'LiftedRep @ (IO a_a23X) ($dIP_s3bc `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N) :: (CallStack :: *) ~R# ((?callStack::CallStack) :: Constraint))) (break<6>(p_X1DX) ++ @ Char lvl_s3by (break<5>(p_X1DX) show @ StaticPtrInfo $fShowStaticPtrInfo (break<4>(p_X1DX) staticPtrInfo @ a_a23X p_X1DX))); Just p_a1DI -> break<3>(p_a1DI) return @ IO $fMonadIO @ a_a23X (break<2>(p_a1DI) deRefStaticPtr @ a_a23X p_a1DI) }) $dTypeable_s3bA :: TypeRep Bool [LclId] $dTypeable_s3bA = mkTrCon @ * @ Bool $tcBool ([] @ SomeTypeRep) s_s3bC :: StaticPtr (Bool -> Bool) [LclId] s_s3bC = case break<9>() sg @ Bool ($dTypeable_s3bA `cast` (Sym N:Typeable[0] <*>_N <Bool>_N :: (TypeRep Bool :: *) ~R# (Typeable Bool :: Constraint))) of { T s_a38b -> s_a38b } lvl_s3bD :: IO (Bool -> Bool) [LclId] lvl_s3bD = lookupKey @ (Bool -> Bool) s_s3bC lvl_s3bE :: (Bool -> Bool) -> IO () [LclId] lvl_s3bE = \ (f_a1DG :: Bool -> Bool) -> break<12>(f_a1DG) print @ Bool $fShowBool (break<11>(f_a1DG) f_a1DG True) main :: IO () [LclIdX] main = break<14>() break<13>(s_s3bC) >>= @ IO $fMonadIO @ (Bool -> Bool) @ () (break<10>(s_a1DF) lvl_s3bD) lvl_s3bE main :: IO () [LclIdX] main = runMainIO @ () main *** End of Offense *** <no location info>: error: Compilation had errors *** Exception: ExitFailure 1 ===== program output begins here ===== program output begins here T12622:6:30: error: Not in scope: ‘Main.main’ No module named ‘Main’ is imported. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13481 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler