Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module defines helper types and type families for working with sets of capabilities.
Synopsis
- type family All (xs :: [k -> Constraint]) a :: Constraint where ...
- type Capability = (Type -> Type) -> Constraint
- data Constraint
- data Dict a where
Documentation
type family All (xs :: [k -> Constraint]) a :: Constraint where ... Source #
Type family used used to express a conjunction of constraints over a single type.
Examples:
All '[Num, Eq] Int -- Equivalent to: (Num Int, Eq Int) All '[HasReader "foo" Int, HasSink "bar" Float] m -- Equivalent to: (HasReader "foo" Int m, HasSink "bar" Float m)
type Capability = (Type -> Type) -> Constraint Source #
A Capability
takes a type constructor Type -> Type
(e.g., a monad) and
returns a Constraint
. Examples of capabilities includ: HasReader "foo"
Int
, MonadIO
, …
data Constraint #
The kind of constraints, like Show a
Values of type
capture a dictionary for a constraint of type Dict
pp
.
e.g.
Dict
::Dict
(Eq
Int
)
captures a dictionary that proves we have an:
instance Eq
'Int
Pattern matching on the Dict
constructor will bring this instance into scope.
Instances
HasDict a (Dict a) | |
Defined in Data.Constraint | |
a :=> (Read (Dict a)) | |
a :=> (Monoid (Dict a)) | |
a :=> (Enum (Dict a)) | |
a :=> (Bounded (Dict a)) | |
() :=> (Eq (Dict a)) | |
() :=> (Ord (Dict a)) | |
() :=> (Show (Dict a)) | |
() :=> (Semigroup (Dict a)) | |
a => Bounded (Dict a) | |
a => Enum (Dict a) | |
Defined in Data.Constraint | |
Eq (Dict a) | |
(Typeable p, p) => Data (Dict p) | |
Defined in Data.Constraint gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dict p -> c (Dict p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dict p) # toConstr :: Dict p -> Constr # dataTypeOf :: Dict p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dict p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dict p)) # gmapT :: (forall b. Data b => b -> b) -> Dict p -> Dict p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r # gmapQ :: (forall d. Data d => d -> u) -> Dict p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dict p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # | |
Ord (Dict a) | |
a => Read (Dict a) | |
Show (Dict a) | |
Semigroup (Dict a) | |
a => Monoid (Dict a) | |
NFData (Dict c) | |
Defined in Data.Constraint |