squares-0.1.1: The double category of Hask functors and profunctors

LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Compose.List

Description

 
Synopsis

Documentation

data FList (fs :: [* -> *]) (a :: *) where Source #

N-ary composition of functors.

FList '[] a ~ a
FList '[f, g, h] a ~ h (g (f a))

Constructors

Id 

Fields

F 

Fields

  • :: { unF :: f a
     
  •    } -> FList '[f] a
     
FComp 

Fields

Instances
(Functor f, Functor (FList (g ': gs))) => Functor (FList (f ': (g ': gs))) Source # 
Instance details

Defined in Data.Functor.Compose.List

Methods

fmap :: (a -> b) -> FList (f ': (g ': gs)) a -> FList (f ': (g ': gs)) b #

(<$) :: a -> FList (f ': (g ': gs)) b -> FList (f ': (g ': gs)) a #

Functor f => Functor (FList (f ': ([] :: [Type -> Type]))) Source # 
Instance details

Defined in Data.Functor.Compose.List

Methods

fmap :: (a -> b) -> FList (f ': []) a -> FList (f ': []) b #

(<$) :: a -> FList (f ': []) b -> FList (f ': []) a #

Functor (FList ([] :: [Type -> Type])) Source # 
Instance details

Defined in Data.Functor.Compose.List

Methods

fmap :: (a -> b) -> FList [] a -> FList [] b #

(<$) :: a -> FList [] b -> FList [] a #

type family PlainF (fs :: [* -> *]) (a :: *) :: * Source #

Calculate the simplified type of the composition of a list of functors.

Instances
type PlainF ([] :: [Type -> Type]) a Source # 
Instance details

Defined in Data.Functor.Compose.List

type PlainF ([] :: [Type -> Type]) a = a
type PlainF (f ': fs) a Source # 
Instance details

Defined in Data.Functor.Compose.List

type PlainF (f ': fs) a = PlainF fs (f a)

class IsFList fs where Source #

Functions for working with FLists.

Methods

fappend :: Functor (FList gs) => FList gs (FList fs a) -> FList (fs ++ gs) a Source #

Combine 2 nested FLists into one FList.

funappend :: Functor (FList gs) => FList (fs ++ gs) a -> FList gs (FList fs a) Source #

Split one FList into 2 nested FLists.

toPlainF :: FList fs a -> PlainF fs a Source #

Convert an FList to its simplified form.

fromPlainF :: PlainF fs a -> FList fs a Source #

Create an FList from its simplified form.

Instances
IsFList ([] :: [Type -> Type]) Source # 
Instance details

Defined in Data.Functor.Compose.List

Methods

fappend :: Functor (FList gs) => FList gs (FList [] a) -> FList ([] ++ gs) a Source #

funappend :: Functor (FList gs) => FList ([] ++ gs) a -> FList gs (FList [] a) Source #

toPlainF :: FList [] a -> PlainF [] a Source #

fromPlainF :: PlainF [] a -> FList [] a Source #

IsFList (g ': gs) => IsFList (f ': (g ': gs)) Source # 
Instance details

Defined in Data.Functor.Compose.List

Methods

fappend :: Functor (FList gs0) => FList gs0 (FList (f ': (g ': gs)) a) -> FList ((f ': (g ': gs)) ++ gs0) a Source #

funappend :: Functor (FList gs0) => FList ((f ': (g ': gs)) ++ gs0) a -> FList gs0 (FList (f ': (g ': gs)) a) Source #

toPlainF :: FList (f ': (g ': gs)) a -> PlainF (f ': (g ': gs)) a Source #

fromPlainF :: PlainF (f ': (g ': gs)) a -> FList (f ': (g ': gs)) a Source #

IsFList (f ': ([] :: [Type -> Type])) Source # 
Instance details

Defined in Data.Functor.Compose.List

Methods

fappend :: Functor (FList gs) => FList gs (FList (f ': []) a) -> FList ((f ': []) ++ gs) a Source #

funappend :: Functor (FList gs) => FList ((f ': []) ++ gs) a -> FList gs (FList (f ': []) a) Source #

toPlainF :: FList (f ': []) a -> PlainF (f ': []) a Source #

fromPlainF :: PlainF (f ': []) a -> FList (f ': []) a Source #

type (~>) f g = forall a. f a -> g a Source #

Natural transformations between two functors. (Why is this still not in base??)