data-map-multikey-0.0.1.2: Data.Map with multiple, unique keys

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Map.MultiKey

Description

Data.Map with multiple, unique keys. IxSet without the Sets.

module Main where

import Data.Map.MultiKey
import Data.Typeable
import Prelude hiding (lookup, null)

data Record = Record
  { rIntKey :: Int
  , rStringKey :: String
  , rData :: String
  } deriving (Show, Typeable)

instance MultiKeyable Record where 
  empty = MultiKey [key rIntKey, key rStringKey]

records :: [Record]
records =
  [ Record 1 "key 1" "data 1"
  , Record 20 "key 20" "data 20"
  , Record 3 "key 3" "data 3"
  ]

mk :: MultiKey Record
mk = fromList records
> lookup (1::Int) mk
Just (Record {rIntKey = 1, rStringKey = "key 1", rData = "data 1"})
it :: Maybe Record
> lookup "key 20" mk
Just (Record {rIntKey = 20, rStringKey = "key 20", rData = "data 20"})
it :: Maybe Record
> lookup 2.0 mk
*** Exception: MultiKey: there is no key of type Double in MultiKey Record

Documentation

data MultiKey a Source

Constructors

MultiKey [Key a] 

Instances

Typeable (* -> *) MultiKey 

class MultiKeyable a where Source

Methods

empty :: MultiKey a Source

key :: (Typeable k, Ord k) => (a -> k) -> Key a Source

lookup :: (Typeable a, Typeable k) => k -> MultiKey a -> Maybe a Source

toList :: MultiKey a -> [a] Source

updateKey :: (Typeable a, Typeable k) => k -> a -> MultiKey a -> MultiKey a Source