File: Adjoint.hs

package info (click to toggle)
haskell-adjunctions 2.4.0.2-1
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 88 kB
  • sloc: haskell: 246; makefile: 2
file content (60 lines) | stat: -rw-r--r-- 1,922 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
{-# LANGUAGE MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Monad.Trans.Contravariant.Adjoint
-- Copyright   :  (C) 2011 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  provisional
-- Portability :  MPTCs, fundeps
--
-- Uses a contravariant adjunction:
--
-- f -| g : Hask^op -> Hask
--
-- to build a 'Comonad' to 'Monad' transformer. Sadly, the dual construction, 
-- which builds a 'Comonad' out of a 'Monad', is uninhabited, because any 
-- 'Adjunction' of the form
-- 
-- > f -| g : Hask -> Hask^op
-- 
-- would trivially admit unsafePerformIO.
-- 
----------------------------------------------------------------------------

module Control.Monad.Trans.Contravariant.Adjoint
  ( Adjoint
  , runAdjoint
  , adjoint
  , AdjointT(..)
  ) where

import Prelude hiding (sequence)
import Control.Applicative
import Control.Comonad
import Control.Monad (ap)
import Data.Functor.Identity
import Data.Functor.Contravariant
import Data.Functor.Contravariant.Adjunction

type Adjoint f g = AdjointT f g Identity

newtype AdjointT f g w a = AdjointT { runAdjointT :: g (w (f a)) }

adjoint :: Contravariant g => g (f a) -> Adjoint f g a
adjoint = AdjointT . contramap runIdentity

runAdjoint :: Contravariant g => Adjoint f g a -> g (f a)
runAdjoint = contramap Identity . runAdjointT

instance (Adjunction f g, Functor w) => Functor (AdjointT f g w) where
  fmap f (AdjointT g) = AdjointT $ contramap (fmap (contramap f)) g
  
instance (Adjunction f g, Comonad w) => Applicative (AdjointT f g w) where
  pure = AdjointT . leftAdjunct extract
  (<*>) = ap

instance (Adjunction f g, Comonad w) => Monad (AdjointT f g w) where
  return = AdjointT . leftAdjunct extract
  AdjointT m >>= f = AdjointT $ contramap (extend (rightAdjunct (runAdjointT . f))) m