
The other day, I found myself writing the following code: data Property x y = forall s. Property s (x -> s -> s) (s -> y) step :: x -> Property x y -> Property x y step x (Property s f g) = Property (f x s) f g read :: Property x y -> y read (Property s _ g) = g s pure :: (x -> y) -> Property x y pure f = Property undefined const f fold :: (x -> y -> y) -> y -> Property x y fold f y = Property y f id fold1 :: (x -> x -> x) -> Property x x fold1 f = Property Nothing (\x mx -> maybe (Just x) (Just . f) mx) fromJust (>==>) :: Property x y -> Property y z -> Property x z p0 >==> p1 = Property (p0,p1) (\x (q0,q1) -> let w0 = step x q0 in (w0, step (read w0) q1)) (\(_,q1) -> (read q1)) (>==<) :: Property x y -> Property x y' -> Property x (y,y') p0 >==< p1 = Property (p0,p1) (\x (q0,q1) -> (step x q0, step x q1)) (\(q0,q1) -> (read q0, read q1)) sum = fold (+) 0 count = pure (const 1) >==> sum minimum = fold1 min maximum = fold1 max Have I just invented arrows? (And if so, why is the above code nowhere to be seen in the libraries?)

On Sat, Feb 20, 2010 at 3:30 AM, Andrew Coppin
Have I just invented arrows?
No... you have a data type which is *an* Arrow (probably/almost). The pure implementation bugs me because of its use of undefined. Might still be okay though. I would be more comfortable if it could not output until it has *some* input; i.e. data Property' a b = forall s. Property' s (a -> s -> (b,s)) Anyway, for yours: try to implement (.) :: Property b c -> Property a b -> Property a c, and first :: Property a b -> Property (a,c) (b,c). Then you will have an arrow. This is a Causal Commutative Arrow, even, similar to the kinds of things that are done in Yampa. It might be more recognizable as the non-recursive version of: newtype Property a b = Property b (a -> Property a b) Luke

Luke Palmer wrote:
On Sat, Feb 20, 2010 at 3:30 AM, Andrew Coppin
wrote: Have I just invented arrows?
No... you have a data type which is *an* Arrow (probably/almost).
Well, OK, that's kind of what I meant. ;-)
The pure implementation bugs me because of its use of undefined. Might still be okay though. I would be more comfortable if it could not output until it has *some* input;
Yes, this irritates me also.
i.e.
data Property' a b = forall s. Property' s (a -> s -> (b,s))
Hmm. I hadn't thought of that. I will work though the consequences and see what happens...
Anyway, for yours: try to implement (.) :: Property b c -> Property a b -> Property a c, and first :: Property a b -> Property (a,c) (b,c). Then you will have an arrow.
(.) = flip (>==>) first p = p >==< pure id
This is a Causal Commutative Arrow, even, similar to the kinds of things that are done in Yampa. It might be more recognizable as the non-recursive version of:
newtype Property a b = Property b (a -> Property a b)
...OK, I'm lost...

Anyway, for yours: try to implement (.) :: Property b c -> Property a b -> Property a c, and first :: Property a b -> Property (a,c) (b,c). Then you will have an arrow.
(.) = flip (>==>)
first p = p >==< pure id
No, not quite. \p -> p >==< pure id :: Property a b -> Property a (b, a) What you want is first p = (pure fst >==> p) >==< (pure snd) which has the required type.

Hi Andrew "Spot the difference" data Property x y = forall s. Property s (x -> s -> s) (s -> y) data Fold b c = forall a. F (a -> b -> a) a (a -> c) The later is from: http://squing.blogspot.com/2008/11/beautiful-folding.html Max Rabkin's is is closer to the original argument ordering of foldl. Best wishes Stephen

Stephen Tetley wrote:
Hi Andrew
"Spot the difference"
data Property x y = forall s. Property s (x -> s -> s) (s -> y) data Fold b c = forall a. F (a -> b -> a) a (a -> c)
The later is from: http://squing.blogspot.com/2008/11/beautiful-folding.html
Max Rabkin's is is closer to the original argument ordering of foldl.
Hmm. So somebody else has come up with the exact same solution to the same problem. My problem isn't exactly the same though. I'm interested in computing a "property" of a list, and recomputing it as elements are appended to the list. My "Property" structure provides an efficient way to do this, and to do so composibly. (E.g., if I want the maximum of the mean or something. Maximum and mean are both folds.) PS. Epic, epic comment spam.

On Sat, Feb 20, 2010 at 9:10 PM, Andrew Coppin
PS. Epic, epic comment spam.
Yeah, sorry. Every now and again I decide I should deal with it. Then I rediscover that it takes about four clicks to delete each comment. Basically, I leave my blog alone until I have something (hopefully) interesting to write. --Max
participants (4)
-
Andrew Coppin
-
Luke Palmer
-
Max Rabkin
-
Stephen Tetley