{-# LANGUAGE Safe #-} {-# LANGUAGE NoImplicitPrelude #-} module Protolude.Applicative ( orAlt, orEmpty, eitherA, purer, liftAA2, (<<*>>), ) where import Control.Applicative import Data.Bool (Bool) import Data.Either (Either (Left, Right)) import Data.Function ((.)) import Data.Monoid (Monoid (mempty)) orAlt :: (Alternative f, Monoid a) => f a -> f a orAlt :: f a -> f a orAlt f a f = f a f f a -> f a -> f a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> a -> f a forall (f :: * -> *) a. Applicative f => a -> f a pure a forall a. Monoid a => a mempty orEmpty :: Alternative f => Bool -> a -> f a orEmpty :: Bool -> a -> f a orEmpty Bool b a a = if Bool b then a -> f a forall (f :: * -> *) a. Applicative f => a -> f a pure a a else f a forall (f :: * -> *) a. Alternative f => f a empty eitherA :: (Alternative f) => f a -> f b -> f (Either a b) eitherA :: f a -> f b -> f (Either a b) eitherA f a a f b b = (a -> Either a b forall a b. a -> Either a b Left (a -> Either a b) -> f a -> f (Either a b) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> f a a) f (Either a b) -> f (Either a b) -> f (Either a b) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> (b -> Either a b forall a b. b -> Either a b Right (b -> Either a b) -> f b -> f (Either a b) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> f b b) purer :: (Applicative f, Applicative g) => a -> f (g a) purer :: a -> f (g a) purer = g a -> f (g a) forall (f :: * -> *) a. Applicative f => a -> f a pure (g a -> f (g a)) -> (a -> g a) -> a -> f (g a) forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> g a forall (f :: * -> *) a. Applicative f => a -> f a pure liftAA2 :: (Applicative f, Applicative g) => (a -> b -> c) -> f (g a) -> f (g b) -> f (g c) liftAA2 :: (a -> b -> c) -> f (g a) -> f (g b) -> f (g c) liftAA2 = (g a -> g b -> g c) -> f (g a) -> f (g b) -> f (g c) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 ((g a -> g b -> g c) -> f (g a) -> f (g b) -> f (g c)) -> ((a -> b -> c) -> g a -> g b -> g c) -> (a -> b -> c) -> f (g a) -> f (g b) -> f (g c) forall b c a. (b -> c) -> (a -> b) -> a -> c . (a -> b -> c) -> g a -> g b -> g c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 infixl 4 <<*>> (<<*>>) :: (Applicative f, Applicative g) => f (g (a -> b)) -> f (g a) -> f (g b) <<*>> :: f (g (a -> b)) -> f (g a) -> f (g b) (<<*>>) = (g (a -> b) -> g a -> g b) -> f (g (a -> b)) -> f (g a) -> f (g b) forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 g (a -> b) -> g a -> g b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b (<*>)