The paper "Programming with Arrows" of John Hughes gives some exercises to do [1].
I'm trying to solve it and would like to receive a feedback if I'm doing it right or not before reading the rest of the paper.
I didn't find the answers in the internet (if someone could point me to it, please do so).

Exercise 2 (section 2.5) is asking to create a Stream Processor that can map more than one output per input (e.g. 3 outcomes for a single consume of the stream).

The paper says that implementing "first" will be tricky, and it really is. I've came up to the solution listed below, is it right?


module SP where

import Prelude hiding (id, (.))
import Control.Category
import Control.Arrow

data SP a b = Put b (SP a b) | Get (a -> SP a b)

runSP :: SP a b -> [a] -> [b]
runSP (Put b s) as = b:runSP s as
runSP (Get k) (a:as) = runSP (k a) as
runSP (Get k) [] = []

compose :: SP b c -> SP a b -> SP a c
compose (Put a s) g = Put a (compose s g)
compose (Get k) (Put a s) = compose (k a) s
compose f (Get k) = Get (\a -> compose f (k a))

instance Category SP where
  id = arr id
  (.) = compose

instance Arrow SP where
  arr f = Get (\a -> Put (f a) (arr f))
  first (Put a s) = Get (\(a', c) -> Put (a, c) (delayed (a', c) s))
  first (Get k) = Get (\(a, c) -> firstWithValue (k a) c)

delayed :: (a, c) -> SP a b -> SP (a, c) (b, c)
delayed (a, c) (Put b s) = Put (b, c) (delayed (a, c) s)
delayed (a, c) (Get k) = firstWithValue (k a) c

firstWithValue :: SP a b -> c -> SP (a, c) (b, c)
firstWithValue (Put a s) c = Put (a, c) (firstWithValue s c)
firstWithValue (Get k) _ = Get (\(a, c) -> firstWithValue (k a) c)

input :: [(String, String)]
input = [("a1", "a2"), ("b1", "b2"), ("c1", "c2"), ("d1", "d2")]

myArrow :: SP (String, String) (String, String)
myArrow = (delay "db1" >>> delay "da1") *** (delay "db2" >>> delay "da2")

delay :: a -> SP a a
delay b = Put b (arr id)

main :: IO ()
main = let output = runSP myArrow input in mapM_ f output
  where f (a, b) = putStrLn $ "(" ++ show a ++ ", " ++ show b ++ ")"


The output of "main" is:


*SP> main
("da1", "da2")
("da1", "db2")
("da1", "a2")
("db1", "a2")
("a1", "a2")
("b1", "b2")
("c1", "c2")
("d1", "d2")


[1] http://www.cse.chalmers.se/~rjmh/afp-arrows.pdf