License | BSD3 |
---|---|
Maintainer | alpmestan@gmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Fun with finite distributions!
This all pretty much comes from Eric Kidd's series of blog posts at http://www.randomhacks.net/probability-monads/.
I have adapted it a bit by making it fit into my own random generation/sampling scheme.
The idea and purpose of this module should be clear after going
through an example. First, let's import the library and vector
.
import Math.Probable import qualified Data.Vector as V
We are going to talk about Books, and particularly about whether a given book is interesting or not.
data Book = Interesting | Boring deriving (Eq, Show)
Let's say we have very particular tastes, and that we think that only 20% of all books are interesting (that's not so small actually. oh well).
bookPrior :: Finite d => d Book bookPrior = weighted [ (Interesting, 0.2) , (Boring, 0.8) ]
weighted
belongs to the Finite
class, which represents
types that can somehow represent a distribution over a finite set.
That makes our distribution polymorphic in how we will use it. Awesome!
So how does it look?
λ> exact bookPrior -- in ghci [Event Interesting 20.0%,Event Boring 80.0%]
exact
takes Fin
a
and gives you the
inner list that Fin
uses to represent the distribution.
Now, what if we pick two books? First, how do we even do that?
Well, any instance of Finite
must be a Monad
, so you have your
good old do notation. The ones provided by this package also
provide Functor
and Applicative
instances, but let's use
do.
twoBooks :: Finite d => d (Book, Book) twoBooks = do book1 <- bookPrior book2 <- bookPrior return (book1, book2)
Nothing impressive. We pick a book with the prior we defined above, then another, pair them together and hand the pair back. What this will actually do is behave just like in the list monad, but in addition to this it will combine the probabilities of the various events we could be dealing with in the appropriate way.
So, how about we verify what I just said:
λ> exact twoBooks [ Event (Interesting,Interesting) 4.0% , Event (Interesting,Boring) 16.0% , Event (Boring,Interesting) 16.0% , Event (Boring,Boring) 64.0% ]
Nice! Let's take a look at a more complicated scenario now.
What if we wanted to take a look at the same distribution, with just a difference: we want at least one of the books to be an Interesting one.
oneInteresting :: Fin (Book, Book) oneInteresting = bayes $ do -- notice the call to bayes (b1, b2) <- twoBooks condition (b1 == Interesting || b2 == Interesting) return (b1, b2)
We get two books from the previous distribution, and use condition
to restrict the current distribution to the values of b1 and b2
that verify our condition. This lifts us in the FinBayes
type,
where our probabilistic computations can "fail" in some sense.
If you want to discard values and restrict the ones on which you'll
run further computations, use condition
.
However, how do we view the distribution now, without having all
those Maybe
s in the middle? That's what bayes
is for. It runs
the computations for the distribution and discards all the ones
where any condition
wasn't satisfied. In particular, it means
it hands you back a normal Fin
distribution.
If we run this one:
λ> exact oneInteresting [ Event (Interesting,Interesting) 11.1% , Event (Interesting,Boring) 44.4% , Event (Boring,Interesting) 44.4% ]
Note that these finite distribution types support random sampling too:
- If one of your distributions has a type like "Finite d => d X",
you can actually consider it as a
RandT
value, from which you can sample. - If you have a
Fin
distribution, you can useliftF
(liftFin
) to randomly sample an element from it, by more or less following the distribution's probabilities.
-- example of the former sampleBooks :: RandT IO (V.Vector Book) sampleBooks = vectorOf 10 bookPrior
λ> mwc sampleBooks fromList [Interesting,Boring,Boring,Boring,Boring ,Boring,Boring,Interesting,Boring,Boring]
λ> mwc $ listOf 4 (liftF oneInteresting) -- example of the latter [ (Boring,Interesting) , (Boring,Interesting) , (Boring,Interesting) , (Interesting,Boring) ]
- newtype P = P Double
- prob :: P -> Double
- data Event a = Event a !P
- never :: Event a
- newtype EventT m a = EventT {}
- class (Functor d, Monad d) => Finite d where
- type Fin = EventT []
- exact :: Fin a -> [Event a]
- uniformly :: Finite d => [a] -> d a
- liftF :: PrimMonad m => Fin a -> RandT m a
- type FinBayes = MaybeT Fin
- bayes :: FinBayes a -> Fin a
- condition :: Bool -> FinBayes ()
- onlyJust :: Fin (Maybe a) -> Fin a
Probability type
Probability type: wrapper around Double for a nicer Show instance and for more easily enforcing normalization of weights
Event
type
An event, and its probability
EventT
monad transformer
EventT
monad transformer
It pairs a value with a probability within the m
monad
Finite distributions: Finite
and Fin
class (Functor d, Monad d) => Finite d where Source #
T distribution of probabilities over a finite set.
Fin
is just 'EventT []'
You can think of 'Fin a' meaning '[Event a]'
i.e a list of the possible outcomes of type a
with their respective probability
exact :: Fin a -> [Event a] Source #
See the outcomes of a finite distribution and their probabilities
λ> exact $ uniformly [True, False] [Event True 50.0%,Event False 50.0%]
λ> data Fruit = Apple | Orange deriving (Eq, Show) λ> exact $ uniformly [Apple, Orange] [Event Apple 50.0%,Event Orange 50.0%]
λ> exact $ weighted [(Apple, 0.8), (Orange, 0.2)] [Event Apple 80.0%,Event Orange 20.0%]
uniformly :: Finite d => [a] -> d a Source #
Create a Finite
distribution over the values in
the list, each with an equal probability
λ> exact $ uniformly [True, False] [Event True 50.0%,Event False 50.0%]
liftF :: PrimMonad m => Fin a -> RandT m a Source #
Make finite distributions (Fin
) citizens of
RandT
by simply sampling an element at random
while still approximately preserving the distribution
λ> mwc . liftF $ uniformly [True, False] False λ> mwc . liftF $ uniformly [True, False] True λ> mwc . liftF $ weighted [("Haskell", 99), ("PHP", 1)] "Haskell"
Bayes' rule: FinBayes
type FinBayes = MaybeT Fin Source #
FinBayes
is Fin
with a MaybeT
layer
What is that for? The MaybeT
lets us express
the fact that what we've drawn from the distribution
isn't of interest anymore, using condition
,
and observing the remaining cases, using bayes
,
to get back to a normal finite distribution. Example:
data Wine = Good | Bad deriving (Eq, Show) wines :: Finite d => d Wine wines = weighted [(Good, 0.2), (Bad, 0.8)] twoWines :: Finite d => d (Wine, Wine) twoWines = (,) <*> wines <$> wines decentMeal :: FinBayes (Wine, Wine) decentMeal = do (wine1, wine2) <- twoWines -- we only consider the outcomes of 'twoWines' -- where at least one of the two wines is good -- because we're having a nice meal and are looking -- for a decent pair of wine condition (wine1 == Good || wine2 == Good) return (wine1, wine2) -- to view the distribution, applying -- Bayes' rule on our way: exact (bayes decentMeal)