Custom state in Trifecta
Asked Answered
V

1

6

I'm using Trifecta parser combinator library and my parser outputs instances of AST data type. I want each instance to have unique ID (which is simple Int).

In Parsec I would create custom state and increment the ID when neccesery. How can we do it in Trifecta?

Veneaux answered 14/9, 2013 at 21:30 Comment(0)
E
6

You can enhance the Parser monad with the StateT monad transformer to get what you want. This integrates well with the rest of the library, as most of the combinators use type classes rather than concrete types (meaning you don't have to do much lifting for the code to work). Here is a decent example of this. It parses a grammar with identifiers and symbols separated by whitespace. Each identifier is give a unique number.

module Main where
import Text.Trifecta
import Control.Monad.State
import Control.Applicative
import Data.Monoid

data Identifier = Identifier String Int deriving (Show)

identifier :: StateT Int Parser Identifier
identifier = do
  name <- some letter
  newId <- get
  modify (+1)
  return $ Identifier name newId

symbolToken :: Parser Char
symbolToken = oneOf "+-*/"

data Token = IdentifierToken Identifier | SymbolToken Char deriving (Show)

singleToken :: StateT Int Parser Token
singleToken = try (IdentifierToken <$> identifier) <|> (SymbolToken <$> lift symbolToken)

parseTokens :: StateT Int Parser [Token]
parseTokens = singleToken `sepBy1` spaces

testParse :: String -> Result [Token]
testParse = parseString (evalStateT parseTokens 0) mempty 

test1 :: Result [Token]
test1 = testParse "these are identifiers and + some / symbols -"

test1 results in:

Success [IdentifierToken (Identifier "these" 0)
,IdentifierToken (Identifier "are" 1)
,IdentifierToken (Identifier "identifiers" 2)
,IdentifierToken (Identifier "and" 3)
,SymbolToken '+',IdentifierToken (Identifier "some" 4)
,SymbolToken '/',IdentifierToken (Identifier "symbols" 5),SymbolToken '-']
Ennis answered 15/9, 2013 at 12:0 Comment(3)
I just discovered the answer is wrong. Look, you are evaluating the state BEFORE parsing, which is wrong - in such use cases as If you would to use the state to generate unique identifiers.Veneaux
Are you sure this is incorrect? The state isn't just being evaluated at the start, but rather through the whole program. The evalStateT parseTokens 0 is effectively just setting the initial state value. This is how I've always done it, and it doesn't seem to have any problems. If you do have an example of how this gives an unexpected result I would like to see it though!Ennis
Right, I was wrong. This example is valid - our example had a typo in a very funny place and we were looking for error in completely wrong place. I will delete the comments tommorow, because they are obsolete now. Thank you! :)Veneaux

© 2022 - 2024 — McMap. All rights reserved.