[Haskell-cafe] "SameConstraints?" type constraints

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Fri Jun 19 12:38:09 UTC 2015


On 19 June 2015 at 22:09, Leza Morais Lutonda
<leza.ml at fecrd.cujae.edu.cu> wrote:
> On 06/19/2015 03:02 AM, MigMit wrote:
>>
>> Typo.
>>
>> {-# LANGUAGE ConstraintKinds, GADTs #-}
>> data SC c e where SC :: c d => d -> e -> SC c e
>
>
> Yes, I have activated the GADTs extension too and the data definition itself
> typechecks but the Show instance do not:
>
> instance Show e => Show (S c e) where
>       show (SC x y) = show x ⧺ show y
>
> Because: Could not deduce (Show d) arising from a use of ‘show’

This works for me if I also enable FlexibleInstances and restrict it to:

instance (Show e) => Show (S Show e) where ...

You could probably also use Edward Kmett's constraints package [1] to
generalise this to any c which is a sub-class of Show.

[1]: http://hackage.haskell.org/package/constraints



-- 
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
http://IvanMiljenovic.wordpress.com


More information about the Haskell-Cafe mailing list