 
            I'm reading through http://www.cse.chalmers.se/~rjmh/afp-arrows.pdf I was following it up until this example in the section about flip-flops: class Arrow arr => ArrowLoop arr where loop :: arr (a,c) (b,c) -> arr a b instance ArrowLoop (->) where loop f a = b where (b,c) = f (a,c) Although I've never seen a function declaration like this, but I think I get it. Because f :: (a, c) -> (b, c) then then loop f :: ((a, c) -> (b, c)) -> (a -> b) which is the same as ((a, c) -> (b, c)) -> a -> b. However, I don't see where the c comes from in f (a,c). Is this a mistake or am I missing something? A friend of mine realized that this is just a recursive definition so f (a, c) == f (a, snd $ f (a, snd $ f (a, ...))). I don't really understand this definition. I can see how it compiles, but I don't see how it would ever produce a legitimate value. Do I have to assume that f never evaluates the second element in the pair and just passes it through?
 
            Michael Baker 
class Arrow arr => ArrowLoop arr where loop :: arr (a,c) (b,c) -> arr a b
instance ArrowLoop (->) where loop f a = b where (b,c) = f (a,c)
Although I've never seen a function declaration like this, but I think I get it. Because f :: (a, c) -> (b, c) then then loop f :: ((a, c) -> (b, c)) -> (a -> b) which is the same as ((a, c) -> (b, c)) -> a -> b.
However, I don't see where the c comes from in f (a,c). Is this a mistake or am I missing something?
This is indeed legitimate and you are missing something. This confusion is the reason I prefer to call this "feedback". Part of the result is fed back as input, which of course requires laziness to work. ArrowLoop is the arrow version of MonadFix: class (Monad m) => MonadFix m where mfix :: (a -> m a) -> m a In fact the ArrowLoop instance of Kleisli is defined in terms of MonadFix (I leave reproducing this as an exercise for you). Of course all this doesn't help understanding the purpose of ArrowLoop, so let me introduce an arrow commonly used in FRP, the automaton arrow: newtype Auto a b = Auto { stepAuto :: a -> (b, Auto a b) } You can read this type literally: It is basically a function from input to result, but along with the result it returns a new version of itself. Calling such a function I call 'stepping'. Here is a counter automaton that ignores its input: countFrom :: Integer -> Auto a Integer countFrom x = Auto (const (x, countFrom (x + 1))) The automaton 'countFrom 10', when stepped, will return 10 and a new version of itself, namely 'countFrom 11'. When you step that one it will return 11 and a new version of itself, namely 'countFrom 12': stepAuto (countFrom 10) () = (10, countFrom 11) stepAuto (countFrom 11) () = (11, countFrom 12) {- ... -} To make a use case for ArrowLoop let's write a slightly more interesting version: sumFrom :: Integer -> Auto Integer Integer sumFrom x = Auto (\dx -> (x, sumFrom (x + dx))) This one uses its input value: stepAuto (sumFrom 10) 5 = (10, sumFrom (10 + 5)) stepAuto (sumFrom 15) 2 = (15, sumFrom (15 + 2)) stepAuto (sumFrom 17) (-1) = (17, sumFrom (17 - 1)) {- ... -} It uses its input value as a delta, so it really corresponds to a running sum or in Haskell terms to a 'scanl (+)'. What makes sumFrom more powerful than scanl (+) is that you can easily use sumFrom's result as its own input: loop ((\x -> (x, x)) ^<< sumFrom 1 <<^ snd) What happens now? Let's examine this: stepAuto (loop ((\x -> (x, x)) ^<< sumFrom 1 <<^ snd)) () = (1, loop ((\x -> (x, x)) ^<< sumFrom (1 + 1) <<^ snd)) stepAuto (loop ((\x -> (x, x)) ^<< sumFrom 2 <<^ snd)) () = (2, loop ((\x -> (x, x)) ^<< sumFrom (2 + 2) <<^ snd)) stepAuto (loop ((\x -> (x, x)) ^<< sumFrom 4 <<^ snd)) () = (4, loop ((\x -> (x, x)) ^<< sumFrom (4 + 4) <<^ snd)) stepAuto (loop ((\x -> (x, x)) ^<< sumFrom 8 <<^ snd)) () = (8, loop ((\x -> (x, x)) ^<< sumFrom (8 + 8) <<^ snd)) So it produces the sequence [1, 2, 4, 8, 16, ...]. Now this was a contrived example. Is there an actual real world use case? Of course! In AFRP you actually use this quite often. Imagine a particle system. A single particle may be defined like this: particle :: Auto a Particle But that would mean that a particle does not interact with other particles. How do you make it? particle :: Auto [Particle] Particle Now the particle can respond to other particles in the system. How do you actually make a particle system in the first place? The following is a basic way to do it: multicast :: [Auto a b] -> Auto a [b] It takes a list of automata producing a particles and turns it into an automaton that produces a list of particles. Now you can express a particle system: multicast particle :: Auto [Particle] [Particle] This looks promising, but one problem is left. You want the particles to interact with each other instead of a separate particle system. How do you do this? Simple: Feed the particles back. This is easiest to express in do/rec notation: rec ps <- multicast particle -< ps id -< ps Now every particle gets fed all particles in the system including itself and you're done. Welcome to the wonderful world of FRP. =) Of course you don't have to reinvent the wheel. If you like this coding style, have a look at the Netwire [1] library and its tutorial [2]. You may also be interested in my arrow tutorial [3], which explains the automaton arrow in depth. I hope this helps. [1]: http://hackage.haskell.org/package/netwire [2]: <http://hackage.haskell.org/packages/archive/netwire/latest/doc/ html/Control-Wire.html> [3]: http://ertes.de/new/tutorials/arrows.html Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.
participants (2)
- 
                 Ertugrul Söylemez Ertugrul Söylemez
- 
                 Michael Baker Michael Baker