On 17-Feb-1999, S.D.Mechveliani <[EMAIL PROTECTED]> wrote:
> Who could please, explain a bit existential types?
> 
> It is required to organise a table with the key
> 
>   data K = K1 | K2 | K3  {- ... -}   deriving(Eq,Ord,Enum)
> 
> to put/extract there the items of different types, say,  'a'  and 
> ('a','b')  as well.  Is this possible?

Yes.  But what do you want to do with the values once you've extracted them?

> Understanding nothing in this subject, i tried
> 
>   data KTab = forall a. KT (FiniteMap K a)

That gives you a FiniteMap whose values are all of the same type.
Probably what you really want is something like

    data Value = forall v. MkValue v
    type KTab = FiniteMap K Value

This gives you single FiniteMap into which you can put values of
different types, so long as you wrap those values using `MkValue'.
You can also extract them from the finite map.  But once you've
extracted them, you can't really do anything useful with them.  If
you want to be able to do something useful with them, e.g. printing
them, then you need to add the appropriate typeclass constraints
to the definition of `Value':

        data Value = forall v. show v => MkValue v
                               ^^^^^^^^^

>   f :: KTab -> KTab 
>   f    (KT t) = case  addToFM t K1 'a'  of
>                                  t' -> KT (addToFM t' K2 ('a','b'))

This would become

   f :: KTab -> KTab 
   f    t = case  addToFM t K1 (MkValue 'a')  of
                                  t' -> addToFM t' K2 (MkValue ('a','b'))

Here I've added the `MkValue' wrappers and deleted the unnecessary `KT'
wrappers.

> And this does not compile. Then, try
> 
>   class Tab t k  where  lkp  :: t a -> k -> Maybe a
>                         addT :: t a -> k -> a -> t a
> 
>   instance Tab KTab K  where  lkp (KT t) k = lookupFM t k
> 
> Also rejected. How to handle with this?

I'm not sure what you're trying to achieve here.
But maybe you wanted something like this,

        class Tab t k v where 
                        lkp  :: t -> k -> Maybe v
                        addT :: t -> k -> v -> t

        instance Tab KTab K where
                        lkp = lookupFM
                        ...

or perhaps this

        class Tab t k where 
                        lkp  :: t -> k -> Maybe Value
                        addT :: t -> k -> Value -> t

        -- instance definition same as before

?

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "Binaries may die
WWW: <http://www.cs.mu.oz.au/~fjh>  |   but source code lives forever"
PGP: finger [EMAIL PROTECTED]        |     -- leaked Microsoft memo.


Reply via email to