{-# LANGUAGE Safe #-}
{-
Copyright (c) 2004-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

{- |
   Module     : Data.Map.Utils
   Copyright  : Copyright (C) 2004-2011 John Goerzen
   SPDX-License-Identifier: BSD-3-Clause

   Stability  : stable
   Portability: portable

This module provides various helpful utilities for dealing with Data.Maps.

Written by John Goerzen, jgoerzen\@complete.org
-}

module Data.Map.Utils (-- * Basic Utilities
                     flipM, flippedLookupM, forceLookupM,
                     -- * Conversions
                     strToM,
                     strFromM
                          )
where

import           Data.List.Utils (flipAL, strFromAL, strToAL)
import qualified Data.Map

{- | Converts a String, String Map into a string representation.
See 'Data.List.Utils.strFromAL' for more on the similar function for
association lists.  This implementation is simple:

>strFromM = strFromAL . Data.Map.toList

This function is designed to work with Map String String objects,
but may also work with other objects with simple representations. -}
strFromM :: (Show a, Show b, Ord a) => Data.Map.Map a b -> String
strFromM :: forall a b. (Show a, Show b, Ord a) => Map a b -> String
strFromM = [(a, b)] -> String
forall a b. (Show a, Show b) => [(a, b)] -> String
strFromAL ([(a, b)] -> String) -> (Map a b -> [(a, b)]) -> Map a b -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map a b -> [(a, b)]
forall k a. Map k a -> [(k, a)]
Data.Map.toList

{- | Converts a String into a String, String Map.  See
'Data.List.Utils.strToAL' for more on the similar function for association
lists.

This implementation is simple:

>strToM = Data.Map.fromList . strToAL

This function is designed to work with Map String String objects,
but may work with other key\/value combinations if they have simple
representations.  -}
strToM :: (Read a, Read b, Ord a) => String -> Data.Map.Map a b
strToM :: forall a b. (Read a, Read b, Ord a) => String -> Map a b
strToM = [(a, b)] -> Map a b
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList ([(a, b)] -> Map a b) -> (String -> [(a, b)]) -> String -> Map a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [(a, b)]
forall a b. (Read a, Read b) => String -> [(a, b)]
strToAL

{- | Flips a Map.  See 'Data.List.Utils.flipAL' for more on the similar
function for lists. -}

flipM :: (Ord key, Ord val) => Data.Map.Map key val -> Data.Map.Map val [key]
flipM :: forall key val. (Ord key, Ord val) => Map key val -> Map val [key]
flipM = [(val, [key])] -> Map val [key]
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList ([(val, [key])] -> Map val [key])
-> (Map key val -> [(val, [key])]) -> Map key val -> Map val [key]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(key, val)] -> [(val, [key])]
forall key val. (Eq key, Eq val) => [(key, val)] -> [(val, [key])]
flipAL ([(key, val)] -> [(val, [key])])
-> (Map key val -> [(key, val)]) -> Map key val -> [(val, [key])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map key val -> [(key, val)]
forall k a. Map k a -> [(k, a)]
Data.Map.toList

{- | Returns a list of all keys in the Map whose value matches the
parameter. If the value does not occur in the Map, the empty
list is returned. -}

flippedLookupM :: (Ord val, Ord key) => val -> Data.Map.Map key val -> [key]
flippedLookupM :: forall val key. (Ord val, Ord key) => val -> Map key val -> [key]
flippedLookupM val
v Map key val
fm =
    case val -> Map val [key] -> Maybe [key]
forall k a. Ord k => k -> Map k a -> Maybe a
Data.Map.lookup val
v (Map key val -> Map val [key]
forall key val. (Ord key, Ord val) => Map key val -> Map val [key]
flipM Map key val
fm) of
                             Maybe [key]
Nothing -> []
                             Just [key]
x  -> [key]
x

{- | Performs a lookup, and raises an exception (with an error message
prepended with the given string) if the key could not be found.
-}
forceLookupM :: (Show key, Ord key) => String -> key ->
                                       Data.Map.Map key elt -> elt
forceLookupM :: forall key elt.
(Show key, Ord key) =>
String -> key -> Map key elt -> elt
forceLookupM String
msg key
k Map key elt
fm =
    case key -> Map key elt -> Maybe elt
forall k a. Ord k => k -> Map k a -> Maybe a
Data.Map.lookup key
k Map key elt
fm of
         Just elt
x  -> elt
x
         Maybe elt
Nothing -> String -> elt
forall a. HasCallStack => String -> a
error (String -> elt) -> String -> elt
forall a b. (a -> b) -> a -> b
$ String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": could not find key " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (key -> String
forall a. Show a => a -> String
show key
k)