module Codec.Archive.Internal.Pack.Common ( mkEntry , mkContent ) where import Codec.Archive.Types import qualified Data.ByteString as BS import System.PosixCompat.Files (FileStatus, fileGroup, fileMode, fileOwner, getFileStatus, isDirectory, isRegularFile, isSymbolicLink, linkCount, readSymbolicLink) mkContent :: FilePath -> FileStatus -> IO (EntryContent FilePath BS.ByteString) mkContent :: FilePath -> FileStatus -> IO (EntryContent FilePath ByteString) mkContent FilePath fp FileStatus status = let res :: (Bool, Bool, Bool, LinkCount) res = (FileStatus -> Bool isRegularFile FileStatus status, FileStatus -> Bool isDirectory FileStatus status, FileStatus -> Bool isSymbolicLink FileStatus status, FileStatus -> LinkCount linkCount FileStatus status) in case (Bool, Bool, Bool, LinkCount) res of (Bool True, Bool False, Bool False, LinkCount 1) -> ByteString -> EntryContent FilePath ByteString forall fp e. e -> EntryContent fp e NormalFile (ByteString -> EntryContent FilePath ByteString) -> IO ByteString -> IO (EntryContent FilePath ByteString) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> FilePath -> IO ByteString BS.readFile FilePath fp (Bool True, Bool False, Bool False, LinkCount _) -> EntryContent FilePath ByteString -> IO (EntryContent FilePath ByteString) forall (f :: * -> *) a. Applicative f => a -> f a pure (EntryContent FilePath ByteString -> IO (EntryContent FilePath ByteString)) -> EntryContent FilePath ByteString -> IO (EntryContent FilePath ByteString) forall a b. (a -> b) -> a -> b $ FilePath -> EntryContent FilePath ByteString forall fp e. fp -> EntryContent fp e Hardlink FilePath fp (Bool False, Bool True, Bool False, LinkCount _) -> EntryContent FilePath ByteString -> IO (EntryContent FilePath ByteString) forall (f :: * -> *) a. Applicative f => a -> f a pure EntryContent FilePath ByteString forall fp e. EntryContent fp e Directory (Bool False, Bool False, Bool True, LinkCount _) -> FilePath -> Symlink -> EntryContent FilePath ByteString forall fp e. fp -> Symlink -> EntryContent fp e Symlink (FilePath -> Symlink -> EntryContent FilePath ByteString) -> IO FilePath -> IO (Symlink -> EntryContent FilePath ByteString) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> FilePath -> IO FilePath readSymbolicLink FilePath fp IO (Symlink -> EntryContent FilePath ByteString) -> IO Symlink -> IO (EntryContent FilePath ByteString) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Symlink -> IO Symlink forall (f :: * -> *) a. Applicative f => a -> f a pure Symlink SymlinkUndefined (Bool _, Bool _, Bool _, LinkCount _) -> FilePath -> IO (EntryContent FilePath ByteString) forall a. HasCallStack => FilePath -> a error FilePath "inconsistent read result" mkEntry :: FilePath -> IO (Entry FilePath BS.ByteString) mkEntry :: FilePath -> IO (Entry FilePath ByteString) mkEntry FilePath fp = do FileStatus status <- FilePath -> IO FileStatus getFileStatus FilePath fp EntryContent FilePath ByteString content' <- FilePath -> FileStatus -> IO (EntryContent FilePath ByteString) mkContent FilePath fp FileStatus status Entry FilePath ByteString -> IO (Entry FilePath ByteString) forall (f :: * -> *) a. Applicative f => a -> f a pure (Entry FilePath ByteString -> IO (Entry FilePath ByteString)) -> Entry FilePath ByteString -> IO (Entry FilePath ByteString) forall a b. (a -> b) -> a -> b $ FilePath -> EntryContent FilePath ByteString -> Permissions -> Ownership -> Maybe ModTime -> Entry FilePath ByteString forall fp e. fp -> EntryContent fp e -> Permissions -> Ownership -> Maybe ModTime -> Entry fp e Entry FilePath fp EntryContent FilePath ByteString content' (FileStatus -> Permissions fileMode FileStatus status) (Maybe FilePath -> Maybe FilePath -> Id -> Id -> Ownership Ownership Maybe FilePath forall a. Maybe a Nothing Maybe FilePath forall a. Maybe a Nothing (UserID -> Id forall a b. (Integral a, Num b) => a -> b fromIntegral (UserID -> Id) -> UserID -> Id forall a b. (a -> b) -> a -> b $ FileStatus -> UserID fileOwner FileStatus status) (GroupID -> Id forall a b. (Integral a, Num b) => a -> b fromIntegral (GroupID -> Id) -> GroupID -> Id forall a b. (a -> b) -> a -> b $ FileStatus -> GroupID fileGroup FileStatus status)) Maybe ModTime forall a. Maybe a Nothing