linnet-0.1.0.0: Lightweight library for building HTTP API

Copyright(c) Sergey Kolbasov 2019
LicenseApache License 2.0
Safe HaskellNone
LanguageHaskell2010

Linnet

Contents

Description

Linnet [ˈlɪnɪt] is a lightweight Haskell library for building HTTP API on top of WAI. Library design is heavily inspired by Scala Finch.

See the detailed documentation on linnet.io.

Synopsis

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 id

Constructors

Endpoint 
Instances
Functor m => Functor (Endpoint m) Source # 
Instance details

Defined in Linnet.Endpoint

Methods

fmap :: (a -> b) -> Endpoint m a -> Endpoint m b #

(<$) :: a -> Endpoint m b -> Endpoint m a #

MonadCatch m => Applicative (Endpoint m) Source # 
Instance details

Defined in Linnet.Endpoint

Methods

pure :: a -> Endpoint m a #

(<*>) :: Endpoint m (a -> b) -> Endpoint m a -> Endpoint m b #

liftA2 :: (a -> b -> c) -> Endpoint m a -> Endpoint m b -> Endpoint m c #

(*>) :: Endpoint m a -> Endpoint m b -> Endpoint m b #

(<*) :: Endpoint m a -> Endpoint m b -> Endpoint m a #

MonadCatch m => Alternative (Endpoint m) Source # 
Instance details

Defined in Linnet.Endpoint

Methods

empty :: Endpoint m a #

(<|>) :: Endpoint m a -> Endpoint m a -> Endpoint m a #

some :: Endpoint m a -> Endpoint m [a] #

many :: Endpoint m a -> Endpoint m [a] #

Show (Endpoint m a) Source # 
Instance details

Defined in Linnet.Endpoint

Methods

showsPrec :: Int -> Endpoint m a -> ShowS #

show :: Endpoint m a -> String #

showList :: [Endpoint m a] -> ShowS #

(KnownSymbol ct, ToResponse ct a, ToResponse ct SomeException, Compile cts m (HList es), MonadCatch m) => Compile (Coproduct (Proxy ct) cts) m (HList (Endpoint m a ': es)) Source # 
Instance details

Defined in Linnet.Compile

Methods

compile :: HList (Endpoint m a ': es) -> ReaderT Request m Response 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 #

Advanced version of ~> operator that allows to map Endpoint m (HList ls) over a function of arity N equal to N elements of HList. General rule of thumb when to use this operator is whenever there is an HList on the left side.

(//) :: (MonadCatch m, AdjoinHList (a ': (b ': '[])) out) => Endpoint m a -> Endpoint m b -> Endpoint m (HList out) infixr 2 Source #

Create product of two Endpoints that sequentially match a request and values are adjoined into HList. If some of endpoints doesn't match a request, the final result is also non-matching

(|+|) :: 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 #

Create new Endpoint of two endpoints, adjoining values into Coproduct During request resolution the following logic is applied:

  • If none of endpoints match, resulting endpoint is also non-matching
  • If both endpoints match, the more specific one is selected (with shorter reminder)

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

p' :: Applicative m => Text -> Endpoint m (HList '[]) Source #

Short alias for pathConst

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 :: Symbol) 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.

Methods

encode :: a -> ByteString Source #

Instances
Encode TextPlain Double Source # 
Instance details

Defined in Linnet.Encode

Encode TextPlain Float Source # 
Instance details

Defined in Linnet.Encode

Encode TextPlain Int Source # 
Instance details

Defined in Linnet.Encode

Encode TextPlain Integer Source # 
Instance details

Defined in Linnet.Encode

Encode TextPlain ByteString Source # 
Instance details

Defined in Linnet.Encode

Encode TextPlain ByteString Source # 
Instance details

Defined in Linnet.Encode

Encode TextPlain Text Source # 
Instance details

Defined in Linnet.Encode

Encode TextPlain Text Source # 
Instance details

Defined in Linnet.Encode

class Decode (ct :: Symbol) 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.

Endpoint output

data Output a Source #

Output of Endpoint that carries some Payload a together with response status and headers

Constructors

Output 
Instances
Monad Output Source # 
Instance details

Defined in Linnet.Output

Methods

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

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

return :: a -> Output a #

fail :: String -> Output a #

Functor Output Source # 
Instance details

Defined in Linnet.Output

Methods

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

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

Applicative Output Source # 
Instance details

Defined in Linnet.Output

Methods

pure :: a -> Output a #

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

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

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

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

Foldable Output Source # 
Instance details

Defined in Linnet.Output

Methods

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 #

toList :: Output a -> [a] #

null :: Output a -> Bool #

length :: Output a -> Int #

elem :: Eq a => a -> Output a -> Bool #

maximum :: Ord a => Output a -> a #

minimum :: Ord a => Output a -> a #

sum :: Num a => Output a -> a #

product :: Num a => Output a -> a #

Traversable Output Source # 
Instance details

Defined in Linnet.Output

Methods

traverse :: Applicative f => (a -> f b) -> Output a -> f (Output b) #

sequenceA :: Applicative f => Output (f a) -> f (Output a) #

mapM :: Monad m => (a -> m b) -> Output a -> m (Output b) #

sequence :: Monad m => Output (m a) -> m (Output a) #

MonadThrow Output Source # 
Instance details

Defined in Linnet.Output

Methods

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

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

Defined in Linnet.Output

Methods

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

show :: Output a -> String #

showList :: [Output a] -> ShowS #

ok :: a -> Output a Source #

Create Output with Payload a and status OK 200

created :: a -> Output a Source #

Create Output with Payload a and status CREATED 201

accepted :: Output a Source #

Create Output with NoPayload and status ACCEPTED 202

noContent :: Output a Source #

Create Output with NoPayload and status NO CONTENT 202

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

gone :: Exception e => e -> Output a Source #

Create Output with ErrorPayload e and status GONE 410

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 :: Symbol) m a. Endpoint m a -> Bootstrap m (Coproduct (Proxy ct) CNil) (HList '[Endpoint m a]) Source #

Create Bootstrap out of single Endpoint and some given Content-Type:

bootstrap @TextPlain (pure "foo")

serve :: forall (ct :: Symbol) cts es m a. Endpoint m a -> Bootstrap m cts (HList es) -> Bootstrap m (Coproduct (Proxy 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") & server @ApplicationJson (pure "bar")

compile :: forall cts m es. Compile cts m es => Bootstrap m cts es -> ReaderT Request m Response Source #

Compile Bootstrap into ReaderT Request m Response for further combinations. Might be useful to implement middleware in context of the same monad m:

bootstrap @TextPlain (pure "foo") & compile

toApp :: (forall a. m a -> IO a) -> ReaderT Request m Response -> Application Source #

Convert ReaderT Request m Response into WAI Application

bootstrap @TextPlain (pure "foo") & compile & toApp id

The first parameter here is a natural transformation of Endpoints monad m into IO. In case if selected monad is IO already then id is just enough. Otherwise, it's a good place to define how to "start" custom monad for each request to come and convert it to IO.

As an example:

  • ReaderT RequestContext IO could be used to pass some data as local context for the request.
  • Some monad for logging (i.e. co-log)

Running a server

run :: Port -> Application -> IO () #

Run an Application on the given port. This calls runSettings with defaultSettings.

Content-Type literals

type ApplicationJson = "application/json" Source #

Content-Type literal for application/json encoding

type TextHtml = "text/html" Source #

Content-Type literal for text/html encoding

type TextPlain = "text/plain" Source #

Content-Type literal for text/plain encoding