summary refs log tree commit diff stats
path: root/doc
diff options
context:
space:
mode:
authorAndreas Rumpf <rumpf_a@web.de>2009-01-07 17:03:25 +0100
committerAndreas Rumpf <rumpf_a@web.de>2009-01-07 17:03:25 +0100
commit439aa2d04d5528b5aed288f70895515d1da2dc3d (patch)
treecda2d0bc4d4f2bab189c4a0567cae3c1428c5ed0 /doc
parent1c8ddca7e08af9075a930edaca6c522d5e6fd8b5 (diff)
downloadNim-439aa2d04d5528b5aed288f70895515d1da2dc3d.tar.gz
version 0.7.4
Diffstat (limited to 'doc')
-rw-r--r--doc/docs.txt17
-rw-r--r--doc/filelist.txt95
-rw-r--r--doc/grammar.txt243
-rw-r--r--doc/intern.txt187
-rw-r--r--doc/manual.txt565
-rw-r--r--doc/nimrodc.txt66
-rw-r--r--doc/rst.txt3
-rw-r--r--doc/theindex.txt15006
-rw-r--r--doc/tut1.txt1382
-rw-r--r--doc/tut2.txt718
-rw-r--r--doc/tutorial.txt215
11 files changed, 10325 insertions, 8172 deletions
diff --git a/doc/docs.txt b/doc/docs.txt
index b2fe3ebed..431a79a29 100644
--- a/doc/docs.txt
+++ b/doc/docs.txt
@@ -3,25 +3,28 @@
 
 The documentation consists of several documents:
 
-- | `First steps after installation <steps.html>`_
-  | Read this after installation for a quick introduction.
+- | `Nimrod tutorial (part I) <tut1.html>`_
+  | The Nimrod tutorial part one deals with the basics.
+
+- | `Nimrod tutorial (part II) <tut2.html>`_
+  | The Nimrod tutorial part two deals with the advanced language constructs.
 
 - | `Nimrod manual <manual.html>`_
-  | Read this to get to know the Nimrod programming system.
+  | The Nimrod manual is a draft that will evolve into a proper specification.
 
 - | `User guide for the Nimrod Compiler <nimrodc.html>`_
-  | The user guide lists command line arguments, Nimrodc's special features, etc.
+  | The user guide lists command line arguments, special features of the
+    compiler, etc.
 
 - | `User guide for the Embedded Nimrod Debugger <endb.html>`_
-  | This document describes how to use the Embedded debugger. The embedded
-    debugger currently has no GUI. Please help!
+  | This document describes how to use the Embedded Debugger. 
 
 - | `Nimrod library documentation <lib.html>`_
   | This document describes Nimrod's standard library.
 
 - | `Nimrod internal documentation <intern.html>`_
   | The internal documentation describes how the compiler is implemented. Read
-    this if you want to hack the compiler or develop advanced macros.
+    this if you want to hack the compiler.
 
 - | `Index <theindex.html>`_
   | The generated index. Often the quickest way to find the piece of
diff --git a/doc/filelist.txt b/doc/filelist.txt
index 5d9f1125e..fb2f67a37 100644
--- a/doc/filelist.txt
+++ b/doc/filelist.txt
@@ -1,41 +1,54 @@
-Short description of Nimrod's modules

--------------------------------------

-

-==============  ==========================================================

-Module          Description

-==============  ==========================================================

-lexbase         buffer handling of the lexical analyser

-scanner         lexical analyser

-

-ast             type definitions of the abstract syntax tree (AST) and

-                node constructors

-astalgo         algorithms for containers of AST nodes; converting the

-                AST to YAML; the symbol table

-passes          implement the passes managemer for passes over the AST

-trees           few algorithms for nodes; this module is less important

-types           module for traversing type graphs; also contain several

-                helpers for dealing with types

-

-sigmatch        contains the matching algorithm that is used for proc

-                calls

-semexprs        contains the semantic checking phase for expressions

-semstmts        contains the semantic checking phase for statements

-semtypes        contains the semantic checking phase for types

-

-idents          implements a general mapping from identifiers to an internal

-                representation (``PIdent``) that is used, so that a simple

-                id-comparison suffices to say whether two Nimrod identifiers

-                are equivalent

-

-ropes           implements long strings using represented as trees for

-                lazy evaluation; used mainly by the code generators

-

-ccgobj          contains type definitions neeeded for C code generation

-                and some helpers

-ccgutils        contains helpers for the C code generator

-ccgtypes        the generator for C types

-ccgstmts        the generator for statements

-ccgexprs        the generator for expressions

-extccomp        this module calls the C compiler and linker; interesting

-                if you want to add support for a new C compiler

-==============  ==========================================================

+Short description of Nimrod's modules
+-------------------------------------
+
+==============  ==========================================================
+Module          Description
+==============  ==========================================================
+nimrod          main module: parses the command line and calls
+                ```main.MainCommand``
+main            implements the top-level command dispatching
+lexbase         buffer handling of the lexical analyser
+scanner         lexical analyser
+pnimsyn         Nimrod's parser
+rnimsyn         Nimrod code renderer (AST back to its textual form)
+
+paslex          lexer for Pascal
+pasparse        parser for Pascal; Pascal's advanced OO features are not
+                supported
+
+options         contains global and local compiler options
+ast             type definitions of the abstract syntax tree (AST) and
+                node constructors
+astalgo         algorithms for containers of AST nodes; converting the
+                AST to YAML; the symbol table
+passes          implement the passes managemer for passes over the AST
+trees           few algorithms for nodes; this module is less important
+types           module for traversing type graphs; also contain several
+                helpers for dealing with types
+
+sigmatch        contains the matching algorithm that is used for proc
+                calls
+semexprs        contains the semantic checking phase for expressions
+semstmts        contains the semantic checking phase for statements
+semtypes        contains the semantic checking phase for types
+semfold         contains code to deal with constant folding
+evals           contains an AST interpreter for compile time evaluation
+pragmas         semantic checking of pragmas
+
+idents          implements a general mapping from identifiers to an internal
+                representation (``PIdent``) that is used, so that a simple
+                id-comparison suffices to say whether two Nimrod identifiers
+                are equivalent
+ropes           implements long strings represented as trees for
+                lazy evaluation; used mainly by the code generators
+
+transf          transformations on the AST that need to be done before
+                code generation
+cgen            main file of the C code generator
+ccgutils        contains helpers for the C code generator
+ccgtypes        the generator for C types
+ccgstmts        the generator for statements
+ccgexprs        the generator for expressions
+extccomp        this module calls the C compiler and linker; interesting
+                if you want to add support for a new C compiler
+==============  ==========================================================
diff --git a/doc/grammar.txt b/doc/grammar.txt
index ee46cd63a..fa5a0d036 100644
--- a/doc/grammar.txt
+++ b/doc/grammar.txt
@@ -1,45 +1,43 @@
 module ::= ([COMMENT] [SAD] stmt)*
 
 comma ::= ',' [COMMENT] [IND]
-operator ::= OP0 | OR | XOR | AND | OP3 | OP4 | OP5 | IS | ISNOT | IN | NOTIN
-           | OP6 | DIV | MOD | SHL | SHR | OP7 | NOT
+operator ::= OP0 | OR | XOR | AND | OP3 | OP4 | OP5 | OP6 | OP7
+           | 'is' | 'isnot' | 'in' | 'notin'
+           | 'div' | 'mod' | 'shl' | 'shr' | 'not'
 
-prefixOperator ::= OP0 | OP3 | OP4 | OP5 | OP6 | OP7 | NOT
+prefixOperator ::= OP0 | OP3 | OP4 | OP5 | OP6 | OP7 | 'not'
 
 optInd ::= [COMMENT] [IND]
 
 
-lowestExpr ::= orExpr ( OP0 optInd orExpr )*
-orExpr ::= andExpr ( OR | XOR optInd andExpr )*
-andExpr ::= cmpExpr ( AND  optInd cmpExpr )*
-cmpExpr ::= ampExpr ( OP3 | IS | ISNOT | IN | NOTIN optInd ampExpr )*
-ampExpr ::= plusExpr ( OP4 optInd plusExpr )*
-plusExpr ::= mulExpr ( OP5 optInd mulExpr )*
-mulExpr ::= dollarExpr ( OP6 | DIV | MOD | SHL | SHR optInd dollarExpr )*
-dollarExpr ::= primary ( OP7 optInd primary )*
+lowestExpr ::= orExpr (OP0 optInd orExpr)*
+orExpr ::= andExpr (OR | 'xor' optInd andExpr)*
+andExpr ::= cmpExpr ('and' optInd cmpExpr)*
+cmpExpr ::= ampExpr (OP3 | 'is' | 'isnot' | 'in' | 'notin' optInd ampExpr)*
+ampExpr ::= plusExpr (OP4 optInd plusExpr)*
+plusExpr ::= mulExpr (OP5 optInd mulExpr)*
+mulExpr ::= dollarExpr (OP6 | 'div' | 'mod' | 'shl' | 'shr' optInd dollarExpr)*
+dollarExpr ::= primary (OP7 optInd primary)*
 
 namedTypeOrExpr ::=
-  DOTDOT [expr]
-  | expr [EQUALS (expr [DOTDOT expr] | typeDescK | DOTDOT [expr] )
-                 | DOTDOT [expr]]
+  '..' [expr]
+  | expr ['=' (expr ['..' expr] | typeDescK | '..' [expr]) | '..' [expr]]
   | typeDescK
 
-castExpr ::= CAST BRACKET_LE optInd typeDesc BRACKERT_RI
-                  PAR_LE optInd expr PAR_RI
-addrExpr ::= ADDR PAR_LE optInd expr PAR_RI
-symbol ::= ACC (KEYWORD | IDENT | operator | PAR_LE PAR_RI
-               | BRACKET_LE BRACKET_RI | EQUALS | literal )+ ACC
+castExpr ::= 'cast' '[' optInd typeDesc [SAD] ']' '(' optInd expr [SAD] ')'
+addrExpr ::= 'addr' '(' optInd expr ')'
+symbol ::= '`' (KEYWORD | IDENT | operator | '(' ')'
+               | '[' ']' | '=' | literal)+ '`'
          | IDENT
-primary ::= ( prefixOperator optInd )* ( symbol | constructor |
-                                                | castExpr | addrExpr ) (
-               DOT optInd symbol
-             #| CURLY_LE namedTypeDescList CURLY_RI
-             | PAR_LE optInd namedExprList PAR_RI
-             | BRACKET_LE optInd
-               [ namedTypeOrExpr (comma namedTypeOrExpr)* [comma] ]
-               BRACKET_RI
-             | CIRCUM
-             | pragma )*
+primary ::= (prefixOperator optInd)* (symbol | constructor |
+                                             | castExpr | addrExpr) (
+               '.' optInd symbol
+             | '(' optInd namedExprList [SAD] ')'
+             | '[' optInd
+               [namedTypeOrExpr (comma namedTypeOrExpr)* [comma]]
+               [SAD] ']'
+             | '^'
+             | pragma)*
 
 literal ::= INT_LIT | INT8_LIT | INT16_LIT | INT32_LIT | INT64_LIT
           | FLOAT_LIT | FLOAT32_LIT | FLOAT64_LIT
@@ -48,48 +46,42 @@ literal ::= INT_LIT | INT8_LIT | INT16_LIT | INT32_LIT | INT64_LIT
           | NIL
 
 constructor ::= literal
-          | BRACKET_LE optInd colonExprList BRACKET_RI # []-Constructor
-          | CURLY_LE optInd sliceExprList CURLY_RI     # {}-Constructor
-          | PAR_LE optInd colonExprList PAR_RI         # ()-Constructor
+          | '[' optInd colonExprList [SAD] ']'
+          | '{' optInd sliceExprList [SAD] '}'
+          | '(' optInd colonExprList [SAD] ')'
 
-exprList ::= [ expr (comma expr)* [comma] ]
+colonExpr ::= expr [':' expr]
+colonExprList ::= [colonExpr (comma colonExpr)* [comma]]
 
-colonExpr ::= expr [COLON expr]
-colonExprList ::= [ colonExpr (comma colonExpr)* [comma] ]
+namedExpr ::= expr ['=' expr]
+namedExprList ::= [namedExpr (comma namedExpr)* [comma]]
 
-namedExpr ::= expr [EQUALS expr] # actually this is symbol EQUALS expr|expr
-namedExprList ::= [ namedExpr (comma namedExpr)* [comma] ]
+sliceExpr ::= expr ['..' expr]
+sliceExprList ::= [sliceExpr (comma sliceExpr)* [comma]]
 
-sliceExpr ::= expr [ DOTDOT expr ]
-sliceExprList ::= [ sliceExpr (comma sliceExpr)* [comma] ]
-
-anonymousProc ::= LAMBDA paramList [pragma] EQUALS stmt
+anonymousProc ::= 'lambda' paramList [pragma] '=' stmt
 expr ::= lowestExpr
      | anonymousProc
-     | IF expr COLON expr
-       (ELIF expr COLON expr)*
-       ELSE COLON expr
+     | 'if' expr ':' expr ('elif' expr ':' expr)* 'else' ':' expr
 
-namedTypeDesc ::= typeDescK | expr [EQUALS (typeDescK | expr)]
-namedTypeDescList ::= [ namedTypeDesc (comma namedTypeDesc)* [comma] ]
+namedTypeDesc ::= typeDescK | expr ['=' (typeDescK | expr)]
+namedTypeDescList ::= [namedTypeDesc (comma namedTypeDesc)* [comma]]
 
-qualifiedIdent ::= symbol [ DOT symbol ]
+qualifiedIdent ::= symbol ['.' symbol]
 
-typeDescK ::= VAR typeDesc
-            | REF typeDesc
-            | PTR typeDesc
-            | TYPE expr
-            | TUPLE tupleDesc
-            | PROC paramList [pragma]
+typeDescK ::= 'var' typeDesc
+            | 'ref' typeDesc
+            | 'ptr' typeDesc
+            | 'type' expr
+            | 'tuple' tupleDesc
+            | 'proc' paramList [pragma]
 
 typeDesc ::= typeDescK | primary
 
-optSemicolon ::= [SEMICOLON]
-
-macroStmt ::= COLON [stmt] (OF [sliceExprList] COLON stmt
-                           | ELIF expr COLON stmt
-                           | EXCEPT exceptList COLON stmt )*
-                           [ELSE COLON stmt]
+macroStmt ::= ':' [stmt] ('of' [sliceExprList] ':' stmt
+                         |'elif' expr ':' stmt
+                         |'except' exceptList ':' stmt )*
+                         ['else' ':' stmt]
 
 simpleStmt ::= returnStmt
            | yieldStmt
@@ -107,88 +99,91 @@ complexStmt ::= ifStmt | whileStmt | caseStmt | tryStmt | forStmt
                  | procDecl | iteratorDecl | macroDecl | templateDecl
                  | constSection | typeSection | whenStmt | varSection
 
-indPush ::= IND # push
+indPush ::= IND # and push indentation onto the stack
+indPop ::= # pop indentation from the stack
+
 stmt ::= simpleStmt [SAD]
  | indPush (complexStmt | simpleStmt)
-  ([SAD] (complexStmt | simpleStmt) )*
-   DED
-
-exprStmt ::= lowestExpr [EQUALS expr | [expr (comma expr)* [comma]] [macroStmt]]
-returnStmt ::= RETURN [expr]
-yieldStmt ::= YIELD expr
-discardStmt ::= DISCARD expr
-raiseStmt ::= RAISE [expr]
-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 sliceExprList COLON stmt)*
-                       (ELIF expr COLON stmt)*
-                       [ELSE COLON stmt]
-whileStmt ::= WHILE expr COLON stmt
-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
+  ([SAD] (complexStmt | simpleStmt))*
+   DED indPop
+
+exprStmt ::= lowestExpr ['=' expr | [expr (comma expr)*] [macroStmt]]
+returnStmt ::= 'return' [expr]
+yieldStmt ::= 'yield' expr
+discardStmt ::= 'discard' expr
+raiseStmt ::= 'raise' [expr]
+breakStmt ::= 'break' [symbol]
+continueStmt ::= 'continue'
+ifStmt ::= 'if' expr ':' stmt ('elif' expr ':' stmt)* ['else' ':' stmt]
+whenStmt ::= 'when' expr ':' stmt ('elif' expr ':' stmt)* ['else' ':' stmt]
+caseStmt ::= 'case' expr [':'] ('of' sliceExprList ':' stmt)*
+                               ('elif' expr ':' stmt)*
+                                ['else' ':' stmt]
+whileStmt ::= 'while' expr ':' stmt
+forStmt ::= 'for' symbol (comma symbol)* 'in' expr ['..' expr] ':' stmt
+exceptList ::= [qualifiedIdent (comma qualifiedIdent)*]
+
+tryStmt ::= 'try' ':' stmt
+           ('except' exceptList ':' stmt)*
+           ['finally' ':' stmt]
+asmStmt ::= 'asm' [pragma] (STR_LIT | RSTR_LIT | TRIPLESTR_LIT)
+blockStmt ::= 'block' [symbol] ':' stmt
 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]
+importStmt ::= 'import' filename (comma filename)*
+includeStmt ::= 'include' filename (comma filename)*
+fromStmt ::= 'from' filename 'import' symbol (comma symbol)*
 
-pragma ::= CURLYDOT_LE colonExprList (CURLYDOT_RI | CURLY_RI)
+pragma ::= '{.' optInd (colonExpr [comma])* [SAD] ('.}' | '}')
 
-param ::= symbol (comma symbol)* [comma] COLON typeDesc
-paramList ::= [PAR_LE [param (comma param)* [comma]] PAR_RI] [COLON typeDesc]
+param ::= symbol (comma symbol)* ':' typeDesc
+paramList ::= ['(' [param (comma param)*] [SAD] ')'] [':' typeDesc]
 
-genericParams ::= BRACKET_LE (symbol [EQUALS typeDesc] )* BRACKET_RI
+genericParam ::= symbol [':' typeDesc]
+genericParams ::= '[' genericParam (comma genericParam)* [SAD] ']'
 
-procDecl ::= PROC symbol ["*"] [genericParams]
-             paramList [pragma]
-             [EQUALS stmt]
-macroDecl ::= MACRO symbol ["*"] [genericParams] paramList [pragma]
-             [EQUALS stmt]
-iteratorDecl ::= ITERATOR symbol ["*"] [genericParams] paramList [pragma]
-             [EQUALS stmt]
-templateDecl ::= TEMPLATE symbol ["*"] [genericParams] paramList [pragma]
-             [EQUALS stmt]
+procDecl ::= 'proc' symbol ['*'] [genericParams] paramList [pragma]
+             ['=' stmt]
+macroDecl ::= 'macro' symbol ['*'] [genericParams] paramList [pragma]
+             ['=' stmt]
+iteratorDecl ::= 'iterator' symbol ['*'] [genericParams] paramList [pragma]
+             ['=' stmt]
+templateDecl ::= 'template' symbol ['*'] [genericParams] paramList [pragma]
+             ['=' stmt]
 
-colonAndEquals ::= [COLON typeDesc] EQUALS expr
+colonAndEquals ::= [':' typeDesc] '=' expr
 
-constDecl ::= symbol ["*"] [pragma] colonAndEquals [COMMENT | IND COMMENT]
+constDecl ::= symbol ['*'] [pragma] colonAndEquals [COMMENT | IND COMMENT]
             | COMMENT
-constSection ::= CONST indPush constDecl (SAD constDecl)* DED
+constSection ::= 'const' indPush constDecl (SAD constDecl)* DED indPop
 typeDef ::= typeDesc | objectDef | enumDef
 
-objectField ::= symbol ["*"] [pragma]
+objectField ::= symbol ['*'] [pragma]
 objectIdentPart ::=
-  objectField (comma objectField)* [comma] COLON typeDesc [COMMENT|IND COMMENT]
+  objectField (comma objectField)* ':' 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 sliceExprList COLON [COMMENT] objectPart)*
-              [ELSE COLON [COMMENT] objectPart]
+objectWhen ::= 'when' expr ':' [COMMENT] objectPart
+              ('elif' expr ':' [COMMENT] objectPart)*
+              ['else' ':' [COMMENT] objectPart]
+objectCase ::= 'case' expr ':' typeDesc [COMMENT]
+              ('of' sliceExprList ':' [COMMENT] objectPart)*
+              ['else' ':' [COMMENT] objectPart]
 
-objectPart ::= objectWhen | objectCase | objectIdentPart | NIL
-             | indPush objectPart (SAD objectPart)* DED
-tupleDesc ::= BRACKET_LE optInd [param (comma param)* [comma]] BRACKET_RI
+objectPart ::= objectWhen | objectCase | objectIdentPart | 'nil'
+             | indPush objectPart (SAD objectPart)* DED indPop
+tupleDesc ::= '[' optInd [param (comma param)*] [SAD] ']'
 
-objectDef ::= OBJECT [pragma] [OF typeDesc] objectPart
-enumField ::= symbol [EQUALS expr]
-enumDef ::= ENUM [OF typeDesc] (enumField [comma | COMMENT | IND COMMENT])+
+objectDef ::= 'object' [pragma] ['of' typeDesc] objectPart
+enumField ::= symbol ['=' expr]
+enumDef ::= 'enum' ['of' typeDesc] (enumField [comma] [COMMENT | IND COMMENT])+
 
 typeDecl ::= COMMENT
-           | symbol ["*"] [genericParams] [EQUALS typeDef] [COMMENT | IND COMMENT]
+           | symbol ['*'] [genericParams] ['=' typeDef] [COMMENT | IND COMMENT]
 
-typeSection ::= TYPE indPush typeDecl (SAD typeDecl)* DED
+typeSection ::= 'type' indPush typeDecl (SAD typeDecl)* DED indPop
 
-colonOrEquals ::= COLON typeDesc [EQUALS expr] | EQUALS expr
-varField ::= symbol ["*"] [pragma]
-varPart ::= symbol (comma symbol)* [comma] colonOrEquals [COMMENT | IND COMMENT]
-varSection ::= VAR (varPart
-                   | indPush (COMMENT|varPart) (SAD (COMMENT|varPart))* DED)
+colonOrEquals ::= ':' typeDesc ['=' expr] | '=' expr
+varField ::= symbol ['*'] [pragma]
+varPart ::= symbol (comma symbol)* colonOrEquals [COMMENT | IND COMMENT]
+varSection ::= 'var' (varPart
+                   | indPush (COMMENT|varPart)
+                     (SAD (COMMENT|varPart))* DED indPop)
diff --git a/doc/intern.txt b/doc/intern.txt
index 4d65c1e55..6496e0e29 100644
--- a/doc/intern.txt
+++ b/doc/intern.txt
@@ -34,7 +34,6 @@ Path           Purpose
                on it!
 ``web``        website of Nimrod; generated by ``koch.py``
                from the ``*.txt`` and ``*.tmpl`` files
-``koch``       the Koch Build System (written for Nimrod)
 ``obj``        generated ``*.obj`` files go into here
 ============   ==============================================
 
@@ -45,44 +44,76 @@ Bootstrapping the compiler
 The compiler is written in a subset of Pascal with special annotations so
 that it can be translated to Nimrod code automatically. This conversion is
 done by Nimrod itself via the undocumented ``boot`` command. Thus both Nimrod
-and Free Pascal can compile the Nimrod compiler.
+and Free Pascal can compile the Nimrod compiler. However, the Pascal version
+has no garbage collector and leaks memory like crazy! So the Pascal version
+should only be used for bootstrapping.
 
 Requirements for bootstrapping:
 
-- Free Pascal (I used version 2.2) [optional]
-- Python (should work with version 1.5 or higher)
+- Python (should work with version 1.5 or higher) (optional)
+- supported C compiler
 
-- C compiler -- one of:
+Compiling the compiler is a simple matter of running::
 
-  * win32-lcc (currently broken)
-  * Borland C++ (tested with 5.5; currently broken)
-  * Microsoft C++
-  * Digital Mars C++
-  * Watcom C++ (currently broken)
-  * GCC
-  * Intel C++
-  * Pelles C (currently broken)
-  * llvm-gcc
+  koch.py boot
 
-| Compiling the compiler is a simple matter of running:
-| ``koch.py boot``
-| Or you can compile by hand, this is not difficult.
+For a release version use::
 
-If you want to debug the compiler, use the command::
+  koch.py boot -d:release
 
-  koch.py boot --debugger:on
+The ``koch.py`` script is Nimrod's maintainance script. It is a replacement for
+make and shell scripting with the advantage that it is much more portable.
 
-The ``koch.py`` script is Nimrod's maintainance script: Everything that has 
-been automated is accessible with it. It is a replacement for make and shell
-scripting with the advantage that it is more portable.
+If you don't have Python, there is a ``boot`` Nimrod program which does roughly
+the same::
 
+  nimrod cc boot.nim
+  ./boot [-d:release]
 
-Coding standards
-================
 
-The compiler is written in a subset of Pascal with special annotations so
-that it can be translated to Nimrod code automatically. As a general rule,
-Pascal code that does not translate to Nimrod automatically is forbidden.
+Pascal annotations
+==================
+There are some annotations that the Pascal sources use so that they can
+be converted to Nimrod automatically:
+
+``{@discard} <expr>``
+    Tells the compiler that a ``discard`` statement is needed for Nimrod
+    here.
+
+``{@cast}typ(expr)``
+    Tells the compiler that the Pascal conversion is a ``cast`` in Nimrod.
+
+``{@emit <code>}``
+    Emits ``<code>``. The code fragment needs to be in Pascal syntax.
+
+``{@ignore} <codeA> {@emit <codeB>}``
+    Ignores ``<codeA>`` and instead emits ``<codeB>`` which needs to be in
+    Pascal syntax. An empty ``{@emit}`` is possible too (it then only closes
+    the ``<codeA>`` part).
+
+``record {@tuple}``
+    Is used to tell the compiler that the record type should be transformed
+    to a Nimrod tuple type.
+
+``^ {@ptr}``
+    Is used to tell the compiler that the pointer type should be transformed
+    to a Nimrod ``ptr`` type. The default is a ``ref`` type.
+
+``'a' + ''``
+    The idiom ``+''`` is used to tell the compiler that it is a string
+    literal and not a character literal. (Pascal does not distinguish between
+    character literals and string literals of length 1.)
+
+``+{&}``
+    This tells the compiler that Pascal's ``+`` here is a string concatenation
+    and thus should be converted to ``&``. Note that this is not needed if
+    any of the operands is a string literal because the compiler then can
+    figure this out by itself.
+
+``{@set}['a', 'b', 'c']``
+    Tells the compiler that Pascal's ``[]`` constructor is a set and not an
+    array. This is only needed if the compiler cannot figure this out for
+    itself.
 
 
 Porting to new platforms
@@ -99,7 +130,7 @@ check that the OS, System modules work and recompile Nimrod.
 The only case where things aren't as easy is when the garbage
 collector needs some assembler tweaking to work. The standard
 version of the GC uses C's ``setjmp`` function to store all registers
-on the hardware stack. It may be that the new platform needs to
+on the hardware stack. It may be necessary that the new platform needs to
 replace this generic code by some assembler code.
 
 
@@ -132,11 +163,11 @@ The Garbage Collector
 Introduction
 ------------
 
-We use the term *cell* here to refer to everything that is traced
+I use the term *cell* here to refer to everything that is traced
 (sequences, refs, strings).
 This section describes how the new GC works.
 
-The basic algorithm is *Deferrent reference counting* with cycle detection.
+The basic algorithm is *Deferrent Reference Counting* with cycle detection.
 References in the stack are not counted for better performance and easier C
 code generation.
 
@@ -170,7 +201,7 @@ modifying a ``TCellSet`` during traversation leads to undefined behaviour.
   iterator elements(s: TCellSet): (elem: PCell)
 
 
-All the operations have to be perform efficiently. Because a Cellset can
+All the operations have to perform efficiently. Because a Cellset can
 become huge a hash table alone is not suitable for this.
 
 We use a mixture of bitset and hash table for this. The hash table maps *pages*
@@ -246,16 +277,10 @@ This syntax tree is the interface between the parser and the code generator.
 It is essential to understand most of the compiler's code.
 
 In order to compile Nimrod correctly, type-checking has to be seperated from
-parsing. Otherwise generics would not work. Code generation is done for a 
-whole module only after it has been checked for semantics.
+parsing. Otherwise generics would not work.
 
 .. include:: filelist.txt
 
-The first command line argument selects the backend. Thus the backend is
-responsible for calling the parser and semantic checker. However, when 
-compiling ``import`` or ``include`` statements, the semantic checker needs to
-call the backend, this is done by embedding a PBackend into a TContext.
-
 
 The syntax tree
 ---------------
@@ -265,7 +290,7 @@ may contain cycles. The AST changes its shape after semantic checking. This
 is needed to make life easier for the code generators. See the "ast" module
 for the type definitions.
 
-We use the notation ``nodeKind(fields, [sons])`` for describing
+I use the notation ``nodeKind(fields, [sons])`` for describing
 nodes. ``nodeKind[sons]`` is a short-cut for ``nodeKind([sons])``.
 XXX: Description of the language's syntax and the corresponding trees.
 
@@ -273,12 +298,16 @@ XXX: Description of the language's syntax and the corresponding trees.
 How the RTL is compiled
 =======================
 
-The system module contains the part of the RTL which needs support by
+The ``system`` module contains the part of the RTL which needs support by
 compiler magic (and the stuff that needs to be in it because the spec
 says so). The C code generator generates the C code for it just like any other
 module. However, calls to some procedures like ``addInt`` are inserted by
-the CCG. Therefore the module ``magicsys`` contains a table
-(``compilerprocs``) with all symbols that are marked as ``compilerproc``.
+the CCG. Therefore the module ``magicsys`` contains a table (``compilerprocs``)
+with all symbols that are marked as ``compilerproc``. ``compilerprocs`` are
+needed by the code generator. A ``magic`` proc is not the same as a
+``compilerproc``: A ``magic`` is a proc that needs compiler magic for its
+semantic checking, a ``compilerproc`` is a proc that is used by the code
+generator.
 
 
 
@@ -290,77 +319,3 @@ underlying C compiler already does all the hard work for us. The problem is the
 common runtime library, especially the memory manager. Note that Borland's
 Delphi had exactly the same problem. The workaround is to not link the GC with
 the Dll and provide an extra runtime dll that needs to be initialized.
-
-
-
-How to implement closures
-=========================
-
-A closure is a record of a proc pointer and a context ref. The context ref
-points to a garbage collected record that contains the needed variables.
-An example:
-
-.. code-block:: Nimrod
-
-  type
-    TListRec = record
-      data: string
-      next: ref TListRec
-
-  proc forEach(head: ref TListRec, visitor: proc (s: string) {.closure.}) =
-    var it = head
-    while it != nil:
-      visit(it.data)
-      it = it.next
-
-  proc sayHello() =
-    var L = new List(["hallo", "Andreas"])
-    var temp = "jup\xff"
-    forEach(L, lambda(s: string) =
-                 io.write(temp)
-                 io.write(s)
-           )
-
-
-This should become the following in C:
-
-.. code-block:: C
-  typedef struct ... /* List type */
-
-  typedef struct closure {
-    void (*PrcPart)(string, void*);
-    void* ClPart;
-  }
-
-  typedef struct Tcl_data {
-    string temp; // all accessed variables are put in here!
-  }
-
-  void forEach(TListRec* head, const closure visitor) {
-    TListRec* it = head;
-    while (it != NIM_NULL) {
-      visitor.prc(it->data, visitor->cl_data);
-      it = it->next;
-    }
-  }
-
-  void printStr(string s, void* cl_data) {
-    Tcl_data* x = (Tcl_data*) cl_data;
-    io_write(x->temp);
-    io_write(s);
-  }
-
-  void sayhello() {
-    Tcl_data* data = new(...);
-    asgnRef(&data->temp, "jup\xff");
-    ...
-
-    closure cl;
-    cl.prc = printStr;
-    cl.cl_data = data;
-    foreach(L, cl);
-  }
-
-
-What about nested closure? - There's not much difference: Just put all used
-variables in the data record.
diff --git a/doc/manual.txt b/doc/manual.txt
index cd982302f..04b8bb97b 100644
--- a/doc/manual.txt
+++ b/doc/manual.txt
@@ -11,6 +11,10 @@ Nimrod Manual
 About this document
 ===================
 
+**Note**: This document is a draft! Several of Nimrod's features need more
+precise wording. This manual will evolve into a proper specification some
+day.
+
 This document describes the lexis, the syntax, and the semantics of Nimrod.
 
 The language constructs are explained using an extended BNF, in
@@ -18,10 +22,11 @@ which ``(a)*`` means 0 or more ``a``'s, ``a+`` means 1 or more ``a``'s, and
 ``(a)?`` means an optional *a*; an alternative spelling for optional parts is
 ``[a]``. The ``|`` symbol is used to mark alternatives
 and has the lowest precedence. Parentheses may be used to group elements.
-Non-terminals are in lowercase, terminal symbols (including keywords) are in
-UPPERCASE. An example::
+Non-terminals start with a lowercase letter, abstract terminal symbols are in
+UPPERCASE. Verbatim terminal symbols (including keywords) are quoted
+with ``'``. An example::
 
-  if_stmt ::= IF expr COLON stmts (ELIF expr COLON stmts)* [ELSE stmts]
+  ifStmt ::= 'if' expr ':' stmts ('elif' expr ':' stmts)* ['else' stmts]
 
 Other parts of Nimrod - like scoping rules or runtime semantics are only
 described in an informal manner. The reason is that formal semantics are
@@ -90,8 +95,7 @@ Indentation consists only of spaces; tabulators are not allowed.
 The terminals ``IND`` (indentation), ``DED`` (dedentation) and ``SAD``
 (same indentation) are generated by the scanner, denoting an indentation.
 
-These terminals are only generated for lines that are not empty or contain
-only whitespace and comments.
+These terminals are only generated for lines that are not empty.
 
 The parser and the scanner communicate over a stack which indentation terminal
 should be generated: The stack consists of integers counting the spaces. The
@@ -100,14 +104,17 @@ If the current indentation token consists of more spaces than the entry at the
 top of the stack, a ``IND`` token is generated, else if it consists of the same
 number of spaces, a ``SAD`` token is generated. If it consists of fewer spaces,
 a ``DED`` token is generated for any item on the stack that is greater than the
-current. These items are then popped from the stack by the scanner. At the end
+current. These items are later popped from the stack by the parser. At the end
 of the file, a ``DED`` token is generated for each number remaining on the
 stack that is larger than zero.
 
 Because the grammar contains some optional ``IND`` tokens, the scanner cannot
 push new indentation levels. This has to be done by the parser. The symbol
 ``indPush`` indicates that an ``IND`` token is expected; the current number of
-leading spaces is pushed onto the stack by the parser.
+leading spaces is pushed onto the stack by the parser. The symbol ``indPop``
+denotes that the parser pops an item from the indentation stack. No token is
+consumed by ``indPop``.
+
 
 Comments
 --------
@@ -131,8 +138,8 @@ aligned to the preceding one, it does not start a new comment:
 Comments are tokens; they are only allowed at certain places in the input file
 as they belong to the syntax tree! This feature enables perfect source-to-source
 transformations (such as pretty-printing) and superior documentation generators.
-A side-effect is that the human reader of the code always knows exactly which
-code snippet the comment refers to.
+A nice side-effect is that the human reader of the code always knows exactly
+which code snippet the comment refers to.
 
 
 Identifiers & Keywords
@@ -159,9 +166,9 @@ case-sensitive and even underscores are ignored:
 **type** is a reserved word, and so is **TYPE** or **T_Y_P_E**. The idea behind
 this is that this allows programmers to use their own prefered spelling style
 and libraries written by different programmers cannot use incompatible
-conventions. The editors or IDE can show the identifiers as preferred. Another
-advantage is that it frees the programmer from remembering the exact spelling
-of an identifier.
+conventions. A Nimrod-aware editor or IDE can show the identifiers as
+preferred. Another advantage is that it frees the programmer from remembering 
+the exact spelling of an identifier.
 
 
 Literal strings
@@ -174,7 +181,7 @@ contain the following `escape sequences`:idx:\ :
   Escape sequence          Meaning
 ==================         ===================================================
   ``\n``                   `newline`:idx:
-  ``\r``                   `carriage return`:idx:
+  ``\r``, ``\c``           `carriage return`:idx:
   ``\l``                   `line feed`:idx:
   ``\f``                   `form feed`:idx:
   ``\t``                   `tabulator`:idx:
@@ -184,8 +191,7 @@ contain the following `escape sequences`:idx:\ :
   ``\'``                   `apostrophe`:idx:
   ``\d+``                  `character with decimal value d`:idx:;
                            all decimal digits directly
-                           following are used for the
-                           character
+                           following are used for the character
   ``\a``                   `alert`:idx:
   ``\b``                   `backspace`:idx:
   ``\e``                   `escape`:idx: `[ESC]`:idx:
@@ -194,15 +200,14 @@ contain the following `escape sequences`:idx:\ :
 ==================         ===================================================
 
 
-Strings in Nimrod may contain any 8-bit value, except embedded zeros
-which are not allowed for compability with `C`:idx:.
+Strings in Nimrod may contain any 8-bit value, except embedded zeros.
 
 Literal strings can also be delimited by three double squotes
 ``"""`` ... ``"""``.
 Literals in this form may run for several lines, may contain ``"`` and do not
 interpret any escape sequences.
-For convenience, when the opening ``"""`` is immediately
-followed by a newline, the newline is not included in the string.
+For convenience, when the opening ``"""`` is immediately followed by a newline, 
+the newline is not included in the string.
 There are also `raw string literals` that are preceded with the letter ``r``
 (or ``R``) and are delimited by matching double quotes (just like ordinary
 string literals) and do not interpret the escape sequences. This is especially
@@ -253,8 +258,8 @@ Numerical constants
 
 As can be seen in the productions, numerical constants can contain unterscores
 for readability. Integer and floating point literals may be given in decimal (no
-prefix), binary (prefix ``0b``), octal (prefix ``0o``) and
-hexadecimal (prefix ``0x``) notation.
+prefix), binary (prefix ``0b``), octal (prefix ``0o``) and hexadecimal 
+(prefix ``0x``) notation.
 
 There exists a literal for each numerical type that is
 defined. The suffix starting with an apostophe ('\'') is called a
@@ -262,7 +267,7 @@ defined. The suffix starting with an apostophe ('\'') is called a
 unless the literal contains a dot or an ``E`` in which case it is of
 type ``float``.
 
-The following table specifies type suffixes:
+The type suffixes are:
 
 =================    =========================
   Type Suffix        Resulting type of literal
@@ -295,11 +300,11 @@ the three tokens `{`:tok:, `..`:tok:, `}`:tok: and not the two tokens
 `{.`:tok:, `.}`:tok:.
 
 In Nimrod one can define his own operators. An `operator`:idx: is any
-combination of the following characters that are not listed above::
+combination of the following characters that is not listed above::
 
        +     -     *     /     <     >
        =     @     $     ~     &     %
-       !     ?     ^     .     |
+       !     ?     ^     .     |     \
 
 These keywords are also operators:
 ``and or not xor shl shr div mod in notin is isnot``.
@@ -348,16 +353,13 @@ Constants
 cannot change. The compiler must be able to evaluate the expression in a
 constant declaration at compile time.
 
-..
-  Nimrod contains a sophisticated
-  compile-time evaluator, so procedures declared with the ``{.noSideEffect.}``
-  pragma can be used in constant expressions:
-
-  .. code-block:: nimrod
+Nimrod contains a sophisticated compile-time evaluator, so procedures which
+have no side-effect can be used in constant expressions too:
 
-    from strutils import findSubStr
-    const
-      x = findSubStr('a', "hallo") # x is 1; this is computed at compile time!
+.. code-block:: nimrod
+  import strutils
+  const 
+    constEval = contains("abc", 'b') # computed at compile time!
 
 
 Types
@@ -414,8 +416,8 @@ intXX
 
 There are no `unsigned integer`:idx: types, only `unsigned operations`:idx:
 that treat their arguments as unsigned. Unsigned operations all wrap around;
-they may not lead to over- or underflow errors. Unsigned operations use the
-``%`` postfix as convention:
+they cannot lead to over- or underflow errors. Unsigned operations use the
+``%`` suffix as convention:
 
 ======================   ======================================================
 operation                meaning
@@ -453,7 +455,7 @@ floatXX
   implementation supports ``float32`` and ``float64``. Literals of these types
   have the suffix 'fXX.
 
-`Automatic type conversion`:idx: is performed in expressions where different 
+`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).
@@ -498,16 +500,15 @@ the resulting programs will still handle UTF-8 properly as UTF-8 was specially
 designed for this.
 Another reason is that Nimrod can support ``array[char, int]`` or
 ``set[char]`` efficiently as many algorithms rely on this feature. The
-`TUniChar` type is used for Unicode characters, it can represent any Unicode
-character. ``TUniChar`` is declared the ``unicode`` standard module.
+`TRune` type is used for Unicode characters, it can represent any Unicode
+character. ``TRune`` is declared the ``unicode`` module.
 
 
 
 Enumeration types
 ~~~~~~~~~~~~~~~~~
-`Enumeration`:idx: types define a new type whose values consist only of the ones
-specified.
-The values are ordered by the order in enum's declaration. Example:
+`Enumeration`:idx: types define a new type whose values consist of the ones
+specified. The values are ordered. Example:
 
 .. code-block:: nimrod
 
@@ -528,8 +529,8 @@ with enumeration types.
 
 For better interfacing to other programming languages, the fields of enum
 types can be assigned an explicit ordinal value. However, the ordinal values
-have to be in ascending order. A field whose ordinal value that is not
-explicitly given, is assigned the value of the previous field + 1.
+have to be in ascending order. A field whose ordinal value is not
+explicitly given is assigned the value of the previous field + 1.
 
 An explicit ordered enum can have *wholes*:
 
@@ -545,7 +546,7 @@ and ``pred`` are not available for them either.
 
 Subrange types
 ~~~~~~~~~~~~~~
-A `subrange`:idx: type is a range of values from an ordinal type (the host
+A `subrange`:idx: type is a range of values from an ordinal type (the base
 type). To define a subrange type, one must specify it's limiting values: the
 highest and lowest value of the type:
 
@@ -566,7 +567,7 @@ A subrange type has the same size as its base type (``int`` in the example).
 String type
 ~~~~~~~~~~~
 All string literals are of the type `string`:idx:. A string in Nimrod is very
-similar to a sequence of characters. However, strings in Nimrod both are
+similar to a sequence of characters. However, strings in Nimrod are both
 zero-terminated and have a length field. One can retrieve the length with the
 builtin ``len`` procedure; the length never counts the terminating zero.
 The assignment operator for strings always copies the string.
@@ -585,7 +586,7 @@ arrays, they can be used in case statements:
 Per convention, all strings are UTF-8 strings, but this is not enforced. For
 example, when reading strings from binary files, they are merely a sequence of
 bytes. The index operation ``s[i]`` means the i-th *char* of ``s``, not the
-i-th *unichar*. The iterator ``unichars`` from the ``unicode`` standard
+i-th *unichar*. The iterator ``runes`` from the ``unicode``
 module can be used for iteration over all unicode characters.
 
 
@@ -611,9 +612,7 @@ constructed by the array constructor ``[]`` in conjunction with the array to
 sequence operator ``@``. Another way to allocate space for a sequence is to
 call the built-in ``newSeq`` procedure.
 
-A sequence may be passed to a parameter that is of type *open array*, but
-not to a multi-dimensional open array, because it is impossible to do so in an
-efficient manner.
+A sequence may be passed to a parameter that is of type *open array*.
 
 Example:
 
@@ -633,18 +632,36 @@ 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``. 
+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.
 
+An open array is  also a means to implement passing a variable number of
+arguments to a procedure. The compiler converts the list of arguments
+to an array automatically:
+
+.. code-block:: nimrod
+  proc myWriteln(f: TFile, a: openarray[string]) =
+    for s in items(a):
+      write(f, s)
+    write(f, "\n")
+
+  myWriteln(stdout, "abc", "def", "xyz")
+  # is transformed by the compiler to:
+  myWriteln(stdout, ["abc", "def", "xyz"])
+
+This transformation is only done if the openarray parameter is the
+last parameter in the procedure header. The current implementation does not
+support nested open arrays.
+
 
 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 also 
+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
@@ -691,7 +708,7 @@ the ``is`` operator can be used to determine the object's type.
     person: TPerson
   assert(student is TStudent) # is true
 
-Object fields that should be visible outside from the defining module, have to
+Object fields that should be visible from outside the defining module, have to
 marked by ``*``. In contrast to tuples, different object types are
 never *equivalent*.
 
@@ -730,7 +747,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 = ""
@@ -783,8 +800,8 @@ point to and modify the same location in memory.
 
 Nimrod distinguishes between `traced`:idx: and `untraced`:idx: references.
 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 
+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.
 
@@ -817,7 +834,7 @@ 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``. 
+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,
@@ -904,9 +921,9 @@ Most calling conventions exist only for the Windows 32-bit platform.
 
 
 
-Statements
-----------
-Nimrod uses the common statement/expression paradigma: `Statements`:idx: do not
+Statements and expressions
+--------------------------
+Nimrod uses the common statement/expression paradigm: `Statements`:idx: do not
 produce a value in contrast to expressions. Call expressions are statements.
 If the called procedure returns a value, it is not a valid statement
 as statements do not produce values. To evaluate an expression for
@@ -943,7 +960,7 @@ Discard statement
 
 Syntax::
 
-  discardStmt ::= DISCARD expr
+  discardStmt ::= 'discard' expr
 
 Example:
 
@@ -962,11 +979,13 @@ Var statement
 
 Syntax::
 
-  colonOrEquals ::= COLON typeDesc [EQUALS expr] | EQUALS expr
-  varField ::= symbol ["*"] [pragma]
+  colonOrEquals ::= ':' typeDesc ['=' expr] | '=' expr
+  varField ::= symbol ['*'] [pragma]
   varPart ::= symbol (comma symbol)* [comma] colonOrEquals [COMMENT | IND COMMENT]
-  varSection ::= VAR (varPart
-                     | indPush (COMMENT|varPart) (SAD (COMMENT|varPart))* DED)
+  varSection ::= 'var' (varPart
+                     | indPush (COMMENT|varPart)
+                       (SAD (COMMENT|varPart))* DED indPop)
+
 
 `Var`:idx: statements declare new local and global variables and
 initialize them. A comma seperated list of variables can be used to specify
@@ -992,7 +1011,7 @@ char                            '\0'
 bool                            false
 ref or pointer type             nil
 procedural type                 nil
-sequence                        nil
+sequence                        nil (**not** ``@[]``)
 string                          nil (**not** "")
 tuple[x: A, y: B, ...]          (default(A), default(B), ...)
                                 (analogous for objects)
@@ -1007,12 +1026,12 @@ Const section
 
 Syntax::
 
-  colonAndEquals ::= [COLON typeDesc] EQUALS expr
-  constDecl ::= CONST
-           indPush
-                symbol ["*"] [pragma] colonAndEquals
-           (SAD symbol ["*"] [pragma] colonAndEquals)*
-           DED
+  colonAndEquals ::= [':' typeDesc] '=' expr
+
+  constDecl ::= symbol ['*'] [pragma] colonAndEquals [COMMENT | IND COMMENT]
+              | COMMENT
+  constSection ::= 'const' indPush constDecl (SAD constDecl)* DED indPop
+
 
 Example:
 
@@ -1031,7 +1050,7 @@ If statement
 
 Syntax::
 
-  ifStmt ::= IF expr COLON stmt (ELIF expr COLON stmt)* [ELSE COLON stmt]
+  ifStmt ::= 'if' expr ':' stmt ('elif' expr ':' stmt)* ['else' ':' stmt]
 
 Example:
 
@@ -1061,9 +1080,9 @@ Case statement
 
 Syntax::
 
-  caseStmt ::= CASE expr (OF sliceList COLON stmt)*
-                         (ELIF expr COLON stmt)*
-                         [ELSE COLON stmt]
+  caseStmt ::= 'case' expr ('of' sliceExprList ':' stmt)*
+                           ('elif' expr ':' stmt)*
+                           ['else' ':' stmt]
 
 Example:
 
@@ -1078,9 +1097,9 @@ Example:
 The `case`:idx: statement is similar to the if statement, but it represents
 a multi-branch selection. The expression after the keyword ``case`` is
 evaluated and if its value is in a *vallist* the corresponding statements
-(after the ``of`` keyword) are executed. If the value is not in any 
-given *slicelist* the ``else`` part is executed. If there is no ``else`` 
-part and not all possible values that ``expr`` can hold occur in a ``vallist``, 
+(after the ``of`` keyword) are executed. If the value is not in any
+given *slicelist* the ``else`` part is executed. If there is no ``else``
+part and not all possible values that ``expr`` can hold occur in a ``vallist``,
 a static error is given. This holds only for expressions of ordinal types.
 If the expression is not of an ordinal type, and no ``else`` part is
 given, control just passes after the ``case`` statement.
@@ -1094,7 +1113,7 @@ When statement
 
 Syntax::
 
-  whenStmt ::= WHEN expr COLON stmt (ELIF expr COLON stmt)* [ELSE COLON stmt]
+  whenStmt ::= 'when' expr ':' stmt ('elif' expr ':' stmt)* ['else' ':' stmt]
 
 Example:
 
@@ -1116,8 +1135,7 @@ exceptions:
 * The statements do not open a new scope if they introduce new identifiers.
 * The statements that belong to the expression that evaluated to true are
   translated by the compiler, the other statements are not checked for
-  syntax or semantics at all! This holds also for any ``expr`` coming
-  after the expression that evaluated to true.
+  semantics! However, each ``expr`` is checked for semantics.
 
 The ``when`` statement enables conditional compilation techniques. As
 a special syntatic extension, the ``when`` construct is also available
@@ -1129,7 +1147,7 @@ Raise statement
 
 Syntax::
 
-  raiseStmt ::= RAISE [expr]
+  raiseStmt ::= 'raise' [expr]
 
 Example:
 
@@ -1137,7 +1155,7 @@ Example:
   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 ``raise`` statement is the only way to raise an exception.
 
 .. XXX document this better!
 
@@ -1152,11 +1170,11 @@ Try statement
 
 Syntax::
 
+  qualifiedIdent ::= symbol ['.' symbol]
   exceptList ::= [qualifiedIdent (comma qualifiedIdent)* [comma]]
-  tryStmt ::= TRY COLON stmt
-            (EXCEPT exceptList COLON stmt)*
-            [FINALLY COLON stmt]
-             
+  tryStmt ::= 'try' ':' stmt
+             ('except' exceptList ':' stmt)*
+             ['finally' ':' stmt]
 
 Example:
 
@@ -1176,6 +1194,8 @@ Example:
       echo("could not convert string to integer")
     except EIO:
       echo("IO error!")
+    except:
+      echo("Unknown exception!")
     finally:
       closeFile(f)
 
@@ -1203,7 +1223,7 @@ Return statement
 
 Syntax::
 
-  returnStmt ::= RETURN [expr]
+  returnStmt ::= 'return' [expr]
 
 Example:
 
@@ -1219,12 +1239,13 @@ sugar for:
   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 
+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::
 
 .. code-block:: nimrod
-    proc returnZero(): int = nil # implicitely returns 0
+    proc returnZero(): int =
+      # implicitely returns 0
 
 
 Yield statement
@@ -1232,7 +1253,7 @@ Yield statement
 
 Syntax::
 
-  yieldStmt ::= YIELD expr
+  yieldStmt ::= 'yield' expr
 
 Example:
 
@@ -1252,7 +1273,7 @@ Block statement
 
 Syntax::
 
-  blockStmt ::= BLOCK [symbol] COLON stmt
+  blockStmt ::= 'block' [symbol] ':' stmt
 
 Example:
 
@@ -1277,7 +1298,7 @@ Break statement
 
 Syntax::
 
-  breakStmt ::= BREAK [symbol]
+  breakStmt ::= 'break' [symbol]
 
 Example:
 
@@ -1294,7 +1315,7 @@ While statement
 
 Syntax::
 
-  whileStmt ::= WHILE expr COLON stmt
+  whileStmt ::= 'while' expr ':' stmt
 
 Example:
 
@@ -1316,7 +1337,7 @@ Continue statement
 
 Syntax::
 
-  continueStmt ::= CONTINUE
+  continueStmt ::= 'continue'
 
 A `continue`:idx: statement leads to the immediate next iteration of the
 surrounding loop construct. It is only allowed within a loop. A continue
@@ -1340,7 +1361,7 @@ Assembler statement
 ~~~~~~~~~~~~~~~~~~~
 Syntax::
 
-  asmStmt ::= ASM [pragma] (STR_LIT | RSTR_LIT | TRIPLESTR_LIT)
+  asmStmt ::= 'asm' [pragma] (STR_LIT | RSTR_LIT | TRIPLESTR_LIT)
 
 The direct embedding of `assembler`:idx: code into Nimrod code is supported
 by the unsafe ``asm`` statement. Identifiers in the assembler code that refer to
@@ -1348,6 +1369,49 @@ Nimrod identifiers shall be enclosed in a special character which can be
 specified in the statement's pragmas. The default special character is ``'`'``.
 
 
+If expression
+~~~~~~~~~~~~~
+
+An `if expression` is almost like an if statement, but it is an expression.
+Example:
+
+.. code-block:: nimrod
+  p(if x > 8: 9 else: 10)
+
+An if expression always results in a value, so the ``else`` part is
+required. ``Elif`` parts are also allowed (but unlikely to be good
+style).
+
+
+Type convertions
+~~~~~~~~~~~~~~~~
+Syntactically a `type conversion` is like a procedure call, but a
+type name replaces the procedure name. A type conversion is always
+safe in the sense that a failure to convert a type to another
+results in an exception (if it cannot be determined statically).
+
+
+Type casts
+~~~~~~~~~~
+Example:
+
+.. code-block:: nimrod
+  cast[int](x)
+
+Type casts are a crude mechanism to interpret the bit pattern of
+an expression as if it would be of another type. Type casts are
+only needed for low-level programming and are inherently unsafe.
+
+
+The addr operator
+~~~~~~~~~~~~~~~~~
+The `addr` operator returns the address of an l-value. If the
+type of the location is ``T``, the `addr` operator result is
+of the type ``ptr T``. Taking the address of an object that resides
+on the stack is **unsafe**, as the pointer may live longer than the
+object on the stack and can thus reference a non-existing object.
+
+
 Procedures
 ~~~~~~~~~~
 What most programming languages call `methods`:idx: or `funtions`:idx: are
@@ -1355,16 +1419,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::
 
-  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]
-               [EQUALS stmt]
-               
-If the ``EQUALS stmt`` part is missing, it is a `forward`:idx: declaration. If
+  param ::= symbol (comma symbol)* [comma] ':' typeDesc
+  paramList ::= ['(' [param (comma param)* [comma]] ')'] [':' typeDesc]
+
+  genericParam ::= symbol [':' typeDesc]
+  genericParams ::= '[' genericParam (comma genericParam)* [comma] ']'
+
+  procDecl ::= 'proc' symbol ['*'] [genericParams] paramList [pragma]
+               ['=' stmt]
+
+If the ``= 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
@@ -1384,6 +1448,24 @@ is used if the caller does not provide a value for this parameter. Example:
     for i in 0..len(s) - 1:
       result[i] = toLower(s[i]) # calls toLower for characters; no recursion!
 
+Calling a procedure can be done in many different ways:
+
+.. code-block:: nimrod
+  proc callme(x, y: int, s: string = "", c: char, b: bool = false) = ...
+
+  # call with positional arguments # parameter bindings:
+  callme(0, 1, "abc", '\t', true)  # (x=0, y=1, s="abc", c='\t', b=true)
+  # call with named and positional arguments:
+  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 () needed:
+  callme 0, 1, "abc", '\t'
+
+
+A procedure cannot modify its parameters (unless the parameters have the
+type `var`).
+
 `Operators`:idx: are procedures with a special operator symbol as identifier:
 
 .. code-block:: nimrod
@@ -1391,19 +1473,79 @@ is used if the caller does not provide a value for this parameter. Example:
     # converts an integer to a string; this is a prefix operator.
     return intToStr(x)
 
-Calling a procedure can be done in many different ways:
+Operators with one parameter are prefix operators, operators with two
+parameters are infix operators. There is no way to declare postfix
+operators: All postfix operators are built-in and handled by the
+grammar explicitely.
+
+Any operator can be called like an ordinary proc with the '`opr`'
+notation. (Thus an operator can have more than two parameters):
 
 .. code-block:: nimrod
-  proc callme(x, y: int, s: string = "", c: char, b: bool = false) = ...
+  proc `*+` (a, b, c: int): int =
+    # Multiply and add
+    return a * b + c
+
+  assert `*+`(3, 4, 6) == `*`(a, `+`(b, c))
+
+
+
+Var parameters
+~~~~~~~~~~~~~~
+The type of a parameter may be prefixed with the ``var`` keyword:
+
+.. code-block:: nimrod
+  proc divmod(a, b: int, res, remainder: var int) =
+    res = a div b
+    remainder = a mod b
+
+  var
+    x, y: int
+
+  divmod(8, 5, x, y) # modifies x and y
+  assert x == 1
+  assert y == 3
+
+In the example, ``res`` and ``remainder`` are `var parameters`.
+Var parameters can be modified by the procedure and the changes are
+visible to the caller. The argument passed to a var parameter has to be
+an l-value. Var parameters are implemented as hidden pointers. The
+above example is equivalent to:
+
+.. code-block:: nimrod
+  proc divmod(a, b: int, res, remainder: ptr int) =
+    res = a div b
+    remainder = a mod b
+
+  var
+    x, y: int
+  divmod(8, 5, addr(x), addr(y))
+  assert x == 1
+  assert y == 3
+
+In the examples, var parameters or pointers are used to provide two
+return values. This can be done in a cleaner way by returning a tuple:
+
+.. code-block:: nimrod
+  proc divmod(a, b: int): tuple[res, remainder: int] =
+    return (a div b, a mod b)
+
+  var t = divmod(8, 5)
+  assert t.res == 1
+  assert t.remainder = 3
+
+Even more elegant is to use `tuple unpacking` to access the tuple's fields:
+
+.. code-block:: nimrod
+  var (x, y) = divmod(8, 5) # tuple unpacking
+  assert x == 1
+  assert y == 3
+
+Unfortunately, this form of tuple unpacking is not yet implemented.
+
+..
+  XXX remove this as soon as tuple unpacking is implemented
 
-  # call with positional arguments# parameter bindings:
-  callme(0, 1, "abc", '\t', true) # (x=0, y=1, s="abc", c='\t', b=true)
-  # call with named and positional arguments:
-  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 () needed:
-  callme 0, 1, "abc", '\t'
 
 
 Iterators and the for statement
@@ -1411,15 +1553,16 @@ Iterators and the for statement
 
 Syntax::
 
-  forStmt ::= FOR symbol (comma symbol)* [comma] IN expr [DOTDOT expr] COLON stmt
+  forStmt ::= 'for' symbol (comma symbol)* [comma] 'in' expr ['..' expr] ':' stmt
 
-  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]
+  param ::= symbol (comma symbol)* [comma] ':' typeDesc
+  paramList ::= ['(' [param (comma param)* [comma]] ')'] [':' typeDesc]
+
+  genericParam ::= symbol [':' typeDesc]
+  genericParams ::= '[' genericParam (comma genericParam)* [comma] ']'
+
+  iteratorDecl ::= 'iterator' symbol ['*'] [genericParams] paramList [pragma]
+               ['=' stmt]
 
 The `for`:idx: statement is an abstract mechanism to iterate over the elements
 of a container. It relies on an `iterator`:idx: to do so. Like ``while``
@@ -1473,13 +1616,15 @@ Type sections
 Syntax::
 
   typeDef ::= typeDesc | objectDef | enumDef
-  genericParams ::= BRACKET_LE (symbol [EQUALS typeDesc] )* BRACKET_RI
 
-  typeDecl ::= TYPE
-           indPush
-                symbol ["*"] [genericParams] [EQUALS typeDef]
-           (SAD symbol ["*"] [genericParams] [EQUALS typeDef])*
-           DED
+  genericParam ::= symbol [':' typeDesc]
+  genericParams ::= '[' genericParam (comma genericParam)* [comma] ']'
+
+  typeDecl ::= COMMENT
+             | symbol ['*'] [genericParams] ['=' typeDef] [COMMENT|IND COMMENT]
+
+  typeSection ::= 'type' indPush typeDecl (SAD typeDecl)* DED indPop
+
 
 Example:
 
@@ -1504,6 +1649,8 @@ possible within a single ``type`` section.
 Generics
 ~~~~~~~~
 
+`Version 0.7.4: Complex generic types like in the example do not work.`:red:
+
 Example:
 
 .. code-block:: nimrod
@@ -1578,26 +1725,119 @@ Example:
     # this definition exists in the System module
     not (a == b)
 
-  writeln(5 != 6) # the compiler rewrites that to: writeln(not (5 == 6))
+  assert(5 != 6) # the compiler rewrites that to: assert(not (5 == 6))
 
 
 Macros
-~~~~~~
+------
 
-`Macros`:idx: are the most powerful feature of Nimrod. They should be used
-only to implement `domain specific languages`:idx:. They may lead to code
+`Macros`:idx: are the most powerful feature of Nimrod. They can be used
+to implement `domain specific languages`:idx:. But they may lead to code
 that is harder to understand and maintain. So one ought to use them sparingly.
-The usage of ordinary procs, iterators or generics is preferred to the usage of
-macros.
+
+While macros enable advanced compile-time code tranformations, they
+cannot change Nimrod's syntax. However, this is no real restriction because
+Nimrod's syntax is flexible enough anyway.
+
+To write macros, one needs to know how the Nimrod concrete syntax is converted
+to an abstract syntax tree. (Unfortunately the AST is not yet documented.)
+
+There are two ways to invoke a macro:
+(1) invoking a macro like a procedure call (`expression macros`)
+(2) invoking a macro with the special ``macrostmt`` syntax (`statement macros`)
+
+
+Expression Macros
+~~~~~~~~~~~~~~~~~
+
+The following example implements a powerful ``debug`` command that accepts a
+variable number of arguments:
+
+.. code-block:: nimrod
+  # to work with Nimrod syntax trees, we need an API that is defined in the
+  # ``macros`` module:
+  import macros
+
+  macro debug(n: expr): stmt =
+    # `n` is a Nimrod AST that contains the whole macro expression
+    # this macro returns a list of statements:
+    result = newNimNode(nnkStmtList, n)
+    # iterate over any argument that is passed to this macro:
+    for i in 1..n.len-1:
+      # add a call to the statement list that writes the expression;
+      # `toStrLit` converts an AST to its string representation:
+      add(result, newCall("write", newIdentNode("stdout"), toStrLit(n[i])))
+      # add a call to the statement list that writes ": "
+      add(result, newCall("write", newIdentNode("stdout"), newStrLitNode(": ")))
+      # add a call to the statement list that writes the expressions value:
+      add(result, newCall("writeln", newIdentNode("stdout"), n[i]))
+
+  var
+    a: array [0..10, int]
+    x = "some string"
+  a[0] = 42
+  a[1] = 45
+
+  debug(a[0], a[1], x)
+
+The macro call expands to:
+
+.. code-block:: nimrod
+  write(stdout, "a[0]")
+  write(stdout, ": ")
+  writeln(stdout, a[0])
+
+  write(stdout, "a[1]")
+  write(stdout, ": ")
+  writeln(stdout, a[1])
+
+  write(stdout, "x")
+  write(stdout, ": ")
+  writeln(stdout, x)
+
+
+Statement Macros
+~~~~~~~~~~~~~~~~
+
+Statement macros are defined just as expression macros. However, they are
+invoked by an expression following a colon::
+
+  exprStmt ::= lowestExpr ['=' expr | [expr (comma expr)* [comma]] [macroStmt]]
+  macroStmt ::= ':' [stmt] ('of' [sliceExprList] ':' stmt
+                          | 'elif' expr ':' stmt
+                          | 'except' exceptList ':' stmt )*
+                           ['else' ':' stmt]
+
+The following example outlines a macro that generates a lexical analyser from
+regular expressions:
+
+.. code-block:: nimrod
+  import macros
+
+  macro case_token(n: stmt): stmt =
+    # creates a lexical analyser from regular expressions
+    # ... (implementation is an exercise for the reader :-)
+    nil
+
+  case_token: # this colon tells the parser it is a macro statement
+  of r"[A-Za-z_]+[A-Za-z_0-9]*":
+    return tkIdentifier
+  of r"0-9+":
+    return tkInteger
+  of r"[\+\-\*\?]+":
+    return tkOperator
+  else:
+    return tkUnknown
+
 
 
 Modules
 -------
 Nimrod supports splitting a program into pieces by a `module`:idx: concept.
-Each module needs to be in its own file. Modules enable 
+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 
+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:
@@ -1622,12 +1862,12 @@ This is best illustrated by an example:
 
   # Module B
   import A  # A is not parsed here! Only the already known symbols
-            # of A are imported here.
+            # of A are imported.
 
-  proc p*(x: A.T1): A.T1 # this works because the compiler has already
-                         # added T1 to A's interface symbol table
-
-  proc p(x: A.T1): A.T1 = return x + 1
+  proc p*(x: A.T1): A.T1 =
+    # this works because the compiler has already
+    # added T1 to A's interface symbol table
+    return x + 1
 
 
 Scope rules
@@ -1649,7 +1889,7 @@ procedure or iterator overloading purposes.
 
 
 Tuple or object scope
-~~~~~~~~~~~~~~~~~~~~~~
+~~~~~~~~~~~~~~~~~~~~~
 The field identifiers inside a tuple or object definition are valid in the
 following places:
 
@@ -1659,16 +1899,14 @@ following places:
 
 Module scope
 ~~~~~~~~~~~~
-All identifiers in the interface part of a module are valid from the point of
-declaration, until the end of the module. Furthermore, the identifiers are
-known in other modules that import the module. Identifiers from indirectly
-dependent modules are *not* available. The `system`:idx: module is automatically
-imported in all other modules.
+All identifiers of a module are valid from the point of declaration until
+the end of the module. Identifiers from indirectly dependent modules are *not* 
+available. The `system`:idx: module is automatically imported in every other 
+module.
 
-If a module imports an identifier by two different modules,
-each occurance of the identifier has to be qualified, unless it is an
-overloaded procedure or iterator in which case the overloading
-resolution takes place:
+If a module imports an identifier by two different modules, each occurance of 
+the identifier has to be qualified, unless it is an overloaded procedure or 
+iterator in which case the overloading resolution takes place:
 
 .. code-block:: nimrod
   # Module A
@@ -1680,7 +1918,7 @@ resolution takes place:
   # Module C
   import A, B
   write(stdout, x) # error: x is ambigious
-  write(sdtout, A.x) # no error: qualifier used
+  write(stdout, A.x) # no error: qualifier used
 
   var x = 4
   write(stdout, x) # not ambigious: uses the module C's x
@@ -1698,14 +1936,14 @@ Pragmas
 
 Syntax::
 
-  colonExpr ::= expr [COLON expr]
-  colonExprList ::= [ colonExpr (comma colonExpr)* [comma] ]
+  colonExpr ::= expr [':' expr]
+  colonExprList ::= [colonExpr (comma colonExpr)* [comma]]
 
-  pragma ::= CURLYDOT_LE colonExprList (CURLYDOT_RI | CURLY_RI)
+  pragma ::= '{.' optInd (colonExpr [comma])* [SAD] ('.}' | '}')
 
 Pragmas are Nimrod's method to give the compiler additional information/
 commands without introducing a massive number of new keywords. Pragmas are
-processed on the fly during parsing. Pragmas are always enclosed in the
+processed on the fly during semantic checking. Pragmas are enclosed in the
 special ``{.`` and ``.}`` curly brackets.
 
 
@@ -1718,7 +1956,7 @@ The compiler defines the target processor and the target operating
 system as conditional symbols.
 
 Warning: The ``define`` pragma is deprecated as it conflicts with separate
-compilation! One should use boolean constants as a replacement - this is 
+compilation! One should use boolean constants as a replacement - this is
 cleaner anyway.
 
 
@@ -1759,10 +1997,6 @@ compilation option pragmas
 --------------------------
 The listed pragmas here can be used to override the code generation options
 for a section of code.
-::
-
-  "{." pragma: val {pragma: val} ".}"
-
 
 The implementation currently provides the following possible options (later
 various others may be added).
@@ -1785,8 +2019,7 @@ warnings         on|off           Turns the warning messages of the compiler
 hints            on|off           Turns the hint messages of the compiler
                                   on or off.
 optimization     none|speed|size  Optimize the code for speed or size, or
-                                  disable optimization. For non-optimizing
-                                  compilers this option has no effect.
+                                  disable optimization.
 callconv         cdecl|...        Specifies the default calling convention for
                                   all procedures (and procedure types) that
                                   follow.
diff --git a/doc/nimrodc.txt b/doc/nimrodc.txt
index 0bd9bdc91..18f9bce5d 100644
--- a/doc/nimrodc.txt
+++ b/doc/nimrodc.txt
@@ -12,7 +12,7 @@ Introduction
 
 This document describes the usage of the *Nimrod compiler*
 on the different supported platforms. It is not a definition of the Nimrod
-programming system (therefore is the Nimrod manual).
+programming language (therefore is the manual).
 
 Nimrod is free software; it is licensed under the
 `GNU General Public License <gpl.html>`_.
@@ -41,7 +41,7 @@ looks for it in the following directories (in this order):
 2. ``$nimrod/config/nimrod.cfg`` (UNIX, Windows)
 3. ``/etc/nimrod.cfg`` (UNIX)
 
-The search stops as soon as a configuration file has been found. The reading 
+The search stops as soon as a configuration file has been found. The reading
 of ``nimrod.cfg`` can be suppressed by the ``--skip_cfg`` command line option.
 Configuration settings can be overwritten in a project specific
 configuration file that is read automatically. This specific file has to
@@ -54,21 +54,13 @@ Command line settings have priority over configuration file settings.
 Nimrod's directory structure
 ----------------------------
 The generated files that Nimrod produces all go into a subdirectory called
-``nimcache`` in your project directory. This makes it easy to delete all 
+``nimcache`` in your project directory. This makes it easy to delete all
 generated files.
 
 However, the generated C code is not platform independant. C code generated for
 Linux does not compile on Windows, for instance. The comment on top of the
 C file lists the OS, CPU and CC the file has been compiled for.
 
-The library lies in ``lib``. Directly in the library directory are essential
-Nimrod modules like the ``system`` and ``os`` modules. Under ``lib/base``
-are additional specialized libraries or interfaces to foreign libraries which
-are included in the standard distribution. The ``lib/extra`` directory is
-initially empty. Third party libraries should go there. In the default
-configuration the compiler always searches for libraries in ``lib``,
-``lib/base`` and ``lib/extra``.
-
 
 Additional Features
 ===================
@@ -86,8 +78,8 @@ available.
 Importc Pragma
 ~~~~~~~~~~~~~~
 The `importc`:idx: pragma provides a means to import a type, a variable, or a
-procedure from C. The optional argument is a string containing the C 
-identifier. If the argument is missing, the C name is the Nimrod 
+procedure from C. The optional argument is a string containing the C
+identifier. If the argument is missing, the C name is the Nimrod
 identifier *exactly as spelled*:
 
 .. code-block::
@@ -97,8 +89,8 @@ identifier *exactly as spelled*:
 Exportc Pragma
 ~~~~~~~~~~~~~~
 The `exportc`:idx: pragma provides a means to export a type, a variable, or a
-procedure to C. The optional argument is a string containing the C 
-identifier. If the argument is missing, the C name is the Nimrod 
+procedure to C. The optional argument is a string containing the C
+identifier. If the argument is missing, the C name is the Nimrod
 identifier *exactly as spelled*:
 
 .. code-block:: Nimrod
@@ -109,7 +101,7 @@ Dynlib Pragma
 ~~~~~~~~~~~~~
 With the `dynlib`:idx: pragma a procedure or a variable can be imported from
 a dynamic library (``.dll`` files for Windows, ``lib*.so`` files for UNIX). The
-non-optional argument has to be the name of the dynamic library: 
+non-optional argument has to be the name of the dynamic library:
 
 .. code-block:: Nimrod
   proc gtk_image_new(): PGtkWidget {.cdecl, dynlib: "libgtk-x11-2.0.so", importc.}
@@ -128,8 +120,8 @@ the C code. Thus it makes the following possible, for example:
 
 .. code-block:: Nimrod
   var
-    EOF {.importc: "EOF", no_decl.}: cint # pretend EOF was a variable, as
-                                          # Nimrod does not know its value
+    EACCES {.importc, no_decl.}: cint # pretend EACCES was a variable, as
+                                      # Nimrod does not know its value
 
 However, the ``header`` pragma is often the better alternative.
 
@@ -164,14 +156,6 @@ strings automatically:
   printf("hallo %s", "world") # "world" will be passed as C string
 
 
-No_static Pragma
-~~~~~~~~~~~~~~~~
-The `no_static`:idx: pragma can be applied to almost any symbol and specifies
-that it shall not be declared ``static`` in the generated C code. Note that
-symbols in the interface part of a module never get declared ``static``, so
-only in very special cases this pragma is necessary.
-
-
 Line_dir Option
 ~~~~~~~~~~~~~~~
 The `line_dir`:idx: option can be turned on or off. If on the generated C code
@@ -216,14 +200,14 @@ The `register`:idx: pragma is for variables only. It declares the variable as
 in a hardware register for faster access. C compilers usually ignore this
 though and for good reason: Often they do a better job without it anyway.
 
-In highly specific cases (a dispatch loop of an bytecode interpreter for 
+In highly specific cases (a dispatch loop of an bytecode interpreter for
 example) it may provide benefits, though.
 
 
 Acyclic Pragma
 ~~~~~~~~~~~~~~
 The `acyclic`:idx: pragma can be used for object types to mark them as acyclic
-even though they seem to be cyclic. This is an **optimization** for the garbage 
+even though they seem to be cyclic. This is an **optimization** for the garbage
 collector to not consider objects of this type as part of a cycle::
 
   type
@@ -231,15 +215,31 @@ collector to not consider objects of this type as part of a cycle::
     TNode {.acyclic, final.} = object
       left, right: PNode
       data: string
-      
+
 In the example a tree structure is declared with the ``TNode`` type. Note that
-the type definition is recursive thus the GC has to assume that objects of 
-this type may form a cyclic graph. The ``acyclic`` pragma passes the 
+the type definition is recursive thus the GC has to assume that objects of
+this type may form a cyclic graph. The ``acyclic`` pragma passes the
 information that this cannot happen to the GC. If the programmer uses the
 ``acyclic`` pragma for data types that are in reality cyclic, the GC may leak
 memory, but nothing worse happens.
 
 
+Dead_code_elim Pragma
+~~~~~~~~~~~~~~~~~~~~~
+The `dead_code_elim`:idx: pragma only applies to whole modules: It tells the
+compiler to active (or deactivate) dead code elimination for the module the
+pragma appers in.
+
+The ``--dead_code_elim:on`` command line switch has the same effect as marking
+any module with ``{.dead_code_elim:on}``. However, for some modules such as
+the GTK wrapper it makes sense to *always* turn on dead code elimination -
+no matter if it is globally active or not.
+
+Example:
+
+.. code-block:: nimrod
+  {.dead_code_elim: on.}
+
 
 Disabling certain messages
 --------------------------
@@ -280,8 +280,8 @@ However, sometimes one has to optimize. Do it in the following order:
 
 This section can only help you with the last item. Note that rewriting parts
 of your program in C is *never* necessary to speed up your program, because
-everything that can be done in C can be done in Nimrod. Rewriting parts in
-assembler *might*.
+everything that can be done in C can be done in Nimrod.
+
 
 Optimizing string handling
 --------------------------
diff --git a/doc/rst.txt b/doc/rst.txt
index c4f3805b3..79d0eb9c4 100644
--- a/doc/rst.txt
+++ b/doc/rst.txt
@@ -18,8 +18,7 @@ compatible to the original implementation as one would like.
 
 Even though Nimrod's |rst| parser does not parse all constructs, it is pretty
 usable. The missing features can easily be circumvented. An indication of this
-fact is that Nimrod's 
-*whole* documentation itself (including this document) is
+fact is that Nimrod's *whole* documentation itself (including this document) is
 processed by Nimrod's |rst| parser. (Which is an order of magnitude faster than
 Docutils' parser.)
 
diff --git a/doc/theindex.txt b/doc/theindex.txt
index f60e85d28..1afbdb791 100644
--- a/doc/theindex.txt
+++ b/doc/theindex.txt
@@ -1,7469 +1,7539 @@
-
-=====
-Index
-=====
-
-.. index::
-
-
-   `!=`:idx:
-     `system.html#351 <system.html#351>`_
-
-   `$`:idx:
-     * `system.html#420 <system.html#420>`_
-     * `system.html#421 <system.html#421>`_
-     * `system.html#422 <system.html#422>`_
-     * `system.html#423 <system.html#423>`_
-     * `system.html#424 <system.html#424>`_
-     * `system.html#425 <system.html#425>`_
-     * `system.html#426 <system.html#426>`_
-     * `times.html#109 <times.html#109>`_
-     * `times.html#110 <times.html#110>`_
-
-   `%`:idx:
-     * `strutils.html#132 <strutils.html#132>`_
-     * `strutils.html#133 <strutils.html#133>`_
-     * `strtabs.html#112 <strtabs.html#112>`_
-
-   `%%`:idx:
-     * `system.html#293 <system.html#293>`_
-     * `system.html#294 <system.html#294>`_
-     * `system.html#295 <system.html#295>`_
-     * `system.html#296 <system.html#296>`_
-     * `system.html#297 <system.html#297>`_
-
-   `&`:idx:
-     * `system.html#362 <system.html#362>`_
-     * `system.html#363 <system.html#363>`_
-     * `system.html#364 <system.html#364>`_
-     * `system.html#365 <system.html#365>`_
-     * `system.html#450 <system.html#450>`_
-     * `system.html#451 <system.html#451>`_
-     * `system.html#452 <system.html#452>`_
-     * `system.html#453 <system.html#453>`_
-
-   `*`:idx:
-     * `system.html#203 <system.html#203>`_
-     * `system.html#204 <system.html#204>`_
-     * `system.html#205 <system.html#205>`_
-     * `system.html#206 <system.html#206>`_
-     * `system.html#207 <system.html#207>`_
-     * `system.html#312 <system.html#312>`_
-     * `system.html#323 <system.html#323>`_
-     * `complex.html#107 <complex.html#107>`_
-
-   `*%`:idx:
-     * `system.html#283 <system.html#283>`_
-     * `system.html#284 <system.html#284>`_
-     * `system.html#285 <system.html#285>`_
-     * `system.html#286 <system.html#286>`_
-     * `system.html#287 <system.html#287>`_
-
-   `+`:idx:
-     * `system.html#178 <system.html#178>`_
-     * `system.html#179 <system.html#179>`_
-     * `system.html#180 <system.html#180>`_
-     * `system.html#181 <system.html#181>`_
-     * `system.html#182 <system.html#182>`_
-     * `system.html#193 <system.html#193>`_
-     * `system.html#194 <system.html#194>`_
-     * `system.html#195 <system.html#195>`_
-     * `system.html#196 <system.html#196>`_
-     * `system.html#197 <system.html#197>`_
-     * `system.html#308 <system.html#308>`_
-     * `system.html#310 <system.html#310>`_
-     * `system.html#324 <system.html#324>`_
-     * `complex.html#103 <complex.html#103>`_
-
-   `+%`:idx:
-     * `system.html#273 <system.html#273>`_
-     * `system.html#274 <system.html#274>`_
-     * `system.html#275 <system.html#275>`_
-     * `system.html#276 <system.html#276>`_
-     * `system.html#277 <system.html#277>`_
-
-   `-`:idx:
-     * `system.html#183 <system.html#183>`_
-     * `system.html#184 <system.html#184>`_
-     * `system.html#185 <system.html#185>`_
-     * `system.html#186 <system.html#186>`_
-     * `system.html#187 <system.html#187>`_
-     * `system.html#198 <system.html#198>`_
-     * `system.html#199 <system.html#199>`_
-     * `system.html#200 <system.html#200>`_
-     * `system.html#201 <system.html#201>`_
-     * `system.html#202 <system.html#202>`_
-     * `system.html#309 <system.html#309>`_
-     * `system.html#311 <system.html#311>`_
-     * `system.html#325 <system.html#325>`_
-     * `complex.html#104 <complex.html#104>`_
-     * `complex.html#105 <complex.html#105>`_
-     * `times.html#113 <times.html#113>`_
-
-   `-%`:idx:
-     * `system.html#278 <system.html#278>`_
-     * `system.html#279 <system.html#279>`_
-     * `system.html#280 <system.html#280>`_
-     * `system.html#281 <system.html#281>`_
-     * `system.html#282 <system.html#282>`_
-
-   `-+-`:idx:
-     `system.html#326 <system.html#326>`_
-
-   `/`:idx:
-     * `system.html#313 <system.html#313>`_
-     * `os.html#119 <os.html#119>`_
-     * `complex.html#106 <complex.html#106>`_
-
-   `/%`:idx:
-     * `system.html#288 <system.html#288>`_
-     * `system.html#289 <system.html#289>`_
-     * `system.html#290 <system.html#290>`_
-     * `system.html#291 <system.html#291>`_
-     * `system.html#292 <system.html#292>`_
-
-   `/../`:idx:
-     `os.html#123 <os.html#123>`_
-
-   `<`:idx:
-     * `system.html#253 <system.html#253>`_
-     * `system.html#254 <system.html#254>`_
-     * `system.html#255 <system.html#255>`_
-     * `system.html#256 <system.html#256>`_
-     * `system.html#257 <system.html#257>`_
-     * `system.html#316 <system.html#316>`_
-     * `system.html#343 <system.html#343>`_
-     * `system.html#344 <system.html#344>`_
-     * `system.html#345 <system.html#345>`_
-     * `system.html#346 <system.html#346>`_
-     * `system.html#347 <system.html#347>`_
-     * `system.html#348 <system.html#348>`_
-     * `system.html#349 <system.html#349>`_
-     * `system.html#350 <system.html#350>`_
-     * `times.html#114 <times.html#114>`_
-
-   `<%`:idx:
-     * `system.html#303 <system.html#303>`_
-     * `system.html#304 <system.html#304>`_
-     * `system.html#305 <system.html#305>`_
-     * `system.html#306 <system.html#306>`_
-     * `system.html#307 <system.html#307>`_
-
-   `<=`:idx:
-     `times.html#115 <times.html#115>`_
-
-   `<=`:idx:
-     * `system.html#248 <system.html#248>`_
-     * `system.html#249 <system.html#249>`_
-     * `system.html#250 <system.html#250>`_
-     * `system.html#251 <system.html#251>`_
-     * `system.html#252 <system.html#252>`_
-     * `system.html#315 <system.html#315>`_
-     * `system.html#336 <system.html#336>`_
-     * `system.html#337 <system.html#337>`_
-     * `system.html#338 <system.html#338>`_
-     * `system.html#339 <system.html#339>`_
-     * `system.html#340 <system.html#340>`_
-     * `system.html#341 <system.html#341>`_
-     * `system.html#342 <system.html#342>`_
-
-   `<=%`:idx:
-     * `system.html#298 <system.html#298>`_
-     * `system.html#299 <system.html#299>`_
-     * `system.html#300 <system.html#300>`_
-     * `system.html#301 <system.html#301>`_
-     * `system.html#302 <system.html#302>`_
-
-   `==`:idx:
-     * `system.html#243 <system.html#243>`_
-     * `system.html#244 <system.html#244>`_
-     * `system.html#245 <system.html#245>`_
-     * `system.html#246 <system.html#246>`_
-     * `system.html#247 <system.html#247>`_
-     * `system.html#314 <system.html#314>`_
-     * `system.html#327 <system.html#327>`_
-     * `system.html#328 <system.html#328>`_
-     * `system.html#329 <system.html#329>`_
-     * `system.html#330 <system.html#330>`_
-     * `system.html#331 <system.html#331>`_
-     * `system.html#332 <system.html#332>`_
-     * `system.html#333 <system.html#333>`_
-     * `system.html#334 <system.html#334>`_
-     * `system.html#335 <system.html#335>`_
-     * `system.html#455 <system.html#455>`_
-     * `complex.html#102 <complex.html#102>`_
-
-   `>`:idx:
-     `system.html#353 <system.html#353>`_
-
-   `>%`:idx:
-     `system.html#419 <system.html#419>`_
-
-   `>=`:idx:
-     `system.html#352 <system.html#352>`_
-
-   `>=%`:idx:
-     `system.html#418 <system.html#418>`_
-
-   `@`:idx:
-     `system.html#361 <system.html#361>`_
-
-   `[]`:idx:
-     `strtabs.html#107 <strtabs.html#107>`_
-
-   `[]=`:idx:
-     `strtabs.html#106 <strtabs.html#106>`_
-
-   `[ESC]`:idx:
-     `manual.html#134 <manual.html#134>`_
-
-   `ABDAY_1`:idx:
-     `posix.html#403 <posix.html#403>`_
-
-   `ABDAY_2`:idx:
-     `posix.html#404 <posix.html#404>`_
-
-   `ABDAY_3`:idx:
-     `posix.html#405 <posix.html#405>`_
-
-   `ABDAY_4`:idx:
-     `posix.html#406 <posix.html#406>`_
-
-   `ABDAY_5`:idx:
-     `posix.html#407 <posix.html#407>`_
-
-   `ABDAY_6`:idx:
-     `posix.html#408 <posix.html#408>`_
-
-   `ABDAY_7`:idx:
-     `posix.html#409 <posix.html#409>`_
-
-   `ABMON_1`:idx:
-     `posix.html#422 <posix.html#422>`_
-
-   `ABMON_10`:idx:
-     `posix.html#431 <posix.html#431>`_
-
-   `ABMON_11`:idx:
-     `posix.html#432 <posix.html#432>`_
-
-   `ABMON_12`:idx:
-     `posix.html#433 <posix.html#433>`_
-
-   `ABMON_2`:idx:
-     `posix.html#423 <posix.html#423>`_
-
-   `ABMON_3`:idx:
-     `posix.html#424 <posix.html#424>`_
-
-   `ABMON_4`:idx:
-     `posix.html#425 <posix.html#425>`_
-
-   `ABMON_5`:idx:
-     `posix.html#426 <posix.html#426>`_
-
-   `ABMON_6`:idx:
-     `posix.html#427 <posix.html#427>`_
-
-   `ABMON_7`:idx:
-     `posix.html#428 <posix.html#428>`_
-
-   `ABMON_8`:idx:
-     `posix.html#429 <posix.html#429>`_
-
-   `ABMON_9`:idx:
-     `posix.html#430 <posix.html#430>`_
-
-   `abs`:idx:
-     * `system.html#258 <system.html#258>`_
-     * `system.html#259 <system.html#259>`_
-     * `system.html#260 <system.html#260>`_
-     * `system.html#261 <system.html#261>`_
-     * `system.html#262 <system.html#262>`_
-     * `system.html#317 <system.html#317>`_
-     * `complex.html#108 <complex.html#108>`_
-
-   `access`:idx:
-     `posix.html#966 <posix.html#966>`_
-
-   `acyclic`:idx:
-     `nimrodc.html#114 <nimrodc.html#114>`_
-
-   `add`:idx:
-     * `system.html#366 <system.html#366>`_
-     * `system.html#367 <system.html#367>`_
-     * `system.html#368 <system.html#368>`_
-     * `system.html#369 <system.html#369>`_
-     * `system.html#370 <system.html#370>`_
-
-   `addFile`:idx:
-     * `zipfiles.html#105 <zipfiles.html#105>`_
-     * `zipfiles.html#106 <zipfiles.html#106>`_
-     * `zipfiles.html#107 <zipfiles.html#107>`_
-
-   `addQuitProc`:idx:
-     `system.html#402 <system.html#402>`_
-
-   `adler32`:idx:
-     `zlib.html#174 <zlib.html#174>`_
-
-   `AIO_ALLDONE`:idx:
-     `posix.html#207 <posix.html#207>`_
-
-   `aio_cancel`:idx:
-     `posix.html#784 <posix.html#784>`_
-
-   `AIO_CANCELED`:idx:
-     `posix.html#208 <posix.html#208>`_
-
-   `aio_error`:idx:
-     `posix.html#785 <posix.html#785>`_
-
-   `aio_fsync`:idx:
-     `posix.html#786 <posix.html#786>`_
-
-   `AIO_NOTCANCELED`:idx:
-     `posix.html#209 <posix.html#209>`_
-
-   `aio_read`:idx:
-     `posix.html#787 <posix.html#787>`_
-
-   `aio_return`:idx:
-     `posix.html#788 <posix.html#788>`_
-
-   `aio_suspend`:idx:
-     `posix.html#789 <posix.html#789>`_
-
-   `aio_write`:idx:
-     `posix.html#790 <posix.html#790>`_
-
-   `alarm`:idx:
-     `posix.html#967 <posix.html#967>`_
-
-   `alert`:idx:
-     `manual.html#131 <manual.html#131>`_
-
-   `allCharsInSet`:idx:
-     `strutils.html#137 <strutils.html#137>`_
-
-   `alloc`:idx:
-     `system.html#411 <system.html#411>`_
-
-   `alloc0`:idx:
-     `system.html#412 <system.html#412>`_
-
-   `ALT_DIGITS`:idx:
-     `posix.html#438 <posix.html#438>`_
-
-   `AltSep`:idx:
-     `os.html#104 <os.html#104>`_
-
-   `AM_STR`:idx:
-     `posix.html#394 <posix.html#394>`_
-
-   `and`:idx:
-     * `system.html#228 <system.html#228>`_
-     * `system.html#229 <system.html#229>`_
-     * `system.html#230 <system.html#230>`_
-     * `system.html#231 <system.html#231>`_
-     * `system.html#232 <system.html#232>`_
-     * `system.html#320 <system.html#320>`_
-
-   `apostrophe`:idx:
-     `manual.html#129 <manual.html#129>`_
-
-   `AppendFileExt`:idx:
-     `os.html#131 <os.html#131>`_
-
-   `arccos`:idx:
-     `math.html#117 <math.html#117>`_
-
-   `arcsin`:idx:
-     `math.html#118 <math.html#118>`_
-
-   `arctan`:idx:
-     `math.html#119 <math.html#119>`_
-
-   `arctan2`:idx:
-     `math.html#120 <math.html#120>`_
-
-   `array`:idx:
-     `system.html#121 <system.html#121>`_
-
-   `Arrays`:idx:
-     `manual.html#153 <manual.html#153>`_
-
-   `asctime`:idx:
-     `posix.html#1092 <posix.html#1092>`_
-
-   `asctime_r`:idx:
-     `posix.html#1093 <posix.html#1093>`_
-
-   `assembler`:idx:
-     `manual.html#197 <manual.html#197>`_
-
-   `assert`:idx:
-     `system.html#416 <system.html#416>`_
-
-   `Automatic type conversion`:idx:
-     `manual.html#145 <manual.html#145>`_
-
-   `backslash`:idx:
-     * `manual.html#127 <manual.html#127>`_
-     * `regexprs.html#101 <regexprs.html#101>`_
-
-   `backspace`:idx:
-     `manual.html#132 <manual.html#132>`_
-
-   `basename`:idx:
-     `posix.html#844 <posix.html#844>`_
-
-   `BiggestFloat`:idx:
-     `system.html#374 <system.html#374>`_
-
-   `BiggestInt`:idx:
-     `system.html#373 <system.html#373>`_
-
-   `block`:idx:
-     `manual.html#193 <manual.html#193>`_
-
-   `bool`:idx:
-     `system.html#109 <system.html#109>`_
-
-   `boolean`:idx:
-     `manual.html#147 <manual.html#147>`_
-
-   `break`:idx:
-     `manual.html#194 <manual.html#194>`_
-
-   `breakpoint`:idx:
-     `endb.html#103 <endb.html#103>`_
-
-   `bsd_signal`:idx:
-     `posix.html#1122 <posix.html#1122>`_
-
-   `Byte`:idx:
-     `system.html#125 <system.html#125>`_
-
-   `C`:idx:
-     `manual.html#136 <manual.html#136>`_
-
-   `calling conventions`:idx:
-     `manual.html#164 <manual.html#164>`_
-
-   `capitalize`:idx:
-     `strutils.html#110 <strutils.html#110>`_
-
-   `card`:idx:
-     `system.html#166 <system.html#166>`_
-
-   `carriage return`:idx:
-     `manual.html#122 <manual.html#122>`_
-
-   `case`:idx:
-     `manual.html#182 <manual.html#182>`_
-
-   `catclose`:idx:
-     `posix.html#1149 <posix.html#1149>`_
-
-   `catgets`:idx:
-     `posix.html#1150 <posix.html#1150>`_
-
-   `catopen`:idx:
-     `posix.html#1151 <posix.html#1151>`_
-
-   `cchar`:idx:
-     `system.html#375 <system.html#375>`_
-
-   `cdecl`:idx:
-     `manual.html#166 <manual.html#166>`_
-
-   `cdouble`:idx:
-     `system.html#382 <system.html#382>`_
-
-   `cfloat`:idx:
-     `system.html#381 <system.html#381>`_
-
-   `ChangeFileExt`:idx:
-     `os.html#132 <os.html#132>`_
-
-   `char`:idx:
-     `system.html#110 <system.html#110>`_
-
-   `character type`:idx:
-     `manual.html#148 <manual.html#148>`_
-
-   `character with decimal value d`:idx:
-     `manual.html#130 <manual.html#130>`_
-
-   `character with hex value HH`:idx:
-     `manual.html#135 <manual.html#135>`_
-
-   `chdir`:idx:
-     `posix.html#968 <posix.html#968>`_
-
-   `checked runtime error`:idx:
-     `manual.html#110 <manual.html#110>`_
-
-   `chmod`:idx:
-     `posix.html#1058 <posix.html#1058>`_
-
-   `ChooseDir`:idx:
-     `dialogs.html#108 <dialogs.html#108>`_
-
-   `ChooseFilesToOpen`:idx:
-     `dialogs.html#106 <dialogs.html#106>`_
-
-   `ChooseFileToOpen`:idx:
-     `dialogs.html#105 <dialogs.html#105>`_
-
-   `ChooseFileToSave`:idx:
-     `dialogs.html#107 <dialogs.html#107>`_
-
-   `chown`:idx:
-     `posix.html#969 <posix.html#969>`_
-
-   `chr`:idx:
-     `system.html#168 <system.html#168>`_
-
-   `cint`:idx:
-     `system.html#378 <system.html#378>`_
-
-   `C_IRGRP`:idx:
-     `posix.html#104 <posix.html#104>`_
-
-   `C_IROTH`:idx:
-     `posix.html#107 <posix.html#107>`_
-
-   `C_IRUSR`:idx:
-     `posix.html#101 <posix.html#101>`_
-
-   `C_ISBLK`:idx:
-     `posix.html#116 <posix.html#116>`_
-
-   `C_ISCHR`:idx:
-     `posix.html#117 <posix.html#117>`_
-
-   `C_ISCTG`:idx:
-     `posix.html#118 <posix.html#118>`_
-
-   `C_ISDIR`:idx:
-     `posix.html#113 <posix.html#113>`_
-
-   `C_ISFIFO`:idx:
-     `posix.html#114 <posix.html#114>`_
-
-   `C_ISGID`:idx:
-     `posix.html#111 <posix.html#111>`_
-
-   `C_ISLNK`:idx:
-     `posix.html#119 <posix.html#119>`_
-
-   `C_ISREG`:idx:
-     `posix.html#115 <posix.html#115>`_
-
-   `C_ISSOCK`:idx:
-     `posix.html#120 <posix.html#120>`_
-
-   `C_ISUID`:idx:
-     `posix.html#110 <posix.html#110>`_
-
-   `C_ISVTX`:idx:
-     `posix.html#112 <posix.html#112>`_
-
-   `C_IWGRP`:idx:
-     `posix.html#105 <posix.html#105>`_
-
-   `C_IWOTH`:idx:
-     `posix.html#108 <posix.html#108>`_
-
-   `C_IWUSR`:idx:
-     `posix.html#102 <posix.html#102>`_
-
-   `C_IXGRP`:idx:
-     `posix.html#106 <posix.html#106>`_
-
-   `C_IXOTH`:idx:
-     `posix.html#109 <posix.html#109>`_
-
-   `C_IXUSR`:idx:
-     `posix.html#103 <posix.html#103>`_
-
-   `classify`:idx:
-     `math.html#104 <math.html#104>`_
-
-   `clock`:idx:
-     `posix.html#1094 <posix.html#1094>`_
-
-   `clock_getcpuclockid`:idx:
-     `posix.html#1095 <posix.html#1095>`_
-
-   `clock_getres`:idx:
-     `posix.html#1096 <posix.html#1096>`_
-
-   `clock_gettime`:idx:
-     `posix.html#1097 <posix.html#1097>`_
-
-   `CLOCK_MONOTONIC`:idx:
-     `posix.html#700 <posix.html#700>`_
-
-   `clock_nanosleep`:idx:
-     `posix.html#1098 <posix.html#1098>`_
-
-   `CLOCK_PROCESS_CPUTIME_ID`:idx:
-     `posix.html#696 <posix.html#696>`_
-
-   `CLOCK_REALTIME`:idx:
-     `posix.html#698 <posix.html#698>`_
-
-   `clock_settime`:idx:
-     `posix.html#1099 <posix.html#1099>`_
-
-   `CLOCKS_PER_SEC`:idx:
-     `posix.html#695 <posix.html#695>`_
-
-   `CLOCK_THREAD_CPUTIME_ID`:idx:
-     `posix.html#697 <posix.html#697>`_
-
-   `clong`:idx:
-     `system.html#379 <system.html#379>`_
-
-   `clongdouble`:idx:
-     `system.html#383 <system.html#383>`_
-
-   `clonglong`:idx:
-     `system.html#380 <system.html#380>`_
-
-   `close`:idx:
-     * `lexbase.html#105 <lexbase.html#105>`_
-     * `parsecfg.html#105 <parsecfg.html#105>`_
-     * `posix.html#970 <posix.html#970>`_
-     * `zipfiles.html#103 <zipfiles.html#103>`_
-
-   `closedir`:idx:
-     `posix.html#800 <posix.html#800>`_
-
-   `CloseFile`:idx:
-     `system.html#484 <system.html#484>`_
-
-   `closure`:idx:
-     `manual.html#171 <manual.html#171>`_
-
-   `cmp`:idx:
-     * `system.html#359 <system.html#359>`_
-     * `system.html#360 <system.html#360>`_
-
-   `cmpIgnoreCase`:idx:
-     `strutils.html#122 <strutils.html#122>`_
-
-   `cmpIgnoreStyle`:idx:
-     `strutils.html#123 <strutils.html#123>`_
-
-   `cmpPaths`:idx:
-     `os.html#130 <os.html#130>`_
-
-   `CODESET`:idx:
-     `posix.html#389 <posix.html#389>`_
-
-   `comment pieces`:idx:
-     `manual.html#115 <manual.html#115>`_
-
-   `Comments`:idx:
-     `manual.html#114 <manual.html#114>`_
-
-   `CompileDate`:idx:
-     `system.html#391 <system.html#391>`_
-
-   `CompileTime`:idx:
-     `system.html#392 <system.html#392>`_
-
-   `complex statements`:idx:
-     `manual.html#176 <manual.html#176>`_
-
-   `compress`:idx:
-     `zlib.html#154 <zlib.html#154>`_
-
-   `compress2`:idx:
-     `zlib.html#155 <zlib.html#155>`_
-
-   `confstr`:idx:
-     `posix.html#971 <posix.html#971>`_
-
-   `const`:idx:
-     `manual.html#180 <manual.html#180>`_
-
-   `constant expressions`:idx:
-     `manual.html#108 <manual.html#108>`_
-
-   `Constants`:idx:
-     `manual.html#140 <manual.html#140>`_
-
-   `constZIP_SOURCE_FREE`:idx:
-     `libzip.html#169 <libzip.html#169>`_
-
-   `continue`:idx:
-     `manual.html#196 <manual.html#196>`_
-
-   `copy`:idx:
-     * `system.html#403 <system.html#403>`_
-     * `system.html#404 <system.html#404>`_
-
-   `copyFile`:idx:
-     `os.html#134 <os.html#134>`_
-
-   `copyMem`:idx:
-     `system.html#408 <system.html#408>`_
-
-   `cos`:idx:
-     `math.html#121 <math.html#121>`_
-
-   `cosh`:idx:
-     `math.html#122 <math.html#122>`_
-
-   `countBits`:idx:
-     `math.html#107 <math.html#107>`_
-
-   `countdown`:idx:
-     `system.html#436 <system.html#436>`_
-
-   `countup`:idx:
-     `system.html#437 <system.html#437>`_
-
-   `cpuEndian`:idx:
-     `system.html#397 <system.html#397>`_
-
-   `crc32`:idx:
-     `zlib.html#175 <zlib.html#175>`_
-
-   `creat`:idx:
-     `posix.html#811 <posix.html#811>`_
-
-   `createDir`:idx:
-     * `os.html#138 <os.html#138>`_
-     * `zipfiles.html#104 <zipfiles.html#104>`_
-
-   `CRNCYSTR`:idx:
-     `posix.html#443 <posix.html#443>`_
-
-   `crypt`:idx:
-     `posix.html#972 <posix.html#972>`_
-
-   `cschar`:idx:
-     `system.html#376 <system.html#376>`_
-
-   `cshort`:idx:
-     `system.html#377 <system.html#377>`_
-
-   `cSIG_HOLD`:idx:
-     `posix.html#721 <posix.html#721>`_
-
-   `CS_PATH`:idx:
-     `posix.html#482 <posix.html#482>`_
-
-   `CS_POSIX_V6_ILP32_OFF32_CFLAGS`:idx:
-     `posix.html#483 <posix.html#483>`_
-
-   `CS_POSIX_V6_ILP32_OFF32_LDFLAGS`:idx:
-     `posix.html#484 <posix.html#484>`_
-
-   `CS_POSIX_V6_ILP32_OFF32_LIBS`:idx:
-     `posix.html#485 <posix.html#485>`_
-
-   `CS_POSIX_V6_ILP32_OFFBIG_CFLAGS`:idx:
-     `posix.html#486 <posix.html#486>`_
-
-   `CS_POSIX_V6_ILP32_OFFBIG_LDFLAGS`:idx:
-     `posix.html#487 <posix.html#487>`_
-
-   `CS_POSIX_V6_ILP32_OFFBIG_LIBS`:idx:
-     `posix.html#488 <posix.html#488>`_
-
-   `CS_POSIX_V6_LP64_OFF64_CFLAGS`:idx:
-     `posix.html#489 <posix.html#489>`_
-
-   `CS_POSIX_V6_LP64_OFF64_LDFLAGS`:idx:
-     `posix.html#490 <posix.html#490>`_
-
-   `CS_POSIX_V6_LP64_OFF64_LIBS`:idx:
-     `posix.html#491 <posix.html#491>`_
-
-   `CS_POSIX_V6_LPBIG_OFFBIG_CFLAGS`:idx:
-     `posix.html#492 <posix.html#492>`_
-
-   `CS_POSIX_V6_LPBIG_OFFBIG_LDFLAGS`:idx:
-     `posix.html#493 <posix.html#493>`_
-
-   `CS_POSIX_V6_LPBIG_OFFBIG_LIBS`:idx:
-     `posix.html#494 <posix.html#494>`_
-
-   `CS_POSIX_V6_WIDTH_RESTRICTED_ENVS`:idx:
-     `posix.html#495 <posix.html#495>`_
-
-   `cstring`:idx:
-     `system.html#112 <system.html#112>`_
-
-   `cstringArray`:idx:
-     `system.html#384 <system.html#384>`_
-
-   `ctermid`:idx:
-     `posix.html#973 <posix.html#973>`_
-
-   `ctime`:idx:
-     `posix.html#1100 <posix.html#1100>`_
-
-   `ctime_r`:idx:
-     `posix.html#1101 <posix.html#1101>`_
-
-   `CurDir`:idx:
-     `os.html#101 <os.html#101>`_
-
-   `dangling else problem`:idx:
-     `manual.html#177 <manual.html#177>`_
-
-   `DAY_1`:idx:
-     `posix.html#396 <posix.html#396>`_
-
-   `DAY_2`:idx:
-     `posix.html#397 <posix.html#397>`_
-
-   `DAY_3`:idx:
-     `posix.html#398 <posix.html#398>`_
-
-   `DAY_4`:idx:
-     `posix.html#399 <posix.html#399>`_
-
-   `DAY_5`:idx:
-     `posix.html#400 <posix.html#400>`_
-
-   `DAY_6`:idx:
-     `posix.html#401 <posix.html#401>`_
-
-   `DAY_7`:idx:
-     `posix.html#402 <posix.html#402>`_
-
-   `daylight`:idx:
-     `posix.html#701 <posix.html#701>`_
-
-   `dbgLineHook`:idx:
-     `system.html#432 <system.html#432>`_
-
-   `dealloc`:idx:
-     `system.html#414 <system.html#414>`_
-
-   `debugger`:idx:
-     `nimrodc.html#111 <nimrodc.html#111>`_
-
-   `dec`:idx:
-     `system.html#157 <system.html#157>`_
-
-   `define`:idx:
-     `manual.html#223 <manual.html#223>`_
-
-   `defined`:idx:
-     `system.html#114 <system.html#114>`_
-
-   `deflate`:idx:
-     `zlib.html#143 <zlib.html#143>`_
-
-   `deflateCopy`:idx:
-     `zlib.html#148 <zlib.html#148>`_
-
-   `deflateEnd`:idx:
-     `zlib.html#144 <zlib.html#144>`_
-
-   `deflateInit`:idx:
-     `zlib.html#178 <zlib.html#178>`_
-
-   `deflateInit2`:idx:
-     `zlib.html#182 <zlib.html#182>`_
-
-   `deflateInit2u`:idx:
-     `zlib.html#180 <zlib.html#180>`_
-
-   `deflateInitu`:idx:
-     `zlib.html#176 <zlib.html#176>`_
-
-   `deflateParams`:idx:
-     `zlib.html#150 <zlib.html#150>`_
-
-   `deflateReset`:idx:
-     `zlib.html#149 <zlib.html#149>`_
-
-   `deflateSetDictionary`:idx:
-     `zlib.html#147 <zlib.html#147>`_
-
-   `deleteStr`:idx:
-     `strutils.html#116 <strutils.html#116>`_
-
-   `D_FMT`:idx:
-     `posix.html#391 <posix.html#391>`_
-
-   `difftime`:idx:
-     `posix.html#1102 <posix.html#1102>`_
-
-   `dirname`:idx:
-     `posix.html#845 <posix.html#845>`_
-
-   `DirSep`:idx:
-     `os.html#103 <os.html#103>`_
-
-   `discard`:idx:
-     `manual.html#178 <manual.html#178>`_
-
-   `div`:idx:
-     * `system.html#208 <system.html#208>`_
-     * `system.html#209 <system.html#209>`_
-     * `system.html#210 <system.html#210>`_
-     * `system.html#211 <system.html#211>`_
-     * `system.html#212 <system.html#212>`_
-
-   `dlclose`:idx:
-     `posix.html#807 <posix.html#807>`_
-
-   `dlerror`:idx:
-     `posix.html#808 <posix.html#808>`_
-
-   `dlopen`:idx:
-     `posix.html#809 <posix.html#809>`_
-
-   `dlsym`:idx:
-     `posix.html#810 <posix.html#810>`_
-
-   `dom`:idx:
-     `nimrodc.html#120 <nimrodc.html#120>`_
-
-   `domain specific languages`:idx:
-     `manual.html#212 <manual.html#212>`_
-
-   `D_T_FMT`:idx:
-     `posix.html#390 <posix.html#390>`_
-
-   `dup`:idx:
-     `posix.html#974 <posix.html#974>`_
-
-   `dup2`:idx:
-     `posix.html#975 <posix.html#975>`_
-
-   `dynamic type`:idx:
-     `manual.html#104 <manual.html#104>`_
-
-   `dynlib`:idx:
-     `nimrodc.html#103 <nimrodc.html#103>`_
-
-   `E`:idx:
-     `math.html#102 <math.html#102>`_
-
-   `E2BIG`:idx:
-     `posix.html#220 <posix.html#220>`_
-
-   `EACCES`:idx:
-     `posix.html#221 <posix.html#221>`_
-
-   `EAccessViolation`:idx:
-     `system.html#140 <system.html#140>`_
-
-   `EADDRINUSE`:idx:
-     `posix.html#222 <posix.html#222>`_
-
-   `EADDRNOTAVAIL`:idx:
-     `posix.html#223 <posix.html#223>`_
-
-   `EAFNOSUPPORT`:idx:
-     `posix.html#224 <posix.html#224>`_
-
-   `EAGAIN`:idx:
-     `posix.html#225 <posix.html#225>`_
-
-   `EALREADY`:idx:
-     `posix.html#226 <posix.html#226>`_
-
-   `EArithmetic`:idx:
-     `system.html#137 <system.html#137>`_
-
-   `EAssertionFailed`:idx:
-     `system.html#141 <system.html#141>`_
-
-   `EAsynch`:idx:
-     `system.html#131 <system.html#131>`_
-
-   `EBADF`:idx:
-     `posix.html#227 <posix.html#227>`_
-
-   `EBADMSG`:idx:
-     `posix.html#228 <posix.html#228>`_
-
-   `E_Base`:idx:
-     `system.html#130 <system.html#130>`_
-
-   `EBUSY`:idx:
-     `posix.html#229 <posix.html#229>`_
-
-   `ECANCELED`:idx:
-     `posix.html#230 <posix.html#230>`_
-
-   `ECHILD`:idx:
-     `posix.html#231 <posix.html#231>`_
-
-   `echo`:idx:
-     `system.html#471 <system.html#471>`_
-
-   `ECMAScript`:idx:
-     `nimrodc.html#115 <nimrodc.html#115>`_
-
-   `ECONNABORTED`:idx:
-     `posix.html#232 <posix.html#232>`_
-
-   `ECONNREFUSED`:idx:
-     `posix.html#233 <posix.html#233>`_
-
-   `ECONNRESET`:idx:
-     `posix.html#234 <posix.html#234>`_
-
-   `EControlC`:idx:
-     `system.html#142 <system.html#142>`_
-
-   `EDEADLK`:idx:
-     `posix.html#235 <posix.html#235>`_
-
-   `EDESTADDRREQ`:idx:
-     `posix.html#236 <posix.html#236>`_
-
-   `editDistance`:idx:
-     `strutils.html#142 <strutils.html#142>`_
-
-   `EDivByZero`:idx:
-     `system.html#138 <system.html#138>`_
-
-   `EDOM`:idx:
-     `posix.html#237 <posix.html#237>`_
-
-   `EDQUOT`:idx:
-     `posix.html#238 <posix.html#238>`_
-
-   `EEXIST`:idx:
-     `posix.html#239 <posix.html#239>`_
-
-   `EFAULT`:idx:
-     `posix.html#240 <posix.html#240>`_
-
-   `EFBIG`:idx:
-     `posix.html#241 <posix.html#241>`_
-
-   `EHOSTUNREACH`:idx:
-     `posix.html#242 <posix.html#242>`_
-
-   `EIDRM`:idx:
-     `posix.html#243 <posix.html#243>`_
-
-   `EILSEQ`:idx:
-     `posix.html#244 <posix.html#244>`_
-
-   `EINPROGRESS`:idx:
-     `posix.html#245 <posix.html#245>`_
-
-   `EINTR`:idx:
-     `posix.html#246 <posix.html#246>`_
-
-   `EINVAL`:idx:
-     `posix.html#247 <posix.html#247>`_
-
-   `EInvalidField`:idx:
-     `system.html#146 <system.html#146>`_
-
-   `EInvalidIndex`:idx:
-     `system.html#145 <system.html#145>`_
-
-   `EInvalidObjectAssignment`:idx:
-     `system.html#150 <system.html#150>`_
-
-   `EInvalidObjectConversion`:idx:
-     `system.html#151 <system.html#151>`_
-
-   `EInvalidRegEx`:idx:
-     `regexprs.html#104 <regexprs.html#104>`_
-
-   `EInvalidValue`:idx:
-     `system.html#143 <system.html#143>`_
-
-   `EIO`:idx:
-     * `system.html#134 <system.html#134>`_
-     * `posix.html#248 <posix.html#248>`_
-
-   `EISCONN`:idx:
-     `posix.html#249 <posix.html#249>`_
-
-   `EISDIR`:idx:
-     `posix.html#250 <posix.html#250>`_
-
-   `ELOOP`:idx:
-     `posix.html#251 <posix.html#251>`_
-
-   `Embedded Nimrod Debugger`:idx:
-     `endb.html#101 <endb.html#101>`_
-
-   `EMFILE`:idx:
-     `posix.html#252 <posix.html#252>`_
-
-   `EMLINK`:idx:
-     `posix.html#253 <posix.html#253>`_
-
-   `EMSGSIZE`:idx:
-     `posix.html#254 <posix.html#254>`_
-
-   `EMULTIHOP`:idx:
-     `posix.html#255 <posix.html#255>`_
-
-   `ENAMETOOLONG`:idx:
-     `posix.html#256 <posix.html#256>`_
-
-   `encrypt`:idx:
-     `posix.html#976 <posix.html#976>`_
-
-   `ENDB`:idx:
-     `endb.html#102 <endb.html#102>`_
-
-   `endgrent`:idx:
-     `posix.html#838 <posix.html#838>`_
-
-   `EndOfFile`:idx:
-     * `system.html#485 <system.html#485>`_
-     * `lexbase.html#101 <lexbase.html#101>`_
-
-   `endpwent`:idx:
-     `posix.html#863 <posix.html#863>`_
-
-   `endsWith`:idx:
-     `strutils.html#136 <strutils.html#136>`_
-
-   `ENETDOWN`:idx:
-     `posix.html#257 <posix.html#257>`_
-
-   `ENETRESET`:idx:
-     `posix.html#258 <posix.html#258>`_
-
-   `ENETUNREACH`:idx:
-     `posix.html#259 <posix.html#259>`_
-
-   `ENFILE`:idx:
-     `posix.html#260 <posix.html#260>`_
-
-   `ENOBUFS`:idx:
-     `posix.html#261 <posix.html#261>`_
-
-   `ENODATA`:idx:
-     `posix.html#262 <posix.html#262>`_
-
-   `ENODEV`:idx:
-     `posix.html#263 <posix.html#263>`_
-
-   `ENOENT`:idx:
-     `posix.html#264 <posix.html#264>`_
-
-   `ENoExceptionToReraise`:idx:
-     * `manual.html#185 <manual.html#185>`_
-     * `system.html#149 <system.html#149>`_
-
-   `ENOEXEC`:idx:
-     `posix.html#265 <posix.html#265>`_
-
-   `ENOLCK`:idx:
-     `posix.html#266 <posix.html#266>`_
-
-   `ENOLINK`:idx:
-     `posix.html#267 <posix.html#267>`_
-
-   `ENOMEM`:idx:
-     `posix.html#268 <posix.html#268>`_
-
-   `ENOMSG`:idx:
-     `posix.html#269 <posix.html#269>`_
-
-   `ENOPROTOOPT`:idx:
-     `posix.html#270 <posix.html#270>`_
-
-   `ENOSPC`:idx:
-     `posix.html#271 <posix.html#271>`_
-
-   `ENOSR`:idx:
-     `posix.html#272 <posix.html#272>`_
-
-   `ENOSTR`:idx:
-     `posix.html#273 <posix.html#273>`_
-
-   `ENOSYS`:idx:
-     `posix.html#274 <posix.html#274>`_
-
-   `ENOTCONN`:idx:
-     `posix.html#275 <posix.html#275>`_
-
-   `ENOTDIR`:idx:
-     `posix.html#276 <posix.html#276>`_
-
-   `ENOTEMPTY`:idx:
-     `posix.html#277 <posix.html#277>`_
-
-   `ENOTSOCK`:idx:
-     `posix.html#278 <posix.html#278>`_
-
-   `ENOTSUP`:idx:
-     `posix.html#279 <posix.html#279>`_
-
-   `ENOTTY`:idx:
-     `posix.html#280 <posix.html#280>`_
-
-   `Enumeration`:idx:
-     `manual.html#149 <manual.html#149>`_
-
-   `ENXIO`:idx:
-     `posix.html#281 <posix.html#281>`_
-
-   `EOPNOTSUPP`:idx:
-     `posix.html#282 <posix.html#282>`_
-
-   `EOS`:idx:
-     `system.html#135 <system.html#135>`_
-
-   `EOutOfMemory`:idx:
-     `system.html#144 <system.html#144>`_
-
-   `EOutOfRange`:idx:
-     * `manual.html#146 <manual.html#146>`_
-     * `system.html#147 <system.html#147>`_
-
-   `EOVERFLOW`:idx:
-     `posix.html#283 <posix.html#283>`_
-
-   `EOverflow`:idx:
-     `system.html#139 <system.html#139>`_
-
-   `EPERM`:idx:
-     `posix.html#284 <posix.html#284>`_
-
-   `EPIPE`:idx:
-     `posix.html#285 <posix.html#285>`_
-
-   `EPROTO`:idx:
-     `posix.html#286 <posix.html#286>`_
-
-   `EPROTONOSUPPORT`:idx:
-     `posix.html#287 <posix.html#287>`_
-
-   `EPROTOTYPE`:idx:
-     `posix.html#288 <posix.html#288>`_
-
-   `equalMem`:idx:
-     `system.html#410 <system.html#410>`_
-
-   `ERA`:idx:
-     `posix.html#434 <posix.html#434>`_
-
-   `ERA_D_FMT`:idx:
-     `posix.html#435 <posix.html#435>`_
-
-   `ERA_D_T_FMT`:idx:
-     `posix.html#436 <posix.html#436>`_
-
-   `ERANGE`:idx:
-     `posix.html#289 <posix.html#289>`_
-
-   `ERA_T_FMT`:idx:
-     `posix.html#437 <posix.html#437>`_
-
-   `ERessourceExhausted`:idx:
-     `system.html#136 <system.html#136>`_
-
-   `EROFS`:idx:
-     `posix.html#290 <posix.html#290>`_
-
-   `errno`:idx:
-     `posix.html#219 <posix.html#219>`_
-
-   `error`:idx:
-     * `manual.html#222 <manual.html#222>`_
-     * `manual.html#225 <manual.html#225>`_
-     * `dialogs.html#104 <dialogs.html#104>`_
-
-   `errorStr`:idx:
-     `parsecfg.html#110 <parsecfg.html#110>`_
-
-   `escape`:idx:
-     * `manual.html#133 <manual.html#133>`_
-     * `strutils.html#141 <strutils.html#141>`_
-
-   `escape sequences`:idx:
-     `manual.html#120 <manual.html#120>`_
-
-   `ESPIPE`:idx:
-     `posix.html#291 <posix.html#291>`_
-
-   `ESRCH`:idx:
-     `posix.html#292 <posix.html#292>`_
-
-   `EStackOverflow`:idx:
-     `system.html#148 <system.html#148>`_
-
-   `ESTALE`:idx:
-     `posix.html#293 <posix.html#293>`_
-
-   `ESynch`:idx:
-     `system.html#132 <system.html#132>`_
-
-   `ESystem`:idx:
-     `system.html#133 <system.html#133>`_
-
-   `ETIME`:idx:
-     `posix.html#294 <posix.html#294>`_
-
-   `ETIMEDOUT`:idx:
-     `posix.html#295 <posix.html#295>`_
-
-   `ETXTBSY`:idx:
-     `posix.html#296 <posix.html#296>`_
-
-   `EWOULDBLOCK`:idx:
-     `posix.html#297 <posix.html#297>`_
-
-   `except`:idx:
-     `manual.html#188 <manual.html#188>`_
-
-   `exception handlers`:idx:
-     `manual.html#187 <manual.html#187>`_
-
-   `excl`:idx:
-     `system.html#165 <system.html#165>`_
-
-   `EXDEV`:idx:
-     `posix.html#298 <posix.html#298>`_
-
-   `execl`:idx:
-     `posix.html#977 <posix.html#977>`_
-
-   `execle`:idx:
-     `posix.html#978 <posix.html#978>`_
-
-   `execlp`:idx:
-     `posix.html#979 <posix.html#979>`_
-
-   `executeShellCommand`:idx:
-     `os.html#133 <os.html#133>`_
-
-   `execv`:idx:
-     `posix.html#980 <posix.html#980>`_
-
-   `execve`:idx:
-     `posix.html#981 <posix.html#981>`_
-
-   `execvp`:idx:
-     `posix.html#982 <posix.html#982>`_
-
-   `ExeExt`:idx:
-     `os.html#107 <os.html#107>`_
-
-   `existsDir`:idx:
-     `os.html#139 <os.html#139>`_
-
-   `existsEnv`:idx:
-     `os.html#144 <os.html#144>`_
-
-   `ExistsFile`:idx:
-     `os.html#117 <os.html#117>`_
-
-   `exp`:idx:
-     `math.html#114 <math.html#114>`_
-
-   `expandFilename`:idx:
-     `os.html#116 <os.html#116>`_
-
-   `exportc`:idx:
-     `nimrodc.html#102 <nimrodc.html#102>`_
-
-   `extractDir`:idx:
-     `os.html#126 <os.html#126>`_
-
-   `extractFileExt`:idx:
-     `os.html#128 <os.html#128>`_
-
-   `extractFilename`:idx:
-     `os.html#127 <os.html#127>`_
-
-   `extractFileTrunk`:idx:
-     `os.html#129 <os.html#129>`_
-
-   `ExtSep`:idx:
-     `os.html#109 <os.html#109>`_
-
-   `fastcall`:idx:
-     `manual.html#169 <manual.html#169>`_
-
-   `fatal`:idx:
-     `manual.html#226 <manual.html#226>`_
-
-   `fchdir`:idx:
-     `posix.html#984 <posix.html#984>`_
-
-   `fchmod`:idx:
-     `posix.html#1059 <posix.html#1059>`_
-
-   `fchown`:idx:
-     `posix.html#983 <posix.html#983>`_
-
-   `fcntl`:idx:
-     `posix.html#812 <posix.html#812>`_
-
-   `fdatasync`:idx:
-     `posix.html#985 <posix.html#985>`_
-
-   `FD_CLOEXEC`:idx:
-     `posix.html#309 <posix.html#309>`_
-
-   `FD_CLR`:idx:
-     `posix.html#1161 <posix.html#1161>`_
-
-   `FD_ISSET`:idx:
-     `posix.html#1162 <posix.html#1162>`_
-
-   `FD_SET`:idx:
-     `posix.html#1163 <posix.html#1163>`_
-
-   `FD_SETSIZE`:idx:
-     `posix.html#774 <posix.html#774>`_
-
-   `F_DUPFD`:idx:
-     `posix.html#299 <posix.html#299>`_
-
-   `FD_ZERO`:idx:
-     `posix.html#1164 <posix.html#1164>`_
-
-   `FE_ALL_EXCEPT`:idx:
-     `posix.html#337 <posix.html#337>`_
-
-   `feclearexcept`:idx:
-     `posix.html#816 <posix.html#816>`_
-
-   `FE_DFL_ENV`:idx:
-     `posix.html#342 <posix.html#342>`_
-
-   `FE_DIVBYZERO`:idx:
-     `posix.html#332 <posix.html#332>`_
-
-   `FE_DOWNWARD`:idx:
-     `posix.html#338 <posix.html#338>`_
-
-   `fegetenv`:idx:
-     `posix.html#823 <posix.html#823>`_
-
-   `fegetexceptflag`:idx:
-     `posix.html#817 <posix.html#817>`_
-
-   `fegetround`:idx:
-     `posix.html#821 <posix.html#821>`_
-
-   `feholdexcept`:idx:
-     `posix.html#824 <posix.html#824>`_
-
-   `FE_INEXACT`:idx:
-     `posix.html#333 <posix.html#333>`_
-
-   `FE_INVALID`:idx:
-     `posix.html#334 <posix.html#334>`_
-
-   `FE_OVERFLOW`:idx:
-     `posix.html#335 <posix.html#335>`_
-
-   `feraiseexcept`:idx:
-     `posix.html#818 <posix.html#818>`_
-
-   `fesetenv`:idx:
-     `posix.html#825 <posix.html#825>`_
-
-   `fesetexceptflag`:idx:
-     `posix.html#819 <posix.html#819>`_
-
-   `fesetround`:idx:
-     `posix.html#822 <posix.html#822>`_
-
-   `fetestexcept`:idx:
-     `posix.html#820 <posix.html#820>`_
-
-   `FE_TONEAREST`:idx:
-     `posix.html#339 <posix.html#339>`_
-
-   `FE_TOWARDZERO`:idx:
-     `posix.html#340 <posix.html#340>`_
-
-   `FE_UNDERFLOW`:idx:
-     `posix.html#336 <posix.html#336>`_
-
-   `feupdateenv`:idx:
-     `posix.html#826 <posix.html#826>`_
-
-   `FE_UPWARD`:idx:
-     `posix.html#341 <posix.html#341>`_
-
-   `F_GETFD`:idx:
-     `posix.html#300 <posix.html#300>`_
-
-   `F_GETFL`:idx:
-     `posix.html#302 <posix.html#302>`_
-
-   `F_GETLK`:idx:
-     `posix.html#304 <posix.html#304>`_
-
-   `F_GETOWN`:idx:
-     `posix.html#307 <posix.html#307>`_
-
-   `fileHandle`:idx:
-     `system.html#509 <system.html#509>`_
-
-   `fileNewer`:idx:
-     `os.html#141 <os.html#141>`_
-
-   `FileSystemCaseSensitive`:idx:
-     `os.html#106 <os.html#106>`_
-
-   `finally`:idx:
-     `manual.html#189 <manual.html#189>`_
-
-   `find`:idx:
-     * `system.html#456 <system.html#456>`_
-     * `regexprs.html#109 <regexprs.html#109>`_
-     * `regexprs.html#110 <regexprs.html#110>`_
-
-   `findSubStr`:idx:
-     * `strutils.html#112 <strutils.html#112>`_
-     * `strutils.html#113 <strutils.html#113>`_
-
-   `float`:idx:
-     `system.html#106 <system.html#106>`_
-
-   `float32`:idx:
-     `system.html#107 <system.html#107>`_
-
-   `float64`:idx:
-     `system.html#108 <system.html#108>`_
-
-   `F_LOCK`:idx:
-     `posix.html#496 <posix.html#496>`_
-
-   `FlushFile`:idx:
-     `system.html#487 <system.html#487>`_
-
-   `fmtmsg`:idx:
-     `posix.html#827 <posix.html#827>`_
-
-   `fnmatch`:idx:
-     `posix.html#828 <posix.html#828>`_
-
-   `FNM_NOESCAPE`:idx:
-     `posix.html#365 <posix.html#365>`_
-
-   `FNM_NOMATCH`:idx:
-     `posix.html#362 <posix.html#362>`_
-
-   `FNM_NOSYS`:idx:
-     `posix.html#366 <posix.html#366>`_
-
-   `FNM_PATHNAME`:idx:
-     `posix.html#363 <posix.html#363>`_
-
-   `FNM_PERIOD`:idx:
-     `posix.html#364 <posix.html#364>`_
-
-   `F_OK`:idx:
-     `posix.html#478 <posix.html#478>`_
-
-   `for`:idx:
-     `manual.html#204 <manual.html#204>`_
-
-   `fork`:idx:
-     `posix.html#986 <posix.html#986>`_
-
-   `form feed`:idx:
-     `manual.html#124 <manual.html#124>`_
-
-   `forward`:idx:
-     `manual.html#201 <manual.html#201>`_
-
-   `fpathconf`:idx:
-     `posix.html#987 <posix.html#987>`_
-
-   `F_RDLCK`:idx:
-     `posix.html#310 <posix.html#310>`_
-
-   `FreeEnvironmentStringsA`:idx:
-     `os.html#151 <os.html#151>`_
-
-   `frexp`:idx:
-     `math.html#115 <math.html#115>`_
-
-   `F_SETFD`:idx:
-     `posix.html#301 <posix.html#301>`_
-
-   `F_SETFL`:idx:
-     `posix.html#303 <posix.html#303>`_
-
-   `F_SETLK`:idx:
-     `posix.html#305 <posix.html#305>`_
-
-   `F_SETLKW`:idx:
-     `posix.html#306 <posix.html#306>`_
-
-   `F_SETOWN`:idx:
-     `posix.html#308 <posix.html#308>`_
-
-   `fstat`:idx:
-     `posix.html#1060 <posix.html#1060>`_
-
-   `fstatvfs`:idx:
-     `posix.html#1057 <posix.html#1057>`_
-
-   `fsync`:idx:
-     `posix.html#988 <posix.html#988>`_
-
-   `F_TEST`:idx:
-     `posix.html#497 <posix.html#497>`_
-
-   `F_TLOCK`:idx:
-     `posix.html#498 <posix.html#498>`_
-
-   `ftok`:idx:
-     `posix.html#1055 <posix.html#1055>`_
-
-   `ftruncate`:idx:
-     `posix.html#989 <posix.html#989>`_
-
-   `ftw`:idx:
-     `posix.html#829 <posix.html#829>`_
-
-   `FTW_CHDIR`:idx:
-     `posix.html#377 <posix.html#377>`_
-
-   `FTW_D`:idx:
-     `posix.html#368 <posix.html#368>`_
-
-   `FTW_DEPTH`:idx:
-     `posix.html#376 <posix.html#376>`_
-
-   `FTW_DNR`:idx:
-     `posix.html#369 <posix.html#369>`_
-
-   `FTW_DP`:idx:
-     `posix.html#370 <posix.html#370>`_
-
-   `FTW_F`:idx:
-     `posix.html#367 <posix.html#367>`_
-
-   `FTW_MOUNT`:idx:
-     `posix.html#375 <posix.html#375>`_
-
-   `FTW_NS`:idx:
-     `posix.html#371 <posix.html#371>`_
-
-   `FTW_PHYS`:idx:
-     `posix.html#374 <posix.html#374>`_
-
-   `FTW_SL`:idx:
-     `posix.html#372 <posix.html#372>`_
-
-   `FTW_SLN`:idx:
-     `posix.html#373 <posix.html#373>`_
-
-   `F_ULOCK`:idx:
-     `posix.html#499 <posix.html#499>`_
-
-   `functional`:idx:
-     `manual.html#163 <manual.html#163>`_
-
-   `F_UNLCK`:idx:
-     `posix.html#311 <posix.html#311>`_
-
-   `funtions`:idx:
-     `manual.html#199 <manual.html#199>`_
-
-   `F_WRLCK`:idx:
-     `posix.html#312 <posix.html#312>`_
-
-   `GC_disable`:idx:
-     `system.html#457 <system.html#457>`_
-
-   `GC_disableMarkAndSweep`:idx:
-     `system.html#463 <system.html#463>`_
-
-   `GC_enable`:idx:
-     `system.html#458 <system.html#458>`_
-
-   `GC_enableMarkAndSweep`:idx:
-     `system.html#462 <system.html#462>`_
-
-   `GC_fullCollect`:idx:
-     `system.html#459 <system.html#459>`_
-
-   `GC_getStatistics`:idx:
-     `system.html#464 <system.html#464>`_
-
-   `GC_ref`:idx:
-     * `system.html#465 <system.html#465>`_
-     * `system.html#466 <system.html#466>`_
-     * `system.html#467 <system.html#467>`_
-
-   `GC_setStrategy`:idx:
-     `system.html#461 <system.html#461>`_
-
-   `GC_unref`:idx:
-     * `system.html#468 <system.html#468>`_
-     * `system.html#469 <system.html#469>`_
-     * `system.html#470 <system.html#470>`_
-
-   `generic character types`:idx:
-     `regexprs.html#102 <regexprs.html#102>`_
-
-   `Generics`:idx:
-     `manual.html#208 <manual.html#208>`_
-
-   `getApplicationDir`:idx:
-     `os.html#110 <os.html#110>`_
-
-   `getApplicationFilename`:idx:
-     `os.html#111 <os.html#111>`_
-
-   `getClockStr`:idx:
-     `times.html#112 <times.html#112>`_
-
-   `getColNumber`:idx:
-     `lexbase.html#107 <lexbase.html#107>`_
-
-   `getColumn`:idx:
-     `parsecfg.html#107 <parsecfg.html#107>`_
-
-   `getConfigDir`:idx:
-     `os.html#115 <os.html#115>`_
-
-   `getcontext`:idx:
-     `posix.html#1188 <posix.html#1188>`_
-
-   `get_crc_table`:idx:
-     `zlib.html#186 <zlib.html#186>`_
-
-   `getCurrentDir`:idx:
-     `os.html#112 <os.html#112>`_
-
-   `getCurrentExceptionMsg`:idx:
-     `system.html#428 <system.html#428>`_
-
-   `getCurrentLine`:idx:
-     `lexbase.html#106 <lexbase.html#106>`_
-
-   `getcwd`:idx:
-     `posix.html#990 <posix.html#990>`_
-
-   `getdate`:idx:
-     `posix.html#1103 <posix.html#1103>`_
-
-   `getDateStr`:idx:
-     `times.html#111 <times.html#111>`_
-
-   `getegid`:idx:
-     `posix.html#991 <posix.html#991>`_
-
-   `getEnv`:idx:
-     `os.html#143 <os.html#143>`_
-
-   `GetEnvironmentStringsA`:idx:
-     `os.html#150 <os.html#150>`_
-
-   `geteuid`:idx:
-     `posix.html#992 <posix.html#992>`_
-
-   `getFilename`:idx:
-     `parsecfg.html#109 <parsecfg.html#109>`_
-
-   `getFilePos`:idx:
-     `system.html#507 <system.html#507>`_
-
-   `getFileSize`:idx:
-     `system.html#499 <system.html#499>`_
-
-   `getFreeMem`:idx:
-     `system.html#434 <system.html#434>`_
-
-   `getgid`:idx:
-     `posix.html#993 <posix.html#993>`_
-
-   `getGMTime`:idx:
-     `times.html#107 <times.html#107>`_
-
-   `getgrent`:idx:
-     `posix.html#837 <posix.html#837>`_
-
-   `getgrgid`:idx:
-     `posix.html#833 <posix.html#833>`_
-
-   `getgrgid_r`:idx:
-     `posix.html#835 <posix.html#835>`_
-
-   `getgrnam`:idx:
-     `posix.html#834 <posix.html#834>`_
-
-   `getgrnam_r`:idx:
-     `posix.html#836 <posix.html#836>`_
-
-   `getgroups`:idx:
-     `posix.html#994 <posix.html#994>`_
-
-   `getHomeDir`:idx:
-     `os.html#114 <os.html#114>`_
-
-   `gethostid`:idx:
-     `posix.html#995 <posix.html#995>`_
-
-   `gethostname`:idx:
-     `posix.html#996 <posix.html#996>`_
-
-   `getLastModificationTime`:idx:
-     `os.html#140 <os.html#140>`_
-
-   `getLine`:idx:
-     `parsecfg.html#108 <parsecfg.html#108>`_
-
-   `getLocalTime`:idx:
-     `times.html#106 <times.html#106>`_
-
-   `getlogin`:idx:
-     `posix.html#997 <posix.html#997>`_
-
-   `getlogin_r`:idx:
-     `posix.html#998 <posix.html#998>`_
-
-   `getOccupiedMem`:idx:
-     `system.html#433 <system.html#433>`_
-
-   `getopt`:idx:
-     * `parseopt.html#106 <parseopt.html#106>`_
-     * `posix.html#999 <posix.html#999>`_
-
-   `getpgid`:idx:
-     `posix.html#1000 <posix.html#1000>`_
-
-   `getpgrp`:idx:
-     `posix.html#1001 <posix.html#1001>`_
-
-   `getpid`:idx:
-     `posix.html#1002 <posix.html#1002>`_
-
-   `getppid`:idx:
-     `posix.html#1003 <posix.html#1003>`_
-
-   `getpwent`:idx:
-     `posix.html#864 <posix.html#864>`_
-
-   `getpwnam`:idx:
-     `posix.html#859 <posix.html#859>`_
-
-   `getpwnam_r`:idx:
-     `posix.html#861 <posix.html#861>`_
-
-   `getpwuid`:idx:
-     `posix.html#860 <posix.html#860>`_
-
-   `getpwuid_r`:idx:
-     `posix.html#862 <posix.html#862>`_
-
-   `getRefcount`:idx:
-     `system.html#427 <system.html#427>`_
-
-   `getRestOfCommandLine`:idx:
-     `parseopt.html#105 <parseopt.html#105>`_
-
-   `getsid`:idx:
-     `posix.html#1004 <posix.html#1004>`_
-
-   `getStartMilsecs`:idx:
-     `times.html#116 <times.html#116>`_
-
-   `getStream`:idx:
-     `zipfiles.html#109 <zipfiles.html#109>`_
-
-   `getTime`:idx:
-     `times.html#105 <times.html#105>`_
-
-   `getTotalMem`:idx:
-     `system.html#435 <system.html#435>`_
-
-   `getuid`:idx:
-     `posix.html#1005 <posix.html#1005>`_
-
-   `getwd`:idx:
-     `posix.html#1006 <posix.html#1006>`_
-
-   `glob`:idx:
-     `posix.html#831 <posix.html#831>`_
-
-   `GLOB_ABORTED`:idx:
-     `posix.html#385 <posix.html#385>`_
-
-   `GLOB_APPEND`:idx:
-     `posix.html#378 <posix.html#378>`_
-
-   `GLOB_DOOFFS`:idx:
-     `posix.html#379 <posix.html#379>`_
-
-   `GLOB_ERR`:idx:
-     `posix.html#380 <posix.html#380>`_
-
-   `globfree`:idx:
-     `posix.html#832 <posix.html#832>`_
-
-   `GLOB_MARK`:idx:
-     `posix.html#381 <posix.html#381>`_
-
-   `GLOB_NOCHECK`:idx:
-     `posix.html#382 <posix.html#382>`_
-
-   `GLOB_NOESCAPE`:idx:
-     `posix.html#383 <posix.html#383>`_
-
-   `GLOB_NOMATCH`:idx:
-     `posix.html#386 <posix.html#386>`_
-
-   `GLOB_NOSORT`:idx:
-     `posix.html#384 <posix.html#384>`_
-
-   `GLOB_NOSPACE`:idx:
-     `posix.html#387 <posix.html#387>`_
-
-   `GLOB_NOSYS`:idx:
-     `posix.html#388 <posix.html#388>`_
-
-   `gmtime`:idx:
-     `posix.html#1104 <posix.html#1104>`_
-
-   `gmtime_r`:idx:
-     `posix.html#1105 <posix.html#1105>`_
-
-   `gzclose`:idx:
-     `zlib.html#172 <zlib.html#172>`_
-
-   `gzdopen`:idx:
-     `zlib.html#158 <zlib.html#158>`_
-
-   `gzeof`:idx:
-     `zlib.html#171 <zlib.html#171>`_
-
-   `gzerror`:idx:
-     `zlib.html#173 <zlib.html#173>`_
-
-   `gzFile`:idx:
-     `zlib.html#115 <zlib.html#115>`_
-
-   `gzflush`:idx:
-     `zlib.html#167 <zlib.html#167>`_
-
-   `gzgetc`:idx:
-     `zlib.html#166 <zlib.html#166>`_
-
-   `gzgets`:idx:
-     `zlib.html#164 <zlib.html#164>`_
-
-   `gzopen`:idx:
-     `zlib.html#157 <zlib.html#157>`_
-
-   `gzprintf`:idx:
-     `zlib.html#162 <zlib.html#162>`_
-
-   `gzputc`:idx:
-     `zlib.html#165 <zlib.html#165>`_
-
-   `gzputs`:idx:
-     `zlib.html#163 <zlib.html#163>`_
-
-   `gzread`:idx:
-     `zlib.html#160 <zlib.html#160>`_
-
-   `gzrewind`:idx:
-     `zlib.html#169 <zlib.html#169>`_
-
-   `gzseek`:idx:
-     `zlib.html#168 <zlib.html#168>`_
-
-   `gzsetparams`:idx:
-     `zlib.html#159 <zlib.html#159>`_
-
-   `gztell`:idx:
-     `zlib.html#170 <zlib.html#170>`_
-
-   `gzwrite`:idx:
-     `zlib.html#161 <zlib.html#161>`_
-
-   `HandleCR`:idx:
-     `lexbase.html#108 <lexbase.html#108>`_
-
-   `HandleLF`:idx:
-     `lexbase.html#109 <lexbase.html#109>`_
-
-   `hash`:idx:
-     * `hashes.html#103 <hashes.html#103>`_
-     * `hashes.html#104 <hashes.html#104>`_
-     * `hashes.html#105 <hashes.html#105>`_
-     * `hashes.html#106 <hashes.html#106>`_
-     * `hashes.html#107 <hashes.html#107>`_
-
-   `hashData`:idx:
-     `hashes.html#102 <hashes.html#102>`_
-
-   `hashIgnoreCase`:idx:
-     `hashes.html#109 <hashes.html#109>`_
-
-   `hashIgnoreStyle`:idx:
-     `hashes.html#108 <hashes.html#108>`_
-
-   `hasKey`:idx:
-     `strtabs.html#108 <strtabs.html#108>`_
-
-   `header`:idx:
-     `nimrodc.html#105 <nimrodc.html#105>`_
-
-   `high`:idx:
-     `system.html#118 <system.html#118>`_
-
-   `hint`:idx:
-     * `manual.html#220 <manual.html#220>`_
-     * `manual.html#228 <manual.html#228>`_
-
-   `htonl`:idx:
-     `posix.html#792 <posix.html#792>`_
-
-   `htons`:idx:
-     `posix.html#793 <posix.html#793>`_
-
-   `hypot`:idx:
-     `math.html#123 <math.html#123>`_
-
-   `iconv`:idx:
-     `posix.html#841 <posix.html#841>`_
-
-   `iconv_close`:idx:
-     `posix.html#842 <posix.html#842>`_
-
-   `iconv_open`:idx:
-     `posix.html#840 <posix.html#840>`_
-
-   `identifier`:idx:
-     `manual.html#105 <manual.html#105>`_
-
-   `Identifiers`:idx:
-     `manual.html#116 <manual.html#116>`_
-
-   `if`:idx:
-     `manual.html#181 <manual.html#181>`_
-
-   `implicit block`:idx:
-     `manual.html#206 <manual.html#206>`_
-
-   `import`:idx:
-     `manual.html#216 <manual.html#216>`_
-
-   `importc`:idx:
-     `nimrodc.html#101 <nimrodc.html#101>`_
-
-   `in`:idx:
-     `system.html#355 <system.html#355>`_
-
-   `inc`:idx:
-     `system.html#156 <system.html#156>`_
-
-   `incl`:idx:
-     `system.html#164 <system.html#164>`_
-
-   `indentation sensitive`:idx:
-     `manual.html#113 <manual.html#113>`_
-
-   `inet_addr`:idx:
-     `posix.html#796 <posix.html#796>`_
-
-   `inet_ntoa`:idx:
-     `posix.html#797 <posix.html#797>`_
-
-   `inet_ntop`:idx:
-     `posix.html#798 <posix.html#798>`_
-
-   `inet_pton`:idx:
-     `posix.html#799 <posix.html#799>`_
-
-   `inf`:idx:
-     `system.html#429 <system.html#429>`_
-
-   `inflate`:idx:
-     `zlib.html#145 <zlib.html#145>`_
-
-   `inflateEnd`:idx:
-     `zlib.html#146 <zlib.html#146>`_
-
-   `inflateInit`:idx:
-     `zlib.html#179 <zlib.html#179>`_
-
-   `inflateInit2`:idx:
-     `zlib.html#183 <zlib.html#183>`_
-
-   `inflateInit2u`:idx:
-     `zlib.html#181 <zlib.html#181>`_
-
-   `inflateInitu`:idx:
-     `zlib.html#177 <zlib.html#177>`_
-
-   `inflateReset`:idx:
-     `zlib.html#153 <zlib.html#153>`_
-
-   `inflateSetDictionary`:idx:
-     `zlib.html#151 <zlib.html#151>`_
-
-   `inflateSync`:idx:
-     `zlib.html#152 <zlib.html#152>`_
-
-   `inflateSyncPoint`:idx:
-     `zlib.html#185 <zlib.html#185>`_
-
-   `info`:idx:
-     `dialogs.html#102 <dialogs.html#102>`_
-
-   `information hiding`:idx:
-     `manual.html#214 <manual.html#214>`_
-
-   `init`:idx:
-     `parseopt.html#103 <parseopt.html#103>`_
-
-   `inline`:idx:
-     `manual.html#168 <manual.html#168>`_
-
-   `in_Operator`:idx:
-     `system.html#354 <system.html#354>`_
-
-   `in_Operator`:idx:
-     * `strutils.html#124 <strutils.html#124>`_
-     * `strutils.html#125 <strutils.html#125>`_
-
-   `int`:idx:
-     `system.html#101 <system.html#101>`_
-
-   `int16`:idx:
-     `system.html#103 <system.html#103>`_
-
-   `int32`:idx:
-     `system.html#104 <system.html#104>`_
-
-   `int64`:idx:
-     `system.html#105 <system.html#105>`_
-
-   `int8`:idx:
-     `system.html#102 <system.html#102>`_
-
-   `intToStr`:idx:
-     `strutils.html#127 <strutils.html#127>`_
-
-   `IPC_CREAT`:idx:
-     `posix.html#642 <posix.html#642>`_
-
-   `IPC_EXCL`:idx:
-     `posix.html#643 <posix.html#643>`_
-
-   `IPC_NOWAIT`:idx:
-     `posix.html#644 <posix.html#644>`_
-
-   `IPC_PRIVATE`:idx:
-     `posix.html#645 <posix.html#645>`_
-
-   `IPC_RMID`:idx:
-     `posix.html#646 <posix.html#646>`_
-
-   `IPC_SET`:idx:
-     `posix.html#647 <posix.html#647>`_
-
-   `IPC_STAT`:idx:
-     `posix.html#648 <posix.html#648>`_
-
-   `is`:idx:
-     `system.html#357 <system.html#357>`_
-
-   `isatty`:idx:
-     `posix.html#1007 <posix.html#1007>`_
-
-   `isMainModule`:idx:
-     `system.html#390 <system.html#390>`_
-
-   `isNil`:idx:
-     * `system.html#444 <system.html#444>`_
-     * `system.html#445 <system.html#445>`_
-     * `system.html#446 <system.html#446>`_
-     * `system.html#447 <system.html#447>`_
-     * `system.html#448 <system.html#448>`_
-     * `system.html#449 <system.html#449>`_
-
-   `is_not`:idx:
-     `system.html#358 <system.html#358>`_
-
-   `isPowerOfTwo`:idx:
-     `math.html#105 <math.html#105>`_
-
-   `items`:idx:
-     * `system.html#438 <system.html#438>`_
-     * `system.html#439 <system.html#439>`_
-     * `system.html#440 <system.html#440>`_
-     * `system.html#441 <system.html#441>`_
-     * `system.html#442 <system.html#442>`_
-     * `system.html#443 <system.html#443>`_
-
-   `iterator`:idx:
-     `manual.html#205 <manual.html#205>`_
-
-   `iterOverEnvironment`:idx:
-     `os.html#152 <os.html#152>`_
-
-   `JavaScript`:idx:
-     `nimrodc.html#116 <nimrodc.html#116>`_
-
-   `JoinPath`:idx:
-     * `os.html#118 <os.html#118>`_
-     * `os.html#120 <os.html#120>`_
-
-   `keywords`:idx:
-     `manual.html#117 <manual.html#117>`_
-
-   `kill`:idx:
-     `posix.html#1123 <posix.html#1123>`_
-
-   `killpg`:idx:
-     `posix.html#1124 <posix.html#1124>`_
-
-   `l-values`:idx:
-     `manual.html#107 <manual.html#107>`_
-
-   `LC_ALL`:idx:
-     `posix.html#444 <posix.html#444>`_
-
-   `LC_COLLATE`:idx:
-     `posix.html#445 <posix.html#445>`_
-
-   `LC_CTYPE`:idx:
-     `posix.html#446 <posix.html#446>`_
-
-   `lchown`:idx:
-     `posix.html#1008 <posix.html#1008>`_
-
-   `LC_MESSAGES`:idx:
-     `posix.html#447 <posix.html#447>`_
-
-   `LC_MONETARY`:idx:
-     `posix.html#448 <posix.html#448>`_
-
-   `LC_NUMERIC`:idx:
-     `posix.html#449 <posix.html#449>`_
-
-   `LC_TIME`:idx:
-     `posix.html#450 <posix.html#450>`_
-
-   `len`:idx:
-     * `system.html#159 <system.html#159>`_
-     * `system.html#160 <system.html#160>`_
-     * `system.html#161 <system.html#161>`_
-     * `system.html#162 <system.html#162>`_
-     * `system.html#163 <system.html#163>`_
-     * `strtabs.html#109 <strtabs.html#109>`_
-
-   `line feed`:idx:
-     `manual.html#123 <manual.html#123>`_
-
-   `line_dir`:idx:
-     `nimrodc.html#108 <nimrodc.html#108>`_
-
-   `lines`:idx:
-     `system.html#508 <system.html#508>`_
-
-   `line_trace`:idx:
-     `nimrodc.html#110 <nimrodc.html#110>`_
-
-   `link`:idx:
-     `posix.html#1009 <posix.html#1009>`_
-
-   `lio_listio`:idx:
-     `posix.html#791 <posix.html#791>`_
-
-   `LIO_NOP`:idx:
-     `posix.html#210 <posix.html#210>`_
-
-   `LIO_NOWAIT`:idx:
-     `posix.html#211 <posix.html#211>`_
-
-   `LIO_READ`:idx:
-     `posix.html#212 <posix.html#212>`_
-
-   `LIO_WAIT`:idx:
-     `posix.html#213 <posix.html#213>`_
-
-   `LIO_WRITE`:idx:
-     `posix.html#214 <posix.html#214>`_
-
-   `Literal strings`:idx:
-     `manual.html#119 <manual.html#119>`_
-
-   `ln`:idx:
-     `math.html#111 <math.html#111>`_
-
-   `localeconv`:idx:
-     `posix.html#846 <posix.html#846>`_
-
-   `localtime`:idx:
-     `posix.html#1106 <posix.html#1106>`_
-
-   `localtime_r`:idx:
-     `posix.html#1107 <posix.html#1107>`_
-
-   `locations`:idx:
-     `manual.html#101 <manual.html#101>`_
-
-   `lockf`:idx:
-     `posix.html#1010 <posix.html#1010>`_
-
-   `log10`:idx:
-     `math.html#112 <math.html#112>`_
-
-   `log2`:idx:
-     `math.html#113 <math.html#113>`_
-
-   `low`:idx:
-     `system.html#119 <system.html#119>`_
-
-   `lseek`:idx:
-     `posix.html#1011 <posix.html#1011>`_
-
-   `lstat`:idx:
-     `posix.html#1061 <posix.html#1061>`_
-
-   `Macros`:idx:
-     `manual.html#211 <manual.html#211>`_
-
-   `makecontext`:idx:
-     `posix.html#1189 <posix.html#1189>`_
-
-   `MAP_FAILED`:idx:
-     `posix.html#686 <posix.html#686>`_
-
-   `MAP_FIXED`:idx:
-     `posix.html#680 <posix.html#680>`_
-
-   `MAP_PRIVATE`:idx:
-     `posix.html#679 <posix.html#679>`_
-
-   `MAP_SHARED`:idx:
-     `posix.html#678 <posix.html#678>`_
-
-   `match`:idx:
-     * `regexprs.html#106 <regexprs.html#106>`_
-     * `regexprs.html#107 <regexprs.html#107>`_
-
-   `matchLen`:idx:
-     `regexprs.html#108 <regexprs.html#108>`_
-
-   `math`:idx:
-     `nimrodc.html#118 <nimrodc.html#118>`_
-
-   `max`:idx:
-     * `system.html#268 <system.html#268>`_
-     * `system.html#269 <system.html#269>`_
-     * `system.html#270 <system.html#270>`_
-     * `system.html#271 <system.html#271>`_
-     * `system.html#272 <system.html#272>`_
-     * `system.html#319 <system.html#319>`_
-
-   `MaxSubpatterns`:idx:
-     `regexprs.html#105 <regexprs.html#105>`_
-
-   `MCL_CURRENT`:idx:
-     `posix.html#684 <posix.html#684>`_
-
-   `MCL_FUTURE`:idx:
-     `posix.html#685 <posix.html#685>`_
-
-   `methods`:idx:
-     `manual.html#198 <manual.html#198>`_
-
-   `min`:idx:
-     * `system.html#263 <system.html#263>`_
-     * `system.html#264 <system.html#264>`_
-     * `system.html#265 <system.html#265>`_
-     * `system.html#266 <system.html#266>`_
-     * `system.html#267 <system.html#267>`_
-     * `system.html#318 <system.html#318>`_
-
-   `MINSIGSTKSZ`:idx:
-     `posix.html#766 <posix.html#766>`_
-
-   `mkdir`:idx:
-     `posix.html#1062 <posix.html#1062>`_
-
-   `mkfifo`:idx:
-     `posix.html#1063 <posix.html#1063>`_
-
-   `mknod`:idx:
-     `posix.html#1064 <posix.html#1064>`_
-
-   `mktime`:idx:
-     `posix.html#1108 <posix.html#1108>`_
-
-   `mlock`:idx:
-     `posix.html#1078 <posix.html#1078>`_
-
-   `mlockall`:idx:
-     `posix.html#1079 <posix.html#1079>`_
-
-   `mmap`:idx:
-     `posix.html#1080 <posix.html#1080>`_
-
-   `MM_APPL`:idx:
-     `posix.html#346 <posix.html#346>`_
-
-   `MM_CONSOLE`:idx:
-     `posix.html#357 <posix.html#357>`_
-
-   `MM_ERROR`:idx:
-     `posix.html#352 <posix.html#352>`_
-
-   `MM_FIRM`:idx:
-     `posix.html#345 <posix.html#345>`_
-
-   `MM_HALT`:idx:
-     `posix.html#351 <posix.html#351>`_
-
-   `MM_HARD`:idx:
-     `posix.html#343 <posix.html#343>`_
-
-   `MM_INFO`:idx:
-     `posix.html#354 <posix.html#354>`_
-
-   `MM_NOCON`:idx:
-     `posix.html#361 <posix.html#361>`_
-
-   `MM_NOMSG`:idx:
-     `posix.html#360 <posix.html#360>`_
-
-   `MM_NOSEV`:idx:
-     `posix.html#355 <posix.html#355>`_
-
-   `MM_NOTOK`:idx:
-     `posix.html#359 <posix.html#359>`_
-
-   `MM_NRECOV`:idx:
-     `posix.html#350 <posix.html#350>`_
-
-   `MM_NULLACT`:idx:
-     `posix.html#125 <posix.html#125>`_
-
-   `MM_NULLLBL`:idx:
-     `posix.html#121 <posix.html#121>`_
-
-   `MM_NULLMC`:idx:
-     `posix.html#123 <posix.html#123>`_
-
-   `MM_NULLSEV`:idx:
-     `posix.html#122 <posix.html#122>`_
-
-   `MM_NULLTAG`:idx:
-     `posix.html#126 <posix.html#126>`_
-
-   `MM_NULLTXT`:idx:
-     `posix.html#124 <posix.html#124>`_
-
-   `MM_OK`:idx:
-     `posix.html#358 <posix.html#358>`_
-
-   `MM_OPSYS`:idx:
-     `posix.html#348 <posix.html#348>`_
-
-   `MM_PRINT`:idx:
-     `posix.html#356 <posix.html#356>`_
-
-   `MM_RECOVER`:idx:
-     `posix.html#349 <posix.html#349>`_
-
-   `MM_SOFT`:idx:
-     `posix.html#344 <posix.html#344>`_
-
-   `MM_UTIL`:idx:
-     `posix.html#347 <posix.html#347>`_
-
-   `MM_WARNING`:idx:
-     `posix.html#353 <posix.html#353>`_
-
-   `mod`:idx:
-     * `system.html#213 <system.html#213>`_
-     * `system.html#214 <system.html#214>`_
-     * `system.html#215 <system.html#215>`_
-     * `system.html#216 <system.html#216>`_
-     * `system.html#217 <system.html#217>`_
-
-   `module`:idx:
-     `manual.html#213 <manual.html#213>`_
-
-   `MON_1`:idx:
-     `posix.html#410 <posix.html#410>`_
-
-   `MON_10`:idx:
-     `posix.html#419 <posix.html#419>`_
-
-   `MON_11`:idx:
-     `posix.html#420 <posix.html#420>`_
-
-   `MON_12`:idx:
-     `posix.html#421 <posix.html#421>`_
-
-   `MON_2`:idx:
-     `posix.html#411 <posix.html#411>`_
-
-   `MON_3`:idx:
-     `posix.html#412 <posix.html#412>`_
-
-   `MON_4`:idx:
-     `posix.html#413 <posix.html#413>`_
-
-   `MON_5`:idx:
-     `posix.html#414 <posix.html#414>`_
-
-   `MON_6`:idx:
-     `posix.html#415 <posix.html#415>`_
-
-   `MON_7`:idx:
-     `posix.html#416 <posix.html#416>`_
-
-   `MON_8`:idx:
-     `posix.html#417 <posix.html#417>`_
-
-   `MON_9`:idx:
-     `posix.html#418 <posix.html#418>`_
-
-   `moveFile`:idx:
-     `os.html#135 <os.html#135>`_
-
-   `moveMem`:idx:
-     `system.html#409 <system.html#409>`_
-
-   `mprotect`:idx:
-     `posix.html#1081 <posix.html#1081>`_
-
-   `mq_close`:idx:
-     `posix.html#849 <posix.html#849>`_
-
-   `mq_getattr`:idx:
-     `posix.html#850 <posix.html#850>`_
-
-   `mq_notify`:idx:
-     `posix.html#851 <posix.html#851>`_
-
-   `mq_open`:idx:
-     `posix.html#852 <posix.html#852>`_
-
-   `mq_receive`:idx:
-     `posix.html#853 <posix.html#853>`_
-
-   `mq_send`:idx:
-     `posix.html#854 <posix.html#854>`_
-
-   `mq_setattr`:idx:
-     `posix.html#855 <posix.html#855>`_
-
-   `mq_timedreceive`:idx:
-     `posix.html#856 <posix.html#856>`_
-
-   `mq_timedsend`:idx:
-     `posix.html#857 <posix.html#857>`_
-
-   `mq_unlink`:idx:
-     `posix.html#858 <posix.html#858>`_
-
-   `MS_ASYNC`:idx:
-     `posix.html#681 <posix.html#681>`_
-
-   `MS_INVALIDATE`:idx:
-     `posix.html#683 <posix.html#683>`_
-
-   `MS_SYNC`:idx:
-     `posix.html#682 <posix.html#682>`_
-
-   `msync`:idx:
-     `posix.html#1082 <posix.html#1082>`_
-
-   `munlock`:idx:
-     `posix.html#1083 <posix.html#1083>`_
-
-   `munlockall`:idx:
-     `posix.html#1084 <posix.html#1084>`_
-
-   `munmap`:idx:
-     `posix.html#1085 <posix.html#1085>`_
-
-   `nan`:idx:
-     `system.html#431 <system.html#431>`_
-
-   `nanosleep`:idx:
-     `posix.html#1109 <posix.html#1109>`_
-
-   `Natural`:idx:
-     `system.html#126 <system.html#126>`_
-
-   `neginf`:idx:
-     `system.html#430 <system.html#430>`_
-
-   `new`:idx:
-     * `system.html#116 <system.html#116>`_
-     * `system.html#117 <system.html#117>`_
-
-   `newFileStream`:idx:
-     * `streams.html#120 <streams.html#120>`_
-     * `streams.html#121 <streams.html#121>`_
-
-   `newline`:idx:
-     `manual.html#121 <manual.html#121>`_
-
-   `NewLines`:idx:
-     `lexbase.html#102 <lexbase.html#102>`_
-
-   `newSeq`:idx:
-     `system.html#158 <system.html#158>`_
-
-   `newString`:idx:
-     `system.html#406 <system.html#406>`_
-
-   `newStringStream`:idx:
-     `streams.html#117 <streams.html#117>`_
-
-   `newStringTable`:idx:
-     * `strtabs.html#104 <strtabs.html#104>`_
-     * `strtabs.html#105 <strtabs.html#105>`_
-
-   `next`:idx:
-     * `parseopt.html#104 <parseopt.html#104>`_
-     * `parsecfg.html#106 <parsecfg.html#106>`_
-
-   `nextPowerOfTwo`:idx:
-     `math.html#106 <math.html#106>`_
-
-   `nftw`:idx:
-     `posix.html#830 <posix.html#830>`_
-
-   `nice`:idx:
-     `posix.html#1012 <posix.html#1012>`_
-
-   `nimcall`:idx:
-     `manual.html#170 <manual.html#170>`_
-
-   `NimrodMajor`:idx:
-     `system.html#394 <system.html#394>`_
-
-   `NimrodMinor`:idx:
-     `system.html#395 <system.html#395>`_
-
-   `NimrodPatch`:idx:
-     `system.html#396 <system.html#396>`_
-
-   `NimrodVersion`:idx:
-     `system.html#393 <system.html#393>`_
-
-   `nl`:idx:
-     `strutils.html#104 <strutils.html#104>`_
-
-   `NL_CAT_LOCALE`:idx:
-     `posix.html#769 <posix.html#769>`_
-
-   `nl_langinfo`:idx:
-     `posix.html#843 <posix.html#843>`_
-
-   `NL_SETD`:idx:
-     `posix.html#768 <posix.html#768>`_
-
-   `noconv`:idx:
-     `manual.html#173 <manual.html#173>`_
-
-   `no_decl`:idx:
-     `nimrodc.html#104 <nimrodc.html#104>`_
-
-   `NOEXPR`:idx:
-     `posix.html#442 <posix.html#442>`_
-
-   `normalize`:idx:
-     `strutils.html#111 <strutils.html#111>`_
-
-   `no_static`:idx:
-     `nimrodc.html#107 <nimrodc.html#107>`_
-
-   `not`:idx:
-     * `system.html#115 <system.html#115>`_
-     * `system.html#188 <system.html#188>`_
-     * `system.html#189 <system.html#189>`_
-     * `system.html#190 <system.html#190>`_
-     * `system.html#191 <system.html#191>`_
-     * `system.html#192 <system.html#192>`_
-
-   `not_in`:idx:
-     `system.html#356 <system.html#356>`_
-
-   `ntohl`:idx:
-     `posix.html#794 <posix.html#794>`_
-
-   `ntohs`:idx:
-     `posix.html#795 <posix.html#795>`_
-
-   `Numerical constants`:idx:
-     `manual.html#137 <manual.html#137>`_
-
-   `O_ACCMODE`:idx:
-     `posix.html#322 <posix.html#322>`_
-
-   `O_APPEND`:idx:
-     `posix.html#317 <posix.html#317>`_
-
-   `object`:idx:
-     `manual.html#156 <manual.html#156>`_
-
-   `O_CREAT`:idx:
-     `posix.html#313 <posix.html#313>`_
-
-   `ODBC_ADD_DSN`:idx:
-     `odbcsql.html#621 <odbcsql.html#621>`_
-
-   `ODBC_ADD_SYS_DSN`:idx:
-     `odbcsql.html#624 <odbcsql.html#624>`_
-
-   `ODBC_CONFIG_DSN`:idx:
-     `odbcsql.html#622 <odbcsql.html#622>`_
-
-   `ODBC_CONFIG_SYS_DSN`:idx:
-     `odbcsql.html#625 <odbcsql.html#625>`_
-
-   `ODBC_REMOVE_DSN`:idx:
-     `odbcsql.html#623 <odbcsql.html#623>`_
-
-   `ODBC_REMOVE_SYS_DSN`:idx:
-     `odbcsql.html#626 <odbcsql.html#626>`_
-
-   `O_DSYNC`:idx:
-     `posix.html#318 <posix.html#318>`_
-
-   `O_EXCL`:idx:
-     `posix.html#314 <posix.html#314>`_
-
-   `O_NOCTTY`:idx:
-     `posix.html#315 <posix.html#315>`_
-
-   `O_NONBLOCK`:idx:
-     `posix.html#319 <posix.html#319>`_
-
-   `open`:idx:
-     * `lexbase.html#104 <lexbase.html#104>`_
-     * `parsecfg.html#104 <parsecfg.html#104>`_
-     * `posix.html#813 <posix.html#813>`_
-     * `zipfiles.html#102 <zipfiles.html#102>`_
-
-   `openarray`:idx:
-     `system.html#122 <system.html#122>`_
-
-   `opendir`:idx:
-     `posix.html#801 <posix.html#801>`_
-
-   `OpenFile`:idx:
-     * `system.html#482 <system.html#482>`_
-     * `system.html#483 <system.html#483>`_
-
-   `operator`:idx:
-     `manual.html#139 <manual.html#139>`_
-
-   `Operators`:idx:
-     `manual.html#203 <manual.html#203>`_
-
-   `or`:idx:
-     * `system.html#233 <system.html#233>`_
-     * `system.html#234 <system.html#234>`_
-     * `system.html#235 <system.html#235>`_
-     * `system.html#236 <system.html#236>`_
-     * `system.html#237 <system.html#237>`_
-     * `system.html#321 <system.html#321>`_
-
-   `ord`:idx:
-     `system.html#167 <system.html#167>`_
-
-   `Ordinal types`:idx:
-     `manual.html#142 <manual.html#142>`_
-
-   `O_RDONLY`:idx:
-     `posix.html#323 <posix.html#323>`_
-
-   `O_RDWR`:idx:
-     `posix.html#324 <posix.html#324>`_
-
-   `O_RSYNC`:idx:
-     `posix.html#320 <posix.html#320>`_
-
-   `OSError`:idx:
-     `os.html#147 <os.html#147>`_
-
-   `O_SYNC`:idx:
-     `posix.html#321 <posix.html#321>`_
-
-   `O_TRUNC`:idx:
-     `posix.html#316 <posix.html#316>`_
-
-   `O_WRONLY`:idx:
-     `posix.html#325 <posix.html#325>`_
-
-   `pairs`:idx:
-     `strtabs.html#110 <strtabs.html#110>`_
-
-   `P_ALL`:idx:
-     `posix.html#716 <posix.html#716>`_
-
-   `paramCount`:idx:
-     `os.html#145 <os.html#145>`_
-
-   `paramStr`:idx:
-     `os.html#146 <os.html#146>`_
-
-   `ParDir`:idx:
-     `os.html#102 <os.html#102>`_
-
-   `parentDir`:idx:
-     `os.html#122 <os.html#122>`_
-
-   `ParseBiggestInt`:idx:
-     `strutils.html#129 <strutils.html#129>`_
-
-   `parseCmdLine`:idx:
-     `os.html#156 <os.html#156>`_
-
-   `ParseFloat`:idx:
-     `strutils.html#130 <strutils.html#130>`_
-
-   `ParseInt`:idx:
-     `strutils.html#128 <strutils.html#128>`_
-
-   `pathconf`:idx:
-     `posix.html#1013 <posix.html#1013>`_
-
-   `PathSep`:idx:
-     `os.html#105 <os.html#105>`_
-
-   `pause`:idx:
-     `posix.html#1014 <posix.html#1014>`_
-
-   `pbyte`:idx:
-     `zlib.html#106 <zlib.html#106>`_
-
-   `pbytef`:idx:
-     `zlib.html#107 <zlib.html#107>`_
-
-   `PC_2_SYMLINKS`:idx:
-     `posix.html#500 <posix.html#500>`_
-
-   `PC_ALLOC_SIZE_MIN`:idx:
-     `posix.html#501 <posix.html#501>`_
-
-   `PC_ASYNC_IO`:idx:
-     `posix.html#502 <posix.html#502>`_
-
-   `PC_CHOWN_RESTRICTED`:idx:
-     `posix.html#503 <posix.html#503>`_
-
-   `PC_FILESIZEBITS`:idx:
-     `posix.html#504 <posix.html#504>`_
-
-   `PC_LINK_MAX`:idx:
-     `posix.html#505 <posix.html#505>`_
-
-   `PC_MAX_CANON`:idx:
-     `posix.html#506 <posix.html#506>`_
-
-   `PC_MAX_INPUT`:idx:
-     `posix.html#507 <posix.html#507>`_
-
-   `PC_NAME_MAX`:idx:
-     `posix.html#508 <posix.html#508>`_
-
-   `PC_NO_TRUNC`:idx:
-     `posix.html#509 <posix.html#509>`_
-
-   `PC_PATH_MAX`:idx:
-     `posix.html#510 <posix.html#510>`_
-
-   `PC_PIPE_BUF`:idx:
-     `posix.html#511 <posix.html#511>`_
-
-   `PC_PRIO_IO`:idx:
-     `posix.html#512 <posix.html#512>`_
-
-   `PC_REC_INCR_XFER_SIZE`:idx:
-     `posix.html#513 <posix.html#513>`_
-
-   `PC_REC_MIN_XFER_SIZE`:idx:
-     `posix.html#514 <posix.html#514>`_
-
-   `PC_REC_XFER_ALIGN`:idx:
-     `posix.html#515 <posix.html#515>`_
-
-   `PC_SYMLINK_MAX`:idx:
-     `posix.html#516 <posix.html#516>`_
-
-   `PC_SYNC_IO`:idx:
-     `posix.html#517 <posix.html#517>`_
-
-   `PC_VDISABLE`:idx:
-     `posix.html#518 <posix.html#518>`_
-
-   `PFileStream`:idx:
-     `streams.html#118 <streams.html#118>`_
-
-   `PFloat32`:idx:
-     `system.html#386 <system.html#386>`_
-
-   `PFloat64`:idx:
-     `system.html#387 <system.html#387>`_
-
-   `PI`:idx:
-     `math.html#101 <math.html#101>`_
-
-   `PInt32`:idx:
-     `system.html#389 <system.html#389>`_
-
-   `PInt64`:idx:
-     `system.html#388 <system.html#388>`_
-
-   `PInternalState`:idx:
-     `zlib.html#111 <zlib.html#111>`_
-
-   `pipe`:idx:
-     `posix.html#1015 <posix.html#1015>`_
-
-   `PM_STR`:idx:
-     `posix.html#395 <posix.html#395>`_
-
-   `PObject`:idx:
-     `system.html#129 <system.html#129>`_
-
-   `pointer`:idx:
-     `system.html#113 <system.html#113>`_
-
-   `pointers`:idx:
-     `manual.html#159 <manual.html#159>`_
-
-   `Positive`:idx:
-     `system.html#127 <system.html#127>`_
-
-   `POSIX_ASYNC_IO`:idx:
-     `posix.html#475 <posix.html#475>`_
-
-   `POSIX_FADV_DONTNEED`:idx:
-     `posix.html#330 <posix.html#330>`_
-
-   `posix_fadvise`:idx:
-     `posix.html#814 <posix.html#814>`_
-
-   `POSIX_FADV_NOREUSE`:idx:
-     `posix.html#331 <posix.html#331>`_
-
-   `POSIX_FADV_NORMAL`:idx:
-     `posix.html#326 <posix.html#326>`_
-
-   `POSIX_FADV_RANDOM`:idx:
-     `posix.html#328 <posix.html#328>`_
-
-   `POSIX_FADV_SEQUENTIAL`:idx:
-     `posix.html#327 <posix.html#327>`_
-
-   `POSIX_FADV_WILLNEED`:idx:
-     `posix.html#329 <posix.html#329>`_
-
-   `posix_fallocate`:idx:
-     `posix.html#815 <posix.html#815>`_
-
-   `POSIX_MADV_DONTNEED`:idx:
-     `posix.html#691 <posix.html#691>`_
-
-   `posix_madvise`:idx:
-     `posix.html#1086 <posix.html#1086>`_
-
-   `POSIX_MADV_NORMAL`:idx:
-     `posix.html#687 <posix.html#687>`_
-
-   `POSIX_MADV_RANDOM`:idx:
-     `posix.html#689 <posix.html#689>`_
-
-   `POSIX_MADV_SEQUENTIAL`:idx:
-     `posix.html#688 <posix.html#688>`_
-
-   `POSIX_MADV_WILLNEED`:idx:
-     `posix.html#690 <posix.html#690>`_
-
-   `posix_mem_offset`:idx:
-     `posix.html#1087 <posix.html#1087>`_
-
-   `POSIX_PRIO_IO`:idx:
-     `posix.html#476 <posix.html#476>`_
-
-   `posix_spawn`:idx:
-     `posix.html#1167 <posix.html#1167>`_
-
-   `posix_spawnattr_destroy`:idx:
-     `posix.html#1173 <posix.html#1173>`_
-
-   `posix_spawnattr_getflags`:idx:
-     `posix.html#1175 <posix.html#1175>`_
-
-   `posix_spawnattr_getpgroup`:idx:
-     `posix.html#1176 <posix.html#1176>`_
-
-   `posix_spawnattr_getschedparam`:idx:
-     `posix.html#1177 <posix.html#1177>`_
-
-   `posix_spawnattr_getschedpolicy`:idx:
-     `posix.html#1178 <posix.html#1178>`_
-
-   `posix_spawnattr_getsigdefault`:idx:
-     `posix.html#1174 <posix.html#1174>`_
-
-   `posix_spawnattr_getsigmask`:idx:
-     `posix.html#1179 <posix.html#1179>`_
-
-   `posix_spawnattr_init`:idx:
-     `posix.html#1180 <posix.html#1180>`_
-
-   `posix_spawnattr_setflags`:idx:
-     `posix.html#1182 <posix.html#1182>`_
-
-   `posix_spawnattr_setpgroup`:idx:
-     `posix.html#1183 <posix.html#1183>`_
-
-   `posix_spawnattr_setschedparam`:idx:
-     `posix.html#1184 <posix.html#1184>`_
-
-   `posix_spawnattr_setschedpolicy`:idx:
-     `posix.html#1185 <posix.html#1185>`_
-
-   `posix_spawnattr_setsigdefault`:idx:
-     `posix.html#1181 <posix.html#1181>`_
-
-   `posix_spawnattr_setsigmask`:idx:
-     `posix.html#1186 <posix.html#1186>`_
-
-   `posix_spawn_file_actions_addclose`:idx:
-     `posix.html#1168 <posix.html#1168>`_
-
-   `posix_spawn_file_actions_adddup2`:idx:
-     `posix.html#1169 <posix.html#1169>`_
-
-   `posix_spawn_file_actions_addopen`:idx:
-     `posix.html#1170 <posix.html#1170>`_
-
-   `posix_spawn_file_actions_destroy`:idx:
-     `posix.html#1171 <posix.html#1171>`_
-
-   `posix_spawn_file_actions_init`:idx:
-     `posix.html#1172 <posix.html#1172>`_
-
-   `posix_spawnp`:idx:
-     `posix.html#1187 <posix.html#1187>`_
-
-   `POSIX_SPAWN_RESETIDS`:idx:
-     `posix.html#778 <posix.html#778>`_
-
-   `POSIX_SPAWN_SETPGROUP`:idx:
-     `posix.html#779 <posix.html#779>`_
-
-   `POSIX_SPAWN_SETSCHEDPARAM`:idx:
-     `posix.html#780 <posix.html#780>`_
-
-   `POSIX_SPAWN_SETSCHEDULER`:idx:
-     `posix.html#781 <posix.html#781>`_
-
-   `POSIX_SPAWN_SETSIGDEF`:idx:
-     `posix.html#782 <posix.html#782>`_
-
-   `POSIX_SPAWN_SETSIGMASK`:idx:
-     `posix.html#783 <posix.html#783>`_
-
-   `POSIX_SYNC_IO`:idx:
-     `posix.html#477 <posix.html#477>`_
-
-   `POSIX_TYPED_MEM_ALLOCATE`:idx:
-     `posix.html#692 <posix.html#692>`_
-
-   `POSIX_TYPED_MEM_ALLOCATE_CONTIG`:idx:
-     `posix.html#693 <posix.html#693>`_
-
-   `posix_typed_mem_get_info`:idx:
-     `posix.html#1088 <posix.html#1088>`_
-
-   `POSIX_TYPED_MEM_MAP_ALLOCATABLE`:idx:
-     `posix.html#694 <posix.html#694>`_
-
-   `posix_typed_mem_open`:idx:
-     `posix.html#1089 <posix.html#1089>`_
-
-   `pow`:idx:
-     `math.html#127 <math.html#127>`_
-
-   `P_PGID`:idx:
-     `posix.html#718 <posix.html#718>`_
-
-   `P_PID`:idx:
-     `posix.html#717 <posix.html#717>`_
-
-   `pread`:idx:
-     `posix.html#1016 <posix.html#1016>`_
-
-   `pred`:idx:
-     `system.html#155 <system.html#155>`_
-
-   `procedural type`:idx:
-     `manual.html#162 <manual.html#162>`_
-
-   `procedures`:idx:
-     `manual.html#200 <manual.html#200>`_
-
-   `PROT_EXEC`:idx:
-     `posix.html#676 <posix.html#676>`_
-
-   `PROT_NONE`:idx:
-     `posix.html#677 <posix.html#677>`_
-
-   `PROT_READ`:idx:
-     `posix.html#674 <posix.html#674>`_
-
-   `PROT_WRITE`:idx:
-     `posix.html#675 <posix.html#675>`_
-
-   `pselect`:idx:
-     `posix.html#1165 <posix.html#1165>`_
-
-   `PSQLCHAR`:idx:
-     `odbcsql.html#116 <odbcsql.html#116>`_
-
-   `PSQL_DATE_STRUCT`:idx:
-     `odbcsql.html#232 <odbcsql.html#232>`_
-
-   `PSQLDOUBLE`:idx:
-     `odbcsql.html#122 <odbcsql.html#122>`_
-
-   `PSQLFLOAT`:idx:
-     `odbcsql.html#123 <odbcsql.html#123>`_
-
-   `PSQLHANDLE`:idx:
-     `odbcsql.html#124 <odbcsql.html#124>`_
-
-   `PSQLINTEGER`:idx:
-     `odbcsql.html#117 <odbcsql.html#117>`_
-
-   `PSQLREAL`:idx:
-     `odbcsql.html#121 <odbcsql.html#121>`_
-
-   `PSQLSMALLINT`:idx:
-     `odbcsql.html#119 <odbcsql.html#119>`_
-
-   `PSQL_TIMESTAMP_STRUCT`:idx:
-     `odbcsql.html#236 <odbcsql.html#236>`_
-
-   `PSQL_TIME_STRUCT`:idx:
-     `odbcsql.html#234 <odbcsql.html#234>`_
-
-   `PSQLUINTEGER`:idx:
-     `odbcsql.html#118 <odbcsql.html#118>`_
-
-   `PSQLUSMALLINT`:idx:
-     `odbcsql.html#120 <odbcsql.html#120>`_
-
-   `PStream`:idx:
-     `streams.html#101 <streams.html#101>`_
-
-   `PStringStream`:idx:
-     `streams.html#115 <streams.html#115>`_
-
-   `PStringTable`:idx:
-     `strtabs.html#103 <strtabs.html#103>`_
-
-   `pthread_atfork`:idx:
-     `posix.html#867 <posix.html#867>`_
-
-   `pthread_attr_destroy`:idx:
-     `posix.html#868 <posix.html#868>`_
-
-   `pthread_attr_getdetachstate`:idx:
-     `posix.html#869 <posix.html#869>`_
-
-   `pthread_attr_getguardsize`:idx:
-     `posix.html#870 <posix.html#870>`_
-
-   `pthread_attr_getinheritsched`:idx:
-     `posix.html#871 <posix.html#871>`_
-
-   `pthread_attr_getschedparam`:idx:
-     `posix.html#872 <posix.html#872>`_
-
-   `pthread_attr_getschedpolicy`:idx:
-     `posix.html#873 <posix.html#873>`_
-
-   `pthread_attr_getscope`:idx:
-     `posix.html#874 <posix.html#874>`_
-
-   `pthread_attr_getstack`:idx:
-     `posix.html#875 <posix.html#875>`_
-
-   `pthread_attr_getstackaddr`:idx:
-     `posix.html#876 <posix.html#876>`_
-
-   `pthread_attr_getstacksize`:idx:
-     `posix.html#877 <posix.html#877>`_
-
-   `pthread_attr_init`:idx:
-     `posix.html#878 <posix.html#878>`_
-
-   `pthread_attr_setdetachstate`:idx:
-     `posix.html#879 <posix.html#879>`_
-
-   `pthread_attr_setguardsize`:idx:
-     `posix.html#880 <posix.html#880>`_
-
-   `pthread_attr_setinheritsched`:idx:
-     `posix.html#881 <posix.html#881>`_
-
-   `pthread_attr_setschedparam`:idx:
-     `posix.html#882 <posix.html#882>`_
-
-   `pthread_attr_setschedpolicy`:idx:
-     `posix.html#883 <posix.html#883>`_
-
-   `pthread_attr_setscope`:idx:
-     `posix.html#884 <posix.html#884>`_
-
-   `pthread_attr_setstack`:idx:
-     `posix.html#885 <posix.html#885>`_
-
-   `pthread_attr_setstackaddr`:idx:
-     `posix.html#886 <posix.html#886>`_
-
-   `pthread_attr_setstacksize`:idx:
-     `posix.html#887 <posix.html#887>`_
-
-   `pthread_barrierattr_destroy`:idx:
-     `posix.html#891 <posix.html#891>`_
-
-   `pthread_barrierattr_getpshared`:idx:
-     `posix.html#892 <posix.html#892>`_
-
-   `pthread_barrierattr_init`:idx:
-     `posix.html#893 <posix.html#893>`_
-
-   `pthread_barrierattr_setpshared`:idx:
-     `posix.html#894 <posix.html#894>`_
-
-   `pthread_barrier_destroy`:idx:
-     `posix.html#888 <posix.html#888>`_
-
-   `pthread_barrier_init`:idx:
-     `posix.html#889 <posix.html#889>`_
-
-   `PTHREAD_BARRIER_SERIAL_THREAD`:idx:
-     `posix.html#451 <posix.html#451>`_
-
-   `pthread_barrier_wait`:idx:
-     `posix.html#890 <posix.html#890>`_
-
-   `pthread_cancel`:idx:
-     `posix.html#895 <posix.html#895>`_
-
-   `PTHREAD_CANCEL_ASYNCHRONOUS`:idx:
-     `posix.html#452 <posix.html#452>`_
-
-   `PTHREAD_CANCEL_DEFERRED`:idx:
-     `posix.html#454 <posix.html#454>`_
-
-   `PTHREAD_CANCEL_DISABLE`:idx:
-     `posix.html#455 <posix.html#455>`_
-
-   `PTHREAD_CANCELED`:idx:
-     `posix.html#456 <posix.html#456>`_
-
-   `PTHREAD_CANCEL_ENABLE`:idx:
-     `posix.html#453 <posix.html#453>`_
-
-   `pthread_cleanup_pop`:idx:
-     `posix.html#897 <posix.html#897>`_
-
-   `pthread_cleanup_push`:idx:
-     `posix.html#896 <posix.html#896>`_
-
-   `pthread_condattr_destroy`:idx:
-     `posix.html#904 <posix.html#904>`_
-
-   `pthread_condattr_getclock`:idx:
-     `posix.html#905 <posix.html#905>`_
-
-   `pthread_condattr_getpshared`:idx:
-     `posix.html#906 <posix.html#906>`_
-
-   `pthread_condattr_init`:idx:
-     `posix.html#907 <posix.html#907>`_
-
-   `pthread_condattr_setclock`:idx:
-     `posix.html#908 <posix.html#908>`_
-
-   `pthread_condattr_setpshared`:idx:
-     `posix.html#909 <posix.html#909>`_
-
-   `pthread_cond_broadcast`:idx:
-     `posix.html#898 <posix.html#898>`_
-
-   `pthread_cond_destroy`:idx:
-     `posix.html#899 <posix.html#899>`_
-
-   `pthread_cond_init`:idx:
-     `posix.html#900 <posix.html#900>`_
-
-   `PTHREAD_COND_INITIALIZER`:idx:
-     `posix.html#457 <posix.html#457>`_
-
-   `pthread_cond_signal`:idx:
-     `posix.html#901 <posix.html#901>`_
-
-   `pthread_cond_timedwait`:idx:
-     `posix.html#902 <posix.html#902>`_
-
-   `pthread_cond_wait`:idx:
-     `posix.html#903 <posix.html#903>`_
-
-   `pthread_create`:idx:
-     `posix.html#910 <posix.html#910>`_
-
-   `PTHREAD_CREATE_DETACHED`:idx:
-     `posix.html#458 <posix.html#458>`_
-
-   `PTHREAD_CREATE_JOINABLE`:idx:
-     `posix.html#459 <posix.html#459>`_
-
-   `pthread_detach`:idx:
-     `posix.html#911 <posix.html#911>`_
-
-   `pthread_equal`:idx:
-     `posix.html#912 <posix.html#912>`_
-
-   `pthread_exit`:idx:
-     `posix.html#913 <posix.html#913>`_
-
-   `PTHREAD_EXPLICIT_SCHED`:idx:
-     `posix.html#460 <posix.html#460>`_
-
-   `pthread_getconcurrency`:idx:
-     `posix.html#914 <posix.html#914>`_
-
-   `pthread_getcpuclockid`:idx:
-     `posix.html#915 <posix.html#915>`_
-
-   `pthread_getschedparam`:idx:
-     `posix.html#916 <posix.html#916>`_
-
-   `pthread_getspecific`:idx:
-     `posix.html#917 <posix.html#917>`_
-
-   `PTHREAD_INHERIT_SCHED`:idx:
-     `posix.html#461 <posix.html#461>`_
-
-   `pthread_join`:idx:
-     `posix.html#918 <posix.html#918>`_
-
-   `pthread_key_create`:idx:
-     `posix.html#919 <posix.html#919>`_
-
-   `pthread_key_delete`:idx:
-     `posix.html#920 <posix.html#920>`_
-
-   `pthread_kill`:idx:
-     `posix.html#1125 <posix.html#1125>`_
-
-   `pthread_mutexattr_destroy`:idx:
-     `posix.html#929 <posix.html#929>`_
-
-   `pthread_mutexattr_getprioceiling`:idx:
-     `posix.html#930 <posix.html#930>`_
-
-   `pthread_mutexattr_getprotocol`:idx:
-     `posix.html#931 <posix.html#931>`_
-
-   `pthread_mutexattr_getpshared`:idx:
-     `posix.html#932 <posix.html#932>`_
-
-   `pthread_mutexattr_gettype`:idx:
-     `posix.html#933 <posix.html#933>`_
-
-   `pthread_mutexattr_init`:idx:
-     `posix.html#934 <posix.html#934>`_
-
-   `pthread_mutexattr_setprioceiling`:idx:
-     `posix.html#935 <posix.html#935>`_
-
-   `pthread_mutexattr_setprotocol`:idx:
-     `posix.html#936 <posix.html#936>`_
-
-   `pthread_mutexattr_setpshared`:idx:
-     `posix.html#937 <posix.html#937>`_
-
-   `pthread_mutexattr_settype`:idx:
-     `posix.html#938 <posix.html#938>`_
-
-   `PTHREAD_MUTEX_DEFAULT`:idx:
-     `posix.html#462 <posix.html#462>`_
-
-   `pthread_mutex_destroy`:idx:
-     `posix.html#921 <posix.html#921>`_
-
-   `PTHREAD_MUTEX_ERRORCHECK`:idx:
-     `posix.html#463 <posix.html#463>`_
-
-   `pthread_mutex_getprioceiling`:idx:
-     `posix.html#922 <posix.html#922>`_
-
-   `pthread_mutex_init`:idx:
-     `posix.html#923 <posix.html#923>`_
-
-   `PTHREAD_MUTEX_INITIALIZER`:idx:
-     `posix.html#464 <posix.html#464>`_
-
-   `pthread_mutex_lock`:idx:
-     `posix.html#924 <posix.html#924>`_
-
-   `PTHREAD_MUTEX_NORMAL`:idx:
-     `posix.html#465 <posix.html#465>`_
-
-   `PTHREAD_MUTEX_RECURSIVE`:idx:
-     `posix.html#466 <posix.html#466>`_
-
-   `pthread_mutex_setprioceiling`:idx:
-     `posix.html#925 <posix.html#925>`_
-
-   `pthread_mutex_timedlock`:idx:
-     `posix.html#926 <posix.html#926>`_
-
-   `pthread_mutex_trylock`:idx:
-     `posix.html#927 <posix.html#927>`_
-
-   `pthread_mutex_unlock`:idx:
-     `posix.html#928 <posix.html#928>`_
-
-   `pthread_once`:idx:
-     `posix.html#939 <posix.html#939>`_
-
-   `PTHREAD_ONCE_INIT`:idx:
-     `posix.html#467 <posix.html#467>`_
-
-   `PTHREAD_PRIO_INHERIT`:idx:
-     `posix.html#468 <posix.html#468>`_
-
-   `PTHREAD_PRIO_NONE`:idx:
-     `posix.html#469 <posix.html#469>`_
-
-   `PTHREAD_PRIO_PROTECT`:idx:
-     `posix.html#470 <posix.html#470>`_
-
-   `PTHREAD_PROCESS_PRIVATE`:idx:
-     `posix.html#472 <posix.html#472>`_
-
-   `PTHREAD_PROCESS_SHARED`:idx:
-     `posix.html#471 <posix.html#471>`_
-
-   `pthread_rwlockattr_destroy`:idx:
-     `posix.html#949 <posix.html#949>`_
-
-   `pthread_rwlockattr_getpshared`:idx:
-     `posix.html#950 <posix.html#950>`_
-
-   `pthread_rwlockattr_init`:idx:
-     `posix.html#951 <posix.html#951>`_
-
-   `pthread_rwlockattr_setpshared`:idx:
-     `posix.html#952 <posix.html#952>`_
-
-   `pthread_rwlock_destroy`:idx:
-     `posix.html#940 <posix.html#940>`_
-
-   `pthread_rwlock_init`:idx:
-     `posix.html#941 <posix.html#941>`_
-
-   `pthread_rwlock_rdlock`:idx:
-     `posix.html#942 <posix.html#942>`_
-
-   `pthread_rwlock_timedrdlock`:idx:
-     `posix.html#943 <posix.html#943>`_
-
-   `pthread_rwlock_timedwrlock`:idx:
-     `posix.html#944 <posix.html#944>`_
-
-   `pthread_rwlock_tryrdlock`:idx:
-     `posix.html#945 <posix.html#945>`_
-
-   `pthread_rwlock_trywrlock`:idx:
-     `posix.html#946 <posix.html#946>`_
-
-   `pthread_rwlock_unlock`:idx:
-     `posix.html#947 <posix.html#947>`_
-
-   `pthread_rwlock_wrlock`:idx:
-     `posix.html#948 <posix.html#948>`_
-
-   `PTHREAD_SCOPE_PROCESS`:idx:
-     `posix.html#473 <posix.html#473>`_
-
-   `PTHREAD_SCOPE_SYSTEM`:idx:
-     `posix.html#474 <posix.html#474>`_
-
-   `pthread_self`:idx:
-     `posix.html#953 <posix.html#953>`_
-
-   `pthread_setcancelstate`:idx:
-     `posix.html#954 <posix.html#954>`_
-
-   `pthread_setcanceltype`:idx:
-     `posix.html#955 <posix.html#955>`_
-
-   `pthread_setconcurrency`:idx:
-     `posix.html#956 <posix.html#956>`_
-
-   `pthread_setschedparam`:idx:
-     `posix.html#957 <posix.html#957>`_
-
-   `pthread_setschedprio`:idx:
-     `posix.html#958 <posix.html#958>`_
-
-   `pthread_setspecific`:idx:
-     `posix.html#959 <posix.html#959>`_
-
-   `pthread_sigmask`:idx:
-     `posix.html#1126 <posix.html#1126>`_
-
-   `pthread_spin_destroy`:idx:
-     `posix.html#960 <posix.html#960>`_
-
-   `pthread_spin_init`:idx:
-     `posix.html#961 <posix.html#961>`_
-
-   `pthread_spin_lock`:idx:
-     `posix.html#962 <posix.html#962>`_
-
-   `pthread_spin_trylock`:idx:
-     `posix.html#963 <posix.html#963>`_
-
-   `pthread_spin_unlock`:idx:
-     `posix.html#964 <posix.html#964>`_
-
-   `pthread_testcancel`:idx:
-     `posix.html#965 <posix.html#965>`_
-
-   `Pulongf`:idx:
-     `zlib.html#104 <zlib.html#104>`_
-
-   `push/pop`:idx:
-     `manual.html#229 <manual.html#229>`_
-
-   `putEnv`:idx:
-     `os.html#142 <os.html#142>`_
-
-   `PWindow`:idx:
-     `dialogs.html#101 <dialogs.html#101>`_
-
-   `pwrite`:idx:
-     `posix.html#1017 <posix.html#1017>`_
-
-   `Pzip`:idx:
-     `libzip.html#105 <libzip.html#105>`_
-
-   `Pzip_file`:idx:
-     `libzip.html#106 <libzip.html#106>`_
-
-   `PZipFileStream`:idx:
-     `zipfiles.html#108 <zipfiles.html#108>`_
-
-   `Pzip_source`:idx:
-     `libzip.html#107 <libzip.html#107>`_
-
-   `Pzip_stat`:idx:
-     `libzip.html#103 <libzip.html#103>`_
-
-   `PZstream`:idx:
-     `zlib.html#114 <zlib.html#114>`_
-
-   `quit`:idx:
-     * `system.html#474 <system.html#474>`_
-     * `system.html#475 <system.html#475>`_
-
-   `QuitFailure`:idx:
-     `system.html#473 <system.html#473>`_
-
-   `QuitSuccess`:idx:
-     `system.html#472 <system.html#472>`_
-
-   `quotation mark`:idx:
-     `manual.html#128 <manual.html#128>`_
-
-   `quoteIfSpaceExists`:idx:
-     `strutils.html#138 <strutils.html#138>`_
-
-   `RADIXCHAR`:idx:
-     `posix.html#439 <posix.html#439>`_
-
-   `raise`:idx:
-     `posix.html#1127 <posix.html#1127>`_
-
-   `random`:idx:
-     `math.html#108 <math.html#108>`_
-
-   `randomize`:idx:
-     `math.html#109 <math.html#109>`_
-
-   `range`:idx:
-     `system.html#120 <system.html#120>`_
-
-   `re-raised`:idx:
-     `manual.html#184 <manual.html#184>`_
-
-   `read`:idx:
-     `posix.html#1018 <posix.html#1018>`_
-
-   `readBool`:idx:
-     `streams.html#106 <streams.html#106>`_
-
-   `readBuffer`:idx:
-     `system.html#502 <system.html#502>`_
-
-   `ReadBytes`:idx:
-     `system.html#500 <system.html#500>`_
-
-   `readChar`:idx:
-     * `system.html#486 <system.html#486>`_
-     * `streams.html#105 <streams.html#105>`_
-
-   `ReadChars`:idx:
-     `system.html#501 <system.html#501>`_
-
-   `readdir`:idx:
-     `posix.html#802 <posix.html#802>`_
-
-   `readdir_r`:idx:
-     `posix.html#803 <posix.html#803>`_
-
-   `readFile`:idx:
-     `system.html#488 <system.html#488>`_
-
-   `readFloat32`:idx:
-     `streams.html#111 <streams.html#111>`_
-
-   `readFloat64`:idx:
-     `streams.html#112 <streams.html#112>`_
-
-   `readInt16`:idx:
-     `streams.html#108 <streams.html#108>`_
-
-   `readInt32`:idx:
-     `streams.html#109 <streams.html#109>`_
-
-   `readInt64`:idx:
-     `streams.html#110 <streams.html#110>`_
-
-   `readInt8`:idx:
-     `streams.html#107 <streams.html#107>`_
-
-   `readLine`:idx:
-     * `system.html#496 <system.html#496>`_
-     * `streams.html#114 <streams.html#114>`_
-
-   `readlink`:idx:
-     `posix.html#1019 <posix.html#1019>`_
-
-   `readStr`:idx:
-     `streams.html#113 <streams.html#113>`_
-
-   `realloc`:idx:
-     `system.html#413 <system.html#413>`_
-
-   `Recursive module dependancies`:idx:
-     `manual.html#217 <manual.html#217>`_
-
-   `register`:idx:
-     `nimrodc.html#113 <nimrodc.html#113>`_
-
-   `removeDir`:idx:
-     `os.html#137 <os.html#137>`_
-
-   `removeFile`:idx:
-     `os.html#136 <os.html#136>`_
-
-   `repeatChar`:idx:
-     `strutils.html#134 <strutils.html#134>`_
-
-   `replaceStr`:idx:
-     * `strutils.html#114 <strutils.html#114>`_
-     * `strutils.html#115 <strutils.html#115>`_
-
-   `repr`:idx:
-     `system.html#371 <system.html#371>`_
-
-   `result`:idx:
-     * `manual.html#191 <manual.html#191>`_
-     * `manual.html#202 <manual.html#202>`_
-
-   `return`:idx:
-     `manual.html#190 <manual.html#190>`_
-
-   `rewinddir`:idx:
-     `posix.html#804 <posix.html#804>`_
-
-   `rmdir`:idx:
-     `posix.html#1020 <posix.html#1020>`_
-
-   `R_OK`:idx:
-     `posix.html#479 <posix.html#479>`_
-
-   `round`:idx:
-     `math.html#116 <math.html#116>`_
-
-   `RTLD_GLOBAL`:idx:
-     `posix.html#217 <posix.html#217>`_
-
-   `RTLD_LAZY`:idx:
-     `posix.html#215 <posix.html#215>`_
-
-   `RTLD_LOCAL`:idx:
-     `posix.html#218 <posix.html#218>`_
-
-   `RTLD_NOW`:idx:
-     `posix.html#216 <posix.html#216>`_
-
-   `safe`:idx:
-     `manual.html#112 <manual.html#112>`_
-
-   `safecall`:idx:
-     `manual.html#167 <manual.html#167>`_
-
-   `sameFile`:idx:
-     `os.html#148 <os.html#148>`_
-
-   `sameFileContent`:idx:
-     `os.html#149 <os.html#149>`_
-
-   `SA_NOCLDSTOP`:idx:
-     `posix.html#754 <posix.html#754>`_
-
-   `SA_NOCLDWAIT`:idx:
-     `posix.html#762 <posix.html#762>`_
-
-   `SA_NODEFER`:idx:
-     `posix.html#763 <posix.html#763>`_
-
-   `SA_ONSTACK`:idx:
-     `posix.html#758 <posix.html#758>`_
-
-   `SA_RESETHAND`:idx:
-     `posix.html#759 <posix.html#759>`_
-
-   `SA_RESTART`:idx:
-     `posix.html#760 <posix.html#760>`_
-
-   `SA_SIGINFO`:idx:
-     `posix.html#761 <posix.html#761>`_
-
-   `SC_2_C_BIND`:idx:
-     `posix.html#519 <posix.html#519>`_
-
-   `SC_2_C_DEV`:idx:
-     `posix.html#520 <posix.html#520>`_
-
-   `SC_2_CHAR_TERM`:idx:
-     `posix.html#521 <posix.html#521>`_
-
-   `SC_2_FORT_DEV`:idx:
-     `posix.html#522 <posix.html#522>`_
-
-   `SC_2_FORT_RUN`:idx:
-     `posix.html#523 <posix.html#523>`_
-
-   `SC_2_LOCALEDEF`:idx:
-     `posix.html#524 <posix.html#524>`_
-
-   `SC_2_PBS`:idx:
-     `posix.html#525 <posix.html#525>`_
-
-   `SC_2_PBS_ACCOUNTING`:idx:
-     `posix.html#526 <posix.html#526>`_
-
-   `SC_2_PBS_CHECKPOINT`:idx:
-     `posix.html#527 <posix.html#527>`_
-
-   `SC_2_PBS_LOCATE`:idx:
-     `posix.html#528 <posix.html#528>`_
-
-   `SC_2_PBS_MESSAGE`:idx:
-     `posix.html#529 <posix.html#529>`_
-
-   `SC_2_PBS_TRACK`:idx:
-     `posix.html#530 <posix.html#530>`_
-
-   `SC_2_SW_DEV`:idx:
-     `posix.html#531 <posix.html#531>`_
-
-   `SC_2_UPE`:idx:
-     `posix.html#532 <posix.html#532>`_
-
-   `SC_2_VERSION`:idx:
-     `posix.html#533 <posix.html#533>`_
-
-   `SC_ADVISORY_INFO`:idx:
-     `posix.html#534 <posix.html#534>`_
-
-   `SC_AIO_LISTIO_MAX`:idx:
-     `posix.html#535 <posix.html#535>`_
-
-   `SC_AIO_MAX`:idx:
-     `posix.html#536 <posix.html#536>`_
-
-   `SC_AIO_PRIO_DELTA_MAX`:idx:
-     `posix.html#537 <posix.html#537>`_
-
-   `SC_ARG_MAX`:idx:
-     `posix.html#538 <posix.html#538>`_
-
-   `SC_ASYNCHRONOUS_IO`:idx:
-     `posix.html#539 <posix.html#539>`_
-
-   `SC_ATEXIT_MAX`:idx:
-     `posix.html#540 <posix.html#540>`_
-
-   `SC_BARRIERS`:idx:
-     `posix.html#541 <posix.html#541>`_
-
-   `SC_BC_BASE_MAX`:idx:
-     `posix.html#542 <posix.html#542>`_
-
-   `SC_BC_DIM_MAX`:idx:
-     `posix.html#543 <posix.html#543>`_
-
-   `SC_BC_SCALE_MAX`:idx:
-     `posix.html#544 <posix.html#544>`_
-
-   `SC_BC_STRING_MAX`:idx:
-     `posix.html#545 <posix.html#545>`_
-
-   `SC_CHILD_MAX`:idx:
-     `posix.html#546 <posix.html#546>`_
-
-   `SC_CLK_TCK`:idx:
-     `posix.html#547 <posix.html#547>`_
-
-   `SC_CLOCK_SELECTION`:idx:
-     `posix.html#548 <posix.html#548>`_
-
-   `SC_COLL_WEIGHTS_MAX`:idx:
-     `posix.html#549 <posix.html#549>`_
-
-   `SC_CPUTIME`:idx:
-     `posix.html#550 <posix.html#550>`_
-
-   `SC_DELAYTIMER_MAX`:idx:
-     `posix.html#551 <posix.html#551>`_
-
-   `SC_EXPR_NEST_MAX`:idx:
-     `posix.html#552 <posix.html#552>`_
-
-   `SC_FSYNC`:idx:
-     `posix.html#553 <posix.html#553>`_
-
-   `SC_GETGR_R_SIZE_MAX`:idx:
-     `posix.html#554 <posix.html#554>`_
-
-   `SC_GETPW_R_SIZE_MAX`:idx:
-     `posix.html#555 <posix.html#555>`_
-
-   `SCHED_FIFO`:idx:
-     `posix.html#770 <posix.html#770>`_
-
-   `sched_getparam`:idx:
-     `posix.html#1154 <posix.html#1154>`_
-
-   `sched_get_priority_max`:idx:
-     `posix.html#1152 <posix.html#1152>`_
-
-   `sched_get_priority_min`:idx:
-     `posix.html#1153 <posix.html#1153>`_
-
-   `sched_getscheduler`:idx:
-     `posix.html#1155 <posix.html#1155>`_
-
-   `SCHED_OTHER`:idx:
-     `posix.html#773 <posix.html#773>`_
-
-   `SCHED_RR`:idx:
-     `posix.html#771 <posix.html#771>`_
-
-   `sched_rr_get_interval`:idx:
-     `posix.html#1156 <posix.html#1156>`_
-
-   `sched_setparam`:idx:
-     `posix.html#1157 <posix.html#1157>`_
-
-   `sched_setscheduler`:idx:
-     `posix.html#1158 <posix.html#1158>`_
-
-   `SCHED_SPORADIC`:idx:
-     `posix.html#772 <posix.html#772>`_
-
-   `sched_yield`:idx:
-     `posix.html#1159 <posix.html#1159>`_
-
-   `SC_HOST_NAME_MAX`:idx:
-     `posix.html#556 <posix.html#556>`_
-
-   `SC_IOV_MAX`:idx:
-     `posix.html#557 <posix.html#557>`_
-
-   `SC_IPV6`:idx:
-     `posix.html#558 <posix.html#558>`_
-
-   `SC_JOB_CONTROL`:idx:
-     `posix.html#559 <posix.html#559>`_
-
-   `SC_LINE_MAX`:idx:
-     `posix.html#560 <posix.html#560>`_
-
-   `SC_LOGIN_NAME_MAX`:idx:
-     `posix.html#561 <posix.html#561>`_
-
-   `SC_MAPPED_FILES`:idx:
-     `posix.html#562 <posix.html#562>`_
-
-   `SC_MEMLOCK`:idx:
-     `posix.html#563 <posix.html#563>`_
-
-   `SC_MEMLOCK_RANGE`:idx:
-     `posix.html#564 <posix.html#564>`_
-
-   `SC_MEMORY_PROTECTION`:idx:
-     `posix.html#565 <posix.html#565>`_
-
-   `SC_MESSAGE_PASSING`:idx:
-     `posix.html#566 <posix.html#566>`_
-
-   `SC_MONOTONIC_CLOCK`:idx:
-     `posix.html#567 <posix.html#567>`_
-
-   `SC_MQ_OPEN_MAX`:idx:
-     `posix.html#568 <posix.html#568>`_
-
-   `SC_MQ_PRIO_MAX`:idx:
-     `posix.html#569 <posix.html#569>`_
-
-   `SC_NGROUPS_MAX`:idx:
-     `posix.html#570 <posix.html#570>`_
-
-   `scope`:idx:
-     * `manual.html#106 <manual.html#106>`_
-     * `manual.html#218 <manual.html#218>`_
-
-   `SC_OPEN_MAX`:idx:
-     `posix.html#571 <posix.html#571>`_
-
-   `SC_PAGE_SIZE`:idx:
-     `posix.html#572 <posix.html#572>`_
-
-   `SC_PRIORITIZED_IO`:idx:
-     `posix.html#573 <posix.html#573>`_
-
-   `SC_PRIORITY_SCHEDULING`:idx:
-     `posix.html#574 <posix.html#574>`_
-
-   `SC_RAW_SOCKETS`:idx:
-     `posix.html#575 <posix.html#575>`_
-
-   `SC_READER_WRITER_LOCKS`:idx:
-     `posix.html#577 <posix.html#577>`_
-
-   `SC_REALTIME_SIGNALS`:idx:
-     `posix.html#578 <posix.html#578>`_
-
-   `SC_RE_DUP_MAX`:idx:
-     `posix.html#576 <posix.html#576>`_
-
-   `SC_REGEXP`:idx:
-     `posix.html#579 <posix.html#579>`_
-
-   `ScriptExt`:idx:
-     `os.html#108 <os.html#108>`_
-
-   `SC_RTSIG_MAX`:idx:
-     `posix.html#580 <posix.html#580>`_
-
-   `SC_SAVED_IDS`:idx:
-     `posix.html#581 <posix.html#581>`_
-
-   `SC_SEMAPHORES`:idx:
-     `posix.html#584 <posix.html#584>`_
-
-   `SC_SEM_NSEMS_MAX`:idx:
-     `posix.html#582 <posix.html#582>`_
-
-   `SC_SEM_VALUE_MAX`:idx:
-     `posix.html#583 <posix.html#583>`_
-
-   `SC_SHARED_MEMORY_OBJECTS`:idx:
-     `posix.html#585 <posix.html#585>`_
-
-   `SC_SHELL`:idx:
-     `posix.html#586 <posix.html#586>`_
-
-   `SC_SIGQUEUE_MAX`:idx:
-     `posix.html#587 <posix.html#587>`_
-
-   `SC_SPAWN`:idx:
-     `posix.html#588 <posix.html#588>`_
-
-   `SC_SPIN_LOCKS`:idx:
-     `posix.html#589 <posix.html#589>`_
-
-   `SC_SPORADIC_SERVER`:idx:
-     `posix.html#590 <posix.html#590>`_
-
-   `SC_SS_REPL_MAX`:idx:
-     `posix.html#591 <posix.html#591>`_
-
-   `SC_STREAM_MAX`:idx:
-     `posix.html#592 <posix.html#592>`_
-
-   `SC_SYMLOOP_MAX`:idx:
-     `posix.html#593 <posix.html#593>`_
-
-   `SC_SYNCHRONIZED_IO`:idx:
-     `posix.html#594 <posix.html#594>`_
-
-   `SC_THREAD_ATTR_STACKADDR`:idx:
-     `posix.html#595 <posix.html#595>`_
-
-   `SC_THREAD_ATTR_STACKSIZE`:idx:
-     `posix.html#596 <posix.html#596>`_
-
-   `SC_THREAD_CPUTIME`:idx:
-     `posix.html#597 <posix.html#597>`_
-
-   `SC_THREAD_DESTRUCTOR_ITERATIONS`:idx:
-     `posix.html#598 <posix.html#598>`_
-
-   `SC_THREAD_KEYS_MAX`:idx:
-     `posix.html#599 <posix.html#599>`_
-
-   `SC_THREAD_PRIO_INHERIT`:idx:
-     `posix.html#600 <posix.html#600>`_
-
-   `SC_THREAD_PRIO_PROTECT`:idx:
-     `posix.html#601 <posix.html#601>`_
-
-   `SC_THREAD_PRIORITY_SCHEDULING`:idx:
-     `posix.html#602 <posix.html#602>`_
-
-   `SC_THREAD_PROCESS_SHARED`:idx:
-     `posix.html#603 <posix.html#603>`_
-
-   `SC_THREADS`:idx:
-     `posix.html#608 <posix.html#608>`_
-
-   `SC_THREAD_SAFE_FUNCTIONS`:idx:
-     `posix.html#604 <posix.html#604>`_
-
-   `SC_THREAD_SPORADIC_SERVER`:idx:
-     `posix.html#605 <posix.html#605>`_
-
-   `SC_THREAD_STACK_MIN`:idx:
-     `posix.html#606 <posix.html#606>`_
-
-   `SC_THREAD_THREADS_MAX`:idx:
-     `posix.html#607 <posix.html#607>`_
-
-   `SC_TIMEOUTS`:idx:
-     `posix.html#609 <posix.html#609>`_
-
-   `SC_TIMER_MAX`:idx:
-     `posix.html#610 <posix.html#610>`_
-
-   `SC_TIMERS`:idx:
-     `posix.html#611 <posix.html#611>`_
-
-   `SC_TRACE`:idx:
-     `posix.html#612 <posix.html#612>`_
-
-   `SC_TRACE_EVENT_FILTER`:idx:
-     `posix.html#613 <posix.html#613>`_
-
-   `SC_TRACE_EVENT_NAME_MAX`:idx:
-     `posix.html#614 <posix.html#614>`_
-
-   `SC_TRACE_INHERIT`:idx:
-     `posix.html#615 <posix.html#615>`_
-
-   `SC_TRACE_LOG`:idx:
-     `posix.html#616 <posix.html#616>`_
-
-   `SC_TRACE_NAME_MAX`:idx:
-     `posix.html#617 <posix.html#617>`_
-
-   `SC_TRACE_SYS_MAX`:idx:
-     `posix.html#618 <posix.html#618>`_
-
-   `SC_TRACE_USER_EVENT_MAX`:idx:
-     `posix.html#619 <posix.html#619>`_
-
-   `SC_TTY_NAME_MAX`:idx:
-     `posix.html#620 <posix.html#620>`_
-
-   `SC_TYPED_MEMORY_OBJECTS`:idx:
-     `posix.html#621 <posix.html#621>`_
-
-   `SC_TZNAME_MAX`:idx:
-     `posix.html#622 <posix.html#622>`_
-
-   `SC_V6_ILP32_OFF32`:idx:
-     `posix.html#623 <posix.html#623>`_
-
-   `SC_V6_ILP32_OFFBIG`:idx:
-     `posix.html#624 <posix.html#624>`_
-
-   `SC_V6_LP64_OFF64`:idx:
-     `posix.html#625 <posix.html#625>`_
-
-   `SC_V6_LPBIG_OFFBIG`:idx:
-     `posix.html#626 <posix.html#626>`_
-
-   `SC_VERSION`:idx:
-     `posix.html#627 <posix.html#627>`_
-
-   `SC_XBS5_ILP32_OFF32`:idx:
-     `posix.html#628 <posix.html#628>`_
-
-   `SC_XBS5_ILP32_OFFBIG`:idx:
-     `posix.html#629 <posix.html#629>`_
-
-   `SC_XBS5_LP64_OFF64`:idx:
-     `posix.html#630 <posix.html#630>`_
-
-   `SC_XBS5_LPBIG_OFFBIG`:idx:
-     `posix.html#631 <posix.html#631>`_
-
-   `SC_XOPEN_CRYPT`:idx:
-     `posix.html#632 <posix.html#632>`_
-
-   `SC_XOPEN_ENH_I18N`:idx:
-     `posix.html#633 <posix.html#633>`_
-
-   `SC_XOPEN_LEGACY`:idx:
-     `posix.html#634 <posix.html#634>`_
-
-   `SC_XOPEN_REALTIME`:idx:
-     `posix.html#635 <posix.html#635>`_
-
-   `SC_XOPEN_REALTIME_THREADS`:idx:
-     `posix.html#636 <posix.html#636>`_
-
-   `SC_XOPEN_SHM`:idx:
-     `posix.html#637 <posix.html#637>`_
-
-   `SC_XOPEN_STREAMS`:idx:
-     `posix.html#638 <posix.html#638>`_
-
-   `SC_XOPEN_UNIX`:idx:
-     `posix.html#639 <posix.html#639>`_
-
-   `SC_XOPEN_VERSION`:idx:
-     `posix.html#640 <posix.html#640>`_
-
-   `SEEK_CUR`:idx:
-     `posix.html#776 <posix.html#776>`_
-
-   `seekdir`:idx:
-     `posix.html#805 <posix.html#805>`_
-
-   `SEEK_END`:idx:
-     `posix.html#777 <posix.html#777>`_
-
-   `SEEK_SET`:idx:
-     `posix.html#775 <posix.html#775>`_
-
-   `select`:idx:
-     `posix.html#1166 <posix.html#1166>`_
-
-   `sem_close`:idx:
-     `posix.html#1045 <posix.html#1045>`_
-
-   `sem_destroy`:idx:
-     `posix.html#1046 <posix.html#1046>`_
-
-   `SEM_FAILED`:idx:
-     `posix.html#641 <posix.html#641>`_
-
-   `sem_getvalue`:idx:
-     `posix.html#1047 <posix.html#1047>`_
-
-   `sem_init`:idx:
-     `posix.html#1048 <posix.html#1048>`_
-
-   `sem_open`:idx:
-     `posix.html#1049 <posix.html#1049>`_
-
-   `sem_post`:idx:
-     `posix.html#1050 <posix.html#1050>`_
-
-   `sem_timedwait`:idx:
-     `posix.html#1051 <posix.html#1051>`_
-
-   `sem_trywait`:idx:
-     `posix.html#1052 <posix.html#1052>`_
-
-   `sem_unlink`:idx:
-     `posix.html#1053 <posix.html#1053>`_
-
-   `sem_wait`:idx:
-     `posix.html#1054 <posix.html#1054>`_
-
-   `separate compilation`:idx:
-     `manual.html#215 <manual.html#215>`_
-
-   `seq`:idx:
-     `system.html#123 <system.html#123>`_
-
-   `seqToPtr`:idx:
-     `system.html#454 <system.html#454>`_
-
-   `Sequences`:idx:
-     `manual.html#154 <manual.html#154>`_
-
-   `set`:idx:
-     `system.html#124 <system.html#124>`_
-
-   `set type`:idx:
-     `manual.html#158 <manual.html#158>`_
-
-   `setcontext`:idx:
-     `posix.html#1190 <posix.html#1190>`_
-
-   `setCurrentDir`:idx:
-     `os.html#113 <os.html#113>`_
-
-   `setegid`:idx:
-     `posix.html#1021 <posix.html#1021>`_
-
-   `seteuid`:idx:
-     `posix.html#1022 <posix.html#1022>`_
-
-   `setFilePos`:idx:
-     `system.html#506 <system.html#506>`_
-
-   `setgid`:idx:
-     `posix.html#1023 <posix.html#1023>`_
-
-   `setgrent`:idx:
-     `posix.html#839 <posix.html#839>`_
-
-   `setLen`:idx:
-     * `system.html#405 <system.html#405>`_
-     * `system.html#415 <system.html#415>`_
-
-   `setlocale`:idx:
-     `posix.html#847 <posix.html#847>`_
-
-   `setpgid`:idx:
-     `posix.html#1024 <posix.html#1024>`_
-
-   `setpgrp`:idx:
-     `posix.html#1025 <posix.html#1025>`_
-
-   `setpwent`:idx:
-     `posix.html#865 <posix.html#865>`_
-
-   `setregid`:idx:
-     `posix.html#1026 <posix.html#1026>`_
-
-   `setreuid`:idx:
-     `posix.html#1027 <posix.html#1027>`_
-
-   `setsid`:idx:
-     `posix.html#1028 <posix.html#1028>`_
-
-   `setuid`:idx:
-     `posix.html#1029 <posix.html#1029>`_
-
-   `shl`:idx:
-     * `system.html#223 <system.html#223>`_
-     * `system.html#224 <system.html#224>`_
-     * `system.html#225 <system.html#225>`_
-     * `system.html#226 <system.html#226>`_
-     * `system.html#227 <system.html#227>`_
-
-   `shm_open`:idx:
-     `posix.html#1090 <posix.html#1090>`_
-
-   `shm_unlink`:idx:
-     `posix.html#1091 <posix.html#1091>`_
-
-   `shr`:idx:
-     * `system.html#218 <system.html#218>`_
-     * `system.html#219 <system.html#219>`_
-     * `system.html#220 <system.html#220>`_
-     * `system.html#221 <system.html#221>`_
-     * `system.html#222 <system.html#222>`_
-
-   `S_IFBLK`:idx:
-     `posix.html#650 <posix.html#650>`_
-
-   `S_IFCHR`:idx:
-     `posix.html#651 <posix.html#651>`_
-
-   `S_IFDIR`:idx:
-     `posix.html#654 <posix.html#654>`_
-
-   `S_IFIFO`:idx:
-     `posix.html#652 <posix.html#652>`_
-
-   `S_IFLNK`:idx:
-     `posix.html#655 <posix.html#655>`_
-
-   `S_IFMT`:idx:
-     `posix.html#649 <posix.html#649>`_
-
-   `S_IFREG`:idx:
-     `posix.html#653 <posix.html#653>`_
-
-   `S_IFSOCK`:idx:
-     `posix.html#656 <posix.html#656>`_
-
-   `SIGABRT`:idx:
-     `posix.html#726 <posix.html#726>`_
-
-   `sigaction`:idx:
-     `posix.html#1128 <posix.html#1128>`_
-
-   `sigaddset`:idx:
-     `posix.html#1129 <posix.html#1129>`_
-
-   `SIGALRM`:idx:
-     `posix.html#727 <posix.html#727>`_
-
-   `sigaltstack`:idx:
-     `posix.html#1130 <posix.html#1130>`_
-
-   `SIG_BLOCK`:idx:
-     `posix.html#755 <posix.html#755>`_
-
-   `SIGBUS`:idx:
-     `posix.html#728 <posix.html#728>`_
-
-   `SIGCHLD`:idx:
-     `posix.html#729 <posix.html#729>`_
-
-   `SIGCONT`:idx:
-     `posix.html#730 <posix.html#730>`_
-
-   `sigdelset`:idx:
-     `posix.html#1131 <posix.html#1131>`_
-
-   `SIG_DFL`:idx:
-     `posix.html#719 <posix.html#719>`_
-
-   `sigemptyset`:idx:
-     `posix.html#1132 <posix.html#1132>`_
-
-   `SIG_ERR`:idx:
-     `posix.html#720 <posix.html#720>`_
-
-   `SIGEV_NONE`:idx:
-     `posix.html#723 <posix.html#723>`_
-
-   `SIGEV_SIGNAL`:idx:
-     `posix.html#724 <posix.html#724>`_
-
-   `SIGEV_THREAD`:idx:
-     `posix.html#725 <posix.html#725>`_
-
-   `sigfillset`:idx:
-     `posix.html#1133 <posix.html#1133>`_
-
-   `SIGFPE`:idx:
-     `posix.html#731 <posix.html#731>`_
-
-   `sighold`:idx:
-     `posix.html#1134 <posix.html#1134>`_
-
-   `SIGHUP`:idx:
-     `posix.html#732 <posix.html#732>`_
-
-   `SIG_IGN`:idx:
-     `posix.html#722 <posix.html#722>`_
-
-   `sigignore`:idx:
-     `posix.html#1135 <posix.html#1135>`_
-
-   `SIGILL`:idx:
-     `posix.html#733 <posix.html#733>`_
-
-   `SIGINT`:idx:
-     `posix.html#734 <posix.html#734>`_
-
-   `siginterrupt`:idx:
-     `posix.html#1136 <posix.html#1136>`_
-
-   `sigismember`:idx:
-     `posix.html#1137 <posix.html#1137>`_
-
-   `SIGKILL`:idx:
-     `posix.html#735 <posix.html#735>`_
-
-   `signal`:idx:
-     `posix.html#1138 <posix.html#1138>`_
-
-   `sigpause`:idx:
-     `posix.html#1139 <posix.html#1139>`_
-
-   `sigpending`:idx:
-     `posix.html#1140 <posix.html#1140>`_
-
-   `SIGPIPE`:idx:
-     `posix.html#736 <posix.html#736>`_
-
-   `SIGPOLL`:idx:
-     `posix.html#746 <posix.html#746>`_
-
-   `sigprocmask`:idx:
-     `posix.html#1141 <posix.html#1141>`_
-
-   `SIGPROF`:idx:
-     `posix.html#747 <posix.html#747>`_
-
-   `sigqueue`:idx:
-     `posix.html#1142 <posix.html#1142>`_
-
-   `SIGQUIT`:idx:
-     `posix.html#737 <posix.html#737>`_
-
-   `sigrelse`:idx:
-     `posix.html#1143 <posix.html#1143>`_
-
-   `SIGSEGV`:idx:
-     `posix.html#738 <posix.html#738>`_
-
-   `sigset`:idx:
-     `posix.html#1144 <posix.html#1144>`_
-
-   `SIG_SETMASK`:idx:
-     `posix.html#757 <posix.html#757>`_
-
-   `SIGSTKSZ`:idx:
-     `posix.html#767 <posix.html#767>`_
-
-   `SIGSTOP`:idx:
-     `posix.html#739 <posix.html#739>`_
-
-   `sigsuspend`:idx:
-     `posix.html#1145 <posix.html#1145>`_
-
-   `SIGSYS`:idx:
-     `posix.html#748 <posix.html#748>`_
-
-   `SIGTERM`:idx:
-     `posix.html#740 <posix.html#740>`_
-
-   `sigtimedwait`:idx:
-     `posix.html#1146 <posix.html#1146>`_
-
-   `SIGTRAP`:idx:
-     `posix.html#749 <posix.html#749>`_
-
-   `SIGTSTP`:idx:
-     `posix.html#741 <posix.html#741>`_
-
-   `SIGTTIN`:idx:
-     `posix.html#742 <posix.html#742>`_
-
-   `SIGTTOU`:idx:
-     `posix.html#743 <posix.html#743>`_
-
-   `SIG_UNBLOCK`:idx:
-     `posix.html#756 <posix.html#756>`_
-
-   `SIGURG`:idx:
-     `posix.html#750 <posix.html#750>`_
-
-   `SIGUSR1`:idx:
-     `posix.html#744 <posix.html#744>`_
-
-   `SIGUSR2`:idx:
-     `posix.html#745 <posix.html#745>`_
-
-   `SIGVTALRM`:idx:
-     `posix.html#751 <posix.html#751>`_
-
-   `sigwait`:idx:
-     `posix.html#1147 <posix.html#1147>`_
-
-   `sigwaitinfo`:idx:
-     `posix.html#1148 <posix.html#1148>`_
-
-   `SIGXCPU`:idx:
-     `posix.html#752 <posix.html#752>`_
-
-   `SIGXFSZ`:idx:
-     `posix.html#753 <posix.html#753>`_
-
-   `simple assertions`:idx:
-     `regexprs.html#103 <regexprs.html#103>`_
-
-   `simple statements`:idx:
-     `manual.html#175 <manual.html#175>`_
-
-   `sinh`:idx:
-     `math.html#124 <math.html#124>`_
-
-   `S_IRGRP`:idx:
-     `posix.html#662 <posix.html#662>`_
-
-   `S_IROTH`:idx:
-     `posix.html#666 <posix.html#666>`_
-
-   `S_IRUSR`:idx:
-     `posix.html#658 <posix.html#658>`_
-
-   `S_IRWXG`:idx:
-     `posix.html#661 <posix.html#661>`_
-
-   `S_IRWXO`:idx:
-     `posix.html#665 <posix.html#665>`_
-
-   `S_IRWXU`:idx:
-     `posix.html#657 <posix.html#657>`_
-
-   `S_ISBLK`:idx:
-     `posix.html#1067 <posix.html#1067>`_
-
-   `S_ISCHR`:idx:
-     `posix.html#1068 <posix.html#1068>`_
-
-   `S_ISDIR`:idx:
-     `posix.html#1069 <posix.html#1069>`_
-
-   `S_ISFIFO`:idx:
-     `posix.html#1070 <posix.html#1070>`_
-
-   `S_ISGID`:idx:
-     `posix.html#670 <posix.html#670>`_
-
-   `S_ISLNK`:idx:
-     `posix.html#1072 <posix.html#1072>`_
-
-   `S_ISREG`:idx:
-     `posix.html#1071 <posix.html#1071>`_
-
-   `S_ISSOCK`:idx:
-     `posix.html#1073 <posix.html#1073>`_
-
-   `S_ISUID`:idx:
-     `posix.html#669 <posix.html#669>`_
-
-   `S_ISVTX`:idx:
-     `posix.html#671 <posix.html#671>`_
-
-   `S_IWGRP`:idx:
-     `posix.html#663 <posix.html#663>`_
-
-   `S_IWOTH`:idx:
-     `posix.html#667 <posix.html#667>`_
-
-   `S_IWUSR`:idx:
-     `posix.html#659 <posix.html#659>`_
-
-   `S_IXGRP`:idx:
-     `posix.html#664 <posix.html#664>`_
-
-   `S_IXOTH`:idx:
-     `posix.html#668 <posix.html#668>`_
-
-   `S_IXUSR`:idx:
-     `posix.html#660 <posix.html#660>`_
-
-   `sizeof`:idx:
-     `system.html#153 <system.html#153>`_
-
-   `sleep`:idx:
-     `posix.html#1030 <posix.html#1030>`_
-
-   `split`:idx:
-     `strutils.html#118 <strutils.html#118>`_
-
-   `SplitFilename`:idx:
-     `os.html#125 <os.html#125>`_
-
-   `splitLines`:idx:
-     `strutils.html#119 <strutils.html#119>`_
-
-   `splitLinesSeq`:idx:
-     `strutils.html#120 <strutils.html#120>`_
-
-   `SplitPath`:idx:
-     `os.html#121 <os.html#121>`_
-
-   `splitSeq`:idx:
-     `strutils.html#121 <strutils.html#121>`_
-
-   `SQL_ACCESS_MODE`:idx:
-     `odbcsql.html#406 <odbcsql.html#406>`_
-
-   `SQL_ADD`:idx:
-     `odbcsql.html#317 <odbcsql.html#317>`_
-
-   `SQLAllocHandle`:idx:
-     `odbcsql.html#627 <odbcsql.html#627>`_
-
-   `SQL_ALL_TYPES`:idx:
-     `odbcsql.html#492 <odbcsql.html#492>`_
-
-   `SQL_API_SQLDESCRIBEPARAM`:idx:
-     `odbcsql.html#229 <odbcsql.html#229>`_
-
-   `SQL_ARD_TYPE`:idx:
-     `odbcsql.html#494 <odbcsql.html#494>`_
-
-   `SQL_ASYNC_ENABLE`:idx:
-     `odbcsql.html#383 <odbcsql.html#383>`_
-
-   `SQL_ATTR_ACCESS_MODE`:idx:
-     `odbcsql.html#415 <odbcsql.html#415>`_
-
-   `SQL_ATTR_APP_PARAM_DESC`:idx:
-     `odbcsql.html#374 <odbcsql.html#374>`_
-
-   `SQL_ATTR_APP_ROW_DESC`:idx:
-     `odbcsql.html#373 <odbcsql.html#373>`_
-
-   `SQL_ATTR_AUTOCOMMIT`:idx:
-     `odbcsql.html#400 <odbcsql.html#400>`_
-
-   `SQL_ATTR_AUTO_IPD`:idx:
-     `odbcsql.html#371 <odbcsql.html#371>`_
-
-   `SQL_ATTR_CONCURRENCY`:idx:
-     `odbcsql.html#395 <odbcsql.html#395>`_
-
-   `SQL_ATTR_CONNECTION_DEAD`:idx:
-     `odbcsql.html#416 <odbcsql.html#416>`_
-
-   `SQL_ATTR_CONNECTION_TIMEOUT`:idx:
-     `odbcsql.html#417 <odbcsql.html#417>`_
-
-   `SQL_ATTR_CURRENT_CATALOG`:idx:
-     `odbcsql.html#418 <odbcsql.html#418>`_
-
-   `SQL_ATTR_CURSOR_SCROLLABLE`:idx:
-     `odbcsql.html#377 <odbcsql.html#377>`_
-
-   `SQL_ATTR_CURSOR_SENSITIVITY`:idx:
-     `odbcsql.html#378 <odbcsql.html#378>`_
-
-   `SQL_ATTR_CURSOR_TYPE`:idx:
-     `odbcsql.html#394 <odbcsql.html#394>`_
-
-   `SQL_ATTR_DISCONNECT_BEHAVIOR`:idx:
-     `odbcsql.html#419 <odbcsql.html#419>`_
-
-   `SQL_ATTR_ENLIST_IN_DTC`:idx:
-     `odbcsql.html#420 <odbcsql.html#420>`_
-
-   `SQL_ATTR_ENLIST_IN_XA`:idx:
-     `odbcsql.html#421 <odbcsql.html#421>`_
-
-   `SQL_ATTR_FETCH_BOOKMARK_PTR`:idx:
-     `odbcsql.html#396 <odbcsql.html#396>`_
-
-   `SQL_ATTR_IMP_PARAM_DESC`:idx:
-     `odbcsql.html#376 <odbcsql.html#376>`_
-
-   `SQL_ATTR_IMP_ROW_DESC`:idx:
-     `odbcsql.html#375 <odbcsql.html#375>`_
-
-   `SQL_ATTR_LOGIN_TIMEOUT`:idx:
-     `odbcsql.html#422 <odbcsql.html#422>`_
-
-   `SQL_ATTR_MAX_ROWS`:idx:
-     `odbcsql.html#404 <odbcsql.html#404>`_
-
-   `SQL_ATTR_METADATA_ID`:idx:
-     `odbcsql.html#372 <odbcsql.html#372>`_
-
-   `SQL_ATTR_ODBC_CURSORS`:idx:
-     `odbcsql.html#341 <odbcsql.html#341>`_
-
-   `SQL_ATTR_ODBC_VERSION`:idx:
-     `odbcsql.html#240 <odbcsql.html#240>`_
-
-   `SQL_ATTR_OUTPUT_NTS`:idx:
-     `odbcsql.html#370 <odbcsql.html#370>`_
-
-   `SQL_ATTR_PACKET_SIZE`:idx:
-     `odbcsql.html#423 <odbcsql.html#423>`_
-
-   `SQL_ATTR_QUIET_MODE`:idx:
-     `odbcsql.html#424 <odbcsql.html#424>`_
-
-   `SQL_ATTR_ROW_ARRAY_SIZE`:idx:
-     `odbcsql.html#620 <odbcsql.html#620>`_
-
-   `SQL_ATTR_ROW_NUMBER`:idx:
-     `odbcsql.html#401 <odbcsql.html#401>`_
-
-   `SQL_ATTR_ROWS_FETCHED_PTR`:idx:
-     `odbcsql.html#398 <odbcsql.html#398>`_
-
-   `SQL_ATTR_ROW_STATUS_PTR`:idx:
-     `odbcsql.html#397 <odbcsql.html#397>`_
-
-   `SQL_ATTR_TRACE`:idx:
-     `odbcsql.html#425 <odbcsql.html#425>`_
-
-   `SQL_ATTR_TRACEFILE`:idx:
-     `odbcsql.html#426 <odbcsql.html#426>`_
-
-   `SQL_ATTR_TRANSLATE_LIB`:idx:
-     `odbcsql.html#427 <odbcsql.html#427>`_
-
-   `SQL_ATTR_TRANSLATE_OPTION`:idx:
-     `odbcsql.html#428 <odbcsql.html#428>`_
-
-   `SQL_ATTR_TXN_ISOLATION`:idx:
-     `odbcsql.html#403 <odbcsql.html#403>`_
-
-   `SQL_ATTR_USE_BOOKMARKS`:idx:
-     `odbcsql.html#405 <odbcsql.html#405>`_
-
-   `SQL_AUTOCOMMIT`:idx:
-     `odbcsql.html#399 <odbcsql.html#399>`_
-
-   `SQL_AUTOCOMMIT_DEFAULT`:idx:
-     `odbcsql.html#434 <odbcsql.html#434>`_
-
-   `SQL_AUTOCOMMIT_OFF`:idx:
-     `odbcsql.html#432 <odbcsql.html#432>`_
-
-   `SQL_AUTOCOMMIT_ON`:idx:
-     `odbcsql.html#433 <odbcsql.html#433>`_
-
-   `SQL_BEST_ROWID`:idx:
-     `odbcsql.html#523 <odbcsql.html#523>`_
-
-   `SQL_BIGINT`:idx:
-     `odbcsql.html#130 <odbcsql.html#130>`_
-
-   `SQL_BINARY`:idx:
-     `odbcsql.html#127 <odbcsql.html#127>`_
-
-   `SQLBindCol`:idx:
-     `odbcsql.html#652 <odbcsql.html#652>`_
-
-   `SQLBindParameter`:idx:
-     `odbcsql.html#660 <odbcsql.html#660>`_
-
-   `SQL_BIND_TYPE`:idx:
-     `odbcsql.html#384 <odbcsql.html#384>`_
-
-   `SQL_BIT`:idx:
-     `odbcsql.html#132 <odbcsql.html#132>`_
-
-   `SQL_BOOKMARK_PERSISTENCE`:idx:
-     `odbcsql.html#262 <odbcsql.html#262>`_
-
-   `SQL_BP_CLOSE`:idx:
-     `odbcsql.html#264 <odbcsql.html#264>`_
-
-   `SQL_BP_DELETE`:idx:
-     `odbcsql.html#265 <odbcsql.html#265>`_
-
-   `SQL_BP_DROP`:idx:
-     `odbcsql.html#266 <odbcsql.html#266>`_
-
-   `SQL_BP_OTHER_HSTMT`:idx:
-     `odbcsql.html#269 <odbcsql.html#269>`_
-
-   `SQL_BP_SCROLL`:idx:
-     `odbcsql.html#270 <odbcsql.html#270>`_
-
-   `SQL_BP_TRANSACTION`:idx:
-     `odbcsql.html#267 <odbcsql.html#267>`_
-
-   `SQL_BP_UPDATE`:idx:
-     `odbcsql.html#268 <odbcsql.html#268>`_
-
-   `SQLBrowseConnect`:idx:
-     `odbcsql.html#636 <odbcsql.html#636>`_
-
-   `SQLBulkOperations`:idx:
-     `odbcsql.html#650 <odbcsql.html#650>`_
-
-   `SQL_CA1_ABSOLUTE`:idx:
-     `odbcsql.html#282 <odbcsql.html#282>`_
-
-   `SQL_CA1_BOOKMARK`:idx:
-     `odbcsql.html#284 <odbcsql.html#284>`_
-
-   `SQL_CA1_BULK_ADD`:idx:
-     `odbcsql.html#295 <odbcsql.html#295>`_
-
-   `SQL_CA1_BULK_DELETE_BY_BOOKMARK`:idx:
-     `odbcsql.html#297 <odbcsql.html#297>`_
-
-   `SQL_CA1_BULK_FETCH_BY_BOOKMARK`:idx:
-     `odbcsql.html#298 <odbcsql.html#298>`_
-
-   `SQL_CA1_BULK_UPDATE_BY_BOOKMARK`:idx:
-     `odbcsql.html#296 <odbcsql.html#296>`_
-
-   `SQL_CA1_LOCK_EXCLUSIVE`:idx:
-     `odbcsql.html#286 <odbcsql.html#286>`_
-
-   `SQL_CA1_LOCK_NO_CHANGE`:idx:
-     `odbcsql.html#285 <odbcsql.html#285>`_
-
-   `SQL_CA1_LOCK_UNLOCK`:idx:
-     `odbcsql.html#287 <odbcsql.html#287>`_
-
-   `SQL_CA1_NEXT`:idx:
-     `odbcsql.html#281 <odbcsql.html#281>`_
-
-   `SQL_CA1_POS_DELETE`:idx:
-     `odbcsql.html#290 <odbcsql.html#290>`_
-
-   `SQL_CA1_POSITIONED_DELETE`:idx:
-     `odbcsql.html#293 <odbcsql.html#293>`_
-
-   `SQL_CA1_POSITIONED_UPDATE`:idx:
-     `odbcsql.html#292 <odbcsql.html#292>`_
-
-   `SQL_CA1_POS_POSITION`:idx:
-     `odbcsql.html#288 <odbcsql.html#288>`_
-
-   `SQL_CA1_POS_REFRESH`:idx:
-     `odbcsql.html#291 <odbcsql.html#291>`_
-
-   `SQL_CA1_POS_UPDATE`:idx:
-     `odbcsql.html#289 <odbcsql.html#289>`_
-
-   `SQL_CA1_RELATIVE`:idx:
-     `odbcsql.html#283 <odbcsql.html#283>`_
-
-   `SQL_CA1_SELECT_FOR_UPDATE`:idx:
-     `odbcsql.html#294 <odbcsql.html#294>`_
-
-   `SQL_CA2_CRC_APPROXIMATE`:idx:
-     `odbcsql.html#313 <odbcsql.html#313>`_
-
-   `SQL_CA2_CRC_EXACT`:idx:
-     `odbcsql.html#312 <odbcsql.html#312>`_
-
-   `SQL_CA2_LOCK_CONCURRENCY`:idx:
-     `odbcsql.html#300 <odbcsql.html#300>`_
-
-   `SQL_CA2_MAX_ROWS_AFFECTS_ALL`:idx:
-     `odbcsql.html#311 <odbcsql.html#311>`_
-
-   `SQL_CA2_MAX_ROWS_CATALOG`:idx:
-     `odbcsql.html#310 <odbcsql.html#310>`_
-
-   `SQL_CA2_MAX_ROWS_DELETE`:idx:
-     `odbcsql.html#308 <odbcsql.html#308>`_
-
-   `SQL_CA2_MAX_ROWS_INSERT`:idx:
-     `odbcsql.html#307 <odbcsql.html#307>`_
-
-   `SQL_CA2_MAX_ROWS_SELECT`:idx:
-     `odbcsql.html#306 <odbcsql.html#306>`_
-
-   `SQL_CA2_MAX_ROWS_UPDATE`:idx:
-     `odbcsql.html#309 <odbcsql.html#309>`_
-
-   `SQL_CA2_OPT_ROWVER_CONCURRENCY`:idx:
-     `odbcsql.html#301 <odbcsql.html#301>`_
-
-   `SQL_CA2_OPT_VALUES_CONCURRENCY`:idx:
-     `odbcsql.html#302 <odbcsql.html#302>`_
-
-   `SQL_CA2_READ_ONLY_CONCURRENCY`:idx:
-     `odbcsql.html#299 <odbcsql.html#299>`_
-
-   `SQL_CA2_SENSITIVITY_ADDITIONS`:idx:
-     `odbcsql.html#303 <odbcsql.html#303>`_
-
-   `SQL_CA2_SENSITIVITY_DELETIONS`:idx:
-     `odbcsql.html#304 <odbcsql.html#304>`_
-
-   `SQL_CA2_SENSITIVITY_UPDATES`:idx:
-     `odbcsql.html#305 <odbcsql.html#305>`_
-
-   `SQL_CA2_SIMULATE_NON_UNIQUE`:idx:
-     `odbcsql.html#314 <odbcsql.html#314>`_
-
-   `SQL_CA2_SIMULATE_TRY_UNIQUE`:idx:
-     `odbcsql.html#315 <odbcsql.html#315>`_
-
-   `SQL_CA2_SIMULATE_UNIQUE`:idx:
-     `odbcsql.html#316 <odbcsql.html#316>`_
-
-   `SQL_CATALOG_NAME`:idx:
-     `odbcsql.html#545 <odbcsql.html#545>`_
-
-   `SQL_C_BINARY`:idx:
-     `odbcsql.html#212 <odbcsql.html#212>`_
-
-   `SQL_C_BIT`:idx:
-     `odbcsql.html#213 <odbcsql.html#213>`_
-
-   `SQL_C_BOOKMARK`:idx:
-     `odbcsql.html#223 <odbcsql.html#223>`_
-
-   `SQL_C_CHAR`:idx:
-     `odbcsql.html#184 <odbcsql.html#184>`_
-
-   `SQL_C_DATE`:idx:
-     `odbcsql.html#193 <odbcsql.html#193>`_
-
-   `SQL_C_DEFAULT`:idx:
-     `odbcsql.html#190 <odbcsql.html#190>`_
-
-   `SQL_C_DOUBLE`:idx:
-     `odbcsql.html#188 <odbcsql.html#188>`_
-
-   `SQL_C_FLOAT`:idx:
-     `odbcsql.html#187 <odbcsql.html#187>`_
-
-   `SQL_C_GUID`:idx:
-     `odbcsql.html#224 <odbcsql.html#224>`_
-
-   `SQL_CHAR`:idx:
-     `odbcsql.html#136 <odbcsql.html#136>`_
-
-   `SQL_C_INTERVAL_DAY`:idx:
-     `odbcsql.html#201 <odbcsql.html#201>`_
-
-   `SQL_C_INTERVAL_DAY_TO_HOUR`:idx:
-     `odbcsql.html#206 <odbcsql.html#206>`_
-
-   `SQL_C_INTERVAL_DAY_TO_MINUTE`:idx:
-     `odbcsql.html#207 <odbcsql.html#207>`_
-
-   `SQL_C_INTERVAL_DAY_TO_SECOND`:idx:
-     `odbcsql.html#208 <odbcsql.html#208>`_
-
-   `SQL_C_INTERVAL_HOUR`:idx:
-     `odbcsql.html#202 <odbcsql.html#202>`_
-
-   `SQL_C_INTERVAL_HOUR_TO_MINUTE`:idx:
-     `odbcsql.html#209 <odbcsql.html#209>`_
-
-   `SQL_C_INTERVAL_HOUR_TO_SECOND`:idx:
-     `odbcsql.html#210 <odbcsql.html#210>`_
-
-   `SQL_C_INTERVAL_MINUTE`:idx:
-     `odbcsql.html#203 <odbcsql.html#203>`_
-
-   `SQL_C_INTERVAL_MINUTE_TO_SECOND`:idx:
-     `odbcsql.html#211 <odbcsql.html#211>`_
-
-   `SQL_C_INTERVAL_MONTH`:idx:
-     `odbcsql.html#200 <odbcsql.html#200>`_
-
-   `SQL_C_INTERVAL_SECOND`:idx:
-     `odbcsql.html#204 <odbcsql.html#204>`_
-
-   `SQL_C_INTERVAL_YEAR`:idx:
-     `odbcsql.html#199 <odbcsql.html#199>`_
-
-   `SQL_C_INTERVAL_YEAR_TO_MONTH`:idx:
-     `odbcsql.html#205 <odbcsql.html#205>`_
-
-   `SQL_C_LONG`:idx:
-     `odbcsql.html#185 <odbcsql.html#185>`_
-
-   `SQL_CLOSE`:idx:
-     `odbcsql.html#503 <odbcsql.html#503>`_
-
-   `SQLCloseCursor`:idx:
-     `odbcsql.html#639 <odbcsql.html#639>`_
-
-   `SQL_C_NUMERIC`:idx:
-     `odbcsql.html#189 <odbcsql.html#189>`_
-
-   `SQL_CODE_DATE`:idx:
-     `odbcsql.html#495 <odbcsql.html#495>`_
-
-   `SQL_CODE_DAY`:idx:
-     `odbcsql.html#156 <odbcsql.html#156>`_
-
-   `SQL_CODE_DAY_TO_HOUR`:idx:
-     `odbcsql.html#161 <odbcsql.html#161>`_
-
-   `SQL_CODE_DAY_TO_MINUTE`:idx:
-     `odbcsql.html#162 <odbcsql.html#162>`_
-
-   `SQL_CODE_DAY_TO_SECOND`:idx:
-     `odbcsql.html#163 <odbcsql.html#163>`_
-
-   `SQL_CODE_HOUR`:idx:
-     `odbcsql.html#157 <odbcsql.html#157>`_
-
-   `SQL_CODE_HOUR_TO_MINUTE`:idx:
-     `odbcsql.html#164 <odbcsql.html#164>`_
-
-   `SQL_CODE_HOUR_TO_SECOND`:idx:
-     `odbcsql.html#165 <odbcsql.html#165>`_
-
-   `SQL_CODE_MINUTE`:idx:
-     `odbcsql.html#158 <odbcsql.html#158>`_
-
-   `SQL_CODE_MINUTE_TO_SECOND`:idx:
-     `odbcsql.html#166 <odbcsql.html#166>`_
-
-   `SQL_CODE_MONTH`:idx:
-     `odbcsql.html#155 <odbcsql.html#155>`_
-
-   `SQL_CODE_SECOND`:idx:
-     `odbcsql.html#159 <odbcsql.html#159>`_
-
-   `SQL_CODE_TIME`:idx:
-     `odbcsql.html#496 <odbcsql.html#496>`_
-
-   `SQL_CODE_TIMESTAMP`:idx:
-     `odbcsql.html#497 <odbcsql.html#497>`_
-
-   `SQL_CODE_YEAR`:idx:
-     `odbcsql.html#154 <odbcsql.html#154>`_
-
-   `SQL_CODE_YEAR_TO_MONTH`:idx:
-     `odbcsql.html#160 <odbcsql.html#160>`_
-
-   `SQL_COLATT_OPT_MAX`:idx:
-     `odbcsql.html#588 <odbcsql.html#588>`_
-
-   `SQLColAttribute`:idx:
-     `odbcsql.html#662 <odbcsql.html#662>`_
-
-   `SQL_COLLATION_SEQ`:idx:
-     `odbcsql.html#546 <odbcsql.html#546>`_
-
-   `SQL_COLUMN_AUTO_INCREMENT`:idx:
-     `odbcsql.html#580 <odbcsql.html#580>`_
-
-   `SQL_COLUMN_CASE_SENSITIVE`:idx:
-     `odbcsql.html#581 <odbcsql.html#581>`_
-
-   `SQL_COLUMN_COUNT`:idx:
-     `odbcsql.html#569 <odbcsql.html#569>`_
-
-   `SQL_COLUMN_DISPLAY_SIZE`:idx:
-     `odbcsql.html#575 <odbcsql.html#575>`_
-
-   `SQL_COLUMN_DRIVER_START`:idx:
-     `odbcsql.html#589 <odbcsql.html#589>`_
-
-   `SQL_COLUMN_LABEL`:idx:
-     `odbcsql.html#587 <odbcsql.html#587>`_
-
-   `SQL_COLUMN_LENGTH`:idx:
-     `odbcsql.html#572 <odbcsql.html#572>`_
-
-   `SQL_COLUMN_MONEY`:idx:
-     `odbcsql.html#578 <odbcsql.html#578>`_
-
-   `SQL_COLUMN_NAME`:idx:
-     `odbcsql.html#570 <odbcsql.html#570>`_
-
-   `SQL_COLUMN_NULLABLE`:idx:
-     `odbcsql.html#576 <odbcsql.html#576>`_
-
-   `SQL_COLUMN_OWNER_NAME`:idx:
-     `odbcsql.html#585 <odbcsql.html#585>`_
-
-   `SQL_COLUMN_PRECISION`:idx:
-     `odbcsql.html#573 <odbcsql.html#573>`_
-
-   `SQL_COLUMN_QUALIFIER_NAME`:idx:
-     `odbcsql.html#586 <odbcsql.html#586>`_
-
-   `SQLColumns`:idx:
-     `odbcsql.html#665 <odbcsql.html#665>`_
-
-   `SQL_COLUMN_SCALE`:idx:
-     `odbcsql.html#574 <odbcsql.html#574>`_
-
-   `SQL_COLUMN_SEARCHABLE`:idx:
-     `odbcsql.html#582 <odbcsql.html#582>`_
-
-   `SQL_COLUMN_TABLE_NAME`:idx:
-     `odbcsql.html#584 <odbcsql.html#584>`_
-
-   `SQL_COLUMN_TYPE`:idx:
-     `odbcsql.html#571 <odbcsql.html#571>`_
-
-   `SQL_COLUMN_TYPE_NAME`:idx:
-     `odbcsql.html#583 <odbcsql.html#583>`_
-
-   `SQL_COLUMN_UNSIGNED`:idx:
-     `odbcsql.html#577 <odbcsql.html#577>`_
-
-   `SQL_COLUMN_UPDATABLE`:idx:
-     `odbcsql.html#579 <odbcsql.html#579>`_
-
-   `SQL_COMMIT`:idx:
-     `odbcsql.html#618 <odbcsql.html#618>`_
-
-   `SQL_CONCUR_DEFAULT`:idx:
-     `odbcsql.html#446 <odbcsql.html#446>`_
-
-   `SQL_CONCUR_LOCK`:idx:
-     `odbcsql.html#443 <odbcsql.html#443>`_
-
-   `SQL_CONCUR_READ_ONLY`:idx:
-     `odbcsql.html#442 <odbcsql.html#442>`_
-
-   `SQL_CONCURRENCY`:idx:
-     `odbcsql.html#386 <odbcsql.html#386>`_
-
-   `SQL_CONCUR_ROWVER`:idx:
-     `odbcsql.html#444 <odbcsql.html#444>`_
-
-   `SQL_CONCUR_VALUES`:idx:
-     `odbcsql.html#445 <odbcsql.html#445>`_
-
-   `SQLConnect`:idx:
-     `odbcsql.html#633 <odbcsql.html#633>`_
-
-   `SQL_C_SBIGINT`:idx:
-     `odbcsql.html#214 <odbcsql.html#214>`_
-
-   `SQL_C_SHORT`:idx:
-     `odbcsql.html#186 <odbcsql.html#186>`_
-
-   `SQL_C_SLONG`:idx:
-     `odbcsql.html#217 <odbcsql.html#217>`_
-
-   `SQL_C_SSHORT`:idx:
-     `odbcsql.html#218 <odbcsql.html#218>`_
-
-   `SQL_C_STINYINT`:idx:
-     `odbcsql.html#219 <odbcsql.html#219>`_
-
-   `SQL_C_TIME`:idx:
-     `odbcsql.html#194 <odbcsql.html#194>`_
-
-   `SQL_C_TIMESTAMP`:idx:
-     `odbcsql.html#195 <odbcsql.html#195>`_
-
-   `SQL_C_TINYINT`:idx:
-     `odbcsql.html#216 <odbcsql.html#216>`_
-
-   `SQL_C_TYPE_DATE`:idx:
-     `odbcsql.html#196 <odbcsql.html#196>`_
-
-   `SQL_C_TYPE_TIME`:idx:
-     `odbcsql.html#197 <odbcsql.html#197>`_
-
-   `SQL_C_TYPE_TIMESTAMP`:idx:
-     `odbcsql.html#198 <odbcsql.html#198>`_
-
-   `SQL_C_UBIGINT`:idx:
-     `odbcsql.html#215 <odbcsql.html#215>`_
-
-   `SQL_C_ULONG`:idx:
-     `odbcsql.html#220 <odbcsql.html#220>`_
-
-   `SQL_CUR_DEFAULT`:idx:
-     `odbcsql.html#345 <odbcsql.html#345>`_
-
-   `SQL_CURRENT_QUALIFIER`:idx:
-     `odbcsql.html#412 <odbcsql.html#412>`_
-
-   `SQL_CURSOR_DYNAMIC`:idx:
-     `odbcsql.html#439 <odbcsql.html#439>`_
-
-   `SQL_CURSOR_FORWARD_ONLY`:idx:
-     `odbcsql.html#437 <odbcsql.html#437>`_
-
-   `SQL_CURSOR_KEYSET_DRIVEN`:idx:
-     `odbcsql.html#438 <odbcsql.html#438>`_
-
-   `SQL_CURSOR_SENSITIVITY`:idx:
-     `odbcsql.html#543 <odbcsql.html#543>`_
-
-   `SQL_CURSOR_STATIC`:idx:
-     `odbcsql.html#440 <odbcsql.html#440>`_
-
-   `SQL_CURSOR_TYPE`:idx:
-     `odbcsql.html#385 <odbcsql.html#385>`_
-
-   `SQL_CURSOR_TYPE_DEFAULT`:idx:
-     `odbcsql.html#441 <odbcsql.html#441>`_
-
-   `SQL_CUR_USE_DRIVER`:idx:
-     `odbcsql.html#344 <odbcsql.html#344>`_
-
-   `SQL_CUR_USE_IF_NEEDED`:idx:
-     `odbcsql.html#342 <odbcsql.html#342>`_
-
-   `SQL_CUR_USE_ODBC`:idx:
-     `odbcsql.html#343 <odbcsql.html#343>`_
-
-   `SQL_C_USHORT`:idx:
-     `odbcsql.html#221 <odbcsql.html#221>`_
-
-   `SQL_C_UTINYINT`:idx:
-     `odbcsql.html#222 <odbcsql.html#222>`_
-
-   `SQL_C_VARBOOKMARK`:idx:
-     `odbcsql.html#228 <odbcsql.html#228>`_
-
-   `SQL_DATA_AT_EXEC`:idx:
-     `odbcsql.html#353 <odbcsql.html#353>`_
-
-   `SQLDataSources`:idx:
-     `odbcsql.html#654 <odbcsql.html#654>`_
-
-   `SQL_DATE`:idx:
-     `odbcsql.html#149 <odbcsql.html#149>`_
-
-   `SQL_DATE_LEN`:idx:
-     `odbcsql.html#363 <odbcsql.html#363>`_
-
-   `SQL_DATE_STRUCT`:idx:
-     `odbcsql.html#231 <odbcsql.html#231>`_
-
-   `SQL_DATETIME`:idx:
-     `odbcsql.html#144 <odbcsql.html#144>`_
-
-   `SQL_DECIMAL`:idx:
-     `odbcsql.html#138 <odbcsql.html#138>`_
-
-   `SQL_DEFAULT`:idx:
-     `odbcsql.html#493 <odbcsql.html#493>`_
-
-   `SQL_DELETE`:idx:
-     `odbcsql.html#325 <odbcsql.html#325>`_
-
-   `SQL_DELETE_BY_BOOKMARK`:idx:
-     `odbcsql.html#320 <odbcsql.html#320>`_
-
-   `SQL_DESC_ALLOC_TYPE`:idx:
-     `odbcsql.html#460 <odbcsql.html#460>`_
-
-   `SQL_DESC_ARRAY_SIZE`:idx:
-     `odbcsql.html#590 <odbcsql.html#590>`_
-
-   `SQL_DESC_ARRAY_STATUS_PTR`:idx:
-     `odbcsql.html#591 <odbcsql.html#591>`_
-
-   `SQL_DESC_AUTO_UNIQUE_VALUE`:idx:
-     `odbcsql.html#592 <odbcsql.html#592>`_
-
-   `SQL_DESC_BASE_COLUMN_NAME`:idx:
-     `odbcsql.html#593 <odbcsql.html#593>`_
-
-   `SQL_DESC_BASE_TABLE_NAME`:idx:
-     `odbcsql.html#594 <odbcsql.html#594>`_
-
-   `SQL_DESC_BIND_OFFSET_PTR`:idx:
-     `odbcsql.html#595 <odbcsql.html#595>`_
-
-   `SQL_DESC_BIND_TYPE`:idx:
-     `odbcsql.html#596 <odbcsql.html#596>`_
-
-   `SQL_DESC_CASE_SENSITIVE`:idx:
-     `odbcsql.html#597 <odbcsql.html#597>`_
-
-   `SQL_DESC_CATALOG_NAME`:idx:
-     `odbcsql.html#598 <odbcsql.html#598>`_
-
-   `SQL_DESC_CONCISE_TYPE`:idx:
-     `odbcsql.html#599 <odbcsql.html#599>`_
-
-   `SQL_DESC_COUNT`:idx:
-     `odbcsql.html#447 <odbcsql.html#447>`_
-
-   `SQL_DESC_DATA_PTR`:idx:
-     `odbcsql.html#456 <odbcsql.html#456>`_
-
-   `SQL_DESC_DATETIME_INTERVAL_CODE`:idx:
-     `odbcsql.html#453 <odbcsql.html#453>`_
-
-   `SQL_DESC_DATETIME_INTERVAL_PRECISION`:idx:
-     `odbcsql.html#600 <odbcsql.html#600>`_
-
-   `SQL_DESC_DISPLAY_SIZE`:idx:
-     `odbcsql.html#601 <odbcsql.html#601>`_
-
-   `SQL_DESC_FIXED_PREC_SCALE`:idx:
-     `odbcsql.html#602 <odbcsql.html#602>`_
-
-   `SQL_DESC_INDICATOR_PTR`:idx:
-     `odbcsql.html#455 <odbcsql.html#455>`_
-
-   `SQL_DESC_LABEL`:idx:
-     `odbcsql.html#603 <odbcsql.html#603>`_
-
-   `SQL_DESC_LENGTH`:idx:
-     `odbcsql.html#449 <odbcsql.html#449>`_
-
-   `SQL_DESC_LITERAL_PREFIX`:idx:
-     `odbcsql.html#604 <odbcsql.html#604>`_
-
-   `SQL_DESC_LITERAL_SUFFIX`:idx:
-     `odbcsql.html#605 <odbcsql.html#605>`_
-
-   `SQL_DESC_LOCAL_TYPE_NAME`:idx:
-     `odbcsql.html#606 <odbcsql.html#606>`_
-
-   `SQL_DESC_MAXIMUM_SCALE`:idx:
-     `odbcsql.html#607 <odbcsql.html#607>`_
-
-   `SQL_DESC_MINIMUM_SCALE`:idx:
-     `odbcsql.html#608 <odbcsql.html#608>`_
-
-   `SQL_DESC_NAME`:idx:
-     `odbcsql.html#457 <odbcsql.html#457>`_
-
-   `SQL_DESC_NULLABLE`:idx:
-     `odbcsql.html#454 <odbcsql.html#454>`_
-
-   `SQL_DESC_NUM_PREC_RADIX`:idx:
-     `odbcsql.html#609 <odbcsql.html#609>`_
-
-   `SQL_DESC_OCTET_LENGTH`:idx:
-     `odbcsql.html#459 <odbcsql.html#459>`_
-
-   `SQL_DESC_OCTET_LENGTH_PTR`:idx:
-     `odbcsql.html#450 <odbcsql.html#450>`_
-
-   `SQL_DESC_PARAMETER_TYPE`:idx:
-     `odbcsql.html#610 <odbcsql.html#610>`_
-
-   `SQL_DESC_PRECISION`:idx:
-     `odbcsql.html#451 <odbcsql.html#451>`_
-
-   `SQLDescribeCol`:idx:
-     `odbcsql.html#643 <odbcsql.html#643>`_
-
-   `SQL_DESCRIBE_PARAMETER`:idx:
-     `odbcsql.html#544 <odbcsql.html#544>`_
-
-   `SQL_DESC_ROWS_PROCESSED_PTR`:idx:
-     `odbcsql.html#611 <odbcsql.html#611>`_
-
-   `SQL_DESC_SCALE`:idx:
-     `odbcsql.html#452 <odbcsql.html#452>`_
-
-   `SQL_DESC_SCHEMA_NAME`:idx:
-     `odbcsql.html#612 <odbcsql.html#612>`_
-
-   `SQL_DESC_SEARCHABLE`:idx:
-     `odbcsql.html#613 <odbcsql.html#613>`_
-
-   `SQL_DESC_TABLE_NAME`:idx:
-     `odbcsql.html#615 <odbcsql.html#615>`_
-
-   `SQL_DESC_TYPE`:idx:
-     `odbcsql.html#448 <odbcsql.html#448>`_
-
-   `SQL_DESC_TYPE_NAME`:idx:
-     `odbcsql.html#614 <odbcsql.html#614>`_
-
-   `SQL_DESC_UNNAMED`:idx:
-     `odbcsql.html#458 <odbcsql.html#458>`_
-
-   `SQL_DESC_UNSIGNED`:idx:
-     `odbcsql.html#616 <odbcsql.html#616>`_
-
-   `SQL_DESC_UPDATABLE`:idx:
-     `odbcsql.html#617 <odbcsql.html#617>`_
-
-   `SQL_DIAG_ALTER_TABLE`:idx:
-     `odbcsql.html#473 <odbcsql.html#473>`_
-
-   `SQL_DIAG_CLASS_ORIGIN`:idx:
-     `odbcsql.html#468 <odbcsql.html#468>`_
-
-   `SQL_DIAG_CONNECTION_NAME`:idx:
-     `odbcsql.html#470 <odbcsql.html#470>`_
-
-   `SQL_DIAG_CREATE_INDEX`:idx:
-     `odbcsql.html#474 <odbcsql.html#474>`_
-
-   `SQL_DIAG_CREATE_TABLE`:idx:
-     `odbcsql.html#475 <odbcsql.html#475>`_
-
-   `SQL_DIAG_CREATE_VIEW`:idx:
-     `odbcsql.html#476 <odbcsql.html#476>`_
-
-   `SQL_DIAG_DELETE_WHERE`:idx:
-     `odbcsql.html#477 <odbcsql.html#477>`_
-
-   `SQL_DIAG_DROP_INDEX`:idx:
-     `odbcsql.html#478 <odbcsql.html#478>`_
-
-   `SQL_DIAG_DROP_TABLE`:idx:
-     `odbcsql.html#479 <odbcsql.html#479>`_
-
-   `SQL_DIAG_DROP_VIEW`:idx:
-     `odbcsql.html#480 <odbcsql.html#480>`_
-
-   `SQL_DIAG_DYNAMIC_DELETE_CURSOR`:idx:
-     `odbcsql.html#481 <odbcsql.html#481>`_
-
-   `SQL_DIAG_DYNAMIC_FUNCTION`:idx:
-     `odbcsql.html#467 <odbcsql.html#467>`_
-
-   `SQL_DIAG_DYNAMIC_FUNCTION_CODE`:idx:
-     `odbcsql.html#472 <odbcsql.html#472>`_
-
-   `SQL_DIAG_DYNAMIC_UPDATE_CURSOR`:idx:
-     `odbcsql.html#482 <odbcsql.html#482>`_
-
-   `SQL_DIAG_GRANT`:idx:
-     `odbcsql.html#483 <odbcsql.html#483>`_
-
-   `SQL_DIAG_INSERT`:idx:
-     `odbcsql.html#484 <odbcsql.html#484>`_
-
-   `SQL_DIAG_MESSAGE_TEXT`:idx:
-     `odbcsql.html#466 <odbcsql.html#466>`_
-
-   `SQL_DIAG_NATIVE`:idx:
-     `odbcsql.html#465 <odbcsql.html#465>`_
-
-   `SQL_DIAG_NUMBER`:idx:
-     `odbcsql.html#462 <odbcsql.html#462>`_
-
-   `SQL_DIAG_RETURNCODE`:idx:
-     `odbcsql.html#461 <odbcsql.html#461>`_
-
-   `SQL_DIAG_REVOKE`:idx:
-     `odbcsql.html#485 <odbcsql.html#485>`_
-
-   `SQL_DIAG_ROW_COUNT`:idx:
-     `odbcsql.html#463 <odbcsql.html#463>`_
-
-   `SQL_DIAG_SELECT_CURSOR`:idx:
-     `odbcsql.html#486 <odbcsql.html#486>`_
-
-   `SQL_DIAG_SERVER_NAME`:idx:
-     `odbcsql.html#471 <odbcsql.html#471>`_
-
-   `SQL_DIAG_SQLSTATE`:idx:
-     `odbcsql.html#464 <odbcsql.html#464>`_
-
-   `SQL_DIAG_SUBCLASS_ORIGIN`:idx:
-     `odbcsql.html#469 <odbcsql.html#469>`_
-
-   `SQL_DIAG_UNKNOWN_STATEMENT`:idx:
-     `odbcsql.html#487 <odbcsql.html#487>`_
-
-   `SQL_DIAG_UPDATE_WHERE`:idx:
-     `odbcsql.html#488 <odbcsql.html#488>`_
-
-   `SQLDisconnect`:idx:
-     `odbcsql.html#634 <odbcsql.html#634>`_
-
-   `SQL_DOUBLE`:idx:
-     `odbcsql.html#143 <odbcsql.html#143>`_
-
-   `SQL_DRIVER_COMPLETE`:idx:
-     `odbcsql.html#242 <odbcsql.html#242>`_
-
-   `SQL_DRIVER_COMPLETE_REQUIRED`:idx:
-     `odbcsql.html#244 <odbcsql.html#244>`_
-
-   `SQLDriverConnect`:idx:
-     `odbcsql.html#635 <odbcsql.html#635>`_
-
-   `SQL_DRIVER_NOPROMPT`:idx:
-     `odbcsql.html#241 <odbcsql.html#241>`_
-
-   `SQL_DRIVER_PROMPT`:idx:
-     `odbcsql.html#243 <odbcsql.html#243>`_
-
-   `SQLDrivers`:idx:
-     `odbcsql.html#655 <odbcsql.html#655>`_
-
-   `SQL_DROP`:idx:
-     `odbcsql.html#504 <odbcsql.html#504>`_
-
-   `SQL_DYNAMIC_CURSOR_ATTRIBUTES1`:idx:
-     `odbcsql.html#271 <odbcsql.html#271>`_
-
-   `SQL_DYNAMIC_CURSOR_ATTRIBUTES2`:idx:
-     `odbcsql.html#272 <odbcsql.html#272>`_
-
-   `SQLEndTran`:idx:
-     `odbcsql.html#663 <odbcsql.html#663>`_
-
-   `SQL_ENSURE`:idx:
-     `odbcsql.html#529 <odbcsql.html#529>`_
-
-   `SQL_ERROR`:idx:
-     `odbcsql.html#357 <odbcsql.html#357>`_
-
-   `SQLExecDirect`:idx:
-     `odbcsql.html#637 <odbcsql.html#637>`_
-
-   `SQLExecute`:idx:
-     `odbcsql.html#640 <odbcsql.html#640>`_
-
-   `SQLExtendedFetch`:idx:
-     `odbcsql.html#645 <odbcsql.html#645>`_
-
-   `SQL_FALSE`:idx:
-     `odbcsql.html#498 <odbcsql.html#498>`_
-
-   `SQLFetch`:idx:
-     `odbcsql.html#641 <odbcsql.html#641>`_
-
-   `SQL_FETCH_ABSOLUTE`:idx:
-     `odbcsql.html#513 <odbcsql.html#513>`_
-
-   `SQL_FETCH_BOOKMARK`:idx:
-     `odbcsql.html#250 <odbcsql.html#250>`_
-
-   `SQL_FETCH_BY_BOOKMARK`:idx:
-     `odbcsql.html#321 <odbcsql.html#321>`_
-
-   `SQL_FETCH_FIRST`:idx:
-     `odbcsql.html#508 <odbcsql.html#508>`_
-
-   `SQL_FETCH_FIRST_SYSTEM`:idx:
-     `odbcsql.html#510 <odbcsql.html#510>`_
-
-   `SQL_FETCH_FIRST_USER`:idx:
-     `odbcsql.html#509 <odbcsql.html#509>`_
-
-   `SQL_FETCH_LAST`:idx:
-     `odbcsql.html#511 <odbcsql.html#511>`_
-
-   `SQL_FETCH_NEXT`:idx:
-     `odbcsql.html#507 <odbcsql.html#507>`_
-
-   `SQL_FETCH_PRIOR`:idx:
-     `odbcsql.html#512 <odbcsql.html#512>`_
-
-   `SQL_FETCH_RELATIVE`:idx:
-     `odbcsql.html#514 <odbcsql.html#514>`_
-
-   `SQLFetchScroll`:idx:
-     `odbcsql.html#644 <odbcsql.html#644>`_
-
-   `SQL_FLOAT`:idx:
-     `odbcsql.html#141 <odbcsql.html#141>`_
-
-   `SQL_FORWARD_ONLY_CURSOR_ATTRIBUTES1`:idx:
-     `odbcsql.html#273 <odbcsql.html#273>`_
-
-   `SQL_FORWARD_ONLY_CURSOR_ATTRIBUTES2`:idx:
-     `odbcsql.html#274 <odbcsql.html#274>`_
-
-   `SQLFreeHandle`:idx:
-     `odbcsql.html#630 <odbcsql.html#630>`_
-
-   `SQLFreeStmt`:idx:
-     `odbcsql.html#661 <odbcsql.html#661>`_
-
-   `SQL_GET_BOOKMARK`:idx:
-     `odbcsql.html#392 <odbcsql.html#392>`_
-
-   `SQLGetCursorName`:idx:
-     `odbcsql.html#657 <odbcsql.html#657>`_
-
-   `SQLGetData`:idx:
-     `odbcsql.html#646 <odbcsql.html#646>`_
-
-   `SQLGetDiagField`:idx:
-     `odbcsql.html#632 <odbcsql.html#632>`_
-
-   `SQLGetDiagRec`:idx:
-     `odbcsql.html#631 <odbcsql.html#631>`_
-
-   `SQLGetEnvAttr`:idx:
-     `odbcsql.html#629 <odbcsql.html#629>`_
-
-   `SQLGetInfo`:idx:
-     `odbcsql.html#649 <odbcsql.html#649>`_
-
-   `SQLGetStmtAttr`:idx:
-     `odbcsql.html#648 <odbcsql.html#648>`_
-
-   `SQL_GUID`:idx:
-     `odbcsql.html#153 <odbcsql.html#153>`_
-
-   `SQL_HANDLE_DBC`:idx:
-     `odbcsql.html#367 <odbcsql.html#367>`_
-
-   `SQL_HANDLE_DESC`:idx:
-     `odbcsql.html#369 <odbcsql.html#369>`_
-
-   `SQL_HANDLE_ENV`:idx:
-     `odbcsql.html#366 <odbcsql.html#366>`_
-
-   `SQL_HANDLE_STMT`:idx:
-     `odbcsql.html#368 <odbcsql.html#368>`_
-
-   `SQL_INDEX_ALL`:idx:
-     `odbcsql.html#527 <odbcsql.html#527>`_
-
-   `SQL_INDEX_CLUSTERED`:idx:
-     `odbcsql.html#531 <odbcsql.html#531>`_
-
-   `SQL_INDEX_HASHED`:idx:
-     `odbcsql.html#532 <odbcsql.html#532>`_
-
-   `SQL_INDEX_KEYWORDS`:idx:
-     `odbcsql.html#275 <odbcsql.html#275>`_
-
-   `SQL_INDEX_OTHER`:idx:
-     `odbcsql.html#533 <odbcsql.html#533>`_
-
-   `SQL_INDEX_UNIQUE`:idx:
-     `odbcsql.html#526 <odbcsql.html#526>`_
-
-   `SQL_INFO_SCHEMA_VIEWS`:idx:
-     `odbcsql.html#276 <odbcsql.html#276>`_
-
-   `SQL_INSENSITIVE`:idx:
-     `odbcsql.html#490 <odbcsql.html#490>`_
-
-   `SQL_INTEGER`:idx:
-     `odbcsql.html#139 <odbcsql.html#139>`_
-
-   `SQL_INTERVAL`:idx:
-     `odbcsql.html#152 <odbcsql.html#152>`_
-
-   `SQL_INTERVAL_DAY`:idx:
-     `odbcsql.html#169 <odbcsql.html#169>`_
-
-   `SQL_INTERVAL_DAY_TO_HOUR`:idx:
-     `odbcsql.html#174 <odbcsql.html#174>`_
-
-   `SQL_INTERVAL_DAY_TO_MINUTE`:idx:
-     `odbcsql.html#175 <odbcsql.html#175>`_
-
-   `SQL_INTERVAL_DAY_TO_SECOND`:idx:
-     `odbcsql.html#176 <odbcsql.html#176>`_
-
-   `SQL_INTERVAL_HOUR`:idx:
-     `odbcsql.html#170 <odbcsql.html#170>`_
-
-   `SQL_INTERVAL_HOUR_TO_MINUTE`:idx:
-     `odbcsql.html#177 <odbcsql.html#177>`_
-
-   `SQL_INTERVAL_HOUR_TO_SECOND`:idx:
-     `odbcsql.html#178 <odbcsql.html#178>`_
-
-   `SQL_INTERVAL_MINUTE`:idx:
-     `odbcsql.html#171 <odbcsql.html#171>`_
-
-   `SQL_INTERVAL_MINUTE_TO_SECOND`:idx:
-     `odbcsql.html#179 <odbcsql.html#179>`_
-
-   `SQL_INTERVAL_MONTH`:idx:
-     `odbcsql.html#168 <odbcsql.html#168>`_
-
-   `SQL_INTERVAL_SECOND`:idx:
-     `odbcsql.html#172 <odbcsql.html#172>`_
-
-   `SQL_INTERVAL_YEAR`:idx:
-     `odbcsql.html#167 <odbcsql.html#167>`_
-
-   `SQL_INTERVAL_YEAR_TO_MONTH`:idx:
-     `odbcsql.html#173 <odbcsql.html#173>`_
-
-   `SQL_INVALID_HANDLE`:idx:
-     `odbcsql.html#358 <odbcsql.html#358>`_
-
-   `SQL_IS_INTEGER`:idx:
-     `odbcsql.html#247 <odbcsql.html#247>`_
-
-   `SQL_IS_POINTER`:idx:
-     `odbcsql.html#245 <odbcsql.html#245>`_
-
-   `SQL_IS_SMALLINT`:idx:
-     `odbcsql.html#249 <odbcsql.html#249>`_
-
-   `SQL_IS_UINTEGER`:idx:
-     `odbcsql.html#246 <odbcsql.html#246>`_
-
-   `SQL_IS_USMALLINT`:idx:
-     `odbcsql.html#248 <odbcsql.html#248>`_
-
-   `SQL_KEYSET_CURSOR_ATTRIBUTES1`:idx:
-     `odbcsql.html#277 <odbcsql.html#277>`_
-
-   `SQL_KEYSET_CURSOR_ATTRIBUTES2`:idx:
-     `odbcsql.html#278 <odbcsql.html#278>`_
-
-   `SQL_KEYSET_SIZE`:idx:
-     `odbcsql.html#387 <odbcsql.html#387>`_
-
-   `SQL_LOCK_EXCLUSIVE`:idx:
-     `odbcsql.html#327 <odbcsql.html#327>`_
-
-   `SQL_LOCK_NO_CHANGE`:idx:
-     `odbcsql.html#326 <odbcsql.html#326>`_
-
-   `SQL_LOCK_UNLOCK`:idx:
-     `odbcsql.html#328 <odbcsql.html#328>`_
-
-   `SQL_LOGIN_TIMEOUT`:idx:
-     `odbcsql.html#407 <odbcsql.html#407>`_
-
-   `SQL_LONGVARBINARY`:idx:
-     `odbcsql.html#129 <odbcsql.html#129>`_
-
-   `SQL_LONGVARCHAR`:idx:
-     `odbcsql.html#126 <odbcsql.html#126>`_
-
-   `SQL_MAX_DSN_LENGTH`:idx:
-     `odbcsql.html#338 <odbcsql.html#338>`_
-
-   `SQL_MAX_IDENTIFIER_LEN`:idx:
-     `odbcsql.html#547 <odbcsql.html#547>`_
-
-   `SQL_MAXIMUM_IDENTIFIER_LENGTH`:idx:
-     `odbcsql.html#548 <odbcsql.html#548>`_
-
-   `SQL_MAX_LENGTH`:idx:
-     `odbcsql.html#382 <odbcsql.html#382>`_
-
-   `SQL_MAX_MESSAGE_LENGTH`:idx:
-     `odbcsql.html#362 <odbcsql.html#362>`_
-
-   `SQL_MAX_OPTION_STRING_LENGTH`:idx:
-     `odbcsql.html#339 <odbcsql.html#339>`_
-
-   `SQL_MAX_ROWS`:idx:
-     `odbcsql.html#380 <odbcsql.html#380>`_
-
-   `SQL_MODE_DEFAULT`:idx:
-     `odbcsql.html#431 <odbcsql.html#431>`_
-
-   `SQL_MODE_READ_ONLY`:idx:
-     `odbcsql.html#430 <odbcsql.html#430>`_
-
-   `SQL_MODE_READ_WRITE`:idx:
-     `odbcsql.html#429 <odbcsql.html#429>`_
-
-   `SQL_NAME_LEN`:idx:
-     `odbcsql.html#237 <odbcsql.html#237>`_
-
-   `SQL_NEED_DATA`:idx:
-     `odbcsql.html#360 <odbcsql.html#360>`_
-
-   `SQL_NO_DATA`:idx:
-     `odbcsql.html#356 <odbcsql.html#356>`_
-
-   `SQL_NONSCROLLABLE`:idx:
-     `odbcsql.html#435 <odbcsql.html#435>`_
-
-   `SQL_NO_NULLS`:idx:
-     `odbcsql.html#500 <odbcsql.html#500>`_
-
-   `SQL_NOSCAN`:idx:
-     `odbcsql.html#381 <odbcsql.html#381>`_
-
-   `SQL_NO_TOTAL`:idx:
-     `odbcsql.html#230 <odbcsql.html#230>`_
-
-   `SQL_NTS`:idx:
-     `odbcsql.html#361 <odbcsql.html#361>`_
-
-   `SQL_NULLABLE`:idx:
-     `odbcsql.html#501 <odbcsql.html#501>`_
-
-   `SQL_NULLABLE_UNKNOWN`:idx:
-     `odbcsql.html#502 <odbcsql.html#502>`_
-
-   `SQL_NULL_DATA`:idx:
-     `odbcsql.html#352 <odbcsql.html#352>`_
-
-   `SQL_NULL_HANDLE`:idx:
-     `odbcsql.html#519 <odbcsql.html#519>`_
-
-   `SQL_NULL_HDBC`:idx:
-     `odbcsql.html#516 <odbcsql.html#516>`_
-
-   `SQL_NULL_HDESC`:idx:
-     `odbcsql.html#518 <odbcsql.html#518>`_
-
-   `SQL_NULL_HENV`:idx:
-     `odbcsql.html#515 <odbcsql.html#515>`_
-
-   `SQL_NULL_HSTMT`:idx:
-     `odbcsql.html#517 <odbcsql.html#517>`_
-
-   `SQL_NUMERIC`:idx:
-     `odbcsql.html#137 <odbcsql.html#137>`_
-
-   `SQLNumResultCols`:idx:
-     `odbcsql.html#642 <odbcsql.html#642>`_
-
-   `SQL_ODBC_CURSORS`:idx:
-     `odbcsql.html#340 <odbcsql.html#340>`_
-
-   `SQL_OJ_CAPABILITIES`:idx:
-     `odbcsql.html#540 <odbcsql.html#540>`_
-
-   `SQL_OPT_TRACE`:idx:
-     `odbcsql.html#408 <odbcsql.html#408>`_
-
-   `SQL_OPT_TRACEFILE`:idx:
-     `odbcsql.html#409 <odbcsql.html#409>`_
-
-   `SQL_OUTER_JOIN_CAPABILITIES`:idx:
-     `odbcsql.html#541 <odbcsql.html#541>`_
-
-   `SQL_OV_ODBC2`:idx:
-     `odbcsql.html#239 <odbcsql.html#239>`_
-
-   `SQL_OV_ODBC3`:idx:
-     `odbcsql.html#238 <odbcsql.html#238>`_
-
-   `SQL_PACKET_SIZE`:idx:
-     `odbcsql.html#414 <odbcsql.html#414>`_
-
-   `SQL_PARAM_INPUT`:idx:
-     `odbcsql.html#347 <odbcsql.html#347>`_
-
-   `SQL_PARAM_INPUT_OUTPUT`:idx:
-     `odbcsql.html#348 <odbcsql.html#348>`_
-
-   `SQL_PARAM_OUTPUT`:idx:
-     `odbcsql.html#350 <odbcsql.html#350>`_
-
-   `SQL_PARAM_TYPE_UNKNOWN`:idx:
-     `odbcsql.html#346 <odbcsql.html#346>`_
-
-   `SQL_POSITION`:idx:
-     `odbcsql.html#322 <odbcsql.html#322>`_
-
-   `SQLPrepare`:idx:
-     `odbcsql.html#638 <odbcsql.html#638>`_
-
-   `SQLPrimaryKeys`:idx:
-     `odbcsql.html#668 <odbcsql.html#668>`_
-
-   `SQLProcedureColumns`:idx:
-     `odbcsql.html#669 <odbcsql.html#669>`_
-
-   `SQLProcedures`:idx:
-     `odbcsql.html#667 <odbcsql.html#667>`_
-
-   `SQLPutData`:idx:
-     `odbcsql.html#651 <odbcsql.html#651>`_
-
-   `SQL_QUERY_TIMEOUT`:idx:
-     `odbcsql.html#379 <odbcsql.html#379>`_
-
-   `SQL_QUICK`:idx:
-     `odbcsql.html#528 <odbcsql.html#528>`_
-
-   `SQL_QUIET_MODE`:idx:
-     `odbcsql.html#413 <odbcsql.html#413>`_
-
-   `SQL_REAL`:idx:
-     `odbcsql.html#142 <odbcsql.html#142>`_
-
-   `SQL_REFRESH`:idx:
-     `odbcsql.html#323 <odbcsql.html#323>`_
-
-   `SQL_RESET_PARAMS`:idx:
-     `odbcsql.html#506 <odbcsql.html#506>`_
-
-   `SQL_RESULT_COL`:idx:
-     `odbcsql.html#349 <odbcsql.html#349>`_
-
-   `SQL_RETRIEVE_DATA`:idx:
-     `odbcsql.html#390 <odbcsql.html#390>`_
-
-   `SQL_RETURN_VALUE`:idx:
-     `odbcsql.html#351 <odbcsql.html#351>`_
-
-   `SQL_ROLLBACK`:idx:
-     `odbcsql.html#619 <odbcsql.html#619>`_
-
-   `SQL_ROW_ADDED`:idx:
-     `odbcsql.html#333 <odbcsql.html#333>`_
-
-   `SQLRowCount`:idx:
-     `odbcsql.html#659 <odbcsql.html#659>`_
-
-   `SQL_ROW_DELETED`:idx:
-     `odbcsql.html#330 <odbcsql.html#330>`_
-
-   `SQL_ROW_ERROR`:idx:
-     `odbcsql.html#334 <odbcsql.html#334>`_
-
-   `SQL_ROW_IDENTIFIER`:idx:
-     `odbcsql.html#525 <odbcsql.html#525>`_
-
-   `SQL_ROW_IGNORE`:idx:
-     `odbcsql.html#337 <odbcsql.html#337>`_
-
-   `SQL_ROW_NOROW`:idx:
-     `odbcsql.html#332 <odbcsql.html#332>`_
-
-   `SQL_ROW_NUMBER`:idx:
-     `odbcsql.html#393 <odbcsql.html#393>`_
-
-   `SQL_ROW_PROCEED`:idx:
-     `odbcsql.html#336 <odbcsql.html#336>`_
-
-   `SQL_ROWSET_SIZE`:idx:
-     `odbcsql.html#388 <odbcsql.html#388>`_
-
-   `SQL_ROW_SUCCESS`:idx:
-     `odbcsql.html#329 <odbcsql.html#329>`_
-
-   `SQL_ROW_SUCCESS_WITH_INFO`:idx:
-     `odbcsql.html#335 <odbcsql.html#335>`_
-
-   `SQL_ROW_UPDATED`:idx:
-     `odbcsql.html#331 <odbcsql.html#331>`_
-
-   `SQL_ROWVER`:idx:
-     `odbcsql.html#524 <odbcsql.html#524>`_
-
-   `SQL_SCCO_LOCK`:idx:
-     `odbcsql.html#550 <odbcsql.html#550>`_
-
-   `SQL_SCCO_OPT_ROWVER`:idx:
-     `odbcsql.html#551 <odbcsql.html#551>`_
-
-   `SQL_SCCO_OPT_VALUES`:idx:
-     `odbcsql.html#552 <odbcsql.html#552>`_
-
-   `SQL_SCCO_READ_ONLY`:idx:
-     `odbcsql.html#549 <odbcsql.html#549>`_
-
-   `SQL_SCOPE_CURROW`:idx:
-     `odbcsql.html#520 <odbcsql.html#520>`_
-
-   `SQL_SCOPE_SESSION`:idx:
-     `odbcsql.html#522 <odbcsql.html#522>`_
-
-   `SQL_SCOPE_TRANSACTION`:idx:
-     `odbcsql.html#521 <odbcsql.html#521>`_
-
-   `SQL_SCROLLABLE`:idx:
-     `odbcsql.html#436 <odbcsql.html#436>`_
-
-   `SQL_SCROLL_CONCURRENCY`:idx:
-     `odbcsql.html#534 <odbcsql.html#534>`_
-
-   `SQL_SCROLL_OPTIONS`:idx:
-     `odbcsql.html#251 <odbcsql.html#251>`_
-
-   `SQL_SENSITIVE`:idx:
-     `odbcsql.html#491 <odbcsql.html#491>`_
-
-   `SQLSetConnectAttr`:idx:
-     `odbcsql.html#656 <odbcsql.html#656>`_
-
-   `SQLSetCursorName`:idx:
-     `odbcsql.html#658 <odbcsql.html#658>`_
-
-   `SQLSetEnvAttr`:idx:
-     `odbcsql.html#628 <odbcsql.html#628>`_
-
-   `SQLSetPos`:idx:
-     `odbcsql.html#653 <odbcsql.html#653>`_
-
-   `SQL_SETPOS_MAX_OPTION_VALUE`:idx:
-     `odbcsql.html#318 <odbcsql.html#318>`_
-
-   `SQLSetStmtAttr`:idx:
-     `odbcsql.html#647 <odbcsql.html#647>`_
-
-   `SQL_SIGNED_OFFSET`:idx:
-     `odbcsql.html#191 <odbcsql.html#191>`_
-
-   `SQL_SIMULATE_CURSOR`:idx:
-     `odbcsql.html#389 <odbcsql.html#389>`_
-
-   `SQL_SMALLINT`:idx:
-     `odbcsql.html#140 <odbcsql.html#140>`_
-
-   `SQL_SO_DYNAMIC`:idx:
-     `odbcsql.html#259 <odbcsql.html#259>`_
-
-   `SQL_SO_FORWARD_ONLY`:idx:
-     `odbcsql.html#257 <odbcsql.html#257>`_
-
-   `SQL_SO_KEYSET_DRIVEN`:idx:
-     `odbcsql.html#258 <odbcsql.html#258>`_
-
-   `SQL_SO_MIXED`:idx:
-     `odbcsql.html#260 <odbcsql.html#260>`_
-
-   `SQL_SO_STATIC`:idx:
-     `odbcsql.html#261 <odbcsql.html#261>`_
-
-   `SQLSpecialColumns`:idx:
-     `odbcsql.html#666 <odbcsql.html#666>`_
-
-   `SQL_SS_ADDITIONS`:idx:
-     `odbcsql.html#566 <odbcsql.html#566>`_
-
-   `SQL_SS_DELETIONS`:idx:
-     `odbcsql.html#567 <odbcsql.html#567>`_
-
-   `SQL_SS_UPDATES`:idx:
-     `odbcsql.html#568 <odbcsql.html#568>`_
-
-   `SQL_STATIC_CURSOR_ATTRIBUTES1`:idx:
-     `odbcsql.html#279 <odbcsql.html#279>`_
-
-   `SQL_STATIC_CURSOR_ATTRIBUTES2`:idx:
-     `odbcsql.html#280 <odbcsql.html#280>`_
-
-   `SQL_STATIC_SENSITIVITY`:idx:
-     `odbcsql.html#263 <odbcsql.html#263>`_
-
-   `SQLStatistics`:idx:
-     `odbcsql.html#670 <odbcsql.html#670>`_
-
-   `SQL_STILL_EXECUTING`:idx:
-     `odbcsql.html#359 <odbcsql.html#359>`_
-
-   `SQL_SUCCESS`:idx:
-     `odbcsql.html#354 <odbcsql.html#354>`_
-
-   `SQL_SUCCESS_WITH_INFO`:idx:
-     `odbcsql.html#355 <odbcsql.html#355>`_
-
-   `SQLTables`:idx:
-     `odbcsql.html#664 <odbcsql.html#664>`_
-
-   `SQL_TABLE_STAT`:idx:
-     `odbcsql.html#530 <odbcsql.html#530>`_
-
-   `SQL_TC_ALL`:idx:
-     `odbcsql.html#555 <odbcsql.html#555>`_
-
-   `SQL_TC_DDL_COMMIT`:idx:
-     `odbcsql.html#556 <odbcsql.html#556>`_
-
-   `SQL_TC_DDL_IGNORE`:idx:
-     `odbcsql.html#557 <odbcsql.html#557>`_
-
-   `SQL_TC_DML`:idx:
-     `odbcsql.html#554 <odbcsql.html#554>`_
-
-   `SQL_TC_NONE`:idx:
-     `odbcsql.html#553 <odbcsql.html#553>`_
-
-   `SQL_TIME`:idx:
-     `odbcsql.html#150 <odbcsql.html#150>`_
-
-   `SQL_TIME_LEN`:idx:
-     `odbcsql.html#364 <odbcsql.html#364>`_
-
-   `SQL_TIMESTAMP`:idx:
-     `odbcsql.html#151 <odbcsql.html#151>`_
-
-   `SQL_TIMESTAMP_LEN`:idx:
-     `odbcsql.html#365 <odbcsql.html#365>`_
-
-   `SQL_TIMESTAMP_STRUCT`:idx:
-     `odbcsql.html#235 <odbcsql.html#235>`_
-
-   `SQL_TIME_STRUCT`:idx:
-     `odbcsql.html#233 <odbcsql.html#233>`_
-
-   `SQL_TINYINT`:idx:
-     `odbcsql.html#131 <odbcsql.html#131>`_
-
-   `SQL_TRANSACTION_CAPABLE`:idx:
-     `odbcsql.html#536 <odbcsql.html#536>`_
-
-   `SQL_TRANSACTION_ISOLATION_OPTION`:idx:
-     `odbcsql.html#539 <odbcsql.html#539>`_
-
-   `SQL_TRANSACTION_READ_COMMITTED`:idx:
-     `odbcsql.html#561 <odbcsql.html#561>`_
-
-   `SQL_TRANSACTION_READ_UNCOMMITTED`:idx:
-     `odbcsql.html#559 <odbcsql.html#559>`_
-
-   `SQL_TRANSACTION_REPEATABLE_READ`:idx:
-     `odbcsql.html#563 <odbcsql.html#563>`_
-
-   `SQL_TRANSACTION_SERIALIZABLE`:idx:
-     `odbcsql.html#565 <odbcsql.html#565>`_
-
-   `SQL_TRANSLATE_DLL`:idx:
-     `odbcsql.html#410 <odbcsql.html#410>`_
-
-   `SQL_TRANSLATE_OPTION`:idx:
-     `odbcsql.html#411 <odbcsql.html#411>`_
-
-   `SQL_TRUE`:idx:
-     `odbcsql.html#499 <odbcsql.html#499>`_
-
-   `SQL_TXN_CAPABLE`:idx:
-     `odbcsql.html#535 <odbcsql.html#535>`_
-
-   `SQL_TXN_ISOLATION`:idx:
-     `odbcsql.html#402 <odbcsql.html#402>`_
-
-   `SQL_TXN_ISOLATION_OPTION`:idx:
-     `odbcsql.html#538 <odbcsql.html#538>`_
-
-   `SQL_TXN_READ_COMMITTED`:idx:
-     `odbcsql.html#560 <odbcsql.html#560>`_
-
-   `SQL_TXN_READ_UNCOMMITTED`:idx:
-     `odbcsql.html#558 <odbcsql.html#558>`_
-
-   `SQL_TXN_REPEATABLE_READ`:idx:
-     `odbcsql.html#562 <odbcsql.html#562>`_
-
-   `SQL_TXN_SERIALIZABLE`:idx:
-     `odbcsql.html#564 <odbcsql.html#564>`_
-
-   `SQL_TYPE_DATE`:idx:
-     `odbcsql.html#146 <odbcsql.html#146>`_
-
-   `SQL_TYPE_MAX`:idx:
-     `odbcsql.html#227 <odbcsql.html#227>`_
-
-   `SQL_TYPE_MIN`:idx:
-     `odbcsql.html#226 <odbcsql.html#226>`_
-
-   `SQL_TYPE_NULL`:idx:
-     `odbcsql.html#225 <odbcsql.html#225>`_
-
-   `SQL_TYPE_TIME`:idx:
-     `odbcsql.html#147 <odbcsql.html#147>`_
-
-   `SQL_TYPE_TIMESTAMP`:idx:
-     `odbcsql.html#148 <odbcsql.html#148>`_
-
-   `SQL_UB_DEFAULT`:idx:
-     `odbcsql.html#254 <odbcsql.html#254>`_
-
-   `SQL_UB_FIXED`:idx:
-     `odbcsql.html#255 <odbcsql.html#255>`_
-
-   `SQL_UB_OFF`:idx:
-     `odbcsql.html#252 <odbcsql.html#252>`_
-
-   `SQL_UB_ON`:idx:
-     `odbcsql.html#253 <odbcsql.html#253>`_
-
-   `SQL_UB_VARIABLE`:idx:
-     `odbcsql.html#256 <odbcsql.html#256>`_
-
-   `SQL_UNBIND`:idx:
-     `odbcsql.html#505 <odbcsql.html#505>`_
-
-   `SQL_UNICODE`:idx:
-     `odbcsql.html#180 <odbcsql.html#180>`_
-
-   `SQL_UNICODE_CHAR`:idx:
-     `odbcsql.html#183 <odbcsql.html#183>`_
-
-   `SQL_UNICODE_LONGVARCHAR`:idx:
-     `odbcsql.html#182 <odbcsql.html#182>`_
-
-   `SQL_UNICODE_VARCHAR`:idx:
-     `odbcsql.html#181 <odbcsql.html#181>`_
-
-   `SQL_UNKNOWN_TYPE`:idx:
-     `odbcsql.html#125 <odbcsql.html#125>`_
-
-   `SQL_UNSIGNED_OFFSET`:idx:
-     `odbcsql.html#192 <odbcsql.html#192>`_
-
-   `SQL_UNSPECIFIED`:idx:
-     `odbcsql.html#489 <odbcsql.html#489>`_
-
-   `SQL_UPDATE`:idx:
-     `odbcsql.html#324 <odbcsql.html#324>`_
-
-   `SQL_UPDATE_BY_BOOKMARK`:idx:
-     `odbcsql.html#319 <odbcsql.html#319>`_
-
-   `SQL_USE_BOOKMARKS`:idx:
-     `odbcsql.html#391 <odbcsql.html#391>`_
-
-   `SQL_USER_NAME`:idx:
-     `odbcsql.html#537 <odbcsql.html#537>`_
-
-   `SQL_VARBINARY`:idx:
-     `odbcsql.html#128 <odbcsql.html#128>`_
-
-   `SQL_VARCHAR`:idx:
-     `odbcsql.html#145 <odbcsql.html#145>`_
-
-   `SQL_WCHAR`:idx:
-     `odbcsql.html#133 <odbcsql.html#133>`_
-
-   `SQL_WLONGVARCHAR`:idx:
-     `odbcsql.html#135 <odbcsql.html#135>`_
-
-   `SQL_WVARCHAR`:idx:
-     `odbcsql.html#134 <odbcsql.html#134>`_
-
-   `SQL_XOPEN_CLI_YEAR`:idx:
-     `odbcsql.html#542 <odbcsql.html#542>`_
-
-   `sqrt`:idx:
-     * `math.html#110 <math.html#110>`_
-     * `complex.html#109 <complex.html#109>`_
-
-   `SS_DISABLE`:idx:
-     `posix.html#765 <posix.html#765>`_
-
-   `SS_ONSTACK`:idx:
-     `posix.html#764 <posix.html#764>`_
-
-   `stack_trace`:idx:
-     `nimrodc.html#109 <nimrodc.html#109>`_
-
-   `startsWith`:idx:
-     `strutils.html#135 <strutils.html#135>`_
-
-   `stat`:idx:
-     `posix.html#1065 <posix.html#1065>`_
-
-   `Statements`:idx:
-     `manual.html#174 <manual.html#174>`_
-
-   `static error`:idx:
-     `manual.html#109 <manual.html#109>`_
-
-   `static type`:idx:
-     `manual.html#103 <manual.html#103>`_
-
-   `statvfs`:idx:
-     `posix.html#1056 <posix.html#1056>`_
-
-   `stdcall`:idx:
-     `manual.html#165 <manual.html#165>`_
-
-   `stderr`:idx:
-     `system.html#481 <system.html#481>`_
-
-   `STDERR_FILENO`:idx:
-     `posix.html#127 <posix.html#127>`_
-
-   `stdin`:idx:
-     `system.html#479 <system.html#479>`_
-
-   `STDIN_FILENO`:idx:
-     `posix.html#128 <posix.html#128>`_
-
-   `stdout`:idx:
-     `system.html#480 <system.html#480>`_
-
-   `STDOUT_FILENO`:idx:
-     `posix.html#129 <posix.html#129>`_
-
-   `ST_NOSUID`:idx:
-     `posix.html#673 <posix.html#673>`_
-
-   `ST_RDONLY`:idx:
-     `posix.html#672 <posix.html#672>`_
-
-   `strerror`:idx:
-     `posix.html#1160 <posix.html#1160>`_
-
-   `strfmon`:idx:
-     `posix.html#848 <posix.html#848>`_
-
-   `strftime`:idx:
-     `posix.html#1110 <posix.html#1110>`_
-
-   `string`:idx:
-     * `manual.html#151 <manual.html#151>`_
-     * `system.html#111 <system.html#111>`_
-
-   `strip`:idx:
-     `strutils.html#105 <strutils.html#105>`_
-
-   `strptime`:idx:
-     `posix.html#1111 <posix.html#1111>`_
-
-   `strStart`:idx:
-     `strutils.html#103 <strutils.html#103>`_
-
-   `structured type`:idx:
-     `manual.html#152 <manual.html#152>`_
-
-   `strutils`:idx:
-     `nimrodc.html#117 <nimrodc.html#117>`_
-
-   `style-insensitive`:idx:
-     `manual.html#118 <manual.html#118>`_
-
-   `S_TYPEISMQ`:idx:
-     `posix.html#1074 <posix.html#1074>`_
-
-   `S_TYPEISSEM`:idx:
-     `posix.html#1075 <posix.html#1075>`_
-
-   `S_TYPEISSHM`:idx:
-     `posix.html#1076 <posix.html#1076>`_
-
-   `S_TYPEISTMO`:idx:
-     `posix.html#1077 <posix.html#1077>`_
-
-   `subrange`:idx:
-     `manual.html#150 <manual.html#150>`_
-
-   `succ`:idx:
-     `system.html#154 <system.html#154>`_
-
-   `swab`:idx:
-     `posix.html#1031 <posix.html#1031>`_
-
-   `swap`:idx:
-     `system.html#417 <system.html#417>`_
-
-   `swapcontext`:idx:
-     `posix.html#1191 <posix.html#1191>`_
-
-   `symlink`:idx:
-     `posix.html#1032 <posix.html#1032>`_
-
-   `sync`:idx:
-     `posix.html#1033 <posix.html#1033>`_
-
-   `syscall`:idx:
-     `manual.html#172 <manual.html#172>`_
-
-   `sysconf`:idx:
-     `posix.html#1034 <posix.html#1034>`_
-
-   `system`:idx:
-     `manual.html#219 <manual.html#219>`_
-
-   `tabulator`:idx:
-     `manual.html#125 <manual.html#125>`_
-
-   `TAddress`:idx:
-     `system.html#372 <system.html#372>`_
-
-   `Taiocb`:idx:
-     `posix.html#204 <posix.html#204>`_
-
-   `TAllocfunc`:idx:
-     `zlib.html#108 <zlib.html#108>`_
-
-   `tan`:idx:
-     `math.html#125 <math.html#125>`_
-
-   `tanh`:idx:
-     `math.html#126 <math.html#126>`_
-
-   `TBaseLexer`:idx:
-     `lexbase.html#103 <lexbase.html#103>`_
-
-   `Tblkcnt`:idx:
-     `posix.html#143 <posix.html#143>`_
-
-   `Tblksize`:idx:
-     `posix.html#144 <posix.html#144>`_
-
-   `TCfgEvent`:idx:
-     `parsecfg.html#102 <parsecfg.html#102>`_
-
-   `TCfgEventKind`:idx:
-     `parsecfg.html#101 <parsecfg.html#101>`_
-
-   `TCfgParser`:idx:
-     `parsecfg.html#103 <parsecfg.html#103>`_
-
-   `tcgetpgrp`:idx:
-     `posix.html#1035 <posix.html#1035>`_
-
-   `TCharSet`:idx:
-     `strutils.html#101 <strutils.html#101>`_
-
-   `TClock`:idx:
-     `posix.html#145 <posix.html#145>`_
-
-   `TClockId`:idx:
-     `posix.html#146 <posix.html#146>`_
-
-   `TCmdLineKind`:idx:
-     `parseopt.html#101 <parseopt.html#101>`_
-
-   `TComplex`:idx:
-     `complex.html#101 <complex.html#101>`_
-
-   `tcsetpgrp`:idx:
-     `posix.html#1036 <posix.html#1036>`_
-
-   `TDev`:idx:
-     `posix.html#147 <posix.html#147>`_
-
-   `TDIR`:idx:
-     `posix.html#130 <posix.html#130>`_
-
-   `Tdirent`:idx:
-     `posix.html#131 <posix.html#131>`_
-
-   `telldir`:idx:
-     `posix.html#806 <posix.html#806>`_
-
-   `template`:idx:
-     `manual.html#210 <manual.html#210>`_
-
-   `TEndian`:idx:
-     `system.html#385 <system.html#385>`_
-
-   `Tfd_set`:idx:
-     `posix.html#201 <posix.html#201>`_
-
-   `Tfenv`:idx:
-     `posix.html#133 <posix.html#133>`_
-
-   `Tfexcept`:idx:
-     `posix.html#134 <posix.html#134>`_
-
-   `TFile`:idx:
-     `system.html#476 <system.html#476>`_
-
-   `TFileHandle`:idx:
-     `system.html#478 <system.html#478>`_
-
-   `TFileMode`:idx:
-     `system.html#477 <system.html#477>`_
-
-   `TFileStream`:idx:
-     `streams.html#119 <streams.html#119>`_
-
-   `TFloatClass`:idx:
-     `math.html#103 <math.html#103>`_
-
-   `Tflock`:idx:
-     `posix.html#132 <posix.html#132>`_
-
-   `T_FMT`:idx:
-     `posix.html#392 <posix.html#392>`_
-
-   `T_FMT_AMPM`:idx:
-     `posix.html#393 <posix.html#393>`_
-
-   `TFormatFlag`:idx:
-     `strtabs.html#111 <strtabs.html#111>`_
-
-   `TFreeFunc`:idx:
-     `zlib.html#109 <zlib.html#109>`_
-
-   `Tfsblkcnt`:idx:
-     `posix.html#148 <posix.html#148>`_
-
-   `Tfsfilcnt`:idx:
-     `posix.html#149 <posix.html#149>`_
-
-   `TFTW`:idx:
-     `posix.html#135 <posix.html#135>`_
-
-   `TGC_Strategy`:idx:
-     `system.html#460 <system.html#460>`_
-
-   `TGid`:idx:
-     `posix.html#150 <posix.html#150>`_
-
-   `TGlob`:idx:
-     `posix.html#136 <posix.html#136>`_
-
-   `TGroup`:idx:
-     `posix.html#137 <posix.html#137>`_
-
-   `THash`:idx:
-     `hashes.html#101 <hashes.html#101>`_
-
-   `THOUSEP`:idx:
-     `posix.html#440 <posix.html#440>`_
-
-   `Ticonv`:idx:
-     `posix.html#138 <posix.html#138>`_
-
-   `Tid`:idx:
-     `posix.html#151 <posix.html#151>`_
-
-   `time`:idx:
-     `posix.html#1112 <posix.html#1112>`_
-
-   `TimeInfoToTime`:idx:
-     `times.html#108 <times.html#108>`_
-
-   `TIMER_ABSTIME`:idx:
-     `posix.html#699 <posix.html#699>`_
-
-   `timer_create`:idx:
-     `posix.html#1113 <posix.html#1113>`_
-
-   `timer_delete`:idx:
-     `posix.html#1114 <posix.html#1114>`_
-
-   `timer_getoverrun`:idx:
-     `posix.html#1116 <posix.html#1116>`_
-
-   `timer_gettime`:idx:
-     `posix.html#1115 <posix.html#1115>`_
-
-   `timer_settime`:idx:
-     `posix.html#1117 <posix.html#1117>`_
-
-   `times`:idx:
-     `nimrodc.html#119 <nimrodc.html#119>`_
-
-   `timezone`:idx:
-     `posix.html#702 <posix.html#702>`_
-
-   `Tino`:idx:
-     `posix.html#152 <posix.html#152>`_
-
-   `TInternalState`:idx:
-     `zlib.html#110 <zlib.html#110>`_
-
-   `Tipc_perm`:idx:
-     `posix.html#182 <posix.html#182>`_
-
-   `titimerspec`:idx:
-     `posix.html#188 <posix.html#188>`_
-
-   `TKey`:idx:
-     `posix.html#153 <posix.html#153>`_
-
-   `Tlconv`:idx:
-     `posix.html#139 <posix.html#139>`_
-
-   `Tmcontext`:idx:
-     `posix.html#202 <posix.html#202>`_
-
-   `TMode`:idx:
-     `posix.html#154 <posix.html#154>`_
-
-   `TMonth`:idx:
-     `times.html#101 <times.html#101>`_
-
-   `TMqAttr`:idx:
-     `posix.html#141 <posix.html#141>`_
-
-   `TMqd`:idx:
-     `posix.html#140 <posix.html#140>`_
-
-   `Tnl_catd`:idx:
-     `posix.html#198 <posix.html#198>`_
-
-   `TNlink`:idx:
-     `posix.html#155 <posix.html#155>`_
-
-   `Tnl_item`:idx:
-     `posix.html#197 <posix.html#197>`_
-
-   `toBiggestFloat`:idx:
-     `system.html#399 <system.html#399>`_
-
-   `toBiggestInt`:idx:
-     `system.html#401 <system.html#401>`_
-
-   `toBin`:idx:
-     `strutils.html#140 <strutils.html#140>`_
-
-   `TObject`:idx:
-     `system.html#128 <system.html#128>`_
-
-   `TOff`:idx:
-     `posix.html#156 <posix.html#156>`_
-
-   `toFloat`:idx:
-     `system.html#398 <system.html#398>`_
-
-   `toHex`:idx:
-     `strutils.html#126 <strutils.html#126>`_
-
-   `toInt`:idx:
-     `system.html#400 <system.html#400>`_
-
-   `toLower`:idx:
-     * `strutils.html#106 <strutils.html#106>`_
-     * `strutils.html#107 <strutils.html#107>`_
-
-   `toOct`:idx:
-     `strutils.html#139 <strutils.html#139>`_
-
-   `toOctal`:idx:
-     `strutils.html#117 <strutils.html#117>`_
-
-   `TOptParser`:idx:
-     `parseopt.html#102 <parseopt.html#102>`_
-
-   `toString`:idx:
-     `strutils.html#131 <strutils.html#131>`_
-
-   `toU16`:idx:
-     `system.html#176 <system.html#176>`_
-
-   `toU32`:idx:
-     `system.html#177 <system.html#177>`_
-
-   `toU8`:idx:
-     `system.html#175 <system.html#175>`_
-
-   `toUpper`:idx:
-     * `strutils.html#108 <strutils.html#108>`_
-     * `strutils.html#109 <strutils.html#109>`_
-
-   `TPasswd`:idx:
-     `posix.html#142 <posix.html#142>`_
-
-   `TPathComponent`:idx:
-     `os.html#154 <os.html#154>`_
-
-   `TPid`:idx:
-     `posix.html#157 <posix.html#157>`_
-
-   `Tposix_spawnattr`:idx:
-     `posix.html#205 <posix.html#205>`_
-
-   `Tposix_spawn_file_actions`:idx:
-     `posix.html#206 <posix.html#206>`_
-
-   `Tposix_typed_mem_info`:idx:
-     `posix.html#185 <posix.html#185>`_
-
-   `Tpthread`:idx:
-     `posix.html#170 <posix.html#170>`_
-
-   `Tpthread_attr`:idx:
-     `posix.html#158 <posix.html#158>`_
-
-   `Tpthread_barrier`:idx:
-     `posix.html#159 <posix.html#159>`_
-
-   `Tpthread_barrierattr`:idx:
-     `posix.html#160 <posix.html#160>`_
-
-   `Tpthread_cond`:idx:
-     `posix.html#161 <posix.html#161>`_
-
-   `Tpthread_condattr`:idx:
-     `posix.html#162 <posix.html#162>`_
-
-   `Tpthread_key`:idx:
-     `posix.html#163 <posix.html#163>`_
-
-   `Tpthread_mutex`:idx:
-     `posix.html#164 <posix.html#164>`_
-
-   `Tpthread_mutexattr`:idx:
-     `posix.html#165 <posix.html#165>`_
-
-   `Tpthread_once`:idx:
-     `posix.html#166 <posix.html#166>`_
-
-   `Tpthread_rwlock`:idx:
-     `posix.html#167 <posix.html#167>`_
-
-   `Tpthread_rwlockattr`:idx:
-     `posix.html#168 <posix.html#168>`_
-
-   `Tpthread_spinlock`:idx:
-     `posix.html#169 <posix.html#169>`_
-
-   `traced`:idx:
-     `manual.html#160 <manual.html#160>`_
-
-   `TResult`:idx:
-     `system.html#152 <system.html#152>`_
-
-   `truncate`:idx:
-     `posix.html#1037 <posix.html#1037>`_
-
-   `try`:idx:
-     `manual.html#186 <manual.html#186>`_
-
-   `Tsched_param`:idx:
-     `posix.html#199 <posix.html#199>`_
-
-   `TSem`:idx:
-     `posix.html#181 <posix.html#181>`_
-
-   `TSigaction`:idx:
-     `posix.html#193 <posix.html#193>`_
-
-   `Tsig_atomic`:idx:
-     `posix.html#189 <posix.html#189>`_
-
-   `TsigEvent`:idx:
-     `posix.html#191 <posix.html#191>`_
-
-   `TsigInfo`:idx:
-     `posix.html#196 <posix.html#196>`_
-
-   `Tsigset`:idx:
-     `posix.html#190 <posix.html#190>`_
-
-   `TSigStack`:idx:
-     `posix.html#195 <posix.html#195>`_
-
-   `TsigVal`:idx:
-     `posix.html#192 <posix.html#192>`_
-
-   `TSqlChar`:idx:
-     `odbcsql.html#101 <odbcsql.html#101>`_
-
-   `TSqlDouble`:idx:
-     `odbcsql.html#113 <odbcsql.html#113>`_
-
-   `TSqlFloat`:idx:
-     `odbcsql.html#114 <odbcsql.html#114>`_
-
-   `TSqlHandle`:idx:
-     `odbcsql.html#104 <odbcsql.html#104>`_
-
-   `TSqlHDBC`:idx:
-     `odbcsql.html#106 <odbcsql.html#106>`_
-
-   `TSqlHDesc`:idx:
-     `odbcsql.html#108 <odbcsql.html#108>`_
-
-   `TSqlHEnv`:idx:
-     `odbcsql.html#105 <odbcsql.html#105>`_
-
-   `TSqlHStmt`:idx:
-     `odbcsql.html#107 <odbcsql.html#107>`_
-
-   `TSqlHWND`:idx:
-     `odbcsql.html#115 <odbcsql.html#115>`_
-
-   `TSqlInteger`:idx:
-     `odbcsql.html#109 <odbcsql.html#109>`_
-
-   `TSqlPointer`:idx:
-     `odbcsql.html#111 <odbcsql.html#111>`_
-
-   `TSqlReal`:idx:
-     `odbcsql.html#112 <odbcsql.html#112>`_
-
-   `TSqlSmallInt`:idx:
-     `odbcsql.html#102 <odbcsql.html#102>`_
-
-   `TSqlUInteger`:idx:
-     `odbcsql.html#110 <odbcsql.html#110>`_
-
-   `TSqlUSmallInt`:idx:
-     `odbcsql.html#103 <odbcsql.html#103>`_
-
-   `TStack`:idx:
-     `posix.html#194 <posix.html#194>`_
-
-   `TStat`:idx:
-     `posix.html#183 <posix.html#183>`_
-
-   `TStatvfs`:idx:
-     `posix.html#184 <posix.html#184>`_
-
-   `TStream`:idx:
-     `streams.html#102 <streams.html#102>`_
-
-   `TStringStream`:idx:
-     `streams.html#116 <streams.html#116>`_
-
-   `TStringTable`:idx:
-     `strtabs.html#102 <strtabs.html#102>`_
-
-   `TStringTableMode`:idx:
-     `strtabs.html#101 <strtabs.html#101>`_
-
-   `Tsuseconds`:idx:
-     `posix.html#171 <posix.html#171>`_
-
-   `Ttime`:idx:
-     `posix.html#172 <posix.html#172>`_
-
-   `TTime`:idx:
-     `times.html#103 <times.html#103>`_
-
-   `TTimeInfo`:idx:
-     `times.html#104 <times.html#104>`_
-
-   `Ttimer`:idx:
-     `posix.html#173 <posix.html#173>`_
-
-   `Ttimespec`:idx:
-     `posix.html#187 <posix.html#187>`_
-
-   `Ttimeval`:idx:
-     `posix.html#200 <posix.html#200>`_
-
-   `Ttm`:idx:
-     `posix.html#186 <posix.html#186>`_
-
-   `Ttrace_attr`:idx:
-     `posix.html#174 <posix.html#174>`_
-
-   `Ttrace_event_id`:idx:
-     `posix.html#175 <posix.html#175>`_
-
-   `Ttrace_event_set`:idx:
-     `posix.html#176 <posix.html#176>`_
-
-   `Ttrace_id`:idx:
-     `posix.html#177 <posix.html#177>`_
-
-   `ttyname`:idx:
-     `posix.html#1038 <posix.html#1038>`_
-
-   `ttyname_r`:idx:
-     `posix.html#1039 <posix.html#1039>`_
-
-   `Tucontext`:idx:
-     `posix.html#203 <posix.html#203>`_
-
-   `Tuid`:idx:
-     `posix.html#178 <posix.html#178>`_
-
-   `tuple`:idx:
-     `manual.html#155 <manual.html#155>`_
-
-   `Tuseconds`:idx:
-     `posix.html#179 <posix.html#179>`_
-
-   `Tutsname`:idx:
-     `posix.html#180 <posix.html#180>`_
-
-   `TWeekDay`:idx:
-     `times.html#102 <times.html#102>`_
-
-   `type`:idx:
-     * `manual.html#102 <manual.html#102>`_
-     * `manual.html#141 <manual.html#141>`_
-     * `manual.html#207 <manual.html#207>`_
-
-   `type parameters`:idx:
-     `manual.html#209 <manual.html#209>`_
-
-   `type suffix`:idx:
-     `manual.html#138 <manual.html#138>`_
-
-   `TZipArchive`:idx:
-     `zipfiles.html#101 <zipfiles.html#101>`_
-
-   `Tzip_source_callback`:idx:
-     `libzip.html#102 <libzip.html#102>`_
-
-   `Tzip_source_cmd`:idx:
-     `libzip.html#101 <libzip.html#101>`_
-
-   `Tzip_stat`:idx:
-     `libzip.html#104 <libzip.html#104>`_
-
-   `tzset`:idx:
-     `posix.html#1118 <posix.html#1118>`_
-
-   `TZStream`:idx:
-     `zlib.html#112 <zlib.html#112>`_
-
-   `TZStreamRec`:idx:
-     `zlib.html#113 <zlib.html#113>`_
-
-   `ualarm`:idx:
-     `posix.html#1040 <posix.html#1040>`_
-
-   `Uint`:idx:
-     `zlib.html#101 <zlib.html#101>`_
-
-   `Ulong`:idx:
-     `zlib.html#102 <zlib.html#102>`_
-
-   `Ulongf`:idx:
-     `zlib.html#103 <zlib.html#103>`_
-
-   `umask`:idx:
-     `posix.html#1066 <posix.html#1066>`_
-
-   `uname`:idx:
-     `posix.html#866 <posix.html#866>`_
-
-   `unchecked runtime error`:idx:
-     `manual.html#111 <manual.html#111>`_
-
-   `uncompress`:idx:
-     `zlib.html#156 <zlib.html#156>`_
-
-   `undef`:idx:
-     `manual.html#224 <manual.html#224>`_
-
-   `UnixToNativePath`:idx:
-     `os.html#124 <os.html#124>`_
-
-   `unlink`:idx:
-     `posix.html#1041 <posix.html#1041>`_
-
-   `unsigned integer`:idx:
-     `manual.html#143 <manual.html#143>`_
-
-   `unsigned operations`:idx:
-     `manual.html#144 <manual.html#144>`_
-
-   `untraced`:idx:
-     `manual.html#161 <manual.html#161>`_
-
-   `usleep`:idx:
-     `posix.html#1042 <posix.html#1042>`_
-
-   `Var`:idx:
-     `manual.html#179 <manual.html#179>`_
-
-   `varargs`:idx:
-     `nimrodc.html#106 <nimrodc.html#106>`_
-
-   `variant`:idx:
-     `manual.html#157 <manual.html#157>`_
-
-   `vertical tabulator`:idx:
-     `manual.html#126 <manual.html#126>`_
-
-   `vfork`:idx:
-     `posix.html#1043 <posix.html#1043>`_
-
-   `volatile`:idx:
-     `nimrodc.html#112 <nimrodc.html#112>`_
-
-   `wait`:idx:
-     `posix.html#1119 <posix.html#1119>`_
-
-   `waitid`:idx:
-     `posix.html#1120 <posix.html#1120>`_
-
-   `waitpid`:idx:
-     `posix.html#1121 <posix.html#1121>`_
-
-   `walkDir`:idx:
-     `os.html#155 <os.html#155>`_
-
-   `walkFiles`:idx:
-     * `os.html#153 <os.html#153>`_
-     * `zipfiles.html#110 <zipfiles.html#110>`_
-
-   `warning`:idx:
-     * `manual.html#221 <manual.html#221>`_
-     * `manual.html#227 <manual.html#227>`_
-     * `dialogs.html#103 <dialogs.html#103>`_
-
-   `WCONTINUED`:idx:
-     `posix.html#714 <posix.html#714>`_
-
-   `WEXITED`:idx:
-     `posix.html#712 <posix.html#712>`_
-
-   `WEXITSTATUS`:idx:
-     `posix.html#705 <posix.html#705>`_
-
-   `when`:idx:
-     `manual.html#183 <manual.html#183>`_
-
-   `while`:idx:
-     `manual.html#195 <manual.html#195>`_
-
-   `Whitespace`:idx:
-     `strutils.html#102 <strutils.html#102>`_
-
-   `WIFCONTINUED`:idx:
-     `posix.html#706 <posix.html#706>`_
-
-   `WIFEXITED`:idx:
-     `posix.html#707 <posix.html#707>`_
-
-   `WIFSIGNALED`:idx:
-     `posix.html#708 <posix.html#708>`_
-
-   `WIFSTOPPED`:idx:
-     `posix.html#709 <posix.html#709>`_
-
-   `WNOHANG`:idx:
-     `posix.html#703 <posix.html#703>`_
-
-   `WNOWAIT`:idx:
-     `posix.html#715 <posix.html#715>`_
-
-   `W_OK`:idx:
-     `posix.html#480 <posix.html#480>`_
-
-   `write`:idx:
-     * `system.html#489 <system.html#489>`_
-     * `system.html#490 <system.html#490>`_
-     * `system.html#491 <system.html#491>`_
-     * `system.html#492 <system.html#492>`_
-     * `system.html#493 <system.html#493>`_
-     * `system.html#494 <system.html#494>`_
-     * `system.html#495 <system.html#495>`_
-     * `posix.html#1044 <posix.html#1044>`_
-     * `streams.html#103 <streams.html#103>`_
-     * `streams.html#104 <streams.html#104>`_
-
-   `writeBuffer`:idx:
-     `system.html#505 <system.html#505>`_
-
-   `writeBytes`:idx:
-     `system.html#503 <system.html#503>`_
-
-   `writeChars`:idx:
-     `system.html#504 <system.html#504>`_
-
-   `writeln`:idx:
-     * `system.html#497 <system.html#497>`_
-     * `system.html#498 <system.html#498>`_
-
-   `WSTOPPED`:idx:
-     `posix.html#713 <posix.html#713>`_
-
-   `WSTOPSIG`:idx:
-     `posix.html#710 <posix.html#710>`_
-
-   `WTERMSIG`:idx:
-     `posix.html#711 <posix.html#711>`_
-
-   `WUNTRACED`:idx:
-     `posix.html#704 <posix.html#704>`_
-
-   `X_OK`:idx:
-     `posix.html#481 <posix.html#481>`_
-
-   `xor`:idx:
-     * `system.html#238 <system.html#238>`_
-     * `system.html#239 <system.html#239>`_
-     * `system.html#240 <system.html#240>`_
-     * `system.html#241 <system.html#241>`_
-     * `system.html#242 <system.html#242>`_
-     * `system.html#322 <system.html#322>`_
-
-   `YESEXPR`:idx:
-     `posix.html#441 <posix.html#441>`_
-
-   `yield`:idx:
-     `manual.html#192 <manual.html#192>`_
-
-   `Z_ASCII`:idx:
-     `zlib.html#138 <zlib.html#138>`_
-
-   `Z_BEST_COMPRESSION`:idx:
-     `zlib.html#132 <zlib.html#132>`_
-
-   `Z_BEST_SPEED`:idx:
-     `zlib.html#131 <zlib.html#131>`_
-
-   `Z_BINARY`:idx:
-     `zlib.html#137 <zlib.html#137>`_
-
-   `Z_BUF_ERROR`:idx:
-     `zlib.html#128 <zlib.html#128>`_
-
-   `Z_DATA_ERROR`:idx:
-     `zlib.html#126 <zlib.html#126>`_
-
-   `Z_DEFAULT_COMPRESSION`:idx:
-     `zlib.html#133 <zlib.html#133>`_
-
-   `Z_DEFAULT_STRATEGY`:idx:
-     `zlib.html#136 <zlib.html#136>`_
-
-   `Z_DEFLATED`:idx:
-     `zlib.html#140 <zlib.html#140>`_
-
-   `ze`:idx:
-     * `system.html#169 <system.html#169>`_
-     * `system.html#170 <system.html#170>`_
-
-   `ze64`:idx:
-     * `system.html#171 <system.html#171>`_
-     * `system.html#172 <system.html#172>`_
-     * `system.html#173 <system.html#173>`_
-     * `system.html#174 <system.html#174>`_
-
-   `zeroMem`:idx:
-     `system.html#407 <system.html#407>`_
-
-   `Z_ERRNO`:idx:
-     `zlib.html#124 <zlib.html#124>`_
-
-   `zError`:idx:
-     `zlib.html#184 <zlib.html#184>`_
-
-   `Z_FILTERED`:idx:
-     `zlib.html#134 <zlib.html#134>`_
-
-   `Z_FINISH`:idx:
-     `zlib.html#120 <zlib.html#120>`_
-
-   `Z_FULL_FLUSH`:idx:
-     `zlib.html#119 <zlib.html#119>`_
-
-   `Z_HUFFMAN_ONLY`:idx:
-     `zlib.html#135 <zlib.html#135>`_
-
-   `zip_add`:idx:
-     `libzip.html#170 <libzip.html#170>`_
-
-   `zip_add_dir`:idx:
-     `libzip.html#171 <libzip.html#171>`_
-
-   `ZIP_AFL_TORRENT`:idx:
-     `libzip.html#116 <libzip.html#116>`_
-
-   `ZIP_CHECKCONS`:idx:
-     `libzip.html#110 <libzip.html#110>`_
-
-   `zip_close`:idx:
-     `libzip.html#172 <libzip.html#172>`_
-
-   `ZIP_CM_BZIP2`:idx:
-     `libzip.html#155 <libzip.html#155>`_
-
-   `ZIP_CM_DEFAULT`:idx:
-     `libzip.html#144 <libzip.html#144>`_
-
-   `ZIP_CM_DEFLATE`:idx:
-     `libzip.html#152 <libzip.html#152>`_
-
-   `ZIP_CM_DEFLATE64`:idx:
-     `libzip.html#153 <libzip.html#153>`_
-
-   `ZIP_CM_IMPLODE`:idx:
-     `libzip.html#151 <libzip.html#151>`_
-
-   `ZIP_CM_LZ77`:idx:
-     `libzip.html#158 <libzip.html#158>`_
-
-   `ZIP_CM_LZMA`:idx:
-     `libzip.html#156 <libzip.html#156>`_
-
-   `ZIP_CM_PKWARE_IMPLODE`:idx:
-     `libzip.html#154 <libzip.html#154>`_
-
-   `ZIP_CM_PPMD`:idx:
-     `libzip.html#160 <libzip.html#160>`_
-
-   `ZIP_CM_REDUCE_1`:idx:
-     `libzip.html#147 <libzip.html#147>`_
-
-   `ZIP_CM_REDUCE_2`:idx:
-     `libzip.html#148 <libzip.html#148>`_
-
-   `ZIP_CM_REDUCE_3`:idx:
-     `libzip.html#149 <libzip.html#149>`_
-
-   `ZIP_CM_REDUCE_4`:idx:
-     `libzip.html#150 <libzip.html#150>`_
-
-   `ZIP_CM_SHRINK`:idx:
-     `libzip.html#146 <libzip.html#146>`_
-
-   `ZIP_CM_STORE`:idx:
-     `libzip.html#145 <libzip.html#145>`_
-
-   `ZIP_CM_TERSE`:idx:
-     `libzip.html#157 <libzip.html#157>`_
-
-   `ZIP_CM_WAVPACK`:idx:
-     `libzip.html#159 <libzip.html#159>`_
-
-   `ZIP_CREATE`:idx:
-     `libzip.html#108 <libzip.html#108>`_
-
-   `zip_delete`:idx:
-     `libzip.html#173 <libzip.html#173>`_
-
-   `ZIP_EM_NONE`:idx:
-     `libzip.html#161 <libzip.html#161>`_
-
-   `ZIP_EM_TRAD_PKWARE`:idx:
-     `libzip.html#162 <libzip.html#162>`_
-
-   `ZIP_EM_UNKNOWN`:idx:
-     `libzip.html#163 <libzip.html#163>`_
-
-   `ZIP_ER_CHANGED`:idx:
-     `libzip.html#132 <libzip.html#132>`_
-
-   `ZIP_ER_CLOSE`:idx:
-     `libzip.html#120 <libzip.html#120>`_
-
-   `ZIP_ER_COMPNOTSUPP`:idx:
-     `libzip.html#133 <libzip.html#133>`_
-
-   `ZIP_ER_CRC`:idx:
-     `libzip.html#124 <libzip.html#124>`_
-
-   `ZIP_ER_DELETED`:idx:
-     `libzip.html#140 <libzip.html#140>`_
-
-   `ZIP_ER_EOF`:idx:
-     `libzip.html#134 <libzip.html#134>`_
-
-   `ZIP_ER_EXISTS`:idx:
-     `libzip.html#127 <libzip.html#127>`_
-
-   `ZIP_ER_INCONS`:idx:
-     `libzip.html#138 <libzip.html#138>`_
-
-   `ZIP_ER_INTERNAL`:idx:
-     `libzip.html#137 <libzip.html#137>`_
-
-   `ZIP_ER_INVAL`:idx:
-     `libzip.html#135 <libzip.html#135>`_
-
-   `ZIP_ER_MEMORY`:idx:
-     `libzip.html#131 <libzip.html#131>`_
-
-   `ZIP_ER_MULTIDISK`:idx:
-     `libzip.html#118 <libzip.html#118>`_
-
-   `ZIP_ER_NOENT`:idx:
-     `libzip.html#126 <libzip.html#126>`_
-
-   `ZIP_ER_NOZIP`:idx:
-     `libzip.html#136 <libzip.html#136>`_
-
-   `ZIP_ER_OK`:idx:
-     `libzip.html#117 <libzip.html#117>`_
-
-   `ZIP_ER_OPEN`:idx:
-     `libzip.html#128 <libzip.html#128>`_
-
-   `ZIP_ER_READ`:idx:
-     `libzip.html#122 <libzip.html#122>`_
-
-   `ZIP_ER_REMOVE`:idx:
-     `libzip.html#139 <libzip.html#139>`_
-
-   `ZIP_ER_RENAME`:idx:
-     `libzip.html#119 <libzip.html#119>`_
-
-   `zip_error_clear`:idx:
-     `libzip.html#174 <libzip.html#174>`_
-
-   `zip_error_get`:idx:
-     `libzip.html#175 <libzip.html#175>`_
-
-   `zip_error_get_sys_type`:idx:
-     `libzip.html#176 <libzip.html#176>`_
-
-   `zip_error_to_str`:idx:
-     `libzip.html#177 <libzip.html#177>`_
-
-   `ZIP_ER_SEEK`:idx:
-     `libzip.html#121 <libzip.html#121>`_
-
-   `ZIP_ER_TMPOPEN`:idx:
-     `libzip.html#129 <libzip.html#129>`_
-
-   `ZIP_ER_WRITE`:idx:
-     `libzip.html#123 <libzip.html#123>`_
-
-   `ZIP_ER_ZIPCLOSED`:idx:
-     `libzip.html#125 <libzip.html#125>`_
-
-   `ZIP_ER_ZLIB`:idx:
-     `libzip.html#130 <libzip.html#130>`_
-
-   `ZIP_ET_NONE`:idx:
-     `libzip.html#141 <libzip.html#141>`_
-
-   `ZIP_ET_SYS`:idx:
-     `libzip.html#142 <libzip.html#142>`_
-
-   `ZIP_ET_ZLIB`:idx:
-     `libzip.html#143 <libzip.html#143>`_
-
-   `ZIP_EXCL`:idx:
-     `libzip.html#109 <libzip.html#109>`_
-
-   `zip_fclose`:idx:
-     `libzip.html#178 <libzip.html#178>`_
-
-   `zip_file_error_clear`:idx:
-     `libzip.html#179 <libzip.html#179>`_
-
-   `zip_file_error_get`:idx:
-     `libzip.html#180 <libzip.html#180>`_
-
-   `zip_file_strerror`:idx:
-     `libzip.html#181 <libzip.html#181>`_
-
-   `ZIP_FL_COMPRESSED`:idx:
-     `libzip.html#113 <libzip.html#113>`_
-
-   `ZIP_FL_NOCASE`:idx:
-     `libzip.html#111 <libzip.html#111>`_
-
-   `ZIP_FL_NODIR`:idx:
-     `libzip.html#112 <libzip.html#112>`_
-
-   `ZIP_FL_RECOMPRESS`:idx:
-     `libzip.html#115 <libzip.html#115>`_
-
-   `ZIP_FL_UNCHANGED`:idx:
-     `libzip.html#114 <libzip.html#114>`_
-
-   `zip_fopen`:idx:
-     `libzip.html#182 <libzip.html#182>`_
-
-   `zip_fopen_index`:idx:
-     `libzip.html#183 <libzip.html#183>`_
-
-   `zip_fread`:idx:
-     `libzip.html#184 <libzip.html#184>`_
-
-   `zip_get_archive_comment`:idx:
-     `libzip.html#185 <libzip.html#185>`_
-
-   `zip_get_archive_flag`:idx:
-     `libzip.html#186 <libzip.html#186>`_
-
-   `zip_get_file_comment`:idx:
-     `libzip.html#187 <libzip.html#187>`_
-
-   `zip_get_name`:idx:
-     `libzip.html#188 <libzip.html#188>`_
-
-   `zip_get_num_files`:idx:
-     `libzip.html#189 <libzip.html#189>`_
-
-   `zip_name_locate`:idx:
-     `libzip.html#190 <libzip.html#190>`_
-
-   `zip_open`:idx:
-     `libzip.html#191 <libzip.html#191>`_
-
-   `zip_rename`:idx:
-     `libzip.html#192 <libzip.html#192>`_
-
-   `zip_replace`:idx:
-     `libzip.html#193 <libzip.html#193>`_
-
-   `zip_set_archive_comment`:idx:
-     `libzip.html#194 <libzip.html#194>`_
-
-   `zip_set_archive_flag`:idx:
-     `libzip.html#195 <libzip.html#195>`_
-
-   `zip_set_file_comment`:idx:
-     `libzip.html#196 <libzip.html#196>`_
-
-   `zip_source_buffer`:idx:
-     `libzip.html#197 <libzip.html#197>`_
-
-   `ZIP_SOURCE_CLOSE`:idx:
-     `libzip.html#166 <libzip.html#166>`_
-
-   `ZIP_SOURCE_ERROR`:idx:
-     `libzip.html#168 <libzip.html#168>`_
-
-   `zip_source_file`:idx:
-     `libzip.html#198 <libzip.html#198>`_
-
-   `zip_source_filep`:idx:
-     `libzip.html#199 <libzip.html#199>`_
-
-   `zip_source_free`:idx:
-     `libzip.html#200 <libzip.html#200>`_
-
-   `zip_source_function`:idx:
-     `libzip.html#201 <libzip.html#201>`_
-
-   `ZIP_SOURCE_OPEN`:idx:
-     `libzip.html#164 <libzip.html#164>`_
-
-   `ZIP_SOURCE_READ`:idx:
-     `libzip.html#165 <libzip.html#165>`_
-
-   `ZIP_SOURCE_STAT`:idx:
-     `libzip.html#167 <libzip.html#167>`_
-
-   `zip_source_zip`:idx:
-     `libzip.html#202 <libzip.html#202>`_
-
-   `zip_stat`:idx:
-     `libzip.html#203 <libzip.html#203>`_
-
-   `zip_stat_index`:idx:
-     `libzip.html#204 <libzip.html#204>`_
-
-   `zip_stat_init`:idx:
-     `libzip.html#205 <libzip.html#205>`_
-
-   `zip_strerror`:idx:
-     `libzip.html#206 <libzip.html#206>`_
-
-   `zip_unchange`:idx:
-     `libzip.html#207 <libzip.html#207>`_
-
-   `zip_unchange_all`:idx:
-     `libzip.html#208 <libzip.html#208>`_
-
-   `zip_unchange_archive`:idx:
-     `libzip.html#209 <libzip.html#209>`_
-
-   `zlibAllocMem`:idx:
-     `zlib.html#187 <zlib.html#187>`_
-
-   `zlibFreeMem`:idx:
-     `zlib.html#188 <zlib.html#188>`_
-
-   `zlibVersion`:idx:
-     `zlib.html#142 <zlib.html#142>`_
-
-   `Z_MEM_ERROR`:idx:
-     `zlib.html#127 <zlib.html#127>`_
-
-   `Z_NEED_DICT`:idx:
-     `zlib.html#123 <zlib.html#123>`_
-
-   `Z_NO_COMPRESSION`:idx:
-     `zlib.html#130 <zlib.html#130>`_
-
-   `Z_NO_FLUSH`:idx:
-     `zlib.html#116 <zlib.html#116>`_
-
-   `Z_NULL`:idx:
-     `zlib.html#141 <zlib.html#141>`_
-
-   `z_off_t`:idx:
-     `zlib.html#105 <zlib.html#105>`_
-
-   `Z_OK`:idx:
-     `zlib.html#121 <zlib.html#121>`_
-
-   `Z_PARTIAL_FLUSH`:idx:
-     `zlib.html#117 <zlib.html#117>`_
-
-   `Z_STREAM_END`:idx:
-     `zlib.html#122 <zlib.html#122>`_
-
-   `Z_STREAM_ERROR`:idx:
-     `zlib.html#125 <zlib.html#125>`_
-
-   `Z_SYNC_FLUSH`:idx:
-     `zlib.html#118 <zlib.html#118>`_
-
-   `Z_UNKNOWN`:idx:
-     `zlib.html#139 <zlib.html#139>`_
-
-   `Z_VERSION_ERROR`:idx:
+

+=====

+Index

+=====

+

+.. index::

+

+

+   `!=`:idx:

+     `system.html#351 <system.html#351>`_

+

+   `$`:idx:

+     * `system.html#422 <system.html#422>`_

+     * `system.html#423 <system.html#423>`_

+     * `system.html#424 <system.html#424>`_

+     * `system.html#425 <system.html#425>`_

+     * `system.html#426 <system.html#426>`_

+     * `system.html#427 <system.html#427>`_

+     * `system.html#428 <system.html#428>`_

+     * `system.html#429 <system.html#429>`_

+     * `times.html#109 <times.html#109>`_

+     * `times.html#110 <times.html#110>`_

+

+   `%`:idx:

+     * `strutils.html#134 <strutils.html#134>`_

+     * `strutils.html#135 <strutils.html#135>`_

+     * `strtabs.html#112 <strtabs.html#112>`_

+

+   `%%`:idx:

+     * `system.html#296 <system.html#296>`_

+     * `system.html#297 <system.html#297>`_

+     * `system.html#298 <system.html#298>`_

+     * `system.html#299 <system.html#299>`_

+     * `system.html#300 <system.html#300>`_

+

+   `&`:idx:

+     * `system.html#362 <system.html#362>`_

+     * `system.html#363 <system.html#363>`_

+     * `system.html#364 <system.html#364>`_

+     * `system.html#365 <system.html#365>`_

+     * `system.html#453 <system.html#453>`_

+     * `system.html#454 <system.html#454>`_

+     * `system.html#455 <system.html#455>`_

+     * `system.html#456 <system.html#456>`_

+

+   `*`:idx:

+     * `system.html#206 <system.html#206>`_

+     * `system.html#207 <system.html#207>`_

+     * `system.html#208 <system.html#208>`_

+     * `system.html#209 <system.html#209>`_

+     * `system.html#210 <system.html#210>`_

+     * `system.html#315 <system.html#315>`_

+     * `system.html#323 <system.html#323>`_

+     * `complex.html#107 <complex.html#107>`_

+

+   `*%`:idx:

+     * `system.html#286 <system.html#286>`_

+     * `system.html#287 <system.html#287>`_

+     * `system.html#288 <system.html#288>`_

+     * `system.html#289 <system.html#289>`_

+     * `system.html#290 <system.html#290>`_

+

+   `+`:idx:

+     * `system.html#181 <system.html#181>`_

+     * `system.html#182 <system.html#182>`_

+     * `system.html#183 <system.html#183>`_

+     * `system.html#184 <system.html#184>`_

+     * `system.html#185 <system.html#185>`_

+     * `system.html#196 <system.html#196>`_

+     * `system.html#197 <system.html#197>`_

+     * `system.html#198 <system.html#198>`_

+     * `system.html#199 <system.html#199>`_

+     * `system.html#200 <system.html#200>`_

+     * `system.html#311 <system.html#311>`_

+     * `system.html#313 <system.html#313>`_

+     * `system.html#324 <system.html#324>`_

+     * `complex.html#103 <complex.html#103>`_

+

+   `+%`:idx:

+     * `system.html#276 <system.html#276>`_

+     * `system.html#277 <system.html#277>`_

+     * `system.html#278 <system.html#278>`_

+     * `system.html#279 <system.html#279>`_

+     * `system.html#280 <system.html#280>`_

+

+   `-`:idx:

+     * `system.html#186 <system.html#186>`_

+     * `system.html#187 <system.html#187>`_

+     * `system.html#188 <system.html#188>`_

+     * `system.html#189 <system.html#189>`_

+     * `system.html#190 <system.html#190>`_

+     * `system.html#201 <system.html#201>`_

+     * `system.html#202 <system.html#202>`_

+     * `system.html#203 <system.html#203>`_

+     * `system.html#204 <system.html#204>`_

+     * `system.html#205 <system.html#205>`_

+     * `system.html#312 <system.html#312>`_

+     * `system.html#314 <system.html#314>`_

+     * `system.html#325 <system.html#325>`_

+     * `complex.html#104 <complex.html#104>`_

+     * `complex.html#105 <complex.html#105>`_

+     * `times.html#113 <times.html#113>`_

+

+   `-%`:idx:

+     * `system.html#281 <system.html#281>`_

+     * `system.html#282 <system.html#282>`_

+     * `system.html#283 <system.html#283>`_

+     * `system.html#284 <system.html#284>`_

+     * `system.html#285 <system.html#285>`_

+

+   `-+-`:idx:

+     `system.html#326 <system.html#326>`_

+

+   `/`:idx:

+     * `system.html#316 <system.html#316>`_

+     * `os.html#119 <os.html#119>`_

+     * `complex.html#106 <complex.html#106>`_

+

+   `/%`:idx:

+     * `system.html#291 <system.html#291>`_

+     * `system.html#292 <system.html#292>`_

+     * `system.html#293 <system.html#293>`_

+     * `system.html#294 <system.html#294>`_

+     * `system.html#295 <system.html#295>`_

+

+   `/../`:idx:

+     `os.html#123 <os.html#123>`_

+

+   `<`:idx:

+     * `system.html#256 <system.html#256>`_

+     * `system.html#257 <system.html#257>`_

+     * `system.html#258 <system.html#258>`_

+     * `system.html#259 <system.html#259>`_

+     * `system.html#260 <system.html#260>`_

+     * `system.html#319 <system.html#319>`_

+     * `system.html#343 <system.html#343>`_

+     * `system.html#344 <system.html#344>`_

+     * `system.html#345 <system.html#345>`_

+     * `system.html#346 <system.html#346>`_

+     * `system.html#347 <system.html#347>`_

+     * `system.html#348 <system.html#348>`_

+     * `system.html#349 <system.html#349>`_

+     * `system.html#350 <system.html#350>`_

+     * `times.html#114 <times.html#114>`_

+

+   `<%`:idx:

+     * `system.html#306 <system.html#306>`_

+     * `system.html#307 <system.html#307>`_

+     * `system.html#308 <system.html#308>`_

+     * `system.html#309 <system.html#309>`_

+     * `system.html#310 <system.html#310>`_

+

+   `<=`:idx:

+     * `system.html#251 <system.html#251>`_

+     * `system.html#252 <system.html#252>`_

+     * `system.html#253 <system.html#253>`_

+     * `system.html#254 <system.html#254>`_

+     * `system.html#255 <system.html#255>`_

+     * `system.html#318 <system.html#318>`_

+     * `system.html#336 <system.html#336>`_

+     * `system.html#337 <system.html#337>`_

+     * `system.html#338 <system.html#338>`_

+     * `system.html#339 <system.html#339>`_

+     * `system.html#340 <system.html#340>`_

+     * `system.html#341 <system.html#341>`_

+     * `system.html#342 <system.html#342>`_

+

+   `<=`:idx:

+     `times.html#115 <times.html#115>`_

+

+   `<=%`:idx:

+     * `system.html#301 <system.html#301>`_

+     * `system.html#302 <system.html#302>`_

+     * `system.html#303 <system.html#303>`_

+     * `system.html#304 <system.html#304>`_

+     * `system.html#305 <system.html#305>`_

+

+   `==`:idx:

+     * `system.html#246 <system.html#246>`_

+     * `system.html#247 <system.html#247>`_

+     * `system.html#248 <system.html#248>`_

+     * `system.html#249 <system.html#249>`_

+     * `system.html#250 <system.html#250>`_

+     * `system.html#317 <system.html#317>`_

+     * `system.html#327 <system.html#327>`_

+     * `system.html#328 <system.html#328>`_

+     * `system.html#329 <system.html#329>`_

+     * `system.html#330 <system.html#330>`_

+     * `system.html#331 <system.html#331>`_

+     * `system.html#332 <system.html#332>`_

+     * `system.html#333 <system.html#333>`_

+     * `system.html#334 <system.html#334>`_

+     * `system.html#335 <system.html#335>`_

+     * `system.html#458 <system.html#458>`_

+     * `complex.html#102 <complex.html#102>`_

+

+   `>`:idx:

+     `system.html#353 <system.html#353>`_

+

+   `>%`:idx:

+     `system.html#421 <system.html#421>`_

+

+   `>=`:idx:

+     `system.html#352 <system.html#352>`_

+

+   `>=%`:idx:

+     `system.html#420 <system.html#420>`_

+

+   `@`:idx:

+     `system.html#361 <system.html#361>`_

+

+   `[]`:idx:

+     `strtabs.html#107 <strtabs.html#107>`_

+

+   `[]=`:idx:

+     `strtabs.html#106 <strtabs.html#106>`_

+

+   `[ESC]`:idx:

+     `manual.html#134 <manual.html#134>`_

+

+   `ABDAY_1`:idx:

+     `posix.html#403 <posix.html#403>`_

+

+   `ABDAY_2`:idx:

+     `posix.html#404 <posix.html#404>`_

+

+   `ABDAY_3`:idx:

+     `posix.html#405 <posix.html#405>`_

+

+   `ABDAY_4`:idx:

+     `posix.html#406 <posix.html#406>`_

+

+   `ABDAY_5`:idx:

+     `posix.html#407 <posix.html#407>`_

+

+   `ABDAY_6`:idx:

+     `posix.html#408 <posix.html#408>`_

+

+   `ABDAY_7`:idx:

+     `posix.html#409 <posix.html#409>`_

+

+   `ABMON_1`:idx:

+     `posix.html#422 <posix.html#422>`_

+

+   `ABMON_10`:idx:

+     `posix.html#431 <posix.html#431>`_

+

+   `ABMON_11`:idx:

+     `posix.html#432 <posix.html#432>`_

+

+   `ABMON_12`:idx:

+     `posix.html#433 <posix.html#433>`_

+

+   `ABMON_2`:idx:

+     `posix.html#423 <posix.html#423>`_

+

+   `ABMON_3`:idx:

+     `posix.html#424 <posix.html#424>`_

+

+   `ABMON_4`:idx:

+     `posix.html#425 <posix.html#425>`_

+

+   `ABMON_5`:idx:

+     `posix.html#426 <posix.html#426>`_

+

+   `ABMON_6`:idx:

+     `posix.html#427 <posix.html#427>`_

+

+   `ABMON_7`:idx:

+     `posix.html#428 <posix.html#428>`_

+

+   `ABMON_8`:idx:

+     `posix.html#429 <posix.html#429>`_

+

+   `ABMON_9`:idx:

+     `posix.html#430 <posix.html#430>`_

+

+   `abs`:idx:

+     * `system.html#261 <system.html#261>`_

+     * `system.html#262 <system.html#262>`_

+     * `system.html#263 <system.html#263>`_

+     * `system.html#264 <system.html#264>`_

+     * `system.html#265 <system.html#265>`_

+     * `system.html#320 <system.html#320>`_

+     * `complex.html#108 <complex.html#108>`_

+

+   `access`:idx:

+     `posix.html#966 <posix.html#966>`_

+

+   `acyclic`:idx:

+     `nimrodc.html#113 <nimrodc.html#113>`_

+

+   `add`:idx:

+     * `system.html#366 <system.html#366>`_

+     * `system.html#367 <system.html#367>`_

+     * `system.html#368 <system.html#368>`_

+     * `system.html#369 <system.html#369>`_

+     * `system.html#370 <system.html#370>`_

+

+   `addFile`:idx:

+     * `zipfiles.html#105 <zipfiles.html#105>`_

+     * `zipfiles.html#106 <zipfiles.html#106>`_

+     * `zipfiles.html#107 <zipfiles.html#107>`_

+

+   `addQuitProc`:idx:

+     `system.html#404 <system.html#404>`_

+

+   `adler32`:idx:

+     `zlib.html#174 <zlib.html#174>`_

+

+   `AIO_ALLDONE`:idx:

+     `posix.html#207 <posix.html#207>`_

+

+   `aio_cancel`:idx:

+     `posix.html#784 <posix.html#784>`_

+

+   `AIO_CANCELED`:idx:

+     `posix.html#208 <posix.html#208>`_

+

+   `aio_error`:idx:

+     `posix.html#785 <posix.html#785>`_

+

+   `aio_fsync`:idx:

+     `posix.html#786 <posix.html#786>`_

+

+   `AIO_NOTCANCELED`:idx:

+     `posix.html#209 <posix.html#209>`_

+

+   `aio_read`:idx:

+     `posix.html#787 <posix.html#787>`_

+

+   `aio_return`:idx:

+     `posix.html#788 <posix.html#788>`_

+

+   `aio_suspend`:idx:

+     `posix.html#789 <posix.html#789>`_

+

+   `aio_write`:idx:

+     `posix.html#790 <posix.html#790>`_

+

+   `alarm`:idx:

+     `posix.html#967 <posix.html#967>`_

+

+   `alert`:idx:

+     `manual.html#131 <manual.html#131>`_

+

+   `allCharsInSet`:idx:

+     `strutils.html#139 <strutils.html#139>`_

+

+   `alloc`:idx:

+     `system.html#413 <system.html#413>`_

+

+   `alloc0`:idx:

+     `system.html#414 <system.html#414>`_

+

+   `ALT_DIGITS`:idx:

+     `posix.html#438 <posix.html#438>`_

+

+   `AltSep`:idx:

+     `os.html#104 <os.html#104>`_

+

+   `AM_STR`:idx:

+     `posix.html#394 <posix.html#394>`_

+

+   `and`:idx:

+     * `system.html#116 <system.html#116>`_

+     * `system.html#231 <system.html#231>`_

+     * `system.html#232 <system.html#232>`_

+     * `system.html#233 <system.html#233>`_

+     * `system.html#234 <system.html#234>`_

+     * `system.html#235 <system.html#235>`_

+

+   `apostrophe`:idx:

+     `manual.html#129 <manual.html#129>`_

+

+   `AppendFileExt`:idx:

+     `os.html#131 <os.html#131>`_

+

+   `arccos`:idx:

+     `math.html#117 <math.html#117>`_

+

+   `arcsin`:idx:

+     `math.html#118 <math.html#118>`_

+

+   `arctan`:idx:

+     `math.html#119 <math.html#119>`_

+

+   `arctan2`:idx:

+     `math.html#120 <math.html#120>`_

+

+   `arithmetic bit shifts`:idx:

+     `tut1.html#110 <tut1.html#110>`_

+

+   `array`:idx:

+     * `tut1.html#117 <tut1.html#117>`_

+     * `system.html#124 <system.html#124>`_

+

+   `array properties`:idx:

+     `tut2.html#105 <tut2.html#105>`_

+

+   `Arrays`:idx:

+     `manual.html#152 <manual.html#152>`_

+

+   `asctime`:idx:

+     `posix.html#1092 <posix.html#1092>`_

+

+   `asctime_r`:idx:

+     `posix.html#1093 <posix.html#1093>`_

+

+   `assembler`:idx:

+     `manual.html#196 <manual.html#196>`_

+

+   `assert`:idx:

+     `system.html#418 <system.html#418>`_

+

+   `Automatic type conversion`:idx:

+     * `manual.html#144 <manual.html#144>`_

+     * `tut1.html#111 <tut1.html#111>`_

+

+   `backslash`:idx:

+     * `manual.html#127 <manual.html#127>`_

+     * `regexprs.html#101 <regexprs.html#101>`_

+

+   `backspace`:idx:

+     `manual.html#132 <manual.html#132>`_

+

+   `basename`:idx:

+     `posix.html#844 <posix.html#844>`_

+

+   `BiggestFloat`:idx:

+     `system.html#374 <system.html#374>`_

+

+   `BiggestInt`:idx:

+     `system.html#373 <system.html#373>`_

+

+   `block`:idx:

+     `manual.html#192 <manual.html#192>`_

+

+   `bool`:idx:

+     `system.html#109 <system.html#109>`_

+

+   `boolean`:idx:

+     * `manual.html#146 <manual.html#146>`_

+     * `tut1.html#107 <tut1.html#107>`_

+

+   `break`:idx:

+     `manual.html#193 <manual.html#193>`_

+

+   `breakpoint`:idx:

+     `endb.html#103 <endb.html#103>`_

+

+   `bsd_signal`:idx:

+     `posix.html#1122 <posix.html#1122>`_

+

+   `Byte`:idx:

+     `system.html#128 <system.html#128>`_

+

+   `calling conventions`:idx:

+     `manual.html#163 <manual.html#163>`_

+

+   `capitalize`:idx:

+     `strutils.html#110 <strutils.html#110>`_

+

+   `card`:idx:

+     `system.html#169 <system.html#169>`_

+

+   `carriage return`:idx:

+     `manual.html#122 <manual.html#122>`_

+

+   `case`:idx:

+     `manual.html#181 <manual.html#181>`_

+

+   `catclose`:idx:

+     `posix.html#1149 <posix.html#1149>`_

+

+   `catgets`:idx:

+     `posix.html#1150 <posix.html#1150>`_

+

+   `catopen`:idx:

+     `posix.html#1151 <posix.html#1151>`_

+

+   `cchar`:idx:

+     `system.html#375 <system.html#375>`_

+

+   `cdecl`:idx:

+     `manual.html#165 <manual.html#165>`_

+

+   `cdouble`:idx:

+     `system.html#382 <system.html#382>`_

+

+   `cfloat`:idx:

+     `system.html#381 <system.html#381>`_

+

+   `ChangeFileExt`:idx:

+     `os.html#132 <os.html#132>`_

+

+   `char`:idx:

+     `system.html#110 <system.html#110>`_

+

+   `character type`:idx:

+     `manual.html#147 <manual.html#147>`_

+

+   `character with decimal value d`:idx:

+     `manual.html#130 <manual.html#130>`_

+

+   `character with hex value HH`:idx:

+     `manual.html#135 <manual.html#135>`_

+

+   `chdir`:idx:

+     `posix.html#968 <posix.html#968>`_

+

+   `checked runtime error`:idx:

+     `manual.html#110 <manual.html#110>`_

+

+   `chmod`:idx:

+     `posix.html#1058 <posix.html#1058>`_

+

+   `ChooseDir`:idx:

+     `dialogs.html#108 <dialogs.html#108>`_

+

+   `ChooseFilesToOpen`:idx:

+     `dialogs.html#106 <dialogs.html#106>`_

+

+   `ChooseFileToOpen`:idx:

+     `dialogs.html#105 <dialogs.html#105>`_

+

+   `ChooseFileToSave`:idx:

+     `dialogs.html#107 <dialogs.html#107>`_

+

+   `chown`:idx:

+     `posix.html#969 <posix.html#969>`_

+

+   `chr`:idx:

+     `system.html#171 <system.html#171>`_

+

+   `cint`:idx:

+     `system.html#378 <system.html#378>`_

+

+   `C_IRGRP`:idx:

+     `posix.html#104 <posix.html#104>`_

+

+   `C_IROTH`:idx:

+     `posix.html#107 <posix.html#107>`_

+

+   `C_IRUSR`:idx:

+     `posix.html#101 <posix.html#101>`_

+

+   `C_ISBLK`:idx:

+     `posix.html#116 <posix.html#116>`_

+

+   `C_ISCHR`:idx:

+     `posix.html#117 <posix.html#117>`_

+

+   `C_ISCTG`:idx:

+     `posix.html#118 <posix.html#118>`_

+

+   `C_ISDIR`:idx:

+     `posix.html#113 <posix.html#113>`_

+

+   `C_ISFIFO`:idx:

+     `posix.html#114 <posix.html#114>`_

+

+   `C_ISGID`:idx:

+     `posix.html#111 <posix.html#111>`_

+

+   `C_ISLNK`:idx:

+     `posix.html#119 <posix.html#119>`_

+

+   `C_ISREG`:idx:

+     `posix.html#115 <posix.html#115>`_

+

+   `C_ISSOCK`:idx:

+     `posix.html#120 <posix.html#120>`_

+

+   `C_ISUID`:idx:

+     `posix.html#110 <posix.html#110>`_

+

+   `C_ISVTX`:idx:

+     `posix.html#112 <posix.html#112>`_

+

+   `C_IWGRP`:idx:

+     `posix.html#105 <posix.html#105>`_

+

+   `C_IWOTH`:idx:

+     `posix.html#108 <posix.html#108>`_

+

+   `C_IWUSR`:idx:

+     `posix.html#102 <posix.html#102>`_

+

+   `C_IXGRP`:idx:

+     `posix.html#106 <posix.html#106>`_

+

+   `C_IXOTH`:idx:

+     `posix.html#109 <posix.html#109>`_

+

+   `C_IXUSR`:idx:

+     `posix.html#103 <posix.html#103>`_

+

+   `classify`:idx:

+     `math.html#104 <math.html#104>`_

+

+   `clock`:idx:

+     `posix.html#1094 <posix.html#1094>`_

+

+   `clock_getcpuclockid`:idx:

+     `posix.html#1095 <posix.html#1095>`_

+

+   `clock_getres`:idx:

+     `posix.html#1096 <posix.html#1096>`_

+

+   `clock_gettime`:idx:

+     `posix.html#1097 <posix.html#1097>`_

+

+   `CLOCK_MONOTONIC`:idx:

+     `posix.html#700 <posix.html#700>`_

+

+   `clock_nanosleep`:idx:

+     `posix.html#1098 <posix.html#1098>`_

+

+   `CLOCK_PROCESS_CPUTIME_ID`:idx:

+     `posix.html#696 <posix.html#696>`_

+

+   `CLOCK_REALTIME`:idx:

+     `posix.html#698 <posix.html#698>`_

+

+   `clock_settime`:idx:

+     `posix.html#1099 <posix.html#1099>`_

+

+   `CLOCKS_PER_SEC`:idx:

+     `posix.html#695 <posix.html#695>`_

+

+   `CLOCK_THREAD_CPUTIME_ID`:idx:

+     `posix.html#697 <posix.html#697>`_

+

+   `clong`:idx:

+     `system.html#379 <system.html#379>`_

+

+   `clongdouble`:idx:

+     `system.html#383 <system.html#383>`_

+

+   `clonglong`:idx:

+     `system.html#380 <system.html#380>`_

+

+   `close`:idx:

+     * `posix.html#970 <posix.html#970>`_

+     * `lexbase.html#105 <lexbase.html#105>`_

+     * `parsecfg.html#105 <parsecfg.html#105>`_

+     * `zipfiles.html#103 <zipfiles.html#103>`_

+

+   `closedir`:idx:

+     `posix.html#800 <posix.html#800>`_

+

+   `CloseFile`:idx:

+     `system.html#488 <system.html#488>`_

+

+   `closure`:idx:

+     `manual.html#170 <manual.html#170>`_

+

+   `cmp`:idx:

+     * `system.html#359 <system.html#359>`_

+     * `system.html#360 <system.html#360>`_

+

+   `cmpIgnoreCase`:idx:

+     `strutils.html#123 <strutils.html#123>`_

+

+   `cmpIgnoreStyle`:idx:

+     `strutils.html#124 <strutils.html#124>`_

+

+   `cmpPaths`:idx:

+     `os.html#130 <os.html#130>`_

+

+   `CODESET`:idx:

+     `posix.html#389 <posix.html#389>`_

+

+   `comment pieces`:idx:

+     * `manual.html#115 <manual.html#115>`_

+     * `tut1.html#103 <tut1.html#103>`_

+

+   `Comments`:idx:

+     * `manual.html#114 <manual.html#114>`_

+     * `tut1.html#102 <tut1.html#102>`_

+

+   `CompileDate`:idx:

+     `system.html#391 <system.html#391>`_

+

+   `CompileTime`:idx:

+     `system.html#392 <system.html#392>`_

+

+   `complex statements`:idx:

+     `manual.html#175 <manual.html#175>`_

+

+   `compress`:idx:

+     `zlib.html#154 <zlib.html#154>`_

+

+   `compress2`:idx:

+     `zlib.html#155 <zlib.html#155>`_

+

+   `confstr`:idx:

+     `posix.html#971 <posix.html#971>`_

+

+   `const`:idx:

+     `manual.html#179 <manual.html#179>`_

+

+   `constant expressions`:idx:

+     `manual.html#108 <manual.html#108>`_

+

+   `Constants`:idx:

+     * `manual.html#139 <manual.html#139>`_

+     * `tut1.html#104 <tut1.html#104>`_

+

+   `constZIP_SOURCE_FREE`:idx:

+     `libzip.html#169 <libzip.html#169>`_

+

+   `contains`:idx:

+     * `system.html#354 <system.html#354>`_

+     * `strutils.html#125 <strutils.html#125>`_

+     * `strutils.html#126 <strutils.html#126>`_

+     * `strutils.html#127 <strutils.html#127>`_

+

+   `continue`:idx:

+     `manual.html#195 <manual.html#195>`_

+

+   `copy`:idx:

+     * `system.html#405 <system.html#405>`_

+     * `system.html#406 <system.html#406>`_

+

+   `copyFile`:idx:

+     `os.html#134 <os.html#134>`_

+

+   `copyMem`:idx:

+     `system.html#410 <system.html#410>`_

+

+   `cos`:idx:

+     `math.html#121 <math.html#121>`_

+

+   `cosh`:idx:

+     `math.html#122 <math.html#122>`_

+

+   `countBits`:idx:

+     `math.html#107 <math.html#107>`_

+

+   `countdown`:idx:

+     `system.html#439 <system.html#439>`_

+

+   `countup`:idx:

+     `system.html#440 <system.html#440>`_

+

+   `cpuEndian`:idx:

+     `system.html#397 <system.html#397>`_

+

+   `crc32`:idx:

+     `zlib.html#175 <zlib.html#175>`_

+

+   `creat`:idx:

+     `posix.html#811 <posix.html#811>`_

+

+   `createDir`:idx:

+     * `os.html#138 <os.html#138>`_

+     * `zipfiles.html#104 <zipfiles.html#104>`_

+

+   `CRNCYSTR`:idx:

+     `posix.html#443 <posix.html#443>`_

+

+   `crypt`:idx:

+     `posix.html#972 <posix.html#972>`_

+

+   `cschar`:idx:

+     `system.html#376 <system.html#376>`_

+

+   `cshort`:idx:

+     `system.html#377 <system.html#377>`_

+

+   `cSIG_HOLD`:idx:

+     `posix.html#721 <posix.html#721>`_

+

+   `CS_PATH`:idx:

+     `posix.html#482 <posix.html#482>`_

+

+   `CS_POSIX_V6_ILP32_OFF32_CFLAGS`:idx:

+     `posix.html#483 <posix.html#483>`_

+

+   `CS_POSIX_V6_ILP32_OFF32_LDFLAGS`:idx:

+     `posix.html#484 <posix.html#484>`_

+

+   `CS_POSIX_V6_ILP32_OFF32_LIBS`:idx:

+     `posix.html#485 <posix.html#485>`_

+

+   `CS_POSIX_V6_ILP32_OFFBIG_CFLAGS`:idx:

+     `posix.html#486 <posix.html#486>`_

+

+   `CS_POSIX_V6_ILP32_OFFBIG_LDFLAGS`:idx:

+     `posix.html#487 <posix.html#487>`_

+

+   `CS_POSIX_V6_ILP32_OFFBIG_LIBS`:idx:

+     `posix.html#488 <posix.html#488>`_

+

+   `CS_POSIX_V6_LP64_OFF64_CFLAGS`:idx:

+     `posix.html#489 <posix.html#489>`_

+

+   `CS_POSIX_V6_LP64_OFF64_LDFLAGS`:idx:

+     `posix.html#490 <posix.html#490>`_

+

+   `CS_POSIX_V6_LP64_OFF64_LIBS`:idx:

+     `posix.html#491 <posix.html#491>`_

+

+   `CS_POSIX_V6_LPBIG_OFFBIG_CFLAGS`:idx:

+     `posix.html#492 <posix.html#492>`_

+

+   `CS_POSIX_V6_LPBIG_OFFBIG_LDFLAGS`:idx:

+     `posix.html#493 <posix.html#493>`_

+

+   `CS_POSIX_V6_LPBIG_OFFBIG_LIBS`:idx:

+     `posix.html#494 <posix.html#494>`_

+

+   `CS_POSIX_V6_WIDTH_RESTRICTED_ENVS`:idx:

+     `posix.html#495 <posix.html#495>`_

+

+   `cstring`:idx:

+     `system.html#112 <system.html#112>`_

+

+   `cstringArray`:idx:

+     `system.html#384 <system.html#384>`_

+

+   `ctermid`:idx:

+     `posix.html#973 <posix.html#973>`_

+

+   `ctime`:idx:

+     `posix.html#1100 <posix.html#1100>`_

+

+   `ctime_r`:idx:

+     `posix.html#1101 <posix.html#1101>`_

+

+   `CurDir`:idx:

+     `os.html#101 <os.html#101>`_

+

+   `dangling else problem`:idx:

+     `manual.html#176 <manual.html#176>`_

+

+   `DAY_1`:idx:

+     `posix.html#396 <posix.html#396>`_

+

+   `DAY_2`:idx:

+     `posix.html#397 <posix.html#397>`_

+

+   `DAY_3`:idx:

+     `posix.html#398 <posix.html#398>`_

+

+   `DAY_4`:idx:

+     `posix.html#399 <posix.html#399>`_

+

+   `DAY_5`:idx:

+     `posix.html#400 <posix.html#400>`_

+

+   `DAY_6`:idx:

+     `posix.html#401 <posix.html#401>`_

+

+   `DAY_7`:idx:

+     `posix.html#402 <posix.html#402>`_

+

+   `daylight`:idx:

+     `posix.html#701 <posix.html#701>`_

+

+   `dbgLineHook`:idx:

+     `system.html#435 <system.html#435>`_

+

+   `dead_code_elim`:idx:

+     `nimrodc.html#114 <nimrodc.html#114>`_

+

+   `dealloc`:idx:

+     `system.html#416 <system.html#416>`_

+

+   `debugger`:idx:

+     `nimrodc.html#110 <nimrodc.html#110>`_

+

+   `dec`:idx:

+     `system.html#160 <system.html#160>`_

+

+   `define`:idx:

+     `manual.html#222 <manual.html#222>`_

+

+   `defined`:idx:

+     `system.html#114 <system.html#114>`_

+

+   `deflate`:idx:

+     `zlib.html#143 <zlib.html#143>`_

+

+   `deflateCopy`:idx:

+     `zlib.html#148 <zlib.html#148>`_

+

+   `deflateEnd`:idx:

+     `zlib.html#144 <zlib.html#144>`_

+

+   `deflateInit`:idx:

+     `zlib.html#178 <zlib.html#178>`_

+

+   `deflateInit2`:idx:

+     `zlib.html#182 <zlib.html#182>`_

+

+   `deflateInit2u`:idx:

+     `zlib.html#180 <zlib.html#180>`_

+

+   `deflateInitu`:idx:

+     `zlib.html#176 <zlib.html#176>`_

+

+   `deflateParams`:idx:

+     `zlib.html#150 <zlib.html#150>`_

+

+   `deflateReset`:idx:

+     `zlib.html#149 <zlib.html#149>`_

+

+   `deflateSetDictionary`:idx:

+     `zlib.html#147 <zlib.html#147>`_

+

+   `deleteStr`:idx:

+     `strutils.html#117 <strutils.html#117>`_

+

+   `D_FMT`:idx:

+     `posix.html#391 <posix.html#391>`_

+

+   `difftime`:idx:

+     `posix.html#1102 <posix.html#1102>`_

+

+   `dirname`:idx:

+     `posix.html#845 <posix.html#845>`_

+

+   `DirSep`:idx:

+     `os.html#103 <os.html#103>`_

+

+   `discard`:idx:

+     `manual.html#177 <manual.html#177>`_

+

+   `div`:idx:

+     * `system.html#211 <system.html#211>`_

+     * `system.html#212 <system.html#212>`_

+     * `system.html#213 <system.html#213>`_

+     * `system.html#214 <system.html#214>`_

+     * `system.html#215 <system.html#215>`_

+

+   `dlclose`:idx:

+     `posix.html#807 <posix.html#807>`_

+

+   `dlerror`:idx:

+     `posix.html#808 <posix.html#808>`_

+

+   `dlopen`:idx:

+     `posix.html#809 <posix.html#809>`_

+

+   `dlsym`:idx:

+     `posix.html#810 <posix.html#810>`_

+

+   `dom`:idx:

+     `nimrodc.html#120 <nimrodc.html#120>`_

+

+   `domain specific languages`:idx:

+     * `manual.html#211 <manual.html#211>`_

+     * `tut2.html#112 <tut2.html#112>`_

+

+   `D_T_FMT`:idx:

+     `posix.html#390 <posix.html#390>`_

+

+   `dup`:idx:

+     `posix.html#974 <posix.html#974>`_

+

+   `dup2`:idx:

+     `posix.html#975 <posix.html#975>`_

+

+   `dynamic type`:idx:

+     `manual.html#104 <manual.html#104>`_

+

+   `dynlib`:idx:

+     `nimrodc.html#103 <nimrodc.html#103>`_

+

+   `E`:idx:

+     `math.html#102 <math.html#102>`_

+

+   `E2BIG`:idx:

+     `posix.html#220 <posix.html#220>`_

+

+   `EACCES`:idx:

+     `posix.html#221 <posix.html#221>`_

+

+   `EAccessViolation`:idx:

+     `system.html#143 <system.html#143>`_

+

+   `EADDRINUSE`:idx:

+     `posix.html#222 <posix.html#222>`_

+

+   `EADDRNOTAVAIL`:idx:

+     `posix.html#223 <posix.html#223>`_

+

+   `EAFNOSUPPORT`:idx:

+     `posix.html#224 <posix.html#224>`_

+

+   `EAGAIN`:idx:

+     `posix.html#225 <posix.html#225>`_

+

+   `EALREADY`:idx:

+     `posix.html#226 <posix.html#226>`_

+

+   `EArithmetic`:idx:

+     `system.html#140 <system.html#140>`_

+

+   `EAssertionFailed`:idx:

+     `system.html#144 <system.html#144>`_

+

+   `EAsynch`:idx:

+     `system.html#134 <system.html#134>`_

+

+   `EBADF`:idx:

+     `posix.html#227 <posix.html#227>`_

+

+   `EBADMSG`:idx:

+     `posix.html#228 <posix.html#228>`_

+

+   `E_Base`:idx:

+     `system.html#133 <system.html#133>`_

+

+   `EBUSY`:idx:

+     `posix.html#229 <posix.html#229>`_

+

+   `ECANCELED`:idx:

+     `posix.html#230 <posix.html#230>`_

+

+   `ECHILD`:idx:

+     `posix.html#231 <posix.html#231>`_

+

+   `echo`:idx:

+     * `system.html#474 <system.html#474>`_

+     * `system.html#475 <system.html#475>`_

+

+   `ECMAScript`:idx:

+     `nimrodc.html#115 <nimrodc.html#115>`_

+

+   `ECONNABORTED`:idx:

+     `posix.html#232 <posix.html#232>`_

+

+   `ECONNREFUSED`:idx:

+     `posix.html#233 <posix.html#233>`_

+

+   `ECONNRESET`:idx:

+     `posix.html#234 <posix.html#234>`_

+

+   `EControlC`:idx:

+     `system.html#145 <system.html#145>`_

+

+   `EDEADLK`:idx:

+     `posix.html#235 <posix.html#235>`_

+

+   `EDESTADDRREQ`:idx:

+     `posix.html#236 <posix.html#236>`_

+

+   `editDistance`:idx:

+     `strutils.html#144 <strutils.html#144>`_

+

+   `EDivByZero`:idx:

+     `system.html#141 <system.html#141>`_

+

+   `EDOM`:idx:

+     `posix.html#237 <posix.html#237>`_

+

+   `EDQUOT`:idx:

+     `posix.html#238 <posix.html#238>`_

+

+   `EEXIST`:idx:

+     `posix.html#239 <posix.html#239>`_

+

+   `EFAULT`:idx:

+     `posix.html#240 <posix.html#240>`_

+

+   `EFBIG`:idx:

+     `posix.html#241 <posix.html#241>`_

+

+   `EHOSTUNREACH`:idx:

+     `posix.html#242 <posix.html#242>`_

+

+   `EIDRM`:idx:

+     `posix.html#243 <posix.html#243>`_

+

+   `EILSEQ`:idx:

+     `posix.html#244 <posix.html#244>`_

+

+   `EINPROGRESS`:idx:

+     `posix.html#245 <posix.html#245>`_

+

+   `EINTR`:idx:

+     `posix.html#246 <posix.html#246>`_

+

+   `EINVAL`:idx:

+     `posix.html#247 <posix.html#247>`_

+

+   `EInvalidField`:idx:

+     `system.html#149 <system.html#149>`_

+

+   `EInvalidIndex`:idx:

+     `system.html#148 <system.html#148>`_

+

+   `EInvalidObjectAssignment`:idx:

+     `system.html#153 <system.html#153>`_

+

+   `EInvalidObjectConversion`:idx:

+     `system.html#154 <system.html#154>`_

+

+   `EInvalidRegEx`:idx:

+     `regexprs.html#104 <regexprs.html#104>`_

+

+   `EInvalidValue`:idx:

+     `system.html#146 <system.html#146>`_

+

+   `EIO`:idx:

+     * `posix.html#248 <posix.html#248>`_

+     * `system.html#137 <system.html#137>`_

+

+   `EISCONN`:idx:

+     `posix.html#249 <posix.html#249>`_

+

+   `EISDIR`:idx:

+     `posix.html#250 <posix.html#250>`_

+

+   `ELOOP`:idx:

+     `posix.html#251 <posix.html#251>`_

+

+   `Embedded Nimrod Debugger`:idx:

+     `endb.html#101 <endb.html#101>`_

+

+   `EMFILE`:idx:

+     `posix.html#252 <posix.html#252>`_

+

+   `EMLINK`:idx:

+     `posix.html#253 <posix.html#253>`_

+

+   `EMSGSIZE`:idx:

+     `posix.html#254 <posix.html#254>`_

+

+   `EMULTIHOP`:idx:

+     `posix.html#255 <posix.html#255>`_

+

+   `ENAMETOOLONG`:idx:

+     `posix.html#256 <posix.html#256>`_

+

+   `encrypt`:idx:

+     `posix.html#976 <posix.html#976>`_

+

+   `ENDB`:idx:

+     `endb.html#102 <endb.html#102>`_

+

+   `endgrent`:idx:

+     `posix.html#838 <posix.html#838>`_

+

+   `EndOfFile`:idx:

+     * `system.html#489 <system.html#489>`_

+     * `lexbase.html#101 <lexbase.html#101>`_

+

+   `endpwent`:idx:

+     `posix.html#863 <posix.html#863>`_

+

+   `endsWith`:idx:

+     `strutils.html#138 <strutils.html#138>`_

+

+   `ENETDOWN`:idx:

+     `posix.html#257 <posix.html#257>`_

+

+   `ENETRESET`:idx:

+     `posix.html#258 <posix.html#258>`_

+

+   `ENETUNREACH`:idx:

+     `posix.html#259 <posix.html#259>`_

+

+   `ENFILE`:idx:

+     `posix.html#260 <posix.html#260>`_

+

+   `ENOBUFS`:idx:

+     `posix.html#261 <posix.html#261>`_

+

+   `ENODATA`:idx:

+     `posix.html#262 <posix.html#262>`_

+

+   `ENODEV`:idx:

+     `posix.html#263 <posix.html#263>`_

+

+   `ENOENT`:idx:

+     `posix.html#264 <posix.html#264>`_

+

+   `ENoExceptionToReraise`:idx:

+     * `manual.html#184 <manual.html#184>`_

+     * `system.html#152 <system.html#152>`_

+

+   `ENOEXEC`:idx:

+     `posix.html#265 <posix.html#265>`_

+

+   `ENOLCK`:idx:

+     `posix.html#266 <posix.html#266>`_

+

+   `ENOLINK`:idx:

+     `posix.html#267 <posix.html#267>`_

+

+   `ENOMEM`:idx:

+     `posix.html#268 <posix.html#268>`_

+

+   `ENOMSG`:idx:

+     `posix.html#269 <posix.html#269>`_

+

+   `ENOPROTOOPT`:idx:

+     `posix.html#270 <posix.html#270>`_

+

+   `ENOSPC`:idx:

+     `posix.html#271 <posix.html#271>`_

+

+   `ENOSR`:idx:

+     `posix.html#272 <posix.html#272>`_

+

+   `ENOSTR`:idx:

+     `posix.html#273 <posix.html#273>`_

+

+   `ENOSYS`:idx:

+     `posix.html#274 <posix.html#274>`_

+

+   `ENOTCONN`:idx:

+     `posix.html#275 <posix.html#275>`_

+

+   `ENOTDIR`:idx:

+     `posix.html#276 <posix.html#276>`_

+

+   `ENOTEMPTY`:idx:

+     `posix.html#277 <posix.html#277>`_

+

+   `ENOTSOCK`:idx:

+     `posix.html#278 <posix.html#278>`_

+

+   `ENOTSUP`:idx:

+     `posix.html#279 <posix.html#279>`_

+

+   `ENOTTY`:idx:

+     `posix.html#280 <posix.html#280>`_

+

+   `Enumeration`:idx:

+     `manual.html#148 <manual.html#148>`_

+

+   `enumeration`:idx:

+     `tut1.html#113 <tut1.html#113>`_

+

+   `ENXIO`:idx:

+     `posix.html#281 <posix.html#281>`_

+

+   `EOPNOTSUPP`:idx:

+     `posix.html#282 <posix.html#282>`_

+

+   `EOS`:idx:

+     `system.html#138 <system.html#138>`_

+

+   `EOutOfMemory`:idx:

+     `system.html#147 <system.html#147>`_

+

+   `EOutOfRange`:idx:

+     * `manual.html#145 <manual.html#145>`_

+     * `tut1.html#112 <tut1.html#112>`_

+     * `system.html#150 <system.html#150>`_

+

+   `EOVERFLOW`:idx:

+     `posix.html#283 <posix.html#283>`_

+

+   `EOverflow`:idx:

+     `system.html#142 <system.html#142>`_

+

+   `EPERM`:idx:

+     `posix.html#284 <posix.html#284>`_

+

+   `EPIPE`:idx:

+     `posix.html#285 <posix.html#285>`_

+

+   `EPROTO`:idx:

+     `posix.html#286 <posix.html#286>`_

+

+   `EPROTONOSUPPORT`:idx:

+     `posix.html#287 <posix.html#287>`_

+

+   `EPROTOTYPE`:idx:

+     `posix.html#288 <posix.html#288>`_

+

+   `equalMem`:idx:

+     `system.html#412 <system.html#412>`_

+

+   `ERA`:idx:

+     `posix.html#434 <posix.html#434>`_

+

+   `ERA_D_FMT`:idx:

+     `posix.html#435 <posix.html#435>`_

+

+   `ERA_D_T_FMT`:idx:

+     `posix.html#436 <posix.html#436>`_

+

+   `ERANGE`:idx:

+     `posix.html#289 <posix.html#289>`_

+

+   `ERA_T_FMT`:idx:

+     `posix.html#437 <posix.html#437>`_

+

+   `ERessourceExhausted`:idx:

+     `system.html#139 <system.html#139>`_

+

+   `EROFS`:idx:

+     `posix.html#290 <posix.html#290>`_

+

+   `errno`:idx:

+     `posix.html#219 <posix.html#219>`_

+

+   `error`:idx:

+     * `dialogs.html#104 <dialogs.html#104>`_

+     * `manual.html#221 <manual.html#221>`_

+     * `manual.html#224 <manual.html#224>`_

+

+   `errorStr`:idx:

+     `parsecfg.html#110 <parsecfg.html#110>`_

+

+   `escape`:idx:

+     * `manual.html#133 <manual.html#133>`_

+     * `strutils.html#143 <strutils.html#143>`_

+

+   `escape sequences`:idx:

+     `manual.html#120 <manual.html#120>`_

+

+   `ESPIPE`:idx:

+     `posix.html#291 <posix.html#291>`_

+

+   `ESRCH`:idx:

+     `posix.html#292 <posix.html#292>`_

+

+   `EStackOverflow`:idx:

+     `system.html#151 <system.html#151>`_

+

+   `ESTALE`:idx:

+     `posix.html#293 <posix.html#293>`_

+

+   `ESynch`:idx:

+     `system.html#135 <system.html#135>`_

+

+   `ESystem`:idx:

+     `system.html#136 <system.html#136>`_

+

+   `ETIME`:idx:

+     `posix.html#294 <posix.html#294>`_

+

+   `ETIMEDOUT`:idx:

+     `posix.html#295 <posix.html#295>`_

+

+   `ETXTBSY`:idx:

+     `posix.html#296 <posix.html#296>`_

+

+   `EWOULDBLOCK`:idx:

+     `posix.html#297 <posix.html#297>`_

+

+   `except`:idx:

+     `manual.html#187 <manual.html#187>`_

+

+   `exception handlers`:idx:

+     `manual.html#186 <manual.html#186>`_

+

+   `exceptions`:idx:

+     `tut2.html#107 <tut2.html#107>`_

+

+   `excl`:idx:

+     `system.html#168 <system.html#168>`_

+

+   `EXDEV`:idx:

+     `posix.html#298 <posix.html#298>`_

+

+   `execl`:idx:

+     `posix.html#977 <posix.html#977>`_

+

+   `execle`:idx:

+     `posix.html#978 <posix.html#978>`_

+

+   `execlp`:idx:

+     `posix.html#979 <posix.html#979>`_

+

+   `executeShellCommand`:idx:

+     `os.html#133 <os.html#133>`_

+

+   `execv`:idx:

+     `posix.html#980 <posix.html#980>`_

+

+   `execve`:idx:

+     `posix.html#981 <posix.html#981>`_

+

+   `execvp`:idx:

+     `posix.html#982 <posix.html#982>`_

+

+   `ExeExt`:idx:

+     `os.html#107 <os.html#107>`_

+

+   `existsDir`:idx:

+     `os.html#139 <os.html#139>`_

+

+   `existsEnv`:idx:

+     `os.html#144 <os.html#144>`_

+

+   `ExistsFile`:idx:

+     `os.html#117 <os.html#117>`_

+

+   `exp`:idx:

+     `math.html#114 <math.html#114>`_

+

+   `expandFilename`:idx:

+     `os.html#116 <os.html#116>`_

+

+   `exportc`:idx:

+     `nimrodc.html#102 <nimrodc.html#102>`_

+

+   `expression macros`:idx:

+     `tut2.html#113 <tut2.html#113>`_

+

+   `extractDir`:idx:

+     `os.html#126 <os.html#126>`_

+

+   `extractFileExt`:idx:

+     `os.html#128 <os.html#128>`_

+

+   `extractFilename`:idx:

+     `os.html#127 <os.html#127>`_

+

+   `extractFileTrunk`:idx:

+     `os.html#129 <os.html#129>`_

+

+   `ExtSep`:idx:

+     `os.html#109 <os.html#109>`_

+

+   `fastcall`:idx:

+     `manual.html#168 <manual.html#168>`_

+

+   `fatal`:idx:

+     `manual.html#225 <manual.html#225>`_

+

+   `fchdir`:idx:

+     `posix.html#984 <posix.html#984>`_

+

+   `fchmod`:idx:

+     `posix.html#1059 <posix.html#1059>`_

+

+   `fchown`:idx:

+     `posix.html#983 <posix.html#983>`_

+

+   `fcntl`:idx:

+     `posix.html#812 <posix.html#812>`_

+

+   `fdatasync`:idx:

+     `posix.html#985 <posix.html#985>`_

+

+   `FD_CLOEXEC`:idx:

+     `posix.html#309 <posix.html#309>`_

+

+   `FD_CLR`:idx:

+     `posix.html#1161 <posix.html#1161>`_

+

+   `FD_ISSET`:idx:

+     `posix.html#1162 <posix.html#1162>`_

+

+   `FD_SET`:idx:

+     `posix.html#1163 <posix.html#1163>`_

+

+   `FD_SETSIZE`:idx:

+     `posix.html#774 <posix.html#774>`_

+

+   `F_DUPFD`:idx:

+     `posix.html#299 <posix.html#299>`_

+

+   `FD_ZERO`:idx:

+     `posix.html#1164 <posix.html#1164>`_

+

+   `FE_ALL_EXCEPT`:idx:

+     `posix.html#337 <posix.html#337>`_

+

+   `feclearexcept`:idx:

+     `posix.html#816 <posix.html#816>`_

+

+   `FE_DFL_ENV`:idx:

+     `posix.html#342 <posix.html#342>`_

+

+   `FE_DIVBYZERO`:idx:

+     `posix.html#332 <posix.html#332>`_

+

+   `FE_DOWNWARD`:idx:

+     `posix.html#338 <posix.html#338>`_

+

+   `fegetenv`:idx:

+     `posix.html#823 <posix.html#823>`_

+

+   `fegetexceptflag`:idx:

+     `posix.html#817 <posix.html#817>`_

+

+   `fegetround`:idx:

+     `posix.html#821 <posix.html#821>`_

+

+   `feholdexcept`:idx:

+     `posix.html#824 <posix.html#824>`_

+

+   `FE_INEXACT`:idx:

+     `posix.html#333 <posix.html#333>`_

+

+   `FE_INVALID`:idx:

+     `posix.html#334 <posix.html#334>`_

+

+   `FE_OVERFLOW`:idx:

+     `posix.html#335 <posix.html#335>`_

+

+   `feraiseexcept`:idx:

+     `posix.html#818 <posix.html#818>`_

+

+   `fesetenv`:idx:

+     `posix.html#825 <posix.html#825>`_

+

+   `fesetexceptflag`:idx:

+     `posix.html#819 <posix.html#819>`_

+

+   `fesetround`:idx:

+     `posix.html#822 <posix.html#822>`_

+

+   `fetestexcept`:idx:

+     `posix.html#820 <posix.html#820>`_

+

+   `FE_TONEAREST`:idx:

+     `posix.html#339 <posix.html#339>`_

+

+   `FE_TOWARDZERO`:idx:

+     `posix.html#340 <posix.html#340>`_

+

+   `FE_UNDERFLOW`:idx:

+     `posix.html#336 <posix.html#336>`_

+

+   `feupdateenv`:idx:

+     `posix.html#826 <posix.html#826>`_

+

+   `FE_UPWARD`:idx:

+     `posix.html#341 <posix.html#341>`_

+

+   `F_GETFD`:idx:

+     `posix.html#300 <posix.html#300>`_

+

+   `F_GETFL`:idx:

+     `posix.html#302 <posix.html#302>`_

+

+   `F_GETLK`:idx:

+     `posix.html#304 <posix.html#304>`_

+

+   `F_GETOWN`:idx:

+     `posix.html#307 <posix.html#307>`_

+

+   `fileHandle`:idx:

+     `system.html#513 <system.html#513>`_

+

+   `fileNewer`:idx:

+     `os.html#141 <os.html#141>`_

+

+   `FileSystemCaseSensitive`:idx:

+     `os.html#106 <os.html#106>`_

+

+   `finally`:idx:

+     `manual.html#188 <manual.html#188>`_

+

+   `find`:idx:

+     * `system.html#459 <system.html#459>`_

+     * `regexprs.html#109 <regexprs.html#109>`_

+     * `regexprs.html#110 <regexprs.html#110>`_

+

+   `findChars`:idx:

+     `strutils.html#114 <strutils.html#114>`_

+

+   `findSubStr`:idx:

+     * `strutils.html#112 <strutils.html#112>`_

+     * `strutils.html#113 <strutils.html#113>`_

+

+   `float`:idx:

+     `system.html#106 <system.html#106>`_

+

+   `float32`:idx:

+     `system.html#107 <system.html#107>`_

+

+   `float64`:idx:

+     `system.html#108 <system.html#108>`_

+

+   `F_LOCK`:idx:

+     `posix.html#496 <posix.html#496>`_

+

+   `FlushFile`:idx:

+     `system.html#491 <system.html#491>`_

+

+   `fmtmsg`:idx:

+     `posix.html#827 <posix.html#827>`_

+

+   `fnmatch`:idx:

+     `posix.html#828 <posix.html#828>`_

+

+   `FNM_NOESCAPE`:idx:

+     `posix.html#365 <posix.html#365>`_

+

+   `FNM_NOMATCH`:idx:

+     `posix.html#362 <posix.html#362>`_

+

+   `FNM_NOSYS`:idx:

+     `posix.html#366 <posix.html#366>`_

+

+   `FNM_PATHNAME`:idx:

+     `posix.html#363 <posix.html#363>`_

+

+   `FNM_PERIOD`:idx:

+     `posix.html#364 <posix.html#364>`_

+

+   `F_OK`:idx:

+     `posix.html#478 <posix.html#478>`_

+

+   `for`:idx:

+     * `manual.html#203 <manual.html#203>`_

+     * `tut1.html#105 <tut1.html#105>`_

+

+   `fork`:idx:

+     `posix.html#986 <posix.html#986>`_

+

+   `form feed`:idx:

+     `manual.html#124 <manual.html#124>`_

+

+   `forward`:idx:

+     `manual.html#200 <manual.html#200>`_

+

+   `fpathconf`:idx:

+     `posix.html#987 <posix.html#987>`_

+

+   `F_RDLCK`:idx:

+     `posix.html#310 <posix.html#310>`_

+

+   `frexp`:idx:

+     `math.html#115 <math.html#115>`_

+

+   `F_SETFD`:idx:

+     `posix.html#301 <posix.html#301>`_

+

+   `F_SETFL`:idx:

+     `posix.html#303 <posix.html#303>`_

+

+   `F_SETLK`:idx:

+     `posix.html#305 <posix.html#305>`_

+

+   `F_SETLKW`:idx:

+     `posix.html#306 <posix.html#306>`_

+

+   `F_SETOWN`:idx:

+     `posix.html#308 <posix.html#308>`_

+

+   `fstat`:idx:

+     `posix.html#1060 <posix.html#1060>`_

+

+   `fstatvfs`:idx:

+     `posix.html#1057 <posix.html#1057>`_

+

+   `fsync`:idx:

+     `posix.html#988 <posix.html#988>`_

+

+   `F_TEST`:idx:

+     `posix.html#497 <posix.html#497>`_

+

+   `F_TLOCK`:idx:

+     `posix.html#498 <posix.html#498>`_

+

+   `ftok`:idx:

+     `posix.html#1055 <posix.html#1055>`_

+

+   `ftruncate`:idx:

+     `posix.html#989 <posix.html#989>`_

+

+   `ftw`:idx:

+     `posix.html#829 <posix.html#829>`_

+

+   `FTW_CHDIR`:idx:

+     `posix.html#377 <posix.html#377>`_

+

+   `FTW_D`:idx:

+     `posix.html#368 <posix.html#368>`_

+

+   `FTW_DEPTH`:idx:

+     `posix.html#376 <posix.html#376>`_

+

+   `FTW_DNR`:idx:

+     `posix.html#369 <posix.html#369>`_

+

+   `FTW_DP`:idx:

+     `posix.html#370 <posix.html#370>`_

+

+   `FTW_F`:idx:

+     `posix.html#367 <posix.html#367>`_

+

+   `FTW_MOUNT`:idx:

+     `posix.html#375 <posix.html#375>`_

+

+   `FTW_NS`:idx:

+     `posix.html#371 <posix.html#371>`_

+

+   `FTW_PHYS`:idx:

+     `posix.html#374 <posix.html#374>`_

+

+   `FTW_SL`:idx:

+     `posix.html#372 <posix.html#372>`_

+

+   `FTW_SLN`:idx:

+     `posix.html#373 <posix.html#373>`_

+

+   `F_ULOCK`:idx:

+     `posix.html#499 <posix.html#499>`_

+

+   `functional`:idx:

+     * `manual.html#162 <manual.html#162>`_

+     * `tut1.html#124 <tut1.html#124>`_

+

+   `F_UNLCK`:idx:

+     `posix.html#311 <posix.html#311>`_

+

+   `funtions`:idx:

+     `manual.html#198 <manual.html#198>`_

+

+   `F_WRLCK`:idx:

+     `posix.html#312 <posix.html#312>`_

+

+   `GC_disable`:idx:

+     `system.html#460 <system.html#460>`_

+

+   `GC_disableMarkAndSweep`:idx:

+     `system.html#466 <system.html#466>`_

+

+   `GC_enable`:idx:

+     `system.html#461 <system.html#461>`_

+

+   `GC_enableMarkAndSweep`:idx:

+     `system.html#465 <system.html#465>`_

+

+   `GC_fullCollect`:idx:

+     `system.html#462 <system.html#462>`_

+

+   `GC_getStatistics`:idx:

+     `system.html#467 <system.html#467>`_

+

+   `GC_ref`:idx:

+     * `system.html#468 <system.html#468>`_

+     * `system.html#469 <system.html#469>`_

+     * `system.html#470 <system.html#470>`_

+

+   `GC_setStrategy`:idx:

+     `system.html#464 <system.html#464>`_

+

+   `GC_unref`:idx:

+     * `system.html#471 <system.html#471>`_

+     * `system.html#472 <system.html#472>`_

+     * `system.html#473 <system.html#473>`_

+

+   `generic character types`:idx:

+     `regexprs.html#102 <regexprs.html#102>`_

+

+   `Generics`:idx:

+     * `manual.html#207 <manual.html#207>`_

+     * `tut2.html#109 <tut2.html#109>`_

+

+   `getApplicationDir`:idx:

+     `os.html#110 <os.html#110>`_

+

+   `getApplicationFilename`:idx:

+     `os.html#111 <os.html#111>`_

+

+   `getClockStr`:idx:

+     `times.html#112 <times.html#112>`_

+

+   `getColNumber`:idx:

+     `lexbase.html#107 <lexbase.html#107>`_

+

+   `getColumn`:idx:

+     `parsecfg.html#107 <parsecfg.html#107>`_

+

+   `getConfigDir`:idx:

+     `os.html#115 <os.html#115>`_

+

+   `getcontext`:idx:

+     `posix.html#1188 <posix.html#1188>`_

+

+   `get_crc_table`:idx:

+     `zlib.html#186 <zlib.html#186>`_

+

+   `getCurrentDir`:idx:

+     `os.html#112 <os.html#112>`_

+

+   `getCurrentExceptionMsg`:idx:

+     `system.html#431 <system.html#431>`_

+

+   `getCurrentLine`:idx:

+     `lexbase.html#106 <lexbase.html#106>`_

+

+   `getcwd`:idx:

+     `posix.html#990 <posix.html#990>`_

+

+   `getdate`:idx:

+     `posix.html#1103 <posix.html#1103>`_

+

+   `getDateStr`:idx:

+     `times.html#111 <times.html#111>`_

+

+   `getegid`:idx:

+     `posix.html#991 <posix.html#991>`_

+

+   `getEnv`:idx:

+     `os.html#143 <os.html#143>`_

+

+   `geteuid`:idx:

+     `posix.html#992 <posix.html#992>`_

+

+   `getFilename`:idx:

+     `parsecfg.html#109 <parsecfg.html#109>`_

+

+   `getFilePos`:idx:

+     `system.html#511 <system.html#511>`_

+

+   `getFileSize`:idx:

+     `system.html#503 <system.html#503>`_

+

+   `getFreeMem`:idx:

+     `system.html#437 <system.html#437>`_

+

+   `getgid`:idx:

+     `posix.html#993 <posix.html#993>`_

+

+   `getGMTime`:idx:

+     `times.html#107 <times.html#107>`_

+

+   `getgrent`:idx:

+     `posix.html#837 <posix.html#837>`_

+

+   `getgrgid`:idx:

+     `posix.html#833 <posix.html#833>`_

+

+   `getgrgid_r`:idx:

+     `posix.html#835 <posix.html#835>`_

+

+   `getgrnam`:idx:

+     `posix.html#834 <posix.html#834>`_

+

+   `getgrnam_r`:idx:

+     `posix.html#836 <posix.html#836>`_

+

+   `getgroups`:idx:

+     `posix.html#994 <posix.html#994>`_

+

+   `getHomeDir`:idx:

+     `os.html#114 <os.html#114>`_

+

+   `gethostid`:idx:

+     `posix.html#995 <posix.html#995>`_

+

+   `gethostname`:idx:

+     `posix.html#996 <posix.html#996>`_

+

+   `getLastModificationTime`:idx:

+     `os.html#140 <os.html#140>`_

+

+   `getLine`:idx:

+     `parsecfg.html#108 <parsecfg.html#108>`_

+

+   `getLocalTime`:idx:

+     `times.html#106 <times.html#106>`_

+

+   `getlogin`:idx:

+     `posix.html#997 <posix.html#997>`_

+

+   `getlogin_r`:idx:

+     `posix.html#998 <posix.html#998>`_

+

+   `getOccupiedMem`:idx:

+     `system.html#436 <system.html#436>`_

+

+   `getopt`:idx:

+     * `posix.html#999 <posix.html#999>`_

+     * `parseopt.html#106 <parseopt.html#106>`_

+

+   `getpgid`:idx:

+     `posix.html#1000 <posix.html#1000>`_

+

+   `getpgrp`:idx:

+     `posix.html#1001 <posix.html#1001>`_

+

+   `getpid`:idx:

+     `posix.html#1002 <posix.html#1002>`_

+

+   `getppid`:idx:

+     `posix.html#1003 <posix.html#1003>`_

+

+   `getpwent`:idx:

+     `posix.html#864 <posix.html#864>`_

+

+   `getpwnam`:idx:

+     `posix.html#859 <posix.html#859>`_

+

+   `getpwnam_r`:idx:

+     `posix.html#861 <posix.html#861>`_

+

+   `getpwuid`:idx:

+     `posix.html#860 <posix.html#860>`_

+

+   `getpwuid_r`:idx:

+     `posix.html#862 <posix.html#862>`_

+

+   `getRefcount`:idx:

+     `system.html#430 <system.html#430>`_

+

+   `getRestOfCommandLine`:idx:

+     `parseopt.html#105 <parseopt.html#105>`_

+

+   `getsid`:idx:

+     `posix.html#1004 <posix.html#1004>`_

+

+   `getStartMilsecs`:idx:

+     `times.html#116 <times.html#116>`_

+

+   `getStream`:idx:

+     `zipfiles.html#109 <zipfiles.html#109>`_

+

+   `getTime`:idx:

+     `times.html#105 <times.html#105>`_

+

+   `getTotalMem`:idx:

+     `system.html#438 <system.html#438>`_

+

+   `getuid`:idx:

+     `posix.html#1005 <posix.html#1005>`_

+

+   `getwd`:idx:

+     `posix.html#1006 <posix.html#1006>`_

+

+   `glob`:idx:

+     `posix.html#831 <posix.html#831>`_

+

+   `GLOB_ABORTED`:idx:

+     `posix.html#385 <posix.html#385>`_

+

+   `GLOB_APPEND`:idx:

+     `posix.html#378 <posix.html#378>`_

+

+   `GLOB_DOOFFS`:idx:

+     `posix.html#379 <posix.html#379>`_

+

+   `GLOB_ERR`:idx:

+     `posix.html#380 <posix.html#380>`_

+

+   `globfree`:idx:

+     `posix.html#832 <posix.html#832>`_

+

+   `GLOB_MARK`:idx:

+     `posix.html#381 <posix.html#381>`_

+

+   `GLOB_NOCHECK`:idx:

+     `posix.html#382 <posix.html#382>`_

+

+   `GLOB_NOESCAPE`:idx:

+     `posix.html#383 <posix.html#383>`_

+

+   `GLOB_NOMATCH`:idx:

+     `posix.html#386 <posix.html#386>`_

+

+   `GLOB_NOSORT`:idx:

+     `posix.html#384 <posix.html#384>`_

+

+   `GLOB_NOSPACE`:idx:

+     `posix.html#387 <posix.html#387>`_

+

+   `GLOB_NOSYS`:idx:

+     `posix.html#388 <posix.html#388>`_

+

+   `gmtime`:idx:

+     `posix.html#1104 <posix.html#1104>`_

+

+   `gmtime_r`:idx:

+     `posix.html#1105 <posix.html#1105>`_

+

+   `gzclose`:idx:

+     `zlib.html#172 <zlib.html#172>`_

+

+   `gzdopen`:idx:

+     `zlib.html#158 <zlib.html#158>`_

+

+   `gzeof`:idx:

+     `zlib.html#171 <zlib.html#171>`_

+

+   `gzerror`:idx:

+     `zlib.html#173 <zlib.html#173>`_

+

+   `gzFile`:idx:

+     `zlib.html#115 <zlib.html#115>`_

+

+   `gzflush`:idx:

+     `zlib.html#167 <zlib.html#167>`_

+

+   `gzgetc`:idx:

+     `zlib.html#166 <zlib.html#166>`_

+

+   `gzgets`:idx:

+     `zlib.html#164 <zlib.html#164>`_

+

+   `gzopen`:idx:

+     `zlib.html#157 <zlib.html#157>`_

+

+   `gzprintf`:idx:

+     `zlib.html#162 <zlib.html#162>`_

+

+   `gzputc`:idx:

+     `zlib.html#165 <zlib.html#165>`_

+

+   `gzputs`:idx:

+     `zlib.html#163 <zlib.html#163>`_

+

+   `gzread`:idx:

+     `zlib.html#160 <zlib.html#160>`_

+

+   `gzrewind`:idx:

+     `zlib.html#169 <zlib.html#169>`_

+

+   `gzseek`:idx:

+     `zlib.html#168 <zlib.html#168>`_

+

+   `gzsetparams`:idx:

+     `zlib.html#159 <zlib.html#159>`_

+

+   `gztell`:idx:

+     `zlib.html#170 <zlib.html#170>`_

+

+   `gzwrite`:idx:

+     `zlib.html#161 <zlib.html#161>`_

+

+   `HandleCR`:idx:

+     `lexbase.html#108 <lexbase.html#108>`_

+

+   `HandleLF`:idx:

+     `lexbase.html#109 <lexbase.html#109>`_

+

+   `hash`:idx:

+     * `hashes.html#103 <hashes.html#103>`_

+     * `hashes.html#104 <hashes.html#104>`_

+     * `hashes.html#105 <hashes.html#105>`_

+     * `hashes.html#106 <hashes.html#106>`_

+     * `hashes.html#107 <hashes.html#107>`_

+

+   `hashData`:idx:

+     `hashes.html#102 <hashes.html#102>`_

+

+   `hashIgnoreCase`:idx:

+     `hashes.html#109 <hashes.html#109>`_

+

+   `hashIgnoreStyle`:idx:

+     `hashes.html#108 <hashes.html#108>`_

+

+   `hasKey`:idx:

+     `strtabs.html#108 <strtabs.html#108>`_

+

+   `header`:idx:

+     `nimrodc.html#105 <nimrodc.html#105>`_

+

+   `high`:idx:

+     `system.html#121 <system.html#121>`_

+

+   `hint`:idx:

+     * `manual.html#219 <manual.html#219>`_

+     * `manual.html#227 <manual.html#227>`_

+

+   `hostCPU`:idx:

+     `system.html#399 <system.html#399>`_

+

+   `hostOS`:idx:

+     `system.html#398 <system.html#398>`_

+

+   `htonl`:idx:

+     `posix.html#792 <posix.html#792>`_

+

+   `htons`:idx:

+     `posix.html#793 <posix.html#793>`_

+

+   `hypot`:idx:

+     `math.html#123 <math.html#123>`_

+

+   `iconv`:idx:

+     `posix.html#841 <posix.html#841>`_

+

+   `iconv_close`:idx:

+     `posix.html#842 <posix.html#842>`_

+

+   `iconv_open`:idx:

+     `posix.html#840 <posix.html#840>`_

+

+   `identifier`:idx:

+     `manual.html#105 <manual.html#105>`_

+

+   `Identifiers`:idx:

+     `manual.html#116 <manual.html#116>`_

+

+   `if`:idx:

+     `manual.html#180 <manual.html#180>`_

+

+   `implicit block`:idx:

+     `manual.html#205 <manual.html#205>`_

+

+   `import`:idx:

+     * `manual.html#215 <manual.html#215>`_

+     * `tut1.html#128 <tut1.html#128>`_

+

+   `importc`:idx:

+     `nimrodc.html#101 <nimrodc.html#101>`_

+

+   `in`:idx:

+     `system.html#355 <system.html#355>`_

+

+   `inc`:idx:

+     `system.html#159 <system.html#159>`_

+

+   `incl`:idx:

+     `system.html#167 <system.html#167>`_

+

+   `include`:idx:

+     `tut1.html#129 <tut1.html#129>`_

+

+   `indentation sensitive`:idx:

+     `manual.html#113 <manual.html#113>`_

+

+   `inet_addr`:idx:

+     `posix.html#796 <posix.html#796>`_

+

+   `inet_ntoa`:idx:

+     `posix.html#797 <posix.html#797>`_

+

+   `inet_ntop`:idx:

+     `posix.html#798 <posix.html#798>`_

+

+   `inet_pton`:idx:

+     `posix.html#799 <posix.html#799>`_

+

+   `inf`:idx:

+     `system.html#432 <system.html#432>`_

+

+   `inflate`:idx:

+     `zlib.html#145 <zlib.html#145>`_

+

+   `inflateEnd`:idx:

+     `zlib.html#146 <zlib.html#146>`_

+

+   `inflateInit`:idx:

+     `zlib.html#179 <zlib.html#179>`_

+

+   `inflateInit2`:idx:

+     `zlib.html#183 <zlib.html#183>`_

+

+   `inflateInit2u`:idx:

+     `zlib.html#181 <zlib.html#181>`_

+

+   `inflateInitu`:idx:

+     `zlib.html#177 <zlib.html#177>`_

+

+   `inflateReset`:idx:

+     `zlib.html#153 <zlib.html#153>`_

+

+   `inflateSetDictionary`:idx:

+     `zlib.html#151 <zlib.html#151>`_

+

+   `inflateSync`:idx:

+     `zlib.html#152 <zlib.html#152>`_

+

+   `inflateSyncPoint`:idx:

+     `zlib.html#185 <zlib.html#185>`_

+

+   `info`:idx:

+     `dialogs.html#102 <dialogs.html#102>`_

+

+   `information hiding`:idx:

+     * `manual.html#213 <manual.html#213>`_

+     * `tut1.html#126 <tut1.html#126>`_

+

+   `init`:idx:

+     `parseopt.html#103 <parseopt.html#103>`_

+

+   `inline`:idx:

+     `manual.html#167 <manual.html#167>`_

+

+   `int`:idx:

+     `system.html#101 <system.html#101>`_

+

+   `int16`:idx:

+     `system.html#103 <system.html#103>`_

+

+   `int32`:idx:

+     `system.html#104 <system.html#104>`_

+

+   `int64`:idx:

+     `system.html#105 <system.html#105>`_

+

+   `int8`:idx:

+     `system.html#102 <system.html#102>`_

+

+   `intToStr`:idx:

+     `strutils.html#129 <strutils.html#129>`_

+

+   `IPC_CREAT`:idx:

+     `posix.html#642 <posix.html#642>`_

+

+   `IPC_EXCL`:idx:

+     `posix.html#643 <posix.html#643>`_

+

+   `IPC_NOWAIT`:idx:

+     `posix.html#644 <posix.html#644>`_

+

+   `IPC_PRIVATE`:idx:

+     `posix.html#645 <posix.html#645>`_

+

+   `IPC_RMID`:idx:

+     `posix.html#646 <posix.html#646>`_

+

+   `IPC_SET`:idx:

+     `posix.html#647 <posix.html#647>`_

+

+   `IPC_STAT`:idx:

+     `posix.html#648 <posix.html#648>`_

+

+   `is`:idx:

+     `system.html#357 <system.html#357>`_

+

+   `isatty`:idx:

+     `posix.html#1007 <posix.html#1007>`_

+

+   `isMainModule`:idx:

+     `system.html#390 <system.html#390>`_

+

+   `isNil`:idx:

+     * `system.html#447 <system.html#447>`_

+     * `system.html#448 <system.html#448>`_

+     * `system.html#449 <system.html#449>`_

+     * `system.html#450 <system.html#450>`_

+     * `system.html#451 <system.html#451>`_

+     * `system.html#452 <system.html#452>`_

+

+   `is_not`:idx:

+     `system.html#358 <system.html#358>`_

+

+   `isPowerOfTwo`:idx:

+     `math.html#105 <math.html#105>`_

+

+   `items`:idx:

+     * `system.html#441 <system.html#441>`_

+     * `system.html#442 <system.html#442>`_

+     * `system.html#443 <system.html#443>`_

+     * `system.html#444 <system.html#444>`_

+     * `system.html#445 <system.html#445>`_

+     * `system.html#446 <system.html#446>`_

+

+   `iterator`:idx:

+     `manual.html#204 <manual.html#204>`_

+

+   `iterOverEnvironment`:idx:

+     `os.html#150 <os.html#150>`_

+

+   `JavaScript`:idx:

+     `nimrodc.html#116 <nimrodc.html#116>`_

+

+   `JoinPath`:idx:

+     * `os.html#118 <os.html#118>`_

+     * `os.html#120 <os.html#120>`_

+

+   `keywords`:idx:

+     `manual.html#117 <manual.html#117>`_

+

+   `kill`:idx:

+     `posix.html#1123 <posix.html#1123>`_

+

+   `killpg`:idx:

+     `posix.html#1124 <posix.html#1124>`_

+

+   `l-values`:idx:

+     `manual.html#107 <manual.html#107>`_

+

+   `lambda`:idx:

+     `tut2.html#106 <tut2.html#106>`_

+

+   `LC_ALL`:idx:

+     `posix.html#444 <posix.html#444>`_

+

+   `LC_COLLATE`:idx:

+     `posix.html#445 <posix.html#445>`_

+

+   `LC_CTYPE`:idx:

+     `posix.html#446 <posix.html#446>`_

+

+   `lchown`:idx:

+     `posix.html#1008 <posix.html#1008>`_

+

+   `LC_MESSAGES`:idx:

+     `posix.html#447 <posix.html#447>`_

+

+   `LC_MONETARY`:idx:

+     `posix.html#448 <posix.html#448>`_

+

+   `LC_NUMERIC`:idx:

+     `posix.html#449 <posix.html#449>`_

+

+   `LC_TIME`:idx:

+     `posix.html#450 <posix.html#450>`_

+

+   `len`:idx:

+     * `system.html#162 <system.html#162>`_

+     * `system.html#163 <system.html#163>`_

+     * `system.html#164 <system.html#164>`_

+     * `system.html#165 <system.html#165>`_

+     * `system.html#166 <system.html#166>`_

+     * `strtabs.html#109 <strtabs.html#109>`_

+

+   `line feed`:idx:

+     `manual.html#123 <manual.html#123>`_

+

+   `line_dir`:idx:

+     `nimrodc.html#107 <nimrodc.html#107>`_

+

+   `lines`:idx:

+     `system.html#512 <system.html#512>`_

+

+   `line_trace`:idx:

+     `nimrodc.html#109 <nimrodc.html#109>`_

+

+   `link`:idx:

+     `posix.html#1009 <posix.html#1009>`_

+

+   `lio_listio`:idx:

+     `posix.html#791 <posix.html#791>`_

+

+   `LIO_NOP`:idx:

+     `posix.html#210 <posix.html#210>`_

+

+   `LIO_NOWAIT`:idx:

+     `posix.html#211 <posix.html#211>`_

+

+   `LIO_READ`:idx:

+     `posix.html#212 <posix.html#212>`_

+

+   `LIO_WAIT`:idx:

+     `posix.html#213 <posix.html#213>`_

+

+   `LIO_WRITE`:idx:

+     `posix.html#214 <posix.html#214>`_

+

+   `Literal strings`:idx:

+     `manual.html#119 <manual.html#119>`_

+

+   `ln`:idx:

+     `math.html#111 <math.html#111>`_

+

+   `local type inference`:idx:

+     `tut1.html#101 <tut1.html#101>`_

+

+   `localeconv`:idx:

+     `posix.html#846 <posix.html#846>`_

+

+   `localtime`:idx:

+     `posix.html#1106 <posix.html#1106>`_

+

+   `localtime_r`:idx:

+     `posix.html#1107 <posix.html#1107>`_

+

+   `locations`:idx:

+     `manual.html#101 <manual.html#101>`_

+

+   `lockf`:idx:

+     `posix.html#1010 <posix.html#1010>`_

+

+   `log10`:idx:

+     `math.html#112 <math.html#112>`_

+

+   `log2`:idx:

+     `math.html#113 <math.html#113>`_

+

+   `low`:idx:

+     `system.html#122 <system.html#122>`_

+

+   `lseek`:idx:

+     `posix.html#1011 <posix.html#1011>`_

+

+   `lstat`:idx:

+     `posix.html#1061 <posix.html#1061>`_

+

+   `Macros`:idx:

+     * `manual.html#210 <manual.html#210>`_

+     * `tut2.html#111 <tut2.html#111>`_

+

+   `makecontext`:idx:

+     `posix.html#1189 <posix.html#1189>`_

+

+   `MAP_FAILED`:idx:

+     `posix.html#686 <posix.html#686>`_

+

+   `MAP_FIXED`:idx:

+     `posix.html#680 <posix.html#680>`_

+

+   `MAP_PRIVATE`:idx:

+     `posix.html#679 <posix.html#679>`_

+

+   `MAP_SHARED`:idx:

+     `posix.html#678 <posix.html#678>`_

+

+   `match`:idx:

+     * `regexprs.html#106 <regexprs.html#106>`_

+     * `regexprs.html#107 <regexprs.html#107>`_

+

+   `matchLen`:idx:

+     `regexprs.html#108 <regexprs.html#108>`_

+

+   `math`:idx:

+     `nimrodc.html#118 <nimrodc.html#118>`_

+

+   `max`:idx:

+     * `system.html#271 <system.html#271>`_

+     * `system.html#272 <system.html#272>`_

+     * `system.html#273 <system.html#273>`_

+     * `system.html#274 <system.html#274>`_

+     * `system.html#275 <system.html#275>`_

+     * `system.html#322 <system.html#322>`_

+

+   `MaxSubpatterns`:idx:

+     `regexprs.html#105 <regexprs.html#105>`_

+

+   `MCL_CURRENT`:idx:

+     `posix.html#684 <posix.html#684>`_

+

+   `MCL_FUTURE`:idx:

+     `posix.html#685 <posix.html#685>`_

+

+   `method call syntax`:idx:

+     `tut2.html#104 <tut2.html#104>`_

+

+   `methods`:idx:

+     `manual.html#197 <manual.html#197>`_

+

+   `min`:idx:

+     * `system.html#266 <system.html#266>`_

+     * `system.html#267 <system.html#267>`_

+     * `system.html#268 <system.html#268>`_

+     * `system.html#269 <system.html#269>`_

+     * `system.html#270 <system.html#270>`_

+     * `system.html#321 <system.html#321>`_

+

+   `MINSIGSTKSZ`:idx:

+     `posix.html#766 <posix.html#766>`_

+

+   `mkdir`:idx:

+     `posix.html#1062 <posix.html#1062>`_

+

+   `mkfifo`:idx:

+     `posix.html#1063 <posix.html#1063>`_

+

+   `mknod`:idx:

+     `posix.html#1064 <posix.html#1064>`_

+

+   `mktime`:idx:

+     `posix.html#1108 <posix.html#1108>`_

+

+   `mlock`:idx:

+     `posix.html#1078 <posix.html#1078>`_

+

+   `mlockall`:idx:

+     `posix.html#1079 <posix.html#1079>`_

+

+   `mmap`:idx:

+     `posix.html#1080 <posix.html#1080>`_

+

+   `MM_APPL`:idx:

+     `posix.html#346 <posix.html#346>`_

+

+   `MM_CONSOLE`:idx:

+     `posix.html#357 <posix.html#357>`_

+

+   `MM_ERROR`:idx:

+     `posix.html#352 <posix.html#352>`_

+

+   `MM_FIRM`:idx:

+     `posix.html#345 <posix.html#345>`_

+

+   `MM_HALT`:idx:

+     `posix.html#351 <posix.html#351>`_

+

+   `MM_HARD`:idx:

+     `posix.html#343 <posix.html#343>`_

+

+   `MM_INFO`:idx:

+     `posix.html#354 <posix.html#354>`_

+

+   `MM_NOCON`:idx:

+     `posix.html#361 <posix.html#361>`_

+

+   `MM_NOMSG`:idx:

+     `posix.html#360 <posix.html#360>`_

+

+   `MM_NOSEV`:idx:

+     `posix.html#355 <posix.html#355>`_

+

+   `MM_NOTOK`:idx:

+     `posix.html#359 <posix.html#359>`_

+

+   `MM_NRECOV`:idx:

+     `posix.html#350 <posix.html#350>`_

+

+   `MM_NULLACT`:idx:

+     `posix.html#125 <posix.html#125>`_

+

+   `MM_NULLLBL`:idx:

+     `posix.html#121 <posix.html#121>`_

+

+   `MM_NULLMC`:idx:

+     `posix.html#123 <posix.html#123>`_

+

+   `MM_NULLSEV`:idx:

+     `posix.html#122 <posix.html#122>`_

+

+   `MM_NULLTAG`:idx:

+     `posix.html#126 <posix.html#126>`_

+

+   `MM_NULLTXT`:idx:

+     `posix.html#124 <posix.html#124>`_

+

+   `MM_OK`:idx:

+     `posix.html#358 <posix.html#358>`_

+

+   `MM_OPSYS`:idx:

+     `posix.html#348 <posix.html#348>`_

+

+   `MM_PRINT`:idx:

+     `posix.html#356 <posix.html#356>`_

+

+   `MM_RECOVER`:idx:

+     `posix.html#349 <posix.html#349>`_

+

+   `MM_SOFT`:idx:

+     `posix.html#344 <posix.html#344>`_

+

+   `MM_UTIL`:idx:

+     `posix.html#347 <posix.html#347>`_

+

+   `MM_WARNING`:idx:

+     `posix.html#353 <posix.html#353>`_

+

+   `mod`:idx:

+     * `system.html#216 <system.html#216>`_

+     * `system.html#217 <system.html#217>`_

+     * `system.html#218 <system.html#218>`_

+     * `system.html#219 <system.html#219>`_

+     * `system.html#220 <system.html#220>`_

+

+   `module`:idx:

+     * `manual.html#212 <manual.html#212>`_

+     * `tut1.html#125 <tut1.html#125>`_

+

+   `MON_1`:idx:

+     `posix.html#410 <posix.html#410>`_

+

+   `MON_10`:idx:

+     `posix.html#419 <posix.html#419>`_

+

+   `MON_11`:idx:

+     `posix.html#420 <posix.html#420>`_

+

+   `MON_12`:idx:

+     `posix.html#421 <posix.html#421>`_

+

+   `MON_2`:idx:

+     `posix.html#411 <posix.html#411>`_

+

+   `MON_3`:idx:

+     `posix.html#412 <posix.html#412>`_

+

+   `MON_4`:idx:

+     `posix.html#413 <posix.html#413>`_

+

+   `MON_5`:idx:

+     `posix.html#414 <posix.html#414>`_

+

+   `MON_6`:idx:

+     `posix.html#415 <posix.html#415>`_

+

+   `MON_7`:idx:

+     `posix.html#416 <posix.html#416>`_

+

+   `MON_8`:idx:

+     `posix.html#417 <posix.html#417>`_

+

+   `MON_9`:idx:

+     `posix.html#418 <posix.html#418>`_

+

+   `moveFile`:idx:

+     `os.html#135 <os.html#135>`_

+

+   `moveMem`:idx:

+     `system.html#411 <system.html#411>`_

+

+   `mprotect`:idx:

+     `posix.html#1081 <posix.html#1081>`_

+

+   `mq_close`:idx:

+     `posix.html#849 <posix.html#849>`_

+

+   `mq_getattr`:idx:

+     `posix.html#850 <posix.html#850>`_

+

+   `mq_notify`:idx:

+     `posix.html#851 <posix.html#851>`_

+

+   `mq_open`:idx:

+     `posix.html#852 <posix.html#852>`_

+

+   `mq_receive`:idx:

+     `posix.html#853 <posix.html#853>`_

+

+   `mq_send`:idx:

+     `posix.html#854 <posix.html#854>`_

+

+   `mq_setattr`:idx:

+     `posix.html#855 <posix.html#855>`_

+

+   `mq_timedreceive`:idx:

+     `posix.html#856 <posix.html#856>`_

+

+   `mq_timedsend`:idx:

+     `posix.html#857 <posix.html#857>`_

+

+   `mq_unlink`:idx:

+     `posix.html#858 <posix.html#858>`_

+

+   `MS_ASYNC`:idx:

+     `posix.html#681 <posix.html#681>`_

+

+   `MS_INVALIDATE`:idx:

+     `posix.html#683 <posix.html#683>`_

+

+   `MS_SYNC`:idx:

+     `posix.html#682 <posix.html#682>`_

+

+   `msync`:idx:

+     `posix.html#1082 <posix.html#1082>`_

+

+   `munlock`:idx:

+     `posix.html#1083 <posix.html#1083>`_

+

+   `munlockall`:idx:

+     `posix.html#1084 <posix.html#1084>`_

+

+   `munmap`:idx:

+     `posix.html#1085 <posix.html#1085>`_

+

+   `nan`:idx:

+     `system.html#434 <system.html#434>`_

+

+   `nanosleep`:idx:

+     `posix.html#1109 <posix.html#1109>`_

+

+   `Natural`:idx:

+     `system.html#129 <system.html#129>`_

+

+   `neginf`:idx:

+     `system.html#433 <system.html#433>`_

+

+   `new`:idx:

+     * `system.html#119 <system.html#119>`_

+     * `system.html#120 <system.html#120>`_

+

+   `newFileStream`:idx:

+     * `streams.html#120 <streams.html#120>`_

+     * `streams.html#121 <streams.html#121>`_

+

+   `newline`:idx:

+     `manual.html#121 <manual.html#121>`_

+

+   `NewLines`:idx:

+     `lexbase.html#102 <lexbase.html#102>`_

+

+   `newSeq`:idx:

+     `system.html#161 <system.html#161>`_

+

+   `newString`:idx:

+     `system.html#408 <system.html#408>`_

+

+   `newStringStream`:idx:

+     `streams.html#117 <streams.html#117>`_

+

+   `newStringTable`:idx:

+     * `strtabs.html#104 <strtabs.html#104>`_

+     * `strtabs.html#105 <strtabs.html#105>`_

+

+   `next`:idx:

+     * `parseopt.html#104 <parseopt.html#104>`_

+     * `parsecfg.html#106 <parsecfg.html#106>`_

+

+   `nextPowerOfTwo`:idx:

+     `math.html#106 <math.html#106>`_

+

+   `nftw`:idx:

+     `posix.html#830 <posix.html#830>`_

+

+   `nice`:idx:

+     `posix.html#1012 <posix.html#1012>`_

+

+   `nimcall`:idx:

+     `manual.html#169 <manual.html#169>`_

+

+   `NimrodMajor`:idx:

+     `system.html#394 <system.html#394>`_

+

+   `NimrodMinor`:idx:

+     `system.html#395 <system.html#395>`_

+

+   `NimrodPatch`:idx:

+     `system.html#396 <system.html#396>`_

+

+   `NimrodVersion`:idx:

+     `system.html#393 <system.html#393>`_

+

+   `nl`:idx:

+     `strutils.html#104 <strutils.html#104>`_

+

+   `NL_CAT_LOCALE`:idx:

+     `posix.html#769 <posix.html#769>`_

+

+   `nl_langinfo`:idx:

+     `posix.html#843 <posix.html#843>`_

+

+   `NL_SETD`:idx:

+     `posix.html#768 <posix.html#768>`_

+

+   `noconv`:idx:

+     `manual.html#172 <manual.html#172>`_

+

+   `no_decl`:idx:

+     `nimrodc.html#104 <nimrodc.html#104>`_

+

+   `NOEXPR`:idx:

+     `posix.html#442 <posix.html#442>`_

+

+   `normalize`:idx:

+     `strutils.html#111 <strutils.html#111>`_

+

+   `not`:idx:

+     * `system.html#115 <system.html#115>`_

+     * `system.html#191 <system.html#191>`_

+     * `system.html#192 <system.html#192>`_

+     * `system.html#193 <system.html#193>`_

+     * `system.html#194 <system.html#194>`_

+     * `system.html#195 <system.html#195>`_

+

+   `not_in`:idx:

+     `system.html#356 <system.html#356>`_

+

+   `ntohl`:idx:

+     `posix.html#794 <posix.html#794>`_

+

+   `ntohs`:idx:

+     `posix.html#795 <posix.html#795>`_

+

+   `Numerical constants`:idx:

+     `manual.html#136 <manual.html#136>`_

+

+   `O_ACCMODE`:idx:

+     `posix.html#322 <posix.html#322>`_

+

+   `O_APPEND`:idx:

+     `posix.html#317 <posix.html#317>`_

+

+   `object`:idx:

+     `manual.html#155 <manual.html#155>`_

+

+   `O_CREAT`:idx:

+     `posix.html#313 <posix.html#313>`_

+

+   `ODBC_ADD_DSN`:idx:

+     `odbcsql.html#621 <odbcsql.html#621>`_

+

+   `ODBC_ADD_SYS_DSN`:idx:

+     `odbcsql.html#624 <odbcsql.html#624>`_

+

+   `ODBC_CONFIG_DSN`:idx:

+     `odbcsql.html#622 <odbcsql.html#622>`_

+

+   `ODBC_CONFIG_SYS_DSN`:idx:

+     `odbcsql.html#625 <odbcsql.html#625>`_

+

+   `ODBC_REMOVE_DSN`:idx:

+     `odbcsql.html#623 <odbcsql.html#623>`_

+

+   `ODBC_REMOVE_SYS_DSN`:idx:

+     `odbcsql.html#626 <odbcsql.html#626>`_

+

+   `O_DSYNC`:idx:

+     `posix.html#318 <posix.html#318>`_

+

+   `O_EXCL`:idx:

+     `posix.html#314 <posix.html#314>`_

+

+   `O_NOCTTY`:idx:

+     `posix.html#315 <posix.html#315>`_

+

+   `O_NONBLOCK`:idx:

+     `posix.html#319 <posix.html#319>`_

+

+   `open`:idx:

+     * `posix.html#813 <posix.html#813>`_

+     * `lexbase.html#104 <lexbase.html#104>`_

+     * `parsecfg.html#104 <parsecfg.html#104>`_

+     * `zipfiles.html#102 <zipfiles.html#102>`_

+

+   `openarray`:idx:

+     * `tut1.html#118 <tut1.html#118>`_

+     * `system.html#125 <system.html#125>`_

+

+   `opendir`:idx:

+     `posix.html#801 <posix.html#801>`_

+

+   `OpenFile`:idx:

+     * `system.html#486 <system.html#486>`_

+     * `system.html#487 <system.html#487>`_

+

+   `operator`:idx:

+     `manual.html#138 <manual.html#138>`_

+

+   `Operators`:idx:

+     `manual.html#202 <manual.html#202>`_

+

+   `or`:idx:

+     * `system.html#117 <system.html#117>`_

+     * `system.html#236 <system.html#236>`_

+     * `system.html#237 <system.html#237>`_

+     * `system.html#238 <system.html#238>`_

+     * `system.html#239 <system.html#239>`_

+     * `system.html#240 <system.html#240>`_

+

+   `ord`:idx:

+     `system.html#170 <system.html#170>`_

+

+   `ordinal`:idx:

+     `tut1.html#114 <tut1.html#114>`_

+

+   `Ordinal types`:idx:

+     `manual.html#141 <manual.html#141>`_

+

+   `O_RDONLY`:idx:

+     `posix.html#323 <posix.html#323>`_

+

+   `O_RDWR`:idx:

+     `posix.html#324 <posix.html#324>`_

+

+   `O_RSYNC`:idx:

+     `posix.html#320 <posix.html#320>`_

+

+   `OSError`:idx:

+     `os.html#147 <os.html#147>`_

+

+   `O_SYNC`:idx:

+     `posix.html#321 <posix.html#321>`_

+

+   `O_TRUNC`:idx:

+     `posix.html#316 <posix.html#316>`_

+

+   `O_WRONLY`:idx:

+     `posix.html#325 <posix.html#325>`_

+

+   `pairs`:idx:

+     `strtabs.html#110 <strtabs.html#110>`_

+

+   `P_ALL`:idx:

+     `posix.html#716 <posix.html#716>`_

+

+   `paramCount`:idx:

+     `os.html#145 <os.html#145>`_

+

+   `paramStr`:idx:

+     `os.html#146 <os.html#146>`_

+

+   `ParDir`:idx:

+     `os.html#102 <os.html#102>`_

+

+   `parentDir`:idx:

+     `os.html#122 <os.html#122>`_

+

+   `ParseBiggestInt`:idx:

+     `strutils.html#131 <strutils.html#131>`_

+

+   `parseCmdLine`:idx:

+     `os.html#154 <os.html#154>`_

+

+   `ParseFloat`:idx:

+     `strutils.html#132 <strutils.html#132>`_

+

+   `ParseInt`:idx:

+     `strutils.html#130 <strutils.html#130>`_

+

+   `pathconf`:idx:

+     `posix.html#1013 <posix.html#1013>`_

+

+   `PathSep`:idx:

+     `os.html#105 <os.html#105>`_

+

+   `pause`:idx:

+     `posix.html#1014 <posix.html#1014>`_

+

+   `pbyte`:idx:

+     `zlib.html#106 <zlib.html#106>`_

+

+   `pbytef`:idx:

+     `zlib.html#107 <zlib.html#107>`_

+

+   `PC_2_SYMLINKS`:idx:

+     `posix.html#500 <posix.html#500>`_

+

+   `PC_ALLOC_SIZE_MIN`:idx:

+     `posix.html#501 <posix.html#501>`_

+

+   `PC_ASYNC_IO`:idx:

+     `posix.html#502 <posix.html#502>`_

+

+   `PC_CHOWN_RESTRICTED`:idx:

+     `posix.html#503 <posix.html#503>`_

+

+   `PC_FILESIZEBITS`:idx:

+     `posix.html#504 <posix.html#504>`_

+

+   `PC_LINK_MAX`:idx:

+     `posix.html#505 <posix.html#505>`_

+

+   `PC_MAX_CANON`:idx:

+     `posix.html#506 <posix.html#506>`_

+

+   `PC_MAX_INPUT`:idx:

+     `posix.html#507 <posix.html#507>`_

+

+   `PC_NAME_MAX`:idx:

+     `posix.html#508 <posix.html#508>`_

+

+   `PC_NO_TRUNC`:idx:

+     `posix.html#509 <posix.html#509>`_

+

+   `PC_PATH_MAX`:idx:

+     `posix.html#510 <posix.html#510>`_

+

+   `PC_PIPE_BUF`:idx:

+     `posix.html#511 <posix.html#511>`_

+

+   `PC_PRIO_IO`:idx:

+     `posix.html#512 <posix.html#512>`_

+

+   `PC_REC_INCR_XFER_SIZE`:idx:

+     `posix.html#513 <posix.html#513>`_

+

+   `PC_REC_MIN_XFER_SIZE`:idx:

+     `posix.html#514 <posix.html#514>`_

+

+   `PC_REC_XFER_ALIGN`:idx:

+     `posix.html#515 <posix.html#515>`_

+

+   `PC_SYMLINK_MAX`:idx:

+     `posix.html#516 <posix.html#516>`_

+

+   `PC_SYNC_IO`:idx:

+     `posix.html#517 <posix.html#517>`_

+

+   `PC_VDISABLE`:idx:

+     `posix.html#518 <posix.html#518>`_

+

+   `PFileStream`:idx:

+     `streams.html#118 <streams.html#118>`_

+

+   `PFloat32`:idx:

+     `system.html#386 <system.html#386>`_

+

+   `PFloat64`:idx:

+     `system.html#387 <system.html#387>`_

+

+   `PI`:idx:

+     `math.html#101 <math.html#101>`_

+

+   `PInt32`:idx:

+     `system.html#389 <system.html#389>`_

+

+   `PInt64`:idx:

+     `system.html#388 <system.html#388>`_

+

+   `PInternalState`:idx:

+     `zlib.html#111 <zlib.html#111>`_

+

+   `pipe`:idx:

+     `posix.html#1015 <posix.html#1015>`_

+

+   `PM_STR`:idx:

+     `posix.html#395 <posix.html#395>`_

+

+   `PObject`:idx:

+     `system.html#132 <system.html#132>`_

+

+   `pointer`:idx:

+     `system.html#113 <system.html#113>`_

+

+   `pointers`:idx:

+     * `manual.html#158 <manual.html#158>`_

+     * `tut1.html#120 <tut1.html#120>`_

+

+   `Positive`:idx:

+     `system.html#130 <system.html#130>`_

+

+   `POSIX_ASYNC_IO`:idx:

+     `posix.html#475 <posix.html#475>`_

+

+   `POSIX_FADV_DONTNEED`:idx:

+     `posix.html#330 <posix.html#330>`_

+

+   `posix_fadvise`:idx:

+     `posix.html#814 <posix.html#814>`_

+

+   `POSIX_FADV_NOREUSE`:idx:

+     `posix.html#331 <posix.html#331>`_

+

+   `POSIX_FADV_NORMAL`:idx:

+     `posix.html#326 <posix.html#326>`_

+

+   `POSIX_FADV_RANDOM`:idx:

+     `posix.html#328 <posix.html#328>`_

+

+   `POSIX_FADV_SEQUENTIAL`:idx:

+     `posix.html#327 <posix.html#327>`_

+

+   `POSIX_FADV_WILLNEED`:idx:

+     `posix.html#329 <posix.html#329>`_

+

+   `posix_fallocate`:idx:

+     `posix.html#815 <posix.html#815>`_

+

+   `POSIX_MADV_DONTNEED`:idx:

+     `posix.html#691 <posix.html#691>`_

+

+   `posix_madvise`:idx:

+     `posix.html#1086 <posix.html#1086>`_

+

+   `POSIX_MADV_NORMAL`:idx:

+     `posix.html#687 <posix.html#687>`_

+

+   `POSIX_MADV_RANDOM`:idx:

+     `posix.html#689 <posix.html#689>`_

+

+   `POSIX_MADV_SEQUENTIAL`:idx:

+     `posix.html#688 <posix.html#688>`_

+

+   `POSIX_MADV_WILLNEED`:idx:

+     `posix.html#690 <posix.html#690>`_

+

+   `posix_mem_offset`:idx:

+     `posix.html#1087 <posix.html#1087>`_

+

+   `POSIX_PRIO_IO`:idx:

+     `posix.html#476 <posix.html#476>`_

+

+   `posix_spawn`:idx:

+     `posix.html#1167 <posix.html#1167>`_

+

+   `posix_spawnattr_destroy`:idx:

+     `posix.html#1173 <posix.html#1173>`_

+

+   `posix_spawnattr_getflags`:idx:

+     `posix.html#1175 <posix.html#1175>`_

+

+   `posix_spawnattr_getpgroup`:idx:

+     `posix.html#1176 <posix.html#1176>`_

+

+   `posix_spawnattr_getschedparam`:idx:

+     `posix.html#1177 <posix.html#1177>`_

+

+   `posix_spawnattr_getschedpolicy`:idx:

+     `posix.html#1178 <posix.html#1178>`_

+

+   `posix_spawnattr_getsigdefault`:idx:

+     `posix.html#1174 <posix.html#1174>`_

+

+   `posix_spawnattr_getsigmask`:idx:

+     `posix.html#1179 <posix.html#1179>`_

+

+   `posix_spawnattr_init`:idx:

+     `posix.html#1180 <posix.html#1180>`_

+

+   `posix_spawnattr_setflags`:idx:

+     `posix.html#1182 <posix.html#1182>`_

+

+   `posix_spawnattr_setpgroup`:idx:

+     `posix.html#1183 <posix.html#1183>`_

+

+   `posix_spawnattr_setschedparam`:idx:

+     `posix.html#1184 <posix.html#1184>`_

+

+   `posix_spawnattr_setschedpolicy`:idx:

+     `posix.html#1185 <posix.html#1185>`_

+

+   `posix_spawnattr_setsigdefault`:idx:

+     `posix.html#1181 <posix.html#1181>`_

+

+   `posix_spawnattr_setsigmask`:idx:

+     `posix.html#1186 <posix.html#1186>`_

+

+   `posix_spawn_file_actions_addclose`:idx:

+     `posix.html#1168 <posix.html#1168>`_

+

+   `posix_spawn_file_actions_adddup2`:idx:

+     `posix.html#1169 <posix.html#1169>`_

+

+   `posix_spawn_file_actions_addopen`:idx:

+     `posix.html#1170 <posix.html#1170>`_

+

+   `posix_spawn_file_actions_destroy`:idx:

+     `posix.html#1171 <posix.html#1171>`_

+

+   `posix_spawn_file_actions_init`:idx:

+     `posix.html#1172 <posix.html#1172>`_

+

+   `posix_spawnp`:idx:

+     `posix.html#1187 <posix.html#1187>`_

+

+   `POSIX_SPAWN_RESETIDS`:idx:

+     `posix.html#778 <posix.html#778>`_

+

+   `POSIX_SPAWN_SETPGROUP`:idx:

+     `posix.html#779 <posix.html#779>`_

+

+   `POSIX_SPAWN_SETSCHEDPARAM`:idx:

+     `posix.html#780 <posix.html#780>`_

+

+   `POSIX_SPAWN_SETSCHEDULER`:idx:

+     `posix.html#781 <posix.html#781>`_

+

+   `POSIX_SPAWN_SETSIGDEF`:idx:

+     `posix.html#782 <posix.html#782>`_

+

+   `POSIX_SPAWN_SETSIGMASK`:idx:

+     `posix.html#783 <posix.html#783>`_

+

+   `POSIX_SYNC_IO`:idx:

+     `posix.html#477 <posix.html#477>`_

+

+   `POSIX_TYPED_MEM_ALLOCATE`:idx:

+     `posix.html#692 <posix.html#692>`_

+

+   `POSIX_TYPED_MEM_ALLOCATE_CONTIG`:idx:

+     `posix.html#693 <posix.html#693>`_

+

+   `posix_typed_mem_get_info`:idx:

+     `posix.html#1088 <posix.html#1088>`_

+

+   `POSIX_TYPED_MEM_MAP_ALLOCATABLE`:idx:

+     `posix.html#694 <posix.html#694>`_

+

+   `posix_typed_mem_open`:idx:

+     `posix.html#1089 <posix.html#1089>`_

+

+   `pow`:idx:

+     `math.html#127 <math.html#127>`_

+

+   `P_PGID`:idx:

+     `posix.html#718 <posix.html#718>`_

+

+   `P_PID`:idx:

+     `posix.html#717 <posix.html#717>`_

+

+   `pread`:idx:

+     `posix.html#1016 <posix.html#1016>`_

+

+   `pred`:idx:

+     `system.html#158 <system.html#158>`_

+

+   `procedural type`:idx:

+     * `manual.html#161 <manual.html#161>`_

+     * `tut1.html#123 <tut1.html#123>`_

+

+   `procedures`:idx:

+     `manual.html#199 <manual.html#199>`_

+

+   `PROT_EXEC`:idx:

+     `posix.html#676 <posix.html#676>`_

+

+   `PROT_NONE`:idx:

+     `posix.html#677 <posix.html#677>`_

+

+   `PROT_READ`:idx:

+     `posix.html#674 <posix.html#674>`_

+

+   `PROT_WRITE`:idx:

+     `posix.html#675 <posix.html#675>`_

+

+   `pselect`:idx:

+     `posix.html#1165 <posix.html#1165>`_

+

+   `PSQLCHAR`:idx:

+     `odbcsql.html#116 <odbcsql.html#116>`_

+

+   `PSQL_DATE_STRUCT`:idx:

+     `odbcsql.html#232 <odbcsql.html#232>`_

+

+   `PSQLDOUBLE`:idx:

+     `odbcsql.html#122 <odbcsql.html#122>`_

+

+   `PSQLFLOAT`:idx:

+     `odbcsql.html#123 <odbcsql.html#123>`_

+

+   `PSQLHANDLE`:idx:

+     `odbcsql.html#124 <odbcsql.html#124>`_

+

+   `PSQLINTEGER`:idx:

+     `odbcsql.html#117 <odbcsql.html#117>`_

+

+   `PSQLREAL`:idx:

+     `odbcsql.html#121 <odbcsql.html#121>`_

+

+   `PSQLSMALLINT`:idx:

+     `odbcsql.html#119 <odbcsql.html#119>`_

+

+   `PSQL_TIMESTAMP_STRUCT`:idx:

+     `odbcsql.html#236 <odbcsql.html#236>`_

+

+   `PSQL_TIME_STRUCT`:idx:

+     `odbcsql.html#234 <odbcsql.html#234>`_

+

+   `PSQLUINTEGER`:idx:

+     `odbcsql.html#118 <odbcsql.html#118>`_

+

+   `PSQLUSMALLINT`:idx:

+     `odbcsql.html#120 <odbcsql.html#120>`_

+

+   `PStream`:idx:

+     `streams.html#101 <streams.html#101>`_

+

+   `PStringStream`:idx:

+     `streams.html#115 <streams.html#115>`_

+

+   `PStringTable`:idx:

+     `strtabs.html#103 <strtabs.html#103>`_

+

+   `pthread_atfork`:idx:

+     `posix.html#867 <posix.html#867>`_

+

+   `pthread_attr_destroy`:idx:

+     `posix.html#868 <posix.html#868>`_

+

+   `pthread_attr_getdetachstate`:idx:

+     `posix.html#869 <posix.html#869>`_

+

+   `pthread_attr_getguardsize`:idx:

+     `posix.html#870 <posix.html#870>`_

+

+   `pthread_attr_getinheritsched`:idx:

+     `posix.html#871 <posix.html#871>`_

+

+   `pthread_attr_getschedparam`:idx:

+     `posix.html#872 <posix.html#872>`_

+

+   `pthread_attr_getschedpolicy`:idx:

+     `posix.html#873 <posix.html#873>`_

+

+   `pthread_attr_getscope`:idx:

+     `posix.html#874 <posix.html#874>`_

+

+   `pthread_attr_getstack`:idx:

+     `posix.html#875 <posix.html#875>`_

+

+   `pthread_attr_getstackaddr`:idx:

+     `posix.html#876 <posix.html#876>`_

+

+   `pthread_attr_getstacksize`:idx:

+     `posix.html#877 <posix.html#877>`_

+

+   `pthread_attr_init`:idx:

+     `posix.html#878 <posix.html#878>`_

+

+   `pthread_attr_setdetachstate`:idx:

+     `posix.html#879 <posix.html#879>`_

+

+   `pthread_attr_setguardsize`:idx:

+     `posix.html#880 <posix.html#880>`_

+

+   `pthread_attr_setinheritsched`:idx:

+     `posix.html#881 <posix.html#881>`_

+

+   `pthread_attr_setschedparam`:idx:

+     `posix.html#882 <posix.html#882>`_

+

+   `pthread_attr_setschedpolicy`:idx:

+     `posix.html#883 <posix.html#883>`_

+

+   `pthread_attr_setscope`:idx:

+     `posix.html#884 <posix.html#884>`_

+

+   `pthread_attr_setstack`:idx:

+     `posix.html#885 <posix.html#885>`_

+

+   `pthread_attr_setstackaddr`:idx:

+     `posix.html#886 <posix.html#886>`_

+

+   `pthread_attr_setstacksize`:idx:

+     `posix.html#887 <posix.html#887>`_

+

+   `pthread_barrierattr_destroy`:idx:

+     `posix.html#891 <posix.html#891>`_

+

+   `pthread_barrierattr_getpshared`:idx:

+     `posix.html#892 <posix.html#892>`_

+

+   `pthread_barrierattr_init`:idx:

+     `posix.html#893 <posix.html#893>`_

+

+   `pthread_barrierattr_setpshared`:idx:

+     `posix.html#894 <posix.html#894>`_

+

+   `pthread_barrier_destroy`:idx:

+     `posix.html#888 <posix.html#888>`_

+

+   `pthread_barrier_init`:idx:

+     `posix.html#889 <posix.html#889>`_

+

+   `PTHREAD_BARRIER_SERIAL_THREAD`:idx:

+     `posix.html#451 <posix.html#451>`_

+

+   `pthread_barrier_wait`:idx:

+     `posix.html#890 <posix.html#890>`_

+

+   `pthread_cancel`:idx:

+     `posix.html#895 <posix.html#895>`_

+

+   `PTHREAD_CANCEL_ASYNCHRONOUS`:idx:

+     `posix.html#452 <posix.html#452>`_

+

+   `PTHREAD_CANCEL_DEFERRED`:idx:

+     `posix.html#454 <posix.html#454>`_

+

+   `PTHREAD_CANCEL_DISABLE`:idx:

+     `posix.html#455 <posix.html#455>`_

+

+   `PTHREAD_CANCELED`:idx:

+     `posix.html#456 <posix.html#456>`_

+

+   `PTHREAD_CANCEL_ENABLE`:idx:

+     `posix.html#453 <posix.html#453>`_

+

+   `pthread_cleanup_pop`:idx:

+     `posix.html#897 <posix.html#897>`_

+

+   `pthread_cleanup_push`:idx:

+     `posix.html#896 <posix.html#896>`_

+

+   `pthread_condattr_destroy`:idx:

+     `posix.html#904 <posix.html#904>`_

+

+   `pthread_condattr_getclock`:idx:

+     `posix.html#905 <posix.html#905>`_

+

+   `pthread_condattr_getpshared`:idx:

+     `posix.html#906 <posix.html#906>`_

+

+   `pthread_condattr_init`:idx:

+     `posix.html#907 <posix.html#907>`_

+

+   `pthread_condattr_setclock`:idx:

+     `posix.html#908 <posix.html#908>`_

+

+   `pthread_condattr_setpshared`:idx:

+     `posix.html#909 <posix.html#909>`_

+

+   `pthread_cond_broadcast`:idx:

+     `posix.html#898 <posix.html#898>`_

+

+   `pthread_cond_destroy`:idx:

+     `posix.html#899 <posix.html#899>`_

+

+   `pthread_cond_init`:idx:

+     `posix.html#900 <posix.html#900>`_

+

+   `PTHREAD_COND_INITIALIZER`:idx:

+     `posix.html#457 <posix.html#457>`_

+

+   `pthread_cond_signal`:idx:

+     `posix.html#901 <posix.html#901>`_

+

+   `pthread_cond_timedwait`:idx:

+     `posix.html#902 <posix.html#902>`_

+

+   `pthread_cond_wait`:idx:

+     `posix.html#903 <posix.html#903>`_

+

+   `pthread_create`:idx:

+     `posix.html#910 <posix.html#910>`_

+

+   `PTHREAD_CREATE_DETACHED`:idx:

+     `posix.html#458 <posix.html#458>`_

+

+   `PTHREAD_CREATE_JOINABLE`:idx:

+     `posix.html#459 <posix.html#459>`_

+

+   `pthread_detach`:idx:

+     `posix.html#911 <posix.html#911>`_

+

+   `pthread_equal`:idx:

+     `posix.html#912 <posix.html#912>`_

+

+   `pthread_exit`:idx:

+     `posix.html#913 <posix.html#913>`_

+

+   `PTHREAD_EXPLICIT_SCHED`:idx:

+     `posix.html#460 <posix.html#460>`_

+

+   `pthread_getconcurrency`:idx:

+     `posix.html#914 <posix.html#914>`_

+

+   `pthread_getcpuclockid`:idx:

+     `posix.html#915 <posix.html#915>`_

+

+   `pthread_getschedparam`:idx:

+     `posix.html#916 <posix.html#916>`_

+

+   `pthread_getspecific`:idx:

+     `posix.html#917 <posix.html#917>`_

+

+   `PTHREAD_INHERIT_SCHED`:idx:

+     `posix.html#461 <posix.html#461>`_

+

+   `pthread_join`:idx:

+     `posix.html#918 <posix.html#918>`_

+

+   `pthread_key_create`:idx:

+     `posix.html#919 <posix.html#919>`_

+

+   `pthread_key_delete`:idx:

+     `posix.html#920 <posix.html#920>`_

+

+   `pthread_kill`:idx:

+     `posix.html#1125 <posix.html#1125>`_

+

+   `pthread_mutexattr_destroy`:idx:

+     `posix.html#929 <posix.html#929>`_

+

+   `pthread_mutexattr_getprioceiling`:idx:

+     `posix.html#930 <posix.html#930>`_

+

+   `pthread_mutexattr_getprotocol`:idx:

+     `posix.html#931 <posix.html#931>`_

+

+   `pthread_mutexattr_getpshared`:idx:

+     `posix.html#932 <posix.html#932>`_

+

+   `pthread_mutexattr_gettype`:idx:

+     `posix.html#933 <posix.html#933>`_

+

+   `pthread_mutexattr_init`:idx:

+     `posix.html#934 <posix.html#934>`_

+

+   `pthread_mutexattr_setprioceiling`:idx:

+     `posix.html#935 <posix.html#935>`_

+

+   `pthread_mutexattr_setprotocol`:idx:

+     `posix.html#936 <posix.html#936>`_

+

+   `pthread_mutexattr_setpshared`:idx:

+     `posix.html#937 <posix.html#937>`_

+

+   `pthread_mutexattr_settype`:idx:

+     `posix.html#938 <posix.html#938>`_

+

+   `PTHREAD_MUTEX_DEFAULT`:idx:

+     `posix.html#462 <posix.html#462>`_

+

+   `pthread_mutex_destroy`:idx:

+     `posix.html#921 <posix.html#921>`_

+

+   `PTHREAD_MUTEX_ERRORCHECK`:idx:

+     `posix.html#463 <posix.html#463>`_

+

+   `pthread_mutex_getprioceiling`:idx:

+     `posix.html#922 <posix.html#922>`_

+

+   `pthread_mutex_init`:idx:

+     `posix.html#923 <posix.html#923>`_

+

+   `PTHREAD_MUTEX_INITIALIZER`:idx:

+     `posix.html#464 <posix.html#464>`_

+

+   `pthread_mutex_lock`:idx:

+     `posix.html#924 <posix.html#924>`_

+

+   `PTHREAD_MUTEX_NORMAL`:idx:

+     `posix.html#465 <posix.html#465>`_

+

+   `PTHREAD_MUTEX_RECURSIVE`:idx:

+     `posix.html#466 <posix.html#466>`_

+

+   `pthread_mutex_setprioceiling`:idx:

+     `posix.html#925 <posix.html#925>`_

+

+   `pthread_mutex_timedlock`:idx:

+     `posix.html#926 <posix.html#926>`_

+

+   `pthread_mutex_trylock`:idx:

+     `posix.html#927 <posix.html#927>`_

+

+   `pthread_mutex_unlock`:idx:

+     `posix.html#928 <posix.html#928>`_

+

+   `pthread_once`:idx:

+     `posix.html#939 <posix.html#939>`_

+

+   `PTHREAD_ONCE_INIT`:idx:

+     `posix.html#467 <posix.html#467>`_

+

+   `PTHREAD_PRIO_INHERIT`:idx:

+     `posix.html#468 <posix.html#468>`_

+

+   `PTHREAD_PRIO_NONE`:idx:

+     `posix.html#469 <posix.html#469>`_

+

+   `PTHREAD_PRIO_PROTECT`:idx:

+     `posix.html#470 <posix.html#470>`_

+

+   `PTHREAD_PROCESS_PRIVATE`:idx:

+     `posix.html#472 <posix.html#472>`_

+

+   `PTHREAD_PROCESS_SHARED`:idx:

+     `posix.html#471 <posix.html#471>`_

+

+   `pthread_rwlockattr_destroy`:idx:

+     `posix.html#949 <posix.html#949>`_

+

+   `pthread_rwlockattr_getpshared`:idx:

+     `posix.html#950 <posix.html#950>`_

+

+   `pthread_rwlockattr_init`:idx:

+     `posix.html#951 <posix.html#951>`_

+

+   `pthread_rwlockattr_setpshared`:idx:

+     `posix.html#952 <posix.html#952>`_

+

+   `pthread_rwlock_destroy`:idx:

+     `posix.html#940 <posix.html#940>`_

+

+   `pthread_rwlock_init`:idx:

+     `posix.html#941 <posix.html#941>`_

+

+   `pthread_rwlock_rdlock`:idx:

+     `posix.html#942 <posix.html#942>`_

+

+   `pthread_rwlock_timedrdlock`:idx:

+     `posix.html#943 <posix.html#943>`_

+

+   `pthread_rwlock_timedwrlock`:idx:

+     `posix.html#944 <posix.html#944>`_

+

+   `pthread_rwlock_tryrdlock`:idx:

+     `posix.html#945 <posix.html#945>`_

+

+   `pthread_rwlock_trywrlock`:idx:

+     `posix.html#946 <posix.html#946>`_

+

+   `pthread_rwlock_unlock`:idx:

+     `posix.html#947 <posix.html#947>`_

+

+   `pthread_rwlock_wrlock`:idx:

+     `posix.html#948 <posix.html#948>`_

+

+   `PTHREAD_SCOPE_PROCESS`:idx:

+     `posix.html#473 <posix.html#473>`_

+

+   `PTHREAD_SCOPE_SYSTEM`:idx:

+     `posix.html#474 <posix.html#474>`_

+

+   `pthread_self`:idx:

+     `posix.html#953 <posix.html#953>`_

+

+   `pthread_setcancelstate`:idx:

+     `posix.html#954 <posix.html#954>`_

+

+   `pthread_setcanceltype`:idx:

+     `posix.html#955 <posix.html#955>`_

+

+   `pthread_setconcurrency`:idx:

+     `posix.html#956 <posix.html#956>`_

+

+   `pthread_setschedparam`:idx:

+     `posix.html#957 <posix.html#957>`_

+

+   `pthread_setschedprio`:idx:

+     `posix.html#958 <posix.html#958>`_

+

+   `pthread_setspecific`:idx:

+     `posix.html#959 <posix.html#959>`_

+

+   `pthread_sigmask`:idx:

+     `posix.html#1126 <posix.html#1126>`_

+

+   `pthread_spin_destroy`:idx:

+     `posix.html#960 <posix.html#960>`_

+

+   `pthread_spin_init`:idx:

+     `posix.html#961 <posix.html#961>`_

+

+   `pthread_spin_lock`:idx:

+     `posix.html#962 <posix.html#962>`_

+

+   `pthread_spin_trylock`:idx:

+     `posix.html#963 <posix.html#963>`_

+

+   `pthread_spin_unlock`:idx:

+     `posix.html#964 <posix.html#964>`_

+

+   `pthread_testcancel`:idx:

+     `posix.html#965 <posix.html#965>`_

+

+   `Pulongf`:idx:

+     `zlib.html#104 <zlib.html#104>`_

+

+   `push/pop`:idx:

+     `manual.html#228 <manual.html#228>`_

+

+   `putEnv`:idx:

+     `os.html#142 <os.html#142>`_

+

+   `PWindow`:idx:

+     `dialogs.html#101 <dialogs.html#101>`_

+

+   `pwrite`:idx:

+     `posix.html#1017 <posix.html#1017>`_

+

+   `Pzip`:idx:

+     `libzip.html#105 <libzip.html#105>`_

+

+   `Pzip_file`:idx:

+     `libzip.html#106 <libzip.html#106>`_

+

+   `PZipFileStream`:idx:

+     `zipfiles.html#108 <zipfiles.html#108>`_

+

+   `Pzip_source`:idx:

+     `libzip.html#107 <libzip.html#107>`_

+

+   `Pzip_stat`:idx:

+     `libzip.html#103 <libzip.html#103>`_

+

+   `PZstream`:idx:

+     `zlib.html#114 <zlib.html#114>`_

+

+   `quit`:idx:

+     * `system.html#478 <system.html#478>`_

+     * `system.html#479 <system.html#479>`_

+

+   `QuitFailure`:idx:

+     `system.html#477 <system.html#477>`_

+

+   `QuitSuccess`:idx:

+     `system.html#476 <system.html#476>`_

+

+   `quotation mark`:idx:

+     `manual.html#128 <manual.html#128>`_

+

+   `quoteIfContainsWhite`:idx:

+     `strutils.html#140 <strutils.html#140>`_

+

+   `RADIXCHAR`:idx:

+     `posix.html#439 <posix.html#439>`_

+

+   `raise`:idx:

+     `posix.html#1127 <posix.html#1127>`_

+

+   `random`:idx:

+     `math.html#108 <math.html#108>`_

+

+   `randomize`:idx:

+     `math.html#109 <math.html#109>`_

+

+   `range`:idx:

+     `system.html#123 <system.html#123>`_

+

+   `re-raised`:idx:

+     `manual.html#183 <manual.html#183>`_

+

+   `read`:idx:

+     `posix.html#1018 <posix.html#1018>`_

+

+   `readBool`:idx:

+     `streams.html#106 <streams.html#106>`_

+

+   `readBuffer`:idx:

+     `system.html#506 <system.html#506>`_

+

+   `ReadBytes`:idx:

+     `system.html#504 <system.html#504>`_

+

+   `readChar`:idx:

+     * `system.html#490 <system.html#490>`_

+     * `streams.html#105 <streams.html#105>`_

+

+   `ReadChars`:idx:

+     `system.html#505 <system.html#505>`_

+

+   `readdir`:idx:

+     `posix.html#802 <posix.html#802>`_

+

+   `readdir_r`:idx:

+     `posix.html#803 <posix.html#803>`_

+

+   `readFile`:idx:

+     `system.html#492 <system.html#492>`_

+

+   `readFloat32`:idx:

+     `streams.html#111 <streams.html#111>`_

+

+   `readFloat64`:idx:

+     `streams.html#112 <streams.html#112>`_

+

+   `readInt16`:idx:

+     `streams.html#108 <streams.html#108>`_

+

+   `readInt32`:idx:

+     `streams.html#109 <streams.html#109>`_

+

+   `readInt64`:idx:

+     `streams.html#110 <streams.html#110>`_

+

+   `readInt8`:idx:

+     `streams.html#107 <streams.html#107>`_

+

+   `readLine`:idx:

+     * `system.html#500 <system.html#500>`_

+     * `streams.html#114 <streams.html#114>`_

+

+   `readlink`:idx:

+     `posix.html#1019 <posix.html#1019>`_

+

+   `readStr`:idx:

+     `streams.html#113 <streams.html#113>`_

+

+   `realloc`:idx:

+     `system.html#415 <system.html#415>`_

+

+   `Recursive module dependancies`:idx:

+     `manual.html#216 <manual.html#216>`_

+

+   `register`:idx:

+     `nimrodc.html#112 <nimrodc.html#112>`_

+

+   `removeDir`:idx:

+     `os.html#137 <os.html#137>`_

+

+   `removeFile`:idx:

+     `os.html#136 <os.html#136>`_

+

+   `repeatChar`:idx:

+     `strutils.html#136 <strutils.html#136>`_

+

+   `replaceStr`:idx:

+     * `strutils.html#115 <strutils.html#115>`_

+     * `strutils.html#116 <strutils.html#116>`_

+

+   `repr`:idx:

+     `system.html#371 <system.html#371>`_

+

+   `result`:idx:

+     * `manual.html#190 <manual.html#190>`_

+     * `manual.html#201 <manual.html#201>`_

+

+   `return`:idx:

+     `manual.html#189 <manual.html#189>`_

+

+   `rewinddir`:idx:

+     `posix.html#804 <posix.html#804>`_

+

+   `rmdir`:idx:

+     `posix.html#1020 <posix.html#1020>`_

+

+   `R_OK`:idx:

+     `posix.html#479 <posix.html#479>`_

+

+   `round`:idx:

+     `math.html#116 <math.html#116>`_

+

+   `RTLD_GLOBAL`:idx:

+     `posix.html#217 <posix.html#217>`_

+

+   `RTLD_LAZY`:idx:

+     `posix.html#215 <posix.html#215>`_

+

+   `RTLD_LOCAL`:idx:

+     `posix.html#218 <posix.html#218>`_

+

+   `RTLD_NOW`:idx:

+     `posix.html#216 <posix.html#216>`_

+

+   `safe`:idx:

+     `manual.html#112 <manual.html#112>`_

+

+   `safecall`:idx:

+     `manual.html#166 <manual.html#166>`_

+

+   `sameFile`:idx:

+     `os.html#148 <os.html#148>`_

+

+   `sameFileContent`:idx:

+     `os.html#149 <os.html#149>`_

+

+   `SA_NOCLDSTOP`:idx:

+     `posix.html#754 <posix.html#754>`_

+

+   `SA_NOCLDWAIT`:idx:

+     `posix.html#762 <posix.html#762>`_

+

+   `SA_NODEFER`:idx:

+     `posix.html#763 <posix.html#763>`_

+

+   `SA_ONSTACK`:idx:

+     `posix.html#758 <posix.html#758>`_

+

+   `SA_RESETHAND`:idx:

+     `posix.html#759 <posix.html#759>`_

+

+   `SA_RESTART`:idx:

+     `posix.html#760 <posix.html#760>`_

+

+   `SA_SIGINFO`:idx:

+     `posix.html#761 <posix.html#761>`_

+

+   `SC_2_C_BIND`:idx:

+     `posix.html#519 <posix.html#519>`_

+

+   `SC_2_C_DEV`:idx:

+     `posix.html#520 <posix.html#520>`_

+

+   `SC_2_CHAR_TERM`:idx:

+     `posix.html#521 <posix.html#521>`_

+

+   `SC_2_FORT_DEV`:idx:

+     `posix.html#522 <posix.html#522>`_

+

+   `SC_2_FORT_RUN`:idx:

+     `posix.html#523 <posix.html#523>`_

+

+   `SC_2_LOCALEDEF`:idx:

+     `posix.html#524 <posix.html#524>`_

+

+   `SC_2_PBS`:idx:

+     `posix.html#525 <posix.html#525>`_

+

+   `SC_2_PBS_ACCOUNTING`:idx:

+     `posix.html#526 <posix.html#526>`_

+

+   `SC_2_PBS_CHECKPOINT`:idx:

+     `posix.html#527 <posix.html#527>`_

+

+   `SC_2_PBS_LOCATE`:idx:

+     `posix.html#528 <posix.html#528>`_

+

+   `SC_2_PBS_MESSAGE`:idx:

+     `posix.html#529 <posix.html#529>`_

+

+   `SC_2_PBS_TRACK`:idx:

+     `posix.html#530 <posix.html#530>`_

+

+   `SC_2_SW_DEV`:idx:

+     `posix.html#531 <posix.html#531>`_

+

+   `SC_2_UPE`:idx:

+     `posix.html#532 <posix.html#532>`_

+

+   `SC_2_VERSION`:idx:

+     `posix.html#533 <posix.html#533>`_

+

+   `SC_ADVISORY_INFO`:idx:

+     `posix.html#534 <posix.html#534>`_

+

+   `SC_AIO_LISTIO_MAX`:idx:

+     `posix.html#535 <posix.html#535>`_

+

+   `SC_AIO_MAX`:idx:

+     `posix.html#536 <posix.html#536>`_

+

+   `SC_AIO_PRIO_DELTA_MAX`:idx:

+     `posix.html#537 <posix.html#537>`_

+

+   `SC_ARG_MAX`:idx:

+     `posix.html#538 <posix.html#538>`_

+

+   `SC_ASYNCHRONOUS_IO`:idx:

+     `posix.html#539 <posix.html#539>`_

+

+   `SC_ATEXIT_MAX`:idx:

+     `posix.html#540 <posix.html#540>`_

+

+   `SC_BARRIERS`:idx:

+     `posix.html#541 <posix.html#541>`_

+

+   `SC_BC_BASE_MAX`:idx:

+     `posix.html#542 <posix.html#542>`_

+

+   `SC_BC_DIM_MAX`:idx:

+     `posix.html#543 <posix.html#543>`_

+

+   `SC_BC_SCALE_MAX`:idx:

+     `posix.html#544 <posix.html#544>`_

+

+   `SC_BC_STRING_MAX`:idx:

+     `posix.html#545 <posix.html#545>`_

+

+   `SC_CHILD_MAX`:idx:

+     `posix.html#546 <posix.html#546>`_

+

+   `SC_CLK_TCK`:idx:

+     `posix.html#547 <posix.html#547>`_

+

+   `SC_CLOCK_SELECTION`:idx:

+     `posix.html#548 <posix.html#548>`_

+

+   `SC_COLL_WEIGHTS_MAX`:idx:

+     `posix.html#549 <posix.html#549>`_

+

+   `SC_CPUTIME`:idx:

+     `posix.html#550 <posix.html#550>`_

+

+   `SC_DELAYTIMER_MAX`:idx:

+     `posix.html#551 <posix.html#551>`_

+

+   `SC_EXPR_NEST_MAX`:idx:

+     `posix.html#552 <posix.html#552>`_

+

+   `SC_FSYNC`:idx:

+     `posix.html#553 <posix.html#553>`_

+

+   `SC_GETGR_R_SIZE_MAX`:idx:

+     `posix.html#554 <posix.html#554>`_

+

+   `SC_GETPW_R_SIZE_MAX`:idx:

+     `posix.html#555 <posix.html#555>`_

+

+   `SCHED_FIFO`:idx:

+     `posix.html#770 <posix.html#770>`_

+

+   `sched_getparam`:idx:

+     `posix.html#1154 <posix.html#1154>`_

+

+   `sched_get_priority_max`:idx:

+     `posix.html#1152 <posix.html#1152>`_

+

+   `sched_get_priority_min`:idx:

+     `posix.html#1153 <posix.html#1153>`_

+

+   `sched_getscheduler`:idx:

+     `posix.html#1155 <posix.html#1155>`_

+

+   `SCHED_OTHER`:idx:

+     `posix.html#773 <posix.html#773>`_

+

+   `SCHED_RR`:idx:

+     `posix.html#771 <posix.html#771>`_

+

+   `sched_rr_get_interval`:idx:

+     `posix.html#1156 <posix.html#1156>`_

+

+   `sched_setparam`:idx:

+     `posix.html#1157 <posix.html#1157>`_

+

+   `sched_setscheduler`:idx:

+     `posix.html#1158 <posix.html#1158>`_

+

+   `SCHED_SPORADIC`:idx:

+     `posix.html#772 <posix.html#772>`_

+

+   `sched_yield`:idx:

+     `posix.html#1159 <posix.html#1159>`_

+

+   `SC_HOST_NAME_MAX`:idx:

+     `posix.html#556 <posix.html#556>`_

+

+   `SC_IOV_MAX`:idx:

+     `posix.html#557 <posix.html#557>`_

+

+   `SC_IPV6`:idx:

+     `posix.html#558 <posix.html#558>`_

+

+   `SC_JOB_CONTROL`:idx:

+     `posix.html#559 <posix.html#559>`_

+

+   `SC_LINE_MAX`:idx:

+     `posix.html#560 <posix.html#560>`_

+

+   `SC_LOGIN_NAME_MAX`:idx:

+     `posix.html#561 <posix.html#561>`_

+

+   `SC_MAPPED_FILES`:idx:

+     `posix.html#562 <posix.html#562>`_

+

+   `SC_MEMLOCK`:idx:

+     `posix.html#563 <posix.html#563>`_

+

+   `SC_MEMLOCK_RANGE`:idx:

+     `posix.html#564 <posix.html#564>`_

+

+   `SC_MEMORY_PROTECTION`:idx:

+     `posix.html#565 <posix.html#565>`_

+

+   `SC_MESSAGE_PASSING`:idx:

+     `posix.html#566 <posix.html#566>`_

+

+   `SC_MONOTONIC_CLOCK`:idx:

+     `posix.html#567 <posix.html#567>`_

+

+   `SC_MQ_OPEN_MAX`:idx:

+     `posix.html#568 <posix.html#568>`_

+

+   `SC_MQ_PRIO_MAX`:idx:

+     `posix.html#569 <posix.html#569>`_

+

+   `SC_NGROUPS_MAX`:idx:

+     `posix.html#570 <posix.html#570>`_

+

+   `scope`:idx:

+     * `manual.html#106 <manual.html#106>`_

+     * `manual.html#217 <manual.html#217>`_

+

+   `SC_OPEN_MAX`:idx:

+     `posix.html#571 <posix.html#571>`_

+

+   `SC_PAGE_SIZE`:idx:

+     `posix.html#572 <posix.html#572>`_

+

+   `SC_PRIORITIZED_IO`:idx:

+     `posix.html#573 <posix.html#573>`_

+

+   `SC_PRIORITY_SCHEDULING`:idx:

+     `posix.html#574 <posix.html#574>`_

+

+   `SC_RAW_SOCKETS`:idx:

+     `posix.html#575 <posix.html#575>`_

+

+   `SC_READER_WRITER_LOCKS`:idx:

+     `posix.html#577 <posix.html#577>`_

+

+   `SC_REALTIME_SIGNALS`:idx:

+     `posix.html#578 <posix.html#578>`_

+

+   `SC_RE_DUP_MAX`:idx:

+     `posix.html#576 <posix.html#576>`_

+

+   `SC_REGEXP`:idx:

+     `posix.html#579 <posix.html#579>`_

+

+   `ScriptExt`:idx:

+     `os.html#108 <os.html#108>`_

+

+   `SC_RTSIG_MAX`:idx:

+     `posix.html#580 <posix.html#580>`_

+

+   `SC_SAVED_IDS`:idx:

+     `posix.html#581 <posix.html#581>`_

+

+   `SC_SEMAPHORES`:idx:

+     `posix.html#584 <posix.html#584>`_

+

+   `SC_SEM_NSEMS_MAX`:idx:

+     `posix.html#582 <posix.html#582>`_

+

+   `SC_SEM_VALUE_MAX`:idx:

+     `posix.html#583 <posix.html#583>`_

+

+   `SC_SHARED_MEMORY_OBJECTS`:idx:

+     `posix.html#585 <posix.html#585>`_

+

+   `SC_SHELL`:idx:

+     `posix.html#586 <posix.html#586>`_

+

+   `SC_SIGQUEUE_MAX`:idx:

+     `posix.html#587 <posix.html#587>`_

+

+   `SC_SPAWN`:idx:

+     `posix.html#588 <posix.html#588>`_

+

+   `SC_SPIN_LOCKS`:idx:

+     `posix.html#589 <posix.html#589>`_

+

+   `SC_SPORADIC_SERVER`:idx:

+     `posix.html#590 <posix.html#590>`_

+

+   `SC_SS_REPL_MAX`:idx:

+     `posix.html#591 <posix.html#591>`_

+

+   `SC_STREAM_MAX`:idx:

+     `posix.html#592 <posix.html#592>`_

+

+   `SC_SYMLOOP_MAX`:idx:

+     `posix.html#593 <posix.html#593>`_

+

+   `SC_SYNCHRONIZED_IO`:idx:

+     `posix.html#594 <posix.html#594>`_

+

+   `SC_THREAD_ATTR_STACKADDR`:idx:

+     `posix.html#595 <posix.html#595>`_

+

+   `SC_THREAD_ATTR_STACKSIZE`:idx:

+     `posix.html#596 <posix.html#596>`_

+

+   `SC_THREAD_CPUTIME`:idx:

+     `posix.html#597 <posix.html#597>`_

+

+   `SC_THREAD_DESTRUCTOR_ITERATIONS`:idx:

+     `posix.html#598 <posix.html#598>`_

+

+   `SC_THREAD_KEYS_MAX`:idx:

+     `posix.html#599 <posix.html#599>`_

+

+   `SC_THREAD_PRIO_INHERIT`:idx:

+     `posix.html#600 <posix.html#600>`_

+

+   `SC_THREAD_PRIO_PROTECT`:idx:

+     `posix.html#601 <posix.html#601>`_

+

+   `SC_THREAD_PRIORITY_SCHEDULING`:idx:

+     `posix.html#602 <posix.html#602>`_

+

+   `SC_THREAD_PROCESS_SHARED`:idx:

+     `posix.html#603 <posix.html#603>`_

+

+   `SC_THREADS`:idx:

+     `posix.html#608 <posix.html#608>`_

+

+   `SC_THREAD_SAFE_FUNCTIONS`:idx:

+     `posix.html#604 <posix.html#604>`_

+

+   `SC_THREAD_SPORADIC_SERVER`:idx:

+     `posix.html#605 <posix.html#605>`_

+

+   `SC_THREAD_STACK_MIN`:idx:

+     `posix.html#606 <posix.html#606>`_

+

+   `SC_THREAD_THREADS_MAX`:idx:

+     `posix.html#607 <posix.html#607>`_

+

+   `SC_TIMEOUTS`:idx:

+     `posix.html#609 <posix.html#609>`_

+

+   `SC_TIMER_MAX`:idx:

+     `posix.html#610 <posix.html#610>`_

+

+   `SC_TIMERS`:idx:

+     `posix.html#611 <posix.html#611>`_

+

+   `SC_TRACE`:idx:

+     `posix.html#612 <posix.html#612>`_

+

+   `SC_TRACE_EVENT_FILTER`:idx:

+     `posix.html#613 <posix.html#613>`_

+

+   `SC_TRACE_EVENT_NAME_MAX`:idx:

+     `posix.html#614 <posix.html#614>`_

+

+   `SC_TRACE_INHERIT`:idx:

+     `posix.html#615 <posix.html#615>`_

+

+   `SC_TRACE_LOG`:idx:

+     `posix.html#616 <posix.html#616>`_

+

+   `SC_TRACE_NAME_MAX`:idx:

+     `posix.html#617 <posix.html#617>`_

+

+   `SC_TRACE_SYS_MAX`:idx:

+     `posix.html#618 <posix.html#618>`_

+

+   `SC_TRACE_USER_EVENT_MAX`:idx:

+     `posix.html#619 <posix.html#619>`_

+

+   `SC_TTY_NAME_MAX`:idx:

+     `posix.html#620 <posix.html#620>`_

+

+   `SC_TYPED_MEMORY_OBJECTS`:idx:

+     `posix.html#621 <posix.html#621>`_

+

+   `SC_TZNAME_MAX`:idx:

+     `posix.html#622 <posix.html#622>`_

+

+   `SC_V6_ILP32_OFF32`:idx:

+     `posix.html#623 <posix.html#623>`_

+

+   `SC_V6_ILP32_OFFBIG`:idx:

+     `posix.html#624 <posix.html#624>`_

+

+   `SC_V6_LP64_OFF64`:idx:

+     `posix.html#625 <posix.html#625>`_

+

+   `SC_V6_LPBIG_OFFBIG`:idx:

+     `posix.html#626 <posix.html#626>`_

+

+   `SC_VERSION`:idx:

+     `posix.html#627 <posix.html#627>`_

+

+   `SC_XBS5_ILP32_OFF32`:idx:

+     `posix.html#628 <posix.html#628>`_

+

+   `SC_XBS5_ILP32_OFFBIG`:idx:

+     `posix.html#629 <posix.html#629>`_

+

+   `SC_XBS5_LP64_OFF64`:idx:

+     `posix.html#630 <posix.html#630>`_

+

+   `SC_XBS5_LPBIG_OFFBIG`:idx:

+     `posix.html#631 <posix.html#631>`_

+

+   `SC_XOPEN_CRYPT`:idx:

+     `posix.html#632 <posix.html#632>`_

+

+   `SC_XOPEN_ENH_I18N`:idx:

+     `posix.html#633 <posix.html#633>`_

+

+   `SC_XOPEN_LEGACY`:idx:

+     `posix.html#634 <posix.html#634>`_

+

+   `SC_XOPEN_REALTIME`:idx:

+     `posix.html#635 <posix.html#635>`_

+

+   `SC_XOPEN_REALTIME_THREADS`:idx:

+     `posix.html#636 <posix.html#636>`_

+

+   `SC_XOPEN_SHM`:idx:

+     `posix.html#637 <posix.html#637>`_

+

+   `SC_XOPEN_STREAMS`:idx:

+     `posix.html#638 <posix.html#638>`_

+

+   `SC_XOPEN_UNIX`:idx:

+     `posix.html#639 <posix.html#639>`_

+

+   `SC_XOPEN_VERSION`:idx:

+     `posix.html#640 <posix.html#640>`_

+

+   `SEEK_CUR`:idx:

+     `posix.html#776 <posix.html#776>`_

+

+   `seekdir`:idx:

+     `posix.html#805 <posix.html#805>`_

+

+   `SEEK_END`:idx:

+     `posix.html#777 <posix.html#777>`_

+

+   `SEEK_SET`:idx:

+     `posix.html#775 <posix.html#775>`_

+

+   `select`:idx:

+     `posix.html#1166 <posix.html#1166>`_

+

+   `sem_close`:idx:

+     `posix.html#1045 <posix.html#1045>`_

+

+   `sem_destroy`:idx:

+     `posix.html#1046 <posix.html#1046>`_

+

+   `SEM_FAILED`:idx:

+     `posix.html#641 <posix.html#641>`_

+

+   `sem_getvalue`:idx:

+     `posix.html#1047 <posix.html#1047>`_

+

+   `sem_init`:idx:

+     `posix.html#1048 <posix.html#1048>`_

+

+   `sem_open`:idx:

+     `posix.html#1049 <posix.html#1049>`_

+

+   `sem_post`:idx:

+     `posix.html#1050 <posix.html#1050>`_

+

+   `sem_timedwait`:idx:

+     `posix.html#1051 <posix.html#1051>`_

+

+   `sem_trywait`:idx:

+     `posix.html#1052 <posix.html#1052>`_

+

+   `sem_unlink`:idx:

+     `posix.html#1053 <posix.html#1053>`_

+

+   `sem_wait`:idx:

+     `posix.html#1054 <posix.html#1054>`_

+

+   `separate compilation`:idx:

+     * `manual.html#214 <manual.html#214>`_

+     * `tut1.html#127 <tut1.html#127>`_

+

+   `seq`:idx:

+     `system.html#126 <system.html#126>`_

+

+   `seqToPtr`:idx:

+     `system.html#457 <system.html#457>`_

+

+   `Sequences`:idx:

+     * `manual.html#153 <manual.html#153>`_

+     * `tut1.html#119 <tut1.html#119>`_

+

+   `set`:idx:

+     `system.html#127 <system.html#127>`_

+

+   `set type`:idx:

+     * `manual.html#157 <manual.html#157>`_

+     * `tut1.html#116 <tut1.html#116>`_

+

+   `setcontext`:idx:

+     `posix.html#1190 <posix.html#1190>`_

+

+   `setCurrentDir`:idx:

+     `os.html#113 <os.html#113>`_

+

+   `setegid`:idx:

+     `posix.html#1021 <posix.html#1021>`_

+

+   `seteuid`:idx:

+     `posix.html#1022 <posix.html#1022>`_

+

+   `setFilePos`:idx:

+     `system.html#510 <system.html#510>`_

+

+   `setgid`:idx:

+     `posix.html#1023 <posix.html#1023>`_

+

+   `setgrent`:idx:

+     `posix.html#839 <posix.html#839>`_

+

+   `setLen`:idx:

+     * `system.html#407 <system.html#407>`_

+     * `system.html#417 <system.html#417>`_

+

+   `setlocale`:idx:

+     `posix.html#847 <posix.html#847>`_

+

+   `setpgid`:idx:

+     `posix.html#1024 <posix.html#1024>`_

+

+   `setpgrp`:idx:

+     `posix.html#1025 <posix.html#1025>`_

+

+   `setpwent`:idx:

+     `posix.html#865 <posix.html#865>`_

+

+   `setregid`:idx:

+     `posix.html#1026 <posix.html#1026>`_

+

+   `setreuid`:idx:

+     `posix.html#1027 <posix.html#1027>`_

+

+   `setsid`:idx:

+     `posix.html#1028 <posix.html#1028>`_

+

+   `setuid`:idx:

+     `posix.html#1029 <posix.html#1029>`_

+

+   `shl`:idx:

+     * `system.html#226 <system.html#226>`_

+     * `system.html#227 <system.html#227>`_

+     * `system.html#228 <system.html#228>`_

+     * `system.html#229 <system.html#229>`_

+     * `system.html#230 <system.html#230>`_

+

+   `shm_open`:idx:

+     `posix.html#1090 <posix.html#1090>`_

+

+   `shm_unlink`:idx:

+     `posix.html#1091 <posix.html#1091>`_

+

+   `shr`:idx:

+     * `system.html#221 <system.html#221>`_

+     * `system.html#222 <system.html#222>`_

+     * `system.html#223 <system.html#223>`_

+     * `system.html#224 <system.html#224>`_

+     * `system.html#225 <system.html#225>`_

+

+   `S_IFBLK`:idx:

+     `posix.html#650 <posix.html#650>`_

+

+   `S_IFCHR`:idx:

+     `posix.html#651 <posix.html#651>`_

+

+   `S_IFDIR`:idx:

+     `posix.html#654 <posix.html#654>`_

+

+   `S_IFIFO`:idx:

+     `posix.html#652 <posix.html#652>`_

+

+   `S_IFLNK`:idx:

+     `posix.html#655 <posix.html#655>`_

+

+   `S_IFMT`:idx:

+     `posix.html#649 <posix.html#649>`_

+

+   `S_IFREG`:idx:

+     `posix.html#653 <posix.html#653>`_

+

+   `S_IFSOCK`:idx:

+     `posix.html#656 <posix.html#656>`_

+

+   `SIGABRT`:idx:

+     `posix.html#726 <posix.html#726>`_

+

+   `sigaction`:idx:

+     `posix.html#1128 <posix.html#1128>`_

+

+   `sigaddset`:idx:

+     `posix.html#1129 <posix.html#1129>`_

+

+   `SIGALRM`:idx:

+     `posix.html#727 <posix.html#727>`_

+

+   `sigaltstack`:idx:

+     `posix.html#1130 <posix.html#1130>`_

+

+   `SIG_BLOCK`:idx:

+     `posix.html#755 <posix.html#755>`_

+

+   `SIGBUS`:idx:

+     `posix.html#728 <posix.html#728>`_

+

+   `SIGCHLD`:idx:

+     `posix.html#729 <posix.html#729>`_

+

+   `SIGCONT`:idx:

+     `posix.html#730 <posix.html#730>`_

+

+   `sigdelset`:idx:

+     `posix.html#1131 <posix.html#1131>`_

+

+   `SIG_DFL`:idx:

+     `posix.html#719 <posix.html#719>`_

+

+   `sigemptyset`:idx:

+     `posix.html#1132 <posix.html#1132>`_

+

+   `SIG_ERR`:idx:

+     `posix.html#720 <posix.html#720>`_

+

+   `SIGEV_NONE`:idx:

+     `posix.html#723 <posix.html#723>`_

+

+   `SIGEV_SIGNAL`:idx:

+     `posix.html#724 <posix.html#724>`_

+

+   `SIGEV_THREAD`:idx:

+     `posix.html#725 <posix.html#725>`_

+

+   `sigfillset`:idx:

+     `posix.html#1133 <posix.html#1133>`_

+

+   `SIGFPE`:idx:

+     `posix.html#731 <posix.html#731>`_

+

+   `sighold`:idx:

+     `posix.html#1134 <posix.html#1134>`_

+

+   `SIGHUP`:idx:

+     `posix.html#732 <posix.html#732>`_

+

+   `SIG_IGN`:idx:

+     `posix.html#722 <posix.html#722>`_

+

+   `sigignore`:idx:

+     `posix.html#1135 <posix.html#1135>`_

+

+   `SIGILL`:idx:

+     `posix.html#733 <posix.html#733>`_

+

+   `SIGINT`:idx:

+     `posix.html#734 <posix.html#734>`_

+

+   `siginterrupt`:idx:

+     `posix.html#1136 <posix.html#1136>`_

+

+   `sigismember`:idx:

+     `posix.html#1137 <posix.html#1137>`_

+

+   `SIGKILL`:idx:

+     `posix.html#735 <posix.html#735>`_

+

+   `signal`:idx:

+     `posix.html#1138 <posix.html#1138>`_

+

+   `sigpause`:idx:

+     `posix.html#1139 <posix.html#1139>`_

+

+   `sigpending`:idx:

+     `posix.html#1140 <posix.html#1140>`_

+

+   `SIGPIPE`:idx:

+     `posix.html#736 <posix.html#736>`_

+

+   `SIGPOLL`:idx:

+     `posix.html#746 <posix.html#746>`_

+

+   `sigprocmask`:idx:

+     `posix.html#1141 <posix.html#1141>`_

+

+   `SIGPROF`:idx:

+     `posix.html#747 <posix.html#747>`_

+

+   `sigqueue`:idx:

+     `posix.html#1142 <posix.html#1142>`_

+

+   `SIGQUIT`:idx:

+     `posix.html#737 <posix.html#737>`_

+

+   `sigrelse`:idx:

+     `posix.html#1143 <posix.html#1143>`_

+

+   `SIGSEGV`:idx:

+     `posix.html#738 <posix.html#738>`_

+

+   `sigset`:idx:

+     `posix.html#1144 <posix.html#1144>`_

+

+   `SIG_SETMASK`:idx:

+     `posix.html#757 <posix.html#757>`_

+

+   `SIGSTKSZ`:idx:

+     `posix.html#767 <posix.html#767>`_

+

+   `SIGSTOP`:idx:

+     `posix.html#739 <posix.html#739>`_

+

+   `sigsuspend`:idx:

+     `posix.html#1145 <posix.html#1145>`_

+

+   `SIGSYS`:idx:

+     `posix.html#748 <posix.html#748>`_

+

+   `SIGTERM`:idx:

+     `posix.html#740 <posix.html#740>`_

+

+   `sigtimedwait`:idx:

+     `posix.html#1146 <posix.html#1146>`_

+

+   `SIGTRAP`:idx:

+     `posix.html#749 <posix.html#749>`_

+

+   `SIGTSTP`:idx:

+     `posix.html#741 <posix.html#741>`_

+

+   `SIGTTIN`:idx:

+     `posix.html#742 <posix.html#742>`_

+

+   `SIGTTOU`:idx:

+     `posix.html#743 <posix.html#743>`_

+

+   `SIG_UNBLOCK`:idx:

+     `posix.html#756 <posix.html#756>`_

+

+   `SIGURG`:idx:

+     `posix.html#750 <posix.html#750>`_

+

+   `SIGUSR1`:idx:

+     `posix.html#744 <posix.html#744>`_

+

+   `SIGUSR2`:idx:

+     `posix.html#745 <posix.html#745>`_

+

+   `SIGVTALRM`:idx:

+     `posix.html#751 <posix.html#751>`_

+

+   `sigwait`:idx:

+     `posix.html#1147 <posix.html#1147>`_

+

+   `sigwaitinfo`:idx:

+     `posix.html#1148 <posix.html#1148>`_

+

+   `SIGXCPU`:idx:

+     `posix.html#752 <posix.html#752>`_

+

+   `SIGXFSZ`:idx:

+     `posix.html#753 <posix.html#753>`_

+

+   `simple assertions`:idx:

+     `regexprs.html#103 <regexprs.html#103>`_

+

+   `simple statements`:idx:

+     `manual.html#174 <manual.html#174>`_

+

+   `sinh`:idx:

+     `math.html#124 <math.html#124>`_

+

+   `S_IRGRP`:idx:

+     `posix.html#662 <posix.html#662>`_

+

+   `S_IROTH`:idx:

+     `posix.html#666 <posix.html#666>`_

+

+   `S_IRUSR`:idx:

+     `posix.html#658 <posix.html#658>`_

+

+   `S_IRWXG`:idx:

+     `posix.html#661 <posix.html#661>`_

+

+   `S_IRWXO`:idx:

+     `posix.html#665 <posix.html#665>`_

+

+   `S_IRWXU`:idx:

+     `posix.html#657 <posix.html#657>`_

+

+   `S_ISBLK`:idx:

+     `posix.html#1067 <posix.html#1067>`_

+

+   `S_ISCHR`:idx:

+     `posix.html#1068 <posix.html#1068>`_

+

+   `S_ISDIR`:idx:

+     `posix.html#1069 <posix.html#1069>`_

+

+   `S_ISFIFO`:idx:

+     `posix.html#1070 <posix.html#1070>`_

+

+   `S_ISGID`:idx:

+     `posix.html#670 <posix.html#670>`_

+

+   `S_ISLNK`:idx:

+     `posix.html#1072 <posix.html#1072>`_

+

+   `S_ISREG`:idx:

+     `posix.html#1071 <posix.html#1071>`_

+

+   `S_ISSOCK`:idx:

+     `posix.html#1073 <posix.html#1073>`_

+

+   `S_ISUID`:idx:

+     `posix.html#669 <posix.html#669>`_

+

+   `S_ISVTX`:idx:

+     `posix.html#671 <posix.html#671>`_

+

+   `S_IWGRP`:idx:

+     `posix.html#663 <posix.html#663>`_

+

+   `S_IWOTH`:idx:

+     `posix.html#667 <posix.html#667>`_

+

+   `S_IWUSR`:idx:

+     `posix.html#659 <posix.html#659>`_

+

+   `S_IXGRP`:idx:

+     `posix.html#664 <posix.html#664>`_

+

+   `S_IXOTH`:idx:

+     `posix.html#668 <posix.html#668>`_

+

+   `S_IXUSR`:idx:

+     `posix.html#660 <posix.html#660>`_

+

+   `sizeof`:idx:

+     `system.html#156 <system.html#156>`_

+

+   `sleep`:idx:

+     `posix.html#1030 <posix.html#1030>`_

+

+   `split`:idx:

+     `strutils.html#119 <strutils.html#119>`_

+

+   `SplitFilename`:idx:

+     `os.html#125 <os.html#125>`_

+

+   `splitLines`:idx:

+     `strutils.html#120 <strutils.html#120>`_

+

+   `splitLinesSeq`:idx:

+     `strutils.html#121 <strutils.html#121>`_

+

+   `SplitPath`:idx:

+     `os.html#121 <os.html#121>`_

+

+   `splitSeq`:idx:

+     `strutils.html#122 <strutils.html#122>`_

+

+   `SQL_ACCESS_MODE`:idx:

+     `odbcsql.html#406 <odbcsql.html#406>`_

+

+   `SQL_ADD`:idx:

+     `odbcsql.html#317 <odbcsql.html#317>`_

+

+   `SQLAllocHandle`:idx:

+     `odbcsql.html#627 <odbcsql.html#627>`_

+

+   `SQL_ALL_TYPES`:idx:

+     `odbcsql.html#492 <odbcsql.html#492>`_

+

+   `SQL_API_SQLDESCRIBEPARAM`:idx:

+     `odbcsql.html#229 <odbcsql.html#229>`_

+

+   `SQL_ARD_TYPE`:idx:

+     `odbcsql.html#494 <odbcsql.html#494>`_

+

+   `SQL_ASYNC_ENABLE`:idx:

+     `odbcsql.html#383 <odbcsql.html#383>`_

+

+   `SQL_ATTR_ACCESS_MODE`:idx:

+     `odbcsql.html#415 <odbcsql.html#415>`_

+

+   `SQL_ATTR_APP_PARAM_DESC`:idx:

+     `odbcsql.html#374 <odbcsql.html#374>`_

+

+   `SQL_ATTR_APP_ROW_DESC`:idx:

+     `odbcsql.html#373 <odbcsql.html#373>`_

+

+   `SQL_ATTR_AUTOCOMMIT`:idx:

+     `odbcsql.html#400 <odbcsql.html#400>`_

+

+   `SQL_ATTR_AUTO_IPD`:idx:

+     `odbcsql.html#371 <odbcsql.html#371>`_

+

+   `SQL_ATTR_CONCURRENCY`:idx:

+     `odbcsql.html#395 <odbcsql.html#395>`_

+

+   `SQL_ATTR_CONNECTION_DEAD`:idx:

+     `odbcsql.html#416 <odbcsql.html#416>`_

+

+   `SQL_ATTR_CONNECTION_TIMEOUT`:idx:

+     `odbcsql.html#417 <odbcsql.html#417>`_

+

+   `SQL_ATTR_CURRENT_CATALOG`:idx:

+     `odbcsql.html#418 <odbcsql.html#418>`_

+

+   `SQL_ATTR_CURSOR_SCROLLABLE`:idx:

+     `odbcsql.html#377 <odbcsql.html#377>`_

+

+   `SQL_ATTR_CURSOR_SENSITIVITY`:idx:

+     `odbcsql.html#378 <odbcsql.html#378>`_

+

+   `SQL_ATTR_CURSOR_TYPE`:idx:

+     `odbcsql.html#394 <odbcsql.html#394>`_

+

+   `SQL_ATTR_DISCONNECT_BEHAVIOR`:idx:

+     `odbcsql.html#419 <odbcsql.html#419>`_

+

+   `SQL_ATTR_ENLIST_IN_DTC`:idx:

+     `odbcsql.html#420 <odbcsql.html#420>`_

+

+   `SQL_ATTR_ENLIST_IN_XA`:idx:

+     `odbcsql.html#421 <odbcsql.html#421>`_

+

+   `SQL_ATTR_FETCH_BOOKMARK_PTR`:idx:

+     `odbcsql.html#396 <odbcsql.html#396>`_

+

+   `SQL_ATTR_IMP_PARAM_DESC`:idx:

+     `odbcsql.html#376 <odbcsql.html#376>`_

+

+   `SQL_ATTR_IMP_ROW_DESC`:idx:

+     `odbcsql.html#375 <odbcsql.html#375>`_

+

+   `SQL_ATTR_LOGIN_TIMEOUT`:idx:

+     `odbcsql.html#422 <odbcsql.html#422>`_

+

+   `SQL_ATTR_MAX_ROWS`:idx:

+     `odbcsql.html#404 <odbcsql.html#404>`_

+

+   `SQL_ATTR_METADATA_ID`:idx:

+     `odbcsql.html#372 <odbcsql.html#372>`_

+

+   `SQL_ATTR_ODBC_CURSORS`:idx:

+     `odbcsql.html#341 <odbcsql.html#341>`_

+

+   `SQL_ATTR_ODBC_VERSION`:idx:

+     `odbcsql.html#240 <odbcsql.html#240>`_

+

+   `SQL_ATTR_OUTPUT_NTS`:idx:

+     `odbcsql.html#370 <odbcsql.html#370>`_

+

+   `SQL_ATTR_PACKET_SIZE`:idx:

+     `odbcsql.html#423 <odbcsql.html#423>`_

+

+   `SQL_ATTR_QUIET_MODE`:idx:

+     `odbcsql.html#424 <odbcsql.html#424>`_

+

+   `SQL_ATTR_ROW_ARRAY_SIZE`:idx:

+     `odbcsql.html#620 <odbcsql.html#620>`_

+

+   `SQL_ATTR_ROW_NUMBER`:idx:

+     `odbcsql.html#401 <odbcsql.html#401>`_

+

+   `SQL_ATTR_ROWS_FETCHED_PTR`:idx:

+     `odbcsql.html#398 <odbcsql.html#398>`_

+

+   `SQL_ATTR_ROW_STATUS_PTR`:idx:

+     `odbcsql.html#397 <odbcsql.html#397>`_

+

+   `SQL_ATTR_TRACE`:idx:

+     `odbcsql.html#425 <odbcsql.html#425>`_

+

+   `SQL_ATTR_TRACEFILE`:idx:

+     `odbcsql.html#426 <odbcsql.html#426>`_

+

+   `SQL_ATTR_TRANSLATE_LIB`:idx:

+     `odbcsql.html#427 <odbcsql.html#427>`_

+

+   `SQL_ATTR_TRANSLATE_OPTION`:idx:

+     `odbcsql.html#428 <odbcsql.html#428>`_

+

+   `SQL_ATTR_TXN_ISOLATION`:idx:

+     `odbcsql.html#403 <odbcsql.html#403>`_

+

+   `SQL_ATTR_USE_BOOKMARKS`:idx:

+     `odbcsql.html#405 <odbcsql.html#405>`_

+

+   `SQL_AUTOCOMMIT`:idx:

+     `odbcsql.html#399 <odbcsql.html#399>`_

+

+   `SQL_AUTOCOMMIT_DEFAULT`:idx:

+     `odbcsql.html#434 <odbcsql.html#434>`_

+

+   `SQL_AUTOCOMMIT_OFF`:idx:

+     `odbcsql.html#432 <odbcsql.html#432>`_

+

+   `SQL_AUTOCOMMIT_ON`:idx:

+     `odbcsql.html#433 <odbcsql.html#433>`_

+

+   `SQL_BEST_ROWID`:idx:

+     `odbcsql.html#523 <odbcsql.html#523>`_

+

+   `SQL_BIGINT`:idx:

+     `odbcsql.html#130 <odbcsql.html#130>`_

+

+   `SQL_BINARY`:idx:

+     `odbcsql.html#127 <odbcsql.html#127>`_

+

+   `SQLBindCol`:idx:

+     `odbcsql.html#652 <odbcsql.html#652>`_

+

+   `SQLBindParameter`:idx:

+     `odbcsql.html#660 <odbcsql.html#660>`_

+

+   `SQL_BIND_TYPE`:idx:

+     `odbcsql.html#384 <odbcsql.html#384>`_

+

+   `SQL_BIT`:idx:

+     `odbcsql.html#132 <odbcsql.html#132>`_

+

+   `SQL_BOOKMARK_PERSISTENCE`:idx:

+     `odbcsql.html#262 <odbcsql.html#262>`_

+

+   `SQL_BP_CLOSE`:idx:

+     `odbcsql.html#264 <odbcsql.html#264>`_

+

+   `SQL_BP_DELETE`:idx:

+     `odbcsql.html#265 <odbcsql.html#265>`_

+

+   `SQL_BP_DROP`:idx:

+     `odbcsql.html#266 <odbcsql.html#266>`_

+

+   `SQL_BP_OTHER_HSTMT`:idx:

+     `odbcsql.html#269 <odbcsql.html#269>`_

+

+   `SQL_BP_SCROLL`:idx:

+     `odbcsql.html#270 <odbcsql.html#270>`_

+

+   `SQL_BP_TRANSACTION`:idx:

+     `odbcsql.html#267 <odbcsql.html#267>`_

+

+   `SQL_BP_UPDATE`:idx:

+     `odbcsql.html#268 <odbcsql.html#268>`_

+

+   `SQLBrowseConnect`:idx:

+     `odbcsql.html#636 <odbcsql.html#636>`_

+

+   `SQLBulkOperations`:idx:

+     `odbcsql.html#650 <odbcsql.html#650>`_

+

+   `SQL_CA1_ABSOLUTE`:idx:

+     `odbcsql.html#282 <odbcsql.html#282>`_

+

+   `SQL_CA1_BOOKMARK`:idx:

+     `odbcsql.html#284 <odbcsql.html#284>`_

+

+   `SQL_CA1_BULK_ADD`:idx:

+     `odbcsql.html#295 <odbcsql.html#295>`_

+

+   `SQL_CA1_BULK_DELETE_BY_BOOKMARK`:idx:

+     `odbcsql.html#297 <odbcsql.html#297>`_

+

+   `SQL_CA1_BULK_FETCH_BY_BOOKMARK`:idx:

+     `odbcsql.html#298 <odbcsql.html#298>`_

+

+   `SQL_CA1_BULK_UPDATE_BY_BOOKMARK`:idx:

+     `odbcsql.html#296 <odbcsql.html#296>`_

+

+   `SQL_CA1_LOCK_EXCLUSIVE`:idx:

+     `odbcsql.html#286 <odbcsql.html#286>`_

+

+   `SQL_CA1_LOCK_NO_CHANGE`:idx:

+     `odbcsql.html#285 <odbcsql.html#285>`_

+

+   `SQL_CA1_LOCK_UNLOCK`:idx:

+     `odbcsql.html#287 <odbcsql.html#287>`_

+

+   `SQL_CA1_NEXT`:idx:

+     `odbcsql.html#281 <odbcsql.html#281>`_

+

+   `SQL_CA1_POS_DELETE`:idx:

+     `odbcsql.html#290 <odbcsql.html#290>`_

+

+   `SQL_CA1_POSITIONED_DELETE`:idx:

+     `odbcsql.html#293 <odbcsql.html#293>`_

+

+   `SQL_CA1_POSITIONED_UPDATE`:idx:

+     `odbcsql.html#292 <odbcsql.html#292>`_

+

+   `SQL_CA1_POS_POSITION`:idx:

+     `odbcsql.html#288 <odbcsql.html#288>`_

+

+   `SQL_CA1_POS_REFRESH`:idx:

+     `odbcsql.html#291 <odbcsql.html#291>`_

+

+   `SQL_CA1_POS_UPDATE`:idx:

+     `odbcsql.html#289 <odbcsql.html#289>`_

+

+   `SQL_CA1_RELATIVE`:idx:

+     `odbcsql.html#283 <odbcsql.html#283>`_

+

+   `SQL_CA1_SELECT_FOR_UPDATE`:idx:

+     `odbcsql.html#294 <odbcsql.html#294>`_

+

+   `SQL_CA2_CRC_APPROXIMATE`:idx:

+     `odbcsql.html#313 <odbcsql.html#313>`_

+

+   `SQL_CA2_CRC_EXACT`:idx:

+     `odbcsql.html#312 <odbcsql.html#312>`_

+

+   `SQL_CA2_LOCK_CONCURRENCY`:idx:

+     `odbcsql.html#300 <odbcsql.html#300>`_

+

+   `SQL_CA2_MAX_ROWS_AFFECTS_ALL`:idx:

+     `odbcsql.html#311 <odbcsql.html#311>`_

+

+   `SQL_CA2_MAX_ROWS_CATALOG`:idx:

+     `odbcsql.html#310 <odbcsql.html#310>`_

+

+   `SQL_CA2_MAX_ROWS_DELETE`:idx:

+     `odbcsql.html#308 <odbcsql.html#308>`_

+

+   `SQL_CA2_MAX_ROWS_INSERT`:idx:

+     `odbcsql.html#307 <odbcsql.html#307>`_

+

+   `SQL_CA2_MAX_ROWS_SELECT`:idx:

+     `odbcsql.html#306 <odbcsql.html#306>`_

+

+   `SQL_CA2_MAX_ROWS_UPDATE`:idx:

+     `odbcsql.html#309 <odbcsql.html#309>`_

+

+   `SQL_CA2_OPT_ROWVER_CONCURRENCY`:idx:

+     `odbcsql.html#301 <odbcsql.html#301>`_

+

+   `SQL_CA2_OPT_VALUES_CONCURRENCY`:idx:

+     `odbcsql.html#302 <odbcsql.html#302>`_

+

+   `SQL_CA2_READ_ONLY_CONCURRENCY`:idx:

+     `odbcsql.html#299 <odbcsql.html#299>`_

+

+   `SQL_CA2_SENSITIVITY_ADDITIONS`:idx:

+     `odbcsql.html#303 <odbcsql.html#303>`_

+

+   `SQL_CA2_SENSITIVITY_DELETIONS`:idx:

+     `odbcsql.html#304 <odbcsql.html#304>`_

+

+   `SQL_CA2_SENSITIVITY_UPDATES`:idx:

+     `odbcsql.html#305 <odbcsql.html#305>`_

+

+   `SQL_CA2_SIMULATE_NON_UNIQUE`:idx:

+     `odbcsql.html#314 <odbcsql.html#314>`_

+

+   `SQL_CA2_SIMULATE_TRY_UNIQUE`:idx:

+     `odbcsql.html#315 <odbcsql.html#315>`_

+

+   `SQL_CA2_SIMULATE_UNIQUE`:idx:

+     `odbcsql.html#316 <odbcsql.html#316>`_

+

+   `SQL_CATALOG_NAME`:idx:

+     `odbcsql.html#545 <odbcsql.html#545>`_

+

+   `SQL_C_BINARY`:idx:

+     `odbcsql.html#212 <odbcsql.html#212>`_

+

+   `SQL_C_BIT`:idx:

+     `odbcsql.html#213 <odbcsql.html#213>`_

+

+   `SQL_C_BOOKMARK`:idx:

+     `odbcsql.html#223 <odbcsql.html#223>`_

+

+   `SQL_C_CHAR`:idx:

+     `odbcsql.html#184 <odbcsql.html#184>`_

+

+   `SQL_C_DATE`:idx:

+     `odbcsql.html#193 <odbcsql.html#193>`_

+

+   `SQL_C_DEFAULT`:idx:

+     `odbcsql.html#190 <odbcsql.html#190>`_

+

+   `SQL_C_DOUBLE`:idx:

+     `odbcsql.html#188 <odbcsql.html#188>`_

+

+   `SQL_C_FLOAT`:idx:

+     `odbcsql.html#187 <odbcsql.html#187>`_

+

+   `SQL_C_GUID`:idx:

+     `odbcsql.html#224 <odbcsql.html#224>`_

+

+   `SQL_CHAR`:idx:

+     `odbcsql.html#136 <odbcsql.html#136>`_

+

+   `SQL_C_INTERVAL_DAY`:idx:

+     `odbcsql.html#201 <odbcsql.html#201>`_

+

+   `SQL_C_INTERVAL_DAY_TO_HOUR`:idx:

+     `odbcsql.html#206 <odbcsql.html#206>`_

+

+   `SQL_C_INTERVAL_DAY_TO_MINUTE`:idx:

+     `odbcsql.html#207 <odbcsql.html#207>`_

+

+   `SQL_C_INTERVAL_DAY_TO_SECOND`:idx:

+     `odbcsql.html#208 <odbcsql.html#208>`_

+

+   `SQL_C_INTERVAL_HOUR`:idx:

+     `odbcsql.html#202 <odbcsql.html#202>`_

+

+   `SQL_C_INTERVAL_HOUR_TO_MINUTE`:idx:

+     `odbcsql.html#209 <odbcsql.html#209>`_

+

+   `SQL_C_INTERVAL_HOUR_TO_SECOND`:idx:

+     `odbcsql.html#210 <odbcsql.html#210>`_

+

+   `SQL_C_INTERVAL_MINUTE`:idx:

+     `odbcsql.html#203 <odbcsql.html#203>`_

+

+   `SQL_C_INTERVAL_MINUTE_TO_SECOND`:idx:

+     `odbcsql.html#211 <odbcsql.html#211>`_

+

+   `SQL_C_INTERVAL_MONTH`:idx:

+     `odbcsql.html#200 <odbcsql.html#200>`_

+

+   `SQL_C_INTERVAL_SECOND`:idx:

+     `odbcsql.html#204 <odbcsql.html#204>`_

+

+   `SQL_C_INTERVAL_YEAR`:idx:

+     `odbcsql.html#199 <odbcsql.html#199>`_

+

+   `SQL_C_INTERVAL_YEAR_TO_MONTH`:idx:

+     `odbcsql.html#205 <odbcsql.html#205>`_

+

+   `SQL_C_LONG`:idx:

+     `odbcsql.html#185 <odbcsql.html#185>`_

+

+   `SQL_CLOSE`:idx:

+     `odbcsql.html#503 <odbcsql.html#503>`_

+

+   `SQLCloseCursor`:idx:

+     `odbcsql.html#639 <odbcsql.html#639>`_

+

+   `SQL_C_NUMERIC`:idx:

+     `odbcsql.html#189 <odbcsql.html#189>`_

+

+   `SQL_CODE_DATE`:idx:

+     `odbcsql.html#495 <odbcsql.html#495>`_

+

+   `SQL_CODE_DAY`:idx:

+     `odbcsql.html#156 <odbcsql.html#156>`_

+

+   `SQL_CODE_DAY_TO_HOUR`:idx:

+     `odbcsql.html#161 <odbcsql.html#161>`_

+

+   `SQL_CODE_DAY_TO_MINUTE`:idx:

+     `odbcsql.html#162 <odbcsql.html#162>`_

+

+   `SQL_CODE_DAY_TO_SECOND`:idx:

+     `odbcsql.html#163 <odbcsql.html#163>`_

+

+   `SQL_CODE_HOUR`:idx:

+     `odbcsql.html#157 <odbcsql.html#157>`_

+

+   `SQL_CODE_HOUR_TO_MINUTE`:idx:

+     `odbcsql.html#164 <odbcsql.html#164>`_

+

+   `SQL_CODE_HOUR_TO_SECOND`:idx:

+     `odbcsql.html#165 <odbcsql.html#165>`_

+

+   `SQL_CODE_MINUTE`:idx:

+     `odbcsql.html#158 <odbcsql.html#158>`_

+

+   `SQL_CODE_MINUTE_TO_SECOND`:idx:

+     `odbcsql.html#166 <odbcsql.html#166>`_

+

+   `SQL_CODE_MONTH`:idx:

+     `odbcsql.html#155 <odbcsql.html#155>`_

+

+   `SQL_CODE_SECOND`:idx:

+     `odbcsql.html#159 <odbcsql.html#159>`_

+

+   `SQL_CODE_TIME`:idx:

+     `odbcsql.html#496 <odbcsql.html#496>`_

+

+   `SQL_CODE_TIMESTAMP`:idx:

+     `odbcsql.html#497 <odbcsql.html#497>`_

+

+   `SQL_CODE_YEAR`:idx:

+     `odbcsql.html#154 <odbcsql.html#154>`_

+

+   `SQL_CODE_YEAR_TO_MONTH`:idx:

+     `odbcsql.html#160 <odbcsql.html#160>`_

+

+   `SQL_COLATT_OPT_MAX`:idx:

+     `odbcsql.html#588 <odbcsql.html#588>`_

+

+   `SQLColAttribute`:idx:

+     `odbcsql.html#662 <odbcsql.html#662>`_

+

+   `SQL_COLLATION_SEQ`:idx:

+     `odbcsql.html#546 <odbcsql.html#546>`_

+

+   `SQL_COLUMN_AUTO_INCREMENT`:idx:

+     `odbcsql.html#580 <odbcsql.html#580>`_

+

+   `SQL_COLUMN_CASE_SENSITIVE`:idx:

+     `odbcsql.html#581 <odbcsql.html#581>`_

+

+   `SQL_COLUMN_COUNT`:idx:

+     `odbcsql.html#569 <odbcsql.html#569>`_

+

+   `SQL_COLUMN_DISPLAY_SIZE`:idx:

+     `odbcsql.html#575 <odbcsql.html#575>`_

+

+   `SQL_COLUMN_DRIVER_START`:idx:

+     `odbcsql.html#589 <odbcsql.html#589>`_

+

+   `SQL_COLUMN_LABEL`:idx:

+     `odbcsql.html#587 <odbcsql.html#587>`_

+

+   `SQL_COLUMN_LENGTH`:idx:

+     `odbcsql.html#572 <odbcsql.html#572>`_

+

+   `SQL_COLUMN_MONEY`:idx:

+     `odbcsql.html#578 <odbcsql.html#578>`_

+

+   `SQL_COLUMN_NAME`:idx:

+     `odbcsql.html#570 <odbcsql.html#570>`_

+

+   `SQL_COLUMN_NULLABLE`:idx:

+     `odbcsql.html#576 <odbcsql.html#576>`_

+

+   `SQL_COLUMN_OWNER_NAME`:idx:

+     `odbcsql.html#585 <odbcsql.html#585>`_

+

+   `SQL_COLUMN_PRECISION`:idx:

+     `odbcsql.html#573 <odbcsql.html#573>`_

+

+   `SQL_COLUMN_QUALIFIER_NAME`:idx:

+     `odbcsql.html#586 <odbcsql.html#586>`_

+

+   `SQLColumns`:idx:

+     `odbcsql.html#665 <odbcsql.html#665>`_

+

+   `SQL_COLUMN_SCALE`:idx:

+     `odbcsql.html#574 <odbcsql.html#574>`_

+

+   `SQL_COLUMN_SEARCHABLE`:idx:

+     `odbcsql.html#582 <odbcsql.html#582>`_

+

+   `SQL_COLUMN_TABLE_NAME`:idx:

+     `odbcsql.html#584 <odbcsql.html#584>`_

+

+   `SQL_COLUMN_TYPE`:idx:

+     `odbcsql.html#571 <odbcsql.html#571>`_

+

+   `SQL_COLUMN_TYPE_NAME`:idx:

+     `odbcsql.html#583 <odbcsql.html#583>`_

+

+   `SQL_COLUMN_UNSIGNED`:idx:

+     `odbcsql.html#577 <odbcsql.html#577>`_

+

+   `SQL_COLUMN_UPDATABLE`:idx:

+     `odbcsql.html#579 <odbcsql.html#579>`_

+

+   `SQL_COMMIT`:idx:

+     `odbcsql.html#618 <odbcsql.html#618>`_

+

+   `SQL_CONCUR_DEFAULT`:idx:

+     `odbcsql.html#446 <odbcsql.html#446>`_

+

+   `SQL_CONCUR_LOCK`:idx:

+     `odbcsql.html#443 <odbcsql.html#443>`_

+

+   `SQL_CONCUR_READ_ONLY`:idx:

+     `odbcsql.html#442 <odbcsql.html#442>`_

+

+   `SQL_CONCURRENCY`:idx:

+     `odbcsql.html#386 <odbcsql.html#386>`_

+

+   `SQL_CONCUR_ROWVER`:idx:

+     `odbcsql.html#444 <odbcsql.html#444>`_

+

+   `SQL_CONCUR_VALUES`:idx:

+     `odbcsql.html#445 <odbcsql.html#445>`_

+

+   `SQLConnect`:idx:

+     `odbcsql.html#633 <odbcsql.html#633>`_

+

+   `SQL_C_SBIGINT`:idx:

+     `odbcsql.html#214 <odbcsql.html#214>`_

+

+   `SQL_C_SHORT`:idx:

+     `odbcsql.html#186 <odbcsql.html#186>`_

+

+   `SQL_C_SLONG`:idx:

+     `odbcsql.html#217 <odbcsql.html#217>`_

+

+   `SQL_C_SSHORT`:idx:

+     `odbcsql.html#218 <odbcsql.html#218>`_

+

+   `SQL_C_STINYINT`:idx:

+     `odbcsql.html#219 <odbcsql.html#219>`_

+

+   `SQL_C_TIME`:idx:

+     `odbcsql.html#194 <odbcsql.html#194>`_

+

+   `SQL_C_TIMESTAMP`:idx:

+     `odbcsql.html#195 <odbcsql.html#195>`_

+

+   `SQL_C_TINYINT`:idx:

+     `odbcsql.html#216 <odbcsql.html#216>`_

+

+   `SQL_C_TYPE_DATE`:idx:

+     `odbcsql.html#196 <odbcsql.html#196>`_

+

+   `SQL_C_TYPE_TIME`:idx:

+     `odbcsql.html#197 <odbcsql.html#197>`_

+

+   `SQL_C_TYPE_TIMESTAMP`:idx:

+     `odbcsql.html#198 <odbcsql.html#198>`_

+

+   `SQL_C_UBIGINT`:idx:

+     `odbcsql.html#215 <odbcsql.html#215>`_

+

+   `SQL_C_ULONG`:idx:

+     `odbcsql.html#220 <odbcsql.html#220>`_

+

+   `SQL_CUR_DEFAULT`:idx:

+     `odbcsql.html#345 <odbcsql.html#345>`_

+

+   `SQL_CURRENT_QUALIFIER`:idx:

+     `odbcsql.html#412 <odbcsql.html#412>`_

+

+   `SQL_CURSOR_DYNAMIC`:idx:

+     `odbcsql.html#439 <odbcsql.html#439>`_

+

+   `SQL_CURSOR_FORWARD_ONLY`:idx:

+     `odbcsql.html#437 <odbcsql.html#437>`_

+

+   `SQL_CURSOR_KEYSET_DRIVEN`:idx:

+     `odbcsql.html#438 <odbcsql.html#438>`_

+

+   `SQL_CURSOR_SENSITIVITY`:idx:

+     `odbcsql.html#543 <odbcsql.html#543>`_

+

+   `SQL_CURSOR_STATIC`:idx:

+     `odbcsql.html#440 <odbcsql.html#440>`_

+

+   `SQL_CURSOR_TYPE`:idx:

+     `odbcsql.html#385 <odbcsql.html#385>`_

+

+   `SQL_CURSOR_TYPE_DEFAULT`:idx:

+     `odbcsql.html#441 <odbcsql.html#441>`_

+

+   `SQL_CUR_USE_DRIVER`:idx:

+     `odbcsql.html#344 <odbcsql.html#344>`_

+

+   `SQL_CUR_USE_IF_NEEDED`:idx:

+     `odbcsql.html#342 <odbcsql.html#342>`_

+

+   `SQL_CUR_USE_ODBC`:idx:

+     `odbcsql.html#343 <odbcsql.html#343>`_

+

+   `SQL_C_USHORT`:idx:

+     `odbcsql.html#221 <odbcsql.html#221>`_

+

+   `SQL_C_UTINYINT`:idx:

+     `odbcsql.html#222 <odbcsql.html#222>`_

+

+   `SQL_C_VARBOOKMARK`:idx:

+     `odbcsql.html#228 <odbcsql.html#228>`_

+

+   `SQL_DATA_AT_EXEC`:idx:

+     `odbcsql.html#353 <odbcsql.html#353>`_

+

+   `SQLDataSources`:idx:

+     `odbcsql.html#654 <odbcsql.html#654>`_

+

+   `SQL_DATE`:idx:

+     `odbcsql.html#149 <odbcsql.html#149>`_

+

+   `SQL_DATE_LEN`:idx:

+     `odbcsql.html#363 <odbcsql.html#363>`_

+

+   `SQL_DATE_STRUCT`:idx:

+     `odbcsql.html#231 <odbcsql.html#231>`_

+

+   `SQL_DATETIME`:idx:

+     `odbcsql.html#144 <odbcsql.html#144>`_

+

+   `SQL_DECIMAL`:idx:

+     `odbcsql.html#138 <odbcsql.html#138>`_

+

+   `SQL_DEFAULT`:idx:

+     `odbcsql.html#493 <odbcsql.html#493>`_

+

+   `SQL_DELETE`:idx:

+     `odbcsql.html#325 <odbcsql.html#325>`_

+

+   `SQL_DELETE_BY_BOOKMARK`:idx:

+     `odbcsql.html#320 <odbcsql.html#320>`_

+

+   `SQL_DESC_ALLOC_TYPE`:idx:

+     `odbcsql.html#460 <odbcsql.html#460>`_

+

+   `SQL_DESC_ARRAY_SIZE`:idx:

+     `odbcsql.html#590 <odbcsql.html#590>`_

+

+   `SQL_DESC_ARRAY_STATUS_PTR`:idx:

+     `odbcsql.html#591 <odbcsql.html#591>`_

+

+   `SQL_DESC_AUTO_UNIQUE_VALUE`:idx:

+     `odbcsql.html#592 <odbcsql.html#592>`_

+

+   `SQL_DESC_BASE_COLUMN_NAME`:idx:

+     `odbcsql.html#593 <odbcsql.html#593>`_

+

+   `SQL_DESC_BASE_TABLE_NAME`:idx:

+     `odbcsql.html#594 <odbcsql.html#594>`_

+

+   `SQL_DESC_BIND_OFFSET_PTR`:idx:

+     `odbcsql.html#595 <odbcsql.html#595>`_

+

+   `SQL_DESC_BIND_TYPE`:idx:

+     `odbcsql.html#596 <odbcsql.html#596>`_

+

+   `SQL_DESC_CASE_SENSITIVE`:idx:

+     `odbcsql.html#597 <odbcsql.html#597>`_

+

+   `SQL_DESC_CATALOG_NAME`:idx:

+     `odbcsql.html#598 <odbcsql.html#598>`_

+

+   `SQL_DESC_CONCISE_TYPE`:idx:

+     `odbcsql.html#599 <odbcsql.html#599>`_

+

+   `SQL_DESC_COUNT`:idx:

+     `odbcsql.html#447 <odbcsql.html#447>`_

+

+   `SQL_DESC_DATA_PTR`:idx:

+     `odbcsql.html#456 <odbcsql.html#456>`_

+

+   `SQL_DESC_DATETIME_INTERVAL_CODE`:idx:

+     `odbcsql.html#453 <odbcsql.html#453>`_

+

+   `SQL_DESC_DATETIME_INTERVAL_PRECISION`:idx:

+     `odbcsql.html#600 <odbcsql.html#600>`_

+

+   `SQL_DESC_DISPLAY_SIZE`:idx:

+     `odbcsql.html#601 <odbcsql.html#601>`_

+

+   `SQL_DESC_FIXED_PREC_SCALE`:idx:

+     `odbcsql.html#602 <odbcsql.html#602>`_

+

+   `SQL_DESC_INDICATOR_PTR`:idx:

+     `odbcsql.html#455 <odbcsql.html#455>`_

+

+   `SQL_DESC_LABEL`:idx:

+     `odbcsql.html#603 <odbcsql.html#603>`_

+

+   `SQL_DESC_LENGTH`:idx:

+     `odbcsql.html#449 <odbcsql.html#449>`_

+

+   `SQL_DESC_LITERAL_PREFIX`:idx:

+     `odbcsql.html#604 <odbcsql.html#604>`_

+

+   `SQL_DESC_LITERAL_SUFFIX`:idx:

+     `odbcsql.html#605 <odbcsql.html#605>`_

+

+   `SQL_DESC_LOCAL_TYPE_NAME`:idx:

+     `odbcsql.html#606 <odbcsql.html#606>`_

+

+   `SQL_DESC_MAXIMUM_SCALE`:idx:

+     `odbcsql.html#607 <odbcsql.html#607>`_

+

+   `SQL_DESC_MINIMUM_SCALE`:idx:

+     `odbcsql.html#608 <odbcsql.html#608>`_

+

+   `SQL_DESC_NAME`:idx:

+     `odbcsql.html#457 <odbcsql.html#457>`_

+

+   `SQL_DESC_NULLABLE`:idx:

+     `odbcsql.html#454 <odbcsql.html#454>`_

+

+   `SQL_DESC_NUM_PREC_RADIX`:idx:

+     `odbcsql.html#609 <odbcsql.html#609>`_

+

+   `SQL_DESC_OCTET_LENGTH`:idx:

+     `odbcsql.html#459 <odbcsql.html#459>`_

+

+   `SQL_DESC_OCTET_LENGTH_PTR`:idx:

+     `odbcsql.html#450 <odbcsql.html#450>`_

+

+   `SQL_DESC_PARAMETER_TYPE`:idx:

+     `odbcsql.html#610 <odbcsql.html#610>`_

+

+   `SQL_DESC_PRECISION`:idx:

+     `odbcsql.html#451 <odbcsql.html#451>`_

+

+   `SQLDescribeCol`:idx:

+     `odbcsql.html#643 <odbcsql.html#643>`_

+

+   `SQL_DESCRIBE_PARAMETER`:idx:

+     `odbcsql.html#544 <odbcsql.html#544>`_

+

+   `SQL_DESC_ROWS_PROCESSED_PTR`:idx:

+     `odbcsql.html#611 <odbcsql.html#611>`_

+

+   `SQL_DESC_SCALE`:idx:

+     `odbcsql.html#452 <odbcsql.html#452>`_

+

+   `SQL_DESC_SCHEMA_NAME`:idx:

+     `odbcsql.html#612 <odbcsql.html#612>`_

+

+   `SQL_DESC_SEARCHABLE`:idx:

+     `odbcsql.html#613 <odbcsql.html#613>`_

+

+   `SQL_DESC_TABLE_NAME`:idx:

+     `odbcsql.html#615 <odbcsql.html#615>`_

+

+   `SQL_DESC_TYPE`:idx:

+     `odbcsql.html#448 <odbcsql.html#448>`_

+

+   `SQL_DESC_TYPE_NAME`:idx:

+     `odbcsql.html#614 <odbcsql.html#614>`_

+

+   `SQL_DESC_UNNAMED`:idx:

+     `odbcsql.html#458 <odbcsql.html#458>`_

+

+   `SQL_DESC_UNSIGNED`:idx:

+     `odbcsql.html#616 <odbcsql.html#616>`_

+

+   `SQL_DESC_UPDATABLE`:idx:

+     `odbcsql.html#617 <odbcsql.html#617>`_

+

+   `SQL_DIAG_ALTER_TABLE`:idx:

+     `odbcsql.html#473 <odbcsql.html#473>`_

+

+   `SQL_DIAG_CLASS_ORIGIN`:idx:

+     `odbcsql.html#468 <odbcsql.html#468>`_

+

+   `SQL_DIAG_CONNECTION_NAME`:idx:

+     `odbcsql.html#470 <odbcsql.html#470>`_

+

+   `SQL_DIAG_CREATE_INDEX`:idx:

+     `odbcsql.html#474 <odbcsql.html#474>`_

+

+   `SQL_DIAG_CREATE_TABLE`:idx:

+     `odbcsql.html#475 <odbcsql.html#475>`_

+

+   `SQL_DIAG_CREATE_VIEW`:idx:

+     `odbcsql.html#476 <odbcsql.html#476>`_

+

+   `SQL_DIAG_DELETE_WHERE`:idx:

+     `odbcsql.html#477 <odbcsql.html#477>`_

+

+   `SQL_DIAG_DROP_INDEX`:idx:

+     `odbcsql.html#478 <odbcsql.html#478>`_

+

+   `SQL_DIAG_DROP_TABLE`:idx:

+     `odbcsql.html#479 <odbcsql.html#479>`_

+

+   `SQL_DIAG_DROP_VIEW`:idx:

+     `odbcsql.html#480 <odbcsql.html#480>`_

+

+   `SQL_DIAG_DYNAMIC_DELETE_CURSOR`:idx:

+     `odbcsql.html#481 <odbcsql.html#481>`_

+

+   `SQL_DIAG_DYNAMIC_FUNCTION`:idx:

+     `odbcsql.html#467 <odbcsql.html#467>`_

+

+   `SQL_DIAG_DYNAMIC_FUNCTION_CODE`:idx:

+     `odbcsql.html#472 <odbcsql.html#472>`_

+

+   `SQL_DIAG_DYNAMIC_UPDATE_CURSOR`:idx:

+     `odbcsql.html#482 <odbcsql.html#482>`_

+

+   `SQL_DIAG_GRANT`:idx:

+     `odbcsql.html#483 <odbcsql.html#483>`_

+

+   `SQL_DIAG_INSERT`:idx:

+     `odbcsql.html#484 <odbcsql.html#484>`_

+

+   `SQL_DIAG_MESSAGE_TEXT`:idx:

+     `odbcsql.html#466 <odbcsql.html#466>`_

+

+   `SQL_DIAG_NATIVE`:idx:

+     `odbcsql.html#465 <odbcsql.html#465>`_

+

+   `SQL_DIAG_NUMBER`:idx:

+     `odbcsql.html#462 <odbcsql.html#462>`_

+

+   `SQL_DIAG_RETURNCODE`:idx:

+     `odbcsql.html#461 <odbcsql.html#461>`_

+

+   `SQL_DIAG_REVOKE`:idx:

+     `odbcsql.html#485 <odbcsql.html#485>`_

+

+   `SQL_DIAG_ROW_COUNT`:idx:

+     `odbcsql.html#463 <odbcsql.html#463>`_

+

+   `SQL_DIAG_SELECT_CURSOR`:idx:

+     `odbcsql.html#486 <odbcsql.html#486>`_

+

+   `SQL_DIAG_SERVER_NAME`:idx:

+     `odbcsql.html#471 <odbcsql.html#471>`_

+

+   `SQL_DIAG_SQLSTATE`:idx:

+     `odbcsql.html#464 <odbcsql.html#464>`_

+

+   `SQL_DIAG_SUBCLASS_ORIGIN`:idx:

+     `odbcsql.html#469 <odbcsql.html#469>`_

+

+   `SQL_DIAG_UNKNOWN_STATEMENT`:idx:

+     `odbcsql.html#487 <odbcsql.html#487>`_

+

+   `SQL_DIAG_UPDATE_WHERE`:idx:

+     `odbcsql.html#488 <odbcsql.html#488>`_

+

+   `SQLDisconnect`:idx:

+     `odbcsql.html#634 <odbcsql.html#634>`_

+

+   `SQL_DOUBLE`:idx:

+     `odbcsql.html#143 <odbcsql.html#143>`_

+

+   `SQL_DRIVER_COMPLETE`:idx:

+     `odbcsql.html#242 <odbcsql.html#242>`_

+

+   `SQL_DRIVER_COMPLETE_REQUIRED`:idx:

+     `odbcsql.html#244 <odbcsql.html#244>`_

+

+   `SQLDriverConnect`:idx:

+     `odbcsql.html#635 <odbcsql.html#635>`_

+

+   `SQL_DRIVER_NOPROMPT`:idx:

+     `odbcsql.html#241 <odbcsql.html#241>`_

+

+   `SQL_DRIVER_PROMPT`:idx:

+     `odbcsql.html#243 <odbcsql.html#243>`_

+

+   `SQLDrivers`:idx:

+     `odbcsql.html#655 <odbcsql.html#655>`_

+

+   `SQL_DROP`:idx:

+     `odbcsql.html#504 <odbcsql.html#504>`_

+

+   `SQL_DYNAMIC_CURSOR_ATTRIBUTES1`:idx:

+     `odbcsql.html#271 <odbcsql.html#271>`_

+

+   `SQL_DYNAMIC_CURSOR_ATTRIBUTES2`:idx:

+     `odbcsql.html#272 <odbcsql.html#272>`_

+

+   `SQLEndTran`:idx:

+     `odbcsql.html#663 <odbcsql.html#663>`_

+

+   `SQL_ENSURE`:idx:

+     `odbcsql.html#529 <odbcsql.html#529>`_

+

+   `SQL_ERROR`:idx:

+     `odbcsql.html#357 <odbcsql.html#357>`_

+

+   `SQLExecDirect`:idx:

+     `odbcsql.html#637 <odbcsql.html#637>`_

+

+   `SQLExecute`:idx:

+     `odbcsql.html#640 <odbcsql.html#640>`_

+

+   `SQLExtendedFetch`:idx:

+     `odbcsql.html#645 <odbcsql.html#645>`_

+

+   `SQL_FALSE`:idx:

+     `odbcsql.html#498 <odbcsql.html#498>`_

+

+   `SQLFetch`:idx:

+     `odbcsql.html#641 <odbcsql.html#641>`_

+

+   `SQL_FETCH_ABSOLUTE`:idx:

+     `odbcsql.html#513 <odbcsql.html#513>`_

+

+   `SQL_FETCH_BOOKMARK`:idx:

+     `odbcsql.html#250 <odbcsql.html#250>`_

+

+   `SQL_FETCH_BY_BOOKMARK`:idx:

+     `odbcsql.html#321 <odbcsql.html#321>`_

+

+   `SQL_FETCH_FIRST`:idx:

+     `odbcsql.html#508 <odbcsql.html#508>`_

+

+   `SQL_FETCH_FIRST_SYSTEM`:idx:

+     `odbcsql.html#510 <odbcsql.html#510>`_

+

+   `SQL_FETCH_FIRST_USER`:idx:

+     `odbcsql.html#509 <odbcsql.html#509>`_

+

+   `SQL_FETCH_LAST`:idx:

+     `odbcsql.html#511 <odbcsql.html#511>`_

+

+   `SQL_FETCH_NEXT`:idx:

+     `odbcsql.html#507 <odbcsql.html#507>`_

+

+   `SQL_FETCH_PRIOR`:idx:

+     `odbcsql.html#512 <odbcsql.html#512>`_

+

+   `SQL_FETCH_RELATIVE`:idx:

+     `odbcsql.html#514 <odbcsql.html#514>`_

+

+   `SQLFetchScroll`:idx:

+     `odbcsql.html#644 <odbcsql.html#644>`_

+

+   `SQL_FLOAT`:idx:

+     `odbcsql.html#141 <odbcsql.html#141>`_

+

+   `SQL_FORWARD_ONLY_CURSOR_ATTRIBUTES1`:idx:

+     `odbcsql.html#273 <odbcsql.html#273>`_

+

+   `SQL_FORWARD_ONLY_CURSOR_ATTRIBUTES2`:idx:

+     `odbcsql.html#274 <odbcsql.html#274>`_

+

+   `SQLFreeHandle`:idx:

+     `odbcsql.html#630 <odbcsql.html#630>`_

+

+   `SQLFreeStmt`:idx:

+     `odbcsql.html#661 <odbcsql.html#661>`_

+

+   `SQL_GET_BOOKMARK`:idx:

+     `odbcsql.html#392 <odbcsql.html#392>`_

+

+   `SQLGetCursorName`:idx:

+     `odbcsql.html#657 <odbcsql.html#657>`_

+

+   `SQLGetData`:idx:

+     `odbcsql.html#646 <odbcsql.html#646>`_

+

+   `SQLGetDiagField`:idx:

+     `odbcsql.html#632 <odbcsql.html#632>`_

+

+   `SQLGetDiagRec`:idx:

+     `odbcsql.html#631 <odbcsql.html#631>`_

+

+   `SQLGetEnvAttr`:idx:

+     `odbcsql.html#629 <odbcsql.html#629>`_

+

+   `SQLGetInfo`:idx:

+     `odbcsql.html#649 <odbcsql.html#649>`_

+

+   `SQLGetStmtAttr`:idx:

+     `odbcsql.html#648 <odbcsql.html#648>`_

+

+   `SQL_GUID`:idx:

+     `odbcsql.html#153 <odbcsql.html#153>`_

+

+   `SQL_HANDLE_DBC`:idx:

+     `odbcsql.html#367 <odbcsql.html#367>`_

+

+   `SQL_HANDLE_DESC`:idx:

+     `odbcsql.html#369 <odbcsql.html#369>`_

+

+   `SQL_HANDLE_ENV`:idx:

+     `odbcsql.html#366 <odbcsql.html#366>`_

+

+   `SQL_HANDLE_STMT`:idx:

+     `odbcsql.html#368 <odbcsql.html#368>`_

+

+   `SQL_INDEX_ALL`:idx:

+     `odbcsql.html#527 <odbcsql.html#527>`_

+

+   `SQL_INDEX_CLUSTERED`:idx:

+     `odbcsql.html#531 <odbcsql.html#531>`_

+

+   `SQL_INDEX_HASHED`:idx:

+     `odbcsql.html#532 <odbcsql.html#532>`_

+

+   `SQL_INDEX_KEYWORDS`:idx:

+     `odbcsql.html#275 <odbcsql.html#275>`_

+

+   `SQL_INDEX_OTHER`:idx:

+     `odbcsql.html#533 <odbcsql.html#533>`_

+

+   `SQL_INDEX_UNIQUE`:idx:

+     `odbcsql.html#526 <odbcsql.html#526>`_

+

+   `SQL_INFO_SCHEMA_VIEWS`:idx:

+     `odbcsql.html#276 <odbcsql.html#276>`_

+

+   `SQL_INSENSITIVE`:idx:

+     `odbcsql.html#490 <odbcsql.html#490>`_

+

+   `SQL_INTEGER`:idx:

+     `odbcsql.html#139 <odbcsql.html#139>`_

+

+   `SQL_INTERVAL`:idx:

+     `odbcsql.html#152 <odbcsql.html#152>`_

+

+   `SQL_INTERVAL_DAY`:idx:

+     `odbcsql.html#169 <odbcsql.html#169>`_

+

+   `SQL_INTERVAL_DAY_TO_HOUR`:idx:

+     `odbcsql.html#174 <odbcsql.html#174>`_

+

+   `SQL_INTERVAL_DAY_TO_MINUTE`:idx:

+     `odbcsql.html#175 <odbcsql.html#175>`_

+

+   `SQL_INTERVAL_DAY_TO_SECOND`:idx:

+     `odbcsql.html#176 <odbcsql.html#176>`_

+

+   `SQL_INTERVAL_HOUR`:idx:

+     `odbcsql.html#170 <odbcsql.html#170>`_

+

+   `SQL_INTERVAL_HOUR_TO_MINUTE`:idx:

+     `odbcsql.html#177 <odbcsql.html#177>`_

+

+   `SQL_INTERVAL_HOUR_TO_SECOND`:idx:

+     `odbcsql.html#178 <odbcsql.html#178>`_

+

+   `SQL_INTERVAL_MINUTE`:idx:

+     `odbcsql.html#171 <odbcsql.html#171>`_

+

+   `SQL_INTERVAL_MINUTE_TO_SECOND`:idx:

+     `odbcsql.html#179 <odbcsql.html#179>`_

+

+   `SQL_INTERVAL_MONTH`:idx:

+     `odbcsql.html#168 <odbcsql.html#168>`_

+

+   `SQL_INTERVAL_SECOND`:idx:

+     `odbcsql.html#172 <odbcsql.html#172>`_

+

+   `SQL_INTERVAL_YEAR`:idx:

+     `odbcsql.html#167 <odbcsql.html#167>`_

+

+   `SQL_INTERVAL_YEAR_TO_MONTH`:idx:

+     `odbcsql.html#173 <odbcsql.html#173>`_

+

+   `SQL_INVALID_HANDLE`:idx:

+     `odbcsql.html#358 <odbcsql.html#358>`_

+

+   `SQL_IS_INTEGER`:idx:

+     `odbcsql.html#247 <odbcsql.html#247>`_

+

+   `SQL_IS_POINTER`:idx:

+     `odbcsql.html#245 <odbcsql.html#245>`_

+

+   `SQL_IS_SMALLINT`:idx:

+     `odbcsql.html#249 <odbcsql.html#249>`_

+

+   `SQL_IS_UINTEGER`:idx:

+     `odbcsql.html#246 <odbcsql.html#246>`_

+

+   `SQL_IS_USMALLINT`:idx:

+     `odbcsql.html#248 <odbcsql.html#248>`_

+

+   `SQL_KEYSET_CURSOR_ATTRIBUTES1`:idx:

+     `odbcsql.html#277 <odbcsql.html#277>`_

+

+   `SQL_KEYSET_CURSOR_ATTRIBUTES2`:idx:

+     `odbcsql.html#278 <odbcsql.html#278>`_

+

+   `SQL_KEYSET_SIZE`:idx:

+     `odbcsql.html#387 <odbcsql.html#387>`_

+

+   `SQL_LOCK_EXCLUSIVE`:idx:

+     `odbcsql.html#327 <odbcsql.html#327>`_

+

+   `SQL_LOCK_NO_CHANGE`:idx:

+     `odbcsql.html#326 <odbcsql.html#326>`_

+

+   `SQL_LOCK_UNLOCK`:idx:

+     `odbcsql.html#328 <odbcsql.html#328>`_

+

+   `SQL_LOGIN_TIMEOUT`:idx:

+     `odbcsql.html#407 <odbcsql.html#407>`_

+

+   `SQL_LONGVARBINARY`:idx:

+     `odbcsql.html#129 <odbcsql.html#129>`_

+

+   `SQL_LONGVARCHAR`:idx:

+     `odbcsql.html#126 <odbcsql.html#126>`_

+

+   `SQL_MAX_DSN_LENGTH`:idx:

+     `odbcsql.html#338 <odbcsql.html#338>`_

+

+   `SQL_MAX_IDENTIFIER_LEN`:idx:

+     `odbcsql.html#547 <odbcsql.html#547>`_

+

+   `SQL_MAXIMUM_IDENTIFIER_LENGTH`:idx:

+     `odbcsql.html#548 <odbcsql.html#548>`_

+

+   `SQL_MAX_LENGTH`:idx:

+     `odbcsql.html#382 <odbcsql.html#382>`_

+

+   `SQL_MAX_MESSAGE_LENGTH`:idx:

+     `odbcsql.html#362 <odbcsql.html#362>`_

+

+   `SQL_MAX_OPTION_STRING_LENGTH`:idx:

+     `odbcsql.html#339 <odbcsql.html#339>`_

+

+   `SQL_MAX_ROWS`:idx:

+     `odbcsql.html#380 <odbcsql.html#380>`_

+

+   `SQL_MODE_DEFAULT`:idx:

+     `odbcsql.html#431 <odbcsql.html#431>`_

+

+   `SQL_MODE_READ_ONLY`:idx:

+     `odbcsql.html#430 <odbcsql.html#430>`_

+

+   `SQL_MODE_READ_WRITE`:idx:

+     `odbcsql.html#429 <odbcsql.html#429>`_

+

+   `SQL_NAME_LEN`:idx:

+     `odbcsql.html#237 <odbcsql.html#237>`_

+

+   `SQL_NEED_DATA`:idx:

+     `odbcsql.html#360 <odbcsql.html#360>`_

+

+   `SQL_NO_DATA`:idx:

+     `odbcsql.html#356 <odbcsql.html#356>`_

+

+   `SQL_NONSCROLLABLE`:idx:

+     `odbcsql.html#435 <odbcsql.html#435>`_

+

+   `SQL_NO_NULLS`:idx:

+     `odbcsql.html#500 <odbcsql.html#500>`_

+

+   `SQL_NOSCAN`:idx:

+     `odbcsql.html#381 <odbcsql.html#381>`_

+

+   `SQL_NO_TOTAL`:idx:

+     `odbcsql.html#230 <odbcsql.html#230>`_

+

+   `SQL_NTS`:idx:

+     `odbcsql.html#361 <odbcsql.html#361>`_

+

+   `SQL_NULLABLE`:idx:

+     `odbcsql.html#501 <odbcsql.html#501>`_

+

+   `SQL_NULLABLE_UNKNOWN`:idx:

+     `odbcsql.html#502 <odbcsql.html#502>`_

+

+   `SQL_NULL_DATA`:idx:

+     `odbcsql.html#352 <odbcsql.html#352>`_

+

+   `SQL_NULL_HANDLE`:idx:

+     `odbcsql.html#519 <odbcsql.html#519>`_

+

+   `SQL_NULL_HDBC`:idx:

+     `odbcsql.html#516 <odbcsql.html#516>`_

+

+   `SQL_NULL_HDESC`:idx:

+     `odbcsql.html#518 <odbcsql.html#518>`_

+

+   `SQL_NULL_HENV`:idx:

+     `odbcsql.html#515 <odbcsql.html#515>`_

+

+   `SQL_NULL_HSTMT`:idx:

+     `odbcsql.html#517 <odbcsql.html#517>`_

+

+   `SQL_NUMERIC`:idx:

+     `odbcsql.html#137 <odbcsql.html#137>`_

+

+   `SQLNumResultCols`:idx:

+     `odbcsql.html#642 <odbcsql.html#642>`_

+

+   `SQL_ODBC_CURSORS`:idx:

+     `odbcsql.html#340 <odbcsql.html#340>`_

+

+   `SQL_OJ_CAPABILITIES`:idx:

+     `odbcsql.html#540 <odbcsql.html#540>`_

+

+   `SQL_OPT_TRACE`:idx:

+     `odbcsql.html#408 <odbcsql.html#408>`_

+

+   `SQL_OPT_TRACEFILE`:idx:

+     `odbcsql.html#409 <odbcsql.html#409>`_

+

+   `SQL_OUTER_JOIN_CAPABILITIES`:idx:

+     `odbcsql.html#541 <odbcsql.html#541>`_

+

+   `SQL_OV_ODBC2`:idx:

+     `odbcsql.html#239 <odbcsql.html#239>`_

+

+   `SQL_OV_ODBC3`:idx:

+     `odbcsql.html#238 <odbcsql.html#238>`_

+

+   `SQL_PACKET_SIZE`:idx:

+     `odbcsql.html#414 <odbcsql.html#414>`_

+

+   `SQL_PARAM_INPUT`:idx:

+     `odbcsql.html#347 <odbcsql.html#347>`_

+

+   `SQL_PARAM_INPUT_OUTPUT`:idx:

+     `odbcsql.html#348 <odbcsql.html#348>`_

+

+   `SQL_PARAM_OUTPUT`:idx:

+     `odbcsql.html#350 <odbcsql.html#350>`_

+

+   `SQL_PARAM_TYPE_UNKNOWN`:idx:

+     `odbcsql.html#346 <odbcsql.html#346>`_

+

+   `SQL_POSITION`:idx:

+     `odbcsql.html#322 <odbcsql.html#322>`_

+

+   `SQLPrepare`:idx:

+     `odbcsql.html#638 <odbcsql.html#638>`_

+

+   `SQLPrimaryKeys`:idx:

+     `odbcsql.html#668 <odbcsql.html#668>`_

+

+   `SQLProcedureColumns`:idx:

+     `odbcsql.html#669 <odbcsql.html#669>`_

+

+   `SQLProcedures`:idx:

+     `odbcsql.html#667 <odbcsql.html#667>`_

+

+   `SQLPutData`:idx:

+     `odbcsql.html#651 <odbcsql.html#651>`_

+

+   `SQL_QUERY_TIMEOUT`:idx:

+     `odbcsql.html#379 <odbcsql.html#379>`_

+

+   `SQL_QUICK`:idx:

+     `odbcsql.html#528 <odbcsql.html#528>`_

+

+   `SQL_QUIET_MODE`:idx:

+     `odbcsql.html#413 <odbcsql.html#413>`_

+

+   `SQL_REAL`:idx:

+     `odbcsql.html#142 <odbcsql.html#142>`_

+

+   `SQL_REFRESH`:idx:

+     `odbcsql.html#323 <odbcsql.html#323>`_

+

+   `SQL_RESET_PARAMS`:idx:

+     `odbcsql.html#506 <odbcsql.html#506>`_

+

+   `SQL_RESULT_COL`:idx:

+     `odbcsql.html#349 <odbcsql.html#349>`_

+

+   `SQL_RETRIEVE_DATA`:idx:

+     `odbcsql.html#390 <odbcsql.html#390>`_

+

+   `SQL_RETURN_VALUE`:idx:

+     `odbcsql.html#351 <odbcsql.html#351>`_

+

+   `SQL_ROLLBACK`:idx:

+     `odbcsql.html#619 <odbcsql.html#619>`_

+

+   `SQL_ROW_ADDED`:idx:

+     `odbcsql.html#333 <odbcsql.html#333>`_

+

+   `SQLRowCount`:idx:

+     `odbcsql.html#659 <odbcsql.html#659>`_

+

+   `SQL_ROW_DELETED`:idx:

+     `odbcsql.html#330 <odbcsql.html#330>`_

+

+   `SQL_ROW_ERROR`:idx:

+     `odbcsql.html#334 <odbcsql.html#334>`_

+

+   `SQL_ROW_IDENTIFIER`:idx:

+     `odbcsql.html#525 <odbcsql.html#525>`_

+

+   `SQL_ROW_IGNORE`:idx:

+     `odbcsql.html#337 <odbcsql.html#337>`_

+

+   `SQL_ROW_NOROW`:idx:

+     `odbcsql.html#332 <odbcsql.html#332>`_

+

+   `SQL_ROW_NUMBER`:idx:

+     `odbcsql.html#393 <odbcsql.html#393>`_

+

+   `SQL_ROW_PROCEED`:idx:

+     `odbcsql.html#336 <odbcsql.html#336>`_

+

+   `SQL_ROWSET_SIZE`:idx:

+     `odbcsql.html#388 <odbcsql.html#388>`_

+

+   `SQL_ROW_SUCCESS`:idx:

+     `odbcsql.html#329 <odbcsql.html#329>`_

+

+   `SQL_ROW_SUCCESS_WITH_INFO`:idx:

+     `odbcsql.html#335 <odbcsql.html#335>`_

+

+   `SQL_ROW_UPDATED`:idx:

+     `odbcsql.html#331 <odbcsql.html#331>`_

+

+   `SQL_ROWVER`:idx:

+     `odbcsql.html#524 <odbcsql.html#524>`_

+

+   `SQL_SCCO_LOCK`:idx:

+     `odbcsql.html#550 <odbcsql.html#550>`_

+

+   `SQL_SCCO_OPT_ROWVER`:idx:

+     `odbcsql.html#551 <odbcsql.html#551>`_

+

+   `SQL_SCCO_OPT_VALUES`:idx:

+     `odbcsql.html#552 <odbcsql.html#552>`_

+

+   `SQL_SCCO_READ_ONLY`:idx:

+     `odbcsql.html#549 <odbcsql.html#549>`_

+

+   `SQL_SCOPE_CURROW`:idx:

+     `odbcsql.html#520 <odbcsql.html#520>`_

+

+   `SQL_SCOPE_SESSION`:idx:

+     `odbcsql.html#522 <odbcsql.html#522>`_

+

+   `SQL_SCOPE_TRANSACTION`:idx:

+     `odbcsql.html#521 <odbcsql.html#521>`_

+

+   `SQL_SCROLLABLE`:idx:

+     `odbcsql.html#436 <odbcsql.html#436>`_

+

+   `SQL_SCROLL_CONCURRENCY`:idx:

+     `odbcsql.html#534 <odbcsql.html#534>`_

+

+   `SQL_SCROLL_OPTIONS`:idx:

+     `odbcsql.html#251 <odbcsql.html#251>`_

+

+   `SQL_SENSITIVE`:idx:

+     `odbcsql.html#491 <odbcsql.html#491>`_

+

+   `SQLSetConnectAttr`:idx:

+     `odbcsql.html#656 <odbcsql.html#656>`_

+

+   `SQLSetCursorName`:idx:

+     `odbcsql.html#658 <odbcsql.html#658>`_

+

+   `SQLSetEnvAttr`:idx:

+     `odbcsql.html#628 <odbcsql.html#628>`_

+

+   `SQLSetPos`:idx:

+     `odbcsql.html#653 <odbcsql.html#653>`_

+

+   `SQL_SETPOS_MAX_OPTION_VALUE`:idx:

+     `odbcsql.html#318 <odbcsql.html#318>`_

+

+   `SQLSetStmtAttr`:idx:

+     `odbcsql.html#647 <odbcsql.html#647>`_

+

+   `SQL_SIGNED_OFFSET`:idx:

+     `odbcsql.html#191 <odbcsql.html#191>`_

+

+   `SQL_SIMULATE_CURSOR`:idx:

+     `odbcsql.html#389 <odbcsql.html#389>`_

+

+   `SQL_SMALLINT`:idx:

+     `odbcsql.html#140 <odbcsql.html#140>`_

+

+   `SQL_SO_DYNAMIC`:idx:

+     `odbcsql.html#259 <odbcsql.html#259>`_

+

+   `SQL_SO_FORWARD_ONLY`:idx:

+     `odbcsql.html#257 <odbcsql.html#257>`_

+

+   `SQL_SO_KEYSET_DRIVEN`:idx:

+     `odbcsql.html#258 <odbcsql.html#258>`_

+

+   `SQL_SO_MIXED`:idx:

+     `odbcsql.html#260 <odbcsql.html#260>`_

+

+   `SQL_SO_STATIC`:idx:

+     `odbcsql.html#261 <odbcsql.html#261>`_

+

+   `SQLSpecialColumns`:idx:

+     `odbcsql.html#666 <odbcsql.html#666>`_

+

+   `SQL_SS_ADDITIONS`:idx:

+     `odbcsql.html#566 <odbcsql.html#566>`_

+

+   `SQL_SS_DELETIONS`:idx:

+     `odbcsql.html#567 <odbcsql.html#567>`_

+

+   `SQL_SS_UPDATES`:idx:

+     `odbcsql.html#568 <odbcsql.html#568>`_

+

+   `SQL_STATIC_CURSOR_ATTRIBUTES1`:idx:

+     `odbcsql.html#279 <odbcsql.html#279>`_

+

+   `SQL_STATIC_CURSOR_ATTRIBUTES2`:idx:

+     `odbcsql.html#280 <odbcsql.html#280>`_

+

+   `SQL_STATIC_SENSITIVITY`:idx:

+     `odbcsql.html#263 <odbcsql.html#263>`_

+

+   `SQLStatistics`:idx:

+     `odbcsql.html#670 <odbcsql.html#670>`_

+

+   `SQL_STILL_EXECUTING`:idx:

+     `odbcsql.html#359 <odbcsql.html#359>`_

+

+   `SQL_SUCCESS`:idx:

+     `odbcsql.html#354 <odbcsql.html#354>`_

+

+   `SQL_SUCCESS_WITH_INFO`:idx:

+     `odbcsql.html#355 <odbcsql.html#355>`_

+

+   `SQLTables`:idx:

+     `odbcsql.html#664 <odbcsql.html#664>`_

+

+   `SQL_TABLE_STAT`:idx:

+     `odbcsql.html#530 <odbcsql.html#530>`_

+

+   `SQL_TC_ALL`:idx:

+     `odbcsql.html#555 <odbcsql.html#555>`_

+

+   `SQL_TC_DDL_COMMIT`:idx:

+     `odbcsql.html#556 <odbcsql.html#556>`_

+

+   `SQL_TC_DDL_IGNORE`:idx:

+     `odbcsql.html#557 <odbcsql.html#557>`_

+

+   `SQL_TC_DML`:idx:

+     `odbcsql.html#554 <odbcsql.html#554>`_

+

+   `SQL_TC_NONE`:idx:

+     `odbcsql.html#553 <odbcsql.html#553>`_

+

+   `SQL_TIME`:idx:

+     `odbcsql.html#150 <odbcsql.html#150>`_

+

+   `SQL_TIME_LEN`:idx:

+     `odbcsql.html#364 <odbcsql.html#364>`_

+

+   `SQL_TIMESTAMP`:idx:

+     `odbcsql.html#151 <odbcsql.html#151>`_

+

+   `SQL_TIMESTAMP_LEN`:idx:

+     `odbcsql.html#365 <odbcsql.html#365>`_

+

+   `SQL_TIMESTAMP_STRUCT`:idx:

+     `odbcsql.html#235 <odbcsql.html#235>`_

+

+   `SQL_TIME_STRUCT`:idx:

+     `odbcsql.html#233 <odbcsql.html#233>`_

+

+   `SQL_TINYINT`:idx:

+     `odbcsql.html#131 <odbcsql.html#131>`_

+

+   `SQL_TRANSACTION_CAPABLE`:idx:

+     `odbcsql.html#536 <odbcsql.html#536>`_

+

+   `SQL_TRANSACTION_ISOLATION_OPTION`:idx:

+     `odbcsql.html#539 <odbcsql.html#539>`_

+

+   `SQL_TRANSACTION_READ_COMMITTED`:idx:

+     `odbcsql.html#561 <odbcsql.html#561>`_

+

+   `SQL_TRANSACTION_READ_UNCOMMITTED`:idx:

+     `odbcsql.html#559 <odbcsql.html#559>`_

+

+   `SQL_TRANSACTION_REPEATABLE_READ`:idx:

+     `odbcsql.html#563 <odbcsql.html#563>`_

+

+   `SQL_TRANSACTION_SERIALIZABLE`:idx:

+     `odbcsql.html#565 <odbcsql.html#565>`_

+

+   `SQL_TRANSLATE_DLL`:idx:

+     `odbcsql.html#410 <odbcsql.html#410>`_

+

+   `SQL_TRANSLATE_OPTION`:idx:

+     `odbcsql.html#411 <odbcsql.html#411>`_

+

+   `SQL_TRUE`:idx:

+     `odbcsql.html#499 <odbcsql.html#499>`_

+

+   `SQL_TXN_CAPABLE`:idx:

+     `odbcsql.html#535 <odbcsql.html#535>`_

+

+   `SQL_TXN_ISOLATION`:idx:

+     `odbcsql.html#402 <odbcsql.html#402>`_

+

+   `SQL_TXN_ISOLATION_OPTION`:idx:

+     `odbcsql.html#538 <odbcsql.html#538>`_

+

+   `SQL_TXN_READ_COMMITTED`:idx:

+     `odbcsql.html#560 <odbcsql.html#560>`_

+

+   `SQL_TXN_READ_UNCOMMITTED`:idx:

+     `odbcsql.html#558 <odbcsql.html#558>`_

+

+   `SQL_TXN_REPEATABLE_READ`:idx:

+     `odbcsql.html#562 <odbcsql.html#562>`_

+

+   `SQL_TXN_SERIALIZABLE`:idx:

+     `odbcsql.html#564 <odbcsql.html#564>`_

+

+   `SQL_TYPE_DATE`:idx:

+     `odbcsql.html#146 <odbcsql.html#146>`_

+

+   `SQL_TYPE_MAX`:idx:

+     `odbcsql.html#227 <odbcsql.html#227>`_

+

+   `SQL_TYPE_MIN`:idx:

+     `odbcsql.html#226 <odbcsql.html#226>`_

+

+   `SQL_TYPE_NULL`:idx:

+     `odbcsql.html#225 <odbcsql.html#225>`_

+

+   `SQL_TYPE_TIME`:idx:

+     `odbcsql.html#147 <odbcsql.html#147>`_

+

+   `SQL_TYPE_TIMESTAMP`:idx:

+     `odbcsql.html#148 <odbcsql.html#148>`_

+

+   `SQL_UB_DEFAULT`:idx:

+     `odbcsql.html#254 <odbcsql.html#254>`_

+

+   `SQL_UB_FIXED`:idx:

+     `odbcsql.html#255 <odbcsql.html#255>`_

+

+   `SQL_UB_OFF`:idx:

+     `odbcsql.html#252 <odbcsql.html#252>`_

+

+   `SQL_UB_ON`:idx:

+     `odbcsql.html#253 <odbcsql.html#253>`_

+

+   `SQL_UB_VARIABLE`:idx:

+     `odbcsql.html#256 <odbcsql.html#256>`_

+

+   `SQL_UNBIND`:idx:

+     `odbcsql.html#505 <odbcsql.html#505>`_

+

+   `SQL_UNICODE`:idx:

+     `odbcsql.html#180 <odbcsql.html#180>`_

+

+   `SQL_UNICODE_CHAR`:idx:

+     `odbcsql.html#183 <odbcsql.html#183>`_

+

+   `SQL_UNICODE_LONGVARCHAR`:idx:

+     `odbcsql.html#182 <odbcsql.html#182>`_

+

+   `SQL_UNICODE_VARCHAR`:idx:

+     `odbcsql.html#181 <odbcsql.html#181>`_

+

+   `SQL_UNKNOWN_TYPE`:idx:

+     `odbcsql.html#125 <odbcsql.html#125>`_

+

+   `SQL_UNSIGNED_OFFSET`:idx:

+     `odbcsql.html#192 <odbcsql.html#192>`_

+

+   `SQL_UNSPECIFIED`:idx:

+     `odbcsql.html#489 <odbcsql.html#489>`_

+

+   `SQL_UPDATE`:idx:

+     `odbcsql.html#324 <odbcsql.html#324>`_

+

+   `SQL_UPDATE_BY_BOOKMARK`:idx:

+     `odbcsql.html#319 <odbcsql.html#319>`_

+

+   `SQL_USE_BOOKMARKS`:idx:

+     `odbcsql.html#391 <odbcsql.html#391>`_

+

+   `SQL_USER_NAME`:idx:

+     `odbcsql.html#537 <odbcsql.html#537>`_

+

+   `SQL_VARBINARY`:idx:

+     `odbcsql.html#128 <odbcsql.html#128>`_

+

+   `SQL_VARCHAR`:idx:

+     `odbcsql.html#145 <odbcsql.html#145>`_

+

+   `SQL_WCHAR`:idx:

+     `odbcsql.html#133 <odbcsql.html#133>`_

+

+   `SQL_WLONGVARCHAR`:idx:

+     `odbcsql.html#135 <odbcsql.html#135>`_

+

+   `SQL_WVARCHAR`:idx:

+     `odbcsql.html#134 <odbcsql.html#134>`_

+

+   `SQL_XOPEN_CLI_YEAR`:idx:

+     `odbcsql.html#542 <odbcsql.html#542>`_

+

+   `sqrt`:idx:

+     * `math.html#110 <math.html#110>`_

+     * `complex.html#109 <complex.html#109>`_

+

+   `SS_DISABLE`:idx:

+     `posix.html#765 <posix.html#765>`_

+

+   `SS_ONSTACK`:idx:

+     `posix.html#764 <posix.html#764>`_

+

+   `stack_trace`:idx:

+     `nimrodc.html#108 <nimrodc.html#108>`_

+

+   `startsWith`:idx:

+     `strutils.html#137 <strutils.html#137>`_

+

+   `stat`:idx:

+     `posix.html#1065 <posix.html#1065>`_

+

+   `statement macros`:idx:

+     `tut2.html#114 <tut2.html#114>`_

+

+   `Statements`:idx:

+     `manual.html#173 <manual.html#173>`_

+

+   `static error`:idx:

+     `manual.html#109 <manual.html#109>`_

+

+   `static type`:idx:

+     `manual.html#103 <manual.html#103>`_

+

+   `statvfs`:idx:

+     `posix.html#1056 <posix.html#1056>`_

+

+   `stdcall`:idx:

+     `manual.html#164 <manual.html#164>`_

+

+   `stderr`:idx:

+     `system.html#485 <system.html#485>`_

+

+   `STDERR_FILENO`:idx:

+     `posix.html#127 <posix.html#127>`_

+

+   `stdin`:idx:

+     `system.html#483 <system.html#483>`_

+

+   `STDIN_FILENO`:idx:

+     `posix.html#128 <posix.html#128>`_

+

+   `stdout`:idx:

+     `system.html#484 <system.html#484>`_

+

+   `STDOUT_FILENO`:idx:

+     `posix.html#129 <posix.html#129>`_

+

+   `ST_NOSUID`:idx:

+     `posix.html#673 <posix.html#673>`_

+

+   `ST_RDONLY`:idx:

+     `posix.html#672 <posix.html#672>`_

+

+   `strerror`:idx:

+     `posix.html#1160 <posix.html#1160>`_

+

+   `strfmon`:idx:

+     `posix.html#848 <posix.html#848>`_

+

+   `strftime`:idx:

+     `posix.html#1110 <posix.html#1110>`_

+

+   `string`:idx:

+     * `manual.html#150 <manual.html#150>`_

+     * `system.html#111 <system.html#111>`_

+

+   `strip`:idx:

+     `strutils.html#105 <strutils.html#105>`_

+

+   `strptime`:idx:

+     `posix.html#1111 <posix.html#1111>`_

+

+   `strStart`:idx:

+     `strutils.html#103 <strutils.html#103>`_

+

+   `structured type`:idx:

+     `manual.html#151 <manual.html#151>`_

+

+   `strutils`:idx:

+     `nimrodc.html#117 <nimrodc.html#117>`_

+

+   `style-insensitive`:idx:

+     `manual.html#118 <manual.html#118>`_

+

+   `S_TYPEISMQ`:idx:

+     `posix.html#1074 <posix.html#1074>`_

+

+   `S_TYPEISSEM`:idx:

+     `posix.html#1075 <posix.html#1075>`_

+

+   `S_TYPEISSHM`:idx:

+     `posix.html#1076 <posix.html#1076>`_

+

+   `S_TYPEISTMO`:idx:

+     `posix.html#1077 <posix.html#1077>`_

+

+   `subrange`:idx:

+     * `manual.html#149 <manual.html#149>`_

+     * `tut1.html#115 <tut1.html#115>`_

+

+   `succ`:idx:

+     `system.html#157 <system.html#157>`_

+

+   `swab`:idx:

+     `posix.html#1031 <posix.html#1031>`_

+

+   `swap`:idx:

+     `system.html#419 <system.html#419>`_

+

+   `swapcontext`:idx:

+     `posix.html#1191 <posix.html#1191>`_

+

+   `symlink`:idx:

+     `posix.html#1032 <posix.html#1032>`_

+

+   `sync`:idx:

+     `posix.html#1033 <posix.html#1033>`_

+

+   `syscall`:idx:

+     `manual.html#171 <manual.html#171>`_

+

+   `sysconf`:idx:

+     `posix.html#1034 <posix.html#1034>`_

+

+   `system`:idx:

+     `manual.html#218 <manual.html#218>`_

+

+   `tabulator`:idx:

+     `manual.html#125 <manual.html#125>`_

+

+   `TAddress`:idx:

+     `system.html#372 <system.html#372>`_

+

+   `Taiocb`:idx:

+     `posix.html#204 <posix.html#204>`_

+

+   `TAllocfunc`:idx:

+     `zlib.html#108 <zlib.html#108>`_

+

+   `tan`:idx:

+     `math.html#125 <math.html#125>`_

+

+   `tanh`:idx:

+     `math.html#126 <math.html#126>`_

+

+   `TBaseLexer`:idx:

+     `lexbase.html#103 <lexbase.html#103>`_

+

+   `Tblkcnt`:idx:

+     `posix.html#143 <posix.html#143>`_

+

+   `Tblksize`:idx:

+     `posix.html#144 <posix.html#144>`_

+

+   `TCfgEvent`:idx:

+     `parsecfg.html#102 <parsecfg.html#102>`_

+

+   `TCfgEventKind`:idx:

+     `parsecfg.html#101 <parsecfg.html#101>`_

+

+   `TCfgParser`:idx:

+     `parsecfg.html#103 <parsecfg.html#103>`_

+

+   `tcgetpgrp`:idx:

+     `posix.html#1035 <posix.html#1035>`_

+

+   `TCharSet`:idx:

+     `strutils.html#101 <strutils.html#101>`_

+

+   `TClock`:idx:

+     `posix.html#145 <posix.html#145>`_

+

+   `TClockId`:idx:

+     `posix.html#146 <posix.html#146>`_

+

+   `TCmdLineKind`:idx:

+     `parseopt.html#101 <parseopt.html#101>`_

+

+   `TComplex`:idx:

+     `complex.html#101 <complex.html#101>`_

+

+   `tcsetpgrp`:idx:

+     `posix.html#1036 <posix.html#1036>`_

+

+   `TDev`:idx:

+     `posix.html#147 <posix.html#147>`_

+

+   `TDIR`:idx:

+     `posix.html#130 <posix.html#130>`_

+

+   `Tdirent`:idx:

+     `posix.html#131 <posix.html#131>`_

+

+   `telldir`:idx:

+     `posix.html#806 <posix.html#806>`_

+

+   `template`:idx:

+     `manual.html#209 <manual.html#209>`_

+

+   `TEndian`:idx:

+     `system.html#385 <system.html#385>`_

+

+   `Tfd_set`:idx:

+     `posix.html#201 <posix.html#201>`_

+

+   `Tfenv`:idx:

+     `posix.html#133 <posix.html#133>`_

+

+   `Tfexcept`:idx:

+     `posix.html#134 <posix.html#134>`_

+

+   `TFile`:idx:

+     `system.html#480 <system.html#480>`_

+

+   `TFileHandle`:idx:

+     `system.html#482 <system.html#482>`_

+

+   `TFileMode`:idx:

+     `system.html#481 <system.html#481>`_

+

+   `TFileStream`:idx:

+     `streams.html#119 <streams.html#119>`_

+

+   `TFloatClass`:idx:

+     `math.html#103 <math.html#103>`_

+

+   `Tflock`:idx:

+     `posix.html#132 <posix.html#132>`_

+

+   `T_FMT`:idx:

+     `posix.html#392 <posix.html#392>`_

+

+   `T_FMT_AMPM`:idx:

+     `posix.html#393 <posix.html#393>`_

+

+   `TFormatFlag`:idx:

+     `strtabs.html#111 <strtabs.html#111>`_

+

+   `TFreeFunc`:idx:

+     `zlib.html#109 <zlib.html#109>`_

+

+   `Tfsblkcnt`:idx:

+     `posix.html#148 <posix.html#148>`_

+

+   `Tfsfilcnt`:idx:

+     `posix.html#149 <posix.html#149>`_

+

+   `TFTW`:idx:

+     `posix.html#135 <posix.html#135>`_

+

+   `TGC_Strategy`:idx:

+     `system.html#463 <system.html#463>`_

+

+   `TGid`:idx:

+     `posix.html#150 <posix.html#150>`_

+

+   `TGlob`:idx:

+     `posix.html#136 <posix.html#136>`_

+

+   `TGroup`:idx:

+     `posix.html#137 <posix.html#137>`_

+

+   `THash`:idx:

+     `hashes.html#101 <hashes.html#101>`_

+

+   `THOUSEP`:idx:

+     `posix.html#440 <posix.html#440>`_

+

+   `Ticonv`:idx:

+     `posix.html#138 <posix.html#138>`_

+

+   `Tid`:idx:

+     `posix.html#151 <posix.html#151>`_

+

+   `time`:idx:

+     `posix.html#1112 <posix.html#1112>`_

+

+   `TimeInfoToTime`:idx:

+     `times.html#108 <times.html#108>`_

+

+   `TIMER_ABSTIME`:idx:

+     `posix.html#699 <posix.html#699>`_

+

+   `timer_create`:idx:

+     `posix.html#1113 <posix.html#1113>`_

+

+   `timer_delete`:idx:

+     `posix.html#1114 <posix.html#1114>`_

+

+   `timer_getoverrun`:idx:

+     `posix.html#1116 <posix.html#1116>`_

+

+   `timer_gettime`:idx:

+     `posix.html#1115 <posix.html#1115>`_

+

+   `timer_settime`:idx:

+     `posix.html#1117 <posix.html#1117>`_

+

+   `times`:idx:

+     `nimrodc.html#119 <nimrodc.html#119>`_

+

+   `timezone`:idx:

+     `posix.html#702 <posix.html#702>`_

+

+   `Tino`:idx:

+     `posix.html#152 <posix.html#152>`_

+

+   `TInternalState`:idx:

+     `zlib.html#110 <zlib.html#110>`_

+

+   `Tipc_perm`:idx:

+     `posix.html#182 <posix.html#182>`_

+

+   `titimerspec`:idx:

+     `posix.html#188 <posix.html#188>`_

+

+   `TKey`:idx:

+     `posix.html#153 <posix.html#153>`_

+

+   `Tlconv`:idx:

+     `posix.html#139 <posix.html#139>`_

+

+   `Tmcontext`:idx:

+     `posix.html#202 <posix.html#202>`_

+

+   `TMode`:idx:

+     `posix.html#154 <posix.html#154>`_

+

+   `TMonth`:idx:

+     `times.html#101 <times.html#101>`_

+

+   `TMqAttr`:idx:

+     `posix.html#141 <posix.html#141>`_

+

+   `TMqd`:idx:

+     `posix.html#140 <posix.html#140>`_

+

+   `Tnl_catd`:idx:

+     `posix.html#198 <posix.html#198>`_

+

+   `TNlink`:idx:

+     `posix.html#155 <posix.html#155>`_

+

+   `Tnl_item`:idx:

+     `posix.html#197 <posix.html#197>`_

+

+   `toBiggestFloat`:idx:

+     `system.html#401 <system.html#401>`_

+

+   `toBiggestInt`:idx:

+     `system.html#403 <system.html#403>`_

+

+   `toBin`:idx:

+     `strutils.html#142 <strutils.html#142>`_

+

+   `TObject`:idx:

+     `system.html#131 <system.html#131>`_

+

+   `TOff`:idx:

+     `posix.html#156 <posix.html#156>`_

+

+   `toFloat`:idx:

+     `system.html#400 <system.html#400>`_

+

+   `toHex`:idx:

+     `strutils.html#128 <strutils.html#128>`_

+

+   `toInt`:idx:

+     `system.html#402 <system.html#402>`_

+

+   `toLower`:idx:

+     * `strutils.html#106 <strutils.html#106>`_

+     * `strutils.html#107 <strutils.html#107>`_

+

+   `toOct`:idx:

+     `strutils.html#141 <strutils.html#141>`_

+

+   `toOctal`:idx:

+     `strutils.html#118 <strutils.html#118>`_

+

+   `TOptParser`:idx:

+     `parseopt.html#102 <parseopt.html#102>`_

+

+   `toString`:idx:

+     `strutils.html#133 <strutils.html#133>`_

+

+   `toU16`:idx:

+     `system.html#179 <system.html#179>`_

+

+   `toU32`:idx:

+     `system.html#180 <system.html#180>`_

+

+   `toU8`:idx:

+     `system.html#178 <system.html#178>`_

+

+   `toUpper`:idx:

+     * `strutils.html#108 <strutils.html#108>`_

+     * `strutils.html#109 <strutils.html#109>`_

+

+   `TPasswd`:idx:

+     `posix.html#142 <posix.html#142>`_

+

+   `TPathComponent`:idx:

+     `os.html#152 <os.html#152>`_

+

+   `TPid`:idx:

+     `posix.html#157 <posix.html#157>`_

+

+   `Tposix_spawnattr`:idx:

+     `posix.html#205 <posix.html#205>`_

+

+   `Tposix_spawn_file_actions`:idx:

+     `posix.html#206 <posix.html#206>`_

+

+   `Tposix_typed_mem_info`:idx:

+     `posix.html#185 <posix.html#185>`_

+

+   `Tpthread`:idx:

+     `posix.html#170 <posix.html#170>`_

+

+   `Tpthread_attr`:idx:

+     `posix.html#158 <posix.html#158>`_

+

+   `Tpthread_barrier`:idx:

+     `posix.html#159 <posix.html#159>`_

+

+   `Tpthread_barrierattr`:idx:

+     `posix.html#160 <posix.html#160>`_

+

+   `Tpthread_cond`:idx:

+     `posix.html#161 <posix.html#161>`_

+

+   `Tpthread_condattr`:idx:

+     `posix.html#162 <posix.html#162>`_

+

+   `Tpthread_key`:idx:

+     `posix.html#163 <posix.html#163>`_

+

+   `Tpthread_mutex`:idx:

+     `posix.html#164 <posix.html#164>`_

+

+   `Tpthread_mutexattr`:idx:

+     `posix.html#165 <posix.html#165>`_

+

+   `Tpthread_once`:idx:

+     `posix.html#166 <posix.html#166>`_

+

+   `Tpthread_rwlock`:idx:

+     `posix.html#167 <posix.html#167>`_

+

+   `Tpthread_rwlockattr`:idx:

+     `posix.html#168 <posix.html#168>`_

+

+   `Tpthread_spinlock`:idx:

+     `posix.html#169 <posix.html#169>`_

+

+   `traced`:idx:

+     * `manual.html#159 <manual.html#159>`_

+     * `tut1.html#121 <tut1.html#121>`_

+

+   `TResult`:idx:

+     `system.html#155 <system.html#155>`_

+

+   `truncate`:idx:

+     `posix.html#1037 <posix.html#1037>`_

+

+   `try`:idx:

+     * `manual.html#185 <manual.html#185>`_

+     * `tut2.html#108 <tut2.html#108>`_

+

+   `Tsched_param`:idx:

+     `posix.html#199 <posix.html#199>`_

+

+   `TSem`:idx:

+     `posix.html#181 <posix.html#181>`_

+

+   `TSigaction`:idx:

+     `posix.html#193 <posix.html#193>`_

+

+   `Tsig_atomic`:idx:

+     `posix.html#189 <posix.html#189>`_

+

+   `TsigEvent`:idx:

+     `posix.html#191 <posix.html#191>`_

+

+   `TsigInfo`:idx:

+     `posix.html#196 <posix.html#196>`_

+

+   `Tsigset`:idx:

+     `posix.html#190 <posix.html#190>`_

+

+   `TSigStack`:idx:

+     `posix.html#195 <posix.html#195>`_

+

+   `TsigVal`:idx:

+     `posix.html#192 <posix.html#192>`_

+

+   `TSqlChar`:idx:

+     `odbcsql.html#101 <odbcsql.html#101>`_

+

+   `TSqlDouble`:idx:

+     `odbcsql.html#113 <odbcsql.html#113>`_

+

+   `TSqlFloat`:idx:

+     `odbcsql.html#114 <odbcsql.html#114>`_

+

+   `TSqlHandle`:idx:

+     `odbcsql.html#104 <odbcsql.html#104>`_

+

+   `TSqlHDBC`:idx:

+     `odbcsql.html#106 <odbcsql.html#106>`_

+

+   `TSqlHDesc`:idx:

+     `odbcsql.html#108 <odbcsql.html#108>`_

+

+   `TSqlHEnv`:idx:

+     `odbcsql.html#105 <odbcsql.html#105>`_

+

+   `TSqlHStmt`:idx:

+     `odbcsql.html#107 <odbcsql.html#107>`_

+

+   `TSqlHWND`:idx:

+     `odbcsql.html#115 <odbcsql.html#115>`_

+

+   `TSqlInteger`:idx:

+     `odbcsql.html#109 <odbcsql.html#109>`_

+

+   `TSqlPointer`:idx:

+     `odbcsql.html#111 <odbcsql.html#111>`_

+

+   `TSqlReal`:idx:

+     `odbcsql.html#112 <odbcsql.html#112>`_

+

+   `TSqlSmallInt`:idx:

+     `odbcsql.html#102 <odbcsql.html#102>`_

+

+   `TSqlUInteger`:idx:

+     `odbcsql.html#110 <odbcsql.html#110>`_

+

+   `TSqlUSmallInt`:idx:

+     `odbcsql.html#103 <odbcsql.html#103>`_

+

+   `TStack`:idx:

+     `posix.html#194 <posix.html#194>`_

+

+   `TStat`:idx:

+     `posix.html#183 <posix.html#183>`_

+

+   `TStatvfs`:idx:

+     `posix.html#184 <posix.html#184>`_

+

+   `TStream`:idx:

+     `streams.html#102 <streams.html#102>`_

+

+   `TStringStream`:idx:

+     `streams.html#116 <streams.html#116>`_

+

+   `TStringTable`:idx:

+     `strtabs.html#102 <strtabs.html#102>`_

+

+   `TStringTableMode`:idx:

+     `strtabs.html#101 <strtabs.html#101>`_

+

+   `Tsuseconds`:idx:

+     `posix.html#171 <posix.html#171>`_

+

+   `Ttime`:idx:

+     `posix.html#172 <posix.html#172>`_

+

+   `TTime`:idx:

+     `times.html#103 <times.html#103>`_

+

+   `TTimeInfo`:idx:

+     `times.html#104 <times.html#104>`_

+

+   `Ttimer`:idx:

+     `posix.html#173 <posix.html#173>`_

+

+   `Ttimespec`:idx:

+     `posix.html#187 <posix.html#187>`_

+

+   `Ttimeval`:idx:

+     `posix.html#200 <posix.html#200>`_

+

+   `Ttm`:idx:

+     `posix.html#186 <posix.html#186>`_

+

+   `Ttrace_attr`:idx:

+     `posix.html#174 <posix.html#174>`_

+

+   `Ttrace_event_id`:idx:

+     `posix.html#175 <posix.html#175>`_

+

+   `Ttrace_event_set`:idx:

+     `posix.html#176 <posix.html#176>`_

+

+   `Ttrace_id`:idx:

+     `posix.html#177 <posix.html#177>`_

+

+   `ttyname`:idx:

+     `posix.html#1038 <posix.html#1038>`_

+

+   `ttyname_r`:idx:

+     `posix.html#1039 <posix.html#1039>`_

+

+   `Tucontext`:idx:

+     `posix.html#203 <posix.html#203>`_

+

+   `Tuid`:idx:

+     `posix.html#178 <posix.html#178>`_

+

+   `tuple`:idx:

+     `manual.html#154 <manual.html#154>`_

+

+   `Tuseconds`:idx:

+     `posix.html#179 <posix.html#179>`_

+

+   `Tutsname`:idx:

+     `posix.html#180 <posix.html#180>`_

+

+   `TWeekDay`:idx:

+     `times.html#102 <times.html#102>`_

+

+   `type`:idx:

+     * `manual.html#102 <manual.html#102>`_

+     * `manual.html#140 <manual.html#140>`_

+     * `manual.html#206 <manual.html#206>`_

+

+   `type casts`:idx:

+     `tut2.html#101 <tut2.html#101>`_

+

+   `type conversions`:idx:

+     `tut2.html#102 <tut2.html#102>`_

+

+   `type parameters`:idx:

+     * `manual.html#208 <manual.html#208>`_

+     * `tut2.html#110 <tut2.html#110>`_

+

+   `type suffix`:idx:

+     `manual.html#137 <manual.html#137>`_

+

+   `TZipArchive`:idx:

+     `zipfiles.html#101 <zipfiles.html#101>`_

+

+   `Tzip_source_callback`:idx:

+     `libzip.html#102 <libzip.html#102>`_

+

+   `Tzip_source_cmd`:idx:

+     `libzip.html#101 <libzip.html#101>`_

+

+   `Tzip_stat`:idx:

+     `libzip.html#104 <libzip.html#104>`_

+

+   `tzset`:idx:

+     `posix.html#1118 <posix.html#1118>`_

+

+   `TZStream`:idx:

+     `zlib.html#112 <zlib.html#112>`_

+

+   `TZStreamRec`:idx:

+     `zlib.html#113 <zlib.html#113>`_

+

+   `ualarm`:idx:

+     `posix.html#1040 <posix.html#1040>`_

+

+   `Uint`:idx:

+     `zlib.html#101 <zlib.html#101>`_

+

+   `Ulong`:idx:

+     `zlib.html#102 <zlib.html#102>`_

+

+   `Ulongf`:idx:

+     `zlib.html#103 <zlib.html#103>`_

+

+   `umask`:idx:

+     `posix.html#1066 <posix.html#1066>`_

+

+   `uname`:idx:

+     `posix.html#866 <posix.html#866>`_

+

+   `unchecked runtime error`:idx:

+     `manual.html#111 <manual.html#111>`_

+

+   `uncompress`:idx:

+     `zlib.html#156 <zlib.html#156>`_

+

+   `undef`:idx:

+     `manual.html#223 <manual.html#223>`_

+

+   `UnixToNativePath`:idx:

+     `os.html#124 <os.html#124>`_

+

+   `unlink`:idx:

+     `posix.html#1041 <posix.html#1041>`_

+

+   `unsigned integer`:idx:

+     * `manual.html#142 <manual.html#142>`_

+     * `tut1.html#108 <tut1.html#108>`_

+

+   `unsigned operations`:idx:

+     * `manual.html#143 <manual.html#143>`_

+     * `tut1.html#109 <tut1.html#109>`_

+

+   `untraced`:idx:

+     * `manual.html#160 <manual.html#160>`_

+     * `tut1.html#122 <tut1.html#122>`_

+

+   `usleep`:idx:

+     `posix.html#1042 <posix.html#1042>`_

+

+   `Var`:idx:

+     `manual.html#178 <manual.html#178>`_

+

+   `varargs`:idx:

+     `nimrodc.html#106 <nimrodc.html#106>`_

+

+   `variant`:idx:

+     * `manual.html#156 <manual.html#156>`_

+     * `tut2.html#103 <tut2.html#103>`_

+

+   `vertical tabulator`:idx:

+     `manual.html#126 <manual.html#126>`_

+

+   `vfork`:idx:

+     `posix.html#1043 <posix.html#1043>`_

+

+   `volatile`:idx:

+     `nimrodc.html#111 <nimrodc.html#111>`_

+

+   `wait`:idx:

+     `posix.html#1119 <posix.html#1119>`_

+

+   `waitid`:idx:

+     `posix.html#1120 <posix.html#1120>`_

+

+   `waitpid`:idx:

+     `posix.html#1121 <posix.html#1121>`_

+

+   `walkDir`:idx:

+     `os.html#153 <os.html#153>`_

+

+   `walkFiles`:idx:

+     * `os.html#151 <os.html#151>`_

+     * `zipfiles.html#110 <zipfiles.html#110>`_

+

+   `warning`:idx:

+     * `dialogs.html#103 <dialogs.html#103>`_

+     * `manual.html#220 <manual.html#220>`_

+     * `manual.html#226 <manual.html#226>`_

+

+   `WCONTINUED`:idx:

+     `posix.html#714 <posix.html#714>`_

+

+   `WEXITED`:idx:

+     `posix.html#712 <posix.html#712>`_

+

+   `WEXITSTATUS`:idx:

+     `posix.html#705 <posix.html#705>`_

+

+   `when`:idx:

+     * `manual.html#182 <manual.html#182>`_

+     * `tut1.html#106 <tut1.html#106>`_

+

+   `while`:idx:

+     `manual.html#194 <manual.html#194>`_

+

+   `Whitespace`:idx:

+     `strutils.html#102 <strutils.html#102>`_

+

+   `WIFCONTINUED`:idx:

+     `posix.html#706 <posix.html#706>`_

+

+   `WIFEXITED`:idx:

+     `posix.html#707 <posix.html#707>`_

+

+   `WIFSIGNALED`:idx:

+     `posix.html#708 <posix.html#708>`_

+

+   `WIFSTOPPED`:idx:

+     `posix.html#709 <posix.html#709>`_

+

+   `WNOHANG`:idx:

+     `posix.html#703 <posix.html#703>`_

+

+   `WNOWAIT`:idx:

+     `posix.html#715 <posix.html#715>`_

+

+   `W_OK`:idx:

+     `posix.html#480 <posix.html#480>`_

+

+   `write`:idx:

+     * `posix.html#1044 <posix.html#1044>`_

+     * `system.html#493 <system.html#493>`_

+     * `system.html#494 <system.html#494>`_

+     * `system.html#495 <system.html#495>`_

+     * `system.html#496 <system.html#496>`_

+     * `system.html#497 <system.html#497>`_

+     * `system.html#498 <system.html#498>`_

+     * `system.html#499 <system.html#499>`_

+     * `streams.html#103 <streams.html#103>`_

+     * `streams.html#104 <streams.html#104>`_

+

+   `writeBuffer`:idx:

+     `system.html#509 <system.html#509>`_

+

+   `writeBytes`:idx:

+     `system.html#507 <system.html#507>`_

+

+   `writeChars`:idx:

+     `system.html#508 <system.html#508>`_

+

+   `writeln`:idx:

+     * `system.html#501 <system.html#501>`_

+     * `system.html#502 <system.html#502>`_

+

+   `WSTOPPED`:idx:

+     `posix.html#713 <posix.html#713>`_

+

+   `WSTOPSIG`:idx:

+     `posix.html#710 <posix.html#710>`_

+

+   `WTERMSIG`:idx:

+     `posix.html#711 <posix.html#711>`_

+

+   `WUNTRACED`:idx:

+     `posix.html#704 <posix.html#704>`_

+

+   `X_OK`:idx:

+     `posix.html#481 <posix.html#481>`_

+

+   `xor`:idx:

+     * `system.html#118 <system.html#118>`_

+     * `system.html#241 <system.html#241>`_

+     * `system.html#242 <system.html#242>`_

+     * `system.html#243 <system.html#243>`_

+     * `system.html#244 <system.html#244>`_

+     * `system.html#245 <system.html#245>`_

+

+   `YESEXPR`:idx:

+     `posix.html#441 <posix.html#441>`_

+

+   `yield`:idx:

+     `manual.html#191 <manual.html#191>`_

+

+   `Z_ASCII`:idx:

+     `zlib.html#138 <zlib.html#138>`_

+

+   `Z_BEST_COMPRESSION`:idx:

+     `zlib.html#132 <zlib.html#132>`_

+

+   `Z_BEST_SPEED`:idx:

+     `zlib.html#131 <zlib.html#131>`_

+

+   `Z_BINARY`:idx:

+     `zlib.html#137 <zlib.html#137>`_

+

+   `Z_BUF_ERROR`:idx:

+     `zlib.html#128 <zlib.html#128>`_

+

+   `Z_DATA_ERROR`:idx:

+     `zlib.html#126 <zlib.html#126>`_

+

+   `Z_DEFAULT_COMPRESSION`:idx:

+     `zlib.html#133 <zlib.html#133>`_

+

+   `Z_DEFAULT_STRATEGY`:idx:

+     `zlib.html#136 <zlib.html#136>`_

+

+   `Z_DEFLATED`:idx:

+     `zlib.html#140 <zlib.html#140>`_

+

+   `ze`:idx:

+     * `system.html#172 <system.html#172>`_

+     * `system.html#173 <system.html#173>`_

+

+   `ze64`:idx:

+     * `system.html#174 <system.html#174>`_

+     * `system.html#175 <system.html#175>`_

+     * `system.html#176 <system.html#176>`_

+     * `system.html#177 <system.html#177>`_

+

+   `zeroMem`:idx:

+     `system.html#409 <system.html#409>`_

+

+   `Z_ERRNO`:idx:

+     `zlib.html#124 <zlib.html#124>`_

+

+   `zError`:idx:

+     `zlib.html#184 <zlib.html#184>`_

+

+   `Z_FILTERED`:idx:

+     `zlib.html#134 <zlib.html#134>`_

+

+   `Z_FINISH`:idx:

+     `zlib.html#120 <zlib.html#120>`_

+

+   `Z_FULL_FLUSH`:idx:

+     `zlib.html#119 <zlib.html#119>`_

+

+   `Z_HUFFMAN_ONLY`:idx:

+     `zlib.html#135 <zlib.html#135>`_

+

+   `zip_add`:idx:

+     `libzip.html#170 <libzip.html#170>`_

+

+   `zip_add_dir`:idx:

+     `libzip.html#171 <libzip.html#171>`_

+

+   `ZIP_AFL_TORRENT`:idx:

+     `libzip.html#116 <libzip.html#116>`_

+

+   `ZIP_CHECKCONS`:idx:

+     `libzip.html#110 <libzip.html#110>`_

+

+   `zip_close`:idx:

+     `libzip.html#172 <libzip.html#172>`_

+

+   `ZIP_CM_BZIP2`:idx:

+     `libzip.html#155 <libzip.html#155>`_

+

+   `ZIP_CM_DEFAULT`:idx:

+     `libzip.html#144 <libzip.html#144>`_

+

+   `ZIP_CM_DEFLATE`:idx:

+     `libzip.html#152 <libzip.html#152>`_

+

+   `ZIP_CM_DEFLATE64`:idx:

+     `libzip.html#153 <libzip.html#153>`_

+

+   `ZIP_CM_IMPLODE`:idx:

+     `libzip.html#151 <libzip.html#151>`_

+

+   `ZIP_CM_LZ77`:idx:

+     `libzip.html#158 <libzip.html#158>`_

+

+   `ZIP_CM_LZMA`:idx:

+     `libzip.html#156 <libzip.html#156>`_

+

+   `ZIP_CM_PKWARE_IMPLODE`:idx:

+     `libzip.html#154 <libzip.html#154>`_

+

+   `ZIP_CM_PPMD`:idx:

+     `libzip.html#160 <libzip.html#160>`_

+

+   `ZIP_CM_REDUCE_1`:idx:

+     `libzip.html#147 <libzip.html#147>`_

+

+   `ZIP_CM_REDUCE_2`:idx:

+     `libzip.html#148 <libzip.html#148>`_

+

+   `ZIP_CM_REDUCE_3`:idx:

+     `libzip.html#149 <libzip.html#149>`_

+

+   `ZIP_CM_REDUCE_4`:idx:

+     `libzip.html#150 <libzip.html#150>`_

+

+   `ZIP_CM_SHRINK`:idx:

+     `libzip.html#146 <libzip.html#146>`_

+

+   `ZIP_CM_STORE`:idx:

+     `libzip.html#145 <libzip.html#145>`_

+

+   `ZIP_CM_TERSE`:idx:

+     `libzip.html#157 <libzip.html#157>`_

+

+   `ZIP_CM_WAVPACK`:idx:

+     `libzip.html#159 <libzip.html#159>`_

+

+   `ZIP_CREATE`:idx:

+     `libzip.html#108 <libzip.html#108>`_

+

+   `zip_delete`:idx:

+     `libzip.html#173 <libzip.html#173>`_

+

+   `ZIP_EM_NONE`:idx:

+     `libzip.html#161 <libzip.html#161>`_

+

+   `ZIP_EM_TRAD_PKWARE`:idx:

+     `libzip.html#162 <libzip.html#162>`_

+

+   `ZIP_EM_UNKNOWN`:idx:

+     `libzip.html#163 <libzip.html#163>`_

+

+   `ZIP_ER_CHANGED`:idx:

+     `libzip.html#132 <libzip.html#132>`_

+

+   `ZIP_ER_CLOSE`:idx:

+     `libzip.html#120 <libzip.html#120>`_

+

+   `ZIP_ER_COMPNOTSUPP`:idx:

+     `libzip.html#133 <libzip.html#133>`_

+

+   `ZIP_ER_CRC`:idx:

+     `libzip.html#124 <libzip.html#124>`_

+

+   `ZIP_ER_DELETED`:idx:

+     `libzip.html#140 <libzip.html#140>`_

+

+   `ZIP_ER_EOF`:idx:

+     `libzip.html#134 <libzip.html#134>`_

+

+   `ZIP_ER_EXISTS`:idx:

+     `libzip.html#127 <libzip.html#127>`_

+

+   `ZIP_ER_INCONS`:idx:

+     `libzip.html#138 <libzip.html#138>`_

+

+   `ZIP_ER_INTERNAL`:idx:

+     `libzip.html#137 <libzip.html#137>`_

+

+   `ZIP_ER_INVAL`:idx:

+     `libzip.html#135 <libzip.html#135>`_

+

+   `ZIP_ER_MEMORY`:idx:

+     `libzip.html#131 <libzip.html#131>`_

+

+   `ZIP_ER_MULTIDISK`:idx:

+     `libzip.html#118 <libzip.html#118>`_

+

+   `ZIP_ER_NOENT`:idx:

+     `libzip.html#126 <libzip.html#126>`_

+

+   `ZIP_ER_NOZIP`:idx:

+     `libzip.html#136 <libzip.html#136>`_

+

+   `ZIP_ER_OK`:idx:

+     `libzip.html#117 <libzip.html#117>`_

+

+   `ZIP_ER_OPEN`:idx:

+     `libzip.html#128 <libzip.html#128>`_

+

+   `ZIP_ER_READ`:idx:

+     `libzip.html#122 <libzip.html#122>`_

+

+   `ZIP_ER_REMOVE`:idx:

+     `libzip.html#139 <libzip.html#139>`_

+

+   `ZIP_ER_RENAME`:idx:

+     `libzip.html#119 <libzip.html#119>`_

+

+   `zip_error_clear`:idx:

+     `libzip.html#174 <libzip.html#174>`_

+

+   `zip_error_get`:idx:

+     `libzip.html#175 <libzip.html#175>`_

+

+   `zip_error_get_sys_type`:idx:

+     `libzip.html#176 <libzip.html#176>`_

+

+   `zip_error_to_str`:idx:

+     `libzip.html#177 <libzip.html#177>`_

+

+   `ZIP_ER_SEEK`:idx:

+     `libzip.html#121 <libzip.html#121>`_

+

+   `ZIP_ER_TMPOPEN`:idx:

+     `libzip.html#129 <libzip.html#129>`_

+

+   `ZIP_ER_WRITE`:idx:

+     `libzip.html#123 <libzip.html#123>`_

+

+   `ZIP_ER_ZIPCLOSED`:idx:

+     `libzip.html#125 <libzip.html#125>`_

+

+   `ZIP_ER_ZLIB`:idx:

+     `libzip.html#130 <libzip.html#130>`_

+

+   `ZIP_ET_NONE`:idx:

+     `libzip.html#141 <libzip.html#141>`_

+

+   `ZIP_ET_SYS`:idx:

+     `libzip.html#142 <libzip.html#142>`_

+

+   `ZIP_ET_ZLIB`:idx:

+     `libzip.html#143 <libzip.html#143>`_

+

+   `ZIP_EXCL`:idx:

+     `libzip.html#109 <libzip.html#109>`_

+

+   `zip_fclose`:idx:

+     `libzip.html#178 <libzip.html#178>`_

+

+   `zip_file_error_clear`:idx:

+     `libzip.html#179 <libzip.html#179>`_

+

+   `zip_file_error_get`:idx:

+     `libzip.html#180 <libzip.html#180>`_

+

+   `zip_file_strerror`:idx:

+     `libzip.html#181 <libzip.html#181>`_

+

+   `ZIP_FL_COMPRESSED`:idx:

+     `libzip.html#113 <libzip.html#113>`_

+

+   `ZIP_FL_NOCASE`:idx:

+     `libzip.html#111 <libzip.html#111>`_

+

+   `ZIP_FL_NODIR`:idx:

+     `libzip.html#112 <libzip.html#112>`_

+

+   `ZIP_FL_RECOMPRESS`:idx:

+     `libzip.html#115 <libzip.html#115>`_

+

+   `ZIP_FL_UNCHANGED`:idx:

+     `libzip.html#114 <libzip.html#114>`_

+

+   `zip_fopen`:idx:

+     `libzip.html#182 <libzip.html#182>`_

+

+   `zip_fopen_index`:idx:

+     `libzip.html#183 <libzip.html#183>`_

+

+   `zip_fread`:idx:

+     `libzip.html#184 <libzip.html#184>`_

+

+   `zip_get_archive_comment`:idx:

+     `libzip.html#185 <libzip.html#185>`_

+

+   `zip_get_archive_flag`:idx:

+     `libzip.html#186 <libzip.html#186>`_

+

+   `zip_get_file_comment`:idx:

+     `libzip.html#187 <libzip.html#187>`_

+

+   `zip_get_name`:idx:

+     `libzip.html#188 <libzip.html#188>`_

+

+   `zip_get_num_files`:idx:

+     `libzip.html#189 <libzip.html#189>`_

+

+   `zip_name_locate`:idx:

+     `libzip.html#190 <libzip.html#190>`_

+

+   `zip_open`:idx:

+     `libzip.html#191 <libzip.html#191>`_

+

+   `zip_rename`:idx:

+     `libzip.html#192 <libzip.html#192>`_

+

+   `zip_replace`:idx:

+     `libzip.html#193 <libzip.html#193>`_

+

+   `zip_set_archive_comment`:idx:

+     `libzip.html#194 <libzip.html#194>`_

+

+   `zip_set_archive_flag`:idx:

+     `libzip.html#195 <libzip.html#195>`_

+

+   `zip_set_file_comment`:idx:

+     `libzip.html#196 <libzip.html#196>`_

+

+   `zip_source_buffer`:idx:

+     `libzip.html#197 <libzip.html#197>`_

+

+   `ZIP_SOURCE_CLOSE`:idx:

+     `libzip.html#166 <libzip.html#166>`_

+

+   `ZIP_SOURCE_ERROR`:idx:

+     `libzip.html#168 <libzip.html#168>`_

+

+   `zip_source_file`:idx:

+     `libzip.html#198 <libzip.html#198>`_

+

+   `zip_source_filep`:idx:

+     `libzip.html#199 <libzip.html#199>`_

+

+   `zip_source_free`:idx:

+     `libzip.html#200 <libzip.html#200>`_

+

+   `zip_source_function`:idx:

+     `libzip.html#201 <libzip.html#201>`_

+

+   `ZIP_SOURCE_OPEN`:idx:

+     `libzip.html#164 <libzip.html#164>`_

+

+   `ZIP_SOURCE_READ`:idx:

+     `libzip.html#165 <libzip.html#165>`_

+

+   `ZIP_SOURCE_STAT`:idx:

+     `libzip.html#167 <libzip.html#167>`_

+

+   `zip_source_zip`:idx:

+     `libzip.html#202 <libzip.html#202>`_

+

+   `zip_stat`:idx:

+     `libzip.html#203 <libzip.html#203>`_

+

+   `zip_stat_index`:idx:

+     `libzip.html#204 <libzip.html#204>`_

+

+   `zip_stat_init`:idx:

+     `libzip.html#205 <libzip.html#205>`_

+

+   `zip_strerror`:idx:

+     `libzip.html#206 <libzip.html#206>`_

+

+   `zip_unchange`:idx:

+     `libzip.html#207 <libzip.html#207>`_

+

+   `zip_unchange_all`:idx:

+     `libzip.html#208 <libzip.html#208>`_

+

+   `zip_unchange_archive`:idx:

+     `libzip.html#209 <libzip.html#209>`_

+

+   `zlibAllocMem`:idx:

+     `zlib.html#187 <zlib.html#187>`_

+

+   `zlibFreeMem`:idx:

+     `zlib.html#188 <zlib.html#188>`_

+

+   `zlibVersion`:idx:

+     `zlib.html#142 <zlib.html#142>`_

+

+   `Z_MEM_ERROR`:idx:

+     `zlib.html#127 <zlib.html#127>`_

+

+   `Z_NEED_DICT`:idx:

+     `zlib.html#123 <zlib.html#123>`_

+

+   `Z_NO_COMPRESSION`:idx:

+     `zlib.html#130 <zlib.html#130>`_

+

+   `Z_NO_FLUSH`:idx:

+     `zlib.html#116 <zlib.html#116>`_

+

+   `Z_NULL`:idx:

+     `zlib.html#141 <zlib.html#141>`_

+

+   `z_off_t`:idx:

+     `zlib.html#105 <zlib.html#105>`_

+

+   `Z_OK`:idx:

+     `zlib.html#121 <zlib.html#121>`_

+

+   `Z_PARTIAL_FLUSH`:idx:

+     `zlib.html#117 <zlib.html#117>`_

+

+   `Z_STREAM_END`:idx:

+     `zlib.html#122 <zlib.html#122>`_

+

+   `Z_STREAM_ERROR`:idx:

+     `zlib.html#125 <zlib.html#125>`_

+

+   `Z_SYNC_FLUSH`:idx:

+     `zlib.html#118 <zlib.html#118>`_

+

+   `Z_UNKNOWN`:idx:

+     `zlib.html#139 <zlib.html#139>`_

+

+   `Z_VERSION_ERROR`:idx:

      `zlib.html#129 <zlib.html#129>`_
\ No newline at end of file
diff --git a/doc/tut1.txt b/doc/tut1.txt
new file mode 100644
index 000000000..ef56c2caa
--- /dev/null
+++ b/doc/tut1.txt
@@ -0,0 +1,1382 @@
+============================
+The Nimrod Tutorial (Part I)
+============================
+
+:Author: Andreas Rumpf
+:Version: |nimrodversion|
+
+.. contents::
+
+Introduction
+============
+
+  "Before you run you must learn to walk."
+
+This document is a tutorial for the programming language *Nimrod*. After this
+tutorial you will have a decent knowledge about Nimrod. This tutorial assumes
+that you are familiar with basic programming concepts like variables, types
+or statements. 
+
+
+The first program
+=================
+
+We start the tour with a modified "hallo world" program:
+
+.. code-block:: Nimrod
+  # This is a comment
+  Echo("What's your name? ")
+  var name: string = readLine(stdin)
+  Echo("Hi, ", name, "!")
+
+
+Save this code to the file "greetings.nim". Now compile and run it::
+
+  nimrod compile --run greetings.nim
+
+As you see, with the ``--run`` switch Nimrod executes the file automatically
+after compilation. You can even give your program command line arguments by
+appending them after the filename::
+
+  nimrod compile --run greetings.nim arg1 arg2
+
+The most used commands and switches have abbreviations, so you can also use::
+
+  nimrod c -r greetings.nim
+
+Though it should be pretty obvious what the program does, I will explain the
+syntax: Statements which are not indented are executed when the program
+starts. Indentation is Nimrod's way of grouping statements. String literals
+are enclosed in double quotes. The ``var`` statement declares a new variable
+named ``name`` of type ``string`` with the value that is returned by the
+``readline`` procedure. Since the compiler knows that ``readline`` returns
+a string, you can leave out the type in the declaration (this is called
+`local type inference`:idx:). So this will work too:
+
+.. code-block:: Nimrod
+  var name = readline(stdin)
+
+Note that this is basically the only form of type inference that exists in
+Nimrod: It is a good compromise between brevity and readability.
+
+The "hallo world" program contains several identifiers that are already
+known to the compiler: ``echo``, ``readLine``, etc. These built-in items are
+declared in the system_ module which is implicitly imported by any other module.
+
+
+Lexical elements
+================
+
+Let us look at Nimrod's lexical elements in more detail: Like other
+programming languages Nimrod consists of (string) literals, identifiers,
+keywords, comments, operators, and other punctation marks. Case is
+*insignificant* in Nimrod and even underscores are ignored:
+``This_is_an_identifier`` and this is the same identifier
+``ThisIsAnIdentifier``. This feature enables you to use other
+peoples code without bothering about a naming convention that conflicts with
+yours. It also frees you from remembering the exact spelling of an identifier
+(was it ``parseURL`` or ``parseUrl`` or ``parse_URL``?).
+
+
+String and character literals
+-----------------------------
+
+String literals are enclosed in double quotes; character literals in single
+quotes. Special characters are escaped with ``\``: ``\n`` means newline, ``\t``
+means tabulator, etc. There exist also *raw* string literals:
+
+.. code-block:: Nimrod
+  r"C:\program files\nim"
+
+In raw literals the backslash is not an escape character, so they fit
+the principle *what you see is what you get*.
+
+The third and last way to write string literals are *long string literals*.
+They are written with three quotes: ``""" ... """``; they can span over
+multiple lines and the ``\`` is not an escape character either. They are very
+useful for embedding HTML code templates for example.
+
+
+Comments
+--------
+
+`Comments`:idx: start anywhere outside a string or character literal with the
+hash character ``#``. Documentation comments start with ``##``.
+Comments consist of a concatenation of `comment pieces`:idx:. A comment piece
+starts with ``#`` and runs until the end of the line. The end of line characters
+belong to the piece. If the next line only consists of a comment piece which is
+aligned to the preceding one, it does not start a new comment:
+
+.. code-block:: nimrod
+
+  i = 0     # This is a single comment over multiple lines belonging to the
+            # assignment statement. The scanner merges these two pieces.
+  # This is a new comment belonging to the current block, but to no particular
+  # statement.
+  i = i + 1 # This a new comment that is NOT
+  echo(i)   # continued here, because this comment refers to the echo statement
+
+Comments are tokens; they are only allowed at certain places in the input file
+as they belong to the syntax tree! This feature enables perfect source-to-source
+transformations (such as pretty-printing) and superior documentation generators.
+A nice side-effect is that the human reader of the code always knows exactly
+which code snippet the comment refers to. Since comments are a proper part of 
+the syntax, watch their indentation:
+
+.. code-block::
+  Echo("Hallo!")
+  # comment has the same indentation as above statement -> fine
+  Echo("Hi!")
+    # comment has not the right indentation -> syntax error!
+
+
+Numbers
+-------
+
+Numerical literals are written as in most other languages. As a special twist,
+underscores are allowed for better readability: ``1_000_000`` (one million).
+A number that contains a dot (or 'e' or 'E') is a floating point literal:
+``1.0e9`` (one million). Hexadecimal literals are prefixed with ``0x``,
+binary literals with ``0b`` and octal literals with ``0c``. A leading zero
+alone does not produce an octal.
+
+
+The var statement
+=================
+The var statement declares a new local or global variable:
+
+.. code-block::
+  var x, y: int # declares x and y to have the type ``int``
+
+Indentation can be used after the ``var`` keyword to list a whole section of
+variables: 
+
+.. code-block::
+  var
+    x, y: int
+    # a comment can occur here too
+    a, b, c: string
+
+
+The assignment statement
+========================
+
+The assignment statement assigns a new value to a variable or more generally
+to a storage location:
+
+.. code-block::
+  var x = "abc" # introduces a new variable `x` and assigns a value to it
+  x = "xyz"     # assigns a new value to `x`
+
+The ``=`` is called the *assignment operator*. The assignment operator cannot
+be overloaded, overwritten or forbidden, but this might change in a future
+version of Nimrod.
+
+
+Constants
+=========
+
+`Constants`:idx: are symbols which are bound to a value. The constant's value
+cannot change. The compiler must be able to evaluate the expression in a
+constant declaration at compile time:
+
+.. code-block:: nimrod
+  const x = "abc" # the constant x contains the string "abc"
+  
+Indentation can be used after the ``const`` keyword to list a whole section of
+constants: 
+
+.. code-block::
+  const
+    x = 1
+    # a comment can occur here too
+    y = 2
+    z = y + 5 # simple computations are possible
+
+
+Control flow statements
+=======================
+
+The greetings program consists of 3 statements that are executed sequentially.
+Only the most primitive programs can get away with that: Branching and looping
+are needed too.
+
+
+If statement
+------------
+
+The if statement is one way to branch the control flow:
+
+.. code-block:: nimrod
+  var name = readLine(stdin)
+  if name == "":
+    echo("Poor soul, you lost your name?")
+  elif name == "name":
+    echo("Very funny, your name is name.")
+  else:
+    Echo("Hi, ", name, "!")
+
+There can be zero or more elif parts, and the else part is optional. The
+keyword ``elif`` is short for ``else if``, and is useful to avoid excessive
+indentation. (The ``""`` is the empty string. It contains no characters.)
+
+
+Case statement
+--------------
+
+Another way to branch is provided by the case statement. A case statement is
+a multi-branch:
+
+.. code-block:: nimrod
+  var name = readLine(stdin)
+  case name
+  of "":
+    echo("Poor soul, you lost your name?")
+  of "name":
+    echo("Very funny, your name is name.")
+  of "Dave", "Frank":
+    echo("Cool name!")
+  else:
+    Echo("Hi, ", name, "!")
+
+As can be seen, for an ``of`` branch a comma separated list of values is also
+allowed.
+
+The case statement can deal with integers, other ordinal types and strings.
+(What an ordinal type is will be explained soon.)
+For integers or other ordinal types value ranges are also possible:
+
+.. code-block:: nimrod
+  # this statement will be explained later:
+  from strutils import parseInt
+
+  Echo("A number please: ")
+  var n = parseInt(readLine(stdin))
+  case n
+  of 0..2, 4..7: Echo("The number is in the set: {0, 1, 2, 4, 5, 6, 7}")
+  of 3, 8: Echo("The number is 3 or 8")
+
+However, the above code does not compile: The reason is that you have to cover
+every value that ``n`` may contain, but the code only handles the values
+``0..8``. Since it is not very practical to list every other possible integer
+(though it is possible thanks to the range notation!), we fix this by telling
+the compiler that for every other value nothing should be done:
+
+.. code-block:: nimrod
+  ...
+  case n
+  of 0..2, 4..7: Echo("The number is in the set: {0, 1, 2, 4, 5, 6, 7}")
+  of 3, 8: Echo("The number is 3 or 8")
+  else: nil
+
+The ``nil`` statement is a *do nothing* statement. The compiler knows that a
+case statement with an else part cannot fail and thus the error disappers. Note
+that it is impossible to cover any possible string value: That is why there is
+no such compiler check for string cases.
+
+In general the case statement is used for subrange types or enumerations where
+it is of great help that the compiler checks that you covered any possible
+value.
+
+
+
+While statement
+---------------
+
+The while statement is a simple looping construct:
+
+.. code-block:: nimrod
+
+  Echo("What's your name? ")
+  var name = readLine(stdin)
+  while name == "":
+    Echo("Please tell me your name: ")
+    name = readLine(stdin)
+    # no ``var``, because we do not declare a new variable here
+
+The example uses a while loop to keep asking the user for his name, as long as
+he types in nothing (only presses RETURN).
+
+
+For statement
+-------------
+
+The `for`:idx: statement is a construct to loop over any elements an *iterator*
+provides. The example uses the built-in ``countup`` iterator:
+
+.. code-block:: nimrod
+  Echo("Counting to ten: ")
+  for i in countup(1, 10):
+    Echo($i)
+
+The built-in ``$`` operator turns an integer (``int``) and many other types
+into a string. The variable ``i`` is implicitely declared by the ``for`` loop
+and has the type ``int``, because that is what ``countup`` returns. ``i`` runs
+through the values 1, 2, .., 10. Each value is ``echo``-ed. This code does
+the same:
+
+.. code-block:: nimrod
+  Echo("Counting to 10: ")
+  var i = 1
+  while i <= 10:
+    Echo($i)
+    inc(i) # increment i by 1
+
+Counting down can be achieved as easily (but is much less needed):
+
+.. code-block:: nimrod
+  Echo("Counting down from 10 to 1: ")
+  for i in countdown(10, 1):
+    Echo($i)
+
+Since counting up occurs so often in programs, Nimrod has a special syntax that
+calls the ``countup`` iterator implicitely:
+
+.. code-block:: nimrod
+  for i in 1..10:
+    ...
+
+The syntax ``for i in 1..10`` is sugar for ``for i in countup(1, 10)``.
+``countdown`` does not have any such sugar.
+
+
+Scopes and the block statement
+------------------------------
+Control flow statements have a feature not covered yet: They open a
+new scope. This means that in the following example, ``x`` is not accessible
+outside the loop:
+
+.. code-block:: nimrod
+  while false:
+    var x = "hi"
+  echo(x) # does not work
+
+A while (for) statement introduces an implicit block. Identifiers
+are only visible within the block they have been declared. The ``block``
+statement can be used to open a new block explicitely:
+
+.. code-block:: nimrod
+  block myblock:
+    var x = "hi"
+  echo(x) # does not work either
+
+The block's `label` (``myblock`` in the example) is optional.
+
+
+Break statement
+---------------
+A block can be left prematurely with a ``break`` statement. The break statement
+can leave a while, for, or a block statement. It leaves the innermost construct,
+unless the label of a block is given:
+
+.. code-block:: nimrod
+  block myblock:
+    Echo("entering block")
+    while true:
+      Echo("looping")
+      break # leaves the loop, but not the block
+    Echo("still in block")
+
+  block myblock2:
+    Echo("entering block")
+    while true:
+      Echo("looping")
+      break myblock2 # leaves the block (and the loop)
+    Echo("still in block")
+
+
+Continue statement
+------------------
+Like in many other programming languages, a ``continue`` statement leads to
+the next iteration immediately:
+
+.. code-block:: nimrod
+  while true:
+    var x = readLine(stdin)
+    if x == "": continue
+    Echo(x)
+
+
+When statement
+--------------
+
+Example:
+
+.. code-block:: nimrod
+
+  when system.hostOS == "windows":
+    echo("running on Windows!")
+  elif system.hostOS == "linux":
+    echo("running on Linux!")
+  elif system.hostOS == "macosx":
+    echo("running on Mac OS X!")
+  else:
+    echo("unknown operating system")
+
+The `when`:idx: statement is almost identical to the ``if`` statement with some
+differences:
+
+* Each condition has to be a constant expression since it is evaluated by the
+  compiler.
+* The statements within a branch do not open a new scope.
+* The compiler checks the semantics and produces code *only* for the statements
+  that belong to the first condition that evaluates to ``true``.
+  
+The ``when`` statement is useful for writing platform specific code, similar to
+the ``#ifdef`` construct in the C programming language.
+
+**Note**: The documentation generator currently always follows the first branch 
+of when statements. 
+
+
+Statements and indentation
+==========================
+
+Now that we covered the basic control flow statements, let's return to Nimrod
+indentation rules. 
+
+In Nimrod there is a distinction between *simple statements* and *complex
+statements*. *Simple statements* cannot contain other statements:
+Assignment, procedure calls or the ``return`` statement belong to the simple
+statements. *Complex statements* like ``if``, ``when``, ``for``, ``while`` can 
+contain other statements. To avoid ambiguities, complex statements always have
+to be intended, but single simple statements do not:
+
+.. code-block:: nimrod
+  # no indentation needed for single assignment statement:
+  if x: x = false
+  
+  # indentation needed for nested if statement:
+  if x: 
+    if y:
+      y = false
+    else:
+      y = true
+  
+  # indentation needed, because two statements follow the condition:
+  if x: 
+    x = false
+    y = false
+
+
+*Expressions* are parts of a statement which usually result in a value. The
+condition in an if statement is an example for an expression. Expressions can
+contain indentation at certain places for better readability: 
+
+.. code-block:: nimrod
+
+  if thisIsaLongCondition() and
+      thisIsAnotherLongCondition(1, 
+         2, 3, 4):
+    x = true 
+
+As a rule of thumb, indentation within expressions is allowed after operators, 
+an open parenthesis and after commas.
+
+
+Procedures
+==========
+
+To define new commands like ``echo``, ``readline`` in the examples, the concept
+of a `procedure` is needed. (Some languages call them *methods* or
+*functions*.) In Nimrod new procedures are defined with the ``proc`` keyword:
+
+.. code-block:: nimrod
+  proc yes(question: string): bool =
+    Echo(question, " (y/n)")
+    while true:
+      case readLine(stdin)
+      of "y", "Y", "yes", "Yes": return true
+      of "n", "N", "no", "No": return false
+      else: Echo("Please be clear: yes or no")
+
+  if yes("Should I delete all your important files?"):
+    Echo("I'm sorry Dave, I'm afraid I can't do that.")
+  else:
+    Echo("I think you know what the problem is just as well as I do.")
+
+This example shows a procedure named ``yes`` that asks the user a ``question``
+and returns true if he answered "yes" (or something similar) and returns
+false if he answered "no" (or something similar). A ``return`` statement leaves
+the procedure (and therefore the while loop) immediately. The 
+``(question: string): bool`` syntax describes that the procedure expects a 
+parameter named ``question`` of type ``string`` and returns a value of type
+``bool``. ``Bool`` is a built-in type: The only valid values for ``bool`` are 
+``true`` and ``false``.
+The conditions in if or while statements need to have the type ``bool``.
+
+Some terminology: In the example ``question`` is called a (formal) *parameter*,
+``"Should I..."`` is called an *argument* that is passed to this parameter.
+
+
+Result variable
+---------------
+A procedure that returns a value has an implicit ``result`` variable that
+represents the return value. A ``return`` statement with no expression is a
+shorthand for ``return result``. So all tree code snippets are equivalent:
+
+.. code-block:: nimrod
+  return 42
+
+  result = 42
+  return
+
+  result = 42
+  return result
+
+
+Parameters
+----------
+Parameters are constant in the procedure body. Their value cannot be changed
+because this allows the compiler to implement parameter passing in the most
+efficient way. If the procedure needs to modify the argument for the 
+caller, a ``var`` parameter can be used: 
+
+.. code-block:: nimrod
+  proc divmod(a, b: int, res, remainder: var int) =
+    res = a div b
+    remainder = a mod b
+
+  var
+    x, y: int
+  divmod(8, 5, x, y) # modifies x and y
+  echo(x)
+  echo(y)
+
+In the example, ``res`` and ``remainder`` are `var parameters`.
+Var parameters can be modified by the procedure and the changes are
+visible to the caller. 
+
+
+Discard statement
+-----------------
+To call a procedure that returns a value just for its side effects and ignoring
+its return value, a discard statement **has** to be used. Nimrod does not
+allow to silently throw away a return value:
+
+.. code-block:: nimrod
+  discard yes("May I ask a pointless question?")
+
+
+Named arguments
+---------------
+
+Often a procedure has many parameters and it is not clear in which order the
+parameters appeared. This is especially true for procedures that construct a
+complex data type. Therefore the arguments to a procedure can be named, so
+that it is clear which argument belongs to which parameter:
+
+.. code-block:: nimrod
+  proc createWindow(x, y, width, height: int, title: string,
+                    show: bool): Window =
+     ...
+
+  var w = createWindow(show = true, title = "My Application",
+                       x = 0, y = 0, height = 600, width = 800)
+
+Now that we use named arguments to call ``createWindow`` the argument order
+does not matter anymore. Mixing named arguments with ordered arguments is
+also possible, but not very readable:
+
+.. code-block:: nimrod
+  var w = createWindow(0, 0, title = "My Application",
+                       height = 600, width = 800, true)
+
+The compiler checks that each parameter receives exactly one argument.
+
+
+Default values
+--------------
+To make the ``createWindow`` proc easier to use it should provide `default
+values`, these are values that are used as arguments if the caller does not
+specify them:
+
+.. code-block:: nimrod
+  proc createWindow(x = 0, y = 0, width = 500, height = 700,
+                    title = "unknown",
+                    show = true): Window =
+     ...
+
+  var w = createWindow(title = "My Application", height = 600, width = 800)
+
+Now the call to ``createWindow`` only needs to set the values that differ
+from the defaults.
+
+Note that type inference works for parameters with default values, there is
+no need to specify ``title: string = "unknown"``, for example.
+
+
+Overloaded procedures
+---------------------
+Nimrod provides the ability to overload procedures similar to C++:
+
+.. code-block:: nimrod
+  proc toString(x: int): string = ...
+  proc toString(x: bool): string =
+    if x: return "true" else: return "false"
+
+  Echo(toString(13))   # calls the toString(x: int) proc
+  Echo(toString(true)) # calls the toString(x: bool) proc
+
+(Note that ``toString`` is usually the ``$`` operator in Nimrod.)
+The compiler chooses the most appropriate proc for the ``toString`` calls. How
+this overloading resolution algorithm works exactly is not discussed here
+(it will be specified in the manual soon).
+However, it does not lead to nasty suprises and is based on a quite simple
+unification algorithm. Ambigious calls are reported as errors.
+
+
+Operators
+---------
+The Nimrod library makes heavy use of overloading - one reason for this is that
+each operator like ``+`` is a just an overloaded proc. The parser lets you
+use operators in `infix notation` (``a + b``) or `prefix notation` (``+ a``).
+An infix operator always receives two arguments, a prefix operator always one.
+Postfix operators are not possible, because this would be ambigious: Does
+``a @ @ b`` mean ``(a) @ (@b)`` or ``(a@) @ (b)``? It always means
+``(a) @ (@b)``, because there are no postfix operators in Nimrod.
+
+Apart from a few built-in keyword operators such as ``and``, ``or``, ``not``,
+operators always consist of these characters:
+``+  -  *  \  /  <  >  =  @  $  ~  &  %  !  ?  ^  .  |``
+
+User defined operators are allowed. Nothing stops you from defining your own
+``@!?+~`` operator, but readability can suffer.
+
+The operator's precedence is determined by its first character. The details
+can be found in the manual.
+
+To define a new operator enclose the operator in "``":
+
+.. code-block:: nimrod
+  proc `$` (x: myDataType): string = ...
+  # now the $ operator also works with myDataType, overloading resolution
+  # ensures that $ works for built-in types just like before
+
+The "``" notation can also be used to call an operator just like a procedure
+with a real name:
+
+.. code-block:: nimrod
+  if `==`( `+`(3, 4), 7): Echo("True")
+
+
+Forward declarations
+--------------------
+
+Every variable, procedure, etc. needs to be declared before it can be used.
+(The reason for this is compilation efficiency.)
+However, this cannot be done for mutually recursive procedures:
+
+.. code-block:: nimrod
+  # forward declaration:
+  proc even(n: int): bool
+
+  proc odd(n: int): bool =
+    if n == 1: return true
+    else: return even(n-1)
+
+  proc even(n: int): bool =
+    if n == 0: return true
+    else: return odd(n-1)
+
+Here ``odd`` depends on ``even`` and vice versa. Thus ``even`` needs to be
+introduced to the compiler before it is completely defined. The syntax for
+such a `forward declaration` is simple: Just omit the ``=`` and the procedure's
+body.
+
+
+Iterators
+=========
+
+Let's return to the boring counting example:
+
+.. code-block:: nimrod
+  Echo("Counting to ten: ")
+  for i in countup(1, 10):
+    Echo($i)
+
+Can a ``countup`` proc be written that supports this loop? Lets try:
+
+.. code-block:: nimrod
+  proc countup(a, b: int): int =
+    var res = a
+    while res <= b:
+      return res
+      inc(res)
+
+However, this does not work. The problem is that the procedure should not
+only ``return``, but return and **continue** after an iteration has
+finished. This *return and continue* is called a `yield` statement. Now
+the only thing left to do is to replace the ``proc`` keyword by ``iterator``
+and there it is - our first iterator:
+
+.. code-block:: nimrod
+  iterator countup(a, b: int): int =
+    var res = a
+    while res <= b:
+      yield res
+      inc(res)
+
+Iterators look very similar to procedures, but there are several
+important differences:
+
+* Iterators can only be called from for loops.
+* Iterators cannot contain a ``return`` statement and procs cannot contain a
+  ``yield`` statement.
+* Iterators have no implicit ``result`` variable.
+* Iterators do not support recursion. (This restriction will be gone in a
+  future version of the compiler.)
+* Iterators cannot be forward declared, because the compiler must be able
+  to inline an iterator. (This restriction will be gone in a
+  future version of the compiler.)
+
+
+Basic types
+===========
+
+This section deals with the basic built-in types and the operations
+that are available for them in detail.
+
+Booleans
+--------
+
+The `boolean`:idx: type is named ``bool`` in Nimrod and consists of the two
+pre-defined values ``true`` and ``false``. Conditions in while,
+if, elif, when statements need to be of type bool.
+
+The operators ``not, and, or, xor, <, <=, >, >=, !=, ==`` are defined
+for the bool type. The ``and`` and ``or`` operators perform short-cut
+evaluation. Example:
+
+.. code-block:: nimrod
+
+  while p != nil and p.name != "xyz":
+    # p.name is not evaluated if p == nil
+    p = p.next
+
+
+Characters
+----------
+The `character type` is named ``char`` in Nimrod. Its size is one byte.
+Thus it cannot represent an UTF-8 character, but a part of it.
+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.
+Character literals are enclosed in single quotes.
+
+Chars can be compared with the ``==``, ``<``, ``<=``, ``>``, ``>=`` operators.
+The ``$`` operator converts a ``char`` to a ``string``. Chars cannot be mixed
+with integers; to get the ordinal value of a ``char`` use the ``ord`` proc.
+Converting from an integer to a ``char`` is done with the ``chr`` proc.
+
+
+Strings
+-------
+String variables in Nimrod are **mutable**, so appending to a string
+is quite efficient. Strings in Nimrod are both zero-terminated and have a
+length field. One can retrieve a string's length with the builtin ``len``
+procedure; the length never counts the terminating zero. Accessing the
+terminating zero is no error and often leads to simpler code:
+
+.. code-block:: nimrod
+  if s[i] == 'a' and s[i+1] == 'b' and s[i+2] == '\0':
+    # no need to check whether ``i < len(s)``!
+    ...
+
+The assignment operator for strings copies the string.
+
+Strings are compared by their lexicographical order. All comparison operators
+are available. Per convention, all strings are UTF-8 strings, but this is not
+enforced. For example, when reading strings from binary files, they are merely
+a sequence of bytes. The index operation ``s[i]`` means the i-th *char* of
+``s``, not the i-th *unichar*.
+
+String variables are initialized with a special value, called ``nil``. However,
+most string operations cannot deal with ``nil`` (leading to an exception being
+raised) for performance reasons. Thus one should use empty strings ``""``
+rather than ``nil`` as the *empty* value. But ``""`` often creates a string
+object on the heap, so there is a trade-off to be made here.
+
+
+Integers
+--------
+Nimrod has these integer types built-in: ``int int8 int16 int32 int64``. These
+are all signed integer types, there are no `unsigned integer`:idx: types, only
+`unsigned operations`:idx: that treat their arguments as unsigned.
+
+The default integer type is ``int``. Integer literals can have a *type suffix*
+to mark them to be of another integer type:
+
+
+.. code-block:: nimrod
+  var
+    x = 0     # x is of type ``int``
+    y = 0'i8  # y is of type ``int8``
+    z = 0'i64 # z is of type ``int64``
+
+Most often integers are used for couting objects that reside in memory, so
+``int`` has the same size as a pointer.
+
+The common operators ``+ - * div mod  <  <=  ==  !=  >  >=`` are defined for
+integers. The ``and or xor not`` operators are defined for integers too and
+provide *bitwise* operations. Left bit shifting is done with the ``shl``, right
+shifting with the ``shr`` operator. Bit shifting operators always treat their
+arguments as *unsigned*. For `arithmetic bit shifts`:idx: ordinary
+multiplication or division can be used.
+
+Unsigned operations all wrap around; they cannot lead to over- or underflow
+errors. Unsigned operations use the ``%`` suffix as convention:
+
+======================   ======================================================
+operation                meaning
+======================   ======================================================
+``a +% b``               unsigned integer addition
+``a -% b``               unsigned integer substraction
+``a *% b``               unsigned integer multiplication
+``a /% b``               unsigned integer division
+``a %% b``               unsigned integer modulo operation
+``a <% b``               treat ``a`` and ``b`` as unsigned and compare
+``a <=% b``              treat ``a`` and ``b`` as unsigned and compare
+======================   ======================================================
+
+`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).
+
+
+
+Floats
+------
+Nimrod has these floating point types built-in: ``float float32 float64``.
+
+The default float type is ``float``. In the current implementation,
+``float`` is always 64 bit wide.
+
+Float literals can have a *type suffix* to mark them to be of another float
+type:
+
+.. code-block:: nimrod
+  var
+    x = 0.0      # x is of type ``float``
+    y = 0.0'f32  # y is of type ``float32``
+    z = 0.0'f64  # z is of type ``int64``
+
+The common operators ``+ - * /  <  <=  ==  !=  >  >=`` are defined for
+floats and follow the IEEE standard.
+
+Automatic type conversion in expressions with different kinds
+of floating point types is performed: The smaller type is
+converted to the larger. Integer types are **not** converted to floating point
+types automatically and vice versa. The ``toInt`` and ``toFloat`` procs can be
+used for these conversions.
+
+
+Advanced types
+==============
+
+In Nimrod new types can be defined within a ``type`` statement:
+
+.. code-block:: nimrod
+  type
+    biggestInt = int64      # biggest integer type that is available
+    biggestFLoat = float64  # biggest float type that is available
+
+Enumeration and object types cannot be defined on the fly, but only within a
+``type`` statement.
+
+
+Enumerations
+------------
+A variable of an `enumeration`:idx: type can only be assigned a value of a
+limited set. This set consists of ordered symbols. Each symbol is mapped
+to an integer value internally. The first symbol is represented
+at runtime by 0, the second by 1 and so on. Example:
+
+.. code-block:: nimrod
+
+  type
+    TDirection = enum
+      north, east, south, west
+
+  var x = south      # `x` is of type `TDirection`; its value is `south`
+  echo($x)           # writes "south" to `stdout`
+
+(To prefix a new type with the letter ``T`` is a convention in Nimrod.)
+All comparison operators can be used with enumeration types.
+
+An enumeration's symbol can be qualified to avoid ambiguities:
+``TDirection.south``.
+
+The ``$`` operator can convert any enumeration value to its name, the ``ord``
+proc to its underlying integer value.
+
+For better interfacing to other programming languages, the symbols of enum
+types can be assigned an explicit ordinal value. However, the ordinal values
+have to be in ascending order. A symbol whose ordinal value is not
+explicitly given is assigned the value of the previous symbol + 1.
+
+An explicit ordered enum can have *wholes*:
+
+.. code-block:: nimrod
+  type
+    TMyEnum = enum
+      a = 2, b = 4, c = 89
+
+
+Ordinal types
+-------------
+Enumerations without wholes, integer types, ``char`` and ``bool`` (and
+subranges) are called `ordinal`:idx: types. Ordinal types have quite
+a few special operations:
+
+-----------------     --------------------------------------------------------
+Operation             Comment
+-----------------     --------------------------------------------------------
+``ord(x)``            returns the integer value that is used to
+                      represent `x`'s value
+``inc(x)``            increments `x` by one
+``inc(x, n)``         increments `x` by `n`; `n` is an integer
+``dec(x)``            decrements `x` by one
+``dec(x, n)``         decrements `x` by `n`; `n` is an integer
+``succ(x)``           returns the successor of `x`
+``succ(x, n)``        returns the `n`'th successor of `x`
+``succ(x)``           returns the predecessor of `x`
+``succ(x, n)``        returns the `n`'th predecessor of `x`
+-----------------     --------------------------------------------------------
+
+The ``inc dec succ pred`` operations can fail by raising an `EOutOfRange` or
+`EOverflow` exception. (If the code has been compiled with the proper runtime
+checks turned on.)
+
+
+Subranges
+---------
+A `subrange`:idx: type is a range of values from an integer or enumeration type
+(the base type). Example:
+
+.. code-block:: nimrod
+  type
+    TSubrange = range[0..5]
+
+
+``TSubrange`` is a subrange of ``int`` which can only hold the values 0
+to 5. Assigning any other value to a variable of type ``TSubrange`` is a
+compile-time or runtime error. Assignments from the base type to one of its
+subrange types (and vice versa) are allowed.
+
+The ``system`` module defines the important ``natural`` type as
+``range[0..high(int)]`` (``high`` returns the maximal value). Other programming
+languages mandate the usage of unsigned integers for natural numbers. This is
+often **wrong**: You don't want unsigned arithmetic (which wraps around) just
+because the numbers cannot be negative. Nimrod's ``natural`` type helps to
+avoid this common programming error.
+
+
+Sets
+----
+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 high performance bit vectors.
+
+Sets can be constructed via the set constructor: ``{}`` is the empty set. The
+empty set is type combatible with any concrete set type. The constructor
+can also be used to include elements (and ranges of elements):
+
+.. code-block:: nimrod
+  type
+    TCharSet = set[char]
+  var
+    x: TCharSet
+  x = {'a'..'z', '0'..'9'} # This constructs a set that conains the
+                           # letters from 'a' to 'z' and the digits
+                           # from '0' to '9'
+
+These operations are supported by sets:
+
+==================    ========================================================
+operation             meaning
+==================    ========================================================
+``A + B``             union of two sets
+``A * B``             intersection of two sets
+``A - B``             difference of two sets (A without B's elements)
+``A == B``            set equality
+``A <= B``            subset relation (A is subset of B or equal to B)
+``A < B``             strong subset relation (A is a real subset of B)
+``e in A``            set membership (A contains element e)
+``e notin A``         A does not contain element e
+``contains(A, e)``    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}``
+``excl(A, elem)``     same as ``A = A - {elem}``
+==================    ========================================================
+
+Sets are often used to define a type for the *flags* of a procedure. This is
+much cleaner (and type safe solution) solution than just defining integer 
+constants that should be ``or``'ed together.
+
+
+Arrays
+------
+An `array`:idx: is a simple fixed length container. Each element in
+the array has the same type. The array's index type can be any ordinal type.
+
+Arrays can be constructed via the array constructor: ``[]`` is the empty
+array. The constructor can also be used to include elements.
+
+.. code-block:: nimrod
+
+  type
+    TIntArray = array[0..5, int] # an array that is indexed with 0..5
+  var
+    x: TIntArray
+  x = [1, 2, 3, 4, 5, 6]
+  for i in low(x)..high(x):
+    echo(x[i])
+
+The notation ``x[i]`` is used to access the i-th element of ``x``.
+Array access is 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.
+
+Arrays are value types, like any other Nimrod type. The assignment operator
+copies the whole array contents.
+
+The built-in ``len`` proc returns the array's length. ``low(a)`` returns the
+lowest valid index for the array `a` and ``high(a)`` the highest valid index.
+
+
+Open arrays
+-----------
+Often fixed size arrays turn out to be too inflexible; procedures should
+be able to deal with arrays of different sizes. The `openarray`:idx: type
+allows this. Openarrays are always indexed with an ``int`` starting at
+position 0. The ``len``, ``low`` and ``high`` operations are available
+for open arrays too. Any array with a compatible base type can be passed to
+an openarray parameter, the index type does not matter.
+
+The openarray type cannot be nested: Multidimensional openarrays are not
+supported because this is seldom needed and cannot be done efficiently.
+
+An openarray is also a means to implement passing a variable number of
+arguments to a procedure. The compiler converts the list of arguments
+to an array automatically:
+
+.. code-block:: nimrod
+  proc myWriteln(f: TFile, a: openarray[string]) =
+    for s in items(a):
+      write(f, s)
+    write(f, "\n")
+
+  myWriteln(stdout, "abc", "def", "xyz")
+  # is transformed by the compiler to:
+  myWriteln(stdout, ["abc", "def", "xyz"])
+
+This transformation is only done if the openarray parameter is the
+last parameter in the procedure header.
+
+
+Sequences
+---------
+`Sequences`:idx: are similar to arrays but of dynamic length which may change
+during runtime (like strings). Since sequences are resizeable they are always
+allocated on the heap and garbage collected.
+
+Sequences are always indexed with an ``int`` starting at position 0.
+The ``len``, ``low`` and ``high`` operations are available for sequences too.
+The notation ``x[i]`` can be used to access the i-th element of ``x``.
+
+Sequences can be constructed by the array constructor ``[]`` in conjunction
+with the array to sequence operator ``@``. Another way to allocate space for
+a sequence is to call the built-in ``newSeq`` procedure.
+
+A sequence may be passed to an openarray parameter.
+
+Example:
+
+.. code-block:: nimrod
+
+  var
+    x: seq[int] # a sequence of integers
+  x = @[1, 2, 3, 4, 5, 6] # the @ turns the array into a sequence
+
+Sequence variables are initialized with ``nil``. However, most sequence
+operations cannot deal with ``nil`` (leading to an exception being
+raised) for performance reasons. Thus one should use empty sequences ``@[]``
+rather than ``nil`` as the *empty* value. But ``@[]`` creates a sequence
+object on the heap, so there is a trade-off to be made here.
+
+
+Tuples
+------
+
+A tuple type defines various named *fields* and an *order* of the fields.
+The constructor ``()`` can be used to construct tuples. The order of the
+fields in the constructor must match the order in the tuple's definition.
+Different tuple-types are *equivalent* if they specify the same fields of
+the same type in the same order.
+
+The assignment operator for tuples copies each component. The notation
+``t.field`` is used to access a tuple's field. Another notation is
+``t[i]`` to access the ``i``'th field. Here ``i`` needs to be a constant
+integer.
+
+.. code-block:: nimrod
+
+  type
+    TPerson = tuple[name: string, age: int] # type representing a person:
+                                            # a person consists of a name
+                                            # and an age
+  var
+    person: TPerson
+  person = (name: "Peter", age: 30)
+  # the same, but less readable:
+  person = ("Peter", 30)
+
+  echo(person.name) # "Peter"
+  echo(person.age)  # 30
+
+  echo(person[0]) # "Peter"
+  echo(person[1]) # 30
+
+
+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.
+
+Nimrod distinguishes between `traced`:idx: and `untraced`:idx: references.
+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.
+
+The ``^`` operator can be used to *derefer* a reference, meaning to retrieve 
+the item the reference points to. The ``addr`` procedure returns the address 
+of an item. An address is always an untraced reference: 
+``addr`` is an *unsafe* feature.
+
+The ``.`` (access a tuple/object field operator)
+and ``[]`` (array/string/sequence index operator) operators perform implicit
+dereferencing operations for reference types:
+
+.. code-block:: nimrod
+
+  type
+    PNode = ref TNode
+    TNode = tuple[le, ri: PNode, data: int]
+  var
+    n: PNode
+  new(n)
+  n.data = 9 # no need to write n^ .data
+
+(As a convention, reference types use a 'P' prefix.)
+
+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 untraced
+memory manually:
+
+.. code-block:: nimrod
+  type
+    TData = tuple[x, y: int, s: string]
+
+  # allocate memory for TData on the heap:
+  var d = cast[ptr TData](alloc0(sizeof(TData)))
+
+  # create a new string on the garbage collected heap:
+  d.s = "abc"
+
+  # tell the GC that the string is not needed anymore:
+  GCunref(d.s)
+
+  # free the memory:
+  dealloc(d)
+
+Without the ``GCunref`` call the memory allocated for the ``d.s`` string would
+never be freed. The example also demonstrates two important features for low
+level programming: The ``sizeof`` proc returns the size of a type or value
+in bytes. The ``cast`` operator can circumvent the type system: The compiler
+is forced to treat the result of the ``alloc0`` call (which returns an untyped
+pointer) as if it would have the type ``ptr TData``. Casting should only be
+done if it is unavoidable: It breaks type safety and bugs can lead to
+mysterious crashes.
+
+**Note**: The example only works because the memory is initialized with zero
+(``alloc0`` instead of ``alloc`` does this): ``d.s`` is thus initialized to
+``nil`` which the string assignment can handle. You need to know low level
+details like this when mixing garbage collected data with unmanaged memory!
+
+
+Procedural type
+---------------
+A `procedural type`:idx: is a (somewhat abstract) pointer to a procedure. 
+``nil`` is an allowed value for a variable 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 (details follow in the OOP section).
+
+Example:
+
+.. code-block:: nimrod
+
+  type
+    TCallback = proc (x: int)
+
+  proc echoItem(x: Int) = echo(x)  
+  
+  proc forEach(callback: TCallback) =
+    const
+      data = [2, 3, 5, 7, 11]
+    for d in items(data):
+      callback(d)
+
+  forEach(echoItem)
+
+A subtle issue with procedural types is that the calling convention of the
+procedure influences the type compability: Procedural types are only compatible
+if they have the same calling convention. The different calling conventions are
+listed in the `user guide <nimrodc.html>`_.
+
+
+Modules
+=======
+Nimrod supports splitting a program into pieces with a `module`:idx: concept.
+Each module is 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. Only top-level symbols that are marked 
+with an asterisk (``*``) are exported:
+
+.. code-block:: nimrod
+  # Module A
+  var
+    x*, y: int
+  
+  proc `*` *(a, b: seq[int]): seq[int] = 
+    # allocate a new sequence:
+    newSeq(result, len(a))
+    # multiply two int sequences:
+    for i in 0..len(a)-1: result[i] = a[i] * b[i]
+
+The above module exports ``x`` and ``*``, but not ``y``.
+
+Modules that depend on each other are possible, but strongly discouraged, 
+because then one module cannot be reused without the other.
+
+The algorithm for compiling modules is:
+
+- Compile the whole module as usual, following import statements recursively
+- 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:
+
+.. code-block:: nimrod
+  # Module A
+  type
+    T1* = int  # Module A exports the type ``T1``
+  import B     # the compiler starts parsing B
+
+  proc main() =
+    var i = p(3) # works because B has been parsed completely here
+
+  main()
+
+
+  # Module B
+  import A  # A is not parsed here! Only the already known symbols
+            # of A are imported.
+
+  proc p*(x: A.T1): A.T1 =
+    # this works because the compiler has already
+    # added T1 to A's interface symbol table
+    return x + 1
+
+
+A symbol of a module *can* be *qualified* with the ``module.symbol`` syntax. If
+the symbol is ambigious, it even *has* to be qualified. A symbol is ambigious 
+if it is defined in two (or more) different modules and both modules are 
+imported by a third one: 
+
+.. code-block:: nimrod
+  # Module A
+  var x*: string
+
+  # Module B
+  var x*: int
+
+  # Module C
+  import A, B
+  write(stdout, x) # error: x is ambigious
+  write(stdout, A.x) # no error: qualifier used
+
+  var x = 4
+  write(stdout, x) # not ambigious: uses the module C's x
+
+
+But this rule does not apply to procedures or iterators. Here the overloading
+rules apply: 
+
+.. code-block:: nimrod
+  # Module A
+  proc x*(a: int): string = return $a
+
+  # Module B
+  proc x*(a: string): string = return $a
+
+  # Module C
+  import A, B
+  write(stdout, x(3))   # no error: A.x is called
+  write(stdout, x(""))  # no error: B.x is called
+
+  proc x*(a: int): string = nil
+  write(stdout, x(3))   # ambigious: which `x` is to call?
+
+
+From statement
+--------------
+
+We have already seen the simple ``import`` statement that just imports all
+exported symbols. An alternative that only imports listed symbols is the
+``from import`` statement: 
+
+.. code-block:: nimrod
+  from mymodule import x, y, z
+
+
+Include statement
+-----------------
+The `include`:idx: statement does something fundametally different than 
+importing a module: It merely includes the contents of a file. The ``include``
+statement is useful to split up a large module into several files:
+
+.. code-block:: nimrod
+  include fileA, fileB, fileC
+
+**Note**: The documentation generator currently does not follow ``include`` 
+statements, so exported symbols in an include file will not show up in the
+generated documentation. 
+
+
+Part 2
+======
+
+So, now that we are done with the basics, let's see what Nimrod offers apart
+from a nice syntax for procedural programming: `Part II <tut2.html>`_
+
+
+.. _strutils: strutils.html
+.. _system: system.html
diff --git a/doc/tut2.txt b/doc/tut2.txt
new file mode 100644
index 000000000..dc14aabc0
--- /dev/null
+++ b/doc/tut2.txt
@@ -0,0 +1,718 @@
+=============================
+The Nimrod Tutorial (Part II)
+=============================
+
+:Author: Andreas Rumpf
+:Version: |nimrodversion|
+
+.. contents::
+
+
+Introduction
+============
+
+  "With great power comes great responsibility." -- Spider-man
+
+This document is a tutorial for the advanced constructs of the *Nimrod* 
+programming language.
+
+
+Pragmas
+=======
+Pragmas are Nimrod's method to give the compiler additional information/
+commands without introducing a massive number of new keywords. Pragmas are
+processed during semantic checking. Pragmas are enclosed in the
+special ``{.`` and ``.}`` curly dot brackets. This tutorial does not cover
+pragmas. See the `manual <manual.html>`_ or `user guide <nimrodc.html>`_ for 
+a description of the available pragmas.
+
+
+Object Oriented Programming
+===========================
+
+While Nimrod's support for object oriented programming (OOP) is minimalistic, 
+powerful OOP technics can be used. OOP is seen as *one* way to design a 
+program, not *the only* way. Often a procedural approach leads to simpler
+and more efficient code.
+
+
+Objects
+-------
+
+Like tuples, objects are a means to pack different values together in a
+structured way. However, objects provide many features that tuples do not:
+They provide inheritance and information hiding. Because objects encapsulate
+data, the ``()`` tuple constructor cannot be used to construct objects. So
+the order of the object's fields is not as important as it is for tuples. The
+programmer should provide a proc to initialize the object (this is called
+a *constructor*).
+
+Objects have access to their type at runtime. There is an
+``is`` operator that can be used to check the object's type:
+
+.. code-block:: nimrod
+
+  type
+    TPerson = object of TObject
+      name*: string  # the * means that `name` is accessible from other modules
+      age: int       # no * means that the field is hidden from other modules
+
+    TStudent = object of TPerson # TStudent inherits from TPerson
+      id: int                    # with an id field
+
+  var
+    student: TStudent
+    person: TPerson
+  assert(student is TStudent) # is true
+
+Object fields that should be visible from outside the defining module, have to
+be marked by ``*``. In contrast to tuples, different object types are
+never *equivalent*. New object types can only be defined within a type
+section.
+
+Inheritance is done with the ``object of`` syntax. Multiple inheritance is
+currently not supported. If an object type has no suitable ancestor, ``TObject``
+should be used as its ancestor, but this is only a convention.
+
+Note that aggregation (*has-a* relation) is often preferable to inheritance
+(*is-a* relation) for simple code reuse. Since objects are value types in
+Nimrod, aggregation is as efficient as inheritance.
+
+
+Mutually recursive types
+------------------------
+
+Objects, tuples and references can model quite complex data structures which
+depend on each other. This is called *mutually recursive types*. In Nimrod 
+these types need to be declared within a single type section. Anything else 
+would require arbitrary symbol lookahead which slows down compilation.
+
+Example:
+
+.. code-block:: nimrod
+  type
+    PNode = ref TNode # a traced reference to a TNode
+    TNode = object
+      le, ri: PNode   # left and right subtrees
+      sym: ref TSym   # leaves contain a reference to a TSym
+
+    TSym = object     # a symbol
+      name: string    # the symbol's name
+      line: int       # the line the symbol was declared in
+      code: PNode     # the symbol's abstract syntax tree
+
+
+Type conversions
+----------------
+Nimrod distinguishes between `type casts`:idx: and `type conversions`:idx:.
+Casts are done with the ``cast`` operator and force the compiler to 
+interpret a bit pattern to be of another type. 
+
+Type conversions are a much more polite way to convert a type into another: 
+They preserve the abstract *value*, not necessarily the *bit-pattern*. If a
+type conversion is not possible, the compiler complains or an exception is
+raised. 
+
+The syntax for type conversions is ``destination_type(expression_to_convert)``
+(like an ordinary call): 
+
+.. code-block:: nimrod
+  proc getID(x: TPerson): int = 
+    return TStudent(x).id
+  
+The ``EInvalidObjectConversion`` exception is raised if ``x`` is not a 
+``TStudent``.
+
+
+Object variants
+---------------
+Often an object hierarchy is overkill in certain situations where simple
+`variant`:idx: types are needed.
+
+An example:
+
+.. code-block:: nimrod
+
+  # This is an example how an abstract syntax tree could be modelled in Nimrod
+  type
+    TNodeKind = enum  # the different node types
+      nkInt,          # a leaf with an integer value
+      nkFloat,        # a leaf with a float value
+      nkString,       # a leaf with a string value
+      nkAdd,          # an addition
+      nkSub,          # a subtraction
+      nkIf            # an if statement
+    PNode = ref TNode
+    TNode = object
+      case kind: TNodeKind  # the ``kind`` field is the discriminator
+      of nkInt: intVal: int
+      of nkFloat: floavVal: float
+      of nkString: strVal: string
+      of nkAdd, nkSub:
+        leftOp, rightOp: PNode
+      of nkIf:
+        condition, thenPart, elsePart: PNode
+
+  var
+    n: PNode
+  new(n)  # creates a new node
+  n.kind = nkFloat
+  n.floatVal = 0.0 # valid, because ``n.kind==nkFloat``
+
+  # the following statement raises an `EInvalidField` exception, because
+  # n.kind's value does not fit:
+  n.strVal = ""
+
+As can been seen from the example, an advantage to an object hierarchy is that
+no conversion between different object types is needed. Yet, access to invalid
+object fields raises an exception.
+
+
+Methods
+-------
+In ordinary object oriented languages, procedures (also called *methods*) are 
+bound to a class. This has disadvantages: 
+
+* Adding a method to a class the programmer has no control over is 
+  impossible or needs ugly workarounds.
+* Often it is unclear where the procedure should belong to: Is
+  ``join`` a string method or an array method? Should the complex 
+  ``vertexCover`` algorithm really be a method of the ``graph`` class?
+
+Nimrod avoids these problems by not distinguishing between methods and 
+procedures. Methods are just ordinary procedures. However, there is a special 
+syntactic sugar for calling procedures: The syntax ``obj.method(args)`` can be
+used instead of ``method(obj, args)``. If there are no remaining arguments, the
+parentheses can be omitted: ``obj.len`` (instead of ``len(obj)``).
+
+This `method call syntax`:idx: is not restricted to objects, it can be used 
+for any type: 
+
+.. code-block:: nimrod
+  
+  echo("abc".len) # is the same as echo(len("abc"))
+  echo("abc".toUpper())
+  echo({'a', 'b', 'c'}.card)
+  stdout.writeln("Hallo") # the same as write(stdout, "Hallo")
+
+If it gives you warm fuzzy feelings, you can even write ``1.`+`(2)`` instead of
+``1 + 2`` and claim that Nimrod is a pure object oriented language. (That 
+would not even be lying: *pure OO* has no meaning anyway. :-)
+
+
+Properties
+----------
+As the above example shows, Nimrod has no need for *get-properties*:  
+Ordinary get-procedures that are called with the *method call syntax* achieve 
+the same. But setting a value is different; for this a special setter syntax 
+is needed:
+
+.. code-block:: nimrod
+  
+  type
+    TSocket* = object of TObject
+      FHost: int # cannot be accessed from the outside of the module
+                 # the `F` prefix is a convention to avoid clashes since
+                 # the accessors are named `host`
+                 
+  proc `host=`*(s: var TSocket, value: int) {.inline.} = 
+    ## setter of hostAddr
+    s.FHost = value
+  
+  proc host*(s: TSocket): int {.inline.} =
+    ## getter of hostAddr
+    return s.FHost
+    
+  var 
+    s: TSocket
+  s.host = 34  # same as `host=`(s, 34)
+
+(The example also shows ``inline`` procedures.)
+
+
+The ``[]`` array access operator can be overloaded to provide 
+`array properties`:idx:\ :
+
+.. code-block:: nimrod
+  type
+    TVector* = object
+      x, y, z: float
+

+  proc `[]=`* (v: var TVector, i: int, value: float) =
+    # setter

+    case i
+    of 0: v.x = value
+    of 1: v.y = value
+    of 2: v.z = value
+    else: assert(false)
+

+  proc `[]`* (v: TVector, i: int): float = 
+    # getter
+    case i
+    of 0: result = v.x
+    of 1: result = v.y
+    of 2: result = v.z
+    else: assert(false)
+   

+The example is silly, since a vector is better modelled by a tuple which 
+already provides ``v[]`` access.
+
+
+Dynamic binding
+---------------
+In Nimrod procedural types are used to implement dynamic binding. The following
+example also shows some more conventions: The ``self`` or ``this`` object 
+is named ``my`` (because it is shorter than the alternatives), each class 
+provides a constructor, etc.
+
+.. code-block:: nimrod
+  type
+    TFigure = object of TObject    # abstract base class:
+      draw: proc (my: var TFigure) # concrete classes implement this proc
+    
+  proc init(f: var TFigure) = 
+    f.draw = nil
+  
+  type
+    TCircle = object of TFigure
+      radius: int
+    
+  proc drawCircle(my: var TCircle) = echo("o " & $my.radius)
+  
+  proc init(my: var TCircle) = 
+    init(TFigure(my)) # call base constructor
+    my.radius = 5
+    my.draw = drawCircle
+
+  type
+    TRectangle = object of TFigure
+      width, height: int
+  
+  proc drawRectangle(my: var TRectangle) = echo("[]")
+  
+  proc init(my: var TRectangle) = 
+    init(TFigure(my)) # call base constructor
+    my.width = 5
+    my.height = 10
+    my.draw = drawRectangle
+
+  # now use these classes:
+  var
+    r: TRectangle
+    c: TCircle
+  init(r)
+  init(c)
+  r.draw(r)
+  c.draw(c) 
+
+The last line shows the syntactical difference between static and dynamic 
+binding: The ``r.draw(r)`` dynamic call refers to ``r`` twice. This difference
+is not necessarily bad. But if you want to eliminate the somewhat redundant
+``r``, it can be done by using *closures*: 
+
+.. code-block:: nimrod
+  type
+    TFigure = object of TObject    # abstract base class:
+      draw: proc () {.closure.}    # concrete classes implement this proc
+    
+  proc init(f: var TFigure) = 
+    f.draw = nil
+  
+  type
+    TCircle = object of TFigure
+      radius: int
+  
+  proc init(me: var TCircle) = 
+    init(TFigure(me)) # call base constructor
+    me.radius = 5
+    me.draw = lambda () = 
+      echo("o " & $me.radius)
+
+  type
+    TRectangle = object of TFigure
+      width, height: int
+  
+  proc init(me: var TRectangle) = 
+    init(TFigure(me)) # call base constructor
+    me.width = 5
+    me.height = 10
+    me.draw = lambda () =
+      echo("[]")
+
+  # now use these classes:
+  var
+    r: TRectangle
+    c: TCircle
+  init(r)
+  init(c)
+  r.draw()
+  c.draw() 
+
+The example also introduces `lambda`:idx: expressions: A ``lambda`` expression
+defines a new proc with the ``closure`` calling convention on the fly.
+
+`Version 0.7.4: Closures and lambda expressions are not implemented.`:red:
+
+
+Exceptions
+==========
+
+In Nimrod `exceptions`:idx: are objects. By convention, exception types are 
+prefixed with an 'E', not 'T'. The ``system`` module defines an exception 
+hierarchy that you should stick to. Reusing an existing exception type is
+often better than defining a new exception type: It avoids a proliferation of
+types. 
+
+Exceptions should be allocated on the heap because their lifetime is unknown.
+
+A convention is that exceptions should be raised in *exceptional* cases: 
+For example, if a file cannot be opened, this should not raise an exception 
+since this is quite common (the file may have been deleted).
+
+
+Raise statement
+---------------
+Raising an exception is done with the ``raise`` statement: 
+
+.. code-block:: nimrod
+  var
+    e: ref EOS
+  new(e)
+  e.msg = "the request to the OS failed"
+  raise e
+
+If the ``raise`` keyword is not followed by an expression, the last exception 
+is *re-raised*. 
+
+
+Try statement
+-------------
+
+The `try`:idx: statement handles exceptions: 
+
+.. code-block:: nimrod
+  # read the first two lines of a text file that should contain numbers
+  # and tries to add them
+  var
+    f: TFile
+  if openFile(f, "numbers.txt"):
+    try:
+      var a = readLine(f)
+      var b = readLine(f)
+      echo("sum: " & $(parseInt(a) + parseInt(b)))
+    except EOverflow:
+      echo("overflow!")
+    except EInvalidValue:
+      echo("could not convert string to integer")
+    except EIO:
+      echo("IO error!")
+    except:
+      echo("Unknown exception!")
+      # reraise the unknown exception:
+      raise
+    finally:
+      closeFile(f)
+
+The statements after the ``try`` are executed unless an exception is 
+raised. Then the appropriate ``except`` part is executed. 
+
+The empty ``except`` part is executed if there is an exception that is
+not explicitely listed. It is similiar to an ``else`` part in ``if`` 
+statements.
+
+If there is a ``finally`` part, it is always executed after the
+exception handlers.
+
+The exception is *consumed* in an ``except`` part. If an exception is not
+handled, it is propagated through the call stack. This means that often
+the rest of the procedure - that is not within a ``finally`` clause -
+is not executed (if an exception occurs).
+
+
+Generics
+========
+
+`Version 0.7.4: Complex generic types like in the example do not work.`:red:
+
+`Generics`:idx: are Nimrod's means to parametrize procs, iterators or types 
+with `type parameters`:idx:. They are most useful for efficient type safe
+containers: 
+
+.. code-block:: nimrod
+  type
+    TBinaryTree[T] = object      # TBinaryTree is a generic type with
+                                 # with generic param ``T``
+      le, ri: ref TBinaryTree[T] # left and right subtrees; may be nil
+      data: T                    # the data stored in a node
+    PBinaryTree*[T] = ref TBinaryTree[T] # type that is exported
+
+  proc newNode*[T](data: T): PBinaryTree[T] = 
+    # constructor for a node
+    new(result)
+    result.dat = data
+
+  proc add*[T](root: var PBinaryTree[T], n: PBinaryTree[T]) =
+    # insert a node into the tree
+    if root == nil:
+      root = n
+    else:
+      var it = root
+      while it != nil:
+        # compare the data items; uses the generic ``cmd`` proc that works for
+        # any type that has a ``==`` and ``<`` operator
+        var c = cmp(it.data, n.data) 
+        if c < 0:
+          if it.le == nil:
+            it.le = n
+            return
+          it = it.le
+        else:
+          if it.ri == nil:
+            it.ri = n
+            return
+          it = it.ri
+
+  proc add*[T](root: var PBinaryTree[T], data: T) = 
+    # convenience proc:
+    add(root, newNode(data))
+
+  iterator preorder*[T](root: PBinaryTree[T]): T =
+    # Preorder traversal of a binary tree.
+    # Since recursive iterators are not yet implemented, 
+    # this uses an explicit stack (which is more efficient anyway):
+    var stack: seq[PBinaryTree[T]] = @[root]
+    while stack.len > 0:
+      var n = stack[stack.len-1]
+      setLen(stack, stack.len-1) # pop `n` of the stack
+      while n != nil:
+        yield n
+        add(stack, n.ri)  # push right subtree onto the stack
+        n = n.le          # and follow the left pointer
+      
+  var
+    root: PBinaryTree[string] # instantiate a PBinaryTree with ``string``
+  add(root, newNode("hallo")) # instantiates generic procs ``newNode`` and ``add``
+  add(root, "world")          # instantiates the second ``add`` proc
+  for str in preorder(root):
+    stdout.writeln(str)
+
+The example shows a generic binary tree. Depending on context, the brackets are 
+used either to introduce type parameters or to instantiate a generic proc, 
+iterator or type. As the example shows, generics work with overloading: The
+best match of ``add`` is used. The built-in ``add`` procedure for sequences
+is not hidden and used in the ``preorder`` iterator. 
+
+
+Templates
+=========
+
+Templates are a simple substitution mechanism that operates on Nimrod's 
+abstract syntax trees. Templates are processed in the semantic pass of the 
+compiler. They integrate well with the rest of the language and share none 
+of C's preprocessor macros flaws. However, they may lead to code that is harder 
+to understand and maintain. So one should use them sparingly. 
+
+To *invoke* a template, call it like a procedure.
+
+Example:
+
+.. code-block:: nimrod
+  template `!=` (a, b: expr): expr =
+    # this definition exists in the System module
+    not (a == b)
+
+  assert(5 != 6) # the compiler rewrites that to: assert(not (5 == 6))
+
+The ``!=``, ``>``, ``>=``, ``in``, ``notin``, ``isnot`` operators are in fact 
+templates: This has the benefit that if you overload the ``==`` operator, 
+the ``!=`` operator is available automatically and does the right thing.
+
+``a > b`` is transformed into ``b < a``.
+``a in b`` is transformed into ``contains(b, a)``. 
+``notin`` and ``isnot`` have the obvious meanings.
+
+Templates are especially useful for lazy evaluation purposes. Consider a
+simple proc for logging: 
+
+.. code-block:: nimrod
+  const
+    debug = True
+    
+  proc log(msg: string) {.inline.} = 
+    if debug:
+      stdout.writeln(msg)
+  
+  var
+    x = 4
+  log("x has the value: " & $x)
+
+This code has a shortcoming: If ``debug`` is set to false someday, the quite
+expensive ``$`` and ``&`` operations are still performed! (The argument 
+evaluation for procedures is said to be *eager*).
+
+Turning the ``log`` proc into a template solves this problem in an elegant way:
+
+.. code-block:: nimrod
+  const
+    debug = True
+    
+  template log(msg: expr): stmt = 
+    if debug:
+      stdout.writeln(msg)
+  
+  var
+    x = 4
+  log("x has the value: " & $x)
+
+The "types" of templates can be the symbols ``expr`` (stands for *expression*), 
+``stmt`` (stands for *statement*) or ``typedesc`` (stands for *type 
+description*). These are no real types, they just help the compiler parsing.
+
+The template body does not open a new scope. To open a new scope
+use a ``block`` statement:
+
+.. code-block:: nimrod
+  template declareInScope(x: expr, t: typeDesc): stmt = 
+    var x: t
+    
+  template declareInNewScope(x: expr, t: typeDesc): stmt = 
+    # open a new scope:
+    block: 
+      var x: t
+
+  declareInScope(a, int)
+  a = 42  # works, `a` is known here
+  
+  declareInNewScope(b, int)
+  b = 42  # does not work, `b` is unknown
+
+
+Macros
+======
+
+If the template mechanism scares you, you will be pleased to hear that 
+templates are not really necessary: Macros can do anything that templates can
+do and much more. Macros are harder to write than templates and even harder 
+to get right :-). Now that you have been warned, lets see what a macro *is*.
+
+Macros enable advanced compile-time code tranformations, but they
+cannot change Nimrod's syntax. However, this is no real restriction because
+Nimrod's syntax is flexible enough anyway. 
+
+`Macros`:idx: can be used to implement `domain specific languages`:idx:. 
+
+To write macros, one needs to know how the Nimrod concrete syntax is converted
+to an abstract syntax tree (AST). (Unfortunately the AST is not documented yet.)
+
+There are two ways to invoke a macro:
+(1) invoking a macro like a procedure call (`expression macros`:idx:)
+(2) invoking a macro with the special ``macrostmt`` syntax (`statement macros`:idx:)
+
+
+Expression Macros
+-----------------
+
+The following example implements a powerful ``debug`` command that accepts a
+variable number of arguments (this cannot be done with templates):
+
+.. code-block:: nimrod
+  # to work with Nimrod syntax trees, we need an API that is defined in the
+  # ``macros`` module:
+  import macros
+
+  macro debug(n: expr): stmt =
+    # `n` is a Nimrod AST that contains the whole macro expression
+    # this macro returns a list of statements:
+    result = newNimNode(nnkStmtList, n)
+    # iterate over any argument that is passed to this macro:
+    for i in 1..n.len-1:
+      # add a call to the statement list that writes the expression;
+      # `toStrLit` converts an AST to its string representation:
+      result.add(newCall("write", newIdentNode("stdout"), toStrLit(n[i])))
+      # add a call to the statement list that writes ": "
+      result.add(newCall("write", newIdentNode("stdout"), newStrLitNode(": ")))
+      # add a call to the statement list that writes the expressions value:
+      result.add(newCall("writeln", newIdentNode("stdout"), n[i]))
+
+  var
+    a: array[0..10, int]
+    x = "some string"
+  a[0] = 42
+  a[1] = 45
+
+  debug(a[0], a[1], x)
+
+The macro call expands to:
+
+.. code-block:: nimrod
+  write(stdout, "a[0]")
+  write(stdout, ": ")
+  writeln(stdout, a[0])
+
+  write(stdout, "a[1]")
+  write(stdout, ": ")
+  writeln(stdout, a[1])
+
+  write(stdout, "x")
+  write(stdout, ": ")
+  writeln(stdout, x)
+
+
+Lets return to the dynamic binding ``r.draw(r)`` notational "problem". Apart 
+from closures, there is another "solution": Define an infix ``!`` macro 
+operator which hides it: 
+
+.. code-block:: 
+
+  macro `!` (n: expr): expr = 
+    result = newNimNode(nnkCall, n)
+    var dot = newNimNode(nnkDotExpr, n)
+    dot.add(n[1])    # obj
+    if n[2].kind == nnkCall:
+      # transforms ``obj!method(arg1, arg2, ...)`` to
+      # ``(obj.method)(obj, arg1, arg2, ...)``
+      dot.add(n[2][0]) # method
+      result.add(dot)
+      result.add(n[1]) # obj
+      for i in 1..n[2].len-1:
+        result.add(n[2][i])
+    else:
+      # transforms ``obj!method`` to
+      # ``(obj.method)(obj)``
+      dot.add(n[2]) # method
+      result.add(dot)
+      result.add(n[1]) # obj
+  
+  r!draw(a, b, c) # will be transfomed into ``r.draw(r, a, b, c)``
+
+Great! 20 lines of complex code to safe a few keystrokes! Obviously, this is
+exactly you should not do! (But it makes a cool example.)
+
+
+Statement Macros
+----------------
+
+Statement macros are defined just as expression macros. However, they are
+invoked by an expression following a colon.
+
+The following example outlines a macro that generates a lexical analyser from
+regular expressions:
+
+.. code-block:: nimrod
+
+  macro case_token(n: stmt): stmt =
+    # creates a lexical analyser from regular expressions
+    # ... (implementation is an exercise for the reader :-)
+    nil
+
+  case_token: # this colon tells the parser it is a macro statement
+  of r"[A-Za-z_]+[A-Za-z_0-9]*":
+    return tkIdentifier
+  of r"0-9+":
+    return tkInteger
+  of r"[\+\-\*\?]+":
+    return tkOperator
+  else:
+    return tkUnknown
+
+
diff --git a/doc/tutorial.txt b/doc/tutorial.txt
deleted file mode 100644
index 795fc0d90..000000000
--- a/doc/tutorial.txt
+++ /dev/null
@@ -1,215 +0,0 @@
-===========================================
-Tutorial of the Nimrod Programming Language
-===========================================
-
-:Author: Andreas Rumpf
-
-Motivation
-==========
-
-Why yet another programming language?
-
-Look at the trends behind all the new programming languages:
-
-* They try to be dynamic: Dynamic typing, dynamic method binding, etc.
-  In my opinion the most things the dynamic features buy could be achieved
-  with static means in a more efficient and *understandable* way. 
-
-* They depend on big runtime environments which you need to
-  ship with your program as each new version of these may break compability
-  in subtle ways or you use recently added features - thus forcing your
-  users to update their runtime environment. Compiled programs where the
-  executable contains all needed code are simply the better solution. 
-
-* They are unsuitable for systems programming: Do you really want to
-  write an operating system, a device driver or an interpreter in a language
-  that is just-in-time compiled (or interpreted)?
-
-
-So what lacks are *good* systems programming languages. Nimrod is such a
-language. It offers the following features:
-
-* It is readable: It reads from left to right (unlike the C-syntax
-  languages).
-* It is strongly and statically typed: This enables the compiler to find
-  more errors. Static typing also makes programs more *readable*.
-* It is compiled. (Currently this is done via compilation to C.)
-* It is garbage collected. Big systems need garbage collection. Manuell
-  memory management is also supported through *untraced pointers*.
-* It scales because high level features are also available: It has built-in
-  bit sets, strings, enumerations, objects, arrays and dynamically resizeable
-  arrays (called *sequences*).
-* It has high performance: The current implementation compiles to C
-  and uses a Deutsch-Bobrow garbage collector together with Christoper's
-  partial mark-sweep garbage collector leading to excellent execution
-  speed and a small memory footprint.
-* It has real modules with proper interfaces and supports separate
-  compilation.
-* It is portable: It compiles to C and platform specific features have
-  been separated and documented. So even if your platform is not supported
-  porting should be easy.
-* It is flexible: Although primilarily a procedural language, generic,
-  functional and object-oriented programming is also supported.
-* It is easy to learn, easy to use and leads to elegant programs.
-* You can link an embedded debugger to your program (ENDB). ENDB is
-  very easy to use - there is no need to clutter your code with
-  ``echo`` statements for proper debugging.
-
-
-Introduction
-============
-
-This document is a tutorial for the programming language *Nimrod*. It should
-be a readable quick tour through the language instead of a dry specification
-(which can be found `here <manual.html>`_). This tutorial assumes that
-the reader already knows some other programming language such as Pascal. Thus
-it is detailed in cases where Nimrod differs from other programming languages
-and kept short where Nimrod is more or less the same.
-
-
-A quick tour through the language
-=================================
-
-The first program
------------------
-
-We start the tour with a modified "hallo world" program:
-
-.. code-block:: Nimrod
-  # This is a comment
-  # Standard IO-routines are always accessible
-  write(stdout, "What's your name? ")
-  var name: string = readLine(stdin)
-  write(stdout, "Hi, " & name & "!\n")
-
-
-Save this code to the file "greeting.nim". Now compile and run it::
-
-  nimrod compile --run greeting.nim
-
-As you see, with the ``--run`` switch Nimrod executes the file automatically
-after compilation. You can even give your program command line arguments by
-appending them after the filename that is to be compiled and run::
-
-  nimrod compile --run greeting.nim arg1 arg2
-
-Though it should be pretty obvious what the program does, I will explain the
-syntax: Statements which are not indented are executed when the program
-starts. Indentation is Nimrod's way of grouping statements. String literals
-are enclosed in double quotes. The ``var`` statement declares a new variable
-named ``name`` of type ``string`` with the value that is returned by the
-``readline`` procedure. Since the compiler knows that ``readline`` returns
-a string, you can leave out the type in the declaration. So this will work too:
-
-.. code-block:: Nimrod
-  var name = readline(stdin)
-
-Note that this is the only form of type inference that exists in Nimrod:
-This is because it yields a good compromise between brevity and readability.
-
-The ``&`` operator concates strings together. ``\n`` stands for the
-new line character(s). On several operating systems ``\n`` is represented by
-*two* characters: Linefeed and Carriage Return. That is why
-*character literals* cannot contain ``\n``. But since Nimrod handles strings
-so well, this is a nonissue.
-
-The "hallo world" program contains several identifiers that are already
-known to the compiler: ``write``, ``stdout``, ``readLine``, etc. These
-built-in items are declared in the system_ module which is implicitly
-imported by any other module.
-
-
-Lexical elements
-----------------
-
-Let us look into Nimrod's lexical elements in more detail: Like other
-programming languages Nimrod consists of identifiers, keywords, comments,
-operators, and other punctation marks. Case is *insignificant* in Nimrod and
-even underscores are ignored: ``This_is_an_identifier`` and this is the same
-identifier ``ThisIsAnIdentifier``. This feature enables one to use other
-peoples code without bothering about a naming convention that one does not
-like.
-
-String literals are enclosed in double quotes, character literals in single
-quotes. There exist also *raw* string and character literals:
-
-.. code-block:: Nimrod
-  r"C:\program files\nim"
-
-In raw literals the backslash is not an escape character, so they fit
-the principle *what you see is what you get*. *Long string literals*
-are also available (``""" ... """``); they can span over multiple lines
-and the ``\`` is not an escape character either. They are very useful
-for embedding SQL code templates for example.
-
-Comments start with ``#`` and run till the end of the line. (Well this is not
-quite true, but you should read the manual for a proper explanation.)
-
-... XXX number literals
-
-
-The usual statements - if, while, for, case
--------------------------------------------
-
-In Nimrod indentation is used to group statements.
-An example showing the most common statement types:
-
-.. code-block:: Nimrod
-  var name = readLine(stdin)
-
-  if name == "Andreas":
-    echo("What a nice name!")
-  elif name == "":
-    echo("Don't you have a name?")
-  else:
-    echo("Boring name...")
-
-  for i in 0..length(name)-1:
-    if name[i] == 'm':
-      echo("hey, there is an *m* in your name!")
-
-  echo("Please give your password: \n")
-  var pw = readLine(stdin)
-
-  while pw != "12345":
-    echo("Wrong password! Next try: \n")
-    pw = readLine(stdin)
-
-  echo("""Login complete!
-  What do you want to do?
-  delete-everything
-  restart-computer
-  go-for-a-walk
-  """)
-
-  case readline(stdin)
-  of "delete-everything", "restart-computer":
-    echo("permission denied")
-  of "go-for-a-walk":     echo("please yourself")
-  else:                   echo("unknown command")
-
-
-..
-  Types
-  -----
-  
-  Nimrod has a rich type system. This tutorial only gives a few examples. Read
-  the `manual <manual.html>`_ for further information:
-  
-  .. code-block:: Nimrod
-    type
-      TMyRecord = object
-        x, y: int
-  
-  
-  Procedures
-  ----------
-  
-  Procedures are subroutines. They are declared in this way:
-  
-  .. code-block:: Nimrod
-    proc findSubStr(sub: string,
-
-
-.. _strutils: strutils.html
-.. _system: system.html