[GHC] #16152: Core lint error from PartialTypeSignatures

#16152: Core lint error from PartialTypeSignatures -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Keywords: | Operating System: Unknown/Multiple PartialTypeSignatures | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# Language PartialTypeSignatures #-} {-# Language PolyKinds #-} {-# Language ScopedTypeVariables #-} {-# Options_GHC -dcore-lint #-} top :: forall f. _ top = undefined where x :: forall a. f a x = undefined }}} causes Core lint errors: {{{ $ ~/../inplace/bin/ghc-stage2 --interactive -ignore-dot-ghci 922_bug.hs GHCi, version 8.7.20181230: https://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( 922_bug.hs, interpreted ) *** Core Lint errors : in result of Desugar (before optimization) *** <no location info>: warning: In the type ‘forall (f :: k_a1z6 -> *) w. w’ @ k_a1z6 is out of scope *** Offending Program *** Rec { $trModule :: Module [LclIdX] $trModule = Module (TrNameS "main"#) (TrNameS "Main"#) top :: forall (f :: k_a1z6 -> *) w. w [LclIdX] top = \ (@ (f_a2BY :: k_a1z6 -> *)) (@ w_a2BZ) -> (\ (@ k_a1z6) (@ (f_a1yV :: k_a1z6 -> *)) (@ w_a1yN) -> let { $dIP_a2BO :: ?callStack::CallStack [LclId] $dIP_a2BO = emptyCallStack `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N) :: CallStack ~R# (?callStack::CallStack)) } in let { $dIP_a2BD :: HasCallStack [LclId] $dIP_a2BD = (pushCallStack (unpackCString# "undefined"#, SrcLoc (unpackCString# "main"#) (unpackCString# "Main"#) (unpackCString# "922_bug.hs"#) (I# 8#) (I# 7#) (I# 8#) (I# 16#)) ($dIP_a2BO `cast` (N:IP[0] <"callStack">_N <CallStack>_N :: (?callStack::CallStack) ~R# CallStack))) `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N) :: CallStack ~R# (?callStack::CallStack)) } in letrec { top_a1yW :: w_a1yN [LclId] top_a1yW = letrec { x_a1yv :: forall (a :: k_a1z6). f_a1yV a [LclId] x_a1yv = \ (@ (a_a1zd :: k_a1z6)) -> let { $dIP_a2BP :: ?callStack::CallStack [LclId] $dIP_a2BP = emptyCallStack `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N) :: CallStack ~R# (?callStack::CallStack)) } in let { $dIP_a2Bz :: HasCallStack [LclId] $dIP_a2Bz = (pushCallStack (unpackCString# "undefined"#, SrcLoc (unpackCString# "main"#) (unpackCString# "Main"#) (unpackCString# "922_bug.hs"#) (I# 11#) (I# 7#) (I# 11#) (I# 16#)) ($dIP_a2BP `cast` (N:IP[0] <"callStack">_N <CallStack>_N :: (?callStack::CallStack) ~R# CallStack))) `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N) :: CallStack ~R# (?callStack::CallStack)) } in break<0>() undefined @ 'LiftedRep @ (f_a1yV a_a1zd) $dIP_a2Bz; } in break<1>() undefined @ 'LiftedRep @ w_a1yN $dIP_a2BD; } in top_a1yW) @ Any @ Any @ w_a2BZ end Rec } *** End of Offense *** <no location info>: error: Compilation had errors *** Exception: ExitFailure 1
}}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16152 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16152: Core lint error from PartialTypeSignatures -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Resolution: | Keywords: | PartialTypeSignatures Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): The `where` clause can be removed completely {{{#!hs {-# Language PartialTypeSignatures #-} {-# Language PolyKinds #-} {-# Language ScopedTypeVariables #-} {-# Options_GHC -dcore-lint #-} top :: forall f. _ top = undefined }}} {{{ GHCi, version 8.7.20181230: https://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( 922_bug.hs, interpreted ) *** Core Lint errors : in result of Desugar (before optimization) *** <no location info>: warning: In the type ‘forall (f :: k_a1yM) w. w’ @ k_a1yM is out of scope *** Offending Program *** Rec { $trModule :: Module [LclIdX] $trModule = Module (TrNameS "main"#) (TrNameS "Main"#) top :: forall (f :: k_a1yM) w. w [LclIdX] top = \ (@ (f_a2Bz :: k_a1yM)) (@ w_a2BA) -> (\ (@ k_a1yM) (@ (f_a1yT :: k_a1yM)) (@ w_a1yL) -> let { $dIP_a2Bq :: ?callStack::CallStack [LclId] $dIP_a2Bq = emptyCallStack `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N) :: CallStack ~R# (?callStack::CallStack)) } in let { $dIP_a2Bf :: HasCallStack [LclId] $dIP_a2Bf = (pushCallStack (unpackCString# "undefined"#, SrcLoc (unpackCString# "main"#) (unpackCString# "Main"#) (unpackCString# "922_bug.hs"#) (I# 8#) (I# 7#) (I# 8#) (I# 16#)) ($dIP_a2Bq `cast` (N:IP[0] <"callStack">_N <CallStack>_N :: (?callStack::CallStack) ~R# CallStack))) `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N) :: CallStack ~R# (?callStack::CallStack)) } in letrec { top_a1yU :: w_a1yL [LclId] top_a1yU = break<0>() undefined @ 'LiftedRep @ w_a1yL $dIP_a2Bf; } in top_a1yU) @ Any @ Any @ w_a2BA end Rec } *** End of Offense *** <no location info>: error: Compilation had errors *** Exception: ExitFailure 1
}}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16152#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16152: Core lint error from PartialTypeSignatures -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Resolution: | Keywords: | PartialTypeSignatures Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The program in comment:1 has some strange interactions w.r.t. `MonoLocalBinds`. This program compiles: {{{#!hs {-# Language PartialTypeSignatures #-} {-# Language PolyKinds #-} {-# Language ScopedTypeVariables #-} {-# Language TypeApplications #-} import GHC.Exts top :: forall f. _ top = undefined f = top @Any }}} But if you compile it with `MonoLocalBinds`, then it doesn't: {{{ $ /opt/ghc/8.6.3/bin/ghci Bug.hs -XMonoLocalBinds GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:11:10: error: • Expected kind ‘k’, but ‘Any’ has kind ‘k00’ • In the type ‘Any’ In the expression: top @Any In an equation for ‘f’: f = top @Any | 11 | f = top @Any | ^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16152#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC