markdown2 :: MdBlockParser :: column_start=
Column startmarkdown2 :: MdBlockParser :: content_offset
Column where the content startsmarkdown2 :: MdBlockParser :: content_offset=
Column where the content startsmarkdown2 :: MdBlockParser :: initialize
Initialize the currentblock
			markdown2 :: MdBlockParser :: location=
Location at startmarkdown2 :: MdBlockParser :: parse_inlines
Parseblock lines
			markdown2 :: MdBlockParser :: try_continue
Canself continue from the current index in parser?
			markdown2 $ MdBlockParser :: SELF
Type of this instance, automatically specialized in every classcore :: Object :: class_factory
Implementation used byget_class to create the specific class.
			markdown2 :: MdBlockParser :: column_start=
Column startmarkdown2 :: MdBlockParser :: content_offset
Column where the content startsmarkdown2 :: MdBlockParser :: content_offset=
Column where the content startscore :: Object :: defaultinit
markdown2 :: MdBlockParser :: initialize
Initialize the currentblock
			core :: Object :: is_same_instance
Return true ifself and other are the same instance (i.e. same identity).
			core :: Object :: is_same_serialized
Isself the same as other in a serialization context?
			core :: Object :: is_same_type
Return true ifself and other have the same dynamic type.
			markdown2 :: MdBlockParser :: location=
Location at startcore :: Object :: output_class_name
Display class name on stdout (debug only).markdown2 :: MdBlockParser :: parse_inlines
Parseblock lines
			markdown2 :: MdBlockParser :: try_continue
Canself continue from the current index in parser?
			
# Parser for a specific block node
abstract class MdBlockParser
	# Kind of block under construction
	type BLOCK: MdBlock
	# MdBlock under construction
	fun block: BLOCK is abstract
	# Line Start
	var line_start: Int
	# Column start
	var column_start: Int
	# Location at start
	#
	# The location end it initialized at `-1` and will be set later in the
	# `finalize` method.
	var location: MdLocation is lazy do return new MdLocation(line_start, column_start, -1, -1)
	# Column where the content starts
	var content_offset: Int
	# Initialize the current `block`
	fun initialize(parser: MdParser) do end
	# Can `self` continue from the current `index` in `parser`?
	#
	# Return a new `MdBlockContinue` if `self` can continue parsing.
	# Return null otherwise.
	fun try_continue(state: MdParser): nullable MdBlockContinue is abstract
	# Add `line` to the current `block`
	fun add_line(line: String) do end
	# Finalize the current `block`
	#
	# Deactivate `self` from `parser` and call `close_block`.
	fun finalize(parser: MdParser) do
		if parser.active_block_parser == self then
			parser.deactivate_block_parser
		end
	end
	# Parse `block` lines
	fun parse_inlines(inline_parser: MdInlineParser) do end
end
					lib/markdown2/markdown_block_parsing.nit:478,1--525,3