[Haskell-cafe] The (!) operation
Francesco Mazzoli
f at mazzo.li
Thu Mar 8 18:27:00 CET 2012
Ok, this should suit your needs better, without functional dependencies
as a bonus:
{-# LANGUAGE TypeFamilies, ScopedTypeVariables, FlexibleInstances #-}
module IxClass (IxClass(..)) where
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Hashable (Hashable)
import Data.HashMap.Lazy (HashMap)
import qualified Data.HashMap.Lazy as HashMap
import qualified Data.List as List
class IxClass a where
type Ix a :: *
type Value a :: *
index :: Ix a -> a -> Maybe (Value a)
(!) :: IxClass a => a -> Ix a -> (Value a)
a ! k = case index k a of
Just v -> v
Nothing -> error "IxClass.(!): index not found"
instance IxClass [a] where
type Ix [a] = Int
type Value [a] = a
index _ [] = Nothing
index 0 (x : _) = Just x
index n (_ : xs) = index (n - 1) xs
instance Ord k => IxClass (Map k v) where
type Ix (Map k v) = k
type Value (Map k v) = v
index = Map.lookup
instance (Hashable k, Eq k) => IxClass (HashMap k v) where
type Ix (HashMap k v) = k
type Value (HashMap k v) = v
index = HashMap.lookup
More information about the Haskell-Cafe
mailing list