module Codec.Phaser.Common (
Position(..),
satisfy,
match,
char,
iChar,
string,
iString,
integerDecimal,
decimal,
directHex,
hex,
integer,
countChar,
countLine,
trackPosition,
parse,
sepBy,
munch,
munch1,
parseFile,
latin1
) where
import Data.Char
import Data.Word
import Control.Monad
import Control.Applicative
import Codec.Phaser.Core
import qualified Codec.Phaser.ByteString as BP
data Position = Position
!Int
!Int
deriving (Eq,Ord)
instance Show Position where
showsPrec p (Position r c) = b m where
b a = if p > 0
then ('(' :) . a . (')' :)
else a
m = ("Row " ++) . showsPrec 0 r . (", Column " ++) . showsPrec 0 c
instance Read Position where
readsPrec p = toReadS (toAutomaton (go p)) where
parenthes a = surround a
(many (satisfy isSpace) >> char '(')
(char ')' >> many (satisfy isSpace))
go 0 = inner <|> parenthes (go 0)
go _ = parenthes (go 0)
inner = do
many (satisfy isSpace)
iString "row"
some (satisfy isSpace)
r <- integer
many (satisfy isSpace)
char ','
many (satisfy isSpace)
iString "column"
some (satisfy isSpace)
c <- integer
return (Position r c)
satisfy :: (i -> Bool) -> Phase p i o i
satisfy p = get >>= \c -> if p c then return c else empty
match :: (Eq i) => i -> Phase p i o i
match t = satisfy (== t)
char :: Char -> Phase p Char o Char
char = match
iChar :: Char -> Phase p Char o Char
iChar t = satisfy (\i -> toLower t == toLower i)
string :: Eq i => [i] -> Phase p i o [i]
string t = go t where
go [] = return t
go (a:r) = get >>= \c -> if c == a then go r else empty
iString :: String -> Phase p Char o String
iString = mapM iChar
integerDecimal :: Num a => Phase p Char o a
integerDecimal = go 0 where
go acc = do
d <- fmap (fromIntegral . digitToInt) $ satisfy isDigit
let acc' = acc * 10 + d
acc' `seq` go acc' <|> return acc'
directHex :: Num a => Phase p Char o a
directHex = go 0 where
go acc = do
d <- fmap (fromIntegral . digitToInt) $ satisfy isHexDigit
let acc' = acc * 16 + d
acc' `seq` go acc' <|> return acc'
hex :: Num a => Phase p Char o a
hex = string "0x" >> directHex
integer :: Num a => Phase p Char o a
integer = integerDecimal <|> hex
decimal :: Fractional a => Phase p Char o a
decimal = do
w <- integerDecimal
(match '.' >> go True 0.1 w) <|> return w
where
go i s acc = do
let
p = if i
then ("At least one digit required after decimal point" <?>)
else id
d <- p $ fmap (fromIntegral . digitToInt) $ satisfy isDigit
let acc' = acc + d * s
acc' `seq` go False (s / 10) acc' <|> return acc'
countChar :: Phase Position i o ()
countChar = count (\(Position r c) -> Position r (c + 1))
countLine :: Phase Position i o ()
countLine = count (\(Position r _) -> Position (r + 1) 1)
trackPosition :: Phase Position Char Char ()
trackPosition = goR where
goR = flip (<|>) (return ()) $ get >>= \c -> yield c >> case c of
'\r' -> countLine >> goN
'\n' -> countLine >> goR
_ -> countChar >> goR
goN = flip (<|>) (return ()) $ get >>= \c -> yield c >> case c of
'\r' -> countLine >> goN
'\n' -> goR
_ -> countChar >> goR
parse :: Phase Position i o a -> [i] -> Either [(Position,[String])] [a]
parse = parse_ (Position 1 1)
sepBy :: Phase p i o a -> Phase p i o s -> Phase p i o [a]
sepBy p sep = go id <|> return [] where
go acc = do
a <- p
let acc' = acc . (a :)
(sep >> go acc') <|> return (acc' [])
surround :: Phase p i o a -> Phase p i o b -> Phase p i o e -> Phase p i o a
surround m o c = (\_ r _ -> r) <$> o <*> m <*> c
munch :: (i -> Bool) -> Phase p i o [i]
munch p = (eof >> return []) <|> munch1 p
munch1 :: (i -> Bool) -> Phase p i o [i]
munch1 p = go id where
go acc = do
c <- get
if p c
then go (acc . (c :)) <|> (eof >> return (acc [c]))
else put1 c >> return (acc [])
parseFile :: Phase Position Word8 o a -> FilePath ->
IO (Either [(Position,[String])] [a])
parseFile = BP.parseFile_ (Position 1 1)
latin1 :: Phase p Word8 Char ()
latin1 = go where
go = flip (<|>) (return ()) $
fmap (toEnum . fromIntegral) get >>= yield >> go