Skip to content

Commit d06b65c

Browse files
authored
Merge pull request #1390 from Profpatsch/document-servant-foreign
Document servant-foreign
2 parents 0743ca7 + e486564 commit d06b65c

File tree

3 files changed

+162
-65
lines changed

3 files changed

+162
-65
lines changed

servant-foreign/src/Servant/Foreign.hs

Lines changed: 22 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,32 @@
11
-- | Generalizes all the data needed to make code generation work with
22
-- arbitrary programming languages.
3+
--
4+
-- See documentation of 'HasForeignType' for a simple example. 'listFromAPI' returns a list of all your endpoints and their foreign types, given a mapping from Haskell types to foreign types (conventionally called `ftypes` below).
35
module Servant.Foreign
4-
( ArgType(..)
5-
, HeaderArg(..)
6-
, QueryArg(..)
6+
(
7+
-- * Main API
8+
listFromAPI
79
, Req(..)
8-
, ReqBodyContentType(..)
9-
, Segment(..)
10-
, SegmentType(..)
10+
, defReq
11+
, HasForeignType(..)
12+
, GenerateList(..)
13+
, HasForeign(..)
14+
, NoTypes
15+
-- * Subtypes of 'Req'
1116
, Url(..)
12-
-- aliases
1317
, Path
18+
, Segment(..)
19+
, SegmentType(..)
20+
, isCapture
21+
, captureArg
22+
, QueryArg(..)
23+
, ArgType(..)
24+
, HeaderArg(..)
1425
, Arg(..)
1526
, FunctionName(..)
27+
, ReqBodyContentType(..)
1628
, PathSegment(..)
17-
-- lenses
29+
-- * Lenses
1830
, argName
1931
, argType
2032
, argPath
@@ -30,7 +42,7 @@ module Servant.Foreign
3042
, queryArgName
3143
, queryArgType
3244
, headerArg
33-
-- prisms
45+
-- * Prisms
3446
, _PathSegment
3547
, _HeaderArg
3648
, _ReplaceHeaderArg
@@ -39,16 +51,7 @@ module Servant.Foreign
3951
, _Normal
4052
, _Flag
4153
, _List
42-
-- rest of it
43-
, HasForeign(..)
44-
, HasForeignType(..)
45-
, GenerateList(..)
46-
, NoTypes
47-
, captureArg
48-
, isCapture
49-
, defReq
50-
, listFromAPI
51-
-- re-exports
54+
-- * Re-exports
5255
, module Servant.API
5356
, module Servant.Foreign.Inflections
5457
) where

servant-foreign/src/Servant/Foreign/Inflections.hs

Lines changed: 18 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -20,20 +20,31 @@ import Prelude hiding
2020
(head, tail)
2121
import Servant.Foreign.Internal
2222

23+
-- | Simply concat each part of the FunctionName together.
24+
--
25+
-- @[ "get", "documents", "by", "id" ] → "getdocumentsbyid"@
26+
concatCase :: FunctionName -> Text
27+
concatCase = view concatCaseL
28+
2329
concatCaseL :: Getter FunctionName Text
2430
concatCaseL = _FunctionName . to mconcat
2531

26-
-- | Function name builder that simply concat each part together
27-
concatCase :: FunctionName -> Text
28-
concatCase = view concatCaseL
32+
-- | Use the snake_case convention.
33+
-- Each part is separated by a single underscore character.
34+
--
35+
-- @[ "get", "documents", "by", "id" ] → "get_documents_by_id"@
36+
snakeCase :: FunctionName -> Text
37+
snakeCase = view snakeCaseL
2938

3039
snakeCaseL :: Getter FunctionName Text
3140
snakeCaseL = _FunctionName . to (intercalate "_")
3241

33-
-- | Function name builder using the snake_case convention.
34-
-- each part is separated by a single underscore character.
35-
snakeCase :: FunctionName -> Text
36-
snakeCase = view snakeCaseL
42+
-- | Use the camelCase convention.
43+
-- The first part is lower case, every other part starts with an upper case character.
44+
--
45+
-- @[ "get", "documents", "by", "id" ] → "getDocumentsById"@
46+
camelCase :: FunctionName -> Text
47+
camelCase = view camelCaseL
3748

3849
camelCaseL :: Getter FunctionName Text
3950
camelCaseL = _FunctionName . to convert
@@ -42,8 +53,3 @@ camelCaseL = _FunctionName . to convert
4253
convert (p:ps) = mconcat $ p : map capitalize ps
4354
capitalize "" = ""
4455
capitalize name = C.toUpper (head name) `cons` tail name
45-
46-
-- | Function name builder using the CamelCase convention.
47-
-- each part begins with an upper case character.
48-
camelCase :: FunctionName -> Text
49-
camelCase = view camelCaseL

servant-foreign/src/Servant/Foreign/Internal.hs

Lines changed: 122 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -13,8 +13,6 @@
1313
{-# LANGUAGE TypeOperators #-}
1414
{-# LANGUAGE UndecidableInstances #-}
1515

16-
-- | Generalizes all the data needed to make code generation work with
17-
-- arbitrary programming languages.
1816
module Servant.Foreign.Internal where
1917

2018
import Prelude ()
@@ -40,55 +38,75 @@ import Servant.API.Modifiers
4038
(RequiredArgument)
4139
import Servant.API.TypeLevel
4240

41+
-- | Canonical name of the endpoint, can be used to generate a function name.
42+
--
43+
-- You can use the functions in "Servant.Foreign.Inflections", like 'Servant.Foreign.Inflections.camelCase' to transform to `Text`.
4344
newtype FunctionName = FunctionName { unFunctionName :: [Text] }
4445
deriving (Data, Show, Eq, Semigroup, Monoid, Typeable)
4546

4647
makePrisms ''FunctionName
4748

49+
-- | See documentation of 'Arg'
4850
newtype PathSegment = PathSegment { unPathSegment :: Text }
4951
deriving (Data, Show, Eq, IsString, Semigroup, Monoid, Typeable)
5052

5153
makePrisms ''PathSegment
5254

53-
data Arg f = Arg
55+
-- | Maps a name to the foreign type that belongs to the annotated value.
56+
--
57+
-- Used for header args, query args, and capture args.
58+
data Arg ftype = Arg
5459
{ _argName :: PathSegment
55-
, _argType :: f }
60+
-- ^ The name to be captured.
61+
--
62+
-- Only for capture args it really denotes a path segment.
63+
, _argType :: ftype
64+
-- ^ Foreign type the associated value will have
65+
}
5666
deriving (Data, Eq, Show, Typeable)
5767

5868
makeLenses ''Arg
5969

60-
argPath :: Getter (Arg f) Text
70+
argPath :: Getter (Arg ftype) Text
6171
argPath = argName . _PathSegment
6272

63-
data SegmentType f
73+
data SegmentType ftype
6474
= Static PathSegment
65-
-- ^ a static path segment. like "/foo"
66-
| Cap (Arg f)
67-
-- ^ a capture. like "/:userid"
75+
-- ^ Static path segment.
76+
--
77+
-- @"foo\/bar\/baz"@
78+
--
79+
-- contains the static segments @"foo"@, @"bar"@ and @"baz"@.
80+
| Cap (Arg ftype)
81+
-- ^ A capture.
82+
--
83+
-- @"user\/{userid}\/name"@
84+
--
85+
-- would capture the arg @userid@ with type @ftype@.
6886
deriving (Data, Eq, Show, Typeable)
6987

7088
makePrisms ''SegmentType
7189

72-
newtype Segment f = Segment { unSegment :: SegmentType f }
90+
-- | A part of the Url’s path.
91+
newtype Segment ftype = Segment { unSegment :: SegmentType ftype }
7392
deriving (Data, Eq, Show, Typeable)
7493

7594
makePrisms ''Segment
7695

77-
isCapture :: Segment f -> Bool
96+
-- | Whether a segment is a 'Cap'.
97+
isCapture :: Segment ftype -> Bool
7898
isCapture (Segment (Cap _)) = True
7999
isCapture _ = False
80100

81-
captureArg :: Segment f -> Arg f
101+
-- | Crashing Arg extraction from segment, TODO: remove
102+
captureArg :: Segment ftype -> Arg ftype
82103
captureArg (Segment (Cap s)) = s
83104
captureArg _ = error "captureArg called on non capture"
84105

85-
type Path f = [Segment f]
86-
87-
newtype Frag f = Frag { unFragment :: Arg f }
88-
deriving (Data, Eq, Show, Typeable)
89-
90-
makePrisms ''Frag
106+
-- TODO: remove, unnecessary indirection
107+
type Path ftype = [Segment ftype]
91108

109+
-- | Type of a 'QueryArg'.
92110
data ArgType
93111
= Normal
94112
| Flag
@@ -97,18 +115,41 @@ data ArgType
97115

98116
makePrisms ''ArgType
99117

100-
data QueryArg f = QueryArg
101-
{ _queryArgName :: Arg f
118+
-- | Url Query argument.
119+
--
120+
-- Urls can contain query arguments, which is a list of key-value pairs.
121+
-- In a typical url, query arguments look like this:
122+
--
123+
-- @?foo=bar&alist[]=el1&alist[]=el2&aflag@
124+
--
125+
-- Each pair can be
126+
--
127+
-- * @?foo=bar@: a plain key-val pair, either optional or required ('QueryParam')
128+
-- * @?aflag@: a flag (no value, implicitly Bool with default `false` if it’s missing) ('QueryFlag')
129+
-- * @?alist[]=el1&alist[]=el2@: list of values ('QueryParams')
130+
--
131+
-- @_queryArgType@ will be set accordingly.
132+
--
133+
-- For the plain key-val pairs ('QueryParam'), @_queryArgName@’s @ftype@ will be wrapped in a @Maybe@ if the argument is optional.
134+
data QueryArg ftype = QueryArg
135+
{ _queryArgName :: Arg ftype
136+
-- ^ Name and foreign type of the argument. Will be wrapped in `Maybe` if the query is optional and in a `[]` if the query is a list
102137
, _queryArgType :: ArgType
138+
-- ^ one of normal/plain, list or flag
103139
}
104140
deriving (Data, Eq, Show, Typeable)
105141

106142
makeLenses ''QueryArg
107143

108-
data HeaderArg f = HeaderArg
109-
{ _headerArg :: Arg f }
144+
data HeaderArg ftype =
145+
-- | The name of the header and the foreign type of its value.
146+
HeaderArg
147+
{ _headerArg :: Arg ftype }
148+
-- | Unused, will never be set.
149+
--
150+
-- TODO: remove
110151
| ReplaceHeaderArg
111-
{ _headerArg :: Arg f
152+
{ _headerArg :: Arg ftype
112153
, _headerPattern :: Text
113154
}
114155
deriving (Data, Eq, Show, Typeable)
@@ -117,29 +158,71 @@ makeLenses ''HeaderArg
117158

118159
makePrisms ''HeaderArg
119160

120-
data Url f = Url
121-
{ _path :: Path f
122-
, _queryStr :: [QueryArg f]
123-
, _frag :: Maybe f
161+
-- | Full endpoint url, with all captures and parameters
162+
data Url ftype = Url
163+
{ _path :: Path ftype
164+
-- ^ Url path, list of either static segments or captures
165+
--
166+
-- @"foo\/{id}\/bar"@
167+
, _queryStr :: [QueryArg ftype]
168+
-- ^ List of query args
169+
--
170+
-- @"?foo=bar&a=b"@
171+
, _frag :: Maybe ftype
172+
-- ^ Url fragment.
173+
--
174+
-- Not sent to the HTTP server, so only useful for frontend matters (e.g. inter-page linking).
175+
--
176+
-- @#fragmentText@
124177
}
125178
deriving (Data, Eq, Show, Typeable)
126179

127-
defUrl :: Url f
180+
defUrl :: Url ftype
128181
defUrl = Url [] [] Nothing
129182

130183
makeLenses ''Url
131184

185+
-- | See documentation of '_reqBodyContentType'
132186
data ReqBodyContentType = ReqBodyJSON | ReqBodyMultipart
133187
deriving (Data, Eq, Show, Read)
134188

135-
data Req f = Req
136-
{ _reqUrl :: Url f
189+
-- | Full description of an endpoint in your API, generated by 'listFromAPI'. It should give you all the information needed to generate foreign language bindings.
190+
--
191+
-- Every field containing @ftype@ will use the foreign type mapping specified via 'HasForeignType' (see its docstring on how to set that up).
192+
--
193+
-- See https://docs.servant.dev/en/stable/tutorial/ApiType.html for accessible documentation of the possible content of an endpoint.
194+
data Req ftype = Req
195+
{ _reqUrl :: Url ftype
196+
-- ^ Full list of URL segments, including captures
137197
, _reqMethod :: HTTP.Method
138-
, _reqHeaders :: [HeaderArg f]
139-
, _reqBody :: Maybe f
140-
, _reqReturnType :: Maybe f
198+
-- ^ @\"GET\"@\/@\"POST\"@\/@\"PUT\"@\/…
199+
, _reqHeaders :: [HeaderArg ftype]
200+
-- ^ Headers required by this endpoint, with their type
201+
, _reqBody :: Maybe ftype
202+
-- ^ Foreign type of the expected request body ('ReqBody'), if any
203+
, _reqReturnType :: Maybe ftype
204+
-- ^ The foreign type of the response, if any
141205
, _reqFuncName :: FunctionName
206+
-- ^ The URL segments rendered in a way that they can be easily concatenated into a canonical function name
142207
, _reqBodyContentType :: ReqBodyContentType
208+
-- ^ The content type the request body is transferred as.
209+
--
210+
-- This is a severe limitation of @servant-foreign@ currently,
211+
-- as we only allow the content type to be `JSON`
212+
-- no user-defined content types. ('ReqBodyMultipart' is not
213+
-- actually implemented.)
214+
--
215+
-- Thus, any routes looking like this will work:
216+
--
217+
-- @"foo" :> Get '[JSON] Foo@
218+
--
219+
-- while routes like
220+
--
221+
-- @"foo" :> Get '[MyFancyContentType] Foo@
222+
--
223+
-- will fail with an error like
224+
--
225+
-- @• JSON expected in list '[MyFancyContentType]@
143226
}
144227
deriving (Data, Eq, Show, Typeable)
145228

@@ -183,11 +266,16 @@ defReq = Req defUrl "GET" [] Nothing Nothing (FunctionName []) ReqBodyJSON
183266
class HasForeignType lang ftype a where
184267
typeFor :: Proxy lang -> Proxy ftype -> Proxy a -> ftype
185268

269+
-- | The language definition without any foreign types. It can be used for dynamic languages which do not /do/ type annotations.
186270
data NoTypes
187271

188-
instance HasForeignType NoTypes NoContent ftype where
272+
-- | Use if the foreign language does not have any types.
273+
instance HasForeignType NoTypes NoContent a where
189274
typeFor _ _ _ = NoContent
190275

276+
-- | Implementation of the Servant framework types.
277+
--
278+
-- Relevant instances: Everything containing 'HasForeignType'.
191279
class HasForeign lang ftype (api :: *) where
192280
type Foreign ftype api :: *
193281
foreignFor :: Proxy lang -> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api

0 commit comments

Comments
 (0)