ShellCheck-0.7.1: Shell script analysis tool

Safe HaskellNone
LanguageHaskell98

ShellCheck.Interface

Documentation

data CheckSpec Source #

Instances
Eq CheckSpec Source # 
Instance details

Defined in ShellCheck.Interface

Show CheckSpec Source # 
Instance details

Defined in ShellCheck.Interface

data ParseSpec Source #

Instances
Eq ParseSpec Source # 
Instance details

Defined in ShellCheck.Interface

Show ParseSpec Source # 
Instance details

Defined in ShellCheck.Interface

data Shell Source #

Constructors

Ksh 
Sh 
Bash 
Dash 
Instances
Eq Shell Source # 
Instance details

Defined in ShellCheck.Interface

Methods

(==) :: Shell -> Shell -> Bool #

(/=) :: Shell -> Shell -> Bool #

Show Shell Source # 
Instance details

Defined in ShellCheck.Interface

Methods

showsPrec :: Int -> Shell -> ShowS #

show :: Shell -> String #

showList :: [Shell] -> ShowS #

data Severity Source #

Constructors

ErrorC 
WarningC 
InfoC 
StyleC 
Instances
Eq Severity Source # 
Instance details

Defined in ShellCheck.Interface

Ord Severity Source # 
Instance details

Defined in ShellCheck.Interface

Show Severity Source # 
Instance details

Defined in ShellCheck.Interface

Generic Severity Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep Severity :: Type -> Type #

Methods

from :: Severity -> Rep Severity x #

to :: Rep Severity x -> Severity #

NFData Severity Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: Severity -> () #

type Rep Severity Source # 
Instance details

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)))

data Position Source #

Instances
Eq Position Source # 
Instance details

Defined in ShellCheck.Interface

Ord Position Source # 
Instance details

Defined in ShellCheck.Interface

Show Position Source # 
Instance details

Defined in ShellCheck.Interface

Generic Position Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep Position :: Type -> Type #

Methods

from :: Position -> Rep Position x #

to :: Rep Position x -> Position #

NFData Position Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: Position -> () #

type Rep Position Source # 
Instance details

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))))

data Comment Source #

Instances
Eq Comment Source # 
Instance details

Defined in ShellCheck.Interface

Methods

(==) :: Comment -> Comment -> Bool #

(/=) :: Comment -> Comment -> Bool #

Show Comment Source # 
Instance details

Defined in ShellCheck.Interface

Generic Comment Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep Comment :: Type -> Type #

Methods

from :: Comment -> Rep Comment x #

to :: Rep Comment x -> Comment #

NFData Comment Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: Comment -> () #

type Rep Comment Source # 
Instance details

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
Eq PositionedComment Source # 
Instance details

Defined in ShellCheck.Interface

Show PositionedComment Source # 
Instance details

Defined in ShellCheck.Interface

Generic PositionedComment Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep PositionedComment :: Type -> Type #

ToJSON PositionedComment Source # 
Instance details

Defined in ShellCheck.Formatter.JSON1

ToJSON PositionedComment Source # 
Instance details

Defined in ShellCheck.Formatter.JSON

NFData PositionedComment Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: PositionedComment -> () #

Ranged PositionedComment Source # 
Instance details

Defined in ShellCheck.Fixer

type Rep PositionedComment Source # 
Instance details

Defined in ShellCheck.Interface

data TokenComment Source #

Instances
Eq TokenComment Source # 
Instance details

Defined in ShellCheck.Interface

Show TokenComment Source # 
Instance details

Defined in ShellCheck.Interface

Generic TokenComment Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep TokenComment :: Type -> Type #

NFData TokenComment Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: TokenComment -> () #

type Rep TokenComment Source # 
Instance details

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)))))

data Fix Source #

Instances
Eq Fix Source # 
Instance details

Defined in ShellCheck.Interface

Methods

(==) :: Fix -> Fix -> Bool #

(/=) :: Fix -> Fix -> Bool #

Show Fix Source # 
Instance details

Defined in ShellCheck.Interface

Methods

showsPrec :: Int -> Fix -> ShowS #

show :: Fix -> String #

showList :: [Fix] -> ShowS #

Generic Fix Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep Fix :: Type -> Type #

Methods

from :: Fix -> Rep Fix x #

to :: Rep Fix x -> Fix #

Semigroup Fix Source # 
Instance details

Defined in ShellCheck.Fixer

Methods

(<>) :: Fix -> Fix -> Fix #

sconcat :: NonEmpty Fix -> Fix #

stimes :: Integral b => b -> Fix -> Fix #

Monoid Fix Source # 
Instance details

Defined in ShellCheck.Fixer

Methods

mempty :: Fix #

mappend :: Fix -> Fix -> Fix #

mconcat :: [Fix] -> Fix #

ToJSON Fix Source # 
Instance details

Defined in ShellCheck.Formatter.JSON1

ToJSON Fix Source # 
Instance details

Defined in ShellCheck.Formatter.JSON

NFData Fix Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: Fix -> () #

type Rep Fix Source # 
Instance details

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 # 
Instance details

Defined in ShellCheck.Interface

Show InsertionPoint Source # 
Instance details

Defined in ShellCheck.Interface

Generic InsertionPoint Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep InsertionPoint :: Type -> Type #

NFData InsertionPoint Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: InsertionPoint -> () #

type Rep InsertionPoint Source # 
Instance details

Defined in ShellCheck.Interface

type Rep InsertionPoint = D1 (MetaData "InsertionPoint" "ShellCheck.Interface" "ShellCheck-0.7.1-K8zDXki0F9s514UhOMMhhH" False) (C1 (MetaCons "InsertBefore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InsertAfter" PrefixI False) (U1 :: Type -> Type))

data Replacement Source #

Instances
Eq Replacement Source # 
Instance details

Defined in ShellCheck.Interface

Show Replacement Source # 
Instance details

Defined in ShellCheck.Interface

Generic Replacement Source # 
Instance details

Defined in ShellCheck.Interface

Associated Types

type Rep Replacement :: Type -> Type #

ToJSON Replacement Source # 
Instance details

Defined in ShellCheck.Formatter.JSON1

ToJSON Replacement Source # 
Instance details

Defined in ShellCheck.Formatter.JSON

NFData Replacement Source # 
Instance details

Defined in ShellCheck.Interface

Methods

rnf :: Replacement -> () #

Ranged Replacement Source # 
Instance details

Defined in ShellCheck.Fixer

type Rep Replacement Source # 
Instance details

Defined in ShellCheck.Interface