{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.Docs.Internal where
import Prelude ()
import Prelude.Compat
import Control.Applicative
import Control.Arrow
(second)
import Control.Lens
(makeLenses, mapped, over, traversed, view, (%~), (&), (.~),
(<>~), (^.), (|>))
import qualified Data.ByteString.Char8 as BSC
import Data.ByteString.Lazy.Char8
(ByteString)
import qualified Data.CaseInsensitive as CI
import Data.Foldable
(toList)
import Data.Foldable
(fold)
import Data.Hashable
(Hashable)
import Data.HashMap.Strict
(HashMap)
import Data.List.Compat
(intercalate, intersperse, sort)
import Data.List.NonEmpty
(NonEmpty ((:|)), groupWith)
import qualified Data.List.NonEmpty as NE
import Data.Maybe
import Data.Monoid
(All (..), Any (..), Dual (..), First (..), Last (..),
Product (..), Sum (..))
import Data.Ord
(comparing)
import Data.Proxy
(Proxy (Proxy))
import Data.Semigroup
(Semigroup (..))
import Data.String.Conversions
(cs)
import Data.Text
(Text, unpack)
import GHC.Generics
import GHC.TypeLits
import Servant.API
import Servant.API.ContentTypes
import Servant.API.TypeLevel
import qualified Data.Universe.Helpers as U
import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T
import qualified Network.HTTP.Media as M
import qualified Network.HTTP.Types as HTTP
data Endpoint = Endpoint
{ _path :: [String]
, _method :: HTTP.Method
} deriving (Eq, Ord, Generic)
instance Show Endpoint where
show (Endpoint p m) =
show m ++ " " ++ showPath p
showPath :: [String] -> String
showPath [] = "/"
showPath ps = concatMap ('/' :) ps
defEndpoint :: Endpoint
defEndpoint = Endpoint [] HTTP.methodGet
instance Hashable Endpoint
data API = API
{ _apiIntros :: [DocIntro]
, _apiEndpoints :: HashMap Endpoint Action
} deriving (Eq, Show)
instance Semigroup API where
(<>) = mappend
instance Monoid API where
API a1 b1 `mappend` API a2 b2 = API (a1 `mappend` a2)
(HM.unionWith combineAction b1 b2)
mempty = API mempty mempty
emptyAPI :: API
emptyAPI = mempty
data DocCapture = DocCapture
{ _capSymbol :: String
, _capDesc :: String
} deriving (Eq, Ord, Show)
data DocQueryParam = DocQueryParam
{ _paramName :: String
, _paramValues :: [String]
, _paramDesc :: String
, _paramKind :: ParamKind
} deriving (Eq, Ord, Show)
data DocIntro = DocIntro
{ _introTitle :: String
, _introBody :: [String]
} deriving (Eq, Show)
data DocAuthentication = DocAuthentication
{ _authIntro :: String
, _authDataRequired :: String
} deriving (Eq, Ord, Show)
instance Ord DocIntro where
compare = comparing _introTitle
data DocNote = DocNote
{ _noteTitle :: String
, _noteBody :: [String]
} deriving (Eq, Ord, Show)
newtype ExtraInfo api = ExtraInfo (HashMap Endpoint Action)
instance Semigroup (ExtraInfo a) where
(<>) = mappend
instance Monoid (ExtraInfo a) where
mempty = ExtraInfo mempty
ExtraInfo a `mappend` ExtraInfo b =
ExtraInfo $ HM.unionWith combineAction a b
data DocOptions = DocOptions
{ _maxSamples :: Int
} deriving (Show)
defaultDocOptions :: DocOptions
defaultDocOptions = DocOptions
{ _maxSamples = 5 }
data ParamKind = Normal | List | Flag
deriving (Eq, Ord, Show)
data Response = Response
{ _respStatus :: Int
, _respTypes :: [M.MediaType]
, _respBody :: [(Text, M.MediaType, ByteString)]
, _respHeaders :: [HTTP.Header]
} deriving (Eq, Ord, Show)
combineResponse :: Response -> Response -> Response
Response s ts bs hs `combineResponse` Response _ ts' bs' hs'
= Response s (ts <> ts') (bs <> bs') (hs <> hs')
defResponse :: Response
defResponse = Response
{ _respStatus = 200
, _respTypes = []
, _respBody = []
, _respHeaders = []
}
data Action = Action
{ _authInfo :: [DocAuthentication]
, _captures :: [DocCapture]
, _headers :: [Text]
, _params :: [DocQueryParam]
, _notes :: [DocNote]
, _mxParams :: [(String, [DocQueryParam])]
, _rqtypes :: [M.MediaType]
, _rqbody :: [(Text, M.MediaType, ByteString)]
, _response :: Response
} deriving (Eq, Ord, Show)
combineAction :: Action -> Action -> Action
Action a c h p n m ts body resp `combineAction` Action a' c' h' p' n' m' ts' body' resp' =
Action (a <> a') (c <> c') (h <> h') (p <> p') (n <> n') (m <> m') (ts <> ts') (body <> body') (resp `combineResponse` resp')
defAction :: Action
defAction =
Action []
[]
[]
[]
[]
[]
[]
[]
defResponse
single :: Endpoint -> Action -> API
single e a = API mempty (HM.singleton e a)
data ShowContentTypes = AllContentTypes
| FirstContentType
deriving (Eq, Ord, Show, Read, Bounded, Enum)
data RenderingOptions = RenderingOptions
{ _requestExamples :: !ShowContentTypes
, _responseExamples :: !ShowContentTypes
, _notesHeading :: !(Maybe String)
} deriving (Show)
defRenderingOptions :: RenderingOptions
defRenderingOptions = RenderingOptions
{ _requestExamples = AllContentTypes
, _responseExamples = AllContentTypes
, _notesHeading = Nothing
}
makeLenses ''DocAuthentication
makeLenses ''DocOptions
makeLenses ''API
makeLenses ''Endpoint
makeLenses ''DocCapture
makeLenses ''DocQueryParam
makeLenses ''DocIntro
makeLenses ''DocNote
makeLenses ''Response
makeLenses ''Action
makeLenses ''RenderingOptions
docs :: HasDocs api => Proxy api -> API
docs p = docsWithOptions p defaultDocOptions
docsWithOptions :: HasDocs api => Proxy api -> DocOptions -> API
docsWithOptions p = docsFor p (defEndpoint, defAction)
extraInfo :: (IsIn endpoint api, HasLink endpoint, HasDocs endpoint)
=> Proxy endpoint -> Action -> ExtraInfo api
extraInfo p action =
let api = docsFor p (defEndpoint, defAction) defaultDocOptions
in ExtraInfo $ api ^. apiEndpoints & traversed .~ action
docsWith :: HasDocs api => DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API
docsWith opts intros (ExtraInfo endpoints) p =
docsWithOptions p opts
& apiIntros <>~ intros
& apiEndpoints %~ HM.unionWith (flip combineAction) endpoints
docsWithIntros :: HasDocs api => [DocIntro] -> Proxy api -> API
docsWithIntros intros = docsWith defaultDocOptions intros mempty
class HasDocs api where
docsFor :: Proxy api -> (Endpoint, Action) -> DocOptions -> API
class ToSample a where
toSamples :: Proxy a -> [(Text, a)]
default toSamples :: (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
toSamples = defaultSamples
toSample :: forall a. ToSample a => Proxy a -> Maybe a
toSample _ = snd <$> listToMaybe (toSamples (Proxy :: Proxy a))
noSamples :: [(Text, a)]
noSamples = empty
singleSample :: a -> [(Text, a)]
singleSample x = [("", x)]
samples :: [a] -> [(Text, a)]
samples = map ("",)
defaultSamples :: forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
defaultSamples _ = second to <$> gtoSamples (Proxy :: Proxy (Rep a))
class GToSample t where
gtoSamples :: proxy t -> [(Text, t x)]
instance GToSample U1 where
gtoSamples _ = singleSample U1
instance GToSample V1 where
gtoSamples _ = empty
instance (GToSample p, GToSample q) => GToSample (p :*: q) where
gtoSamples _ = U.cartesianProduct render ps qs
where
ps = gtoSamples (Proxy :: Proxy p)
qs = gtoSamples (Proxy :: Proxy q)
render (ta, a) (tb, b)
| T.null ta || T.null tb = (ta <> tb, a :*: b)
| otherwise = (ta <> ", " <> tb, a :*: b)
instance (GToSample p, GToSample q) => GToSample (p :+: q) where
gtoSamples _ = lefts U.+++ rights
where
lefts = second L1 <$> gtoSamples (Proxy :: Proxy p)
rights = second R1 <$> gtoSamples (Proxy :: Proxy q)
instance ToSample a => GToSample (K1 i a) where
gtoSamples _ = second K1 <$> toSamples (Proxy :: Proxy a)
instance (GToSample f) => GToSample (M1 i a f) where
gtoSamples _ = second M1 <$> gtoSamples (Proxy :: Proxy f)
class AllHeaderSamples ls where
allHeaderToSample :: Proxy ls -> [HTTP.Header]
instance AllHeaderSamples '[] where
allHeaderToSample _ = []
instance (ToHttpApiData l, AllHeaderSamples ls, ToSample l, KnownSymbol h)
=> AllHeaderSamples (Header h l ': ls) where
allHeaderToSample _ = mkHeader (toSample (Proxy :: Proxy l)) :
allHeaderToSample (Proxy :: Proxy ls)
where headerName = CI.mk . cs $ symbolVal (Proxy :: Proxy h)
mkHeader (Just x) = (headerName, cs $ toHeader x)
mkHeader Nothing = (headerName, "<no header sample provided>")
sampleByteString
:: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a)
=> Proxy (ct ': cts)
-> Proxy a
-> [(M.MediaType, ByteString)]
sampleByteString ctypes@Proxy Proxy =
maybe [] (allMimeRender ctypes) $ toSample (Proxy :: Proxy a)
sampleByteStrings
:: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a)
=> Proxy (ct ': cts)
-> Proxy a
-> [(Text, M.MediaType, ByteString)]
sampleByteStrings ctypes@Proxy Proxy =
let samples' = toSamples (Proxy :: Proxy a)
enc (t, s) = uncurry (t,,) <$> allMimeRender ctypes s
in concatMap enc samples'
class ToParam t where
toParam :: Proxy t -> DocQueryParam
class ToCapture c where
toCapture :: Proxy c -> DocCapture
class ToAuthInfo a where
toAuthInfo :: Proxy a -> DocAuthentication
markdown :: API -> String
markdown = markdownWith defRenderingOptions
markdownWith :: RenderingOptions -> API -> String
markdownWith RenderingOptions{..} api = unlines $
introsStr (api ^. apiIntros)
++ (concatMap (uncurry printEndpoint) . sort . HM.toList $ api ^. apiEndpoints)
where printEndpoint :: Endpoint -> Action -> [String]
printEndpoint endpoint action =
str :
"" :
notesStr (action ^. notes) ++
authStr (action ^. authInfo) ++
capturesStr (action ^. captures) ++
headersStr (action ^. headers) ++
paramsStr meth (action ^. params) ++
rqbodyStr (action ^. rqtypes) (action ^. rqbody) ++
responseStr (action ^. response) ++
[]
where str = "## " ++ BSC.unpack meth
++ " " ++ showPath (endpoint^.path)
meth = endpoint ^. method
introsStr :: [DocIntro] -> [String]
introsStr = concatMap introStr
introStr :: DocIntro -> [String]
introStr i =
("## " ++ i ^. introTitle) :
"" :
intersperse "" (i ^. introBody) ++
"" :
[]
notesStr :: [DocNote] -> [String]
notesStr = addHeading
. concatMap noteStr
where
addHeading nts = maybe nts (\hd -> ("### " ++ hd) : "" : nts) _notesHeading
noteStr :: DocNote -> [String]
noteStr nt =
(hdr ++ nt ^. noteTitle) :
"" :
intersperse "" (nt ^. noteBody) ++
"" :
[]
where
hdr | isJust _notesHeading = "#### "
| otherwise = "### "
authStr :: [DocAuthentication] -> [String]
authStr [] = []
authStr auths =
let authIntros = mapped %~ view authIntro $ auths
clientInfos = mapped %~ view authDataRequired $ auths
in "### Authentication":
"":
unlines authIntros :
"":
"Clients must supply the following data" :
unlines clientInfos :
"" :
[]
capturesStr :: [DocCapture] -> [String]
capturesStr [] = []
capturesStr l =
"### Captures:" :
"" :
map captureStr l ++
"" :
[]
captureStr cap =
"- *" ++ (cap ^. capSymbol) ++ "*: " ++ (cap ^. capDesc)
headersStr :: [Text] -> [String]
headersStr [] = []
headersStr l =
"### Headers:" :
"" :
map headerStr l ++
"" :
[]
where headerStr hname = "- This endpoint is sensitive to the value of the **"
++ unpack hname ++ "** HTTP header."
paramsStr :: HTTP.Method -> [DocQueryParam] -> [String]
paramsStr _ [] = []
paramsStr m l =
("### " ++ cs m ++ " Parameters:") :
"" :
map (paramStr m) l ++
"" :
[]
paramStr m param = unlines $
("- " ++ param ^. paramName) :
(if (not (null values) || param ^. paramKind /= Flag)
then [" - **Values**: *" ++ intercalate ", " values ++ "*"]
else []) ++
(" - **Description**: " ++ param ^. paramDesc) :
(if (param ^. paramKind == List)
then [" - This parameter is a **list**. All " ++ cs m ++ " parameters with the name "
++ param ^. paramName ++ "[] will forward their values in a list to the handler."]
else []) ++
(if (param ^. paramKind == Flag)
then [" - This parameter is a **flag**. This means no value is expected to be associated to this parameter."]
else []) ++
[]
where values = param ^. paramValues
rqbodyStr :: [M.MediaType] -> [(Text, M.MediaType, ByteString)]-> [String]
rqbodyStr [] [] = []
rqbodyStr types s =
["### Request:", ""]
<> formatTypes types
<> formatBodies _requestExamples s
formatTypes [] = []
formatTypes ts = ["- Supported content types are:", ""]
<> map (\t -> " - `" <> show t <> "`") ts
<> [""]
formatBodies :: ShowContentTypes -> [(Text, M.MediaType, ByteString)] -> [String]
formatBodies ex bds = concatMap formatBody (select bodyGroups)
where
bodyGroups :: [(Text, NonEmpty M.MediaType, ByteString)]
bodyGroups =
map (\grps -> let (t,_,b) = NE.head grps in (t, fmap (\(_,m,_) -> m) grps, b))
. groupWith (\(t,_,b) -> (t,b))
$ bds
select = case ex of
AllContentTypes -> id
FirstContentType -> map (\(t,ms,b) -> (t, NE.head ms :| [], b))
formatBody :: (Text, NonEmpty M.MediaType, ByteString) -> [String]
formatBody (t, ms, b) =
"- " <> title <> " (" <> mediaList ms <> "):" :
contentStr (NE.head ms) b
where
mediaList = fold . NE.intersperse ", " . fmap (\m -> "`" ++ show m ++ "`")
title
| T.null t = "Example"
| otherwise = cs t
markdownForType mime_type =
case (M.mainType mime_type, M.subType mime_type) of
("text", "html") -> "html"
("application", "xml") -> "xml"
("text", "xml") -> "xml"
("application", "json") -> "javascript"
("application", "javascript") -> "javascript"
("text", "css") -> "css"
(_, _) -> ""
contentStr mime_type body =
"" :
"```" <> markdownForType mime_type :
cs body :
"```" :
"" :
[]
responseStr :: Response -> [String]
responseStr resp =
"### Response:" :
"" :
("- Status code " ++ show (resp ^. respStatus)) :
("- Headers: " ++ show (resp ^. respHeaders)) :
"" :
formatTypes (resp ^. respTypes) ++
bodies
where bodies = case resp ^. respBody of
[] -> ["- No response body\n"]
[("", t, r)] -> "- Response body as below." : contentStr t r
xs ->
formatBodies _responseExamples xs
instance {-# OVERLAPPABLE #-}
(HasDocs a, HasDocs b)
=> HasDocs (a :<|> b) where
docsFor Proxy (ep, action) = docsFor p1 (ep, action) <> docsFor p2 (ep, action)
where p1 :: Proxy a
p1 = Proxy
p2 :: Proxy b
p2 = Proxy
instance HasDocs EmptyAPI where
docsFor Proxy _ _ = emptyAPI
instance (KnownSymbol sym, ToCapture (Capture sym a), HasDocs api)
=> HasDocs (Capture' mods sym a :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint', action')
where subApiP = Proxy :: Proxy api
captureP = Proxy :: Proxy (Capture sym a)
action' = over captures (|> toCapture captureP) action
endpoint' = over path (\p -> p ++ [":" ++ symbolVal symP]) endpoint
symP = Proxy :: Proxy sym
instance (KnownSymbol sym, ToCapture (CaptureAll sym a), HasDocs sublayout)
=> HasDocs (CaptureAll sym a :> sublayout) where
docsFor Proxy (endpoint, action) =
docsFor sublayoutP (endpoint', action')
where sublayoutP = Proxy :: Proxy sublayout
captureP = Proxy :: Proxy (CaptureAll sym a)
action' = over captures (|> toCapture captureP) action
endpoint' = over path (\p -> p ++ [":" ++ symbolVal symP]) endpoint
symP = Proxy :: Proxy sym
instance {-# OVERLAPPABLE #-}
(ToSample a, AllMimeRender (ct ': cts) a, KnownNat status
, ReflectMethod method)
=> HasDocs (Verb method status (ct ': cts) a) where
docsFor Proxy (endpoint, action) DocOptions{..} =
single endpoint' action'
where endpoint' = endpoint & method .~ method'
action' = action & response.respBody .~ take _maxSamples (sampleByteStrings t p)
& response.respTypes .~ allMime t
& response.respStatus .~ status
t = Proxy :: Proxy (ct ': cts)
method' = reflectMethod (Proxy :: Proxy method)
status = fromInteger $ natVal (Proxy :: Proxy status)
p = Proxy :: Proxy a
instance (ReflectMethod method) =>
HasDocs (NoContentVerb method) where
docsFor Proxy (endpoint, action) DocOptions{..} =
single endpoint' action'
where endpoint' = endpoint & method .~ method'
action' = action & response.respStatus .~ 204
& response.respTypes .~ []
& response.respBody .~ []
& response.respHeaders .~ []
method' = reflectMethod (Proxy :: Proxy method)
instance {-# OVERLAPPABLE #-}
(Accept ct, KnownNat status, ReflectMethod method)
=> HasDocs (Stream method status framing ct a) where
docsFor Proxy (endpoint, action) DocOptions{..} =
single endpoint' action'
where endpoint' = endpoint & method .~ method'
action' = action & response.respTypes .~ allMime t
& response.respStatus .~ status
t = Proxy :: Proxy '[ct]
method' = reflectMethod (Proxy :: Proxy method)
status = fromInteger $ natVal (Proxy :: Proxy status)
instance {-# OVERLAPPING #-}
(ToSample a, AllMimeRender (ct ': cts) a, KnownNat status
, ReflectMethod method, AllHeaderSamples ls, GetHeaders (HList ls))
=> HasDocs (Verb method status (ct ': cts) (Headers ls a)) where
docsFor Proxy (endpoint, action) DocOptions{..} =
single endpoint' action'
where endpoint' = endpoint & method .~ method'
action' = action & response.respBody .~ take _maxSamples (sampleByteStrings t p)
& response.respTypes .~ allMime t
& response.respStatus .~ status
& response.respHeaders .~ hdrs
t = Proxy :: Proxy (ct ': cts)
hdrs = allHeaderToSample (Proxy :: Proxy ls)
method' = reflectMethod (Proxy :: Proxy method)
status = fromInteger $ natVal (Proxy :: Proxy status)
p = Proxy :: Proxy a
instance (KnownSymbol sym, HasDocs api)
=> HasDocs (Header' mods sym a :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint, action')
where subApiP = Proxy :: Proxy api
action' = over headers (|> headername) action
headername = T.pack $ symbolVal (Proxy :: Proxy sym)
instance (KnownSymbol sym, ToParam (QueryParam' mods sym a), HasDocs api)
=> HasDocs (QueryParam' mods sym a :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint, action')
where subApiP = Proxy :: Proxy api
paramP = Proxy :: Proxy (QueryParam' mods sym a)
action' = over params (|> toParam paramP) action
instance (KnownSymbol sym, ToParam (QueryParams sym a), HasDocs api)
=> HasDocs (QueryParams sym a :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint, action')
where subApiP = Proxy :: Proxy api
paramP = Proxy :: Proxy (QueryParams sym a)
action' = over params (|> toParam paramP) action
instance (KnownSymbol sym, ToParam (QueryFlag sym), HasDocs api)
=> HasDocs (QueryFlag sym :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint, action')
where subApiP = Proxy :: Proxy api
paramP = Proxy :: Proxy (QueryFlag sym)
action' = over params (|> toParam paramP) action
instance HasDocs Raw where
docsFor _proxy (endpoint, action) _ =
single endpoint action
instance (KnownSymbol desc, HasDocs api)
=> HasDocs (Description desc :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint, action')
where subApiP = Proxy :: Proxy api
action' = over notes (|> note) action
note = DocNote (symbolVal (Proxy :: Proxy desc)) []
instance (KnownSymbol desc, HasDocs api)
=> HasDocs (Summary desc :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint, action')
where subApiP = Proxy :: Proxy api
action' = over notes (|> note) action
note = DocNote (symbolVal (Proxy :: Proxy desc)) []
instance (ToSample a, AllMimeRender (ct ': cts) a, HasDocs api)
=> HasDocs (ReqBody' mods (ct ': cts) a :> api) where
docsFor Proxy (endpoint, action) opts@DocOptions{..} =
docsFor subApiP (endpoint, action') opts
where subApiP = Proxy :: Proxy api
action' :: Action
action' = action & rqbody .~ take _maxSamples (sampleByteStrings t p)
& rqtypes .~ allMime t
t = Proxy :: Proxy (ct ': cts)
p = Proxy :: Proxy a
instance (HasDocs api, Accept ctype) => HasDocs (StreamBody' mods framing ctype a :> api) where
docsFor Proxy (endpoint, action) opts =
docsFor subApiP (endpoint, action') opts
where
subApiP = Proxy :: Proxy api
action' :: Action
action' = action & rqtypes .~ toList (contentTypes t)
t = Proxy :: Proxy ctype
instance (KnownSymbol path, HasDocs api) => HasDocs (path :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint', action)
where subApiP = Proxy :: Proxy api
endpoint' = endpoint & path <>~ [symbolVal pa]
pa = Proxy :: Proxy path
instance HasDocs api => HasDocs (RemoteHost :> api) where
docsFor Proxy ep =
docsFor (Proxy :: Proxy api) ep
instance HasDocs api => HasDocs (IsSecure :> api) where
docsFor Proxy ep =
docsFor (Proxy :: Proxy api) ep
instance HasDocs api => HasDocs (HttpVersion :> api) where
docsFor Proxy ep =
docsFor (Proxy :: Proxy api) ep
instance HasDocs api => HasDocs (Vault :> api) where
docsFor Proxy ep =
docsFor (Proxy :: Proxy api) ep
instance HasDocs api => HasDocs (WithNamedContext name context api) where
docsFor Proxy = docsFor (Proxy :: Proxy api)
instance (ToAuthInfo (BasicAuth realm usr), HasDocs api) => HasDocs (BasicAuth realm usr :> api) where
docsFor Proxy (endpoint, action) =
docsFor (Proxy :: Proxy api) (endpoint, action')
where
authProxy = Proxy :: Proxy (BasicAuth realm usr)
action' = over authInfo (|> toAuthInfo authProxy) action
instance ToSample NoContent
instance ToSample Bool
instance ToSample Ordering
instance (ToSample a, ToSample b) => ToSample (a, b)
instance (ToSample a, ToSample b, ToSample c) => ToSample (a, b, c)
instance (ToSample a, ToSample b, ToSample c, ToSample d) => ToSample (a, b, c, d)
instance (ToSample a, ToSample b, ToSample c, ToSample d, ToSample e) => ToSample (a, b, c, d, e)
instance (ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f) => ToSample (a, b, c, d, e, f)
instance (ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f, ToSample g) => ToSample (a, b, c, d, e, f, g)
instance ToSample a => ToSample (Maybe a)
instance (ToSample a, ToSample b) => ToSample (Either a b)
instance ToSample a => ToSample [a]
instance ToSample a => ToSample (Const a b)
instance ToSample a => ToSample (ZipList a)
instance ToSample All
instance ToSample Any
instance ToSample a => ToSample (Sum a)
instance ToSample a => ToSample (Product a)
instance ToSample a => ToSample (First a)
instance ToSample a => ToSample (Last a)
instance ToSample a => ToSample (Dual a)