Get rid of tar
This commit is contained in:
@@ -21,11 +21,7 @@ module GHCup.Errors where
|
||||
|
||||
import GHCup.Types
|
||||
|
||||
#if !defined(TAR)
|
||||
import Codec.Archive
|
||||
#else
|
||||
import qualified Codec.Archive.Tar as Tar
|
||||
#endif
|
||||
import Control.Exception.Safe
|
||||
import Data.ByteString ( ByteString )
|
||||
import Data.CaseInsensitive ( CI )
|
||||
@@ -390,7 +386,6 @@ instance Pretty URIParseError where
|
||||
pPrint (OtherError err) =
|
||||
text [i|Failed to parse URI: #{err}|]
|
||||
|
||||
#if !defined(TAR)
|
||||
instance Pretty ArchiveResult where
|
||||
pPrint ArchiveFatal = text "Archive result: fatal"
|
||||
pPrint ArchiveFailed = text "Archive result: failed"
|
||||
@@ -398,14 +393,3 @@ instance Pretty ArchiveResult where
|
||||
pPrint ArchiveRetry = text "Archive result: retry"
|
||||
pPrint ArchiveOk = text "Archive result: Ok"
|
||||
pPrint ArchiveEOF = text "Archive result: EOF"
|
||||
#else
|
||||
instance Pretty Tar.FormatError where
|
||||
pPrint Tar.TruncatedArchive = text "Truncated archive"
|
||||
pPrint Tar.ShortTrailer = text "Short trailer"
|
||||
pPrint Tar.BadTrailer = text "Bad trailer"
|
||||
pPrint Tar.TrailingJunk = text "Trailing junk"
|
||||
pPrint Tar.ChecksumIncorrect = text "Checksum incorrect"
|
||||
pPrint Tar.NotTarFormat = text "Not a tar format"
|
||||
pPrint Tar.UnrecognisedTarFormat = text "Unrecognised tar format"
|
||||
pPrint Tar.HeaderBadNumericEncoding = text "Header has bad numeric encoding"
|
||||
#endif
|
||||
|
||||
@@ -39,9 +39,7 @@ import GHCup.Utils.MegaParsec
|
||||
import GHCup.Utils.Prelude
|
||||
import GHCup.Utils.String.QQ
|
||||
|
||||
#if !defined(TAR)
|
||||
import Codec.Archive hiding ( Directory )
|
||||
#endif
|
||||
import Codec.Archive.Zip
|
||||
import Control.Applicative
|
||||
import Control.Exception.Safe
|
||||
@@ -83,9 +81,6 @@ import Text.PrettyPrint.HughesPJClass hiding ( (<>) )
|
||||
import Text.Regex.Posix
|
||||
import URI.ByteString
|
||||
|
||||
#if defined(TAR)
|
||||
import qualified Codec.Archive.Tar as Tar
|
||||
#endif
|
||||
import qualified Codec.Compression.BZip as BZip
|
||||
import qualified Codec.Compression.GZip as GZip
|
||||
import qualified Codec.Compression.Lzma as Lzma
|
||||
@@ -603,27 +598,17 @@ unpackToDir :: (MonadLogger m, MonadIO m, MonadThrow m)
|
||||
=> FilePath -- ^ destination dir
|
||||
-> FilePath -- ^ archive path
|
||||
-> Excepts '[UnknownArchive
|
||||
#if !defined(TAR)
|
||||
, ArchiveResult
|
||||
#endif
|
||||
] m ()
|
||||
unpackToDir dfp av = do
|
||||
let fn = takeFileName av
|
||||
lift $ $(logInfo) [i|Unpacking: #{fn} to #{dfp}|]
|
||||
|
||||
#if defined(TAR)
|
||||
let untar :: MonadIO m => BL.ByteString -> Excepts '[] m ()
|
||||
untar = liftIO . Tar.unpack dfp . Tar.read
|
||||
|
||||
rf :: MonadIO m => FilePath -> Excepts '[] m BL.ByteString
|
||||
rf = liftIO . BL.readFile
|
||||
#else
|
||||
let untar :: MonadIO m => BL.ByteString -> Excepts '[ArchiveResult] m ()
|
||||
untar = lEM . liftIO . runArchiveM . unpackToDirLazy dfp
|
||||
|
||||
rf :: MonadIO m => FilePath -> Excepts '[ArchiveResult] m BL.ByteString
|
||||
rf = liftIO . BL.readFile
|
||||
#endif
|
||||
|
||||
-- extract, depending on file extension
|
||||
if
|
||||
@@ -644,34 +629,16 @@ unpackToDir dfp av = do
|
||||
getArchiveFiles :: (MonadLogger m, MonadIO m, MonadThrow m)
|
||||
=> FilePath -- ^ archive path
|
||||
-> Excepts '[UnknownArchive
|
||||
#if defined(TAR)
|
||||
, Tar.FormatError
|
||||
#else
|
||||
, ArchiveResult
|
||||
#endif
|
||||
] m [FilePath]
|
||||
getArchiveFiles av = do
|
||||
let fn = takeFileName av
|
||||
|
||||
#if defined(TAR)
|
||||
let entries :: Monad m => BL.ByteString -> Excepts '[Tar.FormatError] m [FilePath]
|
||||
entries =
|
||||
lE @Tar.FormatError
|
||||
. Tar.foldEntries
|
||||
(\e x -> fmap (Tar.entryPath e :) x)
|
||||
(Right [])
|
||||
(\e -> Left e)
|
||||
. Tar.read
|
||||
|
||||
rf :: MonadIO m => FilePath -> Excepts '[Tar.FormatError] m BL.ByteString
|
||||
rf = liftIO . BL.readFile
|
||||
#else
|
||||
let entries :: Monad m => BL.ByteString -> Excepts '[ArchiveResult] m [FilePath]
|
||||
entries = (fmap . fmap) filepath . lE . readArchiveBSL
|
||||
|
||||
rf :: MonadIO m => FilePath -> Excepts '[ArchiveResult] m BL.ByteString
|
||||
rf = liftIO . BL.readFile
|
||||
#endif
|
||||
|
||||
-- extract, depending on file extension
|
||||
if
|
||||
|
||||
Reference in New Issue
Block a user