mig-0.1.0.1: Build lightweight and composable servers
Safe HaskellSafe-Inferred
LanguageGHC2021

Mig.Common

Description

Module for HTML-based servers

Synopsis

types

newtype Server m Source #

Server type. It is a function fron request to response. Some servers does not return valid value. We use it to find right path.

Example:

server :: Server IO
server =
  "api" /. "v1" /.
     mconcat
       [ "foo" /. (\(Query @"name" arg) -> Get  @Json (handleFoo arg)
       , "bar" /. Post @Json handleBar
       ]

handleFoo :: Int -> IO Text
handleBar :: IO Text

Note that server is monoid and it can be constructed with Monoid functions and path constructor (/.). To pass inputs for handler we can use special newtype wrappers:

  • Query - for required query parameters
  • Optional - for optional query parameters
  • Capture - for parsing elements of URI
  • Body - fot JSON-body input
  • RawBody - for raw ByteString input
  • Header - for headers

To distinguish by HTTP-method we use corresponding constructors: Get, Post, Put, etc. Let's discuss the structure of the constructor. Let's take Get for example:

newtype Get ty m a = Get (m a)

Let's look at the arguments of he type

  • ty - type of the response. it can be: Text, Html, Json, ByteString
  • m - underlying server monad
  • a - result type. It should be convertible to the type of the response.

also result can be wrapped to special data types to modify Http-response. we have wrappers:

  • SetStatus - to set status
  • AddHeaders - to append headers
  • Either (Error err) - to response with errors

Constructors

Server 

Fields

Instances

Instances details
Monad m => Monoid (Server m) Source # 
Instance details

Defined in Mig.Internal.Types

Methods

mempty :: Server m #

mappend :: Server m -> Server m -> Server m #

mconcat :: [Server m] -> Server m #

Monad m => Semigroup (Server m) Source # 
Instance details

Defined in Mig.Internal.Types

Methods

(<>) :: Server m -> Server m -> Server m #

sconcat :: NonEmpty (Server m) -> Server m #

stimes :: Integral b => b -> Server m -> Server m #

Monad m => ToServer (Server m) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Server m) :: Type -> Type Source #

type ServerMonad (Server m) Source # 
Instance details

Defined in Mig

type ServerMonad (Server m) = m

DSL

class ToText a where Source #

Values convertible to lazy text

Methods

toText :: a -> Text Source #

Instances

Instances details
ToText Text Source # 
Instance details

Defined in Mig.Internal.Types

Methods

toText :: Text -> Text Source #

ToText Text Source # 
Instance details

Defined in Mig.Internal.Types

Methods

toText :: Text -> Text0 Source #

ToText String Source # 
Instance details

Defined in Mig.Internal.Types

Methods

toText :: String -> Text Source #

ToText Float Source # 
Instance details

Defined in Mig.Internal.Types

Methods

toText :: Float -> Text Source #

ToText Int Source # 
Instance details

Defined in Mig.Internal.Types

Methods

toText :: Int -> Text Source #

class ToHtmlResp a where Source #

Values convertible to Html

Methods

toHtmlResp :: a -> Resp Source #

Instances

Instances details
ToMarkup a => ToHtmlResp a Source # 
Instance details

Defined in Mig

Methods

toHtmlResp :: a -> Resp Source #

ToHtmlResp a => ToHtmlResp (AddHeaders a) Source # 
Instance details

Defined in Mig

ToHtmlResp a => ToHtmlResp (SetStatus a) Source # 
Instance details

Defined in Mig

(ToJSON err, ToHtmlResp a) => ToHtmlResp (Either (Error err) a) Source # 
Instance details

Defined in Mig

Methods

toHtmlResp :: Either (Error err) a -> Resp Source #

class FromText a where Source #

Aything convertible from text

Methods

fromText :: Text -> Maybe a Source #

Instances

Instances details
FromText ByteString Source # 
Instance details

Defined in Mig

FromText Text Source # 
Instance details

Defined in Mig

FromText Text Source # 
Instance details

Defined in Mig

FromText String Source # 
Instance details

Defined in Mig

FromText Integer Source # 
Instance details

Defined in Mig

FromText Bool Source # 
Instance details

Defined in Mig

FromText Float Source # 
Instance details

Defined in Mig

FromText Int Source # 
Instance details

Defined in Mig

Methods

fromText :: Text -> Maybe Int Source #

FromText Word Source # 
Instance details

Defined in Mig

class Monad (ServerMonad a) => ToServer a where Source #

Class ToServer contains anything convertible to Server m. We use it for flexuble composition of servers from functions with arbitrary number of arguments. Arguments can be of specific types: Query, Body, Optional, Capture, Header, etc. We use type-level strings to encode query-names. Example:

"api" /. "foo" /.
    (\(Query @"argA" argA) (Optional @"argB" argB) (Body jsonRequest) -> Post @Json $ handleFoo argA argB jsonRequest)

handleFoo :: Int -> Maybe Text -> FooRequest -> IO FooResponse
handleFoo = ...

Note that we can use any amount of arguments. And type of the input is decoded fron newtype wrapper which is used with argument of the handler function.

Also we can return pure errors with Either. Anything which can be returned from function can be wrapped to Either (Error err).

For example in previous case we can use function which returns errors as values:

type ServerError = Error Text

handleFoo :: Int -> Maybe Text -> FooRequest -> IO (Either ServerError FooResponse)
handleFoo = ...

the result of error response is automatically matched with normal response of the server and standard Error type lets us pass status to response and some details.

Associated Types

type ServerMonad a :: Type -> Type Source #

Methods

toServer :: a -> Server (ServerMonad a) Source #

Instances

Instances details
ToHtmlResp a => ToServer (Delete a) Source # 
Instance details

Defined in Mig.Html.IO

Associated Types

type ServerMonad (Delete a) :: Type -> Type Source #

ToHtmlResp a => ToServer (Get a) Source # 
Instance details

Defined in Mig.Html.IO

Associated Types

type ServerMonad (Get a) :: Type -> Type Source #

Methods

toServer :: Get a -> Server (ServerMonad (Get a)) Source #

ToHtmlResp a => ToServer (Options a) Source # 
Instance details

Defined in Mig.Html.IO

Associated Types

type ServerMonad (Options a) :: Type -> Type Source #

ToHtmlResp a => ToServer (Patch a) Source # 
Instance details

Defined in Mig.Html.IO

Associated Types

type ServerMonad (Patch a) :: Type -> Type Source #

ToHtmlResp a => ToServer (Post a) Source # 
Instance details

Defined in Mig.Html.IO

Associated Types

type ServerMonad (Post a) :: Type -> Type Source #

Methods

toServer :: Post a -> Server (ServerMonad (Post a)) Source #

ToHtmlResp a => ToServer (Put a) Source # 
Instance details

Defined in Mig.Html.IO

Associated Types

type ServerMonad (Put a) :: Type -> Type Source #

Methods

toServer :: Put a -> Server (ServerMonad (Put a)) Source #

Monad m => ToServer (Server m) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Server m) :: Type -> Type Source #

ToJsonResp a => ToServer (Delete a) Source # 
Instance details

Defined in Mig.Json.IO

Associated Types

type ServerMonad (Delete a) :: Type -> Type Source #

ToJsonResp a => ToServer (Get a) Source # 
Instance details

Defined in Mig.Json.IO

Associated Types

type ServerMonad (Get a) :: Type -> Type Source #

Methods

toServer :: Get a -> Server (ServerMonad (Get a)) Source #

ToJsonResp a => ToServer (Options a) Source # 
Instance details

Defined in Mig.Json.IO

Associated Types

type ServerMonad (Options a) :: Type -> Type Source #

ToJsonResp a => ToServer (Patch a) Source # 
Instance details

Defined in Mig.Json.IO

Associated Types

type ServerMonad (Patch a) :: Type -> Type Source #

ToJsonResp a => ToServer (Post a) Source # 
Instance details

Defined in Mig.Json.IO

Associated Types

type ServerMonad (Post a) :: Type -> Type Source #

Methods

toServer :: Post a -> Server (ServerMonad (Post a)) Source #

ToJsonResp a => ToServer (Put a) Source # 
Instance details

Defined in Mig.Json.IO

Associated Types

type ServerMonad (Put a) :: Type -> Type Source #

Methods

toServer :: Put a -> Server (ServerMonad (Put a)) Source #

(MonadIO (ServerMonad b), FromJSON a, ToServer b) => ToServer (Body a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Body a -> b) :: Type -> Type Source #

Methods

toServer :: (Body a -> b) -> Server (ServerMonad (Body a -> b)) Source #

(FromText a, ToServer b) => ToServer (Capture a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Capture a -> b) :: Type -> Type Source #

Methods

toServer :: (Capture a -> b) -> Server (ServerMonad (Capture a -> b)) Source #

(ToServer b, MonadIO (ServerMonad b), FromJSON a) => ToServer (FormJson a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (FormJson a -> b) :: Type -> Type Source #

Methods

toServer :: (FormJson a -> b) -> Server (ServerMonad (FormJson a -> b)) Source #

(ToServer b, KnownSymbol sym) => ToServer (Header sym -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Header sym -> b) :: Type -> Type Source #

Methods

toServer :: (Header sym -> b) -> Server (ServerMonad (Header sym -> b)) Source #

(FromText a, ToServer b, KnownSymbol sym) => ToServer (Optional sym a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Optional sym a -> b) :: Type -> Type Source #

Methods

toServer :: (Optional sym a -> b) -> Server (ServerMonad (Optional sym a -> b)) Source #

ToServer b => ToServer (PathInfo -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (PathInfo -> b) :: Type -> Type Source #

Methods

toServer :: (PathInfo -> b) -> Server (ServerMonad (PathInfo -> b)) Source #

(FromText a, ToServer b, KnownSymbol sym) => ToServer (Query sym a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Query sym a -> b) :: Type -> Type Source #

Methods

toServer :: (Query sym a -> b) -> Server (ServerMonad (Query sym a -> b)) Source #

(MonadIO (ServerMonad b), ToServer b) => ToServer (RawBody -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (RawBody -> b) :: Type -> Type Source #

Methods

toServer :: (RawBody -> b) -> Server (ServerMonad (RawBody -> b)) Source #

(ToServer b, MonadIO (ServerMonad b)) => ToServer (RawFormData -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (RawFormData -> b) :: Type -> Type Source #

(Monad m, ToHtmlResp a) => ToServer (Delete m a) Source # 
Instance details

Defined in Mig.Html

Associated Types

type ServerMonad (Delete m a) :: Type -> Type Source #

Methods

toServer :: Delete m a -> Server (ServerMonad (Delete m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Get m a) Source # 
Instance details

Defined in Mig.Html

Associated Types

type ServerMonad (Get m a) :: Type -> Type Source #

Methods

toServer :: Get m a -> Server (ServerMonad (Get m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Options m a) Source # 
Instance details

Defined in Mig.Html

Associated Types

type ServerMonad (Options m a) :: Type -> Type Source #

Methods

toServer :: Options m a -> Server (ServerMonad (Options m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Patch m a) Source # 
Instance details

Defined in Mig.Html

Associated Types

type ServerMonad (Patch m a) :: Type -> Type Source #

Methods

toServer :: Patch m a -> Server (ServerMonad (Patch m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Post m a) Source # 
Instance details

Defined in Mig.Html

Associated Types

type ServerMonad (Post m a) :: Type -> Type Source #

Methods

toServer :: Post m a -> Server (ServerMonad (Post m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Put m a) Source # 
Instance details

Defined in Mig.Html

Associated Types

type ServerMonad (Put m a) :: Type -> Type Source #

Methods

toServer :: Put m a -> Server (ServerMonad (Put m a)) Source #

(Monad m, ToJsonResp a) => ToServer (Delete m a) Source # 
Instance details

Defined in Mig.Json

Associated Types

type ServerMonad (Delete m a) :: Type -> Type Source #

Methods

toServer :: Delete m a -> Server (ServerMonad (Delete m a)) Source #

(Monad m, ToJsonResp a) => ToServer (Get m a) Source # 
Instance details

Defined in Mig.Json

Associated Types

type ServerMonad (Get m a) :: Type -> Type Source #

Methods

toServer :: Get m a -> Server (ServerMonad (Get m a)) Source #

(Monad m, ToJsonResp a) => ToServer (Options m a) Source # 
Instance details

Defined in Mig.Json

Associated Types

type ServerMonad (Options m a) :: Type -> Type Source #

Methods

toServer :: Options m a -> Server (ServerMonad (Options m a)) Source #

(Monad m, ToJsonResp a) => ToServer (Patch m a) Source # 
Instance details

Defined in Mig.Json

Associated Types

type ServerMonad (Patch m a) :: Type -> Type Source #

Methods

toServer :: Patch m a -> Server (ServerMonad (Patch m a)) Source #

(Monad m, ToJsonResp a) => ToServer (Post m a) Source # 
Instance details

Defined in Mig.Json

Associated Types

type ServerMonad (Post m a) :: Type -> Type Source #

Methods

toServer :: Post m a -> Server (ServerMonad (Post m a)) Source #

(Monad m, ToJsonResp a) => ToServer (Put m a) Source # 
Instance details

Defined in Mig.Json

Associated Types

type ServerMonad (Put m a) :: Type -> Type Source #

Methods

toServer :: Put m a -> Server (ServerMonad (Put m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Delete Html m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Delete Html m a) :: Type -> Type Source #

(Monad m, ToJSON a) => ToServer (Delete Json m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Delete Json m a) :: Type -> Type Source #

(Monad m, ToTextResp a) => ToServer (Delete Text m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Delete Text m a) :: Type -> Type Source #

(Monad m, ToHtmlResp a) => ToServer (Get Html m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Get Html m a) :: Type -> Type Source #

Methods

toServer :: Get Html m a -> Server (ServerMonad (Get Html m a)) Source #

Monad m => ToServer (Get ByteString m ByteString) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Get ByteString m ByteString) :: Type -> Type Source #

Monad m => ToServer (Get ByteString m ByteString) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Get ByteString m ByteString) :: Type -> Type Source #

(Monad m, ToJSON a) => ToServer (Get Json m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Get Json m a) :: Type -> Type Source #

Methods

toServer :: Get Json m a -> Server (ServerMonad (Get Json m a)) Source #

(Monad m, ToTextResp a) => ToServer (Get Text m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Get Text m a) :: Type -> Type Source #

Methods

toServer :: Get Text m a -> Server (ServerMonad (Get Text m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Options Html m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Options Html m a) :: Type -> Type Source #

(Monad m, ToJSON a) => ToServer (Options Json m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Options Json m a) :: Type -> Type Source #

(Monad m, ToTextResp a) => ToServer (Options Text m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Options Text m a) :: Type -> Type Source #

(Monad m, ToHtmlResp a) => ToServer (Patch Html m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Patch Html m a) :: Type -> Type Source #

(Monad m, ToJSON a) => ToServer (Patch Json m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Patch Json m a) :: Type -> Type Source #

(Monad m, ToTextResp a) => ToServer (Patch Text m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Patch Text m a) :: Type -> Type Source #

(Monad m, ToHtmlResp a) => ToServer (Post Html m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Post Html m a) :: Type -> Type Source #

Methods

toServer :: Post Html m a -> Server (ServerMonad (Post Html m a)) Source #

(Monad m, ToJSON a) => ToServer (Post Json m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Post Json m a) :: Type -> Type Source #

Methods

toServer :: Post Json m a -> Server (ServerMonad (Post Json m a)) Source #

(Monad m, ToTextResp a) => ToServer (Post Text m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Post Text m a) :: Type -> Type Source #

Methods

toServer :: Post Text m a -> Server (ServerMonad (Post Text m a)) Source #

(Monad m, ToHtmlResp a) => ToServer (Put Html m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Put Html m a) :: Type -> Type Source #

Methods

toServer :: Put Html m a -> Server (ServerMonad (Put Html m a)) Source #

(Monad m, ToJSON a) => ToServer (Put Json m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Put Json m a) :: Type -> Type Source #

Methods

toServer :: Put Json m a -> Server (ServerMonad (Put Json m a)) Source #

(Monad m, ToTextResp a) => ToServer (Put Text m a) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Put Text m a) :: Type -> Type Source #

Methods

toServer :: Put Text m a -> Server (ServerMonad (Put Text m a)) Source #

withServerAction :: Monad m => Server m -> m () -> Server m Source #

Appends action to the server

path and query

(/.) :: ToServer a => Text -> a -> Server (ServerMonad a) infixr 4 Source #

Path constructor (right associative). Example:

server :: Server IO
server =
  "api" /. "v1" /.
     mconcat
       [ "foo" /. Get  @Json handleFoo
       , "bar" /. Post @Json handleBar
       ]

handleFoo, handleBar :: IO Text

newtype Capture a Source #

Constructors

Capture a 

Instances

Instances details
(FromText a, ToServer b) => ToServer (Capture a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Capture a -> b) :: Type -> Type Source #

Methods

toServer :: (Capture a -> b) -> Server (ServerMonad (Capture a -> b)) Source #

type ServerMonad (Capture a -> b) Source # 
Instance details

Defined in Mig

type ServerMonad (Capture a -> b) = ServerMonad b

newtype Query (sym :: Symbol) a Source #

Mandatary query parameter. Name is encoded as type-level string. Example:

"api" /. handleFoo

handleFoo :: Query "name" Int -> Server IO
handleFoo (Query arg) = ...

Constructors

Query a 

Instances

Instances details
(FromText a, ToServer b, KnownSymbol sym) => ToServer (Query sym a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Query sym a -> b) :: Type -> Type Source #

Methods

toServer :: (Query sym a -> b) -> Server (ServerMonad (Query sym a -> b)) Source #

type ServerMonad (Query sym a -> b) Source # 
Instance details

Defined in Mig

type ServerMonad (Query sym a -> b) = ServerMonad b

newtype Optional (sym :: Symbol) a Source #

Optional query parameter. Name is encoded as type-level string. Example:

"api" /. handleFoo

handleFoo :: Optional "name" -> Server IO
handleFoo (Optional maybeArg) = ...

Constructors

Optional (Maybe a) 

Instances

Instances details
(FromText a, ToServer b, KnownSymbol sym) => ToServer (Optional sym a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Optional sym a -> b) :: Type -> Type Source #

Methods

toServer :: (Optional sym a -> b) -> Server (ServerMonad (Optional sym a -> b)) Source #

type ServerMonad (Optional sym a -> b) Source # 
Instance details

Defined in Mig

type ServerMonad (Optional sym a -> b) = ServerMonad b

newtype Body a Source #

Reads Json body (lazy). We can limit the body size with server config. Example:

"api" /. "search" /. (\(Body request) -> handleSearch request)

Constructors

Body a 

Instances

Instances details
(MonadIO (ServerMonad b), FromJSON a, ToServer b) => ToServer (Body a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Body a -> b) :: Type -> Type Source #

Methods

toServer :: (Body a -> b) -> Server (ServerMonad (Body a -> b)) Source #

type ServerMonad (Body a -> b) Source # 
Instance details

Defined in Mig

type ServerMonad (Body a -> b) = ServerMonad b

newtype RawBody Source #

Reads raw body as lazy bytestring. We can limit the body size with server config. Example:

"api" /. "upload" /. (\(RawBody content) -> handleUpload content)

Constructors

RawBody ByteString 

Instances

Instances details
(MonadIO (ServerMonad b), ToServer b) => ToServer (RawBody -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (RawBody -> b) :: Type -> Type Source #

Methods

toServer :: (RawBody -> b) -> Server (ServerMonad (RawBody -> b)) Source #

type ServerMonad (RawBody -> b) Source # 
Instance details

Defined in Mig

newtype Header (sym :: Symbol) Source #

Reads input header. Example:

"api" /. (\(Header @"Trace-Id" traceId) -> Post @Json (handleFoo traceId))

handleFoo :: Maybe ByteString -> IO FooResponse

Constructors

Header (Maybe ByteString) 

Instances

Instances details
(ToServer b, KnownSymbol sym) => ToServer (Header sym -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (Header sym -> b) :: Type -> Type Source #

Methods

toServer :: (Header sym -> b) -> Server (ServerMonad (Header sym -> b)) Source #

type ServerMonad (Header sym -> b) Source # 
Instance details

Defined in Mig

type ServerMonad (Header sym -> b) = ServerMonad b

newtype RawFormData Source #

Parse raw form body. It includes named form arguments and file info. Note that we can not use FormBody and JSON-body at the same time. They occupy the same field in the HTTP-request.

Constructors

RawFormData FormBody 

Instances

Instances details
(ToServer b, MonadIO (ServerMonad b)) => ToServer (RawFormData -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (RawFormData -> b) :: Type -> Type Source #

type ServerMonad (RawFormData -> b) Source # 
Instance details

Defined in Mig

newtype FormJson a Source #

It reads form as plain JSON-object where name of the form's field becomes a field of JSON-object and every value is Text.

For example if submit a form with fields: name, password, date. We can read it in the data type:

data User = User
 { name :: Text
 , passord :: Text
 , date :: Text
 }

Note that we can not use FormBody and JSON-body at the same time. They occupy the same field in the HTTP-request.

Constructors

FormJson a 

Instances

Instances details
(ToServer b, MonadIO (ServerMonad b), FromJSON a) => ToServer (FormJson a -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (FormJson a -> b) :: Type -> Type Source #

Methods

toServer :: (FormJson a -> b) -> Server (ServerMonad (FormJson a -> b)) Source #

type ServerMonad (FormJson a -> b) Source # 
Instance details

Defined in Mig

type ServerMonad (FormJson a -> b) = ServerMonad b

newtype PathInfo Source #

Reads current path info

Constructors

PathInfo [Text] 

Instances

Instances details
ToServer b => ToServer (PathInfo -> b) Source # 
Instance details

Defined in Mig

Associated Types

type ServerMonad (PathInfo -> b) :: Type -> Type Source #

Methods

toServer :: (PathInfo -> b) -> Server (ServerMonad (PathInfo -> b)) Source #

type ServerMonad (PathInfo -> b) Source # 
Instance details

Defined in Mig

response

data AddHeaders a Source #

Attach headers to response. It can be used inside any ToXxxResp value. Example:

"api" /. handleFoo

handleFoo :: Get Text IO (AddHeaders Text)
handleFoo = Get $ pure $ AddHeaders headers "Hello foo"

Constructors

AddHeaders 

Instances

Instances details
ToHtmlResp a => ToHtmlResp (AddHeaders a) Source # 
Instance details

Defined in Mig

ToJsonResp a => ToJsonResp (AddHeaders a) Source # 
Instance details

Defined in Mig

ToTextResp a => ToTextResp (AddHeaders a) Source # 
Instance details

Defined in Mig

data SetStatus a Source #

Set status to response. It can be ised inside any ToXxxResp value. Example:

"api" /. handleFoo

handleFoo :: Get Text IO (SetStatus Text)
handleFoo = Get $ pure $ SetStatus status500 "Bad request"

Constructors

SetStatus 

Fields

Instances

Instances details
ToHtmlResp a => ToHtmlResp (SetStatus a) Source # 
Instance details

Defined in Mig

ToJsonResp a => ToJsonResp (SetStatus a) Source # 
Instance details

Defined in Mig

ToTextResp a => ToTextResp (SetStatus a) Source # 
Instance details

Defined in Mig

setStatus :: Monad m => Status -> Server m -> Server m Source #

Sets status for response of the server

addHeaders :: Monad m => ResponseHeaders -> Server m -> Server m Source #

Adds headers for response of the server

Errors

data Error a Source #

Errors

Constructors

Error 

Fields

Instances

Instances details
(Typeable a, Show a) => Exception (Error a) Source # 
Instance details

Defined in Mig.Internal.Types

Show a => Show (Error a) Source # 
Instance details

Defined in Mig.Internal.Types

Methods

showsPrec :: Int -> Error a -> ShowS #

show :: Error a -> String #

showList :: [Error a] -> ShowS #

(Show a, Typeable a) => HasServer (ReaderT env (ExceptT (Error a) IO)) Source # 
Instance details

Defined in Mig

Associated Types

type ServerResult (ReaderT env (ExceptT (Error a) IO)) Source #

(ToJSON err, ToHtmlResp a) => ToHtmlResp (Either (Error err) a) Source # 
Instance details

Defined in Mig

Methods

toHtmlResp :: Either (Error err) a -> Resp Source #

(ToJSON err, ToJsonResp a) => ToJsonResp (Either (Error err) a) Source # 
Instance details

Defined in Mig

Methods

toJsonResp :: Either (Error err) a -> Resp Source #

(ToText err, ToTextResp a) => ToTextResp (Either (Error err) a) Source # 
Instance details

Defined in Mig

Methods

toTextResp :: Either (Error err) a -> Resp Source #

type ServerResult (ReaderT env (ExceptT (Error a) IO)) Source # 
Instance details

Defined in Mig

type ServerResult (ReaderT env (ExceptT (Error a) IO)) = (Error a -> Server IO) -> env -> IO (Server IO)

handleError :: (Exception a, MonadCatch m) => (a -> Server m) -> Server m -> Server m Source #

Handle errors

Render

class Monad m => HasServer m where Source #

Class contains types which can be converted to IO-based server to run as with WAI-interface.

We can run plain IO-servers and ReaderT over IO based servers. Readers can be wrapped in newtypes. In that case we can derive automatically HasServer instance.

Associated Types

type ServerResult m :: Type Source #

Instances

Instances details
HasServer IO Source # 
Instance details

Defined in Mig

Associated Types

type ServerResult IO Source #

HasServer (ReaderT env IO) Source # 
Instance details

Defined in Mig

Associated Types

type ServerResult (ReaderT env IO) Source #

(Show a, Typeable a) => HasServer (ReaderT env (ExceptT (Error a) IO)) Source # 
Instance details

Defined in Mig

Associated Types

type ServerResult (ReaderT env (ExceptT (Error a) IO)) Source #

fromReader :: env -> Server (ReaderT env IO) -> IO (Server IO) Source #

Render reader server to IO-based server

Run

data ServerConfig Source #

Server config

Constructors

ServerConfig 

toApplication :: ServerConfig -> Server IO -> Application Source #

Convert server to WAI-application

runServer :: Int -> Server IO -> IO () Source #

Run server on port

utils

badRequest :: Text -> Resp Source #

Bad request response