How to fix DatatypeContexts?

Christopher Done chrisdone at gmail.com
Thu Jul 18 13:13:26 CEST 2013


Good point, classic use-case for GADTs.


On 18 July 2013 13:11, Sjoerd Visscher <sjoerd at w3future.com> wrote:

> I'd use GADT syntax for this:
>
> {-# LANGUAGE GADTs #-}
> data Pair a where Pair :: Eq a => {x::a, y::a} -> Pair a
>
> Sjoerd
>
> On Jul 18, 2013, at 1:05 PM, Christopher Done <chrisdone at gmail.com> wrote:
>
> > Hm, also, with equality constraints you can make the type parametrized,
> too:
> >
> > data Pair a' = forall a. (a ~ a', Eq a) => Pair {x::a, y::a}
> > equal :: Pair a -> Bool
> > equal (Pair x y) = x == y
> >
> >
> > On 18 July 2013 13:00, Christopher Done <chrisdone at gmail.com> wrote:
> > Why not this?
> >
> > data Pair = forall a. Eq a => Pair {x::a, y::a}
> > equal :: Pair -> Bool
> > equal (Pair x y) = x == y
> >
> >
> > _______________________________________________
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users at haskell.org
> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20130718/b96a50b7/attachment.htm>


More information about the Glasgow-haskell-users mailing list