servant-purescript-0.10.0.0: Generate PureScript accessor functions for you servant API

Safe HaskellNone
LanguageHaskell2010

Servant.API.BrowserHeader

Description

A header which gets sent by the browser and is thus of no concern for the client consumer of the API.

Documentation

data BrowserHeader (sym :: Symbol) a Source #

Instances
(KnownSymbol sym, HasForeign lang ftype sublayout) => HasForeign (lang :: Type) ftype (BrowserHeader sym a :> sublayout) Source # 
Instance details

Defined in Servant.API.BrowserHeader

Associated Types

type Foreign ftype (BrowserHeader sym a :> sublayout) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (BrowserHeader sym a :> sublayout) -> Req ftype -> Foreign ftype (BrowserHeader sym a :> sublayout) #

HasLink sub => HasLink (BrowserHeader sym a :> sub :: Type) Source # 
Instance details

Defined in Servant.API.BrowserHeader

Associated Types

type MkLink (BrowserHeader sym a :> sub) a :: Type #

Methods

toLink :: (Link -> a0) -> Proxy (BrowserHeader sym a :> sub) -> Link -> MkLink (BrowserHeader sym a :> sub) a0 #

(KnownSymbol sym, FromHttpApiData a, HasServer sublayout context) => HasServer (BrowserHeader sym a :> sublayout :: Type) context Source # 
Instance details

Defined in Servant.API.BrowserHeader

Associated Types

type ServerT (BrowserHeader sym a :> sublayout) m :: Type #

Methods

route :: Proxy (BrowserHeader sym a :> sublayout) -> Context context -> Delayed env (Server (BrowserHeader sym a :> sublayout)) -> Router env #

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

type IsElem' e (BrowserHeader :> s) Source # 
Instance details

Defined in Servant.API.BrowserHeader

type IsElem' e (BrowserHeader :> s) = IsElem e s
type Foreign ftype (BrowserHeader sym a :> sublayout) Source # 
Instance details

Defined in Servant.API.BrowserHeader

type Foreign ftype (BrowserHeader sym a :> sublayout) = Foreign ftype sublayout
type IsSubscribable' endpoint (BrowserHeader sym a :> sub) Source # 
Instance details

Defined in Servant.API.BrowserHeader

type IsSubscribable' endpoint (BrowserHeader sym a :> sub) = IsSubscribable endpoint sub
type MkLink (BrowserHeader sym a :> sub :: Type) b Source # 
Instance details

Defined in Servant.API.BrowserHeader

type MkLink (BrowserHeader sym a :> sub :: Type) b = MkLink (Header sym a :> sub) b
type ServerT (BrowserHeader sym a :> sublayout :: Type) m Source # 
Instance details

Defined in Servant.API.BrowserHeader

type ServerT (BrowserHeader sym a :> sublayout :: Type) m = ServerT (Header sym a :> sublayout) m