Defining a containing function on polymorphic list

I am trying to define a containing function to see if a value is one of the elements within a list which is polymorphic, but failed with the following codes:
contain :: a -> [a] -> Bool
contain x [] = False
contain x (y:ys) = if x == y then True else contain x ys it seems that the problem is the 'operator' == does not support a polymorphic check? Any way can solve the problem? or any alternative solution to achieve the purpose? Thanks! Raeck
It’s the same Hotmail®. If by “same” you mean up to 70% faster. http://windowslive.com/online/hotmail?ocid=TXT_TAGLM_WL_hotmail_acq_broad1_1...

The problem here is even slightly deeper than you might realize. For
example, what if you have a list of functions. How do you compare two
functions to each other to see if they're equal? There is no good way really
to do it! So, not only is == not completely polymorphic, but it CAN'T be.
There is a nice solution for this, however, and it's very simple:
contain :: Eq a -> [a] -> Bool
contain x [] = False
contain x (y:ys) = if x == y then True else contain x ys
The "Eq a" in the type signature says that 'a' must be a member of the 'Eq'
typeclass. That says, in turn, that 'a' must have == defined for it.
Fortunately, most types have, or can easily derive that definition. Here is
the definition of the typeclass:
class Eqhttp://haskell.org/ghc/docs/latest/html/libraries/base/Data-Eq.html#t%3AEqa
where(==)http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Eq.html#v%3A%3D%...::
a -> a ->
Boolhttp://haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Bool.html#t%3...
(/=)http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Eq.html#v%3A%2F%...::
a -> a ->
Boolhttp://haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Bool.html#t%3...
That is, for 'a' to be a member of 'Eq', it must have a == operator which
can take 2 values of that type and return a Boolean, saying whether or not
they're equal, and it must also have a definition for the /= operator, which
is "not equal". These two are also defined in terms of each other, so if you
define ==, you get /= for free, and vice versa.
That's probably more information than you needed to know, but I hope it
helps.
2008/12/22 Raeck Zhao
contain :: a -> [a] -> Bool contain x [] = False contain x (y:ys) = if x == y then True else contain x ys it seems that
I am trying to define a containing function to see if a value is one of the elements within a list which is polymorphic, but failed with the following codes: the problem is the 'operator' == does not support a polymorphic check? Any way can solve the problem? or any alternative solution to achieve the purpose? Thanks! Raeck
------------------------------ It's the same Hotmail(R). If by "same" you mean up to 70% faster. Get your account now.http://windowslive.com/online/hotmail?ocid=TXT_TAGLM_WL_hotmail_acq_broad1_1...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2008/12/22 Andrew Wagner
The problem here is even slightly deeper than you might realize. For example, what if you have a list of functions. How do you compare two functions to each other to see if they're equal? There is no good way really to do it! So, not only is == not completely polymorphic, but it CAN'T be.
There is a nice solution for this, however, and it's very simple:
contain :: Eq a -> [a] -> Bool
Please note that the syntax here should be: contain :: Eq a => a -> [a] -> Bool Denis

Yes, of course, sorry for the typo.
On Mon, Dec 22, 2008 at 9:17 AM, Denis Bueno
2008/12/22 Andrew Wagner
: The problem here is even slightly deeper than you might realize. For example, what if you have a list of functions. How do you compare two functions to each other to see if they're equal? There is no good way really to do it! So, not only is == not completely polymorphic, but it CAN'T be.
There is a nice solution for this, however, and it's very simple:
contain :: Eq a -> [a] -> Bool
Please note that the syntax here should be:
contain :: Eq a => a -> [a] -> Bool
Denis

On 22 Dec 2008, at 15:18, Andrew Wagner wrote:
Yes, of course, sorry for the typo.
On Mon, Dec 22, 2008 at 9:17 AM, Denis Bueno
wrote: 2008/12/22 Andrew Wagner : The problem here is even slightly deeper than you might realize. For example, what if you have a list of functions. How do you compare two functions to each other to see if they're equal? There is no good way really to do it! So, not only is == not completely polymorphic, but it CAN'T be.
There is a nice solution for this, however, and it's very simple:
contain :: Eq a -> [a] -> Bool
Please note that the syntax here should be:
contain :: Eq a => a -> [a] -> Bool
Denis
Of note, unless this is an exercise, such a function already exists -- it's called elem. How do you find such a function? You search on haskell.org/hoogle. http://haskell.org/hoogle/?hoogle=Eq+a+%3D%3E+a+-%3E+%5Ba%5D+-%3E+Bool Bob

Thank you very much for your reply! It is really helpful!
But I just found another 'problem', I just realize that the list does not support the user-defined data type?
the list is also depending on the Eq function?
For example,
data Shape = Square | Triangle | Circle
when I type either
[Square, Triangle, Circle]
or
Square == Square
there are errors!
So there is no way to construct a truly polymorphic List? any way to extend the list to support some user-defined data type?
Or... I define the Shape in a wrong way actually?
Thanks
Raeck
Date: Mon, 22 Dec 2008 09:02:53 -0500
From: wagner.andrew@gmail.com
To: raeck@msn.com
Subject: Re: [Haskell-cafe] Defining a containing function on polymorphic list
CC: haskell-cafe@haskell.org; beginners@haskell.org
The problem here is even slightly deeper than you might realize. For example, what if you have a list of functions. How do you compare two functions to each other to see if they're equal? There is no good way really to do it! So, not only is == not completely polymorphic, but it CAN'T be.
There is a nice solution for this, however, and it's very simple:
contain :: Eq a -> [a] -> Bool
contain x [] = False
contain x (y:ys) = if x == y then True else contain x ys
The "Eq a" in the type signature says that 'a' must be a member of the 'Eq' typeclass. That says, in turn, that 'a' must have == defined for it. Fortunately, most types have, or can easily derive that definition. Here is the definition of the typeclass:
class Eq a where
(==) :: a -> a -> Bool
(/=) :: a -> a -> Bool
That is, for 'a' to be a member of 'Eq', it must have a == operator which can take 2 values of that type and return a Boolean, saying whether or not they're equal, and it must also have a definition for the /= operator, which is "not equal". These two are also defined in terms of each other, so if you define ==, you get /= for free, and vice versa.
That's probably more information than you needed to know, but I hope it helps.
2008/12/22 Raeck Zhao
contain :: a -> [a] -> Bool
contain x [] = False
contain x (y:ys) = if x == y then True else contain x ys it seems that the problem is the 'operator' == does not support a polymorphic check?
Any way can solve the problem? or any alternative solution to achieve the purpose? Thanks! Raeck It's the same Hotmail®. If by "same" you mean up to 70% faster. Get your account now. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe _________________________________________________________________ Life on your PC is safer, easier, and more enjoyable with Windows Vista®. http://clk.atdmt.com/MRT/go/127032870/direct/01/

There are two ways to fix this. Let me see if I can get my syntax right this
time :)
1.) Let GHC work out the Eq instance:
data Shape = Square | Triangle | Circle deriving Eq
2.) Tell GHC how to do it explicitly:
data Shape = Square | Triangle | Circle
instance Eq Shape where
Square == Square = True
Triangle == Triangle = True
Circle == Circle = True
_ == _ = False
Note that the last line here means that any other comparisons are false.
On Mon, Dec 22, 2008 at 9:35 AM, Raeck Zhao
Thank you very much for your reply! It is really helpful!
But I just found another 'problem', I just realize that the list does not support the user-defined data type? the list is also depending on the Eq function?
For example,
data Shape = Square | Triangle | Circle
when I type either
[Square, Triangle, Circle]
or
Square == Square
there are errors!
So there is no way to construct a truly polymorphic List? any way to extend the list to support some user-defined data type?
Or... I define the Shape in a wrong way actually?
Thanks
Raeck
------------------------------ Date: Mon, 22 Dec 2008 09:02:53 -0500 From: wagner.andrew@gmail.com To: raeck@msn.com Subject: Re: [Haskell-cafe] Defining a containing function on polymorphic list CC: haskell-cafe@haskell.org; beginners@haskell.org
The problem here is even slightly deeper than you might realize. For example, what if you have a list of functions. How do you compare two functions to each other to see if they're equal? There is no good way really to do it! So, not only is == not completely polymorphic, but it CAN'T be.
There is a nice solution for this, however, and it's very simple:
contain :: Eq a -> [a] -> Bool contain x [] = False contain x (y:ys) = if x == y then True else contain x ys
The "Eq a" in the type signature says that 'a' must be a member of the 'Eq' typeclass. That says, in turn, that 'a' must have == defined for it. Fortunately, most types have, or can easily derive that definition. Here is the definition of the typeclass:
class Eqhttp://haskell.org/ghc/docs/latest/html/libraries/base/Data-Eq.html#t:Eqa where (==)http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Eq.html#v:%3D%3D:: a -> a -> Boolhttp://haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Bool.html#t:B... (/=)http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Eq.html#v:/%3D:: a -> a -> Boolhttp://haskell.org/ghc/docs/latest/html/libraries/ghc-prim/GHC-Bool.html#t:B... That is, for 'a' to be a member of 'Eq', it must have a == operator which can take 2 values of that type and return a Boolean, saying whether or not they're equal, and it must also have a definition for the /= operator, which is "not equal". These two are also defined in terms of each other, so if you define ==, you get /= for free, and vice versa.
That's probably more information than you needed to know, but I hope it helps.
2008/12/22 Raeck Zhao
contain :: a -> [a] -> Bool contain x [] = False contain x (y:ys) = if x == y then True else contain x ys it seems that
I am trying to define a containing function to see if a value is one of the elements within a list which is polymorphic, but failed with the following codes: the problem is the 'operator' == does not support a polymorphic check? Any way can solve the problem? or any alternative solution to achieve the purpose? Thanks! Raeck
------------------------------ It's the same Hotmail(R). If by "same" you mean up to 70% faster. Get your account now.http://windowslive.com/online/hotmail?ocid=TXT_TAGLM_WL_hotmail_acq_broad1_1...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------------------------ Life on your PC is safer, easier, and more enjoyable with Windows Vista(R). See how http://clk.atdmt.com/MRT/go/127032870/direct/01/

2008/12/22 Raeck Zhao
Thank you very much for your reply! It is really helpful!
But I just found another 'problem', I just realize that the list does not support the user-defined data type? the list is also depending on the Eq function?
For example,
data Shape = Square | Triangle | Circle
when I type either
[Square, Triangle, Circle]
This is perfectly legal, but GHCi won't be able to print it, because there is no Show instance for Shape. You can declare one: instance Show Shape where show Square = "Square" show Triagle = "Triangle" show Circle = "Circle" This can be generated automatically when you declare the type, by using: data Shape = Square | Triangle | Circle deriving (Show)
or
Square == Square
Similarly, to use (==), you need an Eq instance, which can be defined much in the same way as the Show instance above (deriving also works on Eq -- don't generalize too hastily; not all classes work with deriving). Luke

hi, good ... morning : ) I am just confused by the following code
oneOnly :: [Int] oneOnly = [1] isOneOnly :: [Int] -> Bool isOneOnly oneOnly = True isOneOnly tester = False
what I want to do is to define a 'type' oneOnly as [1] and use it on the pattern matching in function isOneOnly. But it does not work as I expect: When I type isOneOnly [1] it will be True which is the result I expect but for is OneOnly [1,2] the result keeps True, it seems the second pattern has been ignored, I think I try to achieve the purpose in a wrong way, any suggestion? Thanks and Merry Christmas Best wishes, Raeck _________________________________________________________________ Send e-mail anywhere. No map, no compass. http://windowslive.com/oneline/hotmail?ocid=TXT_TAGLM_WL_hotmail_acq_anywher...

The line "isOneOnly oneOnly = True" doesn't do what you expect here.
Basically, it says there are no constraints on the input, and it binds
whatever input it gets to a new *local* variable named oneOnly. Thus, it
always matches that line of the function, and always returns true.
The problem here is that [1] is a value, not a type that you can match on.
If you want to make sure the value is [1], you can do it one of these two
ways:
isOneOnly x = x == [1]
or
isOneOnly x | x == [1] = True
isOneOnly x | otherwise = False
Now at this point you may be wondering how functions like this work:
factorial 1 = 1
factorial n = n * factorial (n-1)
I just said that you can't match against values, but against types. What
gives? Well, in fact, haskell matches against integers as types of sort, of
the structure Succ Int. That is, it treats integers like they were encoded
with the following type:
data Nat = Zero | Succ Nat
Now you can see how it could pattern match against integers, just like it
would against other types with data constructors. Anyway, I"m sure this is
far more information than you wanted to know.
On Tue, Dec 23, 2008 at 7:45 PM, Raeck Zhao
hi, good ... morning : ) I am just confused by the following code
oneOnly :: [Int] oneOnly = [1] isOneOnly :: [Int] -> Bool isOneOnly oneOnly = True isOneOnly tester = False
what I want to do is to define a 'type' oneOnly as [1] and use it on the pattern matching in function isOneOnly. But it does not work as I expect:
When I type
isOneOnly [1]
it will be True which is the result I expect but for
is OneOnly [1,2]
the result keeps True, it seems the second pattern has been ignored, I think I try to achieve the purpose in a wrong way, any suggestion?
Thanks and Merry Christmas
Best wishes, Raeck
------------------------------ Send e-mail anywhere. No map, no compass. Get your Hotmail(R) account now.http://windowslive.com/oneline/hotmail?ocid=TXT_TAGLM_WL_hotmail_acq_anywher...
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am Mittwoch, 24. Dezember 2008 02:45 schrieb Raeck Zhao:
hi, good ... morning : ) I am just confused by the following code
oneOnly :: [Int] oneOnly = [1] isOneOnly :: [Int] -> Bool isOneOnly oneOnly = True isOneOnly tester = False
what I want to do is to define a 'type' oneOnly as [1] and use it on the pattern matching in function isOneOnly. But it does not work as I expect:
When I type
isOneOnly [1]
it will be True which is the result I expect but for
is OneOnly [1,2]
the result keeps True, it seems the second pattern has been ignored, I think I try to achieve the purpose in a wrong way, any suggestion?
In "isOneOnly oneOnly ", the pattern oneOnly is a variable pattern, it matches everything, it also matches [] and _|_. the fact that it is also the name of an entity defined elsewhere doesn't matter. You can find more about pattern matching (basically, a pattern is a wildcard, a variable or a constructor applied to patterns) in the report. If you turn on warnings for overlapping patterns, GHC will warn you: $ ghci -fwarn-overlapping-patterns OneOnly GHCi, version 6.8.3: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. [1 of 1] Compiling Main ( OneOnly.hs, interpreted ) OneOnly.hs:4:0: Warning: Pattern match(es) are overlapped In the definition of `isOneOnly': isOneOnly tester = ... Ok, modules loaded: Main. *Main> isOneOnly undefined True Depending on what you want to achieve, maybe isOneOnly [1] = True isOneOnly _ = False or isOneOnly [_] = True isOneOnly _ = False is the solution.
Thanks and Merry Christmas
Best wishes, Raeck

Here's a tip: leave off the type signature, and ask ghci what it is.
$ ghci
Prelude> let contain x [] = False ; contain x (y:ys) = if x == y then
True else contain x ys
Prelude> :t contain
contain :: (Eq a) => a -> [a] -> Bool
-- ryan
2008/12/22 Raeck Zhao
contain :: a -> [a] -> Bool contain x [] = False contain x (y:ys) = if x == y then True else contain x ys it seems that the problem is the 'operator' == does not support a polymorphic check? Any way can solve the problem? or any alternative solution to achieve the
I am trying to define a containing function to see if a value is one of the elements within a list which is polymorphic, but failed with the following codes: purpose? Thanks! Raeck
________________________________ It's the same Hotmail(R). If by "same" you mean up to 70% faster. Get your account now. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Raeck, as I see what types you defined, don't you doing School of Expression? (In summer I made my way to FAL chapter, but I had no time more (school), but I will definitely finish that book:) Fero
participants (8)
-
Andrew Wagner
-
Daniel Fischer
-
Denis Bueno
-
frantisek kocun
-
Luke Palmer
-
Raeck Zhao
-
Ryan Ingram
-
Thomas Davie