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

Georg Martius mai99dgf at studserv.uni-leipzig.de
Thu Oct 20 06:45:04 EDT 2005


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 <maeder at tzi.de> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries

-- 
---- Georg Martius,  Tel: (+49 34297) 89434 ----
------- http://www.flexman.homeip.net ---------
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: not available
Url : http://www.haskell.org//pipermail/libraries/attachments/20051020/9fa2c756/attachment.bin


More information about the Libraries mailing list