[GHC] #12987: Core lint error with levity polymorphism

GHC ghc-devs at haskell.org
Thu Dec 15 21:08:57 UTC 2016


#12987: Core lint error with levity polymorphism
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
  LevityPolymorphism                 |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{
 $ ghci -ignore-dot-ghci
 GHCi, version 8.0.1: http://www.haskell.org/ghc/  :? for help
 Prelude> import GHC.Types
 Prelude GHC.Types> :set -XTypeInType
 Prelude GHC.Types> class NUM (a :: TYPE rep) where add :: a -> a -> a
 Prelude GHC.Types>
 }}}

 works, but with `-dcore-lint` I get a core lint error

 {{{
 $ ghci -ignore-dot-ghci
 GHCi, version 8.0.1: http://www.haskell.org/ghc/  :? for help
 Prelude> import GHC.Types
 Prelude GHC.Types> :set -XTypeInType
 Prelude GHC.Types> :set -dcore-lint
 Prelude GHC.Types> class NUM (a :: TYPE rep) where add :: a -> a -> a
 *** Core Lint errors : in result of Tidy Core ***
 <no location info>: warning:
     In the type ‘forall a_a17Q.
                  NUM a_a17Q =>
                  a_a17Q -> a_a17Q -> a_a17Q’
     Ill-kinded argument in type or kind ‘a_a17Q -> a_a17Q’
     type or kind ‘a_a17Q -> a_a17Q’ kind: TYPE rep_a17P
 <no location info>: warning:
     In the type ‘forall a_a17Q.
                  NUM a_a17Q =>
                  a_a17Q -> a_a17Q -> a_a17Q’
     Ill-kinded argument in type or kind ‘a_a17Q -> a_a17Q -> a_a17Q’
     type or kind ‘a_a17Q -> a_a17Q -> a_a17Q’ kind: TYPE rep_a17P
 *** Offending Program ***
 add [InlPrag=INLINE]
   :: forall a_a17Q. NUM a_a17Q => a_a17Q -> a_a17Q -> a_a17Q
 [GblId[ClassOp],
  Arity=1,
  Caf=NoCafRefs,
  Str=DmdType <S,U>,
  Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=True)
          Tmpl= \ (@ (rep_a17P :: RuntimeRep))
                  (@ (a_a17Q :: TYPE rep_a17P))
                  (tpl_B1 [Occ=Once] :: NUM a_a17Q) ->
                  tpl_B1
                  `cast` (N:NUM[0] <rep_a17P>_N <a_a17Q>_N
                          :: (NUM a_a17Q :: Constraint)
                             ~R#
                             ((a_a17Q -> a_a17Q -> a_a17Q) :: *))}]
 add =
   \ (@ (rep_a17P :: RuntimeRep))
     (@ (a_a17Q :: TYPE rep_a17P))
     (tpl_B1 :: NUM a_a17Q) ->
     tpl_B1
     `cast` (N:NUM[0] <rep_a17P>_N <a_a17Q>_N
             :: (NUM a_a17Q :: Constraint)
                ~R#
                ((a_a17Q -> a_a17Q -> a_a17Q) :: *))

 $trModule1_r18t :: TrName
 [GblId, Caf=NoCafRefs, Str=DmdType]
 $trModule1_r18t = TrNameS "interactive"#

 $trModule2_r18D :: TrName
 [GblId, Caf=NoCafRefs, Str=DmdType]
 $trModule2_r18D = TrNameS "Ghci1"#

 $trModule :: Module
 [GblId, Caf=NoCafRefs, Str=DmdType]
 $trModule = Module $trModule1_r18t $trModule2_r18D

 $tc'C:NUM1_r18E :: TrName
 [GblId, Caf=NoCafRefs, Str=DmdType]
 $tc'C:NUM1_r18E = TrNameS "'C:NUM"#

 $tc'C:NUM :: TyCon
 [GblId, Caf=NoCafRefs, Str=DmdType]
 $tc'C:NUM =
   TyCon
     13508714812303496948##
     14031386194776682412##
     $trModule
     $tc'C:NUM1_r18E

 $tcNUM1_r18F :: TrName
 [GblId, Caf=NoCafRefs, Str=DmdType]
 $tcNUM1_r18F = TrNameS "NUM"#

 $tcNUM :: TyCon
 [GblId, Caf=NoCafRefs, Str=DmdType]
 $tcNUM =
   TyCon
     18330307158587089132##
     17437587248867430906##
     $trModule
     $tcNUM1_r18F

 *** End of Offense ***


 <no location info>: error:
 Compilation had errors


 *** Exception: ExitFailure 1
 }}}

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


More information about the ghc-tickets mailing list