From 793cc56fbad9da3087e0b26800aec46687ce82dd Mon Sep 17 00:00:00 2001
From: ross <unknown>
Date: Fri, 21 Oct 2005 10:47:25 +0000
Subject: [PATCH] [project @ 2005-10-21 10:47:25 by ross] conformant Show and
 Read instances.

(sorry to jump in, JP, but I had these to hand)
---
 Data/IntMap.hs | 23 ++++++++++++++++++++---
 Data/Map.hs    | 25 ++++++++++++++-----------
 2 files changed, 34 insertions(+), 14 deletions(-)

diff --git a/Data/IntMap.hs b/Data/IntMap.hs
index ff9d30b7..318fe59c 100644
--- a/Data/IntMap.hs
+++ b/Data/IntMap.hs
@@ -147,6 +147,7 @@ import qualified List
 -}  
 
 #if __GLASGOW_HASKELL__
+import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec)
 import Data.Generics.Basics
 import Data.Generics.Instances
 #endif
@@ -978,8 +979,8 @@ instance Functor IntMap where
 --------------------------------------------------------------------}
 
 instance Show a => Show (IntMap a) where
-  showsPrec d t   = showMap (toList t)
-
+  showsPrec d m   = showParen (d > 10) $
+    showString "fromList " . shows (toList m)
 
 showMap :: (Show a) => [(Key,a)] -> ShowS
 showMap []     
@@ -991,7 +992,23 @@ showMap (x:xs)
     showTail (x:xs) = showChar ',' . showElem x . showTail xs
     
     showElem (k,x)  = shows k . showString ":=" . shows x
-  
+
+{--------------------------------------------------------------------
+  Read
+--------------------------------------------------------------------}
+instance (Read e) => Read (IntMap e) where
+#ifdef __GLASGOW_HASKELL__
+  readPrec = parens $ prec 10 $ do
+    Ident "fromList" <- lexP
+    xs <- readPrec
+    return (fromList xs)
+#else
+  readsPrec p = readParen (p > 10) $ \ r -> do
+    ("fromList",s) <- lex
+    (xs,t) <- reads
+    return (fromList xs,t)
+#endif
+
 {--------------------------------------------------------------------
   Typeable
 --------------------------------------------------------------------}
diff --git a/Data/Map.hs b/Data/Map.hs
index 6f11db1d..fd432e25 100644
--- a/Data/Map.hs
+++ b/Data/Map.hs
@@ -161,6 +161,7 @@ import List(nub,sort)
 -}
 
 #if __GLASGOW_HASKELL__
+import Text.Read (Lexeme(Ident), lexP, parens, prec, readPrec)
 import Data.Generics.Basics
 import Data.Generics.Instances
 #endif
@@ -1308,16 +1309,17 @@ instance Functor (Map k) where
   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]
+#ifdef __GLASGOW_HASKELL__
+  readPrec = parens $ prec 10 $ do
+    Ident "fromList" <- lexP
+    xs <- readPrec
+    return (fromList xs)
+#else
+  readsPrec p = readParen (p > 10) $ \ r -> do
+    ("fromList",s) <- lex
+    (xs,t) <- reads
+    return (fromList xs,t)
+#endif
 
 -- parses a pair of things with the syntax a:=b
 readPair :: (Read a, Read b) => ReadS (a,b)
@@ -1330,7 +1332,8 @@ readPair s = do (a, ct1)    <- reads s
   Show
 --------------------------------------------------------------------}
 instance (Show k, Show a) => Show (Map k a) where
-  showsPrec d m  = showMap (toAscList m)
+  showsPrec d m  = showParen (d > 10) $
+    showString "fromList " . shows (toList m)
 
 showMap :: (Show k,Show a) => [(k,a)] -> ShowS
 showMap []     
-- 
GitLab