module Codec.Archive.SAPCAR
    ( SapCar
    , CarEntry (..)
    , CarFileType (..)
    , carEntryFilename
    , withSapCarFile
    , withSapCarPath
    , withSapCarHandle
    , getEntries
    , sourceEntry
    , writeToFile
    , writeToHandle
    ) where
import Control.Monad
import Control.Monad.State.Strict
import Control.Monad.Catch
import Data.Binary.Get
import Data.Binary.Put
import Data.Bits
import Data.Conduit
import Data.Int
import Data.Word
import Data.Text (Text)
import Data.Time.Clock.POSIX
import Data.Time.Format
import Path
import System.IO
import Text.Printf
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Codec.Archive.SAPCAR.FlatedFile as FF
newtype SapCar s m a = SapCar
 { unSapCar :: StateT SapCarFile m a }
 deriving ( Functor
             , Applicative
             , Monad
             , MonadIO
             , MonadThrow
             , MonadCatch
             , MonadMask )
data SapCarFile = SapCarFile
    { 
      sarFileH              :: !Handle
    }
data SapCarHeader s = SapCarHeader
    { 
      scVersion             :: !Text
    , 
      scFiles               :: ![CarEntry s]
    } deriving (Show)
data CarFileType
    = 
      CarFile
    | 
      CarDirectory
    | 
      CarUnknown
    deriving (Show, Eq, Enum)
getType :: Get CarFileType
getType = getType' <$> getByteString 2
    where
        getType' t
            | t == "RG" = CarFile
            | t == "DR" = CarDirectory
            | otherwise = CarUnknown
data CarEntry s = CarEntry
    { 
      cfFileType            :: !CarFileType
    , 
      cfPermissions         :: !Word32
    , 
      cfLength              :: !Word32
    , 
      cfTimestamp           :: !Word32
    , 
      cfFileName            :: !Text
    , 
      cfFileOffset          :: !Int64
    , 
      cfPayloadOffset       :: !Int64
    }
instance Show (CarEntry s) where
    show ce = printf "%s%s 0 root root %d\t%s 00:00 %s"
            (case cfFileType ce of
                CarFile         -> "-" :: Text
                CarDirectory    -> "d"
                CarUnknown      -> "X")
            (toPermissionText $ cfPermissions ce)
            (cfLength ce)
            (unparseDate $ cfTimestamp ce)
            (cfFileName ce)
unparseDate :: Word32 -> String
unparseDate = formatTime defaultTimeLocale "%b %e" . posixSecondsToUTCTime . fromIntegral
toPermissionText :: Word32 -> Text
toPermissionText n = T.concat [u, g, o]
    where
        u = toPermissionText' $ n `shiftR` 6 .&. 7
        g = toPermissionText' $ n `shiftR` 3 .&. 7
        o = toPermissionText' $ n .&. 7
toPermissionText' :: Word32 -> Text
toPermissionText' n = T.concat [r `perm` "r", w `perm` "w", x `perm` "x"]
    where
        x = n .&. 1 == 1
        w = n `shiftR` 1 .&. 1 == 1
        r = n `shiftR` 2 .&. 1 == 1
perm :: Bool -> Text -> Text
perm True w = w
perm False w = "-"
carEntryFilename :: CarEntry s -> Text
carEntryFilename = cfFileName
data CompAlg
    = 
      CompLzh
    | 
      CompLzc
    | 
      CompUnknown
    deriving (Show, Eq, Enum)
data CompHdr = CompHdr
    { 
      chLen                 :: !Word32
    , 
      chAlg                 :: !CompAlg
    , 
      chMagic               :: !Word16
    , 
      chSpe                 :: !Word8
    } deriving (Show)
withSapCarPath
    :: (MonadIO m, MonadThrow m, MonadMask m)
    => Path b File
    -> (forall s. SapCar s m a)
    -> m a
withSapCarPath sarfile a = bracket open close $ withSapCarHandle a
    where
        open   = liftIO $ openBinaryFile (toFilePath sarfile) ReadMode
        close  = liftIO . hClose
withSapCarFile
    :: (MonadIO m, MonadThrow m, MonadMask m)
    => FilePath
    -> (forall s. SapCar s m a)
    -> m a
withSapCarFile sarfile a = bracket open close $ withSapCarHandle a
    where
        open   = liftIO $ openBinaryFile sarfile ReadMode
        close  = liftIO . hClose
withSapCarHandle
    :: (MonadIO m, MonadThrow m, MonadMask m)
    => (forall s. SapCar s m a)
    -> Handle
    -> m a
withSapCarHandle a = evalStateT (unSapCar a) . SapCarFile
getEntries :: MonadIO m => SapCar s m [CarEntry s]
getEntries = SapCar $ do
    fh <- sarFileH <$> get
    let entryParser = runGetIncremental (parseFileHdr >> parseSAPCARFile [])
    res <- liftIO $ feedChunks entryParser fh
    let Done _ _ entries = res
    return entries
sourceEntry :: MonadIO m => CarEntry s -> Sink S.ByteString IO a -> SapCar s m a
sourceEntry entry sink = SapCar $ do
    fh <- sarFileH <$> get
    case cfLength entry of
        0 -> liftIO $ emptySource $$ sink
        _ -> do
            liftIO $ hSeek fh AbsoluteSeek $ fromIntegral $ cfPayloadOffset entry
            liftIO $ decompressBlocks fh $$ sink
emptySource :: Source IO S.ByteString
emptySource = yield ""
feedChunks :: Decoder a -> Handle -> IO (Decoder a)
feedChunks d h = do
    chunk <- S.hGet h 8192
    if chunk == S.empty
    then return $ pushEndOfInput d
    else feedChunks (pushChunk d chunk) h
parseSAPCARFile :: [CarEntry s] -> Get [CarEntry s]
parseSAPCARFile acc = do
    empty <- isEmpty
    if empty
    then return acc
    else do
        entry <- parseEntry
        parseSAPCARFile $ entry:acc
writeToFile :: (MonadIO m, MonadMask m, MonadThrow m) => CarEntry s -> Path b File -> SapCar s m ()
writeToFile entry path = bracket open close w
    where
        open    = liftIO $ openBinaryFile (toFilePath path) WriteMode
        close   = liftIO . hClose
        w       = sourceEntry entry . writer
writeToHandle :: (MonadIO m, MonadMask m, MonadThrow m) => CarEntry s -> Handle -> SapCar s m ()
writeToHandle entry = sourceEntry entry . writer
writer :: Handle -> Sink S.ByteString IO ()
writer h = do
    chunk <- await
    case chunk of
        Just chunk' -> liftIO (S.hPut h chunk') >> writer h
        Nothing -> return ()
parseCompHdr :: Get CompHdr
parseCompHdr = do
    len <- getWord32le
    alg <- getWord8
    let alg' = case alg of
            18 -> CompLzh
            16 -> CompLzc
            _  -> CompUnknown
    magic <- getWord16be
    when (magic /= 8093) $ error $ "Invalid magic value (8093 decimal expected); got " ++ show magic
    spe <- getWord8
    return $ CompHdr len alg' magic spe
parseEntry :: Get (CarEntry s)
parseEntry = do
    fileOffset <- bytesRead
    ftype <- getType
    fperm <- getWord32le
    flen <- getWord32le
    void $ getByteString 8
    ftimestamp <- getWord32le
    void $ getByteString 10
    fnlen <- fromIntegral <$> getWord16le
    fn <- getByteString $ fnlen  1
    nulbyte <- getWord8
    when (nulbyte /= 0) $ error "NUL byte expected"
    case ftype of
        CarFile -> do
            payloadOffset <- bytesRead
            unless (flen == 0) skipBlocks
            return $ CarEntry ftype fperm flen ftimestamp (TE.decodeUtf8 fn) fileOffset payloadOffset
        CarDirectory ->
            return $ CarEntry ftype fperm flen ftimestamp (TE.decodeUtf8 fn) fileOffset 0
        _ -> error $ "Unhandled type " ++ show ftype
skipBlocks :: Get ()
skipBlocks = do
    ed <- getByteString 2
    skipBlock
    case ed of
        "ED" -> void getWord32le
        "UE" -> void getWord32le
        "DA" -> skipBlocks
        "UD" -> skipBlocks
        _    -> error $ "Unknown block type " ++ show ed
skipBlock :: Get ()
skipBlock = void (getWord32le >>= getByteString . fromIntegral)
decompressBlocks :: Handle -> Source IO S.ByteString
decompressBlocks h = do
    ed <- liftIO $ S.hGet h 2
    case ed of
        
        "ED" -> do
            liftIO (decompressBlock h) >>= yield
            void $ liftIO $ S.hGet h 4 
        
        "DA" -> do
            liftIO (decompressBlock h) >>= yield
            decompressBlocks h
        
        "UD" -> do
            liftIO (uncompressedBlock h) >>= yield
            decompressBlocks h
        
        
        "UE" -> liftIO (uncompressedBlock h) >>= yield
        _    -> error $ "(while decompressing) unknown block type " ++ show ed
uncompressedBlock :: Handle -> IO S.ByteString
uncompressedBlock h = do
    blockSize <- S.hGet h 4
    let blockSize' = runGet getWord32le $ L.fromStrict blockSize
    S.hGet h $ fromIntegral blockSize'
decompressBlock :: Handle -> IO S.ByteString
decompressBlock h = do
    hdr <- L.fromStrict <$> S.hGet h 12
    let (fCompLen, compHdr) = runGet ((,) <$> getWord32le <*> parseCompHdr) hdr
    when (chAlg compHdr /= CompLzh) $ error "Currently only LZH is supported, not LZC"
    blob <- S.hGet h $ fromIntegral fCompLen  8
    when (chLen compHdr > 655360) $ error "Max 640k block size supported!"
    return $ FF.decompressBlocks (fromIntegral $ chLen compHdr) blob
parseFileHdr :: Get ()
parseFileHdr = do
    hdr <- getByteString 8
    unless (hdr == "CAR 2.01") $ error "Only the newest SAPCAR format (2.01) is supported"