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

Game.LambdaHack.Core.Dice

Description

Representation of dice scaled with current level depth.

Synopsis

Frequency distribution for casting dice scaled with level depth

data Dice Source #

Multiple dice rolls, some scaled with current level depth, in which case the sum of all rolls is scaled in proportion to current depth divided by maximal dungeon depth.

The simple dice should have positive number of rolls and number of sides.

The Num instance doesn't have abs nor signum defined, because the functions for computing infimum, supremum and mean dice results would be too costly.

Instances

Instances details
Eq Dice Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

Methods

(==) :: Dice -> Dice -> Bool #

(/=) :: Dice -> Dice -> Bool #

Num Dice Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

Methods

(+) :: Dice -> Dice -> Dice #

(-) :: Dice -> Dice -> Dice #

(*) :: Dice -> Dice -> Dice #

negate :: Dice -> Dice #

abs :: Dice -> Dice #

signum :: Dice -> Dice #

fromInteger :: Integer -> Dice #

Show Dice Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

Methods

showsPrec :: Int -> Dice -> ShowS #

show :: Dice -> String #

showList :: [Dice] -> ShowS #

newtype AbsDepth Source #

Absolute depth in the dungeon. When used for the maximum depth of the whole dungeon, this can be different than dungeon size, e.g., when the dungeon is branched, and it can even be different than the length of the longest branch, if levels at some depths are missing.

Constructors

AbsDepth Int 

Instances

Instances details
Eq AbsDepth Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

Ord AbsDepth Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

Show AbsDepth Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

Binary AbsDepth Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

Methods

put :: AbsDepth -> Put #

get :: Get AbsDepth #

putList :: [AbsDepth] -> Put #

castDice :: forall m. Monad m => ((Int, Int) -> m Int) -> AbsDepth -> AbsDepth -> Dice -> m Int Source #

Cast dice scaled with current level depth. When scaling, we round up, so that the value of 1 dL 1 is 1 even at the lowest level, but so is the value of 1 dL depth.

The implementation calls RNG as many times as there are dice rolls, which is costly, so content should prefer to cast fewer dice and then multiply them by a constant. If rounded results are not desired (often they are, to limit the number of distinct item varieties in inventory), another dice may be added to the result.

A different possible implementation, with dice represented as Frequency, makes only one RNG call per dice, but due to lists lengths proportional to the maximal value of the dice, it's is intractable for 1000d1000 and problematic already for 100d100.

d :: Int -> Int -> Dice Source #

A die, rolled the given number of times. E.g., 1 d 2 rolls 2-sided die one time.

dL :: Int -> Int -> Dice Source #

A die rolled the given number of times, with the result scaled with dungeon level depth.

z :: Int -> Int -> Dice Source #

A die, starting from zero, ending at one less than second argument, rolled the given number of times. E.g., 1 z 1 always rolls zero.

zL :: Int -> Int -> Dice Source #

A die, starting from zero, ending at one less than second argument, rolled the given number of times, with the result scaled with dungeon level depth.

infsupDice :: Dice -> (Int, Int) Source #

Minimal and maximal possible value of the dice.

divUp in the implementation corresponds to ceiling, applied to results of meanDice elsewhere in the code, and prevents treating 1d1-power effects (on shallow levels) as null effects.

supDice :: Dice -> Int Source #

Maximal value of dice. The scaled part taken assuming median level.

infDice :: Dice -> Int Source #

Minimal value of dice. The scaled part taken assuming median level.

meanDice :: Dice -> Double Source #

Mean value of dice. The scaled part taken assuming median level, but not taking into account rounding up, and so too low, especially for dice small compared to depth. To fix this, depth would need to be taken as argument.

Dice for rolling a pair of integer parameters representing coordinates.

data DiceXY Source #

Dice for rolling a pair of integer parameters pertaining to, respectively, the X and Y cartesian 2D coordinates.

Constructors

DiceXY Dice Dice 

Instances

Instances details
Show DiceXY Source # 
Instance details

Defined in Game.LambdaHack.Core.Dice

supDiceXY :: DiceXY -> (Int, Int) Source #

Maximal value of DiceXY.

infDiceXY :: DiceXY -> (Int, Int) Source #

Minimal value of DiceXY.