NestedFunctor-0.2.0.1: Nested composition of functors with a type index tracking nesting.

CopyrightCopyright (c) 2014 Kenneth Foner
Maintainerkenneth.foner@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Functor.Nested

Description

This module implements something akin to Compose, but with a type index that tracks the order in which things are nested. This makes it possible to write code using polymorphic recursion over the levels of the structure contained in a Nested value.

Synopsis

Documentation

data Flat x Source

Flat x is the type index used for the base case of a Nested value. Thus, a (Nested (Flat []) Int is isomorphic to a [Int].

Instances

Alternative f => Alternative (Nested (Flat f)) 
Functor f => Functor (Nested (Flat f)) 
Applicative f => Applicative (Nested (Flat f)) 
Foldable f => Foldable (Nested (Flat f)) 
Traversable f => Traversable (Nested (Flat f)) 
Comonad f => Comonad (Nested (Flat f)) 
ComonadApply f => ComonadApply (Nested (Flat f)) 
Distributive f => Distributive (Nested (Flat f)) 
(~) * (AsNestedAs (f a) (Nested (Flat g) b)) (Nested (Flat f) a) => NestedAs (f a) (Nested (Flat g) b) 
Show (f a) => Show (Nested (Flat f) a) 

data Nest o i Source

Nest o i is the type index used for the recursive case of a Nested value: the o parameter is the type constructors corresponding to the outside levels, and the i parameter is the single type constructor corresponding to the inner-most level. Thus, a (Nested (Nest (Flat Maybe) []) Int) is isomorphic to a (Maybe [Int]).

Instances

(Applicative f, Alternative (Nested fs)) => Alternative (Nested (Nest fs f)) 
(Functor f, Functor (Nested fs)) => Functor (Nested (Nest fs f)) 
(Applicative f, Applicative (Nested fs)) => Applicative (Nested (Nest fs f)) 
(Foldable f, Foldable (Nested fs)) => Foldable (Nested (Nest fs f)) 
(Traversable f, Traversable (Nested fs)) => Traversable (Nested (Nest fs f)) 
(Comonad f, Comonad (Nested fs), Distributive f, Functor (Nested (Nest fs f))) => Comonad (Nested (Nest fs f)) 
(ComonadApply f, Distributive f, ComonadApply (Nested fs)) => ComonadApply (Nested (Nest fs f)) 
(Distributive f, Distributive (Nested fs)) => Distributive (Nested (Nest fs f)) 
((~) * (AsNestedAs (f a) (UnNest (Nested (Nest g h) b))) (Nested fs (f' a')), (~) * (AddNest (Nested fs (f' a'))) (Nested (Nest fs f') a'), NestedAs (f a) (UnNest (Nested (Nest g h) b))) => NestedAs (f a) (Nested (Nest g h) b) 
Show (Nested fs (f a)) => Show (Nested (Nest fs f) a) 

data Nested fs a where Source

A Nested fs a is the composition of all the layers mentioned in fs, applied to an a. Specifically, the fs parameter is a sort of snoc-list holding type constructors of kind (* -> *). The outermost layer appears as the parameter to Flat; the innermost layer appears as the rightmost argument to the outermost Nest. For instance:

                 [Just ['a']]   :: [Maybe [Char]]
            Flat [Just ['a']]   :: Nested (Flat []) (Maybe [Char])
      Nest (Flat [Just ['a']])  :: Nested (Nest (Flat []) Maybe) [Char]
Nest (Nest (Flat [Just ['a']])) :: Nested (Nest (Nest (Flat []) Maybe) []) Char

Constructors

Flat :: f a -> Nested (Flat f) a 
Nest :: Nested fs (f a) -> Nested (Nest fs f) a 

Instances

(Applicative f, Alternative (Nested fs)) => Alternative (Nested (Nest fs f)) 
Alternative f => Alternative (Nested (Flat f)) 
(Functor f, Functor (Nested fs)) => Functor (Nested (Nest fs f)) 
Functor f => Functor (Nested (Flat f)) 
(Applicative f, Applicative (Nested fs)) => Applicative (Nested (Nest fs f)) 
Applicative f => Applicative (Nested (Flat f)) 
(Foldable f, Foldable (Nested fs)) => Foldable (Nested (Nest fs f)) 
Foldable f => Foldable (Nested (Flat f)) 
(Traversable f, Traversable (Nested fs)) => Traversable (Nested (Nest fs f)) 
Traversable f => Traversable (Nested (Flat f)) 
(Comonad f, Comonad (Nested fs), Distributive f, Functor (Nested (Nest fs f))) => Comonad (Nested (Nest fs f)) 
Comonad f => Comonad (Nested (Flat f)) 
(ComonadApply f, Distributive f, ComonadApply (Nested fs)) => ComonadApply (Nested (Nest fs f)) 
ComonadApply f => ComonadApply (Nested (Flat f)) 
(Distributive f, Distributive (Nested fs)) => Distributive (Nested (Nest fs f)) 
Distributive f => Distributive (Nested (Flat f)) 
((~) * (AsNestedAs (f a) (UnNest (Nested (Nest g h) b))) (Nested fs (f' a')), (~) * (AddNest (Nested fs (f' a'))) (Nested (Nest fs f') a'), NestedAs (f a) (UnNest (Nested (Nest g h) b))) => NestedAs (f a) (Nested (Nest g h) b) 
(~) * (AsNestedAs (f a) (Nested (Flat g) b)) (Nested (Flat f) a) => NestedAs (f a) (Nested (Flat g) b) 
Show (Nested fs (f a)) => Show (Nested (Nest fs f) a) 
Show (f a) => Show (Nested (Flat f) a) 

type family UnNest x Source

The UnNest type family describes what happens when you peel off one Nested constructor from a Nested value.

Equations

UnNest (Nested (Flat f) a) = f a 
UnNest (Nested (Nest fs f) a) = Nested fs (f a) 

unNest :: Nested fs a -> UnNest (Nested fs a) Source

Removes one Nested constructor (either Nest or Flat) from a Nested value.

unNest . Nest == id
unNest . Flat == id
unNest (Nest (Flat [['x']])) == Flat [['x']]
unNest (Flat (Just 'x')) == Just 'x'

class NestedAs x y where Source

Methods

asNestedAs :: x -> y -> x `AsNestedAs` y Source

Given some nested structure which is not wrapped in Nested constructors, and one which is, wrap the first in the same number of Nested constructors so that they are equivalently nested.

[['a']] `asNestedAs` Nest (Flat (Just (Just 0))) == Nest (Flat [['a']])

Instances

((~) * (AsNestedAs (f a) (UnNest (Nested (Nest g h) b))) (Nested fs (f' a')), (~) * (AddNest (Nested fs (f' a'))) (Nested (Nest fs f') a'), NestedAs (f a) (UnNest (Nested (Nest g h) b))) => NestedAs (f a) (Nested (Nest g h) b) 
(~) * (AsNestedAs (f a) (Nested (Flat g) b)) (Nested (Flat f) a) => NestedAs (f a) (Nested (Flat g) b) 

type family AsNestedAs x y Source

This type family calculates the result type of applying the Nested constructors to its first argument a number of times equal to the depth of nesting in its second argument.

Equations

AsNestedAs (f x) (Nested (Flat g) b) = Nested (Flat f) x 
AsNestedAs x y = AddNest (x `AsNestedAs` UnNest y) 

type family AddNest x Source

This type family calculates the type of a Nested value if one more Nest constructor is applied to it.

Equations

AddNest (Nested fs (f x)) = Nested (Nest fs f) x