{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}

-- |
-- SPDX-License-Identifier: BSD-3-Clause
--
-- Sub-records utilized by 'Swarm.TUI.Model.UI'
-- This exists as a separate module to avoid import cycles.
module Swarm.TUI.Model.UI.Gameplay (
  UIGameplay (..),
  UITiming (..),
  UIInventory (..),
  GoalDisplay (..),
  UIDialogs (..),
  uiTiming,
  uiInventory,
  uiFocusRing,
  uiWorldCursor,
  uiWorldEditor,
  uiREPL,
  uiInventoryList,
  uiInventorySort,
  uiInventorySearch,
  uiScrollToEnd,
  uiModal,
  uiGoal,
  uiStructure,
  uiRobot,
  uiDialogs,
  uiIsAutoPlay,
  uiAutoShowObjectives,
  lgTicksPerSecond,
  lastFrameTime,
  accumulatedTime,
  tickCount,
  frameCount,
  frameTickCount,
  lastInfoTime,
  uiShowFPS,
  uiShowREPL,
  uiShowZero,
  uiShowDebug,
  uiShowRobots,
  uiHideRobotsUntil,
  uiInventoryShouldUpdate,
  uiTPF,
  uiFPS,
  scenarioRef,
) where

import Brick.Focus
import Brick.Widgets.List qualified as BL
import Control.Lens hiding (from, (<.>))
import Data.Bits (FiniteBits (finiteBitSize))
import Data.Text (Text)
import Swarm.Game.Scenario.Status (ScenarioPath)
import Swarm.Game.ScenarioInfo (
  ScenarioWith,
 )
import Swarm.Game.Universe
import Swarm.Game.World.Coords
import Swarm.TUI.Editor.Model
import Swarm.TUI.Inventory.Sorting
import Swarm.TUI.Model.Dialog.Goal
import Swarm.TUI.Model.Dialog.Structure
import Swarm.TUI.Model.Menu
import Swarm.TUI.Model.Name
import Swarm.TUI.Model.Repl
import Swarm.TUI.View.Robot.Type
import Swarm.Util.Lens (makeLensesExcluding, makeLensesNoSigs)
import System.Clock

data UITiming = UITiming
  { UITiming -> Bool
_uiShowFPS :: Bool
  , UITiming -> Double
_uiTPF :: Double
  , UITiming -> Double
_uiFPS :: Double
  , UITiming -> Int
_lgTicksPerSecond :: Int
  , UITiming -> Int
_tickCount :: Int
  , UITiming -> Int
_frameCount :: Int
  , UITiming -> Int
_frameTickCount :: Int
  , UITiming -> TimeSpec
_lastFrameTime :: TimeSpec
  , UITiming -> TimeSpec
_accumulatedTime :: TimeSpec
  , UITiming -> TimeSpec
_lastInfoTime :: TimeSpec
  }

-- * Lenses for UITiming

makeLensesExcluding ['_lgTicksPerSecond] ''UITiming

-- | A toggle to show the FPS by pressing @f@
uiShowFPS :: Lens' UITiming Bool

-- | Computed ticks per milliseconds
uiTPF :: Lens' UITiming Double

-- | Computed frames per milliseconds
uiFPS :: Lens' UITiming Double

-- | The base-2 logarithm of the current game speed in ticks/second.
--   Note that we cap this value to the range of +/- log2 INTMAX.
lgTicksPerSecond :: Lens' UITiming Int
lgTicksPerSecond :: Lens' UITiming Int
lgTicksPerSecond = (UITiming -> Int)
-> (UITiming -> Int -> UITiming) -> Lens' UITiming Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens UITiming -> Int
_lgTicksPerSecond UITiming -> Int -> UITiming
safeSetLgTicks
 where
  maxLog :: Int
maxLog = Int -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (Int
forall a. Bounded a => a
maxBound :: Int)
  maxTicks :: Int
maxTicks = Int
maxLog Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2
  minTicks :: Int
minTicks = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
maxLog
  safeSetLgTicks :: UITiming -> Int -> UITiming
safeSetLgTicks UITiming
ui Int
lTicks
    | Int
lTicks Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
minTicks = UITiming -> Int -> UITiming
setLgTicks UITiming
ui Int
minTicks
    | Int
lTicks Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
maxTicks = UITiming -> Int -> UITiming
setLgTicks UITiming
ui Int
maxTicks
    | Bool
otherwise = UITiming -> Int -> UITiming
setLgTicks UITiming
ui Int
lTicks
  setLgTicks :: UITiming -> Int -> UITiming
setLgTicks UITiming
ui Int
lTicks = UITiming
ui {_lgTicksPerSecond = lTicks}

-- | A counter used to track how many ticks have happened since the
--   last time we updated the ticks/frame statistics.
tickCount :: Lens' UITiming Int

-- | A counter used to track how many frames have been rendered since the
--   last time we updated the ticks/frame statistics.
frameCount :: Lens' UITiming Int

-- | A counter used to track how many ticks have happened in the
--   current frame, so we can stop when we get to the tick cap.
frameTickCount :: Lens' UITiming Int

-- | The time of the last info widget update
lastInfoTime :: Lens' UITiming TimeSpec

-- | The time of the last 'Swarm.TUI.Model.Frame' event.
lastFrameTime :: Lens' UITiming TimeSpec

-- | The amount of accumulated real time.  Every time we get a 'Swarm.TUI.Model.Frame'
--   event, we accumulate the amount of real time that happened since
--   the last frame, then attempt to take an appropriate number of
--   ticks to "catch up", based on the target tick rate.
--
--   See https://gafferongames.com/post/fix_your_timestep/ .
accumulatedTime :: Lens' UITiming TimeSpec

data UIInventory = UIInventory
  { UIInventory -> Maybe (Int, List Name InventoryListEntry)
_uiInventoryList :: Maybe (Int, BL.List Name InventoryListEntry)
  , UIInventory -> InventorySortOptions
_uiInventorySort :: InventorySortOptions
  , UIInventory -> Maybe Text
_uiInventorySearch :: Maybe Text
  , UIInventory -> Bool
_uiShowZero :: Bool
  , UIInventory -> Bool
_uiInventoryShouldUpdate :: Bool
  }

-- * Lenses for UIInventory

makeLensesNoSigs ''UIInventory

-- | The order and direction of sorting inventory list.
uiInventorySort :: Lens' UIInventory InventorySortOptions

-- | The current search string used to narrow the inventory view.
uiInventorySearch :: Lens' UIInventory (Maybe Text)

-- | The hash value of the focused robot entity (so we can tell if its
--   inventory changed) along with a list of the items in the
--   focused robot's inventory.
uiInventoryList :: Lens' UIInventory (Maybe (Int, BL.List Name InventoryListEntry))

-- | A toggle to show or hide inventory items with count 0 by pressing @0@
uiShowZero :: Lens' UIInventory Bool

-- | Whether the Inventory ui panel should update
uiInventoryShouldUpdate :: Lens' UIInventory Bool

-- | State that backs various modal dialogs
data UIDialogs = UIDialogs
  { UIDialogs -> Maybe Modal
_uiModal :: Maybe Modal
  , UIDialogs -> GoalDisplay
_uiGoal :: GoalDisplay
  , UIDialogs -> StructureDisplay
_uiStructure :: StructureDisplay
  , UIDialogs -> RobotDisplay
_uiRobot :: RobotDisplay
  }

-- * Lenses for UIDialogs

makeLensesNoSigs ''UIDialogs

-- | When this is 'Just', it represents a modal to be displayed on
--   top of the UI, e.g. for the Help screen.
uiModal :: Lens' UIDialogs (Maybe Modal)

-- | Status of the scenario goal: whether there is one, and whether it
--   has been displayed to the user initially.
uiGoal :: Lens' UIDialogs GoalDisplay

-- | Definition and status of a recognizable structure
uiStructure :: Lens' UIDialogs StructureDisplay

-- | Definition and status of a recognizable structure
uiRobot :: Lens' UIDialogs RobotDisplay

-- | UI state specific to an actively-playing scenario.
-- Compare to 'UIState', which contains UI state independent of an
-- active scenario.
--
-- For access to the fields, see the lenses below.
data UIGameplay = UIGameplay
  { UIGameplay -> FocusRing Name
_uiFocusRing :: FocusRing Name
  , UIGameplay -> Maybe (Cosmic Coords)
_uiWorldCursor :: Maybe (Cosmic Coords)
  , UIGameplay -> WorldEditor Name
_uiWorldEditor :: WorldEditor Name
  , UIGameplay -> REPLState
_uiREPL :: REPLState
  , UIGameplay -> UIInventory
_uiInventory :: UIInventory
  , UIGameplay -> Bool
_uiScrollToEnd :: Bool
  , UIGameplay -> UIDialogs
_uiDialogs :: UIDialogs
  , UIGameplay -> Bool
_uiIsAutoPlay :: Bool
  , UIGameplay -> Bool
_uiAutoShowObjectives :: Bool
  , UIGameplay -> Bool
_uiShowREPL :: Bool
  , UIGameplay -> Bool
_uiShowDebug :: Bool
  , UIGameplay -> TimeSpec
_uiHideRobotsUntil :: TimeSpec
  , UIGameplay -> UITiming
_uiTiming :: UITiming
  , UIGameplay -> Maybe (ScenarioWith ScenarioPath)
_scenarioRef :: Maybe (ScenarioWith ScenarioPath)
  }

-- * Lenses for UIGameplay

makeLensesNoSigs ''UIGameplay

-- | Temporal information for gameplay UI
uiTiming :: Lens' UIGameplay UITiming

-- | Inventory information for gameplay UI
uiInventory :: Lens' UIGameplay UIInventory

-- | The focus ring is the set of UI panels we can cycle among using
--   the @Tab@ key.
uiFocusRing :: Lens' UIGameplay (FocusRing Name)

-- | The last clicked position on the world view.
uiWorldCursor :: Lens' UIGameplay (Maybe (Cosmic Coords))

-- | State of all World Editor widgets
uiWorldEditor :: Lens' UIGameplay (WorldEditor Name)

-- | The state of REPL panel.
uiREPL :: Lens' UIGameplay REPLState

-- | A flag telling the UI to scroll the info panel to the very end
--   (used when a new log message is appended).
uiScrollToEnd :: Lens' UIGameplay Bool

-- | State that backs various modal dialogs
uiDialogs :: Lens' UIGameplay UIDialogs

-- | When running with @--autoplay@ the progress will not be saved.
uiIsAutoPlay :: Lens' UIGameplay Bool

-- | Do not open objectives modals on objective completion.
uiAutoShowObjectives :: Lens' UIGameplay Bool

-- | A toggle to expand or collapse the REPL by pressing @Ctrl-k@
uiShowREPL :: Lens' UIGameplay Bool

-- | A toggle to show CESK machine debug view and step through it.
--
-- Note that the ability to use it can be enabled by player robot
-- gaining the capability, or being in creative mode or with
-- the debug option 'Swarm.TUI.Model.DebugOption.DebugCESK'.
uiShowDebug :: Lens' UIGameplay Bool

-- | Hide robots on the world map.
uiHideRobotsUntil :: Lens' UIGameplay TimeSpec

-- | Whether to show or hide robots on the world map.
uiShowRobots :: Getter UIGameplay Bool
uiShowRobots :: Getter UIGameplay Bool
uiShowRobots = (UIGameplay -> Bool)
-> (Bool -> f Bool) -> UIGameplay -> f UIGameplay
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to (\UIGameplay
ui -> UIGameplay
ui UIGameplay -> Getting TimeSpec UIGameplay TimeSpec -> TimeSpec
forall s a. s -> Getting a s a -> a
^. (UITiming -> Const TimeSpec UITiming)
-> UIGameplay -> Const TimeSpec UIGameplay
Lens' UIGameplay UITiming
uiTiming ((UITiming -> Const TimeSpec UITiming)
 -> UIGameplay -> Const TimeSpec UIGameplay)
-> ((TimeSpec -> Const TimeSpec TimeSpec)
    -> UITiming -> Const TimeSpec UITiming)
-> Getting TimeSpec UIGameplay TimeSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TimeSpec -> Const TimeSpec TimeSpec)
-> UITiming -> Const TimeSpec UITiming
Lens' UITiming TimeSpec
lastFrameTime TimeSpec -> TimeSpec -> Bool
forall a. Ord a => a -> a -> Bool
> UIGameplay
ui UIGameplay -> Getting TimeSpec UIGameplay TimeSpec -> TimeSpec
forall s a. s -> Getting a s a -> a
^. Getting TimeSpec UIGameplay TimeSpec
Lens' UIGameplay TimeSpec
uiHideRobotsUntil)

-- | The currently active Scenario description, useful for starting over.
scenarioRef :: Lens' UIGameplay (Maybe (ScenarioWith ScenarioPath))