{-#LANGUAGE FlexibleContexts, ExistentialQuantification, ScopedTypeVariables, OverloadedStrings, TypeSynonymInstances, FlexibleInstances #-}
module Transient.Parse(
setParseStream, setParseString, withParseString, withParseStream,
string, tDropUntilToken, tTakeUntilToken, integer, hex, int, double, tChar,anyChar,
manyTill, chainManyTill,between, symbol,parens, braces,angles,brackets,
semi, comma, dot,colon, sepBy, sepBy1, chainSepBy, chainSepBy1,chainMany,
commaSep, semiSep, commaSep1, dropSpaces,dropTillEndOfLine,
parseString, tTakeWhile,tTakeUntil, tTakeWhile', tTake, tDrop, tDropUntil, tPutStr,
isDone,dropUntilDone,
withGetParseString, giveParseString,
notParsed, getParseBuffer,clearParseBuffer, showNext,
(|-)) where
import Transient.Internals
import Control.Applicative
import Data.Char
import Data.Monoid
import System.IO.Unsafe
import Control.Monad
import Control.Monad.State
import Control.Concurrent.MVar
import Data.Maybe(fromJust)
import qualified Data.ByteString.Lazy.Char8 as BS
import Data.ByteString.Builder
import Control.Exception hiding (try)
import Data.IORef
import Control.Concurrent
import Data.Maybe
setParseStream :: TransMonad m => TransIO (StreamData BS.ByteString) -> m ()
setParseStream iox= modify $ \s -> s{execMode=Serial,parseContext= ParseContext iox "" (unsafePerformIO $ newIORef False)}
setParseString :: TransMonad m => BS.ByteString -> m ()
setParseString x = modify $ \s -> s{execMode=Serial,parseContext= ParseContext (return SDone) x (unsafePerformIO $ newIORef False)}
withParseString :: BS.ByteString -> TransIO a -> TransIO a
withParseString x parse= do
p <- gets parseContext
setParseString x
r <- parse
modify $ \s -> s{parseContext= p}
return r
withParseStream stream parse= do
p <- gets parseContext
setParseStream stream
r <- parse
modify $ \s -> s{parseContext= p}
return r
string :: BS.ByteString -> TransIO BS.ByteString
string s= withGetParseString $ \str -> do
let len= BS.length s
ret@(s',_) = BS.splitAt len str
if s == s'
then return ret
else empty
tDropUntilToken token= withGetParseString $ \str ->
if BS.null str then empty else drop2 str
where
drop2 str=
if token `BS.isPrefixOf` str
then return ((),BS.drop (BS.length token) str)
else if not $ BS.null str then drop2 $ BS.tail str else empty
tTakeUntilToken :: BS.ByteString -> TransIO BS.ByteString
tTakeUntilToken token= withGetParseString $ \str -> takeit mempty str
where
takeit :: Builder -> BS.ByteString -> TransIO ( BS.ByteString, BS.ByteString)
takeit res str=
if BS.null str then empty else
if token `BS.isPrefixOf` str
then return (toLazyByteString res ,BS.drop (BS.length token) str)
else if not $ BS.null str then takeit ( res <> (lazyByteString $ BS.singleton $ BS.head str)) $ BS.tail str else empty
integer :: TransIO Integer
integer= withGetParseString $ \str ->
case BS.readInteger str of
Just x -> return x
Nothing -> empty
hex :: TransIO Int
hex = withGetParseString $ \s -> parsehex (-1) s
where
parsehex v s=
case (BS.null s,v) of
(True, -1) -> empty
(True,_) -> return (v, mempty)
_ -> do
let h= BS.head s !> ("HEX",BS.head s)
t= BS.tail s
v'= if v== -1 then 0 else v
x = if h >= '0' && h <= '9' then v' * 16 + ord(h) -ord '0'
else if h >= 'A' && h <= 'F' then v' * 16 + ord h -ord 'A' +10
else if h >= 'a' && h <= 'f' then v' * 16 + ord h -ord 'a' +10
else -1
case (v,x) of
(-1,-1) -> empty
(v, -1) -> return (v,s)
(_, x) -> parsehex x t
int :: TransIO Int
int= withGetParseString $ \str ->
case BS.readInt str of
Just x -> return x
Nothing -> empty
double :: TransIO Double
double= do
ent <- integer
frac <- fracf
exp <- expf
return $ (fromIntegral ent * (10 ^ exp)) +- (( (fromIntegral $ fst $ fromJust $ BS.readInteger frac))
/(10 ^ (fromIntegral (BS.length frac) - exp)))
where
(+-) a b= if a >= 0 then a + b else a - b
fracf= do
tChar '.'
tTakeWhile isDigit
<|> return "0"
expf= do
tChar 'e' <|> tChar 'E'
int
<|> return 0
manyTill :: TransIO a -> TransIO b -> TransIO [a]
manyTill= chainManyTill (:)
chainManyTill op p end= scan
where
scan = do{try end; return mempty }
<|>
do{ x <- p; xs <- scan; return (x `op` xs) }
between open close p = do{ open; x <- p; close; return x }
symbol = string
parens p = between (symbol "(") (symbol ")") p !> "parens "
braces p = between (symbol "{") (symbol "}") p !> "braces "
angles p = between (symbol "<") (symbol ">") p !> "angles "
brackets p = between (symbol "[") (symbol "]") p !> "brackets "
semi = symbol ";" !> "semi"
comma = symbol "," !> "comma"
dot = symbol "." !> "dot"
colon = symbol ":" !> "colon"
sepBy p sep = sepBy1 p sep <|> return []
sepBy1 = chainSepBy1 (:)
chainSepBy chain p sep= chainSepBy1 chain p sep <|> return mempty
chainSepBy1
:: (Monad m, Monoid b, Alternative m) =>
(a -> b -> b) -> m a -> m x -> m b
chainSepBy1 chain p sep= do{ x <- p
; xs <- chainMany chain (sep >> p)
; return (x `chain` xs)
}
!> "chainSepBy "
chainMany chain v= (chain <$> v <*> chainMany chain v) <|> return mempty
commaSep p = sepBy p comma
semiSep p = sepBy p semi
commaSep1 p = sepBy1 p comma
semiSep1 p = sepBy1 p semi
dropSpaces= withGetParseString $ \str -> return( (),BS.dropWhile isSpace str)
dropTillEndOfLine= withGetParseString $ \str -> return ((),BS.dropWhile ( /= '\n') str) !> "dropTillEndOfLine"
parseString= do
tr "parseString"
dropSpaces
r <- tTakeWhile (not . isSpace)
return r
tTakeWhile :: (Char -> Bool) -> TransIO BS.ByteString
tTakeWhile cond=
withGetParseString $ \s -> do
let ret@(h,_)= BS.span cond s
if BS.null h then empty else return ret
tTakeWhile' :: (Char -> Bool) -> TransIO BS.ByteString
tTakeWhile' cond= withGetParseString $ \s -> do
let (h,t)= BS.span cond s
return () !> ("takewhile'",h,t)
if BS.null h then empty else return (h, if BS.null t then t else BS.tail t)
just1 f x= let (h,t)= f x in (Just h,t)
tTake n= withGetParseString $ \s -> return $ BS.splitAt n s !> ("tTake",n)
tDrop n= withGetParseString $ \s -> return $ ((),BS.drop n s)
anyChar= withGetParseString $ \s -> if BS.null s then empty else return (BS.head s ,BS.tail s )
tChar c= withGetParseString $ \s -> if BS.null s || BS.head s /= c then empty else return (BS.head s,BS.tail s)
withGetParseString :: (BS.ByteString -> TransIO (a,BS.ByteString)) -> TransIO a
withGetParseString parser= Transient $ do
ParseContext readMore s done <- gets parseContext
let loop = unsafeInterleaveIO $ do
r <-readIORef done
if r then return mempty else do
(mr,_) <- runTransient readMore
case mr of
Nothing -> mempty
Just(SMore r) -> return r <> do
d <- readIORef done
if d then mempty else loop
Just(SLast r) -> do tr "LAST"; writeIORef done True ; return r
Just SDone -> do tr "DONE"; writeIORef done True ; return mempty
str <- liftIO $ return s <> loop
mr <- runTrans $ parser str
case mr of
Nothing -> return Nothing
Just (v,str') -> do
modify $ \s-> s{parseContext= ParseContext readMore str' done}
return $ Just v
giveParseString :: TransIO BS.ByteString
giveParseString= (noTrans $ do
ParseContext readMore s done<- gets parseContext
let loop = unsafeInterleaveIO $ do
(mr,_) <- runTransient readMore
tr ("read",mr)
case mr of
Nothing -> mempty
Just(SMore r) -> (r <>) `liftM` loop
Just(SLast r) -> (r <>) `liftM` loop
Just SDone -> return mempty
liftIO $ (s <> ) `liftM` loop)
tDropUntil cond= withGetParseString $ \s -> f s
where
f s= if BS.null s then return ((),s) else if cond s then return ((),s) else f $ BS.tail s
tTakeUntil cond= withGetParseString $ \s -> f s
where
f s= if BS.null s then return (s,s) else if cond s then return (s,s) else f $ BS.tail s
tPutStr s'= withGetParseString $ \s -> return ((),s'<> s)
isDone :: TransIO Bool
isDone= noTrans $ do
ParseContext _ _ done<- gets parseContext
liftIO $ readIORef done
dropUntilDone= (withGetParseString $ \s -> do
tr "dropUntilDone"
ParseContext _ _ done <- gets parseContext
let loop s= do
if (unsafePerformIO $ readIORef done)== True || BS.null s then return((), s) else loop $ BS.tail s
loop s)
<|> return()
notParsed:: TransIO BS.ByteString
notParsed= withGetParseString $ \s -> return (s,mempty) !> "notParsed"
getParseBuffer :: TransIO BS.ByteString
getParseBuffer= do
ParseContext _ s _<- gets parseContext
return s
clearParseBuffer :: TransIO ()
clearParseBuffer=
modify$ \s -> s{parseContext= let ParseContext readMore _ d= parseContext s in ParseContext readMore mempty d}
showNext msg n= do
r <- tTake n
liftIO $ print (msg,r);
modify $ \s -> s{parseContext= (parseContext s){buffer= r <>buffer(parseContext s)}}
(|-) :: TransIO (StreamData BS.ByteString) -> TransIO b -> TransIO b
p |- q = do
pcontext <- liftIO $ newIORef $ Just undefined
v <- liftIO $ newEmptyMVar
initp v pcontext <|> initq v pcontext
where
initq v pcontext= do
setParseStream (do r <- liftIO $ takeMVar v; tr ("rec",fmap (BS.take 10) r); return r)
r <- q
dropUntilDone
Just p <- liftIO $ readIORef pcontext
liftIO $ writeIORef pcontext Nothing !> "WRITENOTHING"
pc <- gets parseContext
modify $ \ s -> s{parseContext= p{done=done pc}}
return r
initp v pcontext= do
abduce
ParseContext _ _ done <- gets parseContext
let repeatIt= do
pc <- liftIO $ readIORef pcontext
if isNothing pc then tr "FINNNNNNNNNNNNNNNNNNNNNNNN" >> empty else do
d <- liftIO $ readIORef done
if d then do tr "sendDone";liftIO $ putMVar v SDone; repeatIt else do
r <- p
liftIO $ putMVar v r
p <- gets parseContext
liftIO $ writeIORef pcontext $ Just p
case r of
SDone -> empty
SLast _ -> empty
SMore _ -> repeatIt
repeatIt