
Am Dienstag, 11. November 2008 07:20 schrieb Jeffrey Drake:
I have decided to go in another direction, so the parser here is going to be different, but it works without error correction. I am using a wiki style right here, where I am testing headers level 1 to 5.
I believe I need to essentially throw an error here, normally I would think > might be appropriate, but it doesn't seem to apply in this case.
The problem is that a1, a2 must satisfy two conditions:
a1 == a2 1 <= a1 <= 5
If it doesn't, then an error must be output.
It appears that > is just an operator for 'label'. Which goes to labels, which does eventually go to construct Error, but not sure in the correct context.
> gives you the opportunity to construct a helpful error message if the parser fails. You provide information what the parser expects and if it fails you get the message "unexpected whatever, expecting x, y, z or w"
Again, any help is appreciated, I am getting a feeling for this I think. - Jeff.
Code is below:
module Main where
import Control.Monad
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec.Char import Text.ParserCombinators.Parsec.Combinator
data Wiki = Heading Int String
| Other String
deriving Show
{- a1/a2 heading level 2 5 3 4 4 3 5 2 6 1
:. 7 - a1
-} heading :: Parser Wiki heading = do (a1, s, a2) <- within (length `liftM` many1 (char '=')) (length `liftM` many1 (char '=')) (many1 (alphaNum <|> space)) return $ Heading (7 - a1) s where within open close p = do a1 <- open x <- p a2 <- close return (a1, x, a2)
Perhaps heading :: Parser Wiki heading = do a1 <- length `liftM` many1 (char '=') title <- many1 (alphaNum <|> space) count a1 (char '=') notFollowedBy (char '=') return $ Heading (7-a1) title ? Although that doesn't check that there are at most 5 '=', so you might use the combinators upTo 0 p = do notFollowedBy p return [] upTo k p = (do a <- p as <- upTo (k-1) p return (a:as)) <|> return [] upTo1 k p = do a <- p as <- upTo (k-1) p return (a:as) exactly k p = do as <- count k p notFollowedBy p return as as in heading = do a1 <- length `liftM` upTo1 5 (char '=') <?> ("1 to 5 '='s") title <- many1 (alphaNum <|> space) exactly a1 (char '=') <?> (show a1 ++ " '='s") return $ Heading (7-a1) title
On Mon, 2008-11-10 at 06:10 +0100, Tillmann Rendel wrote:
Jeffrey Drake wrote:
This helps a lot, and I can go over this in the morning. The only final question I have is what you would use to apply all this to an arbitrary string.
You can use parseTest for testing, e.g. in ghci.
parseTest texList "hello\world {example}"
That will either print the resulting {TeX], or a parser error message.
For normal processing, use parse.
case parse texList "<no source>" "hello\world {example}" of Left problem -> error (show problem) Right texList -> convertToHTML texList
Tillmann
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners