Copyright | (c) Sergey Kolbasov 2019 |
---|---|
License | Apache License 2.0 |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Endpoint (m :: * -> *) a = Endpoint {
- runEndpoint :: Input -> EndpointResult m a
- toString :: Text
- (~>) :: Monad m => Endpoint m a -> (a -> m (Output b)) -> Endpoint m b
- (~>>) :: (Monad m, FnToProduct fn ls (m (Output b))) => Endpoint m (HList ls) -> fn -> Endpoint m b
- (//) :: (MonadCatch m, AdjoinHList (a ': (b ': '[])) out) => Endpoint m a -> Endpoint m b -> Endpoint m (HList out)
- (|+|) :: forall m a b out. (MonadCatch m, AdjoinCoproduct (Coproduct a (Coproduct b CNil)) out) => Endpoint m a -> Endpoint m b -> Endpoint m out
- get :: Endpoint m a -> Endpoint m a
- post :: Endpoint m a -> Endpoint m a
- put :: Endpoint m a -> Endpoint m a
- patch :: Endpoint m a -> Endpoint m a
- delete :: Endpoint m a -> Endpoint m a
- head' :: Endpoint m a -> Endpoint m a
- trace' :: Endpoint m a -> Endpoint m a
- connect :: Endpoint m a -> Endpoint m a
- options :: Endpoint m a -> Endpoint m a
- path :: forall a m. (DecodePath a, Applicative m, Typeable a) => Endpoint m a
- pathAny :: Applicative m => Endpoint m (HList '[])
- pathConst :: Applicative m => Text -> Endpoint m (HList '[])
- p' :: Applicative m => Text -> Endpoint m (HList '[])
- pathEmpty :: Applicative m => Endpoint m (HList '[])
- paths :: forall a m. (DecodePath a, Applicative m, Typeable a) => Endpoint m [a]
- param :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m a
- paramMaybe :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (Maybe a)
- params :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m [a]
- paramsNel :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (NonEmpty a)
- body :: forall ct a m. (Decode ct a, MonadIO m, MonadThrow m) => Endpoint m a
- bodyMaybe :: forall ct a m. (Decode ct a, MonadIO m, MonadThrow m) => Endpoint m (Maybe a)
- textBody :: (Decode TextPlain a, MonadIO m, MonadThrow m) => Endpoint m a
- textBodyMaybe :: (Decode TextPlain a, MonadIO m, MonadThrow m) => Endpoint m (Maybe a)
- jsonBody :: (Decode ApplicationJson a, MonadIO m, MonadThrow m) => Endpoint m a
- jsonBodyMaybe :: (Decode ApplicationJson a, MonadIO m, MonadThrow m) => Endpoint m (Maybe a)
- cookie :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m a
- cookieMaybe :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (Maybe a)
- header :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m a
- headerMaybe :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (Maybe a)
- class Encode ct a where
- encode :: a -> ByteString
- class Decode ct a where
- decode :: ByteString -> Either LinnetError a
- data Output a = Output {
- outputStatus :: Status
- outputPayload :: Payload a
- outputHeaders :: [Header]
- ok :: a -> Output a
- created :: a -> Output a
- accepted :: Output a
- noContent :: Output a
- badRequest :: Exception e => e -> Output a
- unauthorized :: Exception e => e -> Output a
- paymentRequired :: Exception e => e -> Output a
- forbidden :: Exception e => e -> Output a
- notFound :: Exception e => e -> Output a
- methodNotAllowed :: Exception e => e -> Output a
- notAcceptable :: Exception e => e -> Output a
- conflict :: Exception e => e -> Output a
- gone :: Exception e => e -> Output a
- lengthRequired :: Exception e => e -> Output a
- preconditionFailed :: Exception e => e -> Output a
- requestEntityTooLarge :: Exception e => e -> Output a
- unprocessableEntity :: Exception e => e -> Output a
- tooManyRequests :: Exception e => e -> Output a
- internalServerError :: Exception e => e -> Output a
- notImplemented :: Exception e => e -> Output a
- badGateway :: Exception e => e -> Output a
- serviceUnavailable :: Exception e => e -> Output a
- gatewayTimeout :: Exception e => e -> Output a
- type Compiled m = ReaderT Request (WriterT Trace m) (Either SomeException Response)
- bootstrap :: forall ct m a. Endpoint m a -> Bootstrap m (ct :+: CNil) (HList '[Endpoint m a])
- serve :: forall ct cts es m a. Endpoint m a -> Bootstrap m cts (HList es) -> Bootstrap m (ct :+: cts) (HList (Endpoint m a ': es))
- compile :: forall cts m es. Compile cts m es => Bootstrap m cts es -> Compiled m
- toApp :: forall m. NaturalTransformation m IO => Compiled m -> Application
- run :: Port -> Application -> IO ()
- type ApplicationJson = Proxy "application/json"
- type TextHtml = Proxy "text/html"
- type TextPlain = Proxy "text/plain"
- data NotAcceptable406
- type (:+:) a b = Coproduct a b
Hello world
Hello name
example using warp server:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeSynonymInstances #-} import Control.Exception (SomeException) import Data.Function ((&)) import Data.Text (Text, append) import Linnet -- It's necessary to define encoding of exceptions for content-type "text/plain". Here it returns no content instance Encode TextPlain SomeException where encode _ = mempty helloWorld = get(p' "hello" // path @Text) ~>> (\name -> return $ ok ("Hello, " `append` name)) main :: IO () main = run 9000 $ bootstrap @TextPlain helloWorld & compile & toApp id
Now try to call your server with curl
command:
curl -v http://localhost:9000/hello/linnet
Main module exposes only subset of available functions and operators to keep application namespace clean.
Explore corresponding modules for additional functionality.
data Endpoint (m :: * -> *) a Source #
Basic Linnet data type that abstracts away operations over HTTP communication.
While WAI Application has type of Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
,
it's practical to treat web applications as functions of Request -> BusinessLogic -> IO Response
where BusinessLogic
is usually a function of a -> m b
where a
and b
are data to be decoded from the request / encoded to response, m
is some monad, and this is the most interesting part of an application.
Endpoint's purpose is exactly to abstract details of encoding and decoding, along with routing and the rest, and provide
simple interface to encapsulate BusinessLogic
into a final web application.
Business logic is encoded as transformation in fmap
, mapOutput
, mapOutputM
, mapM
and the like.
Usual way to transform endpoint is to use ~>
and ~>>
operators:
get (path @Text) ~> (\segment -> return $ ok segment)
Here, ~>
is just an inverted alias for mapOutputM
function. Often, endpoint is a product of multiple endpoints,
and here ~>>
proves to be very handy:
get (p' "sum" // path @Int // path @Int) ~>> (\i1 i2 -> return $ ok (i1 + i2) )
The trick is that //
defines sequential AND
combination of endpoints that is represented as endpoint of HList
, so
instead of dealing with heterogeneous list, it's possible to use ~>>
instead and map with a function of multiple arguments.
Endpoints are also composable in terms of OR
logic with |+|
operator that is useful for routing:
getUsers = get (p' "users") ~>> (ok <$> fetchUsers) newUser = post (p' "users" // jsonBody @User) ~>> (\user -> ok <$> createUser user) usersApi = getUsers |+| newUser
An endpoint might be converted into WAI Application
using bootstrap
and @TypeApplications
language pragma:
main = run 9000 app where app = bootstrap @TextPlain usersApi & compile & toApp @IO
Endpoint | |
|
Instances
Functor m => Functor (Endpoint m) Source # | |
MonadCatch m => Applicative (Endpoint m) Source # | |
MonadCatch m => Alternative (Endpoint m) Source # | |
Show (Endpoint m a) Source # | |
(Negotiable ct a, Negotiable ct SomeException, Negotiable ct (), Compile cts m (HList es), MonadCatch m) => Compile (ct :+: cts) m (HList (Endpoint m a ': es)) Source # | |
(~>) :: Monad m => Endpoint m a -> (a -> m (Output b)) -> Endpoint m b infixl 0 Source #
Inversed alias for mapOutputM
(~>>) :: (Monad m, FnToProduct fn ls (m (Output b))) => Endpoint m (HList ls) -> fn -> Endpoint m b infixl 0 Source #
(//) :: (MonadCatch m, AdjoinHList (a ': (b ': '[])) out) => Endpoint m a -> Endpoint m b -> Endpoint m (HList out) infixr 2 Source #
(|+|) :: forall m a b out. (MonadCatch m, AdjoinCoproduct (Coproduct a (Coproduct b CNil)) out) => Endpoint m a -> Endpoint m b -> Endpoint m out infixl 2 Source #
Method endpoints
get :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for GET requests
post :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for POST requests
put :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for PUT requests
patch :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for PATCH requests
delete :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for DELETE requests
head' :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for HEAD requests
trace' :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for TRACE requests
connect :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for CONNECT requests
options :: Endpoint m a -> Endpoint m a Source #
Turn endpoint into one that matches only for OPTIONS requests
Path matching endpoints
path :: forall a m. (DecodePath a, Applicative m, Typeable a) => Endpoint m a Source #
Endpoint that tries to decode head of the current path reminder into specific type. It consumes head of the reminder.
- If path is empty, Endpoint is not matched
- If decoding has failed, Endpoint is not matched
pathAny :: Applicative m => Endpoint m (HList '[]) Source #
Endpoint that matches any path and discards reminder
pathConst :: Applicative m => Text -> Endpoint m (HList '[]) Source #
Endpoint that matches only if the head of current path reminder is equal to some given constant value. It consumes head of the reminder.
- If value matches the provided constant, saves the tail of the path as a reminder
- Otherwise, resulting endpoint is not matched
pathEmpty :: Applicative m => Endpoint m (HList '[]) Source #
Endpoint that matches only against empty path reminder
paths :: forall a m. (DecodePath a, Applicative m, Typeable a) => Endpoint m [a] Source #
Endpoint that consumes the rest of the path reminder and decode it using provided DecodePath for some type a
Query parameters endpoints
param :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m a Source #
Endpoint that tries to decode parameter name
from the request query string.
Always matches, but may throw an exception in case:
- Parameter is not presented in request query
- There was a parameter decoding error
paramMaybe :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (Maybe a) Source #
Endpoint that tries to decode parameter name
from the request query string.
Always matches, but may throw an exception in case:
- There was a parameter decoding error
params :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m [a] Source #
Endpoint that tries to decode all parameters name
from the request query string.
Always matches, but may throw an exception in case:
- There was a parameter decoding error of at least one parameter value
paramsNel :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (NonEmpty a) Source #
Endpoint that tries to decode all parameters name
from the request query string.
Always matches, but may throw an exception in case:
- There was a parameter decoding error of at least one parameter value
- All parameters are empty or missing in request query
Request body endpoints
body :: forall ct a m. (Decode ct a, MonadIO m, MonadThrow m) => Endpoint m a Source #
Endpoint that tries to decode body of request into some type a
using corresponding Decode
instance.
Matches if body isn't chunked. May throw an exception in case:
- Body is empty
- There was a body decoding error
bodyMaybe :: forall ct a m. (Decode ct a, MonadIO m, MonadThrow m) => Endpoint m (Maybe a) Source #
Endpoint that tries to decode body of request into some type a
using corresponding Decode
instance.
Matches if body isn't chunked. May throw an exception in case:
- There was a body decoding error
textBody :: (Decode TextPlain a, MonadIO m, MonadThrow m) => Endpoint m a Source #
Alias for body @TextPlain
textBodyMaybe :: (Decode TextPlain a, MonadIO m, MonadThrow m) => Endpoint m (Maybe a) Source #
Alias for bodyMaybe @TextPlain
jsonBody :: (Decode ApplicationJson a, MonadIO m, MonadThrow m) => Endpoint m a Source #
Alias for body @ApplicationJson
jsonBodyMaybe :: (Decode ApplicationJson a, MonadIO m, MonadThrow m) => Endpoint m (Maybe a) Source #
Alias for bodyMaybe @ApplicationJson
Cookie endpoints
cookie :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m a Source #
Endpoint that tries to decode cookie name
from a request.
Always matches, but may throw an exception in case:
- Cookie is not presented in the request
- There was a cookie decoding error
cookieMaybe :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (Maybe a) Source #
Endpoint that tries to decode cookie name
from a request.
Always matches, but may throw an exception in case:
- There was a cookie decoding error
Header endpoints
header :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m a Source #
Endpoint that tries to decode header name
from a request.
Always matches, but may throw an exception in case:
- Headers is not presented in the request
- There was a header decoding error
headerMaybe :: forall a m. (DecodeEntity a, MonadThrow m) => ByteString -> Endpoint m (Maybe a) Source #
Endpoint that tries to decode header name
from a request.
Always matches, but may throw an exception in case:
- There was a header decoding error
Response encoding and request decoding
class Encode ct a where Source #
Encoding of some type a
into payload of HTTP response
Phantom type ct
guarantees that compiler checks support of encoding of some a
into content of given Content-Type
by looking for specific Encode
instance.
encode :: a -> ByteString Source #
Instances
Encode TextPlain Double Source # | |
Defined in Linnet.Encode encode :: Double -> ByteString Source # | |
Encode TextPlain Float Source # | |
Defined in Linnet.Encode encode :: Float -> ByteString Source # | |
Encode TextPlain Int Source # | |
Defined in Linnet.Encode encode :: Int -> ByteString Source # | |
Encode TextPlain Integer Source # | |
Defined in Linnet.Encode encode :: Integer -> ByteString Source # | |
Encode TextPlain ByteString Source # | |
Defined in Linnet.Encode encode :: ByteString -> ByteString0 Source # | |
Encode TextPlain ByteString Source # | |
Defined in Linnet.Encode encode :: ByteString -> ByteString Source # | |
Encode TextPlain Text Source # | |
Defined in Linnet.Encode encode :: Text -> ByteString Source # | |
Encode TextPlain Text Source # | |
Defined in Linnet.Encode encode :: Text -> ByteString Source # |
class Decode ct a where Source #
Decoding of HTTP request payload into some type a
.
Phantom type ct
guarantees that compiler checks support of decoding some a
from content of given Content-Type
by looking for specific Decode
instance.
decode :: ByteString -> Either LinnetError a Source #
Instances
Decode TextPlain ByteString Source # | |
Defined in Linnet.Decode | |
Decode TextPlain ByteString Source # | |
Defined in Linnet.Decode |
Endpoint output
Output of Endpoint
that carries some Payload
a
together with response status and headers
Output | |
|
Instances
Monad Output Source # | |
Functor Output Source # | |
Applicative Output Source # | |
Foldable Output Source # | |
Defined in Linnet.Output fold :: Monoid m => Output m -> m # foldMap :: Monoid m => (a -> m) -> Output a -> m # foldr :: (a -> b -> b) -> b -> Output a -> b # foldr' :: (a -> b -> b) -> b -> Output a -> b # foldl :: (b -> a -> b) -> b -> Output a -> b # foldl' :: (b -> a -> b) -> b -> Output a -> b # foldr1 :: (a -> a -> a) -> Output a -> a # foldl1 :: (a -> a -> a) -> Output a -> a # elem :: Eq a => a -> Output a -> Bool # maximum :: Ord a => Output a -> a # minimum :: Ord a => Output a -> a # | |
Traversable Output Source # | |
MonadThrow Output Source # | |
Defined in Linnet.Output | |
Eq a => Eq (Output a) Source # | |
Show a => Show (Output a) Source # | |
badRequest :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status BAD REQUEST 400
unauthorized :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status UNAUTHORIZED 401
paymentRequired :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status PAYMENT REQUIRED 402
forbidden :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status FORBIDDEN 403
notFound :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status NOT FOUND 404
methodNotAllowed :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status METHOD NOT ALLOWED 405
notAcceptable :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status NOT ACCEPTABLE 406
conflict :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status CONFLICT 409
lengthRequired :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status LENGTH REQUIRED 411
preconditionFailed :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status PRECONDITIONED FAILED 412
requestEntityTooLarge :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status REQUEST ENTITY TOO LARGE 413
unprocessableEntity :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status UNPROCESSABLE ENTITY 422
tooManyRequests :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status TOO MANY REQUESTS 422
internalServerError :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status INTERNAL SERVER ERROR 500
notImplemented :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status NOT IMPLEMENTED 501
badGateway :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status BAD GATEWAY 502
serviceUnavailable :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status SERVICE UNAVAILABLE 503
gatewayTimeout :: Exception e => e -> Output a Source #
Create Output
with ErrorPayload e
and status GATEWAY TIMEOUT 504
Compiling an endpoint
bootstrap :: forall ct m a. Endpoint m a -> Bootstrap m (ct :+: CNil) (HList '[Endpoint m a]) Source #
Create Bootstrap
out of single Endpoint
and some given Content-Type:
bootstrap @TextPlain (pure "foo")
To enable Content-Type negotiation based on Accept
header, use Coproduct
:+:
type operator to set the type:
bootstrap @(TextPlain :+: TextHtml) (pure "foo") -- in case of failed negotiation, text/html is picked as the last resort bootstrap @(TextPlain :+: TextHtml :+: NotAcceptable406) (pure "foo") -- in case of failed negotiation, 406 is returned
serve :: forall ct cts es m a. Endpoint m a -> Bootstrap m cts (HList es) -> Bootstrap m (ct :+: cts) (HList (Endpoint m a ': es)) Source #
Add another endpoint to Bootstrap
for purpose of serving multiple Content-Types with *different* endpoints
bootstrap @TextPlain (pure "foo") & serve @ApplicationJson (pure "bar")
compile :: forall cts m es. Compile cts m es => Bootstrap m cts es -> Compiled m Source #
Compile Bootstrap
into Compiled
that is just ReaderT
for further combinations.
Might be useful to implement middleware in context of the same monad m
:
bootstrap @TextPlain (pure "foo") & compile
toApp :: forall m. NaturalTransformation m IO => Compiled m -> Application Source #
Convert Compiled
into WAI Application
bootstrap @TextPlain (pure "foo") & compile & toApp @IO
The constraint here is a natural transformation of Endpoint
s monad m
into IO
.
In case if selected monad is IO
already then provided instance is just enough.
Otherwise, it's necessary define how to "start" custom monad for each request to come and convert it to IO
as the
instance of NaturalTransformation
m IO
.
Running a server
run :: Port -> Application -> IO () #
Run an Application
on the given port.
This calls runSettings
with defaultSettings
.
Content-Type literals
type ApplicationJson = Proxy "application/json" Source #
Content-Type literal for application/json
encoding
Content-Type negotiation
data NotAcceptable406 Source #
Uninhabited type to signal the need of 406 error during Content-Type negotiation