module Servant.API.Routes.Route
(
Route
, defRoute
, renderRoute
, routeMethod
, routePath
, routeParams
, routeRequestHeaders
, routeRequestBody
, routeResponse
, routeAuths
, routeDescription
, routeSummary
, add
, RouteDescription (..)
, RouteSummary (..)
)
where
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Lens.Micro
import Network.HTTP.Types.Method (Method)
import "this" Servant.API.Routes.Internal.Route
import "this" Servant.API.Routes.Param
import "this" Servant.API.Routes.Path
import "this" Servant.API.Routes.Request
import "this" Servant.API.Routes.Response
defRoute :: Method -> Route
defRoute :: Method -> Route
defRoute Method
method =
Route
{ _routeMethod :: Method
_routeMethod = Method
method
, _routePath :: Path
_routePath = Path
rootPath
, _routeParams :: Set Param
_routeParams = Set Param
forall a. Set a
Set.empty
, _routeRequestHeaders :: Set HeaderRep
_routeRequestHeaders = Set HeaderRep
forall a. Monoid a => a
mempty
, _routeRequestBody :: Request
_routeRequestBody = Request
noRequest
, _routeResponse :: Responses
_routeResponse = Responses
noResponse
, _routeAuths :: Set Auth
_routeAuths = Set Auth
forall a. Monoid a => a
mempty
, _routeDescription :: Maybe RouteDescription
_routeDescription = Maybe RouteDescription
forall a. Maybe a
Nothing
, _routeSummary :: Maybe RouteSummary
_routeSummary = Maybe RouteSummary
forall a. Maybe a
Nothing
}
renderRoute :: Route -> T.Text
renderRoute :: Route -> Text
renderRoute Route {Maybe RouteDescription
Maybe RouteSummary
Method
Set Auth
Set Param
Set HeaderRep
Path
Request
Responses
_routeMethod :: Route -> Method
_routePath :: Route -> Path
_routeParams :: Route -> Set Param
_routeRequestHeaders :: Route -> Set HeaderRep
_routeRequestBody :: Route -> Request
_routeResponse :: Route -> Responses
_routeAuths :: Route -> Set Auth
_routeDescription :: Route -> Maybe RouteDescription
_routeSummary :: Route -> Maybe RouteSummary
_routeMethod :: Method
_routePath :: Path
_routeParams :: Set Param
_routeRequestHeaders :: Set HeaderRep
_routeRequestBody :: Request
_routeResponse :: Responses
_routeAuths :: Set Auth
_routeDescription :: Maybe RouteDescription
_routeSummary :: Maybe RouteSummary
..} =
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
[ Text
method
, Text
" "
, Text
path
, Text
params
]
where
method :: Text
method = Method -> Text
TE.decodeUtf8 Method
_routeMethod
path :: Text
path = Path -> Text
renderPath Path
_routePath
params :: Text
params =
if Set Param -> Bool
forall a. Set a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Set Param
_routeParams
then Text
""
else Text
"?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"&" (Param -> Text
renderParam (Param -> Text) -> [Param] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set Param -> [Param]
forall a. Set a -> [a]
Set.toList Set Param
_routeParams)
add :: (Ord a) => ASetter s t (Set.Set a) (Set.Set a) -> a -> s -> t
add :: forall a s t. Ord a => ASetter s t (Set a) (Set a) -> a -> s -> t
add ASetter s t (Set a) (Set a)
setter = ASetter s t (Set a) (Set a) -> (Set a -> Set a) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter s t (Set a) (Set a)
setter ((Set a -> Set a) -> s -> t)
-> (a -> Set a -> Set a) -> a -> s -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Set a -> Set a
forall a. Ord a => a -> Set a -> Set a
Set.insert