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

Mig.Internal.Types

Description

Internal types and functions

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

data Req Source #

Http request

Constructors

Req 

Fields

data Resp Source #

Http response

Constructors

Resp 

Fields

Instances

Instances details
IsString Resp Source # 
Instance details

Defined in Mig.Internal.Types

Methods

fromString :: String -> Resp #

type QueryMap = Map ByteString ByteString Source #

Map of query parameters for fast-access

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 #

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)

constructors

toConst :: Functor m => m Resp -> Server m Source #

Replies to any http-method

toMethod :: Monad m => Method -> m Resp -> Server m Source #

Specify which method to reply

toWithBody :: MonadIO m => (ByteString -> Server m) -> Server m Source #

Reads full body as lazy bytestring

toWithCapture :: Monad m => (Text -> Server m) -> Server m Source #

Reads capture URL-piece element

toWithPath :: Monad m => Text -> Server m -> Server m Source #

Match path prefix

toWithHeader :: (Monad m, FromHttpApiData a) => HeaderName -> (Maybe a -> Server m) -> Server m Source #

Read info from header

toWithFormData :: (FromForm a, MonadIO m) => (a -> Server m) -> Server m Source #

Reads URL-encoded form data

toWithPathInfo :: ([Text] -> Server m) -> Server m Source #

reads path info

responses

text :: ToText a => a -> Resp Source #

Text response constructor

json :: ToJSON resp => resp -> Resp Source #

Json response constructor

html :: ToMarkup a => a -> Resp Source #

Html response constructor

raw :: ByteString -> Resp Source #

Raw bytestring response constructor

ok :: ResponseHeaders -> RespBody -> Resp Source #

Respond with ok 200-status

badRequest :: Text -> Resp Source #

Bad request response

setContent :: ByteString -> ResponseHeaders Source #

Headers to set content type

WAI

data ServerConfig Source #

Server config

Constructors

ServerConfig 

type Kilobytes = Int Source #

Size of the input body

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

Convert server to WAI-application

utils

setRespStatus :: Status -> Resp -> Resp Source #

Sets response status

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

Handle errors

toResponse :: Resp -> Response Source #

Convert response to low-level WAI-response

fromRequest :: Maybe Kilobytes -> Request -> IO Req Source #

Read request from low-level WAI-request First argument limits the size of input body. The body is read in chunks.

pathHead :: Req -> Maybe (Text, Req) Source #

Match on path prefix