> 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
>
>