{-# language ApplicativeDo #-}
{-# language BlockArguments #-}
{-# language OverloadedStrings #-}
{-# language RecordWildCards #-}
module Weeder.Config ( Config(..), config ) where
import Data.Set ( Set )
import qualified Data.Set as Set
import qualified Dhall
data Config = Config
{ Config -> Set String
rootPatterns :: Set String
, Config -> Bool
typeClassRoots :: Bool
}
config :: Dhall.Decoder Config
config :: Decoder Config
config =
forall a. RecordDecoder a -> Decoder a
Dhall.record do
Set String
rootPatterns <- forall a. Ord a => [a] -> Set a
Set.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Text -> Decoder a -> RecordDecoder a
Dhall.field Text
"roots" ( forall a. Decoder a -> Decoder [a]
Dhall.list Decoder String
Dhall.string )
Bool
typeClassRoots <- forall a. Text -> Decoder a -> RecordDecoder a
Dhall.field Text
"type-class-roots" Decoder Bool
Dhall.bool
return Config{Bool
Set String
typeClassRoots :: Bool
rootPatterns :: Set String
typeClassRoots :: Bool
rootPatterns :: Set String
..}