On 2/4/06, raptor <[EMAIL PROTECTED]> wrote:
> does Haskell have a property lists. Like Lisp ?
> any pointer to examples ?
Not built in to the language. It's not hard to get the same
functionality though - I've attached a module that takes a (not
tremendously elegant) approach to the same thing, though. You'll have
to store PLists explicitly, though, and this requires GHC.
/g
--
We have lingered in the chambers of the sea
By sea-girls wreathed with seaweed red and brown
Till human voices wake us, and we drown.
{-# OPTIONS_GHC -fglasgow-exts #-}
module PList (Property, lookup, cons, delete) where
import Data.Typeable
import Prelude hiding (lookup)
class Typeable t => Property a t | a -> t
where label :: a -> String
value :: a -> t
data AnyProperty
where AnyProperty :: Property a t => a -> AnyProperty
instance Property (String, Int) Int
where label = fst
value = snd
instance Property (String, String) String
where label = fst
value = snd
app :: (forall a t. Property a t => a -> r) -> AnyProperty -> r
f `app` (AnyProperty p) = f p
type PList = [AnyProperty]
lookup :: Typeable a => String -> PList -> Maybe a
lookup prop pl | [anyProp] <- property = (cast . value) `app` anyProp
| otherwise = Nothing
where property = filter ((prop ==) . (label `app`)) pl
cons :: Property a t => a -> PList -> PList
cons = (:) . AnyProperty
delete :: String -> PList -> PList
delete prop pl = filter ((prop /=) . (label `app`)) pl
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe