| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- unpackToDir :: FilePath -> ByteString -> ArchiveM ()
 - unpackToDirLazy :: FilePath -> ByteString -> ArchiveM ()
 - unpackArchive :: FilePath -> FilePath -> ArchiveM ()
 - entriesToFile :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM ()
 - entriesToFileZip :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM ()
 - entriesToFile7Zip :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM ()
 - entriesToFileCpio :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM ()
 - entriesToFileXar :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM ()
 - entriesToFileShar :: Foldable t => FilePath -> t (Entry FilePath ByteString) -> ArchiveM ()
 - entriesToBS :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBS7zip :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBSzip :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBSL :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBSLzip :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBSL7zip :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBSLCpio :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBSLXar :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - entriesToBSLShar :: Foldable t => t (Entry FilePath ByteString) -> ByteString
 - readArchiveFile :: FilePath -> ArchiveM [Entry FilePath ByteString]
 - readArchiveBS :: ByteString -> Either ArchiveResult [Entry FilePath ByteString]
 - readArchiveBSL :: ByteString -> Either ArchiveResult [Entry FilePath ByteString]
 - packFiles :: Traversable t => t FilePath -> IO ByteString
 - packFilesZip :: Traversable t => t FilePath -> IO ByteString
 - packFiles7zip :: Traversable t => t FilePath -> IO ByteString
 - packFilesCpio :: Traversable t => t FilePath -> IO ByteString
 - packFilesXar :: Traversable t => t FilePath -> IO ByteString
 - packFilesShar :: Traversable t => t FilePath -> IO ByteString
 - packToFile :: Traversable t => FilePath -> t FilePath -> ArchiveM ()
 - packToFileZip :: Traversable t => FilePath -> t FilePath -> ArchiveM ()
 - packToFile7Zip :: Traversable t => FilePath -> t FilePath -> ArchiveM ()
 - packToFileCpio :: Traversable t => FilePath -> t FilePath -> ArchiveM ()
 - packToFileXar :: Traversable t => FilePath -> t FilePath -> ArchiveM ()
 - packToFileShar :: Traversable t => FilePath -> t FilePath -> ArchiveM ()
 - data ArchiveResult
 - data ArchiveEntryDigest
 - data Entry fp e = Entry {
- filepath :: !fp
 - content :: EntryContent fp e
 - permissions :: !Permissions
 - ownership :: !Ownership
 - time :: !(Maybe ModTime)
 
 - data Symlink
 - data EntryContent fp e
- = NormalFile e
 - | Directory
 - | Symlink !fp !Symlink
 - | Hardlink !fp
 
 - data Ownership = Ownership {}
 - type Permissions = CMode
 - type ModTime = (CTime, CLong)
 - type Id = Int64
 - type ArchiveM = ExceptT ArchiveResult IO
 - runArchiveM :: ArchiveM a -> IO (Either ArchiveResult a)
 - throwArchiveM :: ArchiveM a -> IO a
 - standardPermissions :: Permissions
 - executablePermissions :: Permissions
 
High-level functionality
Arguments
| :: FilePath | Directory to unpack in  | 
| -> ByteString | 
  | 
| -> ArchiveM () | 
Arguments
| :: FilePath | Directory to unpack in  | 
| -> ByteString | 
  | 
| -> ArchiveM () | 
In general, this will be more efficient than unpackToDir
Since: 1.0.4.0
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
entriesToBSLzip :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #
Since: 1.0.5.0
entriesToBSL7zip :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #
Since: 1.0.5.0
entriesToBSLCpio :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #
Since: 2.2.3.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
entriesToBSLShar :: Foldable t => t (Entry FilePath ByteString) -> ByteString Source #
Since: 3.0.0.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
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
packFilesZip :: Traversable t => t FilePath -> IO ByteString Source #
Since: 2.0.0.0
packFiles7zip :: Traversable t => t FilePath -> IO ByteString Source #
Since: 2.0.0.0
packFilesCpio :: Traversable t => t FilePath -> IO ByteString Source #
Since: 2.2.3.0
packFilesXar :: Traversable t => t FilePath -> IO ByteString Source #
Since: 2.2.4.0
packFilesShar :: Traversable t => t FilePath -> IO ByteString Source #
Since: 3.0.0.0
Arguments
| :: Traversable t | |
| => FilePath | 
  | 
| -> 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 #
Constructors
| ArchiveFatal | |
| ArchiveFailed | |
| ArchiveWarn | |
| ArchiveRetry | |
| ArchiveOk | |
| ArchiveEOF | 
Instances
data ArchiveEntryDigest Source #
Constructors
| ArchiveEntryDigestMD5 | |
| ArchiveEntryDigestRMD160 | |
| ArchiveEntryDigestSHA1 | |
| ArchiveEntryDigestSHA256 | |
| ArchiveEntryDigestSHA384 | |
| ArchiveEntryDigestSHA512 | 
Instances
| Enum ArchiveEntryDigest Source # | |
Defined in Codec.Archive.Types.Foreign Methods succ :: ArchiveEntryDigest -> ArchiveEntryDigest # pred :: ArchiveEntryDigest -> ArchiveEntryDigest # toEnum :: Int -> ArchiveEntryDigest # fromEnum :: ArchiveEntryDigest -> Int # enumFrom :: ArchiveEntryDigest -> [ArchiveEntryDigest] # enumFromThen :: ArchiveEntryDigest -> ArchiveEntryDigest -> [ArchiveEntryDigest] # enumFromTo :: ArchiveEntryDigest -> ArchiveEntryDigest -> [ArchiveEntryDigest] # enumFromThenTo :: ArchiveEntryDigest -> ArchiveEntryDigest -> ArchiveEntryDigest -> [ArchiveEntryDigest] #  | |
e is the type of entry contents, for instance ByteString
fp is the type of file paths, for instance FilePath
Constructors
| Entry | |
Fields 
  | |
Instances
| (Eq fp, Eq e) => Eq (Entry fp e) Source # | |
| (Ord fp, Ord e) => Ord (Entry fp e) Source # | |
Defined in Codec.Archive.Types  | |
| (Show fp, Show e) => Show (Entry fp e) Source # | |
Constructors
| SymlinkUndefined | |
| SymlinkFile | |
| SymlinkDirectory | 
Instances
| Enum Symlink Source # | |
| Eq Symlink Source # | |
| Ord Symlink Source # | |
Defined in Codec.Archive.Types.Foreign  | |
| Show Symlink Source # | |
data EntryContent fp e Source #
Constructors
| NormalFile e | |
| Directory | |
| Symlink !fp !Symlink | |
| Hardlink !fp | 
Instances
| (Eq e, Eq fp) => Eq (EntryContent fp e) Source # | |
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 # | |
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 # | |
Defined in Codec.Archive.Types Methods showsPrec :: Int -> EntryContent fp e -> ShowS # show :: EntryContent fp e -> String # showList :: [EntryContent fp e] -> ShowS #  | |
Constructors
| Ownership | |
Instances
| Eq Ownership Source # | |
| Ord Ownership Source # | |
| Show Ownership Source # | |
type Permissions = CMode Source #
Archive monad
runArchiveM :: ArchiveM a -> IO (Either ArchiveResult a) Source #
throwArchiveM :: ArchiveM a -> IO a Source #
Throws ArchiveResult on error.
Since: 2.2.5.0
Permissions helpers
executablePermissions :: Permissions Source #
Also used for directories