| 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 -> ArchiveM ()
- entriesToFileZip :: Foldable t => FilePath -> t Entry -> ArchiveM ()
- entriesToFile7Zip :: Foldable t => FilePath -> t Entry -> ArchiveM ()
- entriesToBS :: Foldable t => t Entry -> ByteString
- entriesToBS7zip :: Foldable t => t Entry -> ByteString
- entriesToBSzip :: Foldable t => t Entry -> ByteString
- entriesToBSL :: Foldable t => t Entry -> ByteString
- entriesToBSLzip :: Foldable t => t Entry -> ByteString
- entriesToBSL7zip :: Foldable t => t Entry -> ByteString
- readArchiveFile :: FilePath -> ArchiveM [Entry]
- readArchiveBS :: ByteString -> Either ArchiveResult [Entry]
- readArchiveBSL :: ByteString -> Either ArchiveResult [Entry]
- packFiles :: Traversable t => t FilePath -> IO ByteString
- packFilesZip :: Traversable t => t FilePath -> IO ByteString
- packFiles7zip :: 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 ()
- data ArchiveResult
- data Entry = Entry {
- filepath :: !FilePath
- content :: !EntryContent
- permissions :: !Permissions
- ownership :: !Ownership
- time :: !(Maybe ModTime)
- data Symlink
- data EntryContent
- 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)
- 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 -> 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 -> ArchiveM () Source #
Write some entries to a file, creating a zip archive.
Since: 1.0.0.0
entriesToFile7Zip :: Foldable t => FilePath -> t Entry -> ArchiveM () Source #
Write some entries to a file, creating a .7z archive.
Since: 1.0.0.0
entriesToBS :: Foldable t => t Entry -> ByteString Source #
Returns a ByteString containing a tar archive with the Entrys
Since: 1.0.0.0
entriesToBS7zip :: Foldable t => t Entry -> ByteString Source #
Returns a ByteString containing a .7z archive with the Entrys
Since: 1.0.0.0
entriesToBSzip :: Foldable t => t Entry -> ByteString Source #
Returns a ByteString containing a zip archive with the Entrys
Since: 1.0.0.0
entriesToBSL :: Foldable t => t Entry -> ByteString Source #
In general, this will be more efficient than entriesToBS
Since: 1.0.5.0
entriesToBSLzip :: Foldable t => t Entry -> ByteString Source #
Since: 1.0.5.0
entriesToBSL7zip :: Foldable t => t Entry -> ByteString Source #
Since: 1.0.5.0
readArchiveFile :: FilePath -> ArchiveM [Entry] 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] 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] 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
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
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
Concrete (Haskell) types
data ArchiveResult Source #
Constructors
| ArchiveFatal | |
| ArchiveFailed | |
| ArchiveWarn | |
| ArchiveRetry | |
| ArchiveOk | |
| ArchiveEOF |
Instances
Constructors
| Entry | |
Fields
| |
Constructors
| SymlinkUndefined | |
| SymlinkFile | |
| SymlinkDirectory |
Instances
| Enum Symlink Source # | |
| Eq Symlink Source # | |
| Show Symlink Source # | |
data EntryContent Source #
Constructors
| NormalFile !ByteString | |
| Directory | |
| Symlink !FilePath !Symlink | |
| Hardlink !FilePath |
Instances
| Eq EntryContent Source # | |
Defined in Codec.Archive.Types | |
| Show EntryContent Source # | |
Defined in Codec.Archive.Types Methods showsPrec :: Int -> EntryContent -> ShowS # show :: EntryContent -> String # showList :: [EntryContent] -> ShowS # | |
type Permissions = CMode Source #
Archive monad
runArchiveM :: ArchiveM a -> IO (Either ArchiveResult a) Source #
Permissions helpers
executablePermissions :: Permissions Source #
Also used for directories