Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data ParseError a
- class AsLexicalError s t | s -> t where
- class AsTabError s a | s -> a where
- class AsIncorrectDedent s a | s -> a where
- _IncorrectDedent :: Prism' s a
- class AsIRError s a | s -> a where
- _InvalidUnpacking :: Prism' s a
- class AsParseError s t | s -> t where
- data ErrorItem t
- data SourcePos = SourcePos {
- sourceName :: FilePath
- sourceLine :: !Pos
- sourceColumn :: !Pos
Documentation
data ParseError a Source #
LexicalError (NonEmpty SourcePos) (Maybe (ErrorItem Char)) (Set (ErrorItem Char)) | An error occured during tokenization (this is a re-packed megaparsec error) |
ParseError (NonEmpty SourcePos) (Maybe (ErrorItem (PyToken a))) (Set (ErrorItem (PyToken a))) | An error occured during parsing (this is a re-packed megaparsec error) |
TabError a | Tabs and spaces were used inconsistently |
IncorrectDedent a | The dedent at the end of a block doesn't match and preceding indents e.g. def a(): if b: pass else: pass pass The final line will cause an |
InvalidUnpacking a | Unpacking ( |
Instances
Eq a => Eq (ParseError a) Source # | |
Defined in Language.Python.Parse.Error (==) :: ParseError a -> ParseError a -> Bool # (/=) :: ParseError a -> ParseError a -> Bool # | |
Show a => Show (ParseError a) Source # | |
Defined in Language.Python.Parse.Error showsPrec :: Int -> ParseError a -> ShowS # show :: ParseError a -> String # showList :: [ParseError a] -> ShowS # | |
AsIRError (ParseError a) a Source # | |
Defined in Language.Python.Parse.Error _InvalidUnpacking :: Prism' (ParseError a) a Source # | |
AsIncorrectDedent (ParseError a) a Source # | |
Defined in Language.Python.Parse.Error _IncorrectDedent :: Prism' (ParseError a) a Source # | |
AsTabError (ParseError a) a Source # | |
Defined in Language.Python.Parse.Error _TabError :: Prism' (ParseError a) a Source # | |
AsLexicalError (ParseError a) Char Source # | |
Defined in Language.Python.Parse.Error | |
AsParseError (ParseError a) (PyToken a) Source # | |
Defined in Language.Python.Parse.Error |
Classy Prisms
class AsLexicalError s t | s -> t where Source #
Instances
AsLexicalError (ParseError a) Char Source # | |
Defined in Language.Python.Parse.Error |
class AsTabError s a | s -> a where Source #
Instances
AsTabError (ParseError a) a Source # | |
Defined in Language.Python.Parse.Error _TabError :: Prism' (ParseError a) a Source # | |
AsTabError (IndentationError a) a Source # | |
Defined in Language.Python.Validate.Indentation.Error _TabError :: Prism' (IndentationError a) a Source # | |
AsTabError (ValidationError a) a Source # | |
Defined in Language.Python.Validate.Error _TabError :: Prism' (ValidationError a) a Source # |
class AsIncorrectDedent s a | s -> a where Source #
_IncorrectDedent :: Prism' s a Source #
Instances
AsIncorrectDedent (ParseError a) a Source # | |
Defined in Language.Python.Parse.Error _IncorrectDedent :: Prism' (ParseError a) a Source # |
class AsIRError s a | s -> a where Source #
_InvalidUnpacking :: Prism' s a Source #
Instances
AsIRError (ParseError a) a Source # | |
Defined in Language.Python.Parse.Error _InvalidUnpacking :: Prism' (ParseError a) a Source # |
class AsParseError s t | s -> t where Source #
Instances
AsParseError (ParseError a) (PyToken a) Source # | |
Defined in Language.Python.Parse.Error |
Megaparsec re-exports
Data type that is used to represent “unexpected/expected” items in
ParseError
. The data type is parametrized over the token type t
.
Since: megaparsec-5.0.0
Tokens (NonEmpty t) | Non-empty stream of tokens |
Label (NonEmpty Char) | Label (cannot be empty) |
EndOfInput | End of input |
Instances
Functor ErrorItem | |
Eq t => Eq (ErrorItem t) | |
Data t => Data (ErrorItem t) | |
Defined in Text.Megaparsec.Error gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorItem t -> c (ErrorItem t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ErrorItem t) # toConstr :: ErrorItem t -> Constr # dataTypeOf :: ErrorItem t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (ErrorItem t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (ErrorItem t)) # gmapT :: (forall b. Data b => b -> b) -> ErrorItem t -> ErrorItem t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorItem t -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorItem t -> r # gmapQ :: (forall d. Data d => d -> u) -> ErrorItem t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorItem t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorItem t -> m (ErrorItem t) # | |
Ord t => Ord (ErrorItem t) | |
Defined in Text.Megaparsec.Error | |
Read t => Read (ErrorItem t) | |
Show t => Show (ErrorItem t) | |
Generic (ErrorItem t) | |
NFData t => NFData (ErrorItem t) | |
Defined in Text.Megaparsec.Error | |
(Ord t, ShowToken t) => ShowErrorComponent (ErrorItem t) | |
Defined in Text.Megaparsec.Error showErrorComponent :: ErrorItem t -> String # | |
type Rep (ErrorItem t) | |
Defined in Text.Megaparsec.Error type Rep (ErrorItem t) = D1 (MetaData "ErrorItem" "Text.Megaparsec.Error" "megaparsec-6.5.0-CK6UWBz91u27EgbRYoKlk2" False) (C1 (MetaCons "Tokens" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty t))) :+: (C1 (MetaCons "Label" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty Char))) :+: C1 (MetaCons "EndOfInput" PrefixI False) (U1 :: Type -> Type))) |
The data type SourcePos
represents source positions. It contains the
name of the source file, a line number, and a column number. Source line
and column positions change intensively during parsing, so we need to
make them strict to avoid memory leaks.
SourcePos | |
|
Instances
Eq SourcePos | |
Data SourcePos | |
Defined in Text.Megaparsec.Pos gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourcePos -> c SourcePos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourcePos # toConstr :: SourcePos -> Constr # dataTypeOf :: SourcePos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourcePos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos) # gmapT :: (forall b. Data b => b -> b) -> SourcePos -> SourcePos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r # gmapQ :: (forall d. Data d => d -> u) -> SourcePos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourcePos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # | |
Ord SourcePos | |
Defined in Text.Megaparsec.Pos | |
Read SourcePos | |
Show SourcePos | |
Generic SourcePos | |
NFData SourcePos | |
Defined in Text.Megaparsec.Pos | |
type Rep SourcePos | |
Defined in Text.Megaparsec.Pos type Rep SourcePos = D1 (MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-6.5.0-CK6UWBz91u27EgbRYoKlk2" False) (C1 (MetaCons "SourcePos" PrefixI True) (S1 (MetaSel (Just "sourceName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: (S1 (MetaSel (Just "sourceLine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos) :*: S1 (MetaSel (Just "sourceColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos)))) |