Multi groupby with foldl' and Map.insertWithKey

My goal is to take data like this: [ Info 0 "Alcohol" "TX" , Info 1 "Alcohol" "TX" , Info 2 "Pregnancy" "MA" ] and build a Map like this: [("MA",[("Pregnancy",1)]),("TX",[("Alcohol",2)])] Here is my failed attempt: {-# LANGUAGE ScopedTypeVariables, BangPatterns #-} import qualified Data.Map as M import Data.List (foldl') import Data.Maybe import Debug.Trace data Info = Info { i :: !Int, healthTopic :: !String, state :: !String } deriving Show m :: M.Map String (M.Map String Integer) m = M.fromList [("MA", M.fromList[("Pregnancy",1)]),("TX", M.fromList[("Alcohol",2)])] constantValsPerState = foldl' (\accum currentRow -> do M.insert (state currentRow) "xxx" accum ) M.empty [ Info 0 "Alcohol" "TX" , Info 1 "Alcohol" "TX" , Info 2 "Pregnancy" "MA" ] -- λ> constantValsPerState -- fromList [("MA","xxx"),("TX","xxx")] -- how can I get something like: -- λ> numTopicsPerState -- fromList [("MA", fromList[("Pregnancy",1)]),("TX", fromList[("Alcohol",2)])] -- so we need to give the modified stae of the new map isntead of M.empty -- λ> m -- fromList [("MA",fromList [("Pregnancy",1)]),("TX",fromList [("Alcohol",2)])] -- λ> M.insertWith (\new old -> new) "MA" M.empty m -- fromList [("MA",fromList []),("TX",fromList [("Alcohol",2)])] numTopicsPerState = foldl' (\(accum :: M.Map String (M.Map String Integer)) currentRow -> do M.insertWithKey (\k new old -> M.insert (healthTopic currentRow) ((fromMaybe 0 $ M.lookup (healthTopic currentRow) old) + 1) new ) (state currentRow) (fromMaybe (M.empty) (M.lookup (state currentRow) accum)) accum ) M.empty [ Info 0 "Alcohol" "TX" , Info 1 "Alcohol" "TX" , Info 2 "Pregnancy" "MA" ] -- WRONG OUTPUT -- λ> numTopicsPerState -- fromList [("MA",fromList []),("TX",fromList [("Alcohol",1)])] -- TODO -- turn -- fromList [("Alcohol",fromList []),("MA",fromList [("Pregnancy",1)]),("TX",fromList [("Alcohol",2)])] -- into -- fromList [("MA",fromList [("Pregnancy",1)]),("TX",fromList [("Alcohol",3)])]

My goal is to take data like this: and build a Map like this:
you do not want to insert into the map but alter instead: numTopicsPerState :: M.Map String (M.Map String Integer) numTopicsPerState = foldl' addState M.empty [ Info 0 "Alcohol" "TX" , Info 1 "Alcohol" "TX" , Info 2 "Pregnancy" "MA" ] where addState accum currentRow = M.alter addTopic (state currentRow) accum where addTopic accum = Just $ M.alter incCount (healthTopic currentRow) (fromMaybe M.empty accum) incCount oldCount = Just $ 1 + fromMaybe 0 oldCount

On Wed, Dec 28, 2016 at 9:28 AM, Cody Goodman wrote: My goal is to take data like this: [ Info 0 "Alcohol" "TX"
, Info 1 "Alcohol" "TX"
, Info 2 "Pregnancy" "MA"
] and build a Map like this: [("MA",[("Pregnancy",1)]),("TX",[("Alcohol",2)])] You can convert each individual record to a singleton map:
wrapRecord :: Info -> M.Map String (M.Map String Integer)
wrapRecord (Info _ state healthTopic) = M.singleton state (M.singleton
healthTopic 1)
and then union all these singletons:
numTopicsPerState = M.unionsWith (M.unionWith (+)) . map wrapRecord $ [Info
0 "Alcohol" "TX", Info 1 "Alcohol" "TX", Info 2 "Pregnancy" "MA"]
participants (3)
-
ALeX Kazik
-
Anatoly Zaretsky
-
Cody Goodman