diff options
Diffstat (limited to 'doc')
-rw-r--r-- | doc/endb.txt | 2 | ||||
-rw-r--r-- | doc/grammar.txt | 65 | ||||
-rw-r--r-- | doc/manual.txt | 160 | ||||
-rw-r--r-- | doc/theindex.txt | 101 |
4 files changed, 175 insertions, 153 deletions
diff --git a/doc/endb.txt b/doc/endb.txt index b69a6ec6d..63e382859 100644 --- a/doc/endb.txt +++ b/doc/endb.txt @@ -14,7 +14,7 @@ compiled with the ``--debugger:on`` command line option. This also defines the conditional symbol ``ENDB`` for you. Note: You must not compile your program with the ``--app:gui`` -command line option because then there is no console +command line option because then there would be no console available for the debugger. If you start your program the debugger will immediately show diff --git a/doc/grammar.txt b/doc/grammar.txt index d8387670b..ee46cd63a 100644 --- a/doc/grammar.txt +++ b/doc/grammar.txt @@ -1,6 +1,6 @@ module ::= ([COMMENT] [SAD] stmt)* -optComma ::= [ ',' ] [COMMENT] [IND] +comma ::= ',' [COMMENT] [IND] operator ::= OP0 | OR | XOR | AND | OP3 | OP4 | OP5 | IS | ISNOT | IN | NOTIN | OP6 | DIV | MOD | SHL | SHR | OP7 | NOT @@ -34,11 +34,9 @@ primary ::= ( prefixOperator optInd )* ( symbol | constructor | | castExpr | addrExpr ) ( DOT optInd symbol #| CURLY_LE namedTypeDescList CURLY_RI - | PAR_LE optInd - namedExprList - PAR_RI + | PAR_LE optInd namedExprList PAR_RI | BRACKET_LE optInd - (namedTypeOrExpr optComma)* + [ namedTypeOrExpr (comma namedTypeOrExpr)* [comma] ] BRACKET_RI | CIRCUM | pragma )* @@ -50,17 +48,20 @@ literal ::= INT_LIT | INT8_LIT | INT16_LIT | INT32_LIT | INT64_LIT | NIL constructor ::= literal - | BRACKET_LE optInd (expr [COLON expr] optComma )* BRACKET_RI # []-Constructor - | CURLY_LE optInd (expr [DOTDOT expr] optComma )* CURLY_RI # {}-Constructor - | PAR_LE optInd (expr [COLON expr] optComma )* PAR_RI # ()-Constructor + | BRACKET_LE optInd colonExprList BRACKET_RI # []-Constructor + | CURLY_LE optInd sliceExprList CURLY_RI # {}-Constructor + | PAR_LE optInd colonExprList PAR_RI # ()-Constructor -exprList ::= ( expr optComma )* +exprList ::= [ expr (comma expr)* [comma] ] + +colonExpr ::= expr [COLON expr] +colonExprList ::= [ colonExpr (comma colonExpr)* [comma] ] namedExpr ::= expr [EQUALS expr] # actually this is symbol EQUALS expr|expr -namedExprList ::= ( namedExpr optComma )* +namedExprList ::= [ namedExpr (comma namedExpr)* [comma] ] -exprOrSlice ::= expr [ DOTDOT expr ] -sliceList ::= ( exprOrSlice optComma )+ +sliceExpr ::= expr [ DOTDOT expr ] +sliceExprList ::= [ sliceExpr (comma sliceExpr)* [comma] ] anonymousProc ::= LAMBDA paramList [pragma] EQUALS stmt expr ::= lowestExpr @@ -70,7 +71,7 @@ expr ::= lowestExpr ELSE COLON expr namedTypeDesc ::= typeDescK | expr [EQUALS (typeDescK | expr)] -namedTypeDescList ::= ( namedTypeDesc optComma )* +namedTypeDescList ::= [ namedTypeDesc (comma namedTypeDesc)* [comma] ] qualifiedIdent ::= symbol [ DOT symbol ] @@ -85,7 +86,7 @@ typeDesc ::= typeDescK | primary optSemicolon ::= [SEMICOLON] -macroStmt ::= COLON [stmt] (OF [sliceList] COLON stmt +macroStmt ::= COLON [stmt] (OF [sliceExprList] COLON stmt | ELIF expr COLON stmt | EXCEPT exceptList COLON stmt )* [ELSE COLON stmt] @@ -112,7 +113,7 @@ stmt ::= simpleStmt [SAD] ([SAD] (complexStmt | simpleStmt) )* DED -exprStmt ::= lowestExpr [EQUALS expr | (expr optComma)* [macroStmt]] +exprStmt ::= lowestExpr [EQUALS expr | [expr (comma expr)* [comma]] [macroStmt]] returnStmt ::= RETURN [expr] yieldStmt ::= YIELD expr discardStmt ::= DISCARD expr @@ -121,25 +122,27 @@ breakStmt ::= BREAK [symbol] continueStmt ::= CONTINUE ifStmt ::= IF expr COLON stmt (ELIF expr COLON stmt)* [ELSE COLON stmt] whenStmt ::= WHEN expr COLON stmt (ELIF expr COLON stmt)* [ELSE COLON stmt] -caseStmt ::= CASE expr (OF sliceList COLON stmt)* +caseStmt ::= CASE expr (OF sliceExprList COLON stmt)* (ELIF expr COLON stmt)* [ELSE COLON stmt] whileStmt ::= WHILE expr COLON stmt -forStmt ::= FOR (symbol optComma)+ IN expr [DOTDOT expr] COLON stmt -exceptList ::= (qualifiedIdent optComma)* +forStmt ::= FOR symbol (comma symbol)* [comma] IN expr [DOTDOT expr] COLON stmt +exceptList ::= [qualifiedIdent (comma qualifiedIdent)* [comma]] tryStmt ::= TRY COLON stmt (EXCEPT exceptList COLON stmt)* [FINALLY COLON stmt] asmStmt ::= ASM [pragma] (STR_LIT | RSTR_LIT | TRIPLESTR_LIT) blockStmt ::= BLOCK [symbol] COLON stmt -importStmt ::= IMPORT ((symbol | STR_LIT | RSTR_LIT | TRIPLESTR_LIT) [AS symbol] optComma)+ -includeStmt ::= INCLUDE ((symbol | STR_LIT | RSTR_LIT | TRIPLESTR_LIT) optComma)+ -fromStmt ::= FROM (symbol | STR_LIT | RSTR_LIT | TRIPLESTR_LIT) IMPORT (symbol optComma)+ +filename ::= symbol | STR_LIT | RSTR_LIT | TRIPLESTR_LIT +importStmt ::= IMPORT filename (comma filename)* [comma] +includeStmt ::= INCLUDE filename (comma filename)* [comma] +fromStmt ::= FROM filename IMPORT symbol (comma symbol)* [comma] -pragma ::= CURLYDOT_LE (expr [COLON expr] optComma)+ (CURLYDOT_RI | CURLY_RI) +pragma ::= CURLYDOT_LE colonExprList (CURLYDOT_RI | CURLY_RI) -paramList ::= [PAR_LE ((symbol optComma)+ COLON typeDesc optComma)* PAR_RI] [COLON typeDesc] +param ::= symbol (comma symbol)* [comma] COLON typeDesc +paramList ::= [PAR_LE [param (comma param)* [comma]] PAR_RI] [COLON typeDesc] genericParams ::= BRACKET_LE (symbol [EQUALS typeDesc] )* BRACKET_RI @@ -160,22 +163,24 @@ constDecl ::= symbol ["*"] [pragma] colonAndEquals [COMMENT | IND COMMENT] constSection ::= CONST indPush constDecl (SAD constDecl)* DED typeDef ::= typeDesc | objectDef | enumDef +objectField ::= symbol ["*"] [pragma] objectIdentPart ::= - (symbol ["*" | "-"] [pragma] optComma)+ COLON typeDesc [COMMENT | IND COMMENT] + objectField (comma objectField)* [comma] COLON typeDesc [COMMENT|IND COMMENT] objectWhen ::= WHEN expr COLON [COMMENT] objectPart (ELIF expr COLON [COMMENT] objectPart)* [ELSE COLON [COMMENT] objectPart] objectCase ::= CASE expr COLON typeDesc [COMMENT] - (OF sliceList COLON [COMMENT] objectPart)* + (OF sliceExprList COLON [COMMENT] objectPart)* [ELSE COLON [COMMENT] objectPart] objectPart ::= objectWhen | objectCase | objectIdentPart | NIL | indPush objectPart (SAD objectPart)* DED -tupleDesc ::= BRACKET_LE optInd ((symbol optComma)+ COLON typeDesc optComma)* BRACKET_RI +tupleDesc ::= BRACKET_LE optInd [param (comma param)* [comma]] BRACKET_RI objectDef ::= OBJECT [pragma] [OF typeDesc] objectPart -enumDef ::= ENUM [OF typeDesc] (symbol [EQUALS expr] optComma [COMMENT | IND COMMENT])+ +enumField ::= symbol [EQUALS expr] +enumDef ::= ENUM [OF typeDesc] (enumField [comma | COMMENT | IND COMMENT])+ typeDecl ::= COMMENT | symbol ["*"] [genericParams] [EQUALS typeDef] [COMMENT | IND COMMENT] @@ -183,5 +188,7 @@ typeDecl ::= COMMENT typeSection ::= TYPE indPush typeDecl (SAD typeDecl)* DED colonOrEquals ::= COLON typeDesc [EQUALS expr] | EQUALS expr -varPart ::= (symbol ["*" | "-"] [pragma] optComma)+ colonOrEquals [COMMENT | IND COMMENT] -varSection ::= VAR (varPart | indPush (COMMENT|varPart) (SAD (COMMENT|varPart))* DED) +varField ::= symbol ["*"] [pragma] +varPart ::= symbol (comma symbol)* [comma] colonOrEquals [COMMENT | IND COMMENT] +varSection ::= VAR (varPart + | indPush (COMMENT|varPart) (SAD (COMMENT|varPart))* DED) diff --git a/doc/manual.txt b/doc/manual.txt index 1c8faf4ac..cd982302f 100644 --- a/doc/manual.txt +++ b/doc/manual.txt @@ -223,7 +223,7 @@ A character is not an Unicode character but a single byte. The reason for this is efficiency: For the overwhelming majority of use-cases, the resulting programs will still handle UTF-8 properly as UTF-8 was specially designed for this. -Another reason is that Nimrod should support ``array[char, int]`` or +Another reason is that Nimrod can thus support ``array[char, int]`` or ``set[char]`` efficiently as many algorithms rely on this feature. @@ -363,9 +363,9 @@ constant declaration at compile time. Types ----- -All expressions have a `type`:idx: which is known at compile time. Thus Nimrod -is statically typed. One can declare new types, which is in -essence defining an identifier that can be used to denote this custom type. +All expressions have a `type`:idx: which is known at compile time. Nimrod +is statically typed. One can declare new types, which is in essence defining +an identifier that can be used to denote this custom type. These are the major type classes: @@ -386,9 +386,9 @@ Ordinal types - Ordinal types are countable and ordered. This property allows the operation of functions as ``Inc``, ``Ord``, ``Dec`` on ordinal types to be defined. -- Ordinal values have a smallest possible value. Trying to count farther +- Ordinal values have a smallest possible value. Trying to count further down than the smallest value gives a checked runtime or static error. -- Ordinal values have a largest possible value. Trying to count farther +- Ordinal values have a largest possible value. Trying to count further than the largest value gives a checked runtime or static error. Integers, bool, characters and enumeration types (and subrange of these @@ -453,16 +453,16 @@ floatXX implementation supports ``float32`` and ``float64``. Literals of these types have the suffix 'fXX. -`Automatic type conversion`:idx: in expressions where different kinds -of integer types are used is performed. However, if the type conversion -loses information, the `EInvalidValue`:idx: exception is raised. Certain cases -of the convert error are detected at compile time. +`Automatic type conversion`:idx: is performed in expressions where different +kinds of integer types are used. However, if the type conversion +loses information, the `EOutOfRange`:idx: exception is raised (if the error +cannot be detected at compile time). Automatic type conversion in expressions with different kinds of floating point types is performed: The smaller type is converted to the larger. Arithmetic performed on floating point types -follows the IEEE standard. Only the ``int`` type is converted to a floating -point type automatically, other integer types are not. +follows the IEEE standard. Integer types are not converted to floating point +types automatically and vice versa. Boolean type @@ -475,7 +475,7 @@ This condition holds:: ord(false) == 0 and ord(true) == 1 -The operators ``not, and, or, xor, implies, <, <=, >, >=, !=, ==`` are defined +The operators ``not, and, or, xor, <, <=, >, >=, !=, ==`` are defined for the bool type. The ``and`` and ``or`` operators perform short-cut evaluation. Example: @@ -633,6 +633,8 @@ The lower bound of an array or sequence may be received by the built-in proc received by ``len()``. ``low()`` for a sequence or an open array always returns 0, as this is the first valid index. +The notation ``x[i]`` can be used to access the i-th element of ``x``. + Arrays are always bounds checked (at compile-time or at runtime). These checks can be disabled via pragmas or invoking the compiler with the ``--bound_checks:off`` command line switch. @@ -642,8 +644,8 @@ Tuples and object types ~~~~~~~~~~~~~~~~~~~~~~~ A variable of a `tuple`:idx: or `object`:idx: type is a heterogenous storage container. -A tuple or object defines various named *fields* of a type. A tuple defines an -*order* of the fields additionally. Tuples are meant for heterogenous storage +A tuple or object defines various named *fields* of a type. A tuple also +defines an *order* of the fields. Tuples are meant for heterogenous storage types with no overhead and few abstraction possibilities. The constructor ``()`` can be used to construct tuples. The order of the fields in the constructor must match the order of the tuple's definition. Different tuple-types are @@ -651,8 +653,9 @@ must match the order of the tuple's definition. Different tuple-types are order. The assignment operator for tuples copies each component. -The default assignment operator for objects is not defined. The programmer may -provide one, however. +The default assignment operator for objects copies each component. Overloading +of the assignment operator for objects is not possible, but this may change in +future versions of the compiler. .. code-block:: nimrod @@ -667,7 +670,7 @@ provide one, however. person = ("Peter", 30) The implementation aligns the fields for best access performance. The alignment -is done in a way that is compatible the way the C compiler does it. +is compatible with the way the C compiler does it. Objects provide many features that tuples do not. Object provide inheritance and information hiding. Objects have access to their type at runtime, so that @@ -677,7 +680,7 @@ the ``is`` operator can be used to determine the object's type. type TPerson = object - name*: string # the * means that `name` is accessible from the outside + name*: string # the * means that `name` is accessible from other modules age: int # no * means that the field is hidden TStudent = object of TPerson # a student is a person @@ -692,6 +695,7 @@ Object fields that should be visible outside from the defining module, have to marked by ``*``. In contrast to tuples, different object types are never *equivalent*. + Object variants ~~~~~~~~~~~~~~~ Often an object hierarchy is overkill in certain situations where simple @@ -726,6 +730,7 @@ An example: new(n) # creates a new node n.kind = nkFloat n.floatVal = 0.0 # valid, because ``n.kind==nkFloat``, so that it fits + # the following statement raises an `EInvalidField` exception, because # n.kind's value does not fit: n.strVal = "" @@ -739,9 +744,7 @@ Set type ~~~~~~~~ The `set type`:idx: models the mathematical notion of a set. The set's basetype can only be an ordinal type. The reason is that sets are implemented -as bit vectors. Sets are designed for high performance computing. - -Note: The sets module can be used for sets of other types. +as high performance bit vectors. Sets can be constructed via the set constructor: ``{}`` is the empty set. The empty set is type combatible with any special set type. The constructor @@ -767,22 +770,23 @@ operation meaning ``e in A`` set membership (A contains element e) ``A -+- B`` symmetric set difference (= (A - B) + (B - A)) ``card(A)`` the cardinality of A (number of elements in A) -``incl(A, elem)`` same as A = A + {elem}, but may be faster -``excl(A, elem)`` same as A = A - {elem}, but may be faster +``incl(A, elem)`` same as A = A + {elem} +``excl(A, elem)`` same as A = A - {elem} ================== ======================================================== -Reference type -~~~~~~~~~~~~~~ + +Reference and pointer types +~~~~~~~~~~~~~~~~~~~~~~~~~~~ References (similiar to `pointers`:idx: in other programming languages) are a way to introduce many-to-one relationships. This means different references can -point to and modify the same location in memory. References should be used -sparingly in a program. They are only needed for constructing graphs. +point to and modify the same location in memory. Nimrod distinguishes between `traced`:idx: and `untraced`:idx: references. -Untraced references are also called *pointers*. The difference between them is -that traced references are garbage collected, untraced are not. Thus untraced -references are *unsafe*. However for certain low-level operations (accessing -the hardware) untraced references are unavoidable. +Untraced references are also called *pointers*. Traced references point to +objects of a garbage collected heap, untraced references point to +manually allocated objects or to objects somewhere else in memory. Thus +untraced references are *unsafe*. However for certain low-level operations +(accessing the hardware) untraced references are unavoidable. Traced references are declared with the **ref** keyword, untraced references are declared with the **ptr** keyword. @@ -806,13 +810,15 @@ dereferencing operations for reference types: var n: PNode new(n) - n.data = 9 # no need to write n^.data + n.data = 9 # no need to write n^ .data To allocate a new traced object, the built-in procedure ``new`` has to be used. To deal with untraced memory, the procedures ``alloc``, ``dealloc`` and ``realloc`` can be used. The documentation of the system module contains further information. +If a reference points to *nothing*, it has the value ``nil``. + Special care has to be taken if an untraced object contains traced objects like traced references, strings or sequences: In order to free everything properly, the built-in procedure ``GCunref`` has to be called before freeing the @@ -822,7 +828,7 @@ untraced memory manually! Procedural type ~~~~~~~~~~~~~~~ -A `procedural type`:idx: is internally a pointer to procedure. ``nil`` is +A `procedural type`:idx: is internally a pointer to a procedure. ``nil`` is an allowed value for variables of a procedural type. Nimrod uses procedural types to achieve `functional`:idx: programming techniques. Dynamic dispatch for OOP constructs can also be implemented with procedural types. @@ -928,7 +934,7 @@ statements always have to be intended:: complexStmt ::= ifStmt | whileStmt | caseStmt | tryStmt | forStmt | blockStmt | asmStmt | procDecl | iteratorDecl | macroDecl | templateDecl - | constDecl | typeDecl | whenStmt | varStmt + | constSection | typeSection | whenStmt | varSection @@ -957,8 +963,10 @@ Var statement Syntax:: colonOrEquals ::= COLON typeDesc [EQUALS expr] | EQUALS expr - varPart ::= (symbol ["*" | "-"] [pragma] optComma)+ colonOrEquals [COMMENT] - varStmt ::= VAR (varPart | indPush varPart (SAD varPart)* DED) + varField ::= symbol ["*"] [pragma] + varPart ::= symbol (comma symbol)* [comma] colonOrEquals [COMMENT | IND COMMENT] + varSection ::= VAR (varPart + | indPush (COMMENT|varPart) (SAD (COMMENT|varPart))* DED) `Var`:idx: statements declare new local and global variables and initialize them. A comma seperated list of variables can be used to specify @@ -1126,14 +1134,12 @@ Syntax:: Example: .. code-block:: nimrod - raise EOS("operating system failed") + raise newEOS("operating system failed") Apart from built-in operations like array indexing, memory allocation, etc. -the ``raise`` statement is the only way to raise an exception. The -identifier has to be the name of a previously declared exception. A -comma followed by an expression may follow; the expression must be of type -``string`` or ``cstring``; this is an error message that can be extracted -with the `getCurrentExceptionMsg`:idx: procedure in the module ``system``. +the ``raise`` statement is the only way to raise an exception. + +.. XXX document this better! If no exception name is given, the current exception is `re-raised`:idx:. The `ENoExceptionToReraise`:idx: exception is raised if there is no exception to @@ -1146,10 +1152,11 @@ Try statement Syntax:: - exceptList ::= (qualifiedIdent optComma)* + exceptList ::= [qualifiedIdent (comma qualifiedIdent)* [comma]] tryStmt ::= TRY COLON stmt - (EXCEPT exceptList COLON stmt)* - [FINALLY COLON stmt] + (EXCEPT exceptList COLON stmt)* + [FINALLY COLON stmt] + Example: @@ -1209,10 +1216,15 @@ sugar for: .. code-block:: nimrod result = expr - return + return result + +``return`` without an expression is a short notation for ``return result`` if +the proc has a return type. The `result`:idx: variable is always the return +value of the procedure. It is automatically declared by the compiler. As all +variables, ``result`` is initialized to (binary) zero:: -The `result`:idx: variable is always the return value of the procedure. It is -automatically declared by the compiler. +.. code-block:: nimrod + proc returnZero(): int = nil # implicitely returns 0 Yield statement @@ -1274,7 +1286,7 @@ Example: The `break`:idx: statement is used to leave a block immediately. If ``symbol`` is given, it is the name of the enclosing block that is to leave. If it is -absent, the innermost block is leaved. +absent, the innermost block is left. While statement @@ -1343,14 +1355,16 @@ called `procedures`:idx: in Nimrod (which is the correct terminology). A procedure declaration defines an identifier and associates it with a block of code. A procedure may call itself recursively. The syntax is:: - paramList ::= [PAR_LE ((symbol optComma)+ COLON typeDesc optComma)* PAR_RI] - [COLON typeDesc] + param ::= symbol (comma symbol)* [comma] COLON typeDesc + paramList ::= [PAR_LE [param (comma param)* [comma]] PAR_RI] [COLON typeDesc] + genericParams ::= BRACKET_LE (symbol [EQUALS typeDesc] )* BRACKET_RI - - procDecl ::= PROC symbol ["*"] [genericParams] paramList [pragma] + + procDecl ::= PROC symbol ["*"] [genericParams] + paramList [pragma] [EQUALS stmt] - -If the ``EQUALS stms`` part is missing, it is a `forward`:idx: declaration. If + +If the ``EQUALS stmt`` part is missing, it is a `forward`:idx: declaration. If the proc returns a value, the procedure body can access an implicit declared variable named `result`:idx: that represents the return value. Procs can be overloaded. The overloading resolution algorithm tries to find the proc that is @@ -1388,8 +1402,8 @@ Calling a procedure can be done in many different ways: callme(y=1, x=0, "abd", '\t') # (x=0, y=1, s="abd", c='\t', b=false) # call with named arguments (order is not relevant): callme(c='\t', y=1, x=0) # (x=0, y=1, s="", c='\t', b=false) - # call as a command statement: no () or , needed: - callme 0 1 "abc" '\t' + # call as a command statement: no () needed: + callme 0, 1, "abc", '\t' Iterators and the for statement @@ -1397,12 +1411,13 @@ Iterators and the for statement Syntax:: - forStmt ::= FOR (symbol optComma)+ IN expr [DOTDOT expr] COLON stmt + forStmt ::= FOR symbol (comma symbol)* [comma] IN expr [DOTDOT expr] COLON stmt - paramList ::= [PAR_LE ((symbol optComma)+ COLON typeDesc optComma)* PAR_RI] - [COLON typeDesc] + param ::= symbol (comma symbol)* [comma] COLON typeDesc + paramList ::= [PAR_LE [param (comma param)* [comma]] PAR_RI] [COLON typeDesc] + genericParams ::= BRACKET_LE (symbol [EQUALS typeDesc] )* BRACKET_RI - + iteratorDecl ::= ITERATOR symbol ["*"] [genericParams] paramList [pragma] [EQUALS stmt] @@ -1482,7 +1497,7 @@ Example: A `type`:idx: section begins with the ``type`` keyword. It contains multiple type definitions. A type definition binds a type to a name. Type definitions -can be recursive or even mutually recursive. Mutually Recursive types are only +can be recursive or even mutually recursive. Mutually recursive types are only possible within a single ``type`` section. @@ -1579,17 +1594,16 @@ macros. Modules ------- Nimrod supports splitting a program into pieces by a `module`:idx: concept. -Modules make separate compilation possible. Each module needs to be in its -own file. Modules enable `information hiding`:idx: and -`separate compilation`:idx:. A module may gain access to symbols of another -module by the `import`:idx: statement. `Recursive module dependancies`:idx: are -allowed, but slightly subtle. Only top-level symbols that are marked with an -asterisk (``*``) are exported. +Each module needs to be in its own file. Modules enable +`information hiding`:idx: and `separate compilation`:idx:. A module may gain +access to symbols of another module by the `import`:idx: statement. +`Recursive module dependancies`:idx: are allowed, but slightly subtle. Only +top-level symbols that are marked with an asterisk (``*``) are exported. The algorithm for compiling modules is: - Compile the whole module as usual, following import statements recursively -- if we have a cycle only import the already parsed symbols (that are +- if there is a cycle only import the already parsed symbols (that are exported); if an unknown identifier occurs then abort This is best illustrated by an example: @@ -1684,7 +1698,10 @@ Pragmas Syntax:: - pragma ::= CURLYDOT_LE (expr [COLON expr] optComma)+ (CURLYDOT_RI | CURLY_RI) + colonExpr ::= expr [COLON expr] + colonExprList ::= [ colonExpr (comma colonExpr)* [comma] ] + + pragma ::= CURLYDOT_LE colonExprList (CURLYDOT_RI | CURLY_RI) Pragmas are Nimrod's method to give the compiler additional information/ commands without introducing a massive number of new keywords. Pragmas are @@ -1770,7 +1787,6 @@ hints on|off Turns the hint messages of the compiler optimization none|speed|size Optimize the code for speed or size, or disable optimization. For non-optimizing compilers this option has no effect. - Neverless they must parse it properly. callconv cdecl|... Specifies the default calling convention for all procedures (and procedure types) that follow. diff --git a/doc/theindex.txt b/doc/theindex.txt index 997329242..f60e85d28 100644 --- a/doc/theindex.txt +++ b/doc/theindex.txt @@ -400,7 +400,7 @@ Index `posix.html#1093 <posix.html#1093>`_ `assembler`:idx: - `manual.html#198 <manual.html#198>`_ + `manual.html#197 <manual.html#197>`_ `assert`:idx: `system.html#416 <system.html#416>`_ @@ -425,7 +425,7 @@ Index `system.html#373 <system.html#373>`_ `block`:idx: - `manual.html#194 <manual.html#194>`_ + `manual.html#193 <manual.html#193>`_ `bool`:idx: `system.html#109 <system.html#109>`_ @@ -434,7 +434,7 @@ Index `manual.html#147 <manual.html#147>`_ `break`:idx: - `manual.html#195 <manual.html#195>`_ + `manual.html#194 <manual.html#194>`_ `breakpoint`:idx: `endb.html#103 <endb.html#103>`_ @@ -702,7 +702,7 @@ Index `libzip.html#169 <libzip.html#169>`_ `continue`:idx: - `manual.html#197 <manual.html#197>`_ + `manual.html#196 <manual.html#196>`_ `copy`:idx: * `system.html#403 <system.html#403>`_ @@ -857,7 +857,7 @@ Index `system.html#157 <system.html#157>`_ `define`:idx: - `manual.html#224 <manual.html#224>`_ + `manual.html#223 <manual.html#223>`_ `defined`:idx: `system.html#114 <system.html#114>`_ @@ -933,7 +933,7 @@ Index `nimrodc.html#120 <nimrodc.html#120>`_ `domain specific languages`:idx: - `manual.html#213 <manual.html#213>`_ + `manual.html#212 <manual.html#212>`_ `D_T_FMT`:idx: `posix.html#390 <posix.html#390>`_ @@ -1083,8 +1083,7 @@ Index `regexprs.html#104 <regexprs.html#104>`_ `EInvalidValue`:idx: - * `manual.html#146 <manual.html#146>`_ - * `system.html#143 <system.html#143>`_ + `system.html#143 <system.html#143>`_ `EIO`:idx: * `system.html#134 <system.html#134>`_ @@ -1161,7 +1160,7 @@ Index `posix.html#264 <posix.html#264>`_ `ENoExceptionToReraise`:idx: - * `manual.html#186 <manual.html#186>`_ + * `manual.html#185 <manual.html#185>`_ * `system.html#149 <system.html#149>`_ `ENOEXEC`:idx: @@ -1228,7 +1227,8 @@ Index `system.html#144 <system.html#144>`_ `EOutOfRange`:idx: - `system.html#147 <system.html#147>`_ + * `manual.html#146 <manual.html#146>`_ + * `system.html#147 <system.html#147>`_ `EOVERFLOW`:idx: `posix.html#283 <posix.html#283>`_ @@ -1279,8 +1279,8 @@ Index `posix.html#219 <posix.html#219>`_ `error`:idx: - * `manual.html#223 <manual.html#223>`_ - * `manual.html#226 <manual.html#226>`_ + * `manual.html#222 <manual.html#222>`_ + * `manual.html#225 <manual.html#225>`_ * `dialogs.html#104 <dialogs.html#104>`_ `errorStr`:idx: @@ -1324,10 +1324,10 @@ Index `posix.html#297 <posix.html#297>`_ `except`:idx: - `manual.html#189 <manual.html#189>`_ + `manual.html#188 <manual.html#188>`_ `exception handlers`:idx: - `manual.html#188 <manual.html#188>`_ + `manual.html#187 <manual.html#187>`_ `excl`:idx: `system.html#165 <system.html#165>`_ @@ -1396,7 +1396,7 @@ Index `manual.html#169 <manual.html#169>`_ `fatal`:idx: - `manual.html#227 <manual.html#227>`_ + `manual.html#226 <manual.html#226>`_ `fchdir`:idx: `posix.html#984 <posix.html#984>`_ @@ -1522,7 +1522,7 @@ Index `os.html#106 <os.html#106>`_ `finally`:idx: - `manual.html#190 <manual.html#190>`_ + `manual.html#189 <manual.html#189>`_ `find`:idx: * `system.html#456 <system.html#456>`_ @@ -1573,7 +1573,7 @@ Index `posix.html#478 <posix.html#478>`_ `for`:idx: - `manual.html#205 <manual.html#205>`_ + `manual.html#204 <manual.html#204>`_ `fork`:idx: `posix.html#986 <posix.html#986>`_ @@ -1582,7 +1582,7 @@ Index `manual.html#124 <manual.html#124>`_ `forward`:idx: - `manual.html#202 <manual.html#202>`_ + `manual.html#201 <manual.html#201>`_ `fpathconf`:idx: `posix.html#987 <posix.html#987>`_ @@ -1678,7 +1678,7 @@ Index `posix.html#311 <posix.html#311>`_ `funtions`:idx: - `manual.html#200 <manual.html#200>`_ + `manual.html#199 <manual.html#199>`_ `F_WRLCK`:idx: `posix.html#312 <posix.html#312>`_ @@ -1718,7 +1718,7 @@ Index `regexprs.html#102 <regexprs.html#102>`_ `Generics`:idx: - `manual.html#209 <manual.html#209>`_ + `manual.html#208 <manual.html#208>`_ `getApplicationDir`:idx: `os.html#110 <os.html#110>`_ @@ -1748,8 +1748,7 @@ Index `os.html#112 <os.html#112>`_ `getCurrentExceptionMsg`:idx: - * `manual.html#184 <manual.html#184>`_ - * `system.html#428 <system.html#428>`_ + `system.html#428 <system.html#428>`_ `getCurrentLine`:idx: `lexbase.html#106 <lexbase.html#106>`_ @@ -2027,8 +2026,8 @@ Index `system.html#118 <system.html#118>`_ `hint`:idx: - * `manual.html#221 <manual.html#221>`_ - * `manual.html#229 <manual.html#229>`_ + * `manual.html#220 <manual.html#220>`_ + * `manual.html#228 <manual.html#228>`_ `htonl`:idx: `posix.html#792 <posix.html#792>`_ @@ -2058,10 +2057,10 @@ Index `manual.html#181 <manual.html#181>`_ `implicit block`:idx: - `manual.html#207 <manual.html#207>`_ + `manual.html#206 <manual.html#206>`_ `import`:idx: - `manual.html#217 <manual.html#217>`_ + `manual.html#216 <manual.html#216>`_ `importc`:idx: `nimrodc.html#101 <nimrodc.html#101>`_ @@ -2127,7 +2126,7 @@ Index `dialogs.html#102 <dialogs.html#102>`_ `information hiding`:idx: - `manual.html#215 <manual.html#215>`_ + `manual.html#214 <manual.html#214>`_ `init`:idx: `parseopt.html#103 <parseopt.html#103>`_ @@ -2213,7 +2212,7 @@ Index * `system.html#443 <system.html#443>`_ `iterator`:idx: - `manual.html#206 <manual.html#206>`_ + `manual.html#205 <manual.html#205>`_ `iterOverEnvironment`:idx: `os.html#152 <os.html#152>`_ @@ -2339,7 +2338,7 @@ Index `posix.html#1061 <posix.html#1061>`_ `Macros`:idx: - `manual.html#212 <manual.html#212>`_ + `manual.html#211 <manual.html#211>`_ `makecontext`:idx: `posix.html#1189 <posix.html#1189>`_ @@ -2384,7 +2383,7 @@ Index `posix.html#685 <posix.html#685>`_ `methods`:idx: - `manual.html#199 <manual.html#199>`_ + `manual.html#198 <manual.html#198>`_ `min`:idx: * `system.html#263 <system.html#263>`_ @@ -2501,7 +2500,7 @@ Index * `system.html#217 <system.html#217>`_ `module`:idx: - `manual.html#214 <manual.html#214>`_ + `manual.html#213 <manual.html#213>`_ `MON_1`:idx: `posix.html#410 <posix.html#410>`_ @@ -2775,7 +2774,7 @@ Index `manual.html#139 <manual.html#139>`_ `Operators`:idx: - `manual.html#204 <manual.html#204>`_ + `manual.html#203 <manual.html#203>`_ `or`:idx: * `system.html#233 <system.html#233>`_ @@ -3122,7 +3121,7 @@ Index `manual.html#162 <manual.html#162>`_ `procedures`:idx: - `manual.html#201 <manual.html#201>`_ + `manual.html#200 <manual.html#200>`_ `PROT_EXEC`:idx: `posix.html#676 <posix.html#676>`_ @@ -3563,7 +3562,7 @@ Index `zlib.html#104 <zlib.html#104>`_ `push/pop`:idx: - `manual.html#230 <manual.html#230>`_ + `manual.html#229 <manual.html#229>`_ `putEnv`:idx: `os.html#142 <os.html#142>`_ @@ -3624,7 +3623,7 @@ Index `system.html#120 <system.html#120>`_ `re-raised`:idx: - `manual.html#185 <manual.html#185>`_ + `manual.html#184 <manual.html#184>`_ `read`:idx: `posix.html#1018 <posix.html#1018>`_ @@ -3686,7 +3685,7 @@ Index `system.html#413 <system.html#413>`_ `Recursive module dependancies`:idx: - `manual.html#218 <manual.html#218>`_ + `manual.html#217 <manual.html#217>`_ `register`:idx: `nimrodc.html#113 <nimrodc.html#113>`_ @@ -3708,11 +3707,11 @@ Index `system.html#371 <system.html#371>`_ `result`:idx: - * `manual.html#192 <manual.html#192>`_ - * `manual.html#203 <manual.html#203>`_ + * `manual.html#191 <manual.html#191>`_ + * `manual.html#202 <manual.html#202>`_ `return`:idx: - `manual.html#191 <manual.html#191>`_ + `manual.html#190 <manual.html#190>`_ `rewinddir`:idx: `posix.html#804 <posix.html#804>`_ @@ -3965,7 +3964,7 @@ Index `scope`:idx: * `manual.html#106 <manual.html#106>`_ - * `manual.html#219 <manual.html#219>`_ + * `manual.html#218 <manual.html#218>`_ `SC_OPEN_MAX`:idx: `posix.html#571 <posix.html#571>`_ @@ -4229,7 +4228,7 @@ Index `posix.html#1054 <posix.html#1054>`_ `separate compilation`:idx: - `manual.html#216 <manual.html#216>`_ + `manual.html#215 <manual.html#215>`_ `seq`:idx: `system.html#123 <system.html#123>`_ @@ -6355,7 +6354,7 @@ Index `posix.html#1034 <posix.html#1034>`_ `system`:idx: - `manual.html#220 <manual.html#220>`_ + `manual.html#219 <manual.html#219>`_ `tabulator`:idx: `manual.html#125 <manual.html#125>`_ @@ -6427,7 +6426,7 @@ Index `posix.html#806 <posix.html#806>`_ `template`:idx: - `manual.html#211 <manual.html#211>`_ + `manual.html#210 <manual.html#210>`_ `TEndian`:idx: `system.html#385 <system.html#385>`_ @@ -6696,7 +6695,7 @@ Index `posix.html#1037 <posix.html#1037>`_ `try`:idx: - `manual.html#187 <manual.html#187>`_ + `manual.html#186 <manual.html#186>`_ `Tsched_param`:idx: `posix.html#199 <posix.html#199>`_ @@ -6854,10 +6853,10 @@ Index `type`:idx: * `manual.html#102 <manual.html#102>`_ * `manual.html#141 <manual.html#141>`_ - * `manual.html#208 <manual.html#208>`_ + * `manual.html#207 <manual.html#207>`_ `type parameters`:idx: - `manual.html#210 <manual.html#210>`_ + `manual.html#209 <manual.html#209>`_ `type suffix`:idx: `manual.html#138 <manual.html#138>`_ @@ -6908,7 +6907,7 @@ Index `zlib.html#156 <zlib.html#156>`_ `undef`:idx: - `manual.html#225 <manual.html#225>`_ + `manual.html#224 <manual.html#224>`_ `UnixToNativePath`:idx: `os.html#124 <os.html#124>`_ @@ -6963,8 +6962,8 @@ Index * `zipfiles.html#110 <zipfiles.html#110>`_ `warning`:idx: - * `manual.html#222 <manual.html#222>`_ - * `manual.html#228 <manual.html#228>`_ + * `manual.html#221 <manual.html#221>`_ + * `manual.html#227 <manual.html#227>`_ * `dialogs.html#103 <dialogs.html#103>`_ `WCONTINUED`:idx: @@ -6980,7 +6979,7 @@ Index `manual.html#183 <manual.html#183>`_ `while`:idx: - `manual.html#196 <manual.html#196>`_ + `manual.html#195 <manual.html#195>`_ `Whitespace`:idx: `strutils.html#102 <strutils.html#102>`_ @@ -7058,7 +7057,7 @@ Index `posix.html#441 <posix.html#441>`_ `yield`:idx: - `manual.html#193 <manual.html#193>`_ + `manual.html#192 <manual.html#192>`_ `Z_ASCII`:idx: `zlib.html#138 <zlib.html#138>`_ |