{-# LANGUAGE DeriveDataTypeable#-}

module Codec.Archive.LibZip.Types
    ( Zip
    , ZipFile
    , ZipSource
    , ZipStat(..)
    , toZipStat
    , OpenFlag(..)
    , FileFlag(..)
    , ZipError(..)
    , ZipCompMethod(..)
    , ZipEncryptionMethod(..)
    , combine
    ) where
    
import Data.Bits ((.|.))
import Data.Time (UTCTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Data.Typeable (Typeable)
import Data.Word (Word)
import Foreign.C.String (peekCString)
import Foreign.C.Types ()
import Foreign.Ptr (Ptr, nullPtr)
import qualified Control.Exception as E

import Bindings.LibZip

-- | Handler of the open zip file.
type Zip = Ptr C'zip

-- | Handler of an open file in the zip archive.
type ZipFile = Ptr C'zip_file

-- | Handler of data source for new files in the zip archive.
type ZipSource = Ptr C'zip_source

-- |  File statistics expressed in native Haskell types.
data ZipStat = ZipStat {
      zs'name :: String
    , zs'index :: Int
    , zs'crc :: Word
    , zs'mtime :: UTCTime
    , zs'size :: Int
    , zs'comp_size :: Int
    , zs'comp_method :: ZipCompMethod
    , zs'encryption_method :: ZipEncryptionMethod
    } deriving (Show, Eq)

-- | Convert marshalled stat record.
toZipStat :: C'zip_stat -> IO ZipStat
toZipStat s = do
    let np = c'zip_stat'name s
    name <- if (np /= nullPtr) then peekCString np else return ""
    let idx = fromIntegral $ c'zip_stat'index s
    let crc = fromIntegral $ c'zip_stat'crc s
    let mtime = posixSecondsToUTCTime . realToFrac $ c'zip_stat'mtime s
    let size = fromIntegral $ c'zip_stat'size s
    let comp_size = fromIntegral $ c'zip_stat'comp_size s
    let comp_meth = toEnum . fromIntegral $ c'zip_stat'comp_method s
    let enc_meth = toEnum . fromIntegral $ c'zip_stat'encryption_method s
    return $ ZipStat name idx crc mtime size comp_size comp_meth enc_meth
   

-- | Flags for opening an archive.
data OpenFlag
  = CreateFlag      -- ^ Create an archive if it does not exist.
  | ExclFlag        -- ^ Error if the archive already exists.
  | CheckConsFlag   -- ^ Check archive's consistency and error on failure.
  deriving (Show,Eq)

instance Enum OpenFlag where
  fromEnum CheckConsFlag = c'ZIP_CHECKCONS
  fromEnum CreateFlag = c'ZIP_CREATE
  fromEnum ExclFlag = c'ZIP_EXCL
  toEnum x | x == c'ZIP_CHECKCONS = CheckConsFlag
  toEnum x | x == c'ZIP_CREATE = CreateFlag
  toEnum x | x == c'ZIP_EXCL = ExclFlag
  toEnum _ = undefined

-- | Flags for accessing files in the archive.
-- Please consult @libzip@ documentation about their use.
data FileFlag
  = FileNOCASE      -- ^ Ignore case on name lookup.
  | FileNODIR       -- ^ Ignore directory component.
  | FileCOMPRESSED  -- ^ Read the compressed data.
  | FileUNCHANGED   -- ^ Read the original data, ignore changes.
  | FileRECOMPRESS  -- ^ Force recompression of data.
  deriving (Show,Eq)

instance Enum FileFlag where
  fromEnum FileCOMPRESSED = c'ZIP_FL_COMPRESSED
  fromEnum FileNOCASE = c'ZIP_FL_NOCASE
  fromEnum FileNODIR = c'ZIP_FL_NODIR
  fromEnum FileRECOMPRESS = c'ZIP_FL_RECOMPRESS
  fromEnum FileUNCHANGED = c'ZIP_FL_UNCHANGED
  toEnum x | x == c'ZIP_FL_COMPRESSED = FileCOMPRESSED
  toEnum x | x == c'ZIP_FL_NOCASE = FileNOCASE
  toEnum x | x == c'ZIP_FL_NODIR = FileNODIR
  toEnum x | x == c'ZIP_FL_RECOMPRESS = FileRECOMPRESS
  toEnum x | x == c'ZIP_FL_UNCHANGED = FileUNCHANGED
  toEnum _ = undefined

-- | @libzip@ error codes.
data ZipError
  = ErrOK             -- ^ No error.
  | ErrMULTIDISK      -- ^ Multi-disk zip archives not supported.
  | ErrRENAME         -- ^ Renaming temporary file failed.
  | ErrCLOSE          -- ^ Closing zip archive failed.
  | ErrSEEK           -- ^ Seek error.
  | ErrREAD           -- ^ Read error.
  | ErrWRITE          -- ^ Write error.
  | ErrCRC            -- ^ CRC error.
  | ErrZIPCLOSED      -- ^ Containing zip archive was closed.
  | ErrNOENT          -- ^ No such file.
  | ErrEXISTS         -- ^ File already exists.
  | ErrOPEN           -- ^ Can't open file.
  | ErrTMPOPEN        -- ^ Failure to create temporary file.
  | ErrZLIB           -- ^ Zlib error.
  | ErrMEMORY         -- ^ Malloc error.
  | ErrCHANGED        -- ^ Entry has been changed.
  | ErrCOMPNOTSUPP    -- ^ Compression method not supported.
  | ErrEOF            -- ^ Premature EOF.
  | ErrINVAL          -- ^ Invalid argument.
  | ErrNOZIP          -- ^ Not a zip archive.
  | ErrINTERNAL       -- ^ Internal error.
  | ErrINCONS         -- ^ Zip archive inconsistent.
  | ErrREMOVE         -- ^ Can't remove file.
  | ErrDELETED        -- ^ Entry has been deleted.
  deriving (Eq, Typeable)

instance Enum ZipError where
  fromEnum ErrCHANGED = c'ZIP_ER_CHANGED
  fromEnum ErrCLOSE = c'ZIP_ER_CLOSE
  fromEnum ErrCOMPNOTSUPP = c'ZIP_ER_COMPNOTSUPP
  fromEnum ErrCRC = c'ZIP_ER_CRC
  fromEnum ErrDELETED = c'ZIP_ER_DELETED
  fromEnum ErrEOF = c'ZIP_ER_EOF
  fromEnum ErrEXISTS = c'ZIP_ER_EXISTS
  fromEnum ErrINCONS = c'ZIP_ER_INCONS
  fromEnum ErrINTERNAL = c'ZIP_ER_INTERNAL
  fromEnum ErrINVAL = c'ZIP_ER_INVAL
  fromEnum ErrMEMORY = c'ZIP_ER_MEMORY
  fromEnum ErrMULTIDISK = c'ZIP_ER_MULTIDISK
  fromEnum ErrNOENT = c'ZIP_ER_NOENT
  fromEnum ErrNOZIP = c'ZIP_ER_NOZIP
  fromEnum ErrOK = c'ZIP_ER_OK
  fromEnum ErrOPEN = c'ZIP_ER_OPEN
  fromEnum ErrREAD = c'ZIP_ER_READ
  fromEnum ErrREMOVE = c'ZIP_ER_REMOVE
  fromEnum ErrRENAME = c'ZIP_ER_RENAME
  fromEnum ErrSEEK = c'ZIP_ER_SEEK
  fromEnum ErrTMPOPEN = c'ZIP_ER_TMPOPEN
  fromEnum ErrWRITE = c'ZIP_ER_WRITE
  fromEnum ErrZIPCLOSED = c'ZIP_ER_ZIPCLOSED
  fromEnum ErrZLIB = c'ZIP_ER_ZLIB
  toEnum x | x == c'ZIP_ER_CHANGED = ErrCHANGED
  toEnum x | x == c'ZIP_ER_CLOSE = ErrCLOSE
  toEnum x | x == c'ZIP_ER_COMPNOTSUPP = ErrCOMPNOTSUPP
  toEnum x | x == c'ZIP_ER_CRC = ErrCRC
  toEnum x | x == c'ZIP_ER_DELETED = ErrDELETED
  toEnum x | x == c'ZIP_ER_EOF = ErrEOF
  toEnum x | x == c'ZIP_ER_EXISTS = ErrEXISTS
  toEnum x | x == c'ZIP_ER_INCONS = ErrINCONS
  toEnum x | x == c'ZIP_ER_INTERNAL = ErrINTERNAL
  toEnum x | x == c'ZIP_ER_INVAL = ErrINVAL
  toEnum x | x == c'ZIP_ER_MEMORY = ErrMEMORY
  toEnum x | x == c'ZIP_ER_MULTIDISK = ErrMULTIDISK
  toEnum x | x == c'ZIP_ER_NOENT = ErrNOENT
  toEnum x | x == c'ZIP_ER_NOZIP = ErrNOZIP
  toEnum x | x == c'ZIP_ER_OK = ErrOK
  toEnum x | x == c'ZIP_ER_OPEN = ErrOPEN
  toEnum x | x == c'ZIP_ER_READ = ErrREAD
  toEnum x | x == c'ZIP_ER_REMOVE = ErrREMOVE
  toEnum x | x == c'ZIP_ER_RENAME = ErrRENAME
  toEnum x | x == c'ZIP_ER_SEEK = ErrSEEK
  toEnum x | x == c'ZIP_ER_TMPOPEN = ErrTMPOPEN
  toEnum x | x == c'ZIP_ER_WRITE = ErrWRITE
  toEnum x | x == c'ZIP_ER_ZIPCLOSED = ErrZIPCLOSED
  toEnum x | x == c'ZIP_ER_ZLIB = ErrZLIB
  toEnum _ = undefined

instance E.Exception ZipError

instance Show ZipError where
  show ErrOK             =  "No error"
  show ErrMULTIDISK      =  "Multi-disk zip archives not supported"
  show ErrRENAME         =  "Renaming temporary file failed"
  show ErrCLOSE          =  "Closing zip archive failed"
  show ErrSEEK           =  "Seek error"
  show ErrREAD           =  "Read error"
  show ErrWRITE          =  "Write error"
  show ErrCRC            =  "CRC error"
  show ErrZIPCLOSED      =  "Containing zip archive was closed"
  show ErrNOENT          =  "No such file"
  show ErrEXISTS         =  "File already exists"
  show ErrOPEN           =  "Can't open file"
  show ErrTMPOPEN        =  "Failure to create temporary file"
  show ErrZLIB           =  "Zlib error"
  show ErrMEMORY         =  "Malloc failure"
  show ErrCHANGED        =  "Entry has been changed"
  show ErrCOMPNOTSUPP    =  "Compression method not supported"
  show ErrEOF            =  "Premature EOF"
  show ErrINVAL          =  "Invalid argument"
  show ErrNOZIP          =  "Not a zip archive"
  show ErrINTERNAL       =  "Internal error"
  show ErrINCONS         =  "Zip archive inconsistent"
  show ErrREMOVE         =  "Can't remove file"
  show ErrDELETED        =  "Entry has been deleted"

-- | Compression methods.
data ZipCompMethod
  = CompDEFAULT         -- ^ Better of deflate or store.
  | CompSTORE           -- ^ Stored (uncompressed).
  | CompSHRINK          -- ^ Shrunk.
  | CompREDUCE_1        -- ^ Reduced with factor 1
  | CompREDUCE_2        -- ^ Reduced with factor 2
  | CompREDUCE_3        -- ^ Reduced with factor 3
  | CompREDUCE_4        -- ^ Reduced with factor 4
  | CompIMPLODE         -- ^ Imploded.
  | CompDEFLATE         -- ^ Deflated.
  | CompDEFLATE64       -- ^ Deflate64.
  | CompPKWARE_IMPLODE  -- ^ PKWARE imploding.
  | CompBZIP2           -- ^ Compressed using BZIP2 algorithm.
  | CompLZMA            -- ^ LZMA (EFS)
  | CompTERSE           -- ^ Compressed using IBM TERSE (new).
  | CompLZ77            -- ^ IBM LZ77 z Architecture (PFS).
  | CompWAVPACK         -- ^ WavPack compressed data.
  | CompPPMD            -- ^ PPMd version I, Rev 1.
  deriving (Show, Eq)

instance Enum ZipCompMethod where
  fromEnum CompDEFAULT = c'ZIP_CM_DEFAULT
  fromEnum CompSTORE = c'ZIP_CM_STORE
  fromEnum CompSHRINK = c'ZIP_CM_SHRINK
  fromEnum CompREDUCE_1 = c'ZIP_CM_REDUCE_1
  fromEnum CompREDUCE_2 = c'ZIP_CM_REDUCE_2
  fromEnum CompREDUCE_3 = c'ZIP_CM_REDUCE_3
  fromEnum CompREDUCE_4 = c'ZIP_CM_REDUCE_4
  fromEnum CompIMPLODE = c'ZIP_CM_IMPLODE
  fromEnum CompDEFLATE = c'ZIP_CM_DEFLATE
  fromEnum CompDEFLATE64 = c'ZIP_CM_DEFLATE64
  fromEnum CompPKWARE_IMPLODE = c'ZIP_CM_PKWARE_IMPLODE
  fromEnum CompBZIP2 = c'ZIP_CM_BZIP2
  fromEnum CompLZMA = c'ZIP_CM_LZMA
  fromEnum CompTERSE = c'ZIP_CM_TERSE
  fromEnum CompLZ77 = c'ZIP_CM_LZ77
  fromEnum CompWAVPACK = c'ZIP_CM_WAVPACK
  fromEnum CompPPMD = c'ZIP_CM_PPMD
  toEnum x | x == c'ZIP_CM_DEFAULT = CompDEFAULT
  toEnum x | x == c'ZIP_CM_STORE = CompSTORE
  toEnum x | x == c'ZIP_CM_SHRINK = CompSHRINK
  toEnum x | x == c'ZIP_CM_REDUCE_1 = CompREDUCE_1
  toEnum x | x == c'ZIP_CM_REDUCE_2 = CompREDUCE_2
  toEnum x | x == c'ZIP_CM_REDUCE_3 = CompREDUCE_3
  toEnum x | x == c'ZIP_CM_REDUCE_4 = CompREDUCE_4
  toEnum x | x == c'ZIP_CM_IMPLODE = CompIMPLODE
  toEnum x | x == c'ZIP_CM_DEFLATE = CompDEFLATE
  toEnum x | x == c'ZIP_CM_DEFLATE64 = CompDEFLATE64
  toEnum x | x == c'ZIP_CM_PKWARE_IMPLODE = CompPKWARE_IMPLODE
  toEnum x | x == c'ZIP_CM_BZIP2 = CompBZIP2
  toEnum x | x == c'ZIP_CM_LZMA = CompLZMA
  toEnum x | x == c'ZIP_CM_TERSE = CompTERSE
  toEnum x | x == c'ZIP_CM_LZ77 = CompLZ77
  toEnum x | x == c'ZIP_CM_WAVPACK = CompWAVPACK
  toEnum x | x == c'ZIP_CM_PPMD = CompPPMD
  toEnum _ = undefined

-- | Encryption methods.
data ZipEncryptionMethod
  = EncryptNONE          -- ^ Not encrypted.
  | EncryptTRAD_PKWARE   -- ^ Traditional PKWARE encryption.
  | EncryptUNKNOWN       -- ^ Unknown algorithm.
  deriving (Show,Eq)

instance Enum ZipEncryptionMethod where
  fromEnum EncryptNONE = c'ZIP_EM_NONE
  fromEnum EncryptTRAD_PKWARE = c'ZIP_EM_TRAD_PKWARE
  fromEnum EncryptUNKNOWN = c'ZIP_EM_UNKNOWN
  toEnum x | x == c'ZIP_EM_NONE = EncryptNONE
  toEnum x | x == c'ZIP_EM_TRAD_PKWARE = EncryptTRAD_PKWARE
  toEnum x | x == c'ZIP_EM_UNKNOWN = EncryptUNKNOWN
  toEnum _ = undefined

-- | 

combine :: (Enum a, Num b) => [a] -> b
combine fs = fromIntegral . foldr (.|.) 0 $ map fromEnum fs