container for different types, avoiding boiler plate

Hal Daume t-hald@microsoft.com
Wed, 20 Aug 2003 08:25:39 -0700


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 =3D Masc | Fem | Neutr      deriving Typeable
  data Number =3D First | Second | Third  deriving Typeable

  let dm =3D 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                                   | hdaume@isi.edu
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


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