Exercise of "Programming with Arrows"

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

Hey Thiago,
First of all, congratulations for reading Hughes! Many of his papers are
worth reading and re-reading for both beginners and experts alike.
On Tue, Oct 8, 2013 at 12:05 AM, Thiago Negri
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).
Given
data SP a b = Put b (SP a b) | Get (a -> SP a b)
it's easy to see that it's not just about more than one output per input. It's about n pieces of input producing m pieces of output, where (n,m) may even -- and probably does -- depend on previous inputs! The exercise asks for an implementation of the following Arrow instance:
first :: arr a b -> arr (a,c) (b,c)
which, specialized to our case, is just SP a b -> SP (a,c) (b,c). It should now be apparent what the 'trickiness' is. On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out. So one way to look at this is as a buffering problem. At this point, I'd encourage you to think of some quickcheck tests you can write to convince yourself whether you have a right implementation or not. Your main function doesn't seem adequate for the task. -- Kim-Ee

"On the one hand, indeterminate a's need to be fed in before indeterminate
b's get pulled out. On the other hand, the c's need to behave as if they
were in a no-op assembly line. One c goes in, the one (and same!) c drops
out."
I agree with "no-op assembly line", but when I'm using `first` on a
processor, I want to process the first stream *only*. The second stream
should remain as it was not touched, so future processors will receive the
same sequence from the second stream.
I mean, I think I need to guarantee that this definition holds:
`g *** f` is the same as `first g >>> swap >>> first f >>> swap`
If my implementation of `first` uses a real no-op assembly line for `c`
(i.e., `arr id`), then I would lose the stream. As you said, I need to
buffer the second stream while processing the first one.
Is my line of tought correct?
I'll try to write some tests to verify this.
Thanks!
2013/10/7 Kim-Ee Yeoh
Hey Thiago,
First of all, congratulations for reading Hughes! Many of his papers are worth reading and re-reading for both beginners and experts alike.
On Tue, Oct 8, 2013 at 12:05 AM, Thiago Negri
wrote: 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).
Given
data SP a b = Put b (SP a b) | Get (a -> SP a b)
it's easy to see that it's not just about more than one output per input. It's about n pieces of input producing m pieces of output, where (n,m) may even -- and probably does -- depend on previous inputs!
The exercise asks for an implementation of the following Arrow instance:
first :: arr a b -> arr (a,c) (b,c)
which, specialized to our case, is just SP a b -> SP (a,c) (b,c).
It should now be apparent what the 'trickiness' is. On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out.
So one way to look at this is as a buffering problem.
At this point, I'd encourage you to think of some quickcheck tests you can write to convince yourself whether you have a right implementation or not.
Your main function doesn't seem adequate for the task.
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

This is my first contact with QuickCheck, but does this test count as a
proof that my implementation is correct?
QuickCheck shows 100 tests passed.
prop_a xs = runSP (f *** g) xs == runSP (first f >>> swap >>> first g >>>
swap) xs
where swap = arr (\(a,b) -> (b,a))
f = arr (++"a")
g = arr (++"b")
2013/10/7 Thiago Negri
"On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out."
I agree with "no-op assembly line", but when I'm using `first` on a processor, I want to process the first stream *only*. The second stream should remain as it was not touched, so future processors will receive the same sequence from the second stream.
I mean, I think I need to guarantee that this definition holds:
`g *** f` is the same as `first g >>> swap >>> first f >>> swap`
If my implementation of `first` uses a real no-op assembly line for `c` (i.e., `arr id`), then I would lose the stream. As you said, I need to buffer the second stream while processing the first one.
Is my line of tought correct?
I'll try to write some tests to verify this.
Thanks!
2013/10/7 Kim-Ee Yeoh
Hey Thiago,
First of all, congratulations for reading Hughes! Many of his papers are worth reading and re-reading for both beginners and experts alike.
On Tue, Oct 8, 2013 at 12:05 AM, Thiago Negri
wrote: 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).
Given
data SP a b = Put b (SP a b) | Get (a -> SP a b)
it's easy to see that it's not just about more than one output per input. It's about n pieces of input producing m pieces of output, where (n,m) may even -- and probably does -- depend on previous inputs!
The exercise asks for an implementation of the following Arrow instance:
first :: arr a b -> arr (a,c) (b,c)
which, specialized to our case, is just SP a b -> SP (a,c) (b,c).
It should now be apparent what the 'trickiness' is. On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out.
So one way to look at this is as a buffering problem.
At this point, I'd encourage you to think of some quickcheck tests you can write to convince yourself whether you have a right implementation or not.
Your main function doesn't seem adequate for the task.
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I think I'm starting to get the "way of arrows".
My implementation was incorrect. I've seen it with the hand made test
listed below [1].
The output of "first arrA" and "first arrB" should be joined together and
form a new stream with the length of the shortest output of both ("arrA ***
arrB"), and this wasn't happening.
I've found package "streamproc" at Hackage and that gave me some insights.
Yet I think "streamproc" is also wrong, as it does not buffer the second
stream.
You can check it at line 58 of SP.hs [3] that it ignores the first element
of the pair.
But I didn't write a test to check what is the implication of this, I'll
try to do this as a next step into understanding arrows.
That exercise really helped me!
My new implementation, wich I think is correct now, is listed below [2].
Thanks!
Thiago
[1]:
inputA :: [String]
inputA = ["a", "b", "hello", "c", "d", "e", "hello", "f", "g", "e", "x"]
arrA :: SP String String
arrA = Get (\a -> if a == "hello" then (Put a (Put "world" arrA))
else (Put "unknown" arrA))
arrB :: SP String String
arrB = Get (\a -> if a == "my" then (Get (\a -> if a == "name" then (Get
(\a -> if a == "is" then Get (\a -> Put ("name: " ++ a) arrB)
else arrB))
else arrB))
else arrB)
inputB :: [String]
inputB = ["a", "b", "my", "name", "is", "thiago", "and", "I", "am", "so",
"cool"]
inputAB :: [(String, String)]
inputAB = zip inputA inputB
main :: IO ()
main = let actualOutputB = runSP arrB inputB
actualOutputB1 = runSP (first arrB) (zip inputB (repeat "a"))
actualOutputA = runSP arrA inputA
actualOutputA1 = runSP (first arrA) (zip inputA (repeat "a"))
actualOutputAB = runSP (arrA *** arrB) inputAB
in do putStrLn $ "inputAB: " ++ show inputAB
putStrLn $ "outputA: " ++ show actualOutputA
putStrLn $ "outputA1: " ++ show actualOutputA1
putStrLn $ "outputB: " ++ show actualOutputB
putStrLn $ "outputB1: " ++ show actualOutputB1
putStrLn $ "outputAB: " ++ show actualOutputAB
[2]:
module SP where
import Prelude hiding (id, (.))
import Control.Category
import Control.Arrow
import Test.QuickCheck
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 = queued empty empty
queued :: Queue a -> Queue c -> SP a b -> SP (a, c) (b, c)
queued qa qc (Put a s) = case pop qc of Nothing -> Get (\(a', c) -> Put (a,
c) (queued (push a' qa) qc s))
Just (c, qc') -> Put (a, c) (queued
qa qc' s)
queued qa qc (Get k) = case pop qa of Nothing -> Get (\(a, c) -> queued qa
(push c qc) (k a))
Just (a, qa') -> queued qa' qc (k a)
data Queue a = Queue [a]
empty :: Queue a
empty = Queue []
push :: a -> Queue a -> Queue a
push a (Queue as) = Queue (a:as)
pop :: Queue a -> Maybe (a, Queue a)
pop (Queue []) = Nothing
pop (Queue (a:as)) = Just (a, Queue as)
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)
inputA :: [String]
inputA = ["a", "b", "hello", "c", "d", "e", "hello", "f", "g", "e", "x"]
arrA :: SP String String
arrA = Get (\a -> if a == "hello" then (Put a (Put "world" arrA))
else (Put "unknown" arrA))
arrB :: SP String String
arrB = Get (\a -> if a == "my" then (Get (\a -> if a == "name" then (Get
(\a -> if a == "is" then Get (\a -> Put ("name: " ++ a) arrB)
else arrB))
else arrB))
else arrB)
inputB :: [String]
inputB = ["a", "b", "my", "name", "is", "thiago", "and", "I", "am", "so",
"cool"]
inputAB :: [(String, String)]
inputAB = zip inputA inputB
main :: IO ()
main = let actualOutputB = runSP arrB inputB
actualOutputB1 = runSP (first arrB) (zip inputB (repeat "a"))
actualOutputA = runSP arrA inputA
actualOutputA1 = runSP (first arrA) (zip inputA (repeat "a"))
actualOutputAB = runSP (arrA *** arrB) inputAB
in do putStrLn $ "inputAB: " ++ show inputAB
putStrLn $ "outputA: " ++ show actualOutputA
putStrLn $ "outputA1: " ++ show actualOutputA1
putStrLn $ "outputB: " ++ show actualOutputB
putStrLn $ "outputB1: " ++ show actualOutputB1
putStrLn $ "outputAB: " ++ show actualOutputAB
[3]: https://github.com/peti/streamproc/blob/master/Control/Arrow/SP.hs#L58
2013/10/7 Thiago Negri
This is my first contact with QuickCheck, but does this test count as a proof that my implementation is correct?
QuickCheck shows 100 tests passed.
prop_a xs = runSP (f *** g) xs == runSP (first f >>> swap >>> first g >>> swap) xs where swap = arr (\(a,b) -> (b,a)) f = arr (++"a") g = arr (++"b")
2013/10/7 Thiago Negri
"On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out."
I agree with "no-op assembly line", but when I'm using `first` on a processor, I want to process the first stream *only*. The second stream should remain as it was not touched, so future processors will receive the same sequence from the second stream.
I mean, I think I need to guarantee that this definition holds:
`g *** f` is the same as `first g >>> swap >>> first f >>> swap`
If my implementation of `first` uses a real no-op assembly line for `c` (i.e., `arr id`), then I would lose the stream. As you said, I need to buffer the second stream while processing the first one.
Is my line of tought correct?
I'll try to write some tests to verify this.
Thanks!
2013/10/7 Kim-Ee Yeoh
Hey Thiago,
First of all, congratulations for reading Hughes! Many of his papers are worth reading and re-reading for both beginners and experts alike.
On Tue, Oct 8, 2013 at 12:05 AM, Thiago Negri
wrote: 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).
Given
data SP a b = Put b (SP a b) | Get (a -> SP a b)
it's easy to see that it's not just about more than one output per input. It's about n pieces of input producing m pieces of output, where (n,m) may even -- and probably does -- depend on previous inputs!
The exercise asks for an implementation of the following Arrow instance:
first :: arr a b -> arr (a,c) (b,c)
which, specialized to our case, is just SP a b -> SP (a,c) (b,c).
It should now be apparent what the 'trickiness' is. On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out.
So one way to look at this is as a buffering problem.
At this point, I'd encourage you to think of some quickcheck tests you can write to convince yourself whether you have a right implementation or not.
Your main function doesn't seem adequate for the task.
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

And now I'm stuck trying to create an instance of ArrowLoop for the stream
processor. :(
My first implementation used a queue, just like the "first" function of my
Arrow instance. It worked like a charm, but failed in the test proposed by
the paper:
"""
- Check that your implementation of loop has the property that the arrows
loop (arr id) and loop (arr swap) behave as arr id:
SP> runSP (loop (arr id)) [1..10]
[1,2,3,4,5,6,7,8,9,10]
SP> runSP (loop (arr swap)) [1..10]
[1,2,3,4,5,6,7,8,9,10]
"""
The first test was ok, but the "runSP (loop (arr swap)) [1..10]" tried to
consume a value from my empty feedback queue and it exploded.
I scrolled back to section 2.3 to see how Hughes did this neat trick to his
SF type and it kind of made sense to me. But I can't express that same
"irrefutable pattern magic" on the SP data type. As the result of consuming
an element of the stream is dynamic (it's like a monad bind), I can't find
a way to declare fit the expression of the feedback stream in terms of
itself, I keep hitting recursion at some point.
I don't even know if I can explain what I'm feeling about what my problem
is. Yet I can't find a way to solve the problem.
Can someone help me?
Please, don't solve it for me, just give some tips.
My current code is here:
https://gist.github.com/thiago-negri/2e541a9f9762c727bdd4
The problematic ArrowLoop instance is at line 45.
Thanks,
Thiago.
2013/10/8 Thiago Negri
I think I'm starting to get the "way of arrows".
My implementation was incorrect. I've seen it with the hand made test listed below [1]. The output of "first arrA" and "first arrB" should be joined together and form a new stream with the length of the shortest output of both ("arrA *** arrB"), and this wasn't happening.
I've found package "streamproc" at Hackage and that gave me some insights. Yet I think "streamproc" is also wrong, as it does not buffer the second stream. You can check it at line 58 of SP.hs [3] that it ignores the first element of the pair. But I didn't write a test to check what is the implication of this, I'll try to do this as a next step into understanding arrows.
That exercise really helped me!
My new implementation, wich I think is correct now, is listed below [2].
Thanks!
Thiago
[1]: inputA :: [String] inputA = ["a", "b", "hello", "c", "d", "e", "hello", "f", "g", "e", "x"]
arrA :: SP String String arrA = Get (\a -> if a == "hello" then (Put a (Put "world" arrA)) else (Put "unknown" arrA))
arrB :: SP String String arrB = Get (\a -> if a == "my" then (Get (\a -> if a == "name" then (Get (\a -> if a == "is" then Get (\a -> Put ("name: " ++ a) arrB)
else arrB)) else arrB)) else arrB)
inputB :: [String] inputB = ["a", "b", "my", "name", "is", "thiago", "and", "I", "am", "so", "cool"]
inputAB :: [(String, String)] inputAB = zip inputA inputB
main :: IO () main = let actualOutputB = runSP arrB inputB actualOutputB1 = runSP (first arrB) (zip inputB (repeat "a")) actualOutputA = runSP arrA inputA actualOutputA1 = runSP (first arrA) (zip inputA (repeat "a")) actualOutputAB = runSP (arrA *** arrB) inputAB in do putStrLn $ "inputAB: " ++ show inputAB putStrLn $ "outputA: " ++ show actualOutputA putStrLn $ "outputA1: " ++ show actualOutputA1 putStrLn $ "outputB: " ++ show actualOutputB putStrLn $ "outputB1: " ++ show actualOutputB1 putStrLn $ "outputAB: " ++ show actualOutputAB
[2]: module SP where
import Prelude hiding (id, (.)) import Control.Category import Control.Arrow import Test.QuickCheck
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 = queued empty empty
queued :: Queue a -> Queue c -> SP a b -> SP (a, c) (b, c) queued qa qc (Put a s) = case pop qc of Nothing -> Get (\(a', c) -> Put (a, c) (queued (push a' qa) qc s)) Just (c, qc') -> Put (a, c) (queued qa qc' s) queued qa qc (Get k) = case pop qa of Nothing -> Get (\(a, c) -> queued qa (push c qc) (k a)) Just (a, qa') -> queued qa' qc (k a)
data Queue a = Queue [a]
empty :: Queue a empty = Queue []
push :: a -> Queue a -> Queue a push a (Queue as) = Queue (a:as)
pop :: Queue a -> Maybe (a, Queue a) pop (Queue []) = Nothing pop (Queue (a:as)) = Just (a, Queue as)
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)
inputA :: [String] inputA = ["a", "b", "hello", "c", "d", "e", "hello", "f", "g", "e", "x"]
arrA :: SP String String arrA = Get (\a -> if a == "hello" then (Put a (Put "world" arrA)) else (Put "unknown" arrA))
arrB :: SP String String arrB = Get (\a -> if a == "my" then (Get (\a -> if a == "name" then (Get (\a -> if a == "is" then Get (\a -> Put ("name: " ++ a) arrB)
else arrB)) else arrB)) else arrB)
inputB :: [String] inputB = ["a", "b", "my", "name", "is", "thiago", "and", "I", "am", "so", "cool"]
inputAB :: [(String, String)] inputAB = zip inputA inputB
main :: IO () main = let actualOutputB = runSP arrB inputB actualOutputB1 = runSP (first arrB) (zip inputB (repeat "a")) actualOutputA = runSP arrA inputA actualOutputA1 = runSP (first arrA) (zip inputA (repeat "a")) actualOutputAB = runSP (arrA *** arrB) inputAB in do putStrLn $ "inputAB: " ++ show inputAB putStrLn $ "outputA: " ++ show actualOutputA putStrLn $ "outputA1: " ++ show actualOutputA1 putStrLn $ "outputB: " ++ show actualOutputB putStrLn $ "outputB1: " ++ show actualOutputB1 putStrLn $ "outputAB: " ++ show actualOutputAB
[3]: https://github.com/peti/streamproc/blob/master/Control/Arrow/SP.hs#L58
2013/10/7 Thiago Negri
This is my first contact with QuickCheck, but does this test count as a proof that my implementation is correct?
QuickCheck shows 100 tests passed.
prop_a xs = runSP (f *** g) xs == runSP (first f >>> swap >>> first g >>> swap) xs where swap = arr (\(a,b) -> (b,a)) f = arr (++"a") g = arr (++"b")
2013/10/7 Thiago Negri
"On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out."
I agree with "no-op assembly line", but when I'm using `first` on a processor, I want to process the first stream *only*. The second stream should remain as it was not touched, so future processors will receive the same sequence from the second stream.
I mean, I think I need to guarantee that this definition holds:
`g *** f` is the same as `first g >>> swap >>> first f >>> swap`
If my implementation of `first` uses a real no-op assembly line for `c` (i.e., `arr id`), then I would lose the stream. As you said, I need to buffer the second stream while processing the first one.
Is my line of tought correct?
I'll try to write some tests to verify this.
Thanks!
2013/10/7 Kim-Ee Yeoh
Hey Thiago,
First of all, congratulations for reading Hughes! Many of his papers are worth reading and re-reading for both beginners and experts alike.
On Tue, Oct 8, 2013 at 12:05 AM, Thiago Negri
wrote: 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).
Given
data SP a b = Put b (SP a b) | Get (a -> SP a b)
it's easy to see that it's not just about more than one output per input. It's about n pieces of input producing m pieces of output, where (n,m) may even -- and probably does -- depend on previous inputs!
The exercise asks for an implementation of the following Arrow instance:
first :: arr a b -> arr (a,c) (b,c)
which, specialized to our case, is just SP a b -> SP (a,c) (b,c).
It should now be apparent what the 'trickiness' is. On the one hand, indeterminate a's need to be fed in before indeterminate b's get pulled out. On the other hand, the c's need to behave as if they were in a no-op assembly line. One c goes in, the one (and same!) c drops out.
So one way to look at this is as a buffering problem.
At this point, I'd encourage you to think of some quickcheck tests you can write to convince yourself whether you have a right implementation or not.
Your main function doesn't seem adequate for the task.
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Fri, Oct 11, 2013 at 12:10 AM, Thiago Negri
And now I'm stuck trying to create an instance of ArrowLoop for the stream processor. :(
If you want quick help, you can always ask on cafe. That said, I believe you're capable of figuring this out on your own. Give it a couple more days to see where it leads you. Read up on irrefutable patterns if need be. "But surely," you ask, "learning more quickly is better, no?" It really depends on what one means by learning. The point is, the struggle etches the ensuing revelation more deeply, resulting in more durable retention. -- Kim-Ee

On Tue, Oct 8, 2013 at 10:43 PM, Thiago Negri
data Queue a = Queue [a]
empty :: Queue a empty = Queue []
push :: a -> Queue a -> Queue a push a (Queue as) = Queue (a:as)
pop :: Queue a -> Maybe (a, Queue a) pop (Queue []) = Nothing pop (Queue (a:as)) = Just (a, Queue as)
This is not a queue! This is a stack, a Last In First Out structure. Queues are First In First Out. Here, I'll help you with the quickcheck instance: instance (CoArbitrary a, Arbitrary b) => Arbitrary (SP a b) where arbitrary = oneof [liftM2 Put arbitrary arbitrary, liftM Get arbitrary] Also, we need a dummy show: instance (Show a, Show b) => Show (SP a b) where show _ = error "SP a b: no show" The test you need to write is the following: prop_SP_first :: SP Int Int -> [(Int,Int)] -> Bool prop_SP_first f xs = x1 == x2 where -- your name is thiago and you WILL be cool once you've fixed your buggy code -- Kim-Ee

Thanks for the new reply. I've fixed the "queue" not being a real queue (see the last gist I've sent to the list [1]). The problem I was having in defining "first" was in my understanding of the execution of the arrow. I didn't realize that (>>>) is just the composition function from Category class. I tought that only the last output would be received by the second arrow of (>>>), and it would continue the stream processing from there. I was really lost. Now I see that the correct thing to do is to fit a no-op on the second stream because outputs will be delivered in pairs to the composed arrow. Sort of a BalanceLine/Merge that I've learned in my COBOL years. I will run your test cases as soon as I get home. By the way, I couldn't figure out a way to define an ArrowLoop instance that "runSP (loop (arr swap))) [1..10]" doesn't evaluate to bottom (loops forever). I don't have much time to this, but I'm trying to solve it mentally when I feel in the mood and typing some code on a 30-min/day basis. The hackage package that defines a Stream Processor as explained by Hughes uses a different definition for SP data type and has the same problem when evaluating "swap" in a loop (it throws an error) [2]. I guess this problem is harder than Hughes expected, as I find it more difficult to solve than the tricky "first" definition. Or, I may be missing something huge. (I still want to solve it by myself, but tips are welcome.) Thanks, Thiago. [1] https://gist.github.com/thiago-negri/2e541a9f9762c727bdd4 [2] http://hackage.haskell.org/package/streamproc

Okay, I solved the exact test case the paper proposed. Now I've hit another problem:
-- -- -- stupid loop -- `runSP loop_swap [1..10]` works loop_swap :: SP a a loop_swap = let swap (a, b) = (b, a) in loop (arr swap)
-- loop_bufid is just a "delayed id" -- `runSP loop_bufid [1..10]` doesn't works :( loop_bufid :: SP a a loop_bufid = loop (Get (\a -> Get (\b -> Put a (Put b id))))
Updated gist: https://gist.github.com/thiago-negri/2e541a9f9762c727bdd4
At least I'm doing progress. :)
2013/10/14 Thiago Negri
Thanks for the new reply.
I've fixed the "queue" not being a real queue (see the last gist I've sent to the list [1]).
The problem I was having in defining "first" was in my understanding of the execution of the arrow. I didn't realize that (>>>) is just the composition function from Category class. I tought that only the last output would be received by the second arrow of (>>>), and it would continue the stream processing from there. I was really lost. Now I see that the correct thing to do is to fit a no-op on the second stream because outputs will be delivered in pairs to the composed arrow. Sort of a BalanceLine/Merge that I've learned in my COBOL years. I will run your test cases as soon as I get home.
By the way, I couldn't figure out a way to define an ArrowLoop instance that "runSP (loop (arr swap))) [1..10]" doesn't evaluate to bottom (loops forever). I don't have much time to this, but I'm trying to solve it mentally when I feel in the mood and typing some code on a 30-min/day basis. The hackage package that defines a Stream Processor as explained by Hughes uses a different definition for SP data type and has the same problem when evaluating "swap" in a loop (it throws an error) [2]. I guess this problem is harder than Hughes expected, as I find it more difficult to solve than the tricky "first" definition. Or, I may be missing something huge. (I still want to solve it by myself, but tips are welcome.)
Thanks, Thiago.
[1] https://gist.github.com/thiago-negri/2e541a9f9762c727bdd4 [2] http://hackage.haskell.org/package/streamproc

On Wed, Oct 16, 2013 at 10:33 PM, Thiago Negri
Okay, I solved the exact test case the paper proposed.
Awesome! Now I've hit another problem:
loop_bufid :: SP a a loop_bufid = loop (Get (\a -> Get (\b -> Put a (Put b id))))
Even better! I was kinda worried that you weren't going to get to this stage. So here's what I see: * this is a problem harder than it look (duh!) * that you've got this far is super-impressive: search "instance ArrowLoop SP" to see what others have attempted And you know what? I don't think there's a solution, not in this generality at least. Let's break up the problem a bit: (A) the fifo/buffer/queue suggested by the problem needs to have Time-Travelling Superpowers. Even when it's empty, you can query values (supplied from the future) to keep your computation running. Oh, and obviously, it's gotta be infinite, i.e. no fixed capacity. (B) some SPs simply won't evaluate to anything meaningful (relative to standard metaphysics) under loop, e.g. existentialism :: SP (String, Bool) (String, Bool) existentialism = let r = Get( \(_,x) -> Put( if x then "Heaven" else "Hell", not x ) r ) in r Either of (A) or (B) is worthy of pursuit. (A) is very haskell-y because one can't even imagine these things using other languages, all of which fall under strict semantics. Good evidence of Sapir-Whorf, don't you think? For (B), I'd think about restricting the space of SPs to get rid of some of the junk. E.g. allow SPs such as Get...Put...Get...Get...Get..., but not those that whose constructors VARY according to the Get binding, essentially the Applicatives vs Monads distinction. (B), whose mantra is Make the Meaningless/Buggy Un-Codeable, is immediately useful in all PLs, but Haskell's type system gives the programmer uniquely powerful leverage in that direction. -- Kim-Ee

Thanks for your words.
The only hit I get in DuckDuckGo was this:
http://sigkill.dk/programs/arrows/
I've tried things like this, and I couldn't make it work.
Yet I've copy&pasted the code, and it worked! Even with the "loop_bufid"
test!
:(
I'll take a deeper look into it.
2013/10/16 Kim-Ee Yeoh
On Wed, Oct 16, 2013 at 10:33 PM, Thiago Negri
wrote: Okay, I solved the exact test case the paper proposed.
Awesome!
Now I've hit another problem:
loop_bufid :: SP a a loop_bufid = loop (Get (\a -> Get (\b -> Put a (Put b id))))
Even better! I was kinda worried that you weren't going to get to this stage.
So here's what I see:
* this is a problem harder than it look (duh!)
* that you've got this far is super-impressive: search "instance ArrowLoop SP" to see what others have attempted
And you know what? I don't think there's a solution, not in this generality at least.
Let's break up the problem a bit:
(A) the fifo/buffer/queue suggested by the problem needs to have Time-Travelling Superpowers. Even when it's empty, you can query values (supplied from the future) to keep your computation running. Oh, and obviously, it's gotta be infinite, i.e. no fixed capacity.
(B) some SPs simply won't evaluate to anything meaningful (relative to standard metaphysics) under loop, e.g.
existentialism :: SP (String, Bool) (String, Bool) existentialism = let r = Get( \(_,x) -> Put( if x then "Heaven" else "Hell", not x ) r ) in r
Either of (A) or (B) is worthy of pursuit.
(A) is very haskell-y because one can't even imagine these things using other languages, all of which fall under strict semantics. Good evidence of Sapir-Whorf, don't you think?
For (B), I'd think about restricting the space of SPs to get rid of some of the junk. E.g. allow SPs such as Get...Put...Get...Get...Get..., but not those that whose constructors VARY according to the Get binding, essentially the Applicatives vs Monads distinction.
(B), whose mantra is Make the Meaningless/Buggy Un-Codeable, is immediately useful in all PLs, but Haskell's type system gives the programmer uniquely powerful leverage in that direction.
-- Kim-Ee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, Oct 17, 2013 at 12:41 AM, Thiago Negri
The only hit I get in DuckDuckGo was this: http://sigkill.dk/programs/arrows/
I've tried things like this, and I couldn't make it work. Yet I've copy&pasted the code, and it worked! Even with the "loop_bufid" test!
If it's any consolation, feed 'er this: arrswap2 :: SP (a,b) (b,a) arrswap2 = let r = Get(\(a1,b1) -> Get(\(a2,b2) -> Put (b1,a1) (Put (b2,a2) r))) in r -- Kim-Ee

On Wed, Oct 16, 2013 at 10:33 PM, Thiago Negri
Updated gist: https://gist.github.com/thiago-negri/2e541a9f9762c727bdd4
Here: prop_SP_first :: SP Int Int -> [(Int,Int)] -> Bool prop_SP_first f xs = x1 == x2 where x1 = map snd xs x2 = map snd (runSP (first f) xs) you check that the second half of the coupled stream are equal, i.e. the (arr id) input of (***) is equivalent across the equal sign: g *** (arr id) = first g What about the first half? -- Kim-Ee
participants (2)
-
Kim-Ee Yeoh
-
Thiago Negri