
Hello!
Yes, classes of that variety exist in a few packages. This is a
particularly good treatment of it:
http://hackage.haskell.org/package/keys
Here are some classes from a very WIP implementation of a few
"Commutative Replicated Data Types":
https://github.com/mgsloan/crdt/blob/master/src/Data/CRDT/Classes.hs
"Function" is identical to your addressable, without (#). There're
also classes for "Update"-able, "Zero"-able, and "Size"-able things.
Zero has a strange definition because CRDT sets need to communicate
what has been deleted, clearing a set results in a value that is not
the same as "zero". I suppose that "clear" aught to be in a separate
class.
-Michael Sloan
On Wed, Apr 11, 2012 at 10:47 PM, 陈文龙
To get element in List,Map... in python's way.
Python:
strMap["apple"]
Haskell:
strMap # "apple"
https://gist.github.com/2364395
{-# LANGUAGE TypeFamilies #-}
module Addressable where
import qualified Data.Map as M
import Prelude
class Addressable a where
type Key a
type Value a
(#!) :: a -> Key a -> Value a
(#) :: a -> Key a -> Maybe (Value a)
instance Addressable [a] where
type Key [a] = Int
type Value [a] = a
(#!) = (!!)
xs # i | i < 0 = Nothing
[] # _ = Nothing
(x:_) # 0 = Just x
(_:xs) # n = xs # (n-1)
instance (Ord k) => Addressable (M.Map k v) where
type Key (M.Map k v) = k
type Value (M.Map k v) = v
a #! i = a M.! i
a # i = M.lookup i a
main :: IO ()
main = do
let strMap = M.fromList [("one","1"),("two","2"),("three","3")]
let strList = ["1","2","3"]
print $ strMap # "two" -- Just "2"
print $ strMap #! "two" -- "2"
print $ strList # 0 -- Just "1"
print $ strList #! 0 -- "1"
print $ strMap # "no-exist" -- Nothing
print $ strList # 100 -- Nothing
print $ strMap #! "no-exist" -- error
print $ strList #! 100 -- error
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe