An abstract node

Introduced properties

fun append_child(child: MdNode)

markdown2 :: MdNode :: append_child

Append a child to self
fun children: Array[MdNode]

markdown2 :: MdNode :: children

Children nodes of self
fun debug

markdown2 :: MdNode :: debug

Print self AST
fun first_child: nullable MdNode

markdown2 :: MdNode :: first_child

First child
fun first_child=(first_child: nullable MdNode)

markdown2 :: MdNode :: first_child=

First child
fun insert_after(sibling: MdNode)

markdown2 :: MdNode :: insert_after

Insert sibling after self.
fun insert_before(sibling: MdNode)

markdown2 :: MdNode :: insert_before

Insert sibling before self.
fun last_child: nullable MdNode

markdown2 :: MdNode :: last_child

Last child
fun last_child=(last_child: nullable MdNode)

markdown2 :: MdNode :: last_child=

Last child
fun location: MdLocation

markdown2 :: MdNode :: location

Node location in original markdown
protected fun location=(location: MdLocation)

markdown2 :: MdNode :: location=

Node location in original markdown
fun next: nullable MdNode

markdown2 :: MdNode :: next

Next node
fun next=(next: nullable MdNode)

markdown2 :: MdNode :: next=

Next node
fun parent: nullable MdNode

markdown2 :: MdNode :: parent

Node parent
fun parent=(parent: nullable MdNode)

markdown2 :: MdNode :: parent=

Node parent
fun post_process(v: MdPostProcessor)

markdown2 :: MdNode :: post_process

Accept the visit of a MdPostProcessor
fun prepend_child(child: MdNode)

markdown2 :: MdNode :: prepend_child

Prepend a child to self
fun prev: nullable MdNode

markdown2 :: MdNode :: prev

Previous node
fun prev=(prev: nullable MdNode)

markdown2 :: MdNode :: prev=

Previous node
fun raw_text: String

markdown2 :: MdNode :: raw_text

Return self as raw text
fun render_html(v: HtmlRenderer)

markdown2 :: MdNode :: render_html

Render self as HTML
fun render_latex(v: LatexRenderer)

markdown2 :: MdNode :: render_latex

Render self as HTML
fun render_man(v: ManRenderer)

markdown2 :: MdNode :: render_man

Render self as Manpage format
fun render_md(v: MarkdownRenderer)

markdown2 :: MdNode :: render_md

Render self as Markdown
fun render_raw_text(v: RawTextVisitor)

markdown2 :: MdNode :: render_raw_text

Render self as raw text
fun to_s_attrs: String

markdown2 :: MdNode :: to_s_attrs

Returns self attributes as a String
fun visit_all(v: MdVisitor)

markdown2 :: MdNode :: visit_all

Visit all children or self

Redefined properties

redef type SELF: MdNode

markdown2 $ MdNode :: SELF

Type of this instance, automatically specialized in every class
redef fun to_s: String

markdown2 $ MdNode :: to_s

User readable representation of self.

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 append_child(child: MdNode)

markdown2 :: MdNode :: append_child

Append a child to self
fun children: Array[MdNode]

markdown2 :: MdNode :: children

Children nodes of self
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.
fun debug

markdown2 :: MdNode :: debug

Print self AST
fun first_child: nullable MdNode

markdown2 :: MdNode :: first_child

First child
fun first_child=(first_child: nullable MdNode)

markdown2 :: MdNode :: first_child=

First child
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.
init init

core :: Object :: init

fun insert_after(sibling: MdNode)

markdown2 :: MdNode :: insert_after

Insert sibling after self.
fun insert_before(sibling: MdNode)

markdown2 :: MdNode :: insert_before

Insert sibling before self.
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.
fun last_child: nullable MdNode

markdown2 :: MdNode :: last_child

Last child
fun last_child=(last_child: nullable MdNode)

markdown2 :: MdNode :: last_child=

Last child
fun location: MdLocation

markdown2 :: MdNode :: location

Node location in original markdown
protected fun location=(location: MdLocation)

markdown2 :: MdNode :: location=

Node location in original markdown
fun next: nullable MdNode

markdown2 :: MdNode :: next

Next node
fun next=(next: nullable MdNode)

markdown2 :: MdNode :: next=

Next node
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).
fun parent: nullable MdNode

markdown2 :: MdNode :: parent

Node parent
fun parent=(parent: nullable MdNode)

markdown2 :: MdNode :: parent=

Node parent
fun post_process(v: MdPostProcessor)

markdown2 :: MdNode :: post_process

Accept the visit of a MdPostProcessor
fun prepend_child(child: MdNode)

markdown2 :: MdNode :: prepend_child

Prepend a child to self
fun prev: nullable MdNode

markdown2 :: MdNode :: prev

Previous node
fun prev=(prev: nullable MdNode)

markdown2 :: MdNode :: prev=

Previous node
fun raw_text: String

markdown2 :: MdNode :: raw_text

Return self as raw text
fun render_html(v: HtmlRenderer)

markdown2 :: MdNode :: render_html

Render self as HTML
fun render_latex(v: LatexRenderer)

markdown2 :: MdNode :: render_latex

Render self as HTML
fun render_man(v: ManRenderer)

markdown2 :: MdNode :: render_man

Render self as Manpage format
fun render_md(v: MarkdownRenderer)

markdown2 :: MdNode :: render_md

Render self as Markdown
fun render_raw_text(v: RawTextVisitor)

markdown2 :: MdNode :: render_raw_text

Render self as raw text
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
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.
fun to_s_attrs: String

markdown2 :: MdNode :: to_s_attrs

Returns self attributes as a String
fun visit_all(v: MdVisitor)

markdown2 :: MdNode :: visit_all

Visit all children or self
package_diagram markdown2::MdNode MdNode core::Object Object markdown2::MdNode->core::Object markdown2::MdBlock MdBlock markdown2::MdBlock->markdown2::MdNode markdown2::MdLineBreak MdLineBreak markdown2::MdLineBreak->markdown2::MdNode markdown2::MdCode MdCode markdown2::MdCode->markdown2::MdNode markdown2::MdDelimited MdDelimited markdown2::MdDelimited->markdown2::MdNode markdown2::MdHtmlInline MdHtmlInline markdown2::MdHtmlInline->markdown2::MdNode markdown2::MdLinkOrImage MdLinkOrImage markdown2::MdLinkOrImage->markdown2::MdNode markdown2::MdText MdText markdown2::MdText->markdown2::MdNode markdown2::MdWikilink MdWikilink markdown2::MdWikilink->markdown2::MdNode markdown2::MdDocument MdDocument markdown2::MdDocument->markdown2::MdBlock markdown2::MdBlockQuote MdBlockQuote markdown2::MdBlockQuote->markdown2::MdBlock markdown2::MdCodeBlock MdCodeBlock markdown2::MdCodeBlock->markdown2::MdBlock markdown2::MdHeading MdHeading markdown2::MdHeading->markdown2::MdBlock markdown2::MdHtmlBlock MdHtmlBlock markdown2::MdHtmlBlock->markdown2::MdBlock markdown2::MdListBlock MdListBlock markdown2::MdListBlock->markdown2::MdBlock markdown2::MdListItem MdListItem markdown2::MdListItem->markdown2::MdBlock markdown2::MdParagraph MdParagraph markdown2::MdParagraph->markdown2::MdBlock markdown2::MdThematicBreak MdThematicBreak markdown2::MdThematicBreak->markdown2::MdBlock markdown2::MdDocument... ... markdown2::MdDocument...->markdown2::MdDocument markdown2::MdBlockQuote... ... markdown2::MdBlockQuote...->markdown2::MdBlockQuote markdown2::MdCodeBlock... ... markdown2::MdCodeBlock...->markdown2::MdCodeBlock markdown2::MdHeading... ... markdown2::MdHeading...->markdown2::MdHeading markdown2::MdHtmlBlock... ... markdown2::MdHtmlBlock...->markdown2::MdHtmlBlock markdown2::MdListBlock... ... markdown2::MdListBlock...->markdown2::MdListBlock markdown2::MdListItem... ... markdown2::MdListItem...->markdown2::MdListItem markdown2::MdParagraph... ... markdown2::MdParagraph...->markdown2::MdParagraph markdown2::MdThematicBreak... ... markdown2::MdThematicBreak...->markdown2::MdThematicBreak markdown2::MdHardLineBreak MdHardLineBreak markdown2::MdHardLineBreak->markdown2::MdLineBreak markdown2::MdSoftLineBreak MdSoftLineBreak markdown2::MdSoftLineBreak->markdown2::MdLineBreak markdown2::MdHardLineBreak... ... markdown2::MdHardLineBreak...->markdown2::MdHardLineBreak markdown2::MdSoftLineBreak... ... markdown2::MdSoftLineBreak...->markdown2::MdSoftLineBreak markdown2::MdEmphasis MdEmphasis markdown2::MdEmphasis->markdown2::MdDelimited markdown2::MdStrongEmphasis MdStrongEmphasis markdown2::MdStrongEmphasis->markdown2::MdDelimited markdown2::MdStrike MdStrike markdown2::MdStrike->markdown2::MdDelimited markdown2::MdSuper MdSuper markdown2::MdSuper->markdown2::MdDelimited markdown2::MdEmphasis... ... markdown2::MdEmphasis...->markdown2::MdEmphasis markdown2::MdStrongEmphasis... ... markdown2::MdStrongEmphasis...->markdown2::MdStrongEmphasis markdown2::MdStrike... ... markdown2::MdStrike...->markdown2::MdStrike markdown2::MdSuper... ... markdown2::MdSuper...->markdown2::MdSuper markdown2::MdImage MdImage markdown2::MdImage->markdown2::MdLinkOrImage markdown2::MdLink MdLink markdown2::MdLink->markdown2::MdLinkOrImage markdown2::MdImage... ... markdown2::MdImage...->markdown2::MdImage markdown2::MdLink... ... markdown2::MdLink...->markdown2::MdLink

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

abstract class MdBlock

markdown2 :: MdBlock

An abstract markdown block
class MdCode

markdown2 :: MdCode

An inline code string
abstract class MdDelimited

markdown2 :: MdDelimited

A node that users delimiters in the Markdown form
class MdHtmlInline

markdown2 :: MdHtmlInline

An inlined html string
abstract class MdLineBreak

markdown2 :: MdLineBreak

A line break (soft or hard)
abstract class MdLinkOrImage

markdown2 :: MdLinkOrImage

A link or image
class MdText

markdown2 :: MdText

A raw text token

Descendants

class MdBlockQuote

markdown2 :: MdBlockQuote

A block quote
abstract class MdCodeBlock

markdown2 :: MdCodeBlock

A block of code (indented or fenced)
class MdDocument

markdown2 :: MdDocument

A Markdown document
class MdEmphasis

markdown2 :: MdEmphasis

An emphasis
class MdFencedCodeBlock

markdown2 :: MdFencedCodeBlock

A code block that starts with a fence
class MdHardLineBreak

markdown2 :: MdHardLineBreak

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

markdown2 :: MdHeading

A heading
class MdHtmlBlock

markdown2 :: MdHtmlBlock

An html block
class MdImage

markdown2 :: MdImage

An image
class MdIndentedCodeBlock

markdown2 :: MdIndentedCodeBlock

A block code that starts with an indent
abstract class MdListBlock

markdown2 :: MdListBlock

An ordered or unordered list block
class MdListItem

markdown2 :: MdListItem

An ordered or unordered list item block
class MdOrderedList

markdown2 :: MdOrderedList

An ordered list block
class MdParagraph

markdown2 :: MdParagraph

A paragraph block
class MdSoftLineBreak

markdown2 :: MdSoftLineBreak

A soft line breack (\r or \n)
class MdStrike

markdown2 :: MdStrike

Striked text
class MdStrongEmphasis

markdown2 :: MdStrongEmphasis

A strong emphasis token
class MdSuper

markdown2 :: MdSuper

Super text
class MdUnorderedList

markdown2 :: MdUnorderedList

An unordered list

Class definitions

markdown2 $ MdNode
# An abstract node
abstract class MdNode

	# Node location in original markdown
	var location: MdLocation

	# Node parent
	var parent: nullable MdNode = null is writable

	# First child
	var first_child: nullable MdNode = null is writable

	# Last child
	var last_child: nullable MdNode = null is writable

	# Previous node
	var prev: nullable MdNode = null is writable

	# Next node
	var next: nullable MdNode = null is writable

	# Children nodes of `self`
	fun children: Array[MdNode] do
		var nodes = new Array[MdNode]

		var node = first_child
		while node != null do
			nodes.add node
			node = node.next
		end

		return nodes
	end

	# Append a child to `self`
	fun append_child(child: MdNode) do
		child.unlink
		child.parent = self
		if last_child != null then
			last_child.as(not null).next = child
			child.prev = last_child
			last_child = child
		else
			first_child = child
			last_child = child
		end
	end

	# Prepend a child to `self`
	fun prepend_child(child: MdNode) do
		child.unlink
		child.parent = self
		if first_child != null then
			first_child.as(not null).prev = child
			child.next = first_child
			first_child = child
		else
			first_child = child
			last_child = child
		end
	end

	# Unlink `self` from its `parent`
	fun unlink do
		if prev != null then
			prev.as(not null).next = next
		else if parent != null then
			parent.as(not null).first_child = next
		end
		if next != null then
			next.as(not null).prev = prev
		else if parent != null then
			parent.as(not null).last_child = prev
		end
		parent = null
		next = null
		prev = null
	end

	# Insert `sibling` after `self`.
	fun insert_after(sibling: MdNode) do
		sibling.unlink
		sibling.next = next
		if sibling.next != null then
			sibling.next.as(not null).prev = sibling
		end
		sibling.prev = self
		next = sibling
		sibling.parent = parent
		if sibling.next == null then
			sibling.parent.as(not null).last_child = sibling
		end
	end

	# Insert `sibling` before `self`.
	fun insert_before(sibling: MdNode) do
		sibling.unlink
		sibling.prev = prev
		if sibling.prev != null then
			sibling.prev.as(not null).next = sibling
		end
		sibling.next = self
		prev = sibling
		sibling.parent = parent
		if sibling.prev == null then
			sibling.parent.as(not null).first_child = sibling
		end
	end

	# Visit all children or `self`
	fun visit_all(v: MdVisitor) do
		var node = first_child
		while node != null do
			var next = node.next
			v.visit(node)
			node = next
		end
	end

	redef fun to_s do return "{super}\{{to_s_attrs}\}"

	# Returns `self` attributes as a String
	#
	# Mainly used for debug purposes.
	fun to_s_attrs: String do return "loc: {location}"

	# Print `self` AST
	fun debug do
		var v = new MdASTPrinter
		v.enter_visit(self)
	end
end
lib/markdown2/markdown_ast.nit:18,1--149,3

markdown2 :: markdown_rendering $ MdNode
redef class MdNode

	# Return `self` as raw text
	fun raw_text: String do
		var v = new RawTextVisitor
		return v.render(self)
	end

	# Render `self` as raw text
	fun render_raw_text(v: RawTextVisitor) do visit_all(v)
end
lib/markdown2/markdown_rendering.nit:47,1--57,3

markdown2 :: markdown_block_parsing $ MdNode
redef class MdNode

	# Accept the visit of a `MdPostProcessor`
	fun post_process(v: MdPostProcessor) do visit_all(v)
end
lib/markdown2/markdown_block_parsing.nit:1387,1--1391,3

markdown2 :: markdown_html_rendering $ MdNode
redef class MdNode

	# Render `self` as HTML
	fun render_html(v: HtmlRenderer) do visit_all(v)
end
lib/markdown2/markdown_html_rendering.nit:182,1--186,3

markdown2 :: markdown_latex_rendering $ MdNode
redef class MdNode

	# Render `self` as HTML
	fun render_latex(v: LatexRenderer) do visit_all(v)
end
lib/markdown2/markdown_latex_rendering.nit:113,1--117,3

markdown2 :: markdown_man_rendering $ MdNode
redef class MdNode

	# Render `self` as Manpage format
	fun render_man(v: ManRenderer) do visit_all(v)
end
lib/markdown2/markdown_man_rendering.nit:54,1--58,3

markdown2 :: markdown_md_rendering $ MdNode
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
lib/markdown2/markdown_md_rendering.nit:69,1--75,3