Re: [Haskell-cafe] a problem defining a monad instance

2009-11-11 Thread Henning Thielemann


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/Constrained/Monad.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a problem defining a monad instance

2009-11-08 Thread Petr Pudlak
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe