{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE GADTs #-}
#if __GLASGOW_HASKELL__ >= 707
{-# LANGUAGE DeriveDataTypeable #-}
#endif
{-# OPTIONS_GHC -Wall #-}
#include "free-common.h"
module Control.Applicative.Free
(
Ap(..)
, runAp
, runAp_
, liftAp
, iterAp
, hoistAp
, retractAp
) where
import Control.Applicative
import Control.Comonad (Comonad(..))
import Data.Functor.Apply
import Data.Typeable
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif
data Ap f a where
Pure :: a -> Ap f a
Ap :: f a -> Ap f (a -> b) -> Ap f b
#if __GLASGOW_HASKELL__ >= 707
deriving Typeable
#endif
runAp :: Applicative g => (forall x. f x -> g x) -> Ap f a -> g a
runAp _ (Pure x) = pure x
runAp u (Ap f x) = flip id <$> u f <*> runAp u x
runAp_ :: Monoid m => (forall a. f a -> m) -> Ap f b -> m
runAp_ f = getConst . runAp (Const . f)
instance Functor (Ap f) where
fmap f (Pure a) = Pure (f a)
fmap f (Ap x y) = Ap x ((f .) <$> y)
instance Apply (Ap f) where
Pure f <.> y = fmap f y
Ap x y <.> z = Ap x (flip <$> y <.> z)
instance Applicative (Ap f) where
pure = Pure
Pure f <*> y = fmap f y
Ap x y <*> z = Ap x (flip <$> y <*> z)
instance Comonad f => Comonad (Ap f) where
extract (Pure a) = a
extract (Ap x y) = extract y (extract x)
duplicate (Pure a) = Pure (Pure a)
duplicate (Ap x y) = Ap (duplicate x) (extend (flip Ap) y)
liftAp :: f a -> Ap f a
liftAp x = Ap x (Pure id)
{-# INLINE liftAp #-}
iterAp :: Functor g => (g a -> a) -> Ap g a -> a
iterAp algebra = go
where go (Pure a) = a
go (Ap underlying apply) = algebra (go . (apply <*>) . pure <$> underlying)
hoistAp :: (forall a. f a -> g a) -> Ap f b -> Ap g b
hoistAp _ (Pure a) = Pure a
hoistAp f (Ap x y) = Ap (f x) (hoistAp f y)
retractAp :: Applicative f => Ap f a -> f a
retractAp (Pure a) = pure a
retractAp (Ap x y) = x <**> retractAp y
#if __GLASGOW_HASKELL__ < 707
instance Typeable1 f => Typeable1 (Ap f) where
typeOf1 t = mkTyConApp apTyCon [typeOf1 (f t)] where
f :: Ap f a -> f a
f = undefined
apTyCon :: TyCon
#if __GLASGOW_HASKELL__ < 704
apTyCon = mkTyCon "Control.Applicative.Free.Ap"
#else
apTyCon = mkTyCon3 "free" "Control.Applicative.Free" "Ap"
#endif
{-# NOINLINE apTyCon #-}
#endif