LambdaHack-0.10.2.0: A game engine library for tactical squad ASCII roguelike dungeon crawlers
Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Server.HandleEffectM

Description

Handle effects. They are most often caused by requests sent by clients but sometimes also caused by projectiles or periodically activated items.

Synopsis

Documentation

data EffToUse Source #

Instances

Instances details
Eq EffToUse Source # 
Instance details

Defined in Game.LambdaHack.Server.HandleEffectM

dropAllEquippedItems :: MonadServerAtomic m => ActorId -> Actor -> m () Source #

Drop all actor's equipped items.

dropCStoreItem :: MonadServerAtomic m => Bool -> Bool -> CStore -> ActorId -> Actor -> Int -> ItemId -> ItemQuant -> m UseResult Source #

Drop a single actor's item (though possibly multiple copies). Note that if there are multiple copies, at most one explodes to avoid excessive carnage and UI clutter (let's say, the multiple explosions interfere with each other or perhaps larger quantities of explosives tend to be packaged more safely). Note also that OnSmash effects are activated even if item discharged.

Internal operations

itemEffectDisco :: MonadServerAtomic m => EffApplyFlags -> ActorId -> ActorId -> ItemId -> ContentId ItemKind -> ItemKind -> Container -> [Effect] -> m UseResult Source #

The source actor affects the target actor, with a given item. If any of the effects fires up, the item gets identified. Even using raw damage (beating the enemy with the magic wand, for example) identifies the item. This means a costly UpdDiscover is processed for each random timeout weapon hit and for most projectiles, but at least not for most explosion particles nor plain organs. And if not needed, the UpdDiscover are eventually not sent to clients. So, enemy missiles that hit us are no longer mysterious until picked up, which is for the better, because the client knows their charging status and so can generate accurate messages in the case when not recharged. This also means that thrown consumables in flasks sturdy enough to cause damage are always identified at hit, even if no effect activated. So throwing them at foes is a better identification method than applying.

Note that if we activate a durable non-passive item, e.g., a spiked shield, from the ground, it will get identified, which is perfectly fine, until we want to add sticky armor that can't be easily taken off (and, e.g., has some maluses).

effectSem :: MonadServerAtomic m => EffApplyFlags -> ActorId -> ActorId -> ItemId -> Container -> Effect -> m UseResult Source #

Source actor affects target actor, with a given effect and it strength. Both actors are on the current level and can be the same actor. The item may or may not still be in the container.

effectEscape :: MonadServerAtomic m => m () -> ActorId -> ActorId -> m UseResult Source #

The faction leaves the dungeon.

effectParalyze :: MonadServerAtomic m => m () -> Dice -> ActorId -> ActorId -> m UseResult Source #

Advance target actor time by this many time clips. Not by actor moves, to hurt fast actors more.

effectParalyzeInWater :: MonadServerAtomic m => m () -> Dice -> ActorId -> ActorId -> m UseResult Source #

Advance target actor time by this many time clips. Not by actor moves, to hurt fast actors more. Due to water, so resistable.

effectInsertMove :: MonadServerAtomic m => m () -> Dice -> ActorId -> ActorId -> m UseResult Source #

Give target actor the given number of tenths of extra move. Don't give an absolute amount of time units, to benefit slow actors more.

effectTeleport :: MonadServerAtomic m => m () -> Dice -> ActorId -> ActorId -> m UseResult Source #

Teleport the target actor. Note that projectiles can be teleported, too, for extra fun.

effectDestroyItem :: MonadServerAtomic m => m () -> Int -> Int -> CStore -> ActorId -> GroupName ItemKind -> m UseResult Source #

Make the target actor destroy items in a store from the given group. The item that caused the effect itself is *not* immune, because often the item needs to destroy itself, e.g., to model wear and tear. In such a case, the item may need to be identified, in a container, when it no longer exists, at least in the container. This is OK. Durable items are not immune, unlike the tools in ConsumeItems.

effectDropItem :: MonadServerAtomic m => m () -> ItemId -> Int -> Int -> CStore -> GroupName ItemKind -> ActorId -> m UseResult Source #

Make the target actor drop items in a store from the given group. The item that caused the effect itself is immune (any copies).

effectConsumeItems :: MonadServerAtomic m => m () -> ItemId -> ActorId -> [(Int, GroupName ItemKind)] -> [(Int, GroupName ItemKind)] -> m UseResult Source #

Make the target actor destroy the given items, if all present, or none at all, if any is missing. To be used in crafting. The item that caused the effect itself is not considered (any copies).

effectRecharge :: forall m. MonadServerAtomic m => Bool -> m () -> ItemId -> Int -> Dice -> ActorId -> m UseResult Source #

effectDetectX :: MonadServerAtomic m => DetectKind -> (Point -> Bool) -> ([Point] -> m Bool) -> m () -> Int -> ActorId -> m UseResult Source #

effectSendFlying :: MonadServerAtomic m => m () -> ThrowMod -> ActorId -> ActorId -> Container -> Maybe Bool -> m UseResult Source #

Send the target actor flying like a projectile. If the actors are adjacent, the vector is directed outwards, if no, inwards, if it's the same actor, boldpos is used, if it can't, a random outward vector of length 10 is picked.