-- |
-- Utilities for HashMap.
module OpcXmlDaClient.Base.HashMap where

import qualified Data.HashMap.Strict as HashMap
import OpcXmlDaClient.Base.Prelude

-- |
-- Build a hash map from keys to autoincremented ids using a projection function from int.
--
-- The ids are generated by incrementing a counter starting from 0.
autoincrementedFoldable :: (Foldable f, Hashable k, Eq k) => f k -> (Int -> v) -> HashMap.HashMap k v
autoincrementedFoldable foldable projValue =
  foldr
    ( \k next !map !counter ->
        HashMap.alterF
          ( maybe
              (succ counter, Just (projValue counter))
              (\value -> (counter, Just value))
          )
          k
          map
          & \(newCounter, newMap) -> next newMap newCounter
    )
    (\map _ -> map)
    foldable
    HashMap.empty
    0