{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Data.API.Doc.Types
( URL
, HTTPMethod
, StatusCode
, Call(..)
, Header(..)
, Param(..)
, View(..)
, Sample(..)
, Body(..)
, DocInfo(..)
, renderAPIType
, renderBodyType
, mk_link
) where
import Data.API.PP
import Data.API.Types
import qualified Data.Text as T
import Text.Printf
type URL = String
type HTTPMethod = String
type StatusCode = Int
data Call
= Call
{ Call -> HTTPMethod
call_http_method :: HTTPMethod
, Call -> [HTTPMethod]
call_path :: [String]
, Call -> HTTPMethod
call_description :: String
, Call -> Bool
call_auth_required :: Bool
, :: [Header]
, Call -> Maybe (APIType, HTTPMethod)
call_body :: Maybe (APIType, String)
, Call -> [Param]
call_params :: [Param]
, Call -> [View]
call_views :: [View]
, Call -> [Sample]
call_samples :: [Sample]
}
deriving (Int -> Call -> ShowS
[Call] -> ShowS
Call -> HTTPMethod
(Int -> Call -> ShowS)
-> (Call -> HTTPMethod) -> ([Call] -> ShowS) -> Show Call
forall a.
(Int -> a -> ShowS)
-> (a -> HTTPMethod) -> ([a] -> ShowS) -> Show a
showList :: [Call] -> ShowS
$cshowList :: [Call] -> ShowS
show :: Call -> HTTPMethod
$cshow :: Call -> HTTPMethod
showsPrec :: Int -> Call -> ShowS
$cshowsPrec :: Int -> Call -> ShowS
Show)
data
=
{ :: String
, :: String
, :: String
, :: APIType
, :: Bool
} deriving (Int -> Header -> ShowS
[Header] -> ShowS
Header -> HTTPMethod
(Int -> Header -> ShowS)
-> (Header -> HTTPMethod) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS)
-> (a -> HTTPMethod) -> ([a] -> ShowS) -> Show a
showList :: [Header] -> ShowS
$cshowList :: [Header] -> ShowS
show :: Header -> HTTPMethod
$cshow :: Header -> HTTPMethod
showsPrec :: Int -> Header -> ShowS
$cshowsPrec :: Int -> Header -> ShowS
Show)
data Param
= Param
{ Param -> HTTPMethod
param_name :: String
, Param -> HTTPMethod
param_expl :: String
, Param -> HTTPMethod
param_desc :: String
, Param -> Either HTTPMethod APIType
param_type :: Either String APIType
, Param -> Bool
param_required :: Bool
} deriving (Int -> Param -> ShowS
[Param] -> ShowS
Param -> HTTPMethod
(Int -> Param -> ShowS)
-> (Param -> HTTPMethod) -> ([Param] -> ShowS) -> Show Param
forall a.
(Int -> a -> ShowS)
-> (a -> HTTPMethod) -> ([a] -> ShowS) -> Show a
showList :: [Param] -> ShowS
$cshowList :: [Param] -> ShowS
show :: Param -> HTTPMethod
$cshow :: Param -> HTTPMethod
showsPrec :: Int -> Param -> ShowS
$cshowsPrec :: Int -> Param -> ShowS
Show)
data View
= View
{ View -> HTTPMethod
view_id :: String
, View -> APIType
view_type :: APIType
, View -> HTTPMethod
view_doc :: String
, View -> [Param]
view_params :: [Param]
} deriving (Int -> View -> ShowS
[View] -> ShowS
View -> HTTPMethod
(Int -> View -> ShowS)
-> (View -> HTTPMethod) -> ([View] -> ShowS) -> Show View
forall a.
(Int -> a -> ShowS)
-> (a -> HTTPMethod) -> ([a] -> ShowS) -> Show a
showList :: [View] -> ShowS
$cshowList :: [View] -> ShowS
show :: View -> HTTPMethod
$cshow :: View -> HTTPMethod
showsPrec :: Int -> View -> ShowS
$cshowsPrec :: Int -> View -> ShowS
Show)
data Sample
= Sample
{ Sample -> Int
sample_status :: StatusCode
, Sample -> Body APIType
sample_type :: Body APIType
, Sample -> Maybe HTTPMethod
sample_response :: Maybe String
} deriving (Int -> Sample -> ShowS
[Sample] -> ShowS
Sample -> HTTPMethod
(Int -> Sample -> ShowS)
-> (Sample -> HTTPMethod) -> ([Sample] -> ShowS) -> Show Sample
forall a.
(Int -> a -> ShowS)
-> (a -> HTTPMethod) -> ([a] -> ShowS) -> Show a
showList :: [Sample] -> ShowS
$cshowList :: [Sample] -> ShowS
show :: Sample -> HTTPMethod
$cshow :: Sample -> HTTPMethod
showsPrec :: Int -> Sample -> ShowS
$cshowsPrec :: Int -> Sample -> ShowS
Show)
data Body t = EmptyBody
| JSONBody t
| OtherBody String
deriving (a -> Body b -> Body a
(a -> b) -> Body a -> Body b
(forall a b. (a -> b) -> Body a -> Body b)
-> (forall a b. a -> Body b -> Body a) -> Functor Body
forall a b. a -> Body b -> Body a
forall a b. (a -> b) -> Body a -> Body b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Body b -> Body a
$c<$ :: forall a b. a -> Body b -> Body a
fmap :: (a -> b) -> Body a -> Body b
$cfmap :: forall a b. (a -> b) -> Body a -> Body b
Functor, Int -> Body t -> ShowS
[Body t] -> ShowS
Body t -> HTTPMethod
(Int -> Body t -> ShowS)
-> (Body t -> HTTPMethod) -> ([Body t] -> ShowS) -> Show (Body t)
forall t. Show t => Int -> Body t -> ShowS
forall t. Show t => [Body t] -> ShowS
forall t. Show t => Body t -> HTTPMethod
forall a.
(Int -> a -> ShowS)
-> (a -> HTTPMethod) -> ([a] -> ShowS) -> Show a
showList :: [Body t] -> ShowS
$cshowList :: forall t. Show t => [Body t] -> ShowS
show :: Body t -> HTTPMethod
$cshow :: forall t. Show t => Body t -> HTTPMethod
showsPrec :: Int -> Body t -> ShowS
$cshowsPrec :: forall t. Show t => Int -> Body t -> ShowS
Show)
data DocInfo
= DocInfo
{ DocInfo -> HTTPMethod -> [HTTPMethod] -> HTTPMethod
doc_info_call_url :: HTTPMethod -> [String] -> URL
, DocInfo -> TypeName -> HTTPMethod
doc_info_type_url :: TypeName -> URL
}
renderBodyType :: DocInfo -> Body APIType -> String
renderBodyType :: DocInfo -> Body APIType -> HTTPMethod
renderBodyType DocInfo
_ Body APIType
EmptyBody = HTTPMethod
"empty"
renderBodyType DocInfo
di (JSONBody APIType
ty) = HTTPMethod
"json " HTTPMethod -> ShowS
forall a. [a] -> [a] -> [a]
++ DocInfo -> APIType -> HTTPMethod
renderAPIType DocInfo
di APIType
ty
renderBodyType DocInfo
_ (OtherBody HTTPMethod
s) = HTTPMethod
s
renderAPIType :: DocInfo -> APIType -> String
renderAPIType :: DocInfo -> APIType -> HTTPMethod
renderAPIType DocInfo
di (TyList APIType
ty ) = HTTPMethod
"[" HTTPMethod -> ShowS
forall a. [a] -> [a] -> [a]
++ DocInfo -> APIType -> HTTPMethod
renderAPIType DocInfo
di APIType
ty HTTPMethod -> ShowS
forall a. [a] -> [a] -> [a]
++ HTTPMethod
"]"
renderAPIType DocInfo
di (TyMaybe APIType
ty ) = HTTPMethod
"?" HTTPMethod -> ShowS
forall a. [a] -> [a] -> [a]
++ DocInfo -> APIType -> HTTPMethod
renderAPIType DocInfo
di APIType
ty
renderAPIType DocInfo
di (TyName TypeName
tn ) = HTTPMethod -> ShowS
mk_link (DocInfo -> TypeName -> HTTPMethod
doc_info_type_url DocInfo
di TypeName
tn) (Text -> HTTPMethod
T.unpack (TypeName -> Text
_TypeName TypeName
tn))
renderAPIType DocInfo
_ (TyBasic BasicType
bt ) = BasicType -> HTTPMethod
forall t. PP t => t -> HTTPMethod
pp BasicType
bt
renderAPIType DocInfo
_ APIType
TyJSON = HTTPMethod
"json"
mk_link :: URL -> String -> String
mk_link :: HTTPMethod -> ShowS
mk_link = HTTPMethod -> HTTPMethod -> ShowS
forall r. PrintfType r => HTTPMethod -> r
printf HTTPMethod
"<b><a class='reflink' href='%s' >%s</a></b>"