Applicative functors with branch/choice ?

Let assume, that some computation takes argument and produces value Either a b. This computation may be represented in for different forms ==== computePure :: a -> Either b c computeMonad :: a -> m (Either b c) computeApplicative :: app a -> app (Either b c) computeArrow :: arr a (Either b c) ===== And now, having result, we need to execute several actions, making a choice, what actions to perform for Left and Right tags of Either. Pure function and monads are easy, as there is way to pattern-match on value and take actions depending on result. There is an extension to Arrow class that do the job -- ArrowChoice. However, I cannot find any way to make choice for Applicative. It seems that both Applicative and Alternative are not suited for it. So, it seems for me, that Applicative API should be extended with typeclass for making choice what actions to execute depending on result of some test (pattern matching). Is there any reasonable definition of such typeclass or clear explanation, why such typeclass is unneeded? The possible extension may look somehow like this: class Applicative a => Branching a where branch :: a (Either b c) -> (a b -> a d) -> (a c -> a d) -> a d

On 25/07/2012, Евгений Пермяков
Let assume, that some computation takes argument and produces value Either a b. This computation may be represented in for different forms
==== ... computeApplicative :: app a -> app (Either b c) ... =====
This seems rather more appropriate for Applicative: computeApplicative :: app (a -> Either b c)

On 2012-07-25 22:22, Евгений Пермяков wrote:
Let assume, that some computation takes argument and produces value Either a b. This computation may be represented in for different forms
==== computePure :: a -> Either b c
computeMonad :: a -> m (Either b c)
computeApplicative :: app a -> app (Either b c)
computeArrow :: arr a (Either b c) ===== And now, having result, we need to execute several actions, making a choice, what actions to perform for Left and Right tags of Either. Pure function and monads are easy, as there is way to pattern-match on value and take actions depending on result. There is an extension to Arrow class that do the job -- ArrowChoice. However, I cannot find any way to make choice for Applicative. It seems that both Applicative and Alternative are not suited for it.
So, it seems for me, that Applicative API should be extended with typeclass for making choice what actions to execute depending on result of some test (pattern matching). Is there any reasonable definition of such typeclass or clear explanation, why such typeclass is unneeded?
The possible extension may look somehow like this:
class Applicative a => Branching a where branch :: a (Either b c) -> (a b -> a d) -> (a c -> a d) -> a d
A nicer typeclass is perhaps the dual to applicative. Given a functor, (<*>) is equivalent to the function pair: class Functor f => Pairing f where pair :: (f a, f b) -> f (a,b) -- pair (x,y) = (,) <$> x <*> y -- (<*>) x y = ($) <$> pair (x,y) You can form the dual of pair by flipping the arrows and replacing products by sums, which gives: class Functor f => Branching f where liftEither :: f (Either a b) -> Either (f a, f b) Which looks almost equivalent to your Branching class. But I can't think of any non-trivial functors that are an instance of this class. Perhaps a better typeclass is the one where you keep the product on the result side: class Functor => Partitionable f where partitionEithers :: f (Either a b) -> (f a, f b) You can build some useful functions on top of partionEithers, such as `partition` and `filter`. filter = fst . partition partition pred = partitionEithers . fmap side where side x = if pred x then Left x else Right x I don't know if it is enough for your ArrowChoice instance. Twan

Евгений,
The possible extension may look somehow like this:
class Applicative a => Branching a where branch :: a (Either b c) -> (a b -> a d) -> (a c -> a d) -> a d
What about the following alternative that does not require an extension? import Control.Applicative eitherA :: Applicative f => f (a -> c) -> f (b -> c) -> f (Either a b) -> f c eitherA = liftA3 either Note by the way that the result of this function will execute the effects of all of its arguments (as you would expect for an Applicative functor). Dominique

On Wed, Jul 25, 2012 at 09:22:23PM +0100, Евгений Пермяков wrote:
So, it seems for me, that Applicative API should be extended with typeclass for making choice what actions to execute depending on result of some test (pattern matching). Is there any reasonable definition of such typeclass or clear explanation, why such typeclass is unneeded?
The possible extension may look somehow like this:
class Applicative a => Branching a where branch :: a (Either b c) -> (a b -> a d) -> (a c -> a d) -> a d
Do you have any instances in mind?

well... This code is both demonstration for use case and more sane class + instance typeclass name is selected quite randomly, may be native speaker will select a better one module Actuative where import Control.Applicative import System.IO import System.IO.Error -- | minimal complete definition : select class Applicative f => Actuative f where -- | select computation conditionally . Side effects of only one two alternative take place select :: f (Either a b) -- ^ selector -> f (a -> c) -- ^ first alternative -> f (b -> c) -- ^ second alternative -> f c -- | correct possible error correct :: f (Either a b) -> f (a -> b) -> f b correct i l = select i l (pure (\x -> x)) -- | similiar for select, but mimics ArrowChoice branch :: f (Either a b) -> f (a -> c) -> f (b -> d) -> f (Either c d) branch i l r = select i (pure (\f x -> Left (f x)) <*> l) (pure (\f x -> Right (f x)) <*> r) -- | execute only if Left onLeft :: f (Either a b) -> f (a -> c) -> f (Either c b) onLeft i l = branch i l (pure (\x -> x)) -- | execute only if Right onRight :: f (Either a b) -> f (b -> c) -> f (Either a c) onRight i r = branch i (pure (\x -> x)) r -- | This is streaming parser combinators for writing LR (k) grammars newtype Parse a = Parse { runParse :: Handle -> IO a } -- | this function is one of reasons. If EOF occurs, we should produce result. If not, we should continue parsing. Monadic interface, however, gives too much freedom. next :: Parse (Maybe Char) next = Parse $ \h -> catchIOError (fmap Just $ hGetChar h) (const $ return Nothing) instance Functor Parse where fmap f s = pure f <*> s instance Applicative Parse where pure a = Parse $ \_ -> return a (Parse l) <*> (Parse r) = Parse $ \h -> do lr <- l h rr <- r h return $ lr rr -- instance for Actuative. instance Actuative Parse where select (Parse i) (Parse l) (Parse r) = Parse $ \h -> do ir <- i h case ir of Left lv -> do lr <- l h return $ lr lv Right rv -> do rr <- r h return $ rr rv On 07/26/2012 12:48 PM, Ross Paterson wrote:
On Wed, Jul 25, 2012 at 09:22:23PM +0100, Евгений Пермяков wrote:
So, it seems for me, that Applicative API should be extended with typeclass for making choice what actions to execute depending on result of some test (pattern matching). Is there any reasonable definition of such typeclass or clear explanation, why such typeclass is unneeded?
The possible extension may look somehow like this:
class Applicative a => Branching a where branch :: a (Either b c) -> (a b -> a d) -> (a c -> a d) -> a d Do you have any instances in mind?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 26/07/12 12:40, Евгений Пермяков wrote:
class Applicative f => Actuative f where -- | select computation conditionally . Side effects of only one two alternative take place select :: f (Either a b) -- ^ selector -> f (a -> c) -- ^ first alternative -> f (b -> c) -- ^ second alternative -> f c
Can't you already define this function in terms of Applicative itself? I.e. select xs fs gs = sel <$> xs <*> fs <*> gs where sel (Left a) f _ = f a sel (Right b) _ g = g b I assume that your intent is that `select` behaves differently from the one I defined here. But you need to specify in what way. Suppose it should work like if-then-else. Then you would perhaps have these laws: select (Left <$> x) f g = f <$> x select (fmap swapEither x) f g = select x g f I think this is a useful class to have, and I would support adding something like it to the standard library. Perhaps the arguments should be swapped to the same order as either, to give class Functor f => Selective f where eitherF :: f (a -> c) -> f (b -> c) -> f (Either a b) -> f c The laws would then be: eitherF f g . fmap swapEither = eitherF g f eitherF f g . fmap Left = f eitherF f g . fmap Right = g -- follows from the other two laws every Monad is an instance via defaultEitherF ls rs xs = either ls rs =<< xs Twan

May be difference will be more clear with this example ? import Control.Monad.State instance (Functor m, Monad m) => Actuative (StateT s m) where select i l r = do iv <- i case iv of Left lv -> l >>= \lf -> return (lf lv) Right rv -> r >>= \rf -> return (rf rv) select' xs fs gs = sel <$> xs <*> fs <*> gs where sel (Left a) f _ = f a sel (Right b) _ g = g b increment :: Monad m => StateT Int m (() -> ()) increment = get >>= (put . (+1)) >> return (const ()) ==== the difference may be seen clearly, when you run in ghci *Actuative> runState (select' (return $ Left ()) increment (increment *> increment *> increment)) 0 ((),4) *Actuative> runState (select (return $ Left ()) increment (increment *> increment *> increment)) 0 ((),1) Not sure, what categorical concept is model for this type class On 07/26/2012 03:14 PM, Twan van Laarhoven wrote:
On 26/07/12 12:40, Евгений Пермяков wrote:
class Applicative f => Actuative f where -- | select computation conditionally . Side effects of only one two alternative take place select :: f (Either a b) -- ^ selector -> f (a -> c) -- ^ first alternative -> f (b -> c) -- ^ second alternative -> f c
Can't you already define this function in terms of Applicative itself? I.e.
select xs fs gs = sel <$> xs <*> fs <*> gs where sel (Left a) f _ = f a sel (Right b) _ g = g b
No. Well, a function with same type signature may be defined in terms of Applicative, as you demonstrated. However, look how select will work with instance for IO, defined like this instance Actuative IO where select i l r = do ir <- i case ir of Left lv -> do lf <- l return $ lf lv Right rv -> do rf <- r return $ rf rv As you can see, if I use select definition with Control.Applicative.<*>, I'll execute both l and r and the only choice will be, what result to drop. Both l and r, however, will be executed, and their side effects will take place. With select from my code only one action will be executed, depending on result of i, and only effects of one of actions (either l or r) will take place. I'm not sure, what categorical concept will correspond to this typeclass.
I assume that your intent is that `select` behaves differently from the one I defined here. But you need to specify in what way.
Suppose it should work like if-then-else. Then you would perhaps have these laws:
select (Left <$> x) f g = f <$> x select (fmap swapEither x) f g = select x g f
I think this is a useful class to have, and I would support adding something like it to the standard library. Perhaps the arguments should be swapped to the same order as either, to give
class Functor f => Selective f where eitherF :: f (a -> c) -> f (b -> c) -> f (Either a b) -> f c
The laws would then be:
eitherF f g . fmap swapEither = eitherF g f eitherF f g . fmap Left = f eitherF f g . fmap Right = g -- follows from the other two laws
every Monad is an instance via
defaultEitherF ls rs xs = either ls rs =<< xs
Twan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 26/07/12 13:58, Евгений Пермяков wrote:
As you can see, if I use select definition with Control.Applicative.<*>, I'll execute both l and r and the only choice will be, what result to drop. Both l and r, however, will be executed, and their side effects will take place. With select from my code only one action will be executed, depending on result of i, and only effects of one of actions (either l or r) will take place.
I realize that, and that is why I insisted on laws to formalize this. Your instance for IO is a special case of a function that works for any Monad: defaultEitherF :: (Functor f, Monad f) => f (a -> c) -> f (b -> c) -> f (Either a b) -> f c defaultEitherF ml mr mx = either (ml <$$>) (mr <$$>) =<< mx where (<$$>) :: Functor f => f (a -> b) -> a -> f b f <$$> x = ($ x) <$> f (the version of this function in my previous post was not correct)
I'm not sure, what categorical concept will correspond to this typeclass.
Well, this type class kind of corresponds to the functionality of ArrowChoice. I believe that class corresponds to a (symmetric) monoidal structure on the dual category. Plus a whole bunch of junk you get from its super classes. Twan
participants (5)
-
Dominique Devriese
-
Ross Paterson
-
Strake
-
Twan van Laarhoven
-
Евгений Пермяков