
Haskellers, in the following testing code I want to model user selection criterias. Explanation of the requirement: - BasicSelect represents a single value (in the beginning: Number or String) - ExtendedSelect is a single value plus a sign if selection is meant inclusive or exclusive - MultipleSelections is a set of ExtendedSelect's I have some problems with that: - The BasicSelect shall only accept SelectionNum's or SelectionStr's. Currently it accepts anything? - The MultipleSelections shall only accept EmptySel or references to ExtendedSelect's. Can anybody give me a hint how do this? Does this work with plain data types? Hartmut module SelectionCriterias where data InclusiveOrExclusive = Inclusive | Exclusive data BasicSelect a = NumberSelect a | StringSelect a data Num a => NumberSelect a = SelectionNum a data Show a => StringSelect a = SelectionStr a data ExtendedSelect a = ExtendedSelect { basicSel :: BasicSelect a, inclOrExcl :: InclusiveOrExclusive } data MultipleSelections a = EmptySel | SingleSel a | MultipleSel [a] ----------------------------------------------------------------------------- -- Examples/Usage: -- e1 :: BasicSelect Integer e1 = NumberSelect 100 e2 = NumberSelect 110 -- e2 :: BasicSelect [Char] e3 = StringSelect "test3" e4 = StringSelect "test4" e5 = StringSelect "test5" -- f1 :: ExtendedSelect Integer f1 = ExtendedSelect { basicSel = e1, inclOrExcl = Inclusive } f2 = ExtendedSelect { basicSel = e2, inclOrExcl = Exclusive } -- f2 :: ExtendedSelect [Char] f3 = ExtendedSelect { basicSel = e3, inclOrExcl = Exclusive } -- multi1 :: MultipleSelections a multi1 = EmptySel -- multi2 :: MultipleSelections (ExtendedSelect Integer) multi2 = SingleSel f1 -- multi3 :: MultipleSelections (ExtendedSelect Integer) multi3 = MultipleSel [f1,f2] -- e.g. shall not be valid - because Bool not supported multi4 = MultipleSel [True, False]

On Mon, Aug 15, 2011 at 19:35, Hartmut
data BasicSelect a = NumberSelect a | StringSelect a data Num a => NumberSelect a = SelectionNum a data Show a => StringSelect a = SelectionStr a
This seems a bit confused. Additionally, the contexts don't do what you intend (they're nearly useless and will probably be removed in a future Haskell revision). I think what you're reaching for here is a GADT:
data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a
I think you otherwise end up with a typeclass or with existentials; both introduce complexity, and I think the existentials solution still allows anything to be stuffed into it, whereas you want to limit it to SelectionNum or SelectionStr. (Typeclasses at least require an instance to be defined first; but they don't prohibit people from doing so, if that's what you're after.) -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Brandon Allbery
I think what you're reaching for here is a GADT:
data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a
I think you otherwise end up with a typeclass or with existentials; both introduce complexity, and I think the existentials solution still allows anything to be stuffed into it, whereas you want to limit it to SelectionNum or SelectionStr. (Typeclasses at least require an instance to be defined first; but they don't prohibit people from doing so, if that's what you're after.)
That's a bit of a contradiction, because you are using existentials yourself in your GADT. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Tue, Aug 16, 2011 at 09:54:52AM +0200, Ertugrul Soeylemez wrote:
Brandon Allbery
wrote: I think what you're reaching for here is a GADT:
data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a
I think you otherwise end up with a typeclass or with existentials; both introduce complexity, and I think the existentials solution still allows anything to be stuffed into it, whereas you want to limit it to SelectionNum or SelectionStr. (Typeclasses at least require an instance to be defined first; but they don't prohibit people from doing so, if that's what you're after.)
That's a bit of a contradiction, because you are using existentials yourself in your GADT.
No, he isn't. data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a 'a' shows up in the result type of both constructors, so there is no existential quantification going on here. -Brent

Brent Yorgey
That's a bit of a contradiction, because you are using existentials yourself in your GADT.
No, he isn't.
data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a
'a' shows up in the result type of both constructors, so there is no existential quantification going on here.
Oh, right. How would one express this as an ADT? Seems impossible to me. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Tue, Aug 16, 2011 at 04:44:15PM +0200, Ertugrul Soeylemez wrote:
Brent Yorgey
wrote: That's a bit of a contradiction, because you are using existentials yourself in your GADT.
No, he isn't.
data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a
'a' shows up in the result type of both constructors, so there is no existential quantification going on here.
Oh, right. How would one express this as an ADT? Seems impossible to me.
You cannot, with just Haskell 2010. Strangely, if you try this: data BasicSelect a = Num a => SelectionNum a | Show a => SelectionStr a you get this error (ghc 7.0.3): Data constructor `SelectionNum' has existential type variables, or a context (Use -XExistentialQuantification or -XGADTs to allow this) In the definition of data constructor `SelectionNum' In the data type declaration for `BasicSelect' And enabling ExistentialQuantification makes the error go away! So apparently the ExistentialQuantification flag also enables type class constraints on data constructors, even when no existential quantification is involved. Odd. -Brent

All,
thank You All for your gentle help. Now I am a step further :-) But there
raises up the next question:
In the last line, I want the datatype MultiSelect being limited to a's which
are of type "ExtendedSelect x".
How can I add this contraint?
Hartmut
{-# LANGUAGE GADTs #-}
module SelectionCriterias2 where
data InclusiveOrExclusive = Inclusive | Exclusive
-- 1. BasicSelect ------------------------------------------
data BasicSelect a where
NumSelect :: Num a => a->BasicSelect a
ShowSelect :: Show a => a->BasicSelect a
-- examples:
x1 = NumSelect 10
x2 = ShowSelect "Hello"
x3 = NumSelect 120.1
-- 2. ExtendedSelect ---------------------------------------
data ExtendedSelect a = ExtendedSelect {
basicSel :: BasicSelect a,
inclOrExcl :: InclusiveOrExclusive
}
-- examples:
x1i :: ExtendedSelect Integer
x1i = ExtendedSelect { basicSel = x1, inclOrExcl = Inclusive }
x1e = ExtendedSelect { basicSel = x1, inclOrExcl = Exclusive }
x2i = ExtendedSelect { basicSel = x2, inclOrExcl = Inclusive }
x2e = ExtendedSelect { basicSel = x2, inclOrExcl = Exclusive }
-- Abbreviation/helper for the construction:
extsel :: BasicSelect a -> InclusiveOrExclusive -> ExtendedSelect a
extsel s ie = ExtendedSelect { basicSel = s, inclOrExcl = ie }
-- examples:
x3i = extsel x3 Inclusive
x3e = extsel x3 Exclusive
-- 3. MultiSelect -----------------------------------------
data MultiSelect a = EmptySel | SingleSel a | MultiSel [a]
On Wed, Aug 17, 2011 at 3:42 PM, Brent Yorgey
On Tue, Aug 16, 2011 at 04:44:15PM +0200, Ertugrul Soeylemez wrote:
Brent Yorgey
wrote: That's a bit of a contradiction, because you are using existentials yourself in your GADT.
No, he isn't.
data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a
'a' shows up in the result type of both constructors, so there is no existential quantification going on here.
Oh, right. How would one express this as an ADT? Seems impossible to me.
You cannot, with just Haskell 2010. Strangely, if you try this:
data BasicSelect a = Num a => SelectionNum a | Show a => SelectionStr a
you get this error (ghc 7.0.3):
Data constructor `SelectionNum' has existential type variables, or a context (Use -XExistentialQuantification or -XGADTs to allow this) In the definition of data constructor `SelectionNum' In the data type declaration for `BasicSelect'
And enabling ExistentialQuantification makes the error go away! So apparently the ExistentialQuantification flag also enables type class constraints on data constructors, even when no existential quantification is involved. Odd.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Now I have found a solution and everything is fine :-)
Thanks again for your help!
-- 3. MultiSelect -----------------------------------------
data MultiSelect a = EmptySel | SingleSel (ExtendedSelect a) | MultiSel
[(ExtendedSelect a)]
a1 = EmptySel
a2 = SingleSel x1i
a3 = MultiSel [x1i, x1e]
On Sat, Aug 20, 2011 at 12:03 AM, Hartmut
All, thank You All for your gentle help. Now I am a step further :-) But there raises up the next question: In the last line, I want the datatype MultiSelect being limited to a's which are of type "ExtendedSelect x". How can I add this contraint? Hartmut
{-# LANGUAGE GADTs #-}
module SelectionCriterias2 where
data InclusiveOrExclusive = Inclusive | Exclusive
-- 1. BasicSelect ------------------------------------------ data BasicSelect a where NumSelect :: Num a => a->BasicSelect a ShowSelect :: Show a => a->BasicSelect a
-- examples: x1 = NumSelect 10 x2 = ShowSelect "Hello" x3 = NumSelect 120.1
-- 2. ExtendedSelect ---------------------------------------
data ExtendedSelect a = ExtendedSelect { basicSel :: BasicSelect a, inclOrExcl :: InclusiveOrExclusive }
-- examples: x1i :: ExtendedSelect Integer x1i = ExtendedSelect { basicSel = x1, inclOrExcl = Inclusive } x1e = ExtendedSelect { basicSel = x1, inclOrExcl = Exclusive } x2i = ExtendedSelect { basicSel = x2, inclOrExcl = Inclusive } x2e = ExtendedSelect { basicSel = x2, inclOrExcl = Exclusive }
-- Abbreviation/helper for the construction: extsel :: BasicSelect a -> InclusiveOrExclusive -> ExtendedSelect a extsel s ie = ExtendedSelect { basicSel = s, inclOrExcl = ie }
-- examples: x3i = extsel x3 Inclusive x3e = extsel x3 Exclusive
-- 3. MultiSelect ----------------------------------------- data MultiSelect a = EmptySel | SingleSel a | MultiSel [a]
On Wed, Aug 17, 2011 at 3:42 PM, Brent Yorgey
wrote: On Tue, Aug 16, 2011 at 04:44:15PM +0200, Ertugrul Soeylemez wrote:
Brent Yorgey
wrote: That's a bit of a contradiction, because you are using existentials yourself in your GADT.
No, he isn't.
data BasicSelect a where SelectionNum :: Num a => a -> BasicSelect a SelectionStr :: Show a => a -> BasicSelect a
'a' shows up in the result type of both constructors, so there is no existential quantification going on here.
Oh, right. How would one express this as an ADT? Seems impossible to me.
You cannot, with just Haskell 2010. Strangely, if you try this:
data BasicSelect a = Num a => SelectionNum a | Show a => SelectionStr a
you get this error (ghc 7.0.3):
Data constructor `SelectionNum' has existential type variables, or a context (Use -XExistentialQuantification or -XGADTs to allow this) In the definition of data constructor `SelectionNum' In the data type declaration for `BasicSelect'
And enabling ExistentialQuantification makes the error go away! So apparently the ExistentialQuantification flag also enables type class constraints on data constructors, even when no existential quantification is involved. Odd.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
Brandon Allbery
-
Brent Yorgey
-
Ertugrul Soeylemez
-
Hartmut