{-# LANGUAGE TemplateHaskell #-}
module Swarm.Game.Robot.Activity (
ActivityCounts,
tickStepBudget,
tangibleCommandCount,
commandsHistogram,
lifetimeStepCount,
activityWindow,
emptyActivityCount,
) where
import Control.Lens hiding (Const, contains)
import Data.Aeson qualified as Ae (FromJSON (..), ToJSON (..))
import Data.Map.Strict (Map)
import GHC.Generics (Generic)
import Swarm.Game.Tick
import Swarm.Language.Syntax (Const)
import Swarm.Util.Lens (makeLensesNoSigs)
import Swarm.Util.WindowedCounter
data ActivityCounts = ActivityCounts
{ ActivityCounts -> Int
_tickStepBudget :: Int
, ActivityCounts -> Int
_tangibleCommandCount :: Int
, ActivityCounts -> Map Const Int
_commandsHistogram :: Map Const Int
, ActivityCounts -> Int
_lifetimeStepCount :: Int
, ActivityCounts -> WindowedCounter TickNumber
_activityWindow :: WindowedCounter TickNumber
}
deriving (ActivityCounts -> ActivityCounts -> Bool
(ActivityCounts -> ActivityCounts -> Bool)
-> (ActivityCounts -> ActivityCounts -> Bool) -> Eq ActivityCounts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActivityCounts -> ActivityCounts -> Bool
== :: ActivityCounts -> ActivityCounts -> Bool
$c/= :: ActivityCounts -> ActivityCounts -> Bool
/= :: ActivityCounts -> ActivityCounts -> Bool
Eq, Int -> ActivityCounts -> ShowS
[ActivityCounts] -> ShowS
ActivityCounts -> String
(Int -> ActivityCounts -> ShowS)
-> (ActivityCounts -> String)
-> ([ActivityCounts] -> ShowS)
-> Show ActivityCounts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ActivityCounts -> ShowS
showsPrec :: Int -> ActivityCounts -> ShowS
$cshow :: ActivityCounts -> String
show :: ActivityCounts -> String
$cshowList :: [ActivityCounts] -> ShowS
showList :: [ActivityCounts] -> ShowS
Show, (forall x. ActivityCounts -> Rep ActivityCounts x)
-> (forall x. Rep ActivityCounts x -> ActivityCounts)
-> Generic ActivityCounts
forall x. Rep ActivityCounts x -> ActivityCounts
forall x. ActivityCounts -> Rep ActivityCounts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ActivityCounts -> Rep ActivityCounts x
from :: forall x. ActivityCounts -> Rep ActivityCounts x
$cto :: forall x. Rep ActivityCounts x -> ActivityCounts
to :: forall x. Rep ActivityCounts x -> ActivityCounts
Generic, Maybe ActivityCounts
Value -> Parser [ActivityCounts]
Value -> Parser ActivityCounts
(Value -> Parser ActivityCounts)
-> (Value -> Parser [ActivityCounts])
-> Maybe ActivityCounts
-> FromJSON ActivityCounts
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ActivityCounts
parseJSON :: Value -> Parser ActivityCounts
$cparseJSONList :: Value -> Parser [ActivityCounts]
parseJSONList :: Value -> Parser [ActivityCounts]
$comittedField :: Maybe ActivityCounts
omittedField :: Maybe ActivityCounts
Ae.FromJSON, [ActivityCounts] -> Value
[ActivityCounts] -> Encoding
ActivityCounts -> Bool
ActivityCounts -> Value
ActivityCounts -> Encoding
(ActivityCounts -> Value)
-> (ActivityCounts -> Encoding)
-> ([ActivityCounts] -> Value)
-> ([ActivityCounts] -> Encoding)
-> (ActivityCounts -> Bool)
-> ToJSON ActivityCounts
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ActivityCounts -> Value
toJSON :: ActivityCounts -> Value
$ctoEncoding :: ActivityCounts -> Encoding
toEncoding :: ActivityCounts -> Encoding
$ctoJSONList :: [ActivityCounts] -> Value
toJSONList :: [ActivityCounts] -> Value
$ctoEncodingList :: [ActivityCounts] -> Encoding
toEncodingList :: [ActivityCounts] -> Encoding
$comitField :: ActivityCounts -> Bool
omitField :: ActivityCounts -> Bool
Ae.ToJSON)
emptyActivityCount :: ActivityCounts
emptyActivityCount :: ActivityCounts
emptyActivityCount =
ActivityCounts
{ _tickStepBudget :: Int
_tickStepBudget = Int
0
, _tangibleCommandCount :: Int
_tangibleCommandCount = Int
0
, _commandsHistogram :: Map Const Int
_commandsHistogram = Map Const Int
forall a. Monoid a => a
mempty
, _lifetimeStepCount :: Int
_lifetimeStepCount = Int
0
,
_activityWindow :: WindowedCounter TickNumber
_activityWindow = Int -> WindowedCounter TickNumber
forall a. Int -> WindowedCounter a
mkWindow Int
64
}
makeLensesNoSigs ''ActivityCounts
tickStepBudget :: Lens' ActivityCounts Int
tangibleCommandCount :: Lens' ActivityCounts Int
commandsHistogram :: Lens' ActivityCounts (Map Const Int)
lifetimeStepCount :: Lens' ActivityCounts Int
activityWindow :: Lens' ActivityCounts (WindowedCounter TickNumber)