{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoGeneralizedNewtypeDeriving #-}
module Swarm.TUI.Model.Dialog.Structure where
import Brick.Focus
import Brick.Widgets.List qualified as BL
import Control.Lens (makeLenses)
import Data.List.Extra (enumerate)
import Swarm.Game.Entity (Entity)
import Swarm.Game.Scenario (RecognizableStructureContent)
import Swarm.Game.Scenario.Topography.Structure.Recognition.Type
import Swarm.TUI.Model.Name
data StructureDisplay = StructureDisplay
{ StructureDisplay
-> List Name (StructureInfo RecognizableStructureContent Entity)
_structurePanelListWidget :: BL.List Name (StructureInfo RecognizableStructureContent Entity)
, StructureDisplay -> FocusRing Name
_structurePanelFocus :: FocusRing Name
}
makeLenses ''StructureDisplay
emptyStructureDisplay :: StructureDisplay
emptyStructureDisplay :: StructureDisplay
emptyStructureDisplay =
List Name (StructureInfo RecognizableStructureContent Entity)
-> FocusRing Name -> StructureDisplay
StructureDisplay
(Name
-> Vector (StructureInfo RecognizableStructureContent Entity)
-> Int
-> List Name (StructureInfo RecognizableStructureContent Entity)
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
BL.list (StructureWidget -> Name
StructureWidgets StructureWidget
StructuresList) Vector (StructureInfo RecognizableStructureContent Entity)
forall a. Monoid a => a
mempty Int
1)
([Name] -> FocusRing Name
forall n. [n] -> FocusRing n
focusRing ([Name] -> FocusRing Name) -> [Name] -> FocusRing Name
forall a b. (a -> b) -> a -> b
$ (StructureWidget -> Name) -> [StructureWidget] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map StructureWidget -> Name
StructureWidgets [StructureWidget]
forall a. (Enum a, Bounded a) => [a]
enumerate)