
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

Petr Pudlak wrote:
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?
Not being allowed constraints on the variables for class methods is probably the problem I have most frequently run into recently in Haskell (is there any way to fix this, or does it open up a whole can of worms?). There is no easy way around it, but for your problem, do you require that the items be kept unique as you go along? Could you not use a list of items with probabilities -- that can potentially contain duplicate items (but all the summed probabilities should add to one at every stage, presumably), and then combine them at the end? i.e. your code would look like: newtype Distrib a = Distrib { undistrib :: [(a, Float)] } runDistrib :: Ord a => Distrib a -> Map.Map a Float runDistrib = Map.fromListWith (+) . undistrib This would push the Ord constraint to runDistrib, and allow you to leave it off (>>=). Neil.

On Fri, Nov 6, 2009 at 10:19 AM, Neil Brown
Petr Pudlak wrote:
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?
Not being allowed constraints on the variables for class methods is probably the problem I have most frequently run into recently in Haskell (is there any way to fix this, or does it open up a whole can of worms?).
I believe this paper is intended to propose a solution: http://tomschrijvers.blogspot.com/2009/11/haskell-type-constraints-unleashed... Jason

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

The usual continuation trick: fromDistrib :: Ord a => Distrib a -> Cont (Distrib r) a fromDistrib da = Cont (\c -> dcompose da c) toDistrib :: Cont (Distrib r) r -> Distrib r toDistrib (Cont f) = f dreturn "Cont anything" is a monad. On 6 Nov 2009, at 21:08, 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

Petr Pudlak wrote:
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.
This is the same reason we do not have e.g. a Monad instance for Set. One solution is a concept of "restricted" monads, and one implementation of restricted monads is given here: http://okmij.org/ftp/Haskell/types.html#restricted-datatypes - Jake

On Fri, Nov 06, 2009 at 07:08:10PM +0100, 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 :-).
See the rmonad package on Hackage, which solves exactly this problem: http://hackage.haskell.org/package/rmonad -Brent

Hi, thanks to all for all the helpful answers and references. Maybe I'll try to collect them into a wiki page, if I have time. It looks like that I'm not the only one facing this problem and many people know different tricks how to handle it. Yes, I was thinking about using lists of pairs instead of Maps. But since I expect to have just a little distinct elements, but many >>= operations, lists would probably grow to an enormous sizes, while Maps will remain quite small. The most intriguing idea for me was wrapping my pseudo-monad into the continuation monad. I didn't have time to think it over, but I wondered if the same (or similar) trick could be used to applicative functors (which are not monads) or arrows. (I found out that J. Hughes faced a similar problem in his paper "Programming with Arrows" (p.42), but not with monads but arrows.) Now I can enjoy playing with probabilities :-). Maybe having complex numbers instead of Floats in the Distrib type would be a nice way how to simulate (at least some) quantum computations. RMonad also seems quite promising, and it looks like a more general solution, but I had no time to try it out yet. With best regards, Petr On Fri, Nov 06, 2009 at 07:08:10PM +0100, 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

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...
participants (8)
-
Brent Yorgey
-
Henning Thielemann
-
Jake McArthur
-
Jason Dagit
-
Miguel Mitrofanov
-
Neil Brown
-
Petr Pudlak
-
Sjoerd Visscher