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 Tue, Aug 16, 2011 at 04:44:15PM +0200, Ertugrul Soeylemez wrote:You cannot, with just Haskell 2010. Strangely, if you try this:
> Brent Yorgey <byorgey@seas.upenn.edu> 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.
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