Re: [Haskell] Read Instances for Data.Map and Data.Set

Georg Martius wrote:
Anyway since there was no response to S. Alexander Jacobson post [1], I decided to write these instances at least for GHC in the style of the other instances in GHC.Read.
Who feels responsible for including something into Data.Set and Data.Map (recently I've proposed a change for Set.intersection and others also made suggestions)? The Read instances should be in "their" modules (to avoid "orphans"). But Set and Map should also remain "portable"!
import GHC.Read
This module isn't even listed under http://www.haskell.org/ghc/docs/latest/html/libraries/index.html Cheers Christian Simon, clicking on any module does not work, currently Not Found The requested URL /ghc/docs/latest/html/libraries/base/Control.Arrow.html was not found on this server. Apache/2.0.46 (Red Hat) Server at www.haskell.org Port 80

Christian Maeder wrote:
Simon, clicking on any module does not work, currently
Not Found
The requested URL /ghc/docs/latest/html/libraries/base/Control.Arrow.html was not found on this server. Apache/2.0.46 (Red Hat) Server at www.haskell.org Port 80
Sorry, it works now after I cleared my cache.

Christian Maeder
Who feels responsible for including something into Data.Set and Data.Map (recently I've proposed a change for Set.intersection and others also made suggestions)?
I checked in a Read instance for Data.Set a few weeks ago, when I needed one. An addition like this is rather obvious, so I doubt it needs any discussion. For other changes (like Set.intersection), some discussion might be desirable, but the best proposal is an implemented one, which others can then improve. Btw, I didn't add a Read instance for Data.Map.
import GHC.Read
This module isn't even listed under http://www.haskell.org/ghc/docs/latest/html/libraries/index.html
As it should not be. It is compiler-specific. The hierarchical libraries are supposed to be portable. Regards, Malcolm

Hi Malcolm, I have just looked at your Read instance for Data.Set and implemented an instance for Data.Map in the same manner. import Text.Read {-------------------------------------------------------------------- Read --------------------------------------------------------------------} instance (Ord k, Read k, Read e) => Read (Map k e) where readsPrec _ = readParen False $ \ r -> [(fromList xs,t) | ("{",s) <- lex r , (xs,t) <- readl s] where readl s = [([],t) | ("}",t) <- lex s] ++ [(x:xs,u) | (x,t) <- readPair s , (xs,u) <- readl' t] readl' s = [([],t) | ("}",t) <- lex s] ++ [(x:xs,v) | (",",t) <- lex s , (x,u) <- readPair t , (xs,v) <- readl' u] -- parses a pair of things with the syntax a:=b readPair :: (Read a, Read b) => ReadS (a,b) readPair s = do (a, ct1) <- reads s (":=", ct2) <- lex ct1 (b, ct3) <- reads ct2 return ((a,b), ct3) Cheers, Georg Am Donnerstag, 20. Oktober 2005 12:12 schrieb Malcolm Wallace:
Christian Maeder
writes: Who feels responsible for including something into Data.Set and Data.Map (recently I've proposed a change for Set.intersection and others also made suggestions)?
I checked in a Read instance for Data.Set a few weeks ago, when I needed one. An addition like this is rather obvious, so I doubt it needs any discussion. For other changes (like Set.intersection), some discussion might be desirable, but the best proposal is an implemented one, which others can then improve.
Btw, I didn't add a Read instance for Data.Map.
import GHC.Read
This module isn't even listed under http://www.haskell.org/ghc/docs/latest/html/libraries/index.html
As it should not be. It is compiler-specific. The hierarchical libraries are supposed to be portable.
Regards, Malcolm _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- ---- Georg Martius, Tel: (+49 34297) 89434 ---- ------- http://www.flexman.homeip.net ---------

Hi Malcolm, Thanks for checking in the stuff. However, I am really sorry, but my code contains a bug! Example: "{Foo:=-0.9,...}" Problem: "lex" parses ":=-" as one lexeme Solution: parse ":=" explicitly Please replace the readPair function with the following one, unless you have a better idea. -- parses a pair of things with the syntax a:=b readPair :: (Read a, Read b) => ReadS (a,b) readPair s = do (a, ct1) <- reads s -- we cannot use lex to parse ":=" -- because for "Foo:=-0.9" the ":=-" would be lexed together ((), ct2) <- readcolonequal ct1 (b, ct3) <- reads ct2 return ((a,b), ct3) where readcolonequal (' ':xs) = readcolonequal xs readcolonequal (':':'=':xs) = [((),xs)] readcolonequal _ = [] Regards, Georg Am Donnerstag, 20. Oktober 2005 13:00 schrieb Malcolm Wallace:
Georg Martius
writes: I have just looked at your Read instance for Data.Set and implemented an instance for Data.Map in the same manner.
OK, checked in. Regards, Malcolm _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- ---- Georg Martius, Tel: (+49 34297) 89434 ---- ------- http://www.flexman.homeip.net ---------

Georg Martius
Thanks for checking in the stuff. However, I am really sorry, but my code contains a bug! Example: "{Foo:=-0.9,...}" Problem: "lex" parses ":=-" as one lexeme
One can reasonably argue that this is actually a bug in show, not read. It can be fixed by adding parens, or spaces, to the show. (I'm inclined towards spaces myself.) Regards, Malcolm

Malcolm Wallace wrote:
Georg Martius
writes: Example: "{Foo:=-0.9,...}" [..] (I'm inclined towards spaces myself.)
I agree, ":=" should be treated like an infix constructor (but a missing space after "," does also look not nice). "{Foo := -0.9,Bar := -1}" Christian

Am Donnerstag, 20. Oktober 2005 16:08 schrieb Malcolm Wallace:
Georg Martius
writes: Thanks for checking in the stuff. However, I am really sorry, but my code contains a bug! Example: "{Foo:=-0.9,...}" Problem: "lex" parses ":=-" as one lexeme
One can reasonably argue that this is actually a bug in show, not read. It can be fixed by adding parens, or spaces, to the show. (I'm inclined towards spaces myself.)
Well, yes and no. I would tend to spaces in show as well, BUT one might create the string represenations somewhere else, if not by hand, and I think the parser should be robust. However, my previous attempt was still not correct since it did not use isSpace to check for leading whitespaces. However you might decide it, please find the Read instances for Data.Map, Data.Set, Data.IntMap, Data.IntSet and Data.Sequence in the attached file. Please note the qualified imports. Regards! Georg -- ---- Georg Martius, Tel: (+49 34297) 89434 ---- ------- http://www.flexman.homeip.net ---------

Georg made the point that if a type is an instance of Show, then it should also be an instance of Read, and read . show == id I'd like to repeat my earlier point that it would be better if the user of the type can decide whether he wants some predefined Show/Read instances or roll his own. http://www.haskell.org/pipermail/libraries/2005-March/003496.html Best regards, -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

Johannes Waldmann wrote:
Georg made the point that if a type is an instance of Show, then it should also be an instance of Read, and read . show == id
That does (hopefully) happened now.
I'd like to repeat my earlier point that it would be better if the user of the type can decide whether he wants some predefined Show/Read instances or roll his own.
It is really not an option (in current Haskell) to put Show/Read instances in a separate module. Just consider if you want to combine a couple of module were two modules rely on different instance implementations. (A horror if you want to share code) IT is, however, an option to add auxiliary (non-overloaded) utility functions for showing and reading (parameterized of some separators). Cheers Christian

Hello Johannes, Friday, October 21, 2005, 11:42:55 AM, you wrote: JW> I'd like to repeat my earlier point that it would be better JW> if the user of the type can decide whether he wants JW> some predefined Show/Read instances or roll his own. JW> http://www.haskell.org/pipermail/libraries/2005-March/003496.html long standing sight...... parameterized modules will be a good solution for all those problems. or ability to hide/import class instances, not only plain functions: import Data.Map hiding (Show(Map)) -- Best regards, Bulat mailto:bulatz@HotPOP.com

Bulat wrote:
parameterized modules will be a good solution for all those problems. or ability to hide/import class instances, not only plain functions:
I see that would work around the problem. But still this does not smell right. If we have to hide something, this indicates that it shouldn't have been there (or been visible) in the first place. Yes, I think hiding identifiers is bad style as well. This only comes up because we're too lazy to write out qualified names. Again this could be helped by bringing imported modules into scope locally: let { import Foo.Bar ; ... } This seems to me like a small extension with obvious semantics. But I might be missing something, perhaps related to the scope of class instances that get imported. Well then, let them have full (module) scope. respectfully submitted, -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

Johannes Waldmann
Yes, I think hiding identifiers is bad style as well. This only comes up because we're too lazy to write out qualified names.
Well, perhaps. But consider module Some.Very.Long.Module.Name where import Prelude hiding (map) map = ... foo = ...... map .... Now, do I really want to be forced to write Some.Very.Long.Module.Name.map on the right-hand-side of the defn of foo? There is no easy way currently for me to create a short synonym for the defining module name. e.g. import Some.Very.Long.Module.Name as Local At least, such a recursive module import would be possible, but tricky to set up and maintain when the module changes over time. Regards, Malcolm

On Fri, 21 Oct 2005, Malcolm Wallace wrote:
Johannes Waldmann
writes: Yes, I think hiding identifiers is bad style as well. This only comes up because we're too lazy to write out qualified names.
Well, perhaps. But consider
module Some.Very.Long.Module.Name where import Prelude hiding (map) map = ... foo = ...... map ....
Now, do I really want to be forced to write Some.Very.Long.Module.Name.map on the right-hand-side of the defn of foo? There is no easy way currently for me to create a short synonym for the defining module name. e.g.
import Some.Very.Long.Module.Name as Local
I'd prefer such self-imports if they wouldn't need so much effort.

On Fri, Oct 21, 2005 at 12:40:39PM +0200, Henning Thielemann wrote:
On Fri, 21 Oct 2005, Malcolm Wallace wrote:
Johannes Waldmann
writes: Yes, I think hiding identifiers is bad style as well. This only comes up because we're too lazy to write out qualified names.
Well, perhaps. But consider
module Some.Very.Long.Module.Name where import Prelude hiding (map) map = ... foo = ...... map ....
Now, do I really want to be forced to write Some.Very.Long.Module.Name.map on the right-hand-side of the defn of foo? There is no easy way currently for me to create a short synonym for the defining module name. e.g.
import Some.Very.Long.Module.Name as Local
I'd prefer such self-imports if they wouldn't need so much effort.
me too. I have requested it on the list before. they should be straightforward to add, the recursive module namespace rules are not very complicated at all and just allowing self-import doesn't involve anything but tweaking the renamer a bit and a fast fixpoint iteration. John -- John Meacham - ⑆repetae.net⑆john⑈

Malcolm Wallace wrote:
module Some.Very.Long.Module.Name where import Prelude hiding (map) map = ... foo = ...... map ....
Now, do I really want to be forced to write Some.Very.Long.Module.Name.map on the right-hand-side of the defn of foo? There is no easy way currently for me to create a short synonym for the defining module name. e.g.
import Some.Very.Long.Module.Name as Local
At least, such a recursive module import would be possible, but tricky to set up and maintain when the module changes over time.
I'ld rather suggest a (small) language extension: "module" modid ["as" modid] [exports] "where" body Christian

Malcolm Wallace wrote:
I checked in a Read instance for Data.Set a few weeks ago, when I needed one. An addition like this is rather obvious, so I doubt it needs any discussion. For other changes (like Set.intersection), some discussion might be desirable, but the best proposal is an implemented one, which others can then improve.
A major problem is to keep Set, Map, IntSet and IntMap in sync, particularly when the interface will change. (In the original DData there used to be Bag, IntBag, Seq and Queue modules that have been considered less important for inclusion under base/Data. The current Data.Queue is not the one from Daan and doesn't follow the naming convention of Data.Set and Data.Map) Before checking in any non-trivial changes the specified properties should be checked using quickcheck. Adding Read instances won't violate any invariances, but why not also add a property for it? It would also be great, if we had a performance test-suite to better judge what changes to commit. At least Daan Leijen and Jean-Philippe Bernardy and probably many others, too, made performance tests (and it would be handy, if these could be simply rerun, before and after a change). My code proposal for Set.intersection can be found in http://www.haskell.org//pipermail/glasgow-haskell-users/2005-September/00901... But I've neither thoroughly tested correctness nor performance nor supplied a quickcheck property "left_biased_intersection", I think, this is a desirable property (others might even disagree), but personally I don't really depend on it and have no time to work much more on it. I'm also pretty sure that "Set a" won't behave like "Map a ()" or an identity map "Map a a", if "Ord a" is not really total (and at least for Sets such orders are expected and the effect is partly documented.) Christian

On Thu, Oct 20, 2005 at 03:16:34PM +0200, Christian Maeder wrote:
(In the original DData there used to be Bag, IntBag, Seq and Queue modules that have been considered less important for inclusion under base/Data. The current Data.Queue is not the one from Daan and doesn't follow the naming convention of Data.Set and Data.Map)
Data.Queue will be replaced by Data.Sequence (already in CVS).
participants (8)
-
Bulat Ziganshin
-
Christian Maeder
-
Georg Martius
-
Henning Thielemann
-
Johannes Waldmann
-
John Meacham
-
Malcolm Wallace
-
Ross Paterson