| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Polysemy.ConstraintAbsorber
Contents
Synopsis
- absorbWithSem :: forall (p :: (Type -> Type) -> Constraint) (x :: (Type -> Type) -> Type -> Type -> Type) d r a. d -> (forall s. Reifies s d :- p (x (Sem r) s)) -> (p (Sem r) => Sem r a) -> Sem r a
- class Reifies (s :: k) a | s -> a
- newtype a :- b = Sub (a -> Dict b)
- data Dict a where
- reflect :: Reifies s a => proxy s -> a
- data Proxy (t :: k) :: forall k. k -> Type = Proxy
Absorb builder
Arguments
| :: forall (p :: (Type -> Type) -> Constraint) (x :: (Type -> Type) -> Type -> Type -> Type). d | Reified dictionary | 
| -> (forall s. Reifies s d :- p (x (Sem r) s)) | |
| -> (p (Sem r) => Sem r a) | |
| -> Sem r a | 
This function can be used to locally introduce typeclass instances for
 Sem. See MonadState for an example of how to
 use it.
Since: 0.3.0.0
Re-exports
class Reifies (s :: k) a | s -> a #
Minimal complete definition
Instances
| KnownNat n => Reifies (n :: Nat) Integer | |
| Defined in Data.Reflection | |
| KnownSymbol n => Reifies (n :: Symbol) String | |
| Defined in Data.Reflection | |
| Reifies Z Int | |
| Defined in Data.Reflection | |
| Reifies n Int => Reifies (D n :: Type) Int | |
| Defined in Data.Reflection | |
| Reifies n Int => Reifies (SD n :: Type) Int | |
| Defined in Data.Reflection | |
| Reifies n Int => Reifies (PD n :: Type) Int | |
| Defined in Data.Reflection | |
| (B b0, B b1, B b2, B b3, B b4, B b5, B b6, B b7, w0 ~ W b0 b1 b2 b3, w1 ~ W b4 b5 b6 b7) => Reifies (Stable w0 w1 a :: Type) a | |
| Defined in Data.Reflection | |
This is the type of entailment.
a  is read as :- ba "entails" b.
With this we can actually build a category for Constraint resolution.
e.g.
Because Eq aOrd aOrd aEq a
Because instance  exists, we can show that Ord a => Ord [a]Ord aOrd [a]
This relationship is captured in the :- entailment type here.
Since p  and entailment composes, :- p:- forms the arrows of a
 Category of constraints. However, Category only became sufficiently
 general to support this instance in GHC 7.8, so prior to 7.8 this instance
 is unavailable.
But due to the coherence of instance resolution in Haskell, this Category
 has some very interesting properties. Notably, in the absence of
 IncoherentInstances, this category is "thin", which is to say that
 between any two objects (constraints) there is at most one distinguishable
 arrow.
This means that for instance, even though there are two ways to derive
 Ord a :- Eq [a]
What are the two ways?
Well, we can go from Ord a :- Eq aEq a :- Eq [a]Ord a :- Ord [a]Ord [a] :- Eq [a]
Diagrammatically,
                   Ord a
               ins /     \ cls
                  v       v
            Ord [a]     Eq a
               cls \     / ins
                    v   v
                   Eq [a]This safety net ensures that pretty much anything you can write with this library is sensible and can't break any assumptions on the behalf of library authors.
Instances
| Category (:-) | Possible since GHC 7.8, when  | 
| () :=> (Eq (a :- b)) | |
| () :=> (Ord (a :- b)) | |
| () :=> (Show (a :- b)) | |
| Eq (a :- b) | Assumes  | 
| (Typeable p, Typeable q, p, q) => Data (p :- q) | |
| Defined in Data.Constraint Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> (p :- q) -> c (p :- q) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (p :- q) # toConstr :: (p :- q) -> Constr # dataTypeOf :: (p :- q) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (p :- q)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (p :- q)) # gmapT :: (forall b. Data b => b -> b) -> (p :- q) -> p :- q # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r # gmapQ :: (forall d. Data d => d -> u) -> (p :- q) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (p :- q) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) # | |
| Ord (a :- b) | Assumes  | 
| Defined in Data.Constraint | |
| Show (a :- b) | |
| a => NFData (a :- b) | |
| Defined in Data.Constraint | |
Values of type Dict pp.
e.g.
Dict::Dict(EqInt)
captures a dictionary that proves we have an:
instance Eq 'Int
Pattern matching on the Dict constructor will bring this instance into scope.
Instances
| 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 Methods 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 :: (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 | |
reflect :: Reifies s a => proxy s -> a #
Recover a value inside a reify context, given a proxy for its
 reified type.
data Proxy (t :: k) :: forall k. k -> Type #
Proxy is a type that holds no data, but has a phantom parameter of
 arbitrary type (or even kind). Its use is to provide type information, even
 though there is no value available of that type (or it may be too costly to
 create one).
Historically, Proxy :: Proxy a'undefined :: a' idiom.
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy | 
Instances
| Generic1 (Proxy :: k -> Type) | |
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
| Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 | 
| Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 | 
| Bounded (Proxy t) | Since: base-4.7.0.0 | 
| Enum (Proxy s) | Since: base-4.7.0.0 | 
| Eq (Proxy s) | Since: base-4.7.0.0 | 
| Ord (Proxy s) | Since: base-4.7.0.0 | 
| Read (Proxy t) | Since: base-4.7.0.0 | 
| Show (Proxy s) | Since: base-4.7.0.0 | 
| Ix (Proxy s) | Since: base-4.7.0.0 | 
| Defined in Data.Proxy | |
| Generic (Proxy t) | |
| Semigroup (Proxy s) | Since: base-4.9.0.0 | 
| Monoid (Proxy s) | Since: base-4.7.0.0 | 
| type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 | 
| type Rep (Proxy t) | Since: base-4.6.0.0 |