Skip to content

DRAFT: Kinds are Calling Conventions Implementation

@sgraf812 @simonpj @rae

So after our last meeting we have atcdump.txt.zipligned the tuple data and type constructors in the code with the paper.

Unboxed Tuple Spec from Kinds are Calling Conventions

-- Type constrcutor
forall (k0 :: RuntimeRep) (k1 :: CallingConv) (k2 :: RuntimeRep)
         (k3 :: CallingConv).
  TYPE (RuntimeInfo k0 k1)
  -> TYPE (RuntimeInfo k2 k3)
  -> TYPE ('RInfo ('TupleRep '[k0, k2]) 'ConvEval)


-- data constructor
  forall (k0 :: RuntimeRep) (k1 :: CallingConv) (k2 :: RuntimeRep)
         (k3 :: CallingConv) (a :: TYPE (RuntimeInfo k0 k1))
         (b :: TYPE (RuntimeInfo k2 k3)).
  a -> b -> (# k3, a, b #)

Once this was fixed, there was another issue that I eventually tracked down to how RuntimeRep TyVar's were being defaulted. After that issue was resolved all of the unboxed tuple errors went away!

Now however, we have new errors in ghc-prim\GHC\Magic.hs

libraries/ghc-prim/GHC/Magic.hs:101:24: error:
    • Couldn't match kind ‘q’ with ‘'GHC.Types.RInfo t2 t3’
      Expected a type, but ‘a’ has kind ‘TYPE q’
      ‘q’ is a rigid type variable bound by
        an explicit forall (q :: RuntimeInfo) (r :: RuntimeInfo)
                           (a :: TYPE q) (b :: TYPE r)
        at libraries/ghc-prim/GHC/Magic.hs:99:20
    • In the type signature:
        oneShot :: forall (q :: RuntimeInfo)
                          (r :: RuntimeInfo)
                          (a :: TYPE q)
                          (b :: TYPE r). (a -> b) -> a -> b
    |
101 |            (a -> b) -> a -> b
    |                        ^

libraries/ghc-prim/GHC/Magic.hs:101:29: error:
    • Couldn't match kind ‘r’ with ‘'GHC.Types.RInfo t4 t5’
      Expected a type, but ‘b’ has kind ‘TYPE r’
      ‘r’ is a rigid type variable bound by
        an explicit forall (q :: RuntimeInfo) (r :: RuntimeInfo)
                           (a :: TYPE q) (b :: TYPE r)
        at libraries/ghc-prim/GHC/Magic.hs:99:39
    • In the type signature:
        oneShot :: forall (q :: RuntimeInfo)
                          (r :: RuntimeInfo)
                          (a :: TYPE q)
                          (b :: TYPE r). (a -> b) -> a -> b
    |
101 |            (a -> b) -> a -> b
    |                             ^

libraries/ghc-prim/GHC/Magic.hs:115:38: error:
    • Couldn't match kind ‘r’ with ‘'GHC.Types.RInfo t0 t1’
      Expected a type, but ‘o’ has kind ‘TYPE r’
      ‘r’ is a rigid type variable bound by
        an explicit forall (r :: RuntimeInfo) (o :: TYPE r)
        at libraries/ghc-prim/GHC/Magic.hs:114:19
    • In the type signature:
        runRW# :: forall (r :: RuntimeInfo)
                         (o :: TYPE r). (State# RealWorld -> o) -> o
    |
115 |           (State# RealWorld -> o) -> o
    | 

I have attached the tc-trace

Merge request reports