[GHC] #16152: Core lint error from PartialTypeSignatures

GHC ghc-devs at haskell.org
Tue Jan 8 19:37:04 UTC 2019


#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


More information about the ghc-tickets mailing list