module Codec.Archive.Types ( -- * Concrete (Haskell) data types
                             Entry (..)
                           , EntryContent (..)
                           , Ownership (..)
                           , ModTime
                           , Id
                           , Permissions
                           , ArchiveEncryption (..)
                           , ArchiveResult (..)
                           -- * Foreign types
                           , module Codec.Archive.Types.Foreign
                           -- * Callbacks
                           , ArchiveOpenCallback
                           , ArchiveCloseCallback
                           , ArchiveSwitchCallback
                           -- * Marshalling functions
                           , resultToErr
                           ) where

import           Codec.Archive.Types.Foreign
import qualified Data.ByteString             as BS
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)

-- TODO: support everything here: http://hackage.haskell.org/package/tar/docs/Codec-Archive-Tar-Entry.html#t:EntryContent
data EntryContent = NormalFile !BS.ByteString
                  | Directory
                  | Symlink !FilePath !Symlink
                  | Hardlink !FilePath
    deriving (Int -> EntryContent -> ShowS
[EntryContent] -> ShowS
EntryContent -> String
(Int -> EntryContent -> ShowS)
-> (EntryContent -> String)
-> ([EntryContent] -> ShowS)
-> Show EntryContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EntryContent] -> ShowS
$cshowList :: [EntryContent] -> ShowS
show :: EntryContent -> String
$cshow :: EntryContent -> String
showsPrec :: Int -> EntryContent -> ShowS
$cshowsPrec :: Int -> EntryContent -> ShowS
Show, EntryContent -> EntryContent -> Bool
(EntryContent -> EntryContent -> Bool)
-> (EntryContent -> EntryContent -> Bool) -> Eq EntryContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EntryContent -> EntryContent -> Bool
$c/= :: EntryContent -> EntryContent -> Bool
== :: EntryContent -> EntryContent -> Bool
$c== :: EntryContent -> EntryContent -> Bool
Eq, Eq EntryContent
Eq EntryContent
-> (EntryContent -> EntryContent -> Ordering)
-> (EntryContent -> EntryContent -> Bool)
-> (EntryContent -> EntryContent -> Bool)
-> (EntryContent -> EntryContent -> Bool)
-> (EntryContent -> EntryContent -> Bool)
-> (EntryContent -> EntryContent -> EntryContent)
-> (EntryContent -> EntryContent -> EntryContent)
-> Ord EntryContent
EntryContent -> EntryContent -> Bool
EntryContent -> EntryContent -> Ordering
EntryContent -> EntryContent -> EntryContent
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 :: EntryContent -> EntryContent -> EntryContent
$cmin :: EntryContent -> EntryContent -> EntryContent
max :: EntryContent -> EntryContent -> EntryContent
$cmax :: EntryContent -> EntryContent -> EntryContent
>= :: EntryContent -> EntryContent -> Bool
$c>= :: EntryContent -> EntryContent -> Bool
> :: EntryContent -> EntryContent -> Bool
$c> :: EntryContent -> EntryContent -> Bool
<= :: EntryContent -> EntryContent -> Bool
$c<= :: EntryContent -> EntryContent -> Bool
< :: EntryContent -> EntryContent -> Bool
$c< :: EntryContent -> EntryContent -> Bool
compare :: EntryContent -> EntryContent -> Ordering
$ccompare :: EntryContent -> EntryContent -> Ordering
$cp1Ord :: Eq EntryContent
Ord)

data Entry = Entry { Entry -> String
filepath    :: !FilePath
                   , Entry -> EntryContent
content     :: EntryContent
                   , Entry -> Permissions
permissions :: !Permissions
                   , Entry -> Ownership
ownership   :: !Ownership
                   , Entry -> Maybe ModTime
time        :: !(Maybe ModTime)
                   }
    deriving (Int -> Entry -> ShowS
[Entry] -> ShowS
Entry -> String
(Int -> Entry -> ShowS)
-> (Entry -> String) -> ([Entry] -> ShowS) -> Show Entry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Entry] -> ShowS
$cshowList :: [Entry] -> ShowS
show :: Entry -> String
$cshow :: Entry -> String
showsPrec :: Int -> Entry -> ShowS
$cshowsPrec :: Int -> Entry -> ShowS
Show, Entry -> Entry -> Bool
(Entry -> Entry -> Bool) -> (Entry -> Entry -> Bool) -> Eq Entry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Entry -> Entry -> Bool
$c/= :: Entry -> Entry -> Bool
== :: Entry -> Entry -> Bool
$c== :: Entry -> Entry -> Bool
Eq, Eq Entry
Eq Entry
-> (Entry -> Entry -> Ordering)
-> (Entry -> Entry -> Bool)
-> (Entry -> Entry -> Bool)
-> (Entry -> Entry -> Bool)
-> (Entry -> Entry -> Bool)
-> (Entry -> Entry -> Entry)
-> (Entry -> Entry -> Entry)
-> Ord Entry
Entry -> Entry -> Bool
Entry -> Entry -> Ordering
Entry -> Entry -> Entry
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 :: Entry -> Entry -> Entry
$cmin :: Entry -> Entry -> Entry
max :: Entry -> Entry -> Entry
$cmax :: Entry -> Entry -> Entry
>= :: Entry -> Entry -> Bool
$c>= :: Entry -> Entry -> Bool
> :: Entry -> Entry -> Bool
$c> :: Entry -> Entry -> Bool
<= :: Entry -> Entry -> Bool
$c<= :: Entry -> Entry -> Bool
< :: Entry -> Entry -> Bool
$c< :: Entry -> Entry -> Bool
compare :: Entry -> Entry -> Ordering
$ccompare :: Entry -> Entry -> Ordering
$cp1Ord :: Eq Entry
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)

-- | A user or group ID
type Id = Int64