Skip to content

Commit e6e13fd

Browse files
committed
Make servant-foreign code nicer
* non-messy imports * got rid of most long lines (>80 chars) * prisms for sum types and newtypes(we use lens anyway, so why not) * consistent indentation
1 parent 761443f commit e6e13fd

File tree

8 files changed

+200
-157
lines changed

8 files changed

+200
-157
lines changed

servant-foreign/src/Servant/Foreign.hs

Lines changed: 35 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,36 +1,50 @@
11
-- | Generalizes all the data needed to make code generation work with
22
-- arbitrary programming languages.
33
module Servant.Foreign
4-
( HasForeign(..)
5-
, HasForeignType(..)
4+
( ArgType(..)
5+
, HeaderArg(..)
6+
, QueryArg(..)
7+
, Req(..)
68
, Segment(..)
79
, SegmentType(..)
10+
, Url(..)
11+
-- aliases
12+
, Path
13+
, ForeignType
14+
, Arg
815
, FunctionName
9-
, QueryArg(..)
10-
, HeaderArg(..)
11-
, ArgType(..)
12-
, Req
13-
, captureArg
14-
, defReq
15-
, concatCase
16-
, snakeCase
17-
, camelCase
18-
-- lenses
19-
, argType
20-
, argName
21-
, isCapture
22-
, funcName
23-
, path
16+
-- lenses
2417
, reqUrl
25-
, reqBody
26-
, reqHeaders
2718
, reqMethod
19+
, reqHeaders
20+
, reqBody
2821
, reqReturnType
29-
, segment
22+
, reqFuncName
23+
, path
3024
, queryStr
31-
, listFromAPI
25+
, argName
26+
, argType
27+
-- prisms
28+
, _HeaderArg
29+
, _ReplaceHeaderArg
30+
, _Static
31+
, _Cap
32+
, _Normal
33+
, _Flag
34+
, _List
35+
-- rest of it
36+
, HasForeign(..)
37+
, HasForeignType(..)
38+
, HasNoForeignType
3239
, GenerateList(..)
3340
, NoTypes
41+
, captureArg
42+
, isCapture
43+
, concatCase
44+
, snakeCase
45+
, camelCase
46+
, defReq
47+
, listFromAPI
3448
-- re-exports
3549
, module Servant.API
3650
) where

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

Lines changed: 85 additions & 65 deletions
Original file line numberDiff line numberDiff line change
@@ -19,17 +19,19 @@
1919
-- arbitrary programming languages.
2020
module Servant.Foreign.Internal where
2121

22-
import Control.Lens (makeLenses, (%~), (&), (.~), (<>~))
23-
import qualified Data.Char as C
22+
import Control.Lens (makeLenses, makePrisms, (%~), (&), (.~), (<>~))
23+
import qualified Data.Char as C
2424
import Data.Proxy
2525
import Data.Text
26-
import Data.Text.Encoding (decodeUtf8)
27-
import GHC.Exts (Constraint)
26+
import Data.Text.Encoding (decodeUtf8)
27+
import GHC.Exts (Constraint)
2828
import GHC.TypeLits
29-
import qualified Network.HTTP.Types as HTTP
30-
import Prelude hiding (concat)
29+
import qualified Network.HTTP.Types as HTTP
30+
import Prelude hiding (concat)
3131
import Servant.API
3232

33+
type FunctionName = [Text]
34+
3335
-- | Function name builder that simply concat each part together
3436
concatCase :: FunctionName -> Text
3537
concatCase = concat
@@ -49,36 +51,50 @@ camelCase = camelCase' . Prelude.map (replace "-" "")
4951
capitalize name = C.toUpper (Data.Text.head name) `cons` Data.Text.tail name
5052

5153
type ForeignType = Text
54+
5255
type Arg = (Text, ForeignType)
5356

54-
newtype Segment = Segment { _segment :: SegmentType }
57+
data SegmentType
58+
= Static Text
59+
-- ^ a static path segment. like "/foo"
60+
| Cap Arg
61+
-- ^ a capture. like "/:userid"
5562
deriving (Eq, Show)
5663

57-
data SegmentType = Static Text -- ^ a static path segment. like "/foo"
58-
| Cap Arg -- ^ a capture. like "/:userid"
64+
makePrisms ''SegmentType
65+
66+
newtype Segment = Segment { unSegment :: SegmentType }
5967
deriving (Eq, Show)
6068

69+
makePrisms ''Segment
70+
6171
type Path = [Segment]
6272

63-
data ArgType =
64-
Normal
73+
data ArgType
74+
= Normal
6575
| Flag
6676
| List
6777
deriving (Eq, Show)
6878

79+
makePrisms ''ArgType
80+
6981
data QueryArg = QueryArg
7082
{ _argName :: Arg
7183
, _argType :: ArgType
7284
} deriving (Eq, Show)
7385

86+
makeLenses ''QueryArg
87+
7488
data HeaderArg = HeaderArg
75-
{ headerArg :: Arg
76-
}
89+
{ headerArg :: Arg }
7790
| ReplaceHeaderArg
78-
{ headerArg :: Arg
79-
, headerPattern :: Text
80-
} deriving (Eq, Show)
91+
{ headerArg :: Arg
92+
, headerPattern :: Text
93+
} deriving (Eq, Show)
8194

95+
makeLenses ''HeaderArg
96+
97+
makePrisms ''HeaderArg
8298

8399
data Url = Url
84100
{ _path :: Path
@@ -88,20 +104,17 @@ data Url = Url
88104
defUrl :: Url
89105
defUrl = Url [] []
90106

91-
type FunctionName = [Text]
107+
makeLenses ''Url
92108

93109
data Req = Req
94110
{ _reqUrl :: Url
95111
, _reqMethod :: HTTP.Method
96112
, _reqHeaders :: [HeaderArg]
97113
, _reqBody :: Maybe ForeignType
98114
, _reqReturnType :: ForeignType
99-
, _funcName :: FunctionName
115+
, _reqFuncName :: FunctionName
100116
} deriving (Eq, Show)
101117

102-
makeLenses ''QueryArg
103-
makeLenses ''Segment
104-
makeLenses ''Url
105118
makeLenses ''Req
106119

107120
isCapture :: Segment -> Bool
@@ -155,105 +168,104 @@ type family Elem (a :: *) (ls::[*]) :: Constraint where
155168
-- >
156169
--
157170
class HasForeignType lang a where
158-
typeFor :: Proxy lang -> Proxy a -> ForeignType
171+
typeFor :: Proxy lang -> Proxy a -> ForeignType
159172

160173
data NoTypes
161174

162-
instance HasForeignType NoTypes a where
163-
typeFor _ _ = empty
175+
instance HasForeignType NoTypes ftype where
176+
typeFor _ _ = empty
177+
178+
type HasNoForeignType = HasForeignType NoTypes
164179

165180
class HasForeign lang (layout :: *) where
166181
type Foreign layout :: *
167182
foreignFor :: Proxy lang -> Proxy layout -> Req -> Foreign layout
168183

169184
instance (HasForeign lang a, HasForeign lang b)
170-
=> HasForeign lang (a :<|> b) where
185+
=> HasForeign lang (a :<|> b) where
171186
type Foreign (a :<|> b) = Foreign a :<|> Foreign b
172187

173188
foreignFor lang Proxy req =
174189
foreignFor lang (Proxy :: Proxy a) req
175190
:<|> foreignFor lang (Proxy :: Proxy b) req
176191

177-
instance (KnownSymbol sym, HasForeignType lang a, HasForeign lang sublayout)
178-
=> HasForeign lang (Capture sym a :> sublayout) where
192+
instance (KnownSymbol sym, HasForeignType lang ftype, HasForeign lang sublayout)
193+
=> HasForeign lang (Capture sym ftype :> sublayout) where
179194
type Foreign (Capture sym a :> sublayout) = Foreign sublayout
180195

181196
foreignFor lang Proxy req =
182197
foreignFor lang (Proxy :: Proxy sublayout) $
183198
req & reqUrl.path <>~ [Segment (Cap arg)]
184-
& funcName %~ (++ ["by", str])
185-
199+
& reqFuncName %~ (++ ["by", str])
186200
where
187-
str = pack . symbolVal $ (Proxy :: Proxy sym)
188-
arg = (str, typeFor lang (Proxy :: Proxy a))
201+
str = pack . symbolVal $ (Proxy :: Proxy sym)
202+
arg = (str, typeFor lang (Proxy :: Proxy ftype))
189203

190204
instance (Elem JSON list, HasForeignType lang a, ReflectMethod method)
191-
=> HasForeign lang (Verb method status list a) where
205+
=> HasForeign lang (Verb method status list a) where
192206
type Foreign (Verb method status list a) = Req
193207

194208
foreignFor lang Proxy req =
195-
req & funcName %~ (methodLC :)
209+
req & reqFuncName %~ (methodLC :)
196210
& reqMethod .~ method
197211
& reqReturnType .~ retType
198212
where
199-
retType = typeFor lang (Proxy :: Proxy a)
200-
method = reflectMethod (Proxy :: Proxy method)
201-
methodLC = toLower $ decodeUtf8 method
213+
retType = typeFor lang (Proxy :: Proxy a)
214+
method = reflectMethod (Proxy :: Proxy method)
215+
methodLC = toLower $ decodeUtf8 method
202216

203217
instance (KnownSymbol sym, HasForeignType lang a, HasForeign lang sublayout)
204-
=> HasForeign lang (Header sym a :> sublayout) where
218+
=> HasForeign lang (Header sym a :> sublayout) where
205219
type Foreign (Header sym a :> sublayout) = Foreign sublayout
206220

207221
foreignFor lang Proxy req =
208222
foreignFor lang subP $ req
209223
& reqHeaders <>~ [HeaderArg arg]
210-
211224
where
212-
hname = pack . symbolVal $ (Proxy :: Proxy sym)
213-
arg = (hname, typeFor lang (Proxy :: Proxy a))
214-
subP = Proxy :: Proxy sublayout
225+
hname = pack . symbolVal $ (Proxy :: Proxy sym)
226+
arg = (hname, typeFor lang (Proxy :: Proxy a))
227+
subP = Proxy :: Proxy sublayout
215228

216229
instance (KnownSymbol sym, HasForeignType lang a, HasForeign lang sublayout)
217-
=> HasForeign lang (QueryParam sym a :> sublayout) where
230+
=> HasForeign lang (QueryParam sym a :> sublayout) where
218231
type Foreign (QueryParam sym a :> sublayout) = Foreign sublayout
219232

220233
foreignFor lang Proxy req =
221234
foreignFor lang (Proxy :: Proxy sublayout) $
222235
req & reqUrl.queryStr <>~ [QueryArg arg Normal]
223236

224237
where
225-
str = pack . symbolVal $ (Proxy :: Proxy sym)
226-
arg = (str, typeFor lang (Proxy :: Proxy a))
238+
str = pack . symbolVal $ (Proxy :: Proxy sym)
239+
arg = (str, typeFor lang (Proxy :: Proxy a))
227240

228-
instance (KnownSymbol sym, HasForeignType lang [a], HasForeign lang sublayout)
229-
=> HasForeign lang (QueryParams sym a :> sublayout) where
241+
instance
242+
(KnownSymbol sym, HasForeignType lang [a], HasForeign lang sublayout)
243+
=> HasForeign lang (QueryParams sym a :> sublayout) where
230244
type Foreign (QueryParams sym a :> sublayout) = Foreign sublayout
231-
232245
foreignFor lang Proxy req =
233246
foreignFor lang (Proxy :: Proxy sublayout) $
234247
req & reqUrl.queryStr <>~ [QueryArg arg List]
235-
236248
where
237-
str = pack . symbolVal $ (Proxy :: Proxy sym)
238-
arg = (str, typeFor lang (Proxy :: Proxy [a]))
249+
str = pack . symbolVal $ (Proxy :: Proxy sym)
250+
arg = (str, typeFor lang (Proxy :: Proxy [a]))
239251

240-
instance (KnownSymbol sym, HasForeignType lang a, a ~ Bool, HasForeign lang sublayout)
241-
=> HasForeign lang (QueryFlag sym :> sublayout) where
252+
instance
253+
(KnownSymbol sym, HasForeignType lang Bool, HasForeign lang sublayout)
254+
=> HasForeign lang (QueryFlag sym :> sublayout) where
242255
type Foreign (QueryFlag sym :> sublayout) = Foreign sublayout
243256

244257
foreignFor lang Proxy req =
245258
foreignFor lang (Proxy :: Proxy sublayout) $
246259
req & reqUrl.queryStr <>~ [QueryArg arg Flag]
247-
248260
where
249-
str = pack . symbolVal $ (Proxy :: Proxy sym)
250-
arg = (str, typeFor lang (Proxy :: Proxy a))
261+
str = pack . symbolVal $ (Proxy :: Proxy sym)
262+
arg = (str, typeFor lang (Proxy :: Proxy Bool))
251263

252264
instance HasForeign lang Raw where
253265
type Foreign Raw = HTTP.Method -> Req
254266

255267
foreignFor _ Proxy req method =
256-
req & funcName %~ ((toLower $ decodeUtf8 method) :)
268+
req & reqFuncName %~ ((toLower $ decodeUtf8 method) :)
257269
& reqMethod .~ method
258270

259271
instance (Elem JSON list, HasForeignType lang a, HasForeign lang sublayout)
@@ -271,19 +283,21 @@ instance (KnownSymbol path, HasForeign lang sublayout)
271283
foreignFor lang Proxy req =
272284
foreignFor lang (Proxy :: Proxy sublayout) $
273285
req & reqUrl.path <>~ [Segment (Static str)]
274-
& funcName %~ (++ [str])
275-
286+
& reqFuncName %~ (++ [str])
276287
where
277-
str = Data.Text.map (\c -> if c == '.' then '_' else c)
278-
. pack . symbolVal $ (Proxy :: Proxy path)
288+
str =
289+
Data.Text.map (\c -> if c == '.' then '_' else c)
290+
. pack . symbolVal $ (Proxy :: Proxy path)
279291

280-
instance HasForeign lang sublayout => HasForeign lang (RemoteHost :> sublayout) where
292+
instance HasForeign lang sublayout
293+
=> HasForeign lang (RemoteHost :> sublayout) where
281294
type Foreign (RemoteHost :> sublayout) = Foreign sublayout
282295

283296
foreignFor lang Proxy req =
284297
foreignFor lang (Proxy :: Proxy sublayout) req
285298

286-
instance HasForeign lang sublayout => HasForeign lang (IsSecure :> sublayout) where
299+
instance HasForeign lang sublayout
300+
=> HasForeign lang (IsSecure :> sublayout) where
287301
type Foreign (IsSecure :> sublayout) = Foreign sublayout
288302

289303
foreignFor lang Proxy req =
@@ -302,7 +316,8 @@ instance HasForeign lang sublayout =>
302316

303317
foreignFor lang Proxy = foreignFor lang (Proxy :: Proxy sublayout)
304318

305-
instance HasForeign lang sublayout => HasForeign lang (HttpVersion :> sublayout) where
319+
instance HasForeign lang sublayout
320+
=> HasForeign lang (HttpVersion :> sublayout) where
306321
type Foreign (HttpVersion :> sublayout) = Foreign sublayout
307322

308323
foreignFor lang Proxy req =
@@ -317,10 +332,15 @@ class GenerateList reqs where
317332
instance GenerateList Req where
318333
generateList r = [r]
319334

320-
instance (GenerateList start, GenerateList rest) => GenerateList (start :<|> rest) where
335+
instance (GenerateList start, GenerateList rest)
336+
=> GenerateList (start :<|> rest) where
321337
generateList (start :<|> rest) = (generateList start) ++ (generateList rest)
322338

323339
-- | Generate the necessary data for codegen as a list, each 'Req'
324340
-- describing one endpoint from your API type.
325-
listFromAPI :: (HasForeign lang api, GenerateList (Foreign api)) => Proxy lang -> Proxy api -> [Req]
341+
listFromAPI
342+
:: (HasForeign lang api, GenerateList (Foreign api))
343+
=> Proxy lang
344+
-> Proxy api
345+
-> [Req]
326346
listFromAPI lang p = generateList (foreignFor lang p defReq)

0 commit comments

Comments
 (0)