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

Ryan Ingram ryani.spam at gmail.com
Tue Nov 1 23:55:05 CET 2011


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 <capn.freako at gmail.com>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 <jvlask at hotmail.com> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111101/2b8ffe45/attachment.htm>


More information about the Haskell-Cafe mailing list