
You cannot make it an instance of Monad, but you can use do syntax: {-# LANGUAGE NoImplicitPrelude #-} module Distribution where import Prelude hiding (return, (>>=)) import qualified Data.Map as M newtype Distrib a = Distrib { undistrib :: M.Map a Float } deriving Show return :: a -> Distrib a return k = Distrib (M.singleton k 1) (>>=) :: (Ord b) => Distrib a -> (a -> Distrib b) -> Distrib b 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) test = do a <- Distrib $ M.fromList [(1, 1), (2, 1)] b <- Distrib $ M.fromList [(10, 1), (20, 1)] return (a + b) Sjoerd On Nov 6, 2009, at 7:08 PM, 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.
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
instance Monad Distrib where return = dreturn (>>=) = dcompose
obviously, I get an error at (>>=): Could not deduce (Ord b) from the context.
Is there some way around? Either to somehow define the monad, or to achieve the same functionality without using Map, which requires Ord instances?
Thanks a lot, Petr _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher sjoerd@w3future.com