Property definitions

markdown2 $ HtmlRenderer :: defaultinit
# 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