[Haskell-cafe] Parameterize constraints of existentially quantified types

Gábor Lehel illissius at gmail.com
Sat Apr 21 20:23:36 CEST 2012


On Sat, Apr 21, 2012 at 6:05 PM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> Hi,
>
> I just found out that with the new ConstraintKinds extension we can
> parameterize the constraint of an existentially quantified type:
>
> {-# LANGUAGE KindSignatures, ConstraintKinds, ExistentialQuantification #-}
> import GHC.Exts
> data Some (c :: * -> Constraint) = forall a. c a => Some a

I have a package containing this type, under a different name:
http://hackage.haskell.org/packages/archive/exists/0.1/doc/html/Data-Exists.html

>
> This could be used to define SomeException for example:
>
> import Control.Exception (Exception)
> type SomeException = Some Exception

Unfortunately it's difficult to make this an instance of Exception,
because Exception requires Typeable, and there's no support at present
for deriving Typeable on anything with Constraints in it. Though I
suppose you could write it manually. (Or maybe StandaloneDeriving?).
Alternately we can just wait for the new Typeable using PolyKinds.

The other thing is that while it's cool that you can factor out the
common existential-type-with-a-class-constraint pattern into this one
datatype, I'm not sure I can see any practical benefit to actually
doing it.

>
> Are there any other use cases?

Surprisingly (for me) the only other class I found looking around in
base and a few other popular libraries which looked useful in
conjunction with this type was Show. If anyone knows of others I'll be
glad to add them.

However, with the * -> * kinded version (which I'm calling Exists1)
you can use Functor/Foldable/Traversable. Can anyone think of a
practical application for that?

(I also have instances for various Comonad classes, but I'm pretty
sure those are useless because there's no way to apply a 'run'
function to them (and I might remove them if anyone's bothered by the
dependencies).)


>
> Bas
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



-- 
Work is punishment for failing to procrastinate effectively.



More information about the Haskell-Cafe mailing list