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 (57 lines) | stat: -rw-r--r-- 1,805 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
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Comonad.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.Comonad.Trans.Adjoint
  ( Adjoint
  , runAdjoint
  , adjoint
  , AdjointT(..)
  ) where

import Prelude hiding (sequence)
import Control.Applicative
import Control.Comonad
import Control.Comonad.Trans.Class
import Data.Functor.Adjunction
import Data.Functor.Identity
import Data.Distributive

type Adjoint f g = AdjointT f g Identity

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

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

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

instance (Adjunction f g, Functor w) => Functor (AdjointT f g w) where
  fmap f (AdjointT g) = AdjointT $ fmap (fmap (fmap f)) g
  b <$ (AdjointT g) = AdjointT $ fmap (fmap (b <$)) g


instance (Adjunction f g, Extend w) => Extend (AdjointT f g w) where
  extend f (AdjointT m) = AdjointT $ fmap (extend $ leftAdjunct (f . AdjointT)) m

instance (Adjunction f g, Comonad w) => Comonad (AdjointT f g w) where
  extract = rightAdjunct extract . runAdjointT
  
{-
instance (Adjunction f g, Monad m) => Applicative (AdjointT f g m) where
  pure = AdjointT . leftAdjunct return
  (<*>) = ap
-}
    
instance (Adjunction f g, Distributive g) => ComonadTrans (AdjointT f g) where
  lower = counit . fmap distribute . runAdjointT