mellon-web-0.8.0.7: A REST web service for Mellon controllers

Copyright(c) 2018 Quixoftic LLC
LicenseBSD3
MaintainerDrew Hess <dhess-src@quixoftic.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Mellon.Web.Server.API

Contents

Description

This module provides a Servant REST web service for mellon-core controllers. The service translates REST methods to controller actions.

See the included API.md file for detailed documentation on the REST service methods and document types.

Synopsis

Types

type MellonAPI = ("time" :> Get '[JSON, HTML] Time) :<|> (("state" :> Get '[JSON, HTML] State) :<|> ("state" :> (ReqBody '[JSON] State :> Put '[JSON, HTML] State))) Source #

A Servant API for interacting with a Controller.

In addition to the controller methods, the API also provides a way to obtain the system time on the server, to ensure that the server's clock is accurate.

data State Source #

Mimics State, but provides JSON conversions. (Avoids orphan instances.)

Constructors

Locked 
Unlocked !UTCTime 

Instances

Eq State Source # 

Methods

(==) :: State -> State -> Bool #

(/=) :: State -> State -> Bool #

Data State Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> State -> c State #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c State #

toConstr :: State -> Constr #

dataTypeOf :: State -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c State) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c State) #

gmapT :: (forall b. Data b => b -> b) -> State -> State #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> State -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> State -> r #

gmapQ :: (forall d. Data d => d -> u) -> State -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> State -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> State -> m State #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> State -> m State #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> State -> m State #

Read State Source # 
Show State Source # 

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

Generic State Source # 

Associated Types

type Rep State :: * -> * #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

ToJSON State Source # 
FromJSON State Source # 
ToHtml State Source # 

Methods

toHtml :: Monad m => State -> HtmlT m () #

toHtmlRaw :: Monad m => State -> HtmlT m () #

ToSample State Source # 

Methods

toSamples :: Proxy * State -> [(Text, State)] #

ToSchema State Source # 
type Rep State Source # 
type Rep State = D1 * (MetaData "State" "Mellon.Web.Server.API" "mellon-web-0.8.0.7-GtVQlPGemFD69eIJXuJuvS" False) ((:+:) * (C1 * (MetaCons "Locked" PrefixI False) (U1 *)) (C1 * (MetaCons "Unlocked" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))))

newtype Time Source #

A newtype wrapper around UTCTime, for serving HTML without orphan instances.

Constructors

Time UTCTime 

Instances

Eq Time Source # 

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Data Time Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Time -> c Time #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Time #

toConstr :: Time -> Constr #

dataTypeOf :: Time -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Time) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Time) #

gmapT :: (forall b. Data b => b -> b) -> Time -> Time #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Time -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Time -> r #

gmapQ :: (forall d. Data d => d -> u) -> Time -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Time -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Time -> m Time #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Time -> m Time #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Time -> m Time #

Ord Time Source # 

Methods

compare :: Time -> Time -> Ordering #

(<) :: Time -> Time -> Bool #

(<=) :: Time -> Time -> Bool #

(>) :: Time -> Time -> Bool #

(>=) :: Time -> Time -> Bool #

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

Read Time Source # 
Show Time Source # 

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Generic Time Source # 

Associated Types

type Rep Time :: * -> * #

Methods

from :: Time -> Rep Time x #

to :: Rep Time x -> Time #

ToJSON Time Source # 
FromJSON Time Source # 
ToHtml Time Source # 

Methods

toHtml :: Monad m => Time -> HtmlT m () #

toHtmlRaw :: Monad m => Time -> HtmlT m () #

ToSample Time Source # 

Methods

toSamples :: Proxy * Time -> [(Text, Time)] #

ToSchema Time Source # 
type Rep Time Source # 
type Rep Time = D1 * (MetaData "Time" "Mellon.Web.Server.API" "mellon-web-0.8.0.7-GtVQlPGemFD69eIJXuJuvS" True) (C1 * (MetaCons "Time" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * UTCTime)))

Servant / WAI functions

app :: Controller d -> Application Source #

A WAI Application which runs the service, using the given Controller.

mellonAPI :: Proxy MellonAPI Source #

A Proxy for MellonAPI, exported in order to make it possible to extend the API.

server :: Controller d -> Server MellonAPI Source #

A Servant Server which serves the MellonAPI on the given Controller.

Normally you will just use app, but this function is exported so that you can extend/wrap MellonAPI.