linnet-0.2.0.0: Lightweight library for building HTTP API

Safe HaskellNone
LanguageHaskell2010

Linnet.Output

Synopsis

Documentation

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 #

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

Defined in Linnet.Output

Methods

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

(/=) :: Output a -> Output a -> Bool #

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 #

data Payload a Source #

Payload of Output that could be:

Constructors

Payload a

Payload with some value a

NoPayload

Represents empty response

Exception e => ErrorPayload e

Failed payload with an exception inside

Instances
Eq a => Eq (Payload a) Source # 
Instance details

Defined in Linnet.Output

Methods

(==) :: Payload a -> Payload a -> Bool #

(/=) :: Payload a -> Payload a -> Bool #

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

Defined in Linnet.Output

Methods

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

show :: Payload a -> String #

showList :: [Payload 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

payloadOutput :: Status -> a -> Output a Source #

Create successful Output with payload a and given status

payloadError :: Exception e => Status -> e -> Output a Source #

Create failed Output with exception e and given status

payloadEmpty :: Status -> Output a Source #

Create empty Output with given status

transformM :: Applicative m => (a -> m (Output b)) -> Output a -> m (Output b) Source #

Transform payload of output

withHeader :: (ByteString, ByteString) -> Output a -> Output a Source #

Add header to given Output