, RecordWildCards
, ScopedTypeVariables
, UnicodeSyntax
+ , ViewPatterns
#-}
-- |Parse \"multipart/form-data\" based on RFC 2388:
-- <http://www.faqs.org/rfcs/rfc2388.html>
import qualified Data.Ascii as A
import Data.Attoparsec
import qualified Data.Attoparsec.Lazy as LP
-import qualified Data.ByteString.Lazy.Char8 as LS
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as LS
import Data.ByteString.Lazy.Search
import Data.Foldable
import Data.List
→ LS.ByteString
→ m (LS.ByteString, LS.ByteString)
{-# INLINEABLE getBody #-}
-getBody boundary src
- = case breakFindAfter (A.toByteString boundary) src of
- ((before, after), True)
- → return (before, after)
- _ → throwError "missing boundary"
+getBody (("\r\n--" ⊕) ∘ A.toByteString → boundary) src
+ = case breakOn boundary src of
+ (before, after)
+ | LS.null after
+ → throwError "missing boundary"
+ | otherwise
+ → let len = fromIntegral $ BS.length boundary
+ after' = LS.drop len after
+ in
+ return (before, after')
partToFormPair ∷ MonadError String m ⇒ Part → m (Ascii, FormData)
{-# INLINEABLE partToFormPair #-}
= emptyResource {
resGet
= Just $ do setContentType $ parseMIMEType "text/plain"
- outputChunk "getRemoteCertificate = "
+ putChunk "getRemoteCertificate = "
cert ← do cert ← getRemoteCertificate
case cert of
Just c → liftIO $ Lazy.pack <$> printX509 c
Nothing → return "Nothing"
- outputChunk cert
+ putChunks cert
}
genCert ∷ KeyPair k ⇒ k → IO X509