Arrow Notation - Command combinators don't work with higher rank types? (GHC 7.4)

Ross Paterson ross at soi.city.ac.uk
Sun Jan 15 11:21:19 CET 2012


On Sun, Jan 15, 2012 at 09:34:35AM +0000, Ben Moseley wrote:
> Consider the code below:
> 
> ----
> 
> {-# LANGUAGE Arrows,Rank2Types #-}
> 
> import Control.Arrow
> 
> -- cmdcomb :: Arrow a => (a (env,x) x) -> a (env,x) x
> -- cmdcomb aegg = aegg
> 
> cmdcomb :: Arrow a => (forall x . a (env,x) x) -> a (env,x) x
> cmdcomb aegg = aegg
> 
> myarr :: Arrow a => a (Int,Bool) Bool
> myarr = proc (i,b) -> do
>           (|cmdcomb (\g -> returnA -< g) |) 'x'
>           -- (| (cmdcomb (arr snd)) |) 'x'
>           returnA -< False
> 
> ----
> 
> This code generates the error below (but using either of the commented sections instead gets it to typecheck):
> 
> ../MyDev/FPF3/saturday/dm.hs:13:13:
>     Couldn't match expected type `t0 t1 t2'
>                 with actual type `forall x. a0 (env0, x) x'
>     Expected type: t0 t1 t2 -> a (a1, t4) t3
>       Actual type: (forall x. a0 (env0, x) x) -> a0 (env0, x0) x0
>     In the expression: cmdcomb
>     In the expression:
>       proc (i, b) -> do { (|cmdcomb ((\ g -> returnA -< g))|) 'x';
>                           returnA -< False }
> Failed, modules loaded: none.
> 
> Is this a bug or a limitation in the current implementation?

It's performing as documented in the User's Guide: "the type of each
argument of the operator (and its result) should have the form

    a (...(e,t1), ... tn)

t where e is a polymorphic variable".  In this case the operator is
cmdcomb, and the commented-out type has the allowed form, but the given
one doesn't.  With the second variant uncommented, the operator would be

    cmdcomb (arr snd) :: Arrow a => a (env,x) x

which also conforms.

So the limitation is in the design rather than the implementation.
Is this a major obstacle?  I appreciate that this was cut down to provide
a concise report; how important is this in the full application?



More information about the Glasgow-haskell-users mailing list