module Scanner
( Scanner
, Result (..)
, scan
, scanOnly
, scanLazy
, scanWith
, anyWord8
, anyChar8
, word8
, char8
, take
, takeWhile
, takeWhileChar8
, string
, skipWhile
, skipSpace
, lookAhead
, lookAheadChar8
, foldlWhile
, foldlWhile1
, satisfy
, satisfyMaybe
, decimal
)
where
import Scanner.Internal
import Prelude hiding (take, takeWhile)
import Data.Word
import qualified Data.Char as Char
import Data.ByteString (ByteString)
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as Lazy (ByteString)
import qualified Data.ByteString.Lazy as Lazy.ByteString
import Control.Monad
import GHC.Base (unsafeChr)
scanOnly :: Scanner a -> ByteString -> Either String a
scanOnly s bs = go (scan s bs)
where
go res = case res of
Done _ r -> Right r
Fail _ err -> Left err
More more -> go (more ByteString.empty)
scanLazy :: Scanner a -> Lazy.ByteString -> Either String a
scanLazy s lbs = go (scan s) (Lazy.ByteString.toChunks lbs)
where
go more chunks =
let (chunk, chunks') = case chunks of
[] -> (ByteString.empty, [])
(c:cs) -> (c, cs)
in case more chunk of
Done _ r -> Right r
Fail _ err -> Left err
More more' -> go more' chunks'
scanWith :: Monad m => m ByteString -> Scanner a -> ByteString -> m (Result a)
scanWith more s input = go input (scan s)
where
go bs next = case next bs of
More next' -> do
bs' <- more
go bs' next'
res -> return res
{-# INLINE anyChar8 #-}
anyChar8 :: Scanner Char
anyChar8 = w2c <$> anyWord8
{-# INLINE word8 #-}
word8 :: Word8 -> Scanner ()
word8 w = do
w' <- anyWord8
unless (w' == w) $
fail "unexpected word"
{-# INLINE char8 #-}
char8 :: Char -> Scanner ()
char8 = word8 . c2w
{-# INLINE takeWhileChar8 #-}
takeWhileChar8 :: (Char -> Bool) -> Scanner ByteString
takeWhileChar8 p = takeWhile (p . w2c)
{-# INLINE lookAheadChar8 #-}
lookAheadChar8 :: Scanner (Maybe Char)
lookAheadChar8 = fmap w2c <$> lookAhead
{-# INLINE skipWhile #-}
skipWhile :: (Word8 -> Bool) -> Scanner ()
skipWhile = void . takeWhile
{-# INLINE skipSpace #-}
skipSpace :: Scanner ()
skipSpace = skipWhile isSpaceWord8
{-# INLINE isSpaceWord8 #-}
isSpaceWord8 :: Word8 -> Bool
isSpaceWord8 w = w == 32 || w <= 13
{-# INLINE w2c #-}
w2c :: Word8 -> Char
w2c = unsafeChr . fromIntegral
{-# INLINE c2w #-}
c2w :: Char -> Word8
c2w = fromIntegral . Char.ord