{-# LANGUAGE StandaloneDeriving, GeneralizedNewtypeDeriving #-} module Data.TrieMap.Applicative where import Control.Applicative import Control.Monad import Data.Monoid newtype Id a = Id {unId :: a} deriving instance Functor First deriving instance Functor Last deriving instance Monad First deriving instance Monad Last instance Applicative Id where pure = Id Id f <*> Id x = Id (f x) instance Functor Id where fmap f (Id x) = Id (f x) instance MonadPlus First where mzero = mempty mplus = mappend instance MonadPlus Last where mzero = mempty mplus = mappend -- instance Monad First where -- return x = First (Just x) -- First Nothing >>= _ = First Nothing -- First (Just x) >>= k = k x -- -- instance Monad Last (.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d (f .: g) x y = f (g x y) (<.>) :: Functor f => (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g (<.:>) :: Functor f => (c -> d) -> (a -> b -> f c) -> a -> b -> f d (f <.:> g) x y = f <$> g x y