Hello community,

here is the log from the commit of package ghc-zip-archive for openSUSE:Factory 
checked in at 2018-12-10 12:29:51
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-zip-archive (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-zip-archive.new.19453 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-zip-archive"

Mon Dec 10 12:29:51 2018 rev:13 rq:656590 version:0.4

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-zip-archive/ghc-zip-archive.changes  
2018-10-25 09:07:56.154447862 +0200
+++ 
/work/SRC/openSUSE:Factory/.ghc-zip-archive.new.19453/ghc-zip-archive.changes   
    2018-12-10 12:29:51.914435394 +0100
@@ -1,0 +2,38 @@
+Tue Dec  4 03:02:25 UTC 2018 - psim...@suse.com
+
+- Update zip-archive to version 0.4.
+  zip-archive 0.4
+
+    * Implement read-only support for PKWARE encryption (Sergii Rudchenko).
+      The "traditional" PKWARE encryption is a symmetric encryption
+      algorithm described in zip format specification in section 6.1.
+      This change allows to extract basic "password-protected" entries from
+      ZIP files.  Note that the standard file extraction function
+      extractFilesFromArchive does not decrypt entries (it will raise
+      an exception if it encounters an encrypted entry). To handle
+      archives with encrypted entries, use the new function
+      fromEncryptedEntry.
+
+      API changes:
+
+      + Add eEncryptionMethod field to Entry.
+      + Add EncryptionMethod type.
+      + Add function isEncryptedEntry.
+      + Add function fromEncryptedEntry.
+      * Add CannotWriteEncryptedEntry constructor to ZipException.
+
+    * Add UnsafePath to ZipException (#50).
+    * writeEntry: raise UnsafePath exception for unsafe paths (#50).
+      This prevents malicious zip files from overwriting paths
+      above the working directory.
+    * Add Paths_zip_archive to autogen-modules.
+    * Clarify README and cabal description.
+    * Specify cabal-version: 2.0.  Otherwise we get an unknown build
+      tool error using `build-depends` without a custom Setup.hs.
+    * Change build-type to simple.  Retain 'build-tools: unzip' in
+      test stanza, though now it doesn't do anything except give a
+      hint to external tools.  If unzip is not found in the path,
+      the test suite prints a message and counts the test that
+      requires unzip as succeeding (see #51).
+
+-------------------------------------------------------------------

Old:
----
  zip-archive-0.3.3.tar.gz

New:
----
  zip-archive-0.4.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-zip-archive.spec ++++++
--- /var/tmp/diff_new_pack.mLy1xA/_old  2018-12-10 12:29:52.494434813 +0100
+++ /var/tmp/diff_new_pack.mLy1xA/_new  2018-12-10 12:29:52.494434813 +0100
@@ -19,7 +19,7 @@
 %global pkg_name zip-archive
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        0.3.3
+Version:        0.4
 Release:        0
 Summary:        Library for creating and modifying zip archives
 License:        BSD-3-Clause
@@ -49,7 +49,25 @@
 
 %description
 The zip-archive library provides functions for creating, modifying, and
-extracting files from zip archives.
+extracting files from zip archives. The zip archive format is documented in
+<http://www.pkware.com/documents/casestudies/APPNOTE.TXT>.
+
+Certain simplifying assumptions are made about the zip archives: in particular,
+there is no support for strong encryption, zip files that span multiple disks,
+ZIP64, OS-specific file attributes, or compression methods other than Deflate.
+However, the library should be able to read the most common zip archives, and
+the archives it produces should be readable by all standard unzip programs.
+
+Archives are built and extracted in memory, so manipulating large zip files
+will consume a lot of memory. If you work with large zip files or need features
+not supported by this library, a better choice may be
+<http://hackage.haskell.org/package/zip zip>, which uses a memory-efficient
+streaming approach. However, zip can only read and write archives inside
+instances of MonadIO, so zip-archive is a better choice if you want to
+manipulate zip archives in "pure" contexts.
+
+As an example of the use of the library, a standalone zip archiver and
+extracter is provided in the source distribution.
 
 %package devel
 Summary:        Haskell %{pkg_name} library development files

++++++ zip-archive-0.3.3.tar.gz -> zip-archive-0.4.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-archive-0.3.3/README.markdown 
new/zip-archive-0.4/README.markdown
--- old/zip-archive-0.3.3/README.markdown       2018-06-25 21:51:15.000000000 
+0200
+++ new/zip-archive-0.4/README.markdown 2018-12-04 01:24:06.000000000 +0100
@@ -1,6 +1,27 @@
 zip-archive
 ===========
 
-The zip-archive library provides functions for creating, modifying, and
-extracting files from zip archives.
+The zip-archive library provides functions for creating, modifying,
+and extracting files from zip archives.  The zip archive format
+is documented in
+<http://www.pkware.com/documents/casestudies/APPNOTE.TXT>.
 
+Certain simplifying assumptions are made about the zip archives:
+in particular, there is no support for strong encryption, zip
+files that span multiple disks, ZIP64, OS-specific file
+attributes, or compression methods other than Deflate.  However,
+the library should be able to read the most common zip archives,
+and the archives it produces should be readable by all standard
+unzip programs.
+
+Archives are built and extracted in memory, so manipulating
+large zip files will consume a lot of memory.  If you work with
+large zip files or need features not supported by this library,
+a better choice may be [zip](http://hackage.haskell.org/package/zip),
+which uses a memory-efficient streaming approach.  However, zip
+can only read and write archives inside instances of MonadIO, so
+zip-archive is a better choice if you want to manipulate zip
+archives in "pure" contexts.
+
+As an example of the use of the library, a standalone zip archiver
+and extracter is provided in the source distribution.
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-archive-0.3.3/Setup.hs 
new/zip-archive-0.4/Setup.hs
--- old/zip-archive-0.3.3/Setup.hs      2018-06-25 21:51:15.000000000 +0200
+++ new/zip-archive-0.4/Setup.hs        2018-12-04 01:24:06.000000000 +0100
@@ -1,8 +1,2 @@
 import Distribution.Simple
-import Distribution.Simple.Program
-
-main :: IO ()
-main = defaultMainWithHooks simpleUserHooks
-  { hookedPrograms = [ simpleProgram "unzip"
-                     ]
-  }
+main = defaultMain
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-archive-0.3.3/changelog 
new/zip-archive-0.4/changelog
--- old/zip-archive-0.3.3/changelog     2018-06-25 21:51:15.000000000 +0200
+++ new/zip-archive-0.4/changelog       2018-12-04 01:24:06.000000000 +0100
@@ -1,3 +1,37 @@
+zip-archive 0.4
+
+  * Implement read-only support for PKWARE encryption (Sergii Rudchenko).
+    The "traditional" PKWARE encryption is a symmetric encryption
+    algorithm described in zip format specification in section 6.1.
+    This change allows to extract basic "password-protected" entries from
+    ZIP files.  Note that the standard file extraction function
+    extractFilesFromArchive does not decrypt entries (it will raise
+    an exception if it encounters an encrypted entry). To handle
+    archives with encrypted entries, use the new function
+    fromEncryptedEntry.
+
+    API changes:
+
+    + Add eEncryptionMethod field to Entry.
+    + Add EncryptionMethod type.
+    + Add function isEncryptedEntry.
+    + Add function fromEncryptedEntry.
+    * Add CannotWriteEncryptedEntry constructor to ZipException.
+
+  * Add UnsafePath to ZipException (#50).
+  * writeEntry: raise UnsafePath exception for unsafe paths (#50).
+    This prevents malicious zip files from overwriting paths
+    above the working directory.
+  * Add Paths_zip_archive to autogen-modules.
+  * Clarify README and cabal description.
+  * Specify cabal-version: 2.0.  Otherwise we get an unknown build
+    tool error using `build-depends` without a custom Setup.hs.
+  * Change build-type to simple.  Retain 'build-tools: unzip' in
+    test stanza, though now it doesn't do anything except give a
+    hint to external tools.  If unzip is not found in the path,
+    the test suite prints a message and counts the test that
+    requires unzip as succeeding (see #51).
+
 zip-archive 0.3.3
 
   * Remove dependency on old-time (typedrat).
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-archive-0.3.3/src/Codec/Archive/Zip.hs 
new/zip-archive-0.4/src/Codec/Archive/Zip.hs
--- old/zip-archive-0.3.3/src/Codec/Archive/Zip.hs      2018-06-25 
21:51:15.000000000 +0200
+++ new/zip-archive-0.4/src/Codec/Archive/Zip.hs        2018-12-04 
01:24:06.000000000 +0100
@@ -15,7 +15,7 @@
 -- and extracting files from zip archives.
 --
 -- Certain simplifying assumptions are made about the zip archives: in
--- particular, there is no support for encryption, zip files that span
+-- particular, there is no support for strong encryption, zip files that span
 -- multiple disks, ZIP64, OS-specific file attributes, or compression
 -- methods other than Deflate.  However, the library should be able to
 -- read the most common zip archives, and the archives it produces should
@@ -35,6 +35,7 @@
          Archive (..)
        , Entry (..)
        , CompressionMethod (..)
+       , EncryptionMethod (..)
        , ZipOption (..)
        , ZipException (..)
        , emptyArchive
@@ -48,6 +49,8 @@
        , deleteEntryFromArchive
        , findEntryByPath
        , fromEntry
+       , fromEncryptedEntry
+       , isEncryptedEntry
        , toEntry
 #ifndef _WINDOWS
        , isEntrySymbolicLink
@@ -70,20 +73,21 @@
 import Data.Time.Clock ( UTCTime(..) )
 import Data.Time.Clock.POSIX ( posixSecondsToUTCTime, utcTimeToPOSIXSeconds )
 import Data.Time.LocalTime ( TimeOfDay(..), timeToTimeOfDay )
-import Data.Bits ( shiftL, shiftR, (.&.) )
+import Data.Bits ( shiftL, shiftR, (.&.), (.|.), xor, testBit )
 import Data.Binary
 import Data.Binary.Get
 import Data.Binary.Put
-import Data.List ( nub, find, intercalate, partition)
+import Data.List (nub, find, intercalate, isPrefixOf, isInfixOf)
 import Data.Data (Data)
-import Data.Maybe (fromJust)
 import Data.Typeable (Typeable)
 import Text.Printf
 import System.FilePath
-import System.Directory ( doesDirectoryExist, getDirectoryContents, 
createDirectoryIfMissing )
-import Control.Monad ( when, unless, zipWithM )
+import System.Directory
+       (doesDirectoryExist, getDirectoryContents,
+        createDirectoryIfMissing, getModificationTime, getCurrentDirectory,
+        makeAbsolute)
+import Control.Monad ( when, unless, zipWithM_ )
 import qualified Control.Exception as E
-import System.Directory ( getModificationTime )
 import System.IO ( stderr, hPutStrLn )
 import qualified Data.Digest.CRC32 as CRC32
 import qualified Data.Map as M
@@ -93,12 +97,14 @@
 #ifndef _WINDOWS
 import System.Posix.Files ( setFileTimes, setFileMode, fileMode, 
getSymbolicLinkStatus, symbolicLinkMode, readSymbolicLink, isSymbolicLink, 
unionFileModes, createSymbolicLink )
 import System.Posix.Types ( CMode(..) )
+import Data.List (partition)
+import Data.Maybe (fromJust)
 #endif
 
 -- from bytestring
 import qualified Data.ByteString as S
 import qualified Data.ByteString.Lazy as B
-import qualified Data.ByteString.Lazy.Char8 as C (pack, unpack)
+import qualified Data.ByteString.Lazy.Char8 as C
 
 -- text
 import qualified Data.Text.Lazy as TL
@@ -107,13 +113,6 @@
 -- from zlib
 import qualified Codec.Compression.Zlib.Raw as Zlib
 
-versionMadeBy :: Word16
-#ifdef _WINDOWS
-versionMadeBy = 0x0000 -- FAT/VFAT/VFAT32 file attributes
-#else
-versionMadeBy = 0x0300 -- UNIX file attributes
-#endif
-
 #if !MIN_VERSION_binary(0, 6, 0)
 manySig :: Word32 -> Get a -> Get [a]
 manySig sig p = do
@@ -145,6 +144,7 @@
 data Entry = Entry
                { eRelativePath            :: FilePath            -- ^ Relative 
path, using '/' as separator
                , eCompressionMethod       :: CompressionMethod   -- ^ 
Compression method
+               , eEncryptionMethod        :: EncryptionMethod    -- ^ 
Encryption method
                , eLastModified            :: Integer             -- ^ 
Modification time (seconds since unix epoch)
                , eCRC32                   :: Word32              -- ^ CRC32 
checksum
                , eCompressedSize          :: Word32              -- ^ 
Compressed size in bytes
@@ -162,6 +162,15 @@
                        | NoCompression
                        deriving (Read, Show, Eq)
 
+data EncryptionMethod = NoEncryption            -- ^ Entry is not encrypted
+                      | PKWAREEncryption Word8  -- ^ Entry is encrypted with 
the traditional PKWARE encryption
+                      deriving (Read, Show, Eq)
+
+-- | The way the password should be verified during entry decryption
+data PKWAREVerificationType = CheckTimeByte
+                            | CheckCRCByte
+                            deriving (Read, Show, Eq)
+
 -- | Options for 'addFilesToArchive' and 'extractFilesFromArchive'.
 data ZipOption = OptRecursive               -- ^ Recurse into directories when 
adding files
                | OptVerbose                 -- ^ Print information to stderr
@@ -171,8 +180,10 @@
                deriving (Read, Show, Eq)
 
 data ZipException =
-  CRC32Mismatch FilePath
-  deriving (Show, Typeable, Data)
+    CRC32Mismatch FilePath
+  | UnsafePath FilePath
+  | CannotWriteEncryptedEntry FilePath
+  deriving (Show, Typeable, Data, Eq)
 
 instance E.Exception ZipException
 
@@ -207,7 +218,7 @@
 
 -- | Returns a list of files in a zip archive.
 filesInArchive :: Archive -> [FilePath]
-filesInArchive = (map eRelativePath) . zEntries
+filesInArchive = map eRelativePath . zEntries
 
 -- | Adds an entry to a zip archive, or updates an existing entry.
 addEntryToArchive :: Entry -> Archive -> Archive
@@ -232,6 +243,18 @@
 fromEntry entry =
   decompressData (eCompressionMethod entry) (eCompressedData entry)
 
+-- | Returns decrypted and uncompressed contents of zip entry.
+fromEncryptedEntry :: String -> Entry -> Maybe B.ByteString
+fromEncryptedEntry password entry =
+  decompressData (eCompressionMethod entry) <$> decryptData password 
(eEncryptionMethod entry) (eCompressedData entry)
+
+-- | Check if an 'Entry' is encrypted
+isEncryptedEntry :: Entry -> Bool
+isEncryptedEntry entry =
+  case eEncryptionMethod entry of
+    (PKWAREEncryption _) -> True
+    _ -> False
+
 -- | Create an 'Entry' with specified file path, modification time, and 
contents.
 toEntry :: FilePath         -- ^ File path for entry
         -> Integer          -- ^ Modification time for entry (seconds since 
unix epoch)
@@ -249,6 +272,7 @@
       crc32 = CRC32.crc32 contents
   in  Entry { eRelativePath            = normalizePath path
             , eCompressionMethod       = compressionMethod
+            , eEncryptionMethod        = NoEncryption
             , eLastModified            = modtime
             , eCRC32                   = crc32
             , eCompressedSize          = fromIntegral finalSize
@@ -293,13 +317,12 @@
                         return B.empty
                       else
                         B.fromStrict <$> S.readFile path
-  modEpochTime <- fmap (floor . utcTimeToPOSIXSeconds)
-                   $ getModificationTime path
+  modEpochTime <- (floor . utcTimeToPOSIXSeconds) <$> getModificationTime path
   let entry = toEntry path' modEpochTime contents
 
   entryE <-
 #ifdef _WINDOWS
-        return $ entry
+        return $ entry { eVersionMadeBy = 0x0000 } -- FAT/VFAT/VFAT32 file 
attributes
 #else
         do
            let fm = if isSymLink
@@ -308,7 +331,7 @@
 
            let modes = fromIntegral $ shiftL (toInteger fm) 16
            return $ entry { eExternalFileAttributes = modes,
-                            eVersionMadeBy = versionMadeBy }
+                            eVersionMadeBy = 0x0300 } -- UNIX file attributes
 #endif
 
   when (OptVerbose `elem` opts) $ do
@@ -325,9 +348,16 @@
 -- does not match the uncompressed data.
 writeEntry :: [ZipOption] -> Entry -> IO ()
 writeEntry opts entry = do
+  when (isEncryptedEntry entry) $
+    E.throwIO $ CannotWriteEncryptedEntry (eRelativePath entry)
   let path = case [d | OptDestination d <- opts] of
                   (x:_) -> x </> eRelativePath entry
                   _     -> eRelativePath entry
+  absPath <- makeAbsolute path
+  curDir <- getCurrentDirectory
+  let isUnsafePath = ".." `isInfixOf` absPath ||
+                     not (curDir `isPrefixOf` absPath)
+  when isUnsafePath $ E.throwIO $ UnsafePath path
   -- create directories if needed
   let dir = takeDirectory path
   exists <- doesDirectoryExist dir
@@ -335,10 +365,10 @@
     createDirectoryIfMissing True dir
     when (OptVerbose `elem` opts) $
       hPutStrLn stderr $ "  creating: " ++ dir
-  if length path > 0 && last path == '/' -- path is a directory
+  if not (null path) && last path == '/' -- path is a directory
      then return ()
      else do
-       when (OptVerbose `elem` opts) $ do
+       when (OptVerbose `elem` opts) $
          hPutStrLn stderr $ case eCompressionMethod entry of
                                  Deflate       -> " inflating: " ++ path
                                  NoCompression -> "extracting: " ++ path
@@ -361,11 +391,11 @@
 -- the options do not contain 'OptPreserveSymbolicLinks`, this
 -- function behaves like `writeEntry`.
 writeSymbolicLinkEntry :: [ZipOption] -> Entry -> IO ()
-writeSymbolicLinkEntry opts entry = do
+writeSymbolicLinkEntry opts entry =
   if OptPreserveSymbolicLinks `notElem` opts
      then writeEntry opts entry
      else do
-        if (isEntrySymbolicLink entry)
+        if isEntrySymbolicLink entry
            then do
              let prefixPath = case [d | OptDestination d <- opts] of
                                    (x:_) -> x
@@ -403,7 +433,7 @@
 #ifdef _WINDOWS
                          then mapM getDirectoryContentsRecursive files >>= 
return . nub . concat
 #else
-                         then mapM (getDirectoryContentsRecursive' opts) files 
>>= return . nub . concat
+                         then nub . concat <$> mapM 
(getDirectoryContentsRecursive' opts) files
 #endif
                          else return files
   entries <- mapM (readEntry opts) filesAndChildren
@@ -413,18 +443,20 @@
 -- as needed.  If 'OptVerbose' is specified, print messages to stderr.
 -- Note that the last-modified time is set correctly only in POSIX,
 -- not in Windows.
+-- This function fails if encrypted entries are present
 extractFilesFromArchive :: [ZipOption] -> Archive -> IO ()
 extractFilesFromArchive opts archive = do
+  let entries = zEntries archive
   if OptPreserveSymbolicLinks `elem` opts
     then do
 #ifdef _WINDOWS
-      mapM_ (writeEntry opts) $ zEntries archive
+      mapM_ (writeEntry opts) entries
 #else
-      let (symbolicLinkEntries, nonSymbolicLinkEntries) = partition 
isEntrySymbolicLink $ zEntries archive
-      mapM_ (writeEntry opts) $ nonSymbolicLinkEntries
-      mapM_ (writeSymbolicLinkEntry opts) $ symbolicLinkEntries
+      let (symbolicLinkEntries, nonSymbolicLinkEntries) = partition 
isEntrySymbolicLink entries
+      mapM_ (writeEntry opts) nonSymbolicLinkEntries
+      mapM_ (writeSymbolicLinkEntry opts) symbolicLinkEntries
 #endif
-    else mapM_ (writeEntry opts) $ zEntries archive
+    else mapM_ (writeEntry opts) entries
 
 
--------------------------------------------------------------------------------
 -- Internal functions for reading and writing zip binary format.
@@ -453,6 +485,39 @@
 decompressData Deflate       = Zlib.decompress
 decompressData NoCompression = id
 
+-- | Decrypt a lazy bytestring
+-- Returns Nothing if password is incorrect
+decryptData :: String -> EncryptionMethod -> B.ByteString -> Maybe B.ByteString
+decryptData _ NoEncryption s = Just s
+decryptData password (PKWAREEncryption controlByte) s =
+  let headerlen = 12
+      initKeys = (305419896, 591751049, 878082192)
+      startKeys = B.foldl pkwareUpdateKeys initKeys (C.pack password)
+      (header, content) = B.splitAt headerlen $ snd $ B.mapAccumL 
pkwareDecryptByte startKeys s
+  in if B.last header == controlByte
+        then Just content
+        else Nothing
+
+-- | PKWARE decryption context
+type DecryptionCtx = (Word32, Word32, Word32)
+
+-- | An interation of the PKWARE decryption algorithm
+pkwareDecryptByte :: DecryptionCtx -> Word8 -> (DecryptionCtx, Word8)
+pkwareDecryptByte keys@(_, _, key2) inB =
+  let tmp = key2 .|. 2
+      tmp' = fromIntegral ((tmp * (tmp `xor` 1)) `shiftR` 8) :: Word8
+      outB = inB `xor` tmp'
+  in (pkwareUpdateKeys keys outB, outB)
+
+-- | Update decryption keys after a decrypted byte
+pkwareUpdateKeys :: DecryptionCtx -> Word8 -> DecryptionCtx
+pkwareUpdateKeys (key0, key1, key2) inB =
+  let key0' = CRC32.crc32Update (key0 `xor` 0xffffffff) [inB] `xor` 0xffffffff
+      key1' = (key1 + (key0' .&. 0xff)) * 134775813 + 1
+      key1Byte = fromIntegral (key1' `shiftR` 24) :: Word8
+      key2' = CRC32.crc32Update (key2 `xor` 0xffffffff) [key1Byte] `xor` 
0xffffffff
+  in (key0', key1', key2')
+
 -- | Calculate compression ratio for an entry (for verbose output).
 compressionRatio :: Entry -> Float
 compressionRatio entry =
@@ -482,10 +547,10 @@
   epochTimeToMSDOSDateTime minMSDOSDateTime
   -- if time is earlier than minimum DOS datetime, return minimum
 epochTimeToMSDOSDateTime epochtime =
-  let 
+  let
     UTCTime
       (toGregorian -> (fromInteger -> year, month, day))
-      (timeToTimeOfDay -> (TimeOfDay hour minutes (floor -> sec))) 
+      (timeToTimeOfDay -> (TimeOfDay hour minutes (floor -> sec)))
       = posixSecondsToUTCTime (fromIntegral epochtime)
 
     dosTime = toEnum $ (sec `div` 2) + shiftL minutes 5 + shiftL hour 11
@@ -494,19 +559,19 @@
 
 -- | Convert a MSDOS datetime to a 'ClockTime'.
 msDOSDateTimeToEpochTime :: MSDOSDateTime -> Integer
-msDOSDateTimeToEpochTime (MSDOSDateTime {msDOSDate = dosDate, msDOSTime = 
dosTime}) =
+msDOSDateTimeToEpochTime MSDOSDateTime {msDOSDate = dosDate, msDOSTime = 
dosTime} =
   let seconds = fromIntegral $ 2 * (dosTime .&. 0O37)
-      minutes = fromIntegral $ (shiftR dosTime 5) .&. 0O77
+      minutes = fromIntegral $ shiftR dosTime 5 .&. 0O77
       hour    = fromIntegral $ shiftR dosTime 11
       day     = fromIntegral $ dosDate .&. 0O37
-      month   = fromIntegral $ ((shiftR dosDate 5) .&. 0O17)
+      month   = fromIntegral ((shiftR dosDate 5) .&. 0O17)
       year    = fromIntegral $ shiftR dosDate 9
       utc = UTCTime (fromGregorian (1980 + year) month day) (3600 * hour + 60 
* minutes + seconds)
   in floor (utcTimeToPOSIXSeconds utc)
 
 #ifndef _WINDOWS
 getDirectoryContentsRecursive' :: [ZipOption] -> FilePath -> IO [FilePath]
-getDirectoryContentsRecursive' opts path = do
+getDirectoryContentsRecursive' opts path =
   if OptPreserveSymbolicLinks `elem` opts
      then do
        isDir <- doesDirectoryExist path
@@ -538,10 +603,10 @@
 
 
 setFileTimeStamp :: FilePath -> Integer -> IO ()
-setFileTimeStamp file epochtime = do
 #ifdef _WINDOWS
-  return ()  -- TODO - figure out how to set the timestamp on Windows
+setFileTimeStamp _ _ = return () -- TODO: figure out how to set the timestamp 
on Windows
 #else
+setFileTimeStamp file epochtime = do
   let epochtime' = fromInteger epochtime
   setFileTimes file epochtime' epochtime'
 #endif
@@ -615,7 +680,7 @@
   skip 4 -- offset of central directory
   commentLength <- getWord16le
   zipComment <- getLazyByteString (toEnum $ fromEnum commentLength)
-  return $ Archive
+  return Archive
            { zEntries                = files
            , zSignature              = digSig
            , zComment                = zipComment
@@ -627,7 +692,7 @@
   let localFileSizes = map localFileSize $ zEntries archive
   let offsets = scanl (+) 0 localFileSizes
   let cdOffset = last offsets
-  _ <- zipWithM putFileHeader offsets (zEntries archive)
+  _ <- zipWithM_ putFileHeader offsets (zEntries archive)
   putDigitalSignature $ zSignature archive
   putWord32le 0x06054b50
   putWord16le 0 -- disk number
@@ -705,7 +770,7 @@
               cs <- getWord32le  -- compressed size
               skip 4 -- uncompressed size
               if fromIntegral cs == B.length raw
-                 then return $ raw
+                 then return raw
                  else fail "Content size mismatch in data descriptor record"
   return (fromIntegral offset, compressedData)
 
@@ -824,7 +889,7 @@
   skip 1 -- upper byte indicates OS part of "version needed to extract"
   unless (versionNeededToExtract <= 20) $
     fail "This archive requires zip >= 2.0 to extract."
-  skip 2 -- general purpose bit flag
+  bitflag <- getWord16le
   rawCompressionMethod <- getWord16le
   compressionMethod <- case rawCompressionMethod of
                         0 -> return NoCompression
@@ -833,6 +898,12 @@
   lastModFileTime <- getWord16le
   lastModFileDate <- getWord16le
   crc32 <- getWord32le
+  encryptionMethod <- case (testBit bitflag 0, testBit bitflag 3, testBit 
bitflag 6) of
+                        (False, _, _) -> return NoEncryption
+                        (True, False, False) -> return $ PKWAREEncryption 
(fromIntegral (crc32 `shiftR` 24))
+                        (True, True, False) -> return $ PKWAREEncryption 
(fromIntegral (lastModFileTime `shiftR` 8))
+                        (True, _, True) -> fail "Strong encryption is not 
supported"
+
   compressedSize <- getWord32le
   uncompressedSize <- getWord32le
   fileNameLength <- getWord16le
@@ -845,13 +916,14 @@
   fileName <- getLazyByteString (toEnum $ fromEnum fileNameLength)
   extraField <- getLazyByteString (toEnum $ fromEnum extraFieldLength)
   fileComment <- getLazyByteString (toEnum $ fromEnum fileCommentLength)
-  compressedData <- case (M.lookup relativeOffset locals) of
+  compressedData <- case M.lookup relativeOffset locals of
                     Just x  -> return x
                     Nothing -> fail $ "Unable to find data at offset " ++
                                         show relativeOffset
-  return $ Entry
+  return Entry
             { eRelativePath            = toString fileName
             , eCompressionMethod       = compressionMethod
+            , eEncryptionMethod        = encryptionMethod
             , eLastModified            = msDOSDateTimeToEpochTime $
                                          MSDOSDateTime { msDOSDate = 
lastModFileDate,
                                                          msDOSTime = 
lastModFileTime }
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-archive-0.3.3/tests/test-zip-archive.hs 
new/zip-archive-0.4/tests/test-zip-archive.hs
--- old/zip-archive-0.3.3/tests/test-zip-archive.hs     2018-06-25 
21:51:15.000000000 +0200
+++ new/zip-archive-0.4/tests/test-zip-archive.hs       2018-12-04 
01:24:06.000000000 +0100
@@ -5,11 +5,14 @@
 
 import Codec.Archive.Zip
 import Control.Applicative
+import Control.Monad (unless)
+import Control.Exception (try)
 import System.Directory hiding (isSymbolicLink)
 import Test.HUnit.Base
 import Test.HUnit.Text
 import qualified Data.ByteString.Char8 as BS
 import qualified Data.ByteString.Lazy as BL
+import qualified Data.ByteString.Lazy.Char8 as BLC
 import System.Exit
 import System.IO.Temp (withTempDirectory)
 
@@ -48,7 +51,13 @@
 
 main :: IO Counts
 main = withTempDirectory "." "test-zip-archive." $ \tmpDir -> do
-  res   <- runTestTT $ TestList $ map (\f -> f tmpDir)
+#ifndef _WINDOWS
+  ec <- rawSystem "which" ["unzip"]
+  let unzipInPath = ec == ExitSuccess
+  unless unzipInPath $
+    putStrLn "\n\nunzip is not in path; skipping testArchiveAndUnzip\n"
+#endif
+  res   <- runTestTT $ TestList $ map (\f -> f tmpDir) $
                                 [ testReadWriteArchive
                                 , testReadExternalZip
                                 , testFromToArchive
@@ -56,13 +65,19 @@
                                 , testAddFilesOptions
                                 , testDeleteEntries
                                 , testExtractFiles
+                                , testExtractFilesFailOnEncrypted
+                                , testPasswordProtectedRead
+                                , testIncorrectPasswordRead
+                                , testEvilPath
 #ifndef _WINDOWS
                                 , testExtractFilesWithPosixAttrs
                                 , testArchiveExtractSymlinks
                                 , testExtractExternalZipWithSymlinks
-                                , testArchiveAndUnzip
 #endif
                                 ]
+#ifndef _WINDOWS
+                                ++ [testArchiveAndUnzip | unzipInPath]
+#endif
   exitWith $ case (failures res + errors res) of
                      0 -> ExitSuccess
                      n -> ExitFailure n
@@ -85,7 +100,10 @@
   bContents <- BL.readFile "tests/test4/b.bin"
   case findEntryByPath "test4/b.bin" archive of
        Nothing  -> assertFailure "test4/b.bin not found in archive"
-       Just f   -> assertEqual "for contents of test4/b.bin in archive"
+       Just f   -> do
+                    assertEqual "for text4/b.bin file entry"
+                      NoEncryption (eEncryptionMethod f)
+                    assertEqual "for contents of test4/b.bin in archive"
                       bContents (fromEntry f)
   case findEntryByPath "test4/" archive of
        Nothing  -> assertFailure "test4/ not found in archive"
@@ -136,6 +154,14 @@
   let archive3 = deleteEntryFromArchive "src" archive2
   assertEqual "for deleteFilesFromArchive" emptyArchive archive3
 
+testEvilPath :: FilePath -> Test
+testEvilPath _tmpDir = TestCase $ do
+  archive <- toArchive <$> BL.readFile "tests/zip_with_evil_path.zip"
+  result <- try $ extractFilesFromArchive [] archive :: IO (Either 
ZipException ())
+  case result of
+    Left err -> assertBool "Wrong exception" $ err == UnsafePath "../evil"
+    Right _ -> assertFailure "extractFilesFromArchive should have failed"
+
 testExtractFiles :: FilePath -> Test
 testExtractFiles tmpDir = TestCase $ do
   createDirectory (tmpDir </> "dir1")
@@ -152,6 +178,41 @@
   assertEqual ("contents of " </> tmpDir </> "dir1/hi") hiMsg hi
   assertEqual ("contents of " </> tmpDir </> "dir1/dir2/hello") helloMsg hello
 
+testExtractFilesFailOnEncrypted :: FilePath -> Test
+testExtractFilesFailOnEncrypted tmpDir = TestCase $ do
+  let dir = tmpDir </> "fail-encrypted"
+  createDirectory dir
+
+  archive <- toArchive <$> BL.readFile "tests/zip_with_password.zip"
+  result <- try $ extractFilesFromArchive [OptDestination dir] archive :: IO 
(Either ZipException ())
+  removeDirectoryRecursive dir
+
+  case result of
+    Left err -> assertBool "Wrong exception" $ err == 
CannotWriteEncryptedEntry "test.txt"
+    Right _ -> assertFailure "extractFilesFromArchive should have failed"
+
+testPasswordProtectedRead :: FilePath -> Test
+testPasswordProtectedRead _tmpDir = TestCase $ do
+  archive <- toArchive <$> BL.readFile "tests/zip_with_password.zip"
+
+  assertEqual "for results of filesInArchive" ["test.txt"] (filesInArchive 
archive)
+  case findEntryByPath "test.txt" archive of
+       Nothing  -> assertFailure "test.txt not found in archive"
+       Just f   -> do
+            assertBool "for encrypted test.txt file entry"
+              (isEncryptedEntry f)
+            assertEqual "for contents of test.txt in archive"
+              (Just $ BLC.pack "SUCCESS\n") (fromEncryptedEntry "s3cr3t" f)
+
+testIncorrectPasswordRead :: FilePath -> Test
+testIncorrectPasswordRead _tmpDir = TestCase $ do
+  archive <- toArchive <$> BL.readFile "tests/zip_with_password.zip"
+  case findEntryByPath "test.txt" archive of
+       Nothing  -> assertFailure "test.txt not found in archive"
+       Just f   -> do
+            assertEqual "for contents of test.txt in archive"
+              Nothing (fromEncryptedEntry "INCORRECT" f)
+
 #ifndef _WINDOWS
 
 testExtractFilesWithPosixAttrs :: FilePath -> Test
Binary files old/zip-archive-0.3.3/tests/zip_with_evil_path.zip and 
new/zip-archive-0.4/tests/zip_with_evil_path.zip differ
Binary files old/zip-archive-0.3.3/tests/zip_with_password.zip and 
new/zip-archive-0.4/tests/zip_with_password.zip differ
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-archive-0.3.3/zip-archive.cabal 
new/zip-archive-0.4/zip-archive.cabal
--- old/zip-archive-0.3.3/zip-archive.cabal     2018-06-25 21:51:15.000000000 
+0200
+++ new/zip-archive-0.4/zip-archive.cabal       2018-12-04 01:24:06.000000000 
+0100
@@ -1,12 +1,33 @@
 Name:                zip-archive
-Version:             0.3.3
-Cabal-Version:       >= 1.10
-Build-type:          Custom
+Version:             0.4
+Cabal-Version:       2.0
+Build-type:          Simple
 Synopsis:            Library for creating and modifying zip archives.
-Description:         The zip-archive library provides functions for creating, 
modifying,
-                     and extracting files from zip archives.
+Description:
+   The zip-archive library provides functions for creating, modifying, and
+   extracting files from zip archives. The zip archive format is
+   documented in <http://www.pkware.com/documents/casestudies/APPNOTE.TXT>.
+   .
+   Certain simplifying assumptions are made about the zip archives: in
+   particular, there is no support for strong encryption, zip files that
+   span multiple disks, ZIP64, OS-specific file attributes, or compression
+   methods other than Deflate. However, the library should be able to read
+   the most common zip archives, and the archives it produces should be
+   readable by all standard unzip programs.
+   .
+   Archives are built and extracted in memory, so manipulating large zip
+   files will consume a lot of memory. If you work with large zip files or
+   need features not supported by this library, a better choice may be
+   <http://hackage.haskell.org/package/zip zip>, which uses a
+   memory-efficient streaming approach. However, zip can only read and
+   write archives inside instances of MonadIO, so zip-archive is a better
+   choice if you want to manipulate zip archives in "pure" contexts.
+   .
+   As an example of the use of the library, a standalone zip archiver and
+   extracter is provided in the source distribution.
 Category:            Codec
-Tested-with:         GHC == 7.8.2, GHC == 7.10.3, GHC == 8.0.2, GHC == 8.2.2
+Tested-with:         GHC == 7.8.2, GHC == 7.10.3, GHC == 8.0.2,
+                     GHC == 8.2.2, GHC == 8.4.3, GHC == 8.6.1
 License:             BSD3
 License-file:        LICENSE
 Homepage:            http://github.com/jgm/zip-archive
@@ -19,6 +40,8 @@
                      tests/test4/b.bin
                      "tests/test4/c/with spaces.txt"
                      tests/zip_with_symlinks.zip
+                     tests/zip_with_password.zip
+                     tests/zip_with_evil_path.zip
 
 Source-repository    head
   type:              git
@@ -51,9 +74,6 @@
   else
     Build-depends:   unix
 
-custom-setup
-  setup-depends: base, Cabal
-
 Executable zip-archive
   if flag(executable)
     Buildable:       True
@@ -66,6 +86,7 @@
                      bytestring >= 0.9.0,
                      zip-archive
   Other-Modules:     Paths_zip_archive
+  Autogen-Modules:   Paths_zip_archive
   Ghc-Options:       -Wall
   Default-Language:  Haskell98
 
@@ -81,5 +102,5 @@
   if os(windows)
     cpp-options:     -D_WINDOWS
   else
-    Build-tools:     unzip
     Build-depends:   unix
+  build-tools: unzip


Reply via email to