[Haskell] Read Instances for Data.Map and Data.Set
Georg Martius
mai99dgf at studserv.uni-leipzig.de
Wed Oct 19 14:20:10 EDT 2005
Hi folks,
I was really annoyed by the fact that for Data.Map and Data.Set are no Read
instances declared, but Show instances are! I believe there should be some
kind of unwritten rule that in the standart lib the Show and Read instances
come pairwise and are fully compatible.
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.
For the {a,b,...} syntax I have used a modified version of @list@ from
GHC.Read
Is there a chance of having this in the libs?
Cheers,
Georg
[1] http://www.haskell.org//pipermail/haskell/2005-February/015380.html
import qualified Data.Map as Map
import qualified Data.Set as Set
import Text.Read
import qualified Text.Read.Lex as L
import GHC.Read
instance (Ord k, Read k, Read e) => Read (Map.Map k e) where
readPrec = do elements <- set (readPair readPrec readPrec)
return $ Map.fromList elements
-- ^ @(readPrec p1 p2)@ parses a pair of things with the syntax @a:=b@
-- where @a@ is parsed by @p1@,
-- and @b@ is parsed by @p2@
readPair :: ReadPrec a -> ReadPrec b -> ReadPrec (a,b)
readPair reada readb =
do a <- reset reada
L.Symbol ":=" <- lexP
b <- reset readb
return (a,b)
instance (Ord a, Read a) => Read (Set.Set a) where
readPrec = do elements <- set (readPrec)
return $ Set.fromList elements
set :: ReadPrec a -> ReadPrec [a]
-- ^ @(set p)@ parses a list of things parsed by @p@,
-- using the curly-braces syntax.
set readx =
parens
( do L.Punc "{" <- lexP
(setRest False +++ setNext)
)
where
setRest started =
do L.Punc c <- lexP
case c of
"}" -> return []
"," | started -> setNext
_ -> pfail
setNext =
do x <- reset readx
xs <- setRest True
return (x:xs)
--
---- 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/haskell/attachments/20051019/da97b2ea/attachment.bin
More information about the Haskell
mailing list