module Network.HTTP.Client.MultipartFormData
    (
    
     Part
    ,partName
    ,partFilename
    ,partContentType
    ,partHeaders
    ,partGetBody
    
    ,partBS
    ,partLBS
    ,partFile
    ,partFileSource
    ,partFileSourceChunked
    ,partFileRequestBody
    ,partFileRequestBodyM
    
    ,addPartHeaders
    
    ,formDataBody
    ,formDataBodyWithBoundary
    
    ,webkitBoundary
    ,webkitBoundaryPure
    
    ,renderParts
    ,renderPart
    ) where
import Network.HTTP.Client hiding (streamFile)
import Network.Mime
import Network.HTTP.Types (hContentType, methodPost, Header())
import Data.Monoid ((<>))
import Data.Foldable (foldMap)
import Blaze.ByteString.Builder
import Data.Text
import qualified Data.Text.Encoding as TE
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString as BS
import qualified Data.CaseInsensitive as CI
import Control.Monad.Trans.State.Strict (state, runState)
import Control.Monad.IO.Class
import System.FilePath
import System.Random
import Data.Array.Base
import System.IO
import Data.Bits
import Data.Word
import Data.Monoid (Monoid(..))
import Control.Monad
import Data.ByteString.Lazy.Internal (defaultChunkSize)
data Part = Part
    { partName :: Text 
    , partFilename :: Maybe String 
    , partContentType :: Maybe MimeType 
    , partHeaders :: [Header] 
    , partGetBody :: IO RequestBody 
                                   
    }
instance Show Part where
    showsPrec d (Part n f c h _) =
        showParen (d>=11) $ showString "Part "
            . showsPrec 11 n
            . showString " "
            . showsPrec 11 f
            . showString " "
            . showsPrec 11 c
            . showString " "
            . showsPrec 11 h
            . showString " "
            . showString "<m (RequestBody m)>"
partBS :: Text              
       -> BS.ByteString     
       -> Part
partBS n b = Part n Data.Monoid.mempty mempty mempty $ return $ RequestBodyBS b
partLBS :: Text             
        -> BL.ByteString    
        -> Part
partLBS n b = Part n mempty mempty mempty $ return $ RequestBodyLBS b
partFile :: Text            
         -> FilePath        
         -> Part
partFile n f =
    partFileRequestBodyM n f $ do
        liftM RequestBodyBS $ liftIO $ BS.readFile f
partFileSource :: Text      
               -> FilePath  
               -> Part
partFileSource n f =
    partFileRequestBodyM n f $ do
        size <- liftIO $ withBinaryFile f ReadMode hFileSize
        return $ RequestBodyStream (fromInteger size) $ streamFile f
streamFile :: FilePath -> GivesPopper ()
streamFile fp np =
    withFile fp ReadMode $ np . go
  where
    go h = BS.hGetSome h defaultChunkSize
partFileSourceChunked :: Text -> FilePath -> Part
partFileSourceChunked n f =
    partFileRequestBody n f $ do
        RequestBodyStreamChunked $ streamFile f
partFileRequestBody :: Text        
                    -> FilePath    
                    -> RequestBody 
                    -> Part
partFileRequestBody n f rqb =
    partFileRequestBodyM n f $ return rqb
partFileRequestBodyM :: Text        
                     -> FilePath    
                     -> IO RequestBody 
                     -> Part
partFileRequestBodyM n f rqb =
    Part n (Just f) (Just $ defaultMimeLookup $ pack f) mempty rqb
cp :: BS.ByteString -> RequestBody
cp bs = RequestBodyBuilder (fromIntegral $ BS.length bs) $ copyByteString bs
addPartHeaders :: Part -> [Header] -> Part
addPartHeaders p hs = p { partHeaders = partHeaders p <> hs }
renderPart :: BS.ByteString     
           -> Part -> IO RequestBody
renderPart boundary (Part name mfilename mcontenttype hdrs get) = liftM render get
  where render renderBody =
            cp "--" <> cp boundary <> cp "\r\n"
         <> cp "Content-Disposition: form-data; name=\""
         <> RequestBodyBS (TE.encodeUtf8 name)
         <> (case mfilename of
                 Just f -> cp "\"; filename=\""
                        <> RequestBodyBS (TE.encodeUtf8 $ pack $ takeFileName f)
                 _ -> mempty)
         <> cp "\""
         <> (case mcontenttype of
                Just ct -> cp "\r\n"
                        <> cp "Content-Type: "
                        <> cp ct
                _ -> mempty)
         <> Data.Foldable.foldMap (\(k, v) ->
               cp "\r\n"
            <> cp (CI.original k)
            <> cp ": "
            <> cp v) hdrs
         <> cp "\r\n\r\n"
         <> renderBody <> cp "\r\n"
renderParts :: BS.ByteString    
            -> [Part] -> IO RequestBody
renderParts boundary parts = (fin . mconcat) `liftM` mapM (renderPart boundary) parts
  where fin = (<> cp "--" <> cp boundary <> cp "--\r\n")
webkitBoundary :: IO BS.ByteString
webkitBoundary = getStdRandom webkitBoundaryPure
webkitBoundaryPure :: RandomGen g => g -> (BS.ByteString, g)
webkitBoundaryPure g = (`runState` g) $ do
    fmap (BS.append prefix . BS.pack . Prelude.concat) $ replicateM 4 $ do
        randomness <- state $ random
        return [unsafeAt alphaNumericEncodingMap $ randomness `shiftR` 24 .&. 0x3F
               ,unsafeAt alphaNumericEncodingMap $ randomness `shiftR` 16 .&. 0x3F
               ,unsafeAt alphaNumericEncodingMap $ randomness `shiftR` 8 .&. 0x3F
               ,unsafeAt alphaNumericEncodingMap $ randomness .&. 0x3F]
  where
    prefix = "----WebKitFormBoundary"
    alphaNumericEncodingMap :: UArray Int Word8
    alphaNumericEncodingMap = listArray (0, 63)
        [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, 0x30, 0x31, 0x32, 0x33,
         0x34, 0x35, 0x36, 0x37, 0x38, 0x39, 0x41, 0x42]
formDataBody :: MonadIO m => [Part] -> Request -> m Request
formDataBody a b = liftIO $ do
    boundary <- webkitBoundary
    formDataBodyWithBoundary boundary a b
formDataBodyWithBoundary :: BS.ByteString -> [Part] -> Request -> IO Request
formDataBodyWithBoundary boundary parts req = do
    body <- renderParts boundary parts
    return $ req
        { method = methodPost
        , requestHeaders =
            (hContentType, "multipart/form-data; boundary=" <> boundary)
          : Prelude.filter (\(x, _) -> x /= hContentType) (requestHeaders req)
        , requestBody = body
        }