{-# 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

-- | An 'Endpoint' type that holds the 'path' and the 'method'.
--
-- Gets used as the key in the 'API' hashmap. Modify 'defEndpoint'
-- or any 'Endpoint' value you want using the 'path' and 'method'
-- lenses to tweak.
--
-- >>> defEndpoint
-- "GET" /
--
-- >>> defEndpoint & path <>~ ["foo"]
-- "GET" /foo
--
-- >>> defEndpoint & path <>~ ["foo"] & method .~ HTTP.methodPost
-- "POST" /foo
--
data Endpoint = Endpoint
  { Endpoint -> [String]
_path   :: [String]      -- type collected
  , Endpoint -> Method
_method :: HTTP.Method   -- type collected
  } deriving (Endpoint -> Endpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Endpoint -> Endpoint -> Bool
$c/= :: Endpoint -> Endpoint -> Bool
== :: Endpoint -> Endpoint -> Bool
$c== :: Endpoint -> Endpoint -> Bool
Eq, Eq 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
min :: Endpoint -> Endpoint -> Endpoint
$cmin :: Endpoint -> Endpoint -> Endpoint
max :: Endpoint -> Endpoint -> Endpoint
$cmax :: Endpoint -> Endpoint -> Endpoint
>= :: Endpoint -> Endpoint -> Bool
$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
compare :: Endpoint -> Endpoint -> Ordering
$ccompare :: Endpoint -> Endpoint -> Ordering
Ord, 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
$cto :: forall x. Rep Endpoint x -> Endpoint
$cfrom :: forall x. Endpoint -> Rep Endpoint x
Generic)

instance Show Endpoint where
  show :: Endpoint -> String
show (Endpoint [String]
p Method
m) =
    forall a. Show a => a -> String
show Method
m forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ [String] -> String
showPath [String]
p

-- |
-- Render a path as a '/'-delimited string
--
showPath :: [String] -> String
showPath :: [String] -> String
showPath [] = String
"/"
showPath [String]
ps = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Char
'/' forall a. a -> [a] -> [a]
:) [String]
ps

-- | An 'Endpoint' whose path is `"/"` and whose method is @GET@
--
-- Here's how you can modify it:
--
-- >>> defEndpoint
-- "GET" /
--
-- >>> defEndpoint & path <>~ ["foo"]
-- "GET" /foo
--
-- >>> defEndpoint & path <>~ ["foo"] & method .~ HTTP.methodPost
-- "POST" /foo
--
defEndpoint :: Endpoint
defEndpoint :: Endpoint
defEndpoint = [String] -> Method -> Endpoint
Endpoint [] Method
HTTP.methodGet

instance Hashable Endpoint

-- | Our API documentation type, a product of top-level information and a good
-- old hashmap from 'Endpoint' to 'Action'
data API = API
  { API -> [DocIntro]
_apiIntros    :: [DocIntro]
  , API -> HashMap Endpoint Action
_apiEndpoints :: HashMap Endpoint Action
  } deriving (API -> API -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: API -> API -> Bool
$c/= :: API -> API -> Bool
== :: API -> API -> Bool
$c== :: API -> API -> Bool
Eq, Int -> API -> ShowS
[API] -> ShowS
API -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [API] -> ShowS
$cshowList :: [API] -> ShowS
show :: API -> String
$cshow :: API -> String
showsPrec :: Int -> API -> ShowS
$cshowsPrec :: Int -> API -> ShowS
Show)

instance Semigroup API where
    <> :: 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 forall a. Monoid a => a -> a -> a
`mappend` [DocIntro]
a2)
                                        (forall k v.
(Eq k, Hashable 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 forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty

-- | An empty 'API'
emptyAPI :: API
emptyAPI :: API
emptyAPI = forall a. Monoid a => a
mempty

-- | A type to represent captures. Holds the name of the capture
--   and a description.
--
-- Write a 'ToCapture' instance for your captured types.
data DocCapture = DocCapture
  { DocCapture -> String
_capSymbol :: String -- type supplied
  , DocCapture -> String
_capDesc   :: String -- user supplied
  } deriving (DocCapture -> DocCapture -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocCapture -> DocCapture -> Bool
$c/= :: DocCapture -> DocCapture -> Bool
== :: DocCapture -> DocCapture -> Bool
$c== :: DocCapture -> DocCapture -> Bool
Eq, Eq 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
min :: DocCapture -> DocCapture -> DocCapture
$cmin :: DocCapture -> DocCapture -> DocCapture
max :: DocCapture -> DocCapture -> DocCapture
$cmax :: DocCapture -> DocCapture -> DocCapture
>= :: DocCapture -> DocCapture -> Bool
$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
compare :: DocCapture -> DocCapture -> Ordering
$ccompare :: DocCapture -> DocCapture -> Ordering
Ord, Int -> DocCapture -> ShowS
[DocCapture] -> ShowS
DocCapture -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocCapture] -> ShowS
$cshowList :: [DocCapture] -> ShowS
show :: DocCapture -> String
$cshow :: DocCapture -> String
showsPrec :: Int -> DocCapture -> ShowS
$cshowsPrec :: Int -> DocCapture -> ShowS
Show)

-- | A type to represent a /GET/ (or other possible 'HTTP.Method')
--   parameter from the Query String. Holds its name, the possible
--   values (leave empty if there isn't a finite number of them), and
--   a description of how it influences the output or behavior.
--
-- Write a 'ToParam' instance for your GET parameter types
data DocQueryParam = DocQueryParam
  { DocQueryParam -> String
_paramName   :: String   -- type supplied
  , DocQueryParam -> [String]
_paramValues :: [String] -- user supplied
  , DocQueryParam -> String
_paramDesc   :: String   -- user supplied
  , DocQueryParam -> ParamKind
_paramKind   :: ParamKind
  } deriving (DocQueryParam -> DocQueryParam -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocQueryParam -> DocQueryParam -> Bool
$c/= :: DocQueryParam -> DocQueryParam -> Bool
== :: DocQueryParam -> DocQueryParam -> Bool
$c== :: DocQueryParam -> DocQueryParam -> Bool
Eq, Eq 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
min :: DocQueryParam -> DocQueryParam -> DocQueryParam
$cmin :: DocQueryParam -> DocQueryParam -> DocQueryParam
max :: DocQueryParam -> DocQueryParam -> DocQueryParam
$cmax :: DocQueryParam -> DocQueryParam -> DocQueryParam
>= :: DocQueryParam -> DocQueryParam -> Bool
$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
compare :: DocQueryParam -> DocQueryParam -> Ordering
$ccompare :: DocQueryParam -> DocQueryParam -> Ordering
Ord, Int -> DocQueryParam -> ShowS
[DocQueryParam] -> ShowS
DocQueryParam -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocQueryParam] -> ShowS
$cshowList :: [DocQueryParam] -> ShowS
show :: DocQueryParam -> String
$cshow :: DocQueryParam -> String
showsPrec :: Int -> DocQueryParam -> ShowS
$cshowsPrec :: Int -> DocQueryParam -> ShowS
Show)

-- | A type to represent fragment. Holds the name of the fragment and its description.
--
-- Write a 'ToFragment' instance for your fragment types.
data DocFragment = DocFragment
  { DocFragment -> String
_fragSymbol :: String -- type supplied
  , DocFragment -> String
_fragDesc   :: String -- user supplied
  } deriving (DocFragment -> DocFragment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocFragment -> DocFragment -> Bool
$c/= :: DocFragment -> DocFragment -> Bool
== :: DocFragment -> DocFragment -> Bool
$c== :: DocFragment -> DocFragment -> Bool
Eq, Eq 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
min :: DocFragment -> DocFragment -> DocFragment
$cmin :: DocFragment -> DocFragment -> DocFragment
max :: DocFragment -> DocFragment -> DocFragment
$cmax :: DocFragment -> DocFragment -> DocFragment
>= :: DocFragment -> DocFragment -> Bool
$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
compare :: DocFragment -> DocFragment -> Ordering
$ccompare :: DocFragment -> DocFragment -> Ordering
Ord, Int -> DocFragment -> ShowS
[DocFragment] -> ShowS
DocFragment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocFragment] -> ShowS
$cshowList :: [DocFragment] -> ShowS
show :: DocFragment -> String
$cshow :: DocFragment -> String
showsPrec :: Int -> DocFragment -> ShowS
$cshowsPrec :: Int -> DocFragment -> ShowS
Show)

-- | There should be at most one 'Fragment' per API endpoint.
-- So here we are keeping the first occurrence.
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
_ = forall a. a -> Maybe a
Just DocFragment
docFragment

-- | An introductory paragraph for your documentation. You can pass these to
-- 'docsWithIntros'.
data DocIntro = DocIntro
  { DocIntro -> String
_introTitle :: String   -- ^ Appears above the intro blob
  , DocIntro -> [String]
_introBody  :: [String] -- ^ Each String is a paragraph.
  } deriving (DocIntro -> DocIntro -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocIntro -> DocIntro -> Bool
$c/= :: DocIntro -> DocIntro -> Bool
== :: DocIntro -> DocIntro -> Bool
$c== :: DocIntro -> DocIntro -> Bool
Eq, Int -> DocIntro -> ShowS
[DocIntro] -> ShowS
DocIntro -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocIntro] -> ShowS
$cshowList :: [DocIntro] -> ShowS
show :: DocIntro -> String
$cshow :: DocIntro -> String
showsPrec :: Int -> DocIntro -> ShowS
$cshowsPrec :: Int -> DocIntro -> ShowS
Show)

-- | A type to represent Authentication information about an endpoint.
data DocAuthentication = DocAuthentication
  { DocAuthentication -> String
_authIntro        :: String
  , DocAuthentication -> String
_authDataRequired :: String
  } deriving (DocAuthentication -> DocAuthentication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocAuthentication -> DocAuthentication -> Bool
$c/= :: DocAuthentication -> DocAuthentication -> Bool
== :: DocAuthentication -> DocAuthentication -> Bool
$c== :: DocAuthentication -> DocAuthentication -> Bool
Eq, Eq 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
min :: DocAuthentication -> DocAuthentication -> DocAuthentication
$cmin :: DocAuthentication -> DocAuthentication -> DocAuthentication
max :: DocAuthentication -> DocAuthentication -> DocAuthentication
$cmax :: DocAuthentication -> DocAuthentication -> DocAuthentication
>= :: DocAuthentication -> DocAuthentication -> Bool
$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
compare :: DocAuthentication -> DocAuthentication -> Ordering
$ccompare :: DocAuthentication -> DocAuthentication -> Ordering
Ord, Int -> DocAuthentication -> ShowS
[DocAuthentication] -> ShowS
DocAuthentication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocAuthentication] -> ShowS
$cshowList :: [DocAuthentication] -> ShowS
show :: DocAuthentication -> String
$cshow :: DocAuthentication -> String
showsPrec :: Int -> DocAuthentication -> ShowS
$cshowsPrec :: Int -> DocAuthentication -> ShowS
Show)

instance Ord DocIntro where
    compare :: DocIntro -> DocIntro -> Ordering
compare = forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing DocIntro -> String
_introTitle

-- | A type to represent extra notes that may be attached to an 'Action'.
--
-- This is intended to be used when writing your own HasDocs instances to
-- add extra sections to your endpoint's documentation.
data DocNote = DocNote
  { DocNote -> String
_noteTitle :: String
  , DocNote -> [String]
_noteBody  :: [String]
  } deriving (DocNote -> DocNote -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocNote -> DocNote -> Bool
$c/= :: DocNote -> DocNote -> Bool
== :: DocNote -> DocNote -> Bool
$c== :: DocNote -> DocNote -> Bool
Eq, Eq 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
min :: DocNote -> DocNote -> DocNote
$cmin :: DocNote -> DocNote -> DocNote
max :: DocNote -> DocNote -> DocNote
$cmax :: DocNote -> DocNote -> DocNote
>= :: DocNote -> DocNote -> Bool
$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
compare :: DocNote -> DocNote -> Ordering
$ccompare :: DocNote -> DocNote -> Ordering
Ord, Int -> DocNote -> ShowS
[DocNote] -> ShowS
DocNote -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocNote] -> ShowS
$cshowList :: [DocNote] -> ShowS
show :: DocNote -> String
$cshow :: DocNote -> String
showsPrec :: Int -> DocNote -> ShowS
$cshowsPrec :: Int -> DocNote -> ShowS
Show)

-- | Type of extra information that a user may wish to "union" with their
-- documentation.
--
-- These are intended to be built using extraInfo.
-- Multiple ExtraInfo may be combined with the monoid instance.
newtype ExtraInfo api = ExtraInfo (HashMap Endpoint Action)
instance Semigroup (ExtraInfo a) where
    <> :: ExtraInfo a -> ExtraInfo a -> ExtraInfo a
(<>) = forall a. Monoid a => a -> a -> a
mappend
instance Monoid (ExtraInfo a) where
    mempty :: ExtraInfo a
mempty = forall {k} (api :: k). HashMap Endpoint Action -> ExtraInfo api
ExtraInfo forall a. Monoid a => a
mempty
    ExtraInfo HashMap Endpoint Action
a mappend :: ExtraInfo a -> ExtraInfo a -> ExtraInfo a
`mappend` ExtraInfo HashMap Endpoint Action
b =
        forall {k} (api :: k). HashMap Endpoint Action -> ExtraInfo api
ExtraInfo forall a b. (a -> b) -> a -> b
$ forall k v.
(Eq k, Hashable 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

-- | Documentation options.
data DocOptions = DocOptions
  { DocOptions -> Int
_maxSamples :: Int    -- ^ Maximum samples allowed.
  } deriving (Int -> DocOptions -> ShowS
[DocOptions] -> ShowS
DocOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocOptions] -> ShowS
$cshowList :: [DocOptions] -> ShowS
show :: DocOptions -> String
$cshow :: DocOptions -> String
showsPrec :: Int -> DocOptions -> ShowS
$cshowsPrec :: Int -> DocOptions -> ShowS
Show)

-- | Default documentation options.
defaultDocOptions :: DocOptions
defaultDocOptions :: DocOptions
defaultDocOptions = DocOptions
  { _maxSamples :: Int
_maxSamples = Int
5 }

-- | Type of GET (or other 'HTTP.Method') parameter:
--
-- - Normal corresponds to @QueryParam@, i.e your usual GET parameter
-- - List corresponds to @QueryParams@, i.e GET parameters with multiple values
-- - Flag corresponds to @QueryFlag@, i.e a value-less GET parameter
data ParamKind = Normal | List | Flag
  deriving (ParamKind -> ParamKind -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamKind -> ParamKind -> Bool
$c/= :: ParamKind -> ParamKind -> Bool
== :: ParamKind -> ParamKind -> Bool
$c== :: ParamKind -> ParamKind -> Bool
Eq, Eq 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
min :: ParamKind -> ParamKind -> ParamKind
$cmin :: ParamKind -> ParamKind -> ParamKind
max :: ParamKind -> ParamKind -> ParamKind
$cmax :: ParamKind -> ParamKind -> ParamKind
>= :: ParamKind -> ParamKind -> Bool
$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
compare :: ParamKind -> ParamKind -> Ordering
$ccompare :: ParamKind -> ParamKind -> Ordering
Ord, Int -> ParamKind -> ShowS
[ParamKind] -> ShowS
ParamKind -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParamKind] -> ShowS
$cshowList :: [ParamKind] -> ShowS
show :: ParamKind -> String
$cshow :: ParamKind -> String
showsPrec :: Int -> ParamKind -> ShowS
$cshowsPrec :: Int -> ParamKind -> ShowS
Show)

-- | A type to represent an HTTP response. Has an 'Int' status, a list of
-- possible 'MediaType's, and a list of example 'ByteString' response bodies.
-- Tweak 'defResponse' using the 'respStatus', 'respTypes' and 'respBody'
-- lenses if you want.
--
-- If you want to respond with a non-empty response body, you'll most likely
-- want to write a 'ToSample' instance for the type that'll be represented
-- as encoded data in the response.
--
-- Can be tweaked with four lenses.
--
-- >>> defResponse
-- Response {_respStatus = 200, _respTypes = [], _respBody = [], _respHeaders = []}
--
-- >>> defResponse & respStatus .~ 204 & respBody .~ [("If everything goes well", "application/json", "{ \"status\": \"ok\" }")]
-- Response {_respStatus = 204, _respTypes = [], _respBody = [("If everything goes well",application/json,"{ \"status\": \"ok\" }")], _respHeaders = []}
--
data Response = Response
  { Response -> Int
_respStatus  :: Int
  , Response -> [MediaType]
_respTypes   :: [M.MediaType]
  , Response -> [(Text, MediaType, ByteString)]
_respBody    :: [(Text, M.MediaType, ByteString)]
  , Response -> [Header]
_respHeaders :: [HTTP.Header]
  } deriving (Response -> Response -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Response -> Response -> Bool
$c/= :: Response -> Response -> Bool
== :: Response -> Response -> Bool
$c== :: Response -> Response -> Bool
Eq, Eq 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
min :: Response -> Response -> Response
$cmin :: Response -> Response -> Response
max :: Response -> Response -> Response
$cmax :: Response -> Response -> Response
>= :: Response -> Response -> Bool
$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
compare :: Response -> Response -> Ordering
$ccompare :: Response -> Response -> Ordering
Ord, Int -> Response -> ShowS
[Response] -> ShowS
Response -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Response] -> ShowS
$cshowList :: [Response] -> ShowS
show :: Response -> String
$cshow :: Response -> String
showsPrec :: Int -> Response -> ShowS
$cshowsPrec :: Int -> Response -> ShowS
Show)

-- | Combine two Responses, we can't make a monoid because merging Status breaks
-- the laws.
--
-- As such, we invent a non-commutative, left associative operation
-- 'combineResponse' to mush two together taking the status from the very left.
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 forall a. Semigroup a => a -> a -> a
<> [MediaType]
ts') ([(Text, MediaType, ByteString)]
bs forall a. Semigroup a => a -> a -> a
<> [(Text, MediaType, ByteString)]
bs') ([Header]
hs forall a. Semigroup a => a -> a -> a
<> [Header]
hs')

-- | Default response: status code 200, no response body.
--
-- Can be tweaked with four lenses.
--
-- >>> defResponse
-- Response {_respStatus = 200, _respTypes = [], _respBody = [], _respHeaders = []}
--
-- >>> defResponse & respStatus .~ 204
-- Response {_respStatus = 204, _respTypes = [], _respBody = [], _respHeaders = []}
--
defResponse :: Response
defResponse :: Response
defResponse = Response
  { _respStatus :: Int
_respStatus  = Int
200
  , _respTypes :: [MediaType]
_respTypes   = []
  , _respBody :: [(Text, MediaType, ByteString)]
_respBody    = []
  , _respHeaders :: [Header]
_respHeaders = []
  }

-- | A datatype that represents everything that can happen
-- at an endpoint, with its lenses:
--
-- - List of captures ('captures')
-- - List of GET (or other 'HTTP.Method') parameters ('params')
-- - What the request body should look like, if any is requested ('rqbody')
-- - What the response should be if everything goes well ('response')
--
-- You can tweak an 'Action' (like the default 'defAction') with these lenses
-- to transform an action and add some information to it.
data Action = Action
  { Action -> [DocAuthentication]
_authInfo :: [DocAuthentication]         -- user supplied info
  , Action -> [DocCapture]
_captures :: [DocCapture]                -- type collected + user supplied info
  , Action -> [Header]
_headers  :: [HTTP.Header]               -- type collected
  , Action -> [DocQueryParam]
_params   :: [DocQueryParam]             -- type collected + user supplied info
  , Action -> Maybe DocFragment
_fragment :: Maybe DocFragment           -- type collected + user supplied info
  , Action -> [DocNote]
_notes    :: [DocNote]                   -- user supplied
  , Action -> [(String, [DocQueryParam])]
_mxParams :: [(String, [DocQueryParam])] -- type collected + user supplied info
  , Action -> [MediaType]
_rqtypes  :: [M.MediaType]               -- type collected
  , Action -> [(Text, MediaType, ByteString)]
_rqbody   :: [(Text, M.MediaType, ByteString)] -- user supplied
  , Action -> Response
_response :: Response                    -- user supplied
  } deriving (Action -> Action -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Action -> Action -> Bool
$c/= :: Action -> Action -> Bool
== :: Action -> Action -> Bool
$c== :: Action -> Action -> Bool
Eq, Eq 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
min :: Action -> Action -> Action
$cmin :: Action -> Action -> Action
max :: Action -> Action -> Action
$cmax :: Action -> Action -> Action
>= :: Action -> Action -> Bool
$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
compare :: Action -> Action -> Ordering
$ccompare :: Action -> Action -> Ordering
Ord, Int -> Action -> ShowS
[Action] -> ShowS
Action -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Action] -> ShowS
$cshowList :: [Action] -> ShowS
show :: Action -> String
$cshow :: Action -> String
showsPrec :: Int -> Action -> ShowS
$cshowsPrec :: Int -> Action -> ShowS
Show)

-- | Combine two Actions, we can't make a monoid as merging Response breaks the
-- laws.
--
-- As such, we invent a non-commutative, left associative operation
-- 'combineAction' to mush two together taking the response from the very left.
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 forall a. Semigroup a => a -> a -> a
<> [DocAuthentication]
a') ([DocCapture]
c forall a. Semigroup a => a -> a -> a
<> [DocCapture]
c') ([Header]
h forall a. Semigroup a => a -> a -> a
<> [Header]
h') ([DocQueryParam]
p forall a. Semigroup a => a -> a -> a
<> [DocQueryParam]
p') (Maybe DocFragment
f Maybe DocFragment -> Maybe DocFragment -> Maybe DocFragment
`combineFragment` Maybe DocFragment
f') ([DocNote]
n forall a. Semigroup a => a -> a -> a
<> [DocNote]
n') ([(String, [DocQueryParam])]
m forall a. Semigroup a => a -> a -> a
<> [(String, [DocQueryParam])]
m') ([MediaType]
ts forall a. Semigroup a => a -> a -> a
<> [MediaType]
ts') ([(Text, MediaType, ByteString)]
body forall a. Semigroup a => a -> a -> a
<> [(Text, MediaType, ByteString)]
body') (Response
resp Response -> Response -> Response
`combineResponse` Response
resp')

-- | Default 'Action'. Has no 'captures', no query 'params', expects
-- no request body ('rqbody') and the typical response is 'defResponse'.
--
-- Tweakable with lenses.
--
-- >>> defAction
-- Action {_authInfo = [], _captures = [], _headers = [], _params = [], _fragment = Nothing, _notes = [], _mxParams = [], _rqtypes = [], _rqbody = [], _response = Response {_respStatus = 200, _respTypes = [], _respBody = [], _respHeaders = []}}
--
-- >>> defAction & response.respStatus .~ 201
-- Action {_authInfo = [], _captures = [], _headers = [], _params = [], _fragment = Nothing, _notes = [], _mxParams = [], _rqtypes = [], _rqbody = [], _response = Response {_respStatus = 201, _respTypes = [], _respBody = [], _respHeaders = []}}
--
defAction :: Action
defAction :: Action
defAction =
  [DocAuthentication]
-> [DocCapture]
-> [Header]
-> [DocQueryParam]
-> Maybe DocFragment
-> [DocNote]
-> [(String, [DocQueryParam])]
-> [MediaType]
-> [(Text, MediaType, ByteString)]
-> Response
-> Action
Action []
         []
         []
         []
         forall a. Maybe a
Nothing
         []
         []
         []
         []
         Response
defResponse

-- | Create an API that's comprised of a single endpoint.
--   'API' is a 'Monoid', so combine multiple endpoints with
--   'mappend' or '<>'.
single :: Endpoint -> Action -> API
single :: Endpoint -> Action -> API
single Endpoint
e Action
a = [DocIntro] -> HashMap Endpoint Action -> API
API forall a. Monoid a => a
mempty (forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton Endpoint
e Action
a)

-- | How many content-types for each example should be shown?
--
--   @since 0.11.1
data ShowContentTypes = AllContentTypes  -- ^ For each example, show each content type.
                      | FirstContentType -- ^ For each example, show only one content type.
  deriving (ShowContentTypes -> ShowContentTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShowContentTypes -> ShowContentTypes -> Bool
$c/= :: ShowContentTypes -> ShowContentTypes -> Bool
== :: ShowContentTypes -> ShowContentTypes -> Bool
$c== :: ShowContentTypes -> ShowContentTypes -> Bool
Eq, Eq 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
min :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
$cmin :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
max :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
$cmax :: ShowContentTypes -> ShowContentTypes -> ShowContentTypes
>= :: ShowContentTypes -> ShowContentTypes -> Bool
$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
compare :: ShowContentTypes -> ShowContentTypes -> Ordering
$ccompare :: ShowContentTypes -> ShowContentTypes -> Ordering
Ord, Int -> ShowContentTypes -> ShowS
[ShowContentTypes] -> ShowS
ShowContentTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShowContentTypes] -> ShowS
$cshowList :: [ShowContentTypes] -> ShowS
show :: ShowContentTypes -> String
$cshow :: ShowContentTypes -> String
showsPrec :: Int -> ShowContentTypes -> ShowS
$cshowsPrec :: Int -> ShowContentTypes -> ShowS
Show, ReadPrec [ShowContentTypes]
ReadPrec ShowContentTypes
Int -> ReadS ShowContentTypes
ReadS [ShowContentTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ShowContentTypes]
$creadListPrec :: ReadPrec [ShowContentTypes]
readPrec :: ReadPrec ShowContentTypes
$creadPrec :: ReadPrec ShowContentTypes
readList :: ReadS [ShowContentTypes]
$creadList :: ReadS [ShowContentTypes]
readsPrec :: Int -> ReadS ShowContentTypes
$creadsPrec :: Int -> ReadS ShowContentTypes
Read, ShowContentTypes
forall a. a -> a -> Bounded a
maxBound :: ShowContentTypes
$cmaxBound :: ShowContentTypes
minBound :: ShowContentTypes
$cminBound :: ShowContentTypes
Bounded, Int -> ShowContentTypes
ShowContentTypes -> Int
ShowContentTypes -> [ShowContentTypes]
ShowContentTypes -> ShowContentTypes
ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
ShowContentTypes
-> ShowContentTypes -> ShowContentTypes -> [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
enumFromThenTo :: ShowContentTypes
-> ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
$cenumFromThenTo :: ShowContentTypes
-> ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
enumFromTo :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
$cenumFromTo :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
enumFromThen :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
$cenumFromThen :: ShowContentTypes -> ShowContentTypes -> [ShowContentTypes]
enumFrom :: ShowContentTypes -> [ShowContentTypes]
$cenumFrom :: ShowContentTypes -> [ShowContentTypes]
fromEnum :: ShowContentTypes -> Int
$cfromEnum :: ShowContentTypes -> Int
toEnum :: Int -> ShowContentTypes
$ctoEnum :: Int -> ShowContentTypes
pred :: ShowContentTypes -> ShowContentTypes
$cpred :: ShowContentTypes -> ShowContentTypes
succ :: ShowContentTypes -> ShowContentTypes
$csucc :: ShowContentTypes -> ShowContentTypes
Enum)

-- | Customise how an 'API' is converted into documentation.
--
--   @since 0.11.1
data RenderingOptions = RenderingOptions
  { RenderingOptions -> ShowContentTypes
_requestExamples    :: !ShowContentTypes
    -- ^ How many content types to display for request body examples?
  , RenderingOptions -> ShowContentTypes
_responseExamples   :: !ShowContentTypes
    -- ^ How many content types to display for response body examples?
  , RenderingOptions -> Maybe String
_notesHeading       :: !(Maybe String)
    -- ^ Optionally group all 'notes' together under a common heading.
  , RenderingOptions -> Maybe String
_renderCurlBasePath :: !(Maybe String)
    -- ^ Optionally render example curl requests under a common base path (e.g. `http://localhost:80`).
  } deriving (Int -> RenderingOptions -> ShowS
[RenderingOptions] -> ShowS
RenderingOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RenderingOptions] -> ShowS
$cshowList :: [RenderingOptions] -> ShowS
show :: RenderingOptions -> String
$cshow :: RenderingOptions -> String
showsPrec :: Int -> RenderingOptions -> ShowS
$cshowsPrec :: Int -> RenderingOptions -> ShowS
Show)

-- | Default API generation options.
--
--   All content types are shown for both 'requestExamples' and
--   'responseExamples'; 'notesHeading' is set to 'Nothing'
--   (i.e. un-grouped).
--
--   @since 0.11.1
defRenderingOptions :: RenderingOptions
defRenderingOptions :: RenderingOptions
defRenderingOptions = RenderingOptions
  { _requestExamples :: ShowContentTypes
_requestExamples    = ShowContentTypes
AllContentTypes
  , _responseExamples :: ShowContentTypes
_responseExamples   = ShowContentTypes
AllContentTypes
  , _notesHeading :: Maybe String
_notesHeading       = forall a. Maybe a
Nothing
  , _renderCurlBasePath :: Maybe String
_renderCurlBasePath = forall a. Maybe a
Nothing
  }

-- gimme some lenses
makeLenses ''DocAuthentication
makeLenses ''DocOptions
makeLenses ''API
makeLenses ''Endpoint
makeLenses ''DocCapture
makeLenses ''DocQueryParam
makeLenses ''DocFragment
makeLenses ''DocIntro
makeLenses ''DocNote
makeLenses ''Response
makeLenses ''Action
makeLenses ''RenderingOptions

-- | Generate the docs for a given API that implements 'HasDocs'. This is the
-- default way to create documentation.
--
-- > docs == docsWithOptions defaultDocOptions
--
docs :: HasDocs api => Proxy api -> API
docs :: forall {k} (api :: k). HasDocs api => Proxy api -> API
docs Proxy api
p = forall {k} (api :: k).
HasDocs api =>
Proxy api -> DocOptions -> API
docsWithOptions Proxy api
p DocOptions
defaultDocOptions

-- | Generate the docs for a given API that implements 'HasDocs'.
docsWithOptions :: HasDocs api => Proxy api -> DocOptions -> API
docsWithOptions :: forall {k} (api :: k).
HasDocs api =>
Proxy api -> DocOptions -> API
docsWithOptions Proxy api
p = forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy api
p (Endpoint
defEndpoint, Action
defAction)

-- | Create an 'ExtraInfo' that is guaranteed to be within the given API layout.
--
-- The safety here is to ensure that you only add custom documentation to an
-- endpoint that actually exists within your API.
--
-- > extra :: ExtraInfo TestApi
-- > extra =
-- >     extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete)) $
-- >              defAction & headers <>~ [("X-Num-Unicorns", 1)]
-- >                        & notes   <>~ [ DocNote "Title" ["This is some text"]
-- >                                      , DocNote "Second section" ["And some more"]
-- >                                      ]

extraInfo :: (IsIn endpoint api, HasLink endpoint, HasDocs endpoint)
          => Proxy endpoint -> Action -> ExtraInfo api
extraInfo :: forall endpoint api.
(IsIn endpoint api, HasLink endpoint, HasDocs endpoint) =>
Proxy endpoint -> Action -> ExtraInfo api
extraInfo Proxy endpoint
p Action
action =
    let api :: API
api = forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy endpoint
p (Endpoint
defEndpoint, Action
defAction) DocOptions
defaultDocOptions
    -- Assume one endpoint, HasLink constraint means that we should only ever
    -- point at one endpoint.
    in forall {k} (api :: k). HashMap Endpoint Action -> ExtraInfo api
ExtraInfo forall a b. (a -> b) -> a -> b
$ API
api forall s a. s -> Getting a s a -> a
^. Lens' API (HashMap Endpoint Action)
apiEndpoints forall a b. a -> (a -> b) -> b
& forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
traversed forall s t a b. ASetter s t a b -> b -> s -> t
.~ Action
action

-- | Generate documentation given some extra introductions (in the form of
-- 'DocInfo') and some extra endpoint documentation (in the form of
-- 'ExtraInfo'.
--
-- The extra introductions will be prepended to the top of the documentation,
-- before the specific endpoint documentation. The extra endpoint documentation
-- will be "unioned" with the automatically generated endpoint documentation.
--
-- You are expected to build up the ExtraInfo with the Monoid instance and
-- 'extraInfo'.
--
-- If you only want to add an introduction, use 'docsWithIntros'.
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 =
    forall {k} (api :: k).
HasDocs api =>
Proxy api -> DocOptions -> API
docsWithOptions Proxy api
p DocOptions
opts
      forall a b. a -> (a -> b) -> b
& Lens' API [DocIntro]
apiIntros forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [DocIntro]
intros
      forall a b. a -> (a -> b) -> b
& Lens' API (HashMap Endpoint Action)
apiEndpoints forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall k v.
(Eq k, Hashable k) =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
HM.unionWith (forall a b c. (a -> b -> c) -> b -> a -> c
flip Action -> Action -> Action
combineAction) HashMap Endpoint Action
endpoints


-- | Generate the docs for a given API that implements 'HasDocs' with any
-- number of introduction(s)
docsWithIntros :: HasDocs api => [DocIntro] -> Proxy api -> API
docsWithIntros :: forall {k} (api :: k).
HasDocs api =>
[DocIntro] -> Proxy api -> API
docsWithIntros [DocIntro]
intros = forall {k} (api :: k).
HasDocs api =>
DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API
docsWith DocOptions
defaultDocOptions [DocIntro]
intros forall a. Monoid a => a
mempty

-- | The class that abstracts away the impact of API combinators
--   on documentation generation.
class HasDocs api where
  docsFor :: Proxy api -> (Endpoint, Action) -> DocOptions -> API

-- | The class that lets us display a sample input or output in the supported
-- content-types when generating documentation for endpoints that either:
--
-- - expect a request body, or
-- - return a non empty response body
--
-- Example of an instance:
--
-- > {-# LANGUAGE DeriveGeneric #-}
-- > {-# LANGUAGE OverloadedStrings #-}
-- >
-- > import Data.Aeson
-- > import Data.Text
-- > import GHC.Generics
-- >
-- > data Greet = Greet { _msg :: Text }
-- >   deriving (Generic, Show)
-- >
-- > instance FromJSON Greet
-- > instance ToJSON Greet
-- >
-- > instance ToSample Greet where
-- >   toSamples _ = singleSample g
-- >
-- >     where g = Greet "Hello, haskeller!"
--
-- You can also instantiate this class using 'toSamples' instead of
-- 'toSample': it lets you specify different responses along with
-- some context (as 'Text') that explains when you're supposed to
-- get the corresponding response.
class ToSample a where
  toSamples :: Proxy a -> [(Text, a)]
  default toSamples :: (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
  toSamples = forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
defaultSamples

-- | Sample input or output (if there is at least one).
toSample :: forall a. ToSample a => Proxy a -> Maybe a
toSample :: forall a. ToSample a => Proxy a -> Maybe a
toSample Proxy a
_ = forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. [a] -> Maybe a
listToMaybe (forall a. ToSample a => Proxy a -> [(Text, a)]
toSamples (forall {k} (t :: k). Proxy t
Proxy :: Proxy a))

-- | No samples.
noSamples :: [(Text, a)]
noSamples :: forall a. [(Text, a)]
noSamples = forall (f :: * -> *) a. Alternative f => f a
empty

-- | Single sample without description.
singleSample :: a -> [(Text, a)]
singleSample :: forall a. a -> [(Text, a)]
singleSample a
x = [(Text
"", a
x)]

-- | Samples without documentation.
samples :: [a] -> [(Text, a)]
samples :: forall a. [a] -> [(Text, a)]
samples = forall a b. (a -> b) -> [a] -> [b]
map (Text
"",)

-- | Default sample Generic-based inputs/outputs.
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
_ = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall a x. Generic a => Rep a x -> a
G.to forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
gtoSamples (forall {k} (t :: k). Proxy t
Proxy :: Proxy (Rep a))

-- | @'ToSample'@ for Generics.
--
-- Note: we use combinators from "Universe.Data.Helpers" for more productive sample generation.
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
_ = forall a. a -> [(Text, a)]
singleSample 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
_ = 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)
_ = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
U.cartesianProduct 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 = forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
gtoSamples (forall {k} (t :: k). Proxy t
Proxy :: Proxy p)
      qs :: [(Text, q x)]
qs = forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
gtoSamples (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 forall a. Semigroup a => a -> a -> a
<> Text
tb, f p
a forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: g p
b)
        | Bool
otherwise              = (Text
ta forall a. Semigroup a => a -> a -> a
<> Text
", " forall a. Semigroup a => a -> a -> a
<> Text
tb, f p
a 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 forall a. [a] -> [a] -> [a]
U.+++ [(Text, (:+:) p q x)]
rights
    where
      lefts :: [(Text, (:+:) p q x)]
lefts  = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
gtoSamples (forall {k} (t :: k). Proxy t
Proxy :: Proxy p)
      rights :: [(Text, (:+:) p q x)]
rights = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
gtoSamples (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)
_ = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall k i c (p :: k). c -> K1 i c p
K1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. ToSample a => Proxy a -> [(Text, a)]
toSamples (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)
_ = forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {k} (t :: k -> *) (proxy :: (k -> *) -> *) (x :: k).
GToSample t =>
proxy t -> [(Text, t x)]
gtoSamples (forall {k} (t :: k). Proxy t
Proxy :: Proxy f)


class AllHeaderSamples ls where
    allHeaderToSample :: 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 (forall a. ToSample a => Proxy a -> Maybe a
toSample (forall {k} (t :: k). Proxy t
Proxy :: Proxy l)) forall a. a -> [a] -> [a]
:
                          forall {k} (ls :: k). AllHeaderSamples ls => Proxy ls -> [Header]
allHeaderToSample (forall {k} (t :: k). Proxy t
Proxy :: Proxy ls)
      where headerName :: CI Method
headerName = forall s. FoldCase s => s -> CI s
CI.mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. ConvertibleStrings a b => a -> b
cs forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy h)
            mkHeader :: Maybe l -> Header
mkHeader (Just l
x) = (CI Method
headerName, forall a b. ConvertibleStrings a b => a -> b
cs forall a b. (a -> b) -> a -> b
$ forall a. ToHttpApiData a => a -> Method
toHeader l
x)
            mkHeader Maybe l
Nothing  = (CI Method
headerName, Method
"<no header sample provided>")

-- | Synthesise a sample value of a type, encoded in the specified media types.
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 =
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (forall (list :: [*]) a.
AllMimeRender list a =>
Proxy list -> a -> [(MediaType, ByteString)]
allMimeRender Proxy (ct : cts)
ctypes) forall a b. (a -> b) -> a -> b
$ forall a. ToSample a => Proxy a -> Maybe a
toSample (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)

-- | Synthesise a list of sample values of a particular type, encoded in the
-- specified media types.
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' = forall a. ToSample a => Proxy a -> [(Text, a)]
toSamples (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
        enc :: (Text, a) -> [(Text, MediaType, ByteString)]
enc (Text
t, a
s) = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (Text
t,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (list :: [*]) a.
AllMimeRender list a =>
Proxy list -> a -> [(MediaType, ByteString)]
allMimeRender Proxy (ct : cts)
ctypes a
s
    in forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Text, a) -> [(Text, MediaType, ByteString)]
enc [(Text, a)]
samples'

-- | The class that helps us automatically get documentation for GET
--   (or other 'HTTP.Method') parameters.
--
-- Example of an instance:
--
-- > instance ToParam (QueryParam' mods "capital" Bool) where
-- >   toParam _ =
-- >     DocQueryParam "capital"
-- >                   ["true", "false"]
-- >                   "Get the greeting message in uppercase (true) or not (false). Default is false."
class ToParam t where
  toParam :: Proxy t -> DocQueryParam

-- | The class that helps us automatically get documentation
--   for URL captures.
--
-- Example of an instance:
--
-- > instance ToCapture (Capture "name" Text) where
-- >   toCapture _ = DocCapture "name" "name of the person to greet"
class ToCapture c where
  toCapture :: Proxy c -> DocCapture

-- | The class that helps us get documentation for authenticated endpoints
class ToAuthInfo a where
      toAuthInfo :: Proxy a -> DocAuthentication

-- | The class that helps us get documentation for URL fragments.
--
-- Example of an instance:
--
-- > instance ToFragment (Fragment a) where
-- >   toFragment _ = DocFragment "fragment" "fragment description"
class ToFragment t where
  toFragment :: Proxy t -> DocFragment

-- | Generate documentation in Markdown format for
--   the given 'API'.
--
--   This is equivalent to @'markdownWith' 'defRenderingOptions'@.
markdown :: API -> String
markdown :: API -> String
markdown = RenderingOptions -> API -> String
markdownWith RenderingOptions
defRenderingOptions

-- | Generate documentation in Markdown format for
--   the given 'API' using the specified options.
--
--   These options allow you to customise aspects such as:
--
--   * Choose how many content-types for each request body example are
--     shown with 'requestExamples'.
--
--   * Choose how many content-types for each response body example
--     are shown with 'responseExamples'.
--
--   For example, to only show the first content-type of each example:
--
--   @
--   markdownWith ('defRenderingOptions'
--                   & 'requestExamples'  '.~' 'FirstContentType'
--                   & 'responseExamples' '.~' 'FirstContentType' )
--                myAPI
--   @
--
--   @since 0.11.1
markdownWith :: RenderingOptions -> API -> String
markdownWith :: RenderingOptions -> API -> String
markdownWith RenderingOptions{Maybe String
ShowContentTypes
_renderCurlBasePath :: Maybe String
_notesHeading :: Maybe String
_responseExamples :: ShowContentTypes
_requestExamples :: ShowContentTypes
_renderCurlBasePath :: RenderingOptions -> Maybe String
_notesHeading :: RenderingOptions -> Maybe String
_responseExamples :: RenderingOptions -> ShowContentTypes
_requestExamples :: RenderingOptions -> ShowContentTypes
..} API
api = [String] -> String
unlines forall a b. (a -> b) -> a -> b
$
       [DocIntro] -> [String]
introsStr (API
api forall s a. s -> Getting a s a -> a
^. Lens' API [DocIntro]
apiIntros)
    forall a. [a] -> [a] -> [a]
++ (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Endpoint -> Action -> [String]
printEndpoint) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. HashMap k v -> [(k, v)]
HM.toList forall a b. (a -> b) -> a -> b
$ API
api forall s a. s -> Getting a s a -> a
^. Lens' API (HashMap Endpoint Action)
apiEndpoints)

  where printEndpoint :: Endpoint -> Action -> [String]
        printEndpoint :: Endpoint -> Action -> [String]
printEndpoint Endpoint
endpoint Action
action =
          String
str forall a. a -> [a] -> [a]
:
          String
"" forall a. a -> [a] -> [a]
:
          [DocNote] -> [String]
notesStr (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [DocNote]
notes) forall a. [a] -> [a] -> [a]
++
          [DocAuthentication] -> [String]
authStr (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [DocAuthentication]
authInfo) forall a. [a] -> [a] -> [a]
++
          [DocCapture] -> [String]
capturesStr (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [DocCapture]
captures) forall a. [a] -> [a] -> [a]
++
          [Text] -> [String]
headersStr (forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf (Lens' Action [Header]
headers forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Each s t a b => Traversal s t a b
each forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Field1 s t a b => Lens s t a b
_1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Method -> String
BSC.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. CI s -> s
CI.original)) Action
action) forall a. [a] -> [a] -> [a]
++
          Method -> [DocQueryParam] -> [String]
paramsStr Method
meth (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [DocQueryParam]
params) forall a. [a] -> [a] -> [a]
++
          Maybe DocFragment -> [String]
fragmentStr (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action (Maybe DocFragment)
fragment) forall a. [a] -> [a] -> [a]
++
          [MediaType] -> [(Text, MediaType, ByteString)] -> [String]
rqbodyStr (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [MediaType]
rqtypes) (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [(Text, MediaType, ByteString)]
rqbody) forall a. [a] -> [a] -> [a]
++
          Response -> [String]
responseStr (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action Response
response) forall a. [a] -> [a] -> [a]
++
          forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Endpoint
-> [Header]
-> [(Text, MediaType, ByteString)]
-> String
-> [String]
curlStr Endpoint
endpoint (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [Header]
headers) (Action
action forall s a. s -> Getting a s a -> a
^. Lens' Action [(Text, MediaType, ByteString)]
rqbody)) Maybe String
_renderCurlBasePath forall a. [a] -> [a] -> [a]
++
          []

          where str :: String
str = String
"## " forall a. [a] -> [a] -> [a]
++ Method -> String
BSC.unpack Method
meth
                    forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ [String] -> String
showPath (Endpoint
endpointforall s a. s -> Getting a s a -> a
^.Lens' Endpoint [String]
path)

                meth :: Method
meth = Endpoint
endpoint forall s a. s -> Getting a s a -> a
^. Lens' Endpoint Method
method

        introsStr :: [DocIntro] -> [String]
        introsStr :: [DocIntro] -> [String]
introsStr = 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
"## " forall a. [a] -> [a] -> [a]
++ DocIntro
i forall s a. s -> Getting a s a -> a
^. Lens' DocIntro String
introTitle) forall a. a -> [a] -> [a]
:
            String
"" forall a. a -> [a] -> [a]
:
            forall a. a -> [a] -> [a]
intersperse String
"" (DocIntro
i forall s a. s -> Getting a s a -> a
^. Lens' DocIntro [String]
introBody) forall a. [a] -> [a] -> [a]
++
            String
"" forall a. a -> [a] -> [a]
:
            []

        notesStr :: [DocNote] -> [String]
        notesStr :: [DocNote] -> [String]
notesStr = [String] -> [String]
addHeading
                   forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DocNote -> [String]
noteStr
          where
            addHeading :: [String] -> [String]
addHeading [String]
nts = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [String]
nts (\String
hd -> (String
"### " forall a. [a] -> [a] -> [a]
++ String
hd) forall a. a -> [a] -> [a]
: String
"" forall a. a -> [a] -> [a]
: [String]
nts) Maybe String
_notesHeading

        noteStr :: DocNote -> [String]
        noteStr :: DocNote -> [String]
noteStr DocNote
nt =
            (String
hdr forall a. [a] -> [a] -> [a]
++ DocNote
nt forall s a. s -> Getting a s a -> a
^. Lens' DocNote String
noteTitle) forall a. a -> [a] -> [a]
:
            String
"" forall a. a -> [a] -> [a]
:
            forall a. a -> [a] -> [a]
intersperse String
"" (DocNote
nt forall s a. s -> Getting a s a -> a
^. Lens' DocNote [String]
noteBody) forall a. [a] -> [a] -> [a]
++
            String
"" forall a. a -> [a] -> [a]
:
            []
          where
            hdr :: String
hdr | 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 = forall (f :: * -> *) a b. Functor f => Setter (f a) (f b) a b
mapped forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Lens' DocAuthentication String
authIntro forall a b. (a -> b) -> a -> b
$ [DocAuthentication]
auths
              clientInfos :: [String]
clientInfos = forall (f :: * -> *) a b. Functor f => Setter (f a) (f b) a b
mapped forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Lens' DocAuthentication String
authDataRequired forall a b. (a -> b) -> a -> b
$ [DocAuthentication]
auths
          in String
"### Authentication"forall a. a -> [a] -> [a]
:
              String
""forall a. a -> [a] -> [a]
:
              [String] -> String
unlines [String]
authIntros forall a. a -> [a] -> [a]
:
              String
""forall a. a -> [a] -> [a]
:
              String
"Clients must supply the following data" forall a. a -> [a] -> [a]
:
              [String] -> String
unlines [String]
clientInfos forall a. a -> [a] -> [a]
:
              String
"" forall a. a -> [a] -> [a]
:
              []

        capturesStr :: [DocCapture] -> [String]
        capturesStr :: [DocCapture] -> [String]
capturesStr [] = []
        capturesStr [DocCapture]
l =
          String
"### Captures:" forall a. a -> [a] -> [a]
:
          String
"" forall a. a -> [a] -> [a]
:
          forall a b. (a -> b) -> [a] -> [b]
map DocCapture -> String
captureStr [DocCapture]
l forall a. [a] -> [a] -> [a]
++
          String
"" forall a. a -> [a] -> [a]
:
          []

        captureStr :: DocCapture -> String
captureStr DocCapture
cap =
          String
"- *" forall a. [a] -> [a] -> [a]
++ (DocCapture
cap forall s a. s -> Getting a s a -> a
^. Lens' DocCapture String
capSymbol) forall a. [a] -> [a] -> [a]
++ String
"*: " forall a. [a] -> [a] -> [a]
++ (DocCapture
cap forall s a. s -> Getting a s a -> a
^. Lens' DocCapture String
capDesc)

        headersStr :: [Text] -> [String]
        headersStr :: [Text] -> [String]
headersStr [] = []
        headersStr [Text]
l =
          String
"### Headers:" forall a. a -> [a] -> [a]
:
          String
"" forall a. a -> [a] -> [a]
:
          forall a b. (a -> b) -> [a] -> [b]
map Text -> String
headerStr [Text]
l forall a. [a] -> [a] -> [a]
++
          String
"" forall a. a -> [a] -> [a]
:
          []

          where headerStr :: Text -> String
headerStr Text
hname = String
"- This endpoint is sensitive to the value of the **"
                               forall a. [a] -> [a] -> [a]
++ Text -> String
unpack Text
hname forall a. [a] -> [a] -> [a]
++ String
"** HTTP header."

        paramsStr :: HTTP.Method -> [DocQueryParam] -> [String]
        paramsStr :: Method -> [DocQueryParam] -> [String]
paramsStr Method
_ [] = []
        paramsStr Method
m [DocQueryParam]
l =
          (String
"### " forall a. [a] -> [a] -> [a]
++ forall a b. ConvertibleStrings a b => a -> b
cs Method
m forall a. [a] -> [a] -> [a]
++ String
" Parameters:") forall a. a -> [a] -> [a]
:
          String
"" forall a. a -> [a] -> [a]
:
          forall a b. (a -> b) -> [a] -> [b]
map (forall {a}.
ConvertibleStrings a String =>
a -> DocQueryParam -> String
paramStr Method
m) [DocQueryParam]
l forall a. [a] -> [a] -> [a]
++
          String
"" forall a. a -> [a] -> [a]
:
          []

        paramStr :: a -> DocQueryParam -> String
paramStr a
m DocQueryParam
param = [String] -> String
unlines forall a b. (a -> b) -> a -> b
$
          (String
"- " forall a. [a] -> [a] -> [a]
++ DocQueryParam
param forall s a. s -> Getting a s a -> a
^. Lens' DocQueryParam String
paramName) forall a. a -> [a] -> [a]
:
          (if (Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
values) Bool -> Bool -> Bool
|| DocQueryParam
param forall s a. s -> Getting a s a -> a
^. Lens' DocQueryParam ParamKind
paramKind forall a. Eq a => a -> a -> Bool
/= ParamKind
Flag)
            then [String
"     - **Values**: *" forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
values forall a. [a] -> [a] -> [a]
++ String
"*"]
            else []) forall a. [a] -> [a] -> [a]
++
          (String
"     - **Description**: " forall a. [a] -> [a] -> [a]
++ DocQueryParam
param forall s a. s -> Getting a s a -> a
^. Lens' DocQueryParam String
paramDesc) forall a. a -> [a] -> [a]
:
          (if (DocQueryParam
param forall s a. s -> Getting a s a -> a
^. Lens' DocQueryParam ParamKind
paramKind forall a. Eq a => a -> a -> Bool
== ParamKind
List)
            then [String
"     - This parameter is a **list**. All " forall a. [a] -> [a] -> [a]
++ forall a b. ConvertibleStrings a b => a -> b
cs a
m forall a. [a] -> [a] -> [a]
++ String
" parameters with the name "
                  forall a. [a] -> [a] -> [a]
++ DocQueryParam
param forall s a. s -> Getting a s a -> a
^. Lens' DocQueryParam String
paramName forall a. [a] -> [a] -> [a]
++ String
"[] will forward their values in a list to the handler."]
            else []) forall a. [a] -> [a] -> [a]
++
          (if (DocQueryParam
param forall s a. s -> Getting a s a -> a
^. Lens' DocQueryParam ParamKind
paramKind 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 []) forall a. [a] -> [a] -> [a]
++
          []

          where values :: [String]
values = DocQueryParam
param forall s a. s -> Getting a s a -> a
^. Lens' DocQueryParam [String]
paramValues

        fragmentStr :: Maybe DocFragment -> [String]
        fragmentStr :: Maybe DocFragment -> [String]
fragmentStr Maybe DocFragment
Nothing = []
        fragmentStr (Just DocFragment
frag) =
          [ String
"### Fragment:", String
""
          , String
"- *" forall a. [a] -> [a] -> [a]
++ (DocFragment
frag forall s a. s -> Getting a s a -> a
^. Lens' DocFragment String
fragSymbol) forall a. [a] -> [a] -> [a]
++ String
"*: " forall a. [a] -> [a] -> [a]
++ (DocFragment
frag forall s a. s -> Getting a s a -> a
^. 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
""]
            forall a. Semigroup a => a -> a -> a
<> forall {a}. Show a => [a] -> [String]
formatTypes [MediaType]
types
            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
""]
            forall a. Semigroup a => a -> a -> a
<> forall a b. (a -> b) -> [a] -> [b]
map (\a
t -> String
"    - `" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show a
t forall a. Semigroup a => a -> a -> a
<> String
"`") [a]
ts
            forall a. Semigroup a => a -> a -> a
<> [String
""]

        -- This assumes that when the bodies are created, identical
        -- labels and representations are located next to each other.
        formatBodies :: ShowContentTypes -> [(Text, M.MediaType, ByteString)] -> [String]
        formatBodies :: ShowContentTypes -> [(Text, MediaType, ByteString)] -> [String]
formatBodies ShowContentTypes
ex [(Text, MediaType, ByteString)]
bds = 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 =
              forall a b. (a -> b) -> [a] -> [b]
map (\NonEmpty (Text, MediaType, ByteString)
grps -> let (Text
t,MediaType
_,ByteString
b) = forall a. NonEmpty a -> a
NE.head NonEmpty (Text, MediaType, ByteString)
grps in (Text
t, 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))
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) b a.
(Foldable f, Eq b) =>
(a -> b) -> f a -> [NonEmpty a]
groupWith (\(Text
t,MediaType
_,ByteString
b) -> (Text
t,ByteString
b))
              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  -> forall a. a -> a
id
                       ShowContentTypes
FirstContentType -> forall a b. (a -> b) -> [a] -> [b]
map (\(Text
t,NonEmpty MediaType
ms,ByteString
b) -> (Text
t, forall a. NonEmpty a -> a
NE.head NonEmpty MediaType
ms 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
"- " forall a. Semigroup a => a -> a -> a
<> String
title forall a. Semigroup a => a -> a -> a
<> String
" (" forall a. Semigroup a => a -> a -> a
<> NonEmpty MediaType -> String
mediaList NonEmpty MediaType
ms forall a. Semigroup a => a -> a -> a
<> String
"):" forall a. a -> [a] -> [a]
:
          forall {a} {a}.
(IsString a, Semigroup a, ConvertibleStrings a a) =>
MediaType -> a -> [a]
contentStr (forall a. NonEmpty a -> a
NE.head NonEmpty MediaType
ms) ByteString
b
          where
            mediaList :: NonEmpty MediaType -> String
mediaList = forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> NonEmpty a -> NonEmpty a
NE.intersperse String
", " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\MediaType
m -> String
"`" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show MediaType
m forall a. [a] -> [a] -> [a]
++ String
"`")

            title :: String
title
              | Text -> Bool
T.null Text
t  = String
"Example"
              | Bool
otherwise = forall a b. ConvertibleStrings a b => a -> b
cs Text
t

        markdownForType :: MediaType -> a
markdownForType MediaType
mime_type =
            case (MediaType -> CI Method
M.mainType MediaType
mime_type, MediaType -> CI Method
M.subType MediaType
mime_type) of
                (CI Method
"text", CI Method
"html") -> a
"html"
                (CI Method
"application", CI Method
"xml") -> a
"xml"
                (CI Method
"text", CI Method
"xml") -> a
"xml"
                (CI Method
"application", CI Method
"json") -> a
"javascript"
                (CI Method
"application", CI Method
"javascript") -> a
"javascript"
                (CI Method
"text", CI Method
"css") -> a
"css"
                (CI Method
_, CI Method
_) -> a
""

        contentStr :: MediaType -> a -> [a]
contentStr MediaType
mime_type a
body =
          a
"" forall a. a -> [a] -> [a]
:
          a
"```" forall a. Semigroup a => a -> a -> a
<> forall {a}. IsString a => MediaType -> a
markdownForType MediaType
mime_type forall a. a -> [a] -> [a]
:
          forall a b. ConvertibleStrings a b => a -> b
cs a
body forall a. a -> [a] -> [a]
:
          a
"```" forall a. a -> [a] -> [a]
:
          a
"" forall a. a -> [a] -> [a]
:
          []

        responseStr :: Response -> [String]
        responseStr :: Response -> [String]
responseStr Response
resp =
          String
"### Response:" forall a. a -> [a] -> [a]
:
          String
"" forall a. a -> [a] -> [a]
:
          (String
"- Status code " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Response
resp forall s a. s -> Getting a s a -> a
^. Lens' Response Int
respStatus)) forall a. a -> [a] -> [a]
:
          (String
"- Headers: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Response
resp forall s a. s -> Getting a s a -> a
^. Lens' Response [Header]
respHeaders)) forall a. a -> [a] -> [a]
:
          String
"" forall a. a -> [a] -> [a]
:
          forall {a}. Show a => [a] -> [String]
formatTypes (Response
resp forall s a. s -> Getting a s a -> a
^. Lens' Response [MediaType]
respTypes) forall a. [a] -> [a] -> [a]
++
          [String]
bodies

          where bodies :: [String]
bodies = case Response
resp forall s a. s -> Getting a s a -> a
^. Lens' Response [(Text, MediaType, ByteString)]
respBody of
                  []        -> [String
"- No response body\n"]
                  [(Text
"", MediaType
t, ByteString
r)] -> String
"- Response body as below." forall a. a -> [a] -> [a]
: 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" forall a. [a] -> [a] -> [a]
++ Method -> String
BSC.unpack (Endpoint
endpoint forall s a. s -> Getting a s a -> a
^. Lens' Endpoint Method
method) forall a. [a] -> [a] -> [a]
++ String
" \\"
          ] forall a. Semigroup a => a -> a -> a
<>
          forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
mbMediaTypeStr forall a. Semigroup a => a -> a -> a
<>
          [String]
headersStrs forall a. Semigroup a => a -> a -> a
<>
          forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
mbReqBodyStr forall a. Semigroup a => a -> a -> a
<>
          [  String
"  " forall a. [a] -> [a] -> [a]
++ String
basePath forall a. [a] -> [a] -> [a]
++ [String] -> String
showPath (Endpoint
endpoint forall s a. s -> Getting a s a -> a
^. Lens' Endpoint [String]
path)
          , String
"```"
          , String
""
          ]

          where escapeQuotes :: String -> String
                escapeQuotes :: ShowS
escapeQuotes = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a b. (a -> b) -> a -> b
$ \Char
c -> case Char
c of
                  Char
'\"' -> String
"\\\""
                  Char
_ -> [Char
c]
                mbReqBody :: Maybe (Text, MediaType, ByteString)
mbReqBody = forall a. [a] -> Maybe a
listToMaybe [(Text, MediaType, ByteString)]
reqBodies
                mbMediaTypeStr :: Maybe String
mbMediaTypeStr = forall {a} {a} {c}. Show a => (a, a, c) -> String
mkMediaTypeStr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Text, MediaType, ByteString)
mbReqBody
                headersStrs :: [String]
headersStrs = forall {a} {a}.
(ConvertibleStrings a String, ConvertibleStrings a String) =>
(CI a, a) -> String
mkHeaderStr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Header]
hdrs
                mbReqBodyStr :: Maybe String
mbReqBodyStr = forall {a} {a} {b}.
ConvertibleStrings a String =>
(a, b, a) -> String
mkReqBodyStr 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: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
media_type forall a. [a] -> [a] -> [a]
++ String
"\" \\"
                mkHeaderStr :: (CI a, a) -> String
mkHeaderStr (CI a
hdrName, a
hdrVal) =
                  String
"  -H \"" forall a. [a] -> [a] -> [a]
++ ShowS
escapeQuotes (forall a b. ConvertibleStrings a b => a -> b
cs (forall s. CI s -> s
CI.original CI a
hdrName)) forall a. [a] -> [a] -> [a]
++ String
": " forall a. [a] -> [a] -> [a]
++
                  ShowS
escapeQuotes (forall a b. ConvertibleStrings a b => a -> b
cs a
hdrVal) forall a. [a] -> [a] -> [a]
++ String
"\" \\"
                mkReqBodyStr :: (a, b, a) -> String
mkReqBodyStr (a
_, b
_, a
body) = String
"  -d \"" forall a. [a] -> [a] -> [a]
++ ShowS
escapeQuotes (forall a b. ConvertibleStrings a b => a -> b
cs a
body) forall a. [a] -> [a] -> [a]
++ String
"\" \\"

-- * Instances

-- | The generated docs for @a ':<|>' b@ just appends the docs
--   for @a@ with the docs for @b@.
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) = forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy a
p1 (Endpoint
ep, Action
action) forall a. Semigroup a => a -> a -> a
<> 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 = forall {k} (t :: k). Proxy t
Proxy

          p2 :: Proxy b
          p2 :: Proxy b
p2 = forall {k} (t :: k). Proxy t
Proxy

-- | The generated docs for @'EmptyAPI'@ are empty.
instance HasDocs EmptyAPI where
  docsFor :: Proxy EmptyAPI -> (Endpoint, Action) -> DocOptions -> API
docsFor Proxy EmptyAPI
Proxy (Endpoint, Action)
_ DocOptions
_ = API
emptyAPI

-- | @"books" :> 'Capture' "isbn" Text@ will appear as
-- @/books/:isbn@ in the docs.
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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          captureP :: Proxy (Capture sym a)
captureP = forall {k} (t :: k). Proxy t
Proxy :: Proxy (Capture sym a)

          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocCapture]
captures (forall s a. Snoc s s a a => s -> a -> s
|> forall {k} (c :: k). ToCapture c => Proxy c -> DocCapture
toCapture Proxy (Capture sym a)
captureP) Action
action
          endpoint' :: Endpoint
endpoint' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Endpoint [String]
path (\[String]
p -> [String]
p forall a. [a] -> [a] -> [a]
++ [String
":" forall a. [a] -> [a] -> [a]
++ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP]) Endpoint
endpoint
          symP :: Proxy sym
symP = 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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api

          docCapture :: DocCapture
docCapture = String -> String -> DocCapture
DocCapture (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP) (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy descr
descrP)
          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocCapture]
captures (forall s a. Snoc s s a a => s -> a -> s
|> DocCapture
docCapture) Action
action
          endpoint' :: Endpoint
endpoint' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Endpoint [String]
path (\[String]
p -> [String]
p forall a. [a] -> [a] -> [a]
++ [String
":" forall a. [a] -> [a] -> [a]
++ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP]) Endpoint
endpoint
          descrP :: Proxy descr
descrP = forall {k} (t :: k). Proxy t
Proxy :: Proxy descr
          symP :: Proxy sym
symP = 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 =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy (Capture' mods sym a :> api)


-- | @"books" :> 'CaptureAll' "isbn" Text@ will appear as
-- @/books/:isbn@ in the docs.
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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy sublayout
          captureP :: Proxy (CaptureAll sym a)
captureP = forall {k} (t :: k). Proxy t
Proxy :: Proxy (CaptureAll sym a)

          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocCapture]
captures (forall s a. Snoc s s a a => s -> a -> s
|> forall {k} (c :: k). ToCapture c => Proxy c -> DocCapture
toCapture Proxy (CaptureAll sym a)
captureP) Action
action
          endpoint' :: Endpoint
endpoint' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Endpoint [String]
path (\[String]
p -> [String]
p forall a. [a] -> [a] -> [a]
++ [String
":" forall a. [a] -> [a] -> [a]
++ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy sym
symP]) Endpoint
endpoint
          symP :: Proxy sym
symP = 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 :: Int
_maxSamples :: DocOptions -> Int
..} =
    Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'

    where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint forall a b. a -> (a -> b) -> b
& Lens' Endpoint Method
method forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method'
          action' :: Action
action' = Action
action forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [(Text, MediaType, ByteString)]
respBody forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. Int -> [a] -> [a]
take Int
_maxSamples (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)
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [MediaType]
respTypes forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy (ct : cts)
t
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response Int
respStatus forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
status
          t :: Proxy (ct : cts)
t = forall {k} (t :: k). Proxy t
Proxy :: Proxy (ct ': cts)
          method' :: Method
method' = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
          status :: Int
status = forall a. Num a => Integer -> a
fromInteger forall a b. (a -> b) -> a -> b
$ forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
          p :: Proxy a
p = 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 :: Int
_maxSamples :: DocOptions -> Int
..} =
    Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'

    where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint forall a b. a -> (a -> b) -> b
& Lens' Endpoint Method
method forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method'
          action' :: Action
action' = Action
action forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response Int
respStatus forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
204
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [MediaType]
respTypes forall s t a b. ASetter s t a b -> b -> s -> t
.~ []
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [(Text, MediaType, ByteString)]
respBody forall s t a b. ASetter s t a b -> b -> s -> t
.~ []
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [Header]
respHeaders forall s t a b. ASetter s t a b -> b -> s -> t
.~ []
          method' :: Method
method' = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)

-- | TODO: mention the endpoint is streaming, its framing strategy
--
-- Also there are no samples.
--
-- TODO: AcceptFraming for content-type
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 :: Int
_maxSamples :: DocOptions -> Int
..} =
    Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'

    where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint forall a b. a -> (a -> b) -> b
& Lens' Endpoint Method
method forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method'
          action' :: Action
action' = Action
action forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [MediaType]
respTypes forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy '[ct]
t
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response Int
respStatus forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
status
          t :: Proxy '[ct]
t = forall {k} (t :: k). Proxy t
Proxy :: Proxy '[ct]
          method' :: Method
method' = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
          status :: Int
status = forall a. Num a => Integer -> a
fromInteger forall a b. (a -> b) -> a -> b
$ forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (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 :: Int
_maxSamples :: DocOptions -> Int
..} =
    Endpoint -> Action -> API
single Endpoint
endpoint' Action
action'

    where endpoint' :: Endpoint
endpoint' = Endpoint
endpoint forall a b. a -> (a -> b) -> b
& Lens' Endpoint Method
method forall s t a b. ASetter s t a b -> b -> s -> t
.~ Method
method'
          action' :: Action
action' = Action
action forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [(Text, MediaType, ByteString)]
respBody forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. Int -> [a] -> [a]
take Int
_maxSamples (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)
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [MediaType]
respTypes forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy (ct : cts)
t
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response Int
respStatus forall s t a b. ASetter s t a b -> b -> s -> t
.~ Int
status
                           forall a b. a -> (a -> b) -> b
& Lens' Action Response
responseforall b c a. (b -> c) -> (a -> b) -> a -> c
.Lens' Response [Header]
respHeaders forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Header]
hdrs
          t :: Proxy (ct : cts)
t = forall {k} (t :: k). Proxy t
Proxy :: Proxy (ct ': cts)
          hdrs :: [Header]
hdrs = forall {k} (ls :: k). AllHeaderSamples ls => Proxy ls -> [Header]
allHeaderToSample (forall {k} (t :: k). Proxy t
Proxy :: Proxy ls)
          method' :: Method
method' = forall {k} (a :: k). ReflectMethod a => Proxy a -> Method
reflectMethod (forall {k} (t :: k). Proxy t
Proxy :: Proxy method)
          status :: Int
status = forall a. Num a => Integer -> a
fromInteger forall a b. (a -> b) -> a -> b
$ forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy status)
          p :: Proxy a
p = 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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [Header]
headers (forall s a. Snoc s s a a => s -> a -> s
|> (CI Method
headerName, Method
headerVal)) Action
action
          headerName :: CI Method
headerName = forall s. FoldCase s => s -> CI s
CI.mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. ConvertibleStrings a b => a -> b
cs forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy sym)
          headerVal :: Method
headerVal = case forall a. ToSample a => Proxy a -> Maybe a
toSample (forall {k} (t :: k). Proxy t
Proxy :: Proxy a) of
            Just a
x -> forall a b. ConvertibleStrings a b => a -> b
cs forall a b. (a -> b) -> a -> b
$ forall a. ToHttpApiData a => a -> Method
toHeader a
x
            Maybe a
Nothing -> Method
"<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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          paramP :: Proxy (QueryParam' mods sym a)
paramP = forall {k} (t :: k). Proxy t
Proxy :: Proxy (QueryParam' mods sym a)
          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocQueryParam]
params (forall s a. Snoc s s a a => s -> a -> s
|> 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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          paramP :: Proxy (QueryParams sym a)
paramP = forall {k} (t :: k). Proxy t
Proxy :: Proxy (QueryParams sym a)
          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocQueryParam]
params (forall s a. Snoc s s a a => s -> a -> s
|> 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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          paramP :: Proxy (QueryFlag sym)
paramP = forall {k} (t :: k). Proxy t
Proxy :: Proxy (QueryFlag sym)
          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocQueryParam]
params (forall s a. Snoc s s a a => s -> a -> s
|> 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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          fragmentP :: Proxy (Fragment a)
fragmentP = forall {k} (t :: k). Proxy t
Proxy :: Proxy (Fragment a)
          action' :: Action
action' = forall s t a b. ASetter s t a b -> b -> s -> t
set Lens' Action (Maybe DocFragment)
fragment (forall a. a -> Maybe a
Just (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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocNote]
notes (forall s a. Snoc s s a a => s -> a -> s
|> DocNote
note) Action
action
          note :: DocNote
note = String -> [String] -> DocNote
DocNote (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocNote]
notes (forall s a. Snoc s s a a => s -> a -> s
|> DocNote
note) Action
action
          note :: DocNote
note = String -> [String] -> DocNote
DocNote (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy desc)) []

-- TODO: We use 'AllMimeRender' here because we need to be able to show the
-- example data. However, there's no reason to believe that the instances of
-- 'AllMimeUnrender' and 'AllMimeRender' actually agree (or to suppose that
-- both are even defined) for any particular type.
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 :: Int
_maxSamples :: DocOptions -> Int
..} =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          action' :: Action
          action' :: Action
action' = Action
action forall a b. a -> (a -> b) -> b
& Lens' Action [(Text, MediaType, ByteString)]
rqbody forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. Int -> [a] -> [a]
take Int
_maxSamples (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)
                           forall a b. a -> (a -> b) -> b
& Lens' Action [MediaType]
rqtypes forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall (list :: [*]). AllMime list => Proxy list -> [MediaType]
allMime Proxy (ct : cts)
t
          t :: Proxy (ct : cts)
t = forall {k} (t :: k). Proxy t
Proxy :: Proxy (ct ': cts)
          p :: Proxy a
p = forall {k} (t :: k). Proxy t
Proxy :: Proxy a

-- | TODO: this instance is incomplete.
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 =
        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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api

        action' :: Action
        action' :: Action
action' = Action
action forall a b. a -> (a -> b) -> b
& Lens' Action [MediaType]
rqtypes forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (forall {k} (ctype :: k).
Accept ctype =>
Proxy ctype -> NonEmpty MediaType
contentTypes Proxy ctype
t)

        t :: Proxy ctype
t = 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) =
    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 = forall {k} (t :: k). Proxy t
Proxy :: Proxy api
          endpoint' :: Endpoint
endpoint' = Endpoint
endpoint forall a b. a -> (a -> b) -> b
& Lens' Endpoint [String]
path forall a s t. Semigroup a => ASetter s t a a -> a -> s -> t
<>~ [forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy path
pa]
          pa :: Proxy path
pa = 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 =
    forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (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 =
    forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (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 =
    forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (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 =
    forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (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 = forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (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 = forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (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) =
    forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (forall {k} (t :: k). Proxy t
Proxy :: Proxy api) (Endpoint
endpoint, Action
action')
      where
        authProxy :: Proxy (BasicAuth realm usr)
authProxy = forall {k} (t :: k). Proxy t
Proxy :: Proxy (BasicAuth realm usr)
        action' :: Action
action' = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over Lens' Action [DocAuthentication]
authInfo (forall s a. Snoc s s a a => s -> a -> s
|> 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 = forall {k} (api :: k).
HasDocs api =>
Proxy api -> (Endpoint, Action) -> DocOptions -> API
docsFor (forall {k} (t :: k). Proxy t
Proxy :: Proxy (ToServantApi api))

-- ToSample instances for simple types
instance ToSample NoContent
instance ToSample Bool
instance ToSample Ordering

-- polymorphic ToSample instances
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)

-- ToSample instances for Control.Applicative types
instance ToSample a => ToSample (Const a b)
instance ToSample a => ToSample (ZipList a)

-- ToSample instances for Data.Monoid newtypes
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)

-- $setup
-- >>> :set -XOverloadedStrings