{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
module Ide.Plugin.Eval.Config
( properties
, getEvalConfig
, EvalConfig(..)
) where
import Development.IDE
import Ide.Plugin.Properties
import Ide.Types (PluginId)
data EvalConfig = EvalConfig
{ EvalConfig -> Bool
eval_cfg_diff :: Bool
, EvalConfig -> Bool
eval_cfg_exception :: Bool
}
deriving (EvalConfig -> EvalConfig -> Bool
(EvalConfig -> EvalConfig -> Bool)
-> (EvalConfig -> EvalConfig -> Bool) -> Eq EvalConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EvalConfig -> EvalConfig -> Bool
== :: EvalConfig -> EvalConfig -> Bool
$c/= :: EvalConfig -> EvalConfig -> Bool
/= :: EvalConfig -> EvalConfig -> Bool
Eq, Eq EvalConfig
Eq EvalConfig =>
(EvalConfig -> EvalConfig -> Ordering)
-> (EvalConfig -> EvalConfig -> Bool)
-> (EvalConfig -> EvalConfig -> Bool)
-> (EvalConfig -> EvalConfig -> Bool)
-> (EvalConfig -> EvalConfig -> Bool)
-> (EvalConfig -> EvalConfig -> EvalConfig)
-> (EvalConfig -> EvalConfig -> EvalConfig)
-> Ord EvalConfig
EvalConfig -> EvalConfig -> Bool
EvalConfig -> EvalConfig -> Ordering
EvalConfig -> EvalConfig -> EvalConfig
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EvalConfig -> EvalConfig -> Ordering
compare :: EvalConfig -> EvalConfig -> Ordering
$c< :: EvalConfig -> EvalConfig -> Bool
< :: EvalConfig -> EvalConfig -> Bool
$c<= :: EvalConfig -> EvalConfig -> Bool
<= :: EvalConfig -> EvalConfig -> Bool
$c> :: EvalConfig -> EvalConfig -> Bool
> :: EvalConfig -> EvalConfig -> Bool
$c>= :: EvalConfig -> EvalConfig -> Bool
>= :: EvalConfig -> EvalConfig -> Bool
$cmax :: EvalConfig -> EvalConfig -> EvalConfig
max :: EvalConfig -> EvalConfig -> EvalConfig
$cmin :: EvalConfig -> EvalConfig -> EvalConfig
min :: EvalConfig -> EvalConfig -> EvalConfig
Ord, Int -> EvalConfig -> ShowS
[EvalConfig] -> ShowS
EvalConfig -> String
(Int -> EvalConfig -> ShowS)
-> (EvalConfig -> String)
-> ([EvalConfig] -> ShowS)
-> Show EvalConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EvalConfig -> ShowS
showsPrec :: Int -> EvalConfig -> ShowS
$cshow :: EvalConfig -> String
show :: EvalConfig -> String
$cshowList :: [EvalConfig] -> ShowS
showList :: [EvalConfig] -> ShowS
Show)
properties :: Properties
'[ 'PropertyKey "exception" 'TBoolean
, 'PropertyKey "diff" 'TBoolean
]
properties :: Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]
properties = Properties '[]
emptyProperties
Properties '[]
-> (Properties '[] -> Properties '[ 'PropertyKey "diff" 'TBoolean])
-> Properties '[ 'PropertyKey "diff" 'TBoolean]
forall a b. a -> (a -> b) -> b
& KeyNameProxy "diff"
-> Text
-> Bool
-> Properties '[]
-> Properties '[ 'PropertyKey "diff" 'TBoolean]
forall (s :: Symbol) (r :: [PropertyKey]).
(KnownSymbol s, NotElem s r) =>
KeyNameProxy s
-> Text
-> Bool
-> Properties r
-> Properties ('PropertyKey s 'TBoolean : r)
defineBooleanProperty KeyNameProxy "diff"
#diff
Text
"Enable the diff output (WAS/NOW) of eval lenses" Bool
True
Properties '[ 'PropertyKey "diff" 'TBoolean]
-> (Properties '[ 'PropertyKey "diff" 'TBoolean]
-> Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean])
-> Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]
forall a b. a -> (a -> b) -> b
& KeyNameProxy "exception"
-> Text
-> Bool
-> Properties '[ 'PropertyKey "diff" 'TBoolean]
-> Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]
forall (s :: Symbol) (r :: [PropertyKey]).
(KnownSymbol s, NotElem s r) =>
KeyNameProxy s
-> Text
-> Bool
-> Properties r
-> Properties ('PropertyKey s 'TBoolean : r)
defineBooleanProperty KeyNameProxy "exception"
#exception
Text
"Enable marking exceptions with `*** Exception:` similarly to doctest and GHCi." Bool
False
getEvalConfig :: PluginId -> Action EvalConfig
getEvalConfig :: PluginId -> Action EvalConfig
getEvalConfig PluginId
plId =
Bool -> Bool -> EvalConfig
EvalConfig
(Bool -> Bool -> EvalConfig)
-> Action Bool -> Action (Bool -> EvalConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> KeyNameProxy "diff"
-> PluginId
-> Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]
-> Action
(ToHsType
(FindByKeyName
"diff"
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]))
forall (s :: Symbol) (k :: PropertyKey) (t :: PropertyType)
(r :: [PropertyKey]).
HasProperty s k t r =>
KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t)
usePropertyAction KeyNameProxy "diff"
#diff PluginId
plId Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]
properties
Action (Bool -> EvalConfig) -> Action Bool -> Action EvalConfig
forall a b. Action (a -> b) -> Action a -> Action b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> KeyNameProxy "exception"
-> PluginId
-> Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]
-> Action
(ToHsType
(FindByKeyName
"exception"
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]))
forall (s :: Symbol) (k :: PropertyKey) (t :: PropertyType)
(r :: [PropertyKey]).
HasProperty s k t r =>
KeyNameProxy s -> PluginId -> Properties r -> Action (ToHsType t)
usePropertyAction KeyNameProxy "exception"
#exception PluginId
plId Properties
'[ 'PropertyKey "exception" 'TBoolean,
'PropertyKey "diff" 'TBoolean]
properties