
Hi, Trying to write a function to deserialize a haskell type from xml. Ideally this wont need a third "DTD" file, ie it will work something like XmlSerializer.Deserialize from C#: deserializeXml :: Data(a) => String -> a serializeXml :: Data(a) => a -> String Writing serializeXml is pretty easy: import Data.Generics -- helper function from http://www.defmacro.org/ramblings/haskell-web.html introspectData :: Data a => a -> [(String http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:String, String http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:String)] introspectData a = zip http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:zip fields (gmapQ gshow a) where fields = constrFields $ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. toConstr a -- function to create xml string from single-layer Haskell data type serializeXml object = "<" ++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. show http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:show(toConstr object) ++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. ">" ++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. foldr http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:foldr (\(a,b) x -> x ++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. "<" ++ a ++ ">" ++ b ++ "" ++ a ++ ">") "" ( introspectData object ) ++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. "" ++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. show http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:show(toConstr object) ++ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. ">" ... however cant figure out how to go the other way. Usage of haxml or HXT to achieve this is ok, whatever it takes ;-)

As a side note i'd like to point out that introspectData has a problem with constructors containing Strings because show (x::String) /= x: data Foo = Foo { bar :: String } deriving (Typeable,Data) introspectData (Foo "quux") --> [("bar","\"quux\"")] Those extras \" don't look very nice in the xml.. (the output of introspectData is also wrong in the article's example ) you should probably use a modified gshow: gshow' :: Data a => a -> String gshow' x = fromMaybe (gshow x) (cast x) which is id for Strings.

Yes, or better:
gshow' :: Data a => a -> String
gshow' t = fromMaybe (showConstr(toConstr t)) (cast t)
(which gets rid of the parentheses around numbers).
Still doesnt get a deserialize though ;-)
On 6/24/07, Andrea Vezzosi
As a side note i'd like to point out that introspectData has a problem with constructors containing Strings because show (x::String) /= x:
data Foo = Foo { bar :: String } deriving (Typeable,Data)
introspectData (Foo "quux") --> [("bar","\"quux\"")]
Those extras \" don't look very nice in the xml.. (the output of introspectData is also wrong in the article's example ) you should probably use a modified gshow:
gshow' :: Data a => a -> String gshow' x = fromMaybe (gshow x) (cast x)
which is id for Strings.

Hugh Perkins wrote:
Hi,
Trying to write a function to deserialize a haskell type from xml.
deserializeXml :: Data(a) => String -> a
That type signature describes a function that can deliver *anything* (that is in class Data), whatever you ask from it. From your description (also the one in your other mail) it rather sounds as if you want a function that delivers *something* (only restricted to be in class Data), with you not asking for anything specific. The correct type would be something like: data Any = forall a . Data a => Any a deserializeXml :: String -> Any (The syntax might be very wrong, I don't actually use this weird stuff.) Now what would you do with the resulting 'Any'? Pass it to a function of course: applyAny :: (forall a . Data a => a -> b) -> Any -> b applyAny f (Any a) = f a ...and there aren't all that many functions that would fit the bill, only generic ones. If you do that, you wind up dragging in all the machinery of Data.Generic just to implement what HaXml does with much simpler technology. I doubt that's what you actually want. On the other hand, I might be misunderstanding. In that case, Data.Generics should have everything you need, in particular gunfold and friends. -Udo -- "In the software business there are many enterprises for which it is not clear that science can help them; that science should try is not clear either." -- E. W. Dijkstra

On 6/25/07, Udo Stenzel
That type signature describes a function that can deliver *anything* (that is in class Data), whatever you ask from it.
Yes, that is the goal :-)
If you do that, you wind up dragging in all the machinery of Data.Generic
Is reflection hard in Haskell? In C# its easy, and its one of the most powerful features of C# just to implement what HaXml does with much
simpler technology. I doubt that's what you actually want.
It is exactly what I want ;-) haxml needs a DTD. On the other hand, I might be misunderstanding. In that case,
Data.Generics should have everything you need, in particular gunfold and friends.
Yes, but I'm kindof stuck giving useful input to makeConstrM, so if anyone has any ideas? kpreid in irc gave me an example of using makeConstrM for a pair of strings , but I cant seem to generalize it to work with a custom data type containing strings and ints ( eg Config{ login :: String, maxLogAgeDays :: Int } ) Current (not working) code looks something like the following. Most of the working bits of testConstrM' / runM' come from kpreid, the rest is my feeble attempts to tweak it. runM' :: (MonadState [String] m, Monad m, Data a) => m a runM' = do value <- gets head modify tail -- then one of: (pick the non-working function of your choice ;-) : -- return read (fromJust value) -- return (fromJust $ cast value ) -- return (fst $ head $ gread( "(" ++ value ++ ")" ) ) -- return (fromConstrM runM' constr) -- return (fromConstr contr) testConstrM' :: (Read a, Data a, Read c, Read b, Data b, Data c) => [String] -> a -> (b,c) testConstrM' fieldvalues object = evalState( fromConstrM runM' (toConstr object) ) fieldvalues data Config = Config{ name :: String, age :: Int } deriving( Data, Show, Typeable, Ord, Eq, Read ) createConfig = Config "blah" 3 test = testConstrM' ["qsdfqsdf", "7"] createConfig (I've left out the xml parsing bit, which you can find at: http://www.haskell.org/haskellwiki/HXT section 9.1.1/9.1.2) Maybe I should escalate the question to the haskell@haskell.org group?

Hugh Perkins wrote:
Is reflection hard in Haskell? In C# its easy, and its one of the most powerful features of C#
That's another way of saying that the truly powerful features are missing from C#...
Yes, but I'm kindof stuck giving useful input to makeConstrM, so if anyone has any ideas?
You mean makeConstr? Well, you don't call that at all. But you do call fromConstrM, and if you don't have suitable input for that, that's when you realizie that you should have written the constructor name or index when serializing.
runM' :: (MonadState [String] m, Monad m, Data a) => m a runM' = do value <- gets head modify tail -- then one of: (pick the non-working function of your choice ;-) : -- return read (fromJust value) -- return (fromJust $ cast value ) -- return (fst $ head $ gread( "(" ++ value ++ ")" ) ) -- return (fromConstrM runM' constr) -- return (fromConstr contr)
Of course not. Wild guesswork will get you nowhere, instead you should read the second SYB paper at http://homepages.cwi.nl/~ralf/syb2/ -Udo

Still struggling with this. If anyone has any constructive ideas? I guess it's not really easy otherwise someone would have come up with a solution by now ;-) The issue is the line in makeConstrM'' where we're trying to read (Data a => a) from (String). "read" doesnt work, because read needs a to be an instance of Read, and Data a does not enforce this. Whilst the parent class can be enforced to be Read, there's nothing to enforce this on the child. Anyway, took a look at SYB3, which came up with this little bit of code: class Data a => StringParser a where parsestring :: String -> a parsestring x = fst $ head $gread(x) instance StringParser Int where parsestring x = read x instance StringParser String where parsestring x = read( "\"" ++ x ++ "\"" ) That looks like it should fix the problem with trying to read primitive child data types: we have a function "parsestring" with various custom methods for each data type we want to handle. On the face of it, it should work with any data type that is an instance of DAta, because of the default parsestring function. Unfortunately (and strangely) not: only data types explicitly added as instances will work with the default function for the Data class, even if the datatypes are in fact members of Data, and logically quite capable of running the default function. So, we cant use this for our Data a=> String -> a function There's a bunch of "ext" functions that look potentially useful, but didnt manage to get any of them to work for this. If anyone has any ideas? For the moment, the only functions that build are: return (fromJust $ fst $ head $ gread( "(" ++ (fromJust value) ++ ")" ) ) or: return ((fromJust . cast) value) ... and neither of these work very well. The second works for strings only, not for other datatypes. The first just plain doesnt seem to work, for some reason. (By the way, if anyone knows how to extract debug information from partially executed functions that would be useful). Here's testConstrM'' at the moment: testConstrM'' :: forall a. (Data a,Read a, Show a) => a -> [(String, Maybe String, DataType,Constr)] -> a testConstrM'' templateobject fieldvalues = evalState (fromConstrM (do --value <- gets head (fieldname,value,datatype,constr) <- gets head modify tail --return (fromJust $ (readConstr datatype value) ) --return (parsestring (fromJust value)) --return (extR (fromJust $ fst $ head $ gread( "(" ++ (fromJust value) ++ ")" ) ) parsestring(fromJust value ) ) return (fromJust $ fst $ head $ gread( "(" ++ (fromJust value) ++ ")" ) ) --return ((fromJust . cast) value) --case constr of -- (toConstr(3::Int)) -> return ((fromJust . cast) value) --IntConstr x -> return ((fromJust . cast) value) --_ -> return ((fromJust . cast) value) --return (read_helper fieldname value datatype) )(toConstr templateobject)) fieldvalues You feed it a template object with the appropriate type, and an array of tuples with the fieldname, fieldvalue, datatype and constructor (we only use the fieldvalue at the moment, so you can leave the others blank).

On 6/26/07, Udo Stenzel
That's another way of saying that the truly powerful features are missing from C#...
Hi Udo, Genuine question: please could you tell me what are the truly powerful features of Haskell? My own personal interest comes from a presentation by Tim Sweenie (Unreal 3 Engine), where he discusses some of the ways that Haskell may help solve the threading issues that currently are the Big Problem in computing right now. A friend of mine told me that they're also useful for mission-critical implementations where you want to mathematically prove that the program wont crash etc. Unfortunately it seems Haskell isnt totally perfect for mission-critical applications because (a) it is hard to predict memory usage (b) it's not real-time (eg garbage-collector might kick in just when it would be an appropriate time to fire those booster rockets.... ?) I'm basically a C# developer looking around for ways to solve threading. I'm interested in a few things: - solutions that might work in C# - solutions that could be integrated into C# later on - solutions that work in other languages Haskell looks like it could possibly "solve" threading at some point in the near future, or at least make a dent into threading issues. Given that Simon Peyton Jones is (a) heavily involved in the birth and development of Haskell (b) works at Microsoft Research, there's a decent chance that anything he gets working will be integrated into C# in the future. As far as C# integration goes, I'd guess some way of marking classes/methods "Pure", and having the compiler enforce this. Remember that the average programmer does not have a phd, or even a degree, so anything that requires formal mathematical training will *not* be adopted by a mainstream programming language, but most of the maths can probably be abstracted away. Anyway, getting back to my question, there's a whole slew of articles around saying that no-one uses Haskell because they're too stupid. That's certainly an argument, but it possibly lacks a certain objectivity ;-) So... what do you see as the "Killer Advantages" that make Haskell stand out from the pack?

Hello Hugh, Sunday, July 1, 2007, 8:56:05 PM, you wrote:
Genuine question: please could you tell me what are the truly powerful features of Haskell?
Anyway, getting back to my question, there's a whole slew of articles around saying that no-one uses Haskell because they're too stupid. That's certainly an argument, but it possibly lacks a certain objectivity ;-)
i agree with it. haskell represents new programming paradigm and most programmers are unable to learn it without help of college in other words, there is not yet enough learning infrastructure for FP languages. the same situation was in 80s for OOP languages. this means that learning FP require much more work, or, spending the same time, one will learn FP much worse than OOP
So... what do you see as the "Killer Advantages" that make Haskell stand out from the pack?
i've written 8kloc "real world" program in haskell and can say what was killer features for me: - natural data structures and easiness of defining algorithms - rich set of list operations - easiness of use of higher-level functions - type inference (dropping almost all declarations) - strong type checking detects many errors just at compile time - non-updateable data simplifies algorithms development for concurrent programming: - it's easy to split algorithm to several parts that are run concurrently and exchange data - channels allows to organize data streams (like Unix pipes) between threads, non-updatability of data significantly simplifies usage of these data - MVar allows to implement shared updateable variables which automatically locks on their use shortly said, non-updatability of data significantly simplifies both usual programming and concurrency, especially later. you can do the same with C# it's an example how i use concurrency for data archiving and compression: - first thread scans disk and finds files to compress. it sends filenames to its output stream - second thread reads contents of these files and sends memory buffers filled with data read to its output stream. it also runs background decompression stream which decompress data from old archive - third thread runs one or several C streams which compress its input buffers and sends buffers with compressed data to output stream. it may be several threads that do it, making a pipe - fourth thread writes compressed data to output archive all four threads are started by line runP$ scanning |> reading |> compression |> writing where each thread represented by a function which has additional argument for exchanging data with previous and next thread in list: reading pipe = do nextFile <- readP pipe .... writeP pipe buffer running additional background thread and exchanging information with it is also trivial: decompressor <- runAsyncP decompressor writeP decompressor request buffer <- readP decompressor you can see module which implements this as Process.hs from http://www.haskell.org/bz/FreeArc-sources.tar.gz although it's actually only a thin layer around forkIO/Chan/MVar features you can do the same in C# although i guess that syntax overhead will be a bit more and allocating a lot of small non-updateable values may be less efficient because its GC isn't aimed to such usage btw, are you read Hoar's book "Communicating Sequential Processes"? i think that his model is very FPish and reading his book should allow to switch your look at concurrency in right direction -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

btw, are you read Hoar's book "Communicating Sequential Processes"? i
Ok good info :-)
think that his model is very FPish and reading his book should allow
to switch your look at concurrency in right direction
No, I'll check it out.
On 7/1/07, Bulat Ziganshin
Hello Hugh,
Sunday, July 1, 2007, 8:56:05 PM, you wrote:
Genuine question: please could you tell me what are the truly powerful features of Haskell?
Anyway, getting back to my question, there's a whole slew of articles around saying that no-one uses Haskell because they're too stupid. That's certainly an argument, but it possibly lacks a certain objectivity ;-)
i agree with it. haskell represents new programming paradigm and most programmers are unable to learn it without help of college
in other words, there is not yet enough learning infrastructure for FP languages. the same situation was in 80s for OOP languages. this means that learning FP require much more work, or, spending the same time, one will learn FP much worse than OOP
So... what do you see as the "Killer Advantages" that make Haskell stand out from the pack?
i've written 8kloc "real world" program in haskell and can say what was killer features for me:
- natural data structures and easiness of defining algorithms - rich set of list operations - easiness of use of higher-level functions - type inference (dropping almost all declarations) - strong type checking detects many errors just at compile time - non-updateable data simplifies algorithms development
for concurrent programming: - it's easy to split algorithm to several parts that are run concurrently and exchange data - channels allows to organize data streams (like Unix pipes) between threads, non-updatability of data significantly simplifies usage of these data - MVar allows to implement shared updateable variables which automatically locks on their use
shortly said, non-updatability of data significantly simplifies both usual programming and concurrency, especially later. you can do the same with C#
it's an example how i use concurrency for data archiving and compression: - first thread scans disk and finds files to compress. it sends filenames to its output stream - second thread reads contents of these files and sends memory buffers filled with data read to its output stream. it also runs background decompression stream which decompress data from old archive - third thread runs one or several C streams which compress its input buffers and sends buffers with compressed data to output stream. it may be several threads that do it, making a pipe - fourth thread writes compressed data to output archive
all four threads are started by line
runP$ scanning |> reading |> compression |> writing
where each thread represented by a function which has additional argument for exchanging data with previous and next thread in list:
reading pipe = do nextFile <- readP pipe .... writeP pipe buffer
running additional background thread and exchanging information with it is also trivial:
decompressor <- runAsyncP decompressor writeP decompressor request buffer <- readP decompressor
you can see module which implements this as Process.hs from http://www.haskell.org/bz/FreeArc-sources.tar.gz although it's actually only a thin layer around forkIO/Chan/MVar features
you can do the same in C# although i guess that syntax overhead will be a bit more and allocating a lot of small non-updateable values may be less efficient because its GC isn't aimed to such usage
btw, are you read Hoar's book "Communicating Sequential Processes"? i think that his model is very FPish and reading his book should allow to switch your look at concurrency in right direction
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Well, figured out a solution to parsing xml. It's not really pretty, but it works. Basically we just convert the incoming xml into a gread compatible format then use gread :-D If someone has a more elegant solution, please let me know. module ParseXml where import IO import Char import List import Maybe import Data.Generics hiding (Unit) import Text.XML.HXT.Arrow hiding (when) data Config = Config{ name :: String, age :: Int } --data Config = Config{ age :: Int } deriving( Data, Show, Typeable, Ord, Eq, Read ) createConfig = Config "qsdfqsdf" 3 --createConfig = Config 3 gshow' :: Data a => a -> String gshow' t = fromMaybe (showConstr(toConstr t)) (cast t) -- helper function from http://www.defmacro.org/ramblings/haskell-web.html introspectData :: Data a => a -> [(String, String)] introspectData a = zip fields (gmapQ gshow' a) where fields = constrFields $ toConstr a -- function to create xml string from single-layer Haskell data type xmlSerialize object = "<" ++ show(toConstr object) ++ ">" ++ foldr (\(a,b) x -> x ++ "<" ++ a ++ ">" ++ b ++ "" ++ a ++ ">") "" ( introspectData object ) ++ "" ++ show(toConstr object) ++ ">" -- parse xml to HXT tree, and obtain the value of node "fieldname" -- returns a string getValue xml fieldname | length(resultlist) > 0 = Just (head resultlist) | otherwise = Nothing where resultlist = (runLA ( constA xml >>> xread >>> deep ( hasName fieldname ) >>> getChildren >>> getText ))[] -- parse templateobject to get list of field names -- apply these to xml to get list of values -- return (fieldnames list, value list) xmlToGShowFormat :: Data a => String -> a -> String xmlToGShowFormat xml templateobject = go where mainconstructorname = (showConstr $ toConstr templateobject) fields = constrFields $ toConstr templateobject values = map ( \fieldname -> getValue xml fieldname ) fields datatypes = gmapQ (dataTypeOf) templateobject constrs = gmapQ (toConstr) templateobject datatypereps = gmapQ (dataTypeRep . dataTypeOf) templateobject fieldtogshowformat (value,datatyperep) = case datatyperep of IntRep -> "(" ++ fromJust value ++ ")" _ -> show(fromJust value) formattedfieldlist = map (fieldtogshowformat) (zip values datatypereps) go = "(" ++ mainconstructorname ++ " " ++ (concat $ intersperse " " formattedfieldlist ) ++ ")" xmlDeserialize xml templateobject = fst $ head $ gread( xmlToGShowFormat xml templateobject) dotest = xmlDeserialize (xmlSerialize createConfig) createConfig :: Config dotest' = xmlDeserialize ("<Config><age>12</age><name>test name!</name></Config>") createConfig :: Config

On Sun, Jul 01, 2007 at 10:48:11PM +0200, Hugh Perkins wrote:
On 7/1/07, Bulat Ziganshin <[1]bulat.ziganshin@gmail.com> wrote:
btw, are you read Hoar's book "Communicating Sequential Processes"? i think that his model is very FPish and reading his book should allow to switch your look at concurrency in right direction
No, I'll check it out.
Just as a point of interest, Jim Davies at Oxford University Computing Lab. has edited a revised edition of Tony Hoare's book which is freely available from http://usingcsp.com/. (Full disclosure: my day job is/was developing CSP-related tools.) Phil -- http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt

Coooolll :-) Thanks for the link. Ermmmm.... are you the Philip Armstrong I was at college with????

On Mon, Jul 02, 2007 at 12:23:36AM +0200, Hugh Perkins wrote:
Coooolll :-) Thanks for the link.
Ermmmm.... are you the Philip Armstrong I was at college with????
Shhh. Don't tell everyone or they'll all want one. (iow, yes: Probably.) Phil -- http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt

lol small world :-)
On 7/2/07, Philip Armstrong
On Mon, Jul 02, 2007 at 12:23:36AM +0200, Hugh Perkins wrote:
Coooolll :-) Thanks for the link.
Ermmmm.... are you the Philip Armstrong I was at college with????
Shhh. Don't tell everyone or they'll all want one. (iow, yes: Probably.)
Phil
participants (5)
-
Andrea Vezzosi
-
Bulat Ziganshin
-
Hugh Perkins
-
Philip Armstrong
-
Udo Stenzel