Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Cell = Cell1 Identity
- data Cell1 f constr = (constr a, Typeable a) => Cell (f a)
- type Inst constr a = Inst1 Identity constr a
- data Inst1 f constr a = (Typeable a, constr a) => Inst (f a)
- type EntailsAll c0 c1 = forall a. c0 a :- c1 a
- dictFunToEntails :: Iso' (Dict p -> Dict q) (p :- q)
- entailsToDictFun :: Iso' (p :- q) (Dict p -> Dict q)
- dict :: Inst1 f constr a -> Dict (constr a)
- class HasCell a b | a -> b where
- makeCell :: (HasCell a (Cell constr), constr b, Typeable b) => b -> a
- makeCell1 :: (HasCell a (Cell1 f constr), constr b, Typeable b) => f b -> a
- _Cell :: (constr b, Typeable b, Typeable a) => Prism (Cell constr) (Cell constr) a b
- _Cell' :: (constr a, Typeable a, HasCell c (Cell constr)) => Prism c c a a
- _Cell1 :: (constr b, Typeable b, Typeable a, Typeable f) => Prism (Cell1 f constr) (Cell1 f constr) (f a) (f b)
- _Cell1' :: (constr a, Typeable a, Typeable f, HasCell c (Cell1 f constr)) => Prism c c (f a) (f a)
- asCell :: (constr a, Typeable a) => Prism (Cell constr) (Cell constr) a a
- asCell1 :: (constr a, Typeable a, Typeable f) => Prism (Cell1 f constr) (Cell1 f constr) (f a) (f a)
- asInst :: Functor g => (forall a. Inst1 f constr a -> g (Inst1 h constr' a)) -> Cell1 f constr -> g (Cell1 h constr')
- asInst1 :: Functor g => (forall a. Inst1 f constr a -> g (Inst1 h constr' a)) -> Cell1 f constr -> g (Cell1 h constr')
- fromInst :: Inst1 f constr a -> Cell1 f constr
- inst :: Lens' (Inst constr a) a
- inst1 :: Lens (Inst1 f constr a) (Inst1 g constr a) (f a) (g a)
- traverseCell :: Functor f => (forall a. (constr a, Typeable a) => a -> f a) -> Cell constr -> f (Cell constr)
- traverseCell' :: (Functor f, HasCell c (Cell constr)) => (forall a. (constr a, Typeable a) => a -> f a) -> c -> f c
- traverseCell1 :: Functor f => (forall a. (constr a, Typeable a) => g a -> f (h a)) -> Cell1 g constr -> f (Cell1 h constr)
- traverseCell1' :: (Functor f, HasCell c (Cell1 g constr)) => (forall a. (constr a, Typeable a) => g a -> f (g a)) -> c -> f c
- traverseInst :: Functor f => (constr a => a -> f a) -> Inst constr a -> f (Inst constr a)
- traverseInst1 :: Functor f => (constr a => g a -> f (h a)) -> Inst1 g constr a -> f (Inst1 h constr a)
- mapCell :: (forall a. (constr a, Typeable a) => a -> a) -> Cell constr -> Cell constr
- mapCell' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a) -> c -> c
- mapCell1 :: (forall a. (constr a, Typeable a) => f a -> f a) -> Cell1 f constr -> Cell1 f constr
- mapCell1' :: HasCell c (Cell1 f constr) => (forall a. (constr a, Typeable a) => f a -> f a) -> c -> c
- mapInst :: (constr a => a -> a) -> Inst constr a -> Inst constr a
- mapInst1 :: (constr a => f a -> f a) -> Inst1 f constr a -> Inst1 f constr a
- readCell1 :: (forall a. (constr a, Typeable a) => f a -> r) -> Cell1 f constr -> r
- readCell1' :: HasCell c (Cell1 f constr) => (forall a. (constr a, Typeable a) => f a -> r) -> c -> r
- readCell :: (forall a. (constr a, Typeable a) => a -> r) -> Cell constr -> r
- readCell' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> r) -> c -> r
- readInst :: (constr a => a -> r) -> Inst constr a -> r
- readInst1 :: (constr a => f a -> r) -> Inst1 f constr a -> r
- apply2Cells :: Functor f => (forall a. (constr a, Typeable a) => a -> a -> f a) -> f (Cell constr) -> Cell constr -> Cell constr -> f (Cell constr)
- apply2Cells' :: (Functor f, HasCell c (Cell constr)) => (forall a. (constr a, Typeable a) => a -> a -> f a) -> f c -> c -> c -> f c
- apply2Cells1 :: (Functor f, Typeable g) => (forall a. (constr a, Typeable a) => g a -> g a -> f (g a)) -> f (Cell1 g constr) -> Cell1 g constr -> Cell1 g constr -> f (Cell1 g constr)
- apply2Cells1' :: (Functor f, Typeable g, HasCell c (Cell1 g constr)) => (forall a. (constr a, Typeable a) => g a -> g a -> f (g a)) -> f c -> c -> c -> f c
- map2Cells :: (forall a. (constr a, Typeable a) => a -> a -> a) -> Cell constr -> Cell constr -> Cell constr -> Cell constr
- map2Cells' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a -> a) -> c -> c -> c -> c
- map2Cells1 :: (forall a. (constr a, Typeable a) => a -> a -> a) -> Cell constr -> Cell constr -> Cell constr -> Cell constr
- map2Cells1' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a -> a) -> c -> c -> c -> c
- read2CellsWith :: (forall a. (constr a, Typeable a) => a -> a -> r) -> r -> Cell constr -> Cell constr -> r
- read2CellsWith' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a -> r) -> r -> c -> c -> r
- read2Cells1With :: Typeable f => (forall a. (constr a, Typeable a) => f a -> f a -> r) -> r -> Cell1 f constr -> Cell1 f constr -> r
- read2Cells1With' :: (HasCell c (Cell1 f constr), Typeable f) => (forall a. (constr a, Typeable a) => f a -> f a -> r) -> r -> c -> c -> r
- read2CellsH :: (forall a b. (constr a, Typeable a, constr b, Typeable b) => a -> b -> r) -> Cell constr -> Cell constr -> r
- read2CellsH' :: HasCell c (Cell constr) => (forall a b. (constr a, Typeable a, constr b, Typeable b) => a -> b -> r) -> c -> c -> r
- read2Cells1H :: (forall a b. (constr a, Typeable a, constr b, Typeable b) => f a -> f b -> r) -> Cell1 f constr -> Cell1 f constr -> r
- read2Cells1H' :: (forall a b. (constr a, Typeable a, constr b, Typeable b) => f a -> f b -> r) -> Cell1 f constr -> Cell1 f constr -> r
- cell1Equal :: Typeable f => (forall a. constr a => f a -> f a -> Bool) -> Cell1 f constr -> Cell1 f constr -> Bool
- cell1Equal' :: (HasCell c (Cell1 f constr), Typeable f) => (forall a. constr a => f a -> f a -> Bool) -> c -> c -> Bool
- cellEqual :: (forall a. constr a => a -> a -> Bool) -> Cell constr -> Cell constr -> Bool
- cellEqual' :: HasCell c (Cell constr) => (forall a. constr a => a -> a -> Bool) -> c -> c -> Bool
- cellZoomEqual' :: (HasCell c (Cell constr), Eq c, Show c) => (forall a. constr a => a -> a -> Invariant) -> c -> c -> Invariant
- cell1ZoomEqual' :: (HasCell c (Cell1 f constr), Eq c, Show c, Typeable f) => (forall a. constr a => f a -> f a -> Invariant) -> c -> c -> Invariant
- cellCompare :: (forall a. constr a => a -> a -> Ordering) -> Cell constr -> Cell constr -> Ordering
- cellCompare' :: HasCell c (Cell constr) => (forall a. constr a => a -> a -> Ordering) -> c -> c -> Ordering
- cell1Compare :: Typeable f => (forall a. constr a => f a -> f a -> Ordering) -> Cell1 f constr -> Cell1 f constr -> Ordering
- cell1Compare' :: (HasCell c (Cell1 f constr), Typeable f) => (forall a. constr a => f a -> f a -> Ordering) -> c -> c -> Ordering
- cellLens :: Functor f => (forall a. constr a => LensLike' f a b) -> LensLike' f (Cell constr) b
- cellLens' :: (HasCell c (Cell constr), Functor f) => (forall a. constr a => LensLike' f a b) -> LensLike' f c b
- cell1Lens :: Functor f => (forall a. constr a => LensLike' f (g a) b) -> LensLike' f (Cell1 g constr) b
- cell1Lens' :: (HasCell c (Cell1 g constr), Functor f) => (forall a. constr a => LensLike' f (g a) b) -> LensLike' f c b
- rewriteCell :: EntailsAll c0 c1 -> Cell1 f c0 -> Cell1 f c1
- rewriteInst :: (c0 a :- c1 a) -> Inst1 f c0 a -> Inst1 f c1 a
- spec :: f a -> (p a :- q a) -> p a :- q a
- transEnt :: EntailsAll c0 c1 -> EntailsAll c1 c2 -> EntailsAll c0 c2
- ordEntailsEq :: EntailsAll Ord Eq
- exArrow :: forall m cl f b. (forall a. Kleisli m (Inst1 f cl a) b) -> Kleisli m (Cell1 f cl) b
- arbitraryCell :: Name -> ExpQ
- arbitraryCell' :: Name -> [TypeQ] -> ExpQ
- arbitraryInstanceOf :: Name -> Name -> ExpQ
- arbitraryInstanceOf' :: Name -> Name -> [TypeQ] -> ExpQ
- onIdentity :: (a -> b -> c) -> Identity a -> Identity b -> c
- prop_consistent_equal :: (Eq a, Typeable a) => a -> a -> Property
- prop_consistent_compare :: (Ord a, Typeable a) => a -> a -> Property
- run_tests :: (PropName -> Property -> IO (a, Result)) -> IO ([a], Bool)
Documentation
Generilization of Cell
. 'Cell1 MyFunctor MyClass' takes values
^ of type 'MyFunctor a' with '(MyClass a,Typeable a)'.
type EntailsAll c0 c1 = forall a. c0 a :- c1 a Source #
_Cell :: (constr b, Typeable b, Typeable a) => Prism (Cell constr) (Cell constr) a b Source #
Prisms
Treats a Cell
as an unbounded sum type: 'c^?_Cell :: Maybe a' has the
^ value 'Just x' if x is of type a
and c
contains value x
. If cell c
^ has a value of any other type then a
, 'c^?_Cell == Nothing'.
_Cell' :: (constr a, Typeable a, HasCell c (Cell constr)) => Prism c c a a Source #
Similar to _Cell
but operates on types that wrap a cell instead of
^ on the cell itself.
_Cell1 :: (constr b, Typeable b, Typeable a, Typeable f) => Prism (Cell1 f constr) (Cell1 f constr) (f a) (f b) Source #
Similar to _Cell
but values are wrapped in type f
inside the cell.
_Cell1' :: (constr a, Typeable a, Typeable f, HasCell c (Cell1 f constr)) => Prism c c (f a) (f a) Source #
asCell :: (constr a, Typeable a) => Prism (Cell constr) (Cell constr) a a Source #
Like _Cell
but disallows changing the type of the content of the cell.
^ facilitates type checking when the prism is not used for modification.
asCell1 :: (constr a, Typeable a, Typeable f) => Prism (Cell1 f constr) (Cell1 f constr) (f a) (f a) Source #
asInst :: Functor g => (forall a. Inst1 f constr a -> g (Inst1 h constr' a)) -> Cell1 f constr -> g (Cell1 h constr') Source #
asInst1 :: Functor g => (forall a. Inst1 f constr a -> g (Inst1 h constr' a)) -> Cell1 f constr -> g (Cell1 h constr') Source #
traverseCell :: Functor f => (forall a. (constr a, Typeable a) => a -> f a) -> Cell constr -> f (Cell constr) Source #
Traversals
traverseCell' :: (Functor f, HasCell c (Cell constr)) => (forall a. (constr a, Typeable a) => a -> f a) -> c -> f c Source #
traverseCell1 :: Functor f => (forall a. (constr a, Typeable a) => g a -> f (h a)) -> Cell1 g constr -> f (Cell1 h constr) Source #
traverseCell1' :: (Functor f, HasCell c (Cell1 g constr)) => (forall a. (constr a, Typeable a) => g a -> f (g a)) -> c -> f c Source #
traverseInst1 :: Functor f => (constr a => g a -> f (h a)) -> Inst1 g constr a -> f (Inst1 h constr a) Source #
mapCell' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a) -> c -> c Source #
mapCell1 :: (forall a. (constr a, Typeable a) => f a -> f a) -> Cell1 f constr -> Cell1 f constr Source #
mapCell1' :: HasCell c (Cell1 f constr) => (forall a. (constr a, Typeable a) => f a -> f a) -> c -> c Source #
readCell1' :: HasCell c (Cell1 f constr) => (forall a. (constr a, Typeable a) => f a -> r) -> c -> r Source #
readCell' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> r) -> c -> r Source #
apply2Cells :: Functor f => (forall a. (constr a, Typeable a) => a -> a -> f a) -> f (Cell constr) -> Cell constr -> Cell constr -> f (Cell constr) Source #
Combinators =
apply2Cells' :: (Functor f, HasCell c (Cell constr)) => (forall a. (constr a, Typeable a) => a -> a -> f a) -> f c -> c -> c -> f c Source #
apply2Cells1 :: (Functor f, Typeable g) => (forall a. (constr a, Typeable a) => g a -> g a -> f (g a)) -> f (Cell1 g constr) -> Cell1 g constr -> Cell1 g constr -> f (Cell1 g constr) Source #
apply2Cells1' :: (Functor f, Typeable g, HasCell c (Cell1 g constr)) => (forall a. (constr a, Typeable a) => g a -> g a -> f (g a)) -> f c -> c -> c -> f c Source #
map2Cells :: (forall a. (constr a, Typeable a) => a -> a -> a) -> Cell constr -> Cell constr -> Cell constr -> Cell constr Source #
map2Cells' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a -> a) -> c -> c -> c -> c Source #
map2Cells1 :: (forall a. (constr a, Typeable a) => a -> a -> a) -> Cell constr -> Cell constr -> Cell constr -> Cell constr Source #
map2Cells1' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a -> a) -> c -> c -> c -> c Source #
read2CellsWith :: (forall a. (constr a, Typeable a) => a -> a -> r) -> r -> Cell constr -> Cell constr -> r Source #
read2CellsWith' :: HasCell c (Cell constr) => (forall a. (constr a, Typeable a) => a -> a -> r) -> r -> c -> c -> r Source #
read2Cells1With :: Typeable f => (forall a. (constr a, Typeable a) => f a -> f a -> r) -> r -> Cell1 f constr -> Cell1 f constr -> r Source #
read2Cells1With' :: (HasCell c (Cell1 f constr), Typeable f) => (forall a. (constr a, Typeable a) => f a -> f a -> r) -> r -> c -> c -> r Source #
read2CellsH :: (forall a b. (constr a, Typeable a, constr b, Typeable b) => a -> b -> r) -> Cell constr -> Cell constr -> r Source #
Heterogenous Combinators
read2CellsH' :: HasCell c (Cell constr) => (forall a b. (constr a, Typeable a, constr b, Typeable b) => a -> b -> r) -> c -> c -> r Source #
read2Cells1H :: (forall a b. (constr a, Typeable a, constr b, Typeable b) => f a -> f b -> r) -> Cell1 f constr -> Cell1 f constr -> r Source #
read2Cells1H' :: (forall a b. (constr a, Typeable a, constr b, Typeable b) => f a -> f b -> r) -> Cell1 f constr -> Cell1 f constr -> r Source #
cell1Equal :: Typeable f => (forall a. constr a => f a -> f a -> Bool) -> Cell1 f constr -> Cell1 f constr -> Bool Source #
Comparing the content of cells
cell1Equal' :: (HasCell c (Cell1 f constr), Typeable f) => (forall a. constr a => f a -> f a -> Bool) -> c -> c -> Bool Source #
cellEqual' :: HasCell c (Cell constr) => (forall a. constr a => a -> a -> Bool) -> c -> c -> Bool Source #
cellZoomEqual' :: (HasCell c (Cell constr), Eq c, Show c) => (forall a. constr a => a -> a -> Invariant) -> c -> c -> Invariant Source #
cell1ZoomEqual' :: (HasCell c (Cell1 f constr), Eq c, Show c, Typeable f) => (forall a. constr a => f a -> f a -> Invariant) -> c -> c -> Invariant Source #
cellCompare :: (forall a. constr a => a -> a -> Ordering) -> Cell constr -> Cell constr -> Ordering Source #
cellCompare' :: HasCell c (Cell constr) => (forall a. constr a => a -> a -> Ordering) -> c -> c -> Ordering Source #
cell1Compare :: Typeable f => (forall a. constr a => f a -> f a -> Ordering) -> Cell1 f constr -> Cell1 f constr -> Ordering Source #
cell1Compare' :: (HasCell c (Cell1 f constr), Typeable f) => (forall a. constr a => f a -> f a -> Ordering) -> c -> c -> Ordering Source #
cellLens :: Functor f => (forall a. constr a => LensLike' f a b) -> LensLike' f (Cell constr) b Source #
Creating Lenses
cellLens' :: (HasCell c (Cell constr), Functor f) => (forall a. constr a => LensLike' f a b) -> LensLike' f c b Source #
cell1Lens :: Functor f => (forall a. constr a => LensLike' f (g a) b) -> LensLike' f (Cell1 g constr) b Source #
cell1Lens' :: (HasCell c (Cell1 g constr), Functor f) => (forall a. constr a => LensLike' f (g a) b) -> LensLike' f c b Source #
rewriteCell :: EntailsAll c0 c1 -> Cell1 f c0 -> Cell1 f c1 Source #
Change type classes
transEnt :: EntailsAll c0 c1 -> EntailsAll c1 c2 -> EntailsAll c0 c2 Source #
exArrow :: forall m cl f b. (forall a. Kleisli m (Inst1 f cl a) b) -> Kleisli m (Cell1 f cl) b Source #
arbitraryCell :: Name -> ExpQ Source #
QuickCheck Helpers
onIdentity :: (a -> b -> c) -> Identity a -> Identity b -> c Source #
prop_consistent_equal :: (Eq a, Typeable a) => a -> a -> Property Source #
Properties
Wrapping two values in cells does not change their equality