A markdown line.

Introduced properties

fun clear

markdown :: MDLine :: clear

Set value as an empty String and update leading, trailing and is_empty.
fun count_chars(ch: Char): Int

markdown :: MDLine :: count_chars

Count the amount of ch in this line.
fun count_chars_start(ch: Char): Int

markdown :: MDLine :: count_chars_start

Count the amount of ch at the start of this line ignoring spaces.
init defaultinit(location: MDLocation, value: String)

markdown :: MDLine :: defaultinit

fun is_empty: Bool

markdown :: MDLine :: is_empty

Is this line empty?
fun is_empty=(is_empty: Bool)

markdown :: MDLine :: is_empty=

Is this line empty?
fun leading: Int

markdown :: MDLine :: leading

Number or leading spaces on this line.
fun leading=(leading: Int)

markdown :: MDLine :: leading=

Number or leading spaces on this line.
fun location: MDLocation

markdown :: MDLine :: location

Location of self in the original input.
protected fun location=(location: MDLocation)

markdown :: MDLine :: location=

Location of self in the original input.
fun next: nullable MDLine

markdown :: MDLine :: next

Next line in MDBlock or null if last line.
fun next=(next: nullable MDLine)

markdown :: MDLine :: next=

Next line in MDBlock or null if last line.
fun next_empty: Bool

markdown :: MDLine :: next_empty

Is the next line empty?
fun next_empty=(next_empty: Bool)

markdown :: MDLine :: next_empty=

Is the next line empty?
fun prev: nullable MDLine

markdown :: MDLine :: prev

Previous line in MDBlock or null if first line.
fun prev=(prev: nullable MDLine)

markdown :: MDLine :: prev=

Previous line in MDBlock or null if first line.
fun prev_empty: Bool

markdown :: MDLine :: prev_empty

Is the previous line empty?
fun prev_empty=(prev_empty: Bool)

markdown :: MDLine :: prev_empty=

Is the previous line empty?
fun process_leading: Int

markdown :: MDLine :: process_leading

Compute leading depending on value.
fun process_trailing: Int

markdown :: MDLine :: process_trailing

Compute trailing depending on value.
fun text: String

markdown :: MDLine :: text

Extract the text of self without leading and trailing.
fun trailing: Int

markdown :: MDLine :: trailing

Number of trailing spaces on this line.
fun trailing=(trailing: Int)

markdown :: MDLine :: trailing=

Number of trailing spaces on this line.
fun value: String

markdown :: MDLine :: value

Text contained in this line.
fun value=(value: String)

markdown :: MDLine :: value=

Text contained in this line.

Redefined properties

redef type SELF: MDLine

markdown $ MDLine :: SELF

Type of this instance, automatically specialized in every class
redef init init

markdown $ MDLine :: init

Initialize a new MDLine from its string value

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
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 clear

markdown :: MDLine :: clear

Set value as an empty String and update leading, trailing and is_empty.
fun count_chars(ch: Char): Int

markdown :: MDLine :: count_chars

Count the amount of ch in this line.
fun count_chars_start(ch: Char): Int

markdown :: MDLine :: count_chars_start

Count the amount of ch at the start of this line ignoring spaces.
init defaultinit(location: MDLocation, value: String)

markdown :: MDLine :: defaultinit

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".
fun is_empty: Bool

markdown :: MDLine :: is_empty

Is this line empty?
fun is_empty=(is_empty: Bool)

markdown :: MDLine :: is_empty=

Is this line empty?
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 leading: Int

markdown :: MDLine :: leading

Number or leading spaces on this line.
fun leading=(leading: Int)

markdown :: MDLine :: leading=

Number or leading spaces on this line.
fun location: MDLocation

markdown :: MDLine :: location

Location of self in the original input.
protected fun location=(location: MDLocation)

markdown :: MDLine :: location=

Location of self in the original input.
fun next: nullable MDLine

markdown :: MDLine :: next

Next line in MDBlock or null if last line.
fun next=(next: nullable MDLine)

markdown :: MDLine :: next=

Next line in MDBlock or null if last line.
fun next_empty: Bool

markdown :: MDLine :: next_empty

Is the next line empty?
fun next_empty=(next_empty: Bool)

markdown :: MDLine :: next_empty=

Is the next line empty?
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 prev: nullable MDLine

markdown :: MDLine :: prev

Previous line in MDBlock or null if first line.
fun prev=(prev: nullable MDLine)

markdown :: MDLine :: prev=

Previous line in MDBlock or null if first line.
fun prev_empty: Bool

markdown :: MDLine :: prev_empty

Is the previous line empty?
fun prev_empty=(prev_empty: Bool)

markdown :: MDLine :: prev_empty=

Is the previous line empty?
fun process_leading: Int

markdown :: MDLine :: process_leading

Compute leading depending on value.
fun process_trailing: Int

markdown :: MDLine :: process_trailing

Compute trailing depending on value.
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.
fun text: String

markdown :: MDLine :: text

Extract the text of self without leading and trailing.
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 trailing: Int

markdown :: MDLine :: trailing

Number of trailing spaces on this line.
fun trailing=(trailing: Int)

markdown :: MDLine :: trailing=

Number of trailing spaces on this line.
fun value: String

markdown :: MDLine :: value

Text contained in this line.
fun value=(value: String)

markdown :: MDLine :: value=

Text contained in this line.
package_diagram markdown::MDLine MDLine core::Object Object markdown::MDLine->core::Object

Parents

interface Object

core :: Object

The root of the class hierarchy.

Class definitions

markdown $ MDLine
# A markdown line.
class MDLine

	# Location of `self` in the original input.
	var location: MDLocation

	# Text contained in this line.
	var value: String is writable

	# Is this line empty?
	# Lines containing only spaces are considered empty.
	var is_empty: Bool = true is writable

	# Previous line in `MDBlock` or null if first line.
	var prev: nullable MDLine = null is writable

	# Next line in `MDBlock` or null if last line.
	var next: nullable MDLine = null is writable

	# Is the previous line empty?
	var prev_empty: Bool = false is writable

	# Is the next line empty?
	var next_empty: Bool = false is writable

	# Initialize a new MDLine from its string value
	init do
		self.leading = process_leading
		if leading != value.length then
			self.is_empty = false
			self.trailing = process_trailing
		end
	end

	# Set `value` as an empty String and update `leading`, `trailing` and is_`empty`.
	fun clear do
		value = ""
		leading = 0
		trailing = 0
		is_empty = true
		if prev != null then prev.as(not null).next_empty = true
		if next != null then next.as(not null).prev_empty = true
	end

	# Number or leading spaces on this line.
	var leading: Int = 0 is writable

	# Compute `leading` depending on `value`.
	fun process_leading: Int do
		var count = 0
		var value = self.value
		while count < value.length and value[count] == ' ' do count += 1
		if leading == value.length then clear
		return count
	end

	# Number of trailing spaces on this line.
	var trailing: Int = 0 is writable

	# Compute `trailing` depending on `value`.
	fun process_trailing: Int do
		var count = 0
		var value = self.value
		while value[value.length - count - 1] == ' ' do
			count += 1
		end
		return count
	end

	# Count the amount of `ch` in this line.
	# Return A value > 0 if this line only consists of `ch` end spaces.
	fun count_chars(ch: Char): Int do
		var count = 0
		for c in value do
			if c == ' ' then
				continue
			end
			if c == ch then
				count += 1
				continue
			end
			count = 0
			break
		end
		return count
	end

	# Count the amount of `ch` at the start of this line ignoring spaces.
	fun count_chars_start(ch: Char): Int do
		var count = 0
		for c in value do
			if c == ' ' then
				continue
			end
			if c == ch then
				count += 1
			else
				break
			end
		end
		return count
	end

	# Last XML line if any.
	private var xml_end_line: nullable MDLine = null

	# Does `value` contains valid XML markup?
	private fun check_html: Bool do
		var tags = new Array[String]
		var tmp = new FlatBuffer
		var pos = leading
		if pos + 1 < value.length and value[pos + 1] == '!' then
			if read_xml_comment(self, pos) > 0 then return true
		end
		pos = value.read_xml(tmp, pos, false)
		var tag: String
		if pos > -1 then
			tag = tmp.xml_tag
			if not tag.is_html_block then
				return false
			end
			if tag == "hr" then
				xml_end_line = self
				return true
			end
			tags.add tag
			var line: nullable MDLine = self
			while line != null do
				while pos < line.value.length and line.value[pos] != '<' do
					pos += 1
				end
				if pos >= line.value.length then
					if pos - 2 >= 0 and line.value[pos - 2] == '/' then
						tags.pop
						if tags.is_empty then
							xml_end_line = line
							break
						end
					end
					line = line.next
					pos = 0
				else
					tmp = new FlatBuffer
					var new_pos = line.value.read_xml(tmp, pos, false)
					if new_pos > 0 then
						tag = tmp.xml_tag
						if tag.is_html_block and not tag == "hr" then
							if tmp[1] == '/' then
								if tags.last != tag then
									return false
								end
								tags.pop
							else
								tags.add tag
							end
						end
						if tags.is_empty then
							xml_end_line = line
							break
						end
						pos = new_pos
					else
						pos += 1
					end
				end
			end
			return tags.is_empty
		end
		return false
	end

	# Read a XML comment.
	# Used by `check_html`.
	private fun read_xml_comment(first_line: MDLine, start: Int): Int do
		var line: nullable MDLine = first_line
		if start + 3 < line.as(not null).value.length then
			if line.as(not null).value[2] == '-' and line.as(not null).value[3] == '-' then
				var pos = start + 4
				while line != null do
					while pos < line.value.length and line.value[pos] != '-' do
						pos += 1
					end
					if pos == line.value.length then
						line = line.next
						pos = 0
					else
						if pos + 2 < line.value.length then
							if line.value[pos + 1] == '-' and line.value[pos + 2] == '>' then
								first_line.xml_end_line = line
								return pos + 3
							end
						end
						pos += 1
					end
				end
			end
		end
		return -1
	end

	# Extract the text of `self` without leading and trailing.
	fun text: String do return value.substring(leading, value.length - trailing)
end
lib/markdown/markdown.nit:1430,1--1632,3