Parsing of literal values in the abstract syntax tree.

Introduced classes

class AAugmentedLiteral

nitc :: AAugmentedLiteral

Any kind of literal which supports a prefix or a suffix
class AugmentedStringFormExpr

nitc :: AugmentedStringFormExpr

Any kind of string form with augmentations from prefixes or suffixes
private class LiteralPhase

nitc :: LiteralPhase

private class LiteralVisitor

nitc :: LiteralVisitor

Redefined classes

redef class ACharExpr

nitc :: literal $ ACharExpr

A character literal
redef class AEndStringExpr

nitc :: literal $ AEndStringExpr

The end of a superstrng. eg }abc"
redef abstract class AExpr

nitc :: literal $ AExpr

Expression and statements
redef class AFloatExpr

nitc :: literal $ AFloatExpr

A float literal
redef class AIntegerExpr

nitc :: literal $ AIntegerExpr

An integer literal
redef class AMidStringExpr

nitc :: literal $ AMidStringExpr

The middle of a superstring. eg }abc{
redef class AModule

nitc :: literal $ AModule

The main node of a Nit source-file
redef abstract class ANode

nitc :: literal $ ANode

Root of the AST class-hierarchy
redef class AStartStringExpr

nitc :: literal $ AStartStringExpr

The start of a superstring. eg "abc{
redef class AStringExpr

nitc :: literal $ AStringExpr

A simple string. eg. "abc"
redef abstract class AStringFormExpr

nitc :: literal $ AStringFormExpr

A string literal
redef class ASuperstringExpr

nitc :: literal $ ASuperstringExpr

A superstring literal. eg "a{x}b{y}c"
redef class ToolContext

nitc :: literal $ ToolContext

Global context for tools

All class definitions

class AAugmentedLiteral

nitc $ AAugmentedLiteral

Any kind of literal which supports a prefix or a suffix
redef class ACharExpr

nitc :: literal $ ACharExpr

A character literal
redef class AEndStringExpr

nitc :: literal $ AEndStringExpr

The end of a superstrng. eg }abc"
redef abstract class AExpr

nitc :: literal $ AExpr

Expression and statements
redef class AFloatExpr

nitc :: literal $ AFloatExpr

A float literal
redef class AIntegerExpr

nitc :: literal $ AIntegerExpr

An integer literal
redef class AMidStringExpr

nitc :: literal $ AMidStringExpr

The middle of a superstring. eg }abc{
redef class AModule

nitc :: literal $ AModule

The main node of a Nit source-file
redef abstract class ANode

nitc :: literal $ ANode

Root of the AST class-hierarchy
redef class AStartStringExpr

nitc :: literal $ AStartStringExpr

The start of a superstring. eg "abc{
redef class AStringExpr

nitc :: literal $ AStringExpr

A simple string. eg. "abc"
redef abstract class AStringFormExpr

nitc :: literal $ AStringFormExpr

A string literal
redef class ASuperstringExpr

nitc :: literal $ ASuperstringExpr

A superstring literal. eg "a{x}b{y}c"
class AugmentedStringFormExpr

nitc $ AugmentedStringFormExpr

Any kind of string form with augmentations from prefixes or suffixes
private class LiteralPhase

nitc $ LiteralPhase

private class LiteralVisitor

nitc $ LiteralVisitor

redef class ToolContext

nitc :: literal $ ToolContext

Global context for tools
package_diagram nitc::literal literal nitc::phase phase nitc::literal->nitc::phase nitc::toolcontext toolcontext nitc::phase->nitc::toolcontext nitc\>parser\> parser nitc::phase->nitc\>parser\> ...nitc::toolcontext ... ...nitc::toolcontext->nitc::toolcontext ...nitc\>parser\> ... ...nitc\>parser\>->nitc\>parser\> nitc::annotation annotation nitc::annotation->nitc::literal nitc::no_warning no_warning nitc::no_warning->nitc::literal nitc::glsl_validation glsl_validation nitc::glsl_validation->nitc::literal nitc::modelize_property modelize_property nitc::modelize_property->nitc::annotation nitc::check_annotation check_annotation nitc::check_annotation->nitc::annotation nitc::modelize_property... ... nitc::modelize_property...->nitc::modelize_property nitc::check_annotation... ... nitc::check_annotation...->nitc::check_annotation nitc::frontend frontend nitc::frontend->nitc::no_warning nitc::frontend->nitc::glsl_validation nitc::frontend... ... nitc::frontend...->nitc::frontend

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 caching

serialization :: caching

Services for caching serialization engines
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 console

console :: console

Defines some ANSI Terminal Control Escape Sequences.
module core

core :: core

Standard classes and methods used by default by Nit programs and libraries.
module engine_tools

serialization :: engine_tools

Advanced services for serialization engines
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 inspect

serialization :: inspect

Refine Serializable::inspect to show more useful information
module iso8859_1

core :: iso8859_1

Codec for ISO8859-1 I/O
module kernel

core :: kernel

Most basic classes and methods.
module lexer

nitc :: lexer

Lexer and its tokens.
module lexer_work

nitc :: lexer_work

Internal algorithm and data structures for the Nit lexer
module list

core :: list

This module handle double linked lists
module location

nitc :: location

Nit source-file and locations in source-file
module math

core :: math

Mathematical operations
module meta

meta :: meta

Simple user-defined meta-level to manipulate types of instances as object.
module more_collections

more_collections :: more_collections

Highly specific, but useful, collections-related classes.
module native

core :: native

Native structures for text and bytes
module numeric

core :: numeric

Advanced services for Numeric types
module opts

opts :: opts

Management of options on the command line
module ordered_tree

ordered_tree :: ordered_tree

Manipulation and presentation of ordered trees.
module parser

nitc :: parser

Parser.
module parser_nodes

nitc :: parser_nodes

AST nodes of the Nit language
module parser_prod

nitc :: parser_prod

Production AST nodes full definition.
module parser_work

nitc :: parser_work

Internal algorithm and data structures for the Nit parser
module poset

poset :: poset

Pre order sets and partial order set (ie hierarchies)
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 serialization

serialization :: serialization

General serialization services
module serialization_core

serialization :: serialization_core

Abstract services to serialize Nit objects to different formats
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 tables

nitc :: tables

Module that interfaces the parsing tables.
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 toolcontext

nitc :: toolcontext

Common command-line tool infrastructure than handle options and error messages
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
module version

nitc :: version

This file was generated by git-gen-version.sh

Parents

module phase

nitc :: phase

Phases of the processing of nit programs

Children

module annotation

nitc :: annotation

Management and utilities on annotations
module glsl_validation

nitc :: glsl_validation

Check shader code within Nit modules using the tool glslangValidator
module no_warning

nitc :: no_warning

Fill toolcontext information about blacklisting of warnings.

Descendants

module a_star-m

a_star-m

module abstract_compiler

nitc :: abstract_compiler

Abstract compiler
module actors_generation_phase

nitc :: actors_generation_phase

Generate a support module for each module that contain a class annotated with is actor
module actors_injection_phase

nitc :: actors_injection_phase

Injects model for the classes annotated with "is actor" so
module android

nitc :: android

Compile program for the Android platform
module android_annotations

nitc :: android_annotations

Additionnal annotations to gather metadata on Android projects
module api

nitc :: api

Components required to build a web server about the nit model.
module api_auth

nitc :: api_auth

module api_base

nitc :: api_base

Base classes used by nitweb.
module api_docdown

nitc :: api_docdown

Nitdoc specific Markdown format handling for Nitweb
module api_feedback

nitc :: api_feedback

Feedback related features
module api_light

nitc :: api_light

Highlight and collect messages from a piece of code
module api_model

nitc :: api_model

module app_annotations

nitc :: app_annotations

Annotations to gather metadata on app.nit projects
module astbuilder

nitc :: astbuilder

Instantiation and transformation of semantic nodes in the AST of expressions and statements
module auto_super_init

nitc :: auto_super_init

Computing of super-constructors that must be implicitly called at the begin of constructors.
module c

nitc :: c

Support for nesting C code within a Nit program using its FFI
module c_compiler_options

nitc :: c_compiler_options

Offers the annotations cflags and ldflags to specify
module catalog

nitc :: catalog

Basic catalog generator for Nit packages
module check_annotation

nitc :: check_annotation

Check that annotation present in the AST are either primitive or user-declared
module code_gen

nitc :: code_gen

Main frontend phases plus code generation phases
module commands_base

nitc :: commands_base

Documentation commands
module commands_catalog

nitc :: commands_catalog

Commands to retrieve Catalog related data
module commands_docdown

nitc :: commands_docdown

Doc down related queries
module commands_graph

nitc :: commands_graph

Graph commands
module commands_http

nitc :: commands_http

Initialize commands from HTTP requests
module commands_model

nitc :: commands_model

Doc commands about a Model or a MEntity
module commands_parser

nitc :: commands_parser

A parser that create DocCommand from a string
module commands_usage

nitc :: commands_usage

Commands about how mentities are used
module compilation

nitc :: compilation

The compilation module of the VirtualMachine
module compiler

nitc :: compiler

Compilation to C
module compiler_ffi

nitc :: compiler_ffi

Full FFI support for the compiler
module compiler_serialization

nitc :: compiler_serialization

Serialization support for the compiler
module contracts

nitc :: contracts

Module to build contract
module cpp

nitc :: cpp

Supports the use of the C++ language through the FFI
module deriving

nitc :: deriving

Injection of automatic method definitions for standard methods, based on the attributes of the classes
module detect_covariance

nitc :: detect_covariance

Detect the static usage of covariance in the code.
module div_by_zero

nitc :: div_by_zero

Detection of divisions by zero in obvious cases
module dynamic_loading_ffi

nitc :: dynamic_loading_ffi

Execute FFI code by creating and loading shared libraries
module emscripten

nitc :: emscripten

Compile to JavaScript using the Emscripten SDK
module explain_assert

nitc :: explain_assert

Explain failed assert to the console by modifying the AST.
module extern_classes

nitc :: extern_classes

Manages all extern classes and their associated foreign type.
module extra_java_files

nitc :: extra_java_files

Intro the annotation extra_java_files to compile extra java files
module ffi

nitc :: ffi

Full FFI support, independent of the compiler
module ffi_base

nitc :: ffi_base

Tools and utilities for implement FFI with different languages
module frontend

nitc :: frontend

Collect and orchestration of main frontend phases
module global_compiler

nitc :: global_compiler

Global compilation of a Nit program
module header_dependency

nitc :: header_dependency

Tracks which modules has public header code that must be imported
module highlight

nitc :: highlight

Highlighting of Nit AST
module html_commands

nitc :: html_commands

Render commands results as HTML
module html_model

nitc :: html_model

Translate mentities to html blocks.
module htmlight

nitc :: htmlight

Highlighting of Nit AST with HTML
module i18n_phase

nitc :: i18n_phase

Basic support of internationalization through the generation of id-to-string tables
module inheritance_metrics

nitc :: inheritance_metrics

Collect metrics about inheritance usage
module interpreter

nitc :: interpreter

Interpretation of Nit programs
module ios

nitc :: ios

Compile programs for the iOS platform
module java

nitc :: java

FFI support for the Java language
module java_compiler

nitc :: java_compiler

Compile Nit code to Java code
module json_commands

nitc :: json_commands

Translate command results to json
module json_model

nitc :: json_model

Make model entities Serializable.
module light

nitc :: light

Light FFI support for the compiler
module light_c

nitc :: light_c

Support for nesting C code within a Nit program using its FFI
module light_ffi

nitc :: light_ffi

Light FFI support, independent of the compiler
module light_only

nitc :: light_only

Compiler support for the light FFI only, detects unsupported usage of callbacks
module mclasses_metrics

nitc :: mclasses_metrics

Collect common metrics about mclasses
module md_commands

nitc :: md_commands

Render commands results as Markdown
module memory_logger

nitc :: memory_logger

Extension to inject memory-tracing instrumentation in code generated by nitc.
module mendel_metrics

nitc :: mendel_metrics

The Mendel model helps to understand class hierarchies.
module metrics

nitc :: metrics

Various statistics about Nit models and programs
module mmodules_metrics

nitc :: mmodules_metrics

Collect common metrics about modules
module model_collect

nitc :: model_collect

Collect things from the model.
module model_index

nitc :: model_index

Search things from the Model
module model_visitor

nitc :: model_visitor

Simple visitor framework for Nit models.
module modelize

nitc :: modelize

Create a model from nit source files
module modelize_property

nitc :: modelize_property

Analysis and verification of property definitions to instantiate model element
module naive_interpreter

nitc :: naive_interpreter

Interpretation of a Nit program directly on the AST
module nit

nitc :: nit

A naive Nit interpreter
module nitc

nitc :: nitc

A Nit compiler
module nitcatalog

nitc :: nitcatalog

Basic catalog generator for Nit packages
module nitdoc

nitc :: nitdoc

Generator of static API documentation for the Nit language
module nith

nitc :: nith

A ligHt Nit compiler
module nitj

nitc :: nitj

Compile Nit into Java code runnable on the Java Virtual Machine.
module nitlight

nitc :: nitlight

Tool that produces highlighting for Nit programs
module nitmetrics

nitc :: nitmetrics

A program that collects various metrics on nit programs and libraries
module nitni

nitc :: nitni

Native interface related services (used underneath the FFI)
module nitni_callbacks

nitc :: nitni_callbacks

nitni services related to callbacks (used underneath the FFI)
module nitpackage

nitc :: nitpackage

Helpful features about packages
module nitpick

nitc :: nitpick

A program that collect potential style and code issues
module nitrestful

nitc :: nitrestful

Tool generating boilerplate code linking RESTful actions to Nit methods
module nitsaf

nitc :: nitsaf

Nit Static Analysis Framework client example.
module nitserial

nitc :: nitserial

Serialization support compiler, a tool to support deserialization of live generic types
module nitsmells

nitc :: nitsmells

module nituml

nitc :: nituml

UML generator in dot format.
module nitunit

nitc :: nitunit

Testing tool.
module nitvm

nitc :: nitvm

The Nit virtual machine launcher
module nitweb

nitc :: nitweb

Runs a webserver based on nitcorn that render things from model.
module nitx

nitc :: nitx

nitx, a command tool that displays useful data about Nit code
module nullables_metrics

nitc :: nullables_metrics

Statistics about the usage of nullables
module objc

nitc :: objc

FFI support for Objective-C
module on_demand_compiler

nitc :: on_demand_compiler

Compiles extern code within a module to a static library, as needed
module parallelization_phase

nitc :: parallelization_phase

Phase generating threads for functions annotated with threaded annotation
module parse_annotations

nitc :: parse_annotations

Simple annotation parsing
module pkgconfig

nitc :: pkgconfig

Offers the PkgconfigPhase to use the external program "pkg-config" in order
module platform

nitc :: platform

Platform system, used to customize the behavior of the compiler.
module rapid_type_analysis

nitc :: rapid_type_analysis

Rapid type analysis on the AST
module readme_metrics

nitc :: readme_metrics

Collect common metrics about README files
module regex_phase

nitc :: regex_phase

Check for error in regular expressions from string literals
module rta_metrics

nitc :: rta_metrics

Metrics from RTA
module semantize

nitc :: semantize

Process bodies of methods in regard with the model.
module separate_compiler

nitc :: separate_compiler

Separate compilation of a Nit program
module separate_erasure_compiler

nitc :: separate_erasure_compiler

Separate compilation of a Nit program with generic type erasure
module serialization_code_gen_phase

nitc :: serialization_code_gen_phase

Phase generating methods (code) to serialize Nit objects
module serialization_model_phase

nitc :: serialization_model_phase

Phase generating methods (model-only) to serialize Nit objects
module ssa

nitc :: ssa

Single-Static Assignment algorithm from an AST
module static

nitc :: static

Nitdoc generation framework
module static_base

nitc :: static_base

Base entities shared by all the nitdoc code
module static_cards

nitc :: static_cards

Cards templates for the static documentation
module static_html

nitc :: static_html

Render documentation pages as HTML
module static_index

nitc :: static_index

Manage indexing of Nit model for Nitdoc QuickSearch.
module static_structure

nitc :: static_structure

Composes the pages of the static documentation
module static_types_metrics

nitc :: static_types_metrics

Metrics on the usage of explicit static types.
module term

nitc :: term

module term_model

nitc :: term_model

Markdown templates for Nit model MEntities.
module test_astbuilder

nitc :: test_astbuilder

Program used to test the clone method of the astbuilder tool
module test_highlight

nitc :: test_highlight

Program used to test the Nit highlighter
module test_model_visitor

nitc :: test_model_visitor

Example of model_visitor
module test_neo

nitc :: test_neo

Test for neo model saving and loading.
module test_test_phase

nitc :: test_test_phase

Example of simple module that aims to do some specific work on nit programs.
module testing

nitc :: testing

Test unit generation and execution for Nit.
module testing_base

nitc :: testing_base

Base options for testing tools.
module testing_doc

nitc :: testing_doc

Testing from code comments.
module testing_gen

nitc :: testing_gen

Test Suites generation.
module testing_suite

nitc :: testing_suite

Testing from external files.
module transform

nitc :: transform

Thansformations that simplify the AST of expressions
module typing

nitc :: typing

Intraprocedural resolution of static types and OO-services
module uml

nitc :: uml

Group head module for UML generation services
module uml_base

nitc :: uml_base

Exposes the base class for UML generation of a Model
module uml_class

nitc :: uml_class

Provides facilities of exporting a Model to a UML class diagram
module uml_module

nitc :: uml_module

Services for generation of a UML package diagram based on a Model
module variables_numbering

nitc :: variables_numbering

Handle all numbering operations related to local variables in the Nit virtual machine
module vim_autocomplete

nitc :: vim_autocomplete

Generate files used by the Vim plugin to autocomplete with doc
module virtual_machine

nitc :: virtual_machine

Implementation of the Nit virtual machine
module vm

nitc :: vm

Entry point of all vm components
module vm_optimizations

nitc :: vm_optimizations

Optimization of the nitvm
module xcode_templates

nitc :: xcode_templates

Templates and other services to create XCode projects
# Parsing of literal values in the abstract syntax tree.
module literal

import phase

redef class ToolContext
	# Parses literal values in the whole AST and produces errors if needed
	var literal_phase: Phase = new LiteralPhase(self, null)
end

private class LiteralPhase
	super Phase

	redef fun process_nmodule(nmodule) do nmodule.do_literal(toolcontext)
end

redef class AModule
	# Visit the module to compute the real value of the literal-related node of the AST.
	# Warnings and errors are displayed on the toolcontext.
	fun do_literal(toolcontext: ToolContext)
	do
		var v = new LiteralVisitor(toolcontext)
		v.enter_visit(self)
	end
end

private class LiteralVisitor
	super Visitor

	var toolcontext: ToolContext

	redef fun visit(n)
	do
		n.accept_literal(self)
		n.visit_all(self)
	end
end

redef class ANode
	private fun accept_literal(v: LiteralVisitor) do end
end

redef class AExpr
	# Get `self` as a `String`.
	# Return null if not a string.
	fun as_string: nullable String
	do
		if not self isa AStringFormExpr then return null
		return self.value
	end

	# Get `self` as an `Int`.
	# Return null if not an integer.
	fun as_int: nullable Int
	do
		if not self isa AIntegerExpr then return null
		return self.value.as(not null).to_i
	end
end

redef class AIntegerExpr
	# The value of the literal int once computed.
	var value: nullable Numeric

	redef fun accept_literal(v) do
		value = n_integer.text.to_num
		if value == null then
			v.toolcontext.error(hot_location, "Error: invalid literal `{n_integer.text}`")
		end
	end
end

redef class AFloatExpr
	# The value of the literal float once computed.
	var value: nullable Float
	redef fun accept_literal(v)
	do
		self.value = self.n_float.text.to_f
	end
end

# Any kind of literal which supports a prefix or a suffix
class AAugmentedLiteral
	# Returns the text of the token
	private fun text: String is abstract

	# Is the combination of prefixes and suffixes in `self` valid ?
	fun is_valid_augmentation: Bool is abstract

	private fun delimiter_start: Char is abstract

	private fun delimiter_end: Char is abstract

	# Prefix for the entity, "" if no prefix is found
	protected var prefix: String is lazy do return text.substring(0, text.index_of(delimiter_start))

	# Suffix for the entity, "" if no prefix is found
	protected var suffix: String is lazy do return text.substring_from(text.last_index_of(delimiter_end) + 1)

	# Content of the entity, without prefix nor suffix
	protected var content: String is lazy do
		var npr = text.substring_from(prefix.length)
		return npr.substring(0, npr.length - suffix.length)
	end
end

redef class ACharExpr
	super AAugmentedLiteral
	# The value of the literal char once computed.
	var value: nullable Char = null

	redef fun delimiter_start do return '\''

	redef fun delimiter_end do return '\''

	# Is the expression returning a Code Point ?
	fun is_code_point: Bool do return prefix == "u"

	redef fun text do return n_char.text

	redef fun is_valid_augmentation do
		if suffix != "" then return false
		if is_code_point then return true
		if prefix != "" then return false
		return true
	end

	redef fun accept_literal(v)
	do
		if not is_valid_augmentation then
			v.toolcontext.error(hot_location, "Syntax Error: invalid prefix/suffix combination {prefix}/{suffix}")
			return
		end
		var txt = content.unescape_nit
		if txt.length != 3 then
			v.toolcontext.error(self.hot_location, "Syntax Error: invalid character literal `{txt}`.")
			return
		end
		self.value = txt.chars[1]
	end
end

# Any kind of string form with augmentations from prefixes or suffixes
class AugmentedStringFormExpr
	super AAugmentedLiteral

	redef var delimiter_start = '"'
	redef var delimiter_end = '"'

	# Is `self` a regular String object ?
	fun is_string: Bool do return prefix == "" or prefix == "raw"

	# Is `self` a Regular Expression ?
	fun is_re: Bool do return prefix == "re"

	# Is `self` a Byte String ?
	fun is_bytestring: Bool do return prefix == "b"

	redef fun is_valid_augmentation do
		if is_string and suffix == "" then return true
		if is_bytestring and suffix == "" then return true
		if is_re then
			var suf = suffix
			for i in suf.chars do
				if i == 'i' then continue
				if i == 'm' then continue
				if i == 'b' then continue
				return false
			end
			return true
		end
		if prefix != "" or suffix != "" then return false
		return true
	end
end

redef class AStringFormExpr
	super AugmentedStringFormExpr

	# The value of the literal string once computed.
	var value: String is noinit

	# The underlying bytes of the String, non-cleaned for UTF-8
	var bytes: Bytes is noinit

	redef fun text do return n_string.text

	# Returns the raw text read by the lexer
	var raw_text: String is lazy do
		var txt = content
		var behead = 1
		var betail = 1
		if txt.chars[0] == txt.chars[1] and txt.length >= 6 then
			behead = 3
			betail = 3
			if txt.chars[0] == delimiter_start and txt.chars[3] == '\n' then behead = 4 # ignore first \n in """
		end
		return txt.substring(behead, txt.length - behead - betail)
	end

	redef fun accept_literal(v) do
		value = raw_text
		bytes = raw_text.to_bytes
	end
end

redef class AEndStringExpr
	redef var delimiter_end is lazy do return '"'
	redef fun prefix do return ""
end

redef class AStartStringExpr
	redef var delimiter_start is lazy do
		var str = n_string.text
		for i in [0 .. str.length[ do
			var c = str[i]
			if c == '"' or c == '\'' then
				return c
			end
		end
		# Cannot happen, unless the parser is bugged
		abort
	end

	redef fun suffix do return ""
end

redef class AMidStringExpr
	redef fun prefix do return ""
	redef fun suffix do return ""
end

redef class AStringExpr
	redef var delimiter_start is lazy do
		var str = text
		for i in [0 .. str.length[ do
			var c = str[i]
			if c == '"' or c == '\'' then
				delimiter_end = c
				return c
			end
		end
		# Cannot happen, unless the parser is bugged
		abort
	end

	redef var delimiter_end is lazy do return delimiter_start

	redef fun accept_literal(v)
	do
		super
		if not is_valid_augmentation then
			v.toolcontext.error(hot_location, "Error: invalid prefix/suffix combination {prefix}/{suffix}")
			return
		end
		if prefix != "raw" then
			bytes = raw_text.unescape_to_bytes
			value = bytes.to_s
		end
	end
end

redef class ASuperstringExpr
	super AugmentedStringFormExpr

	redef var prefix is lazy do
		var fst = n_exprs.first
		if fst isa AugmentedStringFormExpr then
			var prf = fst.prefix
			delimiter_start = fst.delimiter_start
			delimiter_end = delimiter_start
			return prf
		end
		return ""
	end

	redef var suffix is lazy do
		var lst = n_exprs.last
		# Forces the system to update the delimiter's value
		prefix
		if lst isa AugmentedStringFormExpr then
			lst.delimiter_end = delimiter_start
			return lst.suffix
		end
		return ""
	end

	redef fun accept_literal(v)
	do
		if is_bytestring then
			v.toolcontext.error(hot_location, "Error: cannot produce a ByteString on a Superstring")
			return
		end
		if not is_valid_augmentation then
			v.toolcontext.error(hot_location, "Error: invalid prefix/suffix combination {prefix}/{suffix}")
			return
		end
	end

	redef fun visit_all(v) do
		super
		if prefix != "raw" then
			for i in n_exprs do
				if not i isa AStringFormExpr then continue
				i.bytes = i.raw_text.unescape_to_bytes
				i.value = i.bytes.to_s
			end
		end
	end
end
src/literal.nit:17,1--326,3