[Haskell-cafe] Applicative functors with branch/choice ?

Евгений Пермяков permeakra at gmail.com
Thu Jul 26 13:58:09 CEST 2012


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list