Script 'mail_helper' called by obssrc
Hello community,

here is the log from the commit of package ghc-zip for openSUSE:Factory checked 
in at 2021-06-14 23:11:00
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-zip (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-zip.new.32437 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-zip"

Mon Jun 14 23:11:00 2021 rev:4 rq:899832 version:1.7.1

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-zip/ghc-zip.changes  2021-02-16 
22:48:48.766573921 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-zip.new.32437/ghc-zip.changes       
2021-06-14 23:11:30.788796830 +0200
@@ -1,0 +2,8 @@
+Sun Jun  6 19:03:07 UTC 2021 - psim...@suse.com
+
+- Update zip to version 1.7.1.
+  ## Zip 1.7.1
+
+  * Fixed compilation with zstd and/or bzip2 disabled.
+
+-------------------------------------------------------------------

Old:
----
  zip-1.7.0.tar.gz

New:
----
  zip-1.7.1.tar.gz

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

Other differences:
------------------
++++++ ghc-zip.spec ++++++
--- /var/tmp/diff_new_pack.j3bJ18/_old  2021-06-14 23:11:31.156797495 +0200
+++ /var/tmp/diff_new_pack.j3bJ18/_new  2021-06-14 23:11:31.160797502 +0200
@@ -19,7 +19,7 @@
 %global pkg_name zip
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        1.7.0
+Version:        1.7.1
 Release:        0
 Summary:        Operations on zip archives
 License:        BSD-3-Clause

++++++ zip-1.7.0.tar.gz -> zip-1.7.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/CHANGELOG.md new/zip-1.7.1/CHANGELOG.md
--- old/zip-1.7.0/CHANGELOG.md  2001-09-09 03:46:40.000000000 +0200
+++ new/zip-1.7.1/CHANGELOG.md  2001-09-09 03:46:40.000000000 +0200
@@ -1,3 +1,7 @@
+## Zip 1.7.1
+
+* Fixed compilation with zstd and/or bzip2 disabled.
+
 ## Zip 1.7.0
 
 * Set user permissions on linux platform as follows: if an existing file is
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/Codec/Archive/Zip/Internal.hs 
new/zip-1.7.1/Codec/Archive/Zip/Internal.hs
--- old/zip-1.7.0/Codec/Archive/Zip/Internal.hs 2001-09-09 03:46:40.000000000 
+0200
+++ new/zip-1.7.1/Codec/Archive/Zip/Internal.hs 2001-09-09 03:46:40.000000000 
+0200
@@ -12,7 +12,7 @@
 -- Stability   :  experimental
 -- Portability :  portable
 --
--- Low-level, non-public concepts and operations.
+-- Low-level, non-public types and operations.
 module Codec.Archive.Zip.Internal
   ( PendingAction (..),
     targetEntry,
@@ -80,47 +80,47 @@
 ----------------------------------------------------------------------------
 -- Data types
 
--- | The sum type describes all possible actions that can be performed on
+-- | The sum type describes all possible actions that can be performed on an
 -- archive.
 data PendingAction
-  = -- | Add entry given its 'Source'
+  = -- | Add an entry given its 'Source'
     SinkEntry
       CompressionMethod
       (ConduitT () ByteString (ResourceT IO) ())
       EntrySelector
   | -- | Copy an entry form another archive without re-compression
     CopyEntry FilePath EntrySelector EntrySelector
-  | -- | Change name the entry inside archive
+  | -- | Change the name of the entry inside archive
     RenameEntry EntrySelector EntrySelector
-  | -- | Delete entry from archive
+  | -- | Delete an entry from archive
     DeleteEntry EntrySelector
-  | -- | Change compression method on an entry
+  | -- | Change the compression method on an entry
     Recompress CompressionMethod EntrySelector
-  | -- | Set comment for a particular entry
+  | -- | Set the comment for a particular entry
     SetEntryComment Text EntrySelector
-  | -- | Delete comment of particular entry
+  | -- | Delete theh comment of a particular entry
     DeleteEntryComment EntrySelector
-  | -- | Set modification time of particular entry
+  | -- | Set the modification time of a particular entry
     SetModTime UTCTime EntrySelector
-  | -- | Add an extra field to specified entry
+  | -- | Add an extra field to the specified entry
     AddExtraField Word16 ByteString EntrySelector
-  | -- | Delete an extra filed of specified entry
+  | -- | Delete an extra filed of the specified entry
     DeleteExtraField Word16 EntrySelector
-  | -- | Set comment for entire archive
+  | -- | Set the comment for the entire archive
     SetArchiveComment Text
-  | -- | Delete comment of entire archive
+  | -- | Delete the comment of the entire archive
     DeleteArchiveComment
-  | -- | Set an external file attribute for specified entry
+  | -- | Set an external file attribute for the specified entry
     SetExternalFileAttributes Word32 EntrySelector
 
--- | Collection of maps describing how to produce entries in resulting
+-- | A collection of maps describing how to produce entries in the resulting
 -- archive.
 data ProducingActions = ProducingActions
   { paCopyEntry :: Map FilePath (Map EntrySelector EntrySelector),
     paSinkEntry :: Map EntrySelector (ConduitT () ByteString (ResourceT IO) ())
   }
 
--- | Collection of editing actions, that is, actions that modify already
+-- | A collection of editing actions, that is, actions that modify already
 -- existing entries.
 data EditingActions = EditingActions
   { eaCompression :: Map EntrySelector CompressionMethod,
@@ -132,18 +132,18 @@
     eaExtFileAttr :: Map EntrySelector Word32
   }
 
--- | Origin of entries that can be streamed into archive.
+-- | The origin of entries that can be streamed into archive.
 data EntryOrigin
   = GenericOrigin
   | Borrowed EntryDescription
 
--- | Type of file header: local or central directory.
+-- | The type of the file header: local or central directory.
 data HeaderType
   = LocalHeader
   | CentralDirHeader
   deriving (Eq)
 
--- | Data descriptor representation.
+-- | The data descriptor representation.
 data DataDescriptor = DataDescriptor
   { ddCRC32 :: Word32,
     ddCompressedSize :: Natural,
@@ -226,9 +226,9 @@
     Nothing ->
       throwM (ParsingFailed path "Cannot locate end of central directory")
 
--- | Given location of archive and information about specific archive entry
--- 'EntryDescription', return 'Source' of its data. Actual data can be
--- compressed or uncompressed depending on the third argument.
+-- | Given location of the archive and information about a specific archive
+-- entry 'EntryDescription', return 'Source' of its data. The actual data
+-- can be compressed or uncompressed depending on the third argument.
 sourceEntry ::
   (PrimMonad m, MonadThrow m, MonadResource m) =>
   -- | Path to archive that contains the entry
@@ -257,8 +257,9 @@
         else C.awaitForever C.yield
 
 -- | Undertake /all/ actions specified as the fourth argument of the
--- function. This transforms given pending actions so they can be performed
--- in one pass, and then they are performed in the most efficient way.
+-- function. This transforms the given pending actions so they can be
+-- performed in one pass, and then they are applied in the most efficient
+-- way.
 commit ::
   -- | Location of archive file to edit or create
   FilePath ->
@@ -291,8 +292,8 @@
           )
     writeCD h comment (copiedCD `M.union` sunkCD)
 
--- | Create a new file with the guarantee that in case of exception the old
--- file will be preserved intact. The file is only updated\/replaced if the
+-- | Create a new file with the guarantee that in the case of an exception
+-- the old file will be intact. The file is only updated\/replaced if the
 -- second argument finishes without exceptions.
 withNewFile ::
   -- | Name of file to create
@@ -309,9 +310,10 @@
     allocate = openBinaryTempFile (takeDirectory fpath) ".zip"
     release (path, h) = do
       hClose h
-      -- Despite using `bracketOnError` the file is not guaranteed to exist 
here
-      -- since we could be interrupted with an async exception after the file 
has
-      -- been renamed. Therefore, we silentely ignore `DoesNotExistError`.
+      -- Despite using `bracketOnError` the file is not guaranteed to exist
+      -- here since we could be interrupted with an async exception after
+      -- the file has been renamed. Therefore, we silentely ignore
+      -- `DoesNotExistError`.
       catchJust (guard . isDoesNotExistError) (removeFile path) (const $ pure 
())
 
 -- | Determine what comment in new archive will look like given its original
@@ -445,8 +447,8 @@
     er _ Nothing = Nothing
 
 -- | Copy entries from another archive and write them into the file
--- associated with given handle. This can throw 'EntryDoesNotExist' if there
--- is no such entry in that archive.
+-- associated with the given handle. This can throw 'EntryDoesNotExist' if
+-- there is no such entry in that archive.
 copyEntries ::
   -- | Opened 'Handle' of zip archive file
   Handle ->
@@ -472,20 +474,20 @@
           e
   return (M.fromList done)
 
--- | Sink entry from given stream into the file associated with given
--- 'Handle'.
+-- | Sink an entry from the given stream into the file associated with the
+-- given 'Handle'.
 sinkEntry ::
   -- | Opened 'Handle' of zip archive file
   Handle ->
-  -- | Name of entry to add
+  -- | Name of the entry to add
   EntrySelector ->
-  -- | Origin of entry (can contain additional info)
+  -- | Origin of the entry (can contain additional info)
   EntryOrigin ->
-  -- | Source of entry contents
+  -- | Source of the entry contents
   ConduitT () ByteString (ResourceT IO) () ->
   -- | Additional info that can influence result
   EditingActions ->
-  -- | Info to generate central directory file headers later
+  -- | Info to generate the central directory file headers later
   IO (EntrySelector, EntryDescription)
 sinkEntry h s o src EditingActions {..} = do
   currentTime <- getCurrentTime
@@ -561,9 +563,9 @@
   hSeek h AbsoluteSeek afterStreaming
   return (s, desc2)
 
--- | Create 'Sink' to stream data there. Once streaming is finished, return
--- 'DataDescriptor' for the streamed data. The action /does not/ close given
--- 'Handle'.
+-- | Create a 'Sink' to stream data there. Once streaming is finished,
+-- return 'DataDescriptor' for the streamed data. The action /does not/
+-- close the given 'Handle'.
 sinkData ::
   -- | Opened 'Handle' of zip archive file
   Handle ->
@@ -610,14 +612,14 @@
         ddUncompressedSize = uncompressedSize
       }
 
--- | Append central directory entries and end of central directory record to
--- the file that given 'Handle' is associated with. Note that this
+-- | Append central directory entries and the end of central directory
+-- record to the file that given 'Handle' is associated with. Note that this
 -- automatically writes Zip64 end of central directory record and Zip64 end
 -- of central directory locator when necessary.
 writeCD ::
   -- | Opened handle of zip archive file
   Handle ->
-  -- | Commentary to entire archive
+  -- | Commentary to the entire archive
   Maybe Text ->
   -- | Info about already written local headers and entry data
   Map EntrySelector EntryDescription ->
@@ -641,8 +643,8 @@
 ----------------------------------------------------------------------------
 -- Binary serialization
 
--- | Extract the number of bytes between start of file name in local header
--- and start of actual data.
+-- | Extract the number of bytes between the start of file name in local
+-- header and the start of actual data.
 getLocalHeaderGap :: Get Integer
 getLocalHeaderGap = do
   getSignature 0x04034b50
@@ -658,7 +660,7 @@
   extraFieldSize <- fromIntegral <$> getWord16le -- extra field length
   return (fileNameSize + extraFieldSize)
 
--- | Parse central directory file headers and put them into 'Map'.
+-- | Parse central directory file headers and put them into a 'Map'.
 getCD :: Get (Map EntrySelector EntryDescription)
 getCD = M.fromList . catMaybes <$> many getCDHeader
 
@@ -737,7 +739,7 @@
   body <- getBytes (fromIntegral size) -- content
   return (header, body)
 
--- | Get signature. If the extracted data is not equal to provided
+-- | Get signature. If the extracted data is not equal to the provided
 -- signature, fail.
 getSignature :: Word32 -> Get ()
 getSignature sig = do
@@ -788,13 +790,13 @@
   putWord16le (fromIntegral $ B.length b)
   putByteString b
 
--- | Create 'ByteString' representing entire central directory.
+-- | Create 'ByteString' representing the entire central directory.
 putCD :: Map EntrySelector EntryDescription -> Put
 putCD m = forM_ (M.keys m) $ \s ->
   putHeader CentralDirHeader s (m ! s)
 
--- | Create 'ByteString' representing local file header if the first
--- argument is 'False' and central directory file header otherwise.
+-- | Create 'ByteString' representing a local file header if the first
+-- argument is 'False' and a central directory file header otherwise.
 putHeader ::
   -- | Type of header to generate
   HeaderType ->
@@ -870,7 +872,7 @@
   putWord64le (fromIntegral cdSize) -- size of the central directory
   putWord64le (fromIntegral cdOffset) -- offset of central directory
 
--- | Create 'ByteString' representing Zip64 end of central directory
+-- | Create 'ByteString' representing Zip64 end of the central directory
 -- locator.
 putZip64ECDLocator ::
   -- | Offset of Zip64 end of central directory
@@ -884,8 +886,8 @@
   -- of central directory record
   putWord32le 1 -- total number of disks
 
--- | Parse end of central directory record or Zip64 end of central directory
--- record depending on signature binary data begins with.
+-- | Parse end of the central directory record or Zip64 end of the central
+-- directory record depending on signature binary data begins with.
 getECD :: Get ArchiveDescription
 getECD = do
   sig <- getWord32le -- end of central directory signature
@@ -926,7 +928,7 @@
         adCDSize = fromIntegral cdSize
       }
 
--- | Create 'ByteString' representing end of central directory record.
+-- | Create a 'ByteString' representing the end of central directory record.
 putECD ::
   -- | Total number of entries
   Natural ->
@@ -950,8 +952,8 @@
   putWord16le (fromIntegral $ B.length comment)
   putByteString comment
 
--- | Find absolute offset of end of central directory record or, if present,
--- Zip64 end of central directory record.
+-- | Find the absolute offset of the end of central directory record or, if
+-- present, Zip64 end of central directory record.
 locateECD :: FilePath -> Handle -> IO (Maybe Integer)
 locateECD path h = sizeCheck
   where
@@ -1040,7 +1042,7 @@
   where
     bound = maxBound :: b
 
--- | Determine target entry of action.
+-- | Determine the target entry of an action.
 targetEntry :: PendingAction -> Maybe EntrySelector
 targetEntry (SinkEntry _ _ s) = Just s
 targetEntry (CopyEntry _ _ s) = Just s
@@ -1056,7 +1058,7 @@
 targetEntry (SetArchiveComment _) = Nothing
 targetEntry DeleteArchiveComment = Nothing
 
--- | Decode 'ByteString'. The first argument indicates whether we should
+-- | Decode a 'ByteString'. The first argument indicates whether we should
 -- treat it as UTF-8 (in case bit 11 of general-purpose bit flag is set),
 -- otherwise the function assumes CP437. Note that since not every stream of
 -- bytes constitutes valid UTF-8 text, this function can fail. In that case
@@ -1072,20 +1074,20 @@
 decodeText True = either (const Nothing) Just . T.decodeUtf8'
 
 -- | Detect if the given text needs newer Unicode-aware features to be
--- properly encoded in archive.
+-- properly encoded in the archive.
 needsUnicode :: Text -> Bool
 needsUnicode = not . T.all validCP437
   where
     validCP437 x = ord x <= 127
 
--- | Convert numeric representation (as per .ZIP specification) of version
--- into 'Version'.
+-- | Convert numeric representation (as per the .ZIP specification) of
+-- version into 'Version'.
 toVersion :: Word16 -> Version
 toVersion x = makeVersion [major, minor]
   where
     (major, minor) = quotRem (fromIntegral $ x .&. 0x00ff) 10
 
--- | Covert 'Version' to its numeric representation as per .ZIP
+-- | Covert 'Version' to its numeric representation as per the .ZIP
 -- specification.
 fromVersion :: Version -> Word16
 fromVersion v = fromIntegral ((ZIP_OS `shiftL` 8) .|. (major * 10 + minor))
@@ -1096,7 +1098,7 @@
         v0 : _ -> (v0, 0)
         [] -> (0, 0)
 
--- | Get compression method form its numeric representation.
+-- | Get the compression method form its numeric representation.
 toCompressionMethod :: Word16 -> Maybe CompressionMethod
 toCompressionMethod 0 = Just Store
 toCompressionMethod 8 = Just Deflate
@@ -1104,23 +1106,23 @@
 toCompressionMethod 93 = Just Zstd
 toCompressionMethod _ = Nothing
 
--- | Convert 'CompressionMethod' to its numeric representation as per .ZIP
--- specification.
+-- | Convert 'CompressionMethod' to its numeric representation as per the
+-- .ZIP specification.
 fromCompressionMethod :: CompressionMethod -> Word16
 fromCompressionMethod Store = 0
 fromCompressionMethod Deflate = 8
 fromCompressionMethod BZip2 = 12
 fromCompressionMethod Zstd = 93
 
--- | Check if an entry with these parameters needs Zip64 extension.
+-- | Check if an entry with these parameters needs the Zip64 extension.
 needsZip64 :: EntryDescription -> Bool
 needsZip64 EntryDescription {..} =
   any
     (>= ffffffff)
     [edOffset, edCompressedSize, edUncompressedSize]
 
--- | Determine ???version needed to extract??? that should be written to 
headers
--- given need of Zip64 feature and compression method.
+-- | Determine ???version needed to extract??? that should be written to the
+-- headers given the need of the Zip64 feature and the compression method.
 getZipVersion :: Bool -> Maybe CompressionMethod -> Version
 getZipVersion zip64 m = max zip64ver mver
   where
@@ -1132,7 +1134,7 @@
       Just BZip2 -> [4, 6]
       Just Zstd -> [6, 3]
 
--- | Return decompressing 'Conduit' corresponding to the given compression
+-- | Return a decompressing 'Conduit' corresponding to the given compression
 -- method.
 decompressingPipe ::
   (PrimMonad m, MonadThrow m, MonadResource m) =>
@@ -1153,11 +1155,11 @@
 decompressingPipe Zstd = throwM ZstdUnsupported
 #endif
 
--- | Sink that calculates CRC32 check sum for incoming stream.
+-- | A sink that calculates the CRC32 check sum for an incoming stream.
 crc32Sink :: ConduitT ByteString Void (ResourceT IO) Word32
 crc32Sink = CL.fold crc32Update 0
 
--- | Convert 'UTCTime' to MS-DOS time format.
+-- | Convert 'UTCTime' to the MS-DOS time format.
 toMsDosTime :: UTCTime -> MsDosTime
 toMsDosTime UTCTime {..} = MsDosTime dosDate dosTime
   where
@@ -1189,9 +1191,9 @@
 -- We use the constants of the type 'Natural' instead of literals to protect
 -- ourselves from overflows on 32 bit systems.
 --
--- If we're in development mode, use lower values so the tests get a chance
--- to check all cases (otherwise we would need to generate way too big
--- archives on CI).
+-- If we're in the development mode, use lower values so the tests get a
+-- chance to check all cases (otherwise we would need to generate way too
+-- big archives on CI).
 
 ffff, ffffffff :: Natural
 
@@ -1203,8 +1205,8 @@
 ffffffff = 0xffffffff
 #endif
 
--- | Default permissions for the files, permissions not set on windows,
--- and are set to rw on unix. It mimics behavior of zip utility
+-- | The default permissions for the files, permissions not set on Windows,
+-- and are set to rw on Unix. This mimics the behavior of the zip utility.
 defaultFileMode :: Word32
 
 #ifdef mingw32_HOST_OS
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/Codec/Archive/Zip/Type.hs 
new/zip-1.7.1/Codec/Archive/Zip/Type.hs
--- old/zip-1.7.0/Codec/Archive/Zip/Type.hs     2001-09-09 03:46:40.000000000 
+0200
+++ new/zip-1.7.1/Codec/Archive/Zip/Type.hs     2001-09-09 03:46:40.000000000 
+0200
@@ -58,20 +58,19 @@
 -- Entry selector
 
 -- | This data type serves for naming and selection of archive entries. It
--- can be created only with help of the smart constructor 'mkEntrySelector',
--- and it's the only ???key??? that can be used to refer to files in archive or
--- to name new archive entries.
+-- can be created only with the help of the smart constructor
+-- 'mkEntrySelector', and it's the only ???key??? that can be used to refer to
+-- files in the archive or to name new archive entries.
 --
 -- The abstraction is crucial for ensuring that created archives are
--- portable across operating systems, file systems, and different platforms.
--- Since on some operating systems, file paths are case-insensitive, this
--- selector is also case-insensitive. It makes sure that only relative paths
--- are used to name files inside archive, as it's recommended in the
--- specification. It also guarantees that forward slashes are used when the
--- path is stored inside archive for compatibility with Unix-like operating
--- systems (as recommended in the specification). On the other hand, in can
--- be rendered as an ordinary relative file path in OS-specific format when
--- needed.
+-- portable across operating systems, file systems, and platforms. Since on
+-- some operating systems, file paths are case-insensitive, this selector is
+-- also case-insensitive. It makes sure that only relative paths are used to
+-- name files inside archive, as it's recommended in the specification. It
+-- also guarantees that forward slashes are used when the path is stored
+-- inside the archive for compatibility with Unix-like operating systems (as
+-- recommended in the specification). On the other hand, in can be rendered
+-- as an ordinary relative file path in OS-specific format when needed.
 newtype EntrySelector = EntrySelector
   { -- | Path pieces of relative path inside archive
     unES :: NonEmpty (CI String)
@@ -116,7 +115,7 @@
                 else giveup
 
 -- | Restore a relative path from 'EntrySelector'. Every 'EntrySelector'
--- corresponds to a single 'FilePath'.
+-- corresponds to a 'FilePath'.
 unEntrySelector :: EntrySelector -> FilePath
 unEntrySelector =
   FP.joinPath . fmap CI.original . NE.toList . unES
@@ -127,8 +126,7 @@
 getEntryName =
   T.pack . concat . NE.toList . NE.intersperse "/" . fmap CI.original . unES
 
--- | The exception represents various troubles you can have with
--- 'EntrySelector'.
+-- | The problems you can have with an 'EntrySelector'.
 newtype EntrySelectorException
   = -- | 'EntrySelector' cannot be created from this path
     InvalidEntrySelector FilePath
@@ -142,10 +140,10 @@
 ----------------------------------------------------------------------------
 -- Entry description
 
--- | This record represents all information about archive entry that can be
--- stored in a zip archive. It does not mirror local file header or central
--- directory file header, but their binary representations can be built
--- given this data structure and the actual archive contents.
+-- | The information about archive entry that can be stored in a zip
+-- archive. It does not mirror local file header or central directory file
+-- header, but their binary representations can be built given this data
+-- structure and the archive contents.
 data EntryDescription = EntryDescription
   { -- | Version made by
     edVersionMadeBy :: Version,
@@ -174,7 +172,7 @@
   }
   deriving (Eq, Typeable)
 
--- | Supported compression methods.
+-- | The supported compression methods.
 data CompressionMethod
   = -- | Store file uncompressed
     Store
@@ -191,13 +189,13 @@
 ----------------------------------------------------------------------------
 -- Archive description
 
--- | Information about archive as a whole.
+-- | The information about the archive as a whole.
 data ArchiveDescription = ArchiveDescription
-  { -- | Comment of entire archive
+  { -- | The comment of the entire archive
     adComment :: Maybe Text,
-    -- | Absolute offset of start of central directory
+    -- | Absolute offset of the start of central directory
     adCDOffset :: Natural,
-    -- | Size of central directory record
+    -- | The size of central directory record
     adCDSize :: Natural
   }
   deriving (Show, Read, Eq, Ord, Typeable, Data)
@@ -205,11 +203,12 @@
 ----------------------------------------------------------------------------
 -- Exceptions
 
+{- ORMOLU_DISABLE -}
+
 -- | The bad things that can happen when you use the library.
 data ZipException
   = -- | Thrown when you try to get contents of non-existing entry
     EntryDoesNotExist FilePath EntrySelector
-  | -- | Thrown when archive structure cannot be parsed
 #ifndef ENABLE_BZIP2
     -- | Thrown when attempting to decompress a 'BZip2' entry and the
     -- library is compiled without support for it.
@@ -224,9 +223,12 @@
     -- @since 1.6.0
   | ZstdUnsupported
 #endif
-    ParsingFailed FilePath String
+    -- | Thrown when archive structure cannot be parsed.
+  | ParsingFailed FilePath String
   deriving (Eq, Ord, Typeable)
 
+{- ORMOLU_ENABLE -}
+
 instance Show ZipException where
   show (EntryDoesNotExist file s) =
     "No such entry found: " ++ show s ++ " in " ++ show file
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/Codec/Archive/Zip/Unix.hs 
new/zip-1.7.1/Codec/Archive/Zip/Unix.hs
--- old/zip-1.7.0/Codec/Archive/Zip/Unix.hs     2001-09-09 03:46:40.000000000 
+0200
+++ new/zip-1.7.1/Codec/Archive/Zip/Unix.hs     2001-09-09 03:46:40.000000000 
+0200
@@ -7,7 +7,7 @@
 -- Stability   :  experimental
 -- Portability :  portable
 --
--- Unix specific functionality of zip archives.
+-- Unix-specific functionality of zip archives.
 --
 -- @since 1.4.0
 module Codec.Archive.Zip.Unix
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/Codec/Archive/Zip.hs 
new/zip-1.7.1/Codec/Archive/Zip.hs
--- old/zip-1.7.0/Codec/Archive/Zip.hs  2001-09-09 03:46:40.000000000 +0200
+++ new/zip-1.7.1/Codec/Archive/Zip.hs  2001-09-09 03:46:40.000000000 +0200
@@ -16,26 +16,25 @@
 --
 -- The module provides everything you may need to manipulate Zip archives.
 -- There are three things that should be clarified right away, to avoid
--- confusion in the future.
+-- confusion.
 --
 -- First, we use the 'EntrySelector' type that can be obtained from relative
 -- 'FilePath's (paths to directories are not allowed). This method may seem
 -- awkward at first, but it will protect you from the problems with
 -- portability when your archive is unpacked on a different platform.
 --
--- The second thing, that is rather a consequence of the first, is that
--- there is no way to add directories, or to be precise, /empty directories/
--- to your archive. This approach is used in Git, and I find it quite sane.
+-- Second, there is no way to add directories, or to be precise, /empty
+-- directories/ to your archive. This approach is used in Git, and I find it
+-- sane.
 --
 -- Finally, the third feature of the library is that it does not modify
 -- archive instantly, because doing so on every manipulation would often be
--- inefficient. Instead we maintain a collection of pending actions that can
--- be turned into an optimized procedure that efficiently modifies archive
--- in one pass. Normally this should be of no concern to you, because all
--- actions are performed automatically when you leave the realm of
+-- inefficient. Instead, we maintain a collection of pending actions that
+-- can be turned into an optimized procedure that efficiently modifies the
+-- archive in one pass. Normally, this should be of no concern to you,
+-- because all actions are performed automatically when you leave the
 -- 'ZipArchive' monad. If, however, you ever need to force an update, the
--- 'commit' function is your friend. There are even ???undo??? functions, by 
the
--- way.
+-- 'commit' function is your friend.
 --
 -- === Examples
 --
@@ -62,7 +61,7 @@
 -- >   s      <- mkEntrySelector "hello-world.txt"
 -- >   createArchive path (addEntry Store "Hello, World!" s)
 --
--- Extract contents of a specific file and print them:
+-- Extract contents of a file and print them:
 --
 -- > import Codec.Archive.Zip
 -- > import System.Environment (getArgs)
@@ -214,7 +213,7 @@
   restoreM = ZipArchive . StateT . const . return
   {-# INLINEABLE restoreM #-}
 
--- | Internal state record used by the 'ZipArchive' monad. This is only
+-- | The internal state record used by the 'ZipArchive' monad. This is only
 -- exported for use with 'MonadBaseControl' methods, you can't look inside.
 --
 -- @since 0.2.0
@@ -235,9 +234,9 @@
 -- work with an existing archive.
 createArchive ::
   MonadIO m =>
-  -- | Location of archive file to create
+  -- | Location of the archive file to create
   FilePath ->
-  -- | Actions that form archive's content
+  -- | Actions that create the archive's content
   ZipArchive a ->
   m a
 createArchive path m = liftIO $ do
@@ -279,7 +278,7 @@
 -- with this library.
 withArchive ::
   MonadIO m =>
-  -- | Location of archive to work with
+  -- | Location of the archive to work with
   FilePath ->
   -- | Actions on that archive
   ZipArchive a ->
@@ -300,14 +299,14 @@
 ----------------------------------------------------------------------------
 -- Retrieving information
 
--- | Retrieve description of all archive entries. This is an efficient
--- operation that can be used for example to list all entries in an archive.
--- Do not hesitate to use the function frequently: scanning of archive
--- happens only once anyway.
---
--- Please note that the returned value only reflects actual contents of the
--- archive in file system, non-committed actions do not influence the list
--- of entries, see 'commit' for more information.
+-- | Retrieve a description of all archive entries. This is an efficient
+-- operation that can be used for example to list all entries in the
+-- archive. Do not hesitate to use the function frequently: scanning of the
+-- archive happens only once.
+--
+-- Please note that the returned value only reflects the current contents of
+-- the archive in file system, non-committed actions are not reflected, see
+-- 'commit' for more information.
 getEntries :: ZipArchive (Map EntrySelector EntryDescription)
 getEntries = ZipArchive (gets zsEntries)
 
@@ -318,7 +317,7 @@
 doesEntryExist :: EntrySelector -> ZipArchive Bool
 doesEntryExist s = M.member s <$> getEntries
 
--- | Get 'EntryDescription' for specified entry. This is a simple shortcut
+-- | Get 'EntryDescription' for a specified entry. This is a simple shortcut
 -- defined as:
 --
 -- > getEntryDesc s = M.lookup s <$> getEntries
@@ -358,7 +357,7 @@
 --
 -- Throws: 'EntryDoesNotExist'.
 sourceEntry ::
-  -- | Selector that identifies archive entry
+  -- | Selector that identifies the archive entry
   EntrySelector ->
   -- | Sink where to stream entry contents
   ConduitT ByteString Void (ResourceT IO) a ->
@@ -372,7 +371,7 @@
 --
 -- Throws: 'EntryDoesNotExist'.
 saveEntry ::
-  -- | Selector that identifies archive entry
+  -- | Selector that identifies the archive entry
   EntrySelector ->
   -- | Where to save the file
   FilePath ->
@@ -388,19 +387,19 @@
 --
 -- Throws: 'EntryDoesNotExist'.
 checkEntry ::
-  -- | Selector that identifies archive entry
+  -- | Selector that identifies the archive entry
   EntrySelector ->
   -- | Is the entry intact?
   ZipArchive Bool
 checkEntry s = do
   calculated <- sourceEntry s I.crc32Sink
   given <- edCRC32 . (! s) <$> getEntries
-  -- ??? NOTE We can assume that entry exists for sure because otherwise
+  -- NOTE We can assume that entry exists for sure because otherwise
   -- 'sourceEntry' would have thrown 'EntryDoesNotExist' already.
   return (calculated == given)
 
--- | Unpack the entire archive into the specified directory. The directory
--- will be created if it does not exist.
+-- | Unpack the archive into the specified directory. The directory will be
+-- created if it does not exist.
 unpackInto :: FilePath -> ZipArchive ()
 unpackInto dir' = do
   selectors <- M.keysSet <$> getEntries
@@ -425,33 +424,33 @@
 
 -- | Add a new entry to the archive given its contents in binary form.
 addEntry ::
-  -- | Compression method to use
+  -- | The compression method to use
   CompressionMethod ->
   -- | Entry contents
   ByteString ->
-  -- | Name of entry to add
+  -- | Name of the entry to add
   EntrySelector ->
   ZipArchive ()
 addEntry t b s = addPending (I.SinkEntry t (C.yield b) s)
 
 -- | Stream data from the specified source to an archive entry.
 sinkEntry ::
-  -- | Compression method to use
+  -- | The compression method to use
   CompressionMethod ->
   -- | Source of entry contents
   ConduitT () ByteString (ResourceT IO) () ->
-  -- | Name of entry to add
+  -- | Name of the entry to add
   EntrySelector ->
   ZipArchive ()
 sinkEntry t src s = addPending (I.SinkEntry t src s)
 
 -- | Load an entry from a given file.
 loadEntry ::
-  -- | Compression method to use
+  -- | The compression method to use
   CompressionMethod ->
-  -- | Name of entry to add
+  -- | Name of the entry to add
   EntrySelector ->
-  -- | Path to file to add
+  -- | Path to the file to add
   FilePath ->
   ZipArchive ()
 loadEntry t s path = do
@@ -467,30 +466,30 @@
 #endif
 
 -- | Copy an entry ???as is??? from another zip archive. If the entry does not
--- exist in that archive, 'EntryDoesNotExist' will be eventually thrown.
+-- exist in that archive, 'EntryDoesNotExist' will be thrown.
 copyEntry ::
-  -- | Path to archive to copy from
+  -- | Path to the archive to copy from
   FilePath ->
-  -- | Name of entry (in source archive) to copy
+  -- | Name of the entry (in the source archive) to copy
   EntrySelector ->
-  -- | Name of entry to insert (in current archive)
+  -- | Name of the entry to insert (in current archive)
   EntrySelector ->
   ZipArchive ()
 copyEntry path s' s = do
   apath <- liftIO (canonicalizePath path)
   addPending (I.CopyEntry apath s' s)
 
--- | Add an entire directory to the archive. Please note that due to the
--- design of the library, empty sub-directories won't be added.
+-- | Add an directory to the archive. Please note that due to the design of
+-- the library, empty sub-directories will not be added.
 --
 -- The action can throw 'InvalidEntrySelector'.
 packDirRecur ::
-  -- | Compression method to use
+  -- | The compression method to use
   CompressionMethod ->
-  -- | How to get 'EntrySelector' from a path relative to the root of the
-  -- directory we pack
+  -- | How to get the 'EntrySelector' from a path relative to the root of
+  -- the directory we pack
   (FilePath -> ZipArchive EntrySelector) ->
-  -- | Path to directory to add
+  -- | Path to the directory to add
   FilePath ->
   ZipArchive ()
 packDirRecur t f = packDirRecur' t f (const $ return ())
@@ -500,14 +499,14 @@
 --
 -- @since 1.5.0
 packDirRecur' ::
-  -- | Compression method to use
+  -- | The compression method to use
   CompressionMethod ->
-  -- | How to get 'EntrySelector' from a path relative to the root of the
-  -- directory we pack
+  -- | How to get the 'EntrySelector' from a path relative to the root of
+  -- the directory we pack
   (FilePath -> ZipArchive EntrySelector) ->
   -- | How to modify an entry after creation
   (EntrySelector -> ZipArchive ()) ->
-  -- | Path to directory to add
+  -- | Path to the directory to add
   FilePath ->
   ZipArchive ()
 packDirRecur' t f patch path = do
@@ -520,9 +519,9 @@
 -- | Rename an entry in the archive. If the entry does not exist, nothing
 -- will happen.
 renameEntry ::
-  -- | Original entry name
+  -- | The original entry name
   EntrySelector ->
-  -- | New entry name
+  -- | The new entry name
   EntrySelector ->
   ZipArchive ()
 renameEntry old new = addPending (I.RenameEntry old new)
@@ -535,9 +534,9 @@
 -- | Change compression method of an entry, if it does not exist, nothing
 -- will happen.
 recompress ::
-  -- | New compression method
+  -- | The new compression method
   CompressionMethod ->
-  -- | Name of entry to re-compress
+  -- | Name of the entry to re-compress
   EntrySelector ->
   ZipArchive ()
 recompress t s = addPending (I.Recompress t s)
@@ -548,7 +547,7 @@
 setEntryComment ::
   -- | Text of the comment
   Text ->
-  -- | Name of entry to comment on
+  -- | Name of the entry to comment on
   EntrySelector ->
   ZipArchive ()
 setEntryComment text s = addPending (I.SetEntryComment text s)
@@ -558,12 +557,12 @@
 deleteEntryComment :: EntrySelector -> ZipArchive ()
 deleteEntryComment s = addPending (I.DeleteEntryComment s)
 
--- | Set the ???last modification??? date\/time. The specified entry may be
+-- | Set the last modification date\/time. The specified entry may be
 -- missing, in that case the action has no effect.
 setModTime ::
   -- | New modification time
   UTCTime ->
-  -- | Name of entry to modify
+  -- | Name of the entry to modify
   EntrySelector ->
   ZipArchive ()
 setModTime time s = addPending (I.SetModTime time s)
@@ -571,11 +570,11 @@
 -- | Add an extra field. The specified entry may be missing, in that case
 -- this action has no effect.
 addExtraField ::
-  -- | Tag (header id) of extra field to add
+  -- | Tag (header id) of the extra field to add
   Word16 ->
   -- | Body of the field
   ByteString ->
-  -- | Name of entry to modify
+  -- | Name of the entry to modify
   EntrySelector ->
   ZipArchive ()
 addExtraField n b s = addPending (I.AddExtraField n b s)
@@ -583,9 +582,9 @@
 -- | Delete an extra field by its type (tag). The specified entry may be
 -- missing, in that case this action has no effect.
 deleteExtraField ::
-  -- | Tag (header id) of extra field to delete
+  -- | Tag (header id) of the extra field to delete
   Word16 ->
-  -- | Name of entry to modify
+  -- | Name of the entry to modify
   EntrySelector ->
   ZipArchive ()
 deleteExtraField n s = addPending (I.DeleteExtraField n s)
@@ -599,7 +598,7 @@
 setExternalFileAttrs ::
   -- | External file attributes
   Word32 ->
-  -- | Name of entry to modify
+  -- | Name of the entry to modify
   EntrySelector ->
   ZipArchive ()
 setExternalFileAttrs attrs s =
@@ -607,26 +606,26 @@
 
 -- | Perform an action on every entry in the archive.
 forEntries ::
-  -- | Action to perform
+  -- | The action to perform
   (EntrySelector -> ZipArchive ()) ->
   ZipArchive ()
 forEntries action = getEntries >>= mapM_ action . M.keysSet
 
--- | Set comment of the entire archive.
+-- | Set the comment of the entire archive.
 setArchiveComment :: Text -> ZipArchive ()
 setArchiveComment text = addPending (I.SetArchiveComment text)
 
--- | Delete the archive comment if it's present.
+-- | Delete the archive's comment if it's present.
 deleteArchiveComment :: ZipArchive ()
 deleteArchiveComment = addPending I.DeleteArchiveComment
 
--- | Undo changes to a specific archive entry.
+-- | Undo the changes to a specific archive entry.
 undoEntryChanges :: EntrySelector -> ZipArchive ()
 undoEntryChanges s = modifyActions f
   where
     f = S.filter ((/= Just s) . I.targetEntry)
 
--- | Undo changes to the archive as a whole (archive's comment).
+-- | Undo the changes to the archive as a whole (archive's comment).
 undoArchiveChanges :: ZipArchive ()
 undoArchiveChanges = modifyActions f
   where
@@ -639,10 +638,10 @@
 -- | Archive contents are not modified instantly, but instead changes are
 -- collected as ???pending actions??? that should be committed, in order to
 -- efficiently modify the archive in one pass. The actions are committed
--- automatically when the program leaves the realm of 'ZipArchive' monad
--- (i.e. as part of 'createArchive' or 'withArchive'), or can be forced
--- explicitly with the help of this function. Once committed, changes take
--- place in the file system and cannot be undone.
+-- automatically when the program leaves the 'ZipArchive' monad (i.e. as
+-- part of 'createArchive' or 'withArchive'), or can be forced explicitly
+-- with the help of this function. Once committed, changes take place in the
+-- file system and cannot be undone.
 commit :: ZipArchive ()
 commit = do
   file <- getFilePath
@@ -652,7 +651,7 @@
   exists <- liftIO (doesFileExist file)
   unless (S.null actions && exists) $ do
     liftIO (I.commit file odesc oentries actions)
-    -- NOTE The most robust way to update internal description of the
+    -- NOTE The most robust way to update the internal description of the
     -- archive is to scan it again???manual manipulations with descriptions of
     -- entries are too error-prone. We also want to erase all pending
     -- actions because 'I.commit' executes them all by definition.
@@ -676,7 +675,7 @@
 getPending :: ZipArchive (Seq I.PendingAction)
 getPending = ZipArchive (gets zsActions)
 
--- | Modify the collection of pending actions in some way.
+-- | Modify the collection of pending actions.
 modifyActions :: (Seq I.PendingAction -> Seq I.PendingAction) -> ZipArchive ()
 modifyActions f = ZipArchive (modify g)
   where
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/README.md new/zip-1.7.1/README.md
--- old/zip-1.7.0/README.md     2001-09-09 03:46:40.000000000 +0200
+++ new/zip-1.7.1/README.md     2001-09-09 03:46:40.000000000 +0200
@@ -23,39 +23,36 @@
 
 This is a feature-rich, memory-efficient, and type-safe library to
 manipulate Zip archives. The library is the most complete and efficient
-implementation of .ZIP specification in Haskell (at least from open-sourced
-ones). In particular, it's created with large multimedia data in mind and
-provides all features users might expect, comparable in terms of feature-set
-with libraries like `libzip` in C.
+implementation of the .ZIP specification in Haskell (at least from the
+open-sourced ones). In particular, it's created with large multimedia data
+in mind and provides all features users might expect, comparable in terms of
+feature-set with libraries like `libzip` in C.
 
 ## Why this library is written
 
 There are a few libraries to work with Zip archives, yet every one of them
-provides only a subset of all the functionality a user may need (obviously
-the libraries provide functionality that their authors needed) and otherwise
-is flawed in some way so it cannot be easily used in some situations. Let's
-examine all the libraries available on Hackage to understand motivation for
-this package.
+provides only a subset of useful functionality or otherwise is flawed in
+some way so it cannot be easily used in some situations. Let's examine all
+libraries available on Hackage to understand the motivation for this
+package.
 
 ### zip-archive
 
 `zip-archive` is a widely used library. It's quite old, well-known and
-simple to use. However it creates Zip archives purely, as `ByteStrings`s in
-memory that you can then write to the file system. This is not acceptable if
-you work with more-or-less big data. For example, if you have collection of
-files with total size of 500 MB and you want to pack them into archive, you
-can easily consume up to 1 GB of memory (the files plus resulting archive).
-Not always you can afford to do this or do this at scale. Even if you want
-just to look at list of archive entries it will read it into memory in all
-its entirety.
+simple to use. However, it creates Zip archives purely, as `ByteStrings`s in
+memory. This is not acceptable if you work with big data. For example, if
+you have a collection of files with the total size 500 MB and you want to
+pack them into an archive, you can easily consume up to 1 GB of memory (the
+files plus the resulting archive). This is not always affordable. Even if
+you want just to look at the list of archive entries it will read the entire
+archive into memory.
 
 ### LibZip
 
-This is a binding to C library [`libzip`][libzip]. There is always a certain
-kind of trouble with bindings. For example, you need to take care that
-target library is installed and its version is compatible with the version
-of your binding. Yes, this means additional headaches. It should be just
-???plug and play???, but now you need to watch out for compatibility.
+This is a binding to the C library [`libzip`][libzip]. There is always a
+certain kind of trouble with bindings. For example, you need to ensure that
+the target library is installed and its version is compatible with the
+version of your binding.
 
 It's not that bad with libraries that do not break their API for years, but
 it's not the case with `libzip`. As the maintainer of `LibZip` puts it:
@@ -64,25 +61,24 @@
 > 0.11.x, then you should use LibZip 0.11. If your C library is 1.0, then
 > you should use LibZip master branch (not yet released to Hackage).
 
-Now, on my machine I have version 1.0. To put the package on Stackage we had
-to use version 0.10, because Stackage uses Ubuntu to build packages and
-libraries on Ubuntu are always ancient. This means that I cannot use the
+Now, on my machine I have the version 1.0. To put the package on Stackage we
+had to use the version 0.10, because Stackage uses Ubuntu to build packages
+and libraries on Ubuntu are always ancient. This means that I cannot use the
 version of the library from Stackage, and I don't yet know what will be on
 the server.
 
-After much frustration with all these things I decided to avoid using
-`LibZip`, because after all, this is not that sort of a project that
-shouldn't be done completely in Haskell. By rewriting this in Haskell, I
-also can make it safer to use.
+After much frustration, I decided to avoid using `LibZip`. After all, this
+is not a project that shouldn't be done completely in Haskell. By rewriting
+this in Haskell, I also can make it safer to use.
 
 ### zip-conduit
 
 This one uses the right approach: leverage a good streaming library
-(`conduit`) for memory-efficient processing. This is however is not
-feature-rich and has certain problems (including programming style, it uses
-`error` if an entry is missing in archive, among other things), some of them
-are reported on its issue tracker. It also does not appear to be maintained
-(last sign of activity was on December 23, 2014).
+(`conduit`) for memory-efficient processing. The library is however not
+feature-rich and has certain problems (including the programming style, it
+uses `error` if an entry is missing in the archive, among other things),
+some of them are reported on its issue tracker. It also does not appear to
+be maintained (the last sign of activity was on December 23, 2014).
 
 ## Features
 
@@ -116,12 +112,11 @@
 
 ### Sources of file data
 
-The library gives you many options how to get file contents to compress and
-how to get extracted data. The following methods are supported:
+The following sources are supported:
 
 * *File name.* This is an efficient method to perform compression or
-  decompression. You just specify where to get data or where to save it and
-  the rest is handled by the library.
+  decompression. You specify where to get data or where to save it and the
+  rest is handled by the library.
 * *Conduit source or sink.*
 * *ByteString.* Use it only with small data.
 * *Copy file from another archive.* An efficient operation, file is copied
@@ -130,60 +125,60 @@
 ### ZIP64
 
 When necessary, the `ZIP64` extension is automatically used. It's necessary
-when anything from this list takes place:
+when:
 
-* Total size of archive is greater than 4 GB.
-* Size of a single compressed/uncompressed file in archive is greater than 4
-  GB.
-* There are more than 65535 entries in archive.
-
-The library is particularly suited for processing of large files. For
-example, I've been able to easily create 6.5 GB archive with reasonable
-speed and without significant memory consumption.
+* The total size of the archive is greater than 4 GB.
+* The size of a single compressed/uncompressed file in the archive is
+  greater than 4 GB.
+* There are more than 65535 entries in the archive.
+
+The library is particularly well suited for processing large files. For
+example, I've been able to create 6.5 GB archive with reasonable speed and
+without significant memory consumption.
 
 ### Filenames
 
-The library has API that makes it impossible to create archive with
+The library has an API that makes it impossible to create archive with
 non-portable or invalid file names in it.
 
 As of .ZIP specification 6.3.2, files with Unicode symbols in their names
-can be put into Zip archives. The library supports mechanisms for this and
+can be stored in Zip archives. The library supports mechanisms for this and
 uses them automatically when needed. Besides UTF-8, CP437 is also supported
-as it's required in the specification.
+as per the specification.
 
 ### Meta-information about files
 
-The library allows to attach comments to entire archive or individual files,
-and also gives its user full control over extra fields that are written to
-file headers, so the user can store arbitrary information about file in the
-archive.
+The library allows us to attach comments to the entire archive or individual
+files, and also gives its user full control over extra fields that are
+written to file headers, so the user can store arbitrary information about
+files in the archive.
 
 ## Quick start
 
 The module `Codec.Archive.Zip` provides everything you may need to
 manipulate Zip archives. There are three things that should be clarified
-right away, to avoid confusion in the future.
+right away to avoid confusion.
 
 First, we use the `EntrySelector` type that can be obtained from relative
 `FilePath`s (paths to directories are not allowed). This method may seem
 awkward at first, but it will protect you from the problems with portability
 when your archive is unpacked on a different platform.
 
-The second thing, that is rather a consequence of the first, is that there
-is no way to add directories, or to be precise, *empty directories* to your
-archive. This approach is used in Git, and I find it quite sane.
-
-Finally, the third feature of the library is that it does not modify archive
-instantly, because doing so on every manipulation would often be
-inefficient. Instead we maintain a collection of pending actions that can be
-turned into an optimized procedure that efficiently modifies archive in one
-pass. Normally this should be of no concern to you, because all actions are
-performed automatically when you leave the realm of `ZipArchive` monad. If,
-however, you ever need to force an update, the `commit` function is your
-friend. There are even ???undo??? functions, by the way.
+Second, there is no way to add directories, or to be precise, *empty
+directories* to your archive. This approach is used in Git and I find it
+sane.
+
+Finally, the third feature of the library is that it does not modify the
+archive instantly, because doing so on every manipulation would often be
+inefficient. Instead, we maintain a collection of pending actions that can
+be turned into an optimized procedure that efficiently modifies the archive
+in one pass. Normally, this should be of no concern to you, because all
+actions are performed automatically when you leave the `ZipArchive` monad.
+If, however, you ever need to force an update, the `commit` function is your
+friend.
 
-Let's take a look at some examples that show how to accomplish most typical
-tasks with help of the library.
+Let's take a look at some examples that show how to accomplish most common
+tasks.
 
 To get full information about archive entries, use `getEntries`:
 
@@ -210,7 +205,7 @@
 ??> withArchive archivePath (saveEntry entrySelector pathToFile)
 ```
 
-???and finally just unpack the entire archive into some directory:
+???and finally just unpack the entire archive into a directory:
 
 ```haskell
 ??> withArchive archivePath (unpackInto destDir)
@@ -218,9 +213,9 @@
 
 See also `getArchiveComment` and `getArchiveDescription`.
 
-Modifying is also easy, efficient, and powerful. When you want to create a
-new archive use `createArchive`, otherwise `withArchive` will do. To add an
-entry from `ByteString`:
+Modifying is also easy. When you want to create a new archive use
+`createArchive`, otherwise `withArchive` will do. To add an entry from
+`ByteString`:
 
 ```haskell
 ??> createArchive archivePath (addEntry Store "Hello, World!" entrySelector)
@@ -273,7 +268,7 @@
 You can contact the maintainer via [the issue
 tracker](https://github.com/mrkkrp/zip/issues).
 
-Pull requests are also welcome.
+Pull requests are welcome.
 
 ## License
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/tests/Main.hs new/zip-1.7.1/tests/Main.hs
--- old/zip-1.7.0/tests/Main.hs 2001-09-09 03:46:40.000000000 +0200
+++ new/zip-1.7.1/tests/Main.hs 2001-09-09 03:46:40.000000000 +0200
@@ -39,14 +39,9 @@
 import Test.Hspec
 import Test.QuickCheck hiding ((.&.))
 
-#if !MIN_VERSION_base(4,13,0)
-import Data.Semigroup ((<>))
-#endif
-
--- | Zip tests. Please note that Zip64 feature is not currently tested
--- automatically because for it to expose itself we need > 4GB of
--- data. Handling such quantities of data locally is problematic and even
--- more problematic in the context of CI server.
+-- | Zip tests. Please note that the Zip64 feature is not currently tested
+-- automatically because we'd need > 4GB of data. Handling such quantities
+-- of data locally is problematic and even more problematic on CI.
 main :: IO ()
 main = hspec $ do
   describe "mkEntrySelector" mkEntrySelectorSpec
@@ -766,40 +761,42 @@
 ----------------------------------------------------------------------------
 -- Helpers
 
--- | Change the size parameter of generator by dividing it by 2.
+-- | Change the size parameter of a generator by dividing it by 2.
 downScale :: Gen a -> Gen a
 downScale = scale (`div` 2)
 
--- | Check whether given exception is 'EntrySelectorException' with specific
--- path inside.
+-- | Check whether a given exception is 'EntrySelectorException' with a
+-- specific path inside.
 isEntrySelectorException :: FilePath -> EntrySelectorException -> Bool
 isEntrySelectorException path (InvalidEntrySelector p) = p == path
 
--- | Check whether given exception is 'ParsingFailed' exception with
+-- | Check whether a given exception is 'ParsingFailed' exception with a
 -- specific path and error message inside.
 isParsingFailed :: FilePath -> String -> ZipException -> Bool
 isParsingFailed path msg (ParsingFailed path' msg') =
   path == path' && msg == msg'
 isParsingFailed _ _ _ = False
 
--- | Create sandbox directory to model some situation in it and run some
--- tests. Note that we're using new unique sandbox directory for each test
--- case to avoid contamination and it's unconditionally deleted after test
--- case finishes. The function returns vacant file path in that directory.
+-- | Create a sandbox directory to model some situation in it and run some
+-- tests. Note that we're using a new unique sandbox directory for each test
+-- case to avoid contamination and it's unconditionally deleted after the
+-- test case finishes. The function returns a vacant file path in that
+-- directory.
 withSandbox :: ActionWith FilePath -> IO ()
 withSandbox action = withSystemTempDirectory "zip-sandbox" $ \dir ->
   action (dir </> "foo.zip")
 
--- | Given primary name (name of archive), generate a name that does not
+-- | Given a primary name (name of archive), generate a name that does not
 -- collide with it.
 deriveVacant :: FilePath -> FilePath
 deriveVacant = (</> "bar") . FP.takeDirectory
 
--- | Compare times forgiving minor difference.
+-- | Compare times forgiving a minor difference.
 isCloseTo :: UTCTime -> UTCTime -> Bool
 isCloseTo a b = abs (diffUTCTime a b) < 2
 
--- | Compare only some fields of 'EntryDescription' record.
+-- | Compare for equality taking into account only some fields of the
+-- 'EntryDescription' record.
 softEq :: EntryDescription -> EntryDescription -> Bool
 softEq a b =
   edCompression a == edCompression b
@@ -818,7 +815,7 @@
   where
     f a b = if softEq a b then Nothing else Just a
 
--- | Canonical representation of empty Zip archive.
+-- | The canonical representation of an empty Zip archive.
 emptyArchive :: ByteString
 emptyArchive =
   B.pack
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/zip-1.7.0/zip.cabal new/zip-1.7.1/zip.cabal
--- old/zip-1.7.0/zip.cabal     2001-09-09 03:46:40.000000000 +0200
+++ new/zip-1.7.1/zip.cabal     2001-09-09 03:46:40.000000000 +0200
@@ -1,11 +1,11 @@
 cabal-version:   1.18
 name:            zip
-version:         1.7.0
+version:         1.7.1
 license:         BSD3
 license-file:    LICENSE.md
 maintainer:      Mark Karpov <markkarpo...@gmail.com>
 author:          Mark Karpov <markkarpo...@gmail.com>
-tested-with:     ghc ==8.6.5 ghc ==8.8.4 ghc ==8.10.3
+tested-with:     ghc ==8.8.4 ghc ==8.10.4 ghc ==9.0.1
 homepage:        https://github.com/mrkkrp/zip
 bug-reports:     https://github.com/mrkkrp/zip/issues
 synopsis:        Operations on zip archives
@@ -51,7 +51,7 @@
 
     default-language: Haskell2010
     build-depends:
-        base >=4.12 && <5.0,
+        base >=4.13 && <5.0,
         bytestring >=0.9 && <0.12,
         case-insensitive >=1.2.0.2 && <1.3,
         cereal >=0.3 && <0.6,
@@ -69,7 +69,7 @@
         text >=0.2 && <1.3,
         time >=1.4 && <1.10,
         transformers >=0.4 && <0.6,
-        transformers-base -any
+        transformers-base
 
     if !flag(disable-bzip2)
         build-depends: bzlib-conduit >=0.3 && <0.4
@@ -104,9 +104,9 @@
     hs-source-dirs:   bench-app
     default-language: Haskell2010
     build-depends:
-        base >=4.12 && <5.0,
+        base >=4.13 && <5.0,
         filepath >=1.2 && <1.5,
-        zip -any
+        zip
 
     if flag(dev)
         ghc-options:
@@ -122,7 +122,7 @@
     hs-source-dirs:   tests
     default-language: Haskell2010
     build-depends:
-        base >=4.12 && <5.0,
+        base >=4.13 && <5.0,
         QuickCheck >=2.4 && <3.0,
         bytestring >=0.9 && <0.12,
         conduit >=1.3 && <1.4,
@@ -136,7 +136,7 @@
         text >=0.2 && <1.3,
         time >=1.4 && <1.10,
         transformers >=0.4 && <0.6,
-        zip -any
+        zip
 
     if flag(dev)
         ghc-options: -O0 -Wall -Werror

Reply via email to