{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_HADDOCK hide #-}
module Codec.Archive.Tar.Types (
GenEntry(..),
Entry,
entryPath,
GenEntryContent(..),
EntryContent,
FileSize,
Permissions,
Ownership(..),
EpochTime,
TypeCode,
DevMajor,
DevMinor,
Format(..),
simpleEntry,
longLinkEntry,
longSymLinkEntry,
fileEntry,
symlinkEntry,
directoryEntry,
ordinaryFilePermissions,
symbolicLinkPermission,
executableFilePermissions,
directoryPermissions,
TarPath(..),
toTarPath,
toTarPath',
ToTarPathResult(..),
fromTarPath,
fromTarPathToPosixPath,
fromTarPathToWindowsPath,
fromFilePathToNative,
LinkTarget(..),
toLinkTarget,
fromLinkTarget,
fromLinkTargetToPosixPath,
fromLinkTargetToWindowsPath,
fromFilePathToWindowsPath,
GenEntries(..),
Entries,
mapEntries,
mapEntriesNoFail,
foldEntries,
foldlEntries,
unfoldEntries,
unfoldEntriesM,
) where
import Data.Bifunctor (Bifunctor, bimap)
import Data.Int (Int64)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Monoid (Monoid(..))
import Data.Semigroup as Sem
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS.Char8
import qualified Data.ByteString.Lazy as LBS
import Control.DeepSeq
import Control.Exception (Exception, displayException)
import qualified System.FilePath as FilePath.Native
( joinPath, splitDirectories, addTrailingPathSeparator, hasTrailingPathSeparator, pathSeparator, isAbsolute, hasTrailingPathSeparator )
import qualified System.FilePath.Posix as FilePath.Posix
( joinPath, splitPath, splitDirectories, hasTrailingPathSeparator
, addTrailingPathSeparator, pathSeparator )
import qualified System.FilePath.Windows as FilePath.Windows
( joinPath, addTrailingPathSeparator, pathSeparator )
import System.Posix.Types
( FileMode )
import "os-string" System.OsString.Posix (PosixString, PosixChar)
import qualified "os-string" System.OsString.Posix as PS
import Codec.Archive.Tar.PackAscii
type FileSize = Int64
type EpochTime = Int64
type DevMajor = Int
type DevMinor = Int
type TypeCode = Char
type Permissions = FileMode
data GenEntry content tarPath linkTarget = Entry {
forall content tarPath linkTarget.
GenEntry content tarPath linkTarget -> tarPath
entryTarPath :: !tarPath,
forall content tarPath linkTarget.
GenEntry content tarPath linkTarget
-> GenEntryContent content linkTarget
entryContent :: !(GenEntryContent content linkTarget),
forall content tarPath linkTarget.
GenEntry content tarPath linkTarget -> Permissions
entryPermissions :: {-# UNPACK #-} !Permissions,
forall content tarPath linkTarget.
GenEntry content tarPath linkTarget -> Ownership
entryOwnership :: {-# UNPACK #-} !Ownership,
forall content tarPath linkTarget.
GenEntry content tarPath linkTarget -> EpochTime
entryTime :: {-# UNPACK #-} !EpochTime,
forall content tarPath linkTarget.
GenEntry content tarPath linkTarget -> Format
entryFormat :: !Format
}
deriving
( GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool
(GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool)
-> (GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool)
-> Eq (GenEntry content tarPath linkTarget)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall content tarPath linkTarget.
(Eq tarPath, Eq content, Eq linkTarget) =>
GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool
$c== :: forall content tarPath linkTarget.
(Eq tarPath, Eq content, Eq linkTarget) =>
GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool
== :: GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool
$c/= :: forall content tarPath linkTarget.
(Eq tarPath, Eq content, Eq linkTarget) =>
GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool
/= :: GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget -> Bool
Eq
, Int -> GenEntry content tarPath linkTarget -> ShowS
[GenEntry content tarPath linkTarget] -> ShowS
GenEntry content tarPath linkTarget -> String
(Int -> GenEntry content tarPath linkTarget -> ShowS)
-> (GenEntry content tarPath linkTarget -> String)
-> ([GenEntry content tarPath linkTarget] -> ShowS)
-> Show (GenEntry content tarPath linkTarget)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall content tarPath linkTarget.
(Show tarPath, Show content, Show linkTarget) =>
Int -> GenEntry content tarPath linkTarget -> ShowS
forall content tarPath linkTarget.
(Show tarPath, Show content, Show linkTarget) =>
[GenEntry content tarPath linkTarget] -> ShowS
forall content tarPath linkTarget.
(Show tarPath, Show content, Show linkTarget) =>
GenEntry content tarPath linkTarget -> String
$cshowsPrec :: forall content tarPath linkTarget.
(Show tarPath, Show content, Show linkTarget) =>
Int -> GenEntry content tarPath linkTarget -> ShowS
showsPrec :: Int -> GenEntry content tarPath linkTarget -> ShowS
$cshow :: forall content tarPath linkTarget.
(Show tarPath, Show content, Show linkTarget) =>
GenEntry content tarPath linkTarget -> String
show :: GenEntry content tarPath linkTarget -> String
$cshowList :: forall content tarPath linkTarget.
(Show tarPath, Show content, Show linkTarget) =>
[GenEntry content tarPath linkTarget] -> ShowS
showList :: [GenEntry content tarPath linkTarget] -> ShowS
Show
, (forall a b.
(a -> b)
-> GenEntry content tarPath a -> GenEntry content tarPath b)
-> (forall a b.
a -> GenEntry content tarPath b -> GenEntry content tarPath a)
-> Functor (GenEntry content tarPath)
forall a b.
a -> GenEntry content tarPath b -> GenEntry content tarPath a
forall a b.
(a -> b)
-> GenEntry content tarPath a -> GenEntry content tarPath b
forall content tarPath a b.
a -> GenEntry content tarPath b -> GenEntry content tarPath a
forall content tarPath a b.
(a -> b)
-> GenEntry content tarPath a -> GenEntry content tarPath b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall content tarPath a b.
(a -> b)
-> GenEntry content tarPath a -> GenEntry content tarPath b
fmap :: forall a b.
(a -> b)
-> GenEntry content tarPath a -> GenEntry content tarPath b
$c<$ :: forall content tarPath a b.
a -> GenEntry content tarPath b -> GenEntry content tarPath a
<$ :: forall a b.
a -> GenEntry content tarPath b -> GenEntry content tarPath a
Functor
)
instance Bifunctor (GenEntry content) where
bimap :: forall a b c d.
(a -> b)
-> (c -> d) -> GenEntry content a c -> GenEntry content b d
bimap a -> b
f c -> d
g GenEntry content a c
e = GenEntry content a c
e
{ entryTarPath = f (entryTarPath e)
, entryContent = fmap g (entryContent e)
}
type Entry = GenEntry LBS.ByteString TarPath LinkTarget
entryPath :: GenEntry content TarPath linkTarget -> FilePath
entryPath :: forall content linkTarget.
GenEntry content TarPath linkTarget -> String
entryPath = TarPath -> String
fromTarPath (TarPath -> String)
-> (GenEntry content TarPath linkTarget -> TarPath)
-> GenEntry content TarPath linkTarget
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenEntry content TarPath linkTarget -> TarPath
forall content tarPath linkTarget.
GenEntry content tarPath linkTarget -> tarPath
entryTarPath
data GenEntryContent content linkTarget
= NormalFile content {-# UNPACK #-} !FileSize
| Directory
| SymbolicLink !linkTarget
| HardLink !linkTarget
| CharacterDevice {-# UNPACK #-} !DevMajor
{-# UNPACK #-} !DevMinor
| BlockDevice {-# UNPACK #-} !DevMajor
{-# UNPACK #-} !DevMinor
| NamedPipe
| OtherEntryType {-# UNPACK #-} !TypeCode LBS.ByteString
{-# UNPACK #-} !FileSize
deriving
( GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
(GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool)
-> (GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool)
-> Eq (GenEntryContent content linkTarget)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall content linkTarget.
(Eq content, Eq linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
$c== :: forall content linkTarget.
(Eq content, Eq linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
== :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
$c/= :: forall content linkTarget.
(Eq content, Eq linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
/= :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
Eq
, Eq (GenEntryContent content linkTarget)
Eq (GenEntryContent content linkTarget) =>
(GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Ordering)
-> (GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool)
-> (GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool)
-> (GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool)
-> (GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool)
-> (GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget)
-> (GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget)
-> Ord (GenEntryContent content linkTarget)
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Ordering
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall content linkTarget.
(Ord content, Ord linkTarget) =>
Eq (GenEntryContent content linkTarget)
forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Ordering
forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
$ccompare :: forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Ordering
compare :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Ordering
$c< :: forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
< :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
$c<= :: forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
<= :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
$c> :: forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
> :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
$c>= :: forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
>= :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget -> Bool
$cmax :: forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
max :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
$cmin :: forall content linkTarget.
(Ord content, Ord linkTarget) =>
GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
min :: GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
-> GenEntryContent content linkTarget
Ord
, Int -> GenEntryContent content linkTarget -> ShowS
[GenEntryContent content linkTarget] -> ShowS
GenEntryContent content linkTarget -> String
(Int -> GenEntryContent content linkTarget -> ShowS)
-> (GenEntryContent content linkTarget -> String)
-> ([GenEntryContent content linkTarget] -> ShowS)
-> Show (GenEntryContent content linkTarget)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall content linkTarget.
(Show content, Show linkTarget) =>
Int -> GenEntryContent content linkTarget -> ShowS
forall content linkTarget.
(Show content, Show linkTarget) =>
[GenEntryContent content linkTarget] -> ShowS
forall content linkTarget.
(Show content, Show linkTarget) =>
GenEntryContent content linkTarget -> String
$cshowsPrec :: forall content linkTarget.
(Show content, Show linkTarget) =>
Int -> GenEntryContent content linkTarget -> ShowS
showsPrec :: Int -> GenEntryContent content linkTarget -> ShowS
$cshow :: forall content linkTarget.
(Show content, Show linkTarget) =>
GenEntryContent content linkTarget -> String
show :: GenEntryContent content linkTarget -> String
$cshowList :: forall content linkTarget.
(Show content, Show linkTarget) =>
[GenEntryContent content linkTarget] -> ShowS
showList :: [GenEntryContent content linkTarget] -> ShowS
Show
, (forall a b.
(a -> b) -> GenEntryContent content a -> GenEntryContent content b)
-> (forall a b.
a -> GenEntryContent content b -> GenEntryContent content a)
-> Functor (GenEntryContent content)
forall a b.
a -> GenEntryContent content b -> GenEntryContent content a
forall a b.
(a -> b) -> GenEntryContent content a -> GenEntryContent content b
forall content a b.
a -> GenEntryContent content b -> GenEntryContent content a
forall content a b.
(a -> b) -> GenEntryContent content a -> GenEntryContent content b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall content a b.
(a -> b) -> GenEntryContent content a -> GenEntryContent content b
fmap :: forall a b.
(a -> b) -> GenEntryContent content a -> GenEntryContent content b
$c<$ :: forall content a b.
a -> GenEntryContent content b -> GenEntryContent content a
<$ :: forall a b.
a -> GenEntryContent content b -> GenEntryContent content a
Functor
)
type EntryContent = GenEntryContent LBS.ByteString LinkTarget
data Ownership = Ownership {
Ownership -> String
ownerName :: String,
Ownership -> String
groupName :: String,
Ownership -> Int
ownerId :: {-# UNPACK #-} !Int,
Ownership -> Int
groupId :: {-# UNPACK #-} !Int
}
deriving (Ownership -> Ownership -> Bool
(Ownership -> Ownership -> Bool)
-> (Ownership -> Ownership -> Bool) -> Eq Ownership
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ownership -> Ownership -> Bool
== :: Ownership -> Ownership -> Bool
$c/= :: Ownership -> Ownership -> Bool
/= :: Ownership -> Ownership -> Bool
Eq, Eq Ownership
Eq Ownership =>
(Ownership -> Ownership -> Ordering)
-> (Ownership -> Ownership -> Bool)
-> (Ownership -> Ownership -> Bool)
-> (Ownership -> Ownership -> Bool)
-> (Ownership -> Ownership -> Bool)
-> (Ownership -> Ownership -> Ownership)
-> (Ownership -> Ownership -> Ownership)
-> Ord Ownership
Ownership -> Ownership -> Bool
Ownership -> Ownership -> Ordering
Ownership -> Ownership -> Ownership
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Ownership -> Ownership -> Ordering
compare :: Ownership -> Ownership -> Ordering
$c< :: Ownership -> Ownership -> Bool
< :: Ownership -> Ownership -> Bool
$c<= :: Ownership -> Ownership -> Bool
<= :: Ownership -> Ownership -> Bool
$c> :: Ownership -> Ownership -> Bool
> :: Ownership -> Ownership -> Bool
$c>= :: Ownership -> Ownership -> Bool
>= :: Ownership -> Ownership -> Bool
$cmax :: Ownership -> Ownership -> Ownership
max :: Ownership -> Ownership -> Ownership
$cmin :: Ownership -> Ownership -> Ownership
min :: Ownership -> Ownership -> Ownership
Ord, Int -> Ownership -> ShowS
[Ownership] -> ShowS
Ownership -> String
(Int -> Ownership -> ShowS)
-> (Ownership -> String)
-> ([Ownership] -> ShowS)
-> Show Ownership
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ownership -> ShowS
showsPrec :: Int -> Ownership -> ShowS
$cshow :: Ownership -> String
show :: Ownership -> String
$cshowList :: [Ownership] -> ShowS
showList :: [Ownership] -> ShowS
Show)
data Format =
V7Format
| UstarFormat
| GnuFormat
deriving (Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
/= :: Format -> Format -> Bool
Eq, Eq Format
Eq Format =>
(Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Format -> Format -> Ordering
compare :: Format -> Format -> Ordering
$c< :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
>= :: Format -> Format -> Bool
$cmax :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
min :: Format -> Format -> Format
Ord, Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Format -> ShowS
showsPrec :: Int -> Format -> ShowS
$cshow :: Format -> String
show :: Format -> String
$cshowList :: [Format] -> ShowS
showList :: [Format] -> ShowS
Show)
instance (NFData tarPath, NFData content, NFData linkTarget) => NFData (GenEntry content tarPath linkTarget) where
rnf :: GenEntry content tarPath linkTarget -> ()
rnf (Entry tarPath
p GenEntryContent content linkTarget
c Permissions
_ Ownership
_ EpochTime
_ Format
_) = tarPath -> ()
forall a. NFData a => a -> ()
rnf tarPath
p () -> () -> ()
forall a b. a -> b -> b
`seq` GenEntryContent content linkTarget -> ()
forall a. NFData a => a -> ()
rnf GenEntryContent content linkTarget
c
instance (NFData linkTarget, NFData content) => NFData (GenEntryContent content linkTarget) where
rnf :: GenEntryContent content linkTarget -> ()
rnf GenEntryContent content linkTarget
x = case GenEntryContent content linkTarget
x of
NormalFile content
c EpochTime
_ -> content -> ()
forall a. NFData a => a -> ()
rnf content
c
SymbolicLink linkTarget
lnk -> linkTarget -> ()
forall a. NFData a => a -> ()
rnf linkTarget
lnk
HardLink linkTarget
lnk -> linkTarget -> ()
forall a. NFData a => a -> ()
rnf linkTarget
lnk
OtherEntryType Char
_ ByteString
c EpochTime
_ -> ByteString -> ()
forall a. NFData a => a -> ()
rnf ByteString
c
GenEntryContent content linkTarget
_ -> GenEntryContent content linkTarget -> () -> ()
forall a b. a -> b -> b
seq GenEntryContent content linkTarget
x ()
instance NFData Ownership where
rnf :: Ownership -> ()
rnf (Ownership String
o String
g Int
_ Int
_) = String -> ()
forall a. NFData a => a -> ()
rnf String
o () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
g
ordinaryFilePermissions :: Permissions
ordinaryFilePermissions :: Permissions
ordinaryFilePermissions = Permissions
0o0644
symbolicLinkPermission :: Permissions
symbolicLinkPermission :: Permissions
symbolicLinkPermission = Permissions
0o0777
executableFilePermissions :: Permissions
executableFilePermissions :: Permissions
executableFilePermissions = Permissions
0o0755
directoryPermissions :: Permissions
directoryPermissions :: Permissions
directoryPermissions = Permissions
0o0755
simpleEntry :: tarPath -> GenEntryContent content linkTarget -> GenEntry content tarPath linkTarget
simpleEntry :: forall tarPath content linkTarget.
tarPath
-> GenEntryContent content linkTarget
-> GenEntry content tarPath linkTarget
simpleEntry tarPath
tarPath GenEntryContent content linkTarget
content = Entry {
entryTarPath :: tarPath
entryTarPath = tarPath
tarPath,
entryContent :: GenEntryContent content linkTarget
entryContent = GenEntryContent content linkTarget
content,
entryPermissions :: Permissions
entryPermissions = case GenEntryContent content linkTarget
content of
GenEntryContent content linkTarget
Directory -> Permissions
directoryPermissions
SymbolicLink linkTarget
_ -> Permissions
symbolicLinkPermission
GenEntryContent content linkTarget
_ -> Permissions
ordinaryFilePermissions,
entryOwnership :: Ownership
entryOwnership = String -> String -> Int -> Int -> Ownership
Ownership String
"" String
"" Int
0 Int
0,
entryTime :: EpochTime
entryTime = EpochTime
0,
entryFormat :: Format
entryFormat = Format
UstarFormat
}
fileEntry :: tarPath -> LBS.ByteString -> GenEntry LBS.ByteString tarPath linkTarget
fileEntry :: forall tarPath linkTarget.
tarPath -> ByteString -> GenEntry ByteString tarPath linkTarget
fileEntry tarPath
name ByteString
fileContent =
tarPath
-> GenEntryContent ByteString linkTarget
-> GenEntry ByteString tarPath linkTarget
forall tarPath content linkTarget.
tarPath
-> GenEntryContent content linkTarget
-> GenEntry content tarPath linkTarget
simpleEntry tarPath
name (ByteString -> EpochTime -> GenEntryContent ByteString linkTarget
forall content linkTarget.
content -> EpochTime -> GenEntryContent content linkTarget
NormalFile ByteString
fileContent (ByteString -> EpochTime
LBS.length ByteString
fileContent))
symlinkEntry :: tarPath -> linkTarget -> GenEntry content tarPath linkTarget
symlinkEntry :: forall tarPath linkTarget content.
tarPath -> linkTarget -> GenEntry content tarPath linkTarget
symlinkEntry tarPath
name linkTarget
targetLink =
tarPath
-> GenEntryContent content linkTarget
-> GenEntry content tarPath linkTarget
forall tarPath content linkTarget.
tarPath
-> GenEntryContent content linkTarget
-> GenEntry content tarPath linkTarget
simpleEntry tarPath
name (linkTarget -> GenEntryContent content linkTarget
forall content linkTarget.
linkTarget -> GenEntryContent content linkTarget
SymbolicLink linkTarget
targetLink)
longLinkEntry :: FilePath -> GenEntry content TarPath linkTarget
longLinkEntry :: forall content linkTarget.
String -> GenEntry content TarPath linkTarget
longLinkEntry String
tarpath = Entry {
entryTarPath :: TarPath
entryTarPath = PosixString -> PosixString -> TarPath
TarPath [PS.pstr|././@LongLink|] PosixString
forall a. Monoid a => a
mempty,
entryContent :: GenEntryContent content linkTarget
entryContent = Char
-> ByteString -> EpochTime -> GenEntryContent content linkTarget
forall content linkTarget.
Char
-> ByteString -> EpochTime -> GenEntryContent content linkTarget
OtherEntryType Char
'L' (StrictByteString -> ByteString
LBS.fromStrict (StrictByteString -> ByteString) -> StrictByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ PosixString -> StrictByteString
posixToByteString (PosixString -> StrictByteString)
-> PosixString -> StrictByteString
forall a b. (a -> b) -> a -> b
$ String -> PosixString
toPosixString String
tarpath) (Int -> EpochTime
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> EpochTime) -> Int -> EpochTime
forall a b. (a -> b) -> a -> b
$ String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
tarpath),
entryPermissions :: Permissions
entryPermissions = Permissions
ordinaryFilePermissions,
entryOwnership :: Ownership
entryOwnership = String -> String -> Int -> Int -> Ownership
Ownership String
"" String
"" Int
0 Int
0,
entryTime :: EpochTime
entryTime = EpochTime
0,
entryFormat :: Format
entryFormat = Format
GnuFormat
}
longSymLinkEntry :: FilePath -> GenEntry content TarPath linkTarget
longSymLinkEntry :: forall content linkTarget.
String -> GenEntry content TarPath linkTarget
longSymLinkEntry String
linkTarget = Entry {
entryTarPath :: TarPath
entryTarPath = PosixString -> PosixString -> TarPath
TarPath [PS.pstr|././@LongLink|] PosixString
forall a. Monoid a => a
mempty,
entryContent :: GenEntryContent content linkTarget
entryContent = Char
-> ByteString -> EpochTime -> GenEntryContent content linkTarget
forall content linkTarget.
Char
-> ByteString -> EpochTime -> GenEntryContent content linkTarget
OtherEntryType Char
'K' (StrictByteString -> ByteString
LBS.fromStrict (StrictByteString -> ByteString) -> StrictByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ PosixString -> StrictByteString
posixToByteString (PosixString -> StrictByteString)
-> PosixString -> StrictByteString
forall a b. (a -> b) -> a -> b
$ String -> PosixString
toPosixString (String -> PosixString) -> String -> PosixString
forall a b. (a -> b) -> a -> b
$ String
linkTarget) (Int -> EpochTime
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> EpochTime) -> Int -> EpochTime
forall a b. (a -> b) -> a -> b
$ String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
linkTarget),
entryPermissions :: Permissions
entryPermissions = Permissions
ordinaryFilePermissions,
entryOwnership :: Ownership
entryOwnership = String -> String -> Int -> Int -> Ownership
Ownership String
"" String
"" Int
0 Int
0,
entryTime :: EpochTime
entryTime = EpochTime
0,
entryFormat :: Format
entryFormat = Format
GnuFormat
}
directoryEntry :: tarPath -> GenEntry content tarPath linkTarget
directoryEntry :: forall tarPath content linkTarget.
tarPath -> GenEntry content tarPath linkTarget
directoryEntry tarPath
name = tarPath
-> GenEntryContent content linkTarget
-> GenEntry content tarPath linkTarget
forall tarPath content linkTarget.
tarPath
-> GenEntryContent content linkTarget
-> GenEntry content tarPath linkTarget
simpleEntry tarPath
name GenEntryContent content linkTarget
forall content linkTarget. GenEntryContent content linkTarget
Directory
data TarPath = TarPath
{-# UNPACK #-} !PosixString
{-# UNPACK #-} !PosixString
deriving (TarPath -> TarPath -> Bool
(TarPath -> TarPath -> Bool)
-> (TarPath -> TarPath -> Bool) -> Eq TarPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TarPath -> TarPath -> Bool
== :: TarPath -> TarPath -> Bool
$c/= :: TarPath -> TarPath -> Bool
/= :: TarPath -> TarPath -> Bool
Eq, Eq TarPath
Eq TarPath =>
(TarPath -> TarPath -> Ordering)
-> (TarPath -> TarPath -> Bool)
-> (TarPath -> TarPath -> Bool)
-> (TarPath -> TarPath -> Bool)
-> (TarPath -> TarPath -> Bool)
-> (TarPath -> TarPath -> TarPath)
-> (TarPath -> TarPath -> TarPath)
-> Ord TarPath
TarPath -> TarPath -> Bool
TarPath -> TarPath -> Ordering
TarPath -> TarPath -> TarPath
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TarPath -> TarPath -> Ordering
compare :: TarPath -> TarPath -> Ordering
$c< :: TarPath -> TarPath -> Bool
< :: TarPath -> TarPath -> Bool
$c<= :: TarPath -> TarPath -> Bool
<= :: TarPath -> TarPath -> Bool
$c> :: TarPath -> TarPath -> Bool
> :: TarPath -> TarPath -> Bool
$c>= :: TarPath -> TarPath -> Bool
>= :: TarPath -> TarPath -> Bool
$cmax :: TarPath -> TarPath -> TarPath
max :: TarPath -> TarPath -> TarPath
$cmin :: TarPath -> TarPath -> TarPath
min :: TarPath -> TarPath -> TarPath
Ord)
instance NFData TarPath where
rnf :: TarPath -> ()
rnf (TarPath PosixString
_ PosixString
_) = ()
instance Show TarPath where
show :: TarPath -> String
show = ShowS
forall a. Show a => a -> String
show ShowS -> (TarPath -> String) -> TarPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TarPath -> String
fromTarPath
fromTarPath :: TarPath -> FilePath
fromTarPath :: TarPath -> String
fromTarPath = PosixString -> String
fromPosixString (PosixString -> String)
-> (TarPath -> PosixString) -> TarPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixChar -> TarPath -> PosixString
fromTarPathInternal (Char -> PosixChar
PS.unsafeFromChar Char
FilePath.Native.pathSeparator)
fromTarPathToPosixPath :: TarPath -> FilePath
fromTarPathToPosixPath :: TarPath -> String
fromTarPathToPosixPath = PosixString -> String
fromPosixString (PosixString -> String)
-> (TarPath -> PosixString) -> TarPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixChar -> TarPath -> PosixString
fromTarPathInternal (Char -> PosixChar
PS.unsafeFromChar Char
FilePath.Posix.pathSeparator)
fromTarPathToWindowsPath :: TarPath -> FilePath
fromTarPathToWindowsPath :: TarPath -> String
fromTarPathToWindowsPath = PosixString -> String
fromPosixString (PosixString -> String)
-> (TarPath -> PosixString) -> TarPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PosixChar -> TarPath -> PosixString
fromTarPathInternal (Char -> PosixChar
PS.unsafeFromChar Char
FilePath.Windows.pathSeparator)
fromTarPathInternal :: PosixChar -> TarPath -> PosixString
fromTarPathInternal :: PosixChar -> TarPath -> PosixString
fromTarPathInternal PosixChar
sep = TarPath -> PosixString
go
where
posixSep :: PosixChar
posixSep = Char -> PosixChar
PS.unsafeFromChar Char
FilePath.Posix.pathSeparator
adjustSeps :: PosixString -> PosixString
adjustSeps = if PosixChar
sep PosixChar -> PosixChar -> Bool
forall a. Eq a => a -> a -> Bool
== PosixChar
posixSep then PosixString -> PosixString
forall a. a -> a
id else
(PosixChar -> PosixChar) -> PosixString -> PosixString
PS.map ((PosixChar -> PosixChar) -> PosixString -> PosixString)
-> (PosixChar -> PosixChar) -> PosixString -> PosixString
forall a b. (a -> b) -> a -> b
$ \PosixChar
c -> if PosixChar
c PosixChar -> PosixChar -> Bool
forall a. Eq a => a -> a -> Bool
== PosixChar
posixSep then PosixChar
sep else PosixChar
c
go :: TarPath -> PosixString
go (TarPath PosixString
name PosixString
prefix)
| PosixString -> Bool
PS.null PosixString
prefix = PosixString -> PosixString
adjustSeps PosixString
name
| PosixString -> Bool
PS.null PosixString
name = PosixString -> PosixString
adjustSeps PosixString
prefix
| Bool
otherwise = PosixString -> PosixString
adjustSeps PosixString
prefix PosixString -> PosixString -> PosixString
forall a. Semigroup a => a -> a -> a
<> PosixChar -> PosixString -> PosixString
PS.cons PosixChar
sep (PosixString -> PosixString
adjustSeps PosixString
name)
{-# INLINE fromTarPathInternal #-}
toTarPath :: Bool
-> FilePath
-> Either String TarPath
toTarPath :: Bool -> String -> Either String TarPath
toTarPath Bool
isDir String
path = case String -> ToTarPathResult
toTarPath' String
path' of
ToTarPathResult
FileNameEmpty -> String -> Either String TarPath
forall a b. a -> Either a b
Left String
"File name empty"
FileNameOK TarPath
tarPath -> TarPath -> Either String TarPath
forall a b. b -> Either a b
Right TarPath
tarPath
FileNameTooLong{} -> String -> Either String TarPath
forall a b. a -> Either a b
Left (String -> Either String TarPath)
-> String -> Either String TarPath
forall a b. (a -> b) -> a -> b
$ String
"File name too long: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path'
where
path' :: String
path' = if Bool
isDir Bool -> Bool -> Bool
&& Bool -> Bool
not (String -> Bool
FilePath.Native.hasTrailingPathSeparator String
path)
then String
path String -> ShowS
forall a. Semigroup a => a -> a -> a
<> [Char
FilePath.Native.pathSeparator]
else String
path
toTarPath'
:: FilePath
-> ToTarPathResult
toTarPath' :: String -> ToTarPathResult
toTarPath'
= String -> ToTarPathResult
splitLongPath
(String -> ToTarPathResult) -> ShowS -> String -> ToTarPathResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Char
nativeSep Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
posixSep then ShowS
forall a. a -> a
id else ShowS
adjustSeps)
where
nativeSep :: Char
nativeSep = Char
FilePath.Native.pathSeparator
posixSep :: Char
posixSep = Char
FilePath.Posix.pathSeparator
adjustSeps :: ShowS
adjustSeps = (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Char) -> ShowS) -> (Char -> Char) -> ShowS
forall a b. (a -> b) -> a -> b
$ \Char
c -> if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
nativeSep then Char
posixSep else Char
c
data ToTarPathResult
= FileNameEmpty
| FileNameOK TarPath
| FileNameTooLong TarPath
splitLongPath :: FilePath -> ToTarPathResult
splitLongPath :: String -> ToTarPathResult
splitLongPath String
path = case [String] -> [String]
forall a. [a] -> [a]
reverse (String -> [String]
FilePath.Posix.splitPath String
path) of
[] -> ToTarPathResult
FileNameEmpty
String
c : [String]
cs -> case Int -> NonEmpty String -> Maybe (String, [String])
packName Int
nameMax (String
c String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| [String]
cs) of
Maybe (String, [String])
Nothing -> TarPath -> ToTarPathResult
FileNameTooLong (TarPath -> ToTarPathResult) -> TarPath -> ToTarPathResult
forall a b. (a -> b) -> a -> b
$ PosixString -> PosixString -> TarPath
TarPath (String -> PosixString
toPosixString (String -> PosixString) -> String -> PosixString
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
forall a. Int -> [a] -> [a]
take Int
100 String
path) PosixString
forall a. Monoid a => a
mempty
Just (String
name, []) -> TarPath -> ToTarPathResult
FileNameOK (TarPath -> ToTarPathResult) -> TarPath -> ToTarPathResult
forall a b. (a -> b) -> a -> b
$! PosixString -> PosixString -> TarPath
TarPath (String -> PosixString
toPosixString String
name) PosixString
forall a. Monoid a => a
mempty
Just (String
name, String
first:[String]
rest) -> case Int -> NonEmpty String -> Maybe (String, [String])
packName Int
prefixMax NonEmpty String
remainder of
Maybe (String, [String])
Nothing -> TarPath -> ToTarPathResult
FileNameTooLong (TarPath -> ToTarPathResult) -> TarPath -> ToTarPathResult
forall a b. (a -> b) -> a -> b
$ PosixString -> PosixString -> TarPath
TarPath (String -> PosixString
toPosixString (String -> PosixString) -> String -> PosixString
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
forall a. Int -> [a] -> [a]
take Int
100 String
path) PosixString
forall a. Monoid a => a
mempty
Just (String
_ , String
_:[String]
_) -> TarPath -> ToTarPathResult
FileNameTooLong (TarPath -> ToTarPathResult) -> TarPath -> ToTarPathResult
forall a b. (a -> b) -> a -> b
$ PosixString -> PosixString -> TarPath
TarPath (String -> PosixString
toPosixString (String -> PosixString) -> String -> PosixString
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
forall a. Int -> [a] -> [a]
take Int
100 String
path) PosixString
forall a. Monoid a => a
mempty
Just (String
prefix, []) -> TarPath -> ToTarPathResult
FileNameOK (TarPath -> ToTarPathResult) -> TarPath -> ToTarPathResult
forall a b. (a -> b) -> a -> b
$! PosixString -> PosixString -> TarPath
TarPath (String -> PosixString
toPosixString String
name) (String -> PosixString
toPosixString String
prefix)
where
remainder :: NonEmpty String
remainder = ShowS
forall a. HasCallStack => [a] -> [a]
init String
first String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| [String]
rest
where
nameMax, prefixMax :: Int
nameMax :: Int
nameMax = Int
100
prefixMax :: Int
prefixMax = Int
155
packName :: Int -> NonEmpty FilePath -> Maybe (FilePath, [FilePath])
packName :: Int -> NonEmpty String -> Maybe (String, [String])
packName Int
maxLen (String
c :| [String]
cs)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
maxLen = Maybe (String, [String])
forall a. Maybe a
Nothing
| Bool
otherwise = (String, [String]) -> Maybe (String, [String])
forall a. a -> Maybe a
Just (Int -> Int -> [String] -> [String] -> (String, [String])
packName' Int
maxLen Int
n [String
c] [String]
cs)
where n :: Int
n = String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
c
packName' :: Int -> Int -> [FilePath] -> [FilePath] -> (FilePath, [FilePath])
packName' :: Int -> Int -> [String] -> [String] -> (String, [String])
packName' Int
maxLen Int
n [String]
ok (String
c:[String]
cs)
| Int
n' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
maxLen = Int -> Int -> [String] -> [String] -> (String, [String])
packName' Int
maxLen Int
n' (String
cString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ok) [String]
cs
where n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
c
packName' Int
_ Int
_ [String]
ok [String]
cs = ([String] -> String
FilePath.Posix.joinPath [String]
ok, [String]
cs)
newtype LinkTarget = LinkTarget PosixString
deriving (LinkTarget -> LinkTarget -> Bool
(LinkTarget -> LinkTarget -> Bool)
-> (LinkTarget -> LinkTarget -> Bool) -> Eq LinkTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LinkTarget -> LinkTarget -> Bool
== :: LinkTarget -> LinkTarget -> Bool
$c/= :: LinkTarget -> LinkTarget -> Bool
/= :: LinkTarget -> LinkTarget -> Bool
Eq, Eq LinkTarget
Eq LinkTarget =>
(LinkTarget -> LinkTarget -> Ordering)
-> (LinkTarget -> LinkTarget -> Bool)
-> (LinkTarget -> LinkTarget -> Bool)
-> (LinkTarget -> LinkTarget -> Bool)
-> (LinkTarget -> LinkTarget -> Bool)
-> (LinkTarget -> LinkTarget -> LinkTarget)
-> (LinkTarget -> LinkTarget -> LinkTarget)
-> Ord LinkTarget
LinkTarget -> LinkTarget -> Bool
LinkTarget -> LinkTarget -> Ordering
LinkTarget -> LinkTarget -> LinkTarget
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LinkTarget -> LinkTarget -> Ordering
compare :: LinkTarget -> LinkTarget -> Ordering
$c< :: LinkTarget -> LinkTarget -> Bool
< :: LinkTarget -> LinkTarget -> Bool
$c<= :: LinkTarget -> LinkTarget -> Bool
<= :: LinkTarget -> LinkTarget -> Bool
$c> :: LinkTarget -> LinkTarget -> Bool
> :: LinkTarget -> LinkTarget -> Bool
$c>= :: LinkTarget -> LinkTarget -> Bool
>= :: LinkTarget -> LinkTarget -> Bool
$cmax :: LinkTarget -> LinkTarget -> LinkTarget
max :: LinkTarget -> LinkTarget -> LinkTarget
$cmin :: LinkTarget -> LinkTarget -> LinkTarget
min :: LinkTarget -> LinkTarget -> LinkTarget
Ord, Int -> LinkTarget -> ShowS
[LinkTarget] -> ShowS
LinkTarget -> String
(Int -> LinkTarget -> ShowS)
-> (LinkTarget -> String)
-> ([LinkTarget] -> ShowS)
-> Show LinkTarget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LinkTarget -> ShowS
showsPrec :: Int -> LinkTarget -> ShowS
$cshow :: LinkTarget -> String
show :: LinkTarget -> String
$cshowList :: [LinkTarget] -> ShowS
showList :: [LinkTarget] -> ShowS
Show)
instance NFData LinkTarget where
rnf :: LinkTarget -> ()
rnf (LinkTarget PosixString
bs) = PosixString -> ()
forall a. NFData a => a -> ()
rnf PosixString
bs
toLinkTarget :: FilePath -> Maybe LinkTarget
toLinkTarget :: String -> Maybe LinkTarget
toLinkTarget String
path
| String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
path Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
100 = do
String
target <- String -> Maybe String
toLinkTarget' String
path
LinkTarget -> Maybe LinkTarget
forall a. a -> Maybe a
Just (LinkTarget -> Maybe LinkTarget) -> LinkTarget -> Maybe LinkTarget
forall a b. (a -> b) -> a -> b
$! PosixString -> LinkTarget
LinkTarget (String -> PosixString
toPosixString String
target)
| Bool
otherwise = Maybe LinkTarget
forall a. Maybe a
Nothing
data LinkTargetException = IsAbsolute FilePath
| TooLong FilePath
deriving (Int -> LinkTargetException -> ShowS
[LinkTargetException] -> ShowS
LinkTargetException -> String
(Int -> LinkTargetException -> ShowS)
-> (LinkTargetException -> String)
-> ([LinkTargetException] -> ShowS)
-> Show LinkTargetException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LinkTargetException -> ShowS
showsPrec :: Int -> LinkTargetException -> ShowS
$cshow :: LinkTargetException -> String
show :: LinkTargetException -> String
$cshowList :: [LinkTargetException] -> ShowS
showList :: [LinkTargetException] -> ShowS
Show)
instance Exception LinkTargetException where
displayException :: LinkTargetException -> String
displayException (IsAbsolute String
fp) = String
"Link target \"" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
fp String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"\" is unexpectedly absolute"
displayException (TooLong String
_) = String
"The link target is too long"
toLinkTarget' :: FilePath -> Maybe FilePath
toLinkTarget' :: String -> Maybe String
toLinkTarget' String
path
| String -> Bool
FilePath.Native.isAbsolute String
path = Maybe String
forall a. Maybe a
Nothing
| Bool
otherwise = String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ ShowS
adjustDirectory ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ [String] -> String
FilePath.Posix.joinPath ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> [String]
FilePath.Native.splitDirectories String
path
where
adjustDirectory :: ShowS
adjustDirectory | String -> Bool
FilePath.Native.hasTrailingPathSeparator String
path
= ShowS
FilePath.Posix.addTrailingPathSeparator
| Bool
otherwise = ShowS
forall a. a -> a
id
fromLinkTarget :: LinkTarget -> FilePath
fromLinkTarget :: LinkTarget -> String
fromLinkTarget (LinkTarget PosixString
pathbs) = ShowS
fromFilePathToNative ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ PosixString -> String
fromPosixString PosixString
pathbs
fromLinkTargetToPosixPath :: LinkTarget -> FilePath
fromLinkTargetToPosixPath :: LinkTarget -> String
fromLinkTargetToPosixPath (LinkTarget PosixString
pathbs) = PosixString -> String
fromPosixString PosixString
pathbs
fromLinkTargetToWindowsPath :: LinkTarget -> FilePath
fromLinkTargetToWindowsPath :: LinkTarget -> String
fromLinkTargetToWindowsPath (LinkTarget PosixString
pathbs) =
ShowS
fromFilePathToWindowsPath ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ PosixString -> String
fromPosixString PosixString
pathbs
fromFilePathToNative :: FilePath -> FilePath
fromFilePathToNative :: ShowS
fromFilePathToNative =
Char -> Char -> ShowS
fromFilePathInternal Char
FilePath.Posix.pathSeparator Char
FilePath.Native.pathSeparator
fromFilePathToWindowsPath :: FilePath -> FilePath
fromFilePathToWindowsPath :: ShowS
fromFilePathToWindowsPath =
Char -> Char -> ShowS
fromFilePathInternal Char
FilePath.Posix.pathSeparator Char
FilePath.Windows.pathSeparator
fromFilePathInternal :: Char -> Char -> FilePath -> FilePath
fromFilePathInternal :: Char -> Char -> ShowS
fromFilePathInternal Char
fromSep Char
toSep = ShowS
adjustSeps
where
adjustSeps :: ShowS
adjustSeps = if Char
fromSep Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
toSep then ShowS
forall a. a -> a
id else
(Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Char) -> ShowS) -> (Char -> Char) -> ShowS
forall a b. (a -> b) -> a -> b
$ \Char
c -> if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
fromSep then Char
toSep else Char
c
{-# INLINE fromFilePathInternal #-}
data GenEntries content tarPath linkTarget e
= Next (GenEntry content tarPath linkTarget) (GenEntries content tarPath linkTarget e)
| Done
| Fail e
deriving
( GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool
(GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool)
-> (GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool)
-> Eq (GenEntries content tarPath linkTarget e)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall content tarPath linkTarget e.
(Eq tarPath, Eq content, Eq linkTarget, Eq e) =>
GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool
$c== :: forall content tarPath linkTarget e.
(Eq tarPath, Eq content, Eq linkTarget, Eq e) =>
GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool
== :: GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool
$c/= :: forall content tarPath linkTarget e.
(Eq tarPath, Eq content, Eq linkTarget, Eq e) =>
GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool
/= :: GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e -> Bool
Eq
, Int -> GenEntries content tarPath linkTarget e -> ShowS
[GenEntries content tarPath linkTarget e] -> ShowS
GenEntries content tarPath linkTarget e -> String
(Int -> GenEntries content tarPath linkTarget e -> ShowS)
-> (GenEntries content tarPath linkTarget e -> String)
-> ([GenEntries content tarPath linkTarget e] -> ShowS)
-> Show (GenEntries content tarPath linkTarget e)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall content tarPath linkTarget e.
(Show tarPath, Show content, Show linkTarget, Show e) =>
Int -> GenEntries content tarPath linkTarget e -> ShowS
forall content tarPath linkTarget e.
(Show tarPath, Show content, Show linkTarget, Show e) =>
[GenEntries content tarPath linkTarget e] -> ShowS
forall content tarPath linkTarget e.
(Show tarPath, Show content, Show linkTarget, Show e) =>
GenEntries content tarPath linkTarget e -> String
$cshowsPrec :: forall content tarPath linkTarget e.
(Show tarPath, Show content, Show linkTarget, Show e) =>
Int -> GenEntries content tarPath linkTarget e -> ShowS
showsPrec :: Int -> GenEntries content tarPath linkTarget e -> ShowS
$cshow :: forall content tarPath linkTarget e.
(Show tarPath, Show content, Show linkTarget, Show e) =>
GenEntries content tarPath linkTarget e -> String
show :: GenEntries content tarPath linkTarget e -> String
$cshowList :: forall content tarPath linkTarget e.
(Show tarPath, Show content, Show linkTarget, Show e) =>
[GenEntries content tarPath linkTarget e] -> ShowS
showList :: [GenEntries content tarPath linkTarget e] -> ShowS
Show
, (forall a b.
(a -> b)
-> GenEntries content tarPath linkTarget a
-> GenEntries content tarPath linkTarget b)
-> (forall a b.
a
-> GenEntries content tarPath linkTarget b
-> GenEntries content tarPath linkTarget a)
-> Functor (GenEntries content tarPath linkTarget)
forall a b.
a
-> GenEntries content tarPath linkTarget b
-> GenEntries content tarPath linkTarget a
forall a b.
(a -> b)
-> GenEntries content tarPath linkTarget a
-> GenEntries content tarPath linkTarget b
forall content tarPath linkTarget a b.
a
-> GenEntries content tarPath linkTarget b
-> GenEntries content tarPath linkTarget a
forall content tarPath linkTarget a b.
(a -> b)
-> GenEntries content tarPath linkTarget a
-> GenEntries content tarPath linkTarget b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall content tarPath linkTarget a b.
(a -> b)
-> GenEntries content tarPath linkTarget a
-> GenEntries content tarPath linkTarget b
fmap :: forall a b.
(a -> b)
-> GenEntries content tarPath linkTarget a
-> GenEntries content tarPath linkTarget b
$c<$ :: forall content tarPath linkTarget a b.
a
-> GenEntries content tarPath linkTarget b
-> GenEntries content tarPath linkTarget a
<$ :: forall a b.
a
-> GenEntries content tarPath linkTarget b
-> GenEntries content tarPath linkTarget a
Functor
, (forall m.
Monoid m =>
GenEntries content tarPath linkTarget m -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m)
-> (forall m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m)
-> (forall a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b)
-> (forall a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b)
-> (forall b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b)
-> (forall b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b)
-> (forall a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a)
-> (forall a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a)
-> (forall a. GenEntries content tarPath linkTarget a -> [a])
-> (forall a. GenEntries content tarPath linkTarget a -> Bool)
-> (forall a. GenEntries content tarPath linkTarget a -> Int)
-> (forall a.
Eq a =>
a -> GenEntries content tarPath linkTarget a -> Bool)
-> (forall a.
Ord a =>
GenEntries content tarPath linkTarget a -> a)
-> (forall a.
Ord a =>
GenEntries content tarPath linkTarget a -> a)
-> (forall a.
Num a =>
GenEntries content tarPath linkTarget a -> a)
-> (forall a.
Num a =>
GenEntries content tarPath linkTarget a -> a)
-> Foldable (GenEntries content tarPath linkTarget)
forall a.
Eq a =>
a -> GenEntries content tarPath linkTarget a -> Bool
forall a. Num a => GenEntries content tarPath linkTarget a -> a
forall a. Ord a => GenEntries content tarPath linkTarget a -> a
forall m. Monoid m => GenEntries content tarPath linkTarget m -> m
forall a. GenEntries content tarPath linkTarget a -> Bool
forall a. GenEntries content tarPath linkTarget a -> Int
forall a. GenEntries content tarPath linkTarget a -> [a]
forall a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a
forall m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m
forall b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b
forall a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b
forall content tarPath linkTarget a.
Eq a =>
a -> GenEntries content tarPath linkTarget a -> Bool
forall content tarPath linkTarget a.
Num a =>
GenEntries content tarPath linkTarget a -> a
forall content tarPath linkTarget a.
Ord a =>
GenEntries content tarPath linkTarget a -> a
forall content tarPath linkTarget m.
Monoid m =>
GenEntries content tarPath linkTarget m -> m
forall content tarPath linkTarget a.
GenEntries content tarPath linkTarget a -> Bool
forall content tarPath linkTarget a.
GenEntries content tarPath linkTarget a -> Int
forall content tarPath linkTarget a.
GenEntries content tarPath linkTarget a -> [a]
forall content tarPath linkTarget a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a
forall content tarPath linkTarget m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m
forall content tarPath linkTarget b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b
forall content tarPath linkTarget a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall content tarPath linkTarget m.
Monoid m =>
GenEntries content tarPath linkTarget m -> m
fold :: forall m. Monoid m => GenEntries content tarPath linkTarget m -> m
$cfoldMap :: forall content tarPath linkTarget m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m
$cfoldMap' :: forall content tarPath linkTarget m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> GenEntries content tarPath linkTarget a -> m
$cfoldr :: forall content tarPath linkTarget a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b
foldr :: forall a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b
$cfoldr' :: forall content tarPath linkTarget a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b
foldr' :: forall a b.
(a -> b -> b) -> b -> GenEntries content tarPath linkTarget a -> b
$cfoldl :: forall content tarPath linkTarget b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b
foldl :: forall b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b
$cfoldl' :: forall content tarPath linkTarget b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b
foldl' :: forall b a.
(b -> a -> b) -> b -> GenEntries content tarPath linkTarget a -> b
$cfoldr1 :: forall content tarPath linkTarget a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a
foldr1 :: forall a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a
$cfoldl1 :: forall content tarPath linkTarget a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a
foldl1 :: forall a.
(a -> a -> a) -> GenEntries content tarPath linkTarget a -> a
$ctoList :: forall content tarPath linkTarget a.
GenEntries content tarPath linkTarget a -> [a]
toList :: forall a. GenEntries content tarPath linkTarget a -> [a]
$cnull :: forall content tarPath linkTarget a.
GenEntries content tarPath linkTarget a -> Bool
null :: forall a. GenEntries content tarPath linkTarget a -> Bool
$clength :: forall content tarPath linkTarget a.
GenEntries content tarPath linkTarget a -> Int
length :: forall a. GenEntries content tarPath linkTarget a -> Int
$celem :: forall content tarPath linkTarget a.
Eq a =>
a -> GenEntries content tarPath linkTarget a -> Bool
elem :: forall a.
Eq a =>
a -> GenEntries content tarPath linkTarget a -> Bool
$cmaximum :: forall content tarPath linkTarget a.
Ord a =>
GenEntries content tarPath linkTarget a -> a
maximum :: forall a. Ord a => GenEntries content tarPath linkTarget a -> a
$cminimum :: forall content tarPath linkTarget a.
Ord a =>
GenEntries content tarPath linkTarget a -> a
minimum :: forall a. Ord a => GenEntries content tarPath linkTarget a -> a
$csum :: forall content tarPath linkTarget a.
Num a =>
GenEntries content tarPath linkTarget a -> a
sum :: forall a. Num a => GenEntries content tarPath linkTarget a -> a
$cproduct :: forall content tarPath linkTarget a.
Num a =>
GenEntries content tarPath linkTarget a -> a
product :: forall a. Num a => GenEntries content tarPath linkTarget a -> a
Foldable
, Functor (GenEntries content tarPath linkTarget)
Foldable (GenEntries content tarPath linkTarget)
(Functor (GenEntries content tarPath linkTarget),
Foldable (GenEntries content tarPath linkTarget)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> GenEntries content tarPath linkTarget a
-> f (GenEntries content tarPath linkTarget b))
-> (forall (f :: * -> *) a.
Applicative f =>
GenEntries content tarPath linkTarget (f a)
-> f (GenEntries content tarPath linkTarget a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> GenEntries content tarPath linkTarget a
-> m (GenEntries content tarPath linkTarget b))
-> (forall (m :: * -> *) a.
Monad m =>
GenEntries content tarPath linkTarget (m a)
-> m (GenEntries content tarPath linkTarget a))
-> Traversable (GenEntries content tarPath linkTarget)
forall content tarPath linkTarget.
Functor (GenEntries content tarPath linkTarget)
forall content tarPath linkTarget.
Foldable (GenEntries content tarPath linkTarget)
forall content tarPath linkTarget (m :: * -> *) a.
Monad m =>
GenEntries content tarPath linkTarget (m a)
-> m (GenEntries content tarPath linkTarget a)
forall content tarPath linkTarget (f :: * -> *) a.
Applicative f =>
GenEntries content tarPath linkTarget (f a)
-> f (GenEntries content tarPath linkTarget a)
forall content tarPath linkTarget (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> GenEntries content tarPath linkTarget a
-> m (GenEntries content tarPath linkTarget b)
forall content tarPath linkTarget (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> GenEntries content tarPath linkTarget a
-> f (GenEntries content tarPath linkTarget b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
GenEntries content tarPath linkTarget (m a)
-> m (GenEntries content tarPath linkTarget a)
forall (f :: * -> *) a.
Applicative f =>
GenEntries content tarPath linkTarget (f a)
-> f (GenEntries content tarPath linkTarget a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> GenEntries content tarPath linkTarget a
-> m (GenEntries content tarPath linkTarget b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> GenEntries content tarPath linkTarget a
-> f (GenEntries content tarPath linkTarget b)
$ctraverse :: forall content tarPath linkTarget (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> GenEntries content tarPath linkTarget a
-> f (GenEntries content tarPath linkTarget b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> GenEntries content tarPath linkTarget a
-> f (GenEntries content tarPath linkTarget b)
$csequenceA :: forall content tarPath linkTarget (f :: * -> *) a.
Applicative f =>
GenEntries content tarPath linkTarget (f a)
-> f (GenEntries content tarPath linkTarget a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
GenEntries content tarPath linkTarget (f a)
-> f (GenEntries content tarPath linkTarget a)
$cmapM :: forall content tarPath linkTarget (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> GenEntries content tarPath linkTarget a
-> m (GenEntries content tarPath linkTarget b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> GenEntries content tarPath linkTarget a
-> m (GenEntries content tarPath linkTarget b)
$csequence :: forall content tarPath linkTarget (m :: * -> *) a.
Monad m =>
GenEntries content tarPath linkTarget (m a)
-> m (GenEntries content tarPath linkTarget a)
sequence :: forall (m :: * -> *) a.
Monad m =>
GenEntries content tarPath linkTarget (m a)
-> m (GenEntries content tarPath linkTarget a)
Traversable
)
infixr 5 `Next`
type Entries e = GenEntries LBS.ByteString TarPath LinkTarget e
unfoldEntries
:: (a -> Either e (Maybe (GenEntry content tarPath linkTarget, a)))
-> a
-> GenEntries content tarPath linkTarget e
unfoldEntries :: forall a e content tarPath linkTarget.
(a -> Either e (Maybe (GenEntry content tarPath linkTarget, a)))
-> a -> GenEntries content tarPath linkTarget e
unfoldEntries a -> Either e (Maybe (GenEntry content tarPath linkTarget, a))
f = a -> GenEntries content tarPath linkTarget e
unfold
where
unfold :: a -> GenEntries content tarPath linkTarget e
unfold a
x = case a -> Either e (Maybe (GenEntry content tarPath linkTarget, a))
f a
x of
Left e
err -> e -> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
e -> GenEntries content tarPath linkTarget e
Fail e
err
Right Maybe (GenEntry content tarPath linkTarget, a)
Nothing -> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntries content tarPath linkTarget e
Done
Right (Just (GenEntry content tarPath linkTarget
e, a
x')) -> GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
Next GenEntry content tarPath linkTarget
e (a -> GenEntries content tarPath linkTarget e
unfold a
x')
unfoldEntriesM
:: Monad m
=> (forall a. m a -> m a)
-> m (Either e (Maybe (GenEntry content tarPath linkTarget)))
-> m (GenEntries content tarPath linkTarget e)
unfoldEntriesM :: forall (m :: * -> *) e content tarPath linkTarget.
Monad m =>
(forall a. m a -> m a)
-> m (Either e (Maybe (GenEntry content tarPath linkTarget)))
-> m (GenEntries content tarPath linkTarget e)
unfoldEntriesM forall a. m a -> m a
interleave m (Either e (Maybe (GenEntry content tarPath linkTarget)))
f = m (GenEntries content tarPath linkTarget e)
unfold
where
unfold :: m (GenEntries content tarPath linkTarget e)
unfold = do
Either e (Maybe (GenEntry content tarPath linkTarget))
f' <- m (Either e (Maybe (GenEntry content tarPath linkTarget)))
f
case Either e (Maybe (GenEntry content tarPath linkTarget))
f' of
Left e
err -> GenEntries content tarPath linkTarget e
-> m (GenEntries content tarPath linkTarget e)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenEntries content tarPath linkTarget e
-> m (GenEntries content tarPath linkTarget e))
-> GenEntries content tarPath linkTarget e
-> m (GenEntries content tarPath linkTarget e)
forall a b. (a -> b) -> a -> b
$ e -> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
e -> GenEntries content tarPath linkTarget e
Fail e
err
Right Maybe (GenEntry content tarPath linkTarget)
Nothing -> GenEntries content tarPath linkTarget e
-> m (GenEntries content tarPath linkTarget e)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntries content tarPath linkTarget e
Done
Right (Just GenEntry content tarPath linkTarget
e) -> GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
Next GenEntry content tarPath linkTarget
e (GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e)
-> m (GenEntries content tarPath linkTarget e)
-> m (GenEntries content tarPath linkTarget e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (GenEntries content tarPath linkTarget e)
-> m (GenEntries content tarPath linkTarget e)
forall a. m a -> m a
interleave m (GenEntries content tarPath linkTarget e)
unfold
foldEntries
:: (GenEntry content tarPath linkTarget -> a -> a)
-> a
-> (e -> a)
-> GenEntries content tarPath linkTarget e -> a
foldEntries :: forall content tarPath linkTarget a e.
(GenEntry content tarPath linkTarget -> a -> a)
-> a -> (e -> a) -> GenEntries content tarPath linkTarget e -> a
foldEntries GenEntry content tarPath linkTarget -> a -> a
next a
done e -> a
fail' = GenEntries content tarPath linkTarget e -> a
fold
where
fold :: GenEntries content tarPath linkTarget e -> a
fold (Next GenEntry content tarPath linkTarget
e GenEntries content tarPath linkTarget e
es) = GenEntry content tarPath linkTarget -> a -> a
next GenEntry content tarPath linkTarget
e (GenEntries content tarPath linkTarget e -> a
fold GenEntries content tarPath linkTarget e
es)
fold GenEntries content tarPath linkTarget e
Done = a
done
fold (Fail e
err) = e -> a
fail' e
err
foldlEntries
:: (a -> GenEntry content tarPath linkTarget -> a)
-> a
-> GenEntries content tarPath linkTarget e
-> Either (e, a) a
foldlEntries :: forall a content tarPath linkTarget e.
(a -> GenEntry content tarPath linkTarget -> a)
-> a -> GenEntries content tarPath linkTarget e -> Either (e, a) a
foldlEntries a -> GenEntry content tarPath linkTarget -> a
f = a -> GenEntries content tarPath linkTarget e -> Either (e, a) a
forall {a}.
a -> GenEntries content tarPath linkTarget a -> Either (a, a) a
go
where
go :: a -> GenEntries content tarPath linkTarget a -> Either (a, a) a
go !a
acc (Next GenEntry content tarPath linkTarget
e GenEntries content tarPath linkTarget a
es) = a -> GenEntries content tarPath linkTarget a -> Either (a, a) a
go (a -> GenEntry content tarPath linkTarget -> a
f a
acc GenEntry content tarPath linkTarget
e) GenEntries content tarPath linkTarget a
es
go !a
acc GenEntries content tarPath linkTarget a
Done = a -> Either (a, a) a
forall a b. b -> Either a b
Right a
acc
go !a
acc (Fail a
err) = (a, a) -> Either (a, a) a
forall a b. a -> Either a b
Left (a
err, a
acc)
mapEntries
:: (GenEntry content tarPath linkTarget -> Either e' (GenEntry content tarPath linkTarget))
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget (Either e e')
mapEntries :: forall content tarPath linkTarget e' e.
(GenEntry content tarPath linkTarget
-> Either e' (GenEntry content tarPath linkTarget))
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget (Either e e')
mapEntries GenEntry content tarPath linkTarget
-> Either e' (GenEntry content tarPath linkTarget)
f =
(GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget (Either e e')
-> GenEntries content tarPath linkTarget (Either e e'))
-> GenEntries content tarPath linkTarget (Either e e')
-> (e -> GenEntries content tarPath linkTarget (Either e e'))
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget (Either e e')
forall content tarPath linkTarget a e.
(GenEntry content tarPath linkTarget -> a -> a)
-> a -> (e -> a) -> GenEntries content tarPath linkTarget e -> a
foldEntries (\GenEntry content tarPath linkTarget
entry GenEntries content tarPath linkTarget (Either e e')
rest -> (e' -> GenEntries content tarPath linkTarget (Either e e'))
-> (GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget (Either e e'))
-> Either e' (GenEntry content tarPath linkTarget)
-> GenEntries content tarPath linkTarget (Either e e')
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Either e e' -> GenEntries content tarPath linkTarget (Either e e')
forall content tarPath linkTarget e.
e -> GenEntries content tarPath linkTarget e
Fail (Either e e'
-> GenEntries content tarPath linkTarget (Either e e'))
-> (e' -> Either e e')
-> e'
-> GenEntries content tarPath linkTarget (Either e e')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e' -> Either e e'
forall a b. b -> Either a b
Right) (GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget (Either e e')
-> GenEntries content tarPath linkTarget (Either e e')
forall content tarPath linkTarget e.
GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
`Next` GenEntries content tarPath linkTarget (Either e e')
rest) (GenEntry content tarPath linkTarget
-> Either e' (GenEntry content tarPath linkTarget)
f GenEntry content tarPath linkTarget
entry)) GenEntries content tarPath linkTarget (Either e e')
forall content tarPath linkTarget e.
GenEntries content tarPath linkTarget e
Done (Either e e' -> GenEntries content tarPath linkTarget (Either e e')
forall content tarPath linkTarget e.
e -> GenEntries content tarPath linkTarget e
Fail (Either e e'
-> GenEntries content tarPath linkTarget (Either e e'))
-> (e -> Either e e')
-> e
-> GenEntries content tarPath linkTarget (Either e e')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Either e e'
forall a b. a -> Either a b
Left)
mapEntriesNoFail
:: (GenEntry content tarPath linkTarget -> GenEntry content tarPath linkTarget)
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
mapEntriesNoFail :: forall content tarPath linkTarget e.
(GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget)
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
mapEntriesNoFail GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget
f =
(GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e)
-> GenEntries content tarPath linkTarget e
-> (e -> GenEntries content tarPath linkTarget e)
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget a e.
(GenEntry content tarPath linkTarget -> a -> a)
-> a -> (e -> a) -> GenEntries content tarPath linkTarget e -> a
foldEntries (GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
Next (GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e)
-> (GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget)
-> GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenEntry content tarPath linkTarget
-> GenEntry content tarPath linkTarget
f) GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntries content tarPath linkTarget e
Done e -> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
e -> GenEntries content tarPath linkTarget e
Fail
instance Sem.Semigroup (GenEntries content tarPath linkTarget e) where
GenEntries content tarPath linkTarget e
a <> :: GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
<> GenEntries content tarPath linkTarget e
b = (GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e)
-> GenEntries content tarPath linkTarget e
-> (e -> GenEntries content tarPath linkTarget e)
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget a e.
(GenEntry content tarPath linkTarget -> a -> a)
-> a -> (e -> a) -> GenEntries content tarPath linkTarget e -> a
foldEntries GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntry content tarPath linkTarget
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
Next GenEntries content tarPath linkTarget e
b e -> GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
e -> GenEntries content tarPath linkTarget e
Fail GenEntries content tarPath linkTarget e
a
instance Monoid (GenEntries content tarPath linkTarget e) where
mempty :: GenEntries content tarPath linkTarget e
mempty = GenEntries content tarPath linkTarget e
forall content tarPath linkTarget e.
GenEntries content tarPath linkTarget e
Done
mappend :: GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
mappend = GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
-> GenEntries content tarPath linkTarget e
forall a. Semigroup a => a -> a -> a
(Sem.<>)
instance (NFData tarPath, NFData content, NFData linkTarget, NFData e) => NFData (GenEntries content tarPath linkTarget e) where
rnf :: GenEntries content tarPath linkTarget e -> ()
rnf (Next GenEntry content tarPath linkTarget
e GenEntries content tarPath linkTarget e
es) = GenEntry content tarPath linkTarget -> ()
forall a. NFData a => a -> ()
rnf GenEntry content tarPath linkTarget
e () -> () -> ()
forall a b. a -> b -> b
`seq` GenEntries content tarPath linkTarget e -> ()
forall a. NFData a => a -> ()
rnf GenEntries content tarPath linkTarget e
es
rnf GenEntries content tarPath linkTarget e
Done = ()
rnf (Fail e
e) = e -> ()
forall a. NFData a => a -> ()
rnf e
e