module Codec.Archive.Types (
Entry (..)
, EntryContent (..)
, Ownership (..)
, ModTime
, Id
, Permissions
, ArchiveEncryption (..)
, ArchiveResult (..)
, module Codec.Archive.Types.Foreign
, ArchiveOpenCallback
, ArchiveCloseCallback
, ArchiveSwitchCallback
, resultToErr
) where
import Codec.Archive.Types.Foreign
import Data.Int (Int64)
import Foreign.C.Types (CInt, CLong, CTime)
import Foreign.Ptr (Ptr)
import System.Posix.Types (CMode (..))
type ArchiveOpenCallback a = Ptr Archive -> Ptr a -> IO ArchiveResult
type ArchiveCloseCallback a = Ptr Archive -> Ptr a -> IO ArchiveResult
type ArchiveSwitchCallback a b = Ptr Archive -> Ptr a -> Ptr b -> IO ArchiveResult
resultToErr :: ArchiveResult -> CInt
resultToErr :: ArchiveResult -> CInt
resultToErr = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (ArchiveResult -> Int) -> ArchiveResult -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArchiveResult -> Int
forall a. Enum a => a -> Int
fromEnum
data ArchiveEncryption = HasEncryption
| NoEncryption
| EncryptionUnsupported
| EncryptionUnknown
deriving (ArchiveEncryption -> ArchiveEncryption -> Bool
(ArchiveEncryption -> ArchiveEncryption -> Bool)
-> (ArchiveEncryption -> ArchiveEncryption -> Bool)
-> Eq ArchiveEncryption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArchiveEncryption -> ArchiveEncryption -> Bool
$c/= :: ArchiveEncryption -> ArchiveEncryption -> Bool
== :: ArchiveEncryption -> ArchiveEncryption -> Bool
$c== :: ArchiveEncryption -> ArchiveEncryption -> Bool
Eq)
data EntryContent fp e = NormalFile e
| Directory
| Symlink !fp !Symlink
| Hardlink !fp
deriving (Int -> EntryContent fp e -> ShowS
[EntryContent fp e] -> ShowS
EntryContent fp e -> String
(Int -> EntryContent fp e -> ShowS)
-> (EntryContent fp e -> String)
-> ([EntryContent fp e] -> ShowS)
-> Show (EntryContent fp e)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall fp e. (Show e, Show fp) => Int -> EntryContent fp e -> ShowS
forall fp e. (Show e, Show fp) => [EntryContent fp e] -> ShowS
forall fp e. (Show e, Show fp) => EntryContent fp e -> String
showList :: [EntryContent fp e] -> ShowS
$cshowList :: forall fp e. (Show e, Show fp) => [EntryContent fp e] -> ShowS
show :: EntryContent fp e -> String
$cshow :: forall fp e. (Show e, Show fp) => EntryContent fp e -> String
showsPrec :: Int -> EntryContent fp e -> ShowS
$cshowsPrec :: forall fp e. (Show e, Show fp) => Int -> EntryContent fp e -> ShowS
Show, EntryContent fp e -> EntryContent fp e -> Bool
(EntryContent fp e -> EntryContent fp e -> Bool)
-> (EntryContent fp e -> EntryContent fp e -> Bool)
-> Eq (EntryContent fp e)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall fp e.
(Eq e, Eq fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
/= :: EntryContent fp e -> EntryContent fp e -> Bool
$c/= :: forall fp e.
(Eq e, Eq fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
== :: EntryContent fp e -> EntryContent fp e -> Bool
$c== :: forall fp e.
(Eq e, Eq fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
Eq, Eq (EntryContent fp e)
Eq (EntryContent fp e)
-> (EntryContent fp e -> EntryContent fp e -> Ordering)
-> (EntryContent fp e -> EntryContent fp e -> Bool)
-> (EntryContent fp e -> EntryContent fp e -> Bool)
-> (EntryContent fp e -> EntryContent fp e -> Bool)
-> (EntryContent fp e -> EntryContent fp e -> Bool)
-> (EntryContent fp e -> EntryContent fp e -> EntryContent fp e)
-> (EntryContent fp e -> EntryContent fp e -> EntryContent fp e)
-> Ord (EntryContent fp e)
EntryContent fp e -> EntryContent fp e -> Bool
EntryContent fp e -> EntryContent fp e -> Ordering
EntryContent fp e -> EntryContent fp e -> EntryContent fp e
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 fp e. (Ord e, Ord fp) => Eq (EntryContent fp e)
forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> Ordering
forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> EntryContent fp e
min :: EntryContent fp e -> EntryContent fp e -> EntryContent fp e
$cmin :: forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> EntryContent fp e
max :: EntryContent fp e -> EntryContent fp e -> EntryContent fp e
$cmax :: forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> EntryContent fp e
>= :: EntryContent fp e -> EntryContent fp e -> Bool
$c>= :: forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
> :: EntryContent fp e -> EntryContent fp e -> Bool
$c> :: forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
<= :: EntryContent fp e -> EntryContent fp e -> Bool
$c<= :: forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
< :: EntryContent fp e -> EntryContent fp e -> Bool
$c< :: forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> Bool
compare :: EntryContent fp e -> EntryContent fp e -> Ordering
$ccompare :: forall fp e.
(Ord e, Ord fp) =>
EntryContent fp e -> EntryContent fp e -> Ordering
$cp1Ord :: forall fp e. (Ord e, Ord fp) => Eq (EntryContent fp e)
Ord)
data Entry fp e = Entry { Entry fp e -> fp
filepath :: !fp
, Entry fp e -> EntryContent fp e
content :: EntryContent fp e
, Entry fp e -> Permissions
permissions :: !Permissions
, Entry fp e -> Ownership
ownership :: !Ownership
, Entry fp e -> Maybe ModTime
time :: !(Maybe ModTime)
}
deriving (Int -> Entry fp e -> ShowS
[Entry fp e] -> ShowS
Entry fp e -> String
(Int -> Entry fp e -> ShowS)
-> (Entry fp e -> String)
-> ([Entry fp e] -> ShowS)
-> Show (Entry fp e)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall fp e. (Show fp, Show e) => Int -> Entry fp e -> ShowS
forall fp e. (Show fp, Show e) => [Entry fp e] -> ShowS
forall fp e. (Show fp, Show e) => Entry fp e -> String
showList :: [Entry fp e] -> ShowS
$cshowList :: forall fp e. (Show fp, Show e) => [Entry fp e] -> ShowS
show :: Entry fp e -> String
$cshow :: forall fp e. (Show fp, Show e) => Entry fp e -> String
showsPrec :: Int -> Entry fp e -> ShowS
$cshowsPrec :: forall fp e. (Show fp, Show e) => Int -> Entry fp e -> ShowS
Show, Entry fp e -> Entry fp e -> Bool
(Entry fp e -> Entry fp e -> Bool)
-> (Entry fp e -> Entry fp e -> Bool) -> Eq (Entry fp e)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall fp e. (Eq fp, Eq e) => Entry fp e -> Entry fp e -> Bool
/= :: Entry fp e -> Entry fp e -> Bool
$c/= :: forall fp e. (Eq fp, Eq e) => Entry fp e -> Entry fp e -> Bool
== :: Entry fp e -> Entry fp e -> Bool
$c== :: forall fp e. (Eq fp, Eq e) => Entry fp e -> Entry fp e -> Bool
Eq, Eq (Entry fp e)
Eq (Entry fp e)
-> (Entry fp e -> Entry fp e -> Ordering)
-> (Entry fp e -> Entry fp e -> Bool)
-> (Entry fp e -> Entry fp e -> Bool)
-> (Entry fp e -> Entry fp e -> Bool)
-> (Entry fp e -> Entry fp e -> Bool)
-> (Entry fp e -> Entry fp e -> Entry fp e)
-> (Entry fp e -> Entry fp e -> Entry fp e)
-> Ord (Entry fp e)
Entry fp e -> Entry fp e -> Bool
Entry fp e -> Entry fp e -> Ordering
Entry fp e -> Entry fp e -> Entry fp e
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 fp e. (Ord fp, Ord e) => Eq (Entry fp e)
forall fp e. (Ord fp, Ord e) => Entry fp e -> Entry fp e -> Bool
forall fp e.
(Ord fp, Ord e) =>
Entry fp e -> Entry fp e -> Ordering
forall fp e.
(Ord fp, Ord e) =>
Entry fp e -> Entry fp e -> Entry fp e
min :: Entry fp e -> Entry fp e -> Entry fp e
$cmin :: forall fp e.
(Ord fp, Ord e) =>
Entry fp e -> Entry fp e -> Entry fp e
max :: Entry fp e -> Entry fp e -> Entry fp e
$cmax :: forall fp e.
(Ord fp, Ord e) =>
Entry fp e -> Entry fp e -> Entry fp e
>= :: Entry fp e -> Entry fp e -> Bool
$c>= :: forall fp e. (Ord fp, Ord e) => Entry fp e -> Entry fp e -> Bool
> :: Entry fp e -> Entry fp e -> Bool
$c> :: forall fp e. (Ord fp, Ord e) => Entry fp e -> Entry fp e -> Bool
<= :: Entry fp e -> Entry fp e -> Bool
$c<= :: forall fp e. (Ord fp, Ord e) => Entry fp e -> Entry fp e -> Bool
< :: Entry fp e -> Entry fp e -> Bool
$c< :: forall fp e. (Ord fp, Ord e) => Entry fp e -> Entry fp e -> Bool
compare :: Entry fp e -> Entry fp e -> Ordering
$ccompare :: forall fp e.
(Ord fp, Ord e) =>
Entry fp e -> Entry fp e -> Ordering
$cp1Ord :: forall fp e. (Ord fp, Ord e) => Eq (Entry fp e)
Ord)
data Ownership = Ownership { Ownership -> Maybe String
userName :: !(Maybe String)
, Ownership -> Maybe String
groupName :: !(Maybe String)
, Ownership -> Id
ownerId :: !Id
, Ownership -> Id
groupId :: !Id
}
deriving (Ownership -> Ownership -> Bool
(Ownership -> Ownership -> Bool)
-> (Ownership -> Ownership -> Bool) -> Eq Ownership
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ownership -> Ownership -> Bool
$c/= :: Ownership -> Ownership -> Bool
== :: Ownership -> Ownership -> Bool
$c== :: Ownership -> Ownership -> Bool
Eq, 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
showList :: [Ownership] -> ShowS
$cshowList :: [Ownership] -> ShowS
show :: Ownership -> String
$cshow :: Ownership -> String
showsPrec :: Int -> Ownership -> ShowS
$cshowsPrec :: Int -> Ownership -> ShowS
Show, 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
min :: Ownership -> Ownership -> Ownership
$cmin :: Ownership -> Ownership -> Ownership
max :: Ownership -> Ownership -> Ownership
$cmax :: Ownership -> Ownership -> Ownership
>= :: Ownership -> Ownership -> Bool
$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
compare :: Ownership -> Ownership -> Ordering
$ccompare :: Ownership -> Ownership -> Ordering
$cp1Ord :: Eq Ownership
Ord)
type Permissions = CMode
type ModTime = (CTime, CLong)
type Id = Int64