
Miguel Mitrofanov, on 9 July [1]:
I'm trying to do Exercise 2.5.2 from John Hughes's "Programming with Arrows". [...]
Sorry for the delayed reply. I've only just started learning about arrow programming, and since no-one else has replied to you, here is what I've discovered so far... I think there are some problems with your implementation of "first". Here are some examples which don't behave the way I would expect:
delaySP = foldr Out returnA
skipSP n = if n > 0 then Inp (\_ -> skipSP (n-1)) else returnA
*Main> runSP (delaySP [-3,-2,-1] &&& returnA) [0..9] [(-3,0),(-2,1),(-1,2),(2,3),(3,4),(4,5),(5,6),(6,7),(7,8),(8,9)] I would expect 0 and 1 to be present in the sequence in the first component. *Main> runSP (skipSP 2 &&& returnA) [0..9] [(2,2),(3,3),(4,4),(5,5),(6,6),(7,7),(8,8),(9,9)] The second component seems to have been skipped as well as the first. The "tricky point" referred to in the tutorial exercise [2] seems to be that the two components running through first will inevitably get out of sync, possibly by an arbitrary number of elements. My first attempt was to use explicit queues:
import Data.Sequence
data SP a b = Get (a -> SP a b) | Put b (SP a b)
instance Arrow SP where arr f = Get $ \x -> Put (f x) (arr f)
Put y f >>> Get g = f >>> g y Get f >>> Get g = Get (\x -> f x >>> Get g) f >>> Put z g = Put z (f >>> g)
first = step empty empty where -- Invariant: at least one of [qfst,qsnd] must be empty. step qfst qsnd (Put y sp) = case viewl qsnd of EmptyL -> Get $ \(x,z) -> Put (y,z) (step (qfst |> x) qsnd sp) z :< zs -> Put (y,z) (step qfst zs sp) step qfst qsnd (Get fsp) = case viewl qfst of EmptyL -> Get $ \(x,z) -> step qfst (qsnd |> z) (fsp x) x :< xs -> step xs qsnd (fsp x)
instance ArrowChoice SP where left (Get fsp) = Get $ either (left . fsp) (\z -> Put (Right z) (left $ Get fsp)) left (Put y sp) = Put (Left y) (left sp)
This produces something reasonably sensible for the examples above: *Main> runSP (delaySP [-3,-2,-1] &&& returnA) [0..9] [(-3,0),(-2,1),(-1,2),(0,3),(1,4),(2,5),(3,6),(4,7),(5,8),(6,9)] *Main> runSP (skipSP 2 &&& returnA) [0..9] [(2,0),(3,1),(4,2),(5,3),(6,4),(7,5),(8,6),(9,7)] However, if you think about it more closely, it is still not satisfactory: *Main> runSP (Put 42 returnA) [] [42] *Main> runSP (first (Put 42 returnA)) [] [] In the second case, I think the answer should really be [(42,_|_)]. A more severe problem is that because both runSP and the arrow combinators pattern-match on the SP constructors, it is impossible to use recursive arrow structures with this implementation of the SP arrow:
factorial :: (Num a, ArrowChoice arr) => arr a a factorial = arr (choose (==0)) >>> arr (const 1) ||| (returnA &&& (arr (flip (-) 1) >>> factorial) >>> arr (uncurry (*)))
choose c x | c x = Left x | otherwise = Right x
*Main> factorial 4 24 *Main> runSP factorial [3,4] *** Exception: stack overflow Same goes for mapA given in the tutorial [2]. This problem also prevented me from defining an instance of ArrowLoop. So, I don't think explicit queues are the answer. I suspect one needs to use the circular/lazy programming technique described in section 2.3 [2] to implement the basic Arrow combinators, as well as ArrowLoop. With some luck, that might solve both of the above problems. [1]http://www.haskell.org/pipermail/haskell-cafe/2007-July/028180.html [2]http://www.cs.chalmers.se/~rjmh/afp-arrows.pdf