servant-subscriber-0.6.0.2: When REST is not enough ...

Safe HaskellNone
LanguageHaskell2010

Servant.Subscriber.Subscribable

Synopsis

Documentation

data Subscribable Source #

Instances
HasForeign lang ftype sublayout => HasForeign (lang :: k) ftype (Subscribable :> sublayout) Source # 
Instance details

Defined in Servant.Subscriber.Subscribable

Associated Types

type Foreign ftype (Subscribable :> sublayout) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Subscribable :> sublayout) -> Req ftype -> Foreign ftype (Subscribable :> sublayout) #

HasLink sub => HasLink (Subscribable :> sub :: Type) Source # 
Instance details

Defined in Servant.Subscriber.Subscribable

Associated Types

type MkLink (Subscribable :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (Subscribable :> sub) -> Link -> MkLink (Subscribable :> sub) a #

HasServer sublayout context => HasServer (Subscribable :> sublayout :: Type) context Source # 
Instance details

Defined in Servant.Subscriber.Subscribable

Associated Types

type ServerT (Subscribable :> sublayout) m :: Type #

Methods

route :: Proxy (Subscribable :> sublayout) -> Context context -> Delayed env (Server (Subscribable :> sublayout)) -> Router env #

hoistServerWithContext :: Proxy (Subscribable :> sublayout) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Subscribable :> sublayout) m -> ServerT (Subscribable :> sublayout) n #

type IsElem' sa (Subscribable :> sb) Source # 
Instance details

Defined in Servant.Subscriber.Subscribable

type IsElem' sa (Subscribable :> sb)
type Foreign ftype (Subscribable :> sublayout) Source # 
Instance details

Defined in Servant.Subscriber.Subscribable

type Foreign ftype (Subscribable :> sublayout) = Foreign ftype sublayout
type MkLink (Subscribable :> sub :: Type) a Source # 
Instance details

Defined in Servant.Subscriber.Subscribable

type MkLink (Subscribable :> sub :: Type) a = MkLink sub a
type ServerT (Subscribable :> sublayout :: Type) m Source # 
Instance details

Defined in Servant.Subscriber.Subscribable

type ServerT (Subscribable :> sublayout :: Type) m = ServerT sublayout m

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 IsElem' if it exhausts all other options.

>>> 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 b can be seen as capturing the notion of whether the URL represented by a would match the URL represented by b, *not* whether a request represented by a matches the endpoints serving b (for the latter, use IsIn).

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 :: *)) = ()