[GHC] #11232: Panic whilst compiling syb due to OptCoercion

GHC ghc-devs at haskell.org
Tue Dec 15 17:22:40 UTC 2015


#11232: Panic whilst compiling syb due to OptCoercion
-------------------------------------+-------------------------------------
        Reporter:  mpickering        |                Owner:
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:
       Component:  Compiler          |              Version:  7.10.3
      Resolution:                    |             Keywords:
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 mpickering):

 In fact it fails core lint.

 {{{
 *** Core Lint errors : in result of Simplifier ***
 <no location info>: warning:
     In a case alternative: (True)
     Role incompatibility: expected representational, got nominal
     in UnsafeCo nominal b_a1me a_a1md
 *** Offending Program ***
 a_s1F4 :: TrName
 [LclId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 20}]
 a_s1F4 = TrNameS "main"#

 a_s1F5 :: TrName
 [LclId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 80 20}]
 a_s1F5 = TrNameS "Data.Generics.Aliases"#

 $trModule :: Module
 [LclIdX[ReflectionId],
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 $trModule = Module a_s1F4 a_s1F5

 a_s1F6 :: TrName
 [LclId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 20}]
 a_s1F6 = TrNameS "'M"#

 $tc'M :: TyCon
 [LclIdX[ReflectionId],
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 50}]
 $tc'M =
   TyCon 372692395467894104## 3145297546256518361## $trModule a_s1F6

 a_s1F7 :: TrName
 [LclId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 20}]
 a_s1F7 = TrNameS "M"#

 $tcM :: TyCon
 [LclIdX[ReflectionId],
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 50}]
 $tcM =
   TyCon 12760297783238653818## 4193448421405137177## $trModule a_s1F7

 a_s1F8
   :: forall (m_a1kx :: * -> *) x_a1ky.
      M m_a1kx x_a1ky -> M m_a1kx x_a1ky
 [LclId,
  Arity=1,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)}]
 a_s1F8 =
   \ (@ (m_a1kx :: * -> *)) (@ x_a1ky) (ds_d1nw :: M m_a1kx x_a1ky) ->
     ds_d1nw

 unM
   :: forall (m_a1gf :: * -> *) x_a1gg.
      M m_a1gf x_a1gg -> x_a1gg -> m_a1gf x_a1gg
 [LclIdX[[RecSel]],
  Arity=1,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}]
 unM =
   a_s1F8
   `cast` (forall (m_a1kx :: <* -> *>_N).
           forall (x_a1ky :: <*>_N).
           <M m_a1kx x_a1ky>_R -> NTCo:M[0] <m_a1kx>_R <x_a1ky>_N
           :: (forall (m_a1kx :: * -> *) x_a1ky.
               M m_a1kx x_a1ky -> M m_a1kx x_a1ky)
              ~R# (forall (m_a1kx :: * -> *) x_a1ky.
                   M m_a1kx x_a1ky -> x_a1ky -> m_a1kx x_a1ky))

 mkMp
   :: forall (m_a1gh :: * -> *) a_a1gi b_a1gj.
      (MonadPlus m_a1gh, Typeable a_a1gi, Typeable b_a1gj) =>
      (b_a1gj -> m_a1gh b_a1gj) -> a_a1gi -> m_a1gh a_a1gi
 [LclIdX,
  Arity=4,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [60 0 0 0] 146 120}]
 mkMp =
   \ (@ (m_a1mc :: * -> *))
     (@ a_a1md)
     (@ b_a1me)
     ($dMonadPlus_a1mf :: MonadPlus m_a1mc)
     ($dTypeable_a1mg :: Typeable a_a1md)
     ($dTypeable_a1mh :: Typeable b_a1me)
     (ext_a1jq :: b_a1me -> m_a1mc b_a1me) ->
     case ($dTypeable_a1mh
           `cast` (NTCo:Typeable[0] <*>_N <b_a1me>_N
                   :: Typeable b_a1me ~R# (Proxy# b_a1me -> TypeRep)))
            (proxy# @ * @ b_a1me)
     of _ [Occ=Dead]
     { TypeRep dt_a1ED dt1_a1EE ds2_a1EF ds3_a1EG ds4_a1EH ->
     case ($dTypeable_a1mg
           `cast` (NTCo:Typeable[0] <*>_N <a_a1md>_N
                   :: Typeable a_a1md ~R# (Proxy# a_a1md -> TypeRep)))
            (proxy# @ * @ a_a1md)
     of _ [Occ=Dead]
     { TypeRep dt2_a1EL dt3_a1EM ds5_a1EN ds6_a1EO ds7_a1EP ->
     case tagToEnum# @ Bool (eqWord# dt_a1ED dt2_a1EL) of _ [Occ=Dead] {
       False ->
         let {
           x_a1nN :: m_a1mc a_a1md
           [LclId,
            Str=DmdType,
            Unf=Unf{Src=<vanilla>, TopLvl=False, Value=False,
 ConLike=False,
                    WorkFree=False, Expandable=True, Guidance=IF_ARGS [] 20
 0}]
           x_a1nN = mzero @ m_a1mc $dMonadPlus_a1mf @ a_a1md } in
         \ _ [Occ=Dead] -> x_a1nN;
       True ->
         case tagToEnum# @ Bool (eqWord# dt1_a1EE dt3_a1EM)
         of _ [Occ=Dead] {
           False ->
             let {
               x_a1nN :: m_a1mc a_a1md
               [LclId,
                Str=DmdType,
                Unf=Unf{Src=<vanilla>, TopLvl=False, Value=False,
 ConLike=False,
                        WorkFree=False, Expandable=True, Guidance=IF_ARGS
 [] 20 0}]
               x_a1nN = mzero @ m_a1mc $dMonadPlus_a1mf @ a_a1md } in
             \ _ [Occ=Dead] -> x_a1nN;
           True ->
             ext_a1jq
             `cast` (UnsafeCo nominal b_a1me a_a1md
                     -> <m_a1mc>_R (UnsafeCo nominal b_a1me a_a1md)
                     :: (b_a1me -> m_a1mc b_a1me) ~R# (a_a1md -> m_a1mc
 a_a1md))
         }
     }
     }
     }

 *** End of Offense ***


 <no location info>: error:
 Compilation had errors

 }}}

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


More information about the ghc-tickets mailing list