Copyright | © 2015–present Megaparsec contributors © 2007 Paolo Martini © 1999–2001 Daan Leijen |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Definition of Megaparsec's State
.
Since: 6.5.0
Synopsis
- data State s e = State {
- stateInput :: s
- stateOffset :: !Int
- statePosState :: PosState s
- stateParseErrors :: [ParseError s e]
- initialState :: FilePath -> s -> State s e
- data PosState s = PosState {
- pstateInput :: s
- pstateOffset :: !Int
- pstateSourcePos :: !SourcePos
- pstateTabWidth :: Pos
- pstateLinePrefix :: String
- initialPosState :: FilePath -> s -> PosState s
Documentation
This is the Megaparsec's state parametrized over stream type s
and
custom error component type e
.
State | |
|
Instances
(Data e, Data (ParseError s e), Data s) => Data (State s e) Source # | |
Defined in Text.Megaparsec.State gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> State s e -> c (State s e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (State s e) # toConstr :: State s e -> Constr # dataTypeOf :: State s e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (State s e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (State s e)) # gmapT :: (forall b. Data b => b -> b) -> State s e -> State s e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> State s e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> State s e -> r # gmapQ :: (forall d. Data d => d -> u) -> State s e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> State s e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> State s e -> m (State s e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> State s e -> m (State s e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> State s e -> m (State s e) # | |
Generic (State s e) Source # | |
(Show (ParseError s e), Show s) => Show (State s e) Source # | |
(NFData s, NFData (ParseError s e)) => NFData (State s e) Source # | |
Defined in Text.Megaparsec.State | |
(Eq (ParseError s e), Eq s) => Eq (State s e) Source # | |
type Rep (State s e) Source # | |
Defined in Text.Megaparsec.State type Rep (State s e) = D1 ('MetaData "State" "Text.Megaparsec.State" "megaparsec-9.6.1-JBxb9ZPC5mDEdcnxpEGZTp" 'False) (C1 ('MetaCons "State" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stateInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s) :*: S1 ('MetaSel ('Just "stateOffset") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "statePosState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PosState s)) :*: S1 ('MetaSel ('Just "stateParseErrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ParseError s e])))) |
Given the name of the source file and the input construct the initial state for a parser.
Since: 9.6.0
A special kind of state that is used to calculate line/column positions on demand.
Since: 7.0.0
PosState | |
|
Instances
Data s => Data (PosState s) Source # | |
Defined in Text.Megaparsec.State gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PosState s -> c (PosState s) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PosState s) # toConstr :: PosState s -> Constr # dataTypeOf :: PosState s -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PosState s)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PosState s)) # gmapT :: (forall b. Data b => b -> b) -> PosState s -> PosState s # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PosState s -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PosState s -> r # gmapQ :: (forall d. Data d => d -> u) -> PosState s -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PosState s -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PosState s -> m (PosState s) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PosState s -> m (PosState s) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PosState s -> m (PosState s) # | |
Generic (PosState s) Source # | |
Show s => Show (PosState s) Source # | |
NFData s => NFData (PosState s) Source # | |
Defined in Text.Megaparsec.State | |
Eq s => Eq (PosState s) Source # | |
type Rep (PosState s) Source # | |
Defined in Text.Megaparsec.State type Rep (PosState s) = D1 ('MetaData "PosState" "Text.Megaparsec.State" "megaparsec-9.6.1-JBxb9ZPC5mDEdcnxpEGZTp" 'False) (C1 ('MetaCons "PosState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pstateInput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s) :*: S1 ('MetaSel ('Just "pstateOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "pstateSourcePos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "pstateTabWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pos) :*: S1 ('MetaSel ('Just "pstateLinePrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) |
Given the name of source file and the input construct the initial positional state.
Since: 9.6.0