Reads records from a CSV file.

By default, the format recognizes EOLs as \n

var example = """
foo,bar
"Hello, word!",1234.5 + 42
"Something
""else""\", baz
"""
var reader = new CsvReader.from_string(example)
var table = reader.read_all

assert table.header  == ["foo","bar"]
assert table.records == [["Hello, word!","1234.5 + 42"],
            ["Something\n\"else\""," baz"]]

Introduced properties

init defaultinit(istream: Reader)

csv :: CsvReader :: defaultinit

init from_string(s: String)

csv :: CsvReader :: from_string

Creates a new CSVReader from a string data
fun istream: Reader

csv :: CsvReader :: istream

The input stream.
protected fun istream=(istream: Reader)

csv :: CsvReader :: istream=

The input stream.
fun read_all(has_header: nullable Bool): CsvDocument

csv :: CsvReader :: read_all

Reads the content of the Stream and interprets it as a CSV Document
fun skip_empty: Bool

csv :: CsvReader :: skip_empty

Do we skip the empty lines?
fun skip_empty=(skip_empty: Bool)

csv :: CsvReader :: skip_empty=

Do we skip the empty lines?

Redefined properties

redef type SELF: CsvReader

csv $ CsvReader :: SELF

Type of this instance, automatically specialized in every class

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.
init defaultinit(istream: Reader)

csv :: CsvReader :: defaultinit

fun delimiter: Char

csv :: CsvStream :: delimiter

The character that delimits escaped value.
fun delimiter=(delimiter: Char)

csv :: CsvStream :: delimiter=

The character that delimits escaped value.
fun eol: String

csv :: CsvStream :: eol

The character that ends a record (end of line).
fun eol=(eol: String)

csv :: CsvStream :: eol=

The character that ends a record (end of line).
init from_string(s: String)

csv :: CsvReader :: from_string

Creates a new CSVReader from a string data
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.
fun istream: Reader

csv :: CsvReader :: istream

The input stream.
protected fun istream=(istream: Reader)

csv :: CsvReader :: istream=

The input stream.
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 read_all(has_header: nullable Bool): CsvDocument

csv :: CsvReader :: read_all

Reads the content of the Stream and interprets it as a CSV Document
fun separator: Char

csv :: CsvStream :: separator

The character that split each cell in a record.
fun separator=(separator: Char)

csv :: CsvStream :: separator=

The character that split each cell in a record.
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun skip_empty: Bool

csv :: CsvReader :: skip_empty

Do we skip the empty lines?
fun skip_empty=(skip_empty: Bool)

csv :: CsvReader :: skip_empty=

Do we skip the empty lines?
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 csv::CsvReader CsvReader csv::CsvStream CsvStream csv::CsvReader->csv::CsvStream core::Object Object csv::CsvStream->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

abstract class CsvStream

csv :: CsvStream

Shared properties by all CSV-related classes

Class definitions

csv $ CsvReader
# Reads records from a CSV file.
#
# By default, the format recognizes EOLs as `\n`
#
# ~~~nit
# var example = """
# foo,bar
# "Hello, word!",1234.5 + 42
# "Something
# ""else""\", baz
# """
# var reader = new CsvReader.from_string(example)
# var table = reader.read_all
#
# assert table.header  == ["foo","bar"]
# assert table.records == [["Hello, word!","1234.5 + 42"],
# 			["Something\n\"else\""," baz"]]
# ~~~
class CsvReader
	super CsvStream

	# The input stream.
	var istream: Reader

	# Do we skip the empty lines?
	#
	# Note: Even if this attribute is `false`, the presence of an line ending at
	# end of the last record does not change the number of returned record.
	# This is because the line endings are processed as terminators, not as
	# separators. Therefore, when there is more than one line ending at the end
	# of the file, the additional lines are interpreted as empty records that
	# are skipped only if `skip_empty` is set to `true`.
	#
	# `false` by default.
	var skip_empty: Bool = false is writable

	# Creates a new CSVReader from a `string` data
	init from_string(s: String) do init(new StringReader(s))

	# Reads the content of the Stream and interprets it as a CSV Document
	#
	# Optional parameter `has_header` determines whether the first line
	# of the CSV Document is header data.
	# Defaults to true
	fun read_all(has_header: nullable Bool): CsvDocument do
		var header: nullable Array[String] = null
		if has_header == null then has_header = true
		var iss = istream
		var res_data = new Array[Array[String]]
		var eol_st = eol.first
		var line = new Array[String]
		var esc = delimiter
		var sep = separator
		var eol = eol
		var is_eol = false
		var eol_buf = new Buffer.with_cap(eol.length)
		var c = iss.read_char
		var el = new Buffer
		while not iss.eof do
			if c == null then continue
			loop
				if c == esc then
					c = iss.read_char
					loop
						if c == esc then
							c = iss.read_char
							if c != esc then break
						end
						if c == null then break
						el.add c
						c = iss.read_char
					end
				end
				if c == sep then break
				if c == eol_st then
					eol_buf.add c.as(not null)
					is_eol = true
					for i in [1 .. eol.length[ do
						c = iss.read_char
						if c == null or c != eol[i] then
							is_eol = false
							el.append(eol_buf)
							eol_buf.clear
							break
						end
						eol_buf.add c
					end
					if not is_eol then continue
					eol_buf.clear
					break
				end
				if c == sep then break
				el.add c.as(not null)
				c = iss.read_char
				if c == null then break
			end
			line.add el.to_s
			el.clear
			if is_eol or iss.eof then
				c = iss.read_char
				is_eol = false
				if skip_empty and line.is_empty then
					continue
				end
				if has_header and header == null then
					header = line
				else res_data.add line
				line = new Array[String]
			end
			if c == sep then c = iss.read_char
		end
		if header == null then header = new Array[String]
		var doc = new CsvDocument
		doc.header = header
		doc.records = res_data
		return doc
	end
end
lib/csv/csv.nit:225,1--342,3