{-# LANGUAGE Haskell2010 #-} -- | -- Module : Data.Picoparsec.Number -- Copyright : Mario Blažević 2015 -- License : BSD3 -- -- Maintainer : Mario Blažević -- Stability : experimental -- Portability : unknown -- -- This module provides the basic support for parsing state. -- -- To support state, the parser input must be a 'Stateful' monoid. The parsing state thus becomes the final part of the -- input, accessible and modifiable during the parse. Be careful to account for the presence of state before the -- 'Data.Picoparsec.Combinator.endOfInput'! The following parser, for example, would loop forever: -- -- > many (setState "more" *> anyToken) module Data.Picoparsec.State (getState, putState, modifyState) where import Data.Functor ((<$>)) import Data.Monoid.Instances.Stateful (Stateful) import qualified Data.Monoid.Instances.Stateful as Stateful import Data.Picoparsec (Parser) import qualified Data.Picoparsec.Internal as I -- | Returns the current user state. getState :: Parser (Stateful s t) s getState = Stateful.state <$> I.get -- | Sets the current state. putState :: s -> Parser (Stateful s t) () putState s = I.get >>= (I.put . Stateful.setState s) -- | Modifies the current state. modifyState :: (s -> s) -> Parser (Stateful s t) () modifyState f = I.get >>= \i-> I.put (Stateful.setState (f $ Stateful.state i) i)