{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveAnyClass #-}

module Hercules.API.Agent.Evaluate.EvaluateEvent.AttributeEvent where

import Control.Applicative (Alternative ((<|>)))
import Control.Lens ((%~))
import Control.Lens.At (At (at))
import qualified Data.Aeson as A
import Data.Aeson.Lens (_Object)
import Hercules.API.Prelude

data AttributeType
  = Regular
  | MustFail
  | MayFail
  | DependenciesOnly
  | Effect
  deriving (forall x. Rep AttributeType x -> AttributeType
forall x. AttributeType -> Rep AttributeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttributeType x -> AttributeType
$cfrom :: forall x. AttributeType -> Rep AttributeType x
Generic, Int -> AttributeType -> ShowS
[AttributeType] -> ShowS
AttributeType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttributeType] -> ShowS
$cshowList :: [AttributeType] -> ShowS
show :: AttributeType -> String
$cshow :: AttributeType -> String
showsPrec :: Int -> AttributeType -> ShowS
$cshowsPrec :: Int -> AttributeType -> ShowS
Show, AttributeType -> AttributeType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttributeType -> AttributeType -> Bool
$c/= :: AttributeType -> AttributeType -> Bool
== :: AttributeType -> AttributeType -> Bool
$c== :: AttributeType -> AttributeType -> Bool
Eq, AttributeType -> ()
forall a. (a -> ()) -> NFData a
rnf :: AttributeType -> ()
$crnf :: AttributeType -> ()
NFData, [AttributeType] -> Encoding
[AttributeType] -> Value
AttributeType -> Encoding
AttributeType -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AttributeType] -> Encoding
$ctoEncodingList :: [AttributeType] -> Encoding
toJSONList :: [AttributeType] -> Value
$ctoJSONList :: [AttributeType] -> Value
toEncoding :: AttributeType -> Encoding
$ctoEncoding :: AttributeType -> Encoding
toJSON :: AttributeType -> Value
$ctoJSON :: AttributeType -> Value
ToJSON, Value -> Parser [AttributeType]
Value -> Parser AttributeType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AttributeType]
$cparseJSONList :: Value -> Parser [AttributeType]
parseJSON :: Value -> Parser AttributeType
$cparseJSON :: Value -> Parser AttributeType
FromJSON)

data AttributeEvent = AttributeEvent
  { AttributeEvent -> [Text]
expressionPath :: [Text],
    AttributeEvent -> Text
derivationPath :: Text,
    AttributeEvent -> AttributeType
typ :: AttributeType
    -- TODO: meta attributes
  }
  deriving (forall x. Rep AttributeEvent x -> AttributeEvent
forall x. AttributeEvent -> Rep AttributeEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttributeEvent x -> AttributeEvent
$cfrom :: forall x. AttributeEvent -> Rep AttributeEvent x
Generic, Int -> AttributeEvent -> ShowS
[AttributeEvent] -> ShowS
AttributeEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttributeEvent] -> ShowS
$cshowList :: [AttributeEvent] -> ShowS
show :: AttributeEvent -> String
$cshow :: AttributeEvent -> String
showsPrec :: Int -> AttributeEvent -> ShowS
$cshowsPrec :: Int -> AttributeEvent -> ShowS
Show, AttributeEvent -> AttributeEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttributeEvent -> AttributeEvent -> Bool
$c/= :: AttributeEvent -> AttributeEvent -> Bool
== :: AttributeEvent -> AttributeEvent -> Bool
$c== :: AttributeEvent -> AttributeEvent -> Bool
Eq, AttributeEvent -> ()
forall a. (a -> ()) -> NFData a
rnf :: AttributeEvent -> ()
$crnf :: AttributeEvent -> ()
NFData, [AttributeEvent] -> Encoding
[AttributeEvent] -> Value
AttributeEvent -> Encoding
AttributeEvent -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AttributeEvent] -> Encoding
$ctoEncodingList :: [AttributeEvent] -> Encoding
toJSONList :: [AttributeEvent] -> Value
$ctoJSONList :: [AttributeEvent] -> Value
toEncoding :: AttributeEvent -> Encoding
$ctoEncoding :: AttributeEvent -> Encoding
toJSON :: AttributeEvent -> Value
$ctoJSON :: AttributeEvent -> Value
ToJSON)

instance FromJSON AttributeEvent where
  parseJSON :: Value -> Parser AttributeEvent
parseJSON Value
v = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON Options
A.defaultOptions (Value -> Value
fixup Value
v)
    where
      fixup :: A.Value -> A.Value
      fixup :: Value -> Value
fixup = forall t. AsValue t => Prism' t (KeyMap Value)
_Object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Key
"typ" forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. a -> Maybe a
Just (Text -> Value
A.String Text
"Regular"))