Here’s a working example:
import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.Idioms
import Text.ParserCombinators.UU.Utils
import Text.ParserCombinators.UU.BasicInstances
import Data.Foldable
import Data.Word
data IP = IP Word8 Word8 Word8 Word8 deriving Show
ips :: [String]
ips = ["192.168.1.0","8.8.8.8","255.255.255.0"]
ipString :: Int -> String
ipString n = unlines (take n (cycle ips))
pIP :: Parser IP
pIP = iI IP pNatural '.' pNatural '.' pNatural '.' pNatural '\n' Ii
main :: IO ()
main = traverse_ print
(parse (pList pIP <* pEnd) (createStr (LineColPos 0 0 0) (ipString 5)))
This doesn’t (explicitly) stop and resume the parser for each IP address. I know of one parsing library based on the same ideas as uu-parsinglib
, but it is even less easy to understand and it has even less documentation… It is Yi’s incremental parser. I have been thinking before about adding such incremental functionality to uu-parsinglib
, but I haven’t had enough time for it yet (and it is pretty hard).
There is a way to cheat an IO String
stream into an infinite string using unsafeInterleaveIO
.
-- This string is infinite vvvvvv
withStringStream :: IO (Maybe String) -> (String -> IO a) -> IO a
withStringStream m f = f =<< go
where
go = do
x <- m
case x of
Just s -> (s ++) <$> unsafeInterleaveIO go
Nothing -> return ""
Here’s a little gist with example usage.
Another thing that should be noted is that this uses Haskell’s String
type, which is not always very efficient. Additionally, I haven’t done any benchmarks, but I wouldn’t be surprised if uu-parsinglib
is quite a bit slower than your hand-made decomposed attoparsec
parser that works with bytestrings.
Also, this uses idiom brackets, the iI
and Ii
. Syntactically it is a bit of a hack. They can be converted into do notation. These definitions are all interchangable*:
pIP = iI IP pNatural '.' pNatural '.' pNatural '.' pNatural '\n' Ii
pIP = IP <$> pNatural <* pSym '.'
<*> pNatural <* pSym '.'
<*> pNatural <* pSym '.'
<*> pNatural <* pSym '\n'
pIP = do
d1 <- pNatural
pSym '.'
d2 <- pNatural
pSym '.'
d3 <- pNatural
pSym '.'
d4 <- pNatural
pSym '\n'
return $ IP d1 d2 d3 d4
*except that the first two use only Applicative
operations, the last one requires Monad
operations (unless you use the ApplicativeDo
langauge extension). And uu-parsinglib
is able to do more analysis on parsers that only use Applicative
operations, so one of the first two is preffered. Officially, the laws of Monad
state that the monadic operations should be interchangeable with the Applicative
operations, so the uu-parsinglib
parser is not officially a proper monad. But, the only difference should be performance, so it is not a big deal.
EDIT: I have done some benchmarks and the result is that the working example at the top of this comment still uses a linear amount of memory unfortunately.