
Well, for JSON, I think the rendered string must be enclosed in double
quotes, which is what the show instance for String does.
So
renderJValue (JString s) = show s
is not the same as
renderJValue (JString s) = s
You can easily see this with GHCi. A copy from my Windows session:
C:\>ghci
GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude> let s = "Haskell"
Prelude> s
"Haskell"
Prelude> show s
"\"Haskell\""
Prelude> show (show s)
"\"\\\"Haskell\\\"\""
Prelude>
On Thu, Mar 26, 2009 at 4:41 PM, 7stud
In chapter 5, RWH defines a JValue data type like this:
SimpleJSON.hs: --------------
module SimpleJSON ( JValue(..) ) where
data JValue = JNumber Double | JString String | JArray [JValue] | JObject [(String, JValue)] | JBool Bool | JNull deriving (Eq, Ord, Show)
------------
Then RWH defines some functions like this:
PutJSON.hs: ---------- module PutJSON where
import SimpleJSON
renderJValue::JValue->String renderJValue (JNumber f) = show f renderJValue (JString s) = show s renderJValue (JBool True) = "true" renderJValue (JBool False) = "false" renderJValue JNull = "null" ----------
My question is about the function:
renderJValue (JString s) = show s
A JString value contains a string, so why does the function use show to convert s to a string? Why isn't that function defined like this:
renderJValue (JString s) = s
Using that modified function seems to work:
Main.hs: --------- module Main () where
import SimpleJSON import PutJSON
main = let x = JString "hello" in putStrLn (renderJValue x)
$ ghc -o simple Main.hs PutJSON.hs SimpleJSON.hs /usr/libexec/gcc/i686-apple-darwin8/4.0.1/ld: warning -F: directory name (/Users/me/Library/Frameworks) does not exist
$ simple hello
Also can anyone tell me why I always get that warning?
Thanks
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners