[Haskell-cafe] "SameConstraints?" type constraints

David Johnson djohnson.m at gmail.com
Fri Jun 19 05:23:27 UTC 2015


You could constrain d in the type signature of SC.

{-# LANGUAGE GADTs #-}
                                                          data S e where

                                                    SC :: Show d => d -> e
-> S e


instance Show e => Show (S e) where
                                                        show (SC x y) = show
x ++ show y

On Fri, Jun 19, 2015 at 12:16 AM, Leza Morais Lutonda <
leza.ml at fecrd.cujae.edu.cu> wrote:

>
> Hi All,
>
> I have the following data type:
>
>  data S e where
>
>      SC :: d -> e -> S e
>
> And I want to declare a Show instance for it in the following way:
>
>  instance Show e => Show (S e) where
>
>     show (SC x y) = show x ++ show y
>
> But, of course it don't typechecks because: could not deduce `Show d`
> arising from a use of `show`.
> Is there a way to constraint the `d` type in the `SC` constructor
> definition to have the same constraints of the `e` type? Something like:
>
>   SC :: SameConstraints d e => d -> e -> S e ???
>
>
> Thanks!
>
>
> --
> Leza Morais Lutonda, Lemol-C
> http://lemol.github.io
>
>
>
> 50 Aniversario de la Cujae. Inaugurada por Fidel el 2 de diciembre de
> 1964  http://cujae.edu.cu
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>



-- 
Cell: 1.630.740.8204
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150619/ecb0be32/attachment.html>


More information about the Haskell-Cafe mailing list