Implicit parameters and Arrows/Yampa?

If I understand it correctly, implicit parameters in Haskell allow you to pass values to functions with explicitly adding a parameter to each of the functions being "called" (I appologize for my imperative terminology here. How would I say this correctly? Being "evaluated"?) The arrows always use tuples to group the input and output parameters, like: foo :: SF (Int,Int,Int) (Int,Int) foo = proc (x,y,z) -> do p <- cat -< (x,y) q <- dog -< z returnA -< (p,q) where cat = proc (x,y) -> returnA -< (x+y) dog = proc z -> returnA -< 10*z Suppose I don't want to explicitly pass the x and y parameters to the cat (and deeper) arrows, but make them implicit. I guess that would be impossible? I mean, I can't use implicit parameters language extension to make the arrow input parameters implicit? Thanks, Peter

On Sun, 2008-01-06 at 23:44 +0100, Peter Verswyvelen wrote:
If I understand it correctly, implicit parameters in Haskell allow you to pass values to functions with explicitly adding a parameter to each of the functions being “called” (I appologize for my imperative terminology here. How would I say this correctly? Being “evaluated”?)
No one is going to get upset if you use "call", but if you'd like, the more technical term in this context is "applied", instead of "call f passing x", we would say "apply f to x".
The arrows always use tuples to group the input and output parameters, like:
foo :: SF (Int,Int,Int) (Int,Int)
foo = proc (x,y,z) -> do
p <- cat -< (x,y)
q <- dog -< z
returnA -< (p,q)
where
cat = proc (x,y) -> returnA -< (x+y)
dog = proc z -> returnA -< 10*z
Suppose I don’t want to explicitly pass the x and y parameters to the cat (and deeper) arrows, but make them implicit. I guess that would be impossible? I mean, I can’t use implicit parameters language extension to make the arrow input parameters implicit?
Implicit parameters add an extra argument to a function conceptually. What you need is to "add an argument" to "SF" which implicit parameters don't know how to do since SF is just some data structure. One way to deal with this is the way you deal with the same problem in Haskell without implicit parameters. (I never use implicit parameters). In that case you would use the Reader monad (transformer). Similarly, you can use an equivalent Reader/Environment arrow transformer.

Derek Elkins wrote:
Implicit parameters add an extra argument to a function conceptually. What you need is to "add an argument" to "SF" which implicit parameters don't know how to do since SF is just some data structure. One way to deal with this is the way you deal with the same problem in Haskell without implicit parameters. (I never use implicit parameters). In that case you would use the Reader monad (transformer). Similarly, you can use an equivalent Reader/Environment arrow transformer.
Nice, I did not know that monad yet, thanks! But can it be combined together with the arrows do/proc syntax? How would that look like? Cheers, Peter

Peter Verswyvelen wrote:
Derek Elkins wrote:
you can use an equivalent Reader/Environment arrow transformer.
Nice, I did not know that monad yet, thanks!
But can it be combined together with the arrows do/proc syntax? How would that look like?
Something like this? ----8<---- module Main where import Control.Arrow import Control.Arrow.Operations import Control.Arrow.Transformer.Reader -- -- Standard list/stream arrow. -- newtype SF b c = SF { runSF :: [b] -> [c] } instance Arrow SF where arr f = SF (map f) SF f >>> SF g = SF (g . f) first (SF f) = SF (uncurry zip . (f *** id) . unzip) second (SF f) = SF (uncurry zip . (id *** f) . unzip) instance ArrowLoop SF where loop (SF f) = SF $ \as -> let (bs,cs) = unzip (f (zip as (stream cs))) in bs where stream ~(x:xs) = x:stream xs instance ArrowCircuit SF where delay x = SF (init . (x:)) -- -- Some state we want to pass around without manual plumbing. -- data AudioState = AudioState { sampleRate :: Double } runAudio state graph = proc p -> (| runReader (graph -< p) |) state -- -- Some unit generators for audio. -- wrap x = x - fromIntegral (floor x) -- phasor needs the sample rate phasor phase0 = proc hz -> do sr <- pure sampleRate <<< readState -< () rec accum <- delay (wrap phase0) -< wrap (accum + hz / sr) returnA -< accum -- osc doesn't need to know about sample rate osc phase0 = proc hz -> do phase <- phasor phase0 -< hz returnA -< cos (2 * pi * phase) -- -- Test it out. -- main = print (runSF (runAudio (AudioState{sampleRate=1000}) (osc 0)) (replicate 10 100)) ----8<----
Cheers, Peter
Thanks, Claude -- http://claudiusmaximus.goto10.org

Wow, amazing :) How long did it take you to write this little nice example? Examples like this are really welcome. It will take me a while to decipher, but that's the fun of Haskell, it's an endless learning experience! Here's a thought: I hardly know Haskell, but I can already write some code much faster and easier than I could do in C/C++ (and I've been programming 2 decades in that language, plus my colleagues tell me I'm pretty productive at it...). So I wonder what the productivity becomes when you can write code as quickly as Claude seemed to do here... Thanks, Peter PS: Also the scissors in your comment (--8<--), very original! Is this copyrighted? ;) -----Original Message----- From: Claude Heiland-Allen [mailto:claudiusmaximus@goto10.org] Something like this? ----8<---- module Main where import Control.Arrow import Control.Arrow.Operations import Control.Arrow.Transformer.Reader -- -- Standard list/stream arrow. -- newtype SF b c = SF { runSF :: [b] -> [c] } instance Arrow SF where arr f = SF (map f) SF f >>> SF g = SF (g . f) first (SF f) = SF (uncurry zip . (f *** id) . unzip) second (SF f) = SF (uncurry zip . (id *** f) . unzip) instance ArrowLoop SF where loop (SF f) = SF $ \as -> let (bs,cs) = unzip (f (zip as (stream cs))) in bs where stream ~(x:xs) = x:stream xs instance ArrowCircuit SF where delay x = SF (init . (x:)) -- -- Some state we want to pass around without manual plumbing. -- data AudioState = AudioState { sampleRate :: Double } runAudio state graph = proc p -> (| runReader (graph -< p) |) state -- -- Some unit generators for audio. -- wrap x = x - fromIntegral (floor x) -- phasor needs the sample rate phasor phase0 = proc hz -> do sr <- pure sampleRate <<< readState -< () rec accum <- delay (wrap phase0) -< wrap (accum + hz / sr) returnA -< accum -- osc doesn't need to know about sample rate osc phase0 = proc hz -> do phase <- phasor phase0 -< hz returnA -< cos (2 * pi * phase) -- -- Test it out. -- main = print (runSF (runAudio (AudioState{sampleRate=1000}) (osc 0)) (replicate 10 100)) ----8<----
Cheers, Peter
Thanks, Claude -- http://claudiusmaximus.goto10.org

Could I has one question? What is the purpose of the "stream" function in the ArrowLoop instance? Is it just to catch an unexpected [] at runtime?
----8<---- module Main where
import Control.Arrow import Control.Arrow.Operations import Control.Arrow.Transformer.Reader
-- -- Standard list/stream arrow. --
newtype SF b c = SF { runSF :: [b] -> [c] }
instance Arrow SF where arr f = SF (map f) SF f >>> SF g = SF (g . f) first (SF f) = SF (uncurry zip . (f *** id) . unzip) second (SF f) = SF (uncurry zip . (id *** f) . unzip)
instance ArrowLoop SF where loop (SF f) = SF $ \as -> let (bs,cs) = unzip (f (zip as (stream cs))) in bs where stream ~(x:xs) = x:stream xs
It looks like stream is (almost) an identity which would crash at runtime if it encountered a []. In particular it is equivalent to
where stream xs = head xs:stream (tail xs)
instance ArrowCircuit SF where delay x = SF (init . (x:))
-- -- Some state we want to pass around without manual plumbing. --
data AudioState = AudioState { sampleRate :: Double }
runAudio state graph = proc p -> (| runReader (graph -< p) |) state
-- -- Some unit generators for audio. --
wrap x = x - fromIntegral (floor x)
-- phasor needs the sample rate phasor phase0 = proc hz -> do sr <- pure sampleRate <<< readState -< () rec accum <- delay (wrap phase0) -< wrap (accum + hz / sr) returnA -< accum
-- osc doesn't need to know about sample rate osc phase0 = proc hz -> do phase <- phasor phase0 -< hz returnA -< cos (2 * pi * phase)
-- -- Test it out. --
main = print (runSF (runAudio (AudioState{sampleRate=1000}) (osc 0)) (replicate 10 100))
----8<----

ChrisK wrote:
Could I has one question? What is the purpose of the "stream" function in the ArrowLoop instance? Is it just to catch an unexpected [] at runtime?
instance ArrowLoop SF where loop (SF f) = SF $ \as -> let (bs,cs) = unzip (f (zip as (stream cs))) in bs where stream ~(x:xs) = x:stream xs
It looks like stream is (almost) an identity which would crash at runtime if it encountered a []. In particular it is equivalent to
where stream xs = head xs:stream (tail xs)
Not quite that, from a blog post of mine a while back: [snip] But then the trouble arrived - I suddenly noticed that the paper was using infinite sequences, not the finite sequences I was using myself. Trying to implement an ArrowLoop as per the paper led to horrible grief: -- instance ArrowLoop SF where -- loop (SF f) = SF (loop (unzip . f . uncurry zip)) The problem is that this is far too strict - on non-empty input it caused stack overflow crashes, which isn't exactly what I wanted. I found the solution in Programming With Arrows [1] (page 17), which involves some subtlety with lazy patterns: instance ArrowLoop SF where loop (SF f) = SF $ \as -> let (bs,cs) = unzip (f (zip as (stream cs))) in bs where stream ~(x:xs) = x:stream xs [unsnip] http://www.haskell.org/arrows/biblio.html#Hug05 [1] Hope this helps, Claude -- http://claudiusmaximus.goto10.org

Hello Peter, Monday, January 7, 2008, 10:59:30 PM, you wrote:
Here's a thought: I hardly know Haskell, but I can already write some code much faster and easier than I could do in C/C++ (and I've been programming 2 decades in that language, plus my colleagues tell me I'm pretty productive at it...). So I wonder what the productivity becomes when you can write code as quickly as Claude seemed to do here...
are you hear about 7-zip? it's rather popular high-ratio compressor. last two years i've developed my own archiver and outperformed 7-zip in functionality. when people ask why i don't joined 7-zip project instead (it's LGPL-licensed), i say what using C++ i will develop the same program 3x slower [1] http://freearc.sf.net -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Mon, 2008-01-07 at 17:24 +0100, Peter Verswyvelen wrote:
Derek Elkins wrote:
Implicit parameters add an extra argument to a function conceptually. What you need is to "add an argument" to "SF" which implicit parameters don't know how to do since SF is just some data structure. One way to deal with this is the way you deal with the same problem in Haskell without implicit parameters. (I never use implicit parameters). In that case you would use the Reader monad (transformer). Similarly, you can use an equivalent Reader/Environment arrow transformer.
Nice, I did not know that monad yet, thanks!
But can it be combined together with the arrows do/proc syntax? How would that look like?
Claude Heiland-Allen gave an example, I just want to clarify. The only reason I referred to monads is for analogy. You don't use the Reader monad or Reader monad transformer, you use an idea analogous to a monad transformer called an arrow transformer, which is what Claude does.
participants (5)
-
Bulat Ziganshin
-
ChrisK
-
Claude Heiland-Allen
-
Derek Elkins
-
Peter Verswyvelen