[Haskell] duplicate elements in Data.Set

Till Mossakowski till at informatik.uni-bremen.de
Sun Jan 22 06:55:42 EST 2006


The problem probably is that your Ord instance does not
define a total order. Below a small example exhibiting the
same problem.

This shows the usefulness of specification of Haskell programs
(e.g. with Programatica or HasCASL) - verification could be used to
detect such problems.

Till


module SetExample where

import Data.Set

data D = A | B | C deriving (Eq, Show)
instance Ord D where
   compare A B = LT
   compare _ _ = GT

l = fromList [A,B,C,A,B,C]

main = putStrLn (show (valid l))

Walter Moreira wrote:
> Hello list. Are there situations where a set can contain duplicate
> elements?
> 
> I have a newtype and it is an instance of 'Eq' via the 'compare' method,
> and it is also an instance of 'Ord'. After some Data.Set operations
> with sets of that type I get a set which contains two elements which
> compare equal. What am I doing wrong?
> 
> The function 'Set.valid' returns 'False' when applied to the set. I
> use the function 'Set.fromList' sometimes. Is it supposed to always
> yield a valid set? or it may depend on the order or equality?
> 
> Sorry the question is a little vague. When I try to construct small
> examples the problem disappear.
> 
> Thanks,
> Walter
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell


-- 
Till Mossakowski               Phone +49-421-218-4683
Dept. of Computer Science      Fax +49-421-218-3054
University of Bremen           till at tzi.de
P.O.Box 330440, D-28334 Bremen http://www.tzi.de/~till


More information about the Haskell mailing list