{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
module Codec.Archive.Zip.Internal
( PendingAction (..),
targetEntry,
scanArchive,
sourceEntry,
crc32Sink,
commit,
)
where
import Codec.Archive.Zip.CP437 (decodeCP437)
import Codec.Archive.Zip.Type
import Conduit (PrimMonad)
import Control.Applicative (many, (<|>))
import Control.Exception (bracketOnError, catchJust)
import Control.Monad
import Control.Monad.Catch (MonadThrow (..))
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.Resource (MonadResource, ResourceT)
import Data.Bits
import Data.Bool (bool)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.Char (ord)
import Data.Conduit (ConduitT, ZipSink (..), (.|))
import qualified Data.Conduit as C
import qualified Data.Conduit.Binary as CB
import qualified Data.Conduit.List as CL
import qualified Data.Conduit.Zlib as Z
import Data.Digest.CRC32 (crc32Update)
import Data.Fixed (Fixed (..))
import Data.Foldable (foldl')
import Data.Map.Strict (Map, (!))
import qualified Data.Map.Strict as M
import Data.Maybe (catMaybes, fromJust, isNothing)
import Data.Sequence (Seq, (><), (|>))
import qualified Data.Sequence as S
import Data.Serialize
import qualified Data.Set as E
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Time
import Data.Version
import Data.Void
import Data.Word (Word16, Word32)
import Numeric.Natural (Natural)
import System.Directory
import System.FilePath
import System.IO
import System.IO.Error (isDoesNotExistError)
#ifndef mingw32_HOST_OS
import qualified Codec.Archive.Zip.Unix as Unix
#endif
#ifdef ENABLE_BZIP2
import qualified Data.Conduit.BZlib as BZ
#endif
#ifdef ENABLE_ZSTD
import qualified Data.Conduit.Zstd as Zstandard
#endif
data PendingAction
=
SinkEntry
CompressionMethod
(ConduitT () ByteString (ResourceT IO) ())
EntrySelector
|
CopyEntry FilePath EntrySelector EntrySelector
|
RenameEntry EntrySelector EntrySelector
|
DeleteEntry EntrySelector
|
Recompress CompressionMethod EntrySelector
|
Text EntrySelector
|
EntrySelector
|
SetModTime UTCTime EntrySelector
|
Word16 ByteString EntrySelector
|
Word16 EntrySelector
|
Text
|
|
SetExternalFileAttributes Word32 EntrySelector
data ProducingActions = ProducingActions
{ ProducingActions -> Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry :: Map FilePath (Map EntrySelector EntrySelector),
ProducingActions
-> Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry :: Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
}
data EditingActions = EditingActions
{ EditingActions -> Map EntrySelector CompressionMethod
eaCompression :: Map EntrySelector CompressionMethod,
:: Map EntrySelector Text,
:: Map EntrySelector (),
EditingActions -> Map EntrySelector UTCTime
eaModTime :: Map EntrySelector UTCTime,
:: Map EntrySelector (Map Word16 ByteString),
EditingActions -> Map EntrySelector (Map Word16 ())
eaDeleteField :: Map EntrySelector (Map Word16 ()),
EditingActions -> Map EntrySelector Word32
eaExtFileAttr :: Map EntrySelector Word32
}
data EntryOrigin
= GenericOrigin
| Borrowed EntryDescription
data
=
|
deriving (HeaderType -> HeaderType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HeaderType -> HeaderType -> Bool
$c/= :: HeaderType -> HeaderType -> Bool
== :: HeaderType -> HeaderType -> Bool
$c== :: HeaderType -> HeaderType -> Bool
Eq)
data DataDescriptor = DataDescriptor
{ DataDescriptor -> Word32
ddCRC32 :: Word32,
DataDescriptor -> Natural
ddCompressedSize :: Natural,
DataDescriptor -> Natural
ddUncompressedSize :: Natural
}
data =
{ Zip64ExtraField -> Natural
z64efUncompressedSize :: Natural,
Zip64ExtraField -> Natural
z64efCompressedSize :: Natural,
Zip64ExtraField -> Natural
z64efOffset :: Natural
}
data MsDosTime = MsDosTime
{ MsDosTime -> Word16
msDosDate :: Word16,
MsDosTime -> Word16
msDosTime :: Word16
}
zipVersion :: Version
zipVersion :: Version
zipVersion = [Int] -> [FilePath] -> Version
Version [Int
6, Int
3] []
scanArchive ::
FilePath ->
IO (ArchiveDescription, Map EntrySelector EntryDescription)
scanArchive :: FilePath
-> IO (ArchiveDescription, Map EntrySelector EntryDescription)
scanArchive FilePath
path = forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile FilePath
path IOMode
ReadMode forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
Maybe Integer
mecdOffset <- FilePath -> Handle -> IO (Maybe Integer)
locateECD FilePath
path Handle
h
case Maybe Integer
mecdOffset of
Just Integer
ecdOffset -> do
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek Integer
ecdOffset
Integer
ecdSize <- forall a. Num a => a -> a -> a
subtract Integer
ecdOffset forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO Integer
hFileSize Handle
h
ByteString
ecdRaw <- Handle -> Int -> IO ByteString
B.hGet Handle
h (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
ecdSize)
case forall a. Get a -> ByteString -> Either FilePath a
runGet Get ArchiveDescription
getECD ByteString
ecdRaw of
Left FilePath
msg -> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FilePath -> FilePath -> ZipException
ParsingFailed FilePath
path FilePath
msg)
Right ArchiveDescription
ecd -> do
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral (ArchiveDescription -> Natural
adCDOffset ArchiveDescription
ecd)
ByteString
cdRaw <- Handle -> Int -> IO ByteString
B.hGet Handle
h forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral (ArchiveDescription -> Natural
adCDSize ArchiveDescription
ecd)
case forall a. Get a -> ByteString -> Either FilePath a
runGet Get (Map EntrySelector EntryDescription)
getCD ByteString
cdRaw of
Left FilePath
msg -> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FilePath -> FilePath -> ZipException
ParsingFailed FilePath
path FilePath
msg)
Right Map EntrySelector EntryDescription
cd -> forall (m :: * -> *) a. Monad m => a -> m a
return (ArchiveDescription
ecd, Map EntrySelector EntryDescription
cd)
Maybe Integer
Nothing ->
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FilePath -> FilePath -> ZipException
ParsingFailed FilePath
path FilePath
"Cannot locate end of central directory")
sourceEntry ::
(PrimMonad m, MonadThrow m, MonadResource m) =>
FilePath ->
EntryDescription ->
Bool ->
ConduitT () ByteString m ()
sourceEntry :: forall (m :: * -> *).
(PrimMonad m, MonadThrow m, MonadResource m) =>
FilePath -> EntryDescription -> Bool -> ConduitT () ByteString m ()
sourceEntry FilePath
path EntryDescription {Natural
Maybe Text
Word32
Version
Map Word16 ByteString
UTCTime
CompressionMethod
edExternalFileAttrs :: EntryDescription -> Word32
edExtraField :: EntryDescription -> Map Word16 ByteString
edComment :: EntryDescription -> Maybe Text
edOffset :: EntryDescription -> Natural
edUncompressedSize :: EntryDescription -> Natural
edCompressedSize :: EntryDescription -> Natural
edCRC32 :: EntryDescription -> Word32
edModTime :: EntryDescription -> UTCTime
edCompression :: EntryDescription -> CompressionMethod
edVersionNeeded :: EntryDescription -> Version
edVersionMadeBy :: EntryDescription -> Version
edExternalFileAttrs :: Word32
edExtraField :: Map Word16 ByteString
edComment :: Maybe Text
edOffset :: Natural
edUncompressedSize :: Natural
edCompressedSize :: Natural
edCRC32 :: Word32
edModTime :: UTCTime
edCompression :: CompressionMethod
edVersionNeeded :: Version
edVersionMadeBy :: Version
..} Bool
d =
forall {i}. ConduitT i ByteString m ()
source forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| forall (m :: * -> *).
Monad m =>
Int -> ConduitT ByteString ByteString m ()
CB.isolate (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
edCompressedSize) forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ConduitT ByteString ByteString m ()
decompress
where
source :: ConduitT i ByteString m ()
source = forall (m :: * -> *) i.
MonadResource m =>
IO Handle -> ConduitT i ByteString m ()
CB.sourceIOHandle forall a b. (a -> b) -> a -> b
$ do
Handle
h <- FilePath -> IOMode -> IO Handle
openFile FilePath
path IOMode
ReadMode
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
edOffset)
ByteString
localHeader <- Handle -> Int -> IO ByteString
B.hGet Handle
h Int
30
case forall a. Get a -> ByteString -> Either FilePath a
runGet Get Integer
getLocalHeaderGap ByteString
localHeader of
Left FilePath
msg -> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FilePath -> FilePath -> ZipException
ParsingFailed FilePath
path FilePath
msg)
Right Integer
gap -> do
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
RelativeSeek Integer
gap
forall (m :: * -> *) a. Monad m => a -> m a
return Handle
h
decompress :: ConduitT ByteString ByteString m ()
decompress =
if Bool
d
then forall (m :: * -> *).
(PrimMonad m, MonadThrow m, MonadResource m) =>
CompressionMethod -> ConduitT ByteString ByteString m ()
decompressingPipe CompressionMethod
edCompression
else forall (m :: * -> *) i o r.
Monad m =>
(i -> ConduitT i o m r) -> ConduitT i o m ()
C.awaitForever forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
C.yield
commit ::
FilePath ->
ArchiveDescription ->
Map EntrySelector EntryDescription ->
Seq PendingAction ->
IO ()
commit :: FilePath
-> ArchiveDescription
-> Map EntrySelector EntryDescription
-> Seq PendingAction
-> IO ()
commit FilePath
path ArchiveDescription {Natural
Maybe Text
adComment :: ArchiveDescription -> Maybe Text
adCDSize :: Natural
adCDOffset :: Natural
adComment :: Maybe Text
adCDSize :: ArchiveDescription -> Natural
adCDOffset :: ArchiveDescription -> Natural
..} Map EntrySelector EntryDescription
entries Seq PendingAction
xs =
FilePath -> (Handle -> IO ()) -> IO ()
withNewFile FilePath
path forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
let (ProducingActions Map FilePath (Map EntrySelector EntrySelector)
coping Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
sinking, EditingActions
editing) =
Seq PendingAction -> (ProducingActions, EditingActions)
optimize (FilePath -> Map EntrySelector EntryDescription -> Seq PendingAction
toRecreatingActions FilePath
path Map EntrySelector EntryDescription
entries forall a. Seq a -> Seq a -> Seq a
>< Seq PendingAction
xs)
comment :: Maybe Text
comment = Maybe Text -> Seq PendingAction -> Maybe Text
predictComment Maybe Text
adComment Seq PendingAction
xs
Map EntrySelector EntryDescription
copiedCD <-
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
M.unions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM
(forall k a. Map k a -> [k]
M.keys Map FilePath (Map EntrySelector EntrySelector)
coping)
( \FilePath
srcPath ->
Handle
-> FilePath
-> Map EntrySelector EntrySelector
-> EditingActions
-> IO (Map EntrySelector EntryDescription)
copyEntries Handle
h FilePath
srcPath (Map FilePath (Map EntrySelector EntrySelector)
coping forall k a. Ord k => Map k a -> k -> a
! FilePath
srcPath) EditingActions
editing
)
let sinkingKeys :: [EntrySelector]
sinkingKeys = forall k a. Map k a -> [k]
M.keys forall a b. (a -> b) -> a -> b
$ Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
sinking forall k a b. Ord k => Map k a -> Map k b -> Map k a
`M.difference` Map EntrySelector EntryDescription
copiedCD
Map EntrySelector EntryDescription
sunkCD <-
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM
[EntrySelector]
sinkingKeys
( \EntrySelector
selector ->
Handle
-> EntrySelector
-> EntryOrigin
-> ConduitT () ByteString (ResourceT IO) ()
-> EditingActions
-> IO (EntrySelector, EntryDescription)
sinkEntry Handle
h EntrySelector
selector EntryOrigin
GenericOrigin (Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
sinking forall k a. Ord k => Map k a -> k -> a
! EntrySelector
selector) EditingActions
editing
)
Handle -> Maybe Text -> Map EntrySelector EntryDescription -> IO ()
writeCD Handle
h Maybe Text
comment (Map EntrySelector EntryDescription
copiedCD forall k a. Ord k => Map k a -> Map k a -> Map k a
`M.union` Map EntrySelector EntryDescription
sunkCD)
withNewFile ::
FilePath ->
(Handle -> IO ()) ->
IO ()
withNewFile :: FilePath -> (Handle -> IO ()) -> IO ()
withNewFile FilePath
fpath Handle -> IO ()
action =
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError IO (FilePath, Handle)
allocate (FilePath, Handle) -> IO ()
release forall a b. (a -> b) -> a -> b
$ \(FilePath
path, Handle
h) -> do
Handle -> IO ()
action Handle
h
Handle -> IO ()
hClose Handle
h
FilePath -> FilePath -> IO ()
renameFile FilePath
path FilePath
fpath
where
allocate :: IO (FilePath, Handle)
allocate = FilePath -> FilePath -> IO (FilePath, Handle)
openBinaryTempFile (FilePath -> FilePath
takeDirectory FilePath
fpath) FilePath
".zip"
release :: (FilePath, Handle) -> IO ()
release (FilePath
path, Handle
h) = do
Handle -> IO ()
hClose Handle
h
forall e b a.
Exception e =>
(e -> Maybe b) -> IO a -> (b -> IO a) -> IO a
catchJust (forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall b c a. (b -> c) -> (a -> b) -> a -> c
. IOError -> Bool
isDoesNotExistError) (FilePath -> IO ()
removeFile FilePath
path) (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
predictComment :: Maybe Text -> Seq PendingAction -> Maybe Text
Maybe Text
original Seq PendingAction
xs =
case forall a. Seq a -> Int -> a
S.index Seq PendingAction
xs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. (a -> Bool) -> Seq a -> Maybe Int
S.findIndexR (forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. PendingAction -> Maybe EntrySelector
targetEntry) Seq PendingAction
xs of
Maybe PendingAction
Nothing -> Maybe Text
original
Just PendingAction
DeleteArchiveComment -> forall a. Maybe a
Nothing
Just (SetArchiveComment Text
txt) -> forall a. a -> Maybe a
Just Text
txt
Just PendingAction
_ -> forall a. Maybe a
Nothing
toRecreatingActions ::
FilePath ->
Map EntrySelector EntryDescription ->
Seq PendingAction
toRecreatingActions :: FilePath -> Map EntrySelector EntryDescription -> Seq PendingAction
toRecreatingActions FilePath
path Map EntrySelector EntryDescription
entries = forall a b. (a -> b -> a) -> a -> Set b -> a
E.foldl' Seq PendingAction -> EntrySelector -> Seq PendingAction
f forall a. Seq a
S.empty (forall k a. Map k a -> Set k
M.keysSet Map EntrySelector EntryDescription
entries)
where
f :: Seq PendingAction -> EntrySelector -> Seq PendingAction
f Seq PendingAction
s EntrySelector
e = Seq PendingAction
s forall a. Seq a -> a -> Seq a
|> FilePath -> EntrySelector -> EntrySelector -> PendingAction
CopyEntry FilePath
path EntrySelector
e EntrySelector
e
optimize ::
Seq PendingAction ->
(ProducingActions, EditingActions)
optimize :: Seq PendingAction -> (ProducingActions, EditingActions)
optimize =
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl'
(ProducingActions, EditingActions)
-> PendingAction -> (ProducingActions, EditingActions)
f
( Map FilePath (Map EntrySelector EntrySelector)
-> Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
-> ProducingActions
ProducingActions forall k a. Map k a
M.empty forall k a. Map k a
M.empty,
Map EntrySelector CompressionMethod
-> Map EntrySelector Text
-> Map EntrySelector ()
-> Map EntrySelector UTCTime
-> Map EntrySelector (Map Word16 ByteString)
-> Map EntrySelector (Map Word16 ())
-> Map EntrySelector Word32
-> EditingActions
EditingActions forall k a. Map k a
M.empty forall k a. Map k a
M.empty forall k a. Map k a
M.empty forall k a. Map k a
M.empty forall k a. Map k a
M.empty forall k a. Map k a
M.empty forall k a. Map k a
M.empty
)
where
f :: (ProducingActions, EditingActions)
-> PendingAction -> (ProducingActions, EditingActions)
f (ProducingActions
pa, EditingActions
ea) PendingAction
a = case PendingAction
a of
SinkEntry CompressionMethod
m ConduitT () ByteString (ResourceT IO) ()
src EntrySelector
s ->
( ProducingActions
pa
{ paSinkEntry :: Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert EntrySelector
s ConduitT () ByteString (ResourceT IO) ()
src (ProducingActions
-> Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry ProducingActions
pa),
paCopyEntry :: Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry = forall a b k. (a -> b) -> Map k a -> Map k b
M.map (forall a k. (a -> Bool) -> Map k a -> Map k a
M.filter (forall a. Eq a => a -> a -> Bool
/= EntrySelector
s)) (ProducingActions -> Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry ProducingActions
pa)
},
(EntrySelector -> EditingActions -> EditingActions
clearEditingFor EntrySelector
s EditingActions
ea)
{ eaCompression :: Map EntrySelector CompressionMethod
eaCompression = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert EntrySelector
s CompressionMethod
m (EditingActions -> Map EntrySelector CompressionMethod
eaCompression EditingActions
ea)
}
)
CopyEntry FilePath
path EntrySelector
os EntrySelector
ns ->
( ProducingActions
pa
{ paSinkEntry :: Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
ns (ProducingActions
-> Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry ProducingActions
pa),
paCopyEntry :: Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry = forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
M.alter (forall {k} {a}.
Ord k =>
k -> a -> Maybe (Map k a) -> Maybe (Map k a)
ef EntrySelector
os EntrySelector
ns) FilePath
path (ProducingActions -> Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry ProducingActions
pa)
},
EntrySelector -> EditingActions -> EditingActions
clearEditingFor EntrySelector
ns EditingActions
ea
)
RenameEntry EntrySelector
os EntrySelector
ns ->
( ProducingActions
pa
{ paCopyEntry :: Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry = forall a b k. (a -> b) -> Map k a -> Map k b
M.map (forall a b k. (a -> b) -> Map k a -> Map k b
M.map forall a b. (a -> b) -> a -> b
$ forall {p}. Eq p => p -> p -> p -> p
re EntrySelector
os EntrySelector
ns) (ProducingActions -> Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry ProducingActions
pa),
paSinkEntry :: Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry = forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey EntrySelector
os EntrySelector
ns (ProducingActions
-> Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry ProducingActions
pa)
},
EditingActions
ea
{ eaCompression :: Map EntrySelector CompressionMethod
eaCompression = forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey EntrySelector
os EntrySelector
ns (EditingActions -> Map EntrySelector CompressionMethod
eaCompression EditingActions
ea),
eaEntryComment :: Map EntrySelector Text
eaEntryComment = forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey EntrySelector
os EntrySelector
ns (EditingActions -> Map EntrySelector Text
eaEntryComment EditingActions
ea),
eaDeleteComment :: Map EntrySelector ()
eaDeleteComment = forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey EntrySelector
os EntrySelector
ns (EditingActions -> Map EntrySelector ()
eaDeleteComment EditingActions
ea),
eaModTime :: Map EntrySelector UTCTime
eaModTime = forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey EntrySelector
os EntrySelector
ns (EditingActions -> Map EntrySelector UTCTime
eaModTime EditingActions
ea),
eaExtraField :: Map EntrySelector (Map Word16 ByteString)
eaExtraField = forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey EntrySelector
os EntrySelector
ns (EditingActions -> Map EntrySelector (Map Word16 ByteString)
eaExtraField EditingActions
ea),
eaDeleteField :: Map EntrySelector (Map Word16 ())
eaDeleteField = forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey EntrySelector
os EntrySelector
ns (EditingActions -> Map EntrySelector (Map Word16 ())
eaDeleteField EditingActions
ea)
}
)
DeleteEntry EntrySelector
s ->
( ProducingActions
pa
{ paSinkEntry :: Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (ProducingActions
-> Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
paSinkEntry ProducingActions
pa),
paCopyEntry :: Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry = forall a b k. (a -> b) -> Map k a -> Map k b
M.map (forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s) (ProducingActions -> Map FilePath (Map EntrySelector EntrySelector)
paCopyEntry ProducingActions
pa)
},
EntrySelector -> EditingActions -> EditingActions
clearEditingFor EntrySelector
s EditingActions
ea
)
Recompress CompressionMethod
m EntrySelector
s ->
(ProducingActions
pa, EditingActions
ea {eaCompression :: Map EntrySelector CompressionMethod
eaCompression = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert EntrySelector
s CompressionMethod
m (EditingActions -> Map EntrySelector CompressionMethod
eaCompression EditingActions
ea)})
SetEntryComment Text
txt EntrySelector
s ->
( ProducingActions
pa,
EditingActions
ea
{ eaEntryComment :: Map EntrySelector Text
eaEntryComment = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert EntrySelector
s Text
txt (EditingActions -> Map EntrySelector Text
eaEntryComment EditingActions
ea),
eaDeleteComment :: Map EntrySelector ()
eaDeleteComment = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector ()
eaDeleteComment EditingActions
ea)
}
)
DeleteEntryComment EntrySelector
s ->
( ProducingActions
pa,
EditingActions
ea
{ eaEntryComment :: Map EntrySelector Text
eaEntryComment = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector Text
eaEntryComment EditingActions
ea),
eaDeleteComment :: Map EntrySelector ()
eaDeleteComment = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert EntrySelector
s () (EditingActions -> Map EntrySelector ()
eaDeleteComment EditingActions
ea)
}
)
SetModTime UTCTime
time EntrySelector
s ->
(ProducingActions
pa, EditingActions
ea {eaModTime :: Map EntrySelector UTCTime
eaModTime = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert EntrySelector
s UTCTime
time (EditingActions -> Map EntrySelector UTCTime
eaModTime EditingActions
ea)})
AddExtraField Word16
n ByteString
b EntrySelector
s ->
( ProducingActions
pa,
EditingActions
ea
{ eaExtraField :: Map EntrySelector (Map Word16 ByteString)
eaExtraField = forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
M.alter (forall {k} {a}.
Ord k =>
k -> a -> Maybe (Map k a) -> Maybe (Map k a)
ef Word16
n ByteString
b) EntrySelector
s (EditingActions -> Map EntrySelector (Map Word16 ByteString)
eaExtraField EditingActions
ea),
eaDeleteField :: Map EntrySelector (Map Word16 ())
eaDeleteField = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector (Map Word16 ())
eaDeleteField EditingActions
ea)
}
)
DeleteExtraField Word16
n EntrySelector
s ->
( ProducingActions
pa,
EditingActions
ea
{ eaExtraField :: Map EntrySelector (Map Word16 ByteString)
eaExtraField = forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
M.alter (forall {k} {a}. Ord k => k -> Maybe (Map k a) -> Maybe (Map k a)
er Word16
n) EntrySelector
s (EditingActions -> Map EntrySelector (Map Word16 ByteString)
eaExtraField EditingActions
ea),
eaDeleteField :: Map EntrySelector (Map Word16 ())
eaDeleteField = forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
M.alter (forall {k} {a}.
Ord k =>
k -> a -> Maybe (Map k a) -> Maybe (Map k a)
ef Word16
n ()) EntrySelector
s (EditingActions -> Map EntrySelector (Map Word16 ())
eaDeleteField EditingActions
ea)
}
)
SetExternalFileAttributes Word32
b EntrySelector
s ->
( ProducingActions
pa,
EditingActions
ea {eaExtFileAttr :: Map EntrySelector Word32
eaExtFileAttr = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert EntrySelector
s Word32
b (EditingActions -> Map EntrySelector Word32
eaExtFileAttr EditingActions
ea)}
)
PendingAction
_ -> (ProducingActions
pa, EditingActions
ea)
clearEditingFor :: EntrySelector -> EditingActions -> EditingActions
clearEditingFor EntrySelector
s EditingActions
ea =
EditingActions
ea
{ eaCompression :: Map EntrySelector CompressionMethod
eaCompression = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector CompressionMethod
eaCompression EditingActions
ea),
eaEntryComment :: Map EntrySelector Text
eaEntryComment = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector Text
eaEntryComment EditingActions
ea),
eaDeleteComment :: Map EntrySelector ()
eaDeleteComment = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector ()
eaDeleteComment EditingActions
ea),
eaModTime :: Map EntrySelector UTCTime
eaModTime = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector UTCTime
eaModTime EditingActions
ea),
eaExtraField :: Map EntrySelector (Map Word16 ByteString)
eaExtraField = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector (Map Word16 ByteString)
eaExtraField EditingActions
ea),
eaDeleteField :: Map EntrySelector (Map Word16 ())
eaDeleteField = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector (Map Word16 ())
eaDeleteField EditingActions
ea),
eaExtFileAttr :: Map EntrySelector Word32
eaExtFileAttr = forall k a. Ord k => k -> Map k a -> Map k a
M.delete EntrySelector
s (EditingActions -> Map EntrySelector Word32
eaExtFileAttr EditingActions
ea)
}
re :: p -> p -> p -> p
re p
o p
n p
x = if p
x forall a. Eq a => a -> a -> Bool
== p
o then p
n else p
x
ef :: k -> a -> Maybe (Map k a) -> Maybe (Map k a)
ef k
k a
v (Just Map k a
m) = forall a. a -> Maybe a
Just (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert k
k a
v Map k a
m)
ef k
k a
v Maybe (Map k a)
Nothing = forall a. a -> Maybe a
Just (forall k a. k -> a -> Map k a
M.singleton k
k a
v)
er :: k -> Maybe (Map k a) -> Maybe (Map k a)
er k
k (Just Map k a
m) =
let n :: Map k a
n = forall k a. Ord k => k -> Map k a -> Map k a
M.delete k
k Map k a
m
in if forall k a. Map k a -> Bool
M.null Map k a
n then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just Map k a
n
er k
_ Maybe (Map k a)
Nothing = forall a. Maybe a
Nothing
copyEntries ::
Handle ->
FilePath ->
Map EntrySelector EntrySelector ->
EditingActions ->
IO (Map EntrySelector EntryDescription)
copyEntries :: Handle
-> FilePath
-> Map EntrySelector EntrySelector
-> EditingActions
-> IO (Map EntrySelector EntryDescription)
copyEntries Handle
h FilePath
path Map EntrySelector EntrySelector
m EditingActions
e = do
Map EntrySelector EntryDescription
entries <- forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath
-> IO (ArchiveDescription, Map EntrySelector EntryDescription)
scanArchive FilePath
path
[(EntrySelector, EntryDescription)]
done <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (forall k a. Map k a -> [k]
M.keys Map EntrySelector EntrySelector
m) forall a b. (a -> b) -> a -> b
$ \EntrySelector
s ->
case EntrySelector
s forall k a. Ord k => k -> Map k a -> Maybe a
`M.lookup` Map EntrySelector EntryDescription
entries of
Maybe EntryDescription
Nothing -> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FilePath -> EntrySelector -> ZipException
EntryDoesNotExist FilePath
path EntrySelector
s)
Just EntryDescription
desc ->
Handle
-> EntrySelector
-> EntryOrigin
-> ConduitT () ByteString (ResourceT IO) ()
-> EditingActions
-> IO (EntrySelector, EntryDescription)
sinkEntry
Handle
h
(Map EntrySelector EntrySelector
m forall k a. Ord k => Map k a -> k -> a
! EntrySelector
s)
(EntryDescription -> EntryOrigin
Borrowed EntryDescription
desc)
(forall (m :: * -> *).
(PrimMonad m, MonadThrow m, MonadResource m) =>
FilePath -> EntryDescription -> Bool -> ConduitT () ByteString m ()
sourceEntry FilePath
path EntryDescription
desc Bool
False)
EditingActions
e
forall (m :: * -> *) a. Monad m => a -> m a
return (forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(EntrySelector, EntryDescription)]
done)
sinkEntry ::
Handle ->
EntrySelector ->
EntryOrigin ->
ConduitT () ByteString (ResourceT IO) () ->
EditingActions ->
IO (EntrySelector, EntryDescription)
sinkEntry :: Handle
-> EntrySelector
-> EntryOrigin
-> ConduitT () ByteString (ResourceT IO) ()
-> EditingActions
-> IO (EntrySelector, EntryDescription)
sinkEntry Handle
h EntrySelector
s EntryOrigin
o ConduitT () ByteString (ResourceT IO) ()
src EditingActions {Map EntrySelector Word32
Map EntrySelector ()
Map EntrySelector Text
Map EntrySelector (Map Word16 ())
Map EntrySelector (Map Word16 ByteString)
Map EntrySelector UTCTime
Map EntrySelector CompressionMethod
eaExtFileAttr :: Map EntrySelector Word32
eaDeleteField :: Map EntrySelector (Map Word16 ())
eaExtraField :: Map EntrySelector (Map Word16 ByteString)
eaModTime :: Map EntrySelector UTCTime
eaDeleteComment :: Map EntrySelector ()
eaEntryComment :: Map EntrySelector Text
eaCompression :: Map EntrySelector CompressionMethod
eaExtFileAttr :: EditingActions -> Map EntrySelector Word32
eaDeleteField :: EditingActions -> Map EntrySelector (Map Word16 ())
eaExtraField :: EditingActions -> Map EntrySelector (Map Word16 ByteString)
eaModTime :: EditingActions -> Map EntrySelector UTCTime
eaDeleteComment :: EditingActions -> Map EntrySelector ()
eaEntryComment :: EditingActions -> Map EntrySelector Text
eaCompression :: EditingActions -> Map EntrySelector CompressionMethod
..} = do
UTCTime
currentTime <- IO UTCTime
getCurrentTime
Integer
offset <- Handle -> IO Integer
hTell Handle
h
let compressed :: CompressionMethod
compressed = case EntryOrigin
o of
EntryOrigin
GenericOrigin -> CompressionMethod
Store
Borrowed EntryDescription
ed -> EntryDescription -> CompressionMethod
edCompression EntryDescription
ed
compression :: CompressionMethod
compression = forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault CompressionMethod
compressed EntrySelector
s Map EntrySelector CompressionMethod
eaCompression
recompression :: Bool
recompression = CompressionMethod
compression forall a. Eq a => a -> a -> Bool
/= CompressionMethod
compressed
modTime :: UTCTime
modTime = case EntryOrigin
o of
EntryOrigin
GenericOrigin -> UTCTime
currentTime
Borrowed EntryDescription
ed -> EntryDescription -> UTCTime
edModTime EntryDescription
ed
extFileAttr :: Word32
extFileAttr = case EntryOrigin
o of
EntryOrigin
GenericOrigin -> forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault Word32
defaultFileMode EntrySelector
s Map EntrySelector Word32
eaExtFileAttr
Borrowed EntryDescription
_ -> forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault Word32
defaultFileMode EntrySelector
s Map EntrySelector Word32
eaExtFileAttr
oldExtraFields :: Map Word16 ByteString
oldExtraFields = case EntryOrigin
o of
EntryOrigin
GenericOrigin -> forall k a. Map k a
M.empty
Borrowed EntryDescription
ed -> EntryDescription -> Map Word16 ByteString
edExtraField EntryDescription
ed
extraField :: Map Word16 ByteString
extraField =
(forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault forall k a. Map k a
M.empty EntrySelector
s Map EntrySelector (Map Word16 ByteString)
eaExtraField forall k a. Ord k => Map k a -> Map k a -> Map k a
`M.union` Map Word16 ByteString
oldExtraFields)
forall k a b. Ord k => Map k a -> Map k b -> Map k a
`M.difference` forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault forall k a. Map k a
M.empty EntrySelector
s Map EntrySelector (Map Word16 ())
eaDeleteField
oldComment :: Maybe Text
oldComment = case (EntryOrigin
o, forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup EntrySelector
s Map EntrySelector ()
eaDeleteComment) of
(EntryOrigin
GenericOrigin, Maybe ()
_) -> forall a. Maybe a
Nothing
(Borrowed EntryDescription
ed, Maybe ()
Nothing) -> EntryDescription -> Maybe Text
edComment EntryDescription
ed
(Borrowed EntryDescription
_, Just ()) -> forall a. Maybe a
Nothing
desc0 :: EntryDescription
desc0 =
EntryDescription
{ edVersionMadeBy :: Version
edVersionMadeBy = Version
zipVersion,
edVersionNeeded :: Version
edVersionNeeded = Version
zipVersion,
edCompression :: CompressionMethod
edCompression = CompressionMethod
compression,
edModTime :: UTCTime
edModTime = forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault UTCTime
modTime EntrySelector
s Map EntrySelector UTCTime
eaModTime,
edCRC32 :: Word32
edCRC32 = Word32
0,
edCompressedSize :: Natural
edCompressedSize = Natural
0,
edUncompressedSize :: Natural
edUncompressedSize = Natural
0,
edOffset :: Natural
edOffset = forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
offset,
edComment :: Maybe Text
edComment = forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup EntrySelector
s Map EntrySelector Text
eaEntryComment forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Text
oldComment,
edExtraField :: Map Word16 ByteString
edExtraField = Map Word16 ByteString
extraField,
edExternalFileAttrs :: Word32
edExternalFileAttrs = Word32
extFileAttr
}
Handle -> ByteString -> IO ()
B.hPut Handle
h (Put -> ByteString
runPut (HeaderType -> EntrySelector -> EntryDescription -> Put
putHeader HeaderType
LocalHeader EntrySelector
s EntryDescription
desc0))
DataDescriptor {Natural
Word32
ddUncompressedSize :: Natural
ddCompressedSize :: Natural
ddCRC32 :: Word32
ddUncompressedSize :: DataDescriptor -> Natural
ddCompressedSize :: DataDescriptor -> Natural
ddCRC32 :: DataDescriptor -> Word32
..} <-
forall (m :: * -> *) r.
MonadUnliftIO m =>
ConduitT () Void (ResourceT m) r -> m r
C.runConduitRes forall a b. (a -> b) -> a -> b
$
if Bool
recompression
then
if CompressionMethod
compressed forall a. Eq a => a -> a -> Bool
== CompressionMethod
Store
then ConduitT () ByteString (ResourceT IO) ()
src forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| Handle
-> CompressionMethod
-> ConduitT ByteString Void (ResourceT IO) DataDescriptor
sinkData Handle
h CompressionMethod
compression
else ConduitT () ByteString (ResourceT IO) ()
src forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| forall (m :: * -> *).
(PrimMonad m, MonadThrow m, MonadResource m) =>
CompressionMethod -> ConduitT ByteString ByteString m ()
decompressingPipe CompressionMethod
compressed forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| Handle
-> CompressionMethod
-> ConduitT ByteString Void (ResourceT IO) DataDescriptor
sinkData Handle
h CompressionMethod
compression
else ConduitT () ByteString (ResourceT IO) ()
src forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| Handle
-> CompressionMethod
-> ConduitT ByteString Void (ResourceT IO) DataDescriptor
sinkData Handle
h CompressionMethod
Store
Integer
afterStreaming <- Handle -> IO Integer
hTell Handle
h
let desc1 :: EntryDescription
desc1 = case EntryOrigin
o of
EntryOrigin
GenericOrigin ->
EntryDescription
desc0
{ edCRC32 :: Word32
edCRC32 = Word32
ddCRC32,
edCompressedSize :: Natural
edCompressedSize = Natural
ddCompressedSize,
edUncompressedSize :: Natural
edUncompressedSize = Natural
ddUncompressedSize
}
Borrowed EntryDescription
ed ->
EntryDescription
desc0
{ edCRC32 :: Word32
edCRC32 =
forall a. a -> a -> Bool -> a
bool (EntryDescription -> Word32
edCRC32 EntryDescription
ed) Word32
ddCRC32 Bool
recompression,
edCompressedSize :: Natural
edCompressedSize =
forall a. a -> a -> Bool -> a
bool (EntryDescription -> Natural
edCompressedSize EntryDescription
ed) Natural
ddCompressedSize Bool
recompression,
edUncompressedSize :: Natural
edUncompressedSize =
forall a. a -> a -> Bool -> a
bool (EntryDescription -> Natural
edUncompressedSize EntryDescription
ed) Natural
ddUncompressedSize Bool
recompression
}
desc2 :: EntryDescription
desc2 =
EntryDescription
desc1
{ edVersionNeeded :: Version
edVersionNeeded =
Bool -> Maybe CompressionMethod -> Version
getZipVersion (EntryDescription -> Bool
needsZip64 EntryDescription
desc1) (forall a. a -> Maybe a
Just CompressionMethod
compression)
}
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek Integer
offset
Handle -> ByteString -> IO ()
B.hPut Handle
h (Put -> ByteString
runPut (HeaderType -> EntrySelector -> EntryDescription -> Put
putHeader HeaderType
LocalHeader EntrySelector
s EntryDescription
desc2))
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek Integer
afterStreaming
forall (m :: * -> *) a. Monad m => a -> m a
return (EntrySelector
s, EntryDescription
desc2)
sinkData ::
Handle ->
CompressionMethod ->
ConduitT ByteString Void (ResourceT IO) DataDescriptor
sinkData :: Handle
-> CompressionMethod
-> ConduitT ByteString Void (ResourceT IO) DataDescriptor
sinkData Handle
h CompressionMethod
compression = do
let sizeSink :: ConduitT ByteString o (ResourceT IO) Natural
sizeSink = forall (m :: * -> *) b a o.
Monad m =>
(b -> a -> b) -> b -> ConduitT a o m b
CL.fold (\Natural
acc ByteString
input -> forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
B.length ByteString
input) forall a. Num a => a -> a -> a
+ Natural
acc) Natural
0
dataSink :: ConduitT ByteString Void (ResourceT IO) Natural
dataSink =
forall i (m :: * -> *) r. ZipSink i m r -> ConduitT i Void m r
getZipSink forall a b. (a -> b) -> a -> b
$
forall i (m :: * -> *) r. ConduitT i Void m r -> ZipSink i m r
ZipSink forall {o}. ConduitT ByteString o (ResourceT IO) Natural
sizeSink forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall i (m :: * -> *) r. ConduitT i Void m r -> ZipSink i m r
ZipSink (forall (m :: * -> *) o.
MonadIO m =>
Handle -> ConduitT ByteString o m ()
CB.sinkHandle Handle
h)
withCompression :: ConduitT ByteString Void (ResourceT IO) a
-> ConduitT ByteString Void (ResourceT IO) (Natural, Word32, a)
withCompression ConduitT ByteString Void (ResourceT IO) a
sink =
forall i (m :: * -> *) r. ZipSink i m r -> ConduitT i Void m r
getZipSink forall a b. (a -> b) -> a -> b
$
(,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall i (m :: * -> *) r. ConduitT i Void m r -> ZipSink i m r
ZipSink forall {o}. ConduitT ByteString o (ResourceT IO) Natural
sizeSink
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall i (m :: * -> *) r. ConduitT i Void m r -> ZipSink i m r
ZipSink ConduitT ByteString Void (ResourceT IO) Word32
crc32Sink
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall i (m :: * -> *) r. ConduitT i Void m r -> ZipSink i m r
ZipSink ConduitT ByteString Void (ResourceT IO) a
sink
(Natural
uncompressedSize, Word32
crc32, Natural
compressedSize) <-
case CompressionMethod
compression of
CompressionMethod
Store ->
forall {a}.
ConduitT ByteString Void (ResourceT IO) a
-> ConduitT ByteString Void (ResourceT IO) (Natural, Word32, a)
withCompression
ConduitT ByteString Void (ResourceT IO) Natural
dataSink
CompressionMethod
Deflate ->
forall {a}.
ConduitT ByteString Void (ResourceT IO) a
-> ConduitT ByteString Void (ResourceT IO) (Natural, Word32, a)
withCompression forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
(PrimMonad m, MonadThrow m) =>
Int -> WindowBits -> ConduitT ByteString ByteString m ()
Z.compress Int
9 (Int -> WindowBits
Z.WindowBits (-Int
15)) forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ConduitT ByteString Void (ResourceT IO) Natural
dataSink
#ifdef ENABLE_BZIP2
CompressionMethod
BZip2 ->
forall {a}.
ConduitT ByteString Void (ResourceT IO) a
-> ConduitT ByteString Void (ResourceT IO) (Natural, Word32, a)
withCompression forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
MonadResource m =>
ConduitT ByteString ByteString m ()
BZ.bzip2 forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ConduitT ByteString Void (ResourceT IO) Natural
dataSink
#else
BZip2 -> throwM (UnsupportedCompressionMethod BZip2)
#endif
#ifdef ENABLE_ZSTD
CompressionMethod
Zstd ->
forall {a}.
ConduitT ByteString Void (ResourceT IO) a
-> ConduitT ByteString Void (ResourceT IO) (Natural, Word32, a)
withCompression forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *).
MonadIO m =>
Int -> ConduitT ByteString ByteString m ()
Zstandard.compress Int
1 forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ConduitT ByteString Void (ResourceT IO) Natural
dataSink
#else
Zstd -> throwM (UnsupportedCompressionMethod Zstd)
#endif
forall (m :: * -> *) a. Monad m => a -> m a
return
DataDescriptor
{ ddCRC32 :: Word32
ddCRC32 = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
crc32,
ddCompressedSize :: Natural
ddCompressedSize = Natural
compressedSize,
ddUncompressedSize :: Natural
ddUncompressedSize = Natural
uncompressedSize
}
writeCD ::
Handle ->
Maybe Text ->
Map EntrySelector EntryDescription ->
IO ()
writeCD :: Handle -> Maybe Text -> Map EntrySelector EntryDescription -> IO ()
writeCD Handle
h Maybe Text
comment Map EntrySelector EntryDescription
m = do
let cd :: ByteString
cd = Put -> ByteString
runPut (Map EntrySelector EntryDescription -> Put
putCD Map EntrySelector EntryDescription
m)
Natural
cdOffset <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO Integer
hTell Handle
h
Handle -> ByteString -> IO ()
B.hPut Handle
h ByteString
cd
let totalCount :: Natural
totalCount = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall k a. Map k a -> Int
M.size Map EntrySelector EntryDescription
m)
cdSize :: Natural
cdSize = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
B.length ByteString
cd)
needZip64 :: Bool
needZip64 =
Natural
totalCount forall a. Ord a => a -> a -> Bool
>= Natural
ffff
Bool -> Bool -> Bool
|| Natural
cdSize forall a. Ord a => a -> a -> Bool
>= Natural
ffffffff
Bool -> Bool -> Bool
|| Natural
cdOffset forall a. Ord a => a -> a -> Bool
>= Natural
ffffffff
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
needZip64 forall a b. (a -> b) -> a -> b
$ do
Natural
zip64ecdOffset <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO Integer
hTell Handle
h
(Handle -> ByteString -> IO ()
B.hPut Handle
h forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPut) (Natural -> Natural -> Natural -> Put
putZip64ECD Natural
totalCount Natural
cdSize Natural
cdOffset)
(Handle -> ByteString -> IO ()
B.hPut Handle
h forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPut) (Natural -> Put
putZip64ECDLocator Natural
zip64ecdOffset)
(Handle -> ByteString -> IO ()
B.hPut Handle
h forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPut) (Natural -> Natural -> Natural -> Maybe Text -> Put
putECD Natural
totalCount Natural
cdSize Natural
cdOffset Maybe Text
comment)
getLocalHeaderGap :: Get Integer
= do
Word32 -> Get ()
getSignature Word32
0x04034b50
Int -> Get ()
skip Int
2
Int -> Get ()
skip Int
2
Int -> Get ()
skip Int
2
Int -> Get ()
skip Int
2
Int -> Get ()
skip Int
2
Int -> Get ()
skip Int
4
Int -> Get ()
skip Int
4
Int -> Get ()
skip Int
4
Integer
fileNameSize <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le
Integer
extraFieldSize <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer
fileNameSize forall a. Num a => a -> a -> a
+ Integer
extraFieldSize)
getCD :: Get (Map EntrySelector EntryDescription)
getCD :: Get (Map EntrySelector EntryDescription)
getCD = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Maybe a] -> [a]
catMaybes forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f [a]
many Get (Maybe (EntrySelector, EntryDescription))
getCDHeader
getCDHeader :: Get (Maybe (EntrySelector, EntryDescription))
= do
Word32 -> Get ()
getSignature Word32
0x02014b50
Version
versionMadeBy <- Word16 -> Version
toVersion forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le
Version
versionNeeded <- Word16 -> Version
toVersion forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Version
versionNeeded forall a. Ord a => a -> a -> Bool
> Version
zipVersion) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail forall a b. (a -> b) -> a -> b
$
FilePath
"Version required to extract the archive is "
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
showVersion Version
versionNeeded
forall a. [a] -> [a] -> [a]
++ FilePath
" (can do "
forall a. [a] -> [a] -> [a]
++ Version -> FilePath
showVersion Version
zipVersion
forall a. [a] -> [a] -> [a]
++ FilePath
")"
Word16
bitFlag <- Get Word16
getWord16le
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Bits a => a -> Int -> Bool
testBit Word16
bitFlag) [Int
0, Int
6, Int
13]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail forall a b. (a -> b) -> a -> b
$
FilePath
"Encrypted archives are not supported"
let needUnicode :: Bool
needUnicode = forall a. Bits a => a -> Int -> Bool
testBit Word16
bitFlag Int
11
Maybe CompressionMethod
mcompression <- Word16 -> Maybe CompressionMethod
toCompressionMethod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le
Word16
modTime <- Get Word16
getWord16le
Word16
modDate <- Get Word16
getWord16le
Word32
crc32 <- Get Word32
getWord32le
Natural
compressed <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le
Natural
uncompressed <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le
Word16
fileNameSize <- Get Word16
getWord16le
Word16
extraFieldSize <- Get Word16
getWord16le
Word16
commentSize <- Get Word16
getWord16le
Int -> Get ()
skip Int
4
Word32
externalFileAttrs <- Get Word32
getWord32le
Natural
offset <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le
Maybe Text
fileName <-
Bool -> ByteString -> Maybe Text
decodeText Bool
needUnicode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getBytes (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
fileNameSize)
Map Word16 ByteString
extraField <-
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Int -> Get a -> Get a
isolate (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
extraFieldSize) (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many Get (Word16, ByteString)
getExtraField)
Maybe Text
comment <- Bool -> ByteString -> Maybe Text
decodeText Bool
needUnicode forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getBytes (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
commentSize)
let dfltZip64 :: Zip64ExtraField
dfltZip64 =
Zip64ExtraField
{ z64efUncompressedSize :: Natural
z64efUncompressedSize = Natural
uncompressed,
z64efCompressedSize :: Natural
z64efCompressedSize = Natural
compressed,
z64efOffset :: Natural
z64efOffset = Natural
offset
}
z64ef :: Zip64ExtraField
z64ef = case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Word16
1 Map Word16 ByteString
extraField of
Maybe ByteString
Nothing -> Zip64ExtraField
dfltZip64
Just ByteString
b -> Zip64ExtraField -> ByteString -> Zip64ExtraField
parseZip64ExtraField Zip64ExtraField
dfltZip64 ByteString
b
case Maybe CompressionMethod
mcompression of
Maybe CompressionMethod
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Just CompressionMethod
compression ->
let desc :: EntryDescription
desc =
EntryDescription
{ edVersionMadeBy :: Version
edVersionMadeBy = Version
versionMadeBy,
edVersionNeeded :: Version
edVersionNeeded = Version
versionNeeded,
edCompression :: CompressionMethod
edCompression = CompressionMethod
compression,
edModTime :: UTCTime
edModTime = MsDosTime -> UTCTime
fromMsDosTime (Word16 -> Word16 -> MsDosTime
MsDosTime Word16
modDate Word16
modTime),
edCRC32 :: Word32
edCRC32 = Word32
crc32,
edCompressedSize :: Natural
edCompressedSize = Zip64ExtraField -> Natural
z64efCompressedSize Zip64ExtraField
z64ef,
edUncompressedSize :: Natural
edUncompressedSize = Zip64ExtraField -> Natural
z64efUncompressedSize Zip64ExtraField
z64ef,
edOffset :: Natural
edOffset = Zip64ExtraField -> Natural
z64efOffset Zip64ExtraField
z64ef,
edComment :: Maybe Text
edComment = if Word16
commentSize forall a. Eq a => a -> a -> Bool
== Word16
0 then forall a. Maybe a
Nothing else Maybe Text
comment,
edExtraField :: Map Word16 ByteString
edExtraField = Map Word16 ByteString
extraField,
edExternalFileAttrs :: Word32
edExternalFileAttrs = Word32
externalFileAttrs
}
in forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ (,EntryDescription
desc) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Maybe Text
fileName forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *). MonadThrow m => FilePath -> m EntrySelector
mkEntrySelector forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack)
getExtraField :: Get (Word16, ByteString)
= do
Word16
header <- Get Word16
getWord16le
Word16
size <- Get Word16
getWord16le
ByteString
body <- Int -> Get ByteString
getBytes (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
size)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word16
header, ByteString
body)
getSignature :: Word32 -> Get ()
getSignature :: Word32 -> Get ()
getSignature Word32
sig = do
Word32
x <- Get Word32
getWord32le
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Word32
x forall a. Eq a => a -> a -> Bool
== Word32
sig) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail forall a b. (a -> b) -> a -> b
$
FilePath
"Expected signature " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Word32
sig forall a. [a] -> [a] -> [a]
++ FilePath
", but got: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Word32
x
parseZip64ExtraField ::
Zip64ExtraField ->
ByteString ->
Zip64ExtraField
dflt :: Zip64ExtraField
dflt@Zip64ExtraField {Natural
z64efOffset :: Natural
z64efCompressedSize :: Natural
z64efUncompressedSize :: Natural
z64efOffset :: Zip64ExtraField -> Natural
z64efCompressedSize :: Zip64ExtraField -> Natural
z64efUncompressedSize :: Zip64ExtraField -> Natural
..} ByteString
b =
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const Zip64ExtraField
dflt) forall a. a -> a
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Get a -> ByteString -> Either FilePath a
runGet ByteString
b forall a b. (a -> b) -> a -> b
$ do
let ifsat :: Natural -> Get Natural
ifsat Natural
v =
if Natural
v forall a. Ord a => a -> a -> Bool
>= Natural
ffffffff
then forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getWord64le
else forall (m :: * -> *) a. Monad m => a -> m a
return Natural
v
Natural
uncompressed <- Natural -> Get Natural
ifsat Natural
z64efUncompressedSize
Natural
compressed <- Natural -> Get Natural
ifsat Natural
z64efCompressedSize
Natural
offset <- Natural -> Get Natural
ifsat Natural
z64efOffset
forall (m :: * -> *) a. Monad m => a -> m a
return (Natural -> Natural -> Natural -> Zip64ExtraField
Zip64ExtraField Natural
uncompressed Natural
compressed Natural
offset)
makeZip64ExtraField ::
HeaderType ->
Zip64ExtraField ->
ByteString
HeaderType
headerType Zip64ExtraField {Natural
z64efOffset :: Natural
z64efCompressedSize :: Natural
z64efUncompressedSize :: Natural
z64efOffset :: Zip64ExtraField -> Natural
z64efCompressedSize :: Zip64ExtraField -> Natural
z64efUncompressedSize :: Zip64ExtraField -> Natural
..} = Put -> ByteString
runPut forall a b. (a -> b) -> a -> b
$ do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (HeaderType
headerType forall a. Eq a => a -> a -> Bool
== HeaderType
LocalHeader Bool -> Bool -> Bool
|| Natural
z64efUncompressedSize forall a. Ord a => a -> a -> Bool
>= Natural
ffffffff) forall a b. (a -> b) -> a -> b
$
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
z64efUncompressedSize)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (HeaderType
headerType forall a. Eq a => a -> a -> Bool
== HeaderType
LocalHeader Bool -> Bool -> Bool
|| Natural
z64efCompressedSize forall a. Ord a => a -> a -> Bool
>= Natural
ffffffff) forall a b. (a -> b) -> a -> b
$
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
z64efCompressedSize)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (HeaderType
headerType forall a. Eq a => a -> a -> Bool
== HeaderType
CentralDirHeader Bool -> Bool -> Bool
&& Natural
z64efOffset forall a. Ord a => a -> a -> Bool
>= Natural
ffffffff) forall a b. (a -> b) -> a -> b
$
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
z64efOffset)
putExtraField :: Map Word16 ByteString -> Put
Map Word16 ByteString
m = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall k a. Map k a -> [k]
M.keys Map Word16 ByteString
m) forall a b. (a -> b) -> a -> b
$ \Word16
headerId -> do
let b :: ByteString
b = Int -> ByteString -> ByteString
B.take Int
0xffff (Map Word16 ByteString
m forall k a. Ord k => Map k a -> k -> a
! Word16
headerId)
Word16 -> Put
putWord16le Word16
headerId
Word16 -> Put
putWord16le (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
b)
Putter ByteString
putByteString ByteString
b
putCD :: Map EntrySelector EntryDescription -> Put
putCD :: Map EntrySelector EntryDescription -> Put
putCD Map EntrySelector EntryDescription
m = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (forall k a. Map k a -> [k]
M.keys Map EntrySelector EntryDescription
m) forall a b. (a -> b) -> a -> b
$ \EntrySelector
s ->
HeaderType -> EntrySelector -> EntryDescription -> Put
putHeader HeaderType
CentralDirHeader EntrySelector
s (Map EntrySelector EntryDescription
m forall k a. Ord k => Map k a -> k -> a
! EntrySelector
s)
putHeader ::
HeaderType ->
EntrySelector ->
EntryDescription ->
Put
HeaderType
headerType EntrySelector
s entry :: EntryDescription
entry@EntryDescription {Natural
Maybe Text
Word32
Version
Map Word16 ByteString
UTCTime
CompressionMethod
edExternalFileAttrs :: Word32
edExtraField :: Map Word16 ByteString
edComment :: Maybe Text
edOffset :: Natural
edUncompressedSize :: Natural
edCompressedSize :: Natural
edCRC32 :: Word32
edModTime :: UTCTime
edCompression :: CompressionMethod
edVersionNeeded :: Version
edVersionMadeBy :: Version
edExternalFileAttrs :: EntryDescription -> Word32
edExtraField :: EntryDescription -> Map Word16 ByteString
edComment :: EntryDescription -> Maybe Text
edOffset :: EntryDescription -> Natural
edUncompressedSize :: EntryDescription -> Natural
edCompressedSize :: EntryDescription -> Natural
edCRC32 :: EntryDescription -> Word32
edModTime :: EntryDescription -> UTCTime
edCompression :: EntryDescription -> CompressionMethod
edVersionNeeded :: EntryDescription -> Version
edVersionMadeBy :: EntryDescription -> Version
..} = do
let isCentralDirHeader :: Bool
isCentralDirHeader = HeaderType
headerType forall a. Eq a => a -> a -> Bool
== HeaderType
CentralDirHeader
Putter Word32
putWord32le (forall a. a -> a -> Bool -> a
bool Word32
0x04034b50 Word32
0x02014b50 Bool
isCentralDirHeader)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isCentralDirHeader forall a b. (a -> b) -> a -> b
$
Word16 -> Put
putWord16le (Version -> Word16
fromVersion Version
edVersionMadeBy)
Word16 -> Put
putWord16le (Version -> Word16
fromVersion Version
edVersionNeeded)
let entryName :: Text
entryName = EntrySelector -> Text
getEntryName EntrySelector
s
rawName :: ByteString
rawName = Text -> ByteString
T.encodeUtf8 Text
entryName
comment :: ByteString
comment = Int -> ByteString -> ByteString
B.take Int
0xffff (forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
B.empty Text -> ByteString
T.encodeUtf8 Maybe Text
edComment)
unicode :: Bool
unicode =
Text -> Bool
needsUnicode Text
entryName
Bool -> Bool -> Bool
|| forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Text -> Bool
needsUnicode Maybe Text
edComment
modTime :: MsDosTime
modTime = UTCTime -> MsDosTime
toMsDosTime UTCTime
edModTime
Word16 -> Put
putWord16le (if Bool
unicode then forall a. Bits a => a -> Int -> a
setBit Word16
0 Int
11 else Word16
0)
Word16 -> Put
putWord16le (CompressionMethod -> Word16
fromCompressionMethod CompressionMethod
edCompression)
Word16 -> Put
putWord16le (MsDosTime -> Word16
msDosTime MsDosTime
modTime)
Word16 -> Put
putWord16le (MsDosTime -> Word16
msDosDate MsDosTime
modTime)
Putter Word32
putWord32le Word32
edCRC32
Putter Word32
putWord32le (forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation Natural
edCompressedSize)
Putter Word32
putWord32le (forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation Natural
edUncompressedSize)
Word16 -> Put
putWord16le (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
rawName)
let zip64ef :: ByteString
zip64ef =
HeaderType -> Zip64ExtraField -> ByteString
makeZip64ExtraField
HeaderType
headerType
Zip64ExtraField
{ z64efUncompressedSize :: Natural
z64efUncompressedSize = Natural
edUncompressedSize,
z64efCompressedSize :: Natural
z64efCompressedSize = Natural
edCompressedSize,
z64efOffset :: Natural
z64efOffset = Natural
edOffset
}
extraField :: ByteString
extraField =
Int -> ByteString -> ByteString
B.take Int
0xffff forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPut forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Word16 ByteString -> Put
putExtraField forall a b. (a -> b) -> a -> b
$
if EntryDescription -> Bool
needsZip64 EntryDescription
entry
then forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Word16
1 ByteString
zip64ef Map Word16 ByteString
edExtraField
else Map Word16 ByteString
edExtraField
Word16 -> Put
putWord16le (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
extraField)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isCentralDirHeader forall a b. (a -> b) -> a -> b
$ do
Word16 -> Put
putWord16le (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
comment)
Word16 -> Put
putWord16le Word16
0
Word16 -> Put
putWord16le Word16
0
Putter Word32
putWord32le Word32
edExternalFileAttrs
Putter Word32
putWord32le (forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation Natural
edOffset)
Putter ByteString
putByteString ByteString
rawName
Putter ByteString
putByteString ByteString
extraField
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isCentralDirHeader (Putter ByteString
putByteString ByteString
comment)
putZip64ECD ::
Natural ->
Natural ->
Natural ->
Put
putZip64ECD :: Natural -> Natural -> Natural -> Put
putZip64ECD Natural
totalCount Natural
cdSize Natural
cdOffset = do
Putter Word32
putWord32le Word32
0x06064b50
Putter Word64
putWord64le Word64
44
Word16 -> Put
putWord16le (Version -> Word16
fromVersion Version
zipVersion)
Word16 -> Put
putWord16le (Version -> Word16
fromVersion forall a b. (a -> b) -> a -> b
$ Bool -> Maybe CompressionMethod -> Version
getZipVersion Bool
True forall a. Maybe a
Nothing)
Putter Word32
putWord32le Word32
0
Putter Word32
putWord32le Word32
0
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
totalCount)
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
totalCount)
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
cdSize)
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
cdOffset)
putZip64ECDLocator ::
Natural ->
Put
putZip64ECDLocator :: Natural -> Put
putZip64ECDLocator Natural
ecdOffset = do
Putter Word32
putWord32le Word32
0x07064b50
Putter Word32
putWord32le Word32
0
Putter Word64
putWord64le (forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
ecdOffset)
Putter Word32
putWord32le Word32
1
getECD :: Get ArchiveDescription
getECD :: Get ArchiveDescription
getECD = do
Word32
sig <- Get Word32
getWord32le
let zip64 :: Bool
zip64 = Word32
sig forall a. Eq a => a -> a -> Bool
== Word32
0x06064b50
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Word32
sig forall a. Eq a => a -> a -> Bool
== Word32
0x06054b50 Bool -> Bool -> Bool
|| Word32
sig forall a. Eq a => a -> a -> Bool
== Word32
0x06064b50) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Cannot locate end of central directory"
Maybe Word64
zip64size <-
if Bool
zip64
then do
Word64
x <- Get Word64
getWord64le
Int -> Get ()
skip Int
2
Int -> Get ()
skip Int
2
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Word64
x)
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Word32
thisDisk <- forall a. a -> a -> Bool -> a
bool (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le) Get Word32
getWord32le Bool
zip64
Word32
cdDisk <- forall a. a -> a -> Bool -> a
bool (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16le) Get Word32
getWord32le Bool
zip64
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Word32
thisDisk forall a. Eq a => a -> a -> Bool
== Word32
0 Bool -> Bool -> Bool
&& Word32
cdDisk forall a. Eq a => a -> a -> Bool
== Word32
0) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"No support for multi-disk archives"
Int -> Get ()
skip (forall a. a -> a -> Bool -> a
bool Int
2 Int
8 Bool
zip64)
Int -> Get ()
skip (forall a. a -> a -> Bool -> a
bool Int
2 Int
8 Bool
zip64)
Word64
cdSize <- forall a. a -> a -> Bool -> a
bool (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le) Get Word64
getWord64le Bool
zip64
Word64
cdOffset <- forall a. a -> a -> Bool -> a
bool (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32le) Get Word64
getWord64le Bool
zip64
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
zip64 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Get ()
skip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust Maybe Word64
zip64size forall a. Num a => a -> a -> a
- Word64
4
Word16
commentSize <- Get Word16
getWord16le
Maybe Text
comment <- Bool -> ByteString -> Maybe Text
decodeText Bool
True forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getBytes (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
commentSize)
forall (m :: * -> *) a. Monad m => a -> m a
return
ArchiveDescription
{ adComment :: Maybe Text
adComment = if Word16
commentSize forall a. Eq a => a -> a -> Bool
== Word16
0 then forall a. Maybe a
Nothing else Maybe Text
comment,
adCDOffset :: Natural
adCDOffset = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
cdOffset,
adCDSize :: Natural
adCDSize = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
cdSize
}
putECD ::
Natural ->
Natural ->
Natural ->
Maybe Text ->
Put
putECD :: Natural -> Natural -> Natural -> Maybe Text -> Put
putECD Natural
totalCount Natural
cdSize Natural
cdOffset Maybe Text
mcomment = do
Putter Word32
putWord32le Word32
0x06054b50
Word16 -> Put
putWord16le Word16
0
Word16 -> Put
putWord16le Word16
0
Word16 -> Put
putWord16le (forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation Natural
totalCount)
Word16 -> Put
putWord16le (forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation Natural
totalCount)
Putter Word32
putWord32le (forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation Natural
cdSize)
Putter Word32
putWord32le (forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation Natural
cdOffset)
let comment :: ByteString
comment = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
B.empty Text -> ByteString
T.encodeUtf8 Maybe Text
mcomment
Word16 -> Put
putWord16le (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
comment)
Putter ByteString
putByteString ByteString
comment
locateECD :: FilePath -> Handle -> IO (Maybe Integer)
locateECD :: FilePath -> Handle -> IO (Maybe Integer)
locateECD FilePath
path Handle
h = IO (Maybe Integer)
sizeCheck
where
sizeCheck :: IO (Maybe Integer)
sizeCheck = do
Integer
fsize <- Handle -> IO Integer
hFileSize Handle
h
let limit :: Integer
limit = forall a. Ord a => a -> a -> a
max Integer
0 (Integer
fsize forall a. Num a => a -> a -> a
- Integer
0xffff forall a. Num a => a -> a -> a
- Integer
22)
if Integer
fsize forall a. Ord a => a -> a -> Bool
< Integer
22
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
SeekFromEnd (-Integer
22) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Integer -> IO (Maybe Integer)
loop Integer
limit
loop :: Integer -> IO (Maybe Integer)
loop Integer
limit = do
Word32
sig <- forall {b}. Get b -> Int -> IO b
getNum Get Word32
getWord32le Int
4
Integer
pos <- forall a. Num a => a -> a -> a
subtract Integer
4 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO Integer
hTell Handle
h
let again :: IO (Maybe Integer)
again = Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek (Integer
pos forall a. Num a => a -> a -> a
- Integer
1) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Integer -> IO (Maybe Integer)
loop Integer
limit
done :: Bool
done = Integer
pos forall a. Ord a => a -> a -> Bool
<= Integer
limit
if Word32
sig forall a. Eq a => a -> a -> Bool
== Word32
0x06054b50
then do
Maybe Integer
result <-
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (Integer -> IO (Maybe Integer)
checkComment Integer
pos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> IO (Maybe Integer)
checkCDSig
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> IO (Maybe Integer)
checkZip64
case Maybe Integer
result of
Maybe Integer
Nothing -> forall a. a -> a -> Bool -> a
bool IO (Maybe Integer)
again (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing) Bool
done
Just Integer
ecd -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Integer
ecd)
else forall a. a -> a -> Bool -> a
bool IO (Maybe Integer)
again (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing) Bool
done
checkComment :: Integer -> IO (Maybe Integer)
checkComment Integer
pos = do
Integer
size <- Handle -> IO Integer
hFileSize Handle
h
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek (Integer
pos forall a. Num a => a -> a -> a
+ Integer
20)
Integer
l <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {b}. Get b -> Int -> IO b
getNum Get Word16
getWord16le Int
2
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if Integer
l forall a. Num a => a -> a -> a
+ Integer
22 forall a. Eq a => a -> a -> Bool
== Integer
size forall a. Num a => a -> a -> a
- Integer
pos
then forall a. a -> Maybe a
Just Integer
pos
else forall a. Maybe a
Nothing
checkCDSig :: Integer -> IO (Maybe Integer)
checkCDSig Integer
pos = do
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek (Integer
pos forall a. Num a => a -> a -> a
+ Integer
16)
Integer
sigPos <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {b}. Get b -> Int -> IO b
getNum Get Word32
getWord32le Int
4
if Integer
sigPos forall a. Eq a => a -> a -> Bool
== Integer
0xffffffff
then forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Integer
pos)
else do
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek Integer
sigPos
Word32
cdSig <- forall {b}. Get b -> Int -> IO b
getNum Get Word32
getWord32le Int
4
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
if Word32
cdSig forall a. Eq a => a -> a -> Bool
== Word32
0x02014b50
Bool -> Bool -> Bool
||
Word32
cdSig forall a. Eq a => a -> a -> Bool
== Word32
0x06064b50
Bool -> Bool -> Bool
||
Word32
cdSig forall a. Eq a => a -> a -> Bool
== Word32
0x06054b50
then
forall a. a -> Maybe a
Just Integer
pos
else forall a. Maybe a
Nothing
checkZip64 :: Integer -> IO (Maybe Integer)
checkZip64 Integer
pos =
if Integer
pos forall a. Ord a => a -> a -> Bool
< Integer
20
then forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Integer
pos)
else do
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek (Integer
pos forall a. Num a => a -> a -> a
- Integer
20)
Word32
zip64locatorSig <- forall {b}. Get b -> Int -> IO b
getNum Get Word32
getWord32le Int
4
if Word32
zip64locatorSig forall a. Eq a => a -> a -> Bool
== Word32
0x07064b50
then do
Handle -> SeekMode -> Integer -> IO ()
hSeek Handle
h SeekMode
AbsoluteSeek (Integer
pos forall a. Num a => a -> a -> a
- Integer
12)
forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {b}. Get b -> Int -> IO b
getNum Get Word64
getWord64le Int
8
else forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Integer
pos)
getNum :: Get b -> Int -> IO b
getNum Get b
f Int
n = do
Either FilePath b
result <- forall a. Get a -> ByteString -> Either FilePath a
runGet Get b
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> Int -> IO ByteString
B.hGet Handle
h Int
n
case Either FilePath b
result of
Left FilePath
msg -> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (FilePath -> FilePath -> ZipException
ParsingFailed FilePath
path FilePath
msg)
Right b
val -> forall (m :: * -> *) a. Monad m => a -> m a
return b
val
renameKey :: (Ord k) => k -> k -> Map k a -> Map k a
renameKey :: forall k a. Ord k => k -> k -> Map k a -> Map k a
renameKey k
ok k
nk Map k a
m = case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup k
ok Map k a
m of
Maybe a
Nothing -> Map k a
m
Just a
e -> forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert k
nk a
e (forall k a. Ord k => k -> Map k a -> Map k a
M.delete k
ok Map k a
m)
withSaturation :: forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation :: forall a b. (Integral a, Integral b, Bounded b) => a -> b
withSaturation a
x =
if (forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x :: Integer) forall a. Ord a => a -> a -> Bool
> (forall a b. (Integral a, Num b) => a -> b
fromIntegral b
bound :: Integer)
then b
bound
else forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x
where
bound :: b
bound = forall a. Bounded a => a
maxBound :: b
targetEntry :: PendingAction -> Maybe EntrySelector
targetEntry :: PendingAction -> Maybe EntrySelector
targetEntry (SinkEntry CompressionMethod
_ ConduitT () ByteString (ResourceT IO) ()
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (CopyEntry FilePath
_ EntrySelector
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (RenameEntry EntrySelector
s EntrySelector
_) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (DeleteEntry EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (Recompress CompressionMethod
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (SetEntryComment Text
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (DeleteEntryComment EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (SetModTime UTCTime
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (AddExtraField Word16
_ ByteString
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (DeleteExtraField Word16
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (SetExternalFileAttributes Word32
_ EntrySelector
s) = forall a. a -> Maybe a
Just EntrySelector
s
targetEntry (SetArchiveComment Text
_) = forall a. Maybe a
Nothing
targetEntry PendingAction
DeleteArchiveComment = forall a. Maybe a
Nothing
decodeText ::
Bool ->
ByteString ->
Maybe Text
decodeText :: Bool -> ByteString -> Maybe Text
decodeText Bool
False = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeCP437
decodeText Bool
True = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
T.decodeUtf8'
needsUnicode :: Text -> Bool
needsUnicode :: Text -> Bool
needsUnicode = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
validCP437
where
validCP437 :: Char -> Bool
validCP437 Char
x = Char -> Int
ord Char
x forall a. Ord a => a -> a -> Bool
<= Int
127
toVersion :: Word16 -> Version
toVersion :: Word16 -> Version
toVersion Word16
x = [Int] -> Version
makeVersion [Int
major, Int
minor]
where
(Int
major, Int
minor) = forall a. Integral a => a -> a -> (a, a)
quotRem (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Word16
x forall a. Bits a => a -> a -> a
.&. Word16
0x00ff) Int
10
fromVersion :: Version -> Word16
fromVersion :: Version -> Word16
fromVersion Version
v = forall a b. (Integral a, Num b) => a -> b
fromIntegral ((ZIP_OS `shiftL` 8) .|. (major forall a. Num a => a -> a -> a
* 10 + minor))
where
(Int
major, Int
minor) =
case Version -> [Int]
versionBranch Version
v of
Int
v0 : Int
v1 : [Int]
_ -> (Int
v0, Int
v1)
Int
v0 : [Int]
_ -> (Int
v0, Int
0)
[] -> (Int
0, Int
0)
toCompressionMethod :: Word16 -> Maybe CompressionMethod
toCompressionMethod :: Word16 -> Maybe CompressionMethod
toCompressionMethod Word16
0 = forall a. a -> Maybe a
Just CompressionMethod
Store
toCompressionMethod Word16
8 = forall a. a -> Maybe a
Just CompressionMethod
Deflate
toCompressionMethod Word16
12 = forall a. a -> Maybe a
Just CompressionMethod
BZip2
toCompressionMethod Word16
93 = forall a. a -> Maybe a
Just CompressionMethod
Zstd
toCompressionMethod Word16
_ = forall a. Maybe a
Nothing
fromCompressionMethod :: CompressionMethod -> Word16
fromCompressionMethod :: CompressionMethod -> Word16
fromCompressionMethod CompressionMethod
Store = Word16
0
fromCompressionMethod CompressionMethod
Deflate = Word16
8
fromCompressionMethod CompressionMethod
BZip2 = Word16
12
fromCompressionMethod CompressionMethod
Zstd = Word16
93
needsZip64 :: EntryDescription -> Bool
needsZip64 :: EntryDescription -> Bool
needsZip64 EntryDescription {Natural
Maybe Text
Word32
Version
Map Word16 ByteString
UTCTime
CompressionMethod
edExternalFileAttrs :: Word32
edExtraField :: Map Word16 ByteString
edComment :: Maybe Text
edOffset :: Natural
edUncompressedSize :: Natural
edCompressedSize :: Natural
edCRC32 :: Word32
edModTime :: UTCTime
edCompression :: CompressionMethod
edVersionNeeded :: Version
edVersionMadeBy :: Version
edExternalFileAttrs :: EntryDescription -> Word32
edExtraField :: EntryDescription -> Map Word16 ByteString
edComment :: EntryDescription -> Maybe Text
edOffset :: EntryDescription -> Natural
edUncompressedSize :: EntryDescription -> Natural
edCompressedSize :: EntryDescription -> Natural
edCRC32 :: EntryDescription -> Word32
edModTime :: EntryDescription -> UTCTime
edCompression :: EntryDescription -> CompressionMethod
edVersionNeeded :: EntryDescription -> Version
edVersionMadeBy :: EntryDescription -> Version
..} =
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any
(forall a. Ord a => a -> a -> Bool
>= Natural
ffffffff)
[Natural
edOffset, Natural
edCompressedSize, Natural
edUncompressedSize]
getZipVersion :: Bool -> Maybe CompressionMethod -> Version
getZipVersion :: Bool -> Maybe CompressionMethod -> Version
getZipVersion Bool
zip64 Maybe CompressionMethod
m = forall a. Ord a => a -> a -> a
max Version
zip64ver Version
mver
where
zip64ver :: Version
zip64ver = [Int] -> Version
makeVersion (if Bool
zip64 then [Int
4, Int
5] else [Int
2, Int
0])
mver :: Version
mver = [Int] -> Version
makeVersion forall a b. (a -> b) -> a -> b
$ case Maybe CompressionMethod
m of
Maybe CompressionMethod
Nothing -> [Int
2, Int
0]
Just CompressionMethod
Store -> [Int
2, Int
0]
Just CompressionMethod
Deflate -> [Int
2, Int
0]
Just CompressionMethod
BZip2 -> [Int
4, Int
6]
Just CompressionMethod
Zstd -> [Int
6, Int
3]
decompressingPipe ::
(PrimMonad m, MonadThrow m, MonadResource m) =>
CompressionMethod ->
ConduitT ByteString ByteString m ()
decompressingPipe :: forall (m :: * -> *).
(PrimMonad m, MonadThrow m, MonadResource m) =>
CompressionMethod -> ConduitT ByteString ByteString m ()
decompressingPipe CompressionMethod
Store = forall (m :: * -> *) i o r.
Monad m =>
(i -> ConduitT i o m r) -> ConduitT i o m ()
C.awaitForever forall (m :: * -> *) o i. Monad m => o -> ConduitT i o m ()
C.yield
decompressingPipe CompressionMethod
Deflate = forall (m :: * -> *).
(PrimMonad m, MonadThrow m) =>
WindowBits -> ConduitT ByteString ByteString m ()
Z.decompress forall a b. (a -> b) -> a -> b
$ Int -> WindowBits
Z.WindowBits (-Int
15)
#ifdef ENABLE_BZIP2
decompressingPipe CompressionMethod
BZip2 = forall (m :: * -> *).
MonadResource m =>
ConduitT ByteString ByteString m ()
BZ.bunzip2
#else
decompressingPipe BZip2 = throwM (UnsupportedCompressionMethod BZip2)
#endif
#ifdef ENABLE_ZSTD
decompressingPipe CompressionMethod
Zstd = forall (m :: * -> *).
MonadIO m =>
ConduitT ByteString ByteString m ()
Zstandard.decompress
#else
decompressingPipe Zstd = throwM (UnsupportedCompressionMethod Zstd)
#endif
crc32Sink :: ConduitT ByteString Void (ResourceT IO) Word32
crc32Sink :: ConduitT ByteString Void (ResourceT IO) Word32
crc32Sink = forall (m :: * -> *) b a o.
Monad m =>
(b -> a -> b) -> b -> ConduitT a o m b
CL.fold forall a. CRC32 a => Word32 -> a -> Word32
crc32Update Word32
0
toMsDosTime :: UTCTime -> MsDosTime
toMsDosTime :: UTCTime -> MsDosTime
toMsDosTime UTCTime {DiffTime
Day
utctDay :: UTCTime -> Day
utctDayTime :: UTCTime -> DiffTime
utctDayTime :: DiffTime
utctDay :: Day
..} = Word16 -> Word16 -> MsDosTime
MsDosTime Word16
dosDate Word16
dosTime
where
dosTime :: Word16
dosTime = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
seconds forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
shiftL Int
minutes Int
5 forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
shiftL Int
hours Int
11)
dosDate :: Word16
dosDate = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
day forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
shiftL Int
month Int
5 forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
shiftL Int
year Int
9)
seconds :: Int
seconds =
let (MkFixed Integer
x) = TimeOfDay -> Fixed E12
todSec TimeOfDay
tod
in forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
x forall a. Integral a => a -> a -> a
`quot` Integer
2000000000000)
minutes :: Int
minutes = TimeOfDay -> Int
todMin TimeOfDay
tod
hours :: Int
hours = TimeOfDay -> Int
todHour TimeOfDay
tod
tod :: TimeOfDay
tod = DiffTime -> TimeOfDay
timeToTimeOfDay DiffTime
utctDayTime
year :: Int
year = forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
year' forall a. Num a => a -> a -> a
- Int
1980
(Integer
year', Int
month, Int
day) = Day -> (Integer, Int, Int)
toGregorian Day
utctDay
fromMsDosTime :: MsDosTime -> UTCTime
fromMsDosTime :: MsDosTime -> UTCTime
fromMsDosTime MsDosTime {Word16
msDosTime :: Word16
msDosDate :: Word16
msDosTime :: MsDosTime -> Word16
msDosDate :: MsDosTime -> Word16
..} =
Day -> DiffTime -> UTCTime
UTCTime
(Integer -> Int -> Int -> Day
fromGregorian Integer
year Int
month Int
day)
(Integer -> DiffTime
secondsToDiffTime forall a b. (a -> b) -> a -> b
$ Integer
hours forall a. Num a => a -> a -> a
* Integer
3600 forall a. Num a => a -> a -> a
+ Integer
minutes forall a. Num a => a -> a -> a
* Integer
60 forall a. Num a => a -> a -> a
+ Integer
seconds)
where
seconds :: Integer
seconds = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Word16
2 forall a. Num a => a -> a -> a
* (Word16
msDosTime forall a. Bits a => a -> a -> a
.&. Word16
0x1f)
minutes :: Integer
minutes = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word16
msDosTime Int
5 forall a. Bits a => a -> a -> a
.&. Word16
0x3f)
hours :: Integer
hours = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word16
msDosTime Int
11 forall a. Bits a => a -> a -> a
.&. Word16
0x1f)
day :: Int
day = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16
msDosDate forall a. Bits a => a -> a -> a
.&. Word16
0x1f)
month :: Int
month = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> Int -> a
shiftR Word16
msDosDate Int
5 forall a. Bits a => a -> a -> a
.&. Word16
0x0f
year :: Integer
year = Integer
1980 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word16
msDosDate Int
9)
ffff, ffffffff :: Natural
#ifdef HASKELL_ZIP_DEV_MODE
ffff = 200
ffffffff = 5000
#else
ffff :: Natural
ffff = Natural
0xffff
ffffffff :: Natural
ffffffff = Natural
0xffffffff
#endif
defaultFileMode :: Word32
#ifdef mingw32_HOST_OS
defaultFileMode = 0
#else
defaultFileMode :: Word32
defaultFileMode = CMode -> Word32
Unix.fromFileMode CMode
0o600
#endif