Skip to content

Commit e486564

Browse files
committed
doc(servant-foreign): Document module
I spend some considerable time reverse engineering the module, so I thought I’d write the documentation I would have liked to see. The strategy here is that a user not necessarily has insight into how servant works internally, or even how to write complex servant routes, they just want to generate a list of endpoints and convert the `Req` type into e.g. generated code in $language. Thus, they need to know the semantics of all fields of Req, how they interact and how they relate to a plain http route. I made sure every `f` is replaced with `ftype`, so we have one conventional way of referring to the foreign type argument everywhere. Some enums are not set at all, they are marked as such. `_reqBodyContentType` introduces a major restriction of the module, so that is mentioned in the documentation for now, until the time it will be fixed. A few TODO’s describe places where types don’t make sense but would introduce API-breaking changes, so these should probably be simplified, but bundled in one go.
1 parent 07f7954 commit e486564

File tree

2 files changed

+133
-39
lines changed

2 files changed

+133
-39
lines changed

servant-foreign/src/Servant/Foreign.hs

Lines changed: 14 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -3,28 +3,30 @@
33
--
44
-- 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).
55
module Servant.Foreign
6-
( listFromAPI
6+
(
7+
-- * Main API
8+
listFromAPI
79
, Req(..)
810
, defReq
911
, HasForeignType(..)
1012
, GenerateList(..)
1113
, HasForeign(..)
1214
, NoTypes
13-
, ArgType(..)
14-
, HeaderArg(..)
15-
, QueryArg(..)
16-
, ReqBodyContentType(..)
15+
-- * Subtypes of 'Req'
16+
, Url(..)
17+
, Path
1718
, Segment(..)
19+
, SegmentType(..)
1820
, isCapture
1921
, captureArg
20-
, SegmentType(..)
21-
, Url(..)
22-
-- * aliases
23-
, Path
22+
, QueryArg(..)
23+
, ArgType(..)
24+
, HeaderArg(..)
2425
, Arg(..)
2526
, FunctionName(..)
27+
, ReqBodyContentType(..)
2628
, PathSegment(..)
27-
-- * lenses
29+
-- * Lenses
2830
, argName
2931
, argType
3032
, argPath
@@ -40,7 +42,7 @@ module Servant.Foreign
4042
, queryArgName
4143
, queryArgType
4244
, headerArg
43-
-- * prisms
45+
-- * Prisms
4446
, _PathSegment
4547
, _HeaderArg
4648
, _ReplaceHeaderArg
@@ -49,7 +51,7 @@ module Servant.Foreign
4951
, _Normal
5052
, _Flag
5153
, _List
52-
-- * re-exports
54+
-- * Re-exports
5355
, module Servant.API
5456
, module Servant.Foreign.Inflections
5557
) where

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

Lines changed: 119 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -46,45 +46,67 @@ newtype FunctionName = FunctionName { unFunctionName :: [Text] }
4646

4747
makePrisms ''FunctionName
4848

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

5253
makePrisms ''PathSegment
5354

54-
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
5559
{ _argName :: PathSegment
56-
, _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+
}
5766
deriving (Data, Eq, Show, Typeable)
5867

5968
makeLenses ''Arg
6069

61-
argPath :: Getter (Arg f) Text
70+
argPath :: Getter (Arg ftype) Text
6271
argPath = argName . _PathSegment
6372

64-
data SegmentType f
73+
data SegmentType ftype
6574
= Static PathSegment
66-
-- ^ a static path segment. like "/foo"
67-
| Cap (Arg f)
68-
-- ^ 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@.
6986
deriving (Data, Eq, Show, Typeable)
7087

7188
makePrisms ''SegmentType
7289

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

7694
makePrisms ''Segment
7795

78-
isCapture :: Segment f -> Bool
96+
-- | Whether a segment is a 'Cap'.
97+
isCapture :: Segment ftype -> Bool
7998
isCapture (Segment (Cap _)) = True
8099
isCapture _ = False
81100

82-
captureArg :: Segment f -> Arg f
101+
-- | Crashing Arg extraction from segment, TODO: remove
102+
captureArg :: Segment ftype -> Arg ftype
83103
captureArg (Segment (Cap s)) = s
84104
captureArg _ = error "captureArg called on non capture"
85105

86-
type Path f = [Segment f]
106+
-- TODO: remove, unnecessary indirection
107+
type Path ftype = [Segment ftype]
87108

109+
-- | Type of a 'QueryArg'.
88110
data ArgType
89111
= Normal
90112
| Flag
@@ -93,18 +115,41 @@ data ArgType
93115

94116
makePrisms ''ArgType
95117

96-
data QueryArg f = QueryArg
97-
{ _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
98137
, _queryArgType :: ArgType
138+
-- ^ one of normal/plain, list or flag
99139
}
100140
deriving (Data, Eq, Show, Typeable)
101141

102142
makeLenses ''QueryArg
103143

104-
data HeaderArg f = HeaderArg
105-
{ _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
106151
| ReplaceHeaderArg
107-
{ _headerArg :: Arg f
152+
{ _headerArg :: Arg ftype
108153
, _headerPattern :: Text
109154
}
110155
deriving (Data, Eq, Show, Typeable)
@@ -113,29 +158,71 @@ makeLenses ''HeaderArg
113158

114159
makePrisms ''HeaderArg
115160

116-
data Url f = Url
117-
{ _path :: Path f
118-
, _queryStr :: [QueryArg f]
119-
, _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@
120177
}
121178
deriving (Data, Eq, Show, Typeable)
122179

123-
defUrl :: Url f
180+
defUrl :: Url ftype
124181
defUrl = Url [] [] Nothing
125182

126183
makeLenses ''Url
127184

185+
-- | See documentation of '_reqBodyContentType'
128186
data ReqBodyContentType = ReqBodyJSON | ReqBodyMultipart
129187
deriving (Data, Eq, Show, Read)
130188

131-
data Req f = Req
132-
{ _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
133197
, _reqMethod :: HTTP.Method
134-
, _reqHeaders :: [HeaderArg f]
135-
, _reqBody :: Maybe f
136-
, _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
137205
, _reqFuncName :: FunctionName
206+
-- ^ The URL segments rendered in a way that they can be easily concatenated into a canonical function name
138207
, _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]@
139226
}
140227
deriving (Data, Eq, Show, Typeable)
141228

@@ -179,11 +266,16 @@ defReq = Req defUrl "GET" [] Nothing Nothing (FunctionName []) ReqBodyJSON
179266
class HasForeignType lang ftype a where
180267
typeFor :: Proxy lang -> Proxy ftype -> Proxy a -> ftype
181268

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

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

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

0 commit comments

Comments
 (0)