[Haskell-cafe] Why this existential type could not work?

Magicloud Magiclouds magicloud.magiclouds at gmail.com
Thu Aug 21 07:08:52 UTC 2014


Thank you. I think I need to understand the different means of forall when
it at different positions.


On Thu, Aug 21, 2014 at 2:47 PM, Dominique Devriese <
dominique.devriese at cs.kuleuven.be> wrote:

> Dear Magicloud,
>
> What you're writing is not an existential type.  The syntax you used
> meant that Sealed wraps a value of type "forall a. SomeClass a => TVar
> a", while you wanted to say that it should contain a value of type
> "TVar a" for some a that satisfies SomeClass, i.e. an existential
> type. Below is what I think you want:
>
> Regards,
> Dominique
>
>   {-# LANGUAGE RankNTypes, GADTs #-}
>
>   module Test where
>
>   import GHC.Conc
>
>   class SomeClass a
>
>   data Sealed where
>     Sealed :: forall a. SomeClass a => TVar a -> Sealed
>
>   mkSealed :: (SomeClass a) => a -> IO Sealed
>   mkSealed = fmap Sealed . newTVarIO
>
>
> 2014-08-21 8:36 GMT+02:00 Magicloud Magiclouds <
> magicloud.magiclouds at gmail.com>:
> > Hi,
> >
> >   For example, code like this:
> >
> > newtype Sealed = Sealed { unSealed :: forall a. SomeClass a => TVar a }
> >
> > mkSealed :: (SomeClass a) => a -> IO Sealed
> > mkSealed = fmap Sealed . newTVarIO
> >
> >   When compiling, I would get:
> >
> > Expected type: a -> IO (forall a1. SomeClass a1 => TVar a1)
> > Actual type: a -> IO (TVar a)
> >
> >   How to correctly restrict type parameter a here?
> >
> > --
> > 竹密岂妨流水过
> > 山高哪阻野云飞
> >
> > And for G+, please use magiclouds#gmail.com.
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>



-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140821/1652a443/attachment.html>


More information about the Haskell-Cafe mailing list