{-# OPTIONS_GHC -Wno-orphans #-}
module WebGear.OpenApi.Trait.Method where
import Control.Lens ((%~), (&))
import qualified Data.HashMap.Strict.InsOrd as Map
import Data.OpenApi (PathItem (..), paths)
import Network.HTTP.Types (StdMethod (..))
import WebGear.Core.Trait (Get (..))
import WebGear.Core.Trait.Method (Method (..))
import WebGear.OpenApi.Handler (OpenApiHandler (..), addRouteDocumentation)
instance Get (OpenApiHandler m) Method where
{-# INLINE getTrait #-}
getTrait :: forall (ts :: [*]).
Prerequisite Method ts =>
Method
-> OpenApiHandler
m
(With Request ts)
(Either (Absence Method) (Attribute Method Request))
getTrait (Method StdMethod
method) = (OpenApi -> State Documentation OpenApi)
-> OpenApiHandler
m
(With Request ts)
(Either (Absence Method) (Attribute Method Request))
forall {k} {k1} {k2} (m :: k) (a :: k1) (b :: k2).
(OpenApi -> State Documentation OpenApi) -> OpenApiHandler m a b
OpenApiHandler ((OpenApi -> State Documentation OpenApi)
-> OpenApiHandler
m
(With Request ts)
(Either (Absence Method) (Attribute Method Request)))
-> (OpenApi -> State Documentation OpenApi)
-> OpenApiHandler
m
(With Request ts)
(Either (Absence Method) (Attribute Method Request))
forall a b. (a -> b) -> a -> b
$ \OpenApi
doc -> do
OpenApi -> State Documentation OpenApi
forall (m :: * -> *).
MonadState Documentation m =>
OpenApi -> m OpenApi
addRouteDocumentation (OpenApi -> State Documentation OpenApi)
-> OpenApi -> State Documentation OpenApi
forall a b. (a -> b) -> a -> b
$ OpenApi
doc OpenApi -> (OpenApi -> OpenApi) -> OpenApi
forall a b. a -> (a -> b) -> b
& (InsOrdHashMap FilePath PathItem
-> Identity (InsOrdHashMap FilePath PathItem))
-> OpenApi -> Identity OpenApi
forall s a. HasPaths s a => Lens' s a
Lens' OpenApi (InsOrdHashMap FilePath PathItem)
paths ((InsOrdHashMap FilePath PathItem
-> Identity (InsOrdHashMap FilePath PathItem))
-> OpenApi -> Identity OpenApi)
-> (InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem)
-> OpenApi
-> OpenApi
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (PathItem -> PathItem)
-> InsOrdHashMap FilePath PathItem
-> InsOrdHashMap FilePath PathItem
forall v1 v2 k.
(v1 -> v2) -> InsOrdHashMap k v1 -> InsOrdHashMap k v2
Map.map (StdMethod -> PathItem -> PathItem
removeOtherMethods StdMethod
method)
removeOtherMethods :: StdMethod -> PathItem -> PathItem
removeOtherMethods :: StdMethod -> PathItem -> PathItem
removeOtherMethods StdMethod
method PathItem{[Referenced Param]
[Server]
Maybe Text
Maybe Operation
_pathItemSummary :: Maybe Text
_pathItemDescription :: Maybe Text
_pathItemGet :: Maybe Operation
_pathItemPut :: Maybe Operation
_pathItemPost :: Maybe Operation
_pathItemDelete :: Maybe Operation
_pathItemOptions :: Maybe Operation
_pathItemHead :: Maybe Operation
_pathItemPatch :: Maybe Operation
_pathItemTrace :: Maybe Operation
_pathItemServers :: [Server]
_pathItemParameters :: [Referenced Param]
_pathItemSummary :: PathItem -> Maybe Text
_pathItemDescription :: PathItem -> Maybe Text
_pathItemGet :: PathItem -> Maybe Operation
_pathItemPut :: PathItem -> Maybe Operation
_pathItemPost :: PathItem -> Maybe Operation
_pathItemDelete :: PathItem -> Maybe Operation
_pathItemOptions :: PathItem -> Maybe Operation
_pathItemHead :: PathItem -> Maybe Operation
_pathItemPatch :: PathItem -> Maybe Operation
_pathItemTrace :: PathItem -> Maybe Operation
_pathItemServers :: PathItem -> [Server]
_pathItemParameters :: PathItem -> [Referenced Param]
..} =
case StdMethod
method of
StdMethod
GET -> PathItem
forall a. Monoid a => a
mempty{_pathItemGet, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
PUT -> PathItem
forall a. Monoid a => a
mempty{_pathItemPut, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
POST -> PathItem
forall a. Monoid a => a
mempty{_pathItemPost, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
DELETE -> PathItem
forall a. Monoid a => a
mempty{_pathItemDelete, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
HEAD -> PathItem
forall a. Monoid a => a
mempty{_pathItemHead, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
TRACE -> PathItem
forall a. Monoid a => a
mempty{_pathItemTrace, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
OPTIONS -> PathItem
forall a. Monoid a => a
mempty{_pathItemOptions, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
PATCH -> PathItem
forall a. Monoid a => a
mempty{_pathItemPatch, _pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}
StdMethod
CONNECT -> PathItem
forall a. Monoid a => a
mempty{_pathItemSummary, _pathItemDescription, _pathItemServers, _pathItemParameters}