servant-server-0.13: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.Server

Contents

Description

This module lets you implement Servers for defined APIs. You'll most likely just need serve.

Synopsis

Run a wai application from an API

serve :: HasServer api '[] => Proxy api -> Server api -> Application Source #

serve allows you to implement an API and produce a wai Application.

Example:

type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
        :<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books

server :: Server MyApi
server = listAllBooks :<|> postBook
  where listAllBooks = ...
        postBook book = ...

myApi :: Proxy MyApi
myApi = Proxy

app :: Application
app = serve myApi server

main :: IO ()
main = Network.Wai.Handler.Warp.run 8080 app

serveWithContext :: HasServer api context => Proxy api -> Context context -> Server api -> Application Source #

Construct a wai Application from an API

Handlers for all standard combinators

class HasServer api context where Source #

Minimal complete definition

route, hoistServerWithContext

Associated Types

type ServerT api (m :: * -> *) :: * Source #

Methods

route :: Proxy api -> Context context -> Delayed env (Server api) -> Router env Source #

hoistServerWithContext :: Proxy api -> Proxy context -> (forall x. m x -> n x) -> ServerT api m -> ServerT api n Source #

Instances

HasServer * Raw context Source #

Just pass the request to the underlying application and serve its response.

Example:

type MyApi = "images" :> Raw

server :: Server MyApi
server = serveDirectory "/var/www/images"

Associated Types

type ServerT Raw (context :: Raw) (m :: * -> *) :: * Source #

Methods

route :: Proxy Raw context -> Context context -> Delayed env (Server Raw context) -> Router env Source #

hoistServerWithContext :: Proxy Raw context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT Raw context m -> ServerT Raw context n Source #

HasServer * EmptyAPI context Source #

The server for an EmptyAPI is emptyAPIServer.

type MyApi = "nothing" :> EmptyApi

server :: Server MyApi
server = emptyAPIServer

Associated Types

type ServerT EmptyAPI (context :: EmptyAPI) (m :: * -> *) :: * Source #

Methods

route :: Proxy EmptyAPI context -> Context context -> Delayed env (Server EmptyAPI context) -> Router env Source #

hoistServerWithContext :: Proxy EmptyAPI context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT EmptyAPI context m -> ServerT EmptyAPI context n Source #

TypeError Constraint (HasServerArrowTypeError * * a b) => HasServer * (a -> b) context Source #

This instance prevents from accidentally using '->' instead of :>

>>> serve (Proxy :: Proxy (Capture "foo" Int -> Get '[JSON] Int)) (error "...")
...
...No instance HasServer (a -> b).
...Maybe you have used '->' instead of ':>' between
...Capture' '[] "foo" Int
...and
...Verb 'GET 200 '[JSON] Int
...
>>> undefined :: Server (Capture "foo" Int -> Get '[JSON] Int)
...
...No instance HasServer (a -> b).
...Maybe you have used '->' instead of ':>' between
...Capture' '[] "foo" Int
...and
...Verb 'GET 200 '[JSON] Int
...

Associated Types

type ServerT (a -> b) (context :: a -> b) (m :: * -> *) :: * Source #

Methods

route :: Proxy (a -> b) context -> Context context -> Delayed env (Server (a -> b) context) -> Router env Source #

hoistServerWithContext :: Proxy (a -> b) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (a -> b) context m -> ServerT (a -> b) context n Source #

(HasServer * a context, HasServer * b context) => HasServer * ((:<|>) a b) context Source #

A server for a :<|> b first tries to match the request against the route represented by a and if it fails tries b. You must provide a request handler for each route.

type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
        :<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books

server :: Server MyApi
server = listAllBooks :<|> postBook
  where listAllBooks = ...
        postBook book = ...

Associated Types

type ServerT (a :<|> b) (context :: a :<|> b) (m :: * -> *) :: * Source #

Methods

route :: Proxy (a :<|> b) context -> Context context -> Delayed env (Server (a :<|> b) context) -> Router env Source #

hoistServerWithContext :: Proxy (a :<|> b) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (a :<|> b) context m -> ServerT (a :<|> b) context n Source #

(HasContextEntry context (NamedContext name subContext), HasServer * subApi subContext) => HasServer * (WithNamedContext name subContext subApi) context Source # 

Associated Types

type ServerT (WithNamedContext name subContext subApi) (context :: WithNamedContext name subContext subApi) (m :: * -> *) :: * Source #

Methods

route :: Proxy (WithNamedContext name subContext subApi) context -> Context context -> Delayed env (Server (WithNamedContext name subContext subApi) context) -> Router env Source #

hoistServerWithContext :: Proxy (WithNamedContext name subContext subApi) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (WithNamedContext name subContext subApi) context m -> ServerT (WithNamedContext name subContext subApi) context n Source #

TypeError Constraint (HasServerArrowKindError (k -> l) arr) => HasServer * ((:>) (k -> l) arr api) context Source #

This instance catches mistakes when there are non-saturated type applications on LHS of :>.

>>> serve (Proxy :: Proxy (Capture "foo" :> Get '[JSON] Int)) (error "...")
...
...Expected something of kind Symbol or *, got: k -> l on the LHS of ':>'.
...Maybe you haven't applied enough arguments to
...Capture' '[] "foo"
...
>>> undefined :: Server (Capture "foo" :> Get '[JSON] Int)
...
...Expected something of kind Symbol or *, got: k -> l on the LHS of ':>'.
...Maybe you haven't applied enough arguments to
...Capture' '[] "foo"
...

Associated Types

type ServerT (((k -> l) :> arr) api) (context :: ((k -> l) :> arr) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy (((k -> l) :> arr) api) context -> Context context -> Delayed env (Server (((k -> l) :> arr) api) context) -> Router env Source #

hoistServerWithContext :: Proxy (((k -> l) :> arr) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (((k -> l) :> arr) api) context m -> ServerT (((k -> l) :> arr) api) context n Source #

HasServer * api context => HasServer * ((:>) * HttpVersion api) context Source # 

Associated Types

type ServerT ((* :> HttpVersion) api) (context :: (* :> HttpVersion) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> HttpVersion) api) context -> Context context -> Delayed env (Server ((* :> HttpVersion) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> HttpVersion) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> HttpVersion) api) context m -> ServerT ((* :> HttpVersion) api) context n Source #

(AllCTUnrender list a, HasServer * api context, SBoolI (FoldLenient mods)) => HasServer * ((:>) * (ReqBody' mods list a) api) context Source #

If you use ReqBody in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by ReqBody. The Content-Type header is inspected, and the list provided is used to attempt deserialization. If the request does not have a Content-Type header, it is treated as application/octet-stream (as specified in RFC7231. This lets servant worry about extracting it from the request and turning it into a value of the type you specify.

All it asks is for a FromJSON instance.

Example:

type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book

server :: Server MyApi
server = postBook
  where postBook :: Book -> Handler Book
        postBook book = ...insert into your db...

Associated Types

type ServerT ((* :> ReqBody' mods list a) api) (context :: (* :> ReqBody' mods list a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> ReqBody' mods list a) api) context -> Context context -> Delayed env (Server ((* :> ReqBody' mods list a) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> ReqBody' mods list a) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> ReqBody' mods list a) api) context m -> ServerT ((* :> ReqBody' mods list a) api) context n Source #

HasServer * api context => HasServer * ((:>) * RemoteHost api) context Source # 

Associated Types

type ServerT ((* :> RemoteHost) api) (context :: (* :> RemoteHost) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> RemoteHost) api) context -> Context context -> Delayed env (Server ((* :> RemoteHost) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> RemoteHost) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> RemoteHost) api) context m -> ServerT ((* :> RemoteHost) api) context n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer * api context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer * ((:>) * (QueryParam' mods sym a) api) context Source #

If you use QueryParam "author" Text in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type Maybe Text.

This lets servant worry about looking it up in the query string and turning it into a value of the type you specify, enclosed in Maybe, because it may not be there and servant would then hand you Nothing.

You can control how it'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: Maybe Text -> Handler [Book]
        getBooksBy Nothing       = ...return all books...
        getBooksBy (Just author) = ...return books by the given author...

Associated Types

type ServerT ((* :> QueryParam' mods sym a) api) (context :: (* :> QueryParam' mods sym a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> QueryParam' mods sym a) api) context -> Context context -> Delayed env (Server ((* :> QueryParam' mods sym a) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> QueryParam' mods sym a) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> QueryParam' mods sym a) api) context m -> ServerT ((* :> QueryParam' mods sym a) api) context n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer * api context) => HasServer * ((:>) * (QueryParams sym a) api) context Source #

If you use QueryParams "authors" Text in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type [Text].

This lets servant worry about looking up 0 or more values in the query string associated to authors and turning each of them into a value of the type you specify.

You can control how the individual values are converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: [Text] -> Handler [Book]
        getBooksBy authors = ...return all books by these authors...

Associated Types

type ServerT ((* :> QueryParams sym a) api) (context :: (* :> QueryParams sym a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> QueryParams sym a) api) context -> Context context -> Delayed env (Server ((* :> QueryParams sym a) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> QueryParams sym a) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> QueryParams sym a) api) context m -> ServerT ((* :> QueryParams sym a) api) context n Source #

(KnownSymbol sym, HasServer * api context) => HasServer * ((:>) * (QueryFlag sym) api) context Source #

If you use QueryFlag "published" in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type Bool.

Example:

type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]

server :: Server MyApi
server = getBooks
  where getBooks :: Bool -> Handler [Book]
        getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...

Associated Types

type ServerT ((* :> QueryFlag sym) api) (context :: (* :> QueryFlag sym) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> QueryFlag sym) api) context -> Context context -> Delayed env (Server ((* :> QueryFlag sym) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> QueryFlag sym) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> QueryFlag sym) api) context m -> ServerT ((* :> QueryFlag sym) api) context n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer * api context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer * ((:>) * (Header' * mods sym a) api) context Source #

If you use Header in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by Header. This lets servant worry about extracting it from the request and turning it into a value of the type you specify.

All it asks is for a FromHttpApiData instance.

Example:

newtype Referer = Referer Text
  deriving (Eq, Show, FromHttpApiData)

           -- GET /view-my-referer
type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer

server :: Server MyApi
server = viewReferer
  where viewReferer :: Referer -> Handler referer
        viewReferer referer = return referer

Associated Types

type ServerT ((* :> Header' * mods sym a) api) (context :: (* :> Header' * mods sym a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> Header' * mods sym a) api) context -> Context context -> Delayed env (Server ((* :> Header' * mods sym a) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> Header' * mods sym a) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> Header' * mods sym a) api) context m -> ServerT ((* :> Header' * mods sym a) api) context n Source #

HasServer * api context => HasServer * ((:>) * IsSecure api) context Source # 

Associated Types

type ServerT ((* :> IsSecure) api) (context :: (* :> IsSecure) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> IsSecure) api) context -> Context context -> Delayed env (Server ((* :> IsSecure) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> IsSecure) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> IsSecure) api) context m -> ServerT ((* :> IsSecure) api) context n Source #

HasServer * api ctx => HasServer * ((:>) * (Summary desc) api) ctx Source #

Ignore Summary in server handlers.

Associated Types

type ServerT ((* :> Summary desc) api) (ctx :: (* :> Summary desc) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> Summary desc) api) ctx -> Context context -> Delayed env (Server ((* :> Summary desc) api) ctx) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> Summary desc) api) ctx -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> Summary desc) api) ctx m -> ServerT ((* :> Summary desc) api) ctx n Source #

HasServer * api ctx => HasServer * ((:>) * (Description desc) api) ctx Source #

Ignore Description in server handlers.

Associated Types

type ServerT ((* :> Description desc) api) (ctx :: (* :> Description desc) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> Description desc) api) ctx -> Context context -> Delayed env (Server ((* :> Description desc) api) ctx) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> Description desc) api) ctx -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> Description desc) api) ctx m -> ServerT ((* :> Description desc) api) ctx n Source #

(KnownSymbol capture, FromHttpApiData a, HasServer * api context) => HasServer * ((:>) * (Capture' mods capture a) api) context Source #

If you use Capture in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by the Capture. This lets servant worry about getting it from the URL and turning it into a value of the type you specify.

You can control how it'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book

server :: Server MyApi
server = getBook
  where getBook :: Text -> Handler Book
        getBook isbn = ...

Associated Types

type ServerT ((* :> Capture' mods capture a) api) (context :: (* :> Capture' mods capture a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> Capture' mods capture a) api) context -> Context context -> Delayed env (Server ((* :> Capture' mods capture a) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> Capture' mods capture a) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> Capture' mods capture a) api) context m -> ServerT ((* :> Capture' mods capture a) api) context n Source #

(KnownSymbol capture, FromHttpApiData a, HasServer * api context) => HasServer * ((:>) * (CaptureAll capture a) api) context Source #

If you use CaptureAll in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of a list of the type specified by the CaptureAll. This lets servant worry about getting values from the URL and turning them into values of the type you specify.

You can control how they'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile

server :: Server MyApi
server = getSourceFile
  where getSourceFile :: [Text] -> Handler Book
        getSourceFile pathSegments = ...

Associated Types

type ServerT ((* :> CaptureAll capture a) api) (context :: (* :> CaptureAll capture a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> CaptureAll capture a) api) context -> Context context -> Delayed env (Server ((* :> CaptureAll capture a) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> CaptureAll capture a) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> CaptureAll capture a) api) context m -> ServerT ((* :> CaptureAll capture a) api) context n Source #

(KnownSymbol realm, HasServer * api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer * ((:>) * (BasicAuth realm usr) api) context Source #

Basic Authentication

Associated Types

type ServerT ((* :> BasicAuth realm usr) api) (context :: (* :> BasicAuth realm usr) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> BasicAuth realm usr) api) context -> Context context -> Delayed env (Server ((* :> BasicAuth realm usr) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> BasicAuth realm usr) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> BasicAuth realm usr) api) context m -> ServerT ((* :> BasicAuth realm usr) api) context n Source #

HasServer * api context => HasServer * ((:>) * Vault api) context Source # 

Associated Types

type ServerT ((* :> Vault) api) (context :: (* :> Vault) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((* :> Vault) api) context -> Context context -> Delayed env (Server ((* :> Vault) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((* :> Vault) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> Vault) api) context m -> ServerT ((* :> Vault) api) context n Source #

(KnownSymbol path, HasServer * api context) => HasServer * ((:>) Symbol path api) context Source #

Make sure the incoming request starts with "/path", strip it and pass the rest of the request path to api.

Associated Types

type ServerT ((Symbol :> path) api) (context :: (Symbol :> path) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((Symbol :> path) api) context -> Context context -> Delayed env (Server ((Symbol :> path) api) context) -> Router env Source #

hoistServerWithContext :: Proxy ((Symbol :> path) api) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((Symbol :> path) api) context m -> ServerT ((Symbol :> path) api) context n Source #

(AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status, GetHeaders (Headers h a)) => HasServer * (Verb k1 method status ctypes (Headers h a)) context Source # 

Associated Types

type ServerT (Verb k1 method status ctypes (Headers h a)) (context :: Verb k1 method status ctypes (Headers h a)) (m :: * -> *) :: * Source #

Methods

route :: Proxy (Verb k1 method status ctypes (Headers h a)) context -> Context context -> Delayed env (Server (Verb k1 method status ctypes (Headers h a)) context) -> Router env Source #

hoistServerWithContext :: Proxy (Verb k1 method status ctypes (Headers h a)) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (Verb k1 method status ctypes (Headers h a)) context m -> ServerT (Verb k1 method status ctypes (Headers h a)) context n Source #

(AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status) => HasServer * (Verb k1 method status ctypes a) context Source # 

Associated Types

type ServerT (Verb k1 method status ctypes a) (context :: Verb k1 method status ctypes a) (m :: * -> *) :: * Source #

Methods

route :: Proxy (Verb k1 method status ctypes a) context -> Context context -> Delayed env (Server (Verb k1 method status ctypes a) context) -> Router env Source #

hoistServerWithContext :: Proxy (Verb k1 method status ctypes a) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (Verb k1 method status ctypes a) context m -> ServerT (Verb k1 method status ctypes a) context n Source #

(MimeRender * ctype a, ReflectMethod k1 method, FramingRender * * framing ctype, ToStreamGenerator f a, GetHeaders (Headers h (f a))) => HasServer * (Stream k1 method framing ctype (Headers h (f a))) context Source # 

Associated Types

type ServerT (Stream k1 method framing ctype (Headers h (f a))) (context :: Stream k1 method framing ctype (Headers h (f a))) (m :: * -> *) :: * Source #

Methods

route :: Proxy (Stream k1 method framing ctype (Headers h (f a))) context -> Context context -> Delayed env (Server (Stream k1 method framing ctype (Headers h (f a))) context) -> Router env Source #

hoistServerWithContext :: Proxy (Stream k1 method framing ctype (Headers h (f a))) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (Stream k1 method framing ctype (Headers h (f a))) context m -> ServerT (Stream k1 method framing ctype (Headers h (f a))) context n Source #

(MimeRender * ctype a, ReflectMethod k1 method, FramingRender * * framing ctype, ToStreamGenerator f a) => HasServer * (Stream k1 method framing ctype (f a)) context Source # 

Associated Types

type ServerT (Stream k1 method framing ctype (f a)) (context :: Stream k1 method framing ctype (f a)) (m :: * -> *) :: * Source #

Methods

route :: Proxy (Stream k1 method framing ctype (f a)) context -> Context context -> Delayed env (Server (Stream k1 method framing ctype (f a)) context) -> Router env Source #

hoistServerWithContext :: Proxy (Stream k1 method framing ctype (f a)) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT (Stream k1 method framing ctype (f a)) context m -> ServerT (Stream k1 method framing ctype (f a)) context n Source #

type Server api = ServerT api Handler Source #

newtype Handler a Source #

Constructors

Handler 

Instances

Monad Handler Source # 

Methods

(>>=) :: Handler a -> (a -> Handler b) -> Handler b #

(>>) :: Handler a -> Handler b -> Handler b #

return :: a -> Handler a #

fail :: String -> Handler a #

Functor Handler Source # 

Methods

fmap :: (a -> b) -> Handler a -> Handler b #

(<$) :: a -> Handler b -> Handler a #

Applicative Handler Source # 

Methods

pure :: a -> Handler a #

(<*>) :: Handler (a -> b) -> Handler a -> Handler b #

liftA2 :: (a -> b -> c) -> Handler a -> Handler b -> Handler c #

(*>) :: Handler a -> Handler b -> Handler b #

(<*) :: Handler a -> Handler b -> Handler a #

MonadIO Handler Source # 

Methods

liftIO :: IO a -> Handler a #

MonadThrow Handler Source # 

Methods

throwM :: Exception e => e -> Handler a #

MonadCatch Handler Source # 

Methods

catch :: Exception e => Handler a -> (e -> Handler a) -> Handler a #

MonadBase IO Handler Source # 

Methods

liftBase :: IO α -> Handler α #

MonadBaseControl IO Handler Source # 

Associated Types

type StM (Handler :: * -> *) a :: * #

MonadError ServantErr Handler Source # 
Generic (Handler a) Source # 

Associated Types

type Rep (Handler a) :: * -> * #

Methods

from :: Handler a -> Rep (Handler a) x #

to :: Rep (Handler a) x -> Handler a #

type StM Handler a Source # 
type Rep (Handler a) Source # 
type Rep (Handler a) = D1 * (MetaData "Handler" "Servant.Server.Internal.Handler" "servant-server-0.13-BOZo8GLoTgf70i45LCW8jq" True) (C1 * (MetaCons "Handler" PrefixI True) (S1 * (MetaSel (Just Symbol "runHandler'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (ExceptT ServantErr IO a))))

Debugging the server layout

layout :: HasServer api '[] => Proxy api -> Text Source #

The function layout produces a textual description of the internal router layout for debugging purposes. Note that the router layout is determined just by the API, not by the handlers.

Example:

For the following API

type API =
       "a" :> "d" :> Get '[JSON] NoContent
  :<|> "b" :> Capture "x" Int :> Get '[JSON] Bool
  :<|> "c" :> Put '[JSON] Bool
  :<|> "a" :> "e" :> Get '[JSON] Int
  :<|> "b" :> Capture "x" Int :> Put '[JSON] Bool
  :<|> Raw

we get the following output:

/
├─ a/
│  ├─ d/
│  │  └─•
│  └─ e/
│     └─•
├─ b/
│  └─ <capture>/
│     ├─•
│     ┆
│     └─•
├─ c/
│  └─•
┆
└─ <raw>

Explanation of symbols:

Normal lines reflect static branching via a table.
a/
Nodes reflect static path components.
─•
Leaves reflect endpoints.
<capture>/
This is a delayed capture of a path component.
<raw>
This is a part of the API we do not know anything about.
Dashed lines suggest a dynamic choice between the part above and below. If there is a success for fatal failure in the first part, that one takes precedence. If both parts fail, the "better" error code will be returned.

layoutWithContext :: HasServer api context => Proxy api -> Context context -> Text Source #

Variant of layout that takes an additional Context.

Enter / hoisting server

hoistServer :: HasServer api '[] => Proxy api -> (forall x. m x -> n x) -> ServerT api m -> ServerT api n Source #

Hoist server implementation.

Sometimes our cherished Handler monad isn't quite the type you'd like for your handlers. Maybe you want to thread some configuration in a Reader monad. Or have your types ensure that your handlers don't do any IO. Use hoistServer (a successor of now deprecated enter).

With hoistServer, you can provide a function, to convert any number of endpoints from one type constructor to another. For example

Note: Server Raw can also be entered. It will be retagged.

>>> import Control.Monad.Reader
>>> type ReaderAPI = "ep1" :> Get '[JSON] Int :<|> "ep2" :> Get '[JSON] String :<|> Raw :<|> EmptyAPI
>>> let readerApi = Proxy :: Proxy ReaderAPI
>>> let readerServer = return 1797 :<|> ask :<|> Tagged (error "raw server") :<|> emptyServer :: ServerT ReaderAPI (Reader String)
>>> let nt x = return (runReader x "hi")
>>> let mainServer = hoistServer readerApi nt readerServer :: Server ReaderAPI

Functions based on mmorph

tweakResponse :: (RouteResult Response -> RouteResult Response) -> Router env -> Router env Source #

Apply a transformation to the response of a Router.

Context

data Context contextTypes where Source #

Contexts are used to pass values to combinators. (They are not meant to be used to pass parameters to your handlers, i.e. they should not replace any custom ReaderT-monad-stack that you're using with Enter.) If you don't use combinators that require any context entries, you can just use serve as always.

If you are using combinators that require a non-empty Context you have to use serveWithContext and pass it a Context that contains all the values your combinators need. A Context is essentially a heterogenous list and accessing the elements is being done by type (see getContextEntry). The parameter of the type Context is a type-level list reflecting the types of the contained context entries. To create a Context with entries, use the operator (:.):

>>> :type True :. () :. EmptyContext
True :. () :. EmptyContext :: Context '[Bool, ()]

Constructors

EmptyContext :: Context '[] 
(:.) :: x -> Context xs -> Context (x ': xs) infixr 5 

Instances

(Eq a, Eq (Context as)) => Eq (Context ((:) * a as)) Source # 

Methods

(==) :: Context ((* ': a) as) -> Context ((* ': a) as) -> Bool #

(/=) :: Context ((* ': a) as) -> Context ((* ': a) as) -> Bool #

Eq (Context ([] *)) Source # 

Methods

(==) :: Context [*] -> Context [*] -> Bool #

(/=) :: Context [*] -> Context [*] -> Bool #

(Show a, Show (Context as)) => Show (Context ((:) * a as)) Source # 

Methods

showsPrec :: Int -> Context ((* ': a) as) -> ShowS #

show :: Context ((* ': a) as) -> String #

showList :: [Context ((* ': a) as)] -> ShowS #

Show (Context ([] *)) Source # 

Methods

showsPrec :: Int -> Context [*] -> ShowS #

show :: Context [*] -> String #

showList :: [Context [*]] -> ShowS #

class HasContextEntry (context :: [*]) (val :: *) where Source #

This class is used to access context entries in Contexts. getContextEntry returns the first value where the type matches:

>>> getContextEntry (True :. False :. EmptyContext) :: Bool
True

If the Context does not contain an entry of the requested type, you'll get an error:

>>> getContextEntry (True :. False :. EmptyContext) :: String
...
...No instance for (HasContextEntry '[] [Char])
...

Minimal complete definition

getContextEntry

Methods

getContextEntry :: Context context -> val Source #

Instances

HasContextEntry ((:) * val xs) val Source # 

Methods

getContextEntry :: Context ((* ': val) xs) -> val Source #

HasContextEntry xs val => HasContextEntry ((:) * notIt xs) val Source # 

Methods

getContextEntry :: Context ((* ': notIt) xs) -> val Source #

NamedContext

data NamedContext (name :: Symbol) (subContext :: [*]) Source #

Normally context entries are accessed by their types. In case you need to have multiple values of the same type in your Context and need to access them, we provide NamedContext. You can think of it as sub-namespaces for Contexts.

Constructors

NamedContext (Context subContext) 

descendIntoNamedContext :: forall context name subContext. HasContextEntry context (NamedContext name subContext) => Proxy (name :: Symbol) -> Context context -> Context subContext Source #

descendIntoNamedContext allows you to access NamedContexts. Usually you won't have to use it yourself but instead use a combinator like WithNamedContext.

This is how descendIntoNamedContext works:

>>> :set -XFlexibleContexts
>>> let subContext = True :. EmptyContext
>>> :type subContext
subContext :: Context '[Bool]
>>> let parentContext = False :. (NamedContext subContext :: NamedContext "subContext" '[Bool]) :. EmptyContext
>>> :type parentContext
parentContext :: Context '[Bool, NamedContext "subContext" '[Bool]]
>>> descendIntoNamedContext (Proxy :: Proxy "subContext") parentContext :: Context '[Bool]
True :. EmptyContext

Basic Authentication

newtype BasicAuthCheck usr Source #

Datatype wrapping a function used to check authentication.

Instances

Functor BasicAuthCheck Source # 

Methods

fmap :: (a -> b) -> BasicAuthCheck a -> BasicAuthCheck b #

(<$) :: a -> BasicAuthCheck b -> BasicAuthCheck a #

Generic (BasicAuthCheck usr) Source # 

Associated Types

type Rep (BasicAuthCheck usr) :: * -> * #

Methods

from :: BasicAuthCheck usr -> Rep (BasicAuthCheck usr) x #

to :: Rep (BasicAuthCheck usr) x -> BasicAuthCheck usr #

type Rep (BasicAuthCheck usr) Source # 
type Rep (BasicAuthCheck usr) = D1 * (MetaData "BasicAuthCheck" "Servant.Server.Internal.BasicAuth" "servant-server-0.13-BOZo8GLoTgf70i45LCW8jq" True) (C1 * (MetaCons "BasicAuthCheck" PrefixI True) (S1 * (MetaSel (Just Symbol "unBasicAuthCheck") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (BasicAuthData -> IO (BasicAuthResult usr)))))

data BasicAuthResult usr Source #

servant-server's current implementation of basic authentication is not immune to certian kinds of timing attacks. Decoding payloads does not take a fixed amount of time.

The result of authentication/authorization

Instances

Functor BasicAuthResult Source # 

Methods

fmap :: (a -> b) -> BasicAuthResult a -> BasicAuthResult b #

(<$) :: a -> BasicAuthResult b -> BasicAuthResult a #

Eq usr => Eq (BasicAuthResult usr) Source # 
Read usr => Read (BasicAuthResult usr) Source # 
Show usr => Show (BasicAuthResult usr) Source # 
Generic (BasicAuthResult usr) Source # 

Associated Types

type Rep (BasicAuthResult usr) :: * -> * #

Methods

from :: BasicAuthResult usr -> Rep (BasicAuthResult usr) x #

to :: Rep (BasicAuthResult usr) x -> BasicAuthResult usr #

type Rep (BasicAuthResult usr) Source # 
type Rep (BasicAuthResult usr) = D1 * (MetaData "BasicAuthResult" "Servant.Server.Internal.BasicAuth" "servant-server-0.13-BOZo8GLoTgf70i45LCW8jq" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Unauthorized" PrefixI False) (U1 *)) (C1 * (MetaCons "BadPassword" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NoSuchUser" PrefixI False) (U1 *)) (C1 * (MetaCons "Authorized" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * usr)))))

General Authentication

Default error type

3XX

err300 :: ServantErr Source #

err300 Multiple Choices

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err300 { errBody = "I can't choose." }

err301 :: ServantErr Source #

err301 Moved Permanently

Example:

failingHandler :: Handler ()
failingHandler = throwError err301

err302 :: ServantErr Source #

err302 Found

Example:

failingHandler :: Handler ()
failingHandler = throwError err302

err303 :: ServantErr Source #

err303 See Other

Example:

failingHandler :: Handler ()
failingHandler = throwError err303

err304 :: ServantErr Source #

err304 Not Modified

Example:

failingHandler :: Handler ()
failingHandler = throwError err304

err305 :: ServantErr Source #

err305 Use Proxy

Example:

failingHandler :: Handler ()
failingHandler = throwError err305

err307 :: ServantErr Source #

err307 Temporary Redirect

Example:

failingHandler :: Handler ()
failingHandler = throwError err307

4XX

err400 :: ServantErr Source #

err400 Bad Request

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err400 { errBody = "Your request makes no sense to me." }

err401 :: ServantErr Source #

err401 Unauthorized

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err401 { errBody = "Your credentials are invalid." }

err402 :: ServantErr Source #

err402 Payment Required

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err402 { errBody = "You have 0 credits. Please give me $$$." }

err403 :: ServantErr Source #

err403 Forbidden

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err403 { errBody = "Please login first." }

err404 :: ServantErr Source #

err404 Not Found

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err404 { errBody = "(╯°□°)╯︵ ┻━┻)." }

err405 :: ServantErr Source #

err405 Method Not Allowed

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err405 { errBody = "Your account privileges does not allow for this.  Please pay $$$." }

err406 :: ServantErr Source #

err406 Not Acceptable

Example:

failingHandler :: Handler ()
failingHandler = throwError err406

err407 :: ServantErr Source #

err407 Proxy Authentication Required

Example:

failingHandler :: Handler ()
failingHandler = throwError err407

err409 :: ServantErr Source #

err409 Conflict

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err409 { errBody = "Transaction conflicts with 59879cb56c7c159231eeacdd503d755f7e835f74" }

err410 :: ServantErr Source #

err410 Gone

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err410 { errBody = "I know it was here at some point, but.. I blame bad luck." }

err411 :: ServantErr Source #

err411 Length Required

Example:

failingHandler :: Handler ()
failingHandler = throwError err411

err412 :: ServantErr Source #

err412 Precondition Failed

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err412 { errBody = "Precondition fail: x < 42 && y > 57" }

err413 :: ServantErr Source #

err413 Request Entity Too Large

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err413 { errBody = "Request exceeded 64k." }

err414 :: ServantErr Source #

err414 Request-URI Too Large

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err414 { errBody = "Maximum length is 64." }

err415 :: ServantErr Source #

err415 Unsupported Media Type

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err415 { errBody = "Supported media types:  gif, png" }

err416 :: ServantErr Source #

err416 Request range not satisfiable

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err416 { errBody = "Valid range is [0, 424242]." }

err417 :: ServantErr Source #

err417 Expectation Failed

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err417 { errBody = "I found a quux in the request.  This isn't going to work." }

err418 :: ServantErr Source #

err418 Expectation Failed

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err418 { errBody = "Apologies, this is not a webserver but a teapot." }

err422 :: ServantErr Source #

err422 Unprocessable Entity

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err422 { errBody = "I understood your request, but can't process it." }

5XX

err500 :: ServantErr Source #

err500 Internal Server Error

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err500 { errBody = "Exception in module A.B.C:55.  Have a great day!" }

err501 :: ServantErr Source #

err501 Not Implemented

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err501 { errBody = "/v1/foo is not supported with quux in the request." }

err502 :: ServantErr Source #

err502 Bad Gateway

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err502 { errBody = "Tried gateway foo, bar, and baz.  None responded." }

err503 :: ServantErr Source #

err503 Service Unavailable

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err503 { errBody = "We're rewriting in PHP." }

err504 :: ServantErr Source #

err504 Gateway Time-out

Example:

failingHandler :: Handler ()
failingHandler = throwError $ err504 { errBody = "Backend foobar did not respond in 5 seconds." }

err505 :: ServantErr Source #

err505 HTTP Version not supported

Example usage:

failingHandler :: Handler ()
failingHandler = throwError $ err505 { errBody = "I support HTTP/4.0 only." }

Re-exports

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #

The WAI application.

Note that, since WAI 3.0, this type is structured in continuation passing style to allow for proper safe resource handling. This was handled in the past via other means (e.g., ResourceT). As a demonstration:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    (respond $ responseLBS status200 [] "Hello World")

newtype Tagged k (s :: k) b :: forall k. k -> * -> * #

A Tagged s b value is a value b with an attached phantom type s. This can be used in place of the more traditional but less safe idiom of passing in an undefined value with the type, because unlike an (s -> b), a Tagged s b can't try to use the argument s as a real value.

Moreover, you don't have to rely on the compiler to inline away the extra argument, because the newtype is "free"

Tagged has kind k -> * -> * if the compiler supports PolyKinds, therefore there is an extra k showing in the instance haddocks that may cause confusion.

Constructors

Tagged 

Fields

Instances

Bitraversable (Tagged *) 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tagged * a b -> f (Tagged * c d) #

Bifoldable (Tagged *) 

Methods

bifold :: Monoid m => Tagged * m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Tagged * a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Tagged * a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Tagged * a b -> c #

Bifunctor (Tagged *) 

Methods

bimap :: (a -> b) -> (c -> d) -> Tagged * a c -> Tagged * b d #

first :: (a -> b) -> Tagged * a c -> Tagged * b c #

second :: (b -> c) -> Tagged * a b -> Tagged * a c #

Eq2 (Tagged *) 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Tagged * a c -> Tagged * b d -> Bool #

Ord2 (Tagged *) 

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Tagged * a c -> Tagged * b d -> Ordering #

Read2 (Tagged *) 

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Tagged * a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Tagged * a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Tagged * a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Tagged * a b] #

Show2 (Tagged *) 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Tagged * a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Tagged * a b] -> ShowS #

Generic1 * (Tagged k s) 

Associated Types

type Rep1 (Tagged k s) (f :: Tagged k s -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Tagged k s) f a #

to1 :: Rep1 (Tagged k s) f a -> f a #

Monad (Tagged k s) 

Methods

(>>=) :: Tagged k s a -> (a -> Tagged k s b) -> Tagged k s b #

(>>) :: Tagged k s a -> Tagged k s b -> Tagged k s b #

return :: a -> Tagged k s a #

fail :: String -> Tagged k s a #

Functor (Tagged k s) 

Methods

fmap :: (a -> b) -> Tagged k s a -> Tagged k s b #

(<$) :: a -> Tagged k s b -> Tagged k s a #

Applicative (Tagged k s) 

Methods

pure :: a -> Tagged k s a #

(<*>) :: Tagged k s (a -> b) -> Tagged k s a -> Tagged k s b #

liftA2 :: (a -> b -> c) -> Tagged k s a -> Tagged k s b -> Tagged k s c #

(*>) :: Tagged k s a -> Tagged k s b -> Tagged k s b #

(<*) :: Tagged k s a -> Tagged k s b -> Tagged k s a #

Foldable (Tagged k s) 

Methods

fold :: Monoid m => Tagged k s m -> m #

foldMap :: Monoid m => (a -> m) -> Tagged k s a -> m #

foldr :: (a -> b -> b) -> b -> Tagged k s a -> b #

foldr' :: (a -> b -> b) -> b -> Tagged k s a -> b #

foldl :: (b -> a -> b) -> b -> Tagged k s a -> b #

foldl' :: (b -> a -> b) -> b -> Tagged k s a -> b #

foldr1 :: (a -> a -> a) -> Tagged k s a -> a #

foldl1 :: (a -> a -> a) -> Tagged k s a -> a #

toList :: Tagged k s a -> [a] #

null :: Tagged k s a -> Bool #

length :: Tagged k s a -> Int #

elem :: Eq a => a -> Tagged k s a -> Bool #

maximum :: Ord a => Tagged k s a -> a #

minimum :: Ord a => Tagged k s a -> a #

sum :: Num a => Tagged k s a -> a #

product :: Num a => Tagged k s a -> a #

Traversable (Tagged k s) 

Methods

traverse :: Applicative f => (a -> f b) -> Tagged k s a -> f (Tagged k s b) #

sequenceA :: Applicative f => Tagged k s (f a) -> f (Tagged k s a) #

mapM :: Monad m => (a -> m b) -> Tagged k s a -> m (Tagged k s b) #

sequence :: Monad m => Tagged k s (m a) -> m (Tagged k s a) #

Eq1 (Tagged k s) 

Methods

liftEq :: (a -> b -> Bool) -> Tagged k s a -> Tagged k s b -> Bool #

Ord1 (Tagged k s) 

Methods

liftCompare :: (a -> b -> Ordering) -> Tagged k s a -> Tagged k s b -> Ordering #

Read1 (Tagged k s) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tagged k s a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tagged k s a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tagged k s a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tagged k s a] #

Show1 (Tagged k s) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tagged k s a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tagged k s a] -> ShowS #

Bounded b => Bounded (Tagged k s b) 

Methods

minBound :: Tagged k s b #

maxBound :: Tagged k s b #

Enum a => Enum (Tagged k s a) 

Methods

succ :: Tagged k s a -> Tagged k s a #

pred :: Tagged k s a -> Tagged k s a #

toEnum :: Int -> Tagged k s a #

fromEnum :: Tagged k s a -> Int #

enumFrom :: Tagged k s a -> [Tagged k s a] #

enumFromThen :: Tagged k s a -> Tagged k s a -> [Tagged k s a] #

enumFromTo :: Tagged k s a -> Tagged k s a -> [Tagged k s a] #

enumFromThenTo :: Tagged k s a -> Tagged k s a -> Tagged k s a -> [Tagged k s a] #

Eq b => Eq (Tagged k s b) 

Methods

(==) :: Tagged k s b -> Tagged k s b -> Bool #

(/=) :: Tagged k s b -> Tagged k s b -> Bool #

Floating a => Floating (Tagged k s a) 

Methods

pi :: Tagged k s a #

exp :: Tagged k s a -> Tagged k s a #

log :: Tagged k s a -> Tagged k s a #

sqrt :: Tagged k s a -> Tagged k s a #

(**) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

logBase :: Tagged k s a -> Tagged k s a -> Tagged k s a #

sin :: Tagged k s a -> Tagged k s a #

cos :: Tagged k s a -> Tagged k s a #

tan :: Tagged k s a -> Tagged k s a #

asin :: Tagged k s a -> Tagged k s a #

acos :: Tagged k s a -> Tagged k s a #

atan :: Tagged k s a -> Tagged k s a #

sinh :: Tagged k s a -> Tagged k s a #

cosh :: Tagged k s a -> Tagged k s a #

tanh :: Tagged k s a -> Tagged k s a #

asinh :: Tagged k s a -> Tagged k s a #

acosh :: Tagged k s a -> Tagged k s a #

atanh :: Tagged k s a -> Tagged k s a #

log1p :: Tagged k s a -> Tagged k s a #

expm1 :: Tagged k s a -> Tagged k s a #

log1pexp :: Tagged k s a -> Tagged k s a #

log1mexp :: Tagged k s a -> Tagged k s a #

Fractional a => Fractional (Tagged k s a) 

Methods

(/) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

recip :: Tagged k s a -> Tagged k s a #

fromRational :: Rational -> Tagged k s a #

Integral a => Integral (Tagged k s a) 

Methods

quot :: Tagged k s a -> Tagged k s a -> Tagged k s a #

rem :: Tagged k s a -> Tagged k s a -> Tagged k s a #

div :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mod :: Tagged k s a -> Tagged k s a -> Tagged k s a #

quotRem :: Tagged k s a -> Tagged k s a -> (Tagged k s a, Tagged k s a) #

divMod :: Tagged k s a -> Tagged k s a -> (Tagged k s a, Tagged k s a) #

toInteger :: Tagged k s a -> Integer #

(Data s, Data b) => Data (Tagged * s b) 

Methods

gfoldl :: (forall d a. Data d => c (d -> a) -> d -> c a) -> (forall g. g -> c g) -> Tagged * s b -> c (Tagged * s b) #

gunfold :: (forall a r. Data a => c (a -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tagged * s b) #

toConstr :: Tagged * s b -> Constr #

dataTypeOf :: Tagged * s b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Tagged * s b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tagged * s b)) #

gmapT :: (forall a. Data a => a -> a) -> Tagged * s b -> Tagged * s b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tagged * s b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tagged * s b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tagged * s b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tagged * s b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tagged * s b -> m (Tagged * s b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged * s b -> m (Tagged * s b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tagged * s b -> m (Tagged * s b) #

Num a => Num (Tagged k s a) 

Methods

(+) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(-) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(*) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

negate :: Tagged k s a -> Tagged k s a #

abs :: Tagged k s a -> Tagged k s a #

signum :: Tagged k s a -> Tagged k s a #

fromInteger :: Integer -> Tagged k s a #

Ord b => Ord (Tagged k s b) 

Methods

compare :: Tagged k s b -> Tagged k s b -> Ordering #

(<) :: Tagged k s b -> Tagged k s b -> Bool #

(<=) :: Tagged k s b -> Tagged k s b -> Bool #

(>) :: Tagged k s b -> Tagged k s b -> Bool #

(>=) :: Tagged k s b -> Tagged k s b -> Bool #

max :: Tagged k s b -> Tagged k s b -> Tagged k s b #

min :: Tagged k s b -> Tagged k s b -> Tagged k s b #

Read b => Read (Tagged k s b) 

Methods

readsPrec :: Int -> ReadS (Tagged k s b) #

readList :: ReadS [Tagged k s b] #

readPrec :: ReadPrec (Tagged k s b) #

readListPrec :: ReadPrec [Tagged k s b] #

Real a => Real (Tagged k s a) 

Methods

toRational :: Tagged k s a -> Rational #

RealFloat a => RealFloat (Tagged k s a) 

Methods

floatRadix :: Tagged k s a -> Integer #

floatDigits :: Tagged k s a -> Int #

floatRange :: Tagged k s a -> (Int, Int) #

decodeFloat :: Tagged k s a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Tagged k s a #

exponent :: Tagged k s a -> Int #

significand :: Tagged k s a -> Tagged k s a #

scaleFloat :: Int -> Tagged k s a -> Tagged k s a #

isNaN :: Tagged k s a -> Bool #

isInfinite :: Tagged k s a -> Bool #

isDenormalized :: Tagged k s a -> Bool #

isNegativeZero :: Tagged k s a -> Bool #

isIEEE :: Tagged k s a -> Bool #

atan2 :: Tagged k s a -> Tagged k s a -> Tagged k s a #

RealFrac a => RealFrac (Tagged k s a) 

Methods

properFraction :: Integral b => Tagged k s a -> (b, Tagged k s a) #

truncate :: Integral b => Tagged k s a -> b #

round :: Integral b => Tagged k s a -> b #

ceiling :: Integral b => Tagged k s a -> b #

floor :: Integral b => Tagged k s a -> b #

Show b => Show (Tagged k s b) 

Methods

showsPrec :: Int -> Tagged k s b -> ShowS #

show :: Tagged k s b -> String #

showList :: [Tagged k s b] -> ShowS #

Ix b => Ix (Tagged k s b) 

Methods

range :: (Tagged k s b, Tagged k s b) -> [Tagged k s b] #

index :: (Tagged k s b, Tagged k s b) -> Tagged k s b -> Int #

unsafeIndex :: (Tagged k s b, Tagged k s b) -> Tagged k s b -> Int

inRange :: (Tagged k s b, Tagged k s b) -> Tagged k s b -> Bool #

rangeSize :: (Tagged k s b, Tagged k s b) -> Int #

unsafeRangeSize :: (Tagged k s b, Tagged k s b) -> Int

IsString a => IsString (Tagged k s a) 

Methods

fromString :: String -> Tagged k s a #

Generic (Tagged k s b) 

Associated Types

type Rep (Tagged k s b) :: * -> * #

Methods

from :: Tagged k s b -> Rep (Tagged k s b) x #

to :: Rep (Tagged k s b) x -> Tagged k s b #

Semigroup a => Semigroup (Tagged k s a) 

Methods

(<>) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

sconcat :: NonEmpty (Tagged k s a) -> Tagged k s a #

stimes :: Integral b => b -> Tagged k s a -> Tagged k s a #

(Semigroup a, Monoid a) => Monoid (Tagged k s a) 

Methods

mempty :: Tagged k s a #

mappend :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mconcat :: [Tagged k s a] -> Tagged k s a #

Storable a => Storable (Tagged k s a) 

Methods

sizeOf :: Tagged k s a -> Int #

alignment :: Tagged k s a -> Int #

peekElemOff :: Ptr (Tagged k s a) -> Int -> IO (Tagged k s a) #

pokeElemOff :: Ptr (Tagged k s a) -> Int -> Tagged k s a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Tagged k s a) #

pokeByteOff :: Ptr b -> Int -> Tagged k s a -> IO () #

peek :: Ptr (Tagged k s a) -> IO (Tagged k s a) #

poke :: Ptr (Tagged k s a) -> Tagged k s a -> IO () #

Bits a => Bits (Tagged k s a) 

Methods

(.&.) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

(.|.) :: Tagged k s a -> Tagged k s a -> Tagged k s a #

xor :: Tagged k s a -> Tagged k s a -> Tagged k s a #

complement :: Tagged k s a -> Tagged k s a #

shift :: Tagged k s a -> Int -> Tagged k s a #

rotate :: Tagged k s a -> Int -> Tagged k s a #

zeroBits :: Tagged k s a #

bit :: Int -> Tagged k s a #

setBit :: Tagged k s a -> Int -> Tagged k s a #

clearBit :: Tagged k s a -> Int -> Tagged k s a #

complementBit :: Tagged k s a -> Int -> Tagged k s a #

testBit :: Tagged k s a -> Int -> Bool #

bitSizeMaybe :: Tagged k s a -> Maybe Int #

bitSize :: Tagged k s a -> Int #

isSigned :: Tagged k s a -> Bool #

shiftL :: Tagged k s a -> Int -> Tagged k s a #

unsafeShiftL :: Tagged k s a -> Int -> Tagged k s a #

shiftR :: Tagged k s a -> Int -> Tagged k s a #

unsafeShiftR :: Tagged k s a -> Int -> Tagged k s a #

rotateL :: Tagged k s a -> Int -> Tagged k s a #

rotateR :: Tagged k s a -> Int -> Tagged k s a #

popCount :: Tagged k s a -> Int #

FiniteBits a => FiniteBits (Tagged k s a) 

Methods

finiteBitSize :: Tagged k s a -> Int #

countLeadingZeros :: Tagged k s a -> Int #

countTrailingZeros :: Tagged k s a -> Int #

NFData b => NFData (Tagged k s b) 

Methods

rnf :: Tagged k s b -> () #

type Rep1 * (Tagged k s) 
type Rep1 * (Tagged k s) = D1 * (MetaData "Tagged" "Data.Tagged" "tagged-0.8.5-8i4yEdVmPnc52Vc955f6BG" True) (C1 * (MetaCons "Tagged" PrefixI True) (S1 * (MetaSel (Just Symbol "unTagged") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Tagged k s b) 
type Rep (Tagged k s b) = D1 * (MetaData "Tagged" "Data.Tagged" "tagged-0.8.5-8i4yEdVmPnc52Vc955f6BG" True) (C1 * (MetaCons "Tagged" PrefixI True) (S1 * (MetaSel (Just Symbol "unTagged") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * b)))