Copyright | (C) CSIRO 2017-2018 |
---|---|
License | BSD3 |
Maintainer | Isaac Elliott <isaace71295@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- tokenizeWithTabs :: (AsLexicalError s Char, AsTabError s SrcInfo, AsIncorrectDedent s SrcInfo) => FilePath -> Text -> Either s [PyToken SrcInfo]
- data SrcInfo = SrcInfo {
- _srcInfoName :: FilePath
- _srcInfoLineStart :: !Int
- _srcInfoLineEnd :: !Int
- _srcInfoColStart :: !Int
- _srcInfoColEnd :: !Int
- _srcInfoOffsetStart :: !Int
- _srcInfoOffsetEnd :: !Int
- initialSrcInfo :: FilePath -> SrcInfo
- withSrcInfo :: MonadParsec e s m => m (SrcInfo -> a) -> m a
- class AsLexicalError s t | s -> t where
- unsafeFromLexicalError :: (HasCallStack, AsLexicalError s t) => ParseError t Void -> s
- class AsTabError s a | s -> a where
- _TabError :: Prism' s a
- class AsIncorrectDedent s a | s -> a where
- _IncorrectDedent :: Prism' s a
- fromTabError :: (AsTabError s a, AsIncorrectDedent s a) => TabError a -> s
- data TabError a
- = TabError a
- | IncorrectDedent a
- tokenize :: AsLexicalError e Char => FilePath -> Text -> Either e [PyToken SrcInfo]
- insertTabs :: (Semigroup a, AsTabError s a, AsIncorrectDedent s a) => a -> [PyToken a] -> Either s [PyToken a]
- data ParseError t e
Documentation
:: (AsLexicalError s Char, AsTabError s SrcInfo, AsIncorrectDedent s SrcInfo) | |
=> FilePath | File name |
-> Text | Input to tokenize |
-> Either s [PyToken SrcInfo] |
Tokenize an input file, inserting indent/level/dedent tokens in appropriate positions according to the block structure.
Source Information
SrcInfo | |
|
initialSrcInfo :: FilePath -> SrcInfo Source #
withSrcInfo :: MonadParsec e s m => m (SrcInfo -> a) -> m a Source #
Errors
class AsLexicalError s t | s -> t where Source #
Instances
AsLexicalError (ParseError a) Char Source # | |
Defined in Language.Python.Parse.Error |
unsafeFromLexicalError :: (HasCallStack, AsLexicalError s t) => ParseError t Void -> s Source #
Convert a concrete ParseError
to a value that has an instance of AsLexicalError
This function is partial, because our parser will never use FancyError
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 # |
fromTabError :: (AsTabError s a, AsIncorrectDedent s a) => TabError a -> s Source #
Convert a concrete TabError
to a value that has an instance of AsTabError
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 |
Miscellaneous
Convert some input to a sequence of tokens. Indent and dedent tokens are not added
(see insertTabs
)
:: (Semigroup a, AsTabError s a, AsIncorrectDedent s a) | |
=> a | Initial source annotation |
-> [PyToken a] | Token stream |
-> Either s [PyToken a] |
Insert indent and dedent tokens
https://docs.python.org/3.5/reference/lexical_analysis.html#indentation
Megaparsec re-exports
data ParseError t e #
TrivialError (NonEmpty SourcePos) (Maybe (ErrorItem t)) (Set (ErrorItem t)) | |
FancyError (NonEmpty SourcePos) (Set (ErrorFancy e)) |