| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
ShellCheck.Interface
Documentation
data SystemInterface m Source #
Constructors
| SystemInterface | |
Fields
| |
data CheckResult Source #
Instances
| Eq CheckResult Source # | |
Defined in ShellCheck.Interface | |
| Show CheckResult Source # | |
Defined in ShellCheck.Interface Methods showsPrec :: Int -> CheckResult -> ShowS # show :: CheckResult -> String # showList :: [CheckResult] -> ShowS # | |
data ParseResult Source #
Instances
| Eq ParseResult Source # | |
Defined in ShellCheck.Interface | |
| Show ParseResult Source # | |
Defined in ShellCheck.Interface Methods showsPrec :: Int -> ParseResult -> ShowS # show :: ParseResult -> String # showList :: [ParseResult] -> ShowS # | |
data AnalysisSpec Source #
data AnalysisResult Source #
data FormatterOptions Source #
data ExecutionMode Source #
Instances
| Eq ExecutionMode Source # | |
Defined in ShellCheck.Interface Methods (==) :: ExecutionMode -> ExecutionMode -> Bool # (/=) :: ExecutionMode -> ExecutionMode -> Bool # | |
| Show ExecutionMode Source # | |
Defined in ShellCheck.Interface Methods showsPrec :: Int -> ExecutionMode -> ShowS # show :: ExecutionMode -> String # showList :: [ExecutionMode] -> ShowS # | |
type ErrorMessage = String Source #
Instances
| Eq Severity Source # | |
| Ord Severity Source # | |
Defined in ShellCheck.Interface | |
| Show Severity Source # | |
| Generic Severity Source # | |
| NFData Severity Source # | |
Defined in ShellCheck.Interface | |
| type Rep Severity Source # | |
Defined in ShellCheck.Interface type Rep Severity = D1 (MetaData "Severity" "ShellCheck.Interface" "ShellCheck-0.7.1-K8zDXki0F9s514UhOMMhhH" False) ((C1 (MetaCons "ErrorC" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WarningC" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "InfoC" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StyleC" PrefixI False) (U1 :: Type -> Type))) | |
Instances
| Eq Position Source # | |
| Ord Position Source # | |
Defined in ShellCheck.Interface | |
| Show Position Source # | |
| Generic Position Source # | |
| NFData Position Source # | |
Defined in ShellCheck.Interface | |
| type Rep Position Source # | |
Defined in ShellCheck.Interface type Rep Position = D1 (MetaData "Position" "ShellCheck.Interface" "ShellCheck-0.7.1-K8zDXki0F9s514UhOMMhhH" False) (C1 (MetaCons "Position" PrefixI True) (S1 (MetaSel (Just "posFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "posLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Just "posColumn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))) | |
Instances
| Eq Comment Source # | |
| Show Comment Source # | |
| Generic Comment Source # | |
| NFData Comment Source # | |
Defined in ShellCheck.Interface | |
| type Rep Comment Source # | |
Defined in ShellCheck.Interface type Rep Comment = D1 (MetaData "Comment" "ShellCheck.Interface" "ShellCheck-0.7.1-K8zDXki0F9s514UhOMMhhH" False) (C1 (MetaCons "Comment" PrefixI True) (S1 (MetaSel (Just "cSeverity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Severity) :*: (S1 (MetaSel (Just "cCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Code) :*: S1 (MetaSel (Just "cMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) | |
data PositionedComment Source #
Instances
data ColorOption Source #
Constructors
| ColorAuto | |
| ColorAlways | |
| ColorNever |
Instances
| Eq ColorOption Source # | |
Defined in ShellCheck.Interface | |
| Ord ColorOption Source # | |
Defined in ShellCheck.Interface Methods compare :: ColorOption -> ColorOption -> Ordering # (<) :: ColorOption -> ColorOption -> Bool # (<=) :: ColorOption -> ColorOption -> Bool # (>) :: ColorOption -> ColorOption -> Bool # (>=) :: ColorOption -> ColorOption -> Bool # max :: ColorOption -> ColorOption -> ColorOption # min :: ColorOption -> ColorOption -> ColorOption # | |
| Show ColorOption Source # | |
Defined in ShellCheck.Interface Methods showsPrec :: Int -> ColorOption -> ShowS # show :: ColorOption -> String # showList :: [ColorOption] -> ShowS # | |
data TokenComment Source #
Instances
| Eq TokenComment Source # | |
Defined in ShellCheck.Interface | |
| Show TokenComment Source # | |
Defined in ShellCheck.Interface Methods showsPrec :: Int -> TokenComment -> ShowS # show :: TokenComment -> String # showList :: [TokenComment] -> ShowS # | |
| Generic TokenComment Source # | |
Defined in ShellCheck.Interface Associated Types type Rep TokenComment :: Type -> Type # | |
| NFData TokenComment Source # | |
Defined in ShellCheck.Interface Methods rnf :: TokenComment -> () # | |
| type Rep TokenComment Source # | |
Defined in ShellCheck.Interface type Rep TokenComment = D1 (MetaData "TokenComment" "ShellCheck.Interface" "ShellCheck-0.7.1-K8zDXki0F9s514UhOMMhhH" False) (C1 (MetaCons "TokenComment" PrefixI True) (S1 (MetaSel (Just "tcId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Id) :*: (S1 (MetaSel (Just "tcComment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Comment) :*: S1 (MetaSel (Just "tcFix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Fix))))) | |
newAnalysisSpec :: Token -> AnalysisSpec Source #
mockedSystemInterface :: [(String, String)] -> SystemInterface Identity Source #
mockRcFile :: Monad m => String -> SystemInterface m -> SystemInterface m Source #
newComment :: Comment Source #
Instances
| Eq Fix Source # | |
| Show Fix Source # | |
| Generic Fix Source # | |
| Semigroup Fix Source # | |
| Monoid Fix Source # | |
| ToJSON Fix Source # | |
Defined in ShellCheck.Formatter.JSON1 | |
| ToJSON Fix Source # | |
Defined in ShellCheck.Formatter.JSON | |
| NFData Fix Source # | |
Defined in ShellCheck.Interface | |
| type Rep Fix Source # | |
Defined in ShellCheck.Interface type Rep Fix = D1 (MetaData "Fix" "ShellCheck.Interface" "ShellCheck-0.7.1-K8zDXki0F9s514UhOMMhhH" False) (C1 (MetaCons "Fix" PrefixI True) (S1 (MetaSel (Just "fixReplacements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Replacement]))) | |
data InsertionPoint Source #
Constructors
| InsertBefore | |
| InsertAfter |
Instances
| Eq InsertionPoint Source # | |
Defined in ShellCheck.Interface Methods (==) :: InsertionPoint -> InsertionPoint -> Bool # (/=) :: InsertionPoint -> InsertionPoint -> Bool # | |
| Show InsertionPoint Source # | |
Defined in ShellCheck.Interface Methods showsPrec :: Int -> InsertionPoint -> ShowS # show :: InsertionPoint -> String # showList :: [InsertionPoint] -> ShowS # | |
| Generic InsertionPoint Source # | |
Defined in ShellCheck.Interface Associated Types type Rep InsertionPoint :: Type -> Type # Methods from :: InsertionPoint -> Rep InsertionPoint x # to :: Rep InsertionPoint x -> InsertionPoint # | |
| NFData InsertionPoint Source # | |
Defined in ShellCheck.Interface Methods rnf :: InsertionPoint -> () # | |
| type Rep InsertionPoint Source # | |
data Replacement Source #
Instances
data CheckDescription Source #