tofromxml-0.1.0.2: Reading and writing Haskell data from and to XML

Copyright(C) Robert Reitmeier, 2014
LicenseGPL-3
Maintainerconcat ["public","< a t >","thinking","-","machines",".","net"]
Stabilityexperimental
Portabilityn/a
Safe HaskellNone
LanguageHaskell2010

Text.XML.ToFromXML

Description

In order to write a Haskell value to an XML file, the value's type just has to be an instance of Generic (usually one would use the deriving Generic clause in the data defintion). Then, the writeToXMLFile will write an XML file representing the value. This value can be read again using readFromXMLFile. See the following example (pragma syntax below is broken, how can one correctly incorporate comments in a haddock code block?):

{ -# LANGUAGE DeriveGeneric #- }
{ -# OPTIONS_GHC -fcontext-stack=50 #- }

import Text.XML.ToFromXML
-- GHC.Generics is exported by ToFromXML

data Test = Test { str::String, something::(Int,Char) }
	deriving (Generic,Show,Eq)

main = do
	let test = Test "abc" (42,'z')
	writeToXMLFile "test.xml" test
	putStrLn $ "writeToXMLFile : " ++ show test

	-- readFromXMLFile's return type can be inferred in this example,
	-- otherwise it would have to be declared
	test' <- readFromXMLFile "test.xml"
	putStrLn $ "readFromXMLFile: " ++ show test'
	
	putStrLn $ if test==test' then "OK." else "ERROR!"

Remark: Both writeToXMLFile and readFromXMLFile require the value type a's generic represention Rep a be an instance of GFromToXML, but this is automatically fulfilled.

The generated XML file is

<?xml version="1.0" encoding="UTF-8"?>
<CONSTRUCTOR name="Test">
  <ARG-1 selector="str">abc</ARG-1>
  <ARG-2 selector="something">
    <PAIR>
      <FIRST>42</FIRST>
      <SECOND>z</SECOND>
    </PAIR>
  </ARG-2>
</CONSTRUCTOR>

The general intention of this module is to keep the generated XML as intuitive and easy to read as possible. For example, we do flatten nested pairs used by GHC.Generics to represent n-tuples, and TABs and CRs are used to encode long text, so it keeps its formatting (unfortunately, CDATA sections are not supported with the Node types used in Text.XML.Expat.Pickle).

One might need to increase the context stack size with the -fcontext-stack option when compiling code using this module.

A test suite is included in the package, see TestToFromXML.hs in the package's test directory.

Synopsis

Documentation

class ToFromXML a where Source

The class ToFromXML declares that there is a pickler for the instance type wrapped by the generic representation's K1 constructor. There are instances for data types that we do want to encode in more precise way, not following the generic pattern. For example, we want to encode unit () as a distinct tag <UNIT/>, not as text content generated with show/read. We give a default signature and definition which we can use conveniently by just stating instance ToFromXML Word32 for numeric types, for example.

Special chars are represented in XML by Haskell's escape sequences. A char is not embraced by single quotes in the tag content (as it would be using the default instance).

Since unfortunately CDATA sections are not supported with the Node types used in Text.XML.Expat.Pickle we are relying on, a String has to be represented in XML as a tag's text content, using the common Haskell escape sequences. For better readability and prevention of very long lines in the XML file, after each '\r', '\n' and '\t' the same character is inserted unescaped after the character's escape sequence. The unescaped character is removed again when parsing the String. For example, "abcndef" will be written in the XML file as "abc\nndef", with the LF escaped (i.e. "\n") and followed by a real LF ('\n'). Injecting line breaks and tabs makes long text much more readable und editable by humans (which is one of the original purposes of XML). The real LF will be filtered out again while parsing the XML file String.

Minimal complete definition

Nothing

Methods

xMLPickler :: Pickler a Source

An instance of ToFromXML provides a pickler for type a.

toXML :: (Generic a, GToFromXML (Rep a)) => a -> ByteString Source

Converts generic Haskell data to a (strict) ByteString containing the XML representation. In most cases, the data type would probably be deriving Generic using the DeriveGeneric language pragma.

fromXML :: (Generic a, GToFromXML (Rep a)) => ByteString -> a Source

Convenience function wrapping around fromXMLEither, throwing an error in case of a parsing error.

fromXMLEither :: GToFromXML f => ByteString -> Either String (f p) Source

Construct generic Haskell data from a (strict) ByteString containing the XML representation. fromXMLEither will return Left in case of a XMLParseError, Right otherwise.

readFromXMLFile :: (Generic a, GToFromXML (Rep a)) => FilePath -> IO a Source

Action reading generic Haskell data from an XML file. The underlying readFile operation is strict.

writeToXMLFile :: (Generic a, GToFromXML (Rep a)) => FilePath -> a -> IO () Source

Action writing an XML representation of generic Haskell data to a file. The underlying writeFile operation is strict.