I use my 'DynamicMap' type to handle this sort of thing.  However, I
don't really recommend this approach unless you're very careful.  You
basically lose out on all nice type checking properties and enter a
world of dynamic typing (more or less).

Anyway, you can find it at:

 http://www.isi.edu/~hdaume/DynamicMap.hs

it uses "NLP.FiniteMap", but you can replace this with "Data.FiniteMap".

You can then do things like:

  data Gender = Masc | Fem | Neutr      deriving Typeable
  data Number = First | Second | Third  deriving Typeable

  let dm = addToDM (addToDM emptyDM Masc) Second

  case lookupDM dm of
    Just Masc -> "is a guy"
    Just _    -> "is not a guy"
    _         -> "i don't know gender"

  case lookupDM dm of
    Just First  -> "is first"
    Just Second -> "is second"
    _           -> "either i don't know or is third"

of course 'deriving Typeable' means you need GHC6; otherwise you can
write the instances by hand.

 --
 Hal Daume III                                   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


> -----Original Message-----
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of 
> [EMAIL PROTECTED]
> Sent: Wednesday, August 20, 2003 5:01 AM
> To: [EMAIL PROTECTED]
> Subject: container for different types, avoiding boiler plate
> 
> 
> I think similar things have been asked before, but I couldn't 
> find anything
> specific.
> I have a data type with attributes. These attributes have 
> different types.
> Right now I'm using a lot of boilerplate like that:
> 
> 
> > data Gender  = Masc | Fem | Neutr 
> > ...
> > data Attr    = Gender Gender | Cat Cat | Graph Graph | ...
> > data Type    = TypeCat | TypeGender | ... deriving Eq
> > 
> > myTypeOf (Gender _) = TypeGender
> > myTypeOf (Cat    _) = TypeCat
> > ...
> > myTypeOf _          = TypeError
> >
> > data Segment = Seg { attrs :: [Attr] }
> >
> > attr f seg   = seg { attrs = f (attrs seg) }
> >
> > gattr :: Type -> [Attr] -> Maybe Attr
> > gattr theType []     = fail "attribute not found"
> > gattr theType (a:as) = if myTypeOf a == theType then return 
> a else gattr
> theType as
> >
> > cat :: Cat -> Segment -> Segment
> > cat c  = attr ((Cat c):)  -- set value
> >
> > gcat :: Segment -> Maybe Cat    -- get value
> > gcat = deCat . gattr TypeCat . attrs
> >   where deCat (Just (Cat c)) = c
> >         deCat x = x
> > ...
> 
> Does anyone have some suggestions for making this more concise?
> Generic Haskell? Tricky type classes?
> 
> Thanks,
> Markus
> 
> --
> Markus Schnell
> Infineon Technologies AG, CPR ET
> Tel +49 (89) 234-20875
> 
> _______________________________________________
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
> 
_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to