-- |A module for functors module Clean.Functor(Functor(..),Id(..),Const(..),(<$>),(<$),(<&>),void) where import qualified Prelude as P import Clean.Category import Clean.Classes import Clean.Monoid import Clean.Unit import Clean.Core import Data.Tree instance Functor [] where map f = f' where f' [] = [] ; f' (x:t) = f x:f' t instance Functor Tree where map f (Node a subs) = Node (f a) (map (map f) subs) -- |The Identity Functor newtype Id a = Id { getId :: a } deriving instance Nil a => Nil (Id a) deriving instance Monoid w => Monoid (Id w) instance Unit Id where pure = Id instance Functor Id instance Applicative Id instance Monad Id where Id a >>= k = k a -- |The Constant Functor newtype Const a b = Const { getConst :: a } deriving instance Nil a => Nil (Const a b) deriving instance Monoid w => Monoid (Const w a) instance Unit (Const a) where pure _ = Const undefined instance Functor (Const a) instance Applicative (Const a) instance Monad (Const a) where Const a >>= _ = Const a instance Functor (Either b) where map f = Left <|> Right . f instance Functor ((,) b) where map f (b,a) = (b,f a) instance Functor ((->) a) where map = (.) instance Functor IO instance Applicative IO instance Monad IO where (>>=) = (P.>>=) (<$>) = map x<&>f = map f x a <$ x = const a <$> x void :: Functor f => f a -> f () void = map (const ())