{-# LANGUAGE Safe #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module System.FileArchive.GZip (
Header(..), Section, GZipError(..),
Footer(..),
decompress,
hDecompress,
read_sections,
read_header,
read_section
)
where
import Control.Monad.Except (MonadError(..))
import Data.Bits ((.&.))
import Data.Bits.Utils (fromBytes)
import Data.Char (ord)
import Data.Compression.Inflate (inflate_string_remainder)
import Data.Hash.CRC32.GZip (update_crc)
import Data.Word (Word32)
import System.IO (Handle, hGetContents, hPutStr)
data GZipError = CRCError
| NotGZIPFile
| UnknownMethod
| UnknownError String
deriving (GZipError -> GZipError -> Bool
(GZipError -> GZipError -> Bool)
-> (GZipError -> GZipError -> Bool) -> Eq GZipError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GZipError -> GZipError -> Bool
== :: GZipError -> GZipError -> Bool
$c/= :: GZipError -> GZipError -> Bool
/= :: GZipError -> GZipError -> Bool
Eq, Int -> GZipError -> ShowS
[GZipError] -> ShowS
GZipError -> [Char]
(Int -> GZipError -> ShowS)
-> (GZipError -> [Char])
-> ([GZipError] -> ShowS)
-> Show GZipError
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GZipError -> ShowS
showsPrec :: Int -> GZipError -> ShowS
$cshow :: GZipError -> [Char]
show :: GZipError -> [Char]
$cshowList :: [GZipError] -> ShowS
showList :: [GZipError] -> ShowS
Show)
magic :: String
magic :: [Char]
magic = [Char]
"\x1f\x8b"
fFHCRC, fFEXTRA, fFNAME, fFCOMMENT :: Int
fFHCRC :: Int
fFHCRC = Int
2
= Int
4
fFNAME :: Int
fFNAME = Int
8
= Int
16
data = {
Header -> Int
method :: Int,
Header -> Int
flags :: Int,
:: Maybe String,
Header -> Maybe [Char]
filename :: Maybe String,
:: Maybe String,
Header -> Word32
mtime :: Word32,
Header -> Int
xfl :: Int,
Header -> Int
os :: Int
} deriving (Header -> Header -> Bool
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
/= :: Header -> Header -> Bool
Eq, Int -> Header -> ShowS
[Header] -> ShowS
Header -> [Char]
(Int -> Header -> ShowS)
-> (Header -> [Char]) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Header -> ShowS
showsPrec :: Int -> Header -> ShowS
$cshow :: Header -> [Char]
show :: Header -> [Char]
$cshowList :: [Header] -> ShowS
showList :: [Header] -> ShowS
Show)
data = {
Footer -> Word32
size :: Word32,
Footer -> Word32
crc32 :: Word32,
Footer -> Bool
crc32valid :: Bool
}
type Section = (Header, String, Footer)
split1 :: String -> (Char, String)
split1 :: [Char] -> (Char, [Char])
split1 [Char]
s = ([Char] -> Char
forall a. HasCallStack => [a] -> a
head [Char]
s, ShowS
forall a. HasCallStack => [a] -> [a]
tail [Char]
s)
hDecompress :: Handle
-> Handle
-> IO (Maybe GZipError)
hDecompress :: Handle -> Handle -> IO (Maybe GZipError)
hDecompress Handle
infd Handle
outfd =
do inc <- Handle -> IO [Char]
hGetContents Handle
infd
let (outstr, err) = decompress inc
hPutStr outfd outstr
return err
decompress :: String -> (String, Maybe GZipError)
decompress :: [Char] -> ([Char], Maybe GZipError)
decompress [Char]
s =
let procs :: [Section] -> (String, Bool)
procs :: [Section] -> ([Char], Bool)
procs [] = ([], Bool
True)
procs ((Header
_, [Char]
content, Footer
foot):[Section]
xs) =
let ([Char]
nexth, Bool
nextb) = [Section] -> ([Char], Bool)
procs [Section]
xs in
([Char]
content [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
nexth, (Footer -> Bool
crc32valid Footer
foot) Bool -> Bool -> Bool
&& Bool
nextb)
in case [Char] -> Either GZipError [Section]
read_sections [Char]
s of
Left GZipError
x -> ([Char]
"", GZipError -> Maybe GZipError
forall a. a -> Maybe a
Just GZipError
x)
Right [Section]
x -> let ([Char]
decomp, Bool
iscrcok) = [Section] -> ([Char], Bool)
procs [Section]
x
in ([Char]
decomp, if Bool
iscrcok then Maybe GZipError
forall a. Maybe a
Nothing else GZipError -> Maybe GZipError
forall a. a -> Maybe a
Just GZipError
CRCError)
read_sections :: String -> Either GZipError [Section]
read_sections :: [Char] -> Either GZipError [Section]
read_sections [] = [Section] -> Either GZipError [Section]
forall a b. b -> Either a b
Right []
read_sections [Char]
s =
do x <- [Char] -> Either GZipError (Section, [Char])
read_section [Char]
s
case x of
(Section
sect, [Char]
remain) ->
do next <- [Char] -> Either GZipError [Section]
read_sections [Char]
remain
return $ sect : next
parseword :: String -> Word32
parseword :: [Char] -> Word32
parseword [Char]
s = [Word32] -> Word32
forall a. (Bits a, Num a) => [a] -> a
fromBytes ([Word32] -> Word32) -> [Word32] -> Word32
forall a b. (a -> b) -> a -> b
$ (Char -> Word32) -> [Char] -> [Word32]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> (Char -> Int) -> Char -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord) ([Char] -> [Word32]) -> [Char] -> [Word32]
forall a b. (a -> b) -> a -> b
$ ShowS
forall a. [a] -> [a]
reverse [Char]
s
read_section :: String -> Either GZipError (Section, String)
read_section :: [Char] -> Either GZipError (Section, [Char])
read_section [Char]
s =
do x <- [Char] -> Either GZipError (Header, [Char])
read_header [Char]
s
let headerrem = (Header, [Char]) -> [Char]
forall a b. (a, b) -> b
snd (Header, [Char])
x
let (decompressed, crc, remainder) = read_data headerrem
let (crc32str, rm) = splitAt 4 remainder
let (sizestr, rem2) = splitAt 4 rm
let filecrc32 = [Char] -> Word32
parseword [Char]
crc32str
let filesize = [Char] -> Word32
parseword [Char]
sizestr
return ((fst x, decompressed,
Footer {size = filesize, crc32 = filecrc32,
crc32valid = filecrc32 == crc})
,rem2)
read_data :: String -> (String, Word32, String)
read_data :: [Char] -> ([Char], Word32, [Char])
read_data [Char]
x =
let ([Char]
decompressed1, [Char]
remainder) = [Char] -> ([Char], [Char])
inflate_string_remainder [Char]
x
([Char]
decompressed, Word32
crc32) = [Char] -> Word32 -> ([Char], Word32)
read_data_internal [Char]
decompressed1 Word32
0
in
([Char]
decompressed, Word32
crc32, [Char]
remainder)
where
read_data_internal :: [Char] -> Word32 -> ([Char], Word32)
read_data_internal [] Word32
ck = ([], Word32
ck)
read_data_internal (Char
y:[Char]
ys) Word32
ck =
let newcrc :: Word32
newcrc = Word32 -> Char -> Word32
update_crc Word32
ck Char
y
n :: ([Char], Word32)
n = Word32
newcrc Word32 -> ([Char], Word32) -> ([Char], Word32)
forall a b. a -> b -> b
`seq` [Char] -> Word32 -> ([Char], Word32)
read_data_internal [Char]
ys Word32
newcrc
in
(Char
y Char -> ShowS
forall a. a -> [a] -> [a]
: ([Char], Word32) -> [Char]
forall a b. (a, b) -> a
fst ([Char], Word32)
n, ([Char], Word32) -> Word32
forall a b. (a, b) -> b
snd ([Char], Word32)
n)
read_header :: String -> Either GZipError (Header, String)
[Char]
s =
let ok :: Either a [Char]
ok = [Char] -> Either a [Char]
forall a b. b -> Either a b
Right [Char]
"ok" in
do let ([Char]
mag, [Char]
rem1) = Int -> [Char] -> ([Char], [Char])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
2 [Char]
s
_ <- if [Char]
mag [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Char]
magic
then GZipError -> Either GZipError [Char]
forall a. GZipError -> Either GZipError a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError GZipError
NotGZIPFile
else Either GZipError [Char]
forall {a}. Either a [Char]
ok
let (method, rem2) = split1 rem1
_ <- if (ord(method) /= 8)
then throwError UnknownMethod
else ok
let (flag_S, rem3) = split1 rem2
let flag = Char -> Int
ord Char
flag_S
let (mtimea, rem3a) = splitAt 4 rem3
let mtime = [Char] -> Word32
parseword [Char]
mtimea
let (xfla, rem3b) = split1 rem3a
let xfl = Char -> Int
ord Char
xfla
let (osa, _) = split1 rem3b
let os = Char -> Int
ord Char
osa
let rem4 = Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
6 [Char]
rem3
let (extra, rem5) =
if (flag .&. fFEXTRA /= 0)
then let (xlen_S, _) = split1 rem4
(xlen2_S, rem4b) = split1 rem4
xlen = (Char -> Int
ord Char
xlen_S) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
256 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Char -> Int
ord Char
xlen2_S)
(ex, rrem) = splitAt xlen rem4b
in (Just ex, rrem)
else (Nothing, rem4)
let (filename, rem6) =
if (flag .&. fFNAME /= 0)
then let fn = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\x00') [Char]
rem5
in (Just fn, drop ((length fn) + 1) rem5)
else (Nothing, rem5)
let (comment, rem7) =
if (flag .&. fFCOMMENT /= 0)
then let cm = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\x00') [Char]
rem6
in (Just cm, drop ((length cm) + 1) rem6)
else (Nothing, rem6)
rem8 <- if (flag .&. fFHCRC /= 0)
then return $ drop 2 rem7
else return rem7
return (Header {method = ord method,
flags = flag,
extra = extra,
filename = filename,
comment = comment,
mtime = mtime,
xfl = xfl,
os = os}, rem8)