Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type family AllC cs k :: Constraint where ...
- data Somes cs where
- type Some c = Somes '[c]
- data Somes1 csf csa where
- Some1 :: forall k (csf :: [(k -> Type) -> Constraint]) (csa :: [k -> Constraint]) (f :: k -> Type) (a :: k). (AllC csf f, AllC csa a) => f a -> Somes1 csf csa
- type Some1 cf ca = Somes1 '[cf] '[ca]
- type SomesF f csa = Somes1 '[(~) f] csa
- type SomeF f c = SomesF f '[c]
- mapSome :: (forall a. AllC csa a => f a -> g a) -> SomesF f csa -> SomesF g csa
- (<~$>) :: (forall a. AllC csa a => f a -> g a) -> SomesF f csa -> SomesF g csa
- traverseSome :: Functor m => (forall a. AllC csa a => f a -> m (g a)) -> SomesF f csa -> m (SomesF g csa)
- (<~*>) :: Functor m => (forall a. AllC csa a => f a -> m (g a)) -> SomesF f csa -> m (SomesF g csa)
Combining constraints
type family AllC cs k :: Constraint where ... Source #
AllC ensures that a list of Constraint
s is applied to a poly-kinded Type
k
.
Existentials
Flat existentials
Existential with Constraint
s.
Example
Containerized existentials
Constrained containers
data Somes1 csf csa where Source #
Existential for containers with Constraint
s.
Example
Some1 :: forall k (csf :: [(k -> Type) -> Constraint]) (csa :: [k -> Constraint]) (f :: k -> Type) (a :: k). (AllC csf f, AllC csa a) => f a -> Somes1 csf csa |
Fixed containers
type SomesF f csa = Somes1 '[(~) f] csa Source #
Alias for Somes1
with a container f
and multiple Constraint
s csa
for its elements.
mapSome :: (forall a. AllC csa a => f a -> g a) -> SomesF f csa -> SomesF g csa Source #
Natural transformation of one container to another.
(<~$>) :: (forall a. AllC csa a => f a -> g a) -> SomesF f csa -> SomesF g csa infixl 4 Source #
Infix version of mapSome
.