1

I am trying to write a definition for "tabulate", a function that produces the monoidal summary of the values in the given Map that correspond to the keys in the given Foldable collection.

Here is my code:

module Foldables where

import Prelude hiding (Applicative(..), any, concat)
import Data.Foldable
import Data.Semigroup

import qualified Data.Map as Map
import Data.Map (Map)
import Data.Map.Append (AppendMap(..))
import Data.List (intersperse)
import Data.Maybe (maybe)
import Data.Monoid (Any(..), Sum(..))
import GHC.Generics (Generic)

tabulate :: (Ord k, Foldable f, Monoid a) => (v -> a) -> Map k v -> f k -> a
tabulate t m = foldMap (tabulate . k v)

I am getting this error:

src/Foldables.lhs:295:27: error:
    • Data constructor not in scope: Tabulate :: b0 -> a
    • Perhaps you meant variable ‘tabulate’ (line 295)

src/Foldables.lhs:295:38: error:
    Variable not in scope: k :: t0 -> k -> b0

Please don't change anything but what's in the parenthesis on the second line

Update: I think I'm closer to understanding this. Here is my new code. I realize it's incomplete, but it at least compiles.

tabulate :: (Ord k, Foldable f, Monoid a) => (v -> a) -> Map k v -> f k -> a
tabulate t m = foldMap (\x -> mempty maybe [m] maybe map [t])

Now it fails a cabal test:

   Falsified (after 2 tests):
     <fun>
     fromList [(False,'\DC4'),(True,'\1054302')]
     [True,True]

No matter what I do seem to get some variation of that

I'm assuming what I need is some kind of conditional in the event the third argument of tabulate isn't mempty?

steve
  • 119
  • 7
  • 1
    Please add the definition for `Tabulate` (i.e. provide a [MRE]) – Ackdari Aug 17 '20 at 09:55
  • Sorry, I should have been more specific. This is to be the definition for tabulate. I added that point in the opening line, and also have included all of my imports. – steve Aug 17 '20 at 10:16
  • 1
    In addition to @Ackdari's question, what do `k` and `v` in the second line stand for? – Zhiltsoff Igor Aug 17 '20 at 10:16
  • the variables for map – steve Aug 17 '20 at 10:17
  • You're defining a function `tabulate` (with a lowercase `t`), which makes reference to a `Tabulate` (with an uppercase `T`). There is the latter defined? – MathematicalOrchid Aug 17 '20 at 10:31
  • no, I will decapitalize. I misunderstood how that syntax worked – steve Aug 17 '20 at 10:34
  • 1
    @steve I cannot see where `k` and `v` are being bound as the arguments you pass are `t` and `m`. Besides, I cannot see how one could be applied to the other. – Zhiltsoff Igor Aug 17 '20 at 10:47
  • I see what you are saying. Should I keep working at it and update this post or just leave it as is and wait for an answer? – steve Aug 17 '20 at 10:52
  • @steve if you are asking me, I would have updated the error (I am quite sure it shall be different now as you have fixed the capitalisation). Besides, you may add some information on arguments you expect the function to get. – Zhiltsoff Igor Aug 17 '20 at 10:56

1 Answers1

1

Here is a hint (that is a solution without foldMap, which I reckon to be the object of the problem):

If I get you correctly, you want to write down something like this:

tabulate :: (Ord k, Foldable t, Monoid a) => (v -> a) -> Map k v -> t k -> a
tabulate t m ks = let
                    c k x = (t <$> Data.Map.Strict.lookup k m) <> x
                  in case Prelude.foldr c Nothing ks of
                          Just s  -> s
                          Nothing -> mempty

The case I wrote down is there to work when the intersection of ks (by the way, a solution with foldMap would not need this argument - it will be dropped, as you wanted in the post) with the keys of the map (m) is empty (that is, only Nothings were gathered).

In other cases, we just fold the container of keys with something, resembling mappend for Maybe - it first tries to look the given key up in the map. If it succeeds, it puts the result into Just and then fmaps the transformation t (which gives us a monoid) into it. If it does not, it returns Nothing. In the mappend-sequence of Maybes all Nothings get discarded and the results inside Justs get concatenated with mappend. See the defintion of <> for Maybe (<> is Semigroup's method, which underlies mappend as Monoid is Semigroup's subclass):

-- | @since 4.9.0.0
instance Semigroup a => Semigroup (Maybe a) where
    Nothing <> b       = b
    a       <> Nothing = a
    Just a  <> Just b  = Just (a <> b)
    ...

My solution with foldMap:

tabulate :: (Ord k, Foldable t, Monoid a) => (v -> a) -> Map k v -> t k -> a
tabulate t m = foldMap (\ k -> maybe mempty t (Data.Map.Strict.lookup k m))

It does the following: the function-argument of foldMap takes a key k. If it's not in the map, it returns mempty. Otherwise - it returns t x, where Just x is what the lookup got.

Zhiltsoff Igor
  • 1,812
  • 8
  • 24
  • When I try to play around with that I get: Not in scope: ‘Data.Map.lookup’ – steve Aug 17 '20 at 13:34
  • @steve Besides, I have seen your latest edits. Using `maybe` is the right idea. I will add it to my answer if that is the approach you like. Anyway, would you like to give the problem a few tries, or shall I edit my post, replacing `foldr` with `foldMap`? – Zhiltsoff Igor Aug 17 '20 at 13:39
  • @steve sorry - the fault with names is my bad. My version of `ghc` is too old - you shall use `Data.Map.Strict.lookup` (you shall add `Data.Map.Strict` to your imports). – Zhiltsoff Igor Aug 17 '20 at 13:54
  • If you wouldn't mind showing with foldmap; I've tried every combination I think of. Even better if you know how to do it without importing anything. – steve Aug 17 '20 at 14:06
  • @steve sure, I added it to the post. Did the problem with names resolve (as I still use `lookup`)? – Zhiltsoff Igor Aug 17 '20 at 14:17
  • @steve speaking of imports - if you do not want to import, all you actually need from outside of `Prelude` is `lookup`, which is with `Map` in `Data.Map.Strict`. – Zhiltsoff Igor Aug 17 '20 at 14:20
  • Yes, so that actually works great! Im just curious if there a way to do it without importing anything besides whats provided? I don't see anything saying I'm not allowed to, but just in case. – steve Aug 17 '20 at 14:42
  • If I do just "lookup k m", I get "Couldnt match expected type '[(k, v)]' with actual type 'Map k v' – steve Aug 17 '20 at 14:48
  • @steve yes - `Prelude.lookup` works for lists. "What’s provided" - which functions are provided, so I can adjust my solution (at least I will try)? – Zhiltsoff Igor Aug 17 '20 at 14:51
  • the only imports provided are those listed up in my original post. Prelude.lookup doesn't seem to work with or without Data.Map.Strict imported. – steve Aug 17 '20 at 14:58
  • @steve is `toList :: Map k a -> [(k, a)]` available? – Zhiltsoff Igor Aug 17 '20 at 15:06
  • @steve `Prelude.lookup` won’t work in any case as imports could not override `Prelude` definitions. – Zhiltsoff Igor Aug 17 '20 at 15:08
  • @steve in that case, I reckon `fromList . Prelude.lookup . toList` to do the same thing as `Data.Map.Strict.lookup`. Yet, I believe it to be way less efficient. – Zhiltsoff Igor Aug 17 '20 at 21:50
  • foldMap (\ k -> maybe mempty t (fromList . Prelude.lookup . toList k m))? Actually that generates an error: – steve Aug 17 '20 at 21:58
  • foldMap (\ k -> maybe mempty t (fromList . Prelude.lookup . toList k m))? Actually that generates an error: Ambiguous occurrence ‘toList’ It could refer to either ‘Data.Foldable.toList’ – steve Aug 17 '20 at 22:00
  • @steve the line you wrote down indeed generates an error as haskell first applies functions and only then operators, so `toList k m` appears in the composition, instead of `toList` we want. To get it working, you shall put `(fromList . Prelude.lookup . toList)` in `Data.Map.Strict.lookup`'s place (that is, in brackets). – Zhiltsoff Igor Aug 17 '20 at 22:02
  • @steve oh, we need `toList` for maps, not foldables. Add the module name to the function. – Zhiltsoff Igor Aug 17 '20 at 22:03
  • where would I add the module name to the function? – steve Aug 17 '20 at 22:21
  • I tried (Map.fromList . Map.lookup . Map.toList k m) but it's still not working. I'm just going to accept the original answer, but if you can show me how to get toList to work, I think that is what the assignment wants. – steve Aug 17 '20 at 22:48
  • @steve syntax - if you use function `f`, imported from module `X`, you write `X.f`. What you wrote was correct. Brackets - sorry, I made a mistake yesterday. The composition should have looked like that: `((Prelude.lookup k . toList) m)`. – Zhiltsoff Igor Aug 18 '20 at 06:07