| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell98 |
ShellCheck.AST
Documentation
data AssignmentMode Source #
Instances
| Show AssignmentMode Source # | |
Defined in ShellCheck.AST Methods showsPrec :: Int -> AssignmentMode -> ShowS # show :: AssignmentMode -> String # showList :: [AssignmentMode] -> ShowS # | |
| Eq AssignmentMode Source # | |
Defined in ShellCheck.AST Methods (==) :: AssignmentMode -> AssignmentMode -> Bool # (/=) :: AssignmentMode -> AssignmentMode -> Bool # | |
newtype FunctionKeyword Source #
Constructors
| FunctionKeyword Bool |
Instances
| Show FunctionKeyword Source # | |
Defined in ShellCheck.AST Methods showsPrec :: Int -> FunctionKeyword -> ShowS # show :: FunctionKeyword -> String # showList :: [FunctionKeyword] -> ShowS # | |
| Eq FunctionKeyword Source # | |
Defined in ShellCheck.AST Methods (==) :: FunctionKeyword -> FunctionKeyword -> Bool # (/=) :: FunctionKeyword -> FunctionKeyword -> Bool # | |
newtype FunctionParentheses Source #
Constructors
| FunctionParentheses Bool |
Instances
| Show FunctionParentheses Source # | |
Defined in ShellCheck.AST Methods showsPrec :: Int -> FunctionParentheses -> ShowS # show :: FunctionParentheses -> String # showList :: [FunctionParentheses] -> ShowS # | |
| Eq FunctionParentheses Source # | |
Defined in ShellCheck.AST Methods (==) :: FunctionParentheses -> FunctionParentheses -> Bool # (/=) :: FunctionParentheses -> FunctionParentheses -> Bool # | |
Constructors
| CaseBreak | |
| CaseFallThrough | |
| CaseContinue |
Constructors
| OuterToken Id (InnerToken Token) |
data InnerToken t Source #
Constructors
Instances
data Annotation Source #
Constructors
| DisableComment Integer Integer | |
| EnableComment String | |
| SourceOverride String | |
| ShellOverride String | |
| SourcePath String | |
| ExternalSources Bool |
Instances
| Show Annotation Source # | |
Defined in ShellCheck.AST Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
| Eq Annotation Source # | |
Defined in ShellCheck.AST | |
data ConditionType Source #
Constructors
| DoubleBracket | |
| SingleBracket |
Instances
| Show ConditionType Source # | |
Defined in ShellCheck.AST Methods showsPrec :: Int -> ConditionType -> ShowS # show :: ConditionType -> String # showList :: [ConditionType] -> ShowS # | |
| Eq ConditionType Source # | |
Defined in ShellCheck.AST Methods (==) :: ConditionType -> ConditionType -> Bool # (/=) :: ConditionType -> ConditionType -> Bool # | |
pattern T_DLESSDASH :: Id -> Token Source #
pattern T_GREATAND :: Id -> Token Source #
pattern T_LESSGREAT :: Id -> Token Source #
pattern T_Annotation :: Id -> [Annotation] -> Token -> Token Source #
pattern T_Assignment :: Id -> AssignmentMode -> String -> [Token] -> Token -> Token Source #
pattern TC_Nullary :: Id -> ConditionType -> Token -> Token Source #
pattern T_Condition :: Id -> ConditionType -> Token -> Token Source #
pattern T_Function :: Id -> FunctionKeyword -> FunctionParentheses -> String -> Token -> Token Source #