[Haskell-cafe] types for parsing a tree

S. Doaitse Swierstra doaitse at swierstra.net
Fri Sep 17 16:39:01 EDT 2010


On 16 sep 2010, at 05:42, Jared Jennings wrote:

> On Fri, Sep 10, 2010 at 2:00 PM, S. Doaitse Swierstra
> <doaitse at swierstra.net> wrote:
>> I show how this can be done using uu-parsinglib. Note that we have sevral parsers, each having its own type:
> 
> Thanks for such a complete example, Doaitse! Unfortunately I have a
> requirement I didn't disclose: the simple tags like <TRNUID>, <NAME>,
> <AMOUNT> could come in any order; and some are optional. I tried to
> fix that by making every field in my Transaction record a Maybe, and
> keeping a Transaction as state for my parser. But after so many Maybes
> I began to think this was not the right way. And I had to run a parser
> as part of another parser. And after all that, it wouldn't build
> because it was badly typed.

The good news is that the library has combinators for that too ;-} Just change a few lines. If they are optional use the pOpt combinator instead of the pOne. 

          Doaitse

module Transactions where
import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.Examples
import Data.Char

pTagged tag (pAttr, pPayload) =  pToken ("<" ++ tag ++ ">") *> pAttr *> spaces *> pPayload <* spaces <*
                                pToken ("</" ++ tag ++ ">")
pTag    tag         pPayload  =  pToken ("<" ++ tag ++ ">") *> pPayload

data OFX = OFX Response deriving Show
data Response = Response [Transaction] deriving Show
data Transaction = Transaction String String Amount deriving Show
data Amount      = Amount Int Int deriving Show

pAmount          = "TRNAMT"   `pTag` (Amount <$> pNatural <* pSym '.' <*> pNatural)
pTransaction     = "STMTTRN"  `pTagged` (pAttr, Transaction `pMerge`    ( pOne ("TRNUID" `pTag` pLine)
                                                                    <||> pOne ("NAME"   `pTag` pLine)
                                                                    <||> pOne  pAmount
                                                                       )
                                       )
pResponse        = "STMTRS"   `pTagged` (pAttr, Response <$> pList (pTransaction <* spaces))
pOFX             = "OFX"      `pTagged` (pAttr, OFX      <$> pResponse )

pAttr :: Parser String
pAttr = pToken "[...]"

spaces = pMunch (`elem` " \n\t")
pDigitAsInt = digit2Int <$> pDigit 
pNatural = foldl (\a b -> a * 10 + b ) 0 <$> pList1 pDigitAsInt
digit2Int a =  ord a - ord '0'
pDigit :: Parser Char
pDigit = pSym ('0', '9')
pLine  = pMunch (/='\n') <* spaces

main = do input <- readFile "TrInput"
         run (pOFX <* spaces) input




> 
> But in any case, thanks for turning me on to
> Text.ParserCombinators.UU; I'd only tried Parsec before.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list