Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data EndpointResult (m :: * -> *) a
- = Matched {
- matchedReminder :: Input
- matchedTrace :: [Text]
- matchedOutput :: m (Output a)
- | NotMatched { }
- = Matched {
- data Endpoint (m :: * -> *) a = Endpoint {
- runEndpoint :: Input -> EndpointResult m a
- toString :: Text
- data NotMatchedReason
- = MethodNotAllowed { }
- | Other
- type Trace = [Text]
- isMatched :: EndpointResult m a -> Bool
- maybeReminder :: EndpointResult m a -> Maybe Input
- maybeTrace :: EndpointResult m a -> Maybe Trace
- lift :: Functor m => m a -> Endpoint m a
- liftOutputM :: m (Output a) -> Endpoint m a
- mapM' :: Monad m => (a -> m b) -> Endpoint m a -> Endpoint m b
- mapOutput :: Monad m => (a -> Output b) -> Endpoint m a -> Endpoint m b
- mapOutputM :: Monad m => (a -> m (Output b)) -> Endpoint m a -> Endpoint m b
- handle :: (MonadCatch m, Exception e) => (e -> m (Output a)) -> Endpoint m a -> Endpoint m a
- handleAll :: MonadCatch m => (SomeException -> m (Output a)) -> Endpoint m a -> Endpoint m a
- try :: (Exception e, MonadCatch m) => Endpoint m a -> Endpoint m (Either e a)
- transformOutput :: (m (Output a) -> k (Output b)) -> Endpoint m a -> Endpoint k b
- transform :: Monad m => (m a -> m b) -> Endpoint m a -> Endpoint m b
- (~>) :: 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
- productWith :: forall m a b c. MonadCatch m => Endpoint m a -> Endpoint m b -> (a -> b -> c) -> Endpoint m c
- (//) :: (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
- root :: Applicative m => Endpoint m Request
- zero :: Applicative m => Endpoint m (HList '[])
Documentation
data EndpointResult (m :: * -> *) a Source #
Result of returned by Endpoint
that could be either:
Matched
containing reminder of the input together withOutput
inside of monadm
NotMatched
in case endpoint doesn't match the input
Matched | |
| |
NotMatched | |
Instances
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 # | |
data NotMatchedReason Source #
Instances
Eq NotMatchedReason Source # | |
Defined in Linnet.Endpoint (==) :: NotMatchedReason -> NotMatchedReason -> Bool # (/=) :: NotMatchedReason -> NotMatchedReason -> Bool # | |
Show NotMatchedReason Source # | |
Defined in Linnet.Endpoint showsPrec :: Int -> NotMatchedReason -> ShowS # show :: NotMatchedReason -> String # showList :: [NotMatchedReason] -> ShowS # |
isMatched :: EndpointResult m a -> Bool 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
(~>) :: 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 #
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 Endpoint
s 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 #
(|+|) :: 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 #