
On Fri, 6 Nov 2009, Petr Pudlak wrote:
Hi all,
(This is a literate Haskell post.)
I've encountered a small problem when trying to define a specialized monad instance. Maybe someone will able to help me or to tell me that it's impossible :-).
To elaborate: I wanted to define a data type which is a little bit similar to the [] monad. Instead of just having a list of possible outcomes of a computation, I wanted to have a probability associated with each possible outcome.
http://hackage.haskell.org/package/probability
A natural way to define such a structure is to use a map from possible values to numbers, let's say Floats:
module Distribution where
import qualified Data.Map as M
newtype Distrib a = Distrib { undistrib :: M.Map a Float }
Defining functions to get a monad instance is not difficult. "return" is just a singleton:
dreturn :: a -> Distrib a dreturn k = Distrib (M.singleton k 1)
Composition is a little bit more difficult, but the functionality is quite natural. (I welcome suggestions how to make the code nicer / more readable.) However, the exact definition is not so important.
dcompose :: (Ord b) => Distrib a -> (a -> Distrib b) -> Distrib b dcompose (Distrib m) f = Distrib $ M.foldWithKey foldFn M.empty m where foldFn a prob umap = M.unionWith (\psum p -> psum + prob * p) umap (undistrib $ f a)
The problem is the (Ord b) condition, which is required for the Map functions. When I try to define the monad instance as
This won't work and is the common problem of a Monad instance for Data.Set. http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros There is however an idea of how to solve this using existential quantification and type families: http://code.haskell.org/~thielema/category-constrained/src/Control/Constrain...