zip-0.1.10: Operations on zip archives

Copyright© 2016–2017 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov@openmailbox.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Codec.Archive.Zip.Type

Contents

Description

Types used by the package. You don't usually need to import this module, because Codec.Archive.Zip re-exports everything you may need, import that module instead.

Synopsis

Entry selector

data EntrySelector Source #

This data type serves for naming and selection of archive entries. It can be created only with the help of the smart constructor mkEntrySelector, and it's the only “key” that can be used to select files in archive or to name new files.

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 it is recommended in the specification). On the other hand, in can be rendered as ordinary relative file path in OS-specific format, when needed.

Instances

Eq EntrySelector Source # 
Data EntrySelector Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EntrySelector -> c EntrySelector #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EntrySelector #

toConstr :: EntrySelector -> Constr #

dataTypeOf :: EntrySelector -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EntrySelector) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EntrySelector) #

gmapT :: (forall b. Data b => b -> b) -> EntrySelector -> EntrySelector #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EntrySelector -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EntrySelector -> r #

gmapQ :: (forall d. Data d => d -> u) -> EntrySelector -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EntrySelector -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EntrySelector -> m EntrySelector #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EntrySelector -> m EntrySelector #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EntrySelector -> m EntrySelector #

Ord EntrySelector Source # 
Show EntrySelector Source # 
Generic EntrySelector Source # 

Associated Types

type Rep EntrySelector :: * -> * #

type Rep EntrySelector Source # 
type Rep EntrySelector = D1 (MetaData "EntrySelector" "Codec.Archive.Zip.Type" "zip-0.1.10-25VzKDgLqXNJGXynIdbCNk" True) (C1 (MetaCons "EntrySelector" PrefixI True) (S1 (MetaSel (Just Symbol "unES") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (CI String)))))

mkEntrySelector :: MonadThrow m => Path Rel File -> m EntrySelector Source #

Create an EntrySelector from Path Rel File. To avoid problems with distribution of the archive, characters that some operating systems do not expect in paths are not allowed. Proper paths should pass these checks:

  • isValid
  • isValid
  • binary representation of normalized path should be not longer than 65535 bytes

This function can throw EntrySelectorException exception.

unEntrySelector :: EntrySelector -> Path Rel File Source #

Make a relative path from EntrySelector. Every EntrySelector produces single Path Rel File that corresponds to it.

getEntryName :: EntrySelector -> Text Source #

Get entry name given EntrySelector in the from that is suitable for writing to file header.

Entry description

data EntryDescription Source #

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 representation can be built given this date structure and actual archive contents.

Constructors

EntryDescription 

Fields

data CompressionMethod Source #

Supported compression methods.

Constructors

Store

Store file uncompressed

Deflate

Deflate

BZip2

Compressed using BZip2 algorithm

Instances

Bounded CompressionMethod Source # 
Enum CompressionMethod Source # 
Eq CompressionMethod Source # 
Data CompressionMethod Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompressionMethod -> c CompressionMethod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompressionMethod #

toConstr :: CompressionMethod -> Constr #

dataTypeOf :: CompressionMethod -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CompressionMethod) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompressionMethod) #

gmapT :: (forall b. Data b => b -> b) -> CompressionMethod -> CompressionMethod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompressionMethod -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompressionMethod -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompressionMethod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompressionMethod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompressionMethod -> m CompressionMethod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompressionMethod -> m CompressionMethod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompressionMethod -> m CompressionMethod #

Ord CompressionMethod Source # 
Read CompressionMethod Source # 
Show CompressionMethod Source # 

Archive desrciption

data ArchiveDescription Source #

Information about archive as a whole.

Constructors

ArchiveDescription 

Fields

Instances

Eq ArchiveDescription Source # 
Data ArchiveDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArchiveDescription -> c ArchiveDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArchiveDescription #

toConstr :: ArchiveDescription -> Constr #

dataTypeOf :: ArchiveDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ArchiveDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArchiveDescription) #

gmapT :: (forall b. Data b => b -> b) -> ArchiveDescription -> ArchiveDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArchiveDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArchiveDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArchiveDescription -> m ArchiveDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveDescription -> m ArchiveDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveDescription -> m ArchiveDescription #

Ord ArchiveDescription Source # 
Read ArchiveDescription Source # 
Show ArchiveDescription Source # 

Exceptions