{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE PolyKinds #-}
#endif
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
#if (__GLASGOW_HASKELL__ >= 708) && (__GLASGOW_HASKELL__ < 802)
{-# LANGUAGE DeriveDataTypeable #-}
#endif
#if __GLASGOW_HASKELL__ >= 802
{-# LANGUAGE TypeInType #-}
#endif
module Control.Monad.Codensity
( Codensity(..)
, lowerCodensity
, codensityToAdjunction, adjunctionToCodensity
, codensityToRan, ranToCodensity
, codensityToComposedRep, composedRepToCodensity
, wrapCodensity
, improve
) where
import Control.Applicative
import Control.Monad (MonadPlus(..))
import qualified Control.Monad.Fail as Fail
import Control.Monad.Free
import Control.Monad.IO.Class
import Control.Monad.Reader.Class
import Control.Monad.State.Class
import Control.Monad.Trans.Class
import Data.Functor.Adjunction
import Data.Functor.Apply
import Data.Functor.Kan.Ran
import Data.Functor.Plus
import Data.Functor.Rep
#if (__GLASGOW_HASKELL__ >= 708) && (__GLASGOW_HASKELL__ < 800)
import Data.Typeable
#endif
#if __GLASGOW_HASKELL__ >= 802
import GHC.Exts (TYPE)
#endif
#if __GLASGOW_HASKELL__ >= 802
newtype Codensity (m :: k -> TYPE rep) a = Codensity
#else
newtype Codensity m a = Codensity
#endif
{ runCodensity :: forall b. (a -> m b) -> m b
}
#if (__GLASGOW_HASKELL__ >= 708) && (__GLASGOW_HASKELL__ < 800)
deriving Typeable
#endif
#if __GLASGOW_HASKELL__ >= 802
instance Functor (Codensity (k :: j -> TYPE rep)) where
#else
instance Functor (Codensity k) where
#endif
fmap f (Codensity m) = Codensity (\k -> m (\x -> k (f x)))
{-# INLINE fmap #-}
#if __GLASGOW_HASKELL__ >= 802
instance Apply (Codensity (f :: k -> TYPE rep)) where
#else
instance Apply (Codensity f) where
#endif
(<.>) = (<*>)
{-# INLINE (<.>) #-}
#if __GLASGOW_HASKELL__ >= 802
instance Applicative (Codensity (f :: k -> TYPE rep)) where
#else
instance Applicative (Codensity f) where
#endif
pure x = Codensity (\k -> k x)
{-# INLINE pure #-}
Codensity f <*> Codensity g = Codensity (\bfr -> f (\ab -> g (\x -> bfr (ab x))))
{-# INLINE (<*>) #-}
#if __GLASGOW_HASKELL__ >= 802
instance Monad (Codensity (f :: k -> TYPE rep)) where
#else
instance Monad (Codensity f) where
#endif
return = pure
{-# INLINE return #-}
m >>= k = Codensity (\c -> runCodensity m (\a -> runCodensity (k a) c))
{-# INLINE (>>=) #-}
instance Fail.MonadFail f => Fail.MonadFail (Codensity f) where
fail msg = Codensity $ \ _ -> Fail.fail msg
{-# INLINE fail #-}
instance MonadIO m => MonadIO (Codensity m) where
liftIO = lift . liftIO
{-# INLINE liftIO #-}
instance MonadTrans Codensity where
lift m = Codensity (m >>=)
{-# INLINE lift #-}
instance Alt v => Alt (Codensity v) where
Codensity m <!> Codensity n = Codensity (\k -> m k <!> n k)
{-# INLINE (<!>) #-}
instance Plus v => Plus (Codensity v) where
zero = Codensity (const zero)
{-# INLINE zero #-}
instance Alternative v => Alternative (Codensity v) where
empty = Codensity (\_ -> empty)
{-# INLINE empty #-}
Codensity m <|> Codensity n = Codensity (\k -> m k <|> n k)
{-# INLINE (<|>) #-}
#if __GLASGOW_HASKELL__ >= 710
instance Alternative v => MonadPlus (Codensity v)
#else
instance MonadPlus v => MonadPlus (Codensity v) where
mzero = Codensity (\_ -> mzero)
{-# INLINE mzero #-}
Codensity m `mplus` Codensity n = Codensity (\k -> m k `mplus` n k)
{-# INLINE mplus #-}
#endif
#if __GLASGOW_HASKELL__ >= 710
lowerCodensity :: Applicative f => Codensity f a -> f a
lowerCodensity a = runCodensity a pure
#else
lowerCodensity :: Monad m => Codensity m a -> m a
lowerCodensity a = runCodensity a return
#endif
{-# INLINE lowerCodensity #-}
codensityToAdjunction :: Adjunction f g => Codensity g a -> g (f a)
codensityToAdjunction r = runCodensity r unit
{-# INLINE codensityToAdjunction #-}
adjunctionToCodensity :: Adjunction f g => g (f a) -> Codensity g a
adjunctionToCodensity f = Codensity (\a -> fmap (rightAdjunct a) f)
{-# INLINE adjunctionToCodensity #-}
codensityToComposedRep :: Representable u => Codensity u a -> u (Rep u, a)
codensityToComposedRep (Codensity f) = f (\a -> tabulate $ \e -> (e, a))
{-# INLINE codensityToComposedRep #-}
composedRepToCodensity :: Representable u => u (Rep u, a) -> Codensity u a
composedRepToCodensity hfa = Codensity $ \k -> fmap (\(e, a) -> index (k a) e) hfa
{-# INLINE composedRepToCodensity #-}
codensityToRan :: Codensity g a -> Ran g g a
codensityToRan (Codensity m) = Ran m
{-# INLINE codensityToRan #-}
ranToCodensity :: Ran g g a -> Codensity g a
ranToCodensity (Ran m) = Codensity m
{-# INLINE ranToCodensity #-}
instance (Functor f, MonadFree f m) => MonadFree f (Codensity m) where
wrap t = Codensity (\h -> wrap (fmap (\p -> runCodensity p h) t))
{-# INLINE wrap #-}
instance MonadReader r m => MonadState r (Codensity m) where
get = Codensity (ask >>=)
{-# INLINE get #-}
put s = Codensity (\k -> local (const s) (k ()))
{-# INLINE put #-}
instance MonadReader r m => MonadReader r (Codensity m) where
ask = Codensity (ask >>=)
{-# INLINE ask #-}
local f m = Codensity $ \c -> ask >>= \r -> local f . runCodensity m $ local (const r) . c
{-# INLINE local #-}
improve :: Functor f => (forall m. MonadFree f m => m a) -> Free f a
improve m = lowerCodensity m
{-# INLINE improve #-}
wrapCodensity :: (forall a. m a -> m a) -> Codensity m ()
wrapCodensity f = Codensity (\k -> f (k ()))