File: Class.hs

package info (click to toggle)
haskell-free 2.1.1.1-1
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 96 kB
  • sloc: haskell: 322; makefile: 2
file content (40 lines) | stat: -rw-r--r-- 1,422 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
{-# LANGUAGE MultiParamTypeClasses
           , FunctionalDependencies
           , FlexibleInstances
           , UndecidableInstances #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Comonad.Cofree.Class
-- Copyright   :  (C) 2008-2011 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  experimental
-- Portability :  fundeps, MPTCs
----------------------------------------------------------------------------
module Control.Comonad.Cofree.Class
  ( ComonadCofree(..)
  ) where

import Control.Applicative
import Control.Comonad
import Control.Comonad.Trans.Env
import Control.Comonad.Trans.Store
import Control.Comonad.Trans.Traced
import Control.Comonad.Trans.Identity
import Data.Semigroup

class (Functor f, Comonad w) => ComonadCofree f w | w -> f where
  unwrap :: w a -> f (w a)

instance ComonadCofree f w => ComonadCofree f (IdentityT w) where
  unwrap = fmap IdentityT . unwrap . runIdentityT

instance ComonadCofree f w => ComonadCofree f (EnvT e w) where
  unwrap (EnvT e wa) = EnvT e <$> unwrap wa

instance ComonadCofree f w => ComonadCofree f (StoreT s w) where
  unwrap (StoreT wsa s) = flip StoreT s <$> unwrap wsa

instance (ComonadCofree f w, Semigroup m, Monoid m) => ComonadCofree f (TracedT m w) where
  unwrap (TracedT wma) = TracedT <$> unwrap wma