8
8
{-# LANGUAGE ScopedTypeVariables #-}
9
9
{-# LANGUAGE TypeSynonymInstances #-}
10
10
{-# LANGUAGE MultiParamTypeClasses #-}
11
+ {-# LANGUAGE StandaloneDeriving #-}
12
+ {-# LANGUAGE UndecidableInstances #-}
11
13
-- | @multipart/form-data@ support for servant.
12
14
--
13
15
-- This is mostly useful for adding file upload support to
@@ -20,7 +22,8 @@ module Servant.Multipart
20
22
, lookupFile
21
23
, MultipartOptions (.. )
22
24
, defaultMultipartOptions
23
- , TmpBackendOptions (.. )
25
+ , Tmp
26
+ , Mem
24
27
, defaultTmpBackendOptions
25
28
, Input (.. )
26
29
, FileData (.. )
@@ -58,6 +61,10 @@ import qualified Data.ByteString.Lazy as LBS
58
61
-- stand now. This also means that 'MultipartForm' can't be used in
59
62
-- conjunction with 'ReqBody' in an endpoint.
60
63
--
64
+ -- The 'tag' type parameter instructs the function to handle data
65
+ -- either as data to be saved to temporary storage ('Tmp') or saved to
66
+ -- memory ('Mem').
67
+ --
61
68
-- The 'a' type parameter represents the Haskell type to which
62
69
-- you are going to decode the multipart data to, where the
63
70
-- multipart data consists in all the usual form inputs along
@@ -70,12 +77,12 @@ import qualified Data.ByteString.Lazy as LBS
70
77
-- Example:
71
78
--
72
79
-- @
73
- -- type API = MultipartForm MultipartData :> Post '[PlainText] String
80
+ -- type API = MultipartForm Tmp ( MultipartData Tmp) :> Post '[PlainText] String
74
81
--
75
82
-- api :: Proxy API
76
83
-- api = Proxy
77
84
--
78
- -- server :: MultipartData -> Handler String
85
+ -- server :: MultipartData Tmp -> Handler String
79
86
-- server multipartData = return str
80
87
--
81
88
-- where str = "The form was submitted with "
@@ -97,12 +104,12 @@ import qualified Data.ByteString.Lazy as LBS
97
104
-- @
98
105
-- data User = User { username :: Text, pic :: FilePath }
99
106
--
100
- -- instance FromMultipart User where
107
+ -- instance FromMultipart Tmp User where
101
108
-- fromMultipart multipartData =
102
109
-- User \<$\> lookupInput "username" multipartData
103
110
-- \<*\> fmap fileContent (lookupFile "pic" multipartData)
104
111
--
105
- -- type API = MultipartForm User :> Post '[PlainText] String
112
+ -- type API = MultipartForm Tmp User :> Post '[PlainText] String
106
113
--
107
114
-- server :: User -> Handler String
108
115
-- server usr = return str
@@ -125,10 +132,14 @@ import qualified Data.ByteString.Lazy as LBS
125
132
-- after your handler has run, if they are still there. It is
126
133
-- therefore recommended to move or copy them somewhere in your
127
134
-- handler code if you need to keep the content around.
128
- data MultipartForm a
135
+ data MultipartForm tag a
129
136
130
137
-- | What servant gets out of a @multipart/form-data@ form submission.
131
138
--
139
+ -- The type parameter 'tag' tells if 'MultipartData' is stored as a
140
+ -- temporary file or stored in memory. 'tag' is type of either 'Mem'
141
+ -- or 'Tmp'.
142
+ --
132
143
-- The 'inputs' field contains a list of textual 'Input's, where
133
144
-- each input for which a value is provided gets to be in this list,
134
145
-- represented by the input name and the input value. See haddocks for
@@ -139,20 +150,19 @@ data MultipartForm a
139
150
-- 'FileData' which among other things contains the path to the temporary file
140
151
-- (to be removed when your handler is done running) with a given uploaded
141
152
-- file's content. See haddocks for 'FileData'.
142
- data MultipartData = MultipartData
153
+ data MultipartData tag = MultipartData
143
154
{ inputs :: [Input ]
144
- , files :: [FileData ]
155
+ , files :: [FileData tag ]
145
156
}
146
157
147
- -- TODO: this is specific to Tmp. we need a version that
148
- -- can handle Mem as well.
149
- fromRaw :: ([Network.Wai.Parse. Param ], [File FilePath ]) -> MultipartData
158
+ fromRaw :: forall tag . ([Network.Wai.Parse. Param ], [File (MultipartResult tag )])
159
+ -> MultipartData tag
150
160
fromRaw (inputs, files) = MultipartData is fs
151
161
152
162
where is = map (\ (name, val) -> Input (dec name) (dec val)) inputs
153
163
fs = map toFile files
154
164
155
- toFile :: File FilePath -> FileData
165
+ toFile :: File ( MultipartResult tag ) -> FileData tag
156
166
toFile (iname, fileinfo) =
157
167
FileData (dec iname)
158
168
(dec $ fileName fileinfo)
@@ -164,20 +174,24 @@ fromRaw (inputs, files) = MultipartData is fs
164
174
-- | Representation for an uploaded file, usually resulting from
165
175
-- picking a local file for an HTML input that looks like
166
176
-- @\<input type="file" name="somefile" /\>@.
167
- data FileData = FileData
177
+ data FileData tag = FileData
168
178
{ fdInputName :: Text -- ^ @name@ attribute of the corresponding
169
179
-- HTML @\<input\>@
170
180
, fdFileName :: Text -- ^ name of the file on the client's disk
171
181
, fdFileCType :: Text -- ^ MIME type for the file
172
- , fdFilePath :: FilePath -- ^ path to the temporary file that has the
182
+ , fdPayload :: MultipartResult tag
183
+ -- ^ path to the temporary file that has the
173
184
-- content of the user's original file. Only
174
185
-- valid during the execution of your handler as
175
186
-- it gets removed right after, which means you
176
187
-- really want to move or copy it in your handler.
177
- } deriving (Eq , Show )
188
+ }
189
+
190
+ deriving instance Eq (MultipartResult tag ) => Eq (FileData tag )
191
+ deriving instance Show (MultipartResult tag ) => Show (FileData tag )
178
192
179
193
-- | Lookup a file input with the given @name@ attribute.
180
- lookupFile :: Text -> MultipartData -> Maybe FileData
194
+ lookupFile :: Text -> MultipartData tag -> Maybe ( FileData tag )
181
195
lookupFile iname = find ((== iname) . fdInputName) . files
182
196
183
197
-- | Representation for a textual input (any @\<input\>@ type but @file@).
@@ -189,7 +203,7 @@ data Input = Input
189
203
} deriving (Eq , Show )
190
204
191
205
-- | Lookup a textual input with the given @name@ attribute.
192
- lookupInput :: Text -> MultipartData -> Maybe Text
206
+ lookupInput :: Text -> MultipartData tag -> Maybe Text
193
207
lookupInput iname = fmap iValue . find ((== iname) . iName) . inputs
194
208
195
209
-- | 'MultipartData' is the type representing
@@ -209,62 +223,71 @@ lookupInput iname = fmap iValue . find ((==iname) . iName) . inputs
209
223
-- User \<$\> lookupInput "username" (inputs form)
210
224
-- \<*\> fmap fdFilePath (lookupFile "pic" $ files form)
211
225
-- @
212
- class FromMultipart a where
226
+ class FromMultipart tag a where
213
227
-- | Given a value of type 'MultipartData', which consists
214
228
-- in a list of textual inputs and another list for
215
229
-- files, try to extract a value of type @a@. When
216
230
-- extraction fails, servant errors out with status code 400.
217
- fromMultipart :: MultipartData -> Maybe a
231
+ fromMultipart :: MultipartData tag -> Maybe a
218
232
219
- instance FromMultipart MultipartData where
233
+ instance FromMultipart tag ( MultipartData tag ) where
220
234
fromMultipart = Just
221
235
222
236
-- | Upon seeing @MultipartForm a :> ...@ in an API type,
223
237
--- servant-server will hand a value of type @a@ to your handler
224
238
-- assuming the request body's content type is
225
239
-- @multipart/form-data@ and the call to 'fromMultipart' succeeds.
226
- instance ( FromMultipart a
227
- , LookupContext config MultipartOptions
240
+ instance ( FromMultipart tag a
241
+ , MultipartBackend tag
242
+ , LookupContext config (MultipartOptions tag )
228
243
, HasServer sublayout config )
229
- => HasServer (MultipartForm a :> sublayout ) config where
244
+ => HasServer (MultipartForm tag a :> sublayout ) config where
230
245
231
- type ServerT (MultipartForm a :> sublayout ) m =
246
+ type ServerT (MultipartForm tag a :> sublayout ) m =
232
247
a -> ServerT sublayout m
233
248
234
249
route Proxy config subserver =
235
250
route psub config subserver'
236
251
where
237
252
psub = Proxy :: Proxy sublayout
238
253
pbak = Proxy :: Proxy b
239
- popts = Proxy :: Proxy MultipartOptions
240
- multipartOpts = fromMaybe defaultMultipartOptions
254
+ popts = Proxy :: Proxy ( MultipartOptions tag )
255
+ multipartOpts = fromMaybe ( defaultMultipartOptions pbak)
241
256
$ lookupContext popts config
242
- subserver' = addMultipartHandling multipartOpts subserver
257
+ subserver' = addMultipartHandling pbak multipartOpts subserver
243
258
244
259
-- Try and extract the request body as multipart/form-data,
245
260
-- returning the data as well as the resourcet InternalState
246
261
-- that allows us to properly clean up the temporary files
247
262
-- later on.
248
- check :: MultipartOptions -> DelayedIO MultipartData
249
- check opts = withRequest $ \ request -> do
263
+ check :: MultipartBackend tag
264
+ => Proxy tag
265
+ -> MultipartOptions tag
266
+ -> DelayedIO (MultipartData tag )
267
+ check pTag tag = withRequest $ \ request -> do
250
268
st <- liftResourceT getInternalState
251
- rawData <- liftIO $ parseRequestBodyEx parseOpts (tmpBackend opts st) request
269
+ rawData <- liftIO
270
+ $ parseRequestBodyEx
271
+ parseOpts
272
+ (backend pTag (backendOptions tag) st)
273
+ request
252
274
return (fromRaw rawData)
253
- where parseOpts = generalOptions opts
275
+ where parseOpts = generalOptions tag
254
276
255
277
-- Add multipart extraction support to a Delayed.
256
- addMultipartHandling :: FromMultipart multipart
257
- => MultipartOptions
278
+ addMultipartHandling :: forall tag multipart env a . (FromMultipart tag multipart , MultipartBackend tag )
279
+ => Proxy tag
280
+ -> MultipartOptions tag
258
281
-> Delayed env (multipart -> a )
259
282
-> Delayed env a
260
- addMultipartHandling opts subserver =
283
+ addMultipartHandling pTag opts subserver =
261
284
addBodyCheck subserver contentCheck bodyCheck
262
285
where
263
286
contentCheck = withRequest $ \ request ->
264
287
fuzzyMultipartCTCheck (contentTypeH request)
265
288
266
289
bodyCheck () = do
267
- mpd <- check opts :: DelayedIO MultipartData
290
+ mpd <- check pTag opts :: DelayedIO ( MultipartData tag )
268
291
case fromMultipart mpd of
269
292
Nothing -> liftRouteResult $ FailFatal
270
293
err400 { errBody = " fromMultipart returned Nothing" }
@@ -289,31 +312,60 @@ fuzzyMultipartCTCheck ct
289
312
" multipart/form-data" | Just _bound <- lookup " boundary" attrs -> True
290
313
_ -> False
291
314
292
- tmpBackend :: MultipartOptions
293
- -> InternalState
294
- -> ignored1
295
- -> ignored2
296
- -> IO SBS. ByteString
297
- -> IO FilePath
298
- tmpBackend opts =
299
- tempFileBackEndOpts (getTmpDir tmpOpts) (filenamePat tmpOpts)
300
- where
301
- tmpOpts = tmpOptions opts
302
-
303
315
-- | Global options for configuring how the
304
316
-- server should handle multipart data.
305
317
--
306
318
-- 'generalOptions' lets you specify mostly multipart parsing
307
319
-- related options, such as the maximum file size, while
308
- -- 'tmpOptions' lets you configure aspects specific to
309
- -- the temporary file backend. See haddocks for
310
- -- 'ParseRequestBodyOptions' and 'TmpBackendOptions' respectively
311
- -- for more information on what you can tweak.
312
- data MultipartOptions = MultipartOptions
313
- { generalOptions :: ParseRequestBodyOptions
314
- , tmpOptions :: TmpBackendOptions
320
+ -- 'backendOptions' lets you configure aspects specific to the chosen
321
+ -- backend. Note: there isn't anything to tweak in a memory
322
+ -- backend ('Mem'). Maximum file size etc. options are in
323
+ -- 'ParseRequestBodyOptions'.
324
+ --
325
+ -- See haddocks for 'ParseRequestBodyOptions' and
326
+ -- 'TmpBackendOptions' respectively for more information on
327
+ -- what you can tweak.
328
+ data MultipartOptions tag = MultipartOptions
329
+ { generalOptions :: ParseRequestBodyOptions
330
+ , backendOptions :: MultipartBackendOptions tag
315
331
}
316
332
333
+ class MultipartBackend tag where
334
+ type MultipartResult tag :: *
335
+ type MultipartBackendOptions tag :: *
336
+
337
+ backend :: Proxy tag
338
+ -> MultipartBackendOptions tag
339
+ -> InternalState
340
+ -> ignored1
341
+ -> ignored2
342
+ -> IO SBS. ByteString
343
+ -> IO (MultipartResult tag )
344
+
345
+ defaultBackendOptions :: Proxy tag -> MultipartBackendOptions tag
346
+
347
+ -- | Tag for data stored as a temporary file
348
+ data Tmp
349
+
350
+ -- | Tag for data stored in memory
351
+ data Mem
352
+
353
+ instance MultipartBackend Tmp where
354
+ type MultipartResult Tmp = FilePath
355
+ type MultipartBackendOptions Tmp = TmpBackendOptions
356
+
357
+ defaultBackendOptions _ = defaultTmpBackendOptions
358
+ backend _ opts = tmpBackend
359
+ where
360
+ tmpBackend = tempFileBackEndOpts (getTmpDir opts) (filenamePat opts)
361
+
362
+ instance MultipartBackend Mem where
363
+ type MultipartResult Mem = LBS. ByteString
364
+ type MultipartBackendOptions Mem = ()
365
+
366
+ defaultBackendOptions _ = ()
367
+ backend _ opts _ = lbsBackEnd
368
+
317
369
-- | Configuration for the temporary file based backend.
318
370
--
319
371
-- You can configure the way servant-multipart gets its hands
@@ -337,11 +389,11 @@ defaultTmpBackendOptions = TmpBackendOptions
337
389
-- | Default configuration for multipart handling.
338
390
--
339
391
-- Uses 'defaultParseRequestBodyOptions' and
340
- -- 'defaultTmpBackendOptions ' respectively.
341
- defaultMultipartOptions :: MultipartOptions
342
- defaultMultipartOptions = MultipartOptions
392
+ -- 'defaultBackendOptions ' respectively.
393
+ defaultMultipartOptions :: MultipartBackend tag => Proxy tag -> MultipartOptions tag
394
+ defaultMultipartOptions pTag = MultipartOptions
343
395
{ generalOptions = defaultParseRequestBodyOptions
344
- , tmpOptions = defaultTmpBackendOptions
396
+ , backendOptions = defaultBackendOptions pTag
345
397
}
346
398
347
399
-- Utility class that's like HasContextEntry
0 commit comments