{-# LANGUAGE UndecidableInstances #-}
module Servant.Docs.Simple.Parse
( HasDocumentApi (..)
, HasParsable (..)
, symbolVal'
, toDetails
, typeText
) where
import Data.Foldable (fold)
import Data.Map.Ordered (OMap, empty, fromList, (|<))
import Data.Proxy
import Data.Text (Text, pack)
import Data.Typeable (Typeable, typeRep)
import GHC.TypeLits (KnownSymbol, Symbol, symbolVal)
import Servant.API ((:>), AuthProtect, BasicAuth, Capture', CaptureAll, Description, EmptyAPI,
Header', HttpVersion, IsSecure, QueryFlag, QueryParam', QueryParams, RemoteHost,
ReqBody', StreamBody', Summary, Vault, Verb)
import qualified Servant.API.TypeLevel as S (Endpoints)
import Servant.Docs.Simple.Render (ApiDocs (..), Details (..), Parameter, Route)
class HasParsable api where
parse :: ApiDocs
instance HasCollatable (S.Endpoints a) => HasParsable a where
parse = collate @(S.Endpoints a)
instance {-# OVERLAPPING #-} HasParsable EmptyAPI where
parse = collate @'[]
class HasCollatable api where
collate :: ApiDocs
instance (HasDocumentApi api, HasCollatable b) => HasCollatable (api ': b) where
collate = ApiDocs $ (Details <$> documentEndpoint @api) |< previous
where ApiDocs previous = collate @b
instance HasCollatable '[] where
collate = ApiDocs empty
documentEndpoint :: forall a. HasDocumentApi a => (Route, OMap Parameter Details)
documentEndpoint = document @a "" []
class HasDocumentApi api where
document :: Route
-> [(Parameter, Details)]
-> (Route, OMap Parameter Details)
instance (HasDocumentApi b, KnownSymbol route) => HasDocumentApi ((route :: Symbol) :> b) where
document r = document @b formatted
where formatted = fold [r, "/", fragment]
fragment = symbolVal' @route
instance (HasDocumentApi b, KnownSymbol dRoute, Typeable t) => HasDocumentApi (Capture' m (dRoute :: Symbol) t :> b) where
document r = document @b formatted
where formatted = fold [r, "/", "{", var, "::", format, "}"]
var = symbolVal' @dRoute
format = typeText @t
instance (HasDocumentApi b, KnownSymbol dRoute, Typeable t) => HasDocumentApi (CaptureAll (dRoute :: Symbol) t :> b) where
document r = document @b formatted
where formatted = fold [r, "/", "{", var, "::", format, "}"]
var = symbolVal' @dRoute
format = typeText @t
instance HasDocumentApi b => HasDocumentApi (HttpVersion :> b) where
document r a = document @b r $ a <> [("Captures Http Version", Detail "True")]
instance HasDocumentApi b => HasDocumentApi (IsSecure :> b) where
document r a = document @b r $ a <> [("SSL Only", Detail "True")]
instance HasDocumentApi b => HasDocumentApi (RemoteHost :> b) where
document r a = document @b r $ a <> [("Captures RemoteHost/IP", Detail "True")]
instance (HasDocumentApi b, KnownSymbol desc) => HasDocumentApi (Description (desc :: Symbol) :> b) where
document r a = document @b r $ a <> [("Description", Detail $ symbolVal' @desc)]
instance (HasDocumentApi b, KnownSymbol s) => HasDocumentApi (Summary (s :: Symbol) :> b) where
document r a = document @b r $ a <> [("Summary", Detail $ symbolVal' @s)]
instance HasDocumentApi b => HasDocumentApi (Vault :> b) where
document r a = document @b r $ a <> [("Vault", Detail "True")]
instance (HasDocumentApi b, KnownSymbol realm, Typeable a) => HasDocumentApi (BasicAuth (realm :: Symbol) a :> b) where
document r a = document @b r $ a <> [( "Basic Authentication"
, toDetails [ ("Realm", Detail realm)
, ("UserData", Detail userData)
]
)]
where realm = symbolVal' @realm
userData = typeText @a
instance (HasDocumentApi b, KnownSymbol token) => HasDocumentApi (AuthProtect (token :: Symbol) :> b) where
document r a = document @b r $ a <> [("Authentication", Detail authDoc)]
where authDoc = symbolVal' @token
instance (HasDocumentApi b, KnownSymbol ct, Typeable typ) => HasDocumentApi (Header' m (ct :: Symbol) typ :> b) where
document r a = document @b r $ a <> [( "RequestHeaders"
, toDetails [ ("Name", Detail $ symbolVal' @ct)
, ("ContentType", Detail $ typeText @typ)
]
)]
instance (HasDocumentApi b, KnownSymbol param) => HasDocumentApi (QueryFlag (param :: Symbol) :> b) where
document r a = document @b r $ a <> [( "QueryFlag"
, toDetails [ ("Param", Detail $ symbolVal' @param) ]
)]
instance (HasDocumentApi b, KnownSymbol param, Typeable typ) => HasDocumentApi (QueryParam' m (param :: Symbol) typ :> b) where
document r a = document @b r $ a <> [( "QueryParam"
, toDetails [ ("Param", Detail $ symbolVal' @param)
, ("ContentType", Detail $ typeText @typ)
]
)]
instance (HasDocumentApi b, KnownSymbol param, Typeable typ) => HasDocumentApi (QueryParams (param :: Symbol) typ :> b) where
document r a = document @b r $ a <> [( "QueryParams"
, toDetails [ ("Param", Detail $ symbolVal' @param)
, ("ContentType", Detail $ typeText @typ)
]
)]
instance (HasDocumentApi b, Typeable ct, Typeable typ) => HasDocumentApi (ReqBody' m ct typ :> b) where
document r a = document @b r $ a <> [( "RequestBody"
, toDetails [ ("Format", Detail $ typeText @ct)
, ("ContentType", Detail $ typeText @typ)
]
)]
instance (HasDocumentApi b, Typeable ct, Typeable typ) => HasDocumentApi (StreamBody' m ct typ :> b) where
document r a = document @b r $ a <> [( "StreamBody"
, toDetails [ ("Format", Detail $ typeText @ct)
, ("ContentType", Detail $ typeText @typ)
]
)]
instance (Typeable m, Typeable ct, Typeable typ) => HasDocumentApi (Verb m s ct typ) where
document r a = ( r
, fromList $ a <> [requestType, response]
)
where requestType = ("RequestType", Detail $ typeText @m)
response = ( "Response"
, toDetails [ ("Format", Detail $ typeText @ct)
, ("ContentType", Detail $ typeText @typ)
]
)
toDetails :: [(Text, Details)] -> Details
toDetails = Details . fromList
typeText :: forall a. (Typeable a) => Text
typeText = pack . show . typeRep $ Proxy @a
symbolVal' :: forall n. KnownSymbol n => Text
symbolVal' = pack . symbolVal $ Proxy @n