[Haskell-beginners] Parsec, parsing 'free text'
Franco
franco00 at gmx.com
Sun Mar 11 12:45:26 CET 2012
Indeed the second solution is more elegant (and the examples very simple to follow, they should be added to Parsec's documentation!).
For the records, before reading this I was using the ductape solution below:
161
162 -- take a string till t, on that runs parser p.
163 -- The last parameters sets wheter t will be consumed or
164 -- not. FILE HANDLING FOR ERRORS?
165 parseTill :: Parser a -> Parser b -> Parser b
166 parseTill ter p = manyTill anyChar ter >>= \sndPar ->
167 case parse p "" sndPar of
168 Left a -> fail "todo: check how error msg are propagted"
169 Right b -> return b
Thanks again
-F
On Sun, 11 Mar 2012 10:53:50 +0000
Stephen Tetley <stephen.tetley at gmail.com> wrote:
> Hi Franco
>
> Actually the simple case of finding formatting tags in free text was
> easier in Parsec than my email last night suggested. Perhaps it is
> artificially easy because you can identify tag start and ends with a
> single character so you can use `satisfy`.
>
> import Text.Parsec
> import Text.Parsec.String
> import Control.Applicative hiding ( (<|>), many )
>
>
> data Text1 = FreeText String | Formatted String
> deriving (Eq,Ord,Show)
>
> type Text = [Text1]
>
> runText :: String -> Either ParseError Text
> runText = runP lexer () "no-input"
>
>
> notLAngle :: Char -> Bool
> notLAngle = (/= '<')
>
> notRAngle :: Char -> Bool
> notRAngle = (/= '>')
>
> lexer :: Parser Text
> lexer = many (formatted <|> free)
>
> formatted :: Parser Text1
> formatted = Formatted <$>
> between (char '<') (char '>') (many1 (satisfy notRAngle))
>
> free :: Parser Text1
> free = FreeText <$> many1 (satisfy notLAngle)
>
>
>
> demo01 = runText "[ someconditions | this is some <red - formatted> text.]"
> demo02 = runText "<red - formatted> more text."
--
Franco <franco00 at gmx.com>
More information about the Beginners
mailing list