Re: [Haskell-cafe] Monads with "The" contexts?

The bad news is that indeed you don't seem to be able to do what you want. The good news: yes, you can. The enclosed code does exactly what you wanted:
sunPerMars :: NonDet Double sunPerMars = (/) <$> sunMass <*> marsMass
sunPerMars_run = runShare sunPerMars sunPerMars_run_len = length sunPerMars_run -- 27
where earthMass, sunMass, marsMass are all top-level bindings, which can be defined in separate and separately-compiled modules. Let's start with the bad news however. Recall the original problem:
earthMass, sunMass, marsMass :: [Double] earthMass = [5.96e24, 5.97e24, 5.98e24] sunMass = (*) <$> [2.5e5, 3e5, 4e5] <*> earthMass marsMass = (*) <$> [0.01, 0.1, 1.0] <*> earthMass
The problem was that the computation sunPerMars = (/) <$> sunMass <*> marsMass produces too many answers, because earthMass in sunMass and earthMass in marsMass were independent non-deterministic computations. Thus the code says: we measure the earthMass to compute sunMass, and we measure earthMass again to compute marsMass. Each earthMass measurement is independent and gives us, in general, a different value. However, we wanted the code to behave differently. We wanted to measure earthMass only once, and use the same measured value to compute masses of other bodies. There does not seem to be a way to do that in Haskell. Haskell is pure, so we can substitute equals for equals. earthMass is equal to [5.96e24, 5.97e24, 5.98e24]. Thus the meaning of program should not change if we write
sunMass = (*) <$> [2.5e5, 3e5, 4e5] <*> [5.96e24, 5.97e24, 5.98e24] marsMass = (*) <$> [0.01, 0.1, 1.0] <*> [5.96e24, 5.97e24, 5.98e24]
which gives exactly the wrong behavior (and 81 answers for sunPerMars, as easy to see). Thus there is no hope that the original code should behave any differently.
I don't know if memo can solve this problem. I have to test. Is the `memo` in your JFP paper section 4.2 Memoization, a psuedo-code? (What is type `Thunk` ?) and seems like it's not in explicit-sharing hackage.
BTW, the memo in Hansei is different from the memo in the JFP paper. In JFP, memo is a restricted version of share: memo_jfp :: m a -> m (m a) In Hansei, memo is a generalization of share: memo_hansei :: (a -> m b) -> m (a -> m b) You will soon need that generalization (which is not mention in the JFP paper). Given such a let-down, is there any hope at all? Recall, if Haskell doesn't do what you want, embed a language that does. The solution becomes straightforward then. (Please see the enclosed code). Exercise: how does the approach in the code relate to the approaches to sharing explained in http://okmij.org/ftp/tagless-final/sharing/sharing.html Good luck with the contest! {-# LANGUAGE FlexibleContexts, DeriveDataTypeable #-} -- Sharing of top-level bindings -- Solving Takayuki Muranushi's problem -- http://www.haskell.org/pipermail/haskell-cafe/2012-July/102287.html module TopSharing where import qualified Data.Map as M import Control.Monad.State import Data.Dynamic import Control.Applicative -- Let's pretend this is one separate module. -- It exports earthMass, the mass of the Earth, which -- is a non-deterministic computation producing Double. -- The non-determinism reflects our uncertainty about the mass. -- Exercise: why do we need the seemingly redundant EarthMass -- and deriving Typeable? -- Could we use TemplateHaskell instead? data EarthMass deriving Typeable earthMass :: NonDet Double earthMass = memoSta (typeOf (undefined::EarthMass)) $ msum $ map return [5.96e24, 5.97e24, 5.98e24] -- Let's pretend this is another separate module -- It imports earthMass and exports sunMass -- Muranushi: ``Let's also pretend that we can measure the other -- bodies' masses only by their ratio to the Earth mass, and -- the measurements have large uncertainties.'' data SunMass deriving Typeable sunMass :: NonDet Double sunMass = memoSta (typeOf (undefined::SunMass)) mass where mass = (*) <$> proportion <*> earthMass proportion = msum $ map return [2.5e5, 3e5, 4e5] -- Let's pretend this is yet another separate module -- It imports earthMass and exports marsMass data MarsMass deriving Typeable marsMass :: NonDet Double marsMass = memoSta (typeOf (undefined::MarsMass)) mass where mass = (*) <$> proportion <*> earthMass proportion = msum $ map return [0.01, 0.1, 1.0] -- This is the main module, importing the masses of the three bodies -- It computes ``how many Mars mass object can we create -- by taking the sun apart?'' -- This code is exactly the same as in Takayuki Muranushi's message -- His question: ``Is there a way to represent this? -- For example, can we define earthMass'' , sunMass'' , marsMass'' all -- in separate modules, and yet have (length $ sunPerMars'' == 27) ? sunPerMars :: NonDet Double sunPerMars = (/) <$> sunMass <*> marsMass sunPerMars_run = runShare sunPerMars sunPerMars_run_len = length sunPerMars_run -- 27 -- The following is essentially Control.Monad.Sharing.Memoization -- with one important addition -- Can you spot the important addition? type NonDet a = StateT FirstClassStore [] a data Key = KeyDyn Int | KeySta TypeRep deriving (Show, Ord, Eq) -- I wish TypeRep were in Ord by default. The implementation permits that! instance Ord TypeRep where compare x y = compare (show x) (show y) data FirstClassStore = FirstClassStore { freshKey :: Int, store :: M.Map Key Dynamic } emptyStore :: FirstClassStore emptyStore = FirstClassStore { freshKey = 1, store = M.empty } getFreshKey :: MonadState FirstClassStore m => m Key getFreshKey = do key <- gets freshKey modify (\s -> s { freshKey = succ key }) return (KeyDyn key) insertVal :: (Typeable a, MonadState FirstClassStore m) => Key -> a -> m () insertVal key val = modify (\s -> s { store = M.insert key (toDyn val) (store s) }) lookupVal :: (Typeable a, MonadState FirstClassStore m) => Key -> m (Maybe a) lookupVal key = liftM (liftM (flip fromDyn err) . M.lookup key) (gets store) where err = error $ "lookupVal: bad key " ++ show key memo :: (Typeable a, MonadState FirstClassStore m) => m a -> m (m a) memo a = getFreshKey >>= \key -> return (memoKey key a) memoSta :: (Typeable a, MonadState FirstClassStore m) => TypeRep -> m a -> m a memoSta trep a = memoKey (KeySta trep) a memoKey :: (Typeable a, MonadState FirstClassStore m) => Key -> m a -> m a memoKey key a = do valM <- lookupVal key case valM of Just x -> return x Nothing -> do x <- a insertVal key $! x return x runShare :: Monad m => StateT FirstClassStore m a -> m a runShare m = evalStateT m emptyStore -- In My GHC, StateT is still not an Applicative. More bolierplate instance Monad m => Applicative (StateT s m) where pure = return (<*>) = liftM2 ($)

Thank you Oleg, for your detailed instructions! First, let me clarify my problem here (in sacrifice of physical accuracy.) c.f. Wrong.hs .
earthMass, sunMass, marsMass :: [Double] earthMass = [1,10,100] sunMass = (*) <$> [9,10,11] <*> earthMass marsMass = (*) <$> [0.09,0.1,0.11] <*> earthMass
sunPerMars = (/) <$> sunMass <*> marsMass sunPerMars_range = (minimum sunPerMars, maximum sunPerMars)
sunPerMars_range gives> (0.8181818181818182,12222.222222222223)
These extreme answers close to 1 or 10000 are inconsistent in sense that they used different Earth mass value for calculating Sun and Mars mass. Factoring out Earth mass is perfect and efficient solution in this case, but is not always viable when more complicated functions are involved. We want to remove such inconsistency.
-- Exercise: why do we need the seemingly redundant EarthMass -- and deriving Typeable? -- Could we use TemplateHaskell instead?
Aha! you use the Types as unique keys that resides in "The" context. Smart! To understand this, I have made MassStr.hs, which essentially does the same thing with more familiar type Strings. Of course using Strings are naive and collision-prone approach. Printing `stateAfter` shows pretty much what have happened. I'll remember that we can use Types as global identifiers.
-- The following is essentially Control.Monad.Sharing.Memoization -- with one important addition -- Can you spot the important addition?
type NonDet a = StateT FirstClassStore [] a data Key = KeyDyn Int | KeySta TypeRep deriving (Show, Ord, Eq)
Hmm, I don't see what Control.Monad.Sharing.Memoization is; googling https://www.google.co.jp/search?q=Control.Monad.Sharing.Memoization gives our conversation at the top. If it's Memo in chapter 4.2 of your JFP paper, the difference I see is that you used Data.Set here instead of list of pairs for better efficiency.
Exercise: how does the approach in the code relate to the approaches to sharing explained in http://okmij.org/ftp/tagless-final/sharing/sharing.html
Chapter 3 introduces an implicit impure counter, and Chapter 4 uses a database that is passed around. let_ in Chapter 5 of sharing.pdf realizes the sharing with sort of continuation-passing style.The unsafe counter works across the module (c.f. counter.zip) but is generally unpredictable... Now I'm on to the next task; how we represent continuous probability distributions? The existing libraries: http://hackage.haskell.org/package/probability-0.2.4 http://hackage.haskell.org/package/ProbabilityMonads-0.1.0 Seemingly have restricted themselves to discrete distributions, or at least providing Random support for Monte-Carlo simulations. There's some hope; I guess Gaussian distributions form a Monad provided that 1. the standard deviations you are dealing with are small compared to the scale you deal with, and 2. the monadic functions are differentiable. Maybe I can use non-standard analysis and automatic differentiation; maybe I can resort to numerical differentiation; maybe I just give up and be satisfied with random sampling. I have to try first; then finally we can abstract upon different approaches. Also, I can start writing my Knowledge libraries from the part our knowledge is so accurate enough that the deviations are negligible (such as Earth mass!) P.S. extra spaces may have annoyed you. I'm sorry for that. My keyboard is chattering badly now; I have to update him soon. Best wishes, -- Takayuki MURANUSHI The Hakubi Center for Advanced Research, Kyoto University http://www.hakubi.kyoto-u.ac.jp/02_mem/h22/muranushi.html

Done with some exercises on Gaussian distribution as a monad!
http://en.pk.paraiso-lang.org/Haskell/Monad-Gaussian
What do you think? Will this be a good approach or bad?
Also this is the first page in my attempt to create runnable, and even
testable wiki pages. To run the tests, please use
hackage.haskell.org/package/doctest .
2012/7/18 Takayuki Muranushi
Thank you Oleg, for your detailed instructions!
First, let me clarify my problem here (in sacrifice of physical accuracy.) c.f. Wrong.hs .
earthMass, sunMass, marsMass :: [Double] earthMass = [1,10,100] sunMass = (*) <$> [9,10,11] <*> earthMass marsMass = (*) <$> [0.09,0.1,0.11] <*> earthMass
sunPerMars = (/) <$> sunMass <*> marsMass sunPerMars_range = (minimum sunPerMars, maximum sunPerMars)
sunPerMars_range gives> (0.8181818181818182,12222.222222222223)
These extreme answers close to 1 or 10000 are inconsistent in sense that they used different Earth mass value for calculating Sun and Mars mass. Factoring out Earth mass is perfect and efficient solution in this case, but is not always viable when more complicated functions are involved.
We want to remove such inconsistency.
-- Exercise: why do we need the seemingly redundant EarthMass -- and deriving Typeable? -- Could we use TemplateHaskell instead?
Aha! you use the Types as unique keys that resides in "The" context. Smart! To understand this, I have made MassStr.hs, which essentially does the same thing with more familiar type Strings. Of course using Strings are naive and collision-prone approach. Printing `stateAfter` shows pretty much what have happened.
I'll remember that we can use Types as global identifiers.
-- The following is essentially Control.Monad.Sharing.Memoization -- with one important addition -- Can you spot the important addition?
type NonDet a = StateT FirstClassStore [] a data Key = KeyDyn Int | KeySta TypeRep deriving (Show, Ord, Eq)
Hmm, I don't see what Control.Monad.Sharing.Memoization is; googling https://www.google.co.jp/search?q=Control.Monad.Sharing.Memoization gives our conversation at the top.
If it's Memo in chapter 4.2 of your JFP paper, the difference I see is that you used Data.Set here instead of list of pairs for better efficiency.
Exercise: how does the approach in the code relate to the approaches to sharing explained in http://okmij.org/ftp/tagless-final/sharing/sharing.html
Chapter 3 introduces an implicit impure counter, and Chapter 4 uses a database that is passed around. let_ in Chapter 5 of sharing.pdf realizes the sharing with sort of continuation-passing style.The unsafe counter works across the module (c.f. counter.zip) but is generally unpredictable...
Now I'm on to the next task; how we represent continuous probability distributions? The existing libraries:
http://hackage.haskell.org/package/probability-0.2.4 http://hackage.haskell.org/package/ProbabilityMonads-0.1.0
Seemingly have restricted themselves to discrete distributions, or at least providing Random support for Monte-Carlo simulations. There's some hope; I guess Gaussian distributions form a Monad provided that 1. the standard deviations you are dealing with are small compared to the scale you deal with, and 2. the monadic functions are differentiable.
Maybe I can use non-standard analysis and automatic differentiation; maybe I can resort to numerical differentiation; maybe I just give up and be satisfied with random sampling. I have to try first; then finally we can abstract upon different approaches.
Also, I can start writing my Knowledge libraries from the part our knowledge is so accurate enough that the deviations are negligible (such as Earth mass!)
P.S. extra spaces may have annoyed you. I'm sorry for that. My keyboard is chattering badly now; I have to update him soon.
Best wishes,

http://en.pk.paraiso-lang.org/Haskell/Monad-Gaussian What do you think? Will this be a good approach or bad?
I don't think it is a Monad (or even restricted monad, see below). Suppose G a is a `Gaussian' monad and n :: G Double is a random number with the Gaussian (Normal distribution). Then (\x -> x * x) `fmap` n is a random number with the chi-square distribution (of the degree of freedom 1). Chi-square is _not_ a normal distribution. Perhaps a different example is clearer: (\x -> if x > 0 then 1.0 else 0.0) `fmap` n has also the type G Double but obviously does not have the normal distribution (since that random variable is discrete). There are other problems
Let's start with some limitation; we restrict ourselves to Gaussian distributions and assume that the standard deviations are small compared to the scales we deal with.
That assumption is not stated in types and it is hard to see how can we enforce it. Nothing prevents us from writing liftM2 n n in which case the variance will no longer be small compared with the mean. Just a technical remark: The way G a is written, it is a so-called restricted monad, which is not a monad (the adjective `restricted' is restrictive here). http://okmij.org/ftp/Haskell/types.html#restricted-datatypes

Dear Oleg, You're right. The points boil down to
That assumption (that the deviations are small) is not stated in types and it is hard to see how can we enforce it. and even if it's small, there's corner cases at df/dx = 0 or df/dx = infinity (as you have mentioned.)
Thanks to your advices, I'll look for other ways to set up
probabilistic computations.
2012/7/19
http://en.pk.paraiso-lang.org/Haskell/Monad-Gaussian What do you think? Will this be a good approach or bad?
I don't think it is a Monad (or even restricted monad, see below). Suppose G a is a `Gaussian' monad and n :: G Double is a random number with the Gaussian (Normal distribution). Then (\x -> x * x) `fmap` n is a random number with the chi-square distribution (of the degree of freedom 1). Chi-square is _not_ a normal distribution. Perhaps a different example is clearer:
(\x -> if x > 0 then 1.0 else 0.0) `fmap` n
has also the type G Double but obviously does not have the normal distribution (since that random variable is discrete).
There are other problems
Let's start with some limitation; we restrict ourselves to Gaussian distributions and assume that the standard deviations are small compared to the scales we deal with.
That assumption is not stated in types and it is hard to see how can we enforce it. Nothing prevents us from writing liftM2 n n in which case the variance will no longer be small compared with the mean.
Just a technical remark: The way G a is written, it is a so-called restricted monad, which is not a monad (the adjective `restricted' is restrictive here). http://okmij.org/ftp/Haskell/types.html#restricted-datatypes
-- Takayuki MURANUSHI The Hakubi Center for Advanced Research, Kyoto University http://www.hakubi.kyoto-u.ac.jp/02_mem/h22/muranushi.html

Exercise: how does the approach in the code relate to the approaches to sharing explained in http://okmij.org/ftp/tagless-final/sharing/sharing.html
Chapter 3 introduces an implicit impure counter, and Chapter 4 uses a database that is passed around. let_ in Chapter 5 of sharing.pdf realizes the sharing with sort of continuation-passing style.The unsafe counter works across the module (c.f. counter.zip) but is generally unpredictable...
The reason sharing has the type m a -> m (m a) rather than m a -> m a is the fact new calculations to share may be created dynamically. Therefore, we need a supply of keys (gensym). We count on the monad m to provide the supply. However, top-level computations (bound to top-level identifiers) are created only once, at the initialization time. Therefore, a static assignment of identifiers will suffice. The static assignment is similar to the manual label assignment technique -- the first technique described Sec 3 of the sharing.pdf paper. John T. O'Donnell has automated this manual assignment using TH.
Now I'm on to the next task; how we represent continuous probability distributions? The existing libraries:
Seemingly have restricted themselves to discrete distributions, or at least providing Random support for Monte-Carlo simulations.
I must warn that although it is ridiculously easy to implement MonadProb in Haskell, the result is not usable. Try to implement HMM with any of the available MonadProb and see how well it scales. (Hint: we want the linear time scaling as we evolve the model -- not exponential). There is a *huge* gap between a naive MonadProb and something that could be used even for passingly interesting problems. We need support for so-called `variable elimination'. We need better sampling procedures: rejection sampling is better forgotten. Finally, GHC is actually not a very good language system for probabilistic programming of generative-model--variety. See http://okmij.org/ftp/Haskell/index.html#memo-off for details. To give you the flavor of difficulties, consider a passingly interesting target tracking problem: looking at a radar screen and figuring out how many planes are there and where they are going: http://okmij.org/ftp/kakuritu/index.html#blip Since the equipment is imperfect, there could be a random blip on the radar that corresponds to no target. If we have a 10x10 screen and 2% probability of a noise blip in every of the 100 `pixels', we get the search space of 2^100 -- even before we get to the planes and their stochastic equations of motion. Hansei can deal with the problem -- and even scale linearly with time. I don't think you can make a monad out of Gaussian distributions. That is not to say that monads are useless in these problems -- monads are useful, but at a different level, to build a code for say, MCMC (Monte Carlo Markov Chain). It this this meta-programming approach that underlies Infer.net http://research.microsoft.com/en-us/um/cambridge/projects/infernet/ and Avi Pfeffer's Figaro http://www.cs.tufts.edu/~nr/cs257/archive/avi-pfeffer/figaro.pdf I should point out Professor Sato of Toukyou Tech, who is the pioneer in the probabilistic programming http://sato-www.cs.titech.ac.jp/sato/ http://sato-www.cs.titech.ac.jp/en/publication/ You can learn from him all there is to know about probabilistic programming.
participants (2)
-
oleg@okmij.org
-
Takayuki Muranushi