[Haskell-cafe] ANNOUNCE: arrow-list. List arrows for Haskell.
Sebastian Fischer
fischer at nii.ac.jp
Sun Nov 7 23:33:33 EST 2010
to answer my own question:
On Nov 7, 2010, at 8:33 PM, Sebastian Fischer wrote:
> Can you, for example, define a `perm` arrow that yields every
> permutation of it's input? Monadic implementations look like they
> need `>>=` but there may be another way..
A `perm` arrow can be defined in the "usual" way using the list-arrow
package:
{-# LANGUAGE TypeOperators #-}
import Control.Arrow
import Control.Arrow.ArrowList
perm :: (ArrowList (~>), ArrowPlus (~>)) => [a] ~> [a]
perm = isA null <+> (uncons >>> second perm >>> insert)
insert :: (ArrowList (~>), ArrowPlus (~>)) => (a,[a]) ~> [a]
insert = cons <+> (second uncons >>> rearrange >>> second insert
>>> cons)
where rearrange = assocL >>> first swap >>> assocR
It may be possible to do this with `ArrowChoice` only, that is,
without resorting to the operations of `ArrowList`, but they looked
simpler.
In order to support the above, we need a bunch of auxiliary arrows.
First, list con- and destructors:
cons :: Arrow (~>) => (a,[a]) ~> [a]
cons = arr (uncurry (:))
uncons :: ArrowList (~>) => [a] ~> (a,[a])
uncons = isA (not . null) >>> arr (\ (x:xs) -> (x,xs))
Second (and more annoyingly), "reordering" arrows:
swap :: Arrow (~>) => (a,b) ~> (b,a)
swap = arr (\ (x,y) -> (y,x))
assocL :: Arrow (~>) => (a,(b,c)) ~> ((a,b),c)
assocL = arr (\ (x,(y,z)) -> ((x,y),z))
assocR :: Arrow (~>) => ((a,b),c) ~> (a,(b,c))
assocR = arr (\ ((x,y),z) -> (x,(y,z)))
This is my first program with arrows so it might be unnecessarily
complicated. Is there a more elegant way?
I wonder how badly my use of `arr` influences how the program can be
optimized. I hope it's still better than just using
perm = arrL perms
where perms :: [a] -> [[a]]
perms = ...
;o)
Sebastian
More information about the Haskell-Cafe
mailing list