Poly-kinded type family

Richard Eisenberg rae at cs.brynmawr.edu
Mon Apr 30 14:38:38 UTC 2018


Hi Alice,

You'll need mkTemplateTyConBinders, not the two variants of that function you use below. The problem is that both mkTemplateKindTyConBinders and mkTemplateAnonTyConBinders pull Uniques starting from the same value, and so GHC gets very confused when multiple arguments to your TyCon have the same Uniques. mkTemplateTyConBinders, on the other hand, allows you to specify dependency among your arguments without confusing Uniques. You can see a usage of this function in TysPrim.proxyPrimTyCon.

I hope this helps!
Richard

PS: I've made this mistake myself several times, and it's quite baffling to debug!

> On Apr 30, 2018, at 8:27 AM, alice <alicekoroleva239 at gmail.com> wrote:
> 
> Hello. I’m trying to make a type family with resolving it inside type checking classes, like CmpNat. Its type signature is «type family Cmp (a :: k1) (b :: k2)  :: Ordering», so the function is poly kinded. But it seems unclear how to make its TyCon. I’ve tried to follow the CmpNat and CmpSymbol style, and also saw Any TyCon in TysWiredIn. So this is my attempt:
> 
> typeCmpTyCon :: TyCon
> typeCmpTyCon =
>   mkFamilyTyCon name
>     (binders ++ (mkTemplateAnonTyConBinders [ input_kind1, input_kind2 ]))
>     orderingKind
>     Nothing
>     (BuiltInSynFamTyCon ops)
>     Nothing
>     NotInjective
>   where
>   name = mkWiredInTyConName UserSyntax gHC_TYPELITS (fsLit "Cmp")
>                 typeCmpTyFamNameKey typeCmpTyCon
>   ops = BuiltInSynFamily
>     { sfMatchFam      = matchFamCmpType
>     , sfInteractTop   = interactTopCmpType
>     , sfInteractInert = \_ _ _ _ -> []
>     }
>   binders@[kv1, kv2] = mkTemplateKindTyConBinders [ liftedTypeKind, liftedTypeKind ]
>   input_kind1 = mkTyVarTy (binderVar kv1)
>   input_kind2 = mkTyVarTy (binderVar kv2)
> 
> ghci says this:
> 
> :kind Cmp 
> Cmp :: forall {k0} {k1}. k0 -> k1 -> Ordering
> 
> But then I try to apply it to some values and get this exception:
> 
> :kind! Cmp 4 5
> 
> <interactive>:1:15: error:
>     • Expected kind ‘k0’, but ‘4’ has kind ‘Nat’
>     • In the first argument of ‘Cmp’, namely ‘4’
>       In the type ‘Cmp 4 5’
> 
> <interactive>:1:17: error:
>     • Expected kind ‘k1’, but ‘5’ has kind ‘Nat’
>     • In the second argument of ‘Cmp’, namely ‘5’
>       In the type ‘Cmp 4 5’
> 
> Does anyone know where I made a mistake? Any help would be appreciated.
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20180430/bdfcb6f9/attachment.html>


More information about the ghc-devs mailing list