Boxing parameterized datatypes?

Scott Williams Scott@James.com
Wed, 06 Feb 2002 02:51:25 -0800


This one may be fairly basic, but I was wondering if there's a common
idiom for boxing a parameterized datatype into a non-parameterized
one, and accessing the components in a unified manner.  (hope I said
that right, pretend I mentioned polymorphism somewhere)

>  module VarExample where

For example if I create a datatype to hold everything about a variable

>  data Base t =
>       Base { value :: t
>            , name  :: String
>         -- , ... more components
>            }

that I want to use as part of a larger data structure, say a
heterogeneous list or an AST, I think I have to collect all of the
variations under a parameterless datatype declaration.  Is this true?

>  data Var =
>       IntegerT (Base Integer)
>     | DoubleT (Base Double)
>  -- | ... more constructors

>  type HeterogeneousList = [Var]

If so, it looks like I then need to write something like the following
in order to access the name of a given Var, and likewise for other
components.

>  getName :: Var -> String
>  getName (IntegerT b) = name b
>  getName ( DoubleT b) = name b

Doesn't seem bad, but if I have more components and type constructors
it can become unwieldy.

The following give compile-time errors, but represent what I've tried
so far to simplify things.

>  getBase :: Var -> Base t
>  getBase (IntegerT b) = b
>  getBase ( DoubleT b) = b

>  getName2 v = name (getBase v)

>  callBaseFn :: Var -> (Base t -> a) -> a
>  callBaseFn (IntegerT b) fn = fn b
>  callBaseFn ( DoubleT b) fn = fn b

>  getName3 v = callBaseFn v name

The other option I've thought about is to use the GHC Dynamic module,
but it doesn't seem very standard for what there is likely a common
idiom.  As you can see I'm still somewhat new at this, but would
appreciate any help.

- Thanks,
  Scott Williams