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

Ben Moseley ben_moseley at mac.com
Sun Jan 15 13:12:01 CET 2012


Yes, indeed.

Thanks again, (and thanks for building all the arrow notation infrastructure in the first place - it's awesome!)

--Ben

On 15 Jan 2012, at 11:57, Ross Paterson wrote:

> On Sun, Jan 15, 2012 at 11:42:28AM +0000, Ben Moseley wrote:
>> The real application is trying to process a structure containing GADTs - something more like this:
>> 
>> {-# LANGUAGE GADTs,Arrows,Rank2Types #-}
>> import Control.Arrow
>> 
>> data G a where
>>    G1 :: Int -> G Char
>>    G2 :: Int -> G Bool
>> 
>> -- mapcomb :: Arrow a => (a (env,G x) (G x)) -> a (env,(G b,G c)) (G b,G c)
>> -- mapcomb _aegg = proc (_env,bc) -> returnA -< bc
>> 
>> process :: Int -> G x -> G x
>> process i (G1 n) = G1 $ succ n
>> process i (G2 n) = G2 $ succ n
>> 
>> processA :: Arrow a => a (Int,G x) (G x)
>> processA = proc (i,gx) -> returnA -< process i gx
>> 
>> mapcomb :: Arrow a => (forall x . a (env,G x) (G x)) -> a (env,(G b,G c)) (G b,G c)
>> mapcomb aegg = proc (env,(g1,g2)) -> do
>>                 g1' <- aegg -< (env,g1)
>>                 g2' <- aegg -< (env,g2)
>>                 returnA -< (g1',g2')
>> 
>> myarr :: Arrow a => a Int Bool
>> myarr = proc i -> do
>>          (|mapcomb (\g -> processA -< (i,g)) |) (G1 3,G2 3)
>>          -- (| (mapcomb (processA <<^ (\(_,g)->(7,g)) )) |) (G1 3,G2 3)
>>          returnA -< False
>> 
>> I guess to do this it'll be necessary to plumb 'i' through manually (changing the type of 'mapcomb') ?
> 
> In this particular case you could give mapcomb two arguments:
> 
> mapcomb :: Arrow a => a (env,G b) (G b) -> a (env,G c) (G c) -> a (env,(G b,G c)) (G b,G c)
> 
> and pass processA twice, but that wouldn't work in general (with an
> unlimited number of variants).
> 
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list