module Packet.Parse where
import Data.Char
import Control.Applicative
import Debug.Trace
import qualified Data.ByteString.Char8 as BS
import Data.Attoparsec.ByteString.Char8 as Atto
class Parse a where
parser :: Parser a
instance Parse Int where
parser = ord <$> anyChar
instance (Parse a
,Parse b) => Parse (a, b) where
parser = (,) <$> parser
<*> parser
instance (Parse a
,Parse b
,Parse c) => Parse (a, b, c) where
parser = (,,) <$> parser
<*> parser
<*> parser
instance (Parse a
,Parse b
,Parse c
,Parse d) => Parse (a, b, c, d) where
parser = (,,,) <$> parser
<*> parser
<*> parser
<*> parser
parseBS :: (Parse a) => BS.ByteString -> a
parseBS bs = case parse parser bs of
Done i r -> if not $ BS.null i then
trace ("Leftover input: " ++ show i ++
" of length " ++ show (BS.length i)) r
else
r
Partial _ -> error $ "Not enough input to parse anything:\n" ++ show bs
Fail i ctxs msg -> error $ "ParseError: " ++ msg ++ "\n" ++ show ctxs ++ "\nat:\n" ++
show i
untilEOF :: Parser a -> Parser [a]
untilEOF p = loop []
where
loop acc = do
isEnd <- atEnd
if isEnd
then return $ reverse acc
else do
n <- p
loop $ n:acc