module Stan.Config.Pretty
( ConfigAction (..)
, prettyConfigAction
, configActionClass
, configActionColour
, prettyConfigCli
, configToTriples
) where
import Colourista (bold, formatWith, green, magenta, red, yellow)
import Stan.Category (Category (..))
import Stan.Config (Check (..), CheckFilter (..), CheckType (..), Config, ConfigP (..), Scope (..))
import Stan.Core.Id (Id (..))
data ConfigAction
= RemoveAction
| IncludeAction
| ExcludeAction
| IgnoreAction
deriving stock (Int -> ConfigAction -> ShowS
[ConfigAction] -> ShowS
ConfigAction -> FilePath
(Int -> ConfigAction -> ShowS)
-> (ConfigAction -> FilePath)
-> ([ConfigAction] -> ShowS)
-> Show ConfigAction
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfigAction -> ShowS
showsPrec :: Int -> ConfigAction -> ShowS
$cshow :: ConfigAction -> FilePath
show :: ConfigAction -> FilePath
$cshowList :: [ConfigAction] -> ShowS
showList :: [ConfigAction] -> ShowS
Show, ConfigAction -> ConfigAction -> Bool
(ConfigAction -> ConfigAction -> Bool)
-> (ConfigAction -> ConfigAction -> Bool) -> Eq ConfigAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfigAction -> ConfigAction -> Bool
== :: ConfigAction -> ConfigAction -> Bool
$c/= :: ConfigAction -> ConfigAction -> Bool
/= :: ConfigAction -> ConfigAction -> Bool
Eq)
prettyConfigAction :: ConfigAction -> Text
prettyConfigAction :: ConfigAction -> Text
prettyConfigAction = \case
ConfigAction
RemoveAction -> Text
"— Remove "
ConfigAction
IncludeAction -> Text
"∪ Include"
ConfigAction
ExcludeAction -> Text
"∩ Exclude"
ConfigAction
IgnoreAction -> Text
"✖ Ignore "
configActionClass :: ConfigAction -> Text
configActionClass :: ConfigAction -> Text
configActionClass = \case
ConfigAction
RemoveAction -> Text
"remove"
ConfigAction
IncludeAction -> Text
"include"
ConfigAction
ExcludeAction -> Text
"exclude"
ConfigAction
IgnoreAction -> Text
"ignore"
configActionColour :: ConfigAction -> Text
configActionColour :: ConfigAction -> Text
configActionColour = \case
ConfigAction
RemoveAction -> Text
forall str. IsString str => str
red
ConfigAction
IncludeAction -> Text
forall str. IsString str => str
green
ConfigAction
ExcludeAction -> Text
forall str. IsString str => str
yellow
ConfigAction
IgnoreAction -> Text
forall str. IsString str => str
magenta
configToTriples :: Config -> [(ConfigAction, Text, Text)]
configToTriples :: Config -> [(ConfigAction, Text, Text)]
configToTriples ConfigP{'Final ::- [Id Observation]
'Final ::- [Scope]
'Final ::- [Check]
configChecks :: 'Final ::- [Check]
configRemoved :: 'Final ::- [Scope]
configIgnored :: 'Final ::- [Id Observation]
configChecks :: forall (p :: Phase Text). ConfigP p -> p ::- [Check]
configRemoved :: forall (p :: Phase Text). ConfigP p -> p ::- [Scope]
configIgnored :: forall (p :: Phase Text). ConfigP p -> p ::- [Id Observation]
..} =
(Scope -> (ConfigAction, Text, Text))
-> [Scope] -> [(ConfigAction, Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map ((ConfigAction
RemoveAction, Text
"", ) (Text -> (ConfigAction, Text, Text))
-> (Scope -> Text) -> Scope -> (ConfigAction, Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scope -> Text
prettyScope) [Scope]
'Final ::- [Scope]
configRemoved
[(ConfigAction, Text, Text)]
-> [(ConfigAction, Text, Text)] -> [(ConfigAction, Text, Text)]
forall a. [a] -> [a] -> [a]
++ (Check -> (ConfigAction, Text, Text))
-> [Check] -> [(ConfigAction, Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map Check -> (ConfigAction, Text, Text)
checkToTriple [Check]
'Final ::- [Check]
configChecks
[(ConfigAction, Text, Text)]
-> [(ConfigAction, Text, Text)] -> [(ConfigAction, Text, Text)]
forall a. [a] -> [a] -> [a]
++ (Id Observation -> (ConfigAction, Text, Text))
-> [Id Observation] -> [(ConfigAction, Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map ((ConfigAction
IgnoreAction, , Text
"") (Text -> (ConfigAction, Text, Text))
-> (Id Observation -> Text)
-> Id Observation
-> (ConfigAction, Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id Observation -> Text
forall a. Id a -> Text
unId) [Id Observation]
'Final ::- [Id Observation]
configIgnored
checkToTriple :: Check -> (ConfigAction, Text, Text)
checkToTriple :: Check -> (ConfigAction, Text, Text)
checkToTriple Check{Scope
CheckFilter
CheckType
checkType :: CheckType
checkFilter :: CheckFilter
checkScope :: Scope
checkType :: Check -> CheckType
checkFilter :: Check -> CheckFilter
checkScope :: Check -> Scope
..} =
( CheckType -> ConfigAction
checkTypeToAction CheckType
checkType
, CheckFilter -> Text
prettyFilter CheckFilter
checkFilter
, Scope -> Text
prettyScope Scope
checkScope
)
checkTypeToAction :: CheckType -> ConfigAction
checkTypeToAction :: CheckType -> ConfigAction
checkTypeToAction = \case
CheckType
Include -> ConfigAction
IncludeAction
CheckType
Exclude -> ConfigAction
ExcludeAction
prettyFilter :: CheckFilter -> Text
prettyFilter :: CheckFilter -> Text
prettyFilter = \case
CheckInspection Id Inspection
ins -> Text
"ID: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Id Inspection -> Text
forall a. Id a -> Text
unId Id Inspection
ins
CheckSeverity Severity
sev -> Text
"Severity: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Severity -> Text
forall b a. (Show a, IsString b) => a -> b
show Severity
sev
CheckCategory Category
cat -> Text
"Category: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Category -> Text
unCategory Category
cat
CheckFilter
CheckAll -> Text
"All inspections"
prettyScope :: Scope -> Text
prettyScope :: Scope -> Text
prettyScope = \case
ScopeFile FilePath
fp -> Text
"File: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
forall a. ToText a => a -> Text
toText FilePath
fp
ScopeDirectory FilePath
dir -> Text
"Directory: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
forall a. ToText a => a -> Text
toText FilePath
dir
Scope
ScopeAll -> Text
"All files"
prettyConfigCli :: Config -> Text
prettyConfigCli :: Config -> Text
prettyConfigCli = [Text] -> Text
forall t. IsText t "unlines" => [t] -> t
unlines ([Text] -> Text) -> (Config -> [Text]) -> Config -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ConfigAction, Text, Text) -> [Text])
-> [(ConfigAction, Text, Text)] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ConfigAction, Text, Text) -> [Text]
action ([(ConfigAction, Text, Text)] -> [Text])
-> (Config -> [(ConfigAction, Text, Text)]) -> Config -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> [(ConfigAction, Text, Text)]
configToTriples
where
action :: (ConfigAction, Text, Text) -> [Text]
action :: (ConfigAction, Text, Text) -> [Text]
action (ConfigAction
act, Text
check, Text
scope) =
[Text] -> Text -> Text
forall str. (IsString str, Semigroup str) => [str] -> str -> str
formatWith [ConfigAction -> Text
configActionColour ConfigAction
act, Text
forall str. IsString str => str
bold] (ConfigAction -> Text
prettyConfigAction ConfigAction
act)
Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [ Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
check | Text
check Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
""]
[Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [ Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
scope | Text
scope Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
""]