libarchive-3.0.3.1: Haskell interface to libarchive
Safe HaskellNone
LanguageHaskell2010

Codec.Archive

Description

This module contains higher-level functions for working with archives in Haskell. See Codec.Archive.Foreign for direct bindings to libarchive.

Synopsis

High-level functionality

unpackToDir Source #

Arguments

:: FilePath

Directory to unpack in

-> ByteString

ByteString containing archive

-> ArchiveM () 

unpackToDirLazy Source #

Arguments

:: FilePath

Directory to unpack in

-> ByteString

ByteString containing archive

-> ArchiveM () 

In general, this will be more efficient than unpackToDir

Since: 1.0.4.0

unpackArchive Source #

Arguments

:: FilePath

Filepath pointing to archive

-> FilePath

Dirctory to unpack in

-> ArchiveM () 

This is more efficient than

unpackToDir "llvm" =<< BS.readFile "llvm.tar"

entriesToFile :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM () Source #

Write some entries to a file, creating a tar archive. This is more efficient than

BS.writeFile "file.tar" (entriesToBS entries)

Since: 1.0.0.0

entriesToFileZip :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM () Source #

Write some entries to a file, creating a zip archive.

Since: 1.0.0.0

entriesToFile7Zip :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM () Source #

Write some entries to a file, creating a .7z archive.

Since: 1.0.0.0

entriesToFileCpio :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM () Source #

Write some entries to a file, creating a .cpio archive.

Since: 2.2.3.0

entriesToFileXar :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM () Source #

Write some entries to a file, creating a .xar archive.

Since: 2.2.4.0

entriesToFileShar :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM () Source #

Write some entries to a file, creating a .shar archive.

Since: 3.0.0.0

entriesToBS :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #

Returns a ByteString containing a tar archive with the Entrys

Since: 1.0.0.0

entriesToBS7zip :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #

Returns a ByteString containing a .7z archive with the Entrys

Since: 1.0.0.0

entriesToBSzip :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #

Returns a ByteString containing a zip archive with the Entrys

Since: 1.0.0.0

entriesToBSL :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #

In general, this will be more efficient than entriesToBS

Since: 1.0.5.0

entriesToBSLXar :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #

Won't work when built with -system-libarchive or when libarchive is not built with zlib support.

Since: 2.2.4.0

readArchiveFile :: FilePath -> ArchiveM [Entry FilePath ByteString] Source #

Read an archive from a file. The format of the archive is automatically detected.

Since: 1.0.0.0

readArchiveBS :: ByteString -> Either ArchiveResult [Entry FilePath ByteString] Source #

Read an archive contained in a ByteString. The format of the archive is automatically detected.

Since: 1.0.0.0

readArchiveBSL :: ByteString -> Either ArchiveResult [Entry FilePath ByteString] Source #

Read an archive lazily. The format of the archive is automatically detected.

In general, this will be more efficient than readArchiveBS

Since: 1.0.4.0

packFiles Source #

Arguments

:: Traversable t 
=> t FilePath

Filepaths relative to the current directory

-> IO ByteString 

Pack files into a tar archive. This will be more efficient than

BSL.writeFile fp . entriesToBSL

Since: 2.0.0.0

packToFile Source #

Arguments

:: Traversable t 
=> FilePath

.tar archive to be created

-> t FilePath

Files to include

-> ArchiveM () 

Since: 2.0.0.0

packToFileZip :: Traversable t => FilePath -> t FilePath -> ArchiveM () Source #

Since: 2.0.0.0

packToFile7Zip :: Traversable t => FilePath -> t FilePath -> ArchiveM () Source #

Since: 2.0.0.0

packToFileCpio :: Traversable t => FilePath -> t FilePath -> ArchiveM () Source #

Since: 2.2.3.0

packToFileXar :: Traversable t => FilePath -> t FilePath -> ArchiveM () Source #

Since: 2.2.4.0

packToFileShar :: Traversable t => FilePath -> t FilePath -> ArchiveM () Source #

Since: 3.0.0.0

Concrete (Haskell) types

data ArchiveResult Source #

Instances

Instances details
Enum ArchiveResult Source # 
Instance details

Defined in Codec.Archive.Types.Foreign

Eq ArchiveResult Source # 
Instance details

Defined in Codec.Archive.Types.Foreign

Show ArchiveResult Source # 
Instance details

Defined in Codec.Archive.Types.Foreign

Generic ArchiveResult Source # 
Instance details

Defined in Codec.Archive.Types.Foreign

Associated Types

type Rep ArchiveResult :: Type -> Type #

Exception ArchiveResult Source # 
Instance details

Defined in Codec.Archive.Types.Foreign

NFData ArchiveResult Source # 
Instance details

Defined in Codec.Archive.Types.Foreign

Methods

rnf :: ArchiveResult -> () #

type Rep ArchiveResult Source # 
Instance details

Defined in Codec.Archive.Types.Foreign

type Rep ArchiveResult = D1 ('MetaData "ArchiveResult" "Codec.Archive.Types.Foreign" "libarchive-3.0.3.1-inplace" 'False) ((C1 ('MetaCons "ArchiveFatal" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArchiveFailed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArchiveWarn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ArchiveRetry" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArchiveOk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArchiveEOF" 'PrefixI 'False) (U1 :: Type -> Type))))

data Entry fp e Source #

e is the type of entry contents, for instance ByteString

fp is the type of file paths, for instance FilePath

Constructors

Entry 

Instances

Instances details
(Eq fp, Eq e) => Eq (Entry fp e) Source # 
Instance details

Defined in Codec.Archive.Types

Methods

(==) :: Entry fp e -> Entry fp e -> Bool #

(/=) :: Entry fp e -> Entry fp e -> Bool #

(Ord fp, Ord e) => Ord (Entry fp e) Source # 
Instance details

Defined in Codec.Archive.Types

Methods

compare :: Entry fp e -> Entry fp e -> Ordering #

(<) :: Entry fp e -> Entry fp e -> Bool #

(<=) :: Entry fp e -> Entry fp e -> Bool #

(>) :: Entry fp e -> Entry fp e -> Bool #

(>=) :: Entry fp e -> Entry fp e -> Bool #

max :: Entry fp e -> Entry fp e -> Entry fp e #

min :: Entry fp e -> Entry fp e -> Entry fp e #

(Show fp, Show e) => Show (Entry fp e) Source # 
Instance details

Defined in Codec.Archive.Types

Methods

showsPrec :: Int -> Entry fp e -> ShowS #

show :: Entry fp e -> String #

showList :: [Entry fp e] -> ShowS #

data EntryContent fp e Source #

Constructors

NormalFile e 
Directory 
Symlink !fp !Symlink 
Hardlink !fp 

Instances

Instances details
(Eq e, Eq fp) => Eq (EntryContent fp e) Source # 
Instance details

Defined in Codec.Archive.Types

Methods

(==) :: EntryContent fp e -> EntryContent fp e -> Bool #

(/=) :: EntryContent fp e -> EntryContent fp e -> Bool #

(Ord e, Ord fp) => Ord (EntryContent fp e) Source # 
Instance details

Defined in Codec.Archive.Types

Methods

compare :: EntryContent fp e -> EntryContent fp e -> Ordering #

(<) :: EntryContent fp e -> EntryContent fp e -> Bool #

(<=) :: EntryContent fp e -> EntryContent fp e -> Bool #

(>) :: EntryContent fp e -> EntryContent fp e -> Bool #

(>=) :: EntryContent fp e -> EntryContent fp e -> Bool #

max :: EntryContent fp e -> EntryContent fp e -> EntryContent fp e #

min :: EntryContent fp e -> EntryContent fp e -> EntryContent fp e #

(Show e, Show fp) => Show (EntryContent fp e) Source # 
Instance details

Defined in Codec.Archive.Types

Methods

showsPrec :: Int -> EntryContent fp e -> ShowS #

show :: EntryContent fp e -> String #

showList :: [EntryContent fp e] -> ShowS #

data Ownership Source #

Constructors

Ownership 

Fields

Instances

Instances details
Eq Ownership Source # 
Instance details

Defined in Codec.Archive.Types

Ord Ownership Source # 
Instance details

Defined in Codec.Archive.Types

Show Ownership Source # 
Instance details

Defined in Codec.Archive.Types

type ModTime = (CTime, CLong) Source #

Pair of a UNIX time stamp and a nanosecond fractional part.

type Id = Int64 Source #

A user or group ID

Archive monad

throwArchiveM :: ArchiveM a -> IO a Source #

Throws ArchiveResult on error.

Since: 2.2.5.0

Permissions helpers

executablePermissions :: Permissions Source #

Also used for directories