
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

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@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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- Cell: 1.630.740.8204

On 06/19/2015 01:23 AM, David Johnson wrote:
You could constrain d in the type signature of SC.
{-# LANGUAGE GADTs #-}dataS e whereSC::Show d => d -> e ->S e
instanceShow e =>Show (S e) whereshow (SC x y) = show x ++ show y
Hi David, thanks for the rapid answer. But, I also want an instance for Num like: instance Num e => Show (S e) where (SC x1 y1) + (SC x2 y2) = SC (x1+x2) (y1+y2) And in the future I will want another instance that constraints to the `e` type. And the client of the library will implement his own instances or functions. So I think it wont be nice to constraint `Show d` in the type signature of the `SC` constructor. -- Leza Morais Lutonda, Lemol-C Electronic and Telecommunication Engineer Software Development and Architecture Enthusiast http://lemol.github.io 50 Aniversario de la Cujae. Inaugurada por Fidel el 2 de diciembre de 1964 http://cujae.edu.cu

No, constraints aren't a part of type e. But you can specify the constraint in SC itself: data SC c e where SC :: c d => d -> e -> S e (or SC :: (c d, c e) => d -> e -> S e, if you like it better). Of course, you would need ConstraintKind for that. Отправлено с iPad
19 июня 2015 г., в 7:16, Leza Morais Lutonda
написал(а): 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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

On 06/19/2015 01:37 AM, MigMit wrote:
data SC c e where SC :: c d => d -> e -> S e
(or SC :: (c d, c e) => d -> e -> S e, if you like it better). Of course, you would need ConstraintKind for that. Hi MigMit, This don't typechecks for me.
-- 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

Typo. {-# LANGUAGE ConstraintKinds, GADTs #-} data SC c e where SC :: c d => d -> e -> SC c e
On 19 Jun 2015, at 08:33, Leza Morais Lutonda
wrote: On 06/19/2015 01:37 AM, MigMit wrote:
data SC c e where SC :: c d => d -> e -> S e
(or SC :: (c d, c e) => d -> e -> S e, if you like it better). Of course, you would need ConstraintKind for that. Hi MigMit, This don't typechecks for me.
-- 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

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’ -- 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

On 19 June 2015 at 22:09, Leza Morais Lutonda
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@gmail.com http://IvanMiljenovic.wordpress.com

On Fri, Jun 19, 2015 at 2:38 PM, Ivan Lazar Miljenovic wrote:
On 19 June 2015 at 22:09, Leza Morais Lutonda 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 ...
Note this won't work for a Num instance mentioned earlier because the existentially quantified d types in two SC values are not provably the same type. In other words, you can't write instance Num e => Show (S Num e) where SC x1 y1 + SC x2 y2 = SC (x1 + x2) (y1 + y2) because x1 and x2 can have different types. Regards, Sean

Note this won't work for a Num instance mentioned earlier because the existentially quantified d types in two SC values are not provably the same type. In other words, you can't write
instance Num e => Show (S Num e) where SC x1 y1 + SC x2 y2 = SC (x1 + x2) (y1 + y2)
because x1 and x2 can have different types. Another issue is: what if I want to constraint the type `e` to more classes and make `d` to have the same constrains? I have to re-declare
On 06/19/2015 08:44 AM, Sean Leather wrote: the `S` data type like?: data S c1 c2 ... cN e where SC :: (c1 d, c2 d, ..., cN d) -> d -> e -> S c1 c2 ... cN e Does anyone ever needed such a feature? -- 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

How about this:
class (a x, b x) => (a `And` b) x instance (a x, b x) => (a `And` b) x infixr 3 `And`
data S c e where SC :: c d => d -> e -> S c e
foo :: S (Show `And` Read `And` Num) Int foo = SC (5.0 :: Double) (6 :: Int)
Richard
On Jun 19, 2015, at 4:13 PM, Leza Morais Lutonda
On 06/19/2015 08:44 AM, Sean Leather wrote:
Note this won't work for a Num instance mentioned earlier because the existentially quantified d types in two SC values are not provably the same type. In other words, you can't write
instance Num e => Show (S Num e) where SC x1 y1 + SC x2 y2 = SC (x1 + x2) (y1 + y2)
because x1 and x2 can have different types. Another issue is: what if I want to constraint the type `e` to more classes and make `d` to have the same constrains? I have to re-declare the `S` data type like?:
data S c1 c2 ... cN e where SC :: (c1 d, c2 d, ..., cN d) -> d -> e -> S c1 c2 ... cN e
Does anyone ever needed such a feature? -- 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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Den 2015-06-19 22:13, Leza Morais Lutonda skrev:
Note this won't work for a Num instance mentioned earlier because the existentially quantified d types in two SC values are not provably the same type. In other words, you can't write
instance Num e => Show (S Num e) where SC x1 y1 + SC x2 y2 = SC (x1 + x2) (y1 + y2)
because x1 and x2 can have different types. Another issue is: what if I want to constraint the type `e` to more classes and make `d` to have the same constrains? I have to re-declare
On 06/19/2015 08:44 AM, Sean Leather wrote: the `S` data type like?:
data S c1 c2 ... cN e where
SC :: (c1 d, c2 d, ..., cN d) -> d -> e -> S c1 c2 ... cN e
Does anyone ever needed such a feature?
Yes, have a look at the paper "Deconstraing DSLs": http://dl.acm.org/citation.cfm?id=2364571 See also the constraint product (&&&) from the `constraints` package. / Emil

Den 2015-06-22 09:26, Emil Axelsson skrev:
Den 2015-06-19 22:13, Leza Morais Lutonda skrev:
Note this won't work for a Num instance mentioned earlier because the existentially quantified d types in two SC values are not provably the same type. In other words, you can't write
instance Num e => Show (S Num e) where SC x1 y1 + SC x2 y2 = SC (x1 + x2) (y1 + y2)
because x1 and x2 can have different types. Another issue is: what if I want to constraint the type `e` to more classes and make `d` to have the same constrains? I have to re-declare
On 06/19/2015 08:44 AM, Sean Leather wrote: the `S` data type like?:
data S c1 c2 ... cN e where
SC :: (c1 d, c2 d, ..., cN d) -> d -> e -> S c1 c2 ... cN e
Does anyone ever needed such a feature?
Yes, have a look at the paper "Deconstraing DSLs":
http://dl.acm.org/citation.cfm?id=2364571
See also the constraint product (&&&) from the `constraints` package.
Or you might find this interface easier to work with: https://github.com/emilaxelsson/imperative-edsl/blob/master/src/Data/TypePre... It's based on type predicates (`* -> Constraint`), so you can write e.g. `(c1 /\ c2 /\ ... /\ cN) d => ...`. It also implements "sub-classing" using a technique similar to Data Types à la Carte. / Emil

On 06/19/2015 08:38 AM, Ivan Lazar Miljenovic wrote:
This works for me if I also enable FlexibleInstances and restrict it to:
instance (Show e) => Show (S Show e) where ... Thank you Ivan, it works. Now I am analysing the implications of that, after I will post the results.
-- Leza Morais Lutonda, Lemol-C Electronic and Telecommunication Engineer Software Development and Architecture Enthusiast http://lemol.github.io 50 Aniversario de la Cujae. Inaugurada por Fidel el 2 de diciembre de 1964 http://cujae.edu.cu
participants (7)
-
David Johnson
-
Emil Axelsson
-
Ivan Lazar Miljenovic
-
Leza Morais Lutonda
-
MigMit
-
Richard Eisenberg
-
Sean Leather