Markdown document renderer to HTML

Introduced properties

fun add_line

markdown2 :: HtmlRenderer :: add_line

Add a blank line to the output
fun add_raw(html: String)

markdown2 :: HtmlRenderer :: add_raw

Add a raw html string to the output
fun add_text(text: String)

markdown2 :: HtmlRenderer :: add_text

Add text string to the output
fun allowed_id_chars: Array[Char]

markdown2 :: HtmlRenderer :: allowed_id_chars

Allowed characters in ids
protected fun allowed_id_chars=(allowed_id_chars: Array[Char])

markdown2 :: HtmlRenderer :: allowed_id_chars=

Allowed characters in ids
init defaultinit(enable_heading_ids: nullable Bool)

markdown2 :: HtmlRenderer :: defaultinit

fun enable_heading_ids: Bool

markdown2 :: HtmlRenderer :: enable_heading_ids

Add id tags to headings
fun enable_heading_ids=(enable_heading_ids: nullable Bool)

markdown2 :: HtmlRenderer :: enable_heading_ids=

Add id tags to headings
fun encode_uri(uri: String): String

markdown2 :: HtmlRenderer :: encode_uri

Encode the uri string
fun headings: ArrayMap[String, MdHeading]

markdown2 :: HtmlRenderer :: headings

Associate headings ids to blocks
protected fun headings=(headings: ArrayMap[String, MdHeading])

markdown2 :: HtmlRenderer :: headings=

Associate headings ids to blocks
fun html_escape(string: String, keep_entities: Bool): String

markdown2 :: HtmlRenderer :: html_escape

Escape string to HTML
fun reset

markdown2 :: HtmlRenderer :: reset

Reset headings and internal state
fun strip_id(text: String): String

markdown2 :: HtmlRenderer :: strip_id

Strip heading id

Redefined properties

redef type SELF: HtmlRenderer

markdown2 $ HtmlRenderer :: SELF

Type of this instance, automatically specialized in every class
redef fun render(document: MdNode): String

markdown2 $ HtmlRenderer :: render

Render document as HTML
redef fun visit(node: MdNode)

markdown2 $ HtmlRenderer :: visit

Visit node

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun add_line

markdown2 :: HtmlRenderer :: add_line

Add a blank line to the output
fun add_raw(html: String)

markdown2 :: HtmlRenderer :: add_raw

Add a raw html string to the output
fun add_text(text: String)

markdown2 :: HtmlRenderer :: add_text

Add text string to the output
fun allowed_id_chars: Array[Char]

markdown2 :: HtmlRenderer :: allowed_id_chars

Allowed characters in ids
protected fun allowed_id_chars=(allowed_id_chars: Array[Char])

markdown2 :: HtmlRenderer :: allowed_id_chars=

Allowed characters in ids
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
init defaultinit(enable_heading_ids: nullable Bool)

markdown2 :: HtmlRenderer :: defaultinit

fun enable_heading_ids: Bool

markdown2 :: HtmlRenderer :: enable_heading_ids

Add id tags to headings
fun enable_heading_ids=(enable_heading_ids: nullable Bool)

markdown2 :: HtmlRenderer :: enable_heading_ids=

Add id tags to headings
fun encode_uri(uri: String): String

markdown2 :: HtmlRenderer :: encode_uri

Encode the uri string
fun enter_visit(node: MdNode)

markdown2 :: MdVisitor :: enter_visit

Start visiting node
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
fun headings: ArrayMap[String, MdHeading]

markdown2 :: HtmlRenderer :: headings

Associate headings ids to blocks
protected fun headings=(headings: ArrayMap[String, MdHeading])

markdown2 :: HtmlRenderer :: headings=

Associate headings ids to blocks
fun html_escape(string: String, keep_entities: Bool): String

markdown2 :: HtmlRenderer :: html_escape

Escape string to HTML
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
abstract fun render(node: MdNode): String

markdown2 :: MdRenderer :: render

Render node
fun reset

markdown2 :: HtmlRenderer :: reset

Reset headings and internal state
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun strip_id(text: String): String

markdown2 :: HtmlRenderer :: strip_id

Strip heading id
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
protected abstract fun visit(node: MdNode)

markdown2 :: MdVisitor :: visit

Visit node
package_diagram markdown2::HtmlRenderer HtmlRenderer markdown2::MdRenderer MdRenderer markdown2::HtmlRenderer->markdown2::MdRenderer markdown2::MdVisitor MdVisitor markdown2::MdRenderer->markdown2::MdVisitor ...markdown2::MdVisitor ... ...markdown2::MdVisitor->markdown2::MdVisitor

Ancestors

interface MdVisitor

markdown2 :: MdVisitor

A visitor for Markdown AST
interface Object

core :: Object

The root of the class hierarchy.

Parents

interface MdRenderer

markdown2 :: MdRenderer

Common interface for all markdown renderer

Class definitions

markdown2 $ HtmlRenderer
# Markdown document renderer to HTML
class HtmlRenderer
	super MdRenderer

	# HTML output under construction
	private var html: Buffer is noinit

	# Render `document` as HTML
	redef fun render(document) do
		reset
		enter_visit(document)
		return html.write_to_string
	end

	redef fun visit(node) do node.render_html(self)

	# Reset `headings` and internal state
	fun reset do
		html = new Buffer
		if enable_heading_ids then headings.clear
	end

	# Last char visited
	#
	# Used to avoid double blank lines.
	private var last_char: nullable Char = null

	# Add `string` to `html`
	private fun add(string: String) do
		html.append(string)
		if not html.is_empty then
			last_char = html.last
		end
	end

	# Add a raw `html` string to the output
	#
	# Raw means that the string will not be escaped.
	fun add_raw(html: String) do add html

	# Add `text` string to the output
	#
	# The string will be escaped.
	fun add_text(text: String) do add html_escape(text, true)

	# Add a blank line to the output
	fun add_line do
		if last_char != null and last_char != '\n' then
			add "\n"
		end
	end

	# Escape `string` to HTML
	#
	# When `keep_entities`, HTML entities will not be escaped.
	fun html_escape(string: String, keep_entities: Bool): String do
		var buf: nullable Buffer = null
		for i in [0..string.length[ do
			var c = string.chars[i]
			var sub = null
			if c == '&' and (not keep_entities or string.search_from(re_entity, i) == null) then
				sub = "&"
			else if c == '<' then
				sub = "&lt;"
			else if c == '>' then
				sub = "&gt;"
			else if c == '"' then
				sub = "&quot;"
			else
				if buf != null then buf.add c
				continue
			end
			if buf == null then
				buf = new Buffer
				for j in [0..i[ do buf.add string.chars[j]
			end
			buf.append sub
		end

		if buf == null then return string
		return buf.to_s
	end

	# HTML entity pattern
	private var re_entity: Regex = "^&(#x[a-f0-9]\{1,8\}|#[0-9]\{1,8\}|[a-z][a-z0-9]\{1,31\});".to_re

	# Encode the `uri` string
	fun encode_uri(uri: String): String do
		var buf = new Buffer

		var i = 0
		while i < uri.length do
			var c = uri.chars[i]
			if (c >= '0' and c <= '9') or
			   (c >= 'a' and c <= 'z') or
			   (c >= 'A' and c <= 'Z') or
			   c == ';' or c == ',' or c == '/' or c == '?' or
			   c == ':' or c == '@' or c == '=' or c == '+' or
			   c == '$' or c == '-' or c == '_' or c == '.' or
			   c == '!' or c == '~' or c == '*' or c == '(' or
			   c == ')' or c == '#' or c == '\''
			then
				buf.add c
			else if c == '&' then
				buf.append "&amp;"
			else if c == '%' and uri.search_from(re_uri_code, i) != null then
				buf.append uri.substring(i, 3)
				i += 2
			else
				var bytes = c.to_s.bytes
				for b in bytes do buf.append "%{b.to_i.to_hex}".to_upper
			end
			i += 1
		end

		return buf.to_s
	end

	# URI encode pattern
	private var re_uri_code: Regex = "^%[a-zA-Z0-9]\{2\}".to_re

	# Add `id` tags to headings
	var enable_heading_ids = false is optional, writable

	# Associate headings ids to blocks
	var headings = new ArrayMap[String, MdHeading]

	# Strip heading id
	fun strip_id(text: String): String do
		# strip id
		var b = new FlatBuffer
		for c in text do
			if c == ' ' then
				b.add '_'
			else
				if not c.is_letter and
				   not c.is_digit and
				   not allowed_id_chars.has(c) then continue
				b.add c
			end
		end
		var res = b.to_s
		if res.is_empty then res = "_"
		var key = res
		# check for multiple id definitions
		if headings.has_key(key) then
			var i = 1
			key = "{res}_{i}"
			while headings.has_key(key) do
				i += 1
				key = "{res}_{i}"
			end
		end
		return key
	end

	# Allowed characters in ids
	var allowed_id_chars: Array[Char] = ['-', '_', ':', '.']
end
lib/markdown2/markdown_html_rendering.nit:22,1--180,3