{-# LANGUAGE CPP #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
module Servant.Multipart
( MultipartForm
, MultipartForm'
, MultipartData(..)
, FromMultipart(..)
, lookupInput
, lookupFile
, MultipartOptions(..)
, defaultMultipartOptions
, MultipartBackend(..)
, Tmp
, TmpBackendOptions(..)
, Mem
, defaultTmpBackendOptions
, Input(..)
, FileData(..)
, genBoundary
, ToMultipart(..)
, multipartToBody
, ToMultipartSample(..)
) where
import Control.Lens ((<>~), (&), view, (.~))
import Control.Monad (replicateM)
import Control.Monad.IO.Class
import Control.Monad.Trans.Resource
import Data.Array (listArray, (!))
import Data.List (find, foldl')
import Data.Maybe
import Data.Monoid
import Data.String.Conversions (cs)
import Data.Text (Text, unpack)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Typeable
import Network.HTTP.Media.MediaType ((//), (/:))
import Network.Wai
import Network.Wai.Parse
import Servant hiding (contentType)
import Servant.API.Modifiers (FoldLenient)
import Servant.Client.Core (HasClient(..), RequestBody(RequestBodySource), setRequestBody)
import Servant.Docs hiding (samples)
import Servant.Foreign hiding (contentType)
import Servant.Server.Internal
import Servant.Types.SourceT (SourceT(..), source, StepT(..), fromActionStep)
import System.Directory
import System.IO (IOMode(ReadMode), withFile)
import System.Random (getStdRandom, Random(randomR))
import qualified Data.ByteString as SBS
import qualified Data.ByteString.Lazy as LBS
type MultipartForm tag a = MultipartForm' '[] tag a
data MultipartForm' (mods :: [*]) tag a
data MultipartData tag = MultipartData
{ inputs :: [Input]
, files :: [FileData tag]
}
fromRaw :: forall tag. ([Network.Wai.Parse.Param], [File (MultipartResult tag)])
-> MultipartData tag
fromRaw (inputs, files) = MultipartData is fs
where is = map (\(name, val) -> Input (dec name) (dec val)) inputs
fs = map toFile files
toFile :: File (MultipartResult tag) -> FileData tag
toFile (iname, fileinfo) =
FileData (dec iname)
(dec $ fileName fileinfo)
(dec $ fileContentType fileinfo)
(fileContent fileinfo)
dec = decodeUtf8
data FileData tag = FileData
{ fdInputName :: Text
, fdFileName :: Text
, fdFileCType :: Text
, fdPayload :: MultipartResult tag
}
deriving instance Eq (MultipartResult tag) => Eq (FileData tag)
deriving instance Show (MultipartResult tag) => Show (FileData tag)
lookupFile :: Text -> MultipartData tag -> Either String (FileData tag)
lookupFile iname =
maybe (Left $ "File " <> cs iname <> " not found") Right
. find ((==iname) . fdInputName)
. files
data Input = Input
{ iName :: Text
, iValue :: Text
} deriving (Eq, Show)
lookupInput :: Text -> MultipartData tag -> Either String Text
lookupInput iname =
maybe (Left $ "Field " <> cs iname <> " not found") (Right . iValue)
. find ((==iname) . iName)
. inputs
class FromMultipart tag a where
fromMultipart :: MultipartData tag -> Either String a
instance FromMultipart tag (MultipartData tag) where
fromMultipart = Right
class ToMultipart tag a where
toMultipart :: a -> MultipartData tag
instance ToMultipart tag (MultipartData tag) where
toMultipart = id
instance ( FromMultipart tag a
, MultipartBackend tag
, LookupContext config (MultipartOptions tag)
, SBoolI (FoldLenient mods)
, HasServer sublayout config )
=> HasServer (MultipartForm' mods tag a :> sublayout) config where
type ServerT (MultipartForm' mods tag a :> sublayout) m =
If (FoldLenient mods) (Either String a) a -> ServerT sublayout m
#if MIN_VERSION_servant_server(0,12,0)
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy sublayout) pc nt . s
#endif
route Proxy config subserver =
route psub config subserver'
where
psub = Proxy :: Proxy sublayout
pbak = Proxy :: Proxy b
popts = Proxy :: Proxy (MultipartOptions tag)
multipartOpts = fromMaybe (defaultMultipartOptions pbak)
$ lookupContext popts config
subserver' = addMultipartHandling @tag @a @mods pbak multipartOpts subserver
instance (ToMultipart tag a, HasClient m api, MultipartBackend tag)
=> HasClient m (MultipartForm' mods tag a :> api) where
type Client m (MultipartForm' mods tag a :> api) =
(LBS.ByteString, a) -> Client m api
clientWithRoute pm _ req (boundary, param) =
clientWithRoute pm (Proxy @api) $ setRequestBody newBody newMedia req
where
newBody = multipartToBody boundary $ toMultipart @tag param
newMedia = "multipart" // "form-data" /: ("boundary", LBS.toStrict boundary)
hoistClientMonad pm _ f cl = \a ->
hoistClientMonad pm (Proxy @api) f (cl a)
genBoundary :: IO LBS.ByteString
genBoundary = LBS.pack
. map (validChars !)
<$> indices
where
indices = replicateM 55 . getStdRandom $ randomR (0,61)
validChars = listArray (0 :: Int, 61)
[ 0x30, 0x31, 0x32, 0x33, 0x34, 0x35, 0x36, 0x37
, 0x38, 0x39, 0x41, 0x42
, 0x43, 0x44, 0x45, 0x46, 0x47, 0x48, 0x49, 0x4a
, 0x4b, 0x4c, 0x4d, 0x4e, 0x4f, 0x50, 0x51, 0x52
, 0x53, 0x54, 0x55, 0x56, 0x57, 0x58, 0x59, 0x5a
, 0x61, 0x62, 0x63, 0x64, 0x65, 0x66, 0x67, 0x68
, 0x69, 0x6a, 0x6b, 0x6c, 0x6d, 0x6e, 0x6f, 0x70
, 0x71, 0x72, 0x73, 0x74, 0x75, 0x76, 0x77, 0x78
, 0x79, 0x7a
]
multipartToBody :: forall tag.
MultipartBackend tag
=> LBS.ByteString
-> MultipartData tag
-> RequestBody
multipartToBody boundary mp = RequestBodySource $ files' <> source ["--", boundary, "--"]
where
(SourceT l) `mappend'` (SourceT r) = SourceT $ \k ->
l $ \lstep ->
r $ \rstep ->
k (appendStep lstep rstep)
appendStep Stop r = r
appendStep (Error err) _ = Error err
appendStep (Skip s) r = appendStep s r
appendStep (Yield x s) r = Yield x (appendStep s r)
appendStep (Effect ms) r = Effect $ (flip appendStep r <$> ms)
mempty' = SourceT ($ Stop)
crlf = "\r\n"
lencode = LBS.fromStrict . encodeUtf8
renderInput input = renderPart (lencode . iName $ input)
"text/plain"
""
(source . pure . lencode . iValue $ input)
inputs' = foldl' (\acc x -> acc `mappend'` renderInput x) mempty' (inputs mp)
renderFile :: FileData tag -> SourceIO LBS.ByteString
renderFile file = renderPart (lencode . fdInputName $ file)
(lencode . fdFileCType $ file)
((flip mappend) "\"" . mappend "; filename=\""
. lencode
. fdFileName $ file)
(loadFile (Proxy @tag) . fdPayload $ file)
files' = foldl' (\acc x -> acc `mappend'` renderFile x) inputs' (files mp)
renderPart name contentType extraParams payload =
source [ "--"
, boundary
, crlf
, "Content-Disposition: form-data; name=\""
, name
, "\""
, extraParams
, crlf
, "Content-Type: "
, contentType
, crlf
, crlf
] `mappend'` payload `mappend'` source [crlf]
check :: MultipartBackend tag
=> Proxy tag
-> MultipartOptions tag
-> DelayedIO (MultipartData tag)
check pTag tag = withRequest $ \request -> do
st <- liftResourceT getInternalState
rawData <- liftIO
$ parseRequestBodyEx
parseOpts
(backend pTag (backendOptions tag) st)
request
return (fromRaw rawData)
where parseOpts = generalOptions tag
addMultipartHandling :: forall tag multipart (mods :: [*]) env a. (FromMultipart tag multipart, MultipartBackend tag)
=> SBoolI (FoldLenient mods)
=> Proxy tag
-> MultipartOptions tag
-> Delayed env (If (FoldLenient mods) (Either String multipart) multipart -> a)
-> Delayed env a
addMultipartHandling pTag opts subserver =
addBodyCheck subserver contentCheck bodyCheck
where
contentCheck = withRequest $ \request ->
fuzzyMultipartCTCheck (contentTypeH request)
bodyCheck () = do
mpd <- check pTag opts :: DelayedIO (MultipartData tag)
case (sbool :: SBool (FoldLenient mods), fromMultipart @tag @multipart mpd) of
(SFalse, Left msg) -> liftRouteResult $ FailFatal
err400 { errBody = "Could not decode multipart mime body: " <> cs msg }
(SFalse, Right x) -> return x
(STrue, res) -> return $ either (Left . cs) Right res
contentTypeH req = fromMaybe "application/octet-stream" $
lookup "Content-Type" (requestHeaders req)
fuzzyMultipartCTCheck :: SBS.ByteString -> DelayedIO ()
fuzzyMultipartCTCheck ct
| ctMatches = return ()
| otherwise = delayedFailFatal err400 {
errBody = "The content type of the request body is not in application/x-www-form-urlencoded or multipart/form-data"
}
where (ctype, attrs) = parseContentType ct
ctMatches = case ctype of
"application/x-www-form-urlencoded" -> True
"multipart/form-data" | Just _bound <- lookup "boundary" attrs -> True
_ -> False
data MultipartOptions tag = MultipartOptions
{ generalOptions :: ParseRequestBodyOptions
, backendOptions :: MultipartBackendOptions tag
}
class MultipartBackend tag where
type MultipartResult tag :: *
type MultipartBackendOptions tag :: *
backend :: Proxy tag
-> MultipartBackendOptions tag
-> InternalState
-> ignored1
-> ignored2
-> IO SBS.ByteString
-> IO (MultipartResult tag)
loadFile :: Proxy tag -> MultipartResult tag -> SourceIO LBS.ByteString
defaultBackendOptions :: Proxy tag -> MultipartBackendOptions tag
data Tmp
data Mem
instance MultipartBackend Tmp where
type MultipartResult Tmp = FilePath
type MultipartBackendOptions Tmp = TmpBackendOptions
defaultBackendOptions _ = defaultTmpBackendOptions
loadFile _ fp =
SourceT $ \k ->
withFile fp ReadMode $ \hdl ->
k (readHandle hdl)
where
readHandle hdl = fromActionStep LBS.null (LBS.hGet hdl 4096)
backend _ opts = tmpBackend
where
tmpBackend = tempFileBackEndOpts (getTmpDir opts) (filenamePat opts)
instance MultipartBackend Mem where
type MultipartResult Mem = LBS.ByteString
type MultipartBackendOptions Mem = ()
defaultBackendOptions _ = ()
loadFile _ = source . pure
backend _ _ _ = lbsBackEnd
data TmpBackendOptions = TmpBackendOptions
{ getTmpDir :: IO FilePath
, filenamePat :: String
}
defaultTmpBackendOptions :: TmpBackendOptions
defaultTmpBackendOptions = TmpBackendOptions
{ getTmpDir = getTemporaryDirectory
, filenamePat = "servant-multipart.buf"
}
defaultMultipartOptions :: MultipartBackend tag => Proxy tag -> MultipartOptions tag
defaultMultipartOptions pTag = MultipartOptions
{ generalOptions = defaultParseRequestBodyOptions
, backendOptions = defaultBackendOptions pTag
}
class LookupContext ctx a where
lookupContext :: Proxy a -> Context ctx -> Maybe a
instance LookupContext '[] a where
lookupContext _ _ = Nothing
instance {-# OVERLAPPABLE #-}
LookupContext cs a => LookupContext (c ': cs) a where
lookupContext p (_ :. cxts) =
lookupContext p cxts
instance {-# OVERLAPPING #-}
LookupContext cs a => LookupContext (a ': cs) a where
lookupContext _ (c :. _) = Just c
instance HasLink sub => HasLink (MultipartForm tag a :> sub) where
#if MIN_VERSION_servant(0,14,0)
type MkLink (MultipartForm tag a :> sub) r = MkLink sub r
toLink toA _ = toLink toA (Proxy :: Proxy sub)
#else
type MkLink (MultipartForm tag a :> sub) = MkLink sub
toLink _ = toLink (Proxy :: Proxy sub)
#endif
class ToMultipartSample tag a where
toMultipartSamples :: Proxy a -> [(Text, MultipartData tag)]
multipartInputToItem :: Input -> Text
multipartInputToItem (Input name val) =
" - *" <> name <> "*: " <> "`" <> val <> "`"
multipartFileToItem :: FileData tag -> Text
multipartFileToItem (FileData name _ contentType _) =
" - *" <> name <> "*, content-type: " <> "`" <> contentType <> "`"
multipartSampleToDesc
:: Text
-> MultipartData tag
-> Text
multipartSampleToDesc desc (MultipartData inputs files) =
"- " <> desc <> "\n" <>
" - textual inputs (any `<input>` type but file):\n" <>
foldMap (\input -> multipartInputToItem input <> "\n") inputs <>
" - file inputs (any HTML input that looks like `<input type=\"file\" name=\"somefile\" />`):\n" <>
foldMap (\file -> multipartFileToItem file <> "\n") files
toMultipartDescriptions
:: forall tag a.
ToMultipartSample tag a
=> Proxy tag -> Proxy a -> [Text]
toMultipartDescriptions _ proxyA = fmap (uncurry multipartSampleToDesc) samples
where
samples :: [(Text, MultipartData tag)]
samples = toMultipartSamples proxyA
toMultipartNotes
:: ToMultipartSample tag a
=> Int -> Proxy tag -> Proxy a -> DocNote
toMultipartNotes maxSamples' proxyTag proxyA =
let sampleLines = take maxSamples' $ toMultipartDescriptions proxyTag proxyA
body =
[ "This endpoint takes `multipart/form-data` requests. The following is " <>
"a list of sample requests:"
, foldMap (<> "\n") sampleLines
]
in DocNote "Multipart Request Samples" $ fmap unpack body
instance (HasDocs api, ToMultipartSample tag a) => HasDocs (MultipartForm tag a :> api) where
docsFor
:: Proxy (MultipartForm tag a :> api)
-> (Endpoint, Action)
-> DocOptions
-> API
docsFor _ (endpoint, action) opts =
let newAction =
action
& notes <>~
[ toMultipartNotes
(view maxSamples opts)
(Proxy :: Proxy tag)
(Proxy :: Proxy a)
]
in docsFor (Proxy :: Proxy api) (endpoint, newAction) opts
instance (HasForeignType lang ftype a, HasForeign lang ftype api)
=> HasForeign lang ftype (MultipartForm t a :> api) where
type Foreign ftype (MultipartForm t a :> api) = Foreign ftype api
foreignFor lang ftype Proxy req =
foreignFor lang ftype (Proxy @api) $
req & reqBody .~ Just t
& reqBodyContentType .~ ReqBodyMultipart
where
t = typeFor lang ftype (Proxy @a)