Markdown rendering of Markdown documents

Introduced classes

class MarkdownRenderer

markdown2 :: MarkdownRenderer

Markdown document renderer to Markdown

Redefined classes

redef class MdBlockQuote

markdown2 :: markdown_md_rendering $ MdBlockQuote

A block quote
redef class MdCode

markdown2 :: markdown_md_rendering $ MdCode

An inline code string
redef abstract class MdDelimited

markdown2 :: markdown_md_rendering $ MdDelimited

A node that users delimiters in the Markdown form
redef class MdDocument

markdown2 :: markdown_md_rendering $ MdDocument

A Markdown document
redef class MdFencedCodeBlock

markdown2 :: markdown_md_rendering $ MdFencedCodeBlock

A code block that starts with a fence
redef class MdHardLineBreak

markdown2 :: markdown_md_rendering $ MdHardLineBreak

A hardline break (\\n or \n)
redef class MdHeading

markdown2 :: markdown_md_rendering $ MdHeading

A heading
redef class MdHtmlBlock

markdown2 :: markdown_md_rendering $ MdHtmlBlock

An html block
redef class MdHtmlInline

markdown2 :: markdown_md_rendering $ MdHtmlInline

An inlined html string
redef class MdImage

markdown2 :: markdown_md_rendering $ MdImage

An image
redef class MdIndentedCodeBlock

markdown2 :: markdown_md_rendering $ MdIndentedCodeBlock

A block code that starts with an indent
redef abstract class MdLinkOrImage

markdown2 :: markdown_md_rendering $ MdLinkOrImage

A link or image
redef class MdListItem

markdown2 :: markdown_md_rendering $ MdListItem

An ordered or unordered list item block
redef abstract class MdNode

markdown2 :: markdown_md_rendering $ MdNode

An abstract node
redef class MdOrderedList

markdown2 :: markdown_md_rendering $ MdOrderedList

An ordered list block
redef class MdParagraph

markdown2 :: markdown_md_rendering $ MdParagraph

A paragraph block
redef class MdSoftLineBreak

markdown2 :: markdown_md_rendering $ MdSoftLineBreak

A soft line breack (\r or \n)
redef class MdText

markdown2 :: markdown_md_rendering $ MdText

A raw text token

All class definitions

class MarkdownRenderer

markdown2 $ MarkdownRenderer

Markdown document renderer to Markdown
redef class MdBlockQuote

markdown2 :: markdown_md_rendering $ MdBlockQuote

A block quote
redef class MdCode

markdown2 :: markdown_md_rendering $ MdCode

An inline code string
redef abstract class MdDelimited

markdown2 :: markdown_md_rendering $ MdDelimited

A node that users delimiters in the Markdown form
redef class MdDocument

markdown2 :: markdown_md_rendering $ MdDocument

A Markdown document
redef class MdFencedCodeBlock

markdown2 :: markdown_md_rendering $ MdFencedCodeBlock

A code block that starts with a fence
redef class MdHardLineBreak

markdown2 :: markdown_md_rendering $ MdHardLineBreak

A hardline break (\\n or \n)
redef class MdHeading

markdown2 :: markdown_md_rendering $ MdHeading

A heading
redef class MdHtmlBlock

markdown2 :: markdown_md_rendering $ MdHtmlBlock

An html block
redef class MdHtmlInline

markdown2 :: markdown_md_rendering $ MdHtmlInline

An inlined html string
redef class MdImage

markdown2 :: markdown_md_rendering $ MdImage

An image
redef class MdIndentedCodeBlock

markdown2 :: markdown_md_rendering $ MdIndentedCodeBlock

A block code that starts with an indent
redef abstract class MdLinkOrImage

markdown2 :: markdown_md_rendering $ MdLinkOrImage

A link or image
redef class MdListItem

markdown2 :: markdown_md_rendering $ MdListItem

An ordered or unordered list item block
redef abstract class MdNode

markdown2 :: markdown_md_rendering $ MdNode

An abstract node
redef class MdOrderedList

markdown2 :: markdown_md_rendering $ MdOrderedList

An ordered list block
redef class MdParagraph

markdown2 :: markdown_md_rendering $ MdParagraph

A paragraph block
redef class MdSoftLineBreak

markdown2 :: markdown_md_rendering $ MdSoftLineBreak

A soft line breack (\r or \n)
redef class MdText

markdown2 :: markdown_md_rendering $ MdText

A raw text token
package_diagram markdown2::markdown_md_rendering markdown_md_rendering markdown2::markdown_rendering markdown_rendering markdown2::markdown_md_rendering->markdown2::markdown_rendering markdown2::markdown_github markdown_github markdown2::markdown_md_rendering->markdown2::markdown_github markdown2::markdown_wikilinks markdown_wikilinks markdown2::markdown_md_rendering->markdown2::markdown_wikilinks markdown2::markdown_ast markdown_ast markdown2::markdown_rendering->markdown2::markdown_ast markdown2::markdown_block_parsing markdown_block_parsing markdown2::markdown_github->markdown2::markdown_block_parsing markdown2::markdown_wikilinks->markdown2::markdown_block_parsing ...markdown2::markdown_ast ... ...markdown2::markdown_ast->markdown2::markdown_ast ...markdown2::markdown_block_parsing ... ...markdown2::markdown_block_parsing->markdown2::markdown_block_parsing markdown2::nitmd nitmd markdown2::nitmd->markdown2::markdown_md_rendering a_star-m a_star-m a_star-m->markdown2::nitmd a_star-m... ... a_star-m...->a_star-m

Ancestors

module abstract_collection

core :: abstract_collection

Abstract collection classes and services.
module abstract_text

core :: abstract_text

Abstract class for manipulation of sequences of characters
module array

core :: array

This module introduces the standard array structure.
module bitset

core :: bitset

Services to handle BitSet
module bytes

core :: bytes

Services for byte streams and arrays
module circular_array

core :: circular_array

Efficient data structure to access both end of the sequence.
module codec_base

core :: codec_base

Base for codecs to use with streams
module codecs

core :: codecs

Group module for all codec-related manipulations
module collection

core :: collection

This module define several collection classes.
module core

core :: core

Standard classes and methods used by default by Nit programs and libraries.
module environ

core :: environ

Access to the environment variables of the process
module error

core :: error

Standard error-management infrastructure.
module exec

core :: exec

Invocation and management of operating system sub-processes.
module file

core :: file

File manipulations (create, read, write, etc.)
module fixed_ints

core :: fixed_ints

Basic integers of fixed-precision
module fixed_ints_text

core :: fixed_ints_text

Text services to complement fixed_ints
module flat

core :: flat

All the array-based text representations
module gc

core :: gc

Access to the Nit internal garbage collection mechanism
module hash_collection

core :: hash_collection

Introduce HashMap and HashSet.
module iso8859_1

core :: iso8859_1

Codec for ISO8859-1 I/O
module kernel

core :: kernel

Most basic classes and methods.
module list

core :: list

This module handle double linked lists
module markdown_ast

markdown2 :: markdown_ast

Markdown AST representation
module markdown_block_parsing

markdown2 :: markdown_block_parsing

Markdown blocks parsing
module markdown_inline_parsing

markdown2 :: markdown_inline_parsing

Parser for inline markdown
module math

core :: math

Mathematical operations
module native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
module protocol

core :: protocol

module queue

core :: queue

Queuing data structures and wrappers
module range

core :: range

Module for range of discrete objects.
module re

core :: re

Regular expression support for all services based on Pattern
module ropes

core :: ropes

Tree-based representation of a String.
module sorter

core :: sorter

This module contains classes used to compare things and sorts arrays.
module stream

core :: stream

Input and output streams of characters
module text

core :: text

All the classes and methods related to the manipulation of text entities
module time

core :: time

Management of time and dates
module union_find

core :: union_find

union–find algorithm using an efficient disjoint-set data structure
module utf8

core :: utf8

Codec for UTF-8 I/O

Parents

module markdown_github

markdown2 :: markdown_github

Markdown Github mode
module markdown_rendering

markdown2 :: markdown_rendering

Markdown document rendering

Children

module nitmd

markdown2 :: nitmd

A Markdown parser for Nit.

Descendants

module a_star-m

a_star-m

# Markdown rendering of Markdown documents
module markdown_md_rendering

import markdown_rendering
import markdown_github
import markdown_wikilinks

# Markdown document renderer to Markdown
class MarkdownRenderer
	super MdRenderer

	# Markdown output under construction
	private var md: Buffer is noinit

	# Render `node` as Markdown
	redef fun render(node) do
		reset
		enter_visit(node)
		return md.write_to_string
	end

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

	# Reset internal state
	fun reset do
		md = new Buffer
	end

	# Current indentation level
	private var indent = 0

	# Are we currently in a blockquote?
	var in_quote = 0

	# Add a `md` string to the output
	fun add_raw(md: String) do self.md.append(md)

	# Add a blank line to the output
	fun add_line do add_raw "\n"

	# Add an indentation depending on `ident` level
	fun add_indent do
		add_raw " " * indent
	end
end

private class TextLengthVisitor
	super MdVisitor

	var length = 0

	redef fun visit(node) do node.process_len(self)
end

redef class MdNode

	# Render `self` as Markdown
	fun render_md(v: MarkdownRenderer) do visit_all(v)

	private fun process_len(v: TextLengthVisitor) do visit_all(v)
end

redef class MdDocument
	redef fun render_md(v) do
		var node = first_child
		while node != null do
			v.enter_visit(node)
			node = node.next
			if node != null then
				v.add_line
			end
		end
	end
end

# Blocks

redef class MdBlockQuote
	redef fun render_md(v) do
		v.in_quote += 1
		var node = first_child
		while node != null do
			v.add_indent
			v.add_raw "> "
			v.enter_visit(node)
			node = node.next
		end
		v.in_quote -= 1
	end
end

redef class MdIndentedCodeBlock
	redef fun render_md(v) do
		var literal = self.literal
		if literal == null then return

		var lines = literal.split("\n")
		for i in [0..lines.length[ do
			if i == lines.length - 1 then continue
			var line = lines[i]
			if line.is_empty then
				v.add_raw "\n"
			else
				v.add_indent
				if use_tabs then
					v.add_raw "\t"
				else
					v.add_raw " " * 4
				end
				v.add_raw line
				v.add_line
			end
		end
	end
end

redef class MdFencedCodeBlock
	redef fun render_md(v) do
		var info = self.info
		v.add_indent
		v.add_raw fence_char.to_s * fence_length
		v.add_raw info or else ""
		for line in (literal or else "").split("\n") do
			v.add_line
			if not line.is_empty then
				v.add_indent
			end
			v.add_raw line
		end
		v.add_indent
		v.add_raw fence_char.to_s * fence_length
		v.add_line
	end
end

redef class MdHeading
	redef fun render_md(v) do
		if is_setext then
			visit_all(v)
			var length_visitor = new TextLengthVisitor
			length_visitor.enter_visit(self)
			v.add_line
			if level == 1 then
				v.add_raw "=" * length_visitor.length
			else
				v.add_raw "-" * length_visitor.length
			end
		else
			v.add_raw "#" * level
			v.add_raw " "
			visit_all(v)
			if has_atx_trailing then
				v.add_raw " "
				v.add_raw "#" * level
			end
		end
		v.add_line
	end
end

redef class MdOrderedList
	# Children numbering
	private var md_numbering: Int = start_number is lazy
end

redef class MdListItem
	redef fun render_md(v) do
		var parent = self.parent
		var is_tight = parent.as(MdListBlock).is_tight

		v.add_indent
		if parent isa MdUnorderedList then
			v.add_raw parent.bullet_marker.to_s
			v.indent += 2
		else if parent isa MdOrderedList then
			v.add_raw "{parent.md_numbering}{parent.delimiter.to_s}"
			v.indent += 3
		end

		var node = first_child
		if node != null then
			v.add_raw " "
		else
			v.add_line
		end
		while node != null do
			v.enter_visit(node)
			node = node.next
			if node != null and not is_tight then
				v.add_line
			end
		end

		if next != null and not is_tight then
			v.add_line
		end

		if parent isa MdUnorderedList then
			v.indent -= 2
		else if parent isa MdOrderedList then
			parent.md_numbering += 1
			v.indent -= 3
		end
	end
end

redef class MdParagraph
	redef fun render_md(v) do
		if not parent isa MdBlockQuote and not parent isa MdListItem or prev != null then
			v.add_indent
		end
		# if parent isa MdBlockQuote then
			# v.add_raw "> "
			# var node = first_child
			# while node != null do
				# v.enter_visit(node)
				# if node isa MdSoftLineBreak or node isa MdHardLineBreak then
					# v.add_raw "> "
				# end
				# node = node.next
			# end
			# v.add_line
			# return
		# end
		visit_all(v)
		v.add_line
	end
end

redef class MdThematicBreak
	redef fun render_md(v) do
		v.add_raw original_pattern
		v.add_line
	end
end

redef class MdHtmlBlock
	redef fun render_md(v) do
		v.add_raw literal or else ""
		v.add_line
	end
end

# Inlines

redef class MdHardLineBreak
	redef fun render_md(v) do
		if has_backslash then
			v.add_raw "\\"
		else
			v.add_raw "  "
		end
		v.add_line
		v.add_indent
		v.add_raw "> " * v.in_quote
	end

	redef fun process_len(v) do
		super
		v.length += 1
	end
end

redef class MdSoftLineBreak
	redef fun render_md(v) do
		v.add_line
		v.add_indent
		v.add_raw "> " * v.in_quote
	end

	redef fun process_len(v) do
		super
		v.length += 1
	end
end

redef class MdCode
	redef fun render_md(v) do
		v.add_raw delimiter
		v.add_raw literal
		v.add_raw delimiter
	end

	redef fun process_len(v) do
		super
		v.length += delimiter.length
	end
end

redef class MdDelimited
	redef fun render_md(v) do
		v.add_raw delimiter
		visit_all(v)
		v.add_raw delimiter
	end

	redef fun process_len(v) do
		super
		v.length += delimiter.length * 2
	end
end

redef class MdHtmlInline
	redef fun render_md(v) do
		v.add_raw literal
	end

	redef fun process_len(v) do
		v.length += literal.length
	end
end

redef class MdLinkOrImage
	redef fun render_md(v) do
		var title = self.title
		v.add_raw "["
		visit_all(v)
		v.add_raw "]"
		v.add_raw "("
		if has_brackets then
			v.add_raw "<"
		end
		v.add_raw destination
		if has_brackets then
			v.add_raw ">"
		end
		if title != null and not title.is_empty then
			v.add_raw " \""
			v.add_raw title.replace("\"", "\\\"")
			v.add_raw "\""
		end
		v.add_raw ")"
	end
end


redef class MdImage
	redef fun render_md(v) do
		v.add_raw "!"
		super
	end
end

redef class MdLink
	redef fun render_md(v) do
		if is_autolink then
			v.add_raw "<"
			v.add_raw destination
			v.add_raw ">"
			return
		end
		super
	end
end

redef class MdText
	redef fun render_md(v) do
		v.add_raw literal
	end

	redef fun process_len(v) do
		v.length += literal.length
	end
end

# Wikilinks

redef class MdWikilink
	redef fun render_md(v) do
		v.add_raw "[["
		var title = self.title
		if title != null then
			v.add_raw "{title} | "
		end
		v.add_raw link
		v.add_raw "]]"
	end
end
lib/markdown2/markdown_md_rendering.nit:15,1--392,3