{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, CPP #-}
module GHC.SysTools.Ar
(ArchiveEntry(..)
,Archive(..)
,afilter
,parseAr
,loadAr
,loadObj
,writeBSDAr
,writeGNUAr
,isBSDSymdef
,isGNUSymdef
)
where
import GHC.Prelude
import Data.List (mapAccumL, isPrefixOf)
import Data.Monoid ((<>))
import Data.Binary.Get
import Data.Binary.Put
import Control.Monad
import Control.Applicative
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Lazy as L
#if !defined(mingw32_HOST_OS)
import qualified System.Posix.Files as POSIX
#endif
import System.FilePath (takeFileName)
data ArchiveEntry = ArchiveEntry
{ ArchiveEntry -> [Char]
filename :: String
, ArchiveEntry -> Int
filetime :: Int
, ArchiveEntry -> Int
fileown :: Int
, ArchiveEntry -> Int
filegrp :: Int
, ArchiveEntry -> Int
filemode :: Int
, ArchiveEntry -> Int
filesize :: Int
, ArchiveEntry -> ByteString
filedata :: B.ByteString
} deriving (ArchiveEntry -> ArchiveEntry -> Bool
(ArchiveEntry -> ArchiveEntry -> Bool)
-> (ArchiveEntry -> ArchiveEntry -> Bool) -> Eq ArchiveEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArchiveEntry -> ArchiveEntry -> Bool
$c/= :: ArchiveEntry -> ArchiveEntry -> Bool
== :: ArchiveEntry -> ArchiveEntry -> Bool
$c== :: ArchiveEntry -> ArchiveEntry -> Bool
External instance of the constraint type Eq ByteString
External instance of the constraint type Eq Int
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
Eq, Int -> ArchiveEntry -> ShowS
[ArchiveEntry] -> ShowS
ArchiveEntry -> [Char]
(Int -> ArchiveEntry -> ShowS)
-> (ArchiveEntry -> [Char])
-> ([ArchiveEntry] -> ShowS)
-> Show ArchiveEntry
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ArchiveEntry] -> ShowS
$cshowList :: [ArchiveEntry] -> ShowS
show :: ArchiveEntry -> [Char]
$cshow :: ArchiveEntry -> [Char]
showsPrec :: Int -> ArchiveEntry -> ShowS
$cshowsPrec :: Int -> ArchiveEntry -> ShowS
External instance of the constraint type Show ByteString
External instance of the constraint type Ord Int
External instance of the constraint type Show Int
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
Show)
newtype Archive = Archive [ArchiveEntry]
deriving (Archive -> Archive -> Bool
(Archive -> Archive -> Bool)
-> (Archive -> Archive -> Bool) -> Eq Archive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Archive -> Archive -> Bool
$c/= :: Archive -> Archive -> Bool
== :: Archive -> Archive -> Bool
$c== :: Archive -> Archive -> Bool
Instance of class: Eq of the constraint type Eq ArchiveEntry
Instance of class: Eq of the constraint type Eq ArchiveEntry
External instance of the constraint type forall a. Eq a => Eq [a]
Instance of class: Eq of the constraint type Eq ArchiveEntry
Eq, Int -> Archive -> ShowS
[Archive] -> ShowS
Archive -> [Char]
(Int -> Archive -> ShowS)
-> (Archive -> [Char]) -> ([Archive] -> ShowS) -> Show Archive
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Archive] -> ShowS
$cshowList :: [Archive] -> ShowS
show :: Archive -> [Char]
$cshow :: Archive -> [Char]
showsPrec :: Int -> Archive -> ShowS
$cshowsPrec :: Int -> Archive -> ShowS
Instance of class: Show of the constraint type Show ArchiveEntry
External instance of the constraint type Ord Int
External instance of the constraint type forall a. Show a => Show [a]
Instance of class: Show of the constraint type Show ArchiveEntry
Show, b -> Archive -> Archive
NonEmpty Archive -> Archive
Archive -> Archive -> Archive
(Archive -> Archive -> Archive)
-> (NonEmpty Archive -> Archive)
-> (forall b. Integral b => b -> Archive -> Archive)
-> Semigroup Archive
forall b. Integral b => b -> Archive -> Archive
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> Archive -> Archive
$cstimes :: forall b. Integral b => b -> Archive -> Archive
sconcat :: NonEmpty Archive -> Archive
$csconcat :: NonEmpty Archive -> Archive
<> :: Archive -> Archive -> Archive
$c<> :: Archive -> Archive -> Archive
Evidence bound by a type signature of the constraint type Integral b
Evidence bound by a HsWrapper of the constraint type Integral b
Evidence bound by a HsWrapper of the constraint type Integral b
External instance of the constraint type forall a. Semigroup [a]
Semigroup, Semigroup Archive
Archive
Semigroup Archive
-> Archive
-> (Archive -> Archive -> Archive)
-> ([Archive] -> Archive)
-> Monoid Archive
[Archive] -> Archive
Archive -> Archive -> Archive
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [Archive] -> Archive
$cmconcat :: [Archive] -> Archive
mappend :: Archive -> Archive -> Archive
$cmappend :: Archive -> Archive -> Archive
mempty :: Archive
$cmempty :: Archive
Instance of class: Semigroup of the constraint type Semigroup Archive
Instance of class: Semigroup of the constraint type Semigroup Archive
External instance of the constraint type forall a. Monoid [a]
Monoid)
afilter :: (ArchiveEntry -> Bool) -> Archive -> Archive
afilter :: (ArchiveEntry -> Bool) -> Archive -> Archive
afilter ArchiveEntry -> Bool
f (Archive [ArchiveEntry]
xs) = [ArchiveEntry] -> Archive
Archive ((ArchiveEntry -> Bool) -> [ArchiveEntry] -> [ArchiveEntry]
forall a. (a -> Bool) -> [a] -> [a]
filter ArchiveEntry -> Bool
f [ArchiveEntry]
xs)
isBSDSymdef, isGNUSymdef :: ArchiveEntry -> Bool
isBSDSymdef :: ArchiveEntry -> Bool
isBSDSymdef ArchiveEntry
a = [Char]
"__.SYMDEF" [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
External instance of the constraint type Eq Char
`isPrefixOf` (ArchiveEntry -> [Char]
filename ArchiveEntry
a)
isGNUSymdef :: ArchiveEntry -> Bool
isGNUSymdef ArchiveEntry
a = [Char]
"/" [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
== (ArchiveEntry -> [Char]
filename ArchiveEntry
a)
getPaddedInt :: B.ByteString -> Int
getPaddedInt :: ByteString -> Int
getPaddedInt = [Char] -> Int
forall a. Read a => [Char] -> a
External instance of the constraint type Read Int
read ([Char] -> Int) -> (ByteString -> [Char]) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Char]
C.unpack (ByteString -> [Char])
-> (ByteString -> ByteString) -> ByteString -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> ByteString
C.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
/= Char
'\x20')
putPaddedInt :: Int -> Int -> Put
putPaddedInt :: Int -> Int -> Put
putPaddedInt Int
padding Int
i = Char -> Int -> [Char] -> Put
putPaddedString Char
'\x20' Int
padding (Int -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Int
show Int
i)
putPaddedString :: Char -> Int -> String -> Put
putPaddedString :: Char -> Int -> [Char] -> Put
putPaddedString Char
pad Int
padding [Char]
s = ByteString -> Put
putByteString (ByteString -> Put) -> ([Char] -> ByteString) -> [Char] -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ByteString
C.pack ([Char] -> ByteString) -> ShowS -> [Char] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Int -> [a] -> [a]
take Int
padding ([Char] -> Put) -> [Char] -> Put
forall a b. (a -> b) -> a -> b
$ [Char]
s [Char] -> ShowS
forall a. Monoid a => a -> a -> a
External instance of the constraint type forall a. Monoid [a]
`mappend` (Char -> [Char]
forall a. a -> [a]
repeat Char
pad)
getBSDArchEntries :: Get [ArchiveEntry]
getBSDArchEntries :: Get [ArchiveEntry]
getBSDArchEntries = do
Bool
empty <- Get Bool
isEmpty
if Bool
empty then
[ArchiveEntry] -> Get [ArchiveEntry]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return []
else do
ByteString
name <- Int -> Get ByteString
getByteString Int
16
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative Get
when (Char
'/' Char -> ByteString -> Bool
`C.elem` ByteString
name Bool -> Bool -> Bool
&& Int -> ByteString -> ByteString
C.take Int
3 ByteString
name ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ByteString
/= ByteString
"#1/") (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
[Char] -> Get ()
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
External instance of the constraint type MonadFail Get
fail [Char]
"Looks like GNU Archive"
Int
time <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
12
Int
own <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
6
Int
grp <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
6
Int
mode <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
8
Int
st_size <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
10
ByteString
end <- Int -> Get ByteString
getByteString Int
2
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative Get
when (ByteString
end ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ByteString
/= ByteString
"\x60\x0a") (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
[Char] -> Get ()
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
External instance of the constraint type MonadFail Get
fail ([Char]
"[BSD Archive] Invalid archive header end marker for name: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++
ByteString -> [Char]
C.unpack ByteString
name)
Int
off1 <- (Int64 -> Int) -> Get Int64 -> Get Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type Monad Get
liftM Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Int64
fromIntegral Get Int64
bytesRead :: Get Int
[Char]
name <- if ByteString -> [Char]
C.unpack (Int -> ByteString -> ByteString
C.take Int
3 ByteString
name) [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
== [Char]
"#1/" then
(ByteString -> [Char]) -> Get ByteString -> Get [Char]
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type Monad Get
liftM (ByteString -> [Char]
C.unpack (ByteString -> [Char])
-> (ByteString -> ByteString) -> ByteString -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> ByteString
C.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
/= Char
'\0')) (Int -> Get ByteString
getByteString (Int -> Get ByteString) -> Int -> Get ByteString
forall a b. (a -> b) -> a -> b
$ [Char] -> Int
forall a. Read a => [Char] -> a
External instance of the constraint type Read Int
read ([Char] -> Int) -> [Char] -> Int
forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
C.unpack (ByteString -> [Char]) -> ByteString -> [Char]
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
C.drop Int
3 ByteString
name)
else
[Char] -> Get [Char]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return ([Char] -> Get [Char]) -> [Char] -> Get [Char]
forall a b. (a -> b) -> a -> b
$ ByteString -> [Char]
C.unpack (ByteString -> [Char]) -> ByteString -> [Char]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ByteString -> ByteString
C.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
/= Char
' ') ByteString
name
Int
off2 <- (Int64 -> Int) -> Get Int64 -> Get Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type Monad Get
liftM Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral Int64
fromIntegral Get Int64
bytesRead :: Get Int
ByteString
file <- Int -> Get ByteString
getByteString (Int
st_size Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- (Int
off2 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
off1))
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative Get
when (Int -> Bool
forall a. Integral a => a -> Bool
External instance of the constraint type Integral Int
odd Int
st_size) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
External instance of the constraint type Functor Get
void (Int -> Get ByteString
getByteString Int
1)
[ArchiveEntry]
rest <- Get [ArchiveEntry]
getBSDArchEntries
[ArchiveEntry] -> Get [ArchiveEntry]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return ([ArchiveEntry] -> Get [ArchiveEntry])
-> [ArchiveEntry] -> Get [ArchiveEntry]
forall a b. (a -> b) -> a -> b
$ ([Char]
-> Int -> Int -> Int -> Int -> Int -> ByteString -> ArchiveEntry
ArchiveEntry [Char]
name Int
time Int
own Int
grp Int
mode (Int
st_size Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- (Int
off2 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
off1)) ByteString
file) ArchiveEntry -> [ArchiveEntry] -> [ArchiveEntry]
forall a. a -> [a] -> [a]
: [ArchiveEntry]
rest
getGNUArchEntries :: Maybe ArchiveEntry -> Get [ArchiveEntry]
getGNUArchEntries :: Maybe ArchiveEntry -> Get [ArchiveEntry]
getGNUArchEntries Maybe ArchiveEntry
extInfo = do
Bool
empty <- Get Bool
isEmpty
if Bool
empty
then [ArchiveEntry] -> Get [ArchiveEntry]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return []
else
do
ByteString
name <- Int -> Get ByteString
getByteString Int
16
Int
time <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
12
Int
own <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
6
Int
grp <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
6
Int
mode <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
8
Int
st_size <- ByteString -> Int
getPaddedInt (ByteString -> Int) -> Get ByteString -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Int -> Get ByteString
getByteString Int
10
ByteString
end <- Int -> Get ByteString
getByteString Int
2
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative Get
when (ByteString
end ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq ByteString
/= ByteString
"\x60\x0a") (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
[Char] -> Get ()
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
External instance of the constraint type MonadFail Get
fail ([Char]
"[BSD Archive] Invalid archive header end marker for name: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++
ByteString -> [Char]
C.unpack ByteString
name)
ByteString
file <- Int -> Get ByteString
getByteString Int
st_size
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative Get
when (Int -> Bool
forall a. Integral a => a -> Bool
External instance of the constraint type Integral Int
odd Int
st_size) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
External instance of the constraint type Functor Get
void (Int -> Get ByteString
getByteString Int
1)
[Char]
name <- [Char] -> Get [Char]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return ([Char] -> Get [Char])
-> (ByteString -> [Char]) -> ByteString -> Get [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Char]
C.unpack (ByteString -> Get [Char]) -> ByteString -> Get [Char]
forall a b. (a -> b) -> a -> b
$
if ByteString -> [Char]
C.unpack (Int -> ByteString -> ByteString
C.take Int
1 ByteString
name) [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
== [Char]
"/"
then case (Char -> Bool) -> ByteString -> ByteString
C.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
/= Char
' ') ByteString
name of
name :: ByteString
name@ByteString
"/" -> ByteString
name
name :: ByteString
name@ByteString
"//" -> ByteString
name
ByteString
name -> Maybe ArchiveEntry -> Int -> ByteString
getExtName Maybe ArchiveEntry
extInfo ([Char] -> Int
forall a. Read a => [Char] -> a
External instance of the constraint type Read Int
read ([Char] -> Int) -> (ByteString -> [Char]) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Char]
C.unpack (ByteString -> Int) -> ByteString -> Int
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
C.drop Int
1 ByteString
name)
else (Char -> Bool) -> ByteString -> ByteString
C.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
/= Char
'/') ByteString
name
case [Char]
name of
[Char]
"/" -> Maybe ArchiveEntry -> Get [ArchiveEntry]
getGNUArchEntries Maybe ArchiveEntry
extInfo
[Char]
"//" -> Maybe ArchiveEntry -> Get [ArchiveEntry]
getGNUArchEntries (ArchiveEntry -> Maybe ArchiveEntry
forall a. a -> Maybe a
Just ([Char]
-> Int -> Int -> Int -> Int -> Int -> ByteString -> ArchiveEntry
ArchiveEntry [Char]
name Int
time Int
own Int
grp Int
mode Int
st_size ByteString
file))
[Char]
_ -> ([Char]
-> Int -> Int -> Int -> Int -> Int -> ByteString -> ArchiveEntry
ArchiveEntry [Char]
name Int
time Int
own Int
grp Int
mode Int
st_size ByteString
file ArchiveEntry -> [ArchiveEntry] -> [ArchiveEntry]
forall a. a -> [a] -> [a]
:) ([ArchiveEntry] -> [ArchiveEntry])
-> Get [ArchiveEntry] -> Get [ArchiveEntry]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Maybe ArchiveEntry -> Get [ArchiveEntry]
getGNUArchEntries Maybe ArchiveEntry
extInfo
where
getExtName :: Maybe ArchiveEntry -> Int -> B.ByteString
getExtName :: Maybe ArchiveEntry -> Int -> ByteString
getExtName Maybe ArchiveEntry
Nothing Int
_ = [Char] -> ByteString
forall a. HasCallStack => [Char] -> a
error [Char]
"Invalid extended filename reference."
getExtName (Just ArchiveEntry
info) Int
offset = (Char -> Bool) -> ByteString -> ByteString
C.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Char
/= Char
'/') (ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString -> ByteString
C.drop Int
offset (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ArchiveEntry -> ByteString
filedata ArchiveEntry
info
putArchEntry :: ArchiveEntry -> PutM ()
putArchEntry :: ArchiveEntry -> Put
putArchEntry (ArchiveEntry [Char]
name Int
time Int
own Int
grp Int
mode Int
st_size ByteString
file) = do
Char -> Int -> [Char] -> Put
putPaddedString Char
' ' Int
16 [Char]
name
Int -> Int -> Put
putPaddedInt Int
12 Int
time
Int -> Int -> Put
putPaddedInt Int
6 Int
own
Int -> Int -> Put
putPaddedInt Int
6 Int
grp
Int -> Int -> Put
putPaddedInt Int
8 Int
mode
Int -> Int -> Put
putPaddedInt Int
10 (Int
st_size Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
pad)
ByteString -> Put
putByteString ByteString
"\x60\x0a"
ByteString -> Put
putByteString ByteString
file
Bool -> Put -> Put
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative PutM
when (Int
pad Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Int
1) (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$
Word8 -> Put
putWord8 Word8
0x0a
where
pad :: Int
pad = Int
st_size Int -> Int -> Int
forall a. Integral a => a -> a -> a
External instance of the constraint type Integral Int
`mod` Int
2
getArchMagic :: Get ()
getArchMagic :: Get ()
getArchMagic = do
[Char]
magic <- (ByteString -> [Char]) -> Get ByteString -> Get [Char]
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type Monad Get
liftM ByteString -> [Char]
C.unpack (Get ByteString -> Get [Char]) -> Get ByteString -> Get [Char]
forall a b. (a -> b) -> a -> b
$ Int -> Get ByteString
getByteString Int
8
if [Char]
magic [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
/= [Char]
"!<arch>\n"
then [Char] -> Get ()
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
External instance of the constraint type MonadFail Get
fail ([Char] -> Get ()) -> [Char] -> Get ()
forall a b. (a -> b) -> a -> b
$ [Char]
"Invalid magic number " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> [Char]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
show [Char]
magic
else () -> Get ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return ()
putArchMagic :: Put
putArchMagic :: Put
putArchMagic = ByteString -> Put
putByteString (ByteString -> Put) -> ByteString -> Put
forall a b. (a -> b) -> a -> b
$ [Char] -> ByteString
C.pack [Char]
"!<arch>\n"
getArch :: Get Archive
getArch :: Get Archive
getArch = [ArchiveEntry] -> Archive
Archive ([ArchiveEntry] -> Archive) -> Get [ArchiveEntry] -> Get Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> do
Get ()
getArchMagic
Get [ArchiveEntry]
getBSDArchEntries Get [ArchiveEntry] -> Get [ArchiveEntry] -> Get [ArchiveEntry]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
External instance of the constraint type Alternative Get
<|> Maybe ArchiveEntry -> Get [ArchiveEntry]
getGNUArchEntries Maybe ArchiveEntry
forall a. Maybe a
Nothing
putBSDArch :: Archive -> PutM ()
putBSDArch :: Archive -> Put
putBSDArch (Archive [ArchiveEntry]
as) = do
Put
putArchMagic
(ArchiveEntry -> Put) -> [ArchiveEntry] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type Monad PutM
External instance of the constraint type Foldable []
mapM_ ArchiveEntry -> Put
putArchEntry ([ArchiveEntry] -> [ArchiveEntry]
processEntries [ArchiveEntry]
as)
where
padStr :: a -> Int -> [a] -> [a]
padStr a
pad Int
size [a]
str = Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
size ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ [a]
str [a] -> [a] -> [a]
forall a. Semigroup a => a -> a -> a
External instance of the constraint type forall a. Semigroup [a]
<> a -> [a]
forall a. a -> [a]
repeat a
pad
nameSize :: t a -> Int
nameSize t a
name = case t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Evidence bound by a type signature of the constraint type Foldable t
length t a
name Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
External instance of the constraint type Integral Int
`divMod` Int
4 of
(Int
n, Int
0) -> Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
* Int
n
(Int
n, Int
_) -> Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
* (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
1)
needExt :: t Char -> Bool
needExt t Char
name = t Char -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Evidence bound by a type signature of the constraint type Foldable t
length t Char
name Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
16 Bool -> Bool -> Bool
|| Char
' ' Char -> t Char -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq Char
Evidence bound by a type signature of the constraint type Foldable t
`elem` t Char
name
processEntry :: ArchiveEntry -> ArchiveEntry
processEntry :: ArchiveEntry -> ArchiveEntry
processEntry archive :: ArchiveEntry
archive@(ArchiveEntry [Char]
name Int
_ Int
_ Int
_ Int
_ Int
st_size ByteString
_)
| [Char] -> Bool
forall {t :: * -> *}. Foldable t => t Char -> Bool
External instance of the constraint type Foldable []
needExt [Char]
name = ArchiveEntry
archive { filename :: [Char]
filename = [Char]
"#1/" [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
External instance of the constraint type forall a. Semigroup [a]
<> Int -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Int
show Int
sz
, filedata :: ByteString
filedata = [Char] -> ByteString
C.pack (Char -> Int -> ShowS
forall {a}. a -> Int -> [a] -> [a]
padStr Char
'\0' Int
sz [Char]
name) ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
External instance of the constraint type Semigroup ByteString
<> ArchiveEntry -> ByteString
filedata ArchiveEntry
archive
, filesize :: Int
filesize = Int
st_size Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
sz }
| Bool
otherwise = ArchiveEntry
archive
where sz :: Int
sz = [Char] -> Int
forall {t :: * -> *} {a}. Foldable t => t a -> Int
External instance of the constraint type Foldable []
nameSize [Char]
name
processEntries :: [ArchiveEntry] -> [ArchiveEntry]
processEntries = (ArchiveEntry -> ArchiveEntry) -> [ArchiveEntry] -> [ArchiveEntry]
forall a b. (a -> b) -> [a] -> [b]
map ArchiveEntry -> ArchiveEntry
processEntry
putGNUArch :: Archive -> PutM ()
putGNUArch :: Archive -> Put
putGNUArch (Archive [ArchiveEntry]
as) = do
Put
putArchMagic
(ArchiveEntry -> Put) -> [ArchiveEntry] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type Monad PutM
External instance of the constraint type Foldable []
mapM_ ArchiveEntry -> Put
putArchEntry ([ArchiveEntry] -> [ArchiveEntry]
processEntries [ArchiveEntry]
as)
where
processEntry :: ArchiveEntry -> ArchiveEntry -> (ArchiveEntry, ArchiveEntry)
processEntry :: ArchiveEntry -> ArchiveEntry -> (ArchiveEntry, ArchiveEntry)
processEntry ArchiveEntry
extInfo archive :: ArchiveEntry
archive@(ArchiveEntry [Char]
name Int
_ Int
_ Int
_ Int
_ Int
_ ByteString
_)
| [Char] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length [Char]
name Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
15 = ( ArchiveEntry
extInfo { filesize :: Int
filesize = ArchiveEntry -> Int
filesize ArchiveEntry
extInfo Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ [Char] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length [Char]
name Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
2
, filedata :: ByteString
filedata = ArchiveEntry -> ByteString
filedata ArchiveEntry
extInfo ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
External instance of the constraint type Semigroup ByteString
<> [Char] -> ByteString
C.pack [Char]
name ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
External instance of the constraint type Semigroup ByteString
<> ByteString
"/\n" }
, ArchiveEntry
archive { filename :: [Char]
filename = [Char]
"/" [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
External instance of the constraint type forall a. Semigroup [a]
<> Int -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Int
show (ArchiveEntry -> Int
filesize ArchiveEntry
extInfo) } )
| Bool
otherwise = ( ArchiveEntry
extInfo, ArchiveEntry
archive { filename :: [Char]
filename = [Char]
name [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
External instance of the constraint type forall a. Semigroup [a]
<> [Char]
"/" } )
processEntries :: [ArchiveEntry] -> [ArchiveEntry]
processEntries :: [ArchiveEntry] -> [ArchiveEntry]
processEntries =
(ArchiveEntry -> [ArchiveEntry] -> [ArchiveEntry])
-> (ArchiveEntry, [ArchiveEntry]) -> [ArchiveEntry]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (:) ((ArchiveEntry, [ArchiveEntry]) -> [ArchiveEntry])
-> ([ArchiveEntry] -> (ArchiveEntry, [ArchiveEntry]))
-> [ArchiveEntry]
-> [ArchiveEntry]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ArchiveEntry -> ArchiveEntry -> (ArchiveEntry, ArchiveEntry))
-> ArchiveEntry -> [ArchiveEntry] -> (ArchiveEntry, [ArchiveEntry])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
External instance of the constraint type Traversable []
mapAccumL ArchiveEntry -> ArchiveEntry -> (ArchiveEntry, ArchiveEntry)
processEntry ([Char]
-> Int -> Int -> Int -> Int -> Int -> ByteString -> ArchiveEntry
ArchiveEntry [Char]
"//" Int
0 Int
0 Int
0 Int
0 Int
0 ByteString
forall a. Monoid a => a
External instance of the constraint type Monoid ByteString
mempty)
parseAr :: B.ByteString -> Archive
parseAr :: ByteString -> Archive
parseAr = Get Archive -> ByteString -> Archive
forall a. Get a -> ByteString -> a
runGet Get Archive
getArch (ByteString -> Archive)
-> (ByteString -> ByteString) -> ByteString -> Archive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
L.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative []
pure
writeBSDAr, writeGNUAr :: FilePath -> Archive -> IO ()
writeBSDAr :: [Char] -> Archive -> IO ()
writeBSDAr [Char]
fp = [Char] -> ByteString -> IO ()
L.writeFile [Char]
fp (ByteString -> IO ())
-> (Archive -> ByteString) -> Archive -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPut (Put -> ByteString) -> (Archive -> Put) -> Archive -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Archive -> Put
putBSDArch
writeGNUAr :: [Char] -> Archive -> IO ()
writeGNUAr [Char]
fp = [Char] -> ByteString -> IO ()
L.writeFile [Char]
fp (ByteString -> IO ())
-> (Archive -> ByteString) -> Archive -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPut (Put -> ByteString) -> (Archive -> Put) -> Archive -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Archive -> Put
putGNUArch
loadAr :: FilePath -> IO Archive
loadAr :: [Char] -> IO Archive
loadAr [Char]
fp = ByteString -> Archive
parseAr (ByteString -> Archive) -> IO ByteString -> IO Archive
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> [Char] -> IO ByteString
B.readFile [Char]
fp
loadObj :: FilePath -> IO ArchiveEntry
loadObj :: [Char] -> IO ArchiveEntry
loadObj [Char]
fp = do
ByteString
payload <- [Char] -> IO ByteString
B.readFile [Char]
fp
(Int
modt, Int
own, Int
grp, Int
mode) <- [Char] -> IO (Int, Int, Int, Int)
fileInfo [Char]
fp
ArchiveEntry -> IO ArchiveEntry
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (ArchiveEntry -> IO ArchiveEntry)
-> ArchiveEntry -> IO ArchiveEntry
forall a b. (a -> b) -> a -> b
$ [Char]
-> Int -> Int -> Int -> Int -> Int -> ByteString -> ArchiveEntry
ArchiveEntry
(ShowS
takeFileName [Char]
fp) Int
modt Int
own Int
grp Int
mode
(ByteString -> Int
B.length ByteString
payload) ByteString
payload
fileInfo :: FilePath -> IO ( Int, Int, Int, Int)
#if defined(mingw32_HOST_OS)
fileInfo _ = pure (0,0,0,0)
#else
fileInfo :: [Char] -> IO (Int, Int, Int, Int)
fileInfo [Char]
fp = FileStatus -> (Int, Int, Int, Int)
forall {b} {c}. (Num b, Num c) => FileStatus -> (Int, b, c, Int)
External instance of the constraint type Num Int
External instance of the constraint type Num Int
go (FileStatus -> (Int, Int, Int, Int))
-> IO FileStatus -> IO (Int, Int, Int, Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> [Char] -> IO FileStatus
POSIX.getFileStatus [Char]
fp
where go :: FileStatus -> (Int, b, c, Int)
go FileStatus
status = ( EpochTime -> Int
forall a. Enum a => a -> Int
External instance of the constraint type Enum EpochTime
fromEnum (EpochTime -> Int) -> EpochTime -> Int
forall a b. (a -> b) -> a -> b
$ FileStatus -> EpochTime
POSIX.modificationTime FileStatus
status
, UserID -> b
forall a b. (Integral a, Num b) => a -> b
Evidence bound by a type signature of the constraint type Num b
External instance of the constraint type Integral UserID
fromIntegral (UserID -> b) -> UserID -> b
forall a b. (a -> b) -> a -> b
$ FileStatus -> UserID
POSIX.fileOwner FileStatus
status
, GroupID -> c
forall a b. (Integral a, Num b) => a -> b
Evidence bound by a type signature of the constraint type Num c
External instance of the constraint type Integral GroupID
fromIntegral (GroupID -> c) -> GroupID -> c
forall a b. (a -> b) -> a -> b
$ FileStatus -> GroupID
POSIX.fileGroup FileStatus
status
, Int -> Int
oct2dec (Int -> Int) -> (FileMode -> Int) -> FileMode -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileMode -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral FileMode
fromIntegral (FileMode -> Int) -> FileMode -> Int
forall a b. (a -> b) -> a -> b
$ FileStatus -> FileMode
POSIX.fileMode FileStatus
status
)
oct2dec :: Int -> Int
oct2dec :: Int -> Int
oct2dec = (Int -> Int -> Int) -> Int -> [Int] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' (\Int
a Int
b -> Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
* Int
10 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
b) Int
0 ([Int] -> Int) -> (Int -> [Int]) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
forall a. [a] -> [a]
reverse ([Int] -> [Int]) -> (Int -> [Int]) -> Int -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> [Int]
forall {a}. Integral a => a -> a -> [a]
External instance of the constraint type Integral Int
dec Int
8
where dec :: a -> a -> [a]
dec a
_ a
0 = []
dec a
b a
i = let (a
rest, a
last) = a
i a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
Evidence bound by a type signature of the constraint type Integral a
`quotRem` a
b
in a
lasta -> [a] -> [a]
forall a. a -> [a] -> [a]
:a -> a -> [a]
dec a
b a
rest
#endif