Copyright | Copyright (c) 2014 Kenneth Foner |
---|---|
Maintainer | kenneth.foner@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
- data Flat x
- data Nest o i
- data Nested fs a where
- type family UnNest x
- unNest :: Nested fs a -> UnNest (Nested fs a)
- class NestedAs x y where
- asNestedAs :: x -> y -> x `AsNestedAs` y
- type family AsNestedAs x y
- type family AddNest x
Documentation
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]
.
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) |
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])
.
(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) |
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
The UnNest
type family describes what happens when you peel off one Nested
constructor from a Nested
value.
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
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']])
((~) * (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.
AsNestedAs (f x) (Nested (Flat g) b) = Nested (Flat f) x | |
AsNestedAs x y = AddNest (x `AsNestedAs` UnNest y) |