-- | -- Module : Data.Attoparsec.Text.Lazy -- Copyright : Felipe Lessa 2010, Bryan O'Sullivan 2010 -- License : BSD3 -- -- Maintainer : felipe.lessa@gmail.com -- Stability : experimental -- Portability : unknown -- -- Simple, efficient combinator parsing for lazy 'Text' -- strings, loosely based on the Parsec library. -- -- This is essentially the same code as in the 'Data.Attoparsec' -- module, only with a 'parse' function that can consume a lazy -- 'Text' incrementally, and a 'Result' type that does not allow -- more input to be fed in. Think of this as suitable for use with a -- lazily read file, e.g. via 'L.readFile' or 'L.hGetContents'. -- -- Behind the scenes, strict 'T.Text' values are still used -- internally to store parser input and manipulate it efficiently. -- High-performance parsers such as 'string' still expect strict -- 'T.Text' parameters. module Data.Attoparsec.Text.Lazy {-# DEPRECATED "Use version 0.10 or newer of the attoparsec package instead" #-} ( Result(..) , module Data.Attoparsec.Text -- * Running parsers , parse , parseTest -- ** Result conversion , maybeResult , eitherResult ) where import Data.Text.Lazy (Text, fromChunks, toChunks) import qualified Data.Text as T import qualified Data.Attoparsec.Text as A import Data.Attoparsec.Text hiding (Result(..), eitherResult, maybeResult, parse, parseWith, parseTest) -- | The result of a parse. data Result r = Fail Text [String] String -- ^ The parse failed. The 'Text' is the input -- that had not yet been consumed when the failure -- occurred. The @[@'String'@]@ is a list of contexts -- in which the error occurred. The 'String' is the -- message describing the error, if any. | Done Text r -- ^ The parse succeeded. The 'Text' is the -- input that had not yet been consumed (if any) when -- the parse succeeded. instance Show r => Show (Result r) where show (Fail bs stk msg) = "Fail " ++ show bs ++ " " ++ show stk ++ " " ++ show msg show (Done bs r) = "Done " ++ show bs ++ " " ++ show r fmapR :: (a -> b) -> Result a -> Result b fmapR _ (Fail st stk msg) = Fail st stk msg fmapR f (Done bs r) = Done bs (f r) instance Functor Result where fmap = fmapR -- | Run a parser and return its result. parse :: A.Parser a -> Text -> Result a parse p s = case toChunks s of x:xs -> go (A.parse p x) xs [] -> go (A.parse p T.empty) [] where go (A.Fail x stk msg) ys = Fail (fromChunks $ x:ys) stk msg go (A.Done x r) ys = Done (fromChunks $ x:ys) r go (A.Partial k) (y:ys) = go (k y) ys go (A.Partial k) [] = go (k T.empty) [] -- | Run a parser and print its result to standard output. parseTest :: (Show a) => A.Parser a -> Text -> IO () parseTest p s = print (parse p s) -- | Convert a 'Result' value to a 'Maybe' value. maybeResult :: Result r -> Maybe r maybeResult (Done _ r) = Just r maybeResult _ = Nothing -- | Convert a 'Result' value to an 'Either' value. eitherResult :: Result r -> Either String r eitherResult (Done _ r) = Right r eitherResult (Fail _ _ msg) = Left msg