From 24a0763b4b0a87b5abd488ebca67f4c5ff9b966d Mon Sep 17 00:00:00 2001
From: stuebinm <stuebinm@disroot.org>
Date: Sun, 14 Nov 2021 02:42:45 +0100
Subject: [PATCH] add some simple config options

---
 lib/LintConfig.hs | 39 ++++++++++++++++++++++++++++++---------
 1 file changed, 30 insertions(+), 9 deletions(-)

diff --git a/lib/LintConfig.hs b/lib/LintConfig.hs
index fed7e41..0f65752 100644
--- a/lib/LintConfig.hs
+++ b/lib/LintConfig.hs
@@ -13,13 +13,14 @@ module LintConfig where
 
 import           Control.Monad.Identity (Identity)
 import           Data.Aeson             (FromJSON (parseJSON), defaultOptions,
-                                         eitherDecode)
+                                         eitherDecode, Options(..))
 import           Data.Aeson.Types       (genericParseJSON)
 import qualified Data.ByteString.Char8  as C8
 import qualified Data.ByteString.Lazy   as LB
 import           Data.Text              (Text)
 import           GHC.Generics           (Generic (Rep, from, to), K1 (..),
                                          M1 (..), (:*:) (..))
+import           Types                  (Level)
 import           WithCli                (Proxy (..))
 import           WithCli.Pure           (Argument (argumentType, parseArgument))
 
@@ -28,26 +29,46 @@ type family HKD f a where
   HKD Identity a = a
   HKD f a = f a
 
-
 data LintConfig f = LintConfig
-  { assemblies   :: HKD f [Text]
-  , scriptInject :: HKD f (Maybe Text)
+  { configScriptInject :: HKD f (Maybe Text)
+  , configAssemblyTag  :: HKD f Text
+  , configMaxWarnLevel :: HKD f Level
   } deriving (Generic)
 
+type LintConfig' = LintConfig Identity
 
-deriving instance (Show (HKD a (Maybe Text)), Show (HKD a [Text]))
+-- TODO: should probably find a way to write these constraints nicer ...
+deriving instance
+  ( Show (HKD a (Maybe Text))
+  , Show (HKD a Text)
+  , Show (HKD a Level)
+  , Show (HKD a [Text])
+  )
   => Show (LintConfig a)
 
-instance (FromJSON (HKD a (Maybe Text)), FromJSON (HKD a [Text]))
-    => FromJSON (LintConfig a) where
-  parseJSON = genericParseJSON defaultOptions
+aesonOptions :: Options
+aesonOptions = defaultOptions
+  { omitNothingFields = True
+  , rejectUnknownFields = True
+  , fieldLabelModifier = drop 6
+  }
+
+instance
+    ( FromJSON (HKD a (Maybe Text))
+    , FromJSON (HKD a [Text])
+    , FromJSON (HKD a Text)
+    , FromJSON (HKD a Level)
+    )
+    => FromJSON (LintConfig a)
+  where
+    parseJSON = genericParseJSON aesonOptions
 
 -- need to define this one extra, since Aeson will not make
 -- Maybe fields optional if the type isn't given explicitly.
 --
 -- Whoever said instances had confusing semantics?
 instance {-# Overlapping #-} FromJSON (LintConfig Maybe) where
-  parseJSON = genericParseJSON defaultOptions
+  parseJSON = genericParseJSON aesonOptions
 
 
 
-- 
GitLab