<div dir="ltr">Thanks, Ben. That doesn't seem to have an effect on the error I'm getting but Simon suggested that a meeting would be a better way to discuss this modification and the problems we're having. I appreciate you taking the time to look at this.<div><br></div><div>- Shant</div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Wed, Apr 7, 2021 at 8:29 AM Ben Gamari <<a href="mailto:ben@smart-cactus.org">ben@smart-cactus.org</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">Shant Hairapetian <<a href="mailto:shanth2600@gmail.com" target="_blank">shanth2600@gmail.com</a>> writes:<br>
<br>
> Hi Ben,<br>
> Thanks for the reply<br>
><br>
>> Incidentally, the collapse of LiftedRep and UnliftedRep will happen in<br>
>> GHC 9.2 (turning into `BoxedRep :: Levity -> RuntimeRep`).<br>
><br>
> Yes I believe this change was accidentally merged a few months ago then<br>
> reverted? I will keep that in mind.<br>
><br>
It was briefly accidentally merged, then reverted, then re-applied. The<br>
final commit is 3e082f8ff5ea2f42c5e6430094683b26b5818fb8.<br>
<br>
>> Can you provide a program that your patch rejects, as well as<br>
>> the full error that is produced?<br>
><br>
> My error is in stage 1 in the building of the ghc-bignum library. I have<br>
> attached the full error as well as the patch itself.<br>
><br>
See below.<br>
<br>
> Thanks,<br>
> Shant<br>
><br>
><br>
><br>
> On Mon, Apr 5, 2021 at 7:41 PM Ben Gamari <<a href="mailto:ben@smart-cactus.org" target="_blank">ben@smart-cactus.org</a>> wrote:<br>
><br>
>> Shant Hairapetian <<a href="mailto:shanth2600@gmail.com" target="_blank">shanth2600@gmail.com</a>> writes:<br>
>><br>
>> > Hello,<br>
>> ><br>
>> > I’m a master’s student working on implementing the changes outlined in<br>
>> > “Kinds are Calling Conventions“ (<br>
>> > <a href="https://www.microsoft.com/en-us/research/uploads/prod/2020/03/kacc.pdf" rel="noreferrer" target="_blank">https://www.microsoft.com/en-us/research/uploads/prod/2020/03/kacc.pdf</a>).<br>
>> I<br>
>> > have been working directly with Paul Downen but have hit some roadblocks.<br>
>> ><br>
>> > To sum up the changes to the kind system, I am attempting to modify the<br>
>> > “TYPE” type constructor to accept, rather than just a RuntimeRep, a<br>
>> record<br>
>> > type (called RuntimeInfo) comprised of a RuntimeRep and a CallingConv<br>
>> > (calling convention). The calling convention has an “Eval” constructor<br>
>> > which accepts a levity (effectively moving the levity information from<br>
>> the<br>
>> > representation to the calling convention. LiftedRep and UnliftedRep would<br>
>> > also be collapsed into a single PtrRep constructor) and a “Call”<br>
>> > constructor (denoting the arity of primitive, extensional functions,<br>
>> > see: Making<br>
>> > a Faster Curry with Extensional Types<br>
>> > <<br>
>> <a href="https://www.microsoft.com/en-us/research/uploads/prod/2019/07/arity-haskell-symposium-2019.pdf" rel="noreferrer" target="_blank">https://www.microsoft.com/en-us/research/uploads/prod/2019/07/arity-haskell-symposium-2019.pdf</a><br>
>> >)<br>
>> > which accepts a list of RuntimeRep’s. I have created and wired-in the new<br>
>> > RuntimeInfo and CallingConv types in GHC.Builtin.Types, as well as the<br>
>> > corresponding primitive types in GHC.Builtin.Types.Prim and have modified<br>
>> > the “TYPE” constructor to accept a RuntimeInfo rather than a RuntimeRep.<br>
>> ><br>
>> Hi Shant,<br>
>><br>
>> It would be helpful to have a bit more information on the nature of your<br>
>> failure. Can you provide a program that your patch rejects, as well as<br>
>> the full error that is produced?<br>
>><br>
>> Incidentally, the collapse of LiftedRep and UnliftedRep will happen in<br>
>> GHC 9.2 (turning into `BoxedRep :: Levity -> RuntimeRep`).<br>
>><br>
>> Cheers,<br>
>><br>
>> - Ben<br>
>><br>
>><br>
><br>
> -- <br>
> Shant Hairapetian<br>
><br>
>     libraries/ghc-bignum/src/GHC/Num/WordArray.hs:78:22: error:<br>
>         • Couldn't match type: 'TupleRep ('[] @RuntimeRep)<br>
>                          with: 'RInfo ('TupleRep ('[] @RuntimeRep)) 'GHC.Types.ConvEval<br>
>           Expected: (# State# s, MutableWordArray# s #)<br>
>             Actual: (# State# s, MutableByteArray# s #)<br>
>         • In the expression: newByteArray# (wordsToBytes# sz) s<br>
>           In an equation for ‘newWordArray#’:<br>
>               newWordArray# sz s = newByteArray# (wordsToBytes# sz) s<br>
>        |<br>
>     78 | newWordArray# sz s = newByteArray# (wordsToBytes# sz) s<br>
>        |                      ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^<br>
><br>
>     libraries/ghc-bignum/src/GHC/Num/WordArray.hs:112:71: error:<br>
>         • Couldn't match a lifted type with an unlifted type<br>
>           When matching types<br>
>             b0 :: TYPE ('RInfo 'LiftedRep 'GHC.Types.ConvEval)<br>
>             WordArray# :: TYPE ('RInfo 'UnliftedRep 'GHC.Types.ConvEval)<br>
>           Expected: (# () | WordArray# #)<br>
>             Actual: (# () | b0 #)<br>
>         • In the expression: a<br>
>           In a case alternative: (# _, a #) -> a<br>
>           In the expression: case runRW# io of { (# _, a #) -> a }<br>
>         • Relevant bindings include<br>
>             a :: (# () | b0 #)<br>
>               (bound at libraries/ghc-bignum/src/GHC/Num/WordArray.hs:112:63)<br>
>         |<br>
>     112 | withNewWordArrayTrimedMaybe# sz act = case runRW# io of (# _, a #) -> a<br>
>         |                                                                       ^<br>
><br>
>     libraries/ghc-bignum/src/GHC/Num/WordArray.hs:117:40: error:<br>
>         • Couldn't match kind ‘RuntimeInfo’ with ‘RuntimeRep’<br>
>           When matching the kind of ‘'RInfo 'LiftedRep 'GHC.Types.ConvEval’<br>
>         • In the expression: ()<br>
>           In the expression: (# () | #)<br>
>           In the expression: (# s, (# () | #) #)<br>
>         |<br>
>     117 |                (# s, 0# #) -> (# s, (# () | #) #)<br>
>         |                                        ^^<br>
><br>
>     libraries/ghc-bignum/src/GHC/Num/WordArray.hs:120:48: error:<br>
>         • Couldn't match kind ‘RuntimeInfo’ with ‘RuntimeRep’<br>
>           When matching kinds<br>
>             'RInfo 'LiftedRep 'GHC.Types.ConvEval :: RuntimeInfo<br>
>             'RInfo 'UnliftedRep 'GHC.Types.ConvEval :: RuntimeInfo<br>
>         • In the expression: ba<br>
>           In the expression: (# | ba #)<br>
>           In the expression: (# s, (# | ba #) #)<br>
>         |<br>
>     120 |                      (# s, ba #) -> (# s, (# | ba #) #)<br>
>         |                                                ^^<br>
><br>
>     libraries/ghc-bignum/src/GHC/Num/WordArray.hs:431:31: error:<br>
>         • Couldn't match type: 'TupleRep ('[] @RuntimeRep)<br>
>                          with: 'RInfo ('TupleRep ('[] @RuntimeRep)) 'GHC.Types.ConvEval<br>
>           Expected: (# State# s, Word# #)<br>
>             Actual: (# State# s, Word# #)<br>
>         • In the expression: readWordArray# mwa i s2<br>
>           In a case alternative:<br>
>               (# s2, sz #)<br>
>                 | isTrue# (i >=# sz) -> (# s2, 0## #)<br>
>                 | isTrue# (i <# 0#) -> (# s2, 0## #)<br>
>                 | True -> readWordArray# mwa i s2<br>
>           In the expression:<br>
>             case mwaSize# mwa s of {<br>
>               (# s2, sz #)<br>
>                 | isTrue# (i >=# sz) -> (# s2, 0## #)<br>
>                 | isTrue# (i <# 0#) -> (# s2, 0## #)<br>
>                 | True -> readWordArray# mwa i s2 }<br>
>         |<br>
>     431 |       | True               -> readWordArray# mwa i s2<br>
>         |                               ^^^^^^^^^^^^^^^^^^^^^^^<br>
><br>
>     libraries/ghc-bignum/src/GHC/Num/WordArray.hs:434:12: error:<br>
>         • Couldn't match type: 'TupleRep ('[] @RuntimeRep)<br>
>                          with: 'RInfo ('TupleRep ('[] @RuntimeRep)) 'GHC.Types.ConvEval<br>
>           Expected: MutableWordArray# s<br>
>                     -> Int# -> State# s -> (# State# s, Word# #)<br>
>             Actual: MutableByteArray# s<br>
>                     -> Int# -> State# s -> (# State# s, Word# #)<br>
>         • In the expression: readWordArray#<br>
>           In an equation for ‘mwaRead#’: mwaRead# = readWordArray#<br>
>         |<br>
>     434 | mwaRead# = readWordArray#<br>
> diff --git a/compiler/GHC/Builtin/Names.hs b/compiler/GHC/Builtin/Names.hs<br>
> index cf0f72c50f..78c84147cb 100644<br>
> --- a/compiler/GHC/Builtin/Names.hs<br>
> +++ b/compiler/GHC/Builtin/Names.hs<br>
> @@ -1949,6 +1949,15 @@ unrestrictedFunTyConKey = mkPreludeTyConUnique 193<br>
>  multMulTyConKey :: Unique<br>
>  multMulTyConKey = mkPreludeTyConUnique 194<br>
>  <br>
> +-- CallingConv<br>
> +runtimeInfoTyConKey, runtimeInfoDataConKey, callingConvTyConKey,<br>
> +   convEvalDataConKey, convCallDataConKey :: Unique<br>
> +runtimeInfoTyConKey    = mkPreludeTyConUnique 195<br>
> +runtimeInfoDataConKey  = mkPreludeDataConUnique 196<br>
> +callingConvTyConKey    = mkPreludeTyConUnique 197<br>
> +convEvalDataConKey     = mkPreludeDataConUnique 198<br>
> +convCallDataConKey     = mkPreludeDataConUnique 199<br>
> +<br>
>  ---------------- Template Haskell -------------------<br>
>  --      <a href="http://GHC.Builtin.Names.TH" rel="noreferrer" target="_blank">GHC.Builtin.Names.TH</a>: USES TyConUniques 200-299<br>
>  -----------------------------------------------------<br>
> diff --git a/compiler/GHC/Builtin/Types.hs b/compiler/GHC/Builtin/Types.hs<br>
> index d06bc4a12b..1bb6a263c6 100644<br>
> --- a/compiler/GHC/Builtin/Types.hs<br>
> +++ b/compiler/GHC/Builtin/Types.hs<br>
> @@ -109,6 +109,7 @@ module GHC.Builtin.Types (<br>
>  <br>
>          -- * RuntimeRep and friends<br>
>          runtimeRepTyCon, vecCountTyCon, vecElemTyCon,<br>
> +        runtimeInfoTyCon, rInfo,<br>
>  <br>
>          runtimeRepTy, liftedRepTy, liftedRepDataCon, liftedRepDataConTyCon,<br>
>  <br>
> @@ -131,6 +132,9 @@ module GHC.Builtin.Types (<br>
>  <br>
>          doubleElemRepDataConTy,<br>
>  <br>
> +        runtimeInfoTy, runtimeInfoDataConTyCon, callingConvTy, liftedRepEvalTy,<br>
> +        convEvalDataConTy,<br>
> +<br>
>          -- * Multiplicity and friends<br>
>          multiplicityTyConName, oneDataConName, manyDataConName, multiplicityTy,<br>
>          multiplicityTyCon, oneDataCon, manyDataCon, oneDataConTy, manyDataConTy,<br>
> @@ -189,6 +193,7 @@ import GHC.Utils.Outputable<br>
>  import GHC.Utils.Misc<br>
>  import GHC.Utils.Panic<br>
>  <br>
> +import qualified GHC.Core.TyCo.Rep as TyCoRep (Type(TyConApp))<br>
>  import qualified Data.ByteString.Char8 as BS<br>
>  <br>
>  import Data.List        ( elemIndex )<br>
> @@ -266,6 +271,8 @@ wiredInTyCons = [ -- Units are not treated like other tuples, because they<br>
>                  , multiplicityTyCon<br>
>                  , naturalTyCon<br>
>                  , integerTyCon<br>
> +                , runtimeInfoTyCon<br>
> +                , callingConvTyCon<br>
>                  ]<br>
>  <br>
>  mkWiredInTyConName :: BuiltInSyntax -> Module -> FastString -> Unique -> TyCon -> Name<br>
> @@ -689,7 +696,7 @@ constraintKindTyCon :: TyCon<br>
>  constraintKindTyCon = pcTyCon constraintKindTyConName Nothing [] []<br>
>  <br>
>  liftedTypeKind, typeToTypeKind, constraintKind :: Kind<br>
> -liftedTypeKind   = tYPE liftedRepTy<br>
> +liftedTypeKind   = TyCoRep.TyConApp liftedTypeKindTyCon []<br>
>  typeToTypeKind   = liftedTypeKind `mkVisFunTyMany` liftedTypeKind<br>
>  constraintKind   = mkTyConApp constraintKindTyCon []<br>
>  <br>
> @@ -1027,7 +1034,7 @@ cTupleArr = listArray (0,mAX_CTUPLE_SIZE) [mk_ctuple i | i <- [0..mAX_CTUPLE_SIZ<br>
>  -- [IntRep, LiftedRep])@<br>
>  unboxedTupleSumKind :: TyCon -> [Type] -> Kind<br>
>  unboxedTupleSumKind tc rr_tys<br>
> -  = tYPE (mkTyConApp tc [mkPromotedListTy runtimeRepTy rr_tys])<br>
> +  = tYPE $ mkTyConApp runtimeInfoDataConTyCon [(mkTyConApp tc [mkPromotedListTy runtimeRepTy rr_tys]), convEvalDataConTy]<br>
>  <br>
>  -- | Specialization of 'unboxedTupleSumKind' for tuples<br>
>  unboxedTupleKind :: [Type] -> Kind<br>
> @@ -1064,7 +1071,7 @@ mk_tuple Unboxed arity = (tycon, tuple_con)<br>
>  <br>
>      -- See Note [Unboxed tuple RuntimeRep vars] in GHC.Core.TyCon<br>
>      -- Kind:  forall (k1:RuntimeRep) (k2:RuntimeRep). TYPE k1 -> TYPE k2 -> #<br>
> -    tc_binders = mkTemplateTyConBinders (replicate arity runtimeRepTy)<br>
> +    tc_binders = mkTemplateTyConBinders (replicate arity runtimeInfoTy)<br>
>                                          (\ks -> map tYPE ks)<br>
>  <br>
>      tc_res_kind = unboxedTupleKind rr_tys<br>
> @@ -1388,11 +1395,11 @@ unrestrictedFunTyCon :: TyCon<br>
>  unrestrictedFunTyCon = buildSynTyCon unrestrictedFunTyConName [] arrowKind [] unrestrictedFunTy<br>
>    where arrowKind = mkTyConKind binders liftedTypeKind<br>
>          -- See also funTyCon<br>
> -        binders = [ Bndr runtimeRep1TyVar (NamedTCB Inferred)<br>
> -                  , Bndr runtimeRep2TyVar (NamedTCB Inferred)<br>
> +        binders = [ Bndr runtimeInfo1TyVar (NamedTCB Inferred)<br>
> +                  , Bndr runtimeInfo2TyVar (NamedTCB Inferred)<br>
>                    ]<br>
> -                  ++ mkTemplateAnonTyConBinders [ tYPE runtimeRep1Ty<br>
> -                                                , tYPE runtimeRep2Ty<br>
> +                  ++ mkTemplateAnonTyConBinders [ tYPE runtimeInfo1Ty<br>
> +                                                , tYPE runtimeInfo2Ty<br>
>                                                  ]<br>
>  <br>
>  unrestrictedFunTyConName :: Name<br>
> @@ -1400,7 +1407,7 @@ unrestrictedFunTyConName = mkWiredInTyConName BuiltInSyntax gHC_TYPES (fsLit "-><br>
>  <br>
>  {- *********************************************************************<br>
>  *                                                                      *<br>
> -                Kinds and RuntimeRep<br>
> +                Kinds, RuntimeRep and CallingConv<br>
>  *                                                                      *<br>
>  ********************************************************************* -}<br>
>  <br>
> @@ -1413,8 +1420,8 @@ runtimeRepTy = mkTyConTy runtimeRepTyCon<br>
>  -- type Type = tYPE 'LiftedRep<br>
>  liftedTypeKindTyCon :: TyCon<br>
>  liftedTypeKindTyCon   = buildSynTyCon liftedTypeKindTyConName<br>
> -                                       [] liftedTypeKind []<br>
> -                                       (tYPE liftedRepTy)<br>
> +                                       [] liftedTypeKind [] rhs<br>
> +  where rhs = TyCoRep.TyConApp tYPETyCon [mkTyConApp  runtimeInfoDataConTyCon [liftedRepTy, convEvalDataConTy]]<br>
>  <br>
>  runtimeRepTyCon :: TyCon<br>
>  runtimeRepTyCon = pcTyCon runtimeRepTyConName Nothing []<br>
> @@ -1425,13 +1432,13 @@ vecRepDataCon :: DataCon<br>
>  vecRepDataCon = pcSpecialDataCon vecRepDataConName [ mkTyConTy vecCountTyCon<br>
>                                                     , mkTyConTy vecElemTyCon ]<br>
>                                   runtimeRepTyCon<br>
> -                                 (RuntimeRep prim_rep_fun)<br>
> +                                 (RuntimeInfo prim_rep_fun)<br>
>    where<br>
>      -- See Note [Getting from RuntimeRep to PrimRep] in GHC.Types.RepType<br>
>      prim_rep_fun [count, elem]<br>
>        | VecCount n <- tyConRuntimeRepInfo (tyConAppTyCon count)<br>
>        , VecElem  e <- tyConRuntimeRepInfo (tyConAppTyCon elem)<br>
> -      = [VecRep n e]<br>
> +      = [RInfo [(VecRep n e)] ConvEval]<br>
>      prim_rep_fun args<br>
>        = pprPanic "vecRepDataCon" (ppr args)<br>
>  <br>
> @@ -1440,11 +1447,11 @@ vecRepDataConTyCon = promoteDataCon vecRepDataCon<br>
>  <br>
>  tupleRepDataCon :: DataCon<br>
>  tupleRepDataCon = pcSpecialDataCon tupleRepDataConName [ mkListTy runtimeRepTy ]<br>
> -                                   runtimeRepTyCon (RuntimeRep prim_rep_fun)<br>
> +                                   runtimeRepTyCon (RuntimeInfo prim_rep_fun)<br>
>    where<br>
>      -- See Note [Getting from RuntimeRep to PrimRep] in GHC.Types.RepType<br>
>      prim_rep_fun [rr_ty_list]<br>
> -      = concatMap (runtimeRepPrimRep doc) rr_tys<br>
> +      = [RInfo (concatMap (runtimeRepPrimRep doc) rr_tys) ConvEval]<br>
>        where<br>
>          rr_tys = extractPromotedList rr_ty_list<br>
>          doc    = text "tupleRepDataCon" <+> ppr rr_tys<br>
> @@ -1456,11 +1463,11 @@ tupleRepDataConTyCon = promoteDataCon tupleRepDataCon<br>
>  <br>
>  sumRepDataCon :: DataCon<br>
>  sumRepDataCon = pcSpecialDataCon sumRepDataConName [ mkListTy runtimeRepTy ]<br>
> -                                 runtimeRepTyCon (RuntimeRep prim_rep_fun)<br>
> +                                 runtimeRepTyCon (RuntimeInfo prim_rep_fun)<br>
>    where<br>
>      -- See Note [Getting from RuntimeRep to PrimRep] in GHC.Types.RepType<br>
>      prim_rep_fun [rr_ty_list]<br>
> -      = map slotPrimRep (ubxSumRepType prim_repss)<br>
> +      = [RInfo (map slotPrimRep (ubxSumRepType prim_repss)) ConvEval]<br>
>        where<br>
>          rr_tys     = extractPromotedList rr_ty_list<br>
>          doc        = text "sumRepDataCon" <+> ppr rr_tys<br>
> @@ -1488,7 +1495,7 @@ runtimeRepSimpleDataCons@(liftedRepDataCon : _)<br>
>      runtimeRepSimpleDataConNames<br>
>    where<br>
>      mk_runtime_rep_dc primrep name<br>
> -      = pcSpecialDataCon name [] runtimeRepTyCon (RuntimeRep (\_ -> [primrep]))<br>
> +      = pcSpecialDataCon name [] runtimeRepTyCon (RuntimeInfo (\_ -> [RInfo [primrep] ConvEval]))<br>
>  <br>
>  -- See Note [Wiring in RuntimeRep]<br>
>  liftedRepDataConTy, unliftedRepDataConTy,<br>
> @@ -1558,6 +1565,79 @@ liftedRepDataConTyCon = promoteDataCon liftedRepDataCon<br>
>  liftedRepTy :: Type<br>
>  liftedRepTy = liftedRepDataConTy<br>
>  <br>
> +-- The type ('BoxedRep 'UnliftedRep)<br>
> +unliftedRepTy :: Type<br>
> +unliftedRepTy = unliftedRepDataConTy<br>
> +<br>
> +unliftedRepEvalTy :: Type<br>
> +unliftedRepEvalTy = mkTyConApp runtimeInfoDataConTyCon [unliftedRepTy, convEvalDataConTy]<br>
> +<br>
> +liftedRepEvalTy :: Type<br>
> +liftedRepEvalTy = mkTyConApp runtimeInfoDataConTyCon [liftedRepTy, convEvalDataConTy]<br>
> +<br>
> +callingConvTyConName, convEvalDataConName, convCallDataConName :: Name<br>
> +callingConvTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "CallingConv") callingConvTyConKey callingConvTyCon<br>
> +convEvalDataConName  = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "ConvEval") convEvalDataConKey convEvalDataCon<br>
> +-- convCallDataConName  = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "ConvCall") convCallDataConKey convCallDataCon<br>
> +convCallDataConName = undefined<br>
> +<br>
> +convEvalDataCon = pcSpecialDataCon convEvalDataConName [] callingConvTyCon (CallingConvInfo $ \_ -> [ConvEval])<br>
> +<br>
> +convEvalDataConTyCon :: TyCon<br>
> +convEvalDataConTyCon = promoteDataCon convEvalDataCon<br>
> +<br>
> +convEvalDataConTy :: Type<br>
> +convEvalDataConTy = mkTyConTy convEvalDataConTyCon<br>
> +<br>
> +<br>
> +callingConvTyCon :: TyCon<br>
> +callingConvTyCon = pcTyCon callingConvTyConName Nothing []<br>
> +    [convEvalDataCon]<br>
> +<br>
> +callingConvTy :: Type<br>
> +callingConvTy = mkTyConTy callingConvTyCon <br>
> +<br>
> +{- *********************************************************************<br>
> +*                                                                      *<br>
> +     RuntimeInfo Types<br>
> +*                                                                      *<br>
> +********************************************************************* -}<br>
> +<br>
> +runtimeInfoTyConName, runtimeInfoDataConName :: Name<br>
> +runtimeInfoTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "RuntimeInfo") runtimeInfoTyConKey runtimeInfoTyCon<br>
> +runtimeInfoDataConName = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "RInfo") runtimeInfoDataConKey runtimeInfoDataCon<br>
> +<br>
> +runtimeInfoTyCon :: TyCon<br>
> +runtimeInfoTyCon = pcTyCon runtimeInfoTyConName Nothing []<br>
> +    [runtimeInfoDataCon]<br>
> +<br>
> +runtimeInfoDataCon :: DataCon<br>
> +runtimeInfoDataCon = pcSpecialDataCon runtimeInfoDataConName [ runtimeRepTy<br>
> +                                                   , mkTyConTy callingConvTyCon ]<br>
> +                                 runtimeInfoTyCon<br>
> +                                 (RuntimeInfo prim_info_fun)<br>
> +  where<br>
> +    -- See Note [Getting from RuntimeRep to PrimRep] in GHC.Types.RepType<br>
> +    prim_info_fun tys@[rep, conv]<br>
> +      = pprPanic "here runtimeInfoDataCon" (ppr tys)<br>
> +        -- [RInfo (runtimeRepPrimRep doc rep)  ConvEval]<br>
> +        where doc = text "runtimeInfoDataCon" <+> ppr tys<br>
> +    prim_info_fun args<br>
> +      = pprPanic "runtimeInfoDataCon" (ppr args)<br>
> +<br>
> +runtimeInfoDataConTyCon :: TyCon<br>
> +runtimeInfoDataConTyCon = promoteDataCon runtimeInfoDataCon<br>
> +<br>
> +runtimeInfoDataConTy :: Type<br>
> +runtimeInfoDataConTy = mkTyConTy runtimeInfoDataConTyCon<br>
> +<br>
> +runtimeInfoTy :: Type<br>
> +runtimeInfoTy = mkTyConTy runtimeInfoTyCon<br>
> +<br>
> +rInfo :: Type -> Type -> Type<br>
> +rInfo rep conv = TyCoRep.TyConApp runtimeInfoTyCon [rep, conv]<br>
> +<br>
> +<br>
>  {- *********************************************************************<br>
>  *                                                                      *<br>
>       The boxed primitive types: Char, Int, etc<br>
> diff --git a/compiler/GHC/Builtin/Types.hs-boot b/compiler/GHC/Builtin/Types.hs-boot<br>
> index 000df212c3..fc82f9d7b9 100644<br>
> --- a/compiler/GHC/Builtin/Types.hs-boot<br>
> +++ b/compiler/GHC/Builtin/Types.hs-boot<br>
> @@ -23,6 +23,13 @@ constraintKind :: Kind<br>
>  runtimeRepTyCon, vecCountTyCon, vecElemTyCon :: TyCon<br>
>  runtimeRepTy :: Type<br>
>  <br>
> +<br>
> +runtimeInfoTy, callingConvTy, convEvalDataConTy :: Type<br>
> +<br>
> +runtimeInfoTyCon, runtimeInfoDataConTyCon :: TyCon<br>
> +<br>
> +rInfo :: Type -> Type -> Type<br>
> +<br>
>  liftedRepDataConTyCon, vecRepDataConTyCon, tupleRepDataConTyCon :: TyCon<br>
>  <br>
>  liftedRepDataConTy, unliftedRepDataConTy,<br>
> diff --git a/compiler/GHC/Builtin/Types/Prim.hs b/compiler/GHC/Builtin/Types/Prim.hs<br>
> index fc74596e45..5fb750649c 100644<br>
> --- a/compiler/GHC/Builtin/Types/Prim.hs<br>
> +++ b/compiler/GHC/Builtin/Types/Prim.hs<br>
> @@ -24,6 +24,7 @@ module GHC.Builtin.Types.Prim(<br>
>          alphaTyVarsUnliftedRep, alphaTyVarUnliftedRep,<br>
>          alphaTysUnliftedRep, alphaTyUnliftedRep,<br>
>          runtimeRep1TyVar, runtimeRep2TyVar, runtimeRep1Ty, runtimeRep2Ty,<br>
> +        runtimeInfo1TyVar, runtimeInfo2TyVar, runtimeInfo1Ty, runtimeInfo2Ty,<br>
>          openAlphaTy, openBetaTy, openAlphaTyVar, openBetaTyVar,<br>
>  <br>
>          multiplicityTyVar,<br>
> @@ -97,6 +98,7 @@ import GHC.Prelude<br>
>  <br>
>  import {-# SOURCE #-} GHC.Builtin.Types<br>
>    ( runtimeRepTy, unboxedTupleKind, liftedTypeKind<br>
> +  , runtimeInfoTy, runtimeInfoDataConTyCon, convEvalDataConTy<br>
>    , vecRepDataConTyCon, tupleRepDataConTyCon<br>
>    , liftedRepDataConTy, unliftedRepDataConTy<br>
>    , intRepDataConTy<br>
> @@ -382,11 +384,19 @@ runtimeRep1Ty, runtimeRep2Ty :: Type<br>
>  runtimeRep1Ty = mkTyVarTy runtimeRep1TyVar<br>
>  runtimeRep2Ty = mkTyVarTy runtimeRep2TyVar<br>
>  <br>
> +runtimeInfo1TyVar, runtimeInfo2TyVar :: TyVar<br>
> +(runtimeInfo1TyVar : runtimeInfo2TyVar : _)<br>
> +  = drop 16 (mkTemplateTyVars (repeat runtimeInfoTy))  -- selects 'q','r'  <br>
> +<br>
> +runtimeInfo1Ty, runtimeInfo2Ty :: Type<br>
> +runtimeInfo1Ty = mkTyVarTy runtimeInfo1TyVar<br>
> +runtimeInfo2Ty = mkTyVarTy runtimeInfo2TyVar<br>
> +<br>
>  openAlphaTyVar, openBetaTyVar :: TyVar<br>
>  -- alpha :: TYPE r1<br>
>  -- beta  :: TYPE r2<br>
>  [openAlphaTyVar,openBetaTyVar]<br>
> -  = mkTemplateTyVars [tYPE runtimeRep1Ty, tYPE runtimeRep2Ty]<br>
> +  = mkTemplateTyVars [tYPE runtimeInfo1Ty, tYPE runtimeInfo2Ty]<br>
>  <br>
>  openAlphaTy, openBetaTy :: Type<br>
>  openAlphaTy = mkTyVarTy openAlphaTyVar<br>
> @@ -432,10 +442,10 @@ funTyCon = mkFunTyCon funTyConName tc_bndrs tc_rep_nm<br>
>    where<br>
>      -- See also unrestrictedFunTyCon<br>
>      tc_bndrs = [ mkNamedTyConBinder Required multiplicityTyVar<br>
> -               , mkNamedTyConBinder Inferred runtimeRep1TyVar<br>
> -               , mkNamedTyConBinder Inferred runtimeRep2TyVar ]<br>
> -               ++ mkTemplateAnonTyConBinders [ tYPE runtimeRep1Ty<br>
> -                                             , tYPE runtimeRep2Ty<br>
> +               , mkNamedTyConBinder Inferred runtimeInfo1TyVar<br>
> +               , mkNamedTyConBinder Inferred runtimeInfo2TyVar ]<br>
> +               ++ mkTemplateAnonTyConBinders [ tYPE runtimeInfo1Ty<br>
> +                                             , tYPE runtimeInfo2Ty<br>
>                                               ]<br>
>      tc_rep_nm = mkPrelTyConRepName funTyConName<br>
>  <br>
> @@ -529,7 +539,7 @@ tYPETyCon :: TyCon<br>
>  tYPETyConName :: Name<br>
>  <br>
>  tYPETyCon = mkKindTyCon tYPETyConName<br>
> -                        (mkTemplateAnonTyConBinders [runtimeRepTy])<br>
> +                        (mkTemplateAnonTyConBinders [runtimeInfoTy])<br>
>                          liftedTypeKind<br>
>                          [Nominal]<br>
>                          (mkPrelTyConRepName tYPETyConName)<br>
> @@ -574,7 +584,7 @@ pcPrimTyCon name roles rep<br>
>    = mkPrimTyCon name binders result_kind roles<br>
>    where<br>
>      binders     = mkTemplateAnonTyConBinders (map (const liftedTypeKind) roles)<br>
> -    result_kind = tYPE (primRepToRuntimeRep rep)<br>
> +    result_kind = tYPE $ TyConApp runtimeInfoDataConTyCon [(primRepToRuntimeRep rep), convEvalDataConTy]<br>
>  <br>
>  -- | Convert a 'PrimRep' to a 'Type' of kind RuntimeRep<br>
>  -- Defined here to avoid (more) module loops<br>
> diff --git a/compiler/GHC/Core/Make.hs b/compiler/GHC/Core/Make.hs<br>
> index 6d6dd38b29..da285a6455 100644<br>
> --- a/compiler/GHC/Core/Make.hs<br>
> +++ b/compiler/GHC/Core/Make.hs<br>
> @@ -913,7 +913,7 @@ mkRuntimeErrorId name<br>
>  runtimeErrorTy :: Type<br>
>  -- forall (rr :: RuntimeRep) (a :: rr). Addr# -> a<br>
>  --   See Note [Error and friends have an "open-tyvar" forall]<br>
> -runtimeErrorTy = mkSpecForAllTys [runtimeRep1TyVar, openAlphaTyVar]<br>
> +runtimeErrorTy = mkSpecForAllTys [runtimeInfo1TyVar, openAlphaTyVar]<br>
>                                   (mkVisFunTyMany addrPrimTy openAlphaTy)<br>
>  <br>
>  {- Note [Error and friends have an "open-tyvar" forall]<br>
> diff --git a/compiler/GHC/Core/TyCon.hs b/compiler/GHC/Core/TyCon.hs<br>
> index 198b66959b..5c59548ebf 100644<br>
> --- a/compiler/GHC/Core/TyCon.hs<br>
> +++ b/compiler/GHC/Core/TyCon.hs<br>
> @@ -120,6 +120,7 @@ module GHC.Core.TyCon(<br>
>  <br>
>          -- * Primitive representations of Types<br>
>          PrimRep(..), PrimElemRep(..),<br>
> +        PrimConv (..), PrimInfo (..),<br>
>          isVoidRep, isGcPtrRep,<br>
>          primRepSizeB,<br>
>          primElemRepSizeB,<br>
> @@ -172,6 +173,10 @@ import GHC.Unit.Module<br>
>  <br>
>  import qualified Data.Data as Data<br>
>  <br>
> +import {-# SOURCE #-} GHC.Core.Type (splitTyConApp_maybe)<br>
> +-- import {-# SOURCE #-} GHC.Builtin.Types.Prim (mutableByteArrayPrimTyConKey)<br>
> +import GHC.Builtin.Names<br>
> +<br>
>  {-<br>
>  -----------------------------------------------<br>
>          Notes about type families<br>
> @@ -1073,6 +1078,8 @@ data RuntimeRepInfo<br>
>        -- be the list of arguments to the promoted datacon.<br>
>    | VecCount Int         -- ^ A constructor of @VecCount@<br>
>    | VecElem PrimElemRep  -- ^ A constructor of @VecElem@<br>
> +  | RuntimeInfo ([Type] -> [PrimInfo])<br>
> +  | CallingConvInfo ([Type] -> [PrimConv])<br>
>  <br>
>  -- | Extract those 'DataCon's that we are able to learn about.  Note<br>
>  -- that visibility in this sense does not correspond to visibility in<br>
> @@ -1550,6 +1557,26 @@ primRepIsFloat  DoubleRep    = Just True<br>
>  primRepIsFloat  (VecRep _ _) = Nothing<br>
>  primRepIsFloat  _            = Just False<br>
>  <br>
> +{-<br>
> +************************************************************************<br>
> +*                                                                      *<br>
> +                             PrimConv<br>
> +*                                                                      *<br>
> +************************************************************************<br>
> +<br>
> +Note [PrimConv]<br>
> +<br>
> +A type for representing the calling convention of a type. Either the arity<br>
> +for extensional functions or the levity for data terms.<br>
> +-}<br>
> +<br>
> +data PrimConv =  <br>
> +    ConvEval <br>
> +  -- | ConvCall [PrimRep] <br>
> +  deriving (Show)<br>
> +<br>
> +data PrimInfo = RInfo {reps :: [PrimRep], conv :: PrimConv}  <br>
> +<br>
>  <br>
>  {-<br>
>  ************************************************************************<br>
> @@ -2326,11 +2353,17 @@ expandSynTyCon_maybe<br>
>  <br>
>  -- ^ Expand a type synonym application, if any<br>
>  expandSynTyCon_maybe tc tys<br>
> +  -- | SynonymTyCon { tyConTyVars = tvs, synTcRhs = rhs, tyConArity = arity } <- tc<br>
> +  -- , Just (tc' , _) <- splitTyConApp_maybe rhs<br>
> +  -- , tc' `hasKey` (mutableByteArrayPrimTyConKey)<br>
> +  -- = pprPanic "here" (ppr tc)<br>
> +  <br>
>    | SynonymTyCon { tyConTyVars = tvs, synTcRhs = rhs, tyConArity = arity } <- tc<br>
>    = case tys `listLengthCmp` arity of<br>
>          GT -> Just (tvs `zip` tys, rhs, drop arity tys)<br>
>          EQ -> Just (tvs `zip` tys, rhs, [])<br>
>          LT -> Nothing<br>
> +  <br>
>    | otherwise<br>
>    = Nothing<br>
>  <br>
> diff --git a/compiler/GHC/Core/Type.hs b/compiler/GHC/Core/Type.hs<br>
> index 3164e2626b..5f3ab18925 100644<br>
> --- a/compiler/GHC/Core/Type.hs<br>
> +++ b/compiler/GHC/Core/Type.hs<br>
> @@ -68,6 +68,7 @@ module GHC.Core.Type (<br>
>          isPredTy,<br>
>  <br>
>          getRuntimeRep_maybe, kindRep_maybe, kindRep,<br>
> +        getRuntimeInfo, getRuntimeInfo_maybe, kindInfo,<br>
>  <br>
>          mkCastTy, mkCoercionTy, splitCastTy_maybe,<br>
>  <br>
> @@ -125,6 +126,7 @@ module GHC.Core.Type (<br>
>          isAlgType, isDataFamilyAppType,<br>
>          isPrimitiveType, isStrictType,<br>
>          isRuntimeRepTy, isRuntimeRepVar, isRuntimeRepKindedTy,<br>
> +        isRuntimeInfoTy, isRuntimeInfoVar,<br>
>          dropRuntimeRepArgs,<br>
>          getRuntimeRep,<br>
>  <br>
> @@ -554,6 +556,11 @@ kindRep k = case kindRep_maybe k of<br>
>                Just r  -> r<br>
>                Nothing -> pprPanic "kindRep" (ppr k)<br>
>  <br>
> +kindInfo :: HasDebugCallStack => Kind -> Type<br>
> +kindInfo k = case kindInfo_maybe k of<br>
> +              Just r  -> r<br>
> +              Nothing -> pprPanic "kindInfo" (ppr k)              <br>
> +<br>
>  -- | Given a kind (TYPE rr), extract its RuntimeRep classifier rr.<br>
>  -- For example, @kindRep_maybe * = Just LiftedRep@<br>
>  -- Returns 'Nothing' if the kind is not of form (TYPE rr)<br>
> @@ -561,18 +568,33 @@ kindRep k = case kindRep_maybe k of<br>
>  kindRep_maybe :: HasDebugCallStack => Kind -> Maybe Type<br>
>  kindRep_maybe kind<br>
>    | TyConApp tc [arg] <- coreFullView kind<br>
> -  , tc `hasKey` tYPETyConKey    = Just arg<br>
> -  | otherwise                   = Nothing<br>
> +  , tc `hasKey` tYPETyConKey<br>
> +  , TyConApp rinfo [rep, conv] <- coreFullView arg<br>
> +  , rinfo `hasKey` runtimeInfoDataConKey    = Just rep<br>
> +  | TyConApp tc [arg] <- coreFullView kind<br>
> +  , tc `hasKey` tYPETyConKey                = Just arg<br>
> +  | otherwise                               = Nothing<br>
> +<br>
> +kindInfo_maybe :: HasDebugCallStack => Kind -> Maybe Type<br>
> +kindInfo_maybe kind<br>
> +  | TyConApp tc [arg] <- coreFullView kind<br>
> +  , tc `hasKey` tYPETyConKey<br>
> +  , TyConApp rinfo [rep, conv] <- coreFullView arg<br>
> +  , rinfo `hasKey` runtimeInfoDataConKey    = Just arg<br>
> +  | TyConApp tc [arg] <- coreFullView kind<br>
> +  , tc `hasKey` tYPETyConKey                = Just arg<br>
> +  | otherwise                               = Nothing<br>
>  <br>
>  -- | This version considers Constraint to be the same as *. Returns True<br>
>  -- if the argument is equivalent to Type/Constraint and False otherwise.<br>
>  -- See Note [Kind Constraint and kind Type]<br>
>  isLiftedTypeKind :: Kind -> Bool<br>
>  isLiftedTypeKind kind<br>
> -  = case kindRep_maybe kind of<br>
> -      Just rep -> isLiftedRuntimeRep rep<br>
> +  = case kindInfo_maybe kind of<br>
> +      Just rinfo -> isLiftedRuntimeInfo rinfo<br>
>        Nothing  -> False<br>
>  <br>
> +<br>
>  pickyIsLiftedTypeKind :: Kind -> Bool<br>
>  -- Checks whether the kind is literally<br>
>  --      TYPE LiftedRep<br>
> @@ -599,13 +621,23 @@ isLiftedRuntimeRep rep<br>
>    , rr_tc `hasKey` liftedRepDataConKey = ASSERT( null args ) True<br>
>    | otherwise                          = False<br>
>  <br>
> +isLiftedRuntimeInfo :: Type -> Bool<br>
> +-- isLiftedRuntimeRep is true of LiftedRep :: RuntimeRep<br>
> +-- False of type variables (a :: RuntimeRep)<br>
> +--   and of other reps e.g. (IntRep :: RuntimeRep)<br>
> +isLiftedRuntimeInfo rep<br>
> +  | TyConApp rr_tc [rep,conv] <- coreFullView rep<br>
> +  , rr_tc `hasKey` runtimeInfoDataConKey = isLiftedRuntimeRep rep<br>
> +  | otherwise<br>
> +  = False<br>
> +<br>
>  -- | Returns True if the kind classifies unlifted types and False otherwise.<br>
>  -- Note that this returns False for levity-polymorphic kinds, which may<br>
>  -- be specialized to a kind that classifies unlifted types.<br>
>  isUnliftedTypeKind :: Kind -> Bool<br>
>  isUnliftedTypeKind kind<br>
> -  = case kindRep_maybe kind of<br>
> -      Just rep -> isUnliftedRuntimeRep rep<br>
> +  = case kindInfo_maybe kind of<br>
> +      Just rep -> isUnliftedRuntimeInfo rep<br>
>        Nothing  -> False<br>
>  <br>
>  isUnliftedRuntimeRep :: Type -> Bool<br>
> @@ -622,6 +654,17 @@ isUnliftedRuntimeRep rep<br>
>    | otherwise {- Variables, applications -}<br>
>    = False<br>
>  <br>
> +isUnliftedRuntimeInfo rep<br>
> +  | TyConApp rinfo [rep, conv] <- coreFullView rep   -- NB: args might be non-empty<br>
> +  , rinfo `hasKey` runtimeInfoDataConKey<br>
> +  = isUnliftedRuntimeRep rep<br>
> +        -- Avoid searching all the unlifted RuntimeRep type cons<br>
> +        -- In the RuntimeRep data type, only LiftedRep is lifted<br>
> +        -- But be careful of type families (F tys) :: RuntimeRep<br>
> +  | otherwise {- Variables, applications -}<br>
> +  = False<br>
> +<br>
> +<br>
>  -- | Is this the type 'RuntimeRep'?<br>
>  isRuntimeRepTy :: Type -> Bool<br>
>  isRuntimeRepTy ty<br>
> @@ -644,6 +687,17 @@ isMultiplicityTy ty<br>
>  isMultiplicityVar :: TyVar -> Bool<br>
>  isMultiplicityVar = isMultiplicityTy . tyVarKind<br>
>  <br>
> +-- | Is this the type 'RuntimeInfo'?<br>
> +isRuntimeInfoTy :: Type -> Bool<br>
> +isRuntimeInfoTy ty<br>
> +  | TyConApp tc args <- coreFullView ty<br>
> +  , tc `hasKey` runtimeInfoTyConKey = True<br>
> +  | otherwise = False<br>
> +<br>
> +-- | Is a tyvar of type 'RuntimeInfo'?<br>
> +isRuntimeInfoVar :: TyVar -> Bool<br>
> +isRuntimeInfoVar = isRuntimeInfoTy . tyVarKind<br>
> +<br>
>  {- *********************************************************************<br>
>  *                                                                      *<br>
>                 mapType<br>
> @@ -927,8 +981,8 @@ repSplitAppTy_maybe :: HasDebugCallStack => Type -> Maybe (Type,Type)<br>
>  repSplitAppTy_maybe (FunTy _ w ty1 ty2)<br>
>    = Just (TyConApp funTyCon [w, rep1, rep2, ty1], ty2)<br>
>    where<br>
> -    rep1 = getRuntimeRep ty1<br>
> -    rep2 = getRuntimeRep ty2<br>
> +    rep1 = getRuntimeInfo ty1<br>
> +    rep2 = getRuntimeInfo ty2<br>
>  <br>
>  repSplitAppTy_maybe (AppTy ty1 ty2)<br>
>    = Just (ty1, ty2)<br>
> @@ -2049,6 +2103,10 @@ getRuntimeRep_maybe :: HasDebugCallStack<br>
>                      => Type -> Maybe Type<br>
>  getRuntimeRep_maybe = kindRep_maybe . typeKind<br>
>  <br>
> +getRuntimeInfo_maybe :: HasDebugCallStack<br>
> +                    => Type -> Maybe Type<br>
> +getRuntimeInfo_maybe = kindInfo_maybe . typeKind<br>
> +<br>
>  -- | Extract the RuntimeRep classifier of a type. For instance,<br>
>  -- @getRuntimeRep_maybe Int = LiftedRep@. Panics if this is not possible.<br>
>  getRuntimeRep :: HasDebugCallStack => Type -> Type<br>
> @@ -2057,6 +2115,12 @@ getRuntimeRep ty<br>
>        Just r  -> r<br>
>        Nothing -> pprPanic "getRuntimeRep" (ppr ty <+> dcolon <+> ppr (typeKind ty))<br>
>  <br>
> +getRuntimeInfo :: HasDebugCallStack => Type -> Type<br>
> +getRuntimeInfo ty<br>
> +  = case getRuntimeInfo_maybe ty of<br>
> +      Just r  -> r<br>
> +      Nothing -> pprPanic "getRuntimeInfo" (ppr ty <+> dcolon <+> ppr (typeKind ty))      <br>
> +<br>
>  isUnboxedTupleType :: Type -> Bool<br>
>  isUnboxedTupleType ty<br>
>    = tyConAppTyCon (getRuntimeRep ty) `hasKey` tupleRepDataConKey<br>
> @@ -2584,7 +2648,9 @@ tcIsLiftedTypeKind :: Kind -> Bool<br>
>  tcIsLiftedTypeKind ty<br>
>    | Just (tc, [arg]) <- tcSplitTyConApp_maybe ty    -- Note: tcSplit here<br>
>    , tc `hasKey` tYPETyConKey<br>
> -  = isLiftedRuntimeRep arg<br>
> +  , Just (rinfo, [rep, conv]) <- tcSplitTyConApp_maybe arg<br>
> +  , rinfo `hasKey` runtimeInfoDataConKey<br>
> +  = isLiftedRuntimeRep rep<br>
>    | otherwise<br>
>    = False<br>
>  <br>
> diff --git a/compiler/GHC/HsToCore.hs b/compiler/GHC/HsToCore.hs<br>
> index 9cf33aa02a..3522ad6fab 100644<br>
> --- a/compiler/GHC/HsToCore.hs<br>
> +++ b/compiler/GHC/HsToCore.hs<br>
> @@ -714,7 +714,7 @@ mkUnsafeCoercePrimPair _old_id old_expr<br>
>  <br>
>         ; let [unsafe_refl_data_con] = tyConDataCons unsafe_equality_tc<br>
>  <br>
> -             rhs = mkLams [ runtimeRep1TyVar, runtimeRep2TyVar<br>
> +             rhs = mkLams [ runtimeInfo1TyVar, runtimeInfo2TyVar<br>
>                            , openAlphaTyVar, openBetaTyVar<br>
>                            , x ] $<br>
>                     mkSingleAltCase scrut1<br>
> @@ -742,10 +742,10 @@ mkUnsafeCoercePrimPair _old_id old_expr<br>
>               -- NB: UnsafeRefl :: (b ~# a) -> UnsafeEquality a b, so we have to<br>
>               -- carefully swap the arguments above<br>
>  <br>
> -             (scrut1, scrut1_ty, rr_cv_ty) = unsafe_equality runtimeRepTy<br>
> -                                                             runtimeRep1Ty<br>
> -                                                             runtimeRep2Ty<br>
> -             (scrut2, scrut2_ty, ab_cv_ty) = unsafe_equality (tYPE runtimeRep2Ty)<br>
> +             (scrut1, scrut1_ty, rr_cv_ty) = unsafe_equality runtimeInfoTy<br>
> +                                                             runtimeInfo1Ty<br>
> +                                                             runtimeInfo2Ty<br>
> +             (scrut2, scrut2_ty, ab_cv_ty) = unsafe_equality (tYPE runtimeInfo2Ty)<br>
>                                                               (openAlphaTy `mkCastTy` alpha_co)<br>
>                                                               openBetaTy<br>
>  <br>
> @@ -761,7 +761,7 @@ mkUnsafeCoercePrimPair _old_id old_expr<br>
>               info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma<br>
>                                  `setUnfoldingInfo` mkCompulsoryUnfolding' rhs<br>
>  <br>
> -             ty = mkSpecForAllTys [ runtimeRep1TyVar, runtimeRep2TyVar<br>
> +             ty = mkSpecForAllTys [ runtimeInfo1TyVar, runtimeInfo2TyVar<br>
>                                    , openAlphaTyVar, openBetaTyVar ] $<br>
>                    mkVisFunTyMany openAlphaTy openBetaTy<br>
>  <br>
> diff --git a/compiler/GHC/HsToCore/Utils.hs b/compiler/GHC/HsToCore/Utils.hs<br>
> index 01085b3270..688d227a6e 100644<br>
> --- a/compiler/GHC/HsToCore/Utils.hs<br>
> +++ b/compiler/GHC/HsToCore/Utils.hs<br>
> @@ -407,7 +407,7 @@ mkErrorAppDs err_id ty msg = do<br>
>          full_msg = showSDoc dflags (hcat [ppr src_loc, vbar, msg])<br>
>          core_msg = Lit (mkLitString full_msg)<br>
>          -- mkLitString returns a result of type String#<br>
> -    return (mkApps (Var err_id) [Type (getRuntimeRep ty), Type ty, core_msg])<br>
> +    return (mkApps (Var err_id) [Type (getRuntimeInfo ty), Type ty, core_msg])<br>
>  <br>
>  {-<br>
>  'mkCoreAppDs' and 'mkCoreAppsDs' handle the special-case desugaring of 'seq'.<br>
> diff --git a/compiler/GHC/IfaceToCore.hs b/compiler/GHC/IfaceToCore.hs<br>
> index de0fa6f023..b6d1281684 100644<br>
> --- a/compiler/GHC/IfaceToCore.hs<br>
> +++ b/compiler/GHC/IfaceToCore.hs<br>
> @@ -1438,7 +1438,7 @@ tcIfaceExpr (IfaceTuple sort args)<br>
>         ; let con_tys = map exprType args'<br>
>               some_con_args = map Type con_tys ++ args'<br>
>               con_args = case sort of<br>
> -               UnboxedTuple -> map (Type . getRuntimeRep) con_tys ++ some_con_args<br>
> +               UnboxedTuple -> map (Type . getRuntimeInfo) con_tys ++ some_con_args<br>
>                 _            -> some_con_args<br>
>                          -- Put the missing type arguments back in<br>
>               con_id   = dataConWorkId (tyConSingleDataCon tc)<br>
> diff --git a/compiler/GHC/Tc/Gen/HsType.hs b/compiler/GHC/Tc/Gen/HsType.hs<br>
> index bf4b1c91d1..22283296e1 100644<br>
> --- a/compiler/GHC/Tc/Gen/HsType.hs<br>
> +++ b/compiler/GHC/Tc/Gen/HsType.hs<br>
> @@ -1331,7 +1331,7 @@ finish_tuple rn_ty tup_sort tau_tys tau_kinds exp_kind = do<br>
>        check_expected_kind (mkTyConApp tycon tau_tys) liftedTypeKind<br>
>      UnboxedTuple -> do<br>
>        let tycon    = tupleTyCon Unboxed arity<br>
> -          tau_reps = map kindRep tau_kinds<br>
> +          tau_reps = map kindInfo tau_kinds<br>
>            -- See also Note [Unboxed tuple RuntimeRep vars] in GHC.Core.TyCon<br>
>            arg_tys  = tau_reps ++ tau_tys<br>
>            res_kind = unboxedTupleKind tau_reps<br>
> @@ -1340,7 +1340,8 @@ finish_tuple rn_ty tup_sort tau_tys tau_kinds exp_kind = do<br>
>    where<br>
>      arity = length tau_tys<br>
>      check_expected_kind ty act_kind =<br>
> -      checkExpectedKind rn_ty ty act_kind exp_kind<br>
> +      pprPanic "here" (ppr exp_kind)<br>
> +      -- checkExpectedKind rn_ty ty act_kind exp_kind<br>
>  <br>
>  {-<br>
>  Note [Ignore unary constraint tuples]<br>
> diff --git a/compiler/GHC/Tc/Instance/Typeable.hs b/compiler/GHC/Tc/Instance/Typeable.hs<br>
> index e4eb7a1b2d..51f0816860 100644<br>
> --- a/compiler/GHC/Tc/Instance/Typeable.hs<br>
> +++ b/compiler/GHC/Tc/Instance/Typeable.hs<br>
> @@ -28,7 +28,7 @@ import GHC.Builtin.Names<br>
>  import GHC.Builtin.Types.Prim ( primTyCons )<br>
>  import GHC.Builtin.Types<br>
>                    ( tupleTyCon, sumTyCon, runtimeRepTyCon<br>
> -                  , vecCountTyCon, vecElemTyCon<br>
> +                  , runtimeInfoTyCon, vecCountTyCon, vecElemTyCon<br>
>                    , nilDataCon, consDataCon )<br>
>  import <a href="http://GHC.Types.Name" rel="noreferrer" target="_blank">GHC.Types.Name</a><br>
>  import <a href="http://GHC.Types.Id" rel="noreferrer" target="_blank">GHC.Types.Id</a><br>
> @@ -564,7 +564,7 @@ mkKindRepRhs stuff@(Stuff {..}) in_scope = new_kind_rep<br>
>        | not (tcIsConstraintKind k)<br>
>                -- Typeable respects the Constraint/Type distinction<br>
>                -- so do not follow the special case here<br>
> -      , Just arg <- kindRep_maybe k<br>
> +      , Just arg <- kindInfo_maybe k<br>
>        , Just (tc, []) <- splitTyConApp_maybe arg<br>
>        , Just dc <- isPromotedDataCon_maybe tc<br>
>        = return $ nlHsDataCon kindRepTYPEDataCon `nlHsApp` nlHsDataCon dc<br>
> diff --git a/compiler/GHC/Tc/Solver.hs b/compiler/GHC/Tc/Solver.hs<br>
> index 8b21b72768..ae8609541f 100644<br>
> --- a/compiler/GHC/Tc/Solver.hs<br>
> +++ b/compiler/GHC/Tc/Solver.hs<br>
> @@ -53,7 +53,7 @@ import GHC.Core.Predicate<br>
>  import GHC.Tc.Types.Origin<br>
>  import GHC.Tc.Utils.TcType<br>
>  import GHC.Core.Type<br>
> -import GHC.Builtin.Types ( liftedRepTy, manyDataConTy )<br>
> +import GHC.Builtin.Types ( liftedRepEvalTy, manyDataConTy )<br>
>  import GHC.Core.Unify    ( tcMatchTyKi )<br>
>  import GHC.Utils.Misc<br>
>  import GHC.Utils.Panic<br>
> @@ -2283,13 +2283,13 @@ promoteTyVarTcS tv<br>
>  -- | Like 'defaultTyVar', but in the TcS monad.<br>
>  defaultTyVarTcS :: TcTyVar -> TcS Bool<br>
>  defaultTyVarTcS the_tv<br>
> -  | isRuntimeRepVar the_tv<br>
> +  | isRuntimeInfoVar the_tv<br>
>    , not (isTyVarTyVar the_tv)<br>
>      -- TyVarTvs should only be unified with a tyvar<br>
>      -- never with a type; c.f. GHC.Tc.Utils.TcMType.defaultTyVar<br>
>      -- and Note [Inferring kinds for type declarations] in GHC.Tc.TyCl<br>
> -  = do { traceTcS "defaultTyVarTcS RuntimeRep" (ppr the_tv)<br>
> -       ; unifyTyVar the_tv liftedRepTy<br>
> +  = do { traceTcS "defaultTyVarTcS RuntimeInfo" (ppr the_tv)<br>
> +       ; unifyTyVar the_tv liftedRepEvalTy<br>
>         ; return True }<br>
>    | isMultiplicityVar the_tv<br>
>    , not (isTyVarTyVar the_tv)  -- TyVarTvs should only be unified with a tyvar<br>
> diff --git a/compiler/GHC/Tc/TyCl/PatSyn.hs b/compiler/GHC/Tc/TyCl/PatSyn.hs<br>
> index 3f5b10f343..de9f28fbd9 100644<br>
> --- a/compiler/GHC/Tc/TyCl/PatSyn.hs<br>
> +++ b/compiler/GHC/Tc/TyCl/PatSyn.hs<br>
> @@ -756,7 +756,7 @@ tcPatSynMatcher (L loc name) lpat<br>
>                  (args, arg_tys) pat_ty<br>
>    = do { rr_name <- newNameAt (mkTyVarOcc "rep") loc<br>
>         ; tv_name <- newNameAt (mkTyVarOcc "r")   loc<br>
> -       ; let rr_tv  = mkTyVar rr_name runtimeRepTy<br>
> +       ; let rr_tv  = mkTyVar rr_name runtimeInfoTy<br>
>               rr     = mkTyVarTy rr_tv<br>
>               res_tv = mkTyVar tv_name (tYPE rr)<br>
>               res_ty = mkTyVarTy res_tv<br>
> diff --git a/compiler/GHC/Tc/Utils/TcMType.hs b/compiler/GHC/Tc/Utils/TcMType.hs<br>
> index ccb9152e01..67295ac3f5 100644<br>
> --- a/compiler/GHC/Tc/Utils/TcMType.hs<br>
> +++ b/compiler/GHC/Tc/Utils/TcMType.hs<br>
> @@ -492,7 +492,7 @@ inferResultToType (IR { ir_uniq = u, ir_lvl = tc_lvl<br>
>              Just ty -> do { ensureMonoType ty<br>
>                              -- See Note [inferResultToType]<br>
>                            ; return ty }<br>
> -            Nothing -> do { rr  <- newMetaTyVarTyAtLevel tc_lvl runtimeRepTy<br>
> +            Nothing -> do { rr  <- newMetaTyVarTyAtLevel tc_lvl runtimeInfoTy<br>
>                            ; tau <- newMetaTyVarTyAtLevel tc_lvl (tYPE rr)<br>
>                              -- See Note [TcLevel of ExpType]<br>
>                            ; writeMutVar ref (Just tau)<br>
> @@ -667,10 +667,10 @@ promoteTcType dest_lvl ty<br>
>           else promote_it }<br>
>    where<br>
>      promote_it :: TcM (TcCoercion, TcType)<br>
> -    promote_it  -- Emit a constraint  (alpha :: TYPE rr) ~ ty<br>
> +    promote_it  -- Emit a constraint  (alpha :: TYPE ri) ~ ty<br>
>                  -- where alpha and rr are fresh and from level dest_lvl<br>
> -      = do { rr      <- newMetaTyVarTyAtLevel dest_lvl runtimeRepTy<br>
> -           ; prom_ty <- newMetaTyVarTyAtLevel dest_lvl (tYPE rr)<br>
> +      = do { ri      <- newMetaTyVarTyAtLevel dest_lvl runtimeInfoTy<br>
> +           ; prom_ty <- newMetaTyVarTyAtLevel dest_lvl (tYPE ri)<br>
>             ; let eq_orig = TypeEqOrigin { uo_actual   = ty<br>
>                                          , uo_expected = prom_ty<br>
>                                          , uo_thing    = Nothing<br>
> @@ -1048,7 +1048,7 @@ newFlexiTyVarTys n kind = replicateM n (newFlexiTyVarTy kind)<br>
>  <br>
>  newOpenTypeKind :: TcM TcKind<br>
>  newOpenTypeKind<br>
> -  = do { rr <- newFlexiTyVarTy runtimeRepTy<br>
> +  = do { rr <- newFlexiTyVarTy runtimeInfoTy<br>
>         ; return (tYPE rr) }<br>
>  <br>
>  -- | Create a tyvar that can be a lifted or unlifted type.<br>
> @@ -1765,11 +1765,16 @@ defaultTyVar default_kind tv<br>
>      -- See Note [Inferring kinds for type declarations] in GHC.Tc.TyCl<br>
>    = return False<br>
>  <br>
> +  | isRuntimeInfoVar tv  -- Do not quantify over a RuntimeRep var<br>
> +                        -- unless it is a TyVarTv, handled earlier<br>
> +  = do { traceTc "Defaulting a RuntimeRep var to LiftedRep" (ppr tv)<br>
> +       ; writeMetaTyVar tv liftedRepEvalTy<br>
> +       ; return True }<br>
>  <br>
>    | isRuntimeRepVar tv  -- Do not quantify over a RuntimeRep var<br>
>                          -- unless it is a TyVarTv, handled earlier<br>
>    = do { traceTc "Defaulting a RuntimeRep var to LiftedRep" (ppr tv)<br>
> -       ; writeMetaTyVar tv liftedRepTy<br>
> +       ; writeMetaTyVar tv liftedRepEvalTy<br>
<br>
I believe your bug is here. You have filled in a RuntimeRep metavar with<br>
a RuntimeInfo. Leave this as liftedRepTy.<br>
<br>
Cheers,<br>
<br>
- Ben<br>
</blockquote></div><br clear="all"><div><br></div>-- <br><div dir="ltr" class="gmail_signature">Shant Hairapetian</div>