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 (53 lines) | stat: -rw-r--r-- 1,813 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
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Monad.Trans.Adjoint
-- Copyright   :  (C) 2011 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  provisional
-- Portability :  MPTCs, fundeps
--
----------------------------------------------------------------------------

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

import Prelude hiding (sequence)
import Control.Applicative
import Control.Monad (ap, liftM)
import Control.Monad.Trans.Class
import Data.Traversable
import Data.Functor.Adjunction
import Data.Functor.Identity

type Adjoint f g = AdjointT f g Identity

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

adjoint :: Functor g => g (f a) -> Adjoint f g a
adjoint = AdjointT . fmap Identity

runAdjoint :: Functor g => Adjoint f g a -> g (f a)
runAdjoint = fmap runIdentity . runAdjointT

instance (Adjunction f g, Monad m) => Functor (AdjointT f g m) where
  fmap f (AdjointT g) = AdjointT $ fmap (liftM (fmap f)) g
  b <$ (AdjointT g) = AdjointT $ fmap (liftM (b <$)) g
  
instance (Adjunction f g, Monad m) => Applicative (AdjointT f g m) where
  pure = AdjointT . leftAdjunct return
  (<*>) = ap

instance (Adjunction f g, Monad m) => Monad (AdjointT f g m) where
  return = AdjointT . leftAdjunct return
  AdjointT m >>= f = AdjointT $ fmap (>>= rightAdjunct (runAdjointT . f)) m
    
-- | Exploiting this instance requires that we have the missing Traversables for Identity, (,)e and IdentityT
instance (Adjunction f g, Traversable f) => MonadTrans (AdjointT f g) where
  lift = AdjointT . fmap sequence . unit