[GHC] #11747: `Strict` causes core lint error

GHC ghc-devs at haskell.org
Wed Mar 23 15:09:13 UTC 2016


#11747: `Strict` causes core lint error
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
           Keywords:  Strict         |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{
 $ ghci -dcore-lint -XStrict -XGADTs -XRankNTypes -XTypeApplications
 -XScopedTypeVariables -ignore-dot-ghci
 GHCi, version 8.1.20160117: http://www.haskell.org/ghc/  :? for help
 Prelude> import Data.Typeable
 Prelude Data.Typeable> let zero :: forall x. Typeable x => Maybe x; zero =
 do Refl <- eqT @Int @x; pure 0
 Prelude Data.Typeable> zero
 *** Core Lint errors : in result of desugar expression ***
 <no location info>: warning:
     In the expression: ds_d1t9
                          @ x_a1sx $dTypeable_a1sC @ x_a1sx $dTypeable_a1sz
     $dTypeable_a1sz :: Typeable x_a1sx
     [LclId, Str=DmdType] is out of scope
 *** Offending Program ***
 let {
   $dTypeable_a1sS :: Typeable ()
   [LclId, Str=DmdType]
   $dTypeable_a1sS =
     D:Typeable
       @ *
       @ ()
       (let {
          ds_d1tb :: TypeRep
          [LclId, Str=DmdType]
          ds_d1tb = mkPolyTyConApp $tc() ([] @ TypeRep) ([] @ TypeRep) } in
        \ (wild_00 :: Proxy# ()) -> ds_d1tb) } in
 let {
   $dShow_a1sU :: Show ()
   [LclId, Str=DmdType]
   $dShow_a1sU = $fShow() } in
 let {
   $dShow_a1sP :: Show (Maybe ())
   [LclId, Str=DmdType]
   $dShow_a1sP = $fShowMaybe @ () $dShow_a1sU } in
 letrec {
   ds_d1t9
     :: forall x_a1sx.
        Typeable x_a1sx =>
        forall x_a11P. Typeable x_a11P => Maybe x_a11P
   [LclId, Str=DmdType]
   ds_d1t9 =
     \ (@ x_a1sx) ($dTypeable_a1sC :: Typeable x_a1sx) ->
       let {
         $dTypeable_a1sz :: Typeable x_a1sx
         [LclId, Str=DmdType]
         $dTypeable_a1sz = $dTypeable_a1sC } in
       letrec {
         it_a1sw :: forall x_a11P. Typeable x_a11P => Maybe x_a11P
         [LclId, Str=DmdType]
         it_a1sw = zero; } in
       it_a1sw;
   it_a1dz :: forall x_a1sx. Typeable x_a1sx => Maybe x_a1sx
   [LclId, Str=DmdType]
   it_a1dz =
     \ (@ x_a1sx) ($dTypeable_a1sC :: Typeable x_a1sx) ->
       ds_d1t9 @ x_a1sx $dTypeable_a1sC @ x_a1sx $dTypeable_a1sz; } in
 case it_a1dz of it_a1dz { __DEFAULT ->
 thenIO
   @ ()
   @ [()]
   (print @ (Maybe ()) $dShow_a1sP (it_a1dz @ () $dTypeable_a1sS))
   (returnIO
      @ [()]
      (: @ ()
         (unsafeCoerce#
            @ 'Lifted
            @ 'Lifted
            @ (forall x_a1sx. Typeable x_a1sx => Maybe x_a1sx)
            @ ()
            it_a1dz)
         ([] @ ())))
 }
 *** End of Offense ***


 <no location info>: error:
 Compilation had errors


 *** Exception: ExitFailure 1
 Prelude Data.Typeable>
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11747>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list