graphql-engine/server/src-lib/Data/HashMap/Strict/NonEmpty.hs
Antoine Leblanc 0e3beb028d Extract generic containers from the codebase
### Description

There were several places in the codebase where we would either implement a generic container, or express the need for one. This PR extracts / creates all relevant containers, and adapts the relevant parts of the code to make use of said new generic containers. More specifically, it introduces the following modules:
- `Data.Set.Extended`, for new functions on `Data.Set`
- `Data.HashMap.Strict.Multi`, for hash maps that accept multiple values
- `Data.HashMap.Strict.NonEmpty`, for hash maps that can never be constructed as empty
- `Data.Trie`, for a generic implementation of a prefix tree

This PR makes use of those new containers in the following parts of the code:
- `Hasura.GraphQL.Execute.RemoteJoin.Types`
- `Hasura.RQL.Types.Endpoint*`

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3828
GitOrigin-RevId: e6c1b971bcb3f5ab66bc91d0fa4d0e9df7a0c6c6
2022-03-01 16:04:22 +00:00

84 lines
2.8 KiB
Haskell

-- | Non-empty hash maps.
module Data.HashMap.Strict.NonEmpty
( -- * Type
NEHashMap,
-- * Construction and conversions
singleton,
fromHashMap,
fromList,
toHashMap,
-- * Basic interface
lookup,
(!?),
-- * Transformations
mapKeys,
)
where
import Data.HashMap.Strict (HashMap)
import Data.HashMap.Strict qualified as M
import Data.Hashable (Hashable)
import Prelude hiding (lookup)
-------------------------------------------------------------------------------
-- | A non-empty hashmap is a wrapper around a normal hashmap, that
-- only provides a restricted set of functionalities. It doesn't
-- provide a 'Monoid' instance, nor an 'empty' function.
newtype NEHashMap k v = NEHashMap {unNEHashMap :: HashMap k v}
deriving newtype (Show, Eq, Ord, Semigroup)
deriving stock (Functor, Foldable, Traversable)
-------------------------------------------------------------------------------
-- | Construct a non-empty map with a single element.
singleton :: Hashable k => k -> v -> NEHashMap k v
singleton k v = NEHashMap $ M.singleton k v
-- | Construct a non-empty map with the supplied mappings.
-- Returns 'Nothing' if the provided 'HashMap' is empty.
fromHashMap :: HashMap k v -> Maybe (NEHashMap k v)
fromHashMap m
| M.null m = Nothing
| otherwise = Just $ NEHashMap m
-- | Construct a non-empty map with the supplied mappings as follows:
--
-- * if the provided list contains duplicate mappings, the later mappings take
-- precedence;
-- * if the provided list is empty, returns 'Nothing'.
fromList :: (Eq k, Hashable k) => [(k, v)] -> Maybe (NEHashMap k v)
fromList [] = Nothing
fromList v = Just $ NEHashMap $ M.fromList v
-- | Convert a non-empty map to a 'HashMap'.
toHashMap :: NEHashMap k v -> HashMap k v
toHashMap = unNEHashMap
-------------------------------------------------------------------------------
-- | Return the value to which the specified key is mapped, or 'Nothing' if
-- this map contains no mapping for the key.
lookup :: (Eq k, Hashable k) => k -> NEHashMap k v -> Maybe v
lookup k (NEHashMap m) = M.lookup k m
-- | Return the value to which the specified key is mapped, or 'Nothing' if
-- this map contains no mapping for the key.
--
-- This is a flipped version of 'lookup'.
(!?) :: (Eq k, Hashable k) => NEHashMap k v -> k -> Maybe v
(!?) = flip lookup
-------------------------------------------------------------------------------
-- | @'mapKeys' f s@ is the map obtained by applying @f@ to each key of @s@.
--
-- The size of the result may be smaller if f maps two or more distinct keys to
-- the same new key. In this case there is no guarantee which of the associated
-- values is chosen for the conflicting key.
mapKeys :: (Eq k2, Hashable k2) => (k1 -> k2) -> NEHashMap k1 v -> NEHashMap k2 v
mapKeys fun (NEHashMap m) = NEHashMap $ M.mapKeys fun m