Re: [Haskell-cafe] How to implement digital filters using Arrows

Hi John, Thanks for all your help. I've been studying your suggested code:
type FilterAu b c = Automaton (->) b c
liftAu :: ((x,FilterState s)->(y,FilterState s)) -> FilterState s -> FilterAu x y liftAu f s0 = proc x -> do rec (y,s') <- arr f -< (x,s) s <- delay s0 -< s' returnA -< y
runAutomaton is a bit cumbersome, so define a custom run function that takes a list
runAuto a [] = [] runAuto (Automaton f) (x:xs) = let (y,a) = f xt in y:runAuto a xs
as well as the various instance definitions for Automaton. I think I understand how the `returnA' in the last line of your `liftAu' function is getting translated by those instance definitions into: c where c = Automaton ( arr id &&& arr (const c) ) and, furthermore, how that is passing the supplied `y' into the first element of the resulting couple. However, I don't understand how the recursively defined `c' is capturing the modified filter state and preserving it for the next call. It seems like the Automaton being referred to by `c' is a newly constructed entity, which knows nothing about the current state of the running Automaton. Any help in understanding this would be greatly appreciated. Thanks! -db

On 1/11/2011 1:35 AM, Captain Freako wrote: you need to study ArrowLoop and understand that. In the code rec (y,s')<- arr f -< (x,s) s<- delay s0 -< s' the state is 'captured' in the recursive binding. i.e. just like in real circuits the output state "s" is threaded back as an input. The recursive binding is just sugar for the application of the loop combinator. The signature of the loop combinator is loop :: arrow (input, feedback) (output, feedback) -> arrow input output with the loop combinator (with which recursive arrow bindings are defined) the function could have been defined as... liftAu f s0 = loop (second (delay s0) >>> arr f ) the delay is neccessary to break the recursion. i.e. to calculate the next output and state the previous state is used.
liftAu :: ((x,FilterState s)->(y,FilterState s)) -> FilterState s -> FilterAu x y liftAu f s0 = proc x -> do rec (y,s')<- arr f -< (x,s) s<- delay s0 -< s' returnA -< y
I think I understand how the `returnA' in the last line of your `liftAu' function is getting translated by those instance definitions into:
c where c = Automaton ( arr id&&& arr (const c) )
and, furthermore, how that is passing the supplied `y' into the first element of the resulting couple. However, I don't understand how the recursively defined `c' is capturing the modified filter state and preserving it for the next call. It seems like the Automaton being referred to by `c' is a newly constructed entity, which knows nothing about the current state of the running Automaton.
Any help in understanding this would be greatly appreciated.
Thanks! -db

On Mon, Oct 31, 2011 at 3:19 PM, John Lask
On 1/11/2011 1:35 AM, Captain Freako wrote:
you need to study ArrowLoop and understand that.
Thanks, John. I'm working my way through Hughes' suggested exercise in `Programming with Arrows', to wit: "The reader who finds this argument difficult should work out the sequence of approximations in the call `runSF (loop (arr swap)) [1,2,3]'" I think I understand how wrapping `cs' in `stream' provides the needed delay of evaluation, in order to avoid a self propagating `undefined'. However, it's not clear to me exactly what finally triggers the evaluation of c0. So, for instance, I think the `sequence of approximations' looks like this: 1) let (bs, cs) = unzip (map swap (zip as (_:_:_:...))) in bs : bs = [c0, (_:_:...)] cs = [1,2,3] At this point, `c0' is equal to 1, but what triggers the evaluation of c0? Is it simply the binding of it to `b0'? If so, then why aren't `c1' and `c2' also evaluated, which would yield undefined values? Thanks, -db

Hi John,
I'm trying to use the GHCI debugger on this code:
20 instance ArrowLoop SF where
21 loop (SF f) = SF $ \as ->
22 let (bs, cs) = unzip (f (zip as (stream cs))) in bs
23 where stream ~(x:xs) = x : stream xs
24
25 swap :: (a,b) -> (b,a)
26 swap (x,y) = (y,x)
in order to watch the recursion of the `loop' function unfold.
However, when I single step through the code, I never stop on line 22
(where I could, presumably, peek in at `bs' and `cs', in order to see
them develop):
*SF> :break swap
Breakpoint 1 activated at SF.hs:26:1-18
*SF> runSF (loop (arr swap)) [1,2,3]
Stopped at SF.hs:26:1-18
_result :: (b, a) = _
[SF.hs:26:1-18] *SF> :step
Stopped at SF.hs:26:14-18
_result :: (b, a) = _
x :: a = _
y :: b = _
[SF.hs:26:14-18] *SF> :
[1Stopped at SF.hs:23:34-42
_result :: [a] = _
xs :: [a] = _
[SF.hs:23:34-42] *SF> :
Stopped at SF.hs:23:13-42
_result :: [a] = _
[SF.hs:23:13-42] *SF> :
Stopped at SF.hs:23:30-42
_result :: [a] = _
x :: a = _
xs :: [a] = _
[SF.hs:23:30-42] *SF> :
(Pattern repeats.)
Do you have any advice?
Thanks,
-db
On Mon, Oct 31, 2011 at 3:19 PM, John Lask
On 1/11/2011 1:35 AM, Captain Freako wrote:
you need to study ArrowLoop and understand that. In the code

Try
swap p = (snd p, fst p)
or, equivalently
swap ~(x,y) = (y,x)
-- ryan
On Tue, Nov 1, 2011 at 1:30 PM, Captain Freako
Hi John,
I'm trying to use the GHCI debugger on this code:
20 instance ArrowLoop SF where 21 loop (SF f) = SF $ \as -> 22 let (bs, cs) = unzip (f (zip as (stream cs))) in bs 23 where stream ~(x:xs) = x : stream xs 24 25 swap :: (a,b) -> (b,a) 26 swap (x,y) = (y,x)
in order to watch the recursion of the `loop' function unfold. However, when I single step through the code, I never stop on line 22 (where I could, presumably, peek in at `bs' and `cs', in order to see them develop):
*SF> :break swap Breakpoint 1 activated at SF.hs:26:1-18 *SF> runSF (loop (arr swap)) [1,2,3] Stopped at SF.hs:26:1-18 _result :: (b, a) = _ [SF.hs:26:1-18] *SF> :step Stopped at SF.hs:26:14-18 _result :: (b, a) = _ x :: a = _ y :: b = _ [SF.hs:26:14-18] *SF> : [1Stopped at SF.hs:23:34-42 _result :: [a] = _ xs :: [a] = _ [SF.hs:23:34-42] *SF> : Stopped at SF.hs:23:13-42 _result :: [a] = _ [SF.hs:23:13-42] *SF> : Stopped at SF.hs:23:30-42 _result :: [a] = _ x :: a = _ xs :: [a] = _ [SF.hs:23:30-42] *SF> : (Pattern repeats.)
Do you have any advice?
Thanks, -db
On Mon, Oct 31, 2011 at 3:19 PM, John Lask
wrote: On 1/11/2011 1:35 AM, Captain Freako wrote:
you need to study ArrowLoop and understand that. In the code
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Never mind, I misread the code, 'zip' and the lazy definition of stream
should add the necessary laziness.
-- ryan
On Tue, Nov 1, 2011 at 3:36 PM, Ryan Ingram
Try
swap p = (snd p, fst p)
or, equivalently
swap ~(x,y) = (y,x)
-- ryan
On Tue, Nov 1, 2011 at 1:30 PM, Captain Freako
wrote: Hi John,
I'm trying to use the GHCI debugger on this code:
20 instance ArrowLoop SF where 21 loop (SF f) = SF $ \as -> 22 let (bs, cs) = unzip (f (zip as (stream cs))) in bs 23 where stream ~(x:xs) = x : stream xs 24 25 swap :: (a,b) -> (b,a) 26 swap (x,y) = (y,x)
in order to watch the recursion of the `loop' function unfold. However, when I single step through the code, I never stop on line 22 (where I could, presumably, peek in at `bs' and `cs', in order to see them develop):
*SF> :break swap Breakpoint 1 activated at SF.hs:26:1-18 *SF> runSF (loop (arr swap)) [1,2,3] Stopped at SF.hs:26:1-18 _result :: (b, a) = _ [SF.hs:26:1-18] *SF> :step Stopped at SF.hs:26:14-18 _result :: (b, a) = _ x :: a = _ y :: b = _ [SF.hs:26:14-18] *SF> : [1Stopped at SF.hs:23:34-42 _result :: [a] = _ xs :: [a] = _ [SF.hs:23:34-42] *SF> : Stopped at SF.hs:23:13-42 _result :: [a] = _ [SF.hs:23:13-42] *SF> : Stopped at SF.hs:23:30-42 _result :: [a] = _ x :: a = _ xs :: [a] = _ [SF.hs:23:30-42] *SF> : (Pattern repeats.)
Do you have any advice?
Thanks, -db
On Mon, Oct 31, 2011 at 3:19 PM, John Lask
wrote: On 1/11/2011 1:35 AM, Captain Freako wrote:
you need to study ArrowLoop and understand that. In the code
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I can't comment on using ghci debugger to observe evaluation. I have in the past used hood (http://hackage.haskell.org/package/hood) and found it both convenient and useful when trying to observe evaluation order. On 2/11/2011 7:00 AM, Captain Freako wrote:
Hi John,
I'm trying to use the GHCI debugger on this code:
20 instance ArrowLoop SF where 21 loop (SF f) = SF $ \as -> 22 let (bs, cs) = unzip (f (zip as (stream cs))) in bs 23 where stream ~(x:xs) = x : stream xs 24 25 swap :: (a,b) -> (b,a) 26 swap (x,y) = (y,x)
in order to watch the recursion of the `loop' function unfold. However, when I single step through the code, I never stop on line 22 (where I could, presumably, peek in at `bs' and `cs', in order to see them develop):

First, let's lay out our definitions:
unzip [] = ([], [])
unzip ((x,y):xys) = (x:xs, y:ys) where (xs,ys) = unzip xys
zip [] _ = []
zip _ [] = []
zip (x:xs) (y:ys) = (x,y) : zip xs ys
map _ [] = []
map f (x:xs) = f x : map f xs
stream ~(a:as) = a : stream as
-- equivalently
stream xs = head xs : stream (tail xs)
Now we want to evaluate this:
runSF (loop (arr swap)) [1,2,3]
Lets simplify some of the insides a bit:
arr swap
= SF $ map swap
= SF $ map (\(x,y)->(y,x))
loop (arr swap)
= SF $ \as ->
let (bs,cs) = unzip (map swap (zip as (stream cs))) in bs
runSF (loop (arr swap)) [1,2,3]
= runSF (SF $ ...) [1,2,3]
= (\as -> let (bs,cs) = unzip (map swap (zip as (stream cs))) in bs)
[1,2,3]
Here is our heap at this point; we are trying to evaluate bs:
p = unzip (map swap (zip as (stream cs)))
as = [1,2,3]
bs = fst p
cs = snd p
snd p forces p, unzip forces its argument, map forces its second argument,
and zip forces both its arguments.
So now we have:
p = unzip retmap
retmap = map swap retzip
retzip = zip as retstream
retstream = stream cs
as = [1,2,3]
bs = fst p
cs = snd p
Evaluating further:
retstream = head cs : retstream2
retstream2 = stream (tail cs)
retzip = (1, head cs) : retzip2
retzip2 = zip [2,3] (stream (tail cs))
retmap = (head cs, 1) : retmap2
retmap2 = map swap retzip2
p = (head cs : xs1, 1 : ys1)
(xs1,ys1) = unzip retmap2
bs = head cs : xs1
cs = 1 : ys1
bs = 1 : xs1
and we can now return the first cons cell of bs.
This repeats until we get [1,2,3] back out; note that each value goes
through both sides of the swap before coming out the 'front' again.
-- ryan
On Tue, Nov 1, 2011 at 1:30 PM, Captain Freako
Hi John,
I'm trying to use the GHCI debugger on this code:
20 instance ArrowLoop SF where 21 loop (SF f) = SF $ \as -> 22 let (bs, cs) = unzip (f (zip as (stream cs))) in bs 23 where stream ~(x:xs) = x : stream xs 24 25 swap :: (a,b) -> (b,a) 26 swap (x,y) = (y,x)
in order to watch the recursion of the `loop' function unfold. However, when I single step through the code, I never stop on line 22 (where I could, presumably, peek in at `bs' and `cs', in order to see them develop):
*SF> :break swap Breakpoint 1 activated at SF.hs:26:1-18 *SF> runSF (loop (arr swap)) [1,2,3] Stopped at SF.hs:26:1-18 _result :: (b, a) = _ [SF.hs:26:1-18] *SF> :step Stopped at SF.hs:26:14-18 _result :: (b, a) = _ x :: a = _ y :: b = _ [SF.hs:26:14-18] *SF> : [1Stopped at SF.hs:23:34-42 _result :: [a] = _ xs :: [a] = _ [SF.hs:23:34-42] *SF> : Stopped at SF.hs:23:13-42 _result :: [a] = _ [SF.hs:23:13-42] *SF> : Stopped at SF.hs:23:30-42 _result :: [a] = _ x :: a = _ xs :: [a] = _ [SF.hs:23:30-42] *SF> : (Pattern repeats.)
Do you have any advice?
Thanks, -db
On Mon, Oct 31, 2011 at 3:19 PM, John Lask
wrote: On 1/11/2011 1:35 AM, Captain Freako wrote:
you need to study ArrowLoop and understand that. In the code
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Captain Freako
-
John Lask
-
Ryan Ingram