
2009/11/22 Isaac Dupree
Sorry to take offense :-) maybe I was being too modest?
It seems Arrows are a necessary abstraction for a couple very particular world-views/paradigms, and don't fit very well with a lot of other stuff.
Hello All I wouldn't go quite as far as saying Arrows are misfits, but in Isaac's defence, if all you have are pure functions, then arrows are just a wee bit, erm, boring. In Philip's original message he happened to be representing his data as a pair, so second worked fine as a projection/application function, vis: *Arrows> second (\x -> "fish") (10,20) (10,"fish") But of course it doesn't work as a projection/application function for triples (sorry I lack a better term for projection/application): *Arrows> second (\x -> "chips") (10,20,30) <interactive>:1:0: Couldn't match expected type `(t, t1, t2)' against inferred type `(d, b)' In the expression: second (\ x -> "chips") (10, 20, 30) In the definition of `it': it = second (\ x -> "chips") (10, 20, 30) Nor would it work if Philip had defined his own data type. Also for pure functions the derived operators (>>^) and (^>>) become (.), and (<<^) & (^<<) are become reverse composition - which was sometimes called (##) but now seems categorized as (<<<) . The code below is a bit superfluous to the discussion, but it does define the arrow operations for pure functions with the type constructor simplified to (->), I occasionally do the Arrow combinators longhand when I can't remember which Arrow combinator does what. Best wishes Stephen
module ArrowLonghand where
import Control.Arrow
arr :: (b -> c) -> a b c fun_arr :: a b c -> (b -> c) where a = (->)
fun_arr :: (b -> c) -> (b -> c) fun_arr f = f
arr's definition is clearly identity, but specialized to functions
alt_fun_arr :: (b -> c) -> (b -> c) alt_fun_arr = id
first :: a b c -> a (b, d) (c, d) fun_first :: a b c -> a (b,d) (c,d) where a = (->)
fun_first :: (b -> c) -> (b,d) -> (c,d) fun_first f (x,y) = (f x, y)
second :: a b c -> a (d, b) (d, c) fun_second :: a b c -> a (d,b) (d,c) where a = (->)
fun_second :: (b -> c) -> (d,b) -> (d,c) fun_second f (x,y) = (x, f y)
(***) :: a b c -> a b' c' -> a (b, b') (c, c') fun_starstarstar :: a b c -> a b' c' -> a (b,b') (c,c') where a = (->)
fun_starstarstar :: (b -> c) -> (b' -> c') -> (b,b') -> (c,c') fun_starstarstar f g (x,y) = (f x, g y)
Funnily enough, (***) is not unlike prod from Jeremy Gibbons 'Pair Calculus': http://www.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/acmmpc-calc...
prod :: (b -> c) -> (b' -> c') -> (b,b') -> (c,c') prod f g = fork (f . fst, g . snd)
(&&&) :: a b c -> a b c' -> a b (c, c') fun_ampampamp :: a b c -> a b c' -> a b (c,c') where a = (->)
fun_ampampamp :: (b -> c) -> (b -> c') -> b -> (c,c') fun_ampampamp f g x = (f x, g x)
Funnily enough, (&&&) is not unlike fork from the Pair Calculus...
fork :: (b -> c, b -> c') -> b -> (c,c') fork (f,g) a = (f a, g a)
pair_first :: (b -> c) -> (b,d) -> (c,d) pair_first f = f `prod` id
pair_second :: (b -> c) -> (d,b) -> (d,c) pair_second g = id `prod` g
-------------------------------------------------------------------------------- (^>>) :: Arrow a => (b -> c) -> a c d -> a b d
preCompLR :: (b -> c) -> (c -> d) -> (b -> d) preCompLR f g = \x -> g (f x)
(>>^) :: Arrow a => a b c -> (c -> d) -> a b d
postCompLR :: (b -> c) -> (c -> d) -> (b -> d) postCompLR f g = \x -> g (f x)
(^>>) and (>>^) are the same for functions. -- reverse (<<^) :: Arrow a => a c d -> (b -> c) -> a b d
preCompRL :: (c -> d) -> (b -> c) -> (b -> d) preCompRL f g = \x -> f (g x)
(^<<) :: Arrow a => (c -> d) -> a b c -> a b d
postCompRL :: (c -> d) -> (b -> c) -> (b -> d) postCompRL f g = \x -> f (g x)