Simple groff decorator restricted for manpages.

Introduced classes

class ManDecorator

markdown :: ManDecorator

Decorator that outputs markdown.

All class definitions

class ManDecorator

markdown $ ManDecorator

Decorator that outputs markdown.
package_diagram markdown::man man markdown markdown markdown::man->markdown template template markdown->template config config markdown->config ...template ... ...template->template ...config ... ...config->config markdown::nitmd nitmd markdown::nitmd->markdown::man a_star-m a_star-m a_star-m->markdown::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 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 template

template :: template

Basic template system
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

markdown :: markdown

Markdown parsing.

Children

module nitmd

markdown :: nitmd

A Markdown parser for Nit.

Descendants

module a_star-m

a_star-m

# Simple *groff* decorator restricted for manpages.
module man

import markdown

# `Decorator` that outputs markdown.
class ManDecorator
	super Decorator

	redef var headlines = new ArrayMap[String, HeadLine]

	redef fun add_ruler(v, block) do v.add "***\n"

	redef fun add_headline(v, block) do
		var lvl = block.depth
		if lvl == 1 then
			v.add ".SH "
		else if lvl == 2 then
			v.add ".SS "
		else if lvl >= 3 then
			# We use dictionary (titled paragraph) to simulate a 3rd level (or more)
			v.add ".TP\n"
		end
		v.emit_in block
		v.addn
	end

	redef fun add_paragraph(v, block) do
		if not in_unorderedlist and not in_orderedlist then
			v.addn
			v.emit_in block
			v.addn
		else
			v.emit_in block
		end
	end

	redef fun add_code(v, block) do
		v.add ".RS\n.nf\n\\f[C]\n"
		v.emit_in block
		v.addn
		v.add "\\f[]\n.fi\n.RE\n"
	end

	redef fun add_blockquote(v, block) do
		v.add ".RS\n"
		v.emit_in block
		v.add ".RE\n"
	end

	redef fun add_unorderedlist(v, block) do
		v.add ".RS\n"
		in_unorderedlist = true
		v.emit_in block
		in_unorderedlist = false
		v.add ".RE\n"
	end
	private var in_unorderedlist = false

	redef fun add_orderedlist(v, block) do
		v.add ".RS\n"
		in_orderedlist = true
		current_li = 0
		v.emit_in block
		in_orderedlist = false
		v.add ".RE\n"
	end
	private var in_orderedlist = false
	private var current_li = 0

	redef fun add_listitem(v, block) do
		if in_unorderedlist then
			v.add ".IP \\[bu] 3\n"
		else if in_orderedlist then
			current_li += 1
			v.add ".IP \"{current_li}.\" 3\n"
		end
		v.emit_in block
		v.addn
	end

	redef fun add_em(v, text) do
		v.add "\\f[I]"
		v.add text
		v.add "\\f[]"
	end

	redef fun add_strong(v, text) do
		v.add "\\f[B]"
		v.add text
		v.add "\\f[]"
	end

	redef fun add_strike(v, text) do
		v.add "[STRIKEOUT:"
		v.add text
		v.add "]"
	end

	redef fun add_image(v, link, name, comment) do
		v.add name
		v.add " ("
		append_value(v, link)
		if comment != null and not comment.is_empty then
			v.add " "
			append_value(v, comment)
		end
		v.add ")"
	end

	redef fun add_link(v, link, name, comment) do
		v.add name
		v.add " ("
		append_value(v, link)
		if comment != null and not comment.is_empty then
			v.add " "
			append_value(v, comment)
		end
		v.add ")"
	end

	redef fun add_abbr(v, name, comment) do
		v.add "\">"
		v.emit_text(name)
		v.add " ("
		append_value(v, comment)
		v.add ")"
	end

	redef fun add_span_code(v, text, from, to) do
		v.add "\\f[C]"
		append_code(v, text, from, to)
		v.add "\\f[]"
	end

	redef fun add_line_break(v) do
		v.addn
	end

	redef fun append_value(v, text) do for c in text do escape_char(v, c)

	redef fun add_char(v, c) do
		# Escape - because manpages
		if c == '-' then
			v.addc '\\'
		end
		v.addc(c)
	end

	redef fun escape_char(v, c) do add_char(v, c)

	redef fun append_code(v, buffer, from, to) do
		for i in [from..to[ do
			var c = buffer[i]
			if c == '-' or c == ' ' then
				v.addc '\\'
			end
			v.addc c
		end
	end
end
lib/markdown/man.nit:15,1--175,3