File: Zip.hs

package info (click to toggle)
haskell-zip 2.0.1-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 200 kB
  • sloc: haskell: 2,385; makefile: 7
file content (716 lines) | stat: -rw-r--r-- 22,724 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}

-- |
-- Module      :  Codec.Archive.Zip
-- Copyright   :  © 2016–present Mark Karpov
-- License     :  BSD 3 clause
--
-- Maintainer  :  Mark Karpov <markkarpov92@gmail.com>
-- Stability   :  experimental
-- Portability :  portable
--
-- The module provides everything you may need to manipulate Zip archives.
-- There are three things that should be clarified 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.
--
-- 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 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.
--
-- === Examples
--
-- An example of a program that prints a list of archive entries:
--
-- > import Codec.Archive.Zip
-- > import System.Environment (getArgs)
-- > import qualified Data.Map as M
-- >
-- > main :: IO ()
-- > main = do
-- >   [path]  <- getArgs
-- >   entries <- withArchive path (M.keys <$> getEntries)
-- >   mapM_ print entries
--
-- Create a Zip archive with a “Hello World” file:
--
-- > import Codec.Archive.Zip
-- > import System.Environment (getArgs)
-- >
-- > main :: IO ()
-- > main = do
-- >   [path] <- getArgs
-- >   s      <- mkEntrySelector "hello-world.txt"
-- >   createArchive path (addEntry Store "Hello, World!" s)
--
-- Extract contents of a file and print them:
--
-- > import Codec.Archive.Zip
-- > import System.Environment (getArgs)
-- > import qualified Data.ByteString.Char8 as B
-- >
-- > main :: IO ()
-- > main = do
-- >   [path,f] <- getArgs
-- >   s        <- mkEntrySelector f
-- >   bs       <- withArchive path (getEntry s)
-- >   B.putStrLn bs
module Codec.Archive.Zip
  ( -- * Types

    -- ** Entry selector
    EntrySelector,
    mkEntrySelector,
    unEntrySelector,
    getEntryName,
    EntrySelectorException (..),

    -- ** Entry description
    EntryDescription (..),
    CompressionMethod (..),

    -- ** Archive description
    ArchiveDescription (..),

    -- ** Exceptions
    ZipException (..),

    -- * Archive monad
    ZipArchive,
    ZipState,
    createArchive,
    withArchive,

    -- * Retrieving information
    getEntries,
    doesEntryExist,
    getEntryDesc,
    getEntry,
    getEntrySource,
    sourceEntry,
    saveEntry,
    checkEntry,
    unpackInto,
    getArchiveComment,
    getArchiveDescription,

    -- * Modifying archive

    -- ** Adding entries
    addEntry,
    sinkEntry,
    loadEntry,
    copyEntry,
    packDirRecur,
    packDirRecur',

    -- ** Modifying entries
    renameEntry,
    deleteEntry,
    recompress,
    setEntryComment,
    deleteEntryComment,
    setModTime,
    addExtraField,
    deleteExtraField,
    setExternalFileAttrs,
    forEntries,

    -- ** Operations on archive as a whole
    setArchiveComment,
    deleteArchiveComment,

    -- ** Control over editing
    undoEntryChanges,
    undoArchiveChanges,
    undoAll,
    commit,
  )
where

import Codec.Archive.Zip.Internal qualified as I
import Codec.Archive.Zip.Type
import Conduit (PrimMonad)
import Control.Monad
import Control.Monad.Base (MonadBase (..))
import Control.Monad.Catch
import Control.Monad.State.Strict
import Control.Monad.Trans.Control (MonadBaseControl (..))
import Control.Monad.Trans.Resource (MonadResource, ResourceT)
import Data.ByteString (ByteString)
import Data.Conduit (ConduitT, (.|))
import Data.Conduit qualified as C
import Data.Conduit.Binary qualified as CB
import Data.Conduit.List qualified as CL
import Data.DList qualified as DList
import Data.Map.Strict (Map, (!))
import Data.Map.Strict qualified as M
import Data.Sequence (Seq, (|>))
import Data.Sequence qualified as S
import Data.Set qualified as E
import Data.Text (Text)
import Data.Time.Clock (UTCTime)
import Data.Void
import Data.Word (Word16, Word32)
import System.Directory
import System.FilePath ((</>))
import System.FilePath qualified as FP
import System.IO.Error (isDoesNotExistError)

#ifndef mingw32_HOST_OS
import qualified Codec.Archive.Zip.Unix as Unix
import qualified System.Posix as Unix
#endif

----------------------------------------------------------------------------
-- Archive monad

-- | Monad that provides context necessary for performing operations on zip
-- archives. It's intentionally opaque and not a monad transformer to limit
-- the actions that can be performed in it to those provided by this module
-- and their combinations.
newtype ZipArchive a = ZipArchive
  { unZipArchive :: StateT ZipState IO a
  }
  deriving
    ( Functor,
      Applicative,
      Monad,
      MonadIO,
      MonadThrow,
      MonadCatch,
      MonadMask
    )

-- | @since 0.2.0
instance MonadBase IO ZipArchive where
  liftBase = liftIO

-- | @since 0.2.0
instance MonadBaseControl IO ZipArchive where
  type StM ZipArchive a = (a, ZipState)
  liftBaseWith f = ZipArchive . StateT $ \s ->
    (,s) <$> f (flip runStateT s . unZipArchive)
  {-# INLINEABLE liftBaseWith #-}
  restoreM = ZipArchive . StateT . const . return
  {-# INLINEABLE restoreM #-}

-- | 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
data ZipState = ZipState
  { -- | Path to zip archive
    zsFilePath :: FilePath,
    -- | Actual collection of entries
    zsEntries :: Map EntrySelector EntryDescription,
    -- | Info about the whole archive
    zsArchive :: ArchiveDescription,
    -- | Pending actions
    zsActions :: Seq I.PendingAction
  }

-- | Create a new archive given its location and an action that describes
-- how to create contents of the archive. This will silently overwrite the
-- specified file if it already exists. See 'withArchive' if you want to
-- work with an existing archive.
createArchive ::
  (MonadIO m) =>
  -- | Location of the archive file to create
  FilePath ->
  -- | Actions that create the archive's content
  ZipArchive a ->
  m a
createArchive path m = liftIO $ do
  apath <- makeAbsolute path
  ignoringAbsence (removeFile apath)
  let st =
        ZipState
          { zsFilePath = apath,
            zsEntries = M.empty,
            zsArchive = ArchiveDescription Nothing 0 0,
            zsActions = S.empty
          }
      action = unZipArchive (m <* commit)
  evalStateT action st

-- | Work with an existing archive. See 'createArchive' if you want to
-- create a new archive instead.
--
-- This operation may fail with:
--
--     * @isAlreadyInUseError@ if the file is already open and cannot be
--     reopened;
--
--     * @isDoesNotExistError@ if the file does not exist;
--
--     * @isPermissionError@ if the user does not have permission to open
--     the file;
--
--     * 'ParsingFailed' when specified archive is something this library
--     cannot parse (this includes multi-disk archives, for example).
--
-- Please note that entries with invalid (non-portable) file names may be
-- missing in the list of entries. Files that are compressed with
-- unsupported compression methods are skipped as well. Also, if several
-- entries would collide on some operating systems (such as Windows, because
-- of its case-insensitivity), only one of them will be available, because
-- 'EntrySelector' is case-insensitive. These are the consequences of the
-- design decision to make it impossible to create non-portable archives
-- with this library.
withArchive ::
  (MonadIO m) =>
  -- | Location of the archive to work with
  FilePath ->
  -- | Actions on that archive
  ZipArchive a ->
  m a
withArchive path m = liftIO $ do
  apath <- canonicalizePath path
  (desc, entries) <- liftIO (I.scanArchive apath)
  let st =
        ZipState
          { zsFilePath = apath,
            zsEntries = entries,
            zsArchive = desc,
            zsActions = S.empty
          }
      action = unZipArchive (m <* commit)
  liftIO (evalStateT action st)

----------------------------------------------------------------------------
-- Retrieving 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)

-- | Check whether the specified entry exists in the archive. This is a
-- simple shortcut defined as:
--
-- > doesEntryExist s = M.member s <$> getEntries
doesEntryExist :: EntrySelector -> ZipArchive Bool
doesEntryExist s = M.member s <$> getEntries

-- | Get 'EntryDescription' for a specified entry. This is a simple shortcut
-- defined as:
--
-- > getEntryDesc s = M.lookup s <$> getEntries
getEntryDesc :: EntrySelector -> ZipArchive (Maybe EntryDescription)
getEntryDesc s = M.lookup s <$> getEntries

-- | Get contents of a specific archive entry as a strict 'ByteString'. It's
-- not recommended to use this on big entries, because it will suck out a
-- lot of memory. For big entries, use conduits: 'sourceEntry'.
--
-- Throws: 'EntryDoesNotExist'.
getEntry ::
  -- | Selector that identifies archive entry
  EntrySelector ->
  -- | Contents of the entry
  ZipArchive ByteString
getEntry s = sourceEntry s (CL.foldMap id)

-- | Get an entry source.
--
-- Throws: 'EntryDoesNotExist'.
--
-- @since 0.1.3
getEntrySource ::
  (PrimMonad m, MonadThrow m, MonadResource m) =>
  -- | Selector that identifies archive entry
  EntrySelector ->
  ZipArchive (ConduitT () ByteString m ())
getEntrySource s = do
  path <- getFilePath
  mdesc <- M.lookup s <$> getEntries
  case mdesc of
    Nothing -> throwM (EntryDoesNotExist path s)
    Just desc -> return (I.sourceEntry path desc True)

-- | Stream contents of an archive entry to the given 'Sink'.
--
-- Throws: 'EntryDoesNotExist'.
sourceEntry ::
  -- | Selector that identifies the archive entry
  EntrySelector ->
  -- | Sink where to stream entry contents
  ConduitT ByteString Void (ResourceT IO) a ->
  -- | Contents of the entry (if found)
  ZipArchive a
sourceEntry s sink = do
  src <- getEntrySource s
  (liftIO . C.runConduitRes) (src .| sink)

-- | Save a specific archive entry as a file in the file system.
--
-- Throws: 'EntryDoesNotExist'.
saveEntry ::
  -- | Selector that identifies the archive entry
  EntrySelector ->
  -- | Where to save the file
  FilePath ->
  ZipArchive ()
saveEntry s path = do
  sourceEntry s (CB.sinkFile path)
  med <- getEntryDesc s
  forM_ med (liftIO . setModificationTime path . edModTime)

-- | Calculate CRC32 check sum and compare it with the value read from the
-- archive. The function returns 'True' when the check sums are the
-- same—that is, the data is not corrupted.
--
-- Throws: 'EntryDoesNotExist'.
checkEntry ::
  -- | 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
  -- 'sourceEntry' would have thrown 'EntryDoesNotExist' already.
  return (calculated == given)

-- | 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
  unless (null selectors) $ do
    dir <- liftIO (makeAbsolute dir')
    liftIO (createDirectoryIfMissing True dir)
    let dirs = E.map (FP.takeDirectory . (dir </>) . unEntrySelector) selectors
    forM_ dirs (liftIO . createDirectoryIfMissing True)
    forM_ selectors $ \s ->
      saveEntry s (dir </> unEntrySelector s)

-- | Get the archive comment.
getArchiveComment :: ZipArchive (Maybe Text)
getArchiveComment = adComment <$> getArchiveDescription

-- | Get the archive description record.
getArchiveDescription :: ZipArchive ArchiveDescription
getArchiveDescription = ZipArchive (gets zsArchive)

----------------------------------------------------------------------------
-- Modifying archive

-- | Add a new entry to the archive given its contents in binary form.
addEntry ::
  -- | The compression method to use
  CompressionMethod ->
  -- | Entry contents
  ByteString ->
  -- | 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 ::
  -- | The compression method to use
  CompressionMethod ->
  -- | Source of entry contents
  ConduitT () ByteString (ResourceT IO) () ->
  -- | 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 ::
  -- | The compression method to use
  CompressionMethod ->
  -- | Name of the entry to add
  EntrySelector ->
  -- | Path to the file to add
  FilePath ->
  ZipArchive ()
loadEntry t s path = do
  apath <- liftIO (canonicalizePath path)
  modTime <- liftIO (getModificationTime path)
  let src = CB.sourceFile apath
  addPending (I.SinkEntry t src s)
  addPending (I.SetModTime modTime s)

#ifndef mingw32_HOST_OS
  status <- liftIO $ Unix.getFileStatus path
  setExternalFileAttrs (Unix.fromFileMode (Unix.fileMode status)) s
#endif

-- | Copy an entry “as is” from another zip archive. If the entry does not
-- exist in that archive, 'EntryDoesNotExist' will be thrown.
copyEntry ::
  -- | Path to the archive to copy from
  FilePath ->
  -- | Name of the entry (in the source archive) to copy
  EntrySelector ->
  -- | 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 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 ::
  -- | The compression method to use
  CompressionMethod ->
  -- | How to get the 'EntrySelector' from a path relative to the root of
  -- the directory we pack
  (FilePath -> ZipArchive EntrySelector) ->
  -- | Path to the directory to add
  FilePath ->
  ZipArchive ()
packDirRecur t f = packDirRecur' t f (const $ return ())

-- | The same as 'packDirRecur' but allows us to perform modifying actions
-- on the created entities as we go.
--
-- @since 1.5.0
packDirRecur' ::
  -- | The compression method to use
  CompressionMethod ->
  -- | 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 the directory to add
  FilePath ->
  ZipArchive ()
packDirRecur' t f patch path = do
  files <- liftIO (listDirRecur path)
  forM_ files $ \x -> do
    s <- f x
    loadEntry t s (path </> x)
    patch s

-- | Rename an entry in the archive. If the entry does not exist, nothing
-- will happen.
renameEntry ::
  -- | The original entry name
  EntrySelector ->
  -- | The new entry name
  EntrySelector ->
  ZipArchive ()
renameEntry old new = addPending (I.RenameEntry old new)

-- | Delete an entry from the archive, if it does not exist, nothing will
-- happen.
deleteEntry :: EntrySelector -> ZipArchive ()
deleteEntry s = addPending (I.DeleteEntry s)

-- | Change compression method of an entry, if it does not exist, nothing
-- will happen.
recompress ::
  -- | The new compression method
  CompressionMethod ->
  -- | Name of the entry to re-compress
  EntrySelector ->
  ZipArchive ()
recompress t s = addPending (I.Recompress t s)

-- | Set an entry comment, if that entry does not exist, nothing will
-- happen. Note that if binary representation of the comment is longer than
-- 65535 bytes, it will be truncated on writing.
setEntryComment ::
  -- | Text of the comment
  Text ->
  -- | Name of the entry to comment on
  EntrySelector ->
  ZipArchive ()
setEntryComment text s = addPending (I.SetEntryComment text s)

-- | Delete an entry's comment, if that entry does not exist, nothing will
-- happen.
deleteEntryComment :: EntrySelector -> ZipArchive ()
deleteEntryComment s = addPending (I.DeleteEntryComment s)

-- | 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 the entry to modify
  EntrySelector ->
  ZipArchive ()
setModTime time s = addPending (I.SetModTime time s)

-- | Add an extra field. The specified entry may be missing, in that case
-- this action has no effect.
addExtraField ::
  -- | Tag (header id) of the extra field to add
  Word16 ->
  -- | Body of the field
  ByteString ->
  -- | Name of the entry to modify
  EntrySelector ->
  ZipArchive ()
addExtraField n b s = addPending (I.AddExtraField n b s)

-- | 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 the extra field to delete
  Word16 ->
  -- | Name of the entry to modify
  EntrySelector ->
  ZipArchive ()
deleteExtraField n s = addPending (I.DeleteExtraField n s)

-- | Set external file attributes. This function can be used to set file
-- permissions.
--
-- See also: "Codec.Archive.Zip.Unix".
--
-- @since 1.2.0
setExternalFileAttrs ::
  -- | External file attributes
  Word32 ->
  -- | Name of the entry to modify
  EntrySelector ->
  ZipArchive ()
setExternalFileAttrs attrs s =
  addPending (I.SetExternalFileAttributes attrs s)

-- | Perform an action on every entry in the archive.
forEntries ::
  -- | The action to perform
  (EntrySelector -> ZipArchive ()) ->
  ZipArchive ()
forEntries action = getEntries >>= mapM_ action . M.keysSet

-- | Set the comment of the entire archive.
setArchiveComment :: Text -> ZipArchive ()
setArchiveComment text = addPending (I.SetArchiveComment text)

-- | Delete the archive's comment if it's present.
deleteArchiveComment :: ZipArchive ()
deleteArchiveComment = addPending I.DeleteArchiveComment

-- | Undo the changes to a specific archive entry.
undoEntryChanges :: EntrySelector -> ZipArchive ()
undoEntryChanges s = modifyActions f
  where
    f = S.filter ((/= Just s) . I.targetEntry)

-- | Undo the changes to the archive as a whole (archive's comment).
undoArchiveChanges :: ZipArchive ()
undoArchiveChanges = modifyActions f
  where
    f = S.filter ((/= Nothing) . I.targetEntry)

-- | Undo all changes made in this editing session.
undoAll :: ZipArchive ()
undoAll = modifyActions (const S.empty)

-- | 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 '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
  odesc <- getArchiveDescription
  oentries <- getEntries
  actions <- getPending
  exists <- liftIO (doesFileExist file)
  unless (S.null actions && exists) $ do
    liftIO (I.commit file odesc oentries actions)
    -- 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.
    (ndesc, nentries) <- liftIO (I.scanArchive file)
    ZipArchive . modify $ \st ->
      st
        { zsEntries = nentries,
          zsArchive = ndesc,
          zsActions = S.empty
        }

----------------------------------------------------------------------------
-- Helpers

-- | Get the path of the actual archive file from inside of 'ZipArchive'
-- monad.
getFilePath :: ZipArchive FilePath
getFilePath = ZipArchive (gets zsFilePath)

-- | Get the collection of pending actions.
getPending :: ZipArchive (Seq I.PendingAction)
getPending = ZipArchive (gets zsActions)

-- | Modify the collection of pending actions.
modifyActions :: (Seq I.PendingAction -> Seq I.PendingAction) -> ZipArchive ()
modifyActions f = ZipArchive (modify g)
  where
    g st = st {zsActions = f (zsActions st)}

-- | Add a new action to the list of pending actions.
addPending :: I.PendingAction -> ZipArchive ()
addPending a = modifyActions (|> a)

-- | Recursively list a directory. Do not return paths to empty directories.
listDirRecur :: FilePath -> IO [FilePath]
listDirRecur path = DList.toList <$> go ""
  where
    go adir = do
      let cdir = path </> adir
      raw <- listDirectory cdir
      fmap mconcat . forM raw $ \case
        "" -> return mempty
        "." -> return mempty
        ".." -> return mempty
        x -> do
          let fullx = cdir </> x
              adir' = adir </> x
          isFile <- doesFileExist fullx
          isDir <- doesDirectoryExist fullx
          if isFile
            then return (DList.singleton adir')
            else
              if isDir
                then go adir'
                else return mempty

-- | Perform an action ignoring IO exceptions it may throw.
ignoringAbsence :: IO () -> IO ()
ignoringAbsence io = catchJust select io handler
  where
    select e = if isDoesNotExistError e then Just e else Nothing
    handler = const (return ())