Ashley Yakeley wrote:
> Wolfgang Jeltsch wrote:
>
> > This brings me to another point. One year ago we had a discussion on The
> > Haskell Mailing List concerning arrows. (The subject of the mails was just
> > "arrows".) The point was that it seemed strange to me that first and second
> > are included in the basic arrow class Arrow while left and right have their
> > extra class ArrowChoice. Not only that it seemed strange to me but it made
> > impossible to make Parser baseMonad an instance of Arrow. Parser baseMonad
> > has nice implementations of pure and (>>>) but none of first or second.
>
> I agree. My own Arrow module hierarchy looks more or less like this:
>
>   class Compositor comp where [...]
>   class (Compositor arrow) => Arrow arrow where [...]
>   class (Arrow arrow) => ProductArrow arrow where [...]
>   class (Arrow arrow) => CoproductArrow arrow where [...]
>   class (ProductArrow arrow,CoproductArrow arrow) => FullArrow arrow
>   instance (ProductArrow arrow,CoproductArrow arrow) => FullArrow arrow
>   class (Arrow arrow) => ArrowFix arrow where [...]
>   class (FullArrow arrow) => ApplyArrow arrow where [...]


On that topic, see below for what mine looks like
(from HXML, <URL: http://www.flightlab.com/~joe/hxml/ >).

I started off with Hughes' conventions, but for some
reason could never remember the difference between &&& and ***,
or between ||| and +++.  I found &&&, >&<, |||, >|< to have
better mnemonic value.  This also frees up +++ for ArrowPlus,
which -- in HXML applications -- is frequently used and should
thus be easy to type.

When using the ArrowChoice operators, I kept tripping over all
the 'Either' coproduct types, so added some syntactic sugar
(borrowed from HaXML):

data Choice a = a :> a
class (Arrow a) => ArrowChoice a where
        [ ... ]
        ( ?>)   :: (b -> Bool) -> Choice (a b c) -> a b c
        (>?>)   :: a b Bool    -> Choice (a b c) -> a b c

I found "p ?> f :> g" much more pleasant to use.

(I also like the idea of splitting the product operators out of
the base Arrow class -- will consider doing that in my library).

--

infixr 5 +++
infixr 3 >&<, &&&
infixr 2 >|<, |||, ?>, >?>, :>
infixl 1 >>>

class Arrow a where
        arr     :: (b -> c) -> a b c
        (>>>)   :: a b c -> a c d -> a b d
        apfst   :: a b c -> a (b,x) (c,x)
        apsnd   :: a b c -> a (x,b) (x,c)
        (>&<)   :: a b c -> a d e -> a (b,d) (c,e)
        (&&&)   :: a b c -> a b d -> a b (c,d)
        liftA2  :: (b -> c -> d) -> a e b -> a e c -> a e d
        aConst  :: c -> a b c
        idArrow :: a b b
        -- Minimal implementation: arr, >>>,  apfst or >&<

data Choice a = a :> a
class (Arrow a) => ArrowChoice a where
        apl     :: a b c -> a (Either b d) (Either c d)
        apr     :: a b c -> a (Either d b) (Either d c)
        (>|<)   :: a b c -> a d e -> a (Either b d) (Either c e)
        (|||)   :: a b c -> a d c -> a (Either b d) c
        ( ?>)   :: (b -> Bool) -> Choice (a b c) -> a b c
        (>?>)   :: a b Bool    -> Choice (a b c) -> a b c
        -- Minimal implementation: >|< or apl

class (Arrow a) => ArrowApply a where
        app :: a (a b c,b) c

class (Arrow a) => ArrowZero a where
        aZero  :: a b c
        aMaybe :: a (Maybe c) c
        aGuard :: (b -> Bool) -> a b b

class (Arrow a) => ArrowPlus a where
        (+++) :: a b c -> a b c -> a b c



--Joe English

  [EMAIL PROTECTED]
_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to