Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Severity
- data Qualification
- data ModuleAliases
- data NamesList
- data ImportRule = ImportRule {}
- data QualificationStyle
- data ImportRules = ImportRules {
- rules :: [ImportRule]
- severity :: Severity
- data Ban = Ban {}
- data ImportsStyle = ImportsStyle {}
- newtype ModuleName = ModuleName String
Documentation
Report either error or warning during compilation
data Qualification Source #
Instances
FromJSON Qualification Source # | |
Defined in ImportStylePlugin.Config parseJSON :: Value -> Parser Qualification # parseJSONList :: Value -> Parser [Qualification] # | |
Generic Qualification Source # | |
Defined in ImportStylePlugin.Config type Rep Qualification :: Type -> Type # from :: Qualification -> Rep Qualification x # to :: Rep Qualification x -> Qualification # | |
Show Qualification Source # | |
Defined in ImportStylePlugin.Config showsPrec :: Int -> Qualification -> ShowS # show :: Qualification -> String # showList :: [Qualification] -> ShowS # | |
type Rep Qualification Source # | |
Defined in ImportStylePlugin.Config |
data ModuleAliases Source #
Instances
FromJSON ModuleAliases Source # | |
Defined in ImportStylePlugin.Config parseJSON :: Value -> Parser ModuleAliases # parseJSONList :: Value -> Parser [ModuleAliases] # | |
Show ModuleAliases Source # | |
Defined in ImportStylePlugin.Config showsPrec :: Int -> ModuleAliases -> ShowS # show :: ModuleAliases -> String # showList :: [ModuleAliases] -> ShowS # |
data ImportRule Source #
ImportRule | |
|
Instances
data QualificationStyle Source #
Instances
FromJSON QualificationStyle Source # | |
Defined in ImportStylePlugin.Config | |
Generic QualificationStyle Source # | |
Defined in ImportStylePlugin.Config type Rep QualificationStyle :: Type -> Type # from :: QualificationStyle -> Rep QualificationStyle x # to :: Rep QualificationStyle x -> QualificationStyle # | |
Show QualificationStyle Source # | |
Defined in ImportStylePlugin.Config showsPrec :: Int -> QualificationStyle -> ShowS # show :: QualificationStyle -> String # showList :: [QualificationStyle] -> ShowS # | |
type Rep QualificationStyle Source # | |
Defined in ImportStylePlugin.Config |
data ImportRules Source #
ImportRules | |
|
Instances
FromJSON ImportRules Source # | |
Defined in ImportStylePlugin.Config parseJSON :: Value -> Parser ImportRules # parseJSONList :: Value -> Parser [ImportRules] # | |
Generic ImportRules Source # | |
Defined in ImportStylePlugin.Config type Rep ImportRules :: Type -> Type # from :: ImportRules -> Rep ImportRules x # to :: Rep ImportRules x -> ImportRules # | |
Show ImportRules Source # | |
Defined in ImportStylePlugin.Config showsPrec :: Int -> ImportRules -> ShowS # show :: ImportRules -> String # showList :: [ImportRules] -> ShowS # | |
type Rep ImportRules Source # | |
Defined in ImportStylePlugin.Config type Rep ImportRules = D1 ('MetaData "ImportRules" "ImportStylePlugin.Config" "import-style-plugin-0.1.0.0-3mKWth6FJwSHdIC44LJva5" 'False) (C1 ('MetaCons "ImportRules" 'PrefixI 'True) (S1 ('MetaSel ('Just "rules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ImportRule]) :*: S1 ('MetaSel ('Just "severity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Severity))) |
Instances
FromJSON Ban Source # | |
Defined in ImportStylePlugin.Config | |
Generic Ban Source # | |
Show Ban Source # | |
type Rep Ban Source # | |
Defined in ImportStylePlugin.Config type Rep Ban = D1 ('MetaData "Ban" "ImportStylePlugin.Config" "import-style-plugin-0.1.0.0-3mKWth6FJwSHdIC44LJva5" 'False) (C1 ('MetaCons "Ban" 'PrefixI 'True) (S1 ('MetaSel ('Just "severity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Severity) :*: S1 ('MetaSel ('Just "why") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
data ImportsStyle Source #
ImportsStyle | |
|
Instances
newtype ModuleName Source #
Instances
FromJSONKey ModuleName Source # | |
IsString ModuleName Source # | |
Defined in ImportStylePlugin.Config fromString :: String -> ModuleName # | |
Show ModuleName Source # | |
Defined in ImportStylePlugin.Config showsPrec :: Int -> ModuleName -> ShowS # show :: ModuleName -> String # showList :: [ModuleName] -> ShowS # | |
Eq ModuleName Source # | |
Defined in ImportStylePlugin.Config (==) :: ModuleName -> ModuleName -> Bool # (/=) :: ModuleName -> ModuleName -> Bool # | |
Ord ModuleName Source # | |
Defined in ImportStylePlugin.Config compare :: ModuleName -> ModuleName -> Ordering # (<) :: ModuleName -> ModuleName -> Bool # (<=) :: ModuleName -> ModuleName -> Bool # (>) :: ModuleName -> ModuleName -> Bool # (>=) :: ModuleName -> ModuleName -> Bool # max :: ModuleName -> ModuleName -> ModuleName # min :: ModuleName -> ModuleName -> ModuleName # |