functor-combo-0.3.6: Functor combinators with tries & zippers

Copyright(c) Conal Elliott 2010
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

FunctorCombo.Functor

Description

Standard building blocks for functors

Synopsis

Documentation

newtype Const a b :: * -> * -> *

Constructors

Const 

Fields

getConst :: a
 

Instances

Functor (Const m) 
Monoid m => Applicative (Const m) 
Foldable (Const m) 
Traversable (Const m) 
Generic1 (Const a) 
Scan (Const x) 
Holey (Const z) 
Holey (Const x) 
Eq a => Eq (Const a b) 
Ord a => Ord (Const a b) 
Read a => Read (Const a b) 
Show a => Show (Const a b) 
Generic (Const a b) 
Monoid a => Monoid (Const a b) 
Semigroup a => Semigroup (Const a b) 
HasTrie x => HasTrie (Const x a) 
HasTrie x => HasTrie (Const x a) 
Typeable (* -> * -> *) Const 
type Rep1 (Const a) = D1 D1Const (C1 C1_0Const (S1 S1_0_0Const (Rec0 a))) 
type Der (Const a) = Void 
type Der (Const x) = Void 
type Rep (Const a b) = D1 D1Const (C1 C1_0Const (S1 S1_0_0Const (Rec0 a))) 
type Trie (Const x a) = Trie x 
type STrie (Const x a) = STrie x 

data Void a Source

Empty/zero type constructor (no inhabitants)

Instances

voidF :: Void a -> b Source

type Unit = Const () Source

Unit type constructor (one inhabitant)

unit :: Unit () Source

The unit value

newtype Id a :: * -> *

Identity type constructor. Until there's a better place to find it. I'd use Control.Monad.Identity, but I don't want to introduce a dependency on mtl just for Id.

Constructors

Id a 

Instances

Monad Id 
Functor Id 
Applicative Id 
Foldable Id 
Traversable Id 
Scan Id 
HasLubF Id 
Holey Id 
Holey Id 
Show a => Show (Id a) 
HasTrie a => HasTrie (Id a) 
HasTrie a => HasTrie (Id a) 
type Der Id = Unit 
type Der Id = Unit 
type Trie (Id a) = Trie a 
type STrie (Id a) = STrie a 

unId :: Id a -> a

inId :: (a -> b) -> Id a -> Id b

inId2 :: (a -> b -> c) -> Id a -> Id b -> Id c

data (f :+: g) a infixl 6 Source

Sum on unary type constructors

Constructors

InL (f a) 
InR (g a) 

Instances

(Functor f, Functor g) => Functor ((:+:) f g) 
(Foldable f, Foldable g) => Foldable ((:+:) f g) 
(Traversable f, Traversable g) => Traversable ((:+:) f g) 
(Scan f, Scan g) => Scan ((:+:) f g) 
(Holey f, Holey g) => Holey ((:+:) f g) 
(Holey f, Holey g) => Holey ((:+:) f g) 
(Show (f a), Show (g a)) => Show ((:+:) f g a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:+:) f g a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:+:) f g a) 
type Der ((:+:) f g) = (:+:) (Der f) (Der g) 
type Der ((:+:) f g) = (:+:) (Der f) (Der g) 
type Trie ((:+:) f g a) = Trie (Either (f a) (g a)) 
type STrie ((:+:) f g a) = STrie (Either (f a) (g a)) 

eitherF :: (f a -> b) -> (g a -> b) -> (f :+: g) a -> b Source

data (f :*: g) a infixl 7 Source

Product on unary type constructors

Constructors

(f a) :*: (g a) infixl 7 

Instances

(Functor f, Functor g, Monad f, Monad g) => Monad ((:*:) f g) 
(Functor f, Functor g) => Functor ((:*:) f g) 
(Applicative f, Applicative g) => Applicative ((:*:) f g) 
(Foldable f, Foldable g) => Foldable ((:*:) f g) 
(Traversable f, Traversable g) => Traversable ((:*:) f g) 
(Scan f, Scan g, Functor f, Functor g) => Scan ((:*:) f g) 
(HasLubF f, HasLubF g) => HasLubF ((:*:) f g) 
(Holey f, Holey g) => Holey ((:*:) f g) 
(Holey f, Holey g) => Holey ((:*:) f g) 
(Show (f a), Show (g a)) => Show ((:*:) f g a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:*:) f g a) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:*:) f g a) 
type Der ((:*:) f g) = (:+:) ((:*:) (Der f) g) ((:*:) f (Der g)) 
type Der ((:*:) f g) = (:+:) ((:*:) (Der f) g) ((:*:) f (Der g)) 
type Trie ((:*:) f g a) = Trie (f a, g a) 
type STrie ((:*:) f g a) = STrie (f a, g a) 

asProd :: (f a, g a) -> (f :*: g) a Source

asPair :: (f :*: g) a -> (f a, g a) Source

fstF :: (f :*: g) a -> f a Source

Like fst

sndF :: (f :*: g) a -> g a Source

Like snd

newtype (g :. f) a :: (* -> *) -> (* -> *) -> * -> * infixl 9

Composition of unary type constructors

There are (at least) two useful Monoid instances, so you'll have to pick one and type-specialize it (filling in all or parts of g and/or f).

    -- standard Monoid instance for Applicative applied to Monoid
    instance (Applicative (g :. f), Monoid a) => Monoid ((g :. f) a) where
      { mempty = pure mempty; mappend = liftA2 mappend }
    -- Especially handy when g is a Monoid_f.
    instance Monoid (g (f a)) => Monoid ((g :. f) a) where
      { mempty = O mempty; mappend = inO2 mappend }

Corresponding to the first and second definitions above,

    instance (Applicative g, Monoid_f f) => Monoid_f (g :. f) where
      { mempty_f = O (pure mempty_f); mappend_f = inO2 (liftA2 mappend_f) }
    instance Monoid_f g => Monoid_f (g :. f) where
      { mempty_f = O mempty_f; mappend_f = inO2 mappend_f }

Similarly, there are two useful Functor instances and two useful ContraFunctor instances.

    instance (      Functor g,       Functor f) => Functor (g :. f) where fmap = fmapFF
    instance (ContraFunctor g, ContraFunctor f) => Functor (g :. f) where fmap = fmapCC

    instance (      Functor g, ContraFunctor f) => ContraFunctor (g :. f) where contraFmap = contraFmapFC
    instance (ContraFunctor g,       Functor f) => ContraFunctor (g :. f) where contraFmap = contraFmapCF

However, it's such a bother to define the Functor instances per composition type, I've left the fmapFF case in. If you want the fmapCC one, you're out of luck for now. I'd love to hear a good solution. Maybe someday Haskell will do Prolog-style search for instances, subgoaling the constraints, rather than just matching instance heads.

Constructors

O (g (f a)) 

Instances

(Functor g, Functor f) => Functor ((:.) g f) 
(Applicative g, Applicative f) => Applicative ((:.) g f) 
(Foldable g, Foldable f, Functor g) => Foldable ((:.) g f) 
(Traversable g, Traversable f) => Traversable ((:.) g f) 
(Scan g, Scan f, Functor f, Applicative g) => Scan ((:.) g f) 
(Holey f, Holey g) => Holey ((:.) g f) 
(Holey f, Holey g) => Holey ((:.) g f) 
Eq (g (f a)) => Eq ((:.) g f a) 
Show (g (f a)) => Show ((:.) g f a) 
HasTrie (g (f a)) => HasTrie ((:.) g f a) 
HasTrie (g (f a)) => HasTrie ((:.) g f a) 
type Der ((:.) g f) = (:*:) ((:.) (Der g) f) (Der f) 
type Der ((:.) g f) = (:*:) ((:.) (Der g) f) (Der f) 
type Trie ((:.) g f a) = Trie (g (f a)) 
type STrie ((:.) g f a) = STrie (g (f a)) 

unO :: (:.) g f a -> g (f a)

Unwrap a '(:.)'.

inO :: (g (f a) -> g' (f' a')) -> (:.) g f a -> (:.) g' f' a'

Apply a unary function within the O constructor.

inO2 :: (g (f a) -> g' (f' a') -> g'' (f'' a'')) -> (:.) g f a -> (:.) g' f' a' -> (:.) g'' f'' a''

Apply a binary function within the O constructor.

(~>) :: Category * cat => cat a' a -> cat b b' -> cat a b -> cat a' b' infixr 1

Add pre- and post processing

(<~) :: Category * cat => cat b b' -> cat a' a -> cat a b -> cat a' b' infixl 1

data Lift a Source

Add a bottom to a type

Constructors

Lift 

Fields

unLift :: a
 

Instances

Functor Lift 
HasTrie a => HasTrie (Lift a) 
type STrie (Lift a) 

data (f :*:! g) a infixl 7 Source

Strict product functor

Constructors

!(f a) :*:! !(g a) infixl 7 

Instances

(Functor f, Functor g) => Functor ((:*:!) f g) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:*:!) f g a) 
type STrie ((:*:!) f g a) = STrie ((:*!) (f a) (g a)) 

data (f :+:! g) a infixl 6 Source

Strict sum functor

Constructors

InL' !(f a) 
InR' !(g a) 

Instances

(Functor f, Functor g) => Functor ((:+:!) f g) 
(HasTrie (f a), HasTrie (g a)) => HasTrie ((:+:!) f g a) 
type STrie ((:+:!) f g a) = STrie ((:+!) (f a) (g a)) 

eitherF' :: (f a -> c) -> (g a -> c) -> (f :+:! g) a -> c Source

Case analysis on strict sum functor

pairF :: (f a, g a) -> (f :*: g) a Source

unPairF :: (f :*: g) a -> (f a, g a) Source

inProd :: ((f a, g a) -> (h b, i b)) -> (f :*: g) a -> (h :*: i) b Source

inProd2 :: ((f a, g a) -> (h b, i b) -> (j c, k c)) -> (f :*: g) a -> (h :*: i) b -> (j :*: k) c Source

class EncodeF f where Source

Associated Types

type Enc f :: * -> * Source

Methods

encode :: f a -> Enc f a Source

decode :: Enc f a -> f a Source

Instances