{-# LANGUAGE FlexibleInstances #-}
module Lambdabot.Util.Serial
    ( Serial(..)
    , stdSerial
    , mapSerial
    , mapPackedSerial
    , assocListPackedSerial
    , mapListPackedSerial
    , readM
    , Packable(..) 
    , readOnly
    ) where
import Data.Maybe               (mapMaybe)
import Data.Map (Map)
import qualified Data.Map as M
import qualified Data.ByteString.Char8 as P
import Data.ByteString.Char8 (ByteString)
import Data.ByteString.Lazy (fromChunks,toChunks)
import Codec.Compression.GZip
data Serial s = Serial {
        serialize   :: s -> Maybe ByteString,
        deserialize :: ByteString -> Maybe s
     }
gzip   :: ByteString -> ByteString
gzip   = P.concat . toChunks . compress . fromChunks . (:[])
gunzip :: ByteString -> ByteString
gunzip = P.concat . toChunks . decompress . fromChunks . (:[])
readOnly :: (ByteString -> b) -> Serial b
readOnly f = Serial (const Nothing) (Just . f)
stdSerial :: (Show s, Read s) => Serial s
stdSerial = Serial (Just. P.pack.show) (readM.P.unpack)
mapSerial :: (Ord k, Show k, Show v, Read k, Read v) => Serial (Map k v)
mapSerial = Serial {
        serialize   = Just . P.pack . unlines . map show . M.toList,
        deserialize = Just . M.fromList . mapMaybe (readM . P.unpack) . P.lines
   }
readM :: (Monad m, Read a) => String -> m a
readM s = case [x | (x,t) <- {-# SCC "Serial.readM.reads" #-} reads s    
               , ("","")  <- lex t] of
        [x] -> return x
        []  -> fail "Serial.readM: no parse"
        _   -> fail "Serial.readM: ambiguous parse"
class Packable t where
        readPacked :: ByteString -> t
        showPacked :: t -> ByteString
instance Packable (Map ByteString [ByteString]) where
        readPacked ps = M.fromList (readKV ( P.lines . gunzip $ ps))
             where
                readKV :: [ByteString] -> [(ByteString,[ByteString])]
                readKV []       =  []
                readKV (k:rest) = let (vs, rest') = break (== P.empty) rest
                                  in  (k,vs) : readKV (drop 1 rest')
        showPacked m = gzip
                     . P.unlines
                     . concatMap (\(k,vs) -> k : vs ++ [P.empty]) $ M.toList m
instance Packable (Map ByteString ByteString) where
        readPacked ps = M.fromList (readKV (P.lines . gunzip $ ps))
                where
                  readKV :: [ByteString] -> [(ByteString,ByteString)]
                  readKV []         = []
                  readKV (k:v:rest) = (k,v) : readKV rest
                  readKV _      = error "Serial.readPacked: parse failed"
        showPacked m  = gzip. P.unlines . concatMap (\(k,v) -> [k,v]) $ M.toList m
instance Packable ([(ByteString,ByteString)]) where
        readPacked ps = readKV (P.lines . gunzip $ ps)
                where
                  readKV :: [ByteString] -> [(ByteString,ByteString)]
                  readKV []         = []
                  readKV (k:v:rest) = (k,v) : readKV rest
                  readKV _          = error "Serial.readPacked: parse failed"
        showPacked = gzip . P.unlines . concatMap (\(k,v) -> [k,v])
instance Packable (M.Map P.ByteString (Bool, [(String, Int)])) where
    readPacked = M.fromList . readKV . P.lines
        where
          readKV :: [P.ByteString] -> [(P.ByteString,(Bool, [(String, Int)]))]
          readKV []         = []
          readKV (k:v:rest) = (k, (read . P.unpack) v) : readKV rest
          readKV _          = error "Vote.readPacked: parse failed"
    showPacked m = P.unlines . concatMap (\(k,v) -> [k,P.pack . show $ v]) $ M.toList m
mapPackedSerial :: Serial (Map ByteString ByteString)
mapPackedSerial = Serial (Just . showPacked) (Just . readPacked)
mapListPackedSerial :: Serial (Map ByteString [ByteString])
mapListPackedSerial = Serial (Just . showPacked) (Just . readPacked)
assocListPackedSerial :: Serial ([(ByteString,ByteString)])
assocListPackedSerial = Serial (Just . showPacked) (Just . readPacked)