[Haskell-cafe] Existential quantification problem
Jonathan Cast
jonathanccast at fastmail.fm
Thu Jul 10 13:59:56 EDT 2008
On Thu, 2008-07-10 at 14:53 -0300, Marco Túlio Gontijo e Silva wrote:
> Hello,
>
> how do I unbox a existential quantificated data type?
You can't. You have to use case analysis:
case foo of
L l -> <whatever you wanted to do>
where none of the information your case analysis discovers about the
actual type of l can be made available outside of the scope of the case
expression. (It can't `escape'). This is required for decidable static
typing, IIRC.
jcc
>
> > {-# LANGUAGE ExistentialQuantification #-}
> > data L a = forall l. L (l a)
> > unboxL (L l) = l
>
> is giving me, in GHC:
>
> Inferred type is less polymorphic than expected
> Quantified type variable `l' escapes
> When checking an existential match that binds
> l :: l t
> The pattern(s) have type(s): L t
> The body has type: l t
> In the definition of `unboxL': unboxL (L l) = l
>
> Thanks.
>
More information about the Haskell-Cafe
mailing list