module Codec.Archive.SAPCAR.Pat
( patToTransport
) where
import Control.Monad
import Data.Binary.Get
import Data.Bits
import Data.Conduit
import Data.Maybe
import Data.Word
import Data.Text (Text)
import System.IO
import Text.Printf
import Text.Read
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 Data.Text.Encoding.Error as TEE
maximumChunkSize :: Int
maximumChunkSize = 65536
data PatChunk = PatChunk
{
pcVersion :: Int
,
pcType :: PatChunkType
,
pcLength :: Int
,
pcReserved :: S.ByteString
,
pcPayload :: S.ByteString }
deriving (Show, Eq)
data PatChunkType
=
TransportPatChunk
|
UnknownPatChunk
|
NotAPatFile
deriving (Eq, Enum, Show)
getChunkType :: Get PatChunkType
getChunkType = getChunkType' <$> getWord8
getChunkType' :: Word8 -> PatChunkType
getChunkType' 82 = TransportPatChunk
getChunkType' (1) = NotAPatFile
getChunkType' _ = UnknownPatChunk
getChunkVersion :: Get Int
getChunkVersion = fromMaybe (1) . readMaybe . T.unpack . TE.decodeUtf8With TEE.lenientDecode <$> getByteString 2
getChunkLength :: Get Int
getChunkLength = do
length <- fromMaybe (0) . readMaybe . T.unpack . TE.decodeUtf8 <$> getByteString 8 :: Get Int
when (length > maximumChunkSize) $ error "Too big a chunk"
return length
getPatChunk :: Get PatChunk
getPatChunk = do
v <- getChunkVersion
if v == (1)
then return $ PatChunk (1) NotAPatFile 0 S.empty S.empty
else do
t <- getChunkType
l <- getChunkLength
r <- getByteString 14
p <- getByteString $ l 25
return $ PatChunk v t l r p
patToTransport :: Monad m => Conduit S.ByteString m S.ByteString
patToTransport = patToTransport' S.empty $ runGetIncremental getPatChunk
patToTransport'
:: Monad m
=> S.ByteString
-> Decoder PatChunk
-> Conduit S.ByteString m S.ByteString
patToTransport' s (Partial d)
| S.null s = do
chunk <- await
case chunk of
Just chunk' -> patToTransport' S.empty $ pushChunk (Partial d) chunk'
Nothing -> return ()
| otherwise = patToTransport' S.empty $ pushChunk (Partial d) s
patToTransport' s (Done rest _ r) = do
when (pcType r == TransportPatChunk) $
yield (pcPayload r)
unless (pcType r == NotAPatFile) $
patToTransport' rest $ runGetIncremental getPatChunk