Manpages rendering of Markdown documents

Introduced classes

class ManRenderer

markdown2 :: ManRenderer

Markdown document renderer to Manpage

Redefined classes

redef class MdBlockQuote

markdown2 :: markdown_man_rendering $ MdBlockQuote

A block quote
redef class MdCode

markdown2 :: markdown_man_rendering $ MdCode

An inline code string
redef abstract class MdCodeBlock

markdown2 :: markdown_man_rendering $ MdCodeBlock

A block of code (indented or fenced)
redef class MdEmphasis

markdown2 :: markdown_man_rendering $ MdEmphasis

An emphasis
redef class MdHeading

markdown2 :: markdown_man_rendering $ MdHeading

A heading
redef class MdHtmlBlock

markdown2 :: markdown_man_rendering $ MdHtmlBlock

An html block
redef class MdHtmlInline

markdown2 :: markdown_man_rendering $ MdHtmlInline

An inlined html string
redef abstract class MdLineBreak

markdown2 :: markdown_man_rendering $ MdLineBreak

A line break (soft or hard)
redef abstract class MdLinkOrImage

markdown2 :: markdown_man_rendering $ MdLinkOrImage

A link or image
redef abstract class MdNode

markdown2 :: markdown_man_rendering $ MdNode

An abstract node
redef class MdOrderedList

markdown2 :: markdown_man_rendering $ MdOrderedList

An ordered list block
redef class MdParagraph

markdown2 :: markdown_man_rendering $ MdParagraph

A paragraph block
redef class MdStrike

markdown2 :: markdown_man_rendering $ MdStrike

Striked text
redef class MdStrongEmphasis

markdown2 :: markdown_man_rendering $ MdStrongEmphasis

A strong emphasis token
redef class MdText

markdown2 :: markdown_man_rendering $ MdText

A raw text token
redef class MdUnorderedList

markdown2 :: markdown_man_rendering $ MdUnorderedList

An unordered list

All class definitions

class ManRenderer

markdown2 $ ManRenderer

Markdown document renderer to Manpage
redef class MdBlockQuote

markdown2 :: markdown_man_rendering $ MdBlockQuote

A block quote
redef class MdCode

markdown2 :: markdown_man_rendering $ MdCode

An inline code string
redef abstract class MdCodeBlock

markdown2 :: markdown_man_rendering $ MdCodeBlock

A block of code (indented or fenced)
redef class MdEmphasis

markdown2 :: markdown_man_rendering $ MdEmphasis

An emphasis
redef class MdHeading

markdown2 :: markdown_man_rendering $ MdHeading

A heading
redef class MdHtmlBlock

markdown2 :: markdown_man_rendering $ MdHtmlBlock

An html block
redef class MdHtmlInline

markdown2 :: markdown_man_rendering $ MdHtmlInline

An inlined html string
redef abstract class MdLineBreak

markdown2 :: markdown_man_rendering $ MdLineBreak

A line break (soft or hard)
redef abstract class MdLinkOrImage

markdown2 :: markdown_man_rendering $ MdLinkOrImage

A link or image
redef abstract class MdNode

markdown2 :: markdown_man_rendering $ MdNode

An abstract node
redef class MdOrderedList

markdown2 :: markdown_man_rendering $ MdOrderedList

An ordered list block
redef class MdParagraph

markdown2 :: markdown_man_rendering $ MdParagraph

A paragraph block
redef class MdStrike

markdown2 :: markdown_man_rendering $ MdStrike

Striked text
redef class MdStrongEmphasis

markdown2 :: markdown_man_rendering $ MdStrongEmphasis

A strong emphasis token
redef class MdText

markdown2 :: markdown_man_rendering $ MdText

A raw text token
redef class MdUnorderedList

markdown2 :: markdown_man_rendering $ MdUnorderedList

An unordered list
package_diagram markdown2::markdown_man_rendering markdown_man_rendering markdown2::markdown_rendering markdown_rendering markdown2::markdown_man_rendering->markdown2::markdown_rendering markdown2::markdown_github markdown_github markdown2::markdown_man_rendering->markdown2::markdown_github markdown2::markdown_wikilinks markdown_wikilinks markdown2::markdown_man_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_man_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

# Manpages rendering of Markdown documents
module markdown_man_rendering

import markdown_rendering
import markdown_github
import markdown_wikilinks

# Markdown document renderer to Manpage
class ManRenderer
	super MdRenderer

	# Output under construction
	private var man: Buffer is noinit

	# Render `node` as Markdown
	redef fun render(node) do
		man = new Buffer
		enter_visit(node)
		return man.write_to_string
	end

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

	# Add `string` to `man`
	fun add(string: String) do
		man.append(string.replace("-", "\\-"))
	end

	# Add code that need to be escaped
	fun add_code(code: String) do
		add code.replace(" ", "\\ ")
	end

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

redef class MdNode

	# Render `self` as Manpage format
	fun render_man(v: ManRenderer) do visit_all(v)
end

# Blocks

redef class MdBlockQuote
	redef fun render_man(v) do
		v.add ".RS"
		visit_all(v)
		v.add ".RE"
		v.add_line
	end
end

redef class MdCodeBlock
	redef fun render_man(v) do
		v.add ".RS\n.nf\n\\f[C]"
		v.add_line

		var literal = self.literal
		if literal != null then
			var lines = literal.split("\n")
			for i in [0 .. lines.length[ do
				if i == lines.length - 1 then break
				var line = lines[i]
				v.add_code line
				v.add_line
			end
		end

		v.add "\\f[]\n.fi\n.RE"
		v.add_line
	end
end

redef class MdHeading
	redef fun render_man(v) do
		var level = self.level

		if level == 1 then
			v.add ".SH "
		else if level == 2 then
			v.add ".SS "
		else if level >= 3 then
			# We use dictionary (titled paragraph) to simulate a 3rd level (or more)
			v.add ".TP\n"
		end
		visit_all(v)
		v.add_line
	end
end

redef class MdUnorderedList
	redef fun render_man(v) do
		v.add ".RS"
		v.add_line

		var node = first_child
		while node != null do
			v.add ".IP \\[bu] 3"
			v.add_line
			v.enter_visit node
			v.add_line
			node = node.next
		end

		v.add ".RE"
		v.add_line
	end
end

redef class MdOrderedList
	redef fun render_man(v) do
		v.add ".RS"
		v.add_line

		var index = start_number
		var node = first_child
		while node != null do
			v.add ".IP \"{index}.\" 3"
			v.add_line
			v.enter_visit node
			v.add_line
			node = node.next
			index += 1
		end

		v.add ".RE"
		v.add_line
	end
end

redef class MdParagraph
	redef fun render_man(v) do
		var in_list = is_in_list
		if not in_list then
			v.add_line
		end
		visit_all(v)
		if not in_list then
			v.add_line
		end
	end
end

redef class MdThematicBreak
	redef fun render_man(v) do
		v.add "***"
		v.add_line
	end
end

redef class MdHtmlBlock
	redef fun render_man(v) do
		v.add_line
		v.add literal or else ""
		v.add_line
	end
end

# Inlines

redef class MdLineBreak
	redef fun render_man(v) do
		v.add_line
	end
end

redef class MdCode
	redef fun render_man(v) do
		v.add "\\f[C]"
		v.add_code literal
		v.add "\\f[]"
	end
end

redef class MdEmphasis
	redef fun render_man(v) do
		v.add "\\f[I]"
		visit_all(v)
		v.add "\\f[]"
	end
end

redef class MdStrongEmphasis
	redef fun render_man(v) do
		v.add "\\f[B]"
		visit_all(v)
		v.add "\\f[]"
	end
end

redef class MdHtmlInline
	redef fun render_man(v) do
		v.add literal
	end
end

redef class MdLinkOrImage
	redef fun render_man(v) do
		var title = self.title

		visit_all(v)
		v.add " ("
		v.add destination
		if title != null and not title.is_empty then
			v.add " "
			v.add title
		end
		v.add ")"
	end
end

redef class MdText
	redef fun render_man(v) do
		v.add literal
	end
end

# Github

redef class MdStrike
	redef fun render_man(v) do
		v.add "[STRIKEOUT:"
		visit_all(v)
		v.add "]"
	end
end

# Wikilinks

redef class MdWikilink
	redef fun render_man(v) do
		v.add "("
		var title = self.title
		if title != null then
			v.add "{title} | "
		end
		v.add link
		v.add ")"
	end
end
lib/markdown2/markdown_man_rendering.nit:15,1--258,3