random-fu-0.2.7.6: Random number generation

Safe HaskellNone
LanguageHaskell2010

Data.Random.Distribution.Categorical

Synopsis

Documentation

data Categorical p a Source #

Categorical distribution; a list of events with corresponding probabilities. The sum of the probabilities must be 1, and no event should have a zero or negative probability (at least, at time of sampling; very clever users can do what they want with the numbers before sampling, just make sure that if you're one of those clever ones, you at least eliminate negative weights before sampling).

Instances
Fractional p => Monad (Categorical p) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

(>>=) :: Categorical p a -> (a -> Categorical p b) -> Categorical p b #

(>>) :: Categorical p a -> Categorical p b -> Categorical p b #

return :: a -> Categorical p a #

fail :: String -> Categorical p a #

Functor (Categorical p) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

fmap :: (a -> b) -> Categorical p a -> Categorical p b #

(<$) :: a -> Categorical p b -> Categorical p a #

Fractional p => Applicative (Categorical p) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

pure :: a -> Categorical p a #

(<*>) :: Categorical p (a -> b) -> Categorical p a -> Categorical p b #

liftA2 :: (a -> b -> c) -> Categorical p a -> Categorical p b -> Categorical p c #

(*>) :: Categorical p a -> Categorical p b -> Categorical p b #

(<*) :: Categorical p a -> Categorical p b -> Categorical p a #

Foldable (Categorical p) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

fold :: Monoid m => Categorical p m -> m #

foldMap :: Monoid m => (a -> m) -> Categorical p a -> m #

foldr :: (a -> b -> b) -> b -> Categorical p a -> b #

foldr' :: (a -> b -> b) -> b -> Categorical p a -> b #

foldl :: (b -> a -> b) -> b -> Categorical p a -> b #

foldl' :: (b -> a -> b) -> b -> Categorical p a -> b #

foldr1 :: (a -> a -> a) -> Categorical p a -> a #

foldl1 :: (a -> a -> a) -> Categorical p a -> a #

toList :: Categorical p a -> [a] #

null :: Categorical p a -> Bool #

length :: Categorical p a -> Int #

elem :: Eq a => a -> Categorical p a -> Bool #

maximum :: Ord a => Categorical p a -> a #

minimum :: Ord a => Categorical p a -> a #

sum :: Num a => Categorical p a -> a #

product :: Num a => Categorical p a -> a #

Traversable (Categorical p) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

traverse :: Applicative f => (a -> f b) -> Categorical p a -> f (Categorical p b) #

sequenceA :: Applicative f => Categorical p (f a) -> f (Categorical p a) #

mapM :: Monad m => (a -> m b) -> Categorical p a -> m (Categorical p b) #

sequence :: Monad m => Categorical p (m a) -> m (Categorical p a) #

(Fractional p, Ord p, Distribution Uniform p) => Distribution (Categorical p) a Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

rvar :: Categorical p a -> RVar a Source #

rvarT :: Categorical p a -> RVarT n a Source #

(Eq p, Eq a) => Eq (Categorical p a) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

(==) :: Categorical p a -> Categorical p a -> Bool #

(/=) :: Categorical p a -> Categorical p a -> Bool #

(Num p, Read p, Read a) => Read (Categorical p a) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

(Num p, Show p, Show a) => Show (Categorical p a) Source # 
Instance details

Defined in Data.Random.Distribution.Categorical

Methods

showsPrec :: Int -> Categorical p a -> ShowS #

show :: Categorical p a -> String #

showList :: [Categorical p a] -> ShowS #

categorical :: (Num p, Distribution (Categorical p) a) => [(p, a)] -> RVar a Source #

Construct a Categorical random variable from a list of probabilities and categories, where the probabilities all sum to 1.

categoricalT :: (Num p, Distribution (Categorical p) a) => [(p, a)] -> RVarT m a Source #

Construct a Categorical random process from a list of probabilities and categories, where the probabilities all sum to 1.

weightedCategorical :: (Fractional p, Eq p, Distribution (Categorical p) a) => [(p, a)] -> RVar a Source #

Construct a Categorical random variable from a list of weights and categories. The weights do not have to sum to 1.

weightedCategoricalT :: (Fractional p, Eq p, Distribution (Categorical p) a) => [(p, a)] -> RVarT m a Source #

Construct a Categorical random process from a list of weights and categories. The weights do not have to sum to 1.

fromList :: Num p => [(p, a)] -> Categorical p a Source #

Construct a Categorical distribution from a list of weighted categories.

toList :: Num p => Categorical p a -> [(p, a)] Source #

fromWeightedList :: (Fractional p, Eq p) => [(p, a)] -> Categorical p a Source #

Construct a Categorical distribution from a list of weighted categories, where the weights do not necessarily sum to 1.

fromObservations :: (Fractional p, Eq p, Ord a) => [a] -> Categorical p a Source #

Construct a Categorical distribution from a list of observed outcomes. Equivalent events will be grouped and counted, and the probabilities of each event in the returned distribution will be proportional to the number of occurrences of that event.

mapCategoricalPs :: (Num p, Num q) => (p -> q) -> Categorical p e -> Categorical q e Source #

Like fmap, but for the probabilities of a categorical distribution.

normalizeCategoricalPs :: (Fractional p, Eq p) => Categorical p e -> Categorical p e Source #

Adjust all the weights of a categorical distribution so that they sum to unity and remove all events whose probability is zero.

collectEvents :: (Ord e, Num p, Ord p) => Categorical p e -> Categorical p e Source #

Simplify a categorical distribution by combining equivalent events (the new event will have a probability equal to the sum of all the originals).

collectEventsBy :: Num p => (e -> e -> Ordering) -> ([(p, e)] -> (p, e)) -> Categorical p e -> Categorical p e Source #

Simplify a categorical distribution by combining equivalent events (the new event will have a weight equal to the sum of all the originals). The comparator function is used to identify events to combine. Once chosen, the events and their weights are combined by the provided probability and event aggregation function.