[Haskell-beginners] Parsec

David Virebayre dav.vire+haskell at gmail.com
Fri Aug 6 05:41:00 EDT 2010


On Fri, Aug 6, 2010 at 11:03 AM, C Gosch <ch.gosch at googlemail.com> wrote:

> You're right, I probably used the wrong words .. I meant that apparently the
> tokens Parsec uses are of type Char, and I would actually at some point
> like to continue parsing, but using different tokens. Sorry if I still got
> it wrong, I'm new :)  I can post some code later, as I don't have it here
> right now.

Parsec (at least version 3) uses any type of token you want.

Quick example off the top of my head, I didn't check if it compiles:

-- you have to make lists of your token type an instance of Stream :

instance Stream [ MyTokenType ] Identity MyTokenType where
   uncons []     = return Nothing
   uncons (x:xs) = return $ Just (x,xs)

-- your parser type is going to look like this :

type MyParser a = ParsecT [MyTokenType] () Identity a

-- assuming your toke type looks like this

Data MyTokenType = A Char
                 | B Word8
    deriving (Show)


-- you need a basic parser from which you can make more complicated ones

satisChar :: ( Char -> Bool ) -> MyParser Char
satisChar f = tokenPrim prt pos match
    where
      prt           = show
      pos p _l _cs  = incSourceLine p 1
      match (A c)   = if f c then Just c else Nothing
      match _       = Nothing

satisBin :: ( Word8 -> Bool ) -> MyParser Word8
satisBin f = tokenPrim prt pos match
    where
      prt           = show
      pos p _l _cs  = incSourceLine p 1
      match (B w)   = if f w then Just w else Nothing
      match _       = Nothing

-- You can define basic parsers like this

-- parse any letter
letter = satisChar (const True)

-- parse a specific char, it will return
char c = satisChar (==c)

-- parse any binary word
binary = satisBin (const True)

-- parse a specific binary
word w = satisBin (==w)

-- now you can combine this to make more complicated parsers.

...


More information about the Beginners mailing list