{-# 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 ( -- $Remark -- * The Cont category -- $Category -- ** Category laws -- $Laws Cont -- * Utility functions , forget , withCont , lift , cont ) where import Prelude hiding (id, (.)) import Control.Category import Data.Monoid {-$Remark This package provides a new type for the Continuation catgory. Often is anyway easier to use plain functions. -} {-$Category The Continuation category is defined as follow: - object are functions of the type @f :: a -> b@, @g :: c -> d@. - arrows are functions of the type @t :: (a -> b) -> (c -> d)@. - the identity @'id'@ is the function that takes a function f and returns the same function. - the composition @.@ operator takes two functions @t1 :: (a -> b) -> (c -> d)@, @t2 :: (c -> d) -> (e -> f)@ and returns the function @t :: (a -> b) -> (e -> f)@. -} {-$Laws The category laws are trivially verified: - Identity law: @'Cont' f . 'Cont' 'id' = 'Cont' f . 'id' = 'Cont' 'f' = 'Cont' 'id' . f = 'Cont' 'id' . 'Cont' f@ - Associativity law: @('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)@ -} -- |A type for the Continuation category. newtype Cont f g = Cont (f -> g) instance Category Cont where (Cont f) . (Cont g) = Cont (f . g ) id = Cont id 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 -- |Creates a continuation cont :: (f -> g) -> Cont f g cont f = Cont f -- |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