{-# LANGUAGE FlexibleInstances #-} ----------------------------------------------------------------------------- {- | Module : Control.Category.Cont Description : Provides a type for Continuation Passing Style development Copyright : (c) Matteo Provenzano 2015 License : BSD-style (see the LICENSE file in the distribution) Maintainer : matteo.provenzano@alephdue.com Stability : experimental Portability : portable -} module Control.Category.Cont (Cont, forget) where import Prelude hiding (id, (.)) import Control.Category import Data.Monoid newtype Cont f g = Cont (f -> g) instance Category Cont where (Cont f) . (Cont g) = Cont (f . g ) id = Cont id -- | Identity law: -- -- prop> Cont f . Cont id = Cont f . id = Cont f = Cont id . f = Cont id . Cont f -- | Associativity law: -- -- prop> (Cont f . Cont g) . Cont h = Cont (f . g) . Cont h = Cont (f . g . h) = Cont (f . (g . h)) = Cont f . Cont (g .h) = Cont f . (Cont g . Cont h) instance Monoid a => Monoid (Cont t (f -> a)) where Cont f `mappend` Cont g = Cont $ \h x -> f h x `mappend` g h x mempty = Cont $ \h x -> mempty -- |It 'forgets' the continuation. forget :: Cont (a -> a) (b -> c) -> b -> c forget (Cont f) = f id -- |Apply a function to the continuation. withCont :: (b -> c) -> Cont (a -> b) (a -> c) withCont f = Cont $ \g -> f . g -- |Lift the continuation into a Monad. lift :: Monad m => Cont (a -> b) (a -> m b) lift = withCont return