{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Data.API.Doc.Call
( callHtml
) where
import Data.API.Doc.Subst
import Data.API.Doc.Types
import Data.List
import Data.Ord
callHtml :: DocInfo -> Dict -> Call -> String
callHtml :: DocInfo -> Dict -> Call -> String
callHtml DocInfo
di Dict
dct0 call :: Call
call@Call{Bool
String
[String]
[Sample]
[View]
[Param]
[Header]
Maybe (APIType, String)
call_samples :: Call -> [Sample]
call_views :: Call -> [View]
call_params :: Call -> [Param]
call_body :: Call -> Maybe (APIType, String)
call_headers :: Call -> [Header]
call_auth_required :: Call -> Bool
call_description :: Call -> String
call_path :: Call -> [String]
call_http_method :: Call -> String
call_samples :: [Sample]
call_views :: [View]
call_params :: [Param]
call_body :: Maybe (APIType, String)
call_headers :: [Header]
call_auth_required :: Bool
call_description :: String
call_path :: [String]
call_http_method :: String
..} = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Dict -> String
container_open Dict
dct
, DocInfo -> Call -> Dict -> String
headersHtml DocInfo
di Call
call Dict
dct
, DocInfo -> Call -> Dict -> String
paramsHtml DocInfo
di Call
call Dict
dct
, DocInfo -> Call -> Dict -> String
bodyHtml DocInfo
di Call
call Dict
dct
, DocInfo -> Call -> Dict -> String
viewsHtml DocInfo
di Call
call Dict
dct
, DocInfo -> Call -> Dict -> String
samplesHtml DocInfo
di Call
call Dict
dct
]
where
dct :: Dict
dct = ([(String, String)] -> Dict -> Dict)
-> Dict -> [(String, String)] -> Dict
forall a b c. (a -> b -> c) -> b -> a -> c
flip [(String, String)] -> Dict -> Dict
extDict Dict
dct0
[ (,) String
"HTTP-METHOD" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ String
call_http_method
, (,) String
"PATH" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ (Char
'/' Char -> String -> String
forall a. a -> [a] -> [a]
:) (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> [String] -> [String]
forall a. a -> [a] -> [a]
intersperse String
"/" [String]
call_path
, (,) String
"CALL-DESCRIPTION" String
call_description
, (,) String
"AUTH-REQUIRED" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ if Bool
call_auth_required then String
"yes" else String
"no"
]
headersHtml :: DocInfo -> Call -> Dict -> String
DocInfo
di Call{Bool
String
[String]
[Sample]
[View]
[Param]
[Header]
Maybe (APIType, String)
call_samples :: [Sample]
call_views :: [View]
call_params :: [Param]
call_body :: Maybe (APIType, String)
call_headers :: [Header]
call_auth_required :: Bool
call_description :: String
call_path :: [String]
call_http_method :: String
call_samples :: Call -> [Sample]
call_views :: Call -> [View]
call_params :: Call -> [Param]
call_body :: Call -> Maybe (APIType, String)
call_headers :: Call -> [Header]
call_auth_required :: Call -> Bool
call_description :: Call -> String
call_path :: Call -> [String]
call_http_method :: Call -> String
..} Dict
c_dct =
case [Header]
call_headers of
[] -> String
""
[Header]
_ -> [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
headers_head
, (Header -> String) -> [Header] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Header -> String
mk_header ([Header] -> String) -> [Header] -> String
forall a b. (a -> b) -> a -> b
$ (Header -> Header -> Ordering) -> [Header] -> [Header]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((Header -> String) -> Header -> Header -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing Header -> String
header_name) [Header]
call_headers
, String
headers_foot
]
where
mk_header :: Header -> String
mk_header Header
hdr = Dict -> String
header_content (Dict -> String) -> Dict -> String
forall a b. (a -> b) -> a -> b
$ DocInfo -> Dict -> Header -> Dict
call_dict_header DocInfo
di Dict
c_dct Header
hdr
paramsHtml :: DocInfo -> Call -> Dict -> String
paramsHtml :: DocInfo -> Call -> Dict -> String
paramsHtml DocInfo
di Call{Bool
String
[String]
[Sample]
[View]
[Param]
[Header]
Maybe (APIType, String)
call_samples :: [Sample]
call_views :: [View]
call_params :: [Param]
call_body :: Maybe (APIType, String)
call_headers :: [Header]
call_auth_required :: Bool
call_description :: String
call_path :: [String]
call_http_method :: String
call_samples :: Call -> [Sample]
call_views :: Call -> [View]
call_params :: Call -> [Param]
call_body :: Call -> Maybe (APIType, String)
call_headers :: Call -> [Header]
call_auth_required :: Call -> Bool
call_description :: Call -> String
call_path :: Call -> [String]
call_http_method :: Call -> String
..} Dict
c_dct =
case [Param]
call_params of
[] -> Dict -> String
no_params Dict
c_dct
[Param]
_ -> [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Dict -> String
params_head Dict
c_dct
, DocInfo -> Dict -> [Param] -> String
paramsRows DocInfo
di Dict
c_dct [Param]
call_params
, Dict -> String
params_foot Dict
c_dct
]
paramsRows :: DocInfo -> Dict -> [Param] -> String
paramsRows :: DocInfo -> Dict -> [Param] -> String
paramsRows DocInfo
di Dict
c_dct = (Param -> String) -> [Param] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Param -> String
mk_param ([Param] -> String) -> ([Param] -> [Param]) -> [Param] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Param -> Param -> Ordering) -> [Param] -> [Param]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((Param -> String) -> Param -> Param -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing Param -> String
param_name)
where
mk_param :: Param -> String
mk_param Param
param = Dict -> String
parameter_row (Dict -> String) -> Dict -> String
forall a b. (a -> b) -> a -> b
$ DocInfo -> Dict -> Param -> Dict
call_dict_param DocInfo
di Dict
c_dct Param
param
bodyHtml :: DocInfo -> Call -> Dict -> String
bodyHtml :: DocInfo -> Call -> Dict -> String
bodyHtml DocInfo
di Call{Bool
String
[String]
[Sample]
[View]
[Param]
[Header]
Maybe (APIType, String)
call_samples :: [Sample]
call_views :: [View]
call_params :: [Param]
call_body :: Maybe (APIType, String)
call_headers :: [Header]
call_auth_required :: Bool
call_description :: String
call_path :: [String]
call_http_method :: String
call_samples :: Call -> [Sample]
call_views :: Call -> [View]
call_params :: Call -> [Param]
call_body :: Call -> Maybe (APIType, String)
call_headers :: Call -> [Header]
call_auth_required :: Call -> Bool
call_description :: Call -> String
call_path :: Call -> [String]
call_http_method :: Call -> String
..} Dict
c_dct =
case Maybe (APIType, String)
call_body of
Maybe (APIType, String)
Nothing -> String
""
Just (APIType
typ,String
spl) ->
Dict -> String
body_sample (Dict -> String) -> Dict -> String
forall a b. (a -> b) -> a -> b
$
([(String, String)] -> Dict -> Dict)
-> Dict -> [(String, String)] -> Dict
forall a b c. (a -> b -> c) -> b -> a -> c
flip [(String, String)] -> Dict -> Dict
extDict Dict
c_dct
[ (,) String
"BODY-TYPE" (DocInfo -> APIType -> String
renderAPIType DocInfo
di APIType
typ)
, (,) String
"BODY-SAMPLE" String
spl
]
viewsHtml :: DocInfo -> Call -> Dict -> String
viewsHtml :: DocInfo -> Call -> Dict -> String
viewsHtml DocInfo
di Call{Bool
String
[String]
[Sample]
[View]
[Param]
[Header]
Maybe (APIType, String)
call_samples :: [Sample]
call_views :: [View]
call_params :: [Param]
call_body :: Maybe (APIType, String)
call_headers :: [Header]
call_auth_required :: Bool
call_description :: String
call_path :: [String]
call_http_method :: String
call_samples :: Call -> [Sample]
call_views :: Call -> [View]
call_params :: Call -> [Param]
call_body :: Call -> Maybe (APIType, String)
call_headers :: Call -> [Header]
call_auth_required :: Call -> Bool
call_description :: Call -> String
call_path :: Call -> [String]
call_http_method :: Call -> String
..} Dict
c_dct
| [View] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [View]
call_views = String
""
| Bool
otherwise = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ String
views_head
, (View -> String) -> [View] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Dict -> String
view_content (Dict -> String) -> (View -> Dict) -> View -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. View -> Dict
view_dict) [View]
call_views
, String
views_foot
, (View -> String) -> [View] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap View -> String
view_detailed [View]
call_views
]
where
view_dict :: View -> Dict
view_dict View
vw = ([(String, String)] -> Dict -> Dict)
-> Dict -> [(String, String)] -> Dict
forall a b c. (a -> b -> c) -> b -> a -> c
flip [(String, String)] -> Dict -> Dict
extDict Dict
c_dct
[ (,) String
"VIEW-ID" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ View -> String
view_id View
vw
, (,) String
"VIEW-TYPE" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ DocInfo -> APIType -> String
renderAPIType DocInfo
di (APIType -> String) -> APIType -> String
forall a b. (a -> b) -> a -> b
$ View -> APIType
view_type View
vw
, (,) String
"VIEW-DOC" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ View -> String
view_doc View
vw
]
view_detailed :: View -> String
view_detailed View
vw
| [Param] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (View -> [Param]
view_params View
vw) = String
""
| Bool
otherwise = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ Dict -> String
view_detail_head Dict
v_dct
, DocInfo -> Dict -> [Param] -> String
paramsRows DocInfo
di Dict
v_dct ([Param] -> String) -> [Param] -> String
forall a b. (a -> b) -> a -> b
$ View -> [Param]
view_params View
vw
, String
view_detail_foot
]
where v_dct :: Dict
v_dct = View -> Dict
view_dict View
vw
samplesHtml :: DocInfo -> Call -> Dict -> String
samplesHtml :: DocInfo -> Call -> Dict -> String
samplesHtml DocInfo
di Call{Bool
String
[String]
[Sample]
[View]
[Param]
[Header]
Maybe (APIType, String)
call_samples :: [Sample]
call_views :: [View]
call_params :: [Param]
call_body :: Maybe (APIType, String)
call_headers :: [Header]
call_auth_required :: Bool
call_description :: String
call_path :: [String]
call_http_method :: String
call_samples :: Call -> [Sample]
call_views :: Call -> [View]
call_params :: Call -> [Param]
call_body :: Call -> Maybe (APIType, String)
call_headers :: Call -> [Header]
call_auth_required :: Call -> Bool
call_description :: Call -> String
call_path :: Call -> [String]
call_http_method :: Call -> String
..} Dict
c_dct = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Dict -> String
sample_heading Dict
c_dct
, [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (Sample -> String) -> [Sample] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Sample -> String
mk_sample [Sample]
call_samples
]
where
mk_sample :: Sample -> String
mk_sample Sample
spl = Dict -> String
sample Dict
s_dct
where
s_dct :: Dict
s_dct = DocInfo -> Dict -> Sample -> Dict
call_dict_sample DocInfo
di Dict
c_dct Sample
spl
call_dict_header :: DocInfo -> Dict -> Header -> Dict
DocInfo
di Dict
dct Header{Bool
String
APIType
header_required :: Header -> Bool
header_type :: Header -> APIType
header_desc :: Header -> String
header_expl :: Header -> String
header_required :: Bool
header_type :: APIType
header_desc :: String
header_expl :: String
header_name :: String
header_name :: Header -> String
..} = ([(String, String)] -> Dict -> Dict)
-> Dict -> [(String, String)] -> Dict
forall a b c. (a -> b -> c) -> b -> a -> c
flip [(String, String)] -> Dict -> Dict
extDict Dict
dct
[ (,) String
"HEADER-NAME" String
header_name
, (,) String
"HEADER-OR" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ if Bool
header_required then String
"Required" else String
"Optional"
, (,) String
"HEADER-EXAMPLE" String
header_expl
, (,) String
"HEADER-DESC" String
header_desc
, (,) String
"HEADER-TYPE" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ DocInfo -> APIType -> String
renderAPIType DocInfo
di APIType
header_type
]
call_dict_param :: DocInfo -> Dict -> Param -> Dict
call_dict_param :: DocInfo -> Dict -> Param -> Dict
call_dict_param DocInfo
di Dict
dct Param{Bool
String
Either String APIType
param_required :: Param -> Bool
param_type :: Param -> Either String APIType
param_desc :: Param -> String
param_expl :: Param -> String
param_required :: Bool
param_type :: Either String APIType
param_desc :: String
param_expl :: String
param_name :: String
param_name :: Param -> String
..} = ([(String, String)] -> Dict -> Dict)
-> Dict -> [(String, String)] -> Dict
forall a b c. (a -> b -> c) -> b -> a -> c
flip [(String, String)] -> Dict -> Dict
extDict Dict
dct
[ (,) String
"PARAMETER-NAME" String
param_name
, (,) String
"PARAMETER-OR" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ if Bool
param_required then String
"Required" else String
"Optional"
, (,) String
"PARAMETER-EXAMPLE" String
param_expl
, (,) String
"PARAMETER-DESC" String
param_desc
, (,) String
"PARAMETER-TYPE" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ (String -> String)
-> (APIType -> String) -> Either String APIType -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> String
forall a. a -> a
id (DocInfo -> APIType -> String
renderAPIType DocInfo
di) Either String APIType
param_type
]
call_dict_sample :: DocInfo -> Dict -> Sample -> Dict
call_dict_sample :: DocInfo -> Dict -> Sample -> Dict
call_dict_sample DocInfo
di Dict
dct Sample{StatusCode
Maybe String
Body APIType
sample_response :: Sample -> Maybe String
sample_type :: Sample -> Body APIType
sample_status :: Sample -> StatusCode
sample_response :: Maybe String
sample_type :: Body APIType
sample_status :: StatusCode
..} = ([(String, String)] -> Dict -> Dict)
-> Dict -> [(String, String)] -> Dict
forall a b c. (a -> b -> c) -> b -> a -> c
flip [(String, String)] -> Dict -> Dict
extDict Dict
dct
[ (,) String
"HTTP-STATUS" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ StatusCode -> String
forall a. Show a => a -> String
show StatusCode
sample_status
, (,) String
"SAMPLE-TYPE" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ DocInfo -> Body APIType -> String
renderBodyType DocInfo
di Body APIType
sample_type
, (,) String
"SAMPLE-RESPONSE" (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" String -> String
forall a. a -> a
id Maybe String
sample_response
]
container_open :: Dict -> String
container_open :: Dict -> String
container_open Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <nav class='breadcrumbs'>"
, String
" <a href='<<BC-HOME-URL>>'><<BC-HOME-TEXT>></a> » <<HTTP-METHOD>> <<PATH>>"
, String
" </nav>"
, String
" <h2>"
, String
" <<HTTP-METHOD>> <<PATH>>"
, String
" </h2>"
, String
" <br>"
, String
" <div class='description'>"
, String
" <p><<CALL-DESCRIPTION>></p>"
, String
" </div>"
, String
" <table border='0' cellspacing='3' cellpadding='0' class='details-table'>"
, String
" <tr>"
, String
" <td width='180'><strong>Request Method</strong></td>"
, String
" <td><code><<HTTP-METHOD>></code> </td>"
, String
" </tr>"
, String
" <tr>"
, String
" <td width='180'><strong>Resource URI</strong></td>"
, String
" <td><code><<ENDPOINT>><<PATH>></code> </td>"
, String
" </tr>"
, String
" <tr>"
, String
" <td width='180'><strong>Authentication Required</strong></td>"
, String
" <td><code>"
, String
" <<AUTH-REQUIRED>>"
, String
" </code> "
, String
" </td>"
, String
" </tr>"
, String
" </table>"
, String
" <br>"
, String
" <hr/>"
]
headers_head :: String
= [String] -> String
unlines
[ String
" <br>"
, String
" <h3>Headers</h3>"
, String
" <br>"
, String
" <table border='0' cellspacing='0' cellpadding='0' width='100%' id='headers'>"
]
header_content :: Dict -> String
Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <tr>"
, String
" <td><code><<HEADER-NAME>></code></td>"
, String
" <td><em><<HEADER-OR>></em></td>"
, String
" <td class='details'><p><<HEADER-TYPE>></p></td>"
, String
" <td class='details'><p><tt><<HEADER-EXAMPLE>></tt></p></td>"
, String
" <td class='details'><p><<HEADER-DESC>></p></td>"
, String
" </tr>"
]
headers_foot :: String
= String
"</table><br>"
no_params :: Dict -> String
no_params :: Dict -> String
no_params Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <br>"
, String
" <h3>Parameters</h3>"
, String
" <br>"
, String
" <em>There are no parameters for this resource.</em>"
, String
" <br>"
]
params_head :: Dict -> String
params_head :: Dict -> String
params_head Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <br>"
, String
" <h3>Parameters</h3>"
, String
" <br>"
, String
" <table border='0' cellspacing='0' cellpadding='0' width='100%' id='params' class='params'>"
]
parameter_row :: Dict -> String
parameter_row :: Dict -> String
parameter_row Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <tr>"
, String
" <td width='130'><code><<PARAMETER-NAME>></code></td>"
, String
" <td width='75'>"
, String
" <em>"
, String
" <<PARAMETER-OR>>"
, String
" </em>"
, String
" </td>"
, String
" <td class='details'>"
, String
" <p><<PARAMETER-TYPE>></p>"
, String
" </td>"
, String
" <td class='details'>"
, String
" <p><tt><<PARAMETER-EXAMPLE>></tt></p>"
, String
" </td>"
, String
" <td class='details'>"
, String
" <p><<PARAMETER-DESC>></p>"
, String
" </td>"
, String
" </tr>"
]
params_foot :: Dict -> String
Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" </table>"
]
body_sample :: Dict -> String
body_sample :: Dict -> String
body_sample Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <br>"
, String
" <h3>Sample Body</h3>"
, String
" <br>"
, String
" <div class='response-format'>"
, String
" <<BODY-TYPE>>"
, String
" </div>"
, String
" <pre><<BODY-SAMPLE>></pre>"
]
views_head :: String
views_head :: String
views_head = [String] -> String
unlines
[ String
" <br>"
, String
" <h3>Views</h3>"
, String
" <br>"
, String
" <table border='0' cellspacing='0' cellpadding='0' width='100%' id='views'>"
]
view_content :: Dict -> String
view_content :: Dict -> String
view_content Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <tr>"
, String
" <td width='130'><code><<VIEW-ID>></code></td>"
, String
" <td class='details'><p><<VIEW-TYPE>></p></td>"
, String
" <td class='details'><p><<VIEW-DOC>></p></td>"
, String
" </tr>"
]
views_foot :: String
= String
"</table><br>"
view_detail_head :: Dict -> String
view_detail_head :: Dict -> String
view_detail_head Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <br>"
, String
" <h3>Parameters for <code><<VIEW-ID>></code> view :: <<VIEW-TYPE>></h3>"
, String
" <br>"
, String
" <table border='0' cellspacing='0' cellpadding='0' width='100%' class='params view-detail' id='view-<<VIEW-ID>>'>"
]
view_detail_foot :: String
= String
"</table>"
sample_heading :: Dict -> String
sample_heading :: Dict -> String
sample_heading Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <br>"
, String
" <h3>Sample Responses</h3>"
, String
" <br>"
]
sample :: Dict -> String
sample :: Dict -> String
sample Dict
dct = Dict -> [String] -> String
prep Dict
dct
[ String
" <div class='response-format'>"
, String
" <<SAMPLE-TYPE>>"
, String
" <span>HTTP Status: <<HTTP-STATUS>></span>"
, String
" </div>"
, String
" <pre><<SAMPLE-RESPONSE>></pre>"
]