Skip to content

Commit

Permalink
Derive FromJSON instance for Handling with generically
Browse files Browse the repository at this point in the history
  • Loading branch information
jfpedroza committed Dec 17, 2022
1 parent 134350f commit 0a6d845
Showing 1 changed file with 8 additions and 7 deletions.
15 changes: 8 additions & 7 deletions src/Emanote/Model/Stork/Index.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module Emanote.Model.Stork.Index
where

import Control.Monad.Logger (MonadLoggerIO)
import Data.Aeson (FromJSON (parseJSON))
import Data.Aeson (FromJSON, genericParseJSON)
import Data.Aeson qualified as Aeson
import Data.Text qualified as T
import Data.Time (NominalDiffTime, diffUTCTime, getCurrentTime)
Expand Down Expand Up @@ -92,7 +92,7 @@ data Handling
= Handling_Ignore
| Handling_Omit
| Handling_Parse
deriving stock (Eq, Show)
deriving stock (Eq, Show, Generic)

newtype Config = Config
{ configInput :: Input
Expand Down Expand Up @@ -140,9 +140,10 @@ configCodec =
Config
<$> Toml.table inputCodec "input" .= configInput

handlingJSONOptions :: Aeson.Options
handlingJSONOptions = Aeson.defaultOptions
{ Aeson.constructorTagModifier = toString . T.toLower . T.replace "Handling_" "" . toText
}

instance FromJSON Handling where
parseJSON = Aeson.withText "FrontmatterHandling" $ \case
"ignore" -> pure Handling_Ignore
"omit" -> pure Handling_Omit
"parse" -> pure Handling_Parse
_ -> fail "Unsupported value for frontmatter-handling"
parseJSON = genericParseJSON handlingJSONOptions

0 comments on commit 0a6d845

Please sign in to comment.