module Control.Applicative (
Applicative(..),
Alternative(..),
Const(..), WrappedMonad(..), WrappedArrow(..), ZipList(..),
(<$>), (<$), (<**>),
liftA, liftA2, liftA3,
optional,
) where
import Prelude hiding (id,(.))
import Control.Category
import Control.Arrow
import Control.Monad (liftM, ap, MonadPlus(..))
import Control.Monad.ST.Safe (ST)
import qualified Control.Monad.ST.Lazy.Safe as Lazy (ST)
import Data.Functor ((<$>), (<$))
import Data.Monoid (Monoid(..))
import Data.Proxy
import Text.ParserCombinators.ReadP (ReadP)
import Text.ParserCombinators.ReadPrec (ReadPrec)
import GHC.Conc (STM, retry, orElse)
import GHC.Generics
infixl 3 <|>
infixl 4 <*>, <*, *>, <**>
class Functor f => Applicative f where
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
(*>) :: f a -> f b -> f b
(*>) = liftA2 (const id)
(<*) :: f a -> f b -> f a
(<*) = liftA2 const
class Applicative f => Alternative f where
empty :: f a
(<|>) :: f a -> f a -> f a
some :: f a -> f [a]
some v = some_v
where
many_v = some_v <|> pure []
some_v = (:) <$> v <*> many_v
many :: f a -> f [a]
many v = many_v
where
many_v = some_v <|> pure []
some_v = (:) <$> v <*> many_v
instance Applicative Maybe where
pure = return
(<*>) = ap
instance Alternative Maybe where
empty = Nothing
Nothing <|> r = r
l <|> _ = l
instance Applicative [] where
pure = return
(<*>) = ap
instance Alternative [] where
empty = []
(<|>) = (++)
instance Applicative IO where
pure = return
(<*>) = ap
instance Applicative (ST s) where
pure = return
(<*>) = ap
instance Applicative (Lazy.ST s) where
pure = return
(<*>) = ap
instance Applicative STM where
pure = return
(<*>) = ap
instance Alternative STM where
empty = retry
(<|>) = orElse
instance Applicative ((->) a) where
pure = const
(<*>) f g x = f x (g x)
instance Monoid a => Applicative ((,) a) where
pure x = (mempty, x)
(u, f) <*> (v, x) = (u `mappend` v, f x)
instance Applicative (Either e) where
pure = Right
Left e <*> _ = Left e
Right f <*> r = fmap f r
instance Applicative ReadP where
pure = return
(<*>) = ap
instance Alternative ReadP where
empty = mzero
(<|>) = mplus
instance Applicative ReadPrec where
pure = return
(<*>) = ap
instance Alternative ReadPrec where
empty = mzero
(<|>) = mplus
instance Arrow a => Applicative (ArrowMonad a) where
pure x = ArrowMonad (arr (const x))
ArrowMonad f <*> ArrowMonad x = ArrowMonad (f &&& x >>> arr (uncurry id))
instance ArrowPlus a => Alternative (ArrowMonad a) where
empty = ArrowMonad zeroArrow
ArrowMonad x <|> ArrowMonad y = ArrowMonad (x <+> y)
newtype Const a b = Const { getConst :: a }
deriving (Generic, Generic1)
instance Functor (Const m) where
fmap _ (Const v) = Const v
instance Monoid a => Monoid (Const a b) where
mempty = Const mempty
mappend (Const a) (Const b) = Const (mappend a b)
instance Monoid m => Applicative (Const m) where
pure _ = Const mempty
Const f <*> Const v = Const (f `mappend` v)
newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a }
deriving (Generic, Generic1)
instance Monad m => Functor (WrappedMonad m) where
fmap f (WrapMonad v) = WrapMonad (liftM f v)
instance Monad m => Applicative (WrappedMonad m) where
pure = WrapMonad . return
WrapMonad f <*> WrapMonad v = WrapMonad (f `ap` v)
instance Monad m => Monad (WrappedMonad m) where
return = WrapMonad . return
a >>= f = WrapMonad (unwrapMonad a >>= unwrapMonad . f)
instance MonadPlus m => Alternative (WrappedMonad m) where
empty = WrapMonad mzero
WrapMonad u <|> WrapMonad v = WrapMonad (u `mplus` v)
newtype WrappedArrow a b c = WrapArrow { unwrapArrow :: a b c }
deriving (Generic, Generic1)
instance Arrow a => Functor (WrappedArrow a b) where
fmap f (WrapArrow a) = WrapArrow (a >>> arr f)
instance Arrow a => Applicative (WrappedArrow a b) where
pure x = WrapArrow (arr (const x))
WrapArrow f <*> WrapArrow v = WrapArrow (f &&& v >>> arr (uncurry id))
instance (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) where
empty = WrapArrow zeroArrow
WrapArrow u <|> WrapArrow v = WrapArrow (u <+> v)
newtype ZipList a = ZipList { getZipList :: [a] }
deriving (Show, Eq, Ord, Read, Generic, Generic1)
instance Functor ZipList where
fmap f (ZipList xs) = ZipList (map f xs)
instance Applicative ZipList where
pure x = ZipList (repeat x)
ZipList fs <*> ZipList xs = ZipList (zipWith id fs xs)
instance Applicative Proxy where
pure _ = Proxy
_ <*> _ = Proxy
(<**>) :: Applicative f => f a -> f (a -> b) -> f b
(<**>) = liftA2 (flip ($))
liftA :: Applicative f => (a -> b) -> f a -> f b
liftA f a = pure f <*> a
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
liftA2 f a b = f <$> a <*> b
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 f a b c = f <$> a <*> b <*> c
optional :: Alternative f => f a -> f (Maybe a)
optional v = Just <$> v <|> pure Nothing