stack-2.15.3: The Haskell Tool Stack
Safe HaskellSafe-Inferred
LanguageGHC2021

Codec.Archive.Tar.Utf8

Synopsis

Documentation

data Entry #

Tar archive entry.

Instances

Instances details
Show Entry 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

showsPrec :: Int -> Entry -> ShowS #

show :: Entry -> String #

showList :: [Entry] -> ShowS #

NFData Entry 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

rnf :: Entry -> () #

Eq Entry 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

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

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

data Entries e #

A tar archive is a sequence of entries.

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.

It is a concrete data type so you can manipulate it directly but it is often clearer to use the provided functions for mapping, folding and unfolding.

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.

Constructors

Next Entry (Entries e) infixr 5 
Done 
Fail e 

Instances

Instances details
Functor Entries 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

fmap :: (a -> b) -> Entries a -> Entries b #

(<$) :: a -> Entries b -> Entries a #

Monoid (Entries e) 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

mempty :: Entries e #

mappend :: Entries e -> Entries e -> Entries e #

mconcat :: [Entries e] -> Entries e #

Semigroup (Entries e)

Since: tar-0.5.1.0

Instance details

Defined in Codec.Archive.Tar.Types

Methods

(<>) :: Entries e -> Entries e -> Entries e #

sconcat :: NonEmpty (Entries e) -> Entries e #

stimes :: Integral b => b -> Entries e -> Entries e #

Show e => Show (Entries e) 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

showsPrec :: Int -> Entries e -> ShowS #

show :: Entries e -> String #

showList :: [Entries e] -> ShowS #

NFData e => NFData (Entries e) 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

rnf :: Entries e -> () #

Eq e => Eq (Entries e) 
Instance details

Defined in Codec.Archive.Tar.Types

Methods

(==) :: Entries e -> Entries e -> Bool #

(/=) :: Entries e -> Entries e -> Bool #

data FormatError #

Errors that can be encountered when parsing a Tar archive.

Instances

Instances details
Exception FormatError 
Instance details

Defined in Codec.Archive.Tar.Read

Show FormatError 
Instance details

Defined in Codec.Archive.Tar.Read

NFData FormatError 
Instance details

Defined in Codec.Archive.Tar.Read

Methods

rnf :: FormatError -> () #

Eq FormatError 
Instance details

Defined in Codec.Archive.Tar.Read

pack #

Arguments

:: FilePath

Base directory

-> [FilePath]

Files and directories to pack, relative to the base dir

-> IO [Entry] 

Creates a tar archive from a list of directory or files. Any directories specified will have their contents included recursively. Paths in the archive will be relative to the given base directory.

This is a portable implementation of packing suitable for portable archives. In particular it only constructs NormalFile and Directory entries. Hard links and symbolic links are treated like ordinary files. It cannot be used to pack directories containing recursive symbolic links. Special files like FIFOs (named pipes), sockets or device files will also cause problems.

An exception will be thrown for any file names that are too long to represent as a TarPath.

  • This function returns results lazily. Subdirectories are scanned and files are read one by one as the list of entries is consumed.

read :: ByteString -> Entries FormatError #

Convert a data stream in the tar file format into an internal data structure. Decoding errors are reported by the Fail constructor of the Entries type.

  • The conversion is done lazily.

write :: [Entry] -> ByteString #

Create the external representation of a tar archive by serialising a list of tar entries.

  • The conversion is done lazily.

append #

Arguments

:: FilePath

Path of the ".tar" file to write.

-> FilePath

Base directory

-> [FilePath]

Files and directories to archive, relative to base dir

-> IO () 

Append new entries to a ".tar" file from a directory of files.

This is much like create, except that all the entries are added to the end of an existing tar file. Or if the file does not already exists then it behaves the same as create.

create #

Arguments

:: FilePath

Path of the ".tar" file to write.

-> FilePath

Base directory

-> [FilePath]

Files and directories to archive, relative to base dir

-> IO () 

Create a new ".tar" file from a directory of files.

It is equivalent to calling the standard tar program like so:

$ tar -f tarball.tar -C base -c dir

This assumes a directory ./base/dir with files inside, eg ./base/dir/foo.txt. The file names inside the resulting tar file will be relative to dir, eg dir/foo.txt.

This is a high level "all in one" operation. Since you may need variations on this function it is instructive to see how it is written. It is just:

BS.writeFile tar . Tar.write =<< Tar.pack base paths

Notes:

The files and directories must not change during this operation or the result is not well defined.

The intention of this function is to create tarballs that are portable between systems. It is not suitable for doing file system backups because file ownership and permissions are not fully preserved. File ownership is not preserved at all. File permissions are set to simple portable values:

  • rw-r--r-- for normal files
  • rwxr-xr-x for executable files
  • rwxr-xr-x for directories

extract #

Arguments

:: FilePath

Destination directory

-> FilePath

Tarball

-> IO () 

Extract all the files contained in a ".tar" file.

It is equivalent to calling the standard tar program like so:

$ tar -x -f tarball.tar -C dir

So for example if the tarball.tar file contains foo/bar.txt then this will extract it to dir/foo/bar.txt.

This is a high level "all in one" operation. Since you may need variations on this function it is instructive to see how it is written. It is just:

Tar.unpack dir . Tar.read =<< BS.readFile tar

Notes:

Extracting can fail for a number of reasons. The tarball may be incorrectly formatted. There may be IO or permission errors. In such cases an exception will be thrown and extraction will not continue.

Since the extraction may fail part way through it is not atomic. For this reason you may want to extract into an empty directory and, if the extraction fails, recursively delete the directory.

Security: only files inside the target directory will be written. Tarballs containing entries that point outside of the tarball (either absolute paths or relative paths) will be caught and an exception will be thrown.

unfoldEntries :: (a -> Either e (Maybe (Entry, a))) -> a -> Entries e #

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.

foldEntries :: (Entry -> a -> a) -> a -> (e -> a) -> Entries e -> a #

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 -> Entry -> a) -> a -> Entries e -> Either (e, a) a #

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

mapEntries :: (Entry -> Either e' Entry) -> Entries e -> Entries (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 :: (Entry -> Entry) -> Entries e -> Entries e #

Like mapEntries but the mapping function itself cannot fail.

entryPath :: Entry -> FilePath Source #

Native FilePath of the file or directory within the archive.

Assumes that the TarPath of an Entry is UTF8 encoded.

unpack :: Exception e => FilePath -> Entries e -> IO () Source #

Create local files and directories based on the entries of a tar archive.

This is a portable implementation of unpacking suitable for portable archives. It handles NormalFile and Directory entries and has simulated support for SymbolicLink and HardLink entries. Links are implemented by copying the target file. This therefore works on Windows as well as Unix. All other entry types are ignored, that is they are not unpacked and no exception is raised.

If the Entries ends in an error then it is raised an an exception. Any files or directories that have been unpacked before the error was encountered will not be deleted. For this reason you may want to unpack into an empty directory so that you can easily clean up if unpacking fails part-way.

On its own, this function only checks for security (using checkSecurity). You can do other checks by applying checking functions to the Entries that you pass to this function. For example:

unpack dir (checkTarbomb expectedDir entries)

If you care about the priority of the reported errors then you may want to use checkSecurity before checkTarbomb or other checks.

Assumes that the TarPath of an Entry is UTF8 encoded.