All of the implementations of unionWith seem to require the key type to be ordered. This seems to mean that I can’t use such maps as monads.
The concrete example I’m trying to get working is the distribution monad, as implemented at https://web.engr.oregonstate.edu/~erwig/pfp/:
newtype Probability = P {unP :: Float}
newtype Dist a = D {unD :: [(a,Probability)]}
instance Monad Dist where
return x = D [(x,P 1.0)]
(D d) >>= f = D [(y, q * p) | (x, p) <- d, (y, q) <- unD (f x)]
This (pretty old) code has the feature that values of type Dist get “fragmented” every time bind is used.
A norm
function is supplied, that coalesces/accumulates the probability values for each key.
-- normalization = grouping
--
normBy :: Ord a => (a -> a -> Bool) -> Dist a -> Dist a
normBy f = onD $ accumBy f . sort
accumBy :: (Ord b, Num b) => (a -> a -> Bool) -> [(a,b)] -> [(a,b)]
accumBy f ((x,p):ys@((y,q):xs)) | f x y = accumBy f ((x,p+q):xs)
| otherwise = (x,p):accumBy f ys
accumBy _ xs = xs
norm :: Ord a => Dist a -> Dist a
norm = normBy (==)
norm' :: Ord a => [(a,Probability)] -> [(a,Probability)]
norm' = accumBy (==) . sort
I want to find the fixed point resulting from binding a function onto a particular initial distribution. In order to do this, I tried to redefine the bind function in the Dist monad instance:
instance Monad Dist where
return x = D [(x,P 1.0)]
(D d) >>= f = norm $ D [(y, q * p) | (x, p) <- d, (y, q) <- unD (f x)]
My idea was to normalise after every bind, so that fix
could be used to find the fixed point. This doesn’t work because the monad is unconstrained, and norm
needs an Ord
constraint.
• No instance for ‘Ord b’ arising from a use of ‘norm’
Possible fix:
add (Ord b) to the context of
the type signature for:
(>>=) :: forall a b. Dist a -> (a -> Dist b) -> Dist b
• In the first argument of ‘($)’, namely ‘norm’
In the expression:
norm $ D [(y, q * p) | (x, p) <- d, (y, q) <- unD (f x)]
In an equation for ‘>>=’:
(D d) >>= f
= norm $ D [(y, q * p) | (x, p) <- d, (y, q) <- unD (f x)]
So I’m trying to think of ways around this problem, and I don’t really know what to do. One approach would be to define fmap
and join
instead of defining >>=
directly, and use some kind of unionWith
operation to implement join
. But, as noted, this doesn’t seem to get around the Ord
requirement. Maybe I can use zipWith
to merge values of type Dist that I know contain the same “keys” in the same order?
Please let me know if I’m going about this the wrong way, and should be pursuing some other approach, such as using a constrained monad.