Copyright | (C) CSIRO 2017-2018 |
---|---|
License | BSD3 |
Maintainer | Isaac Elliott <isaace71295@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- module Language.Python.Validate.Indentation.Error
- data Indentation
- type ValidateIndentation e = ValidateM (NonEmpty e) (State (NextIndent, [Indent]))
- runValidateIndentation :: ValidateIndentation e a -> Validation (NonEmpty e) a
- validateModuleIndentation :: AsIndentationError e a => Module v a -> ValidateIndentation e (Module (Nub (Indentation ': v)) a)
- validateStatementIndentation :: AsIndentationError e a => Statement v a -> ValidateIndentation e (Statement (Nub (Indentation ': v)) a)
- validateExprIndentation :: AsIndentationError e a => Expr v a -> ValidateIndentation e (Expr (Nub (Indentation ': v)) a)
- data NextIndent
- equivalentIndentation :: [Whitespace] -> [Whitespace] -> Bool
- runValidateIndentation' :: NextIndent -> [Indent] -> ValidateIndentation e a -> Validation (NonEmpty e) a
- validateArgsIndentation :: AsIndentationError e a => CommaSep (Arg v a) -> ValidateIndentation e (CommaSep (Arg (Nub (Indentation ': v)) a))
- validateBlockIndentation :: forall e v a. AsIndentationError e a => Block v a -> ValidateIndentation e (Block (Nub (Indentation ': v)) a)
- validateCompoundStatementIndentation :: forall e v a. AsIndentationError e a => CompoundStatement v a -> ValidateIndentation e (CompoundStatement (Nub (Indentation ': v)) a)
- validateDecoratorIndentation :: AsIndentationError e a => Decorator v a -> ValidateIndentation e (Decorator (Nub (Indentation ': v)) a)
- validateExceptAsIndentation :: AsIndentationError e a => ExceptAs v a -> ValidateIndentation e (ExceptAs (Nub (Indentation ': v)) a)
- validateParamsIndentation :: AsIndentationError e a => CommaSep (Param v a) -> ValidateIndentation e (CommaSep (Param (Nub (Indentation ': v)) a))
- validateSuiteIndentation :: AsIndentationError e a => Indents a -> Suite v a -> ValidateIndentation e (Suite (Nub (Indentation ': v)) a)
Documentation
Main validation functions
data Indentation Source #
type ValidateIndentation e = ValidateM (NonEmpty e) (State (NextIndent, [Indent])) Source #
runValidateIndentation :: ValidateIndentation e a -> Validation (NonEmpty e) a Source #
validateModuleIndentation :: AsIndentationError e a => Module v a -> ValidateIndentation e (Module (Nub (Indentation ': v)) a) Source #
validateStatementIndentation :: AsIndentationError e a => Statement v a -> ValidateIndentation e (Statement (Nub (Indentation ': v)) a) Source #
validateExprIndentation :: AsIndentationError e a => Expr v a -> ValidateIndentation e (Expr (Nub (Indentation ': v)) a) Source #
Miscellany
Extra types
data NextIndent Source #
"The next line must be..."
Instances
Eq NextIndent Source # | |
Defined in Language.Python.Validate.Indentation (==) :: NextIndent -> NextIndent -> Bool # (/=) :: NextIndent -> NextIndent -> Bool # | |
Show NextIndent Source # | |
Defined in Language.Python.Validate.Indentation showsPrec :: Int -> NextIndent -> ShowS # show :: NextIndent -> String # showList :: [NextIndent] -> ShowS # |
Extra functions
equivalentIndentation :: [Whitespace] -> [Whitespace] -> Bool Source #
runValidateIndentation' :: NextIndent -> [Indent] -> ValidateIndentation e a -> Validation (NonEmpty e) a Source #
Validation functions
validateArgsIndentation :: AsIndentationError e a => CommaSep (Arg v a) -> ValidateIndentation e (CommaSep (Arg (Nub (Indentation ': v)) a)) Source #
validateBlockIndentation :: forall e v a. AsIndentationError e a => Block v a -> ValidateIndentation e (Block (Nub (Indentation ': v)) a) Source #
validateCompoundStatementIndentation :: forall e v a. AsIndentationError e a => CompoundStatement v a -> ValidateIndentation e (CompoundStatement (Nub (Indentation ': v)) a) Source #
validateDecoratorIndentation :: AsIndentationError e a => Decorator v a -> ValidateIndentation e (Decorator (Nub (Indentation ': v)) a) Source #
validateExceptAsIndentation :: AsIndentationError e a => ExceptAs v a -> ValidateIndentation e (ExceptAs (Nub (Indentation ': v)) a) Source #
validateParamsIndentation :: AsIndentationError e a => CommaSep (Param v a) -> ValidateIndentation e (CommaSep (Param (Nub (Indentation ': v)) a)) Source #
validateSuiteIndentation :: AsIndentationError e a => Indents a -> Suite v a -> ValidateIndentation e (Suite (Nub (Indentation ': v)) a) Source #