module Config.Type(
Severity(..), Classify(..), HintRule(..), Note(..), Setting(..),
Restrict(..), RestrictType(..), SmellType(..),
defaultHintName, isUnifyVar, showNotes, getSeverity, getRestrictType, getSmellType
) where
import HSE.All
import Data.Char
import Data.List.Extra
import Prelude
getSeverity :: String -> Maybe Severity
getSeverity "ignore" = Just Ignore
getSeverity "warn" = Just Warning
getSeverity "warning" = Just Warning
getSeverity "suggest" = Just Suggestion
getSeverity "suggestion" = Just Suggestion
getSeverity "error" = Just Error
getSeverity "hint" = Just Suggestion
getSeverity _ = Nothing
getRestrictType :: String -> Maybe RestrictType
getRestrictType "modules" = Just RestrictModule
getRestrictType "extensions" = Just RestrictExtension
getRestrictType "flags" = Just RestrictFlag
getRestrictType "functions" = Just RestrictFunction
getRestrictType _ = Nothing
defaultHintName :: String
defaultHintName = "Use alternative"
data Severity
= Ignore
| Suggestion
| Warning
| Error
deriving (Eq,Ord,Show,Read,Bounded,Enum)
isUnifyVar :: String -> Bool
isUnifyVar [x] = x == '?' || isAlpha x
isUnifyVar [] = False
isUnifyVar xs = all (== '?') xs
data Note
= IncreasesLaziness
| DecreasesLaziness
| RemovesError String
| ValidInstance String String
| RequiresExtension String
| Note String
deriving (Eq,Ord)
instance Show Note where
show IncreasesLaziness = "increases laziness"
show DecreasesLaziness = "decreases laziness"
show (RemovesError x) = "removes error " ++ x
show (ValidInstance x y) = "requires a valid `" ++ x ++ "` instance for `" ++ y ++ "`"
show (RequiresExtension x) = "may require `{-# LANGUAGE " ++ x ++ " #-}` adding to the top of the file"
show (Note x) = x
showNotes :: [Note] -> String
showNotes = intercalate ", " . map show . filter use
where use ValidInstance{} = False
use _ = True
data Classify = Classify
{classifySeverity :: Severity
,classifyHint :: String
,classifyModule :: String
,classifyDecl :: String
}
deriving Show
data HintRule = HintRule
{hintRuleSeverity :: Severity
,hintRuleName :: String
,hintRuleScope :: Scope
,hintRuleLHS :: Exp SrcSpanInfo
,hintRuleRHS :: Exp SrcSpanInfo
,hintRuleSide :: Maybe (Exp SrcSpanInfo)
,hintRuleNotes :: [Note]
}
deriving Show
data RestrictType = RestrictModule | RestrictExtension | RestrictFlag | RestrictFunction deriving (Show,Eq,Ord)
data Restrict = Restrict
{restrictType :: RestrictType
,restrictDefault :: Bool
,restrictName :: [String]
,restrictAs :: [String]
,restrictWithin :: [(String, String)]
} deriving Show
data SmellType = SmellLongFunctions | SmellLongTypeLists | SmellManyArgFunctions | SmellManyImports
deriving (Show,Eq,Ord)
getSmellType :: String -> Maybe SmellType
getSmellType "long functions" = Just SmellLongFunctions
getSmellType "long type lists" = Just SmellLongTypeLists
getSmellType "many arg functions" = Just SmellManyArgFunctions
getSmellType "many imports" = Just SmellManyImports
getSmellType _ = Nothing
data Setting
= SettingClassify Classify
| SettingMatchExp HintRule
| SettingRestrict Restrict
| SettingArgument String
| SettingSmell SmellType Int
| Builtin String
| Infix Fixity
deriving Show