[Haskell-cafe] Closed Type Family Simplification
Ian Milligan
ianmllgn at gmail.com
Thu Aug 14 02:42:54 UTC 2014
Here is a small example which shows the problem
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
module TypeFamilyTest where
import GHC.Prim
type family A ∷ * → Constraint
type family C f g a where C f g a = f (g a)
a ∷ A (f (g a)) ⇒ ()
a = ()
b ∷ A (C f g a) ⇒ ()
b = a
On Wednesday, August 13, 2014 6:54:45 PM UTC-7, Richard Eisenberg wrote:
>
> Your operating assumption sounds right. Do you have a complete, minimal
> example showing the error? If not, I recommend using -fprint-explicit-kinds
> to see if kinds are getting in your way at all.
>
> Richard
>
> On Aug 13, 2014, at 8:02 PM, Ian Milligan <ianm... at gmail.com <javascript:>>
> wrote:
>
> > When a closed type family has only one instance it seems like it should
> never fail to simplify. Yet this doesn't appear to be the case. When I
> defined (in GHC 7.8.3) the closed type family
> > type family (:.:) f g a where (:.:) f g a = f (g a)
> > I get errors such as
> > 'Could not deduce (Object c3 ((:.:) f g a) ~ Object c3 (f (g a)))'
> > (where Object is a Constraint family), indicating that f (g a) is not
> being substituted for (:.:) f g a as desired. Any idea why this happens?
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskel... at haskell.org <javascript:>
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskel... at haskell.org <javascript:>
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140813/576b1e5d/attachment.html>
More information about the Haskell-Cafe
mailing list