{-# OPTIONS_GHC -Wno-orphans #-}
module WebGear.OpenApi.Trait.Method where
import WebGear.Core.Request (Request)
import WebGear.Core.Trait (Get (..))
import WebGear.Core.Trait.Method (Method (..))
import WebGear.OpenApi.Handler (DocNode (DocMethod), OpenApiHandler (OpenApiHandler), singletonNode)
instance Get (OpenApiHandler m) Method Request where
{-# INLINEABLE getTrait #-}
getTrait :: Method
-> OpenApiHandler
m
(Linked ts Request)
(Either (Absence Method Request) (Attribute Method Request))
getTrait (Method StdMethod
method) = Tree DocNode
-> OpenApiHandler
m (Linked ts Request) (Either MethodMismatch StdMethod)
forall k k k (m :: k) (a :: k) (b :: k).
Tree DocNode -> OpenApiHandler m a b
OpenApiHandler (Tree DocNode
-> OpenApiHandler
m (Linked ts Request) (Either MethodMismatch StdMethod))
-> Tree DocNode
-> OpenApiHandler
m (Linked ts Request) (Either MethodMismatch StdMethod)
forall a b. (a -> b) -> a -> b
$ DocNode -> Tree DocNode
forall a. a -> Tree a
singletonNode (StdMethod -> DocNode
DocMethod StdMethod
method)