Skip to content

Commit f78bfff

Browse files
author
ArktinenSieni
committed
options not as token
1 parent 34b69a6 commit f78bfff

File tree

2 files changed

+61
-50
lines changed

2 files changed

+61
-50
lines changed

exe/Upload.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ import qualified Data.ByteString.Lazy as LBS
1919
-- Our API, which consists in a single POST endpoint at /
2020
-- that takes a multipart/form-data request body and
2121
-- pretty-prints the data it got to stdout before returning 0.
22-
type API = MultipartForm LbsBackendOptions (MultipartData LbsBackendOptions) :> Post '[JSON] Integer
22+
type API = MultipartForm Mem (MultipartData Mem) :> Post '[JSON] Integer
2323

2424
api :: Proxy API
2525
api = Proxy
@@ -40,7 +40,7 @@ upload multipartData = do
4040
++ " -> " ++ show (iValue input)
4141

4242
forM_ (files multipartData) $ \file -> do
43-
let content = fdFilePath file
43+
let content = fdPayload file
4444
putStrLn $ "Content of " ++ show (fdFileName file)
4545
LBS.putStr content
4646
return 0

src/Servant/Multipart.hs

Lines changed: 59 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -22,8 +22,8 @@ module Servant.Multipart
2222
, lookupFile
2323
, MultipartOptions(..)
2424
, defaultMultipartOptions
25-
, TmpBackendOptions(..)
26-
, LbsBackendOptions(..)
25+
, Tmp
26+
, Mem
2727
, defaultTmpBackendOptions
2828
, Input(..)
2929
, FileData(..)
@@ -128,7 +128,7 @@ import qualified Data.ByteString.Lazy as LBS
128128
-- after your handler has run, if they are still there. It is
129129
-- therefore recommended to move or copy them somewhere in your
130130
-- handler code if you need to keep the content around.
131-
data MultipartForm options a
131+
data MultipartForm tag a
132132

133133
-- | What servant gets out of a @multipart/form-data@ form submission.
134134
--
@@ -142,9 +142,9 @@ data MultipartForm options a
142142
-- 'FileData' which among other things contains the path to the temporary file
143143
-- (to be removed when your handler is done running) with a given uploaded
144144
-- file's content. See haddocks for 'FileData'.
145-
data MultipartData options = MultipartData
145+
data MultipartData tag = MultipartData
146146
{ inputs :: [Input]
147-
, files :: [FileData options]
147+
, files :: [FileData tag]
148148
}
149149

150150

@@ -169,24 +169,24 @@ fromRaw (inputs, files) = MultipartData is fs
169169
-- | Representation for an uploaded file, usually resulting from
170170
-- picking a local file for an HTML input that looks like
171171
-- @\<input type="file" name="somefile" /\>@.
172-
data FileData options = FileData
172+
data FileData tag = FileData
173173
{ fdInputName :: Text -- ^ @name@ attribute of the corresponding
174174
-- HTML @\<input\>@
175175
, fdFileName :: Text -- ^ name of the file on the client's disk
176176
, fdFileCType :: Text -- ^ MIME type for the file
177-
, fdPayload :: MultipartResult options
177+
, fdPayload :: MultipartResult tag
178178
-- ^ path to the temporary file that has the
179179
-- content of the user's original file. Only
180180
-- valid during the execution of your handler as
181181
-- it gets removed right after, which means you
182182
-- really want to move or copy it in your handler.
183183
}
184184

185-
deriving instance Eq (MultipartResult options) => Eq (FileData options)
186-
deriving instance Show (MultipartResult options) => Show (FileData options)
185+
deriving instance Eq (MultipartResult tag) => Eq (FileData tag)
186+
deriving instance Show (MultipartResult tag) => Show (FileData tag)
187187

188188
-- | Lookup a file input with the given @name@ attribute.
189-
lookupFile :: Text -> MultipartData options -> Maybe (FileData options)
189+
lookupFile :: Text -> MultipartData tag -> Maybe (FileData tag)
190190
lookupFile iname = find ((==iname) . fdInputName) . files
191191

192192
-- | Representation for a textual input (any @\<input\>@ type but @file@).
@@ -198,7 +198,7 @@ data Input = Input
198198
} deriving (Eq, Show)
199199

200200
-- | Lookup a textual input with the given @name@ attribute.
201-
lookupInput :: Text -> MultipartData options -> Maybe Text
201+
lookupInput :: Text -> MultipartData tag -> Maybe Text
202202
lookupInput iname = fmap iValue . find ((==iname) . iName) . inputs
203203

204204
-- | 'MultipartData' is the type representing
@@ -218,63 +218,64 @@ lookupInput iname = fmap iValue . find ((==iname) . iName) . inputs
218218
-- User \<$\> lookupInput "username" (inputs form)
219219
-- \<*\> fmap fdFilePath (lookupFile "pic" $ files form)
220220
-- @
221-
class FromMultipart options a where
221+
class FromMultipart tag a where
222222
-- | Given a value of type 'MultipartData', which consists
223223
-- in a list of textual inputs and another list for
224224
-- files, try to extract a value of type @a@. When
225225
-- extraction fails, servant errors out with status code 400.
226-
fromMultipart :: MultipartData options -> Maybe a
226+
fromMultipart :: MultipartData tag -> Maybe a
227227

228-
instance FromMultipart options (MultipartData options) where
228+
instance FromMultipart tag (MultipartData tag) where
229229
fromMultipart = Just
230230

231231
-- | Upon seeing @MultipartForm a :> ...@ in an API type,
232232
--- servant-server will hand a value of type @a@ to your handler
233233
-- assuming the request body's content type is
234234
-- @multipart/form-data@ and the call to 'fromMultipart' succeeds.
235-
instance ( FromMultipart options a
236-
, MultipartBackend options
237-
, LookupContext config (MultipartOptions options)
235+
instance ( FromMultipart tag a
236+
, MultipartBackend tag
237+
, LookupContext config (MultipartOptions tag)
238238
, HasServer sublayout config )
239-
=> HasServer (MultipartForm options a :> sublayout) config where
239+
=> HasServer (MultipartForm tag a :> sublayout) config where
240240

241-
type ServerT (MultipartForm options a :> sublayout) m =
241+
type ServerT (MultipartForm tag a :> sublayout) m =
242242
a -> ServerT sublayout m
243243

244244
route Proxy config subserver =
245245
route psub config subserver'
246246
where
247247
psub = Proxy :: Proxy sublayout
248248
pbak = Proxy :: Proxy b
249-
popts = Proxy :: Proxy (MultipartOptions options)
250-
multipartOpts = fromMaybe defaultMultipartOptions
249+
popts = Proxy :: Proxy (MultipartOptions tag)
250+
multipartOpts = fromMaybe (defaultMultipartOptions pbak)
251251
$ lookupContext popts config
252-
subserver' = addMultipartHandling multipartOpts subserver
252+
subserver' = addMultipartHandling pbak multipartOpts subserver
253253

254254
-- Try and extract the request body as multipart/form-data,
255255
-- returning the data as well as the resourcet InternalState
256256
-- that allows us to properly clean up the temporary files
257257
-- later on.
258-
check :: MultipartBackend options => MultipartOptions options -> DelayedIO (MultipartData options)
259-
check opts = withRequest $ \request -> do
258+
check :: MultipartBackend tag => Proxy tag -> MultipartOptions tag -> DelayedIO (MultipartData tag)
259+
check prx tag = withRequest $ \request -> do
260260
st <- liftResourceT getInternalState
261-
rawData <- liftIO $ parseRequestBodyEx parseOpts (backend (options opts) st) request
261+
rawData <- liftIO $ parseRequestBodyEx parseOpts (backend prx (options tag) st) request
262262
return (fromRaw rawData)
263-
where parseOpts = generalOptions opts
263+
where parseOpts = generalOptions tag
264264

265265
-- Add multipart extraction support to a Delayed.
266-
addMultipartHandling :: forall options multipart env a. (FromMultipart options multipart, MultipartBackend options)
267-
=> MultipartOptions options
266+
addMultipartHandling :: forall tag multipart env a. (FromMultipart tag multipart, MultipartBackend tag)
267+
=> Proxy tag
268+
-> MultipartOptions tag
268269
-> Delayed env (multipart -> a)
269270
-> Delayed env a
270-
addMultipartHandling opts subserver =
271+
addMultipartHandling prx opts subserver =
271272
addBodyCheck subserver contentCheck bodyCheck
272273
where
273274
contentCheck = withRequest $ \request ->
274275
fuzzyMultipartCTCheck (contentTypeH request)
275276

276277
bodyCheck () = do
277-
mpd <- check opts :: DelayedIO (MultipartData options)
278+
mpd <- check prx opts :: DelayedIO (MultipartData tag)
278279
case fromMultipart mpd of
279280
Nothing -> liftRouteResult $ FailFatal
280281
err400 { errBody = "fromMultipart returned Nothing" }
@@ -308,36 +309,46 @@ fuzzyMultipartCTCheck ct
308309
-- the temporary file backend. See haddocks for
309310
-- 'ParseRequestBodyOptions' and 'TmpBackendOptions' respectively
310311
-- for more information on what you can tweak.
311-
data MultipartOptions options = MultipartOptions
312+
data MultipartOptions tag = MultipartOptions
312313
{ generalOptions :: ParseRequestBodyOptions
313-
, options :: options
314+
, options :: MultipartBackendOptions tag
314315
}
315316

316-
class MultipartBackend options where
317-
type MultipartResult options :: *
317+
class MultipartBackend tag where
318+
type MultipartResult tag :: *
319+
type MultipartBackendOptions tag :: *
318320

319-
backend :: options
321+
backend :: Proxy tag
322+
-> MultipartBackendOptions tag
320323
-> InternalState
321324
-> ignored1
322325
-> ignored2
323326
-> IO SBS.ByteString
324-
-> IO (MultipartResult options)
327+
-> IO (MultipartResult tag)
325328

326-
defaultBackendOptions :: options
329+
defaultBackendOptions :: Proxy tag -> MultipartBackendOptions tag
327330

328-
instance MultipartBackend TmpBackendOptions where
329-
type MultipartResult TmpBackendOptions = FilePath
331+
-- | Tag for temporary files
332+
data Tmp
330333

331-
defaultBackendOptions = defaultTmpBackendOptions
332-
backend opts = tmpBackend
334+
-- | Tag for items in memory
335+
data Mem
336+
337+
instance MultipartBackend Tmp where
338+
type MultipartResult Tmp = FilePath
339+
type MultipartBackendOptions Tmp = TmpBackendOptions
340+
341+
defaultBackendOptions _ = defaultTmpBackendOptions
342+
backend _ opts = tmpBackend
333343
where
334344
tmpBackend = tempFileBackEndOpts (getTmpDir opts) (filenamePat opts)
335345

336-
instance MultipartBackend LbsBackendOptions where
337-
type MultipartResult LbsBackendOptions = LBS.ByteString
346+
instance MultipartBackend Mem where
347+
type MultipartResult Mem = LBS.ByteString
348+
type MultipartBackendOptions Mem = LbsBackendOptions
338349

339-
defaultBackendOptions = LbsBackendOptions
340-
backend opts _ = lbsBackEnd
350+
defaultBackendOptions _ = LbsBackendOptions
351+
backend _ opts _ = lbsBackEnd
341352

342353
-- | TODO: write me
343354
data LbsBackendOptions = LbsBackendOptions
@@ -366,10 +377,10 @@ defaultTmpBackendOptions = TmpBackendOptions
366377
--
367378
-- Uses 'defaultParseRequestBodyOptions' and
368379
-- 'defaultTmpBackendOptions' respectively.
369-
defaultMultipartOptions :: MultipartBackend options => MultipartOptions options
370-
defaultMultipartOptions = MultipartOptions
380+
defaultMultipartOptions :: MultipartBackend tag => Proxy tag -> MultipartOptions tag
381+
defaultMultipartOptions prx = MultipartOptions
371382
{ generalOptions = defaultParseRequestBodyOptions
372-
, options = defaultBackendOptions
383+
, options = defaultBackendOptions prx
373384
}
374385

375386
-- Utility class that's like HasContextEntry

0 commit comments

Comments
 (0)