[Haskell-cafe] How to simplify this code?
Levi Greenspan
greenspan.levi at googlemail.com
Thu Jan 15 14:14:45 EST 2009
Dear list members,
I started looking into monadic programming in Haskell and I have some
difficulties to come up with code that is concise, easy to read and
easy on the eyes. In particular I would like to have a function "add"
with following type signature: JSON a => MyData -> String -> a ->
MyData. MyData holds a JSValue and add should add a key and a value to
this JSON object. here is what I came up with and I am far from
satisfied. Maybe someone can help me to simplify this...
module Test where
import Text.JSON
import Data.Maybe (isJust, fromJust)
import Control.Monad
data MyData = MyData { json :: JSValue } deriving (Read, Show)
jsObj :: JSValue -> Maybe (JSObject JSValue)
jsObj (JSObject o) = Just o
jsObj _ = Nothing
add :: JSON a => MyData -> String -> a -> MyData
add m k v = fromJust $ (return $ json m) >>= jsObj >>= (return .
fromJSObject) >>= (return . ((k, showJSON v):)) >>= (return .
toJSObject) >>= (return . showJSON) >>= \js -> (return $ m { json = js
})
add2 :: JSON a => MyData -> String -> a -> MyData
add2 m k v = fromJust $ (\js -> m { json = js }) `liftM` (showJSON
`liftM` (toJSObject `liftM` (((k, showJSON v):) `liftM` (fromJSObject
`liftM` (jsObj $ json m)))))
add3 :: JSON a => MyData -> String -> a -> MyData
add3 = undefined -- How to simplify add?
What the code essentially does is that using functions from Text.JSON,
it gets the list of key-value pairs and conses another pair to it
before wrapping it again in the JSValue-Type.
Many thanks,
Levi
More information about the Haskell-Cafe
mailing list