Chris Stryczynski

Software Developer / Consultant

Simple example of using state with Parsec

Posted on: 16/08/2020

Here is a simple example of a program that parses zero or more digits separated by spaces, which fails if it encounters a digit if it has already parsed previously.

{-# LANGUAGE ScopedTypeVariables #-}
module Main where

import Text.Parsec
import Control.Monad.Identity

type MyParser = ParsecT String [Char] Identity [Int]
type MyParser' = ParsecT String [Char] Identity Char


parseDigitIfNotInState :: MyParser'
parseDigitIfNotInState = do
  x <- digit
  s <- getState
  if (elem x (s :: [Char]))
     then parserFail (x : " is already present in state") 
     else (do
       putState (x : s)
       pure x
          )

myParse :: MyParser
myParse = do
  isEnd <- optionMaybe eof
  case isEnd of
    Just () -> pure []
    _ -> do
      a <- parseDigitIfNotInState
      void $ optional $ char ' '
      b <- optionMaybe myParse
      case b of
        Nothing -> pure $ f a
        Just (b' :: [Int]) -> (pure $ (f a) ++ b')
    where 
      f x = [ read $ pure x]

main :: IO ()
main = do
  case runParser myParse [] "Testing" "1 2 3" of
    Right x -> do
      print "Success"
      print x
    Left e -> print e
  case runParser myParse [] "Testing" "1 2 2 3" of
    Right x -> do
      print "Success"
      print x
    Left e -> print e

The output of the above is:

"Success"
[1,2,3]
"Testing" (line 1, column 6):
2 is already present in state
Comments

No comments, yet!

Submit a comment