No Monad instance for `Data.Map`, but Scala Map?

Using :i Map

I don't see an instance for it Monad

.

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 can see that Scala Map implements flatMap

.

I do not know if Map

, if it obeys the Laws of the Monad.

If my observation is Data.Map

correct, then why isn't Haskell instance Monad (Map)

?

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

+3


source to share


3 answers


It's hard to figure out what Scala is supposed to do flatMap

:

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

      

It takes a couple of maps , meaning (since 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 is not monadic binding, it is closer to Foldable

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 legal 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

      

It looks a bit like an instance ZipList

that buttons the items with a key. Note: ZipList

not Bind

(only Apply

) because you cannot remove items from the range.

And you cannot do this Applicative

or Monad

because there is no way to make a legal pure

/ return

that should matter for all keys. Or perhaps if some type class Finite

shrinks k

(because it Map

is a strict spine in it, so you cannot create infinite maps).


EDIT: pointed out in the comments. If we think correctly, the above is trying to make a specific (testable) view MaybeT (Reader k) v = k -> Maybe v

with Map k v

. But we fail because we cannot imagine pure x = const x

. But we can try to do this by explicitly presenting this 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 really works! But this is a slightly logical definition, since we cannot define a semantically correct instance Eq

:

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

      

m1

are m2

semantically equivalent ( lookup k

have the same results), but structurally different. And we cannot know when MPartial

all the key values ​​are defined.


The spine refers to the spine of the data structure. For example, a list defined as

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

      

is not strict in the spine, but

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

      

there is.

You can define infinite List

, but SList

s:

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

      

As Map

well as a strict spine in him

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

      

we cannot build infinite Map

, even we have the means to get all values ​​of a type k

. But we can build an infinite regular Haskell list: []

make pure

for Applicative ZipList

.

+5


source


No, there is no instance Monad

for Map

.

I can see that Scala Map implements flatMap

.

I'm assuming you've noticed that one doesn't make it a monad ?

But we can try to do Haskell Map

a nonetheless Monad

. How will this intuitively work? We map the values ​​of the card, return a new card for each, and then join

put all those cards together with unions

. It should work!

Indeed, if we take a closer look at the classes that are implemented Map

, we see something very similar:



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

      

where it Monoid.mconcat

takes on a role unions

, and Traversable

offers foldMapDefault

, which does exactly what we want (and can be used for >>=

)!

However, when we want to implement return

, we have a problem - no key! We get meaning, but we can't make it out of it Map

! That the same problem Scala avoided by making it flatMap

more general than the monad. We could solve this by getting a default value for the key, for example. requiring the type of the key to be an instance Monoid

and instance (Ord k, Monoid k) => Monad (Map k)

does with it , but it fails to satisfy the laws of the monad due to being limited return

.

However, all use cases of the overloaded flatMap

in Scala are covered by the equivalent methods in Haskell Map

s. You want to take a closer look at mapMaybe

/ mapMaybeWithkey

and foldMap

/ foldMapWithKey

.

+2


source


How would you implement return

for Data.Map

? Presumably return x

would be x

like a value, but with what keys?

0


source







All Articles