[Haskell] Rank-N types with (.) composition

David Feuer david.feuer at gmail.com
Tue Feb 10 20:51:31 UTC 2015


The problem is that GHC's type system is (almost entirely)
predicative. I couldn't tell you just what that means, but to a first
approximation, it means that type variables cannot be instantiated to
polymorphic types. You write

trip = Wrap . extract


which means

(.) Wrap extract

(.)::(b->c)->(a->b)->a->c

Wrap :: (forall f. Functor f => f Int) -> Wrap

The trouble here is that the type variable b in the type of (.) isn't
allowed to be polymorphic, but Wrap's argument must be.

Note that there's a weird exception: ($) actually has an impredicative
type, because it's a special case in the type checker. This is largely
for historical reasons.

On Tue, Feb 10, 2015 at 3:38 PM, Tyson Whitehead <twhitehead at gmail.com> wrote:
> I came across something that seems a bit strange to me.  Here is a simplified version (the original was trying to move from a lens ReifiedFold to a lens-action ReifiedMonadicFold)
>
>  {-# LANGUAGE RankNTypes #-}
>
>  import Control.Applicative
>
>  newtype Wrap = Wrap { extract :: forall f. Functor f => f Int }
>
>  trip :: Wrap -> Wrap
>  trip a = Wrap (extract a)
>
> The compiler is okay with this.  It chokes on this alternative though
>
>  trip :: Wrap -> Wrap
>  trip = Wrap . extract
>
> giving (GHC 7.8.2)
>
>  Couldn't match type ‘f0 Int’
>                with ‘forall (f :: * -> *). Functor f => f Int’
>  Expected type: f0 Int -> Wrap
>    Actual type: (forall (f :: * -> *). Functor f => f Int) -> Wrap
>  In the first argument of ‘(.)’, namely ‘Wrap’
>  In the expression: Wrap . extract
>
> I'm guessing this is because the compiler fancy footwork to handle the implicit parameters, something like
>
>  trip a = Wrap (\f fDict -> extract a f fDict)
>
> where f is the Functor type and fDict is the associated dictionary, isn't compatible with the (.) definition of
>
>  f . g = \x -> f (g x)
>
> Is this correct?  I would appreciate anyone insight here.  Is there a way combine these (.) style?
>
> Thanks!  -Tyson
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell


More information about the Haskell mailing list