Safe Haskell | None |
---|---|
Language | Haskell2010 |
Client-specific game state components.
Synopsis
- data StateClient = StateClient {
- seps :: Int
- stargetD :: EnumMap ActorId TgtAndPath
- sfleeD :: EnumMap ActorId (Point, Time)
- sexplored :: EnumSet LevelId
- sbfsD :: EnumMap ActorId BfsAndPath
- sundo :: ()
- sdiscoBenefit :: DiscoveryBenefit
- sfper :: PerLid
- salter :: AlterLid
- srandom :: SMGen
- _sleader :: Maybe ActorId
- _sside :: FactionId
- squit :: Bool
- scurChal :: Challenge
- snxtChal :: Challenge
- smarkSuspect :: Int
- scondInMelee :: EnumMap LevelId Bool
- svictories :: EnumMap (ContentId ModeKind) (Map Challenge Int)
- scampings :: EnumSet (ContentId ModeKind)
- srestarts :: EnumSet (ContentId ModeKind)
- soptions :: ClientOptions
- stabs :: (PrimArray PointI, PrimArray PointI)
- type AlterLid = EnumMap LevelId (Array Word8)
- data BfsAndPath
- data TgtAndPath = TgtAndPath {}
- data Target
- data TGoal
- emptyStateClient :: FactionId -> StateClient
- cycleMarkSuspect :: StateClient -> StateClient
- updateTarget :: ActorId -> (Maybe Target -> Maybe Target) -> StateClient -> StateClient
- getTarget :: ActorId -> StateClient -> Maybe Target
- updateLeader :: ActorId -> State -> StateClient -> StateClient
- sside :: StateClient -> FactionId
- sleader :: StateClient -> Maybe ActorId
Documentation
data StateClient Source #
Client state, belonging to a single faction.
StateClient | |
|
Instances
Show StateClient Source # | |
Defined in Game.LambdaHack.Client.State showsPrec :: Int -> StateClient -> ShowS # show :: StateClient -> String # showList :: [StateClient] -> ShowS # | |
Binary StateClient Source # | |
Defined in Game.LambdaHack.Client.State |
data BfsAndPath Source #
Pathfinding distances to all reachable positions of an actor and a shortest paths to some of the positions.
Instances
Show BfsAndPath Source # | |
Defined in Game.LambdaHack.Client.State showsPrec :: Int -> BfsAndPath -> ShowS # show :: BfsAndPath -> String # showList :: [BfsAndPath] -> ShowS # |
data TgtAndPath Source #
Actor's target and a path to it, if any.
Instances
Show TgtAndPath Source # | |
Defined in Game.LambdaHack.Client.State showsPrec :: Int -> TgtAndPath -> ShowS # show :: TgtAndPath -> String # showList :: [TgtAndPath] -> ShowS # | |
Generic TgtAndPath Source # | |
Defined in Game.LambdaHack.Client.State type Rep TgtAndPath :: Type -> Type # from :: TgtAndPath -> Rep TgtAndPath x # to :: Rep TgtAndPath x -> TgtAndPath # | |
Binary TgtAndPath Source # | |
Defined in Game.LambdaHack.Client.State | |
type Rep TgtAndPath Source # | |
Defined in Game.LambdaHack.Client.State type Rep TgtAndPath = D1 ('MetaData "TgtAndPath" "Game.LambdaHack.Client.State" "LambdaHack-0.10.2.0-inplace" 'False) (C1 ('MetaCons "TgtAndPath" 'PrefixI 'True) (S1 ('MetaSel ('Just "tapTgt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Target) :*: S1 ('MetaSel ('Just "tapPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe AndPath)))) |
The type of na actor target.
TEnemy ActorId | target an enemy |
TNonEnemy ActorId | target a friend or neutral |
TPoint TGoal LevelId Point | target a concrete spot |
TVector Vector | target position relative to actor |
Instances
The goal of an actor.
TStash FactionId | shared inventory stash of our or an enemy faction |
TEnemyPos ActorId | last seen position of the targeted actor |
TEmbed ItemBag Point | embedded item that can be triggered;
in |
TItem ItemBag | item lying on the ground |
TSmell | smell potentially left by enemies |
TBlock | a blocking tile to be approached (and, e.g., revealed to be walkable or altered or searched) |
TUnknown | an unknown tile to be explored |
TKnown | a known tile to be patrolled |
THideout | a hideout to either flee to or find a hidden enemy sniper in |
Instances
emptyStateClient :: FactionId -> StateClient Source #
Initial empty game client state.
cycleMarkSuspect :: StateClient -> StateClient Source #
Cycle the smarkSuspect
setting.
updateTarget :: ActorId -> (Maybe Target -> Maybe Target) -> StateClient -> StateClient Source #
Update target parameters within client state.
getTarget :: ActorId -> StateClient -> Maybe Target Source #
Get target parameters from client state.
updateLeader :: ActorId -> State -> StateClient -> StateClient Source #
Update picked leader within state. Verify actor's faction.
sside :: StateClient -> FactionId Source #