Map, Set

2005-06-03 Thread Serge D. Mechveliani
On 2 Jun 2005  S. Alexander Jacobson [EMAIL PROTECTED]
writes 

 Any reason the libaries don't define:
 
   class HasNull a where null::a-Bool
   class HasEmpty a where empty::a

 I find that I sometimes switch between using lists, sets, or tables as 
 my collection type and the forced import qualifification for generic 
 collection operations seems annoying.


Probably, it would be natural for the  Map and Set GHC libraries  to 
introduce some version of  
  class SetLike where ...

My programs also switch with similar operations between sets and 
various tables.
To unify the interface, I defined the following:

  ---
  class Cardinality a where  card :: a - Natural  -- (Integer)

  instance Cardinality (Set.Set a) where
   card = genericLength . Set.elems
  instance Cardinality (Map.Map k a) where
 card = genericLength . Map.keys

  class Cardinality a = SetLike a where sEmpty :: a
 sIsEmpty   :: a - Bool
 sUnion :: [a] - a
 sMinus :: a - a - a
 sIntersect :: [a] - a
 sConcat:: [a] - a
 sNub   :: a - a
  
  instance Ord a = SetLike (Set.Set a)
where
sEmpty   = Set.empty
sIsEmpty = Set.null
sUnion   = Set.unions
sMinus   = Set.difference
sNub = id
sConcat  = sUnion

sIntersect [] = error sIntersect []\n
sIntersect (s:ss) = foldl Set.intersection s ss

  sIncluded :: SetLike a = a - a - Bool
  sIncluded s =  sIsEmpty . sMinus s

  instance SetLike IdList where 
  ...
  ---


This was as under  ghc-6.2.2,  and now it is edited to meet  6.4.


About what Set and Map libraries could provide
--
The candidates may be

  `any', `all'  analogues for Set, Map 
 (anyway, they are simply expressed by composing with  toList).

  direct product  of sets  
 (can be simply expressed by composing with  toList, fromList).

  composition of maps,  inverse map.


On standard
---
It is very desirable to put the Map and Set libraries to future 
standard Haskell library. With this, our struggle with their interface 
changes will end. 
I wonder how the Haskell language and library are going on, whether 
Haskell-2 is coming.

Regards,

-
Serge Mechveliani
[EMAIL PROTECTED]


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Map, Set

2005-06-03 Thread Jean-Philippe Bernardy
We've been discussing these issues last year on the libraries list,
and we reached the concensus that no concensus could be reached ( :) )
on the ultimate class-based collection framewor (tm). Hence we choose
to go for concrete implementation of Set and Map types. Please refer
to the libraries list archives for details.

In this light, if I dare make a suggestion, it would be to craft a
complete collection framework and distribute it via Cabal for
extensive testing before proposing it as inclusion in the standard.

In order to write such a complete framework one could probably build
upon Edison, DData, and the works of Robert Will and Ross Patterson.

Cheers,
JP.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Map, Set libraries

2005-06-02 Thread Christian Maeder
Serge D. Mechveliani wrote:
 As Jens Fisseler notes, I have made a confusion about
 
 Set.elems, Set.toList, Set.setToList.

There is even Set.toAscList (although one may argue that should be
Set.toDistinctAscList)

I think the right choice is Set.toList (replacing setToList)

Is Set.elems just a (nicer?, useless?) synonym for Set.toList?
There are also Map.assocs and Map.toList being synonyms.

But Map.elems is different from Map.toList and Set.elems would only
correspond to Map.elems for some identity maps (not for the old set
implementation using maps with dummy elements ())

Cheers Christian

P.S Map.insert indeed replaces existing values (and should be used
instead of addToFM with changed argument position for the input map)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users