[Haskell-cafe] Re: HaXML - creating a simple document

2006-12-30 Thread Terrence Brannon



On 12/30/06, Jeremy Shaw  [EMAIL PROTECTED] wrote:



So may something like this would work:

 main = print $ htmlprint $ go (CString False )


mk.hs:6:33:
Couldn't match expected type `Content i'
   against inferred type `i1 - Content i1'
In the first argument of `go', namely `(CString False )'
In the second argument of `($)', namely `go (CString False )'
In the second argument of `($)', namely
`htmlprint $ (go (CString False ))'

---

I modified it like this and got the error included in the comment:

The type check error for your version is below. I include my modified source and
associated error jeopardy style. Thanks for your efforts on this.

import Text.XML.HaXml.Html.Generate
import Text.XML.HaXml.Combinators
import Text.XML.HaXml.XmlContent
import Text.XML.HaXml.Wrappers

main = print $ htmlprint $  go $ (CString False )
{-
mk.hs:6:34:
Couldn't match expected type `Content i'
   against inferred type `i1 - Content i1'
In the second argument of `($)', namely `(CString False )'
In the second argument of `($)', namely `go $ (CString False )'
In the second argument of `($)', namely
`htmlprint $ (go $ (CString False ))'
-}

go = html []

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: HaXML - creating a simple document

2006-12-30 Thread Terrence Brannon

Actually, the examples directory in the distro for the development release
has a nice program to create an element and print it to stdout called
SimpleTestBool.hs:

module Main where

import List (isPrefixOf)
import Text.XML.HaXml.XmlContent
import Text.XML.HaXml.Types
import Text.PrettyPrint.HughesPJ (render)
import Text.XML.HaXml.Pretty (document)

-- Test stuff
--value1 :: ([(Bool,Int)],(String,Maybe Char))
value1 = True

--main = do (putStrLn . render . document . toXml) value2

main = fWriteXml /dev/tty value1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe