[Haskell-cafe] types for parsing a tree

S. Doaitse Swierstra doaitse at swierstra.net
Fri Sep 10 15:00:46 EDT 2010


I show how this can be done using uu-parsinglib. Note that we have sevral parsers, each having its own type:

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 <$>  "TRNUID" `pTag` pLine
                                                            <*>  "NAME"   `pTag` pLine
                                                            <*> 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

Running the main function on your code gives:

*Transactions> :r
[1 of 1] Compiling Transactions     ( Transactions.hs, interpreted )
Ok, modules loaded: Transactions.
*Transactions> main
--
-- > Result: OFX (Response [Transaction "9223ry29r389" "THE GROCERY STORE BLABLABLA" (Amount 234 99),Transaction "1237tg832t" "SOME DUDE ON PAYPAL 4781487" (Amount 2174 27)])
-- 
*Transactions> 

It is interesting to what happens if your input is incorrect,

 Doaitse





On 10 sep 2010, at 18:53, Jared Jennings wrote:

> <OFX>[...]
>        <STMTRS>[...]
>            <STMTTRN>[...]
>                <TRNUID>9223ry29r389
>                <NAME>THE GROCERY STORE BLABLABLA
>                <TRNAMT>234.99
>            </STMTTRN>
>            <STMTTRN>[...]
>                <TRNUID>1237tg832t
>                <NAME>SOME DUDE ON PAYPAL 4781487
>                <TRNAMT>2174.27
>            </STMTTRN>
>        </STMTRS>
>    </OFX>



More information about the Haskell-Cafe mailing list