tar-0.6.2.0: Reading, writing and manipulating ".tar" archive files.
Copyright(c) 2007 Bjorn Bringert
2008 Andrea Vezzosi
2008-2009 Duncan Coutts
LicenseBSD3
Maintainerduncan@community.haskell.org
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Codec.Archive.Tar.Entry

Description

Types and functions to manipulate tar entries.

While the Codec.Archive.Tar module provides only the simple high level API, this module provides full access to the details of tar entries. This lets you inspect all the meta-data, construct entries and handle error cases more precisely.

This module uses common names and so is designed to be imported qualified:

import qualified Codec.Archive.Tar       as Tar
import qualified Codec.Archive.Tar.Entry as Tar
Synopsis

Tar entry and associated types

data GenEntry tarPath linkTarget Source #

Polymorphic tar archive entry. High-level interfaces commonly work with GenEntry FilePath FilePath, while low-level ones use GenEntry TarPath LinkTarget.

Since: 0.6.0.0

Constructors

Entry 

Fields

Instances

Instances details
(Show tarPath, Show linkTarget) => Show (GenEntry tarPath linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

showsPrec :: Int -> GenEntry tarPath linkTarget -> ShowS #

show :: GenEntry tarPath linkTarget -> String #

showList :: [GenEntry tarPath linkTarget] -> ShowS #

(NFData tarPath, NFData linkTarget) => NFData (GenEntry tarPath linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

rnf :: GenEntry tarPath linkTarget -> () #

(Eq tarPath, Eq linkTarget) => Eq (GenEntry tarPath linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

(==) :: GenEntry tarPath linkTarget -> GenEntry tarPath linkTarget -> Bool #

(/=) :: GenEntry tarPath linkTarget -> GenEntry tarPath linkTarget -> Bool #

type Entry = GenEntry TarPath LinkTarget Source #

Monomorphic tar archive entry, ready for serialization / deserialization.

entryPath :: GenEntry TarPath linkTarget -> FilePath Source #

Low-level function to get a native FilePath of the file or directory within the archive, not accounting for long names. It's likely that you want to apply decodeLongNames and use entryTarPath afterwards instead of entryPath.

data GenEntryContent linkTarget Source #

Polymorphic content of a tar archive entry. High-level interfaces commonly work with GenEntryContent FilePath, while low-level ones use GenEntryContent LinkTarget.

Portable archives should contain only NormalFile and Directory.

Since: 0.6.0.0

Instances

Instances details
Show linkTarget => Show (GenEntryContent linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

showsPrec :: Int -> GenEntryContent linkTarget -> ShowS #

show :: GenEntryContent linkTarget -> String #

showList :: [GenEntryContent linkTarget] -> ShowS #

NFData linkTarget => NFData (GenEntryContent linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

rnf :: GenEntryContent linkTarget -> () #

Eq linkTarget => Eq (GenEntryContent linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

(==) :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> Bool #

(/=) :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> Bool #

Ord linkTarget => Ord (GenEntryContent linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

compare :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> Ordering #

(<) :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> Bool #

(<=) :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> Bool #

(>) :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> Bool #

(>=) :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> Bool #

max :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> GenEntryContent linkTarget #

min :: GenEntryContent linkTarget -> GenEntryContent linkTarget -> GenEntryContent linkTarget #

type EntryContent = GenEntryContent LinkTarget Source #

Monomorphic content of a tar archive entry, ready for serialization / deserialization.

data Ownership Source #

Ownership information for GenEntry.

Constructors

Ownership 

Fields

  • ownerName :: String

    The owner user name. Should be set to "" if unknown. Must not contain non-ASCII characters.

  • groupName :: String

    The owner group name. Should be set to "" if unknown. Must not contain non-ASCII characters.

  • ownerId :: !Int

    Numeric owner user id. Should be set to 0 if unknown.

  • groupId :: !Int

    Numeric owner group id. Should be set to 0 if unknown.

Instances

Instances details
Show Ownership Source # 
Instance details

Defined in Codec.Archive.Tar.Types

NFData Ownership Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

rnf :: Ownership -> () #

Eq Ownership Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Ord Ownership Source # 
Instance details

Defined in Codec.Archive.Tar.Types

type FileSize = Int64 Source #

File size in bytes.

type Permissions = FileMode Source #

Permissions information for GenEntry.

type EpochTime = Int64 Source #

The number of seconds since the UNIX epoch.

type DevMajor = Int Source #

Major device number.

type DevMinor = Int Source #

Minor device number.

type TypeCode = Char Source #

User-defined tar format expansion.

data Format Source #

There have been a number of extensions to the tar file format over the years. They all share the basic entry fields and put more meta-data in different extended headers.

Constructors

V7Format

This is the classic Unix V7 tar format. It does not support owner and group names, just numeric Ids. It also does not support device numbers.

UstarFormat

The "USTAR" format is an extension of the classic V7 format. It was later standardised by POSIX. It has some restrictions but is the most portable format.

GnuFormat

The GNU tar implementation also extends the classic V7 format, though in a slightly different way from the USTAR format. This is the only format supporting long file names.

Instances

Instances details
Show Format Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Eq Format Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Ord Format Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Constructing simple entry values

simpleEntry :: tarPath -> GenEntryContent linkTarget -> GenEntry tarPath linkTarget Source #

An entry with all default values except for the file name and type. It uses the portable USTAR/POSIX format (see UstarFormat).

You can use this as a basis and override specific fields, eg:

(emptyEntry name HardLink) { linkTarget = target }

fileEntry :: tarPath -> ByteString -> GenEntry tarPath linkTarget Source #

A tar entry for a file.

Entry fields such as file permissions and ownership have default values.

You can use this as a basis and override specific fields. For example if you need an executable file you could use:

(fileEntry name content) { fileMode = executableFileMode }

directoryEntry :: tarPath -> GenEntry tarPath linkTarget Source #

A tar entry for a directory.

Entry fields such as file permissions and ownership have default values.

longLinkEntry :: FilePath -> GenEntry TarPath linkTarget Source #

GNU extension to store a filepath too long to fit into entryTarPath as OtherEntryType 'L' with the full filepath as entryContent. The next entry must contain the actual data with truncated entryTarPath.

See What exactly is the GNU tar ..@LongLink "trick"?

Since: 0.6.0.0

longSymLinkEntry :: FilePath -> GenEntry TarPath linkTarget Source #

GNU extension to store a link target too long to fit into entryTarPath as OtherEntryType 'K' with the full filepath as entryContent. The next entry must contain the actual data with truncated entryTarPath.

Since: 0.6.0.0

Standard file permissions

For maximum portability when constructing archives use only these file permissions.

ordinaryFilePermissions :: Permissions Source #

rw-r--r-- for normal files

executableFilePermissions :: Permissions Source #

rwxr-xr-x for executable files

directoryPermissions :: Permissions Source #

rwxr-xr-x for directories

Constructing entries from disk files

packFileEntry Source #

Arguments

:: FilePath

Full path to find the file on the local disk

-> tarPath

Path to use for the tar GenEntry in the archive

-> IO (GenEntry tarPath linkTarget) 

Construct a tar entry based on a local file.

This sets the entry size, the data contained in the file and the file's modification time. If the file is executable then that information is also preserved. File ownership and detailed permissions are not preserved.

  • The file contents is read lazily.

packDirectoryEntry Source #

Arguments

:: FilePath

Full path to find the file on the local disk

-> tarPath

Path to use for the tar GenEntry in the archive

-> IO (GenEntry tarPath linkTarget) 

Construct a tar entry based on a local directory (but not its contents).

The only attribute of the directory that is used is its modification time. Directory ownership and detailed permissions are not preserved.

packSymlinkEntry Source #

Arguments

:: FilePath

Full path to find the file on the local disk

-> tarPath

Path to use for the tar GenEntry in the archive

-> IO (GenEntry tarPath FilePath) 

Construct a tar entry based on a local symlink.

This automatically checks symlink safety via checkEntrySecurity.

Since: 0.6.0.0

getDirectoryContentsRecursive :: FilePath -> IO [FilePath] Source #

This is a utility function, much like listDirectory. The difference is that it includes the contents of subdirectories.

The paths returned are all relative to the top directory. Directory paths are distinguishable by having a trailing path separator (see hasTrailingPathSeparator).

All directories are listed before the files that they contain. Amongst the contents of a directory, subdirectories are listed after normal files. The overall result is that files within a directory will be together in a single contiguous group. This tends to improve file layout and IO performance when creating or extracting tar archives.

  • This function returns results lazily. Subdirectories are not scanned until the files entries in the parent directory have been consumed. If the source directory structure changes before the result is used in full, the behaviour is undefined.

TarPath type

data TarPath Source #

The classic tar format allowed just 100 characters for the file name. The USTAR format extended this with an extra 155 characters, however it uses a complex method of splitting the name between the two sections.

Instead of just putting any overflow into the extended area, it uses the extended area as a prefix. The aggravating insane bit however is that the prefix (if any) must only contain a directory prefix. That is the split between the two areas must be on a directory separator boundary. So there is no simple calculation to work out if a file name is too long. Instead we have to try to find a valid split that makes the name fit in the two areas.

The rationale presumably was to make it a bit more compatible with old tar programs that only understand the classic format. A classic tar would be able to extract the file name and possibly some dir prefix, but not the full dir prefix. So the files would end up in the wrong place, but that's probably better than ending up with the wrong names too.

So it's understandable but rather annoying.

  • Tar paths use Posix format (ie '/' directory separators), irrespective of the local path conventions.
  • The directory separator between the prefix and name is not stored.

Instances

Instances details
Show TarPath Source # 
Instance details

Defined in Codec.Archive.Tar.Types

NFData TarPath Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

rnf :: TarPath -> () #

Eq TarPath Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

(==) :: TarPath -> TarPath -> Bool #

(/=) :: TarPath -> TarPath -> Bool #

Ord TarPath Source # 
Instance details

Defined in Codec.Archive.Tar.Types

toTarPath Source #

Arguments

:: Bool

Is the path for a directory? This is needed because for directories a TarPath must always use a trailing /.

-> FilePath 
-> Either String TarPath 

Convert a native FilePath to a TarPath.

The conversion may fail if the FilePath is empty or too long.

fromTarPath :: TarPath -> FilePath Source #

Convert a TarPath to a native FilePath.

The native FilePath will use the native directory separator but it is not otherwise checked for validity or sanity. In particular:

  • The tar path may be invalid as a native path, eg the file name "nul" is not valid on Windows.
  • The tar path may be an absolute path or may contain ".." components. For security reasons this should not usually be allowed, but it is your responsibility to check for these conditions (e.g., using checkEntrySecurity).

fromTarPathToPosixPath :: TarPath -> FilePath Source #

Convert a TarPath to a Unix/Posix FilePath.

The difference compared to fromTarPath is that it always returns a Unix style path irrespective of the current operating system.

This is useful to check how a TarPath would be interpreted on a specific operating system, eg to perform portability checks.

fromTarPathToWindowsPath :: TarPath -> FilePath Source #

Convert a TarPath to a Windows FilePath.

The only difference compared to fromTarPath is that it always returns a Windows style path irrespective of the current operating system.

This is useful to check how a TarPath would be interpreted on a specific operating system, eg to perform portability checks.

LinkTarget type

data LinkTarget Source #

The tar format allows just 100 ASCII characters for the SymbolicLink and HardLink entry types.

toLinkTarget :: FilePath -> Maybe LinkTarget Source #

Convert a native FilePath to a tar LinkTarget. string is longer than 100 characters or if it contains non-portable characters.

fromLinkTarget :: LinkTarget -> FilePath Source #

Convert a tar LinkTarget to a native FilePath.

fromLinkTargetToPosixPath :: LinkTarget -> FilePath Source #

Convert a tar LinkTarget to a Unix/POSIX FilePath ('/' path separators).

fromLinkTargetToWindowsPath :: LinkTarget -> FilePath Source #

Convert a tar LinkTarget to a Windows FilePath ('\\' path separators).