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

Codec.Archive.Tar.Types

Description

Types to represent the content of .tar archives.

Synopsis

Documentation

data GenEntry tarPath linkTarget Source #

Polymorphic tar archive entry. High-level interfaces commonly work with GenEntry FilePath FilePath, while low level uses 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 #

Native FilePath of the file or directory within the archive.

data GenEntryContent linkTarget Source #

Polymorphic content of a tar archive entry. High-level interfaces commonly work with GenEntryContent FilePath, while low level uses 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 #

Constructors

Ownership 

Fields

  • ownerName :: String

    The owner user name. Should be set to "" if unknown.

  • groupName :: String

    The owner group name. Should be set to "" if unknown.

  • 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 EpochTime = Int64 Source #

The number of seconds since the UNIX epoch

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

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

An GenEntry 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 }

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

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

A tar GenEntry 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 }

symlinkEntry :: tarPath -> linkTarget -> GenEntry tarPath linkTarget Source #

A tar GenEntry for a symbolic link.

directoryEntry :: tarPath -> GenEntry tarPath linkTarget Source #

A tar GenEntry for a directory.

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

ordinaryFilePermissions :: Permissions Source #

rw-r--r-- for normal files

symbolicLinkPermission :: Permissions Source #

rw-r--r-- for normal files

Since: 0.6.0.0

executableFilePermissions :: Permissions Source #

rwxr-xr-x for executable files

directoryPermissions :: Permissions Source #

rwxr-xr-x for directories

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.

Constructors

TarPath !ByteString !ByteString 

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. Use toTarPath' for a structured output.

toTarPath' :: FilePath -> ToTarPathResult Source #

Convert a native FilePath to a TarPath. Directory paths must always have a trailing /, this is not checked.

Since: 0.6.0.0

data ToTarPathResult Source #

Return type of toTarPath'.

Since: 0.6.0.0

Constructors

FileNameEmpty

FilePath was empty, but TarPath must be non-empty.

FileNameOK TarPath

All good, this is just a normal TarPath.

FileNameTooLong TarPath

FilePath was longer than 255 characters, TarPath contains a truncated part only. An actual entry must be preceded by longLinkEntry.

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.

fromFilePathToNative :: FilePath -> FilePath Source #

Convert a unix FilePath to a native FilePath.

newtype LinkTarget Source #

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

Constructors

LinkTarget ByteString 

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).

fromFilePathToWindowsPath :: FilePath -> FilePath Source #

Convert a unix FilePath to a Windows FilePath.

data GenEntries tarPath linkTarget e Source #

Polymorphic sequence of archive entries. High-level interfaces commonly work with GenEntries FilePath FilePath, while low level uses GenEntries TarPath LinkTarget.

The point of this type as opposed to just using a list is that it makes the failure case explicit. We need this because the sequence of entries we get from reading a tarball can include errors.

Converting from a list can be done with just foldr Next Done. Converting back into a list can be done with foldEntries however in that case you must be prepared to handle the Fail case inherent in the Entries type.

The Monoid instance lets you concatenate archives or append entries to an archive.

Since: 0.6.0.0

Constructors

Next (GenEntry tarPath linkTarget) (GenEntries tarPath linkTarget e) infixr 5 
Done 
Fail e 

Instances

Instances details
Foldable (GenEntries tarPath linkTarget) Source #

Since: 0.6.0.0

Instance details

Defined in Codec.Archive.Tar.Types

Methods

fold :: Monoid m => GenEntries tarPath linkTarget m -> m #

foldMap :: Monoid m => (a -> m) -> GenEntries tarPath linkTarget a -> m #

foldMap' :: Monoid m => (a -> m) -> GenEntries tarPath linkTarget a -> m #

foldr :: (a -> b -> b) -> b -> GenEntries tarPath linkTarget a -> b #

foldr' :: (a -> b -> b) -> b -> GenEntries tarPath linkTarget a -> b #

foldl :: (b -> a -> b) -> b -> GenEntries tarPath linkTarget a -> b #

foldl' :: (b -> a -> b) -> b -> GenEntries tarPath linkTarget a -> b #

foldr1 :: (a -> a -> a) -> GenEntries tarPath linkTarget a -> a #

foldl1 :: (a -> a -> a) -> GenEntries tarPath linkTarget a -> a #

toList :: GenEntries tarPath linkTarget a -> [a] #

null :: GenEntries tarPath linkTarget a -> Bool #

length :: GenEntries tarPath linkTarget a -> Int #

elem :: Eq a => a -> GenEntries tarPath linkTarget a -> Bool #

maximum :: Ord a => GenEntries tarPath linkTarget a -> a #

minimum :: Ord a => GenEntries tarPath linkTarget a -> a #

sum :: Num a => GenEntries tarPath linkTarget a -> a #

product :: Num a => GenEntries tarPath linkTarget a -> a #

Traversable (GenEntries tarPath linkTarget) Source #

Since: 0.6.0.0

Instance details

Defined in Codec.Archive.Tar.Types

Methods

traverse :: Applicative f => (a -> f b) -> GenEntries tarPath linkTarget a -> f (GenEntries tarPath linkTarget b) #

sequenceA :: Applicative f => GenEntries tarPath linkTarget (f a) -> f (GenEntries tarPath linkTarget a) #

mapM :: Monad m => (a -> m b) -> GenEntries tarPath linkTarget a -> m (GenEntries tarPath linkTarget b) #

sequence :: Monad m => GenEntries tarPath linkTarget (m a) -> m (GenEntries tarPath linkTarget a) #

Functor (GenEntries tarPath linkTarget) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

fmap :: (a -> b) -> GenEntries tarPath linkTarget a -> GenEntries tarPath linkTarget b #

(<$) :: a -> GenEntries tarPath linkTarget b -> GenEntries tarPath linkTarget a #

Monoid (GenEntries tarPath linkTarget e) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

mempty :: GenEntries tarPath linkTarget e #

mappend :: GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e #

mconcat :: [GenEntries tarPath linkTarget e] -> GenEntries tarPath linkTarget e #

Semigroup (GenEntries tarPath linkTarget e) Source #

Since: 0.5.1.0

Instance details

Defined in Codec.Archive.Tar.Types

Methods

(<>) :: GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e #

sconcat :: NonEmpty (GenEntries tarPath linkTarget e) -> GenEntries tarPath linkTarget e #

stimes :: Integral b => b -> GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e #

(Show tarPath, Show linkTarget, Show e) => Show (GenEntries tarPath linkTarget e) Source # 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

showsPrec :: Int -> GenEntries tarPath linkTarget e -> ShowS #

show :: GenEntries tarPath linkTarget e -> String #

showList :: [GenEntries tarPath linkTarget e] -> ShowS #

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

Defined in Codec.Archive.Tar.Types

Methods

rnf :: GenEntries tarPath linkTarget e -> () #

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

Defined in Codec.Archive.Tar.Types

Methods

(==) :: GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e -> Bool #

(/=) :: GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e -> Bool #

type Entries e = GenEntries TarPath LinkTarget e Source #

Monomorphic sequence of archive entries, ready for serialization / deserialization.

mapEntries Source #

Arguments

:: (GenEntry tarPath linkTarget -> Either e' (GenEntry tarPath linkTarget))

Function to apply to each entry

-> GenEntries tarPath linkTarget e

Input sequence

-> GenEntries tarPath linkTarget (Either e e') 

This is like the standard map function on lists, but for Entries. It includes failure as a extra possible outcome of the mapping function.

If your mapping function cannot fail it may be more convenient to use mapEntriesNoFail

mapEntriesNoFail :: (GenEntry tarPath linkTarget -> GenEntry tarPath linkTarget) -> GenEntries tarPath linkTarget e -> GenEntries tarPath linkTarget e Source #

Like mapEntries but the mapping function itself cannot fail.

foldEntries :: (GenEntry tarPath linkTarget -> a -> a) -> a -> (e -> a) -> GenEntries tarPath linkTarget e -> a Source #

This is like the standard foldr function on lists, but for Entries. Compared to foldr it takes an extra function to account for the possibility of failure.

This is used to consume a sequence of entries. For example it could be used to scan a tarball for problems or to collect an index of the contents.

foldlEntries :: (a -> GenEntry tarPath linkTarget -> a) -> a -> GenEntries tarPath linkTarget e -> Either (e, a) a Source #

A foldl-like function on Entries. It either returns the final accumulator result, or the failure along with the intermediate accumulator value.

unfoldEntries :: (a -> Either e (Maybe (GenEntry tarPath linkTarget, a))) -> a -> GenEntries tarPath linkTarget e Source #

This is like the standard unfoldr function on lists, but for Entries. It includes failure as an extra possibility that the stepper function may return.

It can be used to generate Entries from some other type. For example it is used internally to lazily unfold entries from a ByteString.