module Data.Swagger.Build.Resource
( Data.Swagger.Build.Resource.resources
, Data.Swagger.Build.Resource.api
, Data.Swagger.Build.Resource.apiVersion
, Data.Swagger.Build.Resource.info
, Data.Swagger.Build.Resource.termsOfServiceUrl
, Data.Swagger.Build.Resource.contact
, Data.Swagger.Build.Resource.license
, Data.Swagger.Build.Resource.licenseUrl
, Data.Swagger.Build.Resource.authorisation
, Data.Swagger.Build.Util.end
, ResourcesBuilder
, InfoBuilder
) where
import Control.Monad.Trans.State.Strict
import Data.Text (Text)
import Data.Swagger.Build.Util hiding (authorisation)
import Data.Swagger.Model.Authorisation as A
import Data.Swagger.Model.Resource as R
type ResourcesBuilder = State Resources ()
resources :: Text -> ResourcesBuilder -> Resources
resources v s = execState s start
where
start = Resources v [] Nothing Nothing Nothing
type ResourceSt = Common '["description"] Resource
type ResourceBuilder = State ResourceSt ()
api :: Text -> ResourceBuilder -> ResourcesBuilder
api p s = modify $ \r ->
r { apis = value (execState s start) : apis r }
where
start = common $ Resource p Nothing
value c = (other c) { R.description = descr c }
apiVersion :: Text -> ResourcesBuilder
apiVersion v = modify $ \r -> r { R.apiVersion = Just v }
type InfoSt = Common '["description"] Info
type InfoBuilder = State InfoSt ()
info :: Text -> InfoBuilder -> ResourcesBuilder
info t s = modify $ \r ->
r { R.info = Just $ value (execState s start) }
where
start = common $ Info t Nothing Nothing Nothing Nothing Nothing
value c = (other c) { infoDescription = descr c }
termsOfServiceUrl :: Text -> InfoBuilder
termsOfServiceUrl u = modify $ \c -> c { other = (other c) { R.termsOfServiceUrl = Just u } }
contact :: Text -> InfoBuilder
contact u = modify $ \c -> c { other = (other c) { R.contact = Just u } }
license :: Text -> InfoBuilder
license u = modify $ \c -> c { other = (other c) { R.license = Just u } }
licenseUrl :: Text -> InfoBuilder
licenseUrl u = modify $ \c -> c { other = (other c) { R.licenseUrl = Just u } }
authorisation :: Text -> Authorisation -> ResourcesBuilder
authorisation n a = modify $ \r -> let x = (n, a) in
r { authorisations = maybe (Just [x]) (Just . (x:)) (authorisations r) }