{-# LANGUAGE DeriveAnyClass #-} module Horizon.Spec.Types.Modifiers ( Modifiers(MkModifiers) , doBenchmark , doCheck , doJailbreak , enableProfiling , includeBenchmarks , includeExecutables , includeTests , defaultModifiers ) where import Data.Kind (Type) import Dhall (FromDhall, Generic, ToDhall) type Modifiers :: Type data Modifiers where MkModifiers :: { doBenchmark :: Bool , doCheck :: Bool , doJailbreak :: Bool , enableProfiling :: Bool , includeBenchmarks :: Bool , includeExecutables :: Bool , includeTests :: Bool } -> Modifiers deriving stock (Show, Eq, Generic) deriving anyclass (FromDhall, ToDhall) defaultModifiers :: Modifiers defaultModifiers = MkModifiers { doBenchmark = False , doCheck = False , doJailbreak = True , enableProfiling = True , includeBenchmarks = True , includeExecutables = True , includeTests = True }