Kriens-0.1.0.0: Category for Continuation Passing Style

Copyright(c) Matteo Provenzano 2015
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainermatteo.provenzano@alephdue.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Category.Cont

Contents

Description

 

Synopsis

The Cont 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).

Category laws

The category laws are trivially verified:

data Cont f g Source

A type for the Continuation category.

Instances

Category * Cont Source 
Monoid a => Monoid (Cont t (f -> a)) Source 

Utility functions

forget :: Cont (a -> a) (b -> c) -> b -> c Source

Forgets the continuation.

withCont :: (b -> c) -> Cont (a -> b) (a -> c) Source

Apply a function to the continuation.

lift :: Monad m => Cont (a -> b) (a -> m b) Source

Lift the continuation into a Monad.

cont :: (f -> g) -> Cont f g Source

Creates a continuation

Example: Composable sorter

Here is an example how to use the Cont category to compose a custom sorter:

import Prelude hiding (id, (.))
import Control.Category
import Control.Category.Cont
import Data.List

data User = User { name :: String
                  , surname :: String
                  , yob :: Int
                  } deriving Show

users = [ User { name = "Amadeus", surname = "Mozart", yob = 1756 }
        , User { name = "Amadeus", surname = "Brahms", yob = 1833 }
        , User { name = "Johannes", surname = "Brahms", yob = 1833 }
        , User { name = "Johannes", surname = "Mozart", yob = 1833 }
        , User { name = "Antonio", surname = "Vivaldi", yob = 1678 }
        , User { name = "Antonio", surname = "Vivaldi", yob = 1679 }
        ]

order = cont $ \f x -> sortBy (curry f) x 
by field = cont $
   \f x -> if ord x == EQ then
              f x
           else
              ord x
        where
           ord x = compare ((field . fst) x) ((field . snd) x)

eqOtherwise = cont $ \f x -> EQ

mysort = forget $ order . (by surname) . (by name) . (by yob) . eqOtherwise

Example: Composable actions

Here is an example how to combine the Cont category with the IO monad:

import Prelude hiding (id, (.))
import Control.Category
import Control.Category.Cont

withPassword pwd = cont $ \f x -> do
    putStrLn "Enter the secret password:"
    pass <- getLine
    if pass == pwd then
        f x
    else
        return "you are not authorized to execute this action."

greet = cont $ \f x -> f $ "hello to " ++ x

secureGreet = forget $ (withPassword "secret") . lift . greet
verySecureGreet = forget $ (withPassword "secret") . (withPassword "verySecret") . lift . greet

The action withPassword requests the user to enter a string. If the string matches the password, the input is handed to the continuation. lift is used to inject the pure code into the IO monad.

Example: Monoid

import Prelude hiding (id, (.))
import Control.Category
import Control.Category.Cont

ins a = [a]
select op = cont $
    \f x -> f $ op x

toList :: (a, a) -> [a]
toList = forget $  (select fst `mappend` select snd) . (withCont ins)