linnet-0.4.0.1: Lightweight library for building HTTP API

Safe HaskellNone
LanguageHaskell2010

Linnet.Endpoint

Synopsis

Documentation

data EndpointResult (m :: * -> *) a Source #

Result of returned by Endpoint that could be either:

  • Matched containing reminder of the input together with Output inside of monad m
  • NotMatched in case endpoint doesn't match the input
Instances
Functor m => Functor (EndpointResult m) Source # 
Instance details

Defined in Linnet.Endpoint

Methods

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

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

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

Defined in Linnet.Endpoint

Generic (EndpointResult m a) Source # 
Instance details

Defined in Linnet.Endpoint

Associated Types

type Rep (EndpointResult m a) :: Type -> Type #

Methods

from :: EndpointResult m a -> Rep (EndpointResult m a) x #

to :: Rep (EndpointResult m a) x -> EndpointResult m a #

type Rep (EndpointResult m a) Source # 
Instance details

Defined in Linnet.Endpoint

type Rep (EndpointResult m a) = D1 (MetaData "EndpointResult" "Linnet.Endpoint" "linnet-0.4.0.1-D6u4YWCshsb5sEmk6fhzNy" False) (C1 (MetaCons "Matched" PrefixI True) (S1 (MetaSel (Just "matchedReminder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Input) :*: (S1 (MetaSel (Just "matchedTrace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]) :*: S1 (MetaSel (Just "matchedOutput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (m (Output a))))) :+: C1 (MetaCons "NotMatched" PrefixI True) (S1 (MetaSel (Just "reason") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NotMatchedReason)))

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

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 #

(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 # 
Instance details

Defined in Linnet.Compile

Methods

compile :: HList (Endpoint m a ': es) -> Compiled m Source #

compileWithContext :: HList (Endpoint m a ': es) -> CompileContext -> Compiled m Source #

type Trace = [Text] Source #

maybeReminder :: EndpointResult m a -> Maybe Input Source #

Return reminder of EndpointResult if it was matched

maybeTrace :: EndpointResult m a -> Maybe Trace Source #

Return trace of EndpointResult if it was matched

lift :: Functor m => m a -> Endpoint m a Source #

Lift monadic value m a into Endpoint that always matches

liftOutputM :: m (Output a) -> Endpoint m a Source #

Lift monadic output m (Output a) into Endpoint that always matches

mapM' :: Monad m => (a -> m b) -> Endpoint m a -> Endpoint m b Source #

Map over the Output of endpoint with function returning new value a lifted in monad m

mapOutput :: Monad m => (a -> Output b) -> Endpoint m a -> Endpoint m b Source #

Map over the value of Endpoint with function returning new Output b

mapOutputM :: Monad m => (a -> m (Output b)) -> Endpoint m a -> Endpoint m b Source #

Map over the value of Endpoint with function returning new m (Output b)

handle :: (MonadCatch m, Exception e) => (e -> m (Output a)) -> Endpoint m a -> Endpoint m a Source #

Handle exception in monad m of Endpoint result using provided function that returns new Output

handleAll :: MonadCatch m => (SomeException -> m (Output a)) -> Endpoint m a -> Endpoint m a Source #

Handle all exceptions in monad m of Endpoint result

try :: (Exception e, MonadCatch m) => Endpoint m a -> Endpoint m (Either e a) Source #

Lift an exception of type e into Either

transformOutput :: (m (Output a) -> k (Output b)) -> Endpoint m a -> Endpoint k b Source #

transform :: Monad m => (m a -> m b) -> Endpoint m a -> Endpoint m b 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.

productWith :: forall m a b c. MonadCatch m => Endpoint m a -> Endpoint m b -> (a -> b -> c) -> Endpoint m c Source #

Create product of two Endpoints that sequentially match a request. | If some of endpoints doesn't match a request, the final result is also non-matching

(//) :: (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)

root :: Applicative m => Endpoint m Request Source #

Endpoint that always matches and returns a request from Input

zero :: Applicative m => Endpoint m (HList '[]) Source #

Endpoint that always matches and doesn't change any reminder