Read the dispositon header when downloading
This commit is contained in:
parent
e5bde183a5
commit
cd15b25db1
@ -18,6 +18,7 @@ module SlackBuilder.Download
|
|||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import qualified Data.ByteString as ByteString
|
import qualified Data.ByteString as ByteString
|
||||||
import qualified Data.ByteString.Char8 as Char8
|
import qualified Data.ByteString.Char8 as Char8
|
||||||
|
import qualified Data.List.NonEmpty as NonEmpty
|
||||||
import Data.Foldable (find)
|
import Data.Foldable (find)
|
||||||
import Data.Map.Strict (Map)
|
import Data.Map.Strict (Map)
|
||||||
import qualified Data.Map.Strict as Map
|
import qualified Data.Map.Strict as Map
|
||||||
@ -40,7 +41,8 @@ import System.Process
|
|||||||
)
|
)
|
||||||
import System.Exit (ExitCode(..))
|
import System.Exit (ExitCode(..))
|
||||||
import Control.Monad (unless)
|
import Control.Monad (unless)
|
||||||
import Text.URI (URI(..), mkURI)
|
import Text.URI (URI(..))
|
||||||
|
import qualified Text.URI as URI
|
||||||
import Network.HTTP.Req
|
import Network.HTTP.Req
|
||||||
( useHttpsURI
|
( useHttpsURI
|
||||||
, HEAD(..)
|
, HEAD(..)
|
||||||
@ -52,7 +54,7 @@ import Network.HTTP.Req
|
|||||||
, responseStatusCode
|
, responseStatusCode
|
||||||
, HttpConfig(..)
|
, HttpConfig(..)
|
||||||
, GET(..)
|
, GET(..)
|
||||||
, reqBr
|
, reqBr, MonadHttp
|
||||||
)
|
)
|
||||||
import Data.Functor ((<&>))
|
import Data.Functor ((<&>))
|
||||||
import Network.HTTP.Client (BodyReader, Response(..), brRead)
|
import Network.HTTP.Client (BodyReader, Response(..), brRead)
|
||||||
@ -72,6 +74,7 @@ import Data.Void (Void)
|
|||||||
import qualified Data.Conduit.Lzma as Lzma
|
import qualified Data.Conduit.Lzma as Lzma
|
||||||
import qualified Data.Conduit.Zlib as Zlib
|
import qualified Data.Conduit.Zlib as Zlib
|
||||||
import Control.Monad.Catch (MonadThrow(..))
|
import Control.Monad.Catch (MonadThrow(..))
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
|
||||||
updateSlackBuildVersion :: Text -> Text -> Map Text Text -> SlackBuilderT ()
|
updateSlackBuildVersion :: Text -> Text -> Map Text Text -> SlackBuilderT ()
|
||||||
updateSlackBuildVersion packagePath version additionalDownloads = do
|
updateSlackBuildVersion packagePath version additionalDownloads = do
|
||||||
@ -127,7 +130,7 @@ commit packagePath version = do
|
|||||||
|
|
||||||
hostedSources :: Text -> SlackBuilderT URI
|
hostedSources :: Text -> SlackBuilderT URI
|
||||||
hostedSources absoluteURL = SlackBuilderT (asks downloadURL)
|
hostedSources absoluteURL = SlackBuilderT (asks downloadURL)
|
||||||
>>= liftIO . mkURI . (<> absoluteURL)
|
>>= liftIO . URI.mkURI . (<> absoluteURL)
|
||||||
|
|
||||||
remoteFileExists :: Text -> SlackBuilderT Bool
|
remoteFileExists :: Text -> SlackBuilderT Bool
|
||||||
remoteFileExists url = hostedSources url
|
remoteFileExists url = hostedSources url
|
||||||
@ -196,17 +199,7 @@ sinkHash = sink hashInit
|
|||||||
sink ctx = await
|
sink ctx = await
|
||||||
>>= maybe (pure $ hashFinalize ctx) (sink . hashUpdate ctx)
|
>>= maybe (pure $ hashFinalize ctx) (sink . hashUpdate ctx)
|
||||||
|
|
||||||
download :: URI -> FilePath -> SlackBuilderT (Maybe (Digest MD5))
|
cloneAndUpload :: Text -> FilePath -> Text -> SlackBuilderT (URI, Digest MD5)
|
||||||
download uri target = traverse (runReq defaultHttpConfig . go . fst)
|
|
||||||
$ useHttpsURI uri
|
|
||||||
where
|
|
||||||
go uri' = reqBr GET uri' NoReqBody mempty readResponse
|
|
||||||
readResponse :: Response BodyReader -> IO (Digest MD5)
|
|
||||||
readResponse response = runConduitRes
|
|
||||||
$ responseBodySource response
|
|
||||||
.| getZipSink (ZipSink (sinkFile target) *> ZipSink sinkHash)
|
|
||||||
|
|
||||||
cloneAndUpload :: Text -> FilePath -> Text -> SlackBuilderT (Maybe (URI, Digest MD5))
|
|
||||||
cloneAndUpload repo tarballPath tagPrefix = do
|
cloneAndUpload repo tarballPath tagPrefix = do
|
||||||
localPath <- relativeToRepository $ tarballPath <.> "tar.xz"
|
localPath <- relativeToRepository $ tarballPath <.> "tar.xz"
|
||||||
let packageName = takeFileName $ takeDirectory tarballPath
|
let packageName = takeFileName $ takeDirectory tarballPath
|
||||||
@ -216,12 +209,40 @@ cloneAndUpload repo tarballPath tagPrefix = do
|
|||||||
remoteFileExists' <- remoteFileExists remoteArchivePath
|
remoteFileExists' <- remoteFileExists remoteArchivePath
|
||||||
|
|
||||||
if remoteFileExists'
|
if remoteFileExists'
|
||||||
then fmap (remoteResultURI,) <$> download remoteResultURI localPath
|
then (remoteResultURI,) . snd
|
||||||
|
<$> download remoteResultURI (takeDirectory localPath)
|
||||||
else
|
else
|
||||||
let go = sourceFile localPath .| sinkHash
|
let go = sourceFile localPath .| sinkHash
|
||||||
in cloneAndArchive repo tarballPath tagPrefix
|
in cloneAndArchive repo tarballPath tagPrefix
|
||||||
>> uploadCommand localPath remoteArchivePath
|
>> uploadCommand localPath remoteArchivePath
|
||||||
>> liftIO (runConduitRes go) <&> Just . (remoteResultURI,)
|
>> liftIO (runConduitRes go) <&> (remoteResultURI,)
|
||||||
|
|
||||||
|
-- | Downlaods a file into the directory. Returns name of the downloaded file
|
||||||
|
-- and checksum.
|
||||||
|
--
|
||||||
|
-- The filename is read from the disposition header or from the URL if the
|
||||||
|
-- Content-Disposition is missing.
|
||||||
|
download :: URI -> FilePath -> SlackBuilderT (FilePath, Digest MD5)
|
||||||
|
download uri packagePath = runReq defaultHttpConfig go
|
||||||
|
where
|
||||||
|
go
|
||||||
|
| Just uriPath <- URI.uriPath uri =
|
||||||
|
reqGet uri
|
||||||
|
$ readResponse
|
||||||
|
$ Text.unpack
|
||||||
|
$ URI.unRText
|
||||||
|
$ NonEmpty.last
|
||||||
|
$ snd uriPath
|
||||||
|
| otherwise = throwM $ HttpsUrlExpected uri
|
||||||
|
readResponse :: FilePath -> Response BodyReader -> IO (FilePath, Digest MD5)
|
||||||
|
readResponse downloadFileName response = do
|
||||||
|
let attachmentName = dispositionAttachment response
|
||||||
|
targetFileName = fromMaybe downloadFileName attachmentName
|
||||||
|
target = packagePath </> fromMaybe downloadFileName attachmentName
|
||||||
|
digest <- runConduitRes
|
||||||
|
$ responseBodySource response
|
||||||
|
.| getZipSink (ZipSink (sinkFile target) *> ZipSink sinkHash)
|
||||||
|
pure (targetFileName, digest)
|
||||||
|
|
||||||
-- | Downloads a compressed tar archive and extracts its contents on the fly to
|
-- | Downloads a compressed tar archive and extracts its contents on the fly to
|
||||||
-- a directory.
|
-- a directory.
|
||||||
@ -230,22 +251,14 @@ cloneAndUpload repo tarballPath tagPrefix = do
|
|||||||
-- recognized as tar archive, returns the attachment name from the
|
-- recognized as tar archive, returns the attachment name from the
|
||||||
-- disposition header without the extension. So if the disposition header
|
-- disposition header without the extension. So if the disposition header
|
||||||
-- is "attachment; filename=package-1.2.3.tar.gz", returns "package-1.2.3".
|
-- is "attachment; filename=package-1.2.3.tar.gz", returns "package-1.2.3".
|
||||||
extractRemote :: URI -> Text -> SlackBuilderT (Maybe Text)
|
extractRemote :: URI -> FilePath -> SlackBuilderT (Maybe FilePath)
|
||||||
extractRemote uri' packagePath = do
|
extractRemote uri' packagePath =
|
||||||
repository' <- SlackBuilderT $ asks repository
|
runReq defaultHttpConfig $ go packagePath
|
||||||
let localToRepository = repository' </> Text.unpack packagePath
|
|
||||||
case useHttpsURI uri' of
|
|
||||||
Just (httpsURI, _httpsOptions) ->
|
|
||||||
runReq defaultHttpConfig $ go localToRepository httpsURI
|
|
||||||
Nothing -> throwM $ HttpsUrlExpected uri'
|
|
||||||
where
|
where
|
||||||
go toTarget url' = reqBr GET url' NoReqBody mempty $ readResponse toTarget
|
go toTarget = reqGet uri' $ readResponse toTarget
|
||||||
readResponse :: FilePath -> Response BodyReader -> IO (Maybe Text)
|
readResponse :: FilePath -> Response BodyReader -> IO (Maybe FilePath)
|
||||||
readResponse toTarget response = do
|
readResponse toTarget response = do
|
||||||
let attachmentName
|
let attachmentName = dispositionAttachment response
|
||||||
= fmap (Char8.unpack . snd . Char8.breakEnd (== '=') . snd)
|
|
||||||
$ find ((== "Content-Disposition") . fst)
|
|
||||||
$ responseHeaders response
|
|
||||||
(decompress, attachmentDirectory) =
|
(decompress, attachmentDirectory) =
|
||||||
case attachmentName of
|
case attachmentName of
|
||||||
Just attachmentName'
|
Just attachmentName'
|
||||||
@ -257,8 +270,23 @@ extractRemote uri' packagePath = do
|
|||||||
runConduitRes $ responseBodySource response
|
runConduitRes $ responseBodySource response
|
||||||
.| decompress
|
.| decompress
|
||||||
.| untar (withDecompressedFile toTarget)
|
.| untar (withDecompressedFile toTarget)
|
||||||
pure $ Text.pack <$> attachmentDirectory
|
pure attachmentDirectory
|
||||||
withDecompressedFile toTarget FileInfo{..}
|
withDecompressedFile toTarget FileInfo{..}
|
||||||
| Char8.last filePath /= '/' =
|
| Char8.last filePath /= '/' =
|
||||||
sinkFile (toTarget </> Char8.unpack filePath)
|
sinkFile (toTarget </> Char8.unpack filePath)
|
||||||
| otherwise = liftIO (createDirectory (toTarget </> Char8.unpack filePath))
|
| otherwise = liftIO (createDirectory (toTarget </> Char8.unpack filePath))
|
||||||
|
|
||||||
|
dispositionAttachment :: Response BodyReader -> Maybe FilePath
|
||||||
|
dispositionAttachment response
|
||||||
|
= fmap (Char8.unpack . snd . Char8.breakEnd (== '=') . snd)
|
||||||
|
$ find ((== "Content-Disposition") . fst)
|
||||||
|
$ responseHeaders response
|
||||||
|
|
||||||
|
reqGet :: (MonadThrow m, MonadHttp m)
|
||||||
|
=> URI
|
||||||
|
-> (Response BodyReader -> IO a)
|
||||||
|
-> m a
|
||||||
|
reqGet uri bodyReader
|
||||||
|
| Just (httpsURI, httpsOptions) <- useHttpsURI uri =
|
||||||
|
reqBr GET httpsURI NoReqBody httpsOptions bodyReader
|
||||||
|
| otherwise = throwM $ HttpsUrlExpected uri
|
||||||
|
55
src/Main.hs
55
src/Main.hs
@ -12,7 +12,7 @@ import Data.List.NonEmpty (NonEmpty(..))
|
|||||||
import qualified Data.List.NonEmpty as NonEmpty
|
import qualified Data.List.NonEmpty as NonEmpty
|
||||||
import Control.Monad.Catch (MonadThrow(..))
|
import Control.Monad.Catch (MonadThrow(..))
|
||||||
import Control.Monad.IO.Class (MonadIO(..))
|
import Control.Monad.IO.Class (MonadIO(..))
|
||||||
import Data.Maybe (fromJust)
|
import Data.Maybe (fromJust, fromMaybe)
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Options.Applicative (execParser)
|
import Options.Applicative (execParser)
|
||||||
import SlackBuilder.CommandLine
|
import SlackBuilder.CommandLine
|
||||||
@ -61,7 +61,7 @@ import System.Console.ANSI
|
|||||||
, ConsoleLayer(..)
|
, ConsoleLayer(..)
|
||||||
)
|
)
|
||||||
import System.Directory (listDirectory, doesDirectoryExist, withCurrentDirectory, removeDirectoryRecursive)
|
import System.Directory (listDirectory, doesDirectoryExist, withCurrentDirectory, removeDirectoryRecursive)
|
||||||
import Control.Monad (filterM, void)
|
import Control.Monad (filterM)
|
||||||
import Data.List (isPrefixOf, isSuffixOf, partition)
|
import Data.List (isPrefixOf, isSuffixOf, partition)
|
||||||
import Conduit (runConduitRes, (.|), sourceFile)
|
import Conduit (runConduitRes, (.|), sourceFile)
|
||||||
import Data.Functor ((<&>))
|
import Data.Functor ((<&>))
|
||||||
@ -381,7 +381,7 @@ cloneFromGit repo tagPrefix packagePath version = do
|
|||||||
$ NonEmpty.last $ snd $ fromJust $ URI.uriPath repo
|
$ NonEmpty.last $ snd $ fromJust $ URI.uriPath repo
|
||||||
relativeTarball = Text.unpack packagePath
|
relativeTarball = Text.unpack packagePath
|
||||||
</> (dropExtension (Text.unpack downloadFileName) <> "-" <> Text.unpack version)
|
</> (dropExtension (Text.unpack downloadFileName) <> "-" <> Text.unpack version)
|
||||||
(uri', checksum) <- fromJust <$> cloneAndUpload (URI.render repo) relativeTarball tagPrefix
|
(uri', checksum) <- cloneAndUpload (URI.render repo) relativeTarball tagPrefix
|
||||||
pure $ Package.Download
|
pure $ Package.Download
|
||||||
{ md5sum = checksum
|
{ md5sum = checksum
|
||||||
, download = uri'
|
, download = uri'
|
||||||
@ -395,43 +395,52 @@ downloadWithTemplate downloadTemplate packagePath version = do
|
|||||||
$ NonEmpty.last $ snd $ fromJust $ URI.uriPath uri'
|
$ NonEmpty.last $ snd $ fromJust $ URI.uriPath uri'
|
||||||
relativeTarball = packagePath <> "/" <> downloadFileName
|
relativeTarball = packagePath <> "/" <> downloadFileName
|
||||||
tarball = repository' </> Text.unpack relativeTarball
|
tarball = repository' </> Text.unpack relativeTarball
|
||||||
checksum <- fromJust <$> download uri' tarball
|
checksum <- download uri' tarball
|
||||||
pure $ Package.Download uri' checksum
|
pure $ Package.Download uri' $ snd checksum
|
||||||
|
|
||||||
reuploadWithTemplate :: Package.DownloadTemplate -> [CmdSpec] -> Text -> Text -> SlackBuilderT Package.Download
|
reuploadWithTemplate :: Package.DownloadTemplate -> [CmdSpec] -> Text -> Text -> SlackBuilderT Package.Download
|
||||||
reuploadWithTemplate downloadTemplate commands packagePath version = do
|
reuploadWithTemplate downloadTemplate commands packagePath version = do
|
||||||
repository' <- SlackBuilderT $ asks repository
|
repository' <- SlackBuilderT $ asks repository
|
||||||
uri' <- liftIO $ Package.renderDownloadWithVersion downloadTemplate version
|
uri' <- liftIO $ Package.renderDownloadWithVersion downloadTemplate version
|
||||||
let downloadFileName = URI.unRText
|
let downloadFileName = Text.unpack
|
||||||
|
$ URI.unRText
|
||||||
$ NonEmpty.last $ snd $ fromJust $ URI.uriPath uri'
|
$ NonEmpty.last $ snd $ fromJust $ URI.uriPath uri'
|
||||||
relativeTarball = Text.unpack $ packagePath <> "/" <> downloadFileName
|
packagePathRelativeToCurrent = repository' </> Text.unpack packagePath
|
||||||
tarball = repository' </> relativeTarball
|
|
||||||
|
|
||||||
void $ extractRemote uri' packagePath
|
(checksum, relativeTarball') <- case commands of
|
||||||
download' <- handleReupload relativeTarball downloadFileName
|
[] -> do
|
||||||
checksum <- liftIO $ runConduitRes $ sourceFile tarball .| sinkHash
|
let relativeTarball = packagePathRelativeToCurrent
|
||||||
|
</> downloadFileName
|
||||||
|
(downloadedFileName, checksum) <- download uri'
|
||||||
|
$ repository' </> relativeTarball
|
||||||
|
pure (checksum, packagePathRelativeToCurrent </> downloadedFileName)
|
||||||
|
_ -> do
|
||||||
|
changedArchiveRootName <- extractRemote uri' packagePathRelativeToCurrent
|
||||||
|
let relativeTarball = packagePathRelativeToCurrent
|
||||||
|
</> fromMaybe downloadFileName changedArchiveRootName
|
||||||
|
prepareSource relativeTarball
|
||||||
|
checksum <- liftIO $ runConduitRes $ sourceFile relativeTarball .| sinkHash
|
||||||
|
|
||||||
|
pure (checksum, relativeTarball)
|
||||||
|
|
||||||
|
download' <- handleReupload relativeTarball' downloadFileName
|
||||||
pure $ Package.Download download' checksum
|
pure $ Package.Download download' checksum
|
||||||
where
|
where
|
||||||
name' = Text.pack $ takeBaseName $ Text.unpack packagePath
|
name' = Text.pack $ takeBaseName $ Text.unpack packagePath
|
||||||
handleReupload relativeTarball downloadFileName = do
|
prepareSource tarballPath = do
|
||||||
repository' <- SlackBuilderT $ asks repository
|
let packedDirectory = dropExtension $ dropExtension tarballPath
|
||||||
downloadURL' <- SlackBuilderT $ asks downloadURL
|
|
||||||
|
|
||||||
liftIO $ putStrLn $ "Upload the source tarball " <> relativeTarball
|
|
||||||
case commands of
|
|
||||||
[] -> uploadCommand relativeTarball ("/" <> name')
|
|
||||||
_ ->
|
|
||||||
let tarballPath = repository' </> relativeTarball
|
|
||||||
packedDirectory = dropExtension $ dropExtension tarballPath
|
|
||||||
in liftIO (traverse (defaultCreateProcess packedDirectory) commands)
|
in liftIO (traverse (defaultCreateProcess packedDirectory) commands)
|
||||||
>> liftIO
|
>> liftIO
|
||||||
( withCurrentDirectory (takeDirectory tarballPath)
|
( withCurrentDirectory (takeDirectory tarballPath)
|
||||||
$ callProcess "tar" ["Jcvf", takeFileName tarballPath, takeFileName packedDirectory]
|
$ callProcess "tar" ["Jcvf", takeFileName tarballPath, takeFileName packedDirectory]
|
||||||
)
|
)
|
||||||
>> liftIO (removeDirectoryRecursive packedDirectory)
|
>> liftIO (removeDirectoryRecursive packedDirectory)
|
||||||
>> uploadCommand relativeTarball ("/" <> name')
|
handleReupload relativeTarball downloadFileName = do
|
||||||
liftIO $ mkURI $ downloadURL' <> "/" <> name' <> "/" <> downloadFileName
|
downloadURL' <- SlackBuilderT $ asks downloadURL
|
||||||
|
|
||||||
|
liftIO $ putStrLn $ "Upload the source tarball " <> relativeTarball
|
||||||
|
uploadCommand relativeTarball ("/" <> name')
|
||||||
|
liftIO $ mkURI $ downloadURL' <> "/" <> name' <> "/" <> Text.pack downloadFileName
|
||||||
defaultCreateProcess cwd' cmdSpec
|
defaultCreateProcess cwd' cmdSpec
|
||||||
= flip withCreateProcess (const . const . const waitForProcess)
|
= flip withCreateProcess (const . const . const waitForProcess)
|
||||||
$ CreateProcess
|
$ CreateProcess
|
||||||
|
Loading…
Reference in New Issue
Block a user