tcod-haskell-0.1.0.0: Bindings to libtcod roguelike engine

Safe HaskellNone
LanguageHaskell2010

Game.TCOD.MersenneTypes

Contents

Synopsis

Documentation

newtype TCODRandom Source #

Reference to TCOD pseudo random generator

Constructors

TCODRandom 

Fields

Instances

data Dice Source #

Dice roll

Constructors

Dice 

Instances

Eq Dice Source # 

Methods

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

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

Show Dice Source # 

Methods

showsPrec :: Int -> Dice -> ShowS #

show :: Dice -> String #

showList :: [Dice] -> ShowS #

Generic Dice Source # 

Associated Types

type Rep Dice :: * -> * #

Methods

from :: Dice -> Rep Dice x #

to :: Rep Dice x -> Dice #

type Rep Dice Source # 
type Rep Dice = D1 (MetaData "Dice" "Game.TCOD.Context" "tcod-haskell-0.1.0.0-9JdFGODCf32GFoGmrQ4wdi" False) (C1 (MetaCons "Dice" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "diceNbRolls") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Just Symbol "diceNbFaces") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "diceMultiplier") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Double)) (S1 (MetaSel (Just Symbol "diceAddSub") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Double)))))

data RandomAlgorithm Source #

Pseudo random number algorithm

Constructors

RngMT

a Mersenne twister generator

RngCMWC

a Complementary-Multiply-With-Carry generator.

Instances

Bounded RandomAlgorithm Source # 
Enum RandomAlgorithm Source # 
Eq RandomAlgorithm Source # 
Ord RandomAlgorithm Source # 
Read RandomAlgorithm Source # 
Show RandomAlgorithm Source # 
Generic RandomAlgorithm Source # 
type Rep RandomAlgorithm Source # 
type Rep RandomAlgorithm = D1 (MetaData "RandomAlgorithm" "Game.TCOD.MersenneTypes" "tcod-haskell-0.1.0.0-9JdFGODCf32GFoGmrQ4wdi" False) ((:+:) (C1 (MetaCons "RngMT" PrefixI False) U1) (C1 (MetaCons "RngCMWC" PrefixI False) U1))

data Distribution Source #

Random number distribution laws

Constructors

DistributionLinear

This is the default distribution. It will return a number from a range min-max. The numbers will be evenly distributed, ie, each number from the range has the exact same chance of being selected.

DistributionGaussian

This distribution does not have minimum and maximum values. Instead, a mean and a standard deviation are used. The mean is the central value. It will appear with the greatest frequency. The farther away from the mean, the less the probability of appearing the possible results have. Although extreme values are possible, 99.7% of the results will be within the radius of 3 standard deviations from the mean. So, if the mean is 0 and the standard deviation is 5, the numbers will mostly fall in the (-15,15) range.

DistributionGaussianRange

This one takes minimum and maximum values. Under the hood, it computes the mean (which falls right between the minimum and maximum) and the standard deviation and applies a standard Gaussian distribution to the values. The difference is that the result is always guaranteed to be in the min-max range.

DistributionGaussianInverse

Essentially, this is the same as DistributionGaussian. The difference is that the values near +3 and -3 standard deviations from the mean have the highest possibility of appearing, while the mean has the lowest.

DistributionGaussianRangeInverse

Essentially, this is the same as DistributionGaussianRange, but the min and max values have the greatest probability of appearing, while the values between them, the lowest.

Instances

Bounded Distribution Source # 
Enum Distribution Source # 
Eq Distribution Source # 
Ord Distribution Source # 
Read Distribution Source # 
Show Distribution Source # 
Generic Distribution Source # 

Associated Types

type Rep Distribution :: * -> * #

type Rep Distribution Source # 
type Rep Distribution = D1 (MetaData "Distribution" "Game.TCOD.MersenneTypes" "tcod-haskell-0.1.0.0-9JdFGODCf32GFoGmrQ4wdi" False) ((:+:) ((:+:) (C1 (MetaCons "DistributionLinear" PrefixI False) U1) (C1 (MetaCons "DistributionGaussian" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DistributionGaussianRange" PrefixI False) U1) ((:+:) (C1 (MetaCons "DistributionGaussianInverse" PrefixI False) U1) (C1 (MetaCons "DistributionGaussianRangeInverse" PrefixI False) U1))))

Orphan instances

Storable Dice Source # 

Methods

sizeOf :: Dice -> Int #

alignment :: Dice -> Int #

peekElemOff :: Ptr Dice -> Int -> IO Dice #

pokeElemOff :: Ptr Dice -> Int -> Dice -> IO () #

peekByteOff :: Ptr b -> Int -> IO Dice #

pokeByteOff :: Ptr b -> Int -> Dice -> IO () #

peek :: Ptr Dice -> IO Dice #

poke :: Ptr Dice -> Dice -> IO () #