{-# 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, each, over, set, to, toListOf, traversed, view,
_1, (%~), (&), (.~), (<>~), (^.), (|>))
import qualified Data.ByteString.Char8 as BSC
import Data.ByteString.Lazy.Char8
(ByteString)
import qualified Data.CaseInsensitive as CI
import Data.Foldable
(fold, toList)
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.String.Conversions
(cs)
import Data.Text
(Text, unpack)
import GHC.Generics
(Generic, Rep, K1(K1), M1(M1), U1(U1), V1,
(:*:)((:*:)), (:+:)(L1, R1))
import qualified GHC.Generics as G
import GHC.TypeLits
import Servant.API
import Servant.API.ContentTypes
import Servant.API.TypeErrors
import Servant.API.TypeLevel
import Servant.API.Generic
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
{ Endpoint -> [String]
_path :: [String]
, Endpoint -> ByteString
_method :: HTTP.Method
} deriving (Endpoint -> Endpoint -> Bool
(Endpoint -> Endpoint -> Bool)
-> (Endpoint -> Endpoint -> Bool) -> Eq Endpoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Endpoint -> Endpoint -> Bool
== :: Endpoint -> Endpoint -> Bool
$c/= :: Endpoint -> Endpoint -> Bool
/= :: Endpoint -> Endpoint -> Bool
Eq, Eq Endpoint
Eq Endpoint =>
(Endpoint -> Endpoint -> Ordering)
-> (Endpoint -> Endpoint -> Bool)
-> (Endpoint -> Endpoint -> Bool)
-> (Endpoint -> Endpoint -> Bool)
-> (Endpoint -> Endpoint -> Bool)
-> (Endpoint -> Endpoint -> Endpoint)
-> (Endpoint -> Endpoint -> Endpoint)
-> Ord Endpoint
Endpoint -> Endpoint -> Bool
Endpoint -> Endpoint -> Ordering
Endpoint -> Endpoint -> Endpoint
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Endpoint -> Endpoint -> Ordering
compare :: Endpoint -> Endpoint -> Ordering
$c< :: Endpoint -> Endpoint -> Bool
< :: Endpoint -> Endpoint -> Bool
$c<= :: Endpoint -> Endpoint -> Bool
<= :: Endpoint -> Endpoint -> Bool
$c> :: Endpoint -> Endpoint -> Bool
> :: Endpoint -> Endpoint -> Bool
$c>= :: Endpoint -> Endpoint -> Bool
>= :: Endpoint -> Endpoint -> Bool
$cmax :: Endpoint -> Endpoint -> Endpoint
max :: Endpoint -> Endpoint -> Endpoint
$cmin :: Endpoint -> Endpoint -> Endpoint
min :: Endpoint -> Endpoint -> Endpoint
Ord, (forall x. Endpoint -> Rep Endpoint x)
-> (forall x. Rep Endpoint x -> Endpoint) -> Generic Endpoint
forall x. Rep Endpoint x -> Endpoint
forall x. Endpoint -> Rep Endpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Endpoint -> Rep Endpoint x
from :: forall x. Endpoint -> Rep Endpoint x
$cto :: forall x. Rep Endpoint x -> Endpoint
to :: forall x. Rep Endpoint x -> Endpoint
Generic)
instance Show Endpoint where
show :: Endpoint -> String
show (Endpoint [String]
p ByteString
m) =
ByteString -> String
forall a. Show a => a -> String
show ByteString
m String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
showPath [String]
p
showPath :: [String] -> String
showPath :: [String] -> String
showPath [] = String
"/"
showPath [String]
ps = ShowS -> [String] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Char
'/' Char -> ShowS
forall a. a -> [a] -> [a]
:) [String]
ps
defEndpoint :: Endpoint
defEndpoint :: Endpoint
defEndpoint = [String] -> ByteString -> Endpoint
Endpoint [] ByteString
HTTP.methodGet
instance Hashable Endpoint
data API = API
{ API -> [DocIntro]
_apiIntros :: [DocIntro]
, API -> HashMap Endpoint Action
_apiEndpoints :: HashMap Endpoint Action
} deriving (API -> API -> Bool
(API -> API -> Bool) -> (API -> API -> Bool) -> Eq API
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: API -> API -> Bool
== :: API -> API -> Bool
$c/= :: API -> API -> Bool
/= :: API -> API -> Bool
Eq, Int -> API -> ShowS
[API] -> ShowS
API -> String
(Int -> API -> ShowS)
-> (API -> String) -> ([API] -> ShowS) -> Show API
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> API -> ShowS
showsPrec :: Int -> API -> ShowS
$cshow :: API -> String
show :: API -> String
$cshowList :: [API] -> ShowS
showList :: [API] -> ShowS
Show)
instance Semigroup API where
<> :: API -> API -> API
(<>) = API -> API -> API
forall a. Monoid a => a -> a -> a
mappend
instance Monoid API where
API [DocIntro]
a1 HashMap Endpoint Action
b1 mappend :: API -> API -> API
`mappend` API [DocIntro]
a2 HashMap Endpoint Action
b2 = [DocIntro] -> HashMap Endpoint Action -> API
API ([DocIntro]
a1 [DocIntro] -> [DocIntro] -> [DocIntro]
forall a. Monoid a => a -> a -> a
`mappend` [DocIntro]
a2)
((Action -> Action -> Action)
-> HashMap Endpoint Action
-> HashMap Endpoint Action
-> HashMap Endpoint Action
forall k v.
Eq k =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
HM.unionWith Action -> Action -> Action
combineAction HashMap Endpoint Action
b1 HashMap Endpoint Action
b2)
mempty :: API
mempty = [DocIntro] -> HashMap Endpoint Action -> API
API [DocIntro]
forall a. Monoid a => a
mempty HashMap Endpoint Action
forall a. Monoid a => a
mempty
emptyAPI :: API
emptyAPI :: API
emptyAPI = API
forall a. Monoid a => a
mempty
data DocCapture = DocCapture
{ DocCapture -> String
_capSymbol :: String
, DocCapture -> String
_capDesc :: String
} deriving (DocCapture -> DocCapture -> Bool
(DocCapture -> DocCapture -> Bool)
-> (DocCapture -> DocCapture -> Bool) -> Eq DocCapture
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocCapture -> DocCapture -> Bool
== :: DocCapture -> DocCapture -> Bool
$c/= :: DocCapture -> DocCapture -> Bool
/= :: DocCapture -> DocCapture -> Bool
Eq, Eq DocCapture
Eq DocCapture =>
(DocCapture -> DocCapture -> Ordering)
-> (DocCapture -> DocCapture -> Bool)
-> (DocCapture -> DocCapture -> Bool)
-> (DocCapture -> DocCapture -> Bool)
-> (DocCapture -> DocCapture -> Bool)
-> (DocCapture -> DocCapture -> DocCapture)
-> (DocCapture -> DocCapture -> DocCapture)
-> Ord DocCapture
DocCapture -> DocCapture -> Bool
DocCapture -> DocCapture -> Ordering
DocCapture -> DocCapture -> DocCapture
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DocCapture -> DocCapture -> Ordering
compare :: DocCapture -> DocCapture -> Ordering
$c< :: DocCapture -> DocCapture -> Bool
< :: DocCapture -> DocCapture -> Bool
$c<= :: DocCapture -> DocCapture -> Bool
<= :: DocCapture -> DocCapture -> Bool
$c> :: DocCapture -> DocCapture -> Bool
> :: DocCapture -> DocCapture -> Bool
$c>= :: DocCapture -> DocCapture -> Bool
>= :: DocCapture -> DocCapture -> Bool
$cmax :: DocCapture -> DocCapture -> DocCapture
max :: DocCapture -> DocCapture -> DocCapture
$cmin :: DocCapture -> DocCapture -> DocCapture
min :: DocCapture -> DocCapture -> DocCapture
Ord, Int -> DocCapture -> ShowS
[DocCapture] -> ShowS
DocCapture -> String
(Int -> DocCapture -> ShowS)
-> (DocCapture -> String)
-> ([DocCapture] -> ShowS)
-> Show DocCapture
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocCapture -> ShowS
showsPrec :: Int -> DocCapture -> ShowS
$cshow :: DocCapture -> String
show :: DocCapture -> String
$cshowList :: [DocCapture] -> ShowS
showList :: [DocCapture] -> ShowS
Show)
data DocQueryParam = DocQueryParam
{ DocQueryParam -> String
_paramName :: String
, DocQueryParam -> [String]
_paramValues :: [String]
, DocQueryParam -> String
_paramDesc :: String
, DocQueryParam -> ParamKind
_paramKind :: ParamKind
} deriving (DocQueryParam -> DocQueryParam -> Bool
(DocQueryParam -> DocQueryParam -> Bool)
-> (DocQueryParam -> DocQueryParam -> Bool) -> Eq DocQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocQueryParam -> DocQueryParam -> Bool
== :: DocQueryParam -> DocQueryParam -> Bool
$c/= :: DocQueryParam -> DocQueryParam -> Bool
/= :: DocQueryParam -> DocQueryParam -> Bool
Eq, Eq DocQueryParam
Eq DocQueryParam =>
(DocQueryParam -> DocQueryParam -> Ordering)
-> (DocQueryParam -> DocQueryParam -> Bool)
-> (DocQueryParam -> DocQueryParam -> Bool)
-> (DocQueryParam -> DocQueryParam -> Bool)
-> (DocQueryParam -> DocQueryParam -> Bool)
-> (DocQueryParam -> DocQueryParam -> DocQueryParam)
-> (DocQueryParam -> DocQueryParam -> DocQueryParam)
-> Ord DocQueryParam
DocQueryParam -> DocQueryParam -> Bool
DocQueryParam -> DocQueryParam -> Ordering
DocQueryParam -> DocQueryParam -> DocQueryParam
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DocQueryParam -> DocQueryParam -> Ordering
compare :: DocQueryParam -> DocQueryParam -> Ordering
$c< :: DocQueryParam -> DocQueryParam -> Bool
< :: DocQueryParam -> DocQueryParam -> Bool
$c<= :: DocQueryParam -> DocQueryParam -> Bool
<= :: DocQueryParam -> DocQueryParam -> Bool
$c> :: DocQueryParam -> DocQueryParam -> Bool
> :: DocQueryParam -> DocQueryParam -> Bool
$c>= :: DocQueryParam -> DocQueryParam -> Bool
>= :: DocQueryParam -> DocQueryParam -> Bool
$cmax :: DocQueryParam -> DocQueryParam -> DocQueryParam
max :: DocQueryParam -> DocQueryParam -> DocQueryParam
$cmin :: DocQueryParam -> DocQueryParam -> DocQueryParam
min :: DocQueryParam -> DocQueryParam -> DocQueryParam
Ord, Int -> DocQueryParam -> ShowS
[DocQueryParam] -> ShowS
DocQueryParam -> String
(Int -> DocQueryParam -> ShowS)
-> (DocQueryParam -> String)
-> ([DocQueryParam] -> ShowS)
-> Show DocQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocQueryParam -> ShowS
showsPrec :: Int -> DocQueryParam -> ShowS
$cshow :: DocQueryParam -> String
show :: DocQueryParam -> String
$cshowList :: [DocQueryParam] -> ShowS
showList :: [DocQueryParam] -> ShowS
Show)
data DocFragment = DocFragment
{ DocFragment -> String
_fragSymbol :: String
, DocFragment -> String
_fragDesc :: String
} deriving (DocFragment -> DocFragment -> Bool
(DocFragment -> DocFragment -> Bool)
-> (DocFragment -> DocFragment -> Bool) -> Eq DocFragment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocFragment -> DocFragment -> Bool
== :: DocFragment -> DocFragment -> Bool
$c/= :: DocFragment -> DocFragment -> Bool
/= :: DocFragment -> DocFragment -> Bool
Eq, Eq DocFragment
Eq DocFragment =>
(DocFragment -> DocFragment -> Ordering)
-> (DocFragment -> DocFragment -> Bool)
-> (DocFragment -> DocFragment -> Bool)
-> (DocFragment -> DocFragment -> Bool)
-> (DocFragment -> DocFragment -> Bool)
-> (DocFragment -> DocFragment -> DocFragment)
-> (DocFragment -> DocFragment -> DocFragment)
-> Ord DocFragment
DocFragment -> DocFragment -> Bool
DocFragment -> DocFragment -> Ordering
DocFragment -> DocFragment -> DocFragment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DocFragment -> DocFragment -> Ordering
compare :: DocFragment -> DocFragment -> Ordering
$c< :: DocFragment -> DocFragment -> Bool
< :: DocFragment -> DocFragment -> Bool
$c<= :: DocFragment -> DocFragment -> Bool
<= :: DocFragment -> DocFragment -> Bool
$c> :: DocFragment -> DocFragment -> Bool
> :: DocFragment -> DocFragment -> Bool
$c>= :: DocFragment -> DocFragment -> Bool
>= :: DocFragment -> DocFragment -> Bool
$cmax :: DocFragment -> DocFragment -> DocFragment
max :: DocFragment -> DocFragment -> DocFragment
$cmin :: DocFragment -> DocFragment -> DocFragment
min :: DocFragment -> DocFragment -> DocFragment
Ord, Int -> DocFragment -> ShowS
[DocFragment] -> ShowS
DocFragment -> String
(Int -> DocFragment -> ShowS)
-> (DocFragment -> String)
-> ([DocFragment] -> ShowS)
-> Show DocFragment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocFragment -> ShowS
showsPrec :: Int -> DocFragment -> ShowS
$cshow :: DocFragment -> String
show :: DocFragment -> String
$cshowList :: [DocFragment] -> ShowS
showList :: [DocFragment] -> ShowS
Show)
combineFragment :: Maybe DocFragment -> Maybe DocFragment -> Maybe DocFragment
Maybe DocFragment
Nothing combineFragment :: Maybe DocFragment -> Maybe DocFragment -> Maybe DocFragment
`combineFragment` Maybe DocFragment
mdocFragment = Maybe DocFragment
mdocFragment
Just DocFragment
docFragment `combineFragment` Maybe DocFragment
_ = DocFragment -> Maybe DocFragment
forall a. a -> Maybe a
Just DocFragment
docFragment
data DocIntro = DocIntro
{ DocIntro -> String
_introTitle :: String
, DocIntro -> [String]
_introBody :: [String]
} deriving (DocIntro -> DocIntro -> Bool
(DocIntro -> DocIntro -> Bool)
-> (DocIntro -> DocIntro -> Bool) -> Eq DocIntro
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocIntro -> DocIntro -> Bool
== :: DocIntro -> DocIntro -> Bool
$c/= :: DocIntro -> DocIntro -> Bool
/= :: DocIntro -> DocIntro -> Bool
Eq, Int -> DocIntro -> ShowS
[DocIntro] -> ShowS
DocIntro -> String
(Int -> DocIntro -> ShowS)
-> (DocIntro -> String) -> ([DocIntro] -> ShowS) -> Show DocIntro
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocIntro -> ShowS
showsPrec :: Int -> DocIntro -> ShowS
$cshow :: DocIntro -> String
show :: DocIntro -> String
$cshowList :: [DocIntro] -> ShowS
showList :: [DocIntro] -> ShowS
Show)
data DocAuthentication = DocAuthentication
{ DocAuthentication -> String
_authIntro :: String
, DocAuthentication -> String
_authDataRequired :: String
} deriving (DocAuthentication -> DocAuthentication -> Bool
(DocAuthentication -> DocAuthentication -> Bool)
-> (DocAuthentication -> DocAuthentication -> Bool)
-> Eq DocAuthentication
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocAuthentication -> DocAuthentication -> Bool
== :: DocAuthentication -> DocAuthentication -> Bool
$c/= :: DocAuthentication -> DocAuthentication -> Bool
/= :: DocAuthentication -> DocAuthentication -> Bool
Eq, Eq DocAuthentication
Eq DocAuthentication =>
(DocAuthentication -> DocAuthentication -> Ordering)
-> (DocAuthentication -> DocAuthentication -> Bool)
-> (DocAuthentication -> DocAuthentication -> Bool)
-> (DocAuthentication -> DocAuthentication -> Bool)
-> (DocAuthentication -> DocAuthentication -> Bool)
-> (DocAuthentication -> DocAuthentication -> DocAuthentication)
-> (DocAuthentication -> DocAuthentication -> DocAuthentication)
-> Ord DocAuthentication
DocAuthentication -> DocAuthentication -> Bool
DocAuthentication -> DocAuthentication -> Ordering
DocAuthentication -> DocAuthentication -> DocAuthentication
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DocAuthentication -> DocAuthentication -> Ordering
compare :: DocAuthentication -> DocAuthentication -> Ordering
$c< :: DocAuthentication -> DocAuthentication -> Bool
< :: DocAuthentication -> DocAuthentication -> Bool
$c<= :: DocAuthentication -> DocAuthentication -> Bool
<= :: DocAuthentication -> DocAuthentication -> Bool
$c> :: DocAuthentication -> DocAuthentication -> Bool
> :: DocAuthentication -> DocAuthentication -> Bool
$c>= :: DocAuthentication -> DocAuthentication -> Bool
>= :: DocAuthentication -> DocAuthentication -> Bool
$cmax :: DocAuthentication -> DocAuthentication -> DocAuthentication
max :: DocAuthentication -> DocAuthentication -> DocAuthentication
$cmin :: DocAuthentication -> DocAuthentication -> DocAuthentication
min :: DocAuthentication -> DocAuthentication -> DocAuthentication
Ord, Int -> DocAuthentication -> ShowS
[DocAuthentication] -> ShowS
DocAuthentication -> String
(Int -> DocAuthentication -> ShowS)
-> (DocAuthentication -> String)
-> ([DocAuthentication] -> ShowS)
-> Show DocAuthentication
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocAuthentication -> ShowS
showsPrec :: Int -> DocAuthentication -> ShowS
$cshow :: DocAuthentication -> String
show :: DocAuthentication -> String
$cshowList :: [DocAuthentication] -> ShowS
showList :: [DocAuthentication] -> ShowS
Show)
instance Ord DocIntro where
compare :: DocIntro -> DocIntro -> Ordering
compare = (DocIntro -> String) -> DocIntro -> DocIntro -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing DocIntro -> String
_introTitle
data DocNote = DocNote
{ DocNote -> String
_noteTitle :: String
, DocNote -> [String]
_noteBody :: [String]
} deriving (DocNote -> DocNote -> Bool
(DocNote -> DocNote -> Bool)
-> (DocNote -> DocNote -> Bool) -> Eq DocNote
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DocNote -> DocNote -> Bool
== :: DocNote -> DocNote -> Bool
$c/= :: DocNote -> DocNote -> Bool
/= :: DocNote -> DocNote -> Bool
Eq, Eq DocNote
Eq DocNote =>
(DocNote -> DocNote -> Ordering)
-> (DocNote -> DocNote -> Bool)
-> (DocNote -> DocNote -> Bool)
-> (DocNote -> DocNote -> Bool)
-> (DocNote -> DocNote -> Bool)
-> (DocNote -> DocNote -> DocNote)
-> (DocNote -> DocNote -> DocNote)
-> Ord DocNote
DocNote -> DocNote -> Bool
DocNote -> DocNote -> Ordering
DocNote -> DocNote -> DocNote
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DocNote -> DocNote -> Ordering
compare :: DocNote -> DocNote -> Ordering
$c< :: DocNote -> DocNote -> Bool
< :: DocNote -> DocNote -> Bool
$c<= :: DocNote -> DocNote -> Bool
<= :: DocNote -> DocNote -> Bool
$c> :: DocNote -> DocNote -> Bool
> :: DocNote -> DocNote -> Bool
$c>= :: DocNote -> DocNote -> Bool
>= :: DocNote -> DocNote -> Bool
$cmax :: DocNote -> DocNote -> DocNote
max :: DocNote -> DocNote -> DocNote
$cmin :: DocNote -> DocNote -> DocNote
min :: DocNote -> DocNote -> DocNote
Ord, Int -> DocNote -> ShowS
[DocNote] -> ShowS
DocNote -> String
(Int -> DocNote -> ShowS)
-> (DocNote -> String) -> ([DocNote] -> ShowS) -> Show DocNote
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocNote -> ShowS
showsPrec :: Int -> DocNote -> ShowS
$cshow :: DocNote -> String
show :: DocNote -> String
$cshowList :: [DocNote] -> ShowS
showList :: [DocNote] -> ShowS
Show)
newtype api = (HashMap Endpoint Action)
instance Semigroup (ExtraInfo a) where
<> :: ExtraInfo a -> ExtraInfo a -> ExtraInfo a
(<>) = ExtraInfo a -> ExtraInfo a -> ExtraInfo a
forall a. Monoid a => a -> a -> a
mappend
instance Monoid (ExtraInfo a) where
mempty :: ExtraInfo a
mempty = HashMap Endpoint Action -> ExtraInfo a
forall {k} (api :: k). HashMap Endpoint Action -> ExtraInfo api
ExtraInfo HashMap Endpoint Action
forall a. Monoid a => a
mempty
ExtraInfo HashMap Endpoint Action
a mappend :: ExtraInfo a -> ExtraInfo a -> ExtraInfo a
`mappend` ExtraInfo HashMap Endpoint Action
b =
HashMap Endpoint Action -> ExtraInfo a
forall {k} (api :: k). HashMap Endpoint Action -> ExtraInfo api
ExtraInfo (HashMap Endpoint Action -> ExtraInfo a)
-> HashMap Endpoint Action -> ExtraInfo a
forall a b. (a -> b) -> a -> b
$ (Action -> Action -> Action)
-> HashMap Endpoint Action
-> HashMap Endpoint Action
-> HashMap Endpoint Action
forall k v.
Eq k =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
HM.unionWith Action -> Action -> Action
combineAction HashMap Endpoint Action
a HashMap Endpoint Action
b
data DocOptions = DocOptions
{ DocOptions -> Int
_maxSamples :: Int
} deriving (Int -> DocOptions -> ShowS
[DocOptions] -> ShowS
DocOptions -> String
(Int -> DocOptions -> ShowS)
-> (DocOptions -> String)
-> ([DocOptions] -> ShowS)
-> Show DocOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DocOptions -> ShowS
showsPrec :: Int -> DocOptions -> ShowS
$cshow :: DocOptions -> String
show :: DocOptions -> String
$cshowList :: [DocOptions] -> ShowS
showList :: [DocOptions] -> ShowS
Show)
defaultDocOptions :: DocOptions
defaultDocOptions :: DocOptions
defaultDocOptions = DocOptions
{ _maxSamples :: Int
_maxSamples = Int
5 }
data ParamKind = Normal | List | Flag
deriving (ParamKind -> ParamKind -> Bool
(ParamKind -> ParamKind -> Bool)
-> (ParamKind -> ParamKind -> Bool) -> Eq ParamKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParamKind -> ParamKind -> Bool
== :: ParamKind -> ParamKind -> Bool
$c/= :: ParamKind -> ParamKind -> Bool
/= :: ParamKind -> ParamKind -> Bool
Eq, Eq ParamKind
Eq ParamKind =>
(ParamKind -> ParamKind -> Ordering)
-> (ParamKind -> ParamKind -> Bool)
-> (ParamKind -> ParamKind -> Bool)
-> (ParamKind -> ParamKind -> Bool)
-> (ParamKind -> ParamKind -> Bool)
-> (ParamKind -> ParamKind -> ParamKind)
-> (ParamKind -> ParamKind -> ParamKind)
-> Ord ParamKind
ParamKind -> ParamKind -> Bool
ParamKind -> ParamKind -> Ordering
ParamKind -> ParamKind -> ParamKind
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ParamKind -> ParamKind -> Ordering
compare :: ParamKind -> ParamKind -> Ordering
$c< :: ParamKind -> ParamKind -> Bool
< :: ParamKind -> ParamKind -> Bool
$c<= :: ParamKind -> ParamKind -> Bool
<= :: ParamKind -> ParamKind -> Bool
$c> :: ParamKind -> ParamKind -> Bool
> :: ParamKind -> ParamKind -> Bool
$c>= :: ParamKind -> ParamKind -> Bool
>= :: ParamKind -> ParamKind -> Bool
$cmax :: ParamKind -> ParamKind -> ParamKind
max :: ParamKind -> ParamKind -> ParamKind
$cmin :: ParamKind -> ParamKind -> ParamKind
min :: ParamKind -> ParamKind -> ParamKind
Ord, Int -> ParamKind -> ShowS
[ParamKind] -> ShowS
ParamKind -> String
(Int -> ParamKind -> ShowS)
-> (ParamKind -> String)
-> ([ParamKind] -> ShowS)
-> Show ParamKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParamKind -> ShowS
showsPrec :: Int -> ParamKind -> ShowS
$cshow :: ParamKind -> String
show :: ParamKind -> String
$cshowList :: [ParamKind] -> ShowS
showList :: [ParamKind] -> ShowS
Show)
data Response = Response
{ Response -> Int
_respStatus :: Int
, Response -> [MediaType]
_respTypes :: [M.MediaType]
, Response -> [(Text, MediaType, ByteString)]
_respBody :: [(Text, M.MediaType, ByteString)]
, :: [HTTP.Header]
} deriving (Response -> Response -> Bool
(Response -> Response -> Bool)
-> (Response -> Response -> Bool) -> Eq Response
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Response -> Response -> Bool
== :: Response -> Response -> Bool
$c/= :: Response -> Response -> Bool
/= :: Response -> Response -> Bool
Eq, Eq Response
Eq Response =>
(Response -> Response -> Ordering)
-> (Response -> Response -> Bool)
-> (Response -> Response -> Bool)
-> (Response -> Response -> Bool)
-> (Response -> Response -> Bool)
-> (Response -> Response -> Response)
-> (Response -> Response -> Response)
-> Ord Response
Response -> Response -> Bool
Response -> Response -> Ordering
Response -> Response -> Response
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Response -> Response -> Ordering
compare :: Response -> Response -> Ordering
$c< :: Response -> Response -> Bool
< :: Response -> Response -> Bool
$c<= :: Response -> Response -> Bool
<= :: Response -> Response -> Bool
$c> :: Response -> Response -> Bool
> :: Response -> Response -> Bool
$c>= :: Response -> Response -> Bool
>= :: Response -> Response -> Bool
$cmax :: Response -> Response -> Response
max :: Response -> Response -> Response
$cmin :: Response -> Response -> Response
min :: Response -> Response -> Response
Ord, Int -> Response -> ShowS
[Response] -> ShowS
Response -> String
(Int -> Response -> ShowS)
-> (Response -> String) -> ([Response] -> ShowS) -> Show Response
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Response -> ShowS
showsPrec :: Int -> Response -> ShowS
$cshow :: Response -> String
show :: Response -> String
$cshowList :: [Response] -> ShowS
showList :: [Response] -> ShowS
Show)
combineResponse :: Response -> Response -> Response
Response Int
s [MediaType]
ts [(Text, MediaType, ByteString)]
bs [Header]
hs combineResponse :: Response -> Response -> Response
`combineResponse` Response Int
_ [MediaType]
ts' [(Text, MediaType, ByteString)]
bs' [Header]
hs'
= Int
-> [MediaType]
-> [(Text, MediaType, ByteString)]
-> [Header]
-> Response
Response Int
s ([MediaType]
ts [MediaType] -> [MediaType] -> [MediaType]
forall a. Semigroup a => a -> a -> a
<> [MediaType]
ts') ([(Text, MediaType, ByteString)]
bs [(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall a. Semigroup a => a -> a -> a
<> [(Text, MediaType, ByteString)]
bs') ([Header]
hs [Header] -> [Header] -> [Header]
forall a. Semigroup a => a -> a -> a
<> [Header]
hs')
defResponse :: Response
defResponse :: Response
defResponse = Response
{ _respStatus :: Int
_respStatus = Int
200
, _respTypes :: [MediaType]
_respTypes = []
, _respBody :: [(Text, MediaType, ByteString)]
_respBody = []
, _respHeaders :: [Header]
_respHeaders = []
}
data Action = Action
{ Action -> [DocAuthentication]
_authInfo :: [DocAuthentication]
, Action -> [DocCapture]
_captures :: [DocCapture]
, :: [HTTP.Header]
, Action -> [DocQueryParam]
_params :: [DocQueryParam]
, Action -> Maybe DocFragment
_fragment :: Maybe DocFragment
, Action -> [DocNote]
_notes :: [DocNote]
, Action -> [(String, [DocQueryParam])]
_mxParams :: [(String, [DocQueryParam])]
, Action -> [MediaType]
_rqtypes :: [M.MediaType]
, Action -> [(Text, MediaType, ByteString)]
_rqbody :: [(Text, M.MediaType, ByteString)]
, Action -> Response
_response :: Response
} deriving (Action -> Action -> Bool
(Action -> Action -> Bool)
-> (Action -> Action -> Bool) -> Eq Action
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Action -> Action -> Bool
== :: Action -> Action -> Bool
$c/= :: Action -> Action -> Bool
/= :: Action -> Action -> Bool
Eq, Eq Action
Eq Action =>
(Action -> Action -> Ordering)
-> (Action -> Action -> Bool)
-> (Action -> Action -> Bool)
-> (Action -> Action -> Bool)
-> (Action -> Action -> Bool)
-> (Action -> Action -> Action)
-> (Action -> Action -> Action)
-> Ord Action
Action -> Action -> Bool
Action -> Action -> Ordering
Action -> Action -> Action
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Action -> Action -> Ordering
compare :: Action -> Action -> Ordering
$c< :: Action -> Action -> Bool
< :: Action -> Action -> Bool
$c<= :: Action -> Action -> Bool
<= :: Action -> Action -> Bool
$c> :: Action -> Action -> Bool
> :: Action -> Action -> Bool
$c>= :: Action -> Action -> Bool
>= :: Action -> Action -> Bool
$cmax :: Action -> Action -> Action
max :: Action -> Action -> Action
$cmin :: Action -> Action -> Action
min :: Action -> Action -> Action
Ord, Int -> Action -> ShowS
[Action] -> ShowS
Action -> String
(Int -> Action -> ShowS)
-> (Action -> String) -> ([Action] -> ShowS) -> Show Action
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Action -> ShowS
showsPrec :: Int -> Action -> ShowS
$cshow :: Action -> String
show :: Action -> String
$cshowList :: [Action] -> ShowS
showList :: [Action] -> ShowS
Show)
combineAction :: Action -> Action -> Action
Action [DocAuthentication]
a [DocCapture]
c [Header]
h [DocQueryParam]
p Maybe DocFragment
f [DocNote]
n [(String, [DocQueryParam])]
m [MediaType]
ts [(Text, MediaType, ByteString)]
body Response
resp
combineAction :: Action -> Action -> Action
`combineAction` Action [DocAuthentication]
a' [DocCapture]
c' [Header]
h' [DocQueryParam]
p' Maybe DocFragment
f' [DocNote]
n' [(String, [DocQueryParam])]
m' [MediaType]
ts' [(Text, MediaType, ByteString)]
body' Response
resp' =
[DocAuthentication]
-> [DocCapture]
-> [Header]
-> [DocQueryParam]
-> Maybe DocFragment
-> [DocNote]
-> [(String, [DocQueryParam])]
-> [MediaType]
-> [(Text, MediaType, ByteString)]
-> Response
-> Action
Action ([DocAuthentication]
a [DocAuthentication] -> [DocAuthentication] -> [DocAuthentication]
forall a. Semigroup a => a -> a -> a
<> [DocAuthentication]
a') ([DocCapture]
c [DocCapture] -> [DocCapture] -> [DocCapture]
forall a. Semigroup a => a -> a -> a
<> [DocCapture]
c') ([Header]
h [Header] -> [Header] -> [Header]
forall a. Semigroup a => a -> a -> a
<> [Header]
h') ([DocQueryParam]
p [DocQueryParam] -> [DocQueryParam] -> [DocQueryParam]
forall a. Semigroup a => a -> a -> a
<> [DocQueryParam]
p') (Maybe DocFragment
f Maybe DocFragment -> Maybe DocFragment -> Maybe DocFragment
`combineFragment` Maybe DocFragment
f') ([DocNote]
n [DocNote] -> [DocNote] -> [DocNote]
forall a. Semigroup a => a -> a -> a
<> [DocNote]
n') ([(String, [DocQueryParam])]
m [(String, [DocQueryParam])]
-> [(String, [DocQueryParam])] -> [(String, [DocQueryParam])]
forall a. Semigroup a => a -> a -> a
<> [(String, [DocQueryParam])]
m') ([MediaType]
ts [MediaType] -> [MediaType] -> [MediaType]
forall a. Semigroup a => a -> a -> a
<> [MediaType]
ts') ([(Text, MediaType, ByteString)]
body [(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall a. Semigroup a => a -> a -> a
<> [(Text, MediaType, ByteString)]
body') (Response
resp Response -> Response -> Response
`combineResponse` Response
resp')
defAction :: Action
defAction :: Action
defAction =
[DocAuthentication]
-> [DocCapture]
-> [Header]
-> [DocQueryParam]
-> Maybe DocFragment
-> [DocNote]
-> [(String, [DocQueryParam])]
-> [MediaType]
-> [(Text, MediaType, ByteString)]
-> Response
-> Action
Action []
[]
[]
[]
Maybe DocFragment
forall a. Maybe a
Nothing
[]
[]
[]
[]
Response
defResponse
single :: Endpoint -> Action -> API
single :: Endpoint -> Action -> API
single Endpoint
e Action
a = [DocIntro] -> HashMap Endpoint Action -> API
API [DocIntro]
forall a. Monoid a => a
mempty (Endpoint -> Action -> HashMap Endpoint Action
forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton Endpoint
e Action
a)
data ShowContentTypes = AllContentTypes
| FirstContentType
deriving (ShowContentTypes -> ShowContentTypes -> Bool
(ShowContentTypes -> ShowContentTypes -> Bool)
-> (ShowContentTypes -> ShowContentTypes -> Bool)
-> Eq ShowContentTypes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShowContentTypes -> ShowContentTypes -> Bool
== :: ShowContentTypes -> ShowContentTypes -> Bool
$c/= :: ShowContentTypes -> ShowContentTypes -> Bool
/= :: ShowContentTypes -> ShowContentTypes -> Bool
Eq, Eq ShowContentTypes
Eq ShowContentTypes =>
(ShowContentTypes -> ShowContentTypes -> Ordering)
-> (ShowContentTypes -> ShowContentTypes -> Bool)
-> (ShowContentTypes -> ShowContentTypes -> Bool)
-> (ShowContentTypes -> ShowContentTypes -> Bool)
-> (ShowContentTypes -> ShowContentTypes -> Bool)
-> (ShowContentTypes -> ShowContentTypes -> ShowContentTypes)
-> (ShowContentTypes -> ShowContentTypes -> ShowContentTypes)
-> Ord ShowContentTypes
ShowContentTypes -> ShowContentTypes -> Bool
ShowContentTypes -> ShowContentTypes -> Ordering
ShowContentTypes -> ShowContentTypes -> ShowContentTypes
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ShowContentTypes -> ShowContentTypes -> Ordering
compare :: ShowContentTypes -> ShowContentTypes -> Ordering
$c< :: ShowContentTypes -> ShowContentTypes -> Bool
< :: ShowContentTypes -> ShowContentTypes -> Bool
$c<= :: ShowContentTypes -> ShowContentTypes -> Bool
<= :: ShowContentTypes -> ShowContentTypes -> Bool
$c> :: ShowContentTypes -> ShowContentTypes -> Bool
> :: ShowContentTypes -> ShowContentTypes -> Bool
$c>= :: ShowContentTypes -> ShowContentTypes -> Bool
>= :: ShowContentTypes -> ShowContentTypes -> Bool
$cmax :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
max :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
$cmin :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
min :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
Ord, Int -> ShowContentTypes -> ShowS
[ShowContentTypes] -> ShowS
ShowContentTypes -> String
(Int -> ShowContentTypes -> ShowS)
-> (ShowContentTypes -> String)
-> ([ShowContentTypes] -> ShowS)
-> Show ShowContentTypes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ShowContentTypes -> ShowS
showsPrec :: Int -> ShowContentTypes -> ShowS
$cshow :: ShowContentTypes -> String
show :: ShowContentTypes -> String
$cshowList :: [ShowContentTypes] -> ShowS
showList :: [ShowContentTypes] -> ShowS
Show, ReadPrec [ShowContentTypes]
ReadPrec ShowContentTypes
Int -> ReadS ShowContentTypes
ReadS [ShowContentTypes]
(Int -> ReadS ShowContentTypes)
-> ReadS [ShowContentTypes]
-> ReadPrec ShowContentTypes
-> ReadPrec [ShowContentTypes]
-> Read ShowContentTypes
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ShowContentTypes
readsPrec :: Int -> ReadS ShowContentTypes
$creadList :: ReadS [ShowContentTypes]
readList :: ReadS [ShowContentTypes]
$creadPrec :: ReadPrec ShowContentTypes
readPrec :: ReadPrec ShowContentTypes
$creadListPrec :: ReadPrec [ShowContentTypes]
readListPrec :: ReadPrec [ShowContentTypes]
Read, ShowContentTypes
ShowContentTypes -> ShowContentTypes -> Bounded ShowContentTypes
forall a. a -> a -> Bounded a
$cminBound :: ShowContentTypes
minBound :: ShowContentTypes
$cmaxBound :: ShowContentTypes
maxBound :: ShowContentTypes
Bounded, Int -> ShowContentTypes
ShowContentTypes -> Int
ShowContentTypes -> [ShowContentTypes]
ShowContentTypes -> ShowContentTypes
ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
ShowContentTypes
-> ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
(ShowContentTypes -> ShowContentTypes)
-> (ShowContentTypes -> ShowContentTypes)
-> (Int -> ShowContentTypes)
-> (ShowContentTypes -> Int)
-> (ShowContentTypes -> [ShowContentTypes])
-> (ShowContentTypes -> ShowContentTypes -> [ShowContentTypes])
-> (ShowContentTypes -> ShowContentTypes -> [ShowContentTypes])
-> (ShowContentTypes
-> ShowContentTypes -> ShowContentTypes -> [ShowContentTypes])
-> Enum ShowContentTypes
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ShowContentTypes -> ShowContentTypes
succ :: ShowContentTypes -> ShowContentTypes
$cpred :: ShowContentTypes -> ShowContentTypes
pred :: ShowContentTypes -> ShowContentTypes
$ctoEnum :: Int -> ShowContentTypes
toEnum :: Int -> ShowContentTypes
$cfromEnum :: ShowContentTypes -> Int
fromEnum :: ShowContentTypes -> Int
$cenumFrom :: ShowContentTypes -> [ShowContentTypes]
enumFrom :: ShowContentTypes -> [ShowContentTypes]
$cenumFromThen :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
enumFromThen :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
$cenumFromTo :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
enumFromTo :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
$cenumFromThenTo :: ShowContentTypes
-> ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
enumFromThenTo :: ShowContentTypes
-> ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
Enum)
data RenderingOptions = RenderingOptions
{ RenderingOptions -> ShowContentTypes
_requestExamples :: !ShowContentTypes
, RenderingOptions -> ShowContentTypes
_responseExamples :: !ShowContentTypes
, RenderingOptions -> Maybe String
_notesHeading :: !(Maybe String)
, RenderingOptions -> Maybe String
_renderCurlBasePath :: !(Maybe String)
} deriving (Int -> RenderingOptions -> ShowS
[RenderingOptions] -> ShowS
RenderingOptions -> String
(Int -> RenderingOptions -> ShowS)
-> (RenderingOptions -> String)
-> ([RenderingOptions] -> ShowS)
-> Show RenderingOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RenderingOptions -> ShowS
showsPrec :: Int -> RenderingOptions -> ShowS
$cshow :: RenderingOptions -> String
show :: RenderingOptions -> String
$cshowList :: [RenderingOptions] -> ShowS
showList :: [RenderingOptions] -> ShowS
Show)
defRenderingOptions :: RenderingOptions
defRenderingOptions :: RenderingOptions
defRenderingOptions = RenderingOptions
{ _requestExamples :: ShowContentTypes
_requestExamples = ShowContentTypes
AllContentTypes
, _responseExamples :: ShowContentTypes
_responseExamples = ShowContentTypes
AllContentTypes
, _notesHeading :: Maybe String
_notesHeading = Maybe String
forall a. Maybe a
Nothing
, _renderCurlBasePath :: Maybe String
_renderCurlBasePath = Maybe String
forall a. Maybe a
Nothing
}
makeLenses ''DocAuthentication
makeLenses ''DocOptions
makeLenses ''API
makeLenses ''Endpoint
makeLenses ''DocCapture
makeLenses ''DocQueryParam
makeLenses ''DocFragment
makeLenses ''DocIntro
makeLenses ''DocNote
makeLenses ''RenderingOptions
docs :: HasDocs api => Proxy api -> API
docs :: forall {k} (api :: k). HasDocs api => Proxy api -> API
docs Proxy api
p = Proxy api -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> DocOptions -> API
docsWithOptions Proxy api
p DocOptions
defaultDocOptions
docsWithOptions :: HasDocs api => Proxy api -> DocOptions -> API
docsWithOptions :: forall {k} (api :: k).
HasDocs api =>
Proxy api -> DocOptions -> API
docsWithOptions Proxy api
p = Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
p (Endpoint
defEndpoint, Action
defAction)
extraInfo :: (IsIn endpoint api, HasLink endpoint, HasDocs endpoint)
=> Proxy endpoint -> Action -> ExtraInfo api
Proxy endpoint
p Action
action =
let api :: API
api = Proxy endpoint -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy endpoint
p (Endpoint
defEndpoint, Action
defAction) DocOptions
defaultDocOptions
in HashMap Endpoint Action -> ExtraInfo api
forall {k} (api :: k). HashMap Endpoint Action -> ExtraInfo api
ExtraInfo (HashMap Endpoint Action -> ExtraInfo api)
-> HashMap Endpoint Action -> ExtraInfo api
forall a b. (a -> b) -> a -> b
$ API
api API
-> Getting (HashMap Endpoint Action) API (HashMap Endpoint Action)
-> HashMap Endpoint Action
forall s a. s -> Getting a s a -> a
^. Getting (HashMap Endpoint Action) API (HashMap Endpoint Action)
Lens' API (HashMap Endpoint Action)
apiEndpoints HashMap Endpoint Action
-> (HashMap Endpoint Action -> HashMap Endpoint Action)
-> HashMap Endpoint Action
forall a b. a -> (a -> b) -> b
& (Action -> Identity Action)
-> HashMap Endpoint Action -> Identity (HashMap Endpoint Action)
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
IndexedTraversal
Int
(HashMap Endpoint Action)
(HashMap Endpoint Action)
Action
Action
traversed ((Action -> Identity Action)
-> HashMap Endpoint Action -> Identity (HashMap Endpoint Action))
-> Action -> HashMap Endpoint Action -> HashMap Endpoint Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Action
action
docsWith :: HasDocs api => DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API
docsWith :: forall {k} (api :: k).
HasDocs api =>
DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API
docsWith DocOptions
opts [DocIntro]
intros (ExtraInfo HashMap Endpoint Action
endpoints) Proxy api
p =
Proxy api -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> DocOptions -> API
docsWithOptions Proxy api
p DocOptions
opts
API -> (API -> API) -> API
forall a b. a -> (a -> b) -> b
& ([DocIntro] -> Identity [DocIntro]) -> API -> Identity API
Lens' API [DocIntro]
apiIntros (([DocIntro] -> Identity [DocIntro]) -> API -> Identity API)
-> [DocIntro] -> API -> API
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [DocIntro]
intros
API -> (API -> API) -> API
forall a b. a -> (a -> b) -> b
& (HashMap Endpoint Action -> Identity (HashMap Endpoint Action))
-> API -> Identity API
Lens' API (HashMap Endpoint Action)
apiEndpoints ((HashMap Endpoint Action -> Identity (HashMap Endpoint Action))
-> API -> Identity API)
-> (HashMap Endpoint Action -> HashMap Endpoint Action)
-> API
-> API
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Action -> Action -> Action)
-> HashMap Endpoint Action
-> HashMap Endpoint Action
-> HashMap Endpoint Action
forall k v.
Eq k =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
HM.unionWith ((Action -> Action -> Action) -> Action -> Action -> Action
forall a b c. (a -> b -> c) -> b -> a -> c
flip Action -> Action -> Action
combineAction) HashMap Endpoint Action
endpoints
docsWithIntros :: HasDocs api => [DocIntro] -> Proxy api -> API
docsWithIntros :: forall {k} (api :: k).
HasDocs api =>
[DocIntro] -> Proxy api -> API
docsWithIntros [DocIntro]
intros = DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API
forall {k} (api :: k).
HasDocs api =>
DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API
docsWith DocOptions
defaultDocOptions [DocIntro]
intros ExtraInfo api
forall a. Monoid a => a
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 = Proxy a -> [(Text, a)]
forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
defaultSamples
toSample :: forall a. ToSample a => Proxy a -> Maybe a
toSample :: forall a. ToSample a => Proxy a -> Maybe a
toSample Proxy a
_ = (Text, a) -> a
forall a b. (a, b) -> b
snd ((Text, a) -> a) -> Maybe (Text, a) -> Maybe a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, a)] -> Maybe (Text, a)
forall a. [a] -> Maybe a
listToMaybe (Proxy a -> [(Text, a)]
forall a. ToSample a => Proxy a -> [(Text, a)]
toSamples (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))
noSamples :: [(Text, a)]
noSamples :: forall a. [(Text, a)]
noSamples = [(Text, a)]
forall a. [a]
forall (f :: * -> *) a. Alternative f => f a
empty
singleSample :: a -> [(Text, a)]
singleSample :: forall a. a -> [(Text, a)]
singleSample a
x = [(Text
"", a
x)]
samples :: [a] -> [(Text, a)]
samples :: forall a. [a] -> [(Text, a)]
samples = (a -> (Text, a)) -> [a] -> [(Text, a)]
forall a b. (a -> b) -> [a] -> [b]
map (Text
"",)
defaultSamples :: forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
defaultSamples :: forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
defaultSamples Proxy a
_ = (Rep a Any -> a) -> (Text, Rep a Any) -> (Text, a)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second Rep a Any -> a
forall a x. Generic a => Rep a x -> a
forall x. Rep a x -> a
G.to ((Text, Rep a Any) -> (Text, a))
-> [(Text, Rep a Any)] -> [(Text, a)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Rep a) -> [(Text, Rep a Any)]
forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
forall (proxy :: (* -> *) -> *) x.
proxy (Rep a) -> [(Text, Rep a x)]
gtoSamples (Proxy (Rep a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Rep a))
class GToSample t where
gtoSamples :: proxy t -> [(Text, t x)]
instance GToSample U1 where
gtoSamples :: forall (proxy :: (k -> *) -> *) (x :: k).
proxy U1 -> [(Text, U1 x)]
gtoSamples proxy U1
_ = U1 x -> [(Text, U1 x)]
forall a. a -> [(Text, a)]
singleSample U1 x
forall k (p :: k). U1 p
U1
instance GToSample V1 where
gtoSamples :: forall (proxy :: (k -> *) -> *) (x :: k).
proxy V1 -> [(Text, V1 x)]
gtoSamples proxy V1
_ = [(Text, V1 x)]
forall a. [a]
forall (f :: * -> *) a. Alternative f => f a
empty
instance (GToSample p, GToSample q) => GToSample (p :*: q) where
gtoSamples :: forall (proxy :: (k -> *) -> *) (x :: k).
proxy (p :*: q) -> [(Text, (:*:) p q x)]
gtoSamples proxy (p :*: q)
_ = ((Text, p x) -> (Text, q x) -> (Text, (:*:) p q x))
-> [(Text, p x)] -> [(Text, q x)] -> [(Text, (:*:) p q x)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
U.cartesianProduct (Text, p x) -> (Text, q x) -> (Text, (:*:) p q x)
forall {k} {f :: k -> *} {p :: k} {g :: k -> *}.
(Text, f p) -> (Text, g p) -> (Text, (:*:) f g p)
render [(Text, p x)]
ps [(Text, q x)]
qs
where
ps :: [(Text, p x)]
ps = Proxy p -> [(Text, p x)]
forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
forall (proxy :: (k -> *) -> *) (x :: k). proxy p -> [(Text, p x)]
gtoSamples (Proxy p
forall {k} (t :: k). Proxy t
Proxy :: Proxy p)
qs :: [(Text, q x)]
qs = Proxy q -> [(Text, q x)]
forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
forall (proxy :: (k -> *) -> *) (x :: k). proxy q -> [(Text, q x)]
gtoSamples (Proxy q
forall {k} (t :: k). Proxy t
Proxy :: Proxy q)
render :: (Text, f p) -> (Text, g p) -> (Text, (:*:) f g p)
render (Text
ta, f p
a) (Text
tb, g p
b)
| Text -> Bool
T.null Text
ta Bool -> Bool -> Bool
|| Text -> Bool
T.null Text
tb = (Text
ta Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tb, f p
a f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g p
b)
| Bool
otherwise = (Text
ta Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
", " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tb, f p
a f p -> g p -> (:*:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g p
b)
instance (GToSample p, GToSample q) => GToSample (p :+: q) where
gtoSamples :: forall (proxy :: (k -> *) -> *) (x :: k).
proxy (p :+: q) -> [(Text, (:+:) p q x)]
gtoSamples proxy (p :+: q)
_ = [(Text, (:+:) p q x)]
lefts [(Text, (:+:) p q x)]
-> [(Text, (:+:) p q x)] -> [(Text, (:+:) p q x)]
forall a. [a] -> [a] -> [a]
U.+++ [(Text, (:+:) p q x)]
rights
where
lefts :: [(Text, (:+:) p q x)]
lefts = (p x -> (:+:) p q x) -> (Text, p x) -> (Text, (:+:) p q x)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second p x -> (:+:) p q x
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 ((Text, p x) -> (Text, (:+:) p q x))
-> [(Text, p x)] -> [(Text, (:+:) p q x)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy p -> [(Text, p x)]
forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
forall (proxy :: (k -> *) -> *) (x :: k). proxy p -> [(Text, p x)]
gtoSamples (Proxy p
forall {k} (t :: k). Proxy t
Proxy :: Proxy p)
rights :: [(Text, (:+:) p q x)]
rights = (q x -> (:+:) p q x) -> (Text, q x) -> (Text, (:+:) p q x)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second q x -> (:+:) p q x
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 ((Text, q x) -> (Text, (:+:) p q x))
-> [(Text, q x)] -> [(Text, (:+:) p q x)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy q -> [(Text, q x)]
forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
forall (proxy :: (k -> *) -> *) (x :: k). proxy q -> [(Text, q x)]
gtoSamples (Proxy q
forall {k} (t :: k). Proxy t
Proxy :: Proxy q)
instance ToSample a => GToSample (K1 i a) where
gtoSamples :: forall (proxy :: (k -> *) -> *) (x :: k).
proxy (K1 i a) -> [(Text, K1 i a x)]
gtoSamples proxy (K1 i a)
_ = (a -> K1 i a x) -> (Text, a) -> (Text, K1 i a x)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second a -> K1 i a x
forall k i c (p :: k). c -> K1 i c p
K1 ((Text, a) -> (Text, K1 i a x))
-> [(Text, a)] -> [(Text, K1 i a x)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy a -> [(Text, a)]
forall a. ToSample a => Proxy a -> [(Text, a)]
toSamples (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
instance (GToSample f) => GToSample (M1 i a f) where
gtoSamples :: forall (proxy :: (k -> *) -> *) (x :: k).
proxy (M1 i a f) -> [(Text, M1 i a f x)]
gtoSamples proxy (M1 i a f)
_ = (f x -> M1 i a f x) -> (Text, f x) -> (Text, M1 i a f x)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second f x -> M1 i a f x
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 ((Text, f x) -> (Text, M1 i a f x))
-> [(Text, f x)] -> [(Text, M1 i a f x)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy f -> [(Text, f x)]
forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
forall (proxy :: (k -> *) -> *) (x :: k). proxy f -> [(Text, f x)]
gtoSamples (Proxy f
forall {k} (t :: k). Proxy t
Proxy :: Proxy f)
class ls where
:: Proxy ls -> [HTTP.Header]
instance AllHeaderSamples '[] where
allHeaderToSample :: Proxy '[] -> [Header]
allHeaderToSample Proxy '[]
_ = []
instance (ToHttpApiData l, AllHeaderSamples ls, ToSample l, KnownSymbol h)
=> AllHeaderSamples (Header h l ': ls) where
allHeaderToSample :: Proxy (Header h l : ls) -> [Header]
allHeaderToSample Proxy (Header h l : ls)
_ = Maybe l -> Header
mkHeader (Proxy l -> Maybe l
forall a. ToSample a => Proxy a -> Maybe a
toSample (Proxy l
forall {k} (t :: k). Proxy t
Proxy :: Proxy l)) Header -> [Header] -> [Header]
forall a. a -> [a] -> [a]
:
Proxy ls -> [Header]
forall {k} (ls :: k). AllHeaderSamples ls => Proxy ls -> [Header]
allHeaderToSample (Proxy ls
forall {k} (t :: k). Proxy t
Proxy :: Proxy ls)
where headerName :: CI ByteString
headerName = ByteString -> CI ByteString
forall s. FoldCase s => s -> CI s
CI.mk (ByteString -> CI ByteString)
-> (String -> ByteString) -> String -> CI ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (String -> CI ByteString) -> String -> CI ByteString
forall a b. (a -> b) -> a -> b
$ Proxy h -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy h
forall {k} (t :: k). Proxy t
Proxy :: Proxy h)
mkHeader :: Maybe l -> Header
mkHeader (Just l
x) = (CI ByteString
headerName, ByteString -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ l -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toHeader l
x)
mkHeader Maybe l
Nothing = (CI ByteString
headerName, ByteString
"<no header sample provided>")
sampleByteString
:: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a)
=> Proxy (ct ': cts)
-> Proxy a
-> [(M.MediaType, ByteString)]
sampleByteString :: forall ct (cts :: [*]) a.
(ToSample a, AllMimeRender (ct : cts) a) =>
Proxy (ct : cts) -> Proxy a -> [(MediaType, ByteString)]
sampleByteString ctypes :: Proxy (ct : cts)
ctypes@Proxy (ct : cts)
Proxy Proxy a
Proxy =
[(MediaType, ByteString)]
-> (a -> [(MediaType, ByteString)])
-> Maybe a
-> [(MediaType, ByteString)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Proxy (ct : cts) -> a -> [(MediaType, ByteString)]
forall (list :: [*]) a.
AllMimeRender list a =>
Proxy list -> a -> [(MediaType, ByteString)]
allMimeRender Proxy (ct : cts)
ctypes) (Maybe a -> [(MediaType, ByteString)])
-> Maybe a -> [(MediaType, ByteString)]
forall a b. (a -> b) -> a -> b
$ Proxy a -> Maybe a
forall a. ToSample a => Proxy a -> Maybe a
toSample (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
sampleByteStrings
:: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a)
=> Proxy (ct ': cts)
-> Proxy a
-> [(Text, M.MediaType, ByteString)]
sampleByteStrings :: forall ct (cts :: [*]) a.
(ToSample a, AllMimeRender (ct : cts) a) =>
Proxy (ct : cts) -> Proxy a -> [(Text, MediaType, ByteString)]
sampleByteStrings ctypes :: Proxy (ct : cts)
ctypes@Proxy (ct : cts)
Proxy Proxy a
Proxy =
let samples' :: [(Text, a)]
samples' = Proxy a -> [(Text, a)]
forall a. ToSample a => Proxy a -> [(Text, a)]
toSamples (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
enc :: (Text, a) -> [(Text, MediaType, ByteString)]
enc (Text
t, a
s) = (MediaType -> ByteString -> (Text, MediaType, ByteString))
-> (MediaType, ByteString) -> (Text, MediaType, ByteString)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (Text
t,,) ((MediaType, ByteString) -> (Text, MediaType, ByteString))
-> [(MediaType, ByteString)] -> [(Text, MediaType, ByteString)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (ct : cts) -> a -> [(MediaType, ByteString)]
forall (list :: [*]) a.
AllMimeRender list a =>
Proxy list -> a -> [(MediaType, ByteString)]
allMimeRender Proxy (ct : cts)
ctypes a
s
in ((Text, a) -> [(Text, MediaType, ByteString)])
-> [(Text, a)] -> [(Text, MediaType, ByteString)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Text, a) -> [(Text, MediaType, ByteString)]
enc [(Text, a)]
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
class ToFragment t where
toFragment :: Proxy t -> DocFragment
markdown :: API -> String
markdown :: API -> String
markdown = RenderingOptions -> API -> String
markdownWith RenderingOptions
defRenderingOptions
markdownWith :: RenderingOptions -> API -> String
markdownWith :: RenderingOptions -> API -> String
markdownWith RenderingOptions{Maybe String
ShowContentTypes
_requestExamples :: RenderingOptions -> ShowContentTypes
_responseExamples :: RenderingOptions -> ShowContentTypes
_notesHeading :: RenderingOptions -> Maybe String
_renderCurlBasePath :: RenderingOptions -> Maybe String
_requestExamples :: ShowContentTypes
_responseExamples :: ShowContentTypes
_notesHeading :: Maybe String
_renderCurlBasePath :: Maybe String
..} API
api = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
[DocIntro] -> [String]
introsStr (API
api API -> Getting [DocIntro] API [DocIntro] -> [DocIntro]
forall s a. s -> Getting a s a -> a
^. Getting [DocIntro] API [DocIntro]
Lens' API [DocIntro]
apiIntros)
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (((Endpoint, Action) -> [String])
-> [(Endpoint, Action)] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Endpoint -> Action -> [String]) -> (Endpoint, Action) -> [String]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Endpoint -> Action -> [String]
printEndpoint) ([(Endpoint, Action)] -> [String])
-> (HashMap Endpoint Action -> [(Endpoint, Action)])
-> HashMap Endpoint Action
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Endpoint, Action)] -> [(Endpoint, Action)]
forall a. Ord a => [a] -> [a]
sort ([(Endpoint, Action)] -> [(Endpoint, Action)])
-> (HashMap Endpoint Action -> [(Endpoint, Action)])
-> HashMap Endpoint Action
-> [(Endpoint, Action)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap Endpoint Action -> [(Endpoint, Action)]
forall k v. HashMap k v -> [(k, v)]
HM.toList (HashMap Endpoint Action -> [String])
-> HashMap Endpoint Action -> [String]
forall a b. (a -> b) -> a -> b
$ API
api API
-> Getting (HashMap Endpoint Action) API (HashMap Endpoint Action)
-> HashMap Endpoint Action
forall s a. s -> Getting a s a -> a
^. Getting (HashMap Endpoint Action) API (HashMap Endpoint Action)
Lens' API (HashMap Endpoint Action)
apiEndpoints)
where printEndpoint :: Endpoint -> Action -> [String]
printEndpoint :: Endpoint -> Action -> [String]
printEndpoint Endpoint
endpoint Action
action =
String
str String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[DocNote] -> [String]
notesStr (Action
action Action -> Getting [DocNote] Action [DocNote] -> [DocNote]
forall s a. s -> Getting a s a -> a
^. Getting [DocNote] Action [DocNote]
Lens' Action [DocNote]
notes) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[DocAuthentication] -> [String]
authStr (Action
action Action
-> Getting [DocAuthentication] Action [DocAuthentication]
-> [DocAuthentication]
forall s a. s -> Getting a s a -> a
^. Getting [DocAuthentication] Action [DocAuthentication]
Lens' Action [DocAuthentication]
authInfo) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[DocCapture] -> [String]
capturesStr (Action
action Action -> Getting [DocCapture] Action [DocCapture] -> [DocCapture]
forall s a. s -> Getting a s a -> a
^. Getting [DocCapture] Action [DocCapture]
Lens' Action [DocCapture]
captures) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[Text] -> [String]
headersStr (Getting (Endo [Text]) Action Text -> Action -> [Text]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf (([Header] -> Const (Endo [Text]) [Header])
-> Action -> Const (Endo [Text]) Action
Lens' Action [Header]
headers (([Header] -> Const (Endo [Text]) [Header])
-> Action -> Const (Endo [Text]) Action)
-> ((Text -> Const (Endo [Text]) Text)
-> [Header] -> Const (Endo [Text]) [Header])
-> Getting (Endo [Text]) Action Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Header -> Const (Endo [Text]) Header)
-> [Header] -> Const (Endo [Text]) [Header]
forall s t a b. Each s t a b => Traversal s t a b
Traversal [Header] [Header] Header Header
each ((Header -> Const (Endo [Text]) Header)
-> [Header] -> Const (Endo [Text]) [Header])
-> ((Text -> Const (Endo [Text]) Text)
-> Header -> Const (Endo [Text]) Header)
-> (Text -> Const (Endo [Text]) Text)
-> [Header]
-> Const (Endo [Text]) [Header]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CI ByteString -> Const (Endo [Text]) (CI ByteString))
-> Header -> Const (Endo [Text]) Header
forall s t a b. Field1 s t a b => Lens s t a b
Lens Header Header (CI ByteString) (CI ByteString)
_1 ((CI ByteString -> Const (Endo [Text]) (CI ByteString))
-> Header -> Const (Endo [Text]) Header)
-> ((Text -> Const (Endo [Text]) Text)
-> CI ByteString -> Const (Endo [Text]) (CI ByteString))
-> (Text -> Const (Endo [Text]) Text)
-> Header
-> Const (Endo [Text]) Header
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CI ByteString -> Text)
-> (Text -> Const (Endo [Text]) Text)
-> CI ByteString
-> Const (Endo [Text]) (CI ByteString)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (String -> Text
T.pack (String -> Text)
-> (CI ByteString -> String) -> CI ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
BSC.unpack (ByteString -> String)
-> (CI ByteString -> ByteString) -> CI ByteString -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CI ByteString -> ByteString
forall s. CI s -> s
CI.original)) Action
action) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
ByteString -> [DocQueryParam] -> [String]
paramsStr ByteString
meth (Action
action Action
-> Getting [DocQueryParam] Action [DocQueryParam]
-> [DocQueryParam]
forall s a. s -> Getting a s a -> a
^. Getting [DocQueryParam] Action [DocQueryParam]
Lens' Action [DocQueryParam]
params) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
Maybe DocFragment -> [String]
fragmentStr (Action
action Action
-> Getting (Maybe DocFragment) Action (Maybe DocFragment)
-> Maybe DocFragment
forall s a. s -> Getting a s a -> a
^. Getting (Maybe DocFragment) Action (Maybe DocFragment)
Lens' Action (Maybe DocFragment)
fragment) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[MediaType] -> [(Text, MediaType, ByteString)] -> [String]
rqbodyStr (Action
action Action -> Getting [MediaType] Action [MediaType] -> [MediaType]
forall s a. s -> Getting a s a -> a
^. Getting [MediaType] Action [MediaType]
Lens' Action [MediaType]
rqtypes) (Action
action Action
-> Getting
[(Text, MediaType, ByteString)]
Action
[(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall s a. s -> Getting a s a -> a
^. Getting
[(Text, MediaType, ByteString)]
Action
[(Text, MediaType, ByteString)]
Lens' Action [(Text, MediaType, ByteString)]
rqbody) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
Response -> [String]
responseStr (Action
action Action -> Getting Response Action Response -> Response
forall s a. s -> Getting a s a -> a
^. Getting Response Action Response
Lens' Action Response
response) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Endpoint
-> [Header]
-> [(Text, MediaType, ByteString)]
-> String
-> [String]
curlStr Endpoint
endpoint (Action
action Action -> Getting [Header] Action [Header] -> [Header]
forall s a. s -> Getting a s a -> a
^. Getting [Header] Action [Header]
Lens' Action [Header]
headers) (Action
action Action
-> Getting
[(Text, MediaType, ByteString)]
Action
[(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall s a. s -> Getting a s a -> a
^. Getting
[(Text, MediaType, ByteString)]
Action
[(Text, MediaType, ByteString)]
Lens' Action [(Text, MediaType, ByteString)]
rqbody)) Maybe String
_renderCurlBasePath [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[]
where str :: String
str = String
"## " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
BSC.unpack ByteString
meth
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
showPath (Endpoint
endpointEndpoint -> Getting [String] Endpoint [String] -> [String]
forall s a. s -> Getting a s a -> a
^.Getting [String] Endpoint [String]
Lens' Endpoint [String]
path)
meth :: ByteString
meth = Endpoint
endpoint Endpoint -> Getting ByteString Endpoint ByteString -> ByteString
forall s a. s -> Getting a s a -> a
^. Getting ByteString Endpoint ByteString
Lens' Endpoint ByteString
method
introsStr :: [DocIntro] -> [String]
introsStr :: [DocIntro] -> [String]
introsStr = (DocIntro -> [String]) -> [DocIntro] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DocIntro -> [String]
introStr
introStr :: DocIntro -> [String]
introStr :: DocIntro -> [String]
introStr DocIntro
i =
(String
"## " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DocIntro
i DocIntro -> Getting String DocIntro String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocIntro String
Lens' DocIntro String
introTitle) String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String -> [String] -> [String]
forall a. a -> [a] -> [a]
intersperse String
"" (DocIntro
i DocIntro -> Getting [String] DocIntro [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] DocIntro [String]
Lens' DocIntro [String]
introBody) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[]
notesStr :: [DocNote] -> [String]
notesStr :: [DocNote] -> [String]
notesStr = [String] -> [String]
addHeading
([String] -> [String])
-> ([DocNote] -> [String]) -> [DocNote] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DocNote -> [String]) -> [DocNote] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DocNote -> [String]
noteStr
where
addHeading :: [String] -> [String]
addHeading [String]
nts = [String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [String]
nts (\String
hd -> (String
"### " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
hd) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
nts) Maybe String
_notesHeading
noteStr :: DocNote -> [String]
noteStr :: DocNote -> [String]
noteStr DocNote
nt =
(String
hdr String -> ShowS
forall a. [a] -> [a] -> [a]
++ DocNote
nt DocNote -> Getting String DocNote String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocNote String
Lens' DocNote String
noteTitle) String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String -> [String] -> [String]
forall a. a -> [a] -> [a]
intersperse String
"" (DocNote
nt DocNote -> Getting [String] DocNote [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] DocNote [String]
Lens' DocNote [String]
noteBody) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[]
where
hdr :: String
hdr | Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
_notesHeading = String
"#### "
| Bool
otherwise = String
"### "
authStr :: [DocAuthentication] -> [String]
authStr :: [DocAuthentication] -> [String]
authStr [] = []
authStr [DocAuthentication]
auths =
let authIntros :: [String]
authIntros = (DocAuthentication -> Identity String)
-> [DocAuthentication] -> Identity [String]
Setter [DocAuthentication] [String] DocAuthentication String
forall (f :: * -> *) a b. Functor f => Setter (f a) (f b) a b
mapped ((DocAuthentication -> Identity String)
-> [DocAuthentication] -> Identity [String])
-> (DocAuthentication -> String) -> [DocAuthentication] -> [String]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Getting String DocAuthentication String
-> DocAuthentication -> String
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting String DocAuthentication String
Lens' DocAuthentication String
authIntro ([DocAuthentication] -> [String])
-> [DocAuthentication] -> [String]
forall a b. (a -> b) -> a -> b
$ [DocAuthentication]
auths
clientInfos :: [String]
clientInfos = (DocAuthentication -> Identity String)
-> [DocAuthentication] -> Identity [String]
Setter [DocAuthentication] [String] DocAuthentication String
forall (f :: * -> *) a b. Functor f => Setter (f a) (f b) a b
mapped ((DocAuthentication -> Identity String)
-> [DocAuthentication] -> Identity [String])
-> (DocAuthentication -> String) -> [DocAuthentication] -> [String]
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Getting String DocAuthentication String
-> DocAuthentication -> String
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting String DocAuthentication String
Lens' DocAuthentication String
authDataRequired ([DocAuthentication] -> [String])
-> [DocAuthentication] -> [String]
forall a b. (a -> b) -> a -> b
$ [DocAuthentication]
auths
in String
"### Authentication"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
""String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[String] -> String
unlines [String]
authIntros String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
""String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"Clients must supply the following data" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[String] -> String
unlines [String]
clientInfos String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[]
capturesStr :: [DocCapture] -> [String]
capturesStr :: [DocCapture] -> [String]
capturesStr [] = []
capturesStr [DocCapture]
l =
String
"### Captures:" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(DocCapture -> String) -> [DocCapture] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map DocCapture -> String
captureStr [DocCapture]
l [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[]
captureStr :: DocCapture -> String
captureStr DocCapture
cap =
String
"- *" String -> ShowS
forall a. [a] -> [a] -> [a]
++ (DocCapture
cap DocCapture -> Getting String DocCapture String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocCapture String
Lens' DocCapture String
capSymbol) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (DocCapture
cap DocCapture -> Getting String DocCapture String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocCapture String
Lens' DocCapture String
capDesc)
headersStr :: [Text] -> [String]
headersStr :: [Text] -> [String]
headersStr [] = []
headersStr [Text]
l =
String
"### Headers:" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Text -> String
headerStr [Text]
l [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[]
where headerStr :: Text -> String
headerStr Text
hname = String
"- This endpoint is sensitive to the value of the **"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
unpack Text
hname String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"** HTTP header."
paramsStr :: HTTP.Method -> [DocQueryParam] -> [String]
paramsStr :: ByteString -> [DocQueryParam] -> [String]
paramsStr ByteString
_ [] = []
paramsStr ByteString
m [DocQueryParam]
l =
(String
"### " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a b. ConvertibleStrings a b => a -> b
cs ByteString
m String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" Parameters:") String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(DocQueryParam -> String) -> [DocQueryParam] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (ByteString -> DocQueryParam -> String
forall {a}.
ConvertibleStrings a String =>
a -> DocQueryParam -> String
paramStr ByteString
m) [DocQueryParam]
l [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[]
paramStr :: a -> DocQueryParam -> String
paramStr a
m DocQueryParam
param = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
(String
"- " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DocQueryParam
param DocQueryParam -> Getting String DocQueryParam String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocQueryParam String
Lens' DocQueryParam String
paramName) String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(if (Bool -> Bool
not ([String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
values) Bool -> Bool -> Bool
|| DocQueryParam
param DocQueryParam
-> Getting ParamKind DocQueryParam ParamKind -> ParamKind
forall s a. s -> Getting a s a -> a
^. Getting ParamKind DocQueryParam ParamKind
Lens' DocQueryParam ParamKind
paramKind ParamKind -> ParamKind -> Bool
forall a. Eq a => a -> a -> Bool
/= ParamKind
Flag)
then [String
" - **Values**: *" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
values String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*"]
else []) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(String
" - **Description**: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DocQueryParam
param DocQueryParam -> Getting String DocQueryParam String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocQueryParam String
Lens' DocQueryParam String
paramDesc) String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(if (DocQueryParam
param DocQueryParam
-> Getting ParamKind DocQueryParam ParamKind -> ParamKind
forall s a. s -> Getting a s a -> a
^. Getting ParamKind DocQueryParam ParamKind
Lens' DocQueryParam ParamKind
paramKind ParamKind -> ParamKind -> Bool
forall a. Eq a => a -> a -> Bool
== ParamKind
List)
then [String
" - This parameter is a **list**. All " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a b. ConvertibleStrings a b => a -> b
cs a
m String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" parameters with the name "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ DocQueryParam
param DocQueryParam -> Getting String DocQueryParam String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocQueryParam String
Lens' DocQueryParam String
paramName String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"[] will forward their values in a list to the handler."]
else []) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(if (DocQueryParam
param DocQueryParam
-> Getting ParamKind DocQueryParam ParamKind -> ParamKind
forall s a. s -> Getting a s a -> a
^. Getting ParamKind DocQueryParam ParamKind
Lens' DocQueryParam ParamKind
paramKind ParamKind -> ParamKind -> Bool
forall a. Eq a => a -> a -> Bool
== ParamKind
Flag)
then [String
" - This parameter is a **flag**. This means no value is expected to be associated to this parameter."]
else []) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[]
where values :: [String]
values = DocQueryParam
param DocQueryParam
-> Getting [String] DocQueryParam [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] DocQueryParam [String]
Lens' DocQueryParam [String]
paramValues
fragmentStr :: Maybe DocFragment -> [String]
fragmentStr :: Maybe DocFragment -> [String]
fragmentStr Maybe DocFragment
Nothing = []
fragmentStr (Just DocFragment
frag) =
[ String
"### Fragment:", String
""
, String
"- *" String -> ShowS
forall a. [a] -> [a] -> [a]
++ (DocFragment
frag DocFragment -> Getting String DocFragment String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocFragment String
Lens' DocFragment String
fragSymbol) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"*: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (DocFragment
frag DocFragment -> Getting String DocFragment String -> String
forall s a. s -> Getting a s a -> a
^. Getting String DocFragment String
Lens' DocFragment String
fragDesc)
, String
""
]
rqbodyStr :: [M.MediaType] -> [(Text, M.MediaType, ByteString)]-> [String]
rqbodyStr :: [MediaType] -> [(Text, MediaType, ByteString)] -> [String]
rqbodyStr [] [] = []
rqbodyStr [MediaType]
types [(Text, MediaType, ByteString)]
s =
[String
"### Request:", String
""]
[String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [MediaType] -> [String]
forall {a}. Show a => [a] -> [String]
formatTypes [MediaType]
types
[String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> ShowContentTypes -> [(Text, MediaType, ByteString)] -> [String]
formatBodies ShowContentTypes
_requestExamples [(Text, MediaType, ByteString)]
s
formatTypes :: [a] -> [String]
formatTypes [] = []
formatTypes [a]
ts = [String
"- Supported content types are:", String
""]
[String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> (a -> String) -> [a] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\a
t -> String
" - `" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
t String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"`") [a]
ts
[String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
""]
formatBodies :: ShowContentTypes -> [(Text, M.MediaType, ByteString)] -> [String]
formatBodies :: ShowContentTypes -> [(Text, MediaType, ByteString)] -> [String]
formatBodies ShowContentTypes
ex [(Text, MediaType, ByteString)]
bds = ((Text, NonEmpty MediaType, ByteString) -> [String])
-> [(Text, NonEmpty MediaType, ByteString)] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Text, NonEmpty MediaType, ByteString) -> [String]
formatBody ([(Text, NonEmpty MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)]
select [(Text, NonEmpty MediaType, ByteString)]
bodyGroups)
where
bodyGroups :: [(Text, NonEmpty M.MediaType, ByteString)]
bodyGroups :: [(Text, NonEmpty MediaType, ByteString)]
bodyGroups =
(NonEmpty (Text, MediaType, ByteString)
-> (Text, NonEmpty MediaType, ByteString))
-> [NonEmpty (Text, MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
map (\NonEmpty (Text, MediaType, ByteString)
grps -> let (Text
t,MediaType
_,ByteString
b) = NonEmpty (Text, MediaType, ByteString)
-> (Text, MediaType, ByteString)
forall a. NonEmpty a -> a
NE.head NonEmpty (Text, MediaType, ByteString)
grps in (Text
t, ((Text, MediaType, ByteString) -> MediaType)
-> NonEmpty (Text, MediaType, ByteString) -> NonEmpty MediaType
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Text
_,MediaType
m,ByteString
_) -> MediaType
m) NonEmpty (Text, MediaType, ByteString)
grps, ByteString
b))
([NonEmpty (Text, MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)])
-> ([(Text, MediaType, ByteString)]
-> [NonEmpty (Text, MediaType, ByteString)])
-> [(Text, MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, MediaType, ByteString) -> (Text, ByteString))
-> [(Text, MediaType, ByteString)]
-> [NonEmpty (Text, MediaType, ByteString)]
forall (f :: * -> *) b a.
(Foldable f, Eq b) =>
(a -> b) -> f a -> [NonEmpty a]
groupWith (\(Text
t,MediaType
_,ByteString
b) -> (Text
t,ByteString
b))
([(Text, MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)])
-> [(Text, MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)]
forall a b. (a -> b) -> a -> b
$ [(Text, MediaType, ByteString)]
bds
select :: [(Text, NonEmpty MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)]
select = case ShowContentTypes
ex of
ShowContentTypes
AllContentTypes -> [(Text, NonEmpty MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)]
forall a. a -> a
id
ShowContentTypes
FirstContentType -> ((Text, NonEmpty MediaType, ByteString)
-> (Text, NonEmpty MediaType, ByteString))
-> [(Text, NonEmpty MediaType, ByteString)]
-> [(Text, NonEmpty MediaType, ByteString)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
t,NonEmpty MediaType
ms,ByteString
b) -> (Text
t, NonEmpty MediaType -> MediaType
forall a. NonEmpty a -> a
NE.head NonEmpty MediaType
ms MediaType -> [MediaType] -> NonEmpty MediaType
forall a. a -> [a] -> NonEmpty a
:| [], ByteString
b))
formatBody :: (Text, NonEmpty M.MediaType, ByteString) -> [String]
formatBody :: (Text, NonEmpty MediaType, ByteString) -> [String]
formatBody (Text
t, NonEmpty MediaType
ms, ByteString
b) =
String
"- " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
title String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" (" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> NonEmpty MediaType -> String
mediaList NonEmpty MediaType
ms String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"):" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
MediaType -> ByteString -> [String]
forall {a} {a}.
(IsString a, Semigroup a, ConvertibleStrings a a) =>
MediaType -> a -> [a]
contentStr (NonEmpty MediaType -> MediaType
forall a. NonEmpty a -> a
NE.head NonEmpty MediaType
ms) ByteString
b
where
mediaList :: NonEmpty MediaType -> String
mediaList = NonEmpty String -> String
forall m. Monoid m => NonEmpty m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (NonEmpty String -> String)
-> (NonEmpty MediaType -> NonEmpty String)
-> NonEmpty MediaType
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> NonEmpty String -> NonEmpty String
forall a. a -> NonEmpty a -> NonEmpty a
NE.intersperse String
", " (NonEmpty String -> NonEmpty String)
-> (NonEmpty MediaType -> NonEmpty String)
-> NonEmpty MediaType
-> NonEmpty String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MediaType -> String) -> NonEmpty MediaType -> NonEmpty String
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\MediaType
m -> String
"`" String -> ShowS
forall a. [a] -> [a] -> [a]
++ MediaType -> String
forall a. Show a => a -> String
show MediaType
m String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"`")
title :: String
title
| Text -> Bool
T.null Text
t = String
"Example"
| Bool
otherwise = Text -> String
forall a b. ConvertibleStrings a b => a -> b
cs Text
t
markdownForType :: MediaType -> a
markdownForType MediaType
mime_type =
case (MediaType -> CI ByteString
M.mainType MediaType
mime_type, MediaType -> CI ByteString
M.subType MediaType
mime_type) of
(CI ByteString
"text", CI ByteString
"html") -> a
"html"
(CI ByteString
"application", CI ByteString
"xml") -> a
"xml"
(CI ByteString
"text", CI ByteString
"xml") -> a
"xml"
(CI ByteString
"application", CI ByteString
"json") -> a
"javascript"
(CI ByteString
"application", CI ByteString
"javascript") -> a
"javascript"
(CI ByteString
"text", CI ByteString
"css") -> a
"css"
(CI ByteString
_, CI ByteString
_) -> a
""
contentStr :: MediaType -> a -> [a]
contentStr MediaType
mime_type a
body =
a
"" a -> [a] -> [a]
forall a. a -> [a] -> [a]
:
a
"```" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> MediaType -> a
forall {a}. IsString a => MediaType -> a
markdownForType MediaType
mime_type a -> [a] -> [a]
forall a. a -> [a] -> [a]
:
a -> a
forall a b. ConvertibleStrings a b => a -> b
cs a
body a -> [a] -> [a]
forall a. a -> [a] -> [a]
:
a
"```" a -> [a] -> [a]
forall a. a -> [a] -> [a]
:
a
"" a -> [a] -> [a]
forall a. a -> [a] -> [a]
:
[]
responseStr :: Response -> [String]
responseStr :: Response -> [String]
responseStr Response
resp =
String
"### Response:" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(String
"- Status code " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Response
resp Response -> Getting Int Response Int -> Int
forall s a. s -> Getting a s a -> a
^. Getting Int Response Int
Lens' Response Int
respStatus)) String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
(String
"- Headers: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Header] -> String
forall a. Show a => a -> String
show (Response
resp Response -> Getting [Header] Response [Header] -> [Header]
forall s a. s -> Getting a s a -> a
^. Getting [Header] Response [Header]
Lens' Response [Header]
respHeaders)) String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
[MediaType] -> [String]
forall {a}. Show a => [a] -> [String]
formatTypes (Response
resp Response -> Getting [MediaType] Response [MediaType] -> [MediaType]
forall s a. s -> Getting a s a -> a
^. Getting [MediaType] Response [MediaType]
Lens' Response [MediaType]
respTypes) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[String]
bodies
where bodies :: [String]
bodies = case Response
resp Response
-> Getting
[(Text, MediaType, ByteString)]
Response
[(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall s a. s -> Getting a s a -> a
^. Getting
[(Text, MediaType, ByteString)]
Response
[(Text, MediaType, ByteString)]
Lens' Response [(Text, MediaType, ByteString)]
respBody of
[] -> [String
"- No response body\n"]
[(Text
"", MediaType
t, ByteString
r)] -> String
"- Response body as below." String -> [String] -> [String]
forall a. a -> [a] -> [a]
: MediaType -> ByteString -> [String]
forall {a} {a}.
(IsString a, Semigroup a, ConvertibleStrings a a) =>
MediaType -> a -> [a]
contentStr MediaType
t ByteString
r
[(Text, MediaType, ByteString)]
xs ->
ShowContentTypes -> [(Text, MediaType, ByteString)] -> [String]
formatBodies ShowContentTypes
_responseExamples [(Text, MediaType, ByteString)]
xs
curlStr :: Endpoint -> [HTTP.Header] -> [(Text, M.MediaType, ByteString)] -> String -> [String]
curlStr :: Endpoint
-> [Header]
-> [(Text, MediaType, ByteString)]
-> String
-> [String]
curlStr Endpoint
endpoint [Header]
hdrs [(Text, MediaType, ByteString)]
reqBodies String
basePath =
[ String
"### Sample Request:"
, String
""
, String
"```bash"
, String
"curl -X" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
BSC.unpack (Endpoint
endpoint Endpoint -> Getting ByteString Endpoint ByteString -> ByteString
forall s a. s -> Getting a s a -> a
^. Getting ByteString Endpoint ByteString
Lens' Endpoint ByteString
method) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" \\"
] [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<>
[String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] String -> [String]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
mbMediaTypeStr [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<>
[String]
headersStrs [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<>
[String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] String -> [String]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
mbReqBodyStr [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<>
[ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
basePath String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
showPath (Endpoint
endpoint Endpoint -> Getting [String] Endpoint [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] Endpoint [String]
Lens' Endpoint [String]
path)
, String
"```"
, String
""
]
where escapeQuotes :: String -> String
escapeQuotes :: ShowS
escapeQuotes = (Char -> String) -> ShowS
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Char -> String) -> ShowS) -> (Char -> String) -> ShowS
forall a b. (a -> b) -> a -> b
$ \Char
c -> case Char
c of
Char
'\"' -> String
"\\\""
Char
_ -> [Char
c]
mbReqBody :: Maybe (Text, MediaType, ByteString)
mbReqBody = [(Text, MediaType, ByteString)]
-> Maybe (Text, MediaType, ByteString)
forall a. [a] -> Maybe a
listToMaybe [(Text, MediaType, ByteString)]
reqBodies
mbMediaTypeStr :: Maybe String
mbMediaTypeStr = (Text, MediaType, ByteString) -> String
forall {a} {a} {c}. Show a => (a, a, c) -> String
mkMediaTypeStr ((Text, MediaType, ByteString) -> String)
-> Maybe (Text, MediaType, ByteString) -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Text, MediaType, ByteString)
mbReqBody
headersStrs :: [String]
headersStrs = Header -> String
forall {a} {a}.
(ConvertibleStrings a String, ConvertibleStrings a String) =>
(CI a, a) -> String
mkHeaderStr (Header -> String) -> [Header] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Header]
hdrs
mbReqBodyStr :: Maybe String
mbReqBodyStr = (Text, MediaType, ByteString) -> String
forall {a} {a} {b}.
ConvertibleStrings a String =>
(a, b, a) -> String
mkReqBodyStr ((Text, MediaType, ByteString) -> String)
-> Maybe (Text, MediaType, ByteString) -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Text, MediaType, ByteString)
mbReqBody
mkMediaTypeStr :: (a, a, c) -> String
mkMediaTypeStr (a
_, a
media_type, c
_) =
String
" -H \"Content-Type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
media_type String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\" \\"
mkHeaderStr :: (CI a, a) -> String
mkHeaderStr (CI a
hdrName, a
hdrVal) =
String
" -H \"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
escapeQuotes (a -> String
forall a b. ConvertibleStrings a b => a -> b
cs (CI a -> a
forall s. CI s -> s
CI.original CI a
hdrName)) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++
ShowS
escapeQuotes (a -> String
forall a b. ConvertibleStrings a b => a -> b
cs a
hdrVal) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\" \\"
mkReqBodyStr :: (a, b, a) -> String
mkReqBodyStr (a
_, b
_, a
body) = String
" -d \"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
escapeQuotes (a -> String
forall a b. ConvertibleStrings a b => a -> b
cs a
body) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\" \\"
instance {-# OVERLAPPABLE #-}
(HasDocs a, HasDocs b)
=> HasDocs (a :<|> b) where
docsFor :: Proxy (a :<|> b) -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (a :<|> b)
Proxy (Endpoint
ep, Action
action) = Proxy a -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy a
p1 (Endpoint
ep, Action
action) (DocOptions -> API) -> (DocOptions -> API) -> DocOptions -> API
forall a. Semigroup a => a -> a -> a
<> Proxy b -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy b
p2 (Endpoint
ep, Action
action)
where p1 :: Proxy a
p1 :: Proxy a
p1 = Proxy a
forall {k} (t :: k). Proxy t
Proxy
p2 :: Proxy b
p2 :: Proxy b
p2 = Proxy b
forall {k} (t :: k). Proxy t
Proxy
instance HasDocs EmptyAPI where
docsFor :: Proxy EmptyAPI -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy EmptyAPI
Proxy (Endpoint, Action)
_ DocOptions
_ = API
emptyAPI
instance (KnownSymbol sym, ToCapture (Capture sym a), HasDocs api)
=> HasDocs (Capture' '[] sym a :> api) where
docsFor :: Proxy (Capture' '[] sym a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Capture' '[] sym a :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint', Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
captureP :: Proxy (Capture' '[] sym a)
captureP = Proxy (Capture' '[] sym a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Capture sym a)
action' :: Action
action' = ASetter Action Action [DocCapture] [DocCapture]
-> ([DocCapture] -> [DocCapture]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocCapture] [DocCapture]
Lens' Action [DocCapture]
captures ([DocCapture] -> DocCapture -> [DocCapture]
forall s a. Snoc s s a a => s -> a -> s
|> Proxy (Capture' '[] sym a) -> DocCapture
forall {k} (c :: k). ToCapture c => Proxy c -> DocCapture
toCapture Proxy (Capture' '[] sym a)
captureP) Action
action
endpoint' :: Endpoint
endpoint' = ASetter Endpoint Endpoint [String] [String]
-> ([String] -> [String]) -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Endpoint Endpoint [String] [String]
Lens' Endpoint [String]
path (\[String]
p -> [String]
p [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP]) Endpoint
endpoint
symP :: Proxy sym
symP = Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym
instance (KnownSymbol descr, KnownSymbol sym, HasDocs api)
=> HasDocs (Capture' (Description descr ': mods) sym a :> api) where
docsFor :: Proxy (Capture' (Description descr : mods) sym a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Capture' (Description descr : mods) sym a :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint', Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
docCapture :: DocCapture
docCapture = String -> String -> DocCapture
DocCapture (Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP) (Proxy descr -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy descr
descrP)
action' :: Action
action' = ASetter Action Action [DocCapture] [DocCapture]
-> ([DocCapture] -> [DocCapture]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocCapture] [DocCapture]
Lens' Action [DocCapture]
captures ([DocCapture] -> DocCapture -> [DocCapture]
forall s a. Snoc s s a a => s -> a -> s
|> DocCapture
docCapture) Action
action
endpoint' :: Endpoint
endpoint' = ASetter Endpoint Endpoint [String] [String]
-> ([String] -> [String]) -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Endpoint Endpoint [String] [String]
Lens' Endpoint [String]
path (\[String]
p -> [String]
p [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP]) Endpoint
endpoint
descrP :: Proxy descr
descrP = Proxy descr
forall {k} (t :: k). Proxy t
Proxy :: Proxy descr
symP :: Proxy sym
symP = Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym
instance {-# OVERLAPPABLE #-} HasDocs (Capture' mods sym a :> api)
=> HasDocs (Capture' (mod ': mods) sym a :> api) where
docsFor :: Proxy (Capture' (mod : mods) sym a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Capture' (mod : mods) sym a :> api)
Proxy =
Proxy (Capture' mods sym a :> api)
-> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Capture' mods sym a :> api)
apiP
where apiP :: Proxy (Capture' mods sym a :> api)
apiP = Proxy (Capture' mods sym a :> api)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Capture' mods sym a :> api)
instance (KnownSymbol sym, ToCapture (CaptureAll sym a), HasDocs sublayout)
=> HasDocs (CaptureAll sym a :> sublayout) where
docsFor :: Proxy (CaptureAll sym a :> sublayout)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (CaptureAll sym a :> sublayout)
Proxy (Endpoint
endpoint, Action
action) =
Proxy sublayout -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy sublayout
sublayoutP (Endpoint
endpoint', Action
action')
where sublayoutP :: Proxy sublayout
sublayoutP = Proxy sublayout
forall {k} (t :: k). Proxy t
Proxy :: Proxy sublayout
captureP :: Proxy (CaptureAll sym a)
captureP = Proxy (CaptureAll sym a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (CaptureAll sym a)
action' :: Action
action' = ASetter Action Action [DocCapture] [DocCapture]
-> ([DocCapture] -> [DocCapture]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocCapture] [DocCapture]
Lens' Action [DocCapture]
captures ([DocCapture] -> DocCapture -> [DocCapture]
forall s a. Snoc s s a a => s -> a -> s
|> Proxy (CaptureAll sym a) -> DocCapture
forall {k} (c :: k). ToCapture c => Proxy c -> DocCapture
toCapture Proxy (CaptureAll sym a)
captureP) Action
action
endpoint' :: Endpoint
endpoint' = ASetter Endpoint Endpoint [String] [String]
-> ([String] -> [String]) -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Endpoint Endpoint [String] [String]
Lens' Endpoint [String]
path (\[String]
p -> [String]
p [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP]) Endpoint
endpoint
symP :: Proxy sym
symP = Proxy sym
forall {k} (t :: k). Proxy t
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 (Verb method status (ct : cts) a)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Verb method status (ct : cts) a)
Proxy (Endpoint
endpoint, Action
action) DocOptions{Int
_maxSamples :: DocOptions -> Int
_maxSamples :: Int
..} =
Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'
where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& (ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint
Lens' Endpoint ByteString
method ((ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint)
-> ByteString -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ByteString
method'
action' :: Action
action' = Action
action Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Response -> Identity Response)
-> ([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Response -> Identity Response
Lens' Response [(Text, MediaType, ByteString)]
respBody (([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action -> Identity Action)
-> [(Text, MediaType, ByteString)] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
-> [(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall a. Int -> [a] -> [a]
take Int
_maxSamples (Proxy (ct : cts) -> Proxy a -> [(Text, MediaType, ByteString)]
forall ct (cts :: [*]) a.
(ToSample a, AllMimeRender (ct : cts) a) =>
Proxy (ct : cts) -> Proxy a -> [(Text, MediaType, ByteString)]
sampleByteStrings Proxy (ct : cts)
t Proxy a
p)
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([MediaType] -> Identity [MediaType])
-> Response -> Identity Response)
-> ([MediaType] -> Identity [MediaType])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([MediaType] -> Identity [MediaType])
-> Response -> Identity Response
Lens' Response [MediaType]
respTypes (([MediaType] -> Identity [MediaType])
-> Action -> Identity Action)
-> [MediaType] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Proxy (ct : cts) -> [MediaType]
forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy (ct : cts)
t
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> ((Int -> Identity Int) -> Response -> Identity Response)
-> (Int -> Identity Int)
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Int -> Identity Int) -> Response -> Identity Response
Lens' Response Int
respStatus ((Int -> Identity Int) -> Action -> Identity Action)
-> Int -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
status
t :: Proxy (ct : cts)
t = Proxy (ct : cts)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ct ': cts)
method' :: ByteString
method' = Proxy method -> ByteString
forall {k} (a :: k). ReflectMethod a => Proxy a -> ByteString
reflectMethod (Proxy method
forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
status :: Int
status = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy status -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy status
forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
p :: Proxy a
p = Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a
instance (ReflectMethod method) =>
HasDocs (NoContentVerb method) where
docsFor :: Proxy (NoContentVerb method)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (NoContentVerb method)
Proxy (Endpoint
endpoint, Action
action) DocOptions{Int
_maxSamples :: DocOptions -> Int
_maxSamples :: Int
..} =
Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'
where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& (ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint
Lens' Endpoint ByteString
method ((ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint)
-> ByteString -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ByteString
method'
action' :: Action
action' = Action
action Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> ((Int -> Identity Int) -> Response -> Identity Response)
-> (Int -> Identity Int)
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Int -> Identity Int) -> Response -> Identity Response
Lens' Response Int
respStatus ((Int -> Identity Int) -> Action -> Identity Action)
-> Int -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
204
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([MediaType] -> Identity [MediaType])
-> Response -> Identity Response)
-> ([MediaType] -> Identity [MediaType])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([MediaType] -> Identity [MediaType])
-> Response -> Identity Response
Lens' Response [MediaType]
respTypes (([MediaType] -> Identity [MediaType])
-> Action -> Identity Action)
-> [MediaType] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ []
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Response -> Identity Response)
-> ([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Response -> Identity Response
Lens' Response [(Text, MediaType, ByteString)]
respBody (([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action -> Identity Action)
-> [(Text, MediaType, ByteString)] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ []
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([Header] -> Identity [Header])
-> Response -> Identity Response)
-> ([Header] -> Identity [Header])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([Header] -> Identity [Header]) -> Response -> Identity Response
Lens' Response [Header]
respHeaders (([Header] -> Identity [Header]) -> Action -> Identity Action)
-> [Header] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ []
method' :: ByteString
method' = Proxy method -> ByteString
forall {k} (a :: k). ReflectMethod a => Proxy a -> ByteString
reflectMethod (Proxy method
forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
instance {-# OVERLAPPABLE #-}
(Accept ct, KnownNat status, ReflectMethod method)
=> HasDocs (Stream method status framing ct a) where
docsFor :: Proxy (Stream method status framing ct a)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Stream method status framing ct a)
Proxy (Endpoint
endpoint, Action
action) DocOptions{Int
_maxSamples :: DocOptions -> Int
_maxSamples :: Int
..} =
Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'
where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& (ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint
Lens' Endpoint ByteString
method ((ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint)
-> ByteString -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ByteString
method'
action' :: Action
action' = Action
action Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([MediaType] -> Identity [MediaType])
-> Response -> Identity Response)
-> ([MediaType] -> Identity [MediaType])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([MediaType] -> Identity [MediaType])
-> Response -> Identity Response
Lens' Response [MediaType]
respTypes (([MediaType] -> Identity [MediaType])
-> Action -> Identity Action)
-> [MediaType] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Proxy '[ct] -> [MediaType]
forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy '[ct]
t
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> ((Int -> Identity Int) -> Response -> Identity Response)
-> (Int -> Identity Int)
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Int -> Identity Int) -> Response -> Identity Response
Lens' Response Int
respStatus ((Int -> Identity Int) -> Action -> Identity Action)
-> Int -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
status
t :: Proxy '[ct]
t = Proxy '[ct]
forall {k} (t :: k). Proxy t
Proxy :: Proxy '[ct]
method' :: ByteString
method' = Proxy method -> ByteString
forall {k} (a :: k). ReflectMethod a => Proxy a -> ByteString
reflectMethod (Proxy method
forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
status :: Int
status = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy status -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy status
forall {k} (t :: k). Proxy t
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 (Verb method status (ct : cts) (Headers ls a))
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Verb method status (ct : cts) (Headers ls a))
Proxy (Endpoint
endpoint, Action
action) DocOptions{Int
_maxSamples :: DocOptions -> Int
_maxSamples :: Int
..} =
Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'
where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& (ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint
Lens' Endpoint ByteString
method ((ByteString -> Identity ByteString)
-> Endpoint -> Identity Endpoint)
-> ByteString -> Endpoint -> Endpoint
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ByteString
method'
action' :: Action
action' = Action
action Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Response -> Identity Response)
-> ([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Response -> Identity Response
Lens' Response [(Text, MediaType, ByteString)]
respBody (([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action -> Identity Action)
-> [(Text, MediaType, ByteString)] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
-> [(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall a. Int -> [a] -> [a]
take Int
_maxSamples (Proxy (ct : cts) -> Proxy a -> [(Text, MediaType, ByteString)]
forall ct (cts :: [*]) a.
(ToSample a, AllMimeRender (ct : cts) a) =>
Proxy (ct : cts) -> Proxy a -> [(Text, MediaType, ByteString)]
sampleByteStrings Proxy (ct : cts)
t Proxy a
p)
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([MediaType] -> Identity [MediaType])
-> Response -> Identity Response)
-> ([MediaType] -> Identity [MediaType])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([MediaType] -> Identity [MediaType])
-> Response -> Identity Response
Lens' Response [MediaType]
respTypes (([MediaType] -> Identity [MediaType])
-> Action -> Identity Action)
-> [MediaType] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Proxy (ct : cts) -> [MediaType]
forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy (ct : cts)
t
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> ((Int -> Identity Int) -> Response -> Identity Response)
-> (Int -> Identity Int)
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Int -> Identity Int) -> Response -> Identity Response
Lens' Response Int
respStatus ((Int -> Identity Int) -> Action -> Identity Action)
-> Int -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
status
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& (Response -> Identity Response) -> Action -> Identity Action
Lens' Action Response
response((Response -> Identity Response) -> Action -> Identity Action)
-> (([Header] -> Identity [Header])
-> Response -> Identity Response)
-> ([Header] -> Identity [Header])
-> Action
-> Identity Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([Header] -> Identity [Header]) -> Response -> Identity Response
Lens' Response [Header]
respHeaders (([Header] -> Identity [Header]) -> Action -> Identity Action)
-> [Header] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Header]
hdrs
t :: Proxy (ct : cts)
t = Proxy (ct : cts)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ct ': cts)
hdrs :: [Header]
hdrs = Proxy ls -> [Header]
forall {k} (ls :: k). AllHeaderSamples ls => Proxy ls -> [Header]
allHeaderToSample (Proxy ls
forall {k} (t :: k). Proxy t
Proxy :: Proxy ls)
method' :: ByteString
method' = Proxy method -> ByteString
forall {k} (a :: k). ReflectMethod a => Proxy a -> ByteString
reflectMethod (Proxy method
forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
status :: Int
status = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Proxy status -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy status
forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
p :: Proxy a
p = Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a
instance (ToHttpApiData a, ToSample a, KnownSymbol sym, HasDocs api)
=> HasDocs (Header' mods sym a :> api) where
docsFor :: Proxy (Header' mods sym a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Header' mods sym a :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
action' :: Action
action' = (([Header] -> Identity [Header]) -> Action -> Identity Action)
-> ([Header] -> [Header]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ([Header] -> Identity [Header]) -> Action -> Identity Action
Lens' Action [Header]
headers ([Header] -> Header -> [Header]
forall s a. Snoc s s a a => s -> a -> s
|> (CI ByteString
headerName, ByteString
headerVal)) Action
action
headerName :: CI ByteString
headerName = ByteString -> CI ByteString
forall s. FoldCase s => s -> CI s
CI.mk (ByteString -> CI ByteString)
-> (String -> ByteString) -> String -> CI ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (String -> CI ByteString) -> String -> CI ByteString
forall a b. (a -> b) -> a -> b
$ Proxy sym -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sym
forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
headerVal :: ByteString
headerVal = case Proxy a -> Maybe a
forall a. ToSample a => Proxy a -> Maybe a
toSample (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a) of
Just a
x -> ByteString -> ByteString
forall a b. ConvertibleStrings a b => a -> b
cs (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ a -> ByteString
forall a. ToHttpApiData a => a -> ByteString
toHeader a
x
Maybe a
Nothing -> ByteString
"<no header sample provided>"
instance (KnownSymbol sym, ToParam (QueryParam' mods sym a), HasDocs api)
=> HasDocs (QueryParam' mods sym a :> api) where
docsFor :: Proxy (QueryParam' mods sym a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (QueryParam' mods sym a :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
paramP :: Proxy (QueryParam' mods sym a)
paramP = Proxy (QueryParam' mods sym a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (QueryParam' mods sym a)
action' :: Action
action' = ASetter Action Action [DocQueryParam] [DocQueryParam]
-> ([DocQueryParam] -> [DocQueryParam]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocQueryParam] [DocQueryParam]
Lens' Action [DocQueryParam]
params ([DocQueryParam] -> DocQueryParam -> [DocQueryParam]
forall s a. Snoc s s a a => s -> a -> s
|> Proxy (QueryParam' mods sym a) -> DocQueryParam
forall {k} (t :: k). ToParam t => Proxy t -> DocQueryParam
toParam Proxy (QueryParam' mods sym a)
paramP) Action
action
instance (KnownSymbol sym, ToParam (QueryParams sym a), HasDocs api)
=> HasDocs (QueryParams sym a :> api) where
docsFor :: Proxy (QueryParams sym a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (QueryParams sym a :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
paramP :: Proxy (QueryParams sym a)
paramP = Proxy (QueryParams sym a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (QueryParams sym a)
action' :: Action
action' = ASetter Action Action [DocQueryParam] [DocQueryParam]
-> ([DocQueryParam] -> [DocQueryParam]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocQueryParam] [DocQueryParam]
Lens' Action [DocQueryParam]
params ([DocQueryParam] -> DocQueryParam -> [DocQueryParam]
forall s a. Snoc s s a a => s -> a -> s
|> Proxy (QueryParams sym a) -> DocQueryParam
forall {k} (t :: k). ToParam t => Proxy t -> DocQueryParam
toParam Proxy (QueryParams sym a)
paramP) Action
action
instance (KnownSymbol sym, ToParam (QueryFlag sym), HasDocs api)
=> HasDocs (QueryFlag sym :> api) where
docsFor :: Proxy (QueryFlag sym :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (QueryFlag sym :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
paramP :: Proxy (QueryFlag sym)
paramP = Proxy (QueryFlag sym)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (QueryFlag sym)
action' :: Action
action' = ASetter Action Action [DocQueryParam] [DocQueryParam]
-> ([DocQueryParam] -> [DocQueryParam]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocQueryParam] [DocQueryParam]
Lens' Action [DocQueryParam]
params ([DocQueryParam] -> DocQueryParam -> [DocQueryParam]
forall s a. Snoc s s a a => s -> a -> s
|> Proxy (QueryFlag sym) -> DocQueryParam
forall {k} (t :: k). ToParam t => Proxy t -> DocQueryParam
toParam Proxy (QueryFlag sym)
paramP) Action
action
instance (ToFragment (Fragment a), HasDocs api)
=> HasDocs (Fragment a :> api) where
docsFor :: Proxy (Fragment a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Fragment a :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
fragmentP :: Proxy (Fragment a)
fragmentP = Proxy (Fragment a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (Fragment a)
action' :: Action
action' = ASetter Action Action (Maybe DocFragment) (Maybe DocFragment)
-> Maybe DocFragment -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Action Action (Maybe DocFragment) (Maybe DocFragment)
Lens' Action (Maybe DocFragment)
fragment (DocFragment -> Maybe DocFragment
forall a. a -> Maybe a
Just (Proxy (Fragment a) -> DocFragment
forall {k} (t :: k). ToFragment t => Proxy t -> DocFragment
toFragment Proxy (Fragment a)
fragmentP)) Action
action
instance HasDocs Raw where
docsFor :: Proxy Raw -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy Raw
_proxy (Endpoint
endpoint, Action
action) DocOptions
_ =
Endpoint -> Action -> API
single Endpoint
endpoint Action
action
instance (KnownSymbol desc, HasDocs api)
=> HasDocs (Description desc :> api) where
docsFor :: Proxy (Description desc :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Description desc :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
action' :: Action
action' = ASetter Action Action [DocNote] [DocNote]
-> ([DocNote] -> [DocNote]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocNote] [DocNote]
Lens' Action [DocNote]
notes ([DocNote] -> DocNote -> [DocNote]
forall s a. Snoc s s a a => s -> a -> s
|> DocNote
note) Action
action
note :: DocNote
note = String -> [String] -> DocNote
DocNote (Proxy desc -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy desc
forall {k} (t :: k). Proxy t
Proxy :: Proxy desc)) []
instance (KnownSymbol desc, HasDocs api)
=> HasDocs (Summary desc :> api) where
docsFor :: Proxy (Summary desc :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Summary desc :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action')
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
action' :: Action
action' = ASetter Action Action [DocNote] [DocNote]
-> ([DocNote] -> [DocNote]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocNote] [DocNote]
Lens' Action [DocNote]
notes ([DocNote] -> DocNote -> [DocNote]
forall s a. Snoc s s a a => s -> a -> s
|> DocNote
note) Action
action
note :: DocNote
note = String -> [String] -> DocNote
DocNote (Proxy desc -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy desc
forall {k} (t :: k). Proxy t
Proxy :: Proxy desc)) []
instance (ToSample a, AllMimeRender (ct ': cts) a, HasDocs api)
=> HasDocs (ReqBody' mods (ct ': cts) a :> api) where
docsFor :: Proxy (ReqBody' mods (ct : cts) a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (ReqBody' mods (ct : cts) a :> api)
Proxy (Endpoint
endpoint, Action
action) opts :: DocOptions
opts@DocOptions{Int
_maxSamples :: DocOptions -> Int
_maxSamples :: Int
..} =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action') DocOptions
opts
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
action' :: Action
action' :: Action
action' = Action
action Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& ([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action -> Identity Action
Lens' Action [(Text, MediaType, ByteString)]
rqbody (([(Text, MediaType, ByteString)]
-> Identity [(Text, MediaType, ByteString)])
-> Action -> Identity Action)
-> [(Text, MediaType, ByteString)] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
-> [(Text, MediaType, ByteString)]
-> [(Text, MediaType, ByteString)]
forall a. Int -> [a] -> [a]
take Int
_maxSamples (Proxy (ct : cts) -> Proxy a -> [(Text, MediaType, ByteString)]
forall ct (cts :: [*]) a.
(ToSample a, AllMimeRender (ct : cts) a) =>
Proxy (ct : cts) -> Proxy a -> [(Text, MediaType, ByteString)]
sampleByteStrings Proxy (ct : cts)
t Proxy a
p)
Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& ([MediaType] -> Identity [MediaType]) -> Action -> Identity Action
Lens' Action [MediaType]
rqtypes (([MediaType] -> Identity [MediaType])
-> Action -> Identity Action)
-> [MediaType] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Proxy (ct : cts) -> [MediaType]
forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy (ct : cts)
t
t :: Proxy (ct : cts)
t = Proxy (ct : cts)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ct ': cts)
p :: Proxy a
p = Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a
instance (HasDocs api, Accept ctype) => HasDocs (StreamBody' mods framing ctype a :> api) where
docsFor :: Proxy (StreamBody' mods framing ctype a :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (StreamBody' mods framing ctype a :> api)
Proxy (Endpoint
endpoint, Action
action) DocOptions
opts =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint, Action
action') DocOptions
opts
where
subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
action' :: Action
action' :: Action
action' = Action
action Action -> (Action -> Action) -> Action
forall a b. a -> (a -> b) -> b
& ([MediaType] -> Identity [MediaType]) -> Action -> Identity Action
Lens' Action [MediaType]
rqtypes (([MediaType] -> Identity [MediaType])
-> Action -> Identity Action)
-> [MediaType] -> Action -> Action
forall s t a b. ASetter s t a b -> b -> s -> t
.~ NonEmpty MediaType -> [MediaType]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (Proxy ctype -> NonEmpty MediaType
forall {k} (ctype :: k).
Accept ctype =>
Proxy ctype -> NonEmpty MediaType
contentTypes Proxy ctype
t)
t :: Proxy ctype
t = Proxy ctype
forall {k} (t :: k). Proxy t
Proxy :: Proxy ctype
instance (KnownSymbol path, HasDocs api) => HasDocs (path :> api) where
docsFor :: Proxy (path :> api) -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (path :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
subApiP (Endpoint
endpoint', Action
action)
where subApiP :: Proxy api
subApiP = Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api
endpoint' :: Endpoint
endpoint' = Endpoint
endpoint Endpoint -> (Endpoint -> Endpoint) -> Endpoint
forall a b. a -> (a -> b) -> b
& ASetter Endpoint Endpoint [String] [String]
Lens' Endpoint [String]
path ASetter Endpoint Endpoint [String] [String]
-> [String] -> Endpoint -> Endpoint
forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [Proxy path -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy path
pa]
pa :: Proxy path
pa = Proxy path
forall {k} (t :: k). Proxy t
Proxy :: Proxy path
instance HasDocs api => HasDocs (RemoteHost :> api) where
docsFor :: Proxy (RemoteHost :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (RemoteHost :> api)
Proxy (Endpoint, Action)
ep =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Endpoint, Action)
ep
instance HasDocs api => HasDocs (IsSecure :> api) where
docsFor :: Proxy (IsSecure :> api) -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (IsSecure :> api)
Proxy (Endpoint, Action)
ep =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Endpoint, Action)
ep
instance HasDocs api => HasDocs (HttpVersion :> api) where
docsFor :: Proxy (HttpVersion :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (HttpVersion :> api)
Proxy (Endpoint, Action)
ep =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Endpoint, Action)
ep
instance HasDocs api => HasDocs (Vault :> api) where
docsFor :: Proxy (Vault :> api) -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (Vault :> api)
Proxy (Endpoint, Action)
ep =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Endpoint, Action)
ep
instance HasDocs api => HasDocs (WithNamedContext name context api) where
docsFor :: Proxy (WithNamedContext name context api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (WithNamedContext name context api)
Proxy = Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
instance HasDocs api => HasDocs (WithResource res :> api) where
docsFor :: Proxy (WithResource res :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (WithResource res :> api)
Proxy = Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api)
instance (ToAuthInfo (BasicAuth realm usr), HasDocs api) => HasDocs (BasicAuth realm usr :> api) where
docsFor :: Proxy (BasicAuth realm usr :> api)
-> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (BasicAuth realm usr :> api)
Proxy (Endpoint
endpoint, Action
action) =
Proxy api -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy api
forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Endpoint
endpoint, Action
action')
where
authProxy :: Proxy (BasicAuth realm usr)
authProxy = Proxy (BasicAuth realm usr)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (BasicAuth realm usr)
action' :: Action
action' = ASetter Action Action [DocAuthentication] [DocAuthentication]
-> ([DocAuthentication] -> [DocAuthentication]) -> Action -> Action
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter Action Action [DocAuthentication] [DocAuthentication]
Lens' Action [DocAuthentication]
authInfo ([DocAuthentication] -> DocAuthentication -> [DocAuthentication]
forall s a. Snoc s s a a => s -> a -> s
|> Proxy (BasicAuth realm usr) -> DocAuthentication
forall {k} (a :: k). ToAuthInfo a => Proxy a -> DocAuthentication
toAuthInfo Proxy (BasicAuth realm usr)
authProxy) Action
action
instance
( HasDocs (ToServantApi api)
, ErrorIfNoGeneric api
) => HasDocs (NamedRoutes api) where
docsFor :: Proxy (NamedRoutes api) -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy (NamedRoutes api)
Proxy = Proxy (ToServantApi api) -> (Endpoint, Action) -> DocOptions -> API
forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (Proxy (ToServantApi api)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ToServantApi api))
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 (NonEmpty 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)