{-# LANGUAGE CPP #-}
#if WINDOWS
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
#endif
module Data.Conduit.Tar.Types
    ( Header(..)
    , TarChunk(..)
    , TarException(..)
    , TarCreateException(..)
    , FileType(..)
    , FileInfo(..)
    , FileOffset
    , ByteCount
    , UserID
    , GroupID
    , DeviceID
    , EpochTime
    , CUid(..)
    , CGid(..)
    , encodeFilePath
    , decodeFilePath
    , getFileInfoPath
    ) where
import           Control.Exception        (Exception)
import           Data.ByteString          (ByteString)
import           Data.ByteString.Short    (ShortByteString)
import           Data.Word
import           System.Posix.Types
import qualified Data.ByteString.Char8         as S8
import           Data.Text                     as T
import           Data.Text.Encoding            as T
import           Data.Text.Encoding.Error      as T
#if WINDOWS
import           Data.Bits
import           Foreign.Storable
newtype CUid =
  CUid Word32
  deriving ( Bounded
           , Enum
           , Eq
           , Integral
           , Num
           , Ord
           , Read
           , Real
           , Show
           , Bits
           , Storable
           )
newtype CGid =
  CGid Word32
  deriving ( Bounded
           , Enum
           , Eq
           , Integral
           , Num
           , Ord
           , Read
           , Real
           , Show
           , Bits
           , Storable
           )
type UserID = CUid
type GroupID = CGid
#endif
data FileType
    = FTNormal
    | FTHardLink !ByteString
    | FTSymbolicLink !ByteString
    | FTCharacterSpecial
    | FTBlockSpecial
    | FTDirectory
    | FTFifo
    | FTOther !Word8
    deriving (Int -> FileType -> ShowS
[FileType] -> ShowS
FileType -> String
(Int -> FileType -> ShowS)
-> (FileType -> String) -> ([FileType] -> ShowS) -> Show FileType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileType] -> ShowS
$cshowList :: [FileType] -> ShowS
show :: FileType -> String
$cshow :: FileType -> String
showsPrec :: Int -> FileType -> ShowS
$cshowsPrec :: Int -> FileType -> ShowS
Show, FileType -> FileType -> Bool
(FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool) -> Eq FileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileType -> FileType -> Bool
$c/= :: FileType -> FileType -> Bool
== :: FileType -> FileType -> Bool
$c== :: FileType -> FileType -> Bool
Eq)
data FileInfo = FileInfo
    { FileInfo -> ByteString
filePath      :: !ByteString 
    , FileInfo -> UserID
fileUserId    :: !UserID  
    , FileInfo -> ByteString
fileUserName  :: !ByteString  
    , FileInfo -> GroupID
fileGroupId   :: !GroupID 
    , FileInfo -> ByteString
fileGroupName :: !ByteString  
    , FileInfo -> FileMode
fileMode      :: !FileMode 
    , FileInfo -> FileOffset
fileSize      :: !FileOffset 
    , FileInfo -> FileType
fileType      :: !FileType  
                                  
                                  
    , FileInfo -> EpochTime
fileModTime   :: !EpochTime 
    } deriving (Int -> FileInfo -> ShowS
[FileInfo] -> ShowS
FileInfo -> String
(Int -> FileInfo -> ShowS)
-> (FileInfo -> String) -> ([FileInfo] -> ShowS) -> Show FileInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileInfo] -> ShowS
$cshowList :: [FileInfo] -> ShowS
show :: FileInfo -> String
$cshow :: FileInfo -> String
showsPrec :: Int -> FileInfo -> ShowS
$cshowsPrec :: Int -> FileInfo -> ShowS
Show, FileInfo -> FileInfo -> Bool
(FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> Bool) -> Eq FileInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileInfo -> FileInfo -> Bool
$c/= :: FileInfo -> FileInfo -> Bool
== :: FileInfo -> FileInfo -> Bool
$c== :: FileInfo -> FileInfo -> Bool
Eq)
data  = 
    {          :: !FileOffset
    ,   :: !FileOffset
    ,  :: !ShortByteString
    ,        :: !CMode
    ,         :: !UserID
    ,         :: !GroupID
    ,     :: !FileOffset
    ,            :: !EpochTime
    ,   :: !Word8
    ,        :: !ShortByteString
    ,    :: !ShortByteString
    ,       :: !ShortByteString
    ,       :: !ShortByteString
    ,     :: !DeviceID
    ,     :: !DeviceID
    ,  :: !ShortByteString
    }
    deriving Int -> Header -> ShowS
[Header] -> ShowS
Header -> String
(Int -> Header -> ShowS)
-> (Header -> String) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Header] -> ShowS
$cshowList :: [Header] -> ShowS
show :: Header -> String
$cshow :: Header -> String
showsPrec :: Int -> Header -> ShowS
$cshowsPrec :: Int -> Header -> ShowS
Show
data TarChunk
    =  Header
    | ChunkPayload !FileOffset !ByteString
    | ChunkException TarException
    deriving Int -> TarChunk -> ShowS
[TarChunk] -> ShowS
TarChunk -> String
(Int -> TarChunk -> ShowS)
-> (TarChunk -> String) -> ([TarChunk] -> ShowS) -> Show TarChunk
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TarChunk] -> ShowS
$cshowList :: [TarChunk] -> ShowS
show :: TarChunk -> String
$cshow :: TarChunk -> String
showsPrec :: Int -> TarChunk -> ShowS
$cshowsPrec :: Int -> TarChunk -> ShowS
Show
data TarException
    = 
    | UnexpectedPayload !FileOffset
    |   !FileOffset
    | IncompletePayload !FileOffset !ByteCount
    | ShortTrailer      !FileOffset
    | BadTrailer        !FileOffset
    |      !FileOffset
    | BadChecksum       !FileOffset
    | FileTypeError     !FileOffset !Char !String
    | UnsupportedType   !FileType
    deriving Int -> TarException -> ShowS
[TarException] -> ShowS
TarException -> String
(Int -> TarException -> ShowS)
-> (TarException -> String)
-> ([TarException] -> ShowS)
-> Show TarException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TarException] -> ShowS
$cshowList :: [TarException] -> ShowS
show :: TarException -> String
$cshow :: TarException -> String
showsPrec :: Int -> TarException -> ShowS
$cshowsPrec :: Int -> TarException -> ShowS
Show
instance Exception TarException
data TarCreateException
    = FileNameTooLong   !FileInfo
    | TarCreationError  !String
    deriving Int -> TarCreateException -> ShowS
[TarCreateException] -> ShowS
TarCreateException -> String
(Int -> TarCreateException -> ShowS)
-> (TarCreateException -> String)
-> ([TarCreateException] -> ShowS)
-> Show TarCreateException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TarCreateException] -> ShowS
$cshowList :: [TarCreateException] -> ShowS
show :: TarCreateException -> String
$cshow :: TarCreateException -> String
showsPrec :: Int -> TarCreateException -> ShowS
$cshowsPrec :: Int -> TarCreateException -> ShowS
Show
instance Exception TarCreateException
encodeFilePath :: FilePath -> S8.ByteString
encodeFilePath :: String -> ByteString
encodeFilePath = Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> (String -> Text) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
decodeFilePath :: S8.ByteString -> FilePath
decodeFilePath :: ByteString -> String
decodeFilePath = Text -> String
T.unpack (Text -> String) -> (ByteString -> Text) -> ByteString -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OnDecodeError -> ByteString -> Text
T.decodeUtf8With OnDecodeError
T.lenientDecode
getFileInfoPath :: FileInfo -> FilePath
getFileInfoPath :: FileInfo -> String
getFileInfoPath = ByteString -> String
decodeFilePath (ByteString -> String)
-> (FileInfo -> ByteString) -> FileInfo -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileInfo -> ByteString
filePath