[Haskell-beginners] Adapting code from an imperative loop

Michael Orlitzky michael at orlitzky.com
Fri Jun 19 17:05:20 UTC 2015


On 06/19/2015 01:51 AM, Matt Williams wrote:
> 
> In an imperative language this might look like:
> 
> myMap = new map()
> for elem in myElems:
>     key = makeKey(elem)
>     myMap[key] = myMap[key] + elem
> 
> ...
> 
> My thought was that I needed to go through the list of the elems, and at
> each point add them to the Hash Map, handing the updated Map onto the
> next step - but this is what I cannot write.
> 

Your thought was right. You want to go through the list of elems,
building up a new value (the hash map) as you go. The pattern is called
a fold, as others have mentioned. The only tricky part is gluing
together the pieces.

Your pseudocode above looks like it assumes that myMap[key] will return
zero if `key` isn't present in `myMap`. I think I've managed to
reproduce what you want. The "key from element" function I used is just
the identity function, but you should be able to adapt it.


module Main
where

import Data.Map (Map, empty, insert)
import qualified Data.Map as M (lookup)

key_from_elem :: Int -> Int
key_from_elem = id

loop :: [Int] -> (Map Int Int) -> (Map Int Int)
loop elems initial_map =
  foldr update_map initial_map elems
  where
    update_map :: Int -> (Map Int Int) -> (Map Int Int)
    update_map x m =
      let k = key_from_elem x in
                case (M.lookup k m) of
                  Nothing -> insert k x m
                  Just v  -> insert k (v + x) m

main :: IO ()
main = do
  let elems = [1,2,3,4,5]
  let l1 = loop elems empty
  print l1
  let l2 = loop elems l1
  print l2
  let l3 = loop elems l2
  print l3



More information about the Beginners mailing list