[Haskell-beginners] question about show -- RWH chapter 5

Daniel Fischer daniel.is.fischer at web.de
Thu Mar 26 11:53:58 EDT 2009


Am Donnerstag 26 März 2009 16:41:47 schrieb 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

The JSON values are rendered so that they can be parsed at the 
other end. The parser must have the string enclosed in quotation 
marks for that, also some characters need to be escaped.
Consider having 
JString "true"
JString "[true, null, false]"
JString "This is a\nmultiline text.\b!"

>
> 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?

Does the directory exist? If it exists, is in in the linker path?

>
> Thanks




More information about the Beginners mailing list