[Haskell-cafe] Having trouble with this recursive Parsec parser
Cody Goodman
codygman.consulting at gmail.com
Fri Jun 23 06:26:14 UTC 2017
Hi all,
I'm having trouble with a recursive parsec parser that keeps recursing on
one type of end tag and terminates on another type of end tag. I'm sure I'm
stuck on something silly, but here's what I have so far.
Git repo with stack/cabal project:
https://github.com/codygman/megaparsectest/blob/master/library/Example.hs
Code I have so far (I deleted a few different approaches I tried because I
thought they would clutter things up and make it harder to assist me with
this issue):
{-# LANGUAGE QuasiQuotes #-}
-- | An example module.
module Example where
import Text.Megaparsec
import Text.RawString.QQ
import Text.Megaparsec.String -- input stream is of the type ‘String’
import qualified Text.Megaparsec.Lexer as L
import Control.Monad (void, join)
ex :: String
ex = [r|
begin
field1 string
begin
field11 int
field12 string
end subsection; // optional
end;
|]
data Field = Field String String deriving Show
data Block = Fields [Field] | Block [Field] deriving Show
sc :: Parser ()
sc = L.space (void spaceChar) lineCmnt blockCmnt
where lineCmnt = L.skipLineComment "//"
blockCmnt = L.skipBlockComment "/*" "*/"
field :: Parser Field
field = dbg "field" $ do
sc
Field <$> someTill ((oneOf' (['a'..'z'] ++ ['0'..'9']))) spaceChar
<*> some ((oneOf' (['a'..'z'] ++ ['0'..'9'])))
endEof = do
sc *> string "end" *> char ';' *> sc *> eof
pure ""
endIdent = do
string "end" *> sc
ident <- someTill ((oneOf' (['a'..'z'] ++ ['0'..'9']))) (char ';')
sc *> eof
pure ident
block = error "TODO implement"
-- Thanks,
-- Cody
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170623/b0b60487/attachment.html>
More information about the Haskell-Cafe
mailing list