{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
module Config.Type(
Severity(..), Classify(..), HintRule(..), Note(..), Setting(..),
Restrict(..), RestrictType(..), RestrictIdents(..), SmellType(..),
RestrictImportStyle(..), QualifiedStyle(..),
defaultHintName, isUnifyVar, showNotes, getSeverity, getRestrictType, getSmellType
) where
import Data.Char
import Data.List.Extra
import Data.Monoid
import Prelude
import GHC.Hs qualified
import Fixity
import GHC.Util
import Language.Haskell.GhclibParserEx.GHC.Hs.ExtendInstances
import Deriving.Aeson
import System.Console.CmdArgs.Implicit
import Data.Aeson hiding (Error)
getSeverity :: String -> Maybe Severity
getSeverity :: String -> Maybe Severity
getSeverity String
"ignore" = Severity -> Maybe Severity
forall a. a -> Maybe a
Just Severity
Ignore
getSeverity String
"warn" = Severity -> Maybe Severity
forall a. a -> Maybe a
Just Severity
Warning
getSeverity String
"warning" = Severity -> Maybe Severity
forall a. a -> Maybe a
Just Severity
Warning
getSeverity String
"suggest" = Severity -> Maybe Severity
forall a. a -> Maybe a
Just Severity
Suggestion
getSeverity String
"suggestion" = Severity -> Maybe Severity
forall a. a -> Maybe a
Just Severity
Suggestion
getSeverity String
"error" = Severity -> Maybe Severity
forall a. a -> Maybe a
Just Severity
Error
getSeverity String
"hint" = Severity -> Maybe Severity
forall a. a -> Maybe a
Just Severity
Suggestion
getSeverity String
_ = Maybe Severity
forall a. Maybe a
Nothing
getRestrictType :: String -> Maybe RestrictType
getRestrictType :: String -> Maybe RestrictType
getRestrictType String
"modules" = RestrictType -> Maybe RestrictType
forall a. a -> Maybe a
Just RestrictType
RestrictModule
getRestrictType String
"extensions" = RestrictType -> Maybe RestrictType
forall a. a -> Maybe a
Just RestrictType
RestrictExtension
getRestrictType String
"flags" = RestrictType -> Maybe RestrictType
forall a. a -> Maybe a
Just RestrictType
RestrictFlag
getRestrictType String
"functions" = RestrictType -> Maybe RestrictType
forall a. a -> Maybe a
Just RestrictType
RestrictFunction
getRestrictType String
_ = Maybe RestrictType
forall a. Maybe a
Nothing
defaultHintName :: String
defaultHintName :: String
defaultHintName = String
"Use alternative"
data Severity
= Ignore
| Suggestion
| Warning
| Error
deriving (Severity -> Severity -> Bool
(Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool) -> Eq Severity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Severity -> Severity -> Bool
== :: Severity -> Severity -> Bool
$c/= :: Severity -> Severity -> Bool
/= :: Severity -> Severity -> Bool
Eq,Eq Severity
Eq Severity =>
(Severity -> Severity -> Ordering)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Bool)
-> (Severity -> Severity -> Severity)
-> (Severity -> Severity -> Severity)
-> Ord Severity
Severity -> Severity -> Bool
Severity -> Severity -> Ordering
Severity -> Severity -> Severity
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Severity -> Severity -> Ordering
compare :: Severity -> Severity -> Ordering
$c< :: Severity -> Severity -> Bool
< :: Severity -> Severity -> Bool
$c<= :: Severity -> Severity -> Bool
<= :: Severity -> Severity -> Bool
$c> :: Severity -> Severity -> Bool
> :: Severity -> Severity -> Bool
$c>= :: Severity -> Severity -> Bool
>= :: Severity -> Severity -> Bool
$cmax :: Severity -> Severity -> Severity
max :: Severity -> Severity -> Severity
$cmin :: Severity -> Severity -> Severity
min :: Severity -> Severity -> Severity
Ord,Int -> Severity -> ShowS
[Severity] -> ShowS
Severity -> String
(Int -> Severity -> ShowS)
-> (Severity -> String) -> ([Severity] -> ShowS) -> Show Severity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Severity -> ShowS
showsPrec :: Int -> Severity -> ShowS
$cshow :: Severity -> String
show :: Severity -> String
$cshowList :: [Severity] -> ShowS
showList :: [Severity] -> ShowS
Show,ReadPrec [Severity]
ReadPrec Severity
Int -> ReadS Severity
ReadS [Severity]
(Int -> ReadS Severity)
-> ReadS [Severity]
-> ReadPrec Severity
-> ReadPrec [Severity]
-> Read Severity
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Severity
readsPrec :: Int -> ReadS Severity
$creadList :: ReadS [Severity]
readList :: ReadS [Severity]
$creadPrec :: ReadPrec Severity
readPrec :: ReadPrec Severity
$creadListPrec :: ReadPrec [Severity]
readListPrec :: ReadPrec [Severity]
Read,Severity
Severity -> Severity -> Bounded Severity
forall a. a -> a -> Bounded a
$cminBound :: Severity
minBound :: Severity
$cmaxBound :: Severity
maxBound :: Severity
Bounded,Int -> Severity
Severity -> Int
Severity -> [Severity]
Severity -> Severity
Severity -> Severity -> [Severity]
Severity -> Severity -> Severity -> [Severity]
(Severity -> Severity)
-> (Severity -> Severity)
-> (Int -> Severity)
-> (Severity -> Int)
-> (Severity -> [Severity])
-> (Severity -> Severity -> [Severity])
-> (Severity -> Severity -> [Severity])
-> (Severity -> Severity -> Severity -> [Severity])
-> Enum Severity
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Severity -> Severity
succ :: Severity -> Severity
$cpred :: Severity -> Severity
pred :: Severity -> Severity
$ctoEnum :: Int -> Severity
toEnum :: Int -> Severity
$cfromEnum :: Severity -> Int
fromEnum :: Severity -> Int
$cenumFrom :: Severity -> [Severity]
enumFrom :: Severity -> [Severity]
$cenumFromThen :: Severity -> Severity -> [Severity]
enumFromThen :: Severity -> Severity -> [Severity]
$cenumFromTo :: Severity -> Severity -> [Severity]
enumFromTo :: Severity -> Severity -> [Severity]
$cenumFromThenTo :: Severity -> Severity -> Severity -> [Severity]
enumFromThenTo :: Severity -> Severity -> Severity -> [Severity]
Enum,(forall x. Severity -> Rep Severity x)
-> (forall x. Rep Severity x -> Severity) -> Generic Severity
forall x. Rep Severity x -> Severity
forall x. Severity -> Rep Severity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Severity -> Rep Severity x
from :: forall x. Severity -> Rep Severity x
$cto :: forall x. Rep Severity x -> Severity
to :: forall x. Rep Severity x -> Severity
Generic,Typeable Severity
Typeable Severity =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Severity -> c Severity)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Severity)
-> (Severity -> Constr)
-> (Severity -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Severity))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Severity))
-> ((forall b. Data b => b -> b) -> Severity -> Severity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r)
-> (forall u. (forall d. Data d => d -> u) -> Severity -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Severity -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity)
-> Data Severity
Severity -> Constr
Severity -> DataType
(forall b. Data b => b -> b) -> Severity -> Severity
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Severity -> u
forall u. (forall d. Data d => d -> u) -> Severity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Severity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Severity -> c Severity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Severity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Severity)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Severity -> c Severity
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Severity -> c Severity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Severity
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Severity
$ctoConstr :: Severity -> Constr
toConstr :: Severity -> Constr
$cdataTypeOf :: Severity -> DataType
dataTypeOf :: Severity -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Severity)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Severity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Severity)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Severity)
$cgmapT :: (forall b. Data b => b -> b) -> Severity -> Severity
gmapT :: (forall b. Data b => b -> b) -> Severity -> Severity
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Severity -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Severity -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Severity -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Severity -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Severity -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Severity -> m Severity
Data)
deriving ([Severity] -> Value
[Severity] -> Encoding
Severity -> Bool
Severity -> Value
Severity -> Encoding
(Severity -> Value)
-> (Severity -> Encoding)
-> ([Severity] -> Value)
-> ([Severity] -> Encoding)
-> (Severity -> Bool)
-> ToJSON Severity
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Severity -> Value
toJSON :: Severity -> Value
$ctoEncoding :: Severity -> Encoding
toEncoding :: Severity -> Encoding
$ctoJSONList :: [Severity] -> Value
toJSONList :: [Severity] -> Value
$ctoEncodingList :: [Severity] -> Encoding
toEncodingList :: [Severity] -> Encoding
$comitField :: Severity -> Bool
omitField :: Severity -> Bool
ToJSON) via CustomJSON '[FieldLabelModifier CamelToSnake] Severity
isUnifyVar :: String -> Bool
isUnifyVar :: String -> Bool
isUnifyVar [Char
x] = Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'?' Bool -> Bool -> Bool
|| Char -> Bool
isAlpha Char
x
isUnifyVar [] = Bool
False
isUnifyVar String
xs = (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'?') String
xs
data Note
= IncreasesLaziness
| DecreasesLaziness
| RemovesError String
| ValidInstance String String
| RequiresExtension String
| Note String
deriving (Note -> Note -> Bool
(Note -> Note -> Bool) -> (Note -> Note -> Bool) -> Eq Note
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Note -> Note -> Bool
== :: Note -> Note -> Bool
$c/= :: Note -> Note -> Bool
/= :: Note -> Note -> Bool
Eq,Eq Note
Eq Note =>
(Note -> Note -> Ordering)
-> (Note -> Note -> Bool)
-> (Note -> Note -> Bool)
-> (Note -> Note -> Bool)
-> (Note -> Note -> Bool)
-> (Note -> Note -> Note)
-> (Note -> Note -> Note)
-> Ord Note
Note -> Note -> Bool
Note -> Note -> Ordering
Note -> Note -> Note
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Note -> Note -> Ordering
compare :: Note -> Note -> Ordering
$c< :: Note -> Note -> Bool
< :: Note -> Note -> Bool
$c<= :: Note -> Note -> Bool
<= :: Note -> Note -> Bool
$c> :: Note -> Note -> Bool
> :: Note -> Note -> Bool
$c>= :: Note -> Note -> Bool
>= :: Note -> Note -> Bool
$cmax :: Note -> Note -> Note
max :: Note -> Note -> Note
$cmin :: Note -> Note -> Note
min :: Note -> Note -> Note
Ord)
instance Show Note where
show :: Note -> String
show Note
IncreasesLaziness = String
"increases laziness"
show Note
DecreasesLaziness = String
"decreases laziness"
show (RemovesError String
x) = String
"removes error " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
x
show (ValidInstance String
x String
y) = String
"requires a valid `" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"` instance for `" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
y String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"`"
show (RequiresExtension String
x) = String
"may require `{-# LANGUAGE " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" #-}` adding to the top of the file"
show (Note String
x) = String
x
showNotes :: [Note] -> String
showNotes :: [Note] -> String
showNotes = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ([String] -> String) -> ([Note] -> [String]) -> [Note] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Note -> String) -> [Note] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Note -> String
forall a. Show a => a -> String
show ([Note] -> [String]) -> ([Note] -> [Note]) -> [Note] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Note -> Bool) -> [Note] -> [Note]
forall a. (a -> Bool) -> [a] -> [a]
filter Note -> Bool
use
where use :: Note -> Bool
use ValidInstance{} = Bool
False
use Note
_ = Bool
True
data Classify = Classify
{Classify -> Severity
classifySeverity :: Severity
,Classify -> String
classifyHint :: String
,Classify -> String
classifyModule :: String
,Classify -> String
classifyDecl :: String
}
deriving Int -> Classify -> ShowS
[Classify] -> ShowS
Classify -> String
(Int -> Classify -> ShowS)
-> (Classify -> String) -> ([Classify] -> ShowS) -> Show Classify
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Classify -> ShowS
showsPrec :: Int -> Classify -> ShowS
$cshow :: Classify -> String
show :: Classify -> String
$cshowList :: [Classify] -> ShowS
showList :: [Classify] -> ShowS
Show
data HintRule = HintRule
{HintRule -> Severity
hintRuleSeverity :: Severity
,HintRule -> String
hintRuleName :: String
,HintRule -> [Note]
hintRuleNotes :: [Note]
,HintRule -> Scope
hintRuleScope :: Scope
,HintRule -> HsExtendInstances (LHsExpr GhcPs)
hintRuleLHS :: HsExtendInstances (GHC.Hs.LHsExpr GHC.Hs.GhcPs)
,HintRule -> HsExtendInstances (LHsExpr GhcPs)
hintRuleRHS :: HsExtendInstances (GHC.Hs.LHsExpr GHC.Hs.GhcPs)
,HintRule -> Maybe (HsExtendInstances (LHsExpr GhcPs))
hintRuleSide :: Maybe (HsExtendInstances (GHC.Hs.LHsExpr GHC.Hs.GhcPs))
}
deriving Int -> HintRule -> ShowS
[HintRule] -> ShowS
HintRule -> String
(Int -> HintRule -> ShowS)
-> (HintRule -> String) -> ([HintRule] -> ShowS) -> Show HintRule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HintRule -> ShowS
showsPrec :: Int -> HintRule -> ShowS
$cshow :: HintRule -> String
show :: HintRule -> String
$cshowList :: [HintRule] -> ShowS
showList :: [HintRule] -> ShowS
Show
instance ToJSON HintRule where
toJSON :: HintRule -> Value
toJSON HintRule{String
[Note]
Maybe (HsExtendInstances (LHsExpr GhcPs))
HsExtendInstances (LHsExpr GhcPs)
Scope
Severity
hintRuleSeverity :: HintRule -> Severity
hintRuleName :: HintRule -> String
hintRuleNotes :: HintRule -> [Note]
hintRuleScope :: HintRule -> Scope
hintRuleLHS :: HintRule -> HsExtendInstances (LHsExpr GhcPs)
hintRuleRHS :: HintRule -> HsExtendInstances (LHsExpr GhcPs)
hintRuleSide :: HintRule -> Maybe (HsExtendInstances (LHsExpr GhcPs))
hintRuleSeverity :: Severity
hintRuleName :: String
hintRuleNotes :: [Note]
hintRuleScope :: Scope
hintRuleLHS :: HsExtendInstances (LHsExpr GhcPs)
hintRuleRHS :: HsExtendInstances (LHsExpr GhcPs)
hintRuleSide :: Maybe (HsExtendInstances (LHsExpr GhcPs))
..} = [Pair] -> Value
object
[ Key
"name" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= String
hintRuleName
, Key
"lhs" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= HsExtendInstances (GenLocated SrcSpanAnnA (HsExpr GhcPs)) -> String
forall a. Show a => a -> String
show HsExtendInstances (LHsExpr GhcPs)
HsExtendInstances (GenLocated SrcSpanAnnA (HsExpr GhcPs))
hintRuleLHS
, Key
"rhs" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= HsExtendInstances (GenLocated SrcSpanAnnA (HsExpr GhcPs)) -> String
forall a. Show a => a -> String
show HsExtendInstances (LHsExpr GhcPs)
HsExtendInstances (GenLocated SrcSpanAnnA (HsExpr GhcPs))
hintRuleRHS
]
data RestrictType = RestrictModule | RestrictExtension | RestrictFlag | RestrictFunction deriving (Int -> RestrictType -> ShowS
[RestrictType] -> ShowS
RestrictType -> String
(Int -> RestrictType -> ShowS)
-> (RestrictType -> String)
-> ([RestrictType] -> ShowS)
-> Show RestrictType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestrictType -> ShowS
showsPrec :: Int -> RestrictType -> ShowS
$cshow :: RestrictType -> String
show :: RestrictType -> String
$cshowList :: [RestrictType] -> ShowS
showList :: [RestrictType] -> ShowS
Show,RestrictType -> RestrictType -> Bool
(RestrictType -> RestrictType -> Bool)
-> (RestrictType -> RestrictType -> Bool) -> Eq RestrictType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RestrictType -> RestrictType -> Bool
== :: RestrictType -> RestrictType -> Bool
$c/= :: RestrictType -> RestrictType -> Bool
/= :: RestrictType -> RestrictType -> Bool
Eq,Eq RestrictType
Eq RestrictType =>
(RestrictType -> RestrictType -> Ordering)
-> (RestrictType -> RestrictType -> Bool)
-> (RestrictType -> RestrictType -> Bool)
-> (RestrictType -> RestrictType -> Bool)
-> (RestrictType -> RestrictType -> Bool)
-> (RestrictType -> RestrictType -> RestrictType)
-> (RestrictType -> RestrictType -> RestrictType)
-> Ord RestrictType
RestrictType -> RestrictType -> Bool
RestrictType -> RestrictType -> Ordering
RestrictType -> RestrictType -> RestrictType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RestrictType -> RestrictType -> Ordering
compare :: RestrictType -> RestrictType -> Ordering
$c< :: RestrictType -> RestrictType -> Bool
< :: RestrictType -> RestrictType -> Bool
$c<= :: RestrictType -> RestrictType -> Bool
<= :: RestrictType -> RestrictType -> Bool
$c> :: RestrictType -> RestrictType -> Bool
> :: RestrictType -> RestrictType -> Bool
$c>= :: RestrictType -> RestrictType -> Bool
>= :: RestrictType -> RestrictType -> Bool
$cmax :: RestrictType -> RestrictType -> RestrictType
max :: RestrictType -> RestrictType -> RestrictType
$cmin :: RestrictType -> RestrictType -> RestrictType
min :: RestrictType -> RestrictType -> RestrictType
Ord)
data RestrictIdents
= NoRestrictIdents
| ForbidIdents [String]
| OnlyIdents [String]
deriving Int -> RestrictIdents -> ShowS
[RestrictIdents] -> ShowS
RestrictIdents -> String
(Int -> RestrictIdents -> ShowS)
-> (RestrictIdents -> String)
-> ([RestrictIdents] -> ShowS)
-> Show RestrictIdents
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestrictIdents -> ShowS
showsPrec :: Int -> RestrictIdents -> ShowS
$cshow :: RestrictIdents -> String
show :: RestrictIdents -> String
$cshowList :: [RestrictIdents] -> ShowS
showList :: [RestrictIdents] -> ShowS
Show
instance Semigroup RestrictIdents where
RestrictIdents
NoRestrictIdents <> :: RestrictIdents -> RestrictIdents -> RestrictIdents
<> RestrictIdents
ri = RestrictIdents
ri
RestrictIdents
ri <> RestrictIdents
NoRestrictIdents = RestrictIdents
ri
ForbidIdents [String]
x1 <> ForbidIdents [String]
y1 = [String] -> RestrictIdents
ForbidIdents ([String] -> RestrictIdents) -> [String] -> RestrictIdents
forall a b. (a -> b) -> a -> b
$ [String]
x1 [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
y1
OnlyIdents [String]
x1 <> OnlyIdents [String]
x2 = [String] -> RestrictIdents
OnlyIdents ([String] -> RestrictIdents) -> [String] -> RestrictIdents
forall a b. (a -> b) -> a -> b
$ [String]
x1 [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
x2
RestrictIdents
ri1 <> RestrictIdents
ri2 = String -> RestrictIdents
forall a. HasCallStack => String -> a
error (String -> RestrictIdents) -> String -> RestrictIdents
forall a b. (a -> b) -> a -> b
$ String
"Incompatible restrictions: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (RestrictIdents, RestrictIdents) -> String
forall a. Show a => a -> String
show (RestrictIdents
ri1, RestrictIdents
ri2)
data RestrictImportStyle
= ImportStyleQualified
| ImportStyleUnqualified
| ImportStyleExplicit
| ImportStyleExplicitOrQualified
| ImportStyleUnrestricted
deriving Int -> RestrictImportStyle -> ShowS
[RestrictImportStyle] -> ShowS
RestrictImportStyle -> String
(Int -> RestrictImportStyle -> ShowS)
-> (RestrictImportStyle -> String)
-> ([RestrictImportStyle] -> ShowS)
-> Show RestrictImportStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestrictImportStyle -> ShowS
showsPrec :: Int -> RestrictImportStyle -> ShowS
$cshow :: RestrictImportStyle -> String
show :: RestrictImportStyle -> String
$cshowList :: [RestrictImportStyle] -> ShowS
showList :: [RestrictImportStyle] -> ShowS
Show
data QualifiedStyle
= QualifiedStylePre
| QualifiedStylePost
| QualifiedStyleUnrestricted
deriving Int -> QualifiedStyle -> ShowS
[QualifiedStyle] -> ShowS
QualifiedStyle -> String
(Int -> QualifiedStyle -> ShowS)
-> (QualifiedStyle -> String)
-> ([QualifiedStyle] -> ShowS)
-> Show QualifiedStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QualifiedStyle -> ShowS
showsPrec :: Int -> QualifiedStyle -> ShowS
$cshow :: QualifiedStyle -> String
show :: QualifiedStyle -> String
$cshowList :: [QualifiedStyle] -> ShowS
showList :: [QualifiedStyle] -> ShowS
Show
data Restrict = Restrict
{Restrict -> RestrictType
restrictType :: RestrictType
,Restrict -> Bool
restrictDefault :: Bool
,Restrict -> [String]
restrictName :: [String]
,Restrict -> [String]
restrictAs :: [String]
,Restrict -> Alt Maybe Bool
restrictAsRequired :: Alt Maybe Bool
,Restrict -> Alt Maybe RestrictImportStyle
restrictImportStyle :: Alt Maybe RestrictImportStyle
,Restrict -> Alt Maybe QualifiedStyle
restrictQualifiedStyle :: Alt Maybe QualifiedStyle
,Restrict -> [(String, String)]
restrictWithin :: [(String, String)]
,Restrict -> RestrictIdents
restrictIdents :: RestrictIdents
,Restrict -> Maybe String
restrictMessage :: Maybe String
} deriving Int -> Restrict -> ShowS
[Restrict] -> ShowS
Restrict -> String
(Int -> Restrict -> ShowS)
-> (Restrict -> String) -> ([Restrict] -> ShowS) -> Show Restrict
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Restrict -> ShowS
showsPrec :: Int -> Restrict -> ShowS
$cshow :: Restrict -> String
show :: Restrict -> String
$cshowList :: [Restrict] -> ShowS
showList :: [Restrict] -> ShowS
Show
data SmellType = SmellLongFunctions | SmellLongTypeLists | SmellManyArgFunctions | SmellManyImports
deriving (Int -> SmellType -> ShowS
[SmellType] -> ShowS
SmellType -> String
(Int -> SmellType -> ShowS)
-> (SmellType -> String)
-> ([SmellType] -> ShowS)
-> Show SmellType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SmellType -> ShowS
showsPrec :: Int -> SmellType -> ShowS
$cshow :: SmellType -> String
show :: SmellType -> String
$cshowList :: [SmellType] -> ShowS
showList :: [SmellType] -> ShowS
Show,SmellType -> SmellType -> Bool
(SmellType -> SmellType -> Bool)
-> (SmellType -> SmellType -> Bool) -> Eq SmellType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SmellType -> SmellType -> Bool
== :: SmellType -> SmellType -> Bool
$c/= :: SmellType -> SmellType -> Bool
/= :: SmellType -> SmellType -> Bool
Eq,Eq SmellType
Eq SmellType =>
(SmellType -> SmellType -> Ordering)
-> (SmellType -> SmellType -> Bool)
-> (SmellType -> SmellType -> Bool)
-> (SmellType -> SmellType -> Bool)
-> (SmellType -> SmellType -> Bool)
-> (SmellType -> SmellType -> SmellType)
-> (SmellType -> SmellType -> SmellType)
-> Ord SmellType
SmellType -> SmellType -> Bool
SmellType -> SmellType -> Ordering
SmellType -> SmellType -> SmellType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SmellType -> SmellType -> Ordering
compare :: SmellType -> SmellType -> Ordering
$c< :: SmellType -> SmellType -> Bool
< :: SmellType -> SmellType -> Bool
$c<= :: SmellType -> SmellType -> Bool
<= :: SmellType -> SmellType -> Bool
$c> :: SmellType -> SmellType -> Bool
> :: SmellType -> SmellType -> Bool
$c>= :: SmellType -> SmellType -> Bool
>= :: SmellType -> SmellType -> Bool
$cmax :: SmellType -> SmellType -> SmellType
max :: SmellType -> SmellType -> SmellType
$cmin :: SmellType -> SmellType -> SmellType
min :: SmellType -> SmellType -> SmellType
Ord)
getSmellType :: String -> Maybe SmellType
getSmellType :: String -> Maybe SmellType
getSmellType String
"long functions" = SmellType -> Maybe SmellType
forall a. a -> Maybe a
Just SmellType
SmellLongFunctions
getSmellType String
"long type lists" = SmellType -> Maybe SmellType
forall a. a -> Maybe a
Just SmellType
SmellLongTypeLists
getSmellType String
"many arg functions" = SmellType -> Maybe SmellType
forall a. a -> Maybe a
Just SmellType
SmellManyArgFunctions
getSmellType String
"many imports" = SmellType -> Maybe SmellType
forall a. a -> Maybe a
Just SmellType
SmellManyImports
getSmellType String
_ = Maybe SmellType
forall a. Maybe a
Nothing
data Setting
= SettingClassify Classify
| SettingMatchExp HintRule
| SettingRestrict Restrict
| SettingArgument String
| SettingSmell SmellType Int
| Builtin String
| Infix FixityInfo
deriving Int -> Setting -> ShowS
[Setting] -> ShowS
Setting -> String
(Int -> Setting -> ShowS)
-> (Setting -> String) -> ([Setting] -> ShowS) -> Show Setting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Setting -> ShowS
showsPrec :: Int -> Setting -> ShowS
$cshow :: Setting -> String
show :: Setting -> String
$cshowList :: [Setting] -> ShowS
showList :: [Setting] -> ShowS
Show