| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Subscriber.Subscribable
Synopsis
- data Subscribable
- type family IsSubscribable endpoint api :: Constraint where ...
- type family IsSubscribable' endpoint api :: Constraint
- type family IsElem endpoint api :: Constraint where ...
- type family IsValidEndpoint endpoint :: Constraint where ...
Documentation
data Subscribable Source #
Instances
type family IsSubscribable endpoint api :: Constraint where ... Source #
Equations
| IsSubscribable sa (Subscribable :> sb) = () | |
| IsSubscribable e (sa :<|> sb) = Or (IsSubscribable e sa) (IsSubscribable e sb) | |
| IsSubscribable ((sym :: Symbol) :> sa) (sym :> sb) = IsSubscribable sa sb | |
| IsSubscribable (e :> sa) (e :> sb) = IsSubscribable sa sb | |
| IsSubscribable sa (Header sym x :> sb) = IsSubscribable sa sb | |
| IsSubscribable sa (ReqBody y x :> sb) = IsSubscribable sa sb | |
| IsSubscribable (Capture z y :> sa) (Capture x y :> sb) = IsSubscribable sa sb | |
| IsSubscribable sa (QueryParam x y :> sb) = IsSubscribable sa sb | |
| IsSubscribable sa (QueryParams x y :> sb) = IsSubscribable sa sb | |
| IsSubscribable sa (QueryFlag x :> sb) = IsSubscribable sa sb | |
| IsSubscribable e a = IsSubscribable' e a |
type family IsSubscribable' endpoint api :: Constraint Source #
You may use this type family to tell the type checker that your custom
type may be skipped as part of a link. This is useful for things like
QueryParam that are optional in a URI and are not part of a subscription uri.
>>>data CustomThing>>>type instance IsSubscribable' e (CustomThing :> sa) s = IsSubscribable e sa s
Note that IsSubscribable is called, which will mutually recurse back to IsSubscribable'
if it exhausts all other options again.
Once you have written a HasSubscription instance for CustomThing you are ready to go.
type family IsElem endpoint api :: Constraint where ... #
Closed type family, check if endpoint is within api.
Uses if it exhausts all other options.IsElem'
>>>ok (Proxy :: Proxy (IsElem ("hello" :> Get '[JSON] Int) SampleAPI))OK
>>>ok (Proxy :: Proxy (IsElem ("bye" :> Get '[JSON] Int) SampleAPI))... ... Could not deduce... ...
An endpoint is considered within an api even if it is missing combinators that don't affect the URL:
>>>ok (Proxy :: Proxy (IsElem (Get '[JSON] Int) (Header "h" Bool :> Get '[JSON] Int)))OK
>>>ok (Proxy :: Proxy (IsElem (Get '[JSON] Int) (ReqBody '[JSON] Bool :> Get '[JSON] Int)))OK
- N.B.:*
IsElem a bcan be seen as capturing the notion of whether the URL represented byawould match the URL represented byb, *not* whether a request represented byamatches the endpoints servingb(for the latter, useIsIn).
Equations
| IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb) | |
| IsElem (e :> sa) (e :> sb) = IsElem sa sb | |
| IsElem sa (Header sym x :> sb) = IsElem sa sb | |
| IsElem sa (ReqBody y x :> sb) = IsElem sa sb | |
| IsElem (CaptureAll z y :> sa) (CaptureAll x y :> sb) = IsElem sa sb | |
| IsElem (Capture z y :> sa) (Capture x y :> sb) = IsElem sa sb | |
| IsElem sa (QueryParam x y :> sb) = IsElem sa sb | |
| IsElem sa (QueryParams x y :> sb) = IsElem sa sb | |
| IsElem sa (QueryFlag x :> sb) = IsElem sa sb | |
| IsElem (Verb m s ct typ) (Verb m s ct' typ) = IsSubList ct ct' | |
| IsElem e e = () | |
| IsElem e a = IsElem' e a |
type family IsValidEndpoint endpoint :: Constraint where ... Source #
A valid endpoint may only contain Symbols and captures & for convenince Subscribable:
Equations
| IsValidEndpoint ((sym :: Symbol) :> sub) = IsValidEndpoint sub | |
| IsValidEndpoint (Capture z y :> sub) = IsValidEndpoint sub | |
| IsValidEndpoint (Subscribable :> sub) = IsValidEndpoint sub | |
| IsValidEndpoint (Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [*]) (a :: *)) = () |