{-# OPTIONS_GHC -Wno-orphans #-}
module WebGear.OpenApi.Trait.Auth.Basic where
import Data.OpenApi
import Data.Proxy (Proxy (..))
import Data.String (fromString)
import GHC.TypeLits (KnownSymbol, symbolVal)
import WebGear.Core.Request (Request)
import WebGear.Core.Trait (Absence, Attribute, Get (..), With)
import WebGear.Core.Trait.Auth.Basic (BasicAuth' (..))
import WebGear.OpenApi.Handler (OpenApiHandler (..))
import WebGear.OpenApi.Trait.Auth (addSecurityScheme)
instance (KnownSymbol scheme) => Get (OpenApiHandler m) (BasicAuth' x scheme m e a) where
{-# INLINE getTrait #-}
getTrait ::
BasicAuth' x scheme m e a ->
OpenApiHandler m (Request `With` ts) (Either (Absence (BasicAuth' x scheme m e a)) (Attribute (BasicAuth' x scheme m e a) Request))
getTrait :: forall (ts :: [*]).
BasicAuth' x scheme m e a
-> OpenApiHandler
m
(With Request ts)
(Either
(Absence (BasicAuth' x scheme m e a))
(Attribute (BasicAuth' x scheme m e a) Request))
getTrait BasicAuth' x scheme m e a
_ =
let schemeName :: Text
schemeName = Text
"http" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
forall a. IsString a => String -> a
fromString (Proxy scheme -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
forall (t :: Symbol). Proxy t
Proxy @scheme))
scheme :: SecurityScheme
scheme =
SecurityScheme
{ _securitySchemeType :: SecuritySchemeType
_securitySchemeType = HttpSchemeType -> SecuritySchemeType
SecuritySchemeHttp HttpSchemeType
HttpSchemeBasic
, _securitySchemeDescription :: Maybe Text
_securitySchemeDescription = Maybe Text
forall a. Maybe a
Nothing
}
in (OpenApi -> State Documentation OpenApi)
-> OpenApiHandler
m
(With Request ts)
(Either
(Absence (BasicAuth' x scheme m e a))
(Attribute (BasicAuth' x scheme m e a) 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 (BasicAuth' x scheme m e a))
(Attribute (BasicAuth' x scheme m e a) Request)))
-> (OpenApi -> State Documentation OpenApi)
-> OpenApiHandler
m
(With Request ts)
(Either
(Absence (BasicAuth' x scheme m e a))
(Attribute (BasicAuth' x scheme m e a) Request))
forall a b. (a -> b) -> a -> b
$ Text -> SecurityScheme -> OpenApi -> State Documentation OpenApi
forall (m :: * -> *).
MonadState Documentation m =>
Text -> SecurityScheme -> OpenApi -> m OpenApi
addSecurityScheme Text
schemeName SecurityScheme
scheme