4

Using :i Map, I don't see a Monad instance for it.

ghci> import Data.Map
ghci> :i Map
type role Map nominal representational
data Map k a
  = containers-0.5.5.1:Data.Map.Base.Bin {-# UNPACK #-} !containers-0.5.5.1:Data.Map.Base.Size
                                         !k
                                         a
                                         !(Map k a)
                                         !(Map k a)
  | containers-0.5.5.1:Data.Map.Base.Tip
    -- Defined in ‘containers-0.5.5.1:Data.Map.Base’
instance (Eq k, Eq a) => Eq (Map k a)
  -- Defined in ‘containers-0.5.5.1:Data.Map.Base’
instance Functor (Map k)
  -- Defined in ‘containers-0.5.5.1:Data.Map.Base’
instance (Ord k, Ord v) => Ord (Map k v)
  -- Defined in ‘containers-0.5.5.1:Data.Map.Base’
instance (Ord k, Read k, Read e) => Read (Map k e)
  -- Defined in ‘containers-0.5.5.1:Data.Map.Base’
instance (Show k, Show a) => Show (Map k a)
  -- Defined in ‘containers-0.5.5.1:Data.Map.Base

However, I see that Scala's Map implements flatMap.

I do not know if Map if obeys the Monad Laws.

If my observation on Data.Map is correct, then why isn't there an instance Monad (Map) in Haskell?

I looked at this answer, but it looks like it uses Monad Transformers.

Community
  • 1
  • 1
Kevin Meredith
  • 41,036
  • 63
  • 209
  • 384

3 Answers3

6

It's hard to reason what Scala's flatMap is supposed to do:

trait Map[A, B+] extends Iterable[(A, B)] {
  def flatMap[B](f: (A) ⇒ GenTraversableOnce[B]): Map[B]
}

It takes a key, value pair of map (because flatMap comes from Iterable, where A is (A,B)):

scala> val m = Map("one" -> 1, "two" -> 2)
m: scala.collection.immutable.Map[String,Int] = Map(one -> 1, two -> 2)

scala> m.flatMap (p => p match { case (_, v) => List(v, v + 3) })
res1: scala.collection.immutable.Iterable[Int] = List(1, 4, 2, 5)

This isn't monadic bind, it's more closer to Foldable's foldMap

λ > import Data.Map
λ > import Data.Monoid
λ > import Data.Foldable
λ > let m = fromList [("one", 1), ("two", 2)]
λ > (\v -> [v, v + 3]) `foldMap` m
[1,4,2,5]

Map is lawful Ord k => Apply (Map k v) and Ord k => Bind (Map k v):

-- | A Map is not 'Applicative', but it is an instance of 'Apply'
instance Ord k => Apply (Map k) where
  (<.>) = Map.intersectionWith id
  (<. ) = Map.intersectionWith const
  ( .>) = Map.intersectionWith (const id)

-- | A 'Map' is not a 'Monad', but it is an instance of 'Bind'
instance Ord k => Bind (Map k) where
  m >>- f = Map.mapMaybeWithKey (\k -> Map.lookup k . f) m

Which is a bit like ZipList instance could be, zipping elements by key. Note: ZipList isn't Bind (only Apply) because you cannot remove elements from between the range.

And you cannot make it Applicative or Monad, because there are no way to make lawful pure / return, which should have a value at all keys. Or it might be possible if some Finite type class is constraining k (because Map is strict in it's spine, so you cannot create infinite maps).


EDIT: pointed out in the comments. If we think properly, the above tries to make a concrete (inspectable) representation of MaybeT (Reader k) v = k -> Maybe v with Map k v. But we fail, as we cannot represent pure x = const x. But we can try to do that by explicitly representing that case:

module MMap (main) where

import Data.Map (Map)
import qualified Data.Map as Map
import Test.QuickCheck
import Test.QuickCheck.Function

import Control.Applicative
import Control.Monad

-- [[ MMap k v ]] ≅ k -> Maybe v 
data MMap k v = MConstant v
              | MPartial (Map k v)
  deriving (Eq, Ord, Show)

-- Morphism
lookup :: Ord k => k -> MMap k v -> Maybe v
lookup _ (MConstant x) = Just x
lookup k (MPartial m)  = Map.lookup k m

instance Functor (MMap k) where
  fmap f (MConstant v) = MConstant (f v)
  fmap f (MPartial m)  = MPartial (fmap f m)

instance Ord k => Applicative (MMap k) where
  pure = MConstant
  (MConstant f) <*> (MConstant x) = MConstant (f x)
  (MConstant f) <*> (MPartial x)  = MPartial (fmap f x)
  (MPartial f)  <*> (MConstant x) = MPartial (fmap ($x) f)
  (MPartial f)  <*> (MPartial x)  = MPartial (Map.intersectionWith ($) f x)

instance Ord k => Monad (MMap k) where
  return = MConstant
  (MConstant x) >>= f = f x
  (MPartial m) >>= f  = MPartial $ Map.mapMaybeWithKey (\k -> MMap.lookup k . f) m

instance (Ord k, Arbitrary k, Arbitrary v) => Arbitrary (MMap k v) where
  arbitrary = oneof [ MConstant <$> arbitrary 
                    , MPartial . Map.fromList <$> arbitrary
                    ]

prop1 :: Int -> Fun Int (MMap Int Int) -> Property
prop1 x (Fun _ f) = (return x >>= f) === f x

prop2 :: MMap Int Int -> Property
prop2 x = (x >>= return) === x

prop3 :: MMap Int Int -> Fun Int (MMap Int Int) -> Fun Int (MMap Int Int) -> Property
prop3 m (Fun _ f) (Fun _ g) = ((m >>= f) >>= g) === (m >>= (\x -> f x >>= g))

main :: IO ()
main = do
  quickCheck prop1
  quickCheck prop2
  quickCheck prop3

It indeed works! Yet this a bit fishy definition, as we cannot define semantically correct Eq instance:

m1 = MConstant 'a'
m2 = MPartial (Map.fromList [(True, 'a'), (False, 'a')])

The m1 are m2 are semantically equivalent (lookup k has same results), but structurally different. And we can't know when MPartial have all key-values defined.


Spine refers to, uh, data structure spine. For example list defined as

data List a = Nil | Cons a (List a)

ins't strict in the spine, but

data SList a = SNil | SCons a !(SList a)

is.

You can define infinite List, but SLists:

λ Prelude > let l = Cons 'a' l
λ Prelude > let sl = SCons 'a' sl
λ Prelude > l `seq` ()
()
λ Prelude > sl `seq` () -- goes into infinite loop

As Map is also strict in it's spine

data Map k a  = Bin {-# UNPACK #-} !Size !k a !(Map k a) !(Map k a)
              | Tip

we cannot construct infinite Map, even we had means to get all values of k type. But we can construct infinite ordinary Haskell list: [] to make pure for Applicative ZipList.

phadej
  • 11,947
  • 41
  • 78
3

No, there is no Monad instance for Map indeed.

I see that Scala's Map implements flatMap.

I assume you notice that alone doesn't make it a monad?

But we can try nonetheless to make Haskell's Map a Monad. How would it intuitively work? We'd map over the values of the map, return a new map for each, and then join together all those maps by using unions. That should work!

Indeed, if we take a closer look at the classes that Map implements we see something very similar:

import Data.Map
import Data.Traversable
import Data.Foldable
import Data.Monoid

where Monoid.mconcat takes the role of our unions, and Traversable offers a foldMapDefault that does exactly what we want (and could be used for >>=)!

However, when we want to implement return we have a problem - there's no key! We get a value, but we cannot make a Map from that! That's the same problem Scala has avoided by making flatMap more generic than a monad. We could solve this by getting a default value for the key, e.g. by requiring the key type to be a Monoid instance, and make an instance (Ord k, Monoid k) => Monad (Map k) with that - but it will fail to satisfy the monad laws because of the limited return.

Still, all the use cases of the overloaded flatMap in Scala are covered by equivalent methods on Haskell Maps. You'll want to have a closer look at mapMaybe/mapMaybeWithkey and foldMap/foldMapWithKey.

Community
  • 1
  • 1
Bergi
  • 630,263
  • 148
  • 957
  • 1,375
  • 1
    The right identity law doesn't seem to hold: `m >>= return` for any map with non-`mempty` key. Invalid instances destroy equational reasoning, please don't make them. – phadej Jul 17 '15 at 15:36
  • @phadej: Thanks. I initially planned to incorporate a check of the monad laws in my answer, but then forgot it. I've removed the nonsense :-) – Bergi Jul 17 '15 at 15:53
0

How would you implement return for Data.Map? Presumably return x would have x as a value, but with what key(s)?

Alexey Romanov
  • 167,066
  • 35
  • 309
  • 487