Re: [Haskell] Haskell as a markup language

2006-03-22 Thread oleg

shelarcy wrote:
 SXML can add useful function for macro, like this;

 (define (M:link keyword url)
`(a (@ (href ,url)) ,keyword))

 (define (M:link_amazon keyword asin)
(M:link keyword
`(http://www.amazon.co.jp/exec/obidos/ASIN/; ,asin /someone_id/)))

 (define (M:book keyword urn)
`((cite ,(M:link keyword `(urn:isbn: ,urn)))
( ,(M:link_amazon Amazon urn) ) ))

 and M:link can use SXML code in its parameter any place;

 ,(M:link `(SXML  (em can write)  this.) http://foo.bar/;)

HSXML can do all this, too (modulo replacement of the round
parentheses with a pair of square ones).

First, we need `Transparent' SPAN: the grouping of SPAN-level
elements.  TSPAN is an administrative element, which is precisely
equivalent to the sequence of SPAN-level elements in its content.  It
is useful as a return value from a function, if a function needs to
return several SPAN-level elements.  The body of TSPAN has the content
Inline, and the TSPAN element itself is in the Inline context.  TSPAN
is the `inline' analogue of TDIV (which works in the block context).

 newtype TSPAN a = TSPAN a deriving Show
 tspan x = build (as_inline . HW . TSPAN . rev'apppend HNil) nil_inline x

 instance RenderInline b = RenderInline (HW CT_inline (TSPAN b)) where
 render_inline f (HW (TSPAN body)) = render_inline f body

We can now write

 link url body = a (attr [href (URL url)]) body

 link_amazon asin = 
link (concat [http://www.amazon.co.jp/exec/obidos/ASIN/,asin,
/someone_id/])

which is the close analogue of the SXML code above, only the 'body'
argument is the last one. That seems to be more consistent, although
tastes may vary.

we can write a simple test
 test1 = as_block (p [[link_amazon 123.456 Amazon book]])

where the body of the link is a simple string. But we can make
it a bit more complex:

 test2 = as_block (p [[link_amazon 123.456 [[tspan Amazon book)

In fact, we can use arbitrary _inline_ markup in the body of the link:

 book urn body = as_block $
 p [[link (urn:isbn: ++ urn) body]]
   ( [[link_amazon urn [[tspan [[em Amazon]] nosp .com )
 test3 = book 123.456 Amazon book

Again, the body of the 'book' doesn't have to be a simple string. We
can use arbitrary _inline_ markup.

 test4 = book 123.456 
 [[tspan HSXML [[em [[strong can]] write]] this, too.]]

But the following leads to the type error
``Couldn't match `CT_inline' against `CT_block'''

-- testb = book 123.456 
--[[h1 HSXML [[em [[strong can]] write]] this, too.]]

Indeed, the h1 element is a block rather than inline element.

Rendering of test4 above

 test4h :: IO () = runHTMLRender $ render test4

gives the expected output.

Perhaps we should move to Cafe for further discussion?

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


Re: [Haskell] Haskell as a markup language

2006-03-21 Thread shelarcy

On Wed, 01 Mar 2006 17:46:47 +0900, [EMAIL PROTECTED] wrote:

We demonstrate that Haskell as it is, with no TH or other
pre-processors, can rather concisely represent semi-structured
documents and the rules of their processing. In short, Haskell can
implement SXML (ssax.sourceforge.net), right in its syntax and with
the *open* and extensible set of `tags'. The benefit of Haskell is of
course in static type guarantees, such as prohibiting an H1 element to
appear in the character content of other elements. It also seems that
the specification of various pre-post-order and context-sensitive
traversals is more concise in Haskell compared to Scheme. Again, we
are talking about the existing Haskell, i.e., Haskell98 plus common
extensions. No Template Haskell or even overlapping instances are
required.


It's Great!
But ... replacing my HTML Generator from SXML, I face s problems.



We should note that |title| -- which can be either an element or an
attribute -- is indeed rendered differently depending on the context.

Just to emphasize the extensibility of the framework, we show how easy
it is to add new elements. For example, the `tags' |longdash|, |a|, |div|
and |title| are not defined in the base file HSXML.hs. We add these
tags in sample1c.hs, as follows:

Let us start with an abbreviation for the long dash. It may appear in
the character content of an element or an attribute


data LongDash = LongDash deriving Show
longdash :: Check_ia LongDash ct = HW ct LongDash
longdash = HW LongDash

-- and how to render it in HTML
instance RenderInline (HW ct LongDash) where
   render_inline f _ = emit_lit mdash;  return f


Actually, the latter instance describes rendering of longdash in any
|MonadRender m| -- any monad that defines morphisms |emit|,
|emit_elem| and |emit_attr|.

Anchor is an inline element with an inline content


data Anchor a b = Anchor a b deriving Show
a attrs body =
  build (as_inline . HW . Anchor (as_block attrs) . rev'apppend HNil)
nil_inline body

instance (Render a, RenderInline b) =RenderInline (HW ct (Anchor a b))  
where

render_inline f (HW (Anchor attrs body)) =
emit_elem a [] (Just (render attrs)) (render_ib body)
 return False



Title can be either
- a block-level element whose content is CT_inline
- an attribute (whose content is, therefore, CT_attr)


newtype Title a = Title a deriving Show
title x = build ((`as_ctx`  co) . HW . Title . rev'apppend HNil) nil_ab  
x

   where nil_ab = HW HNil `as_ctx` ci
  (ci,co) = title_ctx
class Check_ia (Title ()) i = TitleCtx i o | i - o, o - i where
title_ctx :: (HW i a, HW o a) ; title_ctx = undefined
instance TitleCtx CT_attr CT_battr
instance TitleCtx CT_inline CT_block


It can be rendered context-sensitively:


instance RenderInline a = Render (HW CT_battr (Title a)) where
   render (HW (Title x)) = emit_attr title
 ((render_inline False x)  return ())
instance RenderInline a = Render (HW CT_block (Title a)) where
   render (HW (Title x)) = emit_elem title [Hint_nl] Nothing
 (render_ib x)


Okay, I know how to add element, attribute and Character Entity
References ... but how to write placeholder - pseudo element and
pseudo attribute in HSXML?


SXML can add useful function for macro, like this;

(define (M:link keyword url)
   `(a (@ (href ,url)) ,keyword))

(define (M:link_amazon keyword asin)
   (M:link keyword
 `(http://www.amazon.co.jp/exec/obidos/ASIN/; ,asin /someone_id/)))

(define (M:book keyword urn)
   `((cite ,(M:link keyword `(urn:isbn: ,urn)))
 ( ,(M:link_amazon Amazon urn) ) ))

and M:link can use SXML code in its parameter any place;

,(M:link `(SXML  (em can write)  this.) http://foo.bar/;)


But if use HSXML, I must write rest of List in last parameter,

link url keyword = a (attr [href url]) keyword
linkToAmazon asin keyword = link (URL $ concat
[http://www.amazon.co.jp/exec/obidos/ASIN/;, asin, /someone_id/])
keyword

and can't write part of code. So I must wirte code like this form,


book urn first rest keyword = p first [[link (URL $ concat [urn:isbn:,
urn]) keyword]] ( [[linkToAmazon urn Amazon]] ) rest

I think this is less convenient than SXML.



--
shelarcy shelarcy capella.freemail.ne.jp
http://page.freett.com/shelarcy/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Haskell as a markup language

2006-03-01 Thread oleg

We demonstrate that Haskell as it is, with no TH or other
pre-processors, can rather concisely represent semi-structured
documents and the rules of their processing. In short, Haskell can
implement SXML (ssax.sourceforge.net), right in its syntax and with
the *open* and extensible set of `tags'. The benefit of Haskell is of
course in static type guarantees, such as prohibiting an H1 element to
appear in the character content of other elements. It also seems that
the specification of various pre-post-order and context-sensitive
traversals is more concise in Haskell compared to Scheme. Again, we
are talking about the existing Haskell, i.e., Haskell98 plus common
extensions. No Template Haskell or even overlapping instances are
required.

The features of our framework are:

- extensibility: at any time the user can add new `tags' and
new transformation/traversal modes.

- static safety: there are no dynamics, and no variant data
types for elements or attributes, and thus no possibility of a run-time
pattern-match failure.

- static guarantees: the framework statically ensures that a
`block-level element' cannot appear in the inline (i.e., character)
content and that a character-content entity cannot appear in a pure
element content. Some entities (e.g., `title') may be either element
or attribute. OTH, many other entities may not occur in the attribute
context. Thus the generated XML or HTML document will not only be
well-formed: it would also satisfy some validity constraints. More
validity constraints can be added to the framework.

- flexibility of the traversal: the same document can be
transformed in pre-, post-, accumulating or other ways, even within
the same session. A document can be processed in a pure function, or
in a monadic action, including an IO action. In the latter case, we
can, e.g., verify URLs as we generate an HTML document.
A `tag' can be transformed depending of the transformation modes and
tag's context: e.g., the same `(title title)' expression may appear as
an attribute or an element -- and it will be rendered differently by
the (X)HMTL serializer.

   - pleasant syntax, which closely resembles SXML. We can write
(p string string1 br string3) without unnecessary commas and
other syntactic distractions. We take polyvariadic functions to the
new level (pun intended). We also exploit functional dependencies on a
per-instance level -- which is a very useful but, alas, rarely used
technique.


We introduce two frameworks for representing semi-structured data in
Haskell. In one, semi-structured data is truly a heterogeneous
structure -- and so can be showed, stored, written and read. In the
second approach, semi-structured data are represented as a monadic
value, polymorphic over the rendering monad. Different choices of the
monad give different views of data. In GHC, this amounts to
representing semi-structured data by linked dictionaries; in JHC, both
approaches are probably equivalent. The first representation is quite
reminiscent of HList; the second has clear SYB3 (``Scratch your
boilerplate with class'') overtones, although the realization is quite
different. In particular, there is no need for recursive instances.

Because of the amount of code involved (to describe common HTML tags
and their constraints), this message is not the complete code. The
code is available from

 http://pobox.com/~oleg/ftp/Haskell/HSXML.tar.gz

Please see the files HSXML.hs, HSXML_HTML.hs and the sample code
sample1c.hs for the data-centric framework. The monad-centric
framework is in one self-contained file CSXML.hs.  The first framework
is more in line with SXML, and so will be considered here.

Our running example, inspired by the Haskell.org web site, is:

test_haskell =
(document
 (head
  [title Haskell longdash HaskellWiki]
  [meta_tag [description All about the language br Haskell]])
(body
 [h1 Haskell]
 [div (attr [title titleline])
  [p
   [[a (attr [href (FileURL /haskellwiki/Image:Haskelllogo.jpg)])
 Haskell br A purely functional language]]
   br
  ]
  [p Haskell is a general purpose, 
   [[em [[strong purely]] functional]] programming language]]))


We should point out the absence of commas.  The [[x]] syntax can be
replaced with a simple [x], but that would require overlapping
instances. So far, we have avoided overlapping instances.
Incidentally, in many Scheme systems (and, reputedly, in R6RS) square
brackets are taken to be synonymous to the round ones.


We see that the |br| can be used in various contexts: in the character
content of an element and of an attribute (cf. `description' for the
latter). However, if we try to replace Haskell within the
`description' attribute with [[em Haskell]] we get an error that
Couldn't match `CT_attr' against `CT_inline'
  Expected type: CT_attr
  Inferred type: CT_inline

OTH, the string Haskell that appears within |h1| element may be