constrained-some-0.1.2: Existential type that can be constrained
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Some.Constraint

Synopsis

Combining constraints

type family AllC cs k :: Constraint where ... Source #

AllC ensures that a list of Constraints is applied to a poly-kinded Type k.

Equations

AllC '[] k = () 
AllC (c ': cs) k = (c k, AllC cs k) 

Existentials

Flat existentials

data Somes cs where Source #

Existential with Constraints.

Example

Expand
someShowableOrd :: Somes '[Show, Ord]
someShowableOrd = Somes (mempty :: [Double])

Constructors

Some :: forall (cs :: [Type -> Constraint]) (a :: Type). AllC cs a => a -> Somes cs 

Instances

Instances details
Show (Somes (Show ': cs)) Source # 
Instance details

Defined in Data.Some.Constraint

Methods

showsPrec :: Int -> Somes (Show ': cs) -> ShowS #

show :: Somes (Show ': cs) -> String #

showList :: [Somes (Show ': cs)] -> ShowS #

Show (Somes cs) => Show (Somes (c ': cs)) Source # 
Instance details

Defined in Data.Some.Constraint

Methods

showsPrec :: Int -> Somes (c ': cs) -> ShowS #

show :: Somes (c ': cs) -> String #

showList :: [Somes (c ': cs)] -> ShowS #

type Some c = Somes '[c] Source #

Alias for Somes with just one Constraint.

Containerized existentials

Constrained containers

data Somes1 csf csa where Source #

Existential for containers with Constraints.

Example

Expand
someNumFunctor :: Somes1 '[Functor] '[Num]
someNumFunctor = Somes1 $ [1, 2, 3 :: Int]

Constructors

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 

Instances

Instances details
(forall a. Show a => Show (f a)) => Show (SomesF f (Show ': cs)) Source # 
Instance details

Defined in Data.Some.Constraint

Methods

showsPrec :: Int -> SomesF f (Show ': cs) -> ShowS #

show :: SomesF f (Show ': cs) -> String #

showList :: [SomesF f (Show ': cs)] -> ShowS #

Show (SomesF f cs) => Show (SomesF f (c ': cs)) Source # 
Instance details

Defined in Data.Some.Constraint

Methods

showsPrec :: Int -> SomesF f (c ': cs) -> ShowS #

show :: SomesF f (c ': cs) -> String #

showList :: [SomesF f (c ': cs)] -> ShowS #

type Some1 cf ca = Somes1 '[cf] '[ca] Source #

Alias for Somes1 with just one Constraint.

Fixed containers

type SomesF f csa = Somes1 '[(~) f] csa Source #

Alias for Somes1 with a container f and multiple Constraints csa for its elements.

type SomeF f c = SomesF f '[c] Source #

Alias for SomeF with just one Constraint 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.

traverseSome :: Functor m => (forall a. AllC csa a => f a -> m (g a)) -> SomesF f csa -> m (SomesF g csa) Source #

Natural transformation of one container to another - with side effects in m.

(<~*>) :: Functor m => (forall a. AllC csa a => f a -> m (g a)) -> SomesF f csa -> m (SomesF g csa) infixl 4 Source #

Infix version of traverseSome.