Re: Set, Map libraries

2005-06-02 Thread Jens Fisseler
 1.  elems :: Set a - [a]
 setToList :: Set a - [a]
 
   These two look like synonyms, but have different comments.
   Am I missing something? 

Both functions compute the same list, and IMHO the comments state the
same.

 2.  size :: Set a - Int-- O(1) ...
 
   And for large sets, the user needs to program
 
   genericSize :: Set a - Integer  
   genericSize =  genericLength . Data.Set.elems
   ?
   Is this possible to make it O(1) too?

No, 'genericSize' cannot work in O(1) time, but by looking at the source
you will see that a 'Set' contains an element representing its size, so
'size' can work in constant time.

Regards,

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


RE: Simplifier output explanation needed

2005-06-02 Thread Simon Marlow
On 01 June 2005 13:54, Jens Fisseler wrote:

 I'm currently trying to optimize some code, in particular trying to
 make some functions as strict as possible. To do this, I quite often
 look for strictness annotations either in the interface files or the
 the simplifier output. Doing this, something odd occured to me:
 inserting a '$!' into a function call, trying to enforce eager
 evaluation, the simplifier output changed. Ok, I should expect this,
 but I don't understand the change. The function name got '$s' as a
 prefix and the strictness annotation ('Str: DmdType SSL') vanished.
 
 So my question is what all those different prefixes mean. I've
 stumbled across at least '$s' and '$w' (worker wrapper?). Why did the
 strictness annotation disappear? Is there any documentation that can
 enlighten me? 

$s means specialised I believe (Simon PJ is away until next week, so
you'll have to wait until then for a definitive answer).

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


Re[4]: [Haskell-cafe] ghc 6.4 import problem

2005-06-02 Thread Bulat Ziganshin
Hello Simon,

Thursday, June 02, 2005, 12:26:48 PM, you wrote:

SM You mean allowing

SM   import M hiding (x)

SM even if x is not exported by M?  Or making it a warning?

yes. i think that warning will be enough - it will compile silently
with new library versions and give warning, but still compile, when we
use old version of module M

SM That's certainly possible, but it constitutes an extension to Haskell
SM 98, so it would at least require the -fglasgow-exts flag.  I think
SM you're better off keeping your code portable.

my own code in any case use many GHC-specific tricks, so for me
personally it is acceptable


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


doc on Map.insert

2005-06-02 Thread Serge D. Mechveliani
The ghc-6.4 documentation says about  Data.Map

  insert :: Ord k = k - a - Map k a - Map k a
  O(log n). Insert a new key and value in the map.


If this is to replace old  addToFM,  then it is better to remove the
word new.
Right?

-
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 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


Re: Map library

2005-06-02 Thread Mario Blazevic
This being the topic, I'll list the issues I ran into with the new 
Data.Map library:


1. The function Map.union is left-biased whereas the old 
FiniteMap.unionFM was right-biased. The change seems rather arbitrary. 
There are also other changes of this kind, the following two notable 
among them:


2. The functions passed to Map.insertWith and Map.insertWithKey expect 
their arguments in opposite order from the old FiniteMap.addToFM_C. To 
make matters worse, the correct order is not documented so the user is 
forced to guess. When I converted my source to use Data.Map instead of 
FiniteMap, I guessed wrong and it took me a while to find what was wrong.


3. The Data.Map looks much better than the FiniteMap library, and its 
export list is very complete.  There are, however, two (or four) more 
functions that would be really nice to have in there, as they are 
impossible to write efficiently with the functions currently provided:



  mapFilter :: (a - Maybe b) - Map k a - Map k b
  mapFilter f = map Maybe.fromJust . filter Maybe.isJust . map f

  mapPartition :: (a - Either b c) - Map k a - (Map k b, Map k c)
  mapPartition f = removeTags . partition isLeft . map f
  where isLeft (Either.Left _) = True
isLeft (Either.Right _) = False
removeTags (leftMap, rightMap) = (map (\ (Left x) - x) 
leftMap,
  map (\ (Right x) - 
x) rightMap)



For completeness, mapFilterWithKey and mapPartitionWithKey could be 
thrown in too.



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


Re: Map library

2005-06-02 Thread Christian Maeder
Mario Blazevic wrote:
   mapFilter :: (a - Maybe b) - Map k a - Map k b
   mapFilter f = map Maybe.fromJust . filter Maybe.isJust . map f

How about using Map.foldWithKey (and adding Ord k = to the type
signature)?

mapFilter f = Map.foldWithKey ( \ k - maybe id (Map.insert k) . f)
Map.empty

mapPartition f = Map.foldWithKey ( \ k v (l, r) - either
   ( \ x - (Map.insert k x l, r))
   ( \ x - (l, Map.insert k x r)) $ f v)
   (Map.empty, Map.empty)

Could it be more efficient?

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


Re: Map library

2005-06-02 Thread Mario Blazevic

Christian Maeder wrote:


Mario Blazevic wrote:
 


 mapFilter :: (a - Maybe b) - Map k a - Map k b
 mapFilter f = map Maybe.fromJust . filter Maybe.isJust . map f
   



How about using Map.foldWithKey (and adding Ord k = to the type
signature)?

mapFilter f = Map.foldWithKey ( \ k - maybe id (Map.insert k) . f)
   Map.empty
 


   That's what I ended up doing, more or less. Not having seen the
library source code, I can't be completely sure. Maybe ghc can perform
some deforestation wonder and make it more efficient than the sum of its
parts. Otherwise, here's how it works out:

   Map.filter has O(n) complexity, and I don't see any reason to expect
library-provided mapFilter to be any worse.

   Map.foldWithKey is O(n)
   Map.insert is O(log n), and gets executed as many times as f returns
True. That's O (n log n)

   The complexity of user implementation of  mapFilter is O (n + n
log(n)) = O(n log n)

--
Mario Blazevic
[EMAIL PROTECTED]
Stilo Corporation

This message, including any attachments, is for the sole use of the
intended recipient(s) and may contain confidential and privileged
information. Any unauthorized review, use, disclosure, copying, or
distribution is strictly prohibited. If you are not the intended
recipient(s) please contact the sender by reply email and destroy
all copies of the original message and any attachments.


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


Re: Set, Map libraries

2005-06-02 Thread S. Alexander Jacobson

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.


-Alex-


On Thu, 2 Jun 2005, Robert van Herk wrote:




6. My module applies  Data.Set.null (s :: Set a),
  and null (xs :: [a]).

 Why ghc reports of the clash with  GHC.List.null ?
 Is  GHC.List  same as old  List  library module?
 Should I write
import GHC.List (genericLength, null)
 instead of import List (genericLength)
 ?


As the documentation reads:

This module is intended to be imported qualified, to avoid name clashes with 
Prelude 
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html 
functions. eg.


import Data.Set as Set



So, you should write:

import qualified Data./x/ as /y/

Now, no name clashes will occur. However, you will have to write /y/.null to 
access null in /x/, for example:


import qualified Data.Set as Set

if (Set.null ...) then ... else ...

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



__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Set, Map libraries

2005-06-02 Thread John Meacham
On Thu, Jun 02, 2005 at 05:03:26PM -0400, S. Alexander Jacobson wrote:
 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.

HasEmpty should be a superclass of Monoid. I have wanted that split out
on various occasions.
John

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