An implementation of MdDelimiterProcessor that dispatches all calls to others

The sub processors called bepends on the length of the delimiter run. All child processors must have different minimum lengths. A given delimiter run is dispatched to the child with the largest acceptable minimum length. If not child is applicable, the one with the largest minimum length is chosen.

Introduced properties

fun add(dp: MdDelimiterProcessor)

markdown2 :: MdStaggeredDelimiterProcessor :: add

Add a new sub delimiter processor
fun delim: Char

markdown2 :: MdStaggeredDelimiterProcessor :: delim

Delimiter character
protected fun delim=(delim: Char)

markdown2 :: MdStaggeredDelimiterProcessor :: delim=

Delimiter character
fun find_processor(len: Int): MdDelimiterProcessor

markdown2 :: MdStaggeredDelimiterProcessor :: find_processor

Find the corresponding processor for a length of len delimiter characters
protected fun processors=(processors: Array[MdDelimiterProcessor])

markdown2 :: MdStaggeredDelimiterProcessor :: processors=

Sub processors to apply

Redefined properties

redef type SELF: MdStaggeredDelimiterProcessor

markdown2 $ MdStaggeredDelimiterProcessor :: SELF

Type of this instance, automatically specialized in every class
redef fun closing_delimiter: Char

markdown2 $ MdStaggeredDelimiterProcessor :: closing_delimiter

The character that marks the ending of a delimited node
redef fun delimiter_use(opener: MdDelimiter, closer: MdDelimiter): Int

markdown2 $ MdStaggeredDelimiterProcessor :: delimiter_use

Determine how many (if any) of the delimiter characters should be used
redef fun min_length: Int

markdown2 $ MdStaggeredDelimiterProcessor :: min_length

Minimum number of delimiters characters that are needed to active this
redef fun opening_delimiter: Char

markdown2 $ MdStaggeredDelimiterProcessor :: opening_delimiter

The character that marks the beginning of a delimited node
redef fun process(opener: MdText, closer: MdText, delimiter_use: Int)

markdown2 $ MdStaggeredDelimiterProcessor :: process

Process the matched delimiters

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 add(dp: MdDelimiterProcessor)

markdown2 :: MdStaggeredDelimiterProcessor :: add

Add a new sub delimiter processor
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.
abstract fun closing_delimiter: Char

markdown2 :: MdDelimiterProcessor :: closing_delimiter

The character that marks the ending of a delimited node
fun delim: Char

markdown2 :: MdStaggeredDelimiterProcessor :: delim

Delimiter character
protected fun delim=(delim: Char)

markdown2 :: MdStaggeredDelimiterProcessor :: delim=

Delimiter character
abstract fun delimiter_use(opener: MdDelimiter, closer: MdDelimiter): Int

markdown2 :: MdDelimiterProcessor :: delimiter_use

Determine how many (if any) of the delimiter characters should be used
fun find_processor(len: Int): MdDelimiterProcessor

markdown2 :: MdStaggeredDelimiterProcessor :: find_processor

Find the corresponding processor for a length of len delimiter characters
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 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.
abstract fun min_length: Int

markdown2 :: MdDelimiterProcessor :: min_length

Minimum number of delimiters characters that are needed to active this
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
abstract fun opening_delimiter: Char

markdown2 :: MdDelimiterProcessor :: opening_delimiter

The character that marks the beginning of a delimited node
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).
abstract fun process(opener: MdText, closer: MdText, delimiter_use: Int)

markdown2 :: MdDelimiterProcessor :: process

Process the matched delimiters
protected fun processors=(processors: Array[MdDelimiterProcessor])

markdown2 :: MdStaggeredDelimiterProcessor :: processors=

Sub processors to apply
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.
package_diagram markdown2::MdStaggeredDelimiterProcessor MdStaggeredDelimiterProcessor markdown2::MdDelimiterProcessor MdDelimiterProcessor markdown2::MdStaggeredDelimiterProcessor->markdown2::MdDelimiterProcessor core::Object Object markdown2::MdDelimiterProcessor->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

interface MdDelimiterProcessor

markdown2 :: MdDelimiterProcessor

Custom delimiter processor for additional delimiters besides _ and *

Class definitions

markdown2 $ MdStaggeredDelimiterProcessor
# An implementation of MdDelimiterProcessor that dispatches all calls to others
#
# The sub processors called bepends on the length of the delimiter run.
# All child processors must have different minimum lengths.
# A given delimiter run is dispatched to the child with the largest acceptable minimum length.
# If not child is applicable, the one with the largest minimum length is chosen.
class MdStaggeredDelimiterProcessor
	super MdDelimiterProcessor

	# Delimiter character
	var delim: Char

	# Sub processors to apply
	var processors = new Array[MdDelimiterProcessor]

	redef var min_length = 0
	redef fun opening_delimiter do return delim
	redef fun closing_delimiter do return delim

	# Add a new sub delimiter processor
	fun add(dp: MdDelimiterProcessor) do
		var len = dp.min_length
		var i = 0
		while i < processors.length do
			var p = processors[i]
			assert len != p.min_length else
				print "Cannot add two delimiter processor for `{delim}` " +
					"and mininimum length `{len}`"
			end
			if len > p.min_length then
				break
			end
			i += 1
		end
		processors.insert(dp, i)
	end

	# Find the corresponding processor for a length of `len` delimiter characters
	fun find_processor(len: Int): MdDelimiterProcessor do
		for processor in processors do
			if processor.min_length <= len then return processor
		end
		return processors.first
	end

	redef fun delimiter_use(opener, closer) do
		return find_processor(opener.length).delimiter_use(opener, closer)
	end

	redef fun process(opener, closer, delimiter_use) do
		find_processor(delimiter_use).process(opener, closer, delimiter_use)
	end
end
lib/markdown2/markdown_inline_parsing.nit:1242,1--1294,3