1==========
2Nim Manual
3==========
4
5:Authors: Andreas Rumpf, Zahary Karadjov
6:Version: |nimversion|
7
8.. default-role:: code
9.. include:: rstcommon.rst
10.. contents::
11
12
13  "Complexity" seems to be a lot like "energy": you can transfer it from the
14  end-user to one/some of the other players, but the total amount seems to remain
15  pretty much constant for a given task. -- Ran
16
17
18About this document
19===================
20
21**Note**: This document is a draft! Several of Nim's features may need more
22precise wording. This manual is constantly evolving into a proper specification.
23
24**Note**: The experimental features of Nim are
25covered `here <manual_experimental.html>`_.
26
27**Note**: Assignments, moves, and destruction are specified in
28the `destructors <destructors.html>`_ document.
29
30
31This document describes the lexis, the syntax, and the semantics of the Nim language.
32
33To learn how to compile Nim programs and generate documentation see
34the `Compiler User Guide <nimc.html>`_ and the `DocGen Tools Guide <docgen.html>`_.
35
36The language constructs are explained using an extended BNF, in which `(a)*`
37means 0 or more `a`'s, `a+` means 1 or more `a`'s, and `(a)?` means an
38optional *a*. Parentheses may be used to group elements.
39
40`&` is the lookahead operator; `&a` means that an `a` is expected but
41not consumed. It will be consumed in the following rule.
42
43The `|`, `/` symbols are used to mark alternatives and have the lowest
44precedence. `/` is the ordered choice that requires the parser to try the
45alternatives in the given order. `/` is often used to ensure the grammar
46is not ambiguous.
47
48Non-terminals start with a lowercase letter, abstract terminal symbols are in
49UPPERCASE. Verbatim terminal symbols (including keywords) are quoted
50with `'`. An example::
51
52  ifStmt = 'if' expr ':' stmts ('elif' expr ':' stmts)* ('else' stmts)?
53
54The binary `^*` operator is used as a shorthand for 0 or more occurrences
55separated by its second argument; likewise `^+` means 1 or more
56occurrences: `a ^+ b` is short for `a (b a)*`
57and `a ^* b` is short for `(a (b a)*)?`. Example::
58
59  arrayConstructor = '[' expr ^* ',' ']'
60
61Other parts of Nim, like scoping rules or runtime semantics, are
62described informally.
63
64
65
66
67Definitions
68===========
69
70Nim code specifies a computation that acts on a memory consisting of
71components called `locations`:idx:. A variable is basically a name for a
72location. Each variable and location is of a certain `type`:idx:. The
73variable's type is called `static type`:idx:, the location's type is called
74`dynamic type`:idx:. If the static type is not the same as the dynamic type,
75it is a super-type or subtype of the dynamic type.
76
77An `identifier`:idx: is a symbol declared as a name for a variable, type,
78procedure, etc. The region of the program over which a declaration applies is
79called the `scope`:idx: of the declaration. Scopes can be nested. The meaning
80of an identifier is determined by the smallest enclosing scope in which the
81identifier is declared unless overloading resolution rules suggest otherwise.
82
83An expression specifies a computation that produces a value or location.
84Expressions that produce locations are called `l-values`:idx:. An l-value
85can denote either a location or the value the location contains, depending on
86the context.
87
88A Nim `program`:idx: consists of one or more text `source files`:idx: containing
89Nim code. It is processed by a Nim `compiler`:idx: into an `executable`:idx:.
90The nature of this executable depends on the compiler implementation; it may,
91for example, be a native binary or JavaScript source code.
92
93In a typical Nim program, most of the code is compiled into the executable.
94However, some of the code may be executed at
95`compile-time`:idx:. This can include constant expressions, macro definitions,
96and Nim procedures used by macro definitions. Most of the Nim language is
97supported at compile-time, but there are some restrictions -- see `Restrictions
98on Compile-Time Execution <#restrictions-on-compileminustime-execution>`_ for
99details. We use the term `runtime`:idx: to cover both compile-time execution
100and code execution in the executable.
101
102The compiler parses Nim source code into an internal data structure called the
103`abstract syntax tree`:idx: (`AST`:idx:). Then, before executing the code or
104compiling it into the executable, it transforms the AST through
105`semantic analysis`:idx:. This adds semantic information such as expression types,
106identifier meanings, and in some cases expression values. An error detected
107during semantic analysis is called a `static error`:idx:. Errors described in
108this manual are static errors when not otherwise specified.
109
110A `panic`:idx: is an error that the implementation detects
111and reports at runtime. The method for reporting such errors is via
112*raising exceptions* or *dying with a fatal error*. However, the implementation
113provides a means to disable these `runtime checks`:idx:. See the section
114pragmas_ for details.
115
116Whether a panic results in an exception or in a fatal error is
117implementation specific. Thus the following program is invalid; even though the
118code purports to catch the `IndexDefect` from an out-of-bounds array access, the
119compiler may instead choose to allow the program to die with a fatal error.
120
121.. code-block:: nim
122  var a: array[0..1, char]
123  let i = 5
124  try:
125    a[i] = 'N'
126  except IndexDefect:
127    echo "invalid index"
128
129The current implementation allows to switch between these different behaviors
130via `--panics:on|off`:option:. When panics are turned on, the program dies with a
131panic, if they are turned off the runtime errors are turned into
132exceptions. The benefit of `--panics:on`:option: is that it produces smaller binary
133code and the compiler has more freedom to optimize the code.
134
135An `unchecked runtime error`:idx: is an error that is not guaranteed to be
136detected and can cause the subsequent behavior of the computation to
137be arbitrary. Unchecked runtime errors cannot occur if only `safe`:idx:
138language features are used and if no runtime checks are disabled.
139
140A `constant expression`:idx: is an expression whose value can be computed during
141a semantic analysis of the code in which it appears. It is never an l-value and
142never has side effects. Constant expressions are not limited to the capabilities
143of semantic analysis, such as constant folding; they can use all Nim language
144features that are supported for compile-time execution. Since constant
145expressions can be used as an input to semantic analysis (such as for defining
146array bounds), this flexibility requires the compiler to interleave semantic
147analysis and compile-time code execution.
148
149It is mostly accurate to picture semantic analysis proceeding top to bottom and
150left to right in the source code, with compile-time code execution interleaved
151when necessary to compute values that are required for subsequent semantic
152analysis. We will see much later in this document that macro invocation not only
153requires this interleaving, but also creates a situation where semantic analysis
154does not entirely proceed top to bottom and left to right.
155
156
157Lexical Analysis
158================
159
160Encoding
161--------
162
163All Nim source files are in the UTF-8 encoding (or its ASCII subset). Other
164encodings are not supported. Any of the standard platform line termination
165sequences can be used - the Unix form using ASCII LF (linefeed), the Windows
166form using the ASCII sequence CR LF (return followed by linefeed), or the old
167Macintosh form using the ASCII CR (return) character. All of these forms can be
168used equally, regardless of the platform.
169
170
171Indentation
172-----------
173
174Nim's standard grammar describes an `indentation sensitive`:idx: language.
175This means that all the control structures are recognized by indentation.
176Indentation consists only of spaces; tabulators are not allowed.
177
178The indentation handling is implemented as follows: The lexer annotates the
179following token with the preceding number of spaces; indentation is not
180a separate token. This trick allows parsing of Nim with only 1 token of
181lookahead.
182
183The parser uses a stack of indentation levels: the stack consists of integers
184counting the spaces. The indentation information is queried at strategic
185places in the parser but ignored otherwise: The pseudo-terminal `IND{>}`
186denotes an indentation that consists of more spaces than the entry at the top
187of the stack; `IND{=}` an indentation that has the same number of spaces. `DED`
188is another pseudo terminal that describes the *action* of popping a value
189from the stack, `IND{>}` then implies to push onto the stack.
190
191With this notation we can now easily define the core of the grammar: A block of
192statements (simplified example)::
193
194  ifStmt = 'if' expr ':' stmt
195           (IND{=} 'elif' expr ':' stmt)*
196           (IND{=} 'else' ':' stmt)?
197
198  simpleStmt = ifStmt / ...
199
200  stmt = IND{>} stmt ^+ IND{=} DED  # list of statements
201       / simpleStmt                 # or a simple statement
202
203
204
205Comments
206--------
207
208Comments start anywhere outside a string or character literal with the
209hash character `#`.
210Comments consist of a concatenation of `comment pieces`:idx:. A comment piece
211starts with `#` and runs until the end of the line. The end of line characters
212belong to the piece. If the next line only consists of a comment piece with
213no other tokens between it and the preceding one, it does not start a new
214comment:
215
216
217.. code-block:: nim
218  i = 0     # This is a single comment over multiple lines.
219    # The lexer merges these two pieces.
220    # The comment continues here.
221
222
223`Documentation comments`:idx: are comments that start with two `##`.
224Documentation comments are tokens; they are only allowed at certain places in
225the input file as they belong to the syntax tree.
226
227
228Multiline comments
229------------------
230
231Starting with version 0.13.0 of the language Nim supports multiline comments.
232They look like:
233
234.. code-block:: nim
235  #[Comment here.
236  Multiple lines
237  are not a problem.]#
238
239Multiline comments support nesting:
240
241.. code-block:: nim
242  #[  #[ Multiline comment in already
243     commented out code. ]#
244  proc p[T](x: T) = discard
245  ]#
246
247Multiline documentation comments also exist and support nesting too:
248
249.. code-block:: nim
250  proc foo =
251    ##[Long documentation comment
252       here.
253    ]##
254
255
256Identifiers & Keywords
257----------------------
258
259Identifiers in Nim can be any string of letters, digits
260and underscores, with the following restrictions:
261
262* begins with a letter
263* does not end with an underscore `_`
264* two immediate following underscores `__` are not allowed:
265
266.. code-block::
267  letter ::= 'A'..'Z' | 'a'..'z' | '\x80'..'\xff'
268  digit ::= '0'..'9'
269  IDENTIFIER ::= letter ( ['_'] (letter | digit) )*
270
271Currently, any Unicode character with an ordinal value > 127 (non-ASCII) is
272classified as a `letter` and may thus be part of an identifier but later
273versions of the language may assign some Unicode characters to belong to the
274operator characters instead.
275
276The following keywords are reserved and cannot be used as identifiers:
277
278.. code-block:: nim
279   :file: keywords.txt
280
281Some keywords are unused; they are reserved for future developments of the
282language.
283
284
285Identifier equality
286-------------------
287
288Two identifiers are considered equal if the following algorithm returns true:
289
290.. code-block:: nim
291  proc sameIdentifier(a, b: string): bool =
292    a[0] == b[0] and
293      a.replace("_", "").toLowerAscii == b.replace("_", "").toLowerAscii
294
295That means only the first letters are compared in a case-sensitive manner. Other
296letters are compared case-insensitively within the ASCII range and underscores are ignored.
297
298This rather unorthodox way to do identifier comparisons is called
299`partial case-insensitivity`:idx: and has some advantages over the conventional
300case sensitivity:
301
302It allows programmers to mostly use their own preferred
303spelling style, be it humpStyle or snake_style, and libraries written
304by different programmers cannot use incompatible conventions.
305A Nim-aware editor or IDE can show the identifiers as preferred.
306Another advantage is that it frees the programmer from remembering
307the exact spelling of an identifier. The exception with respect to the first
308letter allows common code like `var foo: Foo` to be parsed unambiguously.
309
310Note that this rule also applies to keywords, meaning that `notin` is
311the same as `notIn` and `not_in` (all-lowercase version (`notin`, `isnot`)
312is the preferred way of writing keywords).
313
314Historically, Nim was a fully `style-insensitive`:idx: language. This meant that
315it was not case-sensitive and underscores were ignored and there was not even a
316distinction between `foo` and `Foo`.
317
318
319Keywords as identifiers
320-----------------------
321
322If a keyword is enclosed in backticks it loses its keyword property and becomes an ordinary identifier.
323
324Examples
325
326.. code-block:: nim
327  var `var` = "Hello Stropping"
328
329.. code-block:: nim
330  type Obj = object
331    `type`: int
332
333  let `object` = Obj(`type`: 9)
334  assert `object` is Obj
335  assert `object`.`type` == 9
336
337  var `var` = 42
338  let `let` = 8
339  assert `var` + `let` == 50
340
341  const `assert` = true
342  assert `assert`
343
344
345String literals
346---------------
347
348Terminal symbol in the grammar: `STR_LIT`.
349
350String literals can be delimited by matching double quotes, and can
351contain the following `escape sequences`:idx:\ :
352
353==================         ===================================================
354  Escape sequence          Meaning
355==================         ===================================================
356  ``\p``                   platform specific newline: CRLF on Windows,
357                           LF on Unix
358  ``\r``, ``\c``           `carriage return`:idx:
359  ``\n``, ``\l``           `line feed`:idx: (often called `newline`:idx:)
360  ``\f``                   `form feed`:idx:
361  ``\t``                   `tabulator`:idx:
362  ``\v``                   `vertical tabulator`:idx:
363  ``\\``                   `backslash`:idx:
364  ``\"``                   `quotation mark`:idx:
365  ``\'``                   `apostrophe`:idx:
366  ``\`` '0'..'9'+         `character with decimal value d`:idx:;
367                           all decimal digits directly
368                           following are used for the character
369  ``\a``                   `alert`:idx:
370  ``\b``                   `backspace`:idx:
371  ``\e``                   `escape`:idx: `[ESC]`:idx:
372  ``\x`` HH                `character with hex value HH`:idx:;
373                           exactly two hex digits are allowed
374  ``\u`` HHHH              `unicode codepoint with hex value HHHH`:idx:;
375                           exactly four hex digits are allowed
376  ``\u`` {H+}              `unicode codepoint`:idx:;
377                           all hex digits enclosed in `{}` are used for
378                           the codepoint
379==================         ===================================================
380
381
382Strings in Nim may contain any 8-bit value, even embedded zeros. However
383some operations may interpret the first binary zero as a terminator.
384
385
386Triple quoted string literals
387-----------------------------
388
389Terminal symbol in the grammar: `TRIPLESTR_LIT`.
390
391String literals can also be delimited by three double quotes `"""` ... `"""`.
392Literals in this form may run for several lines, may contain `"` and do not
393interpret any escape sequences.
394For convenience, when the opening `"""` is followed by a newline (there may
395be whitespace between the opening `"""` and the newline),
396the newline (and the preceding whitespace) is not included in the string. The
397ending of the string literal is defined by the pattern `"""[^"]`, so this:
398
399.. code-block:: nim
400  """"long string within quotes""""
401
402Produces::
403
404  "long string within quotes"
405
406
407Raw string literals
408-------------------
409
410Terminal symbol in the grammar: `RSTR_LIT`.
411
412There are also raw string literals that are preceded with the
413letter `r` (or `R`) and are delimited by matching double quotes (just
414like ordinary string literals) and do not interpret the escape sequences.
415This is especially convenient for regular expressions or Windows paths:
416
417.. code-block:: nim
418
419  var f = openFile(r"C:\texts\text.txt") # a raw string, so ``\t`` is no tab
420
421To produce a single `"` within a raw string literal, it has to be doubled:
422
423.. code-block:: nim
424
425  r"a""b"
426
427Produces::
428
429  a"b
430
431`r""""` is not possible with this notation, because the three leading
432quotes introduce a triple quoted string literal. `r"""` is the same
433as `"""` since triple quoted string literals do not interpret escape
434sequences either.
435
436
437Generalized raw string literals
438-------------------------------
439
440Terminal symbols in the grammar: `GENERALIZED_STR_LIT`,
441`GENERALIZED_TRIPLESTR_LIT`.
442
443The construct `identifier"string literal"` (without whitespace between the
444identifier and the opening quotation mark) is a
445generalized raw string literal. It is a shortcut for the construct
446`identifier(r"string literal")`, so it denotes a routine call with a
447raw string literal as its only argument. Generalized raw string literals
448are especially convenient for embedding mini languages directly into Nim
449(for example regular expressions).
450
451The construct `identifier"""string literal"""` exists too. It is a shortcut
452for `identifier("""string literal""")`.
453
454
455Character literals
456------------------
457
458Character literals are enclosed in single quotes `''` and can contain the
459same escape sequences as strings - with one exception: the platform
460dependent `newline`:idx: (``\p``)
461is not allowed as it may be wider than one character (it can be the pair
462CR/LF). Here are the valid `escape sequences`:idx: for character
463literals:
464
465==================         ===================================================
466  Escape sequence          Meaning
467==================         ===================================================
468  ``\r``, ``\c``           `carriage return`:idx:
469  ``\n``, ``\l``           `line feed`:idx:
470  ``\f``                   `form feed`:idx:
471  ``\t``                   `tabulator`:idx:
472  ``\v``                   `vertical tabulator`:idx:
473  ``\\``                   `backslash`:idx:
474  ``\"``                   `quotation mark`:idx:
475  ``\'``                   `apostrophe`:idx:
476  ``\`` '0'..'9'+          `character with decimal value d`:idx:;
477                           all decimal digits directly
478                           following are used for the character
479  ``\a``                   `alert`:idx:
480  ``\b``                   `backspace`:idx:
481  ``\e``                   `escape`:idx: `[ESC]`:idx:
482  ``\x`` HH                `character with hex value HH`:idx:;
483                           exactly two hex digits are allowed
484==================         ===================================================
485
486A character is not a Unicode character but a single byte.
487
488Rationale: It enables the efficient support of `array[char, int]` or
489`set[char]`.
490
491The `Rune` type can represent any Unicode character.
492`Rune` is declared in the `unicode module <unicode.html>`_.
493
494A character literal that does not end in `'` is interpreted as `'` if there
495is a preceeding backtick token. There must be no whitespace between the preceeding
496backtick token and the character literal. This special case ensures that a declaration
497like ``proc `'customLiteral`(s: string)`` is valid. ``proc `'customLiteral`(s: string)``
498is the same as ``proc `'\''customLiteral`(s: string)``.
499
500See also `Custom Numeric Literals <#custom-numeric-literals>`_.
501
502
503Numeric Literals
504----------------
505
506Numeric literals have the form::
507
508  hexdigit = digit | 'A'..'F' | 'a'..'f'
509  octdigit = '0'..'7'
510  bindigit = '0'..'1'
511  unary_minus = '-' # See the section about unary minus
512  HEX_LIT = unary_minus? '0' ('x' | 'X' ) hexdigit ( ['_'] hexdigit )*
513  DEC_LIT = unary_minus? digit ( ['_'] digit )*
514  OCT_LIT = unary_minus? '0' 'o' octdigit ( ['_'] octdigit )*
515  BIN_LIT = unary_minus? '0' ('b' | 'B' ) bindigit ( ['_'] bindigit )*
516
517  INT_LIT = HEX_LIT
518          | DEC_LIT
519          | OCT_LIT
520          | BIN_LIT
521
522  INT8_LIT = INT_LIT ['\''] ('i' | 'I') '8'
523  INT16_LIT = INT_LIT ['\''] ('i' | 'I') '16'
524  INT32_LIT = INT_LIT ['\''] ('i' | 'I') '32'
525  INT64_LIT = INT_LIT ['\''] ('i' | 'I') '64'
526
527  UINT_LIT = INT_LIT ['\''] ('u' | 'U')
528  UINT8_LIT = INT_LIT ['\''] ('u' | 'U') '8'
529  UINT16_LIT = INT_LIT ['\''] ('u' | 'U') '16'
530  UINT32_LIT = INT_LIT ['\''] ('u' | 'U') '32'
531  UINT64_LIT = INT_LIT ['\''] ('u' | 'U') '64'
532
533  exponent = ('e' | 'E' ) ['+' | '-'] digit ( ['_'] digit )*
534  FLOAT_LIT = unary_minus? digit (['_'] digit)* (('.' digit (['_'] digit)* [exponent]) |exponent)
535  FLOAT32_SUFFIX = ('f' | 'F') ['32']
536  FLOAT32_LIT = HEX_LIT '\'' FLOAT32_SUFFIX
537              | (FLOAT_LIT | DEC_LIT | OCT_LIT | BIN_LIT) ['\''] FLOAT32_SUFFIX
538  FLOAT64_SUFFIX = ( ('f' | 'F') '64' ) | 'd' | 'D'
539  FLOAT64_LIT = HEX_LIT '\'' FLOAT64_SUFFIX
540              | (FLOAT_LIT | DEC_LIT | OCT_LIT | BIN_LIT) ['\''] FLOAT64_SUFFIX
541
542  CUSTOM_NUMERIC_LIT = (FLOAT_LIT | INT_LIT) '\'' CUSTOM_NUMERIC_SUFFIX
543
544  # CUSTOM_NUMERIC_SUFFIX is any Nim identifier that is not
545  # a pre-defined type suffix.
546
547
548As can be seen in the productions, numeric literals can contain underscores
549for readability. Integer and floating-point literals may be given in decimal (no
550prefix), binary (prefix `0b`), octal (prefix `0o`), and hexadecimal
551(prefix `0x`) notation.
552
553The fact that the unary minus `-` in a number literal like `-1` is considered
554to be part of the literal is a late addition to the language. The rationale is that
555an expression `-128'i8` should be valid and without this special case, this would
556be impossible -- `128` is not a valid `int8` value, only `-128` is.
557
558For the `unary_minus` rule there are further restrictions that are not covered
559in the formal grammar. For `-` to be part of the number literal its immediately
560preceeding character has to be in the
561set `{' ', '\t', '\n', '\r', ',', ';', '(', '[', '{'}`. This set was designed to
562cover most cases in a natural manner.
563
564In the following examples, `-1` is a single token:
565
566.. code-block:: nim
567
568  echo -1
569  echo(-1)
570  echo [-1]
571  echo 3,-1
572
573  "abc";-1
574
575In the following examples, `-1` is parsed as two separate tokens
576(as `-`:tok: `1`:tok:):
577
578.. code-block:: nim
579
580  echo x-1
581  echo (int)-1
582  echo [a]-1
583  "abc"-1
584
585
586The suffix starting with an apostrophe ('\'') is called a
587`type suffix`:idx:. Literals without a type suffix are of an integer type
588unless the literal contains a dot or `E|e` in which case it is of
589type `float`. This integer type is `int` if the literal is in the range
590`low(int32)..high(int32)`, otherwise it is `int64`.
591For notational convenience, the apostrophe of a type suffix
592is optional if it is not ambiguous (only hexadecimal floating-point literals
593with a type suffix can be ambiguous).
594
595
596The pre-defined type suffixes are:
597
598=================    =========================
599  Type Suffix        Resulting type of literal
600=================    =========================
601  `'i8`              int8
602  `'i16`             int16
603  `'i32`             int32
604  `'i64`             int64
605  `'u`               uint
606  `'u8`              uint8
607  `'u16`             uint16
608  `'u32`             uint32
609  `'u64`             uint64
610  `'f`               float32
611  `'d`               float64
612  `'f32`             float32
613  `'f64`             float64
614=================    =========================
615
616Floating-point literals may also be in binary, octal or hexadecimal
617notation:
618`0B0_10001110100_0000101001000111101011101111111011000101001101001001'f64`
619is approximately 1.72826e35 according to the IEEE floating-point standard.
620
621Literals must match the datatype, for example, `333'i8` is an invalid literal.
622Non-base-10 literals are used mainly for flags and bit pattern representations,
623therefore the checking is done on bit width and not on value range.
624Hence: 0b10000000'u8 == 0x80'u8 == 128, but, 0b10000000'i8 == 0x80'i8 == -1
625instead of causing an overflow error.
626
627
628Custom Numeric Literals
629~~~~~~~~~~~~~~~~~~~~~~~
630
631If the suffix is not predefined, then the suffix is assumed to be a call
632to a proc, template, macro or other callable identifier that is passed the
633string containing the literal. The callable identifier needs to be declared
634with a special ``'`` prefix:
635
636.. code-block:: nim
637
638  import strutils
639  type u4 = distinct uint8 # a 4-bit unsigned integer aka "nibble"
640  proc `'u4`(n: string): u4 =
641    # The leading ' is required.
642    result = (parseInt(n) and 0x0F).u4
643
644  var x = 5'u4
645
646More formally, a custom numeric literal `123'custom` is transformed
647to r"123".`'custom` in the parsing step. There is no AST node kind that
648corresponds to this transformation. The transformation naturally handles
649the case that additional parameters are passed to the callee:
650
651.. code-block:: nim
652
653  import strutils
654  type u4 = distinct uint8 # a 4-bit unsigned integer aka "nibble"
655  proc `'u4`(n: string; moreData: int): u4 =
656    result = (parseInt(n) and 0x0F).u4
657
658  var x = 5'u4(123)
659
660Custom numeric literals are covered by the grammar rule named `CUSTOM_NUMERIC_LIT`.
661A custom numeric literal is a single token.
662
663
664Operators
665---------
666
667Nim allows user defined operators. An operator is any combination of the
668following characters::
669
670       =     +     -     *     /     <     >
671       @     $     ~     &     %     |
672       !     ?     ^     .     :     \
673
674(The grammar uses the terminal OPR to refer to operator symbols as
675defined here.)
676
677These keywords are also operators:
678`and or not xor shl shr div mod in notin is isnot of as from`.
679
680`.`:tok:, `=`:tok:, `:`:tok:, `::`:tok: are not available as general operators; they
681are used for other notational purposes.
682
683`*:` is as a special case treated as the two tokens `*`:tok: and `:`:tok:
684(to support `var v*: T`).
685
686The `not` keyword is always a unary operator, `a not b` is parsed
687as `a(not b)`, not as `(a) not (b)`.
688
689
690Other tokens
691------------
692
693The following strings denote other tokens::
694
695    `   (    )     {    }     [    ]    ,  ;   [.    .]  {.   .}  (.  .)  [:
696
697
698The `slice`:idx: operator `..`:tok: takes precedence over other tokens that
699contain a dot: `{..}` are the three tokens `{`:tok:, `..`:tok:, `}`:tok:
700and not the two tokens `{.`:tok:, `.}`:tok:.
701
702
703Unicode Operators
704-----------------
705
706Under the `--experimental:unicodeOperators` switch these Unicode operators are
707also parsed as operators::
708
709  ∙ ∘ × ★ ⊗ ⊘ ⊙ ⊛ ⊠ ⊡ ∩ ∧ ⊓   # same priority as * (multiplication)
710  ± ⊕ ⊖ ⊞ ⊟ ∪ ∨ ⊔             # same priority as + (addition)
711
712
713If enabled, Unicode operators can be combined with non-Unicode operator
714symbols. The usual precedence extensions then apply, for example, `⊠=` is an
715assignment like operator just like `*=` is.
716
717No Unicode normalization step is performed.
718
719**Note**: Due to parser limitations one **cannot** enable this feature via a
720pragma `{.experimental: "unicodeOperators".}` reliably.
721
722
723Syntax
724======
725
726This section lists Nim's standard syntax. How the parser handles
727the indentation is already described in the `Lexical Analysis`_ section.
728
729Nim allows user-definable operators.
730Binary operators have 11 different levels of precedence.
731
732
733
734Associativity
735-------------
736
737Binary operators whose first character is `^` are right-associative, all
738other binary operators are left-associative.
739
740.. code-block:: nim
741  proc `^/`(x, y: float): float =
742    # a right-associative division operator
743    result = x / y
744  echo 12 ^/ 4 ^/ 8 # 24.0 (4 / 8 = 0.5, then 12 / 0.5 = 24.0)
745  echo 12  / 4  / 8 # 0.375 (12 / 4 = 3.0, then 3 / 8 = 0.375)
746
747Precedence
748----------
749
750Unary operators always bind stronger than any binary
751operator: `$a + b` is `($a) + b` and not `$(a + b)`.
752
753If a unary operator's first character is `@` it is a `sigil-like`:idx:
754operator which binds stronger than a `primarySuffix`: `@x.abc` is parsed
755as `(@x).abc` whereas `$x.abc` is parsed as `$(x.abc)`.
756
757
758For binary operators that are not keywords, the precedence is determined by the
759following rules:
760
761Operators ending in either `->`, `~>` or `=>` are called
762`arrow like`:idx:, and have the lowest precedence of all operators.
763
764If the operator ends with `=` and its first character is none of
765`<`, `>`, `!`, `=`, `~`, `?`, it is an *assignment operator* which
766has the second-lowest precedence.
767
768Otherwise, precedence is determined by the first character.
769
770
771================  =======================================================  ==================  ===============
772Precedence level    Operators                                              First character     Terminal symbol
773================  =======================================================  ==================  ===============
774 10 (highest)                                                              `$  ^`              OP10
775  9               `*    /    div   mod   shl  shr  %`                      `*  %  \  /`        OP9
776  8               `+    -`                                                 `+  -  ~  |`        OP8
777  7               `&`                                                      `&`                 OP7
778  6               `..`                                                     `.`                 OP6
779  5               `==  <= < >= > !=  in notin is isnot not of as from`     `=  <  >  !`        OP5
780  4               `and`                                                                        OP4
781  3               `or xor`                                                                     OP3
782  2                                                                        `@  :  ?`           OP2
783  1               *assignment operator* (like `+=`, `*=`)                                      OP1
784  0 (lowest)      *arrow like operator* (like `->`, `=>`)                                      OP0
785================  =======================================================  ==================  ===============
786
787
788Whether an operator is used as a prefix operator is also affected by preceding
789whitespace (this parsing change was introduced with version 0.13.0):
790
791.. code-block:: nim
792  echo $foo
793  # is parsed as
794  echo($foo)
795
796
797Spacing also determines whether `(a, b)` is parsed as an argument list
798of a call or whether it is parsed as a tuple constructor:
799
800.. code-block:: nim
801  echo(1, 2) # pass 1 and 2 to echo
802
803.. code-block:: nim
804  echo (1, 2) # pass the tuple (1, 2) to echo
805
806Dot-like operators
807------------------
808
809Terminal symbol in the grammar: `DOTLIKEOP`.
810
811Dot-like operators are operators starting with `.`, but not with `..`, for e.g. `.?`;
812they have the same precedence as `.`, so that `a.?b.c` is parsed as `(a.?b).c` instead of `a.?(b.c)`.
813
814
815Grammar
816-------
817
818The grammar's start symbol is `module`.
819
820.. include:: grammar.txt
821   :literal:
822
823
824
825Order of evaluation
826===================
827
828Order of evaluation is strictly left-to-right, inside-out as it is typical for most others
829imperative programming languages:
830
831.. code-block:: nim
832    :test: "nim c $1"
833
834  var s = ""
835
836  proc p(arg: int): int =
837    s.add $arg
838    result = arg
839
840  discard p(p(1) + p(2))
841
842  doAssert s == "123"
843
844
845Assignments are not special, the left-hand-side expression is evaluated before the
846right-hand side:
847
848.. code-block:: nim
849    :test: "nim c $1"
850
851  var v = 0
852  proc getI(): int =
853    result = v
854    inc v
855
856  var a, b: array[0..2, int]
857
858  proc someCopy(a: var int; b: int) = a = b
859
860  a[getI()] = getI()
861
862  doAssert a == [1, 0, 0]
863
864  v = 0
865  someCopy(b[getI()], getI())
866
867  doAssert b == [1, 0, 0]
868
869
870Rationale: Consistency with overloaded assignment or assignment-like operations,
871`a = b` can be read as `performSomeCopy(a, b)`.
872
873
874However, the concept of "order of evaluation" is only applicable after the code
875was normalized: The normalization involves template expansions and argument
876reorderings that have been passed to named parameters:
877
878.. code-block:: nim
879    :test: "nim c $1"
880
881  var s = ""
882
883  proc p(): int =
884    s.add "p"
885    result = 5
886
887  proc q(): int =
888    s.add "q"
889    result = 3
890
891  # Evaluation order is 'b' before 'a' due to template
892  # expansion's semantics.
893  template swapArgs(a, b): untyped =
894    b + a
895
896  doAssert swapArgs(p() + q(), q() - p()) == 6
897  doAssert s == "qppq"
898
899  # Evaluation order is not influenced by named parameters:
900  proc construct(first, second: int) =
901    discard
902
903  # 'p' is evaluated before 'q'!
904  construct(second = q(), first = p())
905
906  doAssert s == "qppqpq"
907
908
909Rationale: This is far easier to implement than hypothetical alternatives.
910
911
912Constants and Constant Expressions
913==================================
914
915A `constant`:idx: is a symbol that is bound to the value of a constant
916expression. Constant expressions are restricted to depend only on the following
917categories of values and operations, because these are either built into the
918language or declared and evaluated before semantic analysis of the constant
919expression:
920
921* literals
922* built-in operators
923* previously declared constants and compile-time variables
924* previously declared macros and templates
925* previously declared procedures that have no side effects beyond
926  possibly modifying compile-time variables
927
928A constant expression can contain code blocks that may internally use all Nim
929features supported at compile time (as detailed in the next section below).
930Within such a code block, it is possible to declare variables and then later
931read and update them, or declare variables and pass them to procedures that
932modify them. However, the code in such a block must still adhere to the
933restrictions listed above for referencing values and operations outside the
934block.
935
936The ability to access and modify compile-time variables adds flexibility to
937constant expressions that may be surprising to those coming from other
938statically typed languages. For example, the following code echoes the beginning
939of the Fibonacci series **at compile-time**. (This is a demonstration of
940flexibility in defining constants, not a recommended style for solving this
941problem.)
942
943.. code-block:: nim
944    :test: "nim c $1"
945  import std/strformat
946
947  var fibN {.compileTime.}: int
948  var fibPrev {.compileTime.}: int
949  var fibPrevPrev {.compileTime.}: int
950
951  proc nextFib(): int =
952    result = if fibN < 2:
953      fibN
954    else:
955      fibPrevPrev + fibPrev
956    inc(fibN)
957    fibPrevPrev = fibPrev
958    fibPrev = result
959
960  const f0 = nextFib()
961  const f1 = nextFib()
962
963  const displayFib = block:
964    const f2 = nextFib()
965    var result = fmt"Fibonacci sequence: {f0}, {f1}, {f2}"
966    for i in 3..12:
967      add(result, fmt", {nextFib()}")
968    result
969
970  static:
971    echo displayFib
972
973
974Restrictions on Compile-Time Execution
975======================================
976
977Nim code that will be executed at compile time cannot use the following
978language features:
979
980* methods
981* closure iterators
982* the `cast` operator
983* reference (pointer) types
984* FFI
985
986The use of wrappers that use FFI and/or `cast` is also disallowed. Note that
987these wrappers include the ones in the standard libraries.
988
989Some or all of these restrictions are likely to be lifted over time.
990
991
992Types
993=====
994
995All expressions have a type that is known during semantic analysis. Nim
996is statically typed. One can declare new types, which is in essence defining
997an identifier that can be used to denote this custom type.
998
999These are the major type classes:
1000
1001* ordinal types (consist of integer, bool, character, enumeration
1002  (and subranges thereof) types)
1003* floating-point types
1004* string type
1005* structured types
1006* reference (pointer) type
1007* procedural type
1008* generic type
1009
1010
1011Ordinal types
1012-------------
1013Ordinal types have the following characteristics:
1014
1015- Ordinal types are countable and ordered. This property allows the operation
1016  of functions such as `inc`, `ord`, and `dec` on ordinal types to
1017  be defined.
1018- Ordinal types have a smallest possible value, accessible with `low(type)`.
1019  Trying to count further down than the smallest value produces a panic or
1020  a static error.
1021- Ordinal types have a largest possible value, accessible with `high(type)`.
1022  Trying to count further up than the largest value produces a panic or
1023  a static error.
1024
1025Integers, bool, characters, and enumeration types (and subranges of these
1026types) belong to ordinal types.
1027
1028A distinct type is an ordinal type if its base type is an ordinal type.
1029
1030
1031Pre-defined integer types
1032-------------------------
1033These integer types are pre-defined:
1034
1035`int`
1036  the generic signed integer type; its size is platform-dependent and has the
1037  same size as a pointer. This type should be used in general. An integer
1038  literal that has no type suffix is of this type if it is in the range
1039  `low(int32)..high(int32)` otherwise the literal's type is `int64`.
1040
1041`int`\ XX
1042  additional signed integer types of XX bits use this naming scheme
1043  (example: int16 is a 16-bit wide integer).
1044  The current implementation supports `int8`, `int16`, `int32`, `int64`.
1045  Literals of these types have the suffix 'iXX.
1046
1047`uint`
1048  the generic `unsigned integer`:idx: type; its size is platform-dependent and
1049  has the same size as a pointer. An integer literal with the type
1050  suffix `'u` is of this type.
1051
1052`uint`\ XX
1053  additional unsigned integer types of XX bits use this naming scheme
1054  (example: uint16 is a 16-bit wide unsigned integer).
1055  The current implementation supports `uint8`, `uint16`, `uint32`,
1056  `uint64`. Literals of these types have the suffix 'uXX.
1057  Unsigned operations all wrap around; they cannot lead to over- or
1058  underflow errors.
1059
1060
1061In addition to the usual arithmetic operators for signed and unsigned integers
1062(`+ - *` etc.) there are also operators that formally work on *signed*
1063integers but treat their arguments as *unsigned*: They are mostly provided
1064for backwards compatibility with older versions of the language that lacked
1065unsigned integer types. These unsigned operations for signed integers use
1066the `%` suffix as convention:
1067
1068
1069======================   ======================================================
1070operation                meaning
1071======================   ======================================================
1072`a +% b`                 unsigned integer addition
1073`a -% b`                 unsigned integer subtraction
1074`a *% b`                 unsigned integer multiplication
1075`a /% b`                 unsigned integer division
1076`a %% b`                 unsigned integer modulo operation
1077`a <% b`                 treat `a` and `b` as unsigned and compare
1078`a <=% b`                treat `a` and `b` as unsigned and compare
1079`ze(a)`                  extends the bits of `a` with zeros until it has the
1080                         width of the `int` type
1081`toU8(a)`                treats `a` as unsigned and converts it to an
1082                         unsigned integer of 8 bits (but still the
1083                         `int8` type)
1084`toU16(a)`               treats `a` as unsigned and converts it to an
1085                         unsigned integer of 16 bits (but still the
1086                         `int16` type)
1087`toU32(a)`               treats `a` as unsigned and converts it to an
1088                         unsigned integer of 32 bits (but still the
1089                         `int32` type)
1090======================   ======================================================
1091
1092`Automatic type conversion`:idx: is performed in expressions where different
1093kinds of integer types are used: the smaller type is converted to the larger.
1094
1095A `narrowing type conversion`:idx: converts a larger to a smaller type (for
1096example `int32 -> int16`). A `widening type conversion`:idx: converts a
1097smaller type to a larger type (for example `int16 -> int32`). In Nim only
1098widening type conversions are *implicit*:
1099
1100.. code-block:: nim
1101  var myInt16 = 5i16
1102  var myInt: int
1103  myInt16 + 34     # of type `int16`
1104  myInt16 + myInt  # of type `int`
1105  myInt16 + 2i32   # of type `int32`
1106
1107However, `int` literals are implicitly convertible to a smaller integer type
1108if the literal's value fits this smaller type and such a conversion is less
1109expensive than other implicit conversions, so `myInt16 + 34` produces
1110an `int16` result.
1111
1112For further details, see `Convertible relation
1113<#type-relations-convertible-relation>`_.
1114
1115
1116Subrange types
1117--------------
1118A subrange type is a range of values from an ordinal or floating-point type (the base
1119type). To define a subrange type, one must specify its limiting values -- the
1120lowest and highest value of the type. For example:
1121
1122.. code-block:: nim
1123  type
1124    Subrange = range[0..5]
1125    PositiveFloat = range[0.0..Inf]
1126    Positive* = range[1..high(int)] # as defined in `system`
1127
1128
1129`Subrange` is a subrange of an integer which can only hold the values 0
1130to 5. `PositiveFloat` defines a subrange of all positive floating-point values.
1131NaN does not belong to any subrange of floating-point types.
1132Assigning any other value to a variable of type `Subrange` is a
1133panic (or a static error if it can be determined during
1134semantic analysis). Assignments from the base type to one of its subrange types
1135(and vice versa) are allowed.
1136
1137A subrange type has the same size as its base type (`int` in the
1138Subrange example).
1139
1140
1141Pre-defined floating-point types
1142--------------------------------
1143
1144The following floating-point types are pre-defined:
1145
1146`float`
1147  the generic floating-point type; its size used to be platform-dependent,
1148  but now it is always mapped to `float64`.
1149  This type should be used in general.
1150
1151`float`\ XX
1152  an implementation may define additional floating-point types of XX bits using
1153  this naming scheme (example: `float64` is a 64-bit wide float). The current
1154  implementation supports `float32` and `float64`. Literals of these types
1155  have the suffix 'fXX.
1156
1157
1158Automatic type conversion in expressions with different kinds
1159of floating-point types is performed: See `Convertible relation`_ for further
1160details. Arithmetic performed on floating-point types follows the IEEE
1161standard. Integer types are not converted to floating-point types automatically
1162and vice versa.
1163
1164The IEEE standard defines five types of floating-point exceptions:
1165
1166* Invalid: operations with mathematically invalid operands,
1167  for example 0.0/0.0, sqrt(-1.0), and log(-37.8).
1168* Division by zero: divisor is zero and dividend is a finite nonzero number,
1169  for example 1.0/0.0.
1170* Overflow: operation produces a result that exceeds the range of the exponent,
1171  for example MAXDOUBLE+0.0000000000001e308.
1172* Underflow: operation produces a result that is too small to be represented
1173  as a normal number, for example, MINDOUBLE * MINDOUBLE.
1174* Inexact: operation produces a result that cannot be represented with infinite
1175  precision, for example, 2.0 / 3.0, log(1.1) and 0.1 in input.
1176
1177The IEEE exceptions are either ignored during execution or mapped to the
1178Nim exceptions: `FloatInvalidOpDefect`:idx:, `FloatDivByZeroDefect`:idx:,
1179`FloatOverflowDefect`:idx:, `FloatUnderflowDefect`:idx:,
1180and `FloatInexactDefect`:idx:.
1181These exceptions inherit from the `FloatingPointDefect`:idx: base class.
1182
1183Nim provides the pragmas `nanChecks`:idx: and `infChecks`:idx: to control
1184whether the IEEE exceptions are ignored or trap a Nim exception:
1185
1186.. code-block:: nim
1187  {.nanChecks: on, infChecks: on.}
1188  var a = 1.0
1189  var b = 0.0
1190  echo b / b # raises FloatInvalidOpDefect
1191  echo a / b # raises FloatOverflowDefect
1192
1193In the current implementation `FloatDivByZeroDefect` and `FloatInexactDefect`
1194are never raised. `FloatOverflowDefect` is raised instead of
1195`FloatDivByZeroDefect`.
1196There is also a `floatChecks`:idx: pragma that is a short-cut for the
1197combination of `nanChecks` and `infChecks` pragmas. `floatChecks` are
1198turned off as default.
1199
1200The only operations that are affected by the `floatChecks` pragma are
1201the `+`, `-`, `*`, `/` operators for floating-point types.
1202
1203An implementation should always use the maximum precision available to evaluate
1204floating-point values during semantic analysis; this means expressions like
1205`0.09'f32 + 0.01'f32 == 0.09'f64 + 0.01'f64` that are evaluating during
1206constant folding are true.
1207
1208
1209Boolean type
1210------------
1211The boolean type is named `bool`:idx: in Nim and can be one of the two
1212pre-defined values `true` and `false`. Conditions in `while`,
1213`if`, `elif`, `when`-statements need to be of type `bool`.
1214
1215This condition holds::
1216
1217  ord(false) == 0 and ord(true) == 1
1218
1219The operators `not, and, or, xor, <, <=, >, >=, !=, ==` are defined
1220for the bool type. The `and` and `or` operators perform short-cut
1221evaluation. Example:
1222
1223.. code-block:: nim
1224
1225  while p != nil and p.name != "xyz":
1226    # p.name is not evaluated if p == nil
1227    p = p.next
1228
1229
1230The size of the bool type is one byte.
1231
1232
1233Character type
1234--------------
1235The character type is named `char` in Nim. Its size is one byte.
1236Thus it cannot represent a UTF-8 character, but a part of it.
1237
1238The `Rune` type is used for Unicode characters, it can represent any Unicode
1239character. `Rune` is declared in the `unicode module <unicode.html>`_.
1240
1241
1242
1243
1244Enumeration types
1245-----------------
1246Enumeration types define a new type whose values consist of the ones
1247specified. The values are ordered. Example:
1248
1249.. code-block:: nim
1250
1251  type
1252    Direction = enum
1253      north, east, south, west
1254
1255
1256Now the following holds::
1257
1258  ord(north) == 0
1259  ord(east) == 1
1260  ord(south) == 2
1261  ord(west) == 3
1262
1263  # Also allowed:
1264  ord(Direction.west) == 3
1265
1266The implied order is: north < east < south < west. The comparison operators can be used
1267with enumeration types. Instead of `north` etc, the enum value can also
1268be qualified with the enum type that it resides in, `Direction.north`.
1269
1270For better interfacing to other programming languages, the fields of enum
1271types can be assigned an explicit ordinal value. However, the ordinal values
1272have to be in ascending order. A field whose ordinal value is not
1273explicitly given is assigned the value of the previous field + 1.
1274
1275An explicit ordered enum can have *holes*:
1276
1277.. code-block:: nim
1278  type
1279    TokenType = enum
1280      a = 2, b = 4, c = 89 # holes are valid
1281
1282However, it is then not ordinal anymore, so it is impossible to use these
1283enums as an index type for arrays. The procedures `inc`, `dec`, `succ`
1284and `pred` are not available for them either.
1285
1286
1287The compiler supports the built-in stringify operator `$` for enumerations.
1288The stringify's result can be controlled by explicitly giving the string
1289values to use:
1290
1291.. code-block:: nim
1292
1293  type
1294    MyEnum = enum
1295      valueA = (0, "my value A"),
1296      valueB = "value B",
1297      valueC = 2,
1298      valueD = (3, "abc")
1299
1300As can be seen from the example, it is possible to both specify a field's
1301ordinal value and its string value by using a tuple. It is also
1302possible to only specify one of them.
1303
1304An enum can be marked with the `pure` pragma so that its fields are
1305added to a special module-specific hidden scope that is only queried
1306as the last attempt. Only non-ambiguous symbols are added to this scope.
1307But one can always access these via type qualification written
1308as `MyEnum.value`:
1309
1310.. code-block:: nim
1311
1312  type
1313    MyEnum {.pure.} = enum
1314      valueA, valueB, valueC, valueD, amb
1315
1316    OtherEnum {.pure.} = enum
1317      valueX, valueY, valueZ, amb
1318
1319
1320  echo valueA # MyEnum.valueA
1321  echo amb    # Error: Unclear whether it's MyEnum.amb or OtherEnum.amb
1322  echo MyEnum.amb # OK.
1323
1324To implement bit fields with enums see `Bit fields <#set-type-bit-fields>`_
1325
1326Overloadable enum field names
1327-----------------------------
1328
1329To be enabled via `{.experimental: "overloadableEnums".}`.
1330
1331Enum field names are overloadable much like routines. When an overloaded
1332enum field is used, it produces a closed sym choice construct, here
1333written as `(E|E)`.
1334During overload resolution the right `E` is picked, if possible.
1335For (array/object...) constructors the right `E` is picked, comparable to
1336how `[byte(1), 2, 3]` works, one needs to use `[T.E, E2, E3]`. Ambiguous
1337enum fields produce a static error:
1338
1339.. code-block:: nim
1340    :test: "nim c $1"
1341
1342  {.experimental: "overloadableEnums".}
1343
1344  type
1345    E1 = enum
1346      value1,
1347      value2
1348    E2 = enum
1349      value1,
1350      value2 = 4
1351
1352  const
1353    Lookuptable = [
1354      E1.value1: "1",
1355      value2: "2"
1356    ]
1357
1358  proc p(e: E1) =
1359    # disambiguation in 'case' statements:
1360    case e
1361    of value1: echo "A"
1362    of value2: echo "B"
1363
1364  p value2
1365
1366
1367String type
1368-----------
1369All string literals are of the type `string`. A string in Nim is very
1370similar to a sequence of characters. However, strings in Nim are both
1371zero-terminated and have a length field. One can retrieve the length with the
1372builtin `len` procedure; the length never counts the terminating zero.
1373
1374The terminating zero cannot be accessed unless the string is converted
1375to the `cstring` type first. The terminating zero assures that this
1376conversion can be done in O(1) and without any allocations.
1377
1378The assignment operator for strings always copies the string.
1379The `&` operator concatenates strings.
1380
1381Most native Nim types support conversion to strings with the special `$` proc.
1382When calling the `echo` proc, for example, the built-in stringify operation
1383for the parameter is called:
1384
1385.. code-block:: nim
1386
1387  echo 3 # calls `$` for `int`
1388
1389Whenever a user creates a specialized object, implementation of this procedure
1390provides for `string` representation.
1391
1392.. code-block:: nim
1393  type
1394    Person = object
1395      name: string
1396      age: int
1397
1398  proc `$`(p: Person): string = # `$` always returns a string
1399    result = p.name & " is " &
1400            $p.age & # we *need* the `$` in front of p.age which
1401                     # is natively an integer to convert it to
1402                     # a string
1403            " years old."
1404
1405While `$p.name` can also be used, the `$` operation on a string does
1406nothing. Note that we cannot rely on automatic conversion from an `int` to
1407a `string` like we can for the `echo` proc.
1408
1409Strings are compared by their lexicographical order. All comparison operators
1410are available. Strings can be indexed like arrays (lower bound is 0). Unlike
1411arrays, they can be used in case statements:
1412
1413.. code-block:: nim
1414
1415  case paramStr(i)
1416  of "-v": incl(options, optVerbose)
1417  of "-h", "-?": incl(options, optHelp)
1418  else: write(stdout, "invalid command line option!\n")
1419
1420Per convention, all strings are UTF-8 strings, but this is not enforced. For
1421example, when reading strings from binary files, they are merely a sequence of
1422bytes. The index operation `s[i]` means the i-th *char* of `s`, not the
1423i-th *unichar*. The iterator `runes` from the `unicode module
1424<unicode.html>`_ can be used for iteration over all Unicode characters.
1425
1426
1427cstring type
1428------------
1429
1430The `cstring` type meaning `compatible string` is the native representation
1431of a string for the compilation backend. For the C backend the `cstring` type
1432represents a pointer to a zero-terminated char array
1433compatible with the type `char*` in Ansi C. Its primary purpose lies in easy
1434interfacing with C. The index operation `s[i]` means the i-th *char* of
1435`s`; however no bounds checking for `cstring` is performed making the
1436index operation unsafe.
1437
1438A Nim `string` is implicitly convertible
1439to `cstring` for convenience. If a Nim string is passed to a C-style
1440variadic proc, it is implicitly converted to `cstring` too:
1441
1442.. code-block:: nim
1443  proc printf(formatstr: cstring) {.importc: "printf", varargs,
1444                                    header: "<stdio.h>".}
1445
1446  printf("This works %s", "as expected")
1447
1448Even though the conversion is implicit, it is not *safe*: The garbage collector
1449does not consider a `cstring` to be a root and may collect the underlying
1450memory. For this reason, the implicit conversion will be removed in future
1451releases of the Nim compiler. Certain idioms like conversion of a `const` string
1452to `cstring` are safe and will remain to be allowed.
1453
1454A `$` proc is defined for cstrings that returns a string. Thus to get a nim
1455string from a cstring:
1456
1457.. code-block:: nim
1458  var str: string = "Hello!"
1459  var cstr: cstring = str
1460  var newstr: string = $cstr
1461
1462`cstring` literals shouldn't be modified.
1463
1464.. code-block:: nim
1465  var x = cstring"literals"
1466  x[1] = 'A' # This is wrong!!!
1467
1468If the `cstring` originates from a regular memory (not read-only memory),
1469it can be modified:
1470
1471.. code-block:: nim
1472  var x = "123456"
1473  var s: cstring = x
1474  s[0] = 'u' # This is ok
1475
1476Structured types
1477----------------
1478A variable of a structured type can hold multiple values at the same
1479time. Structured types can be nested to unlimited levels. Arrays, sequences,
1480tuples, objects, and sets belong to the structured types.
1481
1482Array and sequence types
1483------------------------
1484Arrays are a homogeneous type, meaning that each element in the array has the
1485same type. Arrays always have a fixed length specified as a constant expression
1486(except for open arrays). They can be indexed by any ordinal type.
1487A parameter `A` may be an *open array*, in which case it is indexed by
1488integers from 0 to `len(A)-1`. An array expression may be constructed by the
1489array constructor `[]`. The element type of this array expression is
1490inferred from the type of the first element. All other elements need to be
1491implicitly convertible to this type.
1492
1493An array type can be defined using the `array[size, T]` syntax, or using
1494`array[lo..hi, T]` for arrays that start at an index other than zero.
1495
1496Sequences are similar to arrays but of dynamic length which may change
1497during runtime (like strings). Sequences are implemented as growable arrays,
1498allocating pieces of memory as items are added. A sequence `S` is always
1499indexed by integers from 0 to `len(S)-1` and its bounds are checked.
1500Sequences can be constructed by the array constructor `[]` in conjunction
1501with the array to sequence operator `@`. Another way to allocate space for a
1502sequence is to call the built-in `newSeq` procedure.
1503
1504A sequence may be passed to a parameter that is of type *open array*.
1505
1506Example:
1507
1508.. code-block:: nim
1509
1510  type
1511    IntArray = array[0..5, int] # an array that is indexed with 0..5
1512    IntSeq = seq[int] # a sequence of integers
1513  var
1514    x: IntArray
1515    y: IntSeq
1516  x = [1, 2, 3, 4, 5, 6]  # [] is the array constructor
1517  y = @[1, 2, 3, 4, 5, 6] # the @ turns the array into a sequence
1518
1519  let z = [1.0, 2, 3, 4] # the type of z is array[0..3, float]
1520
1521The lower bound of an array or sequence may be received by the built-in proc
1522`low()`, the higher bound by `high()`. The length may be
1523received by `len()`. `low()` for a sequence or an open array always returns
15240, as this is the first valid index.
1525One can append elements to a sequence with the `add()` proc or the `&`
1526operator, and remove (and get) the last element of a sequence with the
1527`pop()` proc.
1528
1529The notation `x[i]` can be used to access the i-th element of `x`.
1530
1531Arrays are always bounds checked (statically or at runtime). These
1532checks can be disabled via pragmas or invoking the compiler with the
1533`--boundChecks:off`:option: command-line switch.
1534
1535An array constructor can have explicit indexes for readability:
1536
1537.. code-block:: nim
1538
1539  type
1540    Values = enum
1541      valA, valB, valC
1542
1543  const
1544    lookupTable = [
1545      valA: "A",
1546      valB: "B",
1547      valC: "C"
1548    ]
1549
1550If an index is left out, `succ(lastIndex)` is used as the index
1551value:
1552
1553.. code-block:: nim
1554
1555  type
1556    Values = enum
1557      valA, valB, valC, valD, valE
1558
1559  const
1560    lookupTable = [
1561      valA: "A",
1562      "B",
1563      valC: "C",
1564      "D", "e"
1565    ]
1566
1567
1568
1569Open arrays
1570-----------
1571
1572Often fixed size arrays turn out to be too inflexible; procedures should
1573be able to deal with arrays of different sizes. The `openarray`:idx: type
1574allows this; it can only be used for parameters. Openarrays are always
1575indexed with an `int` starting at position 0. The `len`, `low`
1576and `high` operations are available for open arrays too. Any array with
1577a compatible base type can be passed to an openarray parameter, the index
1578type does not matter. In addition to arrays, sequences can also be passed
1579to an open array parameter.
1580
1581The openarray type cannot be nested: multidimensional openarrays are not
1582supported because this is seldom needed and cannot be done efficiently.
1583
1584.. code-block:: nim
1585  proc testOpenArray(x: openArray[int]) = echo repr(x)
1586
1587  testOpenArray([1,2,3])  # array[]
1588  testOpenArray(@[1,2,3]) # seq[]
1589
1590Varargs
1591-------
1592
1593A `varargs` parameter is an openarray parameter that additionally
1594allows to pass a variable number of arguments to a procedure. The compiler
1595converts the list of arguments to an array implicitly:
1596
1597.. code-block:: nim
1598  proc myWriteln(f: File, a: varargs[string]) =
1599    for s in items(a):
1600      write(f, s)
1601    write(f, "\n")
1602
1603  myWriteln(stdout, "abc", "def", "xyz")
1604  # is transformed to:
1605  myWriteln(stdout, ["abc", "def", "xyz"])
1606
1607This transformation is only done if the varargs parameter is the
1608last parameter in the procedure header. It is also possible to perform
1609type conversions in this context:
1610
1611.. code-block:: nim
1612  proc myWriteln(f: File, a: varargs[string, `$`]) =
1613    for s in items(a):
1614      write(f, s)
1615    write(f, "\n")
1616
1617  myWriteln(stdout, 123, "abc", 4.0)
1618  # is transformed to:
1619  myWriteln(stdout, [$123, $"def", $4.0])
1620
1621In this example `$` is applied to any argument that is passed to the
1622parameter `a`. (Note that `$` applied to strings is a nop.)
1623
1624Note that an explicit array constructor passed to a `varargs` parameter is
1625not wrapped in another implicit array construction:
1626
1627.. code-block:: nim
1628  proc takeV[T](a: varargs[T]) = discard
1629
1630  takeV([123, 2, 1]) # takeV's T is "int", not "array of int"
1631
1632
1633`varargs[typed]` is treated specially: It matches a variable list of arguments
1634of arbitrary type but *always* constructs an implicit array. This is required
1635so that the builtin `echo` proc does what is expected:
1636
1637.. code-block:: nim
1638  proc echo*(x: varargs[typed, `$`]) {...}
1639
1640  echo @[1, 2, 3]
1641  # prints "@[1, 2, 3]" and not "123"
1642
1643
1644Unchecked arrays
1645----------------
1646The `UncheckedArray[T]` type is a special kind of `array` where its bounds
1647are not checked. This is often useful to implement customized flexibly sized
1648arrays. Additionally, an unchecked array is translated into a C array of
1649undetermined size:
1650
1651.. code-block:: nim
1652  type
1653    MySeq = object
1654      len, cap: int
1655      data: UncheckedArray[int]
1656
1657Produces roughly this C code:
1658
1659.. code-block:: C
1660  typedef struct {
1661    NI len;
1662    NI cap;
1663    NI data[];
1664  } MySeq;
1665
1666The base type of the unchecked array may not contain any GC'ed memory but this
1667is currently not checked.
1668
1669**Future directions**: GC'ed memory should be allowed in unchecked arrays and
1670there should be an explicit annotation of how the GC is to determine the
1671runtime size of the array.
1672
1673
1674
1675Tuples and object types
1676-----------------------
1677A variable of a tuple or object type is a heterogeneous storage
1678container.
1679A tuple or object defines various named *fields* of a type. A tuple also
1680defines a lexicographic *order* of the fields. Tuples are meant to be
1681heterogeneous storage types with few abstractions. The `()` syntax
1682can be used to construct tuples. The order of the fields in the constructor
1683must match the order of the tuple's definition. Different tuple-types are
1684*equivalent* if they specify the same fields of the same type in the same
1685order. The *names* of the fields also have to be the same.
1686
1687The assignment operator for tuples copies each component.
1688The default assignment operator for objects copies each component. Overloading
1689of the assignment operator is described `here
1690<manual_experimental.html#type-bound-operations>`_.
1691
1692.. code-block:: nim
1693
1694  type
1695    Person = tuple[name: string, age: int] # type representing a person:
1696                                           # it consists of a name and an age.
1697  var person: Person
1698  person = (name: "Peter", age: 30)
1699  assert person.name == "Peter"
1700  # the same, but less readable:
1701  person = ("Peter", 30)
1702  assert person[0] == "Peter"
1703  assert Person is (string, int)
1704  assert (string, int) is Person
1705  assert Person isnot tuple[other: string, age: int] # `other` is a different identifier
1706
1707A tuple with one unnamed field can be constructed with the parentheses and a
1708trailing comma:
1709
1710.. code-block:: nim
1711  proc echoUnaryTuple(a: (int,)) =
1712    echo a[0]
1713
1714  echoUnaryTuple (1,)
1715
1716
1717In fact, a trailing comma is allowed for every tuple construction.
1718
1719The implementation aligns the fields for the best access performance. The alignment
1720is compatible with the way the C compiler does it.
1721
1722For consistency  with `object` declarations, tuples in a `type` section
1723can also be defined with indentation instead of `[]`:
1724
1725.. code-block:: nim
1726  type
1727    Person = tuple   # type representing a person
1728      name: string   # a person consists of a name
1729      age: Natural   # and an age
1730
1731Objects provide many features that tuples do not. Objects provide inheritance
1732and the ability to hide fields from other modules. Objects with inheritance
1733enabled have information about their type at runtime so that the `of` operator
1734can be used to determine the object's type. The `of` operator is similar to
1735the `instanceof` operator in Java.
1736
1737.. code-block:: nim
1738  type
1739    Person = object of RootObj
1740      name*: string   # the * means that `name` is accessible from other modules
1741      age: int        # no * means that the field is hidden
1742
1743    Student = ref object of Person # a student is a person
1744      id: int                      # with an id field
1745
1746  var
1747    student: Student
1748    person: Person
1749  assert(student of Student) # is true
1750  assert(student of Person) # also true
1751
1752Object fields that should be visible from outside the defining module have to
1753be marked by `*`. In contrast to tuples, different object types are
1754never *equivalent*, they are nominal types whereas tuples are structural.
1755Objects that have no ancestor are implicitly `final` and thus have no hidden
1756type information. One can use the `inheritable` pragma to
1757introduce new object roots apart from `system.RootObj`.
1758
1759.. code-block:: nim
1760  type
1761    Person = object # example of a final object
1762      name*: string
1763      age: int
1764
1765    Student = ref object of Person # Error: inheritance only works with non-final objects
1766      id: int
1767
1768
1769Object construction
1770-------------------
1771
1772Objects can also be created with an `object construction expression`:idx: that
1773has the syntax `T(fieldA: valueA, fieldB: valueB, ...)` where `T` is
1774an `object` type or a `ref object` type:
1775
1776.. code-block:: nim
1777  type
1778    Student = object
1779      name: string
1780      age: int
1781    PStudent = ref Student
1782  var a1 = Student(name: "Anton", age: 5)
1783  var a2 = PStudent(name: "Anton", age: 5)
1784  # this also works directly:
1785  var a3 = (ref Student)(name: "Anton", age: 5)
1786  # not all fields need to be mentioned, and they can be mentioned out of order:
1787  var a4 = Student(age: 5)
1788
1789Note that, unlike tuples, objects require the field names along with their values.
1790For a `ref object` type `system.new` is invoked implicitly.
1791
1792
1793Object variants
1794---------------
1795Often an object hierarchy is an overkill in certain situations where simple variant
1796types are needed. Object variants are tagged unions discriminated via an
1797enumerated type used for runtime type flexibility, mirroring the concepts of
1798*sum types* and *algebraic data types (ADTs)* as found in other languages.
1799
1800An example:
1801
1802.. code-block:: nim
1803
1804  # This is an example of how an abstract syntax tree could be modelled in Nim
1805  type
1806    NodeKind = enum  # the different node types
1807      nkInt,          # a leaf with an integer value
1808      nkFloat,        # a leaf with a float value
1809      nkString,       # a leaf with a string value
1810      nkAdd,          # an addition
1811      nkSub,          # a subtraction
1812      nkIf            # an if statement
1813    Node = ref NodeObj
1814    NodeObj = object
1815      case kind: NodeKind  # the `kind` field is the discriminator
1816      of nkInt: intVal: int
1817      of nkFloat: floatVal: float
1818      of nkString: strVal: string
1819      of nkAdd, nkSub:
1820        leftOp, rightOp: Node
1821      of nkIf:
1822        condition, thenPart, elsePart: Node
1823
1824  # create a new case object:
1825  var n = Node(kind: nkIf, condition: nil)
1826  # accessing n.thenPart is valid because the `nkIf` branch is active:
1827  n.thenPart = Node(kind: nkFloat, floatVal: 2.0)
1828
1829  # the following statement raises an `FieldDefect` exception, because
1830  # n.kind's value does not fit and the `nkString` branch is not active:
1831  n.strVal = ""
1832
1833  # invalid: would change the active object branch:
1834  n.kind = nkInt
1835
1836  var x = Node(kind: nkAdd, leftOp: Node(kind: nkInt, intVal: 4),
1837                            rightOp: Node(kind: nkInt, intVal: 2))
1838  # valid: does not change the active object branch:
1839  x.kind = nkSub
1840
1841As can be seen from the example, an advantage to an object hierarchy is that
1842no casting between different object types is needed. Yet, access to invalid
1843object fields raises an exception.
1844
1845The syntax of `case` in an object declaration follows closely the syntax of
1846the `case` statement: The branches in a `case` section may be indented too.
1847
1848In the example, the `kind` field is called the `discriminator`:idx:\: For
1849safety, its address cannot be taken and assignments to it are restricted: The
1850new value must not lead to a change of the active object branch. Also, when the
1851fields of a particular branch are specified during object construction, the
1852corresponding discriminator value must be specified as a constant expression.
1853
1854Instead of changing the active object branch, replace the old object in memory
1855with a new one completely:
1856
1857.. code-block:: nim
1858
1859  var x = Node(kind: nkAdd, leftOp: Node(kind: nkInt, intVal: 4),
1860                            rightOp: Node(kind: nkInt, intVal: 2))
1861  # change the node's contents:
1862  x[] = NodeObj(kind: nkString, strVal: "abc")
1863
1864
1865Starting with version 0.20 `system.reset` cannot be used anymore to support
1866object branch changes as this never was completely memory safe.
1867
1868As a special rule, the discriminator kind can also be bounded using a `case`
1869statement. If possible values of the discriminator variable in a
1870`case` statement branch are a subset of discriminator values for the selected
1871object branch, the initialization is considered valid. This analysis only works
1872for immutable discriminators of an ordinal type and disregards `elif`
1873branches. For discriminator values with a `range` type, the compiler
1874checks if the entire range of possible values for the discriminator value is
1875valid for the chosen object branch.
1876
1877A small example:
1878
1879.. code-block:: nim
1880
1881  let unknownKind = nkSub
1882
1883  # invalid: unsafe initialization because the kind field is not statically known:
1884  var y = Node(kind: unknownKind, strVal: "y")
1885
1886  var z = Node()
1887  case unknownKind
1888  of nkAdd, nkSub:
1889    # valid: possible values of this branch are a subset of nkAdd/nkSub object branch:
1890    z = Node(kind: unknownKind, leftOp: Node(), rightOp: Node())
1891  else:
1892    echo "ignoring: ", unknownKind
1893
1894  # also valid, since unknownKindBounded can only contain the values nkAdd or nkSub
1895  let unknownKindBounded = range[nkAdd..nkSub](unknownKind)
1896  z = Node(kind: unknownKindBounded, leftOp: Node(), rightOp: Node())
1897
1898
1899cast uncheckedAssign
1900--------------------
1901
1902Some restrictions for case objects can be disabled via a `{.cast(unsafeAssign).}` section:
1903
1904.. code-block:: nim
1905    :test: "nim c $1"
1906
1907  type
1908    TokenKind* = enum
1909      strLit, intLit
1910    Token = object
1911      case kind*: TokenKind
1912      of strLit:
1913        s*: string
1914      of intLit:
1915        i*: int64
1916
1917  proc passToVar(x: var TokenKind) = discard
1918
1919  var t = Token(kind: strLit, s: "abc")
1920
1921  {.cast(uncheckedAssign).}:
1922    # inside the 'cast' section it is allowed to pass 't.kind' to a 'var T' parameter:
1923    passToVar(t.kind)
1924
1925    # inside the 'cast' section it is allowed to set field 's' even though the
1926    # constructed 'kind' field has an unknown value:
1927    t = Token(kind: t.kind, s: "abc")
1928
1929    # inside the 'cast' section it is allowed to assign to the 't.kind' field directly:
1930    t.kind = intLit
1931
1932
1933Set type
1934--------
1935
1936.. include:: sets_fragment.txt
1937
1938Reference and pointer types
1939---------------------------
1940References (similar to pointers in other programming languages) are a
1941way to introduce many-to-one relationships. This means different references can
1942point to and modify the same location in memory (also called `aliasing`:idx:).
1943
1944Nim distinguishes between `traced`:idx: and `untraced`:idx: references.
1945Untraced references are also called *pointers*. Traced references point to
1946objects of a garbage-collected heap, untraced references point to
1947manually allocated objects or objects somewhere else in memory. Thus
1948untraced references are *unsafe*. However, for certain low-level operations
1949(accessing the hardware) untraced references are unavoidable.
1950
1951Traced references are declared with the **ref** keyword, untraced references
1952are declared with the **ptr** keyword. In general, a `ptr T` is implicitly
1953convertible to the `pointer` type.
1954
1955An empty subscript `[]` notation can be used to de-refer a reference,
1956the `addr` procedure returns the address of an item. An address is always
1957an untraced reference.
1958Thus the usage of `addr` is an *unsafe* feature.
1959
1960The `.` (access a tuple/object field operator)
1961and `[]` (array/string/sequence index operator) operators perform implicit
1962dereferencing operations for reference types:
1963
1964.. code-block:: nim
1965
1966  type
1967    Node = ref NodeObj
1968    NodeObj = object
1969      le, ri: Node
1970      data: int
1971
1972  var
1973    n: Node
1974  new(n)
1975  n.data = 9
1976  # no need to write n[].data; in fact n[].data is highly discouraged!
1977
1978Automatic dereferencing can be performed for the first argument of a routine
1979call, but this is an experimental feature and is described `here
1980<manual_experimental.html#automatic-dereferencing>`_.
1981
1982In order to simplify structural type checking, recursive tuples are not valid:
1983
1984.. code-block:: nim
1985  # invalid recursion
1986  type MyTuple = tuple[a: ref MyTuple]
1987
1988Likewise `T = ref T` is an invalid type.
1989
1990As a syntactical extension, `object` types can be anonymous if
1991declared in a type section via the `ref object` or `ptr object` notations.
1992This feature is useful if an object should only gain reference semantics:
1993
1994.. code-block:: nim
1995
1996  type
1997    Node = ref object
1998      le, ri: Node
1999      data: int
2000
2001
2002To allocate a new traced object, the built-in procedure `new` has to be used.
2003To deal with untraced memory, the procedures `alloc`, `dealloc` and
2004`realloc` can be used. The documentation of the `system <system.html>`_ module
2005contains further information.
2006
2007
2008Nil
2009---
2010
2011If a reference points to *nothing*, it has the value `nil`. `nil` is the
2012default value for all `ref` and `ptr` types. The `nil` value can also be
2013used like any other literal value. For example, it can be used in an assignment
2014like `myRef = nil`.
2015
2016Dereferencing `nil` is an unrecoverable fatal runtime error (and not a panic).
2017
2018A successful dereferencing operation `p[]` implies that `p` is not nil. This
2019can be exploited by the implementation to optimize code like:
2020
2021.. code-block:: nim
2022
2023  p[].field = 3
2024  if p != nil:
2025    # if p were nil, `p[]` would have caused a crash already,
2026    # so we know `p` is always not nil here.
2027    action()
2028
2029Into:
2030
2031.. code-block:: nim
2032
2033  p[].field = 3
2034  action()
2035
2036
2037*Note*: This is not comparable to C's "undefined behavior" for
2038dereferencing NULL pointers.
2039
2040
2041Mixing GC'ed memory with `ptr`
2042--------------------------------
2043
2044Special care has to be taken if an untraced object contains traced objects like
2045traced references, strings, or sequences: in order to free everything properly,
2046the built-in procedure `reset` has to be called before freeing the untraced
2047memory manually:
2048
2049.. code-block:: nim
2050  type
2051    Data = tuple[x, y: int, s: string]
2052
2053  # allocate memory for Data on the heap:
2054  var d = cast[ptr Data](alloc0(sizeof(Data)))
2055
2056  # create a new string on the garbage collected heap:
2057  d.s = "abc"
2058
2059  # tell the GC that the string is not needed anymore:
2060  reset(d.s)
2061
2062  # free the memory:
2063  dealloc(d)
2064
2065Without the `reset` call the memory allocated for the `d.s` string would
2066never be freed. The example also demonstrates two important features for
2067low-level programming: the `sizeof` proc returns the size of a type or value
2068in bytes. The `cast` operator can circumvent the type system: the compiler
2069is forced to treat the result of the `alloc0` call (which returns an untyped
2070pointer) as if it would have the type `ptr Data`. Casting should only be
2071done if it is unavoidable: it breaks type safety and bugs can lead to
2072mysterious crashes.
2073
2074**Note**: The example only works because the memory is initialized to zero
2075(`alloc0` instead of `alloc` does this): `d.s` is thus initialized to
2076binary zero which the string assignment can handle. One needs to know low-level
2077details like this when mixing garbage-collected data with unmanaged memory.
2078
2079.. XXX finalizers for traced objects
2080
2081
2082Procedural type
2083---------------
2084A procedural type is internally a pointer to a procedure. `nil` is
2085an allowed value for a variable of a procedural type.
2086
2087Examples:
2088
2089.. code-block:: nim
2090
2091  proc printItem(x: int) = ...
2092
2093  proc forEach(c: proc (x: int) {.cdecl.}) =
2094    ...
2095
2096  forEach(printItem)  # this will NOT compile because calling conventions differ
2097
2098
2099.. code-block:: nim
2100
2101  type
2102    OnMouseMove = proc (x, y: int) {.closure.}
2103
2104  proc onMouseMove(mouseX, mouseY: int) =
2105    # has default calling convention
2106    echo "x: ", mouseX, " y: ", mouseY
2107
2108  proc setOnMouseMove(mouseMoveEvent: OnMouseMove) = discard
2109
2110  # ok, 'onMouseMove' has the default calling convention, which is compatible
2111  # to 'closure':
2112  setOnMouseMove(onMouseMove)
2113
2114
2115A subtle issue with procedural types is that the calling convention of the
2116procedure influences the type compatibility: procedural types are only
2117compatible if they have the same calling convention. As a special extension,
2118a procedure of the calling convention `nimcall` can be passed to a parameter
2119that expects a proc of the calling convention `closure`.
2120
2121Nim supports these `calling conventions`:idx:\:
2122
2123`nimcall`:idx:
2124    is the default convention used for a Nim **proc**. It is the
2125    same as `fastcall`, but only for C compilers that support `fastcall`.
2126
2127`closure`:idx:
2128    is the default calling convention for a **procedural type** that lacks
2129    any pragma annotations. It indicates that the procedure has a hidden
2130    implicit parameter (an *environment*). Proc vars that have the calling
2131    convention `closure` take up two machine words: One for the proc pointer
2132    and another one for the pointer to implicitly passed environment.
2133
2134`stdcall`:idx:
2135    This is the stdcall convention as specified by Microsoft. The generated C
2136    procedure is declared with the `__stdcall` keyword.
2137
2138`cdecl`:idx:
2139    The cdecl convention means that a procedure shall use the same convention
2140    as the C compiler. Under Windows the generated C procedure is declared with
2141    the `__cdecl` keyword.
2142
2143`safecall`:idx:
2144    This is the safecall convention as specified by Microsoft. The generated C
2145    procedure is declared with the `__safecall` keyword. The word *safe*
2146    refers to the fact that all hardware registers shall be pushed to the
2147    hardware stack.
2148
2149`inline`:idx:
2150    The inline convention means the caller should not call the procedure,
2151    but inline its code directly. Note that Nim does not inline, but leaves
2152    this to the C compiler; it generates `__inline` procedures. This is
2153    only a hint for the compiler: it may completely ignore it and
2154    it may inline procedures that are not marked as `inline`.
2155
2156`fastcall`:idx:
2157    Fastcall means different things to different C compilers. One gets whatever
2158    the C `__fastcall` means.
2159
2160`thiscall`:idx:
2161    This is the thiscall calling convention as specified by Microsoft, used on
2162    C++ class member functions on the x86 architecture.
2163
2164`syscall`:idx:
2165    The syscall convention is the same as `__syscall`:c: in C. It is used for
2166    interrupts.
2167
2168`noconv`:idx:
2169    The generated C code will not have any explicit calling convention and thus
2170    use the C compiler's default calling convention. This is needed because
2171    Nim's default calling convention for procedures is `fastcall` to
2172    improve speed.
2173
2174Most calling conventions exist only for the Windows 32-bit platform.
2175
2176The default calling convention is `nimcall`, unless it is an inner proc (a
2177proc inside of a proc). For an inner proc an analysis is performed whether it
2178accesses its environment. If it does so, it has the calling convention
2179`closure`, otherwise it has the calling convention `nimcall`.
2180
2181
2182Distinct type
2183-------------
2184
2185A `distinct` type is a new type derived from a `base type`:idx: that is
2186incompatible with its base type. In particular, it is an essential property
2187of a distinct type that it **does not** imply a subtype relation between it
2188and its base type. Explicit type conversions from a distinct type to its
2189base type and vice versa are allowed. See also `distinctBase` to get the
2190reverse operation.
2191
2192A distinct type is an ordinal type if its base type is an ordinal type.
2193
2194
2195Modeling currencies
2196~~~~~~~~~~~~~~~~~~~~
2197
2198A distinct type can be used to model different physical `units`:idx: with a
2199numerical base type, for example. The following example models currencies.
2200
2201Different currencies should not be mixed in monetary calculations. Distinct
2202types are a perfect tool to model different currencies:
2203
2204.. code-block:: nim
2205  type
2206    Dollar = distinct int
2207    Euro = distinct int
2208
2209  var
2210    d: Dollar
2211    e: Euro
2212
2213  echo d + 12
2214  # Error: cannot add a number with no unit and a `Dollar`
2215
2216Unfortunately, `d + 12.Dollar` is not allowed either,
2217because `+` is defined for `int` (among others), not for `Dollar`. So
2218a `+` for dollars needs to be defined:
2219
2220.. code-block::
2221  proc `+` (x, y: Dollar): Dollar =
2222    result = Dollar(int(x) + int(y))
2223
2224It does not make sense to multiply a dollar with a dollar, but with a
2225number without unit; and the same holds for division:
2226
2227.. code-block::
2228  proc `*` (x: Dollar, y: int): Dollar =
2229    result = Dollar(int(x) * y)
2230
2231  proc `*` (x: int, y: Dollar): Dollar =
2232    result = Dollar(x * int(y))
2233
2234  proc `div` ...
2235
2236This quickly gets tedious. The implementations are trivial and the compiler
2237should not generate all this code only to optimize it away later - after all
2238`+` for dollars should produce the same binary code as `+` for ints.
2239The pragma `borrow`:idx: has been designed to solve this problem; in principle,
2240it generates the above trivial implementations:
2241
2242.. code-block:: nim
2243  proc `*` (x: Dollar, y: int): Dollar {.borrow.}
2244  proc `*` (x: int, y: Dollar): Dollar {.borrow.}
2245  proc `div` (x: Dollar, y: int): Dollar {.borrow.}
2246
2247The `borrow` pragma makes the compiler use the same implementation as
2248the proc that deals with the distinct type's base type, so no code is
2249generated.
2250
2251But it seems all this boilerplate code needs to be repeated for the `Euro`
2252currency. This can be solved with templates_.
2253
2254.. code-block:: nim
2255    :test: "nim c $1"
2256
2257  template additive(typ: typedesc) =
2258    proc `+` *(x, y: typ): typ {.borrow.}
2259    proc `-` *(x, y: typ): typ {.borrow.}
2260
2261    # unary operators:
2262    proc `+` *(x: typ): typ {.borrow.}
2263    proc `-` *(x: typ): typ {.borrow.}
2264
2265  template multiplicative(typ, base: typedesc) =
2266    proc `*` *(x: typ, y: base): typ {.borrow.}
2267    proc `*` *(x: base, y: typ): typ {.borrow.}
2268    proc `div` *(x: typ, y: base): typ {.borrow.}
2269    proc `mod` *(x: typ, y: base): typ {.borrow.}
2270
2271  template comparable(typ: typedesc) =
2272    proc `<` * (x, y: typ): bool {.borrow.}
2273    proc `<=` * (x, y: typ): bool {.borrow.}
2274    proc `==` * (x, y: typ): bool {.borrow.}
2275
2276  template defineCurrency(typ, base: untyped) =
2277    type
2278      typ* = distinct base
2279    additive(typ)
2280    multiplicative(typ, base)
2281    comparable(typ)
2282
2283  defineCurrency(Dollar, int)
2284  defineCurrency(Euro, int)
2285
2286
2287The borrow pragma can also be used to annotate the distinct type to allow
2288certain builtin operations to be lifted:
2289
2290.. code-block:: nim
2291  type
2292    Foo = object
2293      a, b: int
2294      s: string
2295
2296    Bar {.borrow: `.`.} = distinct Foo
2297
2298  var bb: ref Bar
2299  new bb
2300  # field access now valid
2301  bb.a = 90
2302  bb.s = "abc"
2303
2304Currently, only the dot accessor can be borrowed in this way.
2305
2306
2307Avoiding SQL injection attacks
2308~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2309
2310An SQL statement that is passed from Nim to an SQL database might be
2311modeled as a string. However, using string templates and filling in the
2312values is vulnerable to the famous `SQL injection attack`:idx:\:
2313
2314.. code-block:: nim
2315  import std/strutils
2316
2317  proc query(db: DbHandle, statement: string) = ...
2318
2319  var
2320    username: string
2321
2322  db.query("SELECT FROM users WHERE name = '$1'" % username)
2323  # Horrible security hole, but the compiler does not mind!
2324
2325This can be avoided by distinguishing strings that contain SQL from strings
2326that don't. Distinct types provide a means to introduce a new string type
2327`SQL` that is incompatible with `string`:
2328
2329.. code-block:: nim
2330  type
2331    SQL = distinct string
2332
2333  proc query(db: DbHandle, statement: SQL) = ...
2334
2335  var
2336    username: string
2337
2338  db.query("SELECT FROM users WHERE name = '$1'" % username)
2339  # Static error: `query` expects an SQL string!
2340
2341
2342It is an essential property of abstract types that they **do not** imply a
2343subtype relation between the abstract type and its base type. Explicit type
2344conversions from `string` to `SQL` are allowed:
2345
2346.. code-block:: nim
2347  import std/[strutils, sequtils]
2348
2349  proc properQuote(s: string): SQL =
2350    # quotes a string properly for an SQL statement
2351    return SQL(s)
2352
2353  proc `%` (frmt: SQL, values: openarray[string]): SQL =
2354    # quote each argument:
2355    let v = values.mapIt(properQuote(it))
2356    # we need a temporary type for the type conversion :-(
2357    type StrSeq = seq[string]
2358    # call strutils.`%`:
2359    result = SQL(string(frmt) % StrSeq(v))
2360
2361  db.query("SELECT FROM users WHERE name = '$1'".SQL % [username])
2362
2363Now we have compile-time checking against SQL injection attacks. Since
2364`"".SQL` is transformed to `SQL("")` no new syntax is needed for nice
2365looking `SQL` string literals. The hypothetical `SQL` type actually
2366exists in the library as the `SqlQuery type <db_common.html#SqlQuery>`_ of
2367modules like `db_sqlite <db_sqlite.html>`_.
2368
2369
2370Auto type
2371---------
2372
2373The `auto` type can only be used for return types and parameters. For return
2374types it causes the compiler to infer the type from the routine body:
2375
2376.. code-block:: nim
2377  proc returnsInt(): auto = 1984
2378
2379For parameters it currently creates implicitly generic routines:
2380
2381.. code-block:: nim
2382  proc foo(a, b: auto) = discard
2383
2384Is the same as:
2385
2386.. code-block:: nim
2387  proc foo[T1, T2](a: T1, b: T2) = discard
2388
2389However, later versions of the language might change this to mean "infer the
2390parameters' types from the body". Then the above `foo` would be rejected as
2391the parameters' types can not be inferred from an empty `discard` statement.
2392
2393
2394Type relations
2395==============
2396
2397The following section defines several relations on types that are needed to
2398describe the type checking done by the compiler.
2399
2400
2401Type equality
2402-------------
2403
2404Nim uses structural type equivalence for most types. Only for objects,
2405enumerations and distinct types and for generic types name equivalence is used.
2406
2407
2408Subtype relation
2409----------------
2410
2411If object `a` inherits from `b`, `a` is a subtype of `b`.
2412
2413This subtype relation is extended to the types `var`, `ref`, `ptr`.
2414If `A` is a subtype of `B` and `A` and `B` are `object` types then:
2415
2416- `var A` is a subtype of `var B`
2417- `ref A` is a subtype of `ref B`
2418- `ptr A` is a subtype of `ptr B`.
2419
2420**Note**: In later versions of the language the subtype relation might
2421be changed to *require* the pointer indirection in order to prevent
2422"object slicing".
2423
2424
2425Convertible relation
2426--------------------
2427
2428A type `a` is **implicitly** convertible to type `b` iff the following
2429algorithm returns true:
2430
2431.. code-block:: nim
2432
2433  proc isImplicitlyConvertible(a, b: PType): bool =
2434    if isSubtype(a, b):
2435      return true
2436    if isIntLiteral(a):
2437      return b in {int8, int16, int32, int64, int, uint, uint8, uint16,
2438                   uint32, uint64, float32, float64}
2439    case a.kind
2440    of int:     result = b in {int32, int64}
2441    of int8:    result = b in {int16, int32, int64, int}
2442    of int16:   result = b in {int32, int64, int}
2443    of int32:   result = b in {int64, int}
2444    of uint:    result = b in {uint32, uint64}
2445    of uint8:   result = b in {uint16, uint32, uint64}
2446    of uint16:  result = b in {uint32, uint64}
2447    of uint32:  result = b in {uint64}
2448    of float32: result = b in {float64}
2449    of float64: result = b in {float32}
2450    of seq:
2451      result = b == openArray and typeEquals(a.baseType, b.baseType)
2452    of array:
2453      result = b == openArray and typeEquals(a.baseType, b.baseType)
2454      if a.baseType == char and a.indexType.rangeA == 0:
2455        result = b == cstring
2456    of cstring, ptr:
2457      result = b == pointer
2458    of string:
2459      result = b == cstring
2460    of proc:
2461      result = typeEquals(a, b) or compatibleParametersAndEffects(a, b)
2462
2463We used the predicate `typeEquals(a, b)` for the "type equality" property
2464and the predicate `isSubtype(a, b)` for the "subtype relation".
2465`compatibleParametersAndEffects(a, b)` is currently not specified.
2466
2467Implicit conversions are also performed for Nim's `range` type
2468constructor.
2469
2470Let `a0`, `b0` of type `T`.
2471
2472Let `A = range[a0..b0]` be the argument's type, `F` the formal
2473parameter's type. Then an implicit conversion from `A` to `F`
2474exists if `a0 >= low(F) and b0 <= high(F)` and both `T` and `F`
2475are signed integers or if both are unsigned integers.
2476
2477
2478A type `a` is **explicitly** convertible to type `b` iff the following
2479algorithm returns true:
2480
2481.. code-block:: nim
2482  proc isIntegralType(t: PType): bool =
2483    result = isOrdinal(t) or t.kind in {float, float32, float64}
2484
2485  proc isExplicitlyConvertible(a, b: PType): bool =
2486    result = false
2487    if isImplicitlyConvertible(a, b): return true
2488    if typeEquals(a, b): return true
2489    if a == distinct and typeEquals(a.baseType, b): return true
2490    if b == distinct and typeEquals(b.baseType, a): return true
2491    if isIntegralType(a) and isIntegralType(b): return true
2492    if isSubtype(a, b) or isSubtype(b, a): return true
2493
2494The convertible relation can be relaxed by a user-defined type
2495`converter`:idx:.
2496
2497.. code-block:: nim
2498  converter toInt(x: char): int = result = ord(x)
2499
2500  var
2501    x: int
2502    chr: char = 'a'
2503
2504  # implicit conversion magic happens here
2505  x = chr
2506  echo x # => 97
2507  # one can use the explicit form too
2508  x = chr.toInt
2509  echo x # => 97
2510
2511The type conversion `T(a)` is an L-value if `a` is an L-value and
2512`typeEqualsOrDistinct(T, typeof(a))` holds.
2513
2514
2515Assignment compatibility
2516------------------------
2517
2518An expression `b` can be assigned to an expression `a` iff `a` is an
2519`l-value` and `isImplicitlyConvertible(b.typ, a.typ)` holds.
2520
2521
2522Overload resolution
2523===================
2524
2525In a call `p(args)` the routine `p` that matches best is selected. If
2526multiple routines match equally well, the ambiguity is reported during
2527semantic analysis.
2528
2529Every arg in args needs to match. There are multiple different categories how an
2530argument can match. Let `f` be the formal parameter's type and `a` the type
2531of the argument.
2532
25331. Exact match: `a` and `f` are of the same type.
25342. Literal match: `a` is an integer literal of value `v`
2535   and `f` is a signed or unsigned integer type and `v` is in `f`'s
2536   range. Or:  `a` is a floating-point literal of value `v`
2537   and `f` is a floating-point type and `v` is in `f`'s
2538   range.
25393. Generic match: `f` is a generic type and `a` matches, for
2540   instance `a` is `int` and `f` is a generic (constrained) parameter
2541   type (like in `[T]` or `[T: int|char]`).
25424. Subrange or subtype match: `a` is a `range[T]` and `T`
2543   matches `f` exactly. Or: `a` is a subtype of `f`.
25445. Integral conversion match: `a` is convertible to `f` and `f` and `a`
2545   is some integer or floating-point type.
25466. Conversion match: `a` is convertible to `f`, possibly via a user
2547   defined `converter`.
2548
2549These matching categories have a priority: An exact match is better than a
2550literal match and that is better than a generic match etc. In the following,
2551`count(p, m)` counts the number of matches of the matching category `m`
2552for the routine `p`.
2553
2554A routine `p` matches better than a routine `q` if the following
2555algorithm returns true::
2556
2557  for each matching category m in ["exact match", "literal match",
2558                                  "generic match", "subtype match",
2559                                  "integral match", "conversion match"]:
2560    if count(p, m) > count(q, m): return true
2561    elif count(p, m) == count(q, m):
2562      discard "continue with next category m"
2563    else:
2564      return false
2565  return "ambiguous"
2566
2567
2568Some examples:
2569
2570.. code-block:: nim
2571  proc takesInt(x: int) = echo "int"
2572  proc takesInt[T](x: T) = echo "T"
2573  proc takesInt(x: int16) = echo "int16"
2574
2575  takesInt(4) # "int"
2576  var x: int32
2577  takesInt(x) # "T"
2578  var y: int16
2579  takesInt(y) # "int16"
2580  var z: range[0..4] = 0
2581  takesInt(z) # "T"
2582
2583
2584If this algorithm returns "ambiguous" further disambiguation is performed:
2585If the argument `a` matches both the parameter type `f` of `p`
2586and `g` of `q` via a subtyping relation, the inheritance depth is taken
2587into account:
2588
2589.. code-block:: nim
2590  type
2591    A = object of RootObj
2592    B = object of A
2593    C = object of B
2594
2595  proc p(obj: A) =
2596    echo "A"
2597
2598  proc p(obj: B) =
2599    echo "B"
2600
2601  var c = C()
2602  # not ambiguous, calls 'B', not 'A' since B is a subtype of A
2603  # but not vice versa:
2604  p(c)
2605
2606  proc pp(obj: A, obj2: B) = echo "A B"
2607  proc pp(obj: B, obj2: A) = echo "B A"
2608
2609  # but this is ambiguous:
2610  pp(c, c)
2611
2612
2613Likewise, for generic matches, the most specialized generic type (that still
2614matches) is preferred:
2615
2616.. code-block:: nim
2617  proc gen[T](x: ref ref T) = echo "ref ref T"
2618  proc gen[T](x: ref T) = echo "ref T"
2619  proc gen[T](x: T) = echo "T"
2620
2621  var ri: ref int
2622  gen(ri) # "ref T"
2623
2624
2625Overloading based on 'var T'
2626--------------------------------------
2627
2628If the formal parameter `f` is of type `var T`
2629in addition to the ordinary type checking,
2630the argument is checked to be an `l-value`:idx:.
2631`var T` matches better than just `T` then.
2632
2633.. code-block:: nim
2634  proc sayHi(x: int): string =
2635    # matches a non-var int
2636    result = $x
2637  proc sayHi(x: var int): string =
2638    # matches a var int
2639    result = $(x + 10)
2640
2641  proc sayHello(x: int) =
2642    var m = x # a mutable version of x
2643    echo sayHi(x) # matches the non-var version of sayHi
2644    echo sayHi(m) # matches the var version of sayHi
2645
2646  sayHello(3) # 3
2647              # 13
2648
2649
2650Lazy type resolution for untyped
2651--------------------------------
2652
2653**Note**: An `unresolved`:idx: expression is an expression for which no symbol
2654lookups and no type checking have been performed.
2655
2656Since templates and macros that are not declared as `immediate` participate
2657in overloading resolution, it's essential to have a way to pass unresolved
2658expressions to a template or macro. This is what the meta-type `untyped`
2659accomplishes:
2660
2661.. code-block:: nim
2662  template rem(x: untyped) = discard
2663
2664  rem unresolvedExpression(undeclaredIdentifier)
2665
2666A parameter of type `untyped` always matches any argument (as long as there is
2667any argument passed to it).
2668
2669But one has to watch out because other overloads might trigger the
2670argument's resolution:
2671
2672.. code-block:: nim
2673  template rem(x: untyped) = discard
2674  proc rem[T](x: T) = discard
2675
2676  # undeclared identifier: 'unresolvedExpression'
2677  rem unresolvedExpression(undeclaredIdentifier)
2678
2679`untyped` and `varargs[untyped]` are the only metatype that are lazy in this sense, the other
2680metatypes `typed` and `typedesc` are not lazy.
2681
2682
2683Varargs matching
2684----------------
2685
2686See `Varargs <#types-varargs>`_.
2687
2688iterable
2689--------
2690
2691A called `iterator` yielding type `T` can be passed to a template or macro via
2692a parameter typed as `untyped` (for unresolved expressions) or the type class
2693`iterable` or `iterable[T]` (after type checking and overload resolution).
2694
2695.. code-block:: nim
2696  iterator iota(n: int): int =
2697    for i in 0..<n: yield i
2698
2699  template toSeq2[T](a: iterable[T]): seq[T] =
2700    var ret: seq[T]
2701    assert a.typeof is T
2702    for ai in a: ret.add ai
2703    ret
2704
2705  assert iota(3).toSeq2 == @[0, 1, 2]
2706  assert toSeq2(5..7) == @[5, 6, 7]
2707  assert not compiles(toSeq2(@[1,2])) # seq[int] is not an iterable
2708  assert toSeq2(items(@[1,2])) == @[1, 2] # but items(@[1,2]) is
2709
2710
2711Overload disambiguation
2712=======================
2713
2714For routine calls "overload resolution" is performed. There is a weaker form of
2715overload resolution called *overload disambiguation* that is performed when an
2716overloaded symbol is used in a context where there is additional type information
2717available. Let `p` be an overloaded symbol. These contexts are:
2718
2719- In a function call `q(..., p, ...)` when the corresponding formal parameter
2720  of `q` is a `proc` type. If `q` itself is overloaded then the cartesian product
2721  of every interpretation of `q` and `p` must be considered.
2722- In an object constructor `Obj(..., field: p, ...)` when `field` is a `proc`
2723  type. Analogous rules exist for array/set/tuple constructors.
2724- In a declaration like `x: T = p` when `T` is a `proc` type.
2725
2726As usual, ambiguous matches produce a compile-time error.
2727
2728
2729Statements and expressions
2730==========================
2731
2732Nim uses the common statement/expression paradigm: Statements do not
2733produce a value in contrast to expressions. However, some expressions are
2734statements.
2735
2736Statements are separated into `simple statements`:idx: and
2737`complex statements`:idx:.
2738Simple statements are statements that cannot contain other statements like
2739assignments, calls, or the `return` statement; complex statements can
2740contain other statements. To avoid the `dangling else problem`:idx:, complex
2741statements always have to be indented. The details can be found in the grammar.
2742
2743
2744Statement list expression
2745-------------------------
2746
2747Statements can also occur in an expression context that looks
2748like `(stmt1; stmt2; ...; ex)`. This is called
2749a statement list expression or `(;)`. The type
2750of `(stmt1; stmt2; ...; ex)` is the type of `ex`. All the other statements
2751must be of type `void`. (One can use `discard` to produce a `void` type.)
2752`(;)` does not introduce a new scope.
2753
2754
2755Discard statement
2756-----------------
2757
2758Example:
2759
2760.. code-block:: nim
2761  proc p(x, y: int): int =
2762    result = x + y
2763
2764  discard p(3, 4) # discard the return value of `p`
2765
2766The `discard` statement evaluates its expression for side-effects and
2767throws the expression's resulting value away, and should only be used
2768when ignoring this value is known not to cause problems.
2769
2770Ignoring the return value of a procedure without using a discard statement is
2771a static error.
2772
2773The return value can be ignored implicitly if the called proc/iterator has
2774been declared with the `discardable`:idx: pragma:
2775
2776.. code-block:: nim
2777  proc p(x, y: int): int {.discardable.} =
2778    result = x + y
2779
2780  p(3, 4) # now valid
2781
2782however the discardable pragma does not work on templates as templates substitute the AST in place. For example:
2783
2784.. code-block:: nim
2785  {.push discardable .}
2786  template example(): string = "https://nim-lang.org"
2787  {.pop.}
2788
2789  example()
2790
2791This template will resolve into "https://nim-lang.org" which is a string literal and since {.discardable.} doesn't apply to literals, the compiler will error.
2792
2793An empty `discard` statement is often used as a null statement:
2794
2795.. code-block:: nim
2796  proc classify(s: string) =
2797    case s[0]
2798    of SymChars, '_': echo "an identifier"
2799    of '0'..'9': echo "a number"
2800    else: discard
2801
2802
2803Void context
2804------------
2805
2806In a list of statements, every expression except the last one needs to have the
2807type `void`. In addition to this rule an assignment to the builtin `result`
2808symbol also triggers a mandatory `void` context for the subsequent expressions:
2809
2810.. code-block:: nim
2811  proc invalid*(): string =
2812    result = "foo"
2813    "invalid"  # Error: value of type 'string' has to be discarded
2814
2815.. code-block:: nim
2816  proc valid*(): string =
2817    let x = 317
2818    "valid"
2819
2820
2821Var statement
2822-------------
2823
2824Var statements declare new local and global variables and
2825initialize them. A comma-separated list of variables can be used to specify
2826variables of the same type:
2827
2828.. code-block:: nim
2829
2830  var
2831    a: int = 0
2832    x, y, z: int
2833
2834If an initializer is given, the type can be omitted: the variable is then of the
2835same type as the initializing expression. Variables are always initialized
2836with a default value if there is no initializing expression. The default
2837value depends on the type and is always a zero in binary.
2838
2839============================    ==============================================
2840Type                            default value
2841============================    ==============================================
2842any integer type                0
2843any float                       0.0
2844char                            '\\0'
2845bool                            false
2846ref or pointer type             nil
2847procedural type                 nil
2848sequence                        `@[]`
2849string                          `""`
2850tuple[x: A, y: B, ...]          (default(A), default(B), ...)
2851                                (analogous for objects)
2852array[0..., T]                  [default(T), ...]
2853range[T]                        default(T); this may be out of the valid range
2854T = enum                        cast[T]\(0); this may be an invalid value
2855============================    ==============================================
2856
2857
2858The implicit initialization can be avoided for optimization reasons with the
2859`noinit`:idx: pragma:
2860
2861.. code-block:: nim
2862  var
2863    a {.noInit.}: array[0..1023, char]
2864
2865If a proc is annotated with the `noinit` pragma, this refers to its implicit
2866`result` variable:
2867
2868.. code-block:: nim
2869  proc returnUndefinedValue: int {.noinit.} = discard
2870
2871
2872The implicit initialization can also be prevented by the `requiresInit`:idx:
2873type pragma. The compiler requires an explicit initialization for the object
2874and all of its fields. However, it does a `control flow analysis`:idx: to prove
2875the variable has been initialized and does not rely on syntactic properties:
2876
2877.. code-block:: nim
2878  type
2879    MyObject = object {.requiresInit.}
2880
2881  proc p() =
2882    # the following is valid:
2883    var x: MyObject
2884    if someCondition():
2885      x = a()
2886    else:
2887      x = a()
2888    # use x
2889
2890`requiresInit` pragma can also be applyied to `distinct` types.
2891
2892Given the following distinct type definitions:
2893
2894.. code-block:: nim
2895  type
2896    DistinctObject {.requiresInit, borrow: `.`.} = distinct MyObject
2897    DistinctString {.requiresInit.} = distinct string
2898
2899The following code blocks will fail to compile:
2900
2901.. code-block:: nim
2902  var foo: DistinctFoo
2903  foo.x = "test"
2904  doAssert foo.x == "test"
2905
2906.. code-block:: nim
2907  var s: DistinctString
2908  s = "test"
2909  doAssert s == "test"
2910
2911But these ones will compile successfully:
2912
2913.. code-block:: nim
2914  let foo = DistinctFoo(Foo(x: "test"))
2915  doAssert foo.x == "test"
2916
2917.. code-block:: nim
2918  let s = "test"
2919  doAssert s == "test"
2920
2921Let statement
2922-------------
2923
2924A `let` statement declares new local and global `single assignment`:idx:
2925variables and binds a value to them. The syntax is the same as that of the `var`
2926statement, except that the keyword `var` is replaced by the keyword `let`.
2927Let variables are not l-values and can thus not be passed to `var` parameters
2928nor can their address be taken. They cannot be assigned new values.
2929
2930For let variables, the same pragmas are available as for ordinary variables.
2931
2932As `let` statements are immutable after creation they need to define a value
2933when they are declared. The only exception to this is if the `{.importc.}`
2934pragma (or any of the other `importX` pragmas) is applied, in this case the
2935value is expected to come from native code, typically a C/C++ `const`.
2936
2937
2938Tuple unpacking
2939---------------
2940
2941In a `var` or `let` statement tuple unpacking can be performed. The special
2942identifier `_` can be used to ignore some parts of the tuple:
2943
2944.. code-block:: nim
2945    proc returnsTuple(): (int, int, int) = (4, 2, 3)
2946
2947    let (x, _, z) = returnsTuple()
2948
2949
2950
2951Const section
2952-------------
2953
2954A const section declares constants whose values are constant expressions:
2955
2956.. code-block::
2957  import std/[strutils]
2958  const
2959    roundPi = 3.1415
2960    constEval = contains("abc", 'b') # computed at compile time!
2961
2962Once declared, a constant's symbol can be used as a constant expression.
2963
2964See `Constants and Constant Expressions <#constants-and-constant-expressions>`_
2965for details.
2966
2967Static statement/expression
2968---------------------------
2969
2970A static statement/expression explicitly requires compile-time execution.
2971Even some code that has side effects is permitted in a static block:
2972
2973.. code-block::
2974
2975  static:
2976    echo "echo at compile time"
2977
2978There are limitations on what Nim code can be executed at compile time;
2979see `Restrictions on Compile-Time Execution
2980<#restrictions-on-compileminustime-execution>`_ for details.
2981It's a static error if the compiler cannot execute the block at compile
2982time.
2983
2984
2985If statement
2986------------
2987
2988Example:
2989
2990.. code-block:: nim
2991
2992  var name = readLine(stdin)
2993
2994  if name == "Andreas":
2995    echo "What a nice name!"
2996  elif name == "":
2997    echo "Don't you have a name?"
2998  else:
2999    echo "Boring name..."
3000
3001The `if` statement is a simple way to make a branch in the control flow:
3002The expression after the keyword `if` is evaluated, if it is true
3003the corresponding statements after the `:` are executed. Otherwise
3004the expression after the `elif` is evaluated (if there is an
3005`elif` branch), if it is true the corresponding statements after
3006the `:` are executed. This goes on until the last `elif`. If all
3007conditions fail, the `else` part is executed. If there is no `else`
3008part, execution continues with the next statement.
3009
3010In `if` statements, new scopes begin immediately after
3011the `if`/`elif`/`else` keywords and ends after the
3012corresponding *then* block.
3013For visualization purposes the scopes have been enclosed
3014in `{|  |}` in the following example:
3015
3016.. code-block:: nim
3017  if {| (let m = input =~ re"(\w+)=\w+"; m.isMatch):
3018    echo "key ", m[0], " value ", m[1]  |}
3019  elif {| (let m = input =~ re""; m.isMatch):
3020    echo "new m in this scope"  |}
3021  else: {|
3022    echo "m not declared here"  |}
3023
3024Case statement
3025--------------
3026
3027Example:
3028
3029.. code-block:: nim
3030
3031  let line = readline(stdin)
3032  case line
3033  of "delete-everything", "restart-computer":
3034    echo "permission denied"
3035  of "go-for-a-walk":     echo "please yourself"
3036  elif line.len == 0:     echo "empty" # optional, must come after `of` branches
3037  else:                   echo "unknown command" # ditto
3038
3039  # indentation of the branches is also allowed; and so is an optional colon
3040  # after the selecting expression:
3041  case readline(stdin):
3042    of "delete-everything", "restart-computer":
3043      echo "permission denied"
3044    of "go-for-a-walk":     echo "please yourself"
3045    else:                   echo "unknown command"
3046
3047
3048The `case` statement is similar to the `if` statement, but it represents
3049a multi-branch selection. The expression after the keyword `case` is
3050evaluated and if its value is in a *slicelist* the corresponding statements
3051(after the `of` keyword) are executed. If the value is not in any
3052given *slicelist*, trailing `elif` and `else` parts are executed using same
3053semantics as for `if` statement, and `elif` is handled just like `else: if`.
3054If there are no `else` or `elif` parts and not
3055all possible values that `expr` can hold occur in a *slicelist*, a static error occurs.
3056This holds only for expressions of ordinal types.
3057"All possible values" of `expr` are determined by `expr`'s type.
3058To suppress the static error an `else: discard` should be used.
3059
3060For non-ordinal types, it is not possible to list every possible value and so
3061these always require an `else` part.
3062An exception to this rule is for the `string` type, which currently doesn't
3063require a trailing `else` or `elif` branch; it's unspecified whether this will
3064keep working in future versions.
3065
3066Because case statements are checked for exhaustiveness during semantic analysis,
3067the value in every `of` branch must be a constant expression.
3068This restriction also allows the compiler to generate more performant code.
3069
3070As a special semantic extension, an expression in an `of` branch of a case
3071statement may evaluate to a set or array constructor; the set or array is then
3072expanded into a list of its elements:
3073
3074.. code-block:: nim
3075  const
3076    SymChars: set[char] = {'a'..'z', 'A'..'Z', '\x80'..'\xFF'}
3077
3078  proc classify(s: string) =
3079    case s[0]
3080    of SymChars, '_': echo "an identifier"
3081    of '0'..'9': echo "a number"
3082    else: echo "other"
3083
3084  # is equivalent to:
3085  proc classify(s: string) =
3086    case s[0]
3087    of 'a'..'z', 'A'..'Z', '\x80'..'\xFF', '_': echo "an identifier"
3088    of '0'..'9': echo "a number"
3089    else: echo "other"
3090
3091The `case` statement doesn't produce an l-value, so the following example
3092won't work:
3093
3094.. code-block:: nim
3095  type
3096    Foo = ref object
3097      x: seq[string]
3098
3099  proc get_x(x: Foo): var seq[string] =
3100    # doesn't work
3101    case true
3102    of true:
3103      x.x
3104    else:
3105      x.x
3106
3107  var foo = Foo(x: @[])
3108  foo.get_x().add("asd")
3109
3110This can be fixed by explicitly using `result` or `return`:
3111
3112.. code-block:: nim
3113  proc get_x(x: Foo): var seq[string] =
3114    case true
3115    of true:
3116      result = x.x
3117    else:
3118      result = x.x
3119
3120
3121When statement
3122--------------
3123
3124Example:
3125
3126.. code-block:: nim
3127
3128  when sizeof(int) == 2:
3129    echo "running on a 16 bit system!"
3130  elif sizeof(int) == 4:
3131    echo "running on a 32 bit system!"
3132  elif sizeof(int) == 8:
3133    echo "running on a 64 bit system!"
3134  else:
3135    echo "cannot happen!"
3136
3137The `when` statement is almost identical to the `if` statement with some
3138exceptions:
3139
3140* Each condition (`expr`) has to be a constant expression (of type `bool`).
3141* The statements do not open a new scope.
3142* The statements that belong to the expression that evaluated to true are
3143  translated by the compiler, the other statements are not checked for
3144  semantics! However, each condition is checked for semantics.
3145
3146The `when` statement enables conditional compilation techniques. As
3147a special syntactic extension, the `when` construct is also available
3148within `object` definitions.
3149
3150
3151When nimvm statement
3152--------------------
3153
3154`nimvm` is a special symbol that may be used as the expression of a
3155`when nimvm` statement to differentiate the execution path between
3156compile-time and the executable.
3157
3158Example:
3159
3160.. code-block:: nim
3161  proc someProcThatMayRunInCompileTime(): bool =
3162    when nimvm:
3163      # This branch is taken at compile time.
3164      result = true
3165    else:
3166      # This branch is taken in the executable.
3167      result = false
3168  const ctValue = someProcThatMayRunInCompileTime()
3169  let rtValue = someProcThatMayRunInCompileTime()
3170  assert(ctValue == true)
3171  assert(rtValue == false)
3172
3173A `when nimvm` statement must meet the following requirements:
3174
3175* Its expression must always be `nimvm`. More complex expressions are not
3176  allowed.
3177* It must not contain `elif` branches.
3178* It must contain an `else` branch.
3179* Code in branches must not affect semantics of the code that follows the
3180  `when nimvm` statement. E.g. it must not define symbols that are used in
3181  the following code.
3182
3183Return statement
3184----------------
3185
3186Example:
3187
3188.. code-block:: nim
3189  return 40+2
3190
3191The `return` statement ends the execution of the current procedure.
3192It is only allowed in procedures. If there is an `expr`, this is syntactic
3193sugar for:
3194
3195.. code-block:: nim
3196  result = expr
3197  return result
3198
3199
3200`return` without an expression is a short notation for `return result` if
3201the proc has a return type. The `result`:idx: variable is always the return
3202value of the procedure. It is automatically declared by the compiler. As all
3203variables, `result` is initialized to (binary) zero:
3204
3205.. code-block:: nim
3206  proc returnZero(): int =
3207    # implicitly returns 0
3208
3209
3210Yield statement
3211---------------
3212
3213Example:
3214
3215.. code-block:: nim
3216  yield (1, 2, 3)
3217
3218The `yield` statement is used instead of the `return` statement in
3219iterators. It is only valid in iterators. Execution is returned to the body
3220of the for loop that called the iterator. Yield does not end the iteration
3221process, but the execution is passed back to the iterator if the next iteration
3222starts. See the section about iterators (`Iterators and the for statement`_)
3223for further information.
3224
3225
3226Block statement
3227---------------
3228
3229Example:
3230
3231.. code-block:: nim
3232  var found = false
3233  block myblock:
3234    for i in 0..3:
3235      for j in 0..3:
3236        if a[j][i] == 7:
3237          found = true
3238          break myblock # leave the block, in this case both for-loops
3239  echo found
3240
3241The block statement is a means to group statements to a (named) `block`.
3242Inside the block, the `break` statement is allowed to leave the block
3243immediately. A `break` statement can contain a name of a surrounding
3244block to specify which block is to be left.
3245
3246
3247Break statement
3248---------------
3249
3250Example:
3251
3252.. code-block:: nim
3253  break
3254
3255The `break` statement is used to leave a block immediately. If `symbol`
3256is given, it is the name of the enclosing block that is to be left. If it is
3257absent, the innermost block is left.
3258
3259
3260While statement
3261---------------
3262
3263Example:
3264
3265.. code-block:: nim
3266  echo "Please tell me your password:"
3267  var pw = readLine(stdin)
3268  while pw != "12345":
3269    echo "Wrong password! Next try:"
3270    pw = readLine(stdin)
3271
3272
3273The `while` statement is executed until the `expr` evaluates to false.
3274Endless loops are no error. `while` statements open an `implicit block`
3275so that they can be left with a `break` statement.
3276
3277
3278Continue statement
3279------------------
3280
3281A `continue` statement leads to the immediate next iteration of the
3282surrounding loop construct. It is only allowed within a loop. A continue
3283statement is syntactic sugar for a nested block:
3284
3285.. code-block:: nim
3286  while expr1:
3287    stmt1
3288    continue
3289    stmt2
3290
3291Is equivalent to:
3292
3293.. code-block:: nim
3294  while expr1:
3295    block myBlockName:
3296      stmt1
3297      break myBlockName
3298      stmt2
3299
3300
3301Assembler statement
3302-------------------
3303
3304The direct embedding of assembler code into Nim code is supported
3305by the unsafe `asm` statement. Identifiers in the assembler code that refer to
3306Nim identifiers shall be enclosed in a special character which can be
3307specified in the statement's pragmas. The default special character is `'\`'`:
3308
3309.. code-block:: nim
3310  {.push stackTrace:off.}
3311  proc addInt(a, b: int): int =
3312    # a in eax, and b in edx
3313    asm """
3314        mov eax, `a`
3315        add eax, `b`
3316        jno theEnd
3317        call `raiseOverflow`
3318      theEnd:
3319    """
3320  {.pop.}
3321
3322If the GNU assembler is used, quotes and newlines are inserted automatically:
3323
3324.. code-block:: nim
3325  proc addInt(a, b: int): int =
3326    asm """
3327      addl %%ecx, %%eax
3328      jno 1
3329      call `raiseOverflow`
3330      1:
3331      :"=a"(`result`)
3332      :"a"(`a`), "c"(`b`)
3333    """
3334
3335Instead of:
3336
3337.. code-block:: nim
3338  proc addInt(a, b: int): int =
3339    asm """
3340      "addl %%ecx, %%eax\n"
3341      "jno 1\n"
3342      "call `raiseOverflow`\n"
3343      "1: \n"
3344      :"=a"(`result`)
3345      :"a"(`a`), "c"(`b`)
3346    """
3347
3348Using statement
3349---------------
3350
3351The `using` statement provides syntactic convenience in modules where
3352the same parameter names and types are used over and over. Instead of:
3353
3354.. code-block:: nim
3355  proc foo(c: Context; n: Node) = ...
3356  proc bar(c: Context; n: Node, counter: int) = ...
3357  proc baz(c: Context; n: Node) = ...
3358
3359One can tell the compiler about the convention that a parameter of
3360name `c` should default to type `Context`, `n` should default to
3361`Node` etc.:
3362
3363.. code-block:: nim
3364  using
3365    c: Context
3366    n: Node
3367    counter: int
3368
3369  proc foo(c, n) = ...
3370  proc bar(c, n, counter) = ...
3371  proc baz(c, n) = ...
3372
3373  proc mixedMode(c, n; x, y: int) =
3374    # 'c' is inferred to be of the type 'Context'
3375    # 'n' is inferred to be of the type 'Node'
3376    # But 'x' and 'y' are of type 'int'.
3377
3378The `using` section uses the same indentation based grouping syntax as
3379a `var` or `let` section.
3380
3381Note that `using` is not applied for `template` since the untyped template
3382parameters default to the type `system.untyped`.
3383
3384Mixing parameters that should use the `using` declaration with parameters
3385that are explicitly typed is possible and requires a semicolon between them.
3386
3387
3388If expression
3389-------------
3390
3391An `if` expression is almost like an if statement, but it is an expression.
3392This feature is similar to *ternary operators* in other languages.
3393Example:
3394
3395.. code-block:: nim
3396  var y = if x > 8: 9 else: 10
3397
3398An if expression always results in a value, so the `else` part is
3399required. `Elif` parts are also allowed.
3400
3401When expression
3402---------------
3403
3404Just like an `if` expression, but corresponding to the `when` statement.
3405
3406Case expression
3407---------------
3408
3409The `case` expression is again very similar to the case statement:
3410
3411.. code-block:: nim
3412  var favoriteFood = case animal
3413    of "dog": "bones"
3414    of "cat": "mice"
3415    elif animal.endsWith"whale": "plankton"
3416    else:
3417      echo "I'm not sure what to serve, but everybody loves ice cream"
3418      "ice cream"
3419
3420As seen in the above example, the case expression can also introduce side
3421effects. When multiple statements are given for a branch, Nim will use
3422the last expression as the result value.
3423
3424Block expression
3425----------------
3426
3427A `block` expression is almost like a block statement, but it is an expression
3428that uses the last expression under the block as the value.
3429It is similar to the statement list expression, but the statement list expression
3430does not open a new block scope.
3431
3432.. code-block:: nim
3433  let a = block:
3434    var fib = @[0, 1]
3435    for i in 0..10:
3436      fib.add fib[^1] + fib[^2]
3437    fib
3438
3439Table constructor
3440-----------------
3441
3442A table constructor is syntactic sugar for an array constructor:
3443
3444.. code-block:: nim
3445  {"key1": "value1", "key2", "key3": "value2"}
3446
3447  # is the same as:
3448  [("key1", "value1"), ("key2", "value2"), ("key3", "value2")]
3449
3450
3451The empty table can be written `{:}` (in contrast to the empty set
3452which is `{}`) which is thus another way to write the empty array
3453constructor `[]`. This slightly unusual way of supporting tables
3454has lots of advantages:
3455
3456* The order of the (key,value)-pairs is preserved, thus it is easy to
3457  support ordered dicts with for example `{key: val}.newOrderedTable`.
3458* A table literal can be put into a `const` section and the compiler
3459  can easily put it into the executable's data section just like it can
3460  for arrays and the generated data section requires a minimal amount
3461  of memory.
3462* Every table implementation is treated equally syntactically.
3463* Apart from the minimal syntactic sugar, the language core does not need to
3464  know about tables.
3465
3466
3467Type conversions
3468----------------
3469
3470Syntactically a *type conversion* is like a procedure call, but a
3471type name replaces the procedure name. A type conversion is always
3472safe in the sense that a failure to convert a type to another
3473results in an exception (if it cannot be determined statically).
3474
3475Ordinary procs are often preferred over type conversions in Nim: For instance,
3476`$` is the `toString` operator by convention and `toFloat` and `toInt`
3477can be used to convert from floating-point to integer or vice versa.
3478
3479Type conversion can also be used to disambiguate overloaded routines:
3480
3481.. code-block:: nim
3482
3483  proc p(x: int) = echo "int"
3484  proc p(x: string) = echo "string"
3485
3486  let procVar = (proc(x: string))(p)
3487  procVar("a")
3488
3489Since operations on unsigned numbers wrap around and are unchecked so are
3490type conversions to unsigned integers and between unsigned integers. The
3491rationale for this is mostly better interoperability with the C Programming
3492language when algorithms are ported from C to Nim.
3493
3494Exception: Values that are converted to an unsigned type at compile time
3495are checked so that code like `byte(-1)` does not compile.
3496
3497**Note**: Historically the operations
3498were unchecked and the conversions were sometimes checked but starting with
3499the revision 1.0.4 of this document and the language implementation the
3500conversions too are now *always unchecked*.
3501
3502
3503Type casts
3504----------
3505
3506*Type casts* are a crude mechanism to interpret the bit pattern of an expression
3507as if it would be of another type. Type casts are only needed for low-level
3508programming and are inherently unsafe.
3509
3510.. code-block:: nim
3511  cast[int](x)
3512
3513The target type of a cast must be a concrete type, for instance, a target type
3514that is a type class (which is non-concrete) would be invalid:
3515
3516.. code-block:: nim
3517  type Foo = int or float
3518  var x = cast[Foo](1) # Error: cannot cast to a non concrete type: 'Foo'
3519
3520Type casts should not be confused with *type conversions,* as mentioned in the
3521prior section. Unlike type conversions, a type cast cannot change the underlying
3522bit pattern of the data being casted (aside from that the size of the target type
3523may differ from the source type). Casting resembles *type punning* in other
3524languages or C++'s `reinterpret_cast`:cpp: and `bit_cast`:cpp: features.
3525
3526The addr operator
3527-----------------
3528The `addr` operator returns the address of an l-value. If the type of the
3529location is `T`, the `addr` operator result is of the type `ptr T`. An
3530address is always an untraced reference. Taking the address of an object that
3531resides on the stack is **unsafe**, as the pointer may live longer than the
3532object on the stack and can thus reference a non-existing object. One can get
3533the address of variables, but one can't use it on variables declared through
3534`let` statements:
3535
3536.. code-block:: nim
3537
3538  let t1 = "Hello"
3539  var
3540    t2 = t1
3541    t3 : pointer = addr(t2)
3542  echo repr(addr(t2))
3543  # --> ref 0x7fff6b71b670 --> 0x10bb81050"Hello"
3544  echo cast[ptr string](t3)[]
3545  # --> Hello
3546  # The following line doesn't compile:
3547  echo repr(addr(t1))
3548  # Error: expression has no address
3549
3550
3551The unsafeAddr operator
3552-----------------------
3553
3554For easier interoperability with other compiled languages such as C, retrieving
3555the address of a `let` variable, a parameter, or a `for` loop variable can
3556be accomplished by using the `unsafeAddr` operation:
3557
3558.. code-block:: nim
3559
3560  let myArray = [1, 2, 3]
3561  foreignProcThatTakesAnAddr(unsafeAddr myArray)
3562
3563
3564Procedures
3565==========
3566
3567What most programming languages call `methods`:idx: or `functions`:idx: are
3568called `procedures`:idx: in Nim. A procedure
3569declaration consists of an identifier, zero or more formal parameters, a return
3570value type and a block of code. Formal parameters are declared as a list of
3571identifiers separated by either comma or semicolon. A parameter is given a type
3572by `: typename`. The type applies to all parameters immediately before it,
3573until either the beginning of the parameter list, a semicolon separator, or an
3574already typed parameter, is reached. The semicolon can be used to make
3575separation of types and subsequent identifiers more distinct.
3576
3577.. code-block:: nim
3578  # Using only commas
3579  proc foo(a, b: int, c, d: bool): int
3580
3581  # Using semicolon for visual distinction
3582  proc foo(a, b: int; c, d: bool): int
3583
3584  # Will fail: a is untyped since ';' stops type propagation.
3585  proc foo(a; b: int; c, d: bool): int
3586
3587A parameter may be declared with a default value which is used if the caller
3588does not provide a value for the argument. The value will be reevaluated
3589every time the function is called.
3590
3591.. code-block:: nim
3592  # b is optional with 47 as its default value
3593  proc foo(a: int, b: int = 47): int
3594
3595Parameters can be declared mutable and so allow the proc to modify those
3596arguments, by using the type modifier `var`.
3597
3598.. code-block:: nim
3599  # "returning" a value to the caller through the 2nd argument
3600  # Notice that the function uses no actual return value at all (ie void)
3601  proc foo(inp: int, outp: var int) =
3602    outp = inp + 47
3603
3604If the proc declaration has no body, it is a `forward`:idx: declaration. If the
3605proc returns a value, the procedure body can access an implicitly declared
3606variable named `result`:idx: that represents the return value. Procs can be
3607overloaded. The overloading resolution algorithm determines which proc is the
3608best match for the arguments. Example:
3609
3610.. code-block:: nim
3611
3612  proc toLower(c: char): char = # toLower for characters
3613    if c in {'A'..'Z'}:
3614      result = chr(ord(c) + (ord('a') - ord('A')))
3615    else:
3616      result = c
3617
3618  proc toLower(s: string): string = # toLower for strings
3619    result = newString(len(s))
3620    for i in 0..len(s) - 1:
3621      result[i] = toLower(s[i]) # calls toLower for characters; no recursion!
3622
3623Calling a procedure can be done in many different ways:
3624
3625.. code-block:: nim
3626  proc callme(x, y: int, s: string = "", c: char, b: bool = false) = ...
3627
3628  # call with positional arguments      # parameter bindings:
3629  callme(0, 1, "abc", '\t', true)       # (x=0, y=1, s="abc", c='\t', b=true)
3630  # call with named and positional arguments:
3631  callme(y=1, x=0, "abd", '\t')         # (x=0, y=1, s="abd", c='\t', b=false)
3632  # call with named arguments (order is not relevant):
3633  callme(c='\t', y=1, x=0)              # (x=0, y=1, s="", c='\t', b=false)
3634  # call as a command statement: no () needed:
3635  callme 0, 1, "abc", '\t'              # (x=0, y=1, s="abc", c='\t', b=false)
3636
3637A procedure may call itself recursively.
3638
3639
3640`Operators`:idx: are procedures with a special operator symbol as identifier:
3641
3642.. code-block:: nim
3643  proc `$` (x: int): string =
3644    # converts an integer to a string; this is a prefix operator.
3645    result = intToStr(x)
3646
3647Operators with one parameter are prefix operators, operators with two
3648parameters are infix operators. (However, the parser distinguishes these from
3649the operator's position within an expression.) There is no way to declare
3650postfix operators: all postfix operators are built-in and handled by the
3651grammar explicitly.
3652
3653Any operator can be called like an ordinary proc with the \`opr\`
3654notation. (Thus an operator can have more than two parameters):
3655
3656.. code-block:: nim
3657  proc `*+` (a, b, c: int): int =
3658    # Multiply and add
3659    result = a * b + c
3660
3661  assert `*+`(3, 4, 6) == `+`(`*`(a, b), c)
3662
3663
3664Export marker
3665-------------
3666
3667If a declared symbol is marked with an `asterisk`:idx: it is exported from the
3668current module:
3669
3670.. code-block:: nim
3671
3672  proc exportedEcho*(s: string) = echo s
3673  proc `*`*(a: string; b: int): string =
3674    result = newStringOfCap(a.len * b)
3675    for i in 1..b: result.add a
3676
3677  var exportedVar*: int
3678  const exportedConst* = 78
3679  type
3680    ExportedType* = object
3681      exportedField*: int
3682
3683
3684Method call syntax
3685------------------
3686
3687For object-oriented programming, the syntax `obj.methodName(args)` can be used
3688instead of `methodName(obj, args)`. The parentheses can be omitted if
3689there are no remaining arguments: `obj.len` (instead of `len(obj)`).
3690
3691This method call syntax is not restricted to objects, it can be used
3692to supply any type of first argument for procedures:
3693
3694.. code-block:: nim
3695
3696  echo "abc".len # is the same as echo len "abc"
3697  echo "abc".toUpper()
3698  echo {'a', 'b', 'c'}.card
3699  stdout.writeLine("Hallo") # the same as writeLine(stdout, "Hallo")
3700
3701Another way to look at the method call syntax is that it provides the missing
3702postfix notation.
3703
3704The method call syntax conflicts with explicit generic instantiations:
3705`p[T](x)` cannot be written as `x.p[T]` because `x.p[T]` is always
3706parsed as `(x.p)[T]`.
3707
3708See also: `Limitations of the method call syntax
3709<#templates-limitations-of-the-method-call-syntax>`_.
3710
3711The `[: ]` notation has been designed to mitigate this issue: `x.p[:T]`
3712is rewritten by the parser to `p[T](x)`, `x.p[:T](y)` is rewritten to
3713`p[T](x, y)`. Note that `[: ]` has no AST representation, the rewrite
3714is performed directly in the parsing step.
3715
3716
3717Properties
3718----------
3719Nim has no need for *get-properties*: Ordinary get-procedures that are called
3720with the *method call syntax* achieve the same. But setting a value is
3721different; for this, a special setter syntax is needed:
3722
3723.. code-block:: nim
3724  # Module asocket
3725  type
3726    Socket* = ref object of RootObj
3727      host: int # cannot be accessed from the outside of the module
3728
3729  proc `host=`*(s: var Socket, value: int) {.inline.} =
3730    ## setter of hostAddr.
3731    ## This accesses the 'host' field and is not a recursive call to
3732    ## `host=` because the builtin dot access is preferred if it is
3733    ## available:
3734    s.host = value
3735
3736  proc host*(s: Socket): int {.inline.} =
3737    ## getter of hostAddr
3738    ## This accesses the 'host' field and is not a recursive call to
3739    ## `host` because the builtin dot access is preferred if it is
3740    ## available:
3741    s.host
3742
3743.. code-block:: nim
3744  # module B
3745  import asocket
3746  var s: Socket
3747  new s
3748  s.host = 34  # same as `host=`(s, 34)
3749
3750A proc defined as `f=` (with the trailing `=`) is called
3751a `setter`:idx:. A setter can be called explicitly via the common
3752backticks notation:
3753
3754.. code-block:: nim
3755
3756  proc `f=`(x: MyObject; value: string) =
3757    discard
3758
3759  `f=`(myObject, "value")
3760
3761
3762`f=` can be called implicitly in the pattern
3763`x.f = value` if and only if the type of `x` does not have a field
3764named `f` or if `f` is not visible in the current module. These rules
3765ensure that object fields and accessors can have the same name. Within the
3766module `x.f` is then always interpreted as field access and outside the
3767module it is interpreted as an accessor proc call.
3768
3769
3770Command invocation syntax
3771-------------------------
3772
3773Routines can be invoked without the `()` if the call is syntactically
3774a statement. This command invocation syntax also works for
3775expressions, but then only a single argument may follow. This restriction
3776means `echo f 1, f 2` is parsed as `echo(f(1), f(2))` and not as
3777`echo(f(1, f(2)))`. The method call syntax may be used to provide one
3778more argument in this case:
3779
3780.. code-block:: nim
3781  proc optarg(x: int, y: int = 0): int = x + y
3782  proc singlearg(x: int): int = 20*x
3783
3784  echo optarg 1, " ", singlearg 2  # prints "1 40"
3785
3786  let fail = optarg 1, optarg 8   # Wrong. Too many arguments for a command call
3787  let x = optarg(1, optarg 8)  # traditional procedure call with 2 arguments
3788  let y = 1.optarg optarg 8    # same thing as above, w/o the parenthesis
3789  assert x == y
3790
3791The command invocation syntax also can't have complex expressions as arguments.
3792For example: (`anonymous procs <#procedures-anonymous-procs>`_), `if`,
3793`case` or `try`. Function calls with no arguments still need () to
3794distinguish between a call and the function itself as a first-class value.
3795
3796
3797Closures
3798--------
3799
3800Procedures can appear at the top level in a module as well as inside other
3801scopes, in which case they are called nested procs. A nested proc can access
3802local variables from its enclosing scope and if it does so it becomes a
3803closure. Any captured variables are stored in a hidden additional argument
3804to the closure (its environment) and they are accessed by reference by both
3805the closure and its enclosing scope (i.e. any modifications made to them are
3806visible in both places). The closure environment may be allocated on the heap
3807or on the stack if the compiler determines that this would be safe.
3808
3809Creating closures in loops
3810~~~~~~~~~~~~~~~~~~~~~~~~~~
3811
3812Since closures capture local variables by reference it is often not wanted
3813behavior inside loop bodies. See `closureScope
3814<system.html#closureScope.t,untyped>`_ and `capture
3815<sugar.html#capture.m,varargs[typed],untyped>`_ for details on how to change this behavior.
3816
3817Anonymous Procs
3818---------------
3819
3820Unnamed procedures can be used as lambda expressions to pass into other
3821procedures:
3822
3823.. code-block:: nim
3824  var cities = @["Frankfurt", "Tokyo", "New York", "Kyiv"]
3825
3826  cities.sort(proc (x,y: string): int =
3827      cmp(x.len, y.len))
3828
3829
3830Procs as expressions can appear both as nested procs and inside top-level
3831executable code. The  `sugar <sugar.html>`_ module contains the `=>` macro
3832which enables a more succinct syntax for anonymous procedures resembling
3833lambdas as they are in languages like JavaScript, C#, etc.
3834
3835
3836Func
3837----
3838
3839The `func` keyword introduces a shortcut for a `noSideEffect`:idx: proc.
3840
3841.. code-block:: nim
3842  func binarySearch[T](a: openArray[T]; elem: T): int
3843
3844Is short for:
3845
3846.. code-block:: nim
3847  proc binarySearch[T](a: openArray[T]; elem: T): int {.noSideEffect.}
3848
3849
3850
3851Routines
3852--------
3853
3854A routine is a symbol of kind: `proc`, `func`, `method`, `iterator`, `macro`, `template`, `converter`.
3855
3856Type bound operators
3857--------------------
3858
3859A type bound operator is a `proc` or `func` whose name starts with `=` but isn't an operator
3860(i.e. containing only symbols, such as `==`). These are unrelated to setters
3861(see `properties <manual.html#procedures-properties>`_), which instead end in `=`.
3862A type bound operator declared for a type applies to the type regardless of whether
3863the operator is in scope (including if it is private).
3864
3865.. code-block:: nim
3866  # foo.nim:
3867  var witness* = 0
3868  type Foo[T] = object
3869  proc initFoo*(T: typedesc): Foo[T] = discard
3870  proc `=destroy`[T](x: var Foo[T]) = witness.inc # type bound operator
3871
3872  # main.nim:
3873  import foo
3874  block:
3875    var a = initFoo(int)
3876    doAssert witness == 0
3877  doAssert witness == 1
3878  block:
3879    var a = initFoo(int)
3880    doAssert witness == 1
3881    `=destroy`(a) # can be called explicitly, even without being in scope
3882    doAssert witness == 2
3883  # will still be called upon exiting scope
3884  doAssert witness == 3
3885
3886Type bound operators are:
3887`=destroy`, `=copy`, `=sink`, `=trace`, `=deepcopy`.
3888
3889For more details on some of those procs, see
3890`Lifetime-tracking hooks <destructors.html#lifetimeminustracking-hooks>`_.
3891
3892Nonoverloadable builtins
3893------------------------
3894
3895The following built-in procs cannot be overloaded for reasons of implementation
3896simplicity (they require specialized semantic checking)::
3897
3898  declared, defined, definedInScope, compiles, sizeof,
3899  is, shallowCopy, getAst, astToStr, spawn, procCall
3900
3901Thus they act more like keywords than like ordinary identifiers; unlike a
3902keyword however, a redefinition may `shadow`:idx: the definition in
3903the system_ module. From this list the following should not be written in dot
3904notation `x.f` since `x` cannot be type-checked before it gets passed
3905to `f`::
3906
3907  declared, defined, definedInScope, compiles, getAst, astToStr
3908
3909
3910Var parameters
3911--------------
3912The type of a parameter may be prefixed with the `var` keyword:
3913
3914.. code-block:: nim
3915  proc divmod(a, b: int; res, remainder: var int) =
3916    res = a div b
3917    remainder = a mod b
3918
3919  var
3920    x, y: int
3921
3922  divmod(8, 5, x, y) # modifies x and y
3923  assert x == 1
3924  assert y == 3
3925
3926In the example, `res` and `remainder` are `var parameters`.
3927Var parameters can be modified by the procedure and the changes are
3928visible to the caller. The argument passed to a var parameter has to be
3929an l-value. Var parameters are implemented as hidden pointers. The
3930above example is equivalent to:
3931
3932.. code-block:: nim
3933  proc divmod(a, b: int; res, remainder: ptr int) =
3934    res[] = a div b
3935    remainder[] = a mod b
3936
3937  var
3938    x, y: int
3939  divmod(8, 5, addr(x), addr(y))
3940  assert x == 1
3941  assert y == 3
3942
3943In the examples, var parameters or pointers are used to provide two
3944return values. This can be done in a cleaner way by returning a tuple:
3945
3946.. code-block:: nim
3947  proc divmod(a, b: int): tuple[res, remainder: int] =
3948    (a div b, a mod b)
3949
3950  var t = divmod(8, 5)
3951
3952  assert t.res == 1
3953  assert t.remainder == 3
3954
3955One can use `tuple unpacking`:idx: to access the tuple's fields:
3956
3957.. code-block:: nim
3958  var (x, y) = divmod(8, 5) # tuple unpacking
3959  assert x == 1
3960  assert y == 3
3961
3962
3963**Note**: `var` parameters are never necessary for efficient parameter
3964passing. Since non-var parameters cannot be modified the compiler is always
3965free to pass arguments by reference if it considers it can speed up execution.
3966
3967
3968Var return type
3969---------------
3970
3971A proc, converter, or iterator may return a `var` type which means that the
3972returned value is an l-value and can be modified by the caller:
3973
3974.. code-block:: nim
3975  var g = 0
3976
3977  proc writeAccessToG(): var int =
3978    result = g
3979
3980  writeAccessToG() = 6
3981  assert g == 6
3982
3983It is a static error if the implicitly introduced pointer could be
3984used to access a location beyond its lifetime:
3985
3986.. code-block:: nim
3987  proc writeAccessToG(): var int =
3988    var g = 0
3989    result = g # Error!
3990
3991For iterators, a component of a tuple return type can have a `var` type too:
3992
3993.. code-block:: nim
3994  iterator mpairs(a: var seq[string]): tuple[key: int, val: var string] =
3995    for i in 0..a.high:
3996      yield (i, a[i])
3997
3998In the standard library every name of a routine that returns a `var` type
3999starts with the prefix `m` per convention.
4000
4001
4002.. include:: manual/var_t_return.rst
4003
4004Future directions
4005~~~~~~~~~~~~~~~~~
4006
4007Later versions of Nim can be more precise about the borrowing rule with
4008a syntax like:
4009
4010.. code-block:: nim
4011  proc foo(other: Y; container: var X): var T from container
4012
4013Here `var T from container` explicitly exposes that the
4014location is derived from the second parameter (called
4015'container' in this case). The syntax `var T from p` specifies a type
4016`varTy[T, 2]` which is incompatible with `varTy[T, 1]`.
4017
4018
4019NRVO
4020----
4021
4022**Note**: This section describes the current implementation. This part
4023of the language specification will be changed.
4024See https://github.com/nim-lang/RFCs/issues/230 for more information.
4025
4026The return value is represented inside the body of a routine as the special
4027`result`:idx: variable. This allows for a mechanism much like C++'s
4028"named return value optimization" (`NRVO`:idx:). NRVO means that the stores
4029to `result` inside `p` directly affect the destination `dest`
4030in `let/var dest = p(args)` (definition of `dest`) and also in `dest = p(args)`
4031(assignment to `dest`). This is achieved by rewriting `dest = p(args)`
4032to `p'(args, dest)` where `p'` is a variation of `p` that returns `void` and
4033receives a hidden mutable parameter representing `result`.
4034
4035Informally:
4036
4037.. code-block:: nim
4038  proc p(): BigT = ...
4039
4040  var x = p()
4041  x = p()
4042
4043  # is roughly turned into:
4044
4045  proc p(result: var BigT) = ...
4046
4047  var x; p(x)
4048  p(x)
4049
4050
4051Let `T`'s be `p`'s return type. NRVO applies for `T`
4052if `sizeof(T) >= N` (where `N` is implementation dependent),
4053in other words, it applies for "big" structures.
4054
4055If `p` can raise an exception, NRVO applies regardless. This can produce
4056observable differences in behavior:
4057
4058.. code-block:: nim
4059
4060  type
4061    BigT = array[16, int]
4062
4063  proc p(raiseAt: int): BigT =
4064    for i in 0..high(result):
4065      if i == raiseAt: raise newException(ValueError, "interception")
4066      result[i] = i
4067
4068  proc main =
4069    var x: BigT
4070    try:
4071      x = p(8)
4072    except ValueError:
4073      doAssert x == [0, 1, 2, 3, 4, 5, 6, 7, 0, 0, 0, 0, 0, 0, 0, 0]
4074
4075  main()
4076
4077
4078However, the current implementation produces a warning in these cases.
4079There are different ways to deal with this warning:
4080
40811. Disable the warning via `{.push warning[ObservableStores]: off.}` ... `{.pop.}`.
4082   Then one may need to ensure that `p` only raises *before* any stores to `result`
4083   happen.
4084
40852. One can use a temporary helper variable, for example instead of `x = p(8)`
4086   use `let tmp = p(8); x = tmp`.
4087
4088
4089Overloading of the subscript operator
4090-------------------------------------
4091
4092The `[]` subscript operator for arrays/openarrays/sequences can be overloaded.
4093
4094
4095Methods
4096=============
4097
4098Procedures always use static dispatch. Methods use dynamic
4099dispatch. For dynamic dispatch to work on an object it should be a reference
4100type.
4101
4102.. code-block:: nim
4103  type
4104    Expression = ref object of RootObj ## abstract base class for an expression
4105    Literal = ref object of Expression
4106      x: int
4107    PlusExpr = ref object of Expression
4108      a, b: Expression
4109
4110  method eval(e: Expression): int {.base.} =
4111    # override this base method
4112    raise newException(CatchableError, "Method without implementation override")
4113
4114  method eval(e: Literal): int = return e.x
4115
4116  method eval(e: PlusExpr): int =
4117    # watch out: relies on dynamic binding
4118    result = eval(e.a) + eval(e.b)
4119
4120  proc newLit(x: int): Literal =
4121    new(result)
4122    result.x = x
4123
4124  proc newPlus(a, b: Expression): PlusExpr =
4125    new(result)
4126    result.a = a
4127    result.b = b
4128
4129  echo eval(newPlus(newPlus(newLit(1), newLit(2)), newLit(4)))
4130
4131In the example the constructors `newLit` and `newPlus` are procs
4132because they should use static binding, but `eval` is a method because it
4133requires dynamic binding.
4134
4135As can be seen in the example, base methods have to be annotated with
4136the `base`:idx: pragma. The `base` pragma also acts as a reminder for the
4137programmer that a base method `m` is used as the foundation to determine all
4138the effects that a call to `m` might cause.
4139
4140
4141**Note**: Compile-time execution is not (yet) supported for methods.
4142
4143**Note**: Starting from Nim 0.20, generic methods are deprecated.
4144
4145Multi-methods
4146--------------
4147
4148**Note:** Starting from Nim 0.20, to use multi-methods one must explicitly pass
4149`--multimethods:on`:option: when compiling.
4150
4151In a multi-method, all parameters that have an object type are used for the
4152dispatching:
4153
4154.. code-block:: nim
4155    :test: "nim c --multiMethods:on $1"
4156
4157  type
4158    Thing = ref object of RootObj
4159    Unit = ref object of Thing
4160      x: int
4161
4162  method collide(a, b: Thing) {.inline.} =
4163    quit "to override!"
4164
4165  method collide(a: Thing, b: Unit) {.inline.} =
4166    echo "1"
4167
4168  method collide(a: Unit, b: Thing) {.inline.} =
4169    echo "2"
4170
4171  var a, b: Unit
4172  new a
4173  new b
4174  collide(a, b) # output: 2
4175
4176Inhibit dynamic method resolution via procCall
4177-----------------------------------------------
4178
4179Dynamic method resolution can be inhibited via the builtin `system.procCall`:idx:.
4180This is somewhat comparable to the `super`:idx: keyword that traditional OOP
4181languages offer.
4182
4183.. code-block:: nim
4184    :test: "nim c $1"
4185
4186  type
4187    Thing = ref object of RootObj
4188    Unit = ref object of Thing
4189      x: int
4190
4191  method m(a: Thing) {.base.} =
4192    echo "base"
4193
4194  method m(a: Unit) =
4195    # Call the base method:
4196    procCall m(Thing(a))
4197    echo "1"
4198
4199
4200Iterators and the for statement
4201===============================
4202
4203The `for`:idx: statement is an abstract mechanism to iterate over the elements
4204of a container. It relies on an `iterator`:idx: to do so. Like `while`
4205statements, `for` statements open an `implicit block`:idx: so that they
4206can be left with a `break` statement.
4207
4208The `for` loop declares iteration variables - their scope reaches until the
4209end of the loop body. The iteration variables' types are inferred by the
4210return type of the iterator.
4211
4212An iterator is similar to a procedure, except that it can be called in the
4213context of a `for` loop. Iterators provide a way to specify the iteration over
4214an abstract type. The `yield` statement in the called iterator plays a key
4215role in the execution of a `for` loop. Whenever a `yield` statement is
4216reached, the data is bound to the `for` loop variables and control continues
4217in the body of the `for` loop. The iterator's local variables and execution
4218state are automatically saved between calls. Example:
4219
4220.. code-block:: nim
4221  # this definition exists in the system module
4222  iterator items*(a: string): char {.inline.} =
4223    var i = 0
4224    while i < len(a):
4225      yield a[i]
4226      inc(i)
4227
4228  for ch in items("hello world"): # `ch` is an iteration variable
4229    echo ch
4230
4231The compiler generates code as if the programmer would have written this:
4232
4233.. code-block:: nim
4234  var i = 0
4235  while i < len(a):
4236    var ch = a[i]
4237    echo ch
4238    inc(i)
4239
4240If the iterator yields a tuple, there can be as many iteration variables
4241as there are components in the tuple. The i'th iteration variable's type is
4242the type of the i'th component. In other words, implicit tuple unpacking in a
4243for loop context is supported.
4244
4245Implicit items/pairs invocations
4246--------------------------------
4247
4248If the for loop expression `e` does not denote an iterator and the for loop
4249has exactly 1 variable, the for loop expression is rewritten to `items(e)`;
4250ie. an `items` iterator is implicitly invoked:
4251
4252.. code-block:: nim
4253  for x in [1,2,3]: echo x
4254
4255If the for loop has exactly 2 variables, a `pairs` iterator is implicitly
4256invoked.
4257
4258Symbol lookup of the identifiers `items`/`pairs` is performed after
4259the rewriting step, so that all overloads of `items`/`pairs` are taken
4260into account.
4261
4262
4263First-class iterators
4264---------------------
4265
4266There are 2 kinds of iterators in Nim: *inline* and *closure* iterators.
4267An `inline iterator`:idx: is an iterator that's always inlined by the compiler
4268leading to zero overhead for the abstraction, but may result in a heavy
4269increase in code size.
4270
4271Caution: the body of a for loop over an inline iterator is inlined into
4272each `yield` statement appearing in the iterator code,
4273so ideally the code should be refactored to contain a single yield when possible
4274to avoid code bloat.
4275
4276Inline iterators are second class citizens;
4277They can be passed as parameters only to other inlining code facilities like
4278templates, macros, and other inline iterators.
4279
4280In contrast to that, a `closure iterator`:idx: can be passed around more freely:
4281
4282.. code-block:: nim
4283  iterator count0(): int {.closure.} =
4284    yield 0
4285
4286  iterator count2(): int {.closure.} =
4287    var x = 1
4288    yield x
4289    inc x
4290    yield x
4291
4292  proc invoke(iter: iterator(): int {.closure.}) =
4293    for x in iter(): echo x
4294
4295  invoke(count0)
4296  invoke(count2)
4297
4298Closure iterators and inline iterators have some restrictions:
4299
43001. For now, a closure iterator cannot be executed at compile time.
43012. `return` is allowed in a closure iterator but not in an inline iterator
4302   (but rarely useful) and ends the iteration.
43033. Neither inline nor closure iterators can be (directly)* recursive.
43044. Neither inline nor closure iterators have the special `result` variable.
43055. Closure iterators are not supported by the JS backend.
4306
4307(*) Closure iterators can be co-recursive with a factory proc which results
4308in similar syntax to a recursive iterator. More details follow.
4309
4310Iterators that are neither marked `{.closure.}` nor `{.inline.}` explicitly
4311default to being inline, but this may change in future versions of the
4312implementation.
4313
4314The `iterator` type is always of the calling convention `closure`
4315implicitly; the following example shows how to use iterators to implement
4316a `collaborative tasking`:idx: system:
4317
4318.. code-block:: nim
4319  # simple tasking:
4320  type
4321    Task = iterator (ticker: int)
4322
4323  iterator a1(ticker: int) {.closure.} =
4324    echo "a1: A"
4325    yield
4326    echo "a1: B"
4327    yield
4328    echo "a1: C"
4329    yield
4330    echo "a1: D"
4331
4332  iterator a2(ticker: int) {.closure.} =
4333    echo "a2: A"
4334    yield
4335    echo "a2: B"
4336    yield
4337    echo "a2: C"
4338
4339  proc runTasks(t: varargs[Task]) =
4340    var ticker = 0
4341    while true:
4342      let x = t[ticker mod t.len]
4343      if finished(x): break
4344      x(ticker)
4345      inc ticker
4346
4347  runTasks(a1, a2)
4348
4349The builtin `system.finished` can be used to determine if an iterator has
4350finished its operation; no exception is raised on an attempt to invoke an
4351iterator that has already finished its work.
4352
4353Note that `system.finished` is error prone to use because it only returns
4354`true` one iteration after the iterator has finished:
4355
4356.. code-block:: nim
4357  iterator mycount(a, b: int): int {.closure.} =
4358    var x = a
4359    while x <= b:
4360      yield x
4361      inc x
4362
4363  var c = mycount # instantiate the iterator
4364  while not finished(c):
4365    echo c(1, 3)
4366
4367  # Produces
4368  1
4369  2
4370  3
4371  0
4372
4373Instead this code has to be used:
4374
4375.. code-block:: nim
4376  var c = mycount # instantiate the iterator
4377  while true:
4378    let value = c(1, 3)
4379    if finished(c): break # and discard 'value'!
4380    echo value
4381
4382It helps to think that the iterator actually returns a
4383pair `(value, done)` and `finished` is used to access the hidden `done`
4384field.
4385
4386
4387Closure iterators are *resumable functions* and so one has to provide the
4388arguments to every call. To get around this limitation one can capture
4389parameters of an outer factory proc:
4390
4391.. code-block:: nim
4392  proc mycount(a, b: int): iterator (): int =
4393    result = iterator (): int =
4394      var x = a
4395      while x <= b:
4396        yield x
4397        inc x
4398
4399  let foo = mycount(1, 4)
4400
4401  for f in foo():
4402    echo f
4403
4404The call can be made more like an inline iterator with a for loop macro:
4405
4406.. code-block:: nim
4407  import std/macros
4408  macro toItr(x: ForLoopStmt): untyped =
4409    let expr = x[0]
4410    let call = x[1][1] # Get foo out of toItr(foo)
4411    let body = x[2]
4412    result = quote do:
4413      block:
4414        let itr = `call`
4415        for `expr` in itr():
4416            `body`
4417
4418  for f in toItr(mycount(1, 4)): # using early `proc mycount`
4419    echo f
4420
4421Because of full backend function call aparatus involvment, closure iterator
4422invocation is typically higher cost than inline iterators. Adornment by
4423a macro wrapper at the call site like this is a possibly useful reminder.
4424
4425The factory `proc`, as an ordinary procedure, can be recursive. The
4426above macro allows such recursion to look much like a recursive iterator
4427would. For example:
4428
4429.. code-block:: nim
4430  proc recCountDown(n: int): iterator(): int =
4431    result = iterator(): int =
4432      if n > 0:
4433        yield n
4434        for e in toItr(recCountDown(n - 1)):
4435          yield e
4436
4437  for i in toItr(recCountDown(6)): # Emits: 6 5 4 3 2 1
4438    echo i
4439
4440
4441See also see `iterable <#overloading-resolution-iterable>`_ for passing iterators to templates and macros.
4442
4443Converters
4444==========
4445
4446A converter is like an ordinary proc except that it enhances
4447the "implicitly convertible" type relation (see `Convertible relation`_):
4448
4449.. code-block:: nim
4450  # bad style ahead: Nim is not C.
4451  converter toBool(x: int): bool = x != 0
4452
4453  if 4:
4454    echo "compiles"
4455
4456
4457A converter can also be explicitly invoked for improved readability. Note that
4458implicit converter chaining is not supported: If there is a converter from
4459type A to type B and from type B to type C the implicit conversion from A to C
4460is not provided.
4461
4462
4463Type sections
4464=============
4465
4466Example:
4467
4468.. code-block:: nim
4469  type # example demonstrating mutually recursive types
4470    Node = ref object  # an object managed by the garbage collector (ref)
4471      le, ri: Node     # left and right subtrees
4472      sym: ref Sym     # leaves contain a reference to a Sym
4473
4474    Sym = object       # a symbol
4475      name: string     # the symbol's name
4476      line: int        # the line the symbol was declared in
4477      code: Node       # the symbol's abstract syntax tree
4478
4479A type section begins with the `type` keyword. It contains multiple
4480type definitions. A type definition binds a type to a name. Type definitions
4481can be recursive or even mutually recursive. Mutually recursive types are only
4482possible within a single `type` section. Nominal types like `objects`
4483or `enums` can only be defined in a `type` section.
4484
4485
4486
4487Exception handling
4488==================
4489
4490Try statement
4491-------------
4492
4493Example:
4494
4495.. code-block:: nim
4496  # read the first two lines of a text file that should contain numbers
4497  # and tries to add them
4498  var
4499    f: File
4500  if open(f, "numbers.txt"):
4501    try:
4502      var a = readLine(f)
4503      var b = readLine(f)
4504      echo "sum: " & $(parseInt(a) + parseInt(b))
4505    except OverflowDefect:
4506      echo "overflow!"
4507    except ValueError, IOError:
4508      echo "catch multiple exceptions!"
4509    except:
4510      echo "Unknown exception!"
4511    finally:
4512      close(f)
4513
4514
4515The statements after the `try` are executed in sequential order unless
4516an exception `e` is raised. If the exception type of `e` matches any
4517listed in an `except` clause, the corresponding statements are executed.
4518The statements following the `except` clauses are called
4519`exception handlers`:idx:.
4520
4521The empty `except`:idx: clause is executed if there is an exception that is
4522not listed otherwise. It is similar to an `else` clause in `if` statements.
4523
4524If there is a `finally`:idx: clause, it is always executed after the
4525exception handlers.
4526
4527The exception is *consumed* in an exception handler. However, an
4528exception handler may raise another exception. If the exception is not
4529handled, it is propagated through the call stack. This means that often
4530the rest of the procedure - that is not within a `finally` clause -
4531is not executed (if an exception occurs).
4532
4533
4534Try expression
4535--------------
4536
4537Try can also be used as an expression; the type of the `try` branch then
4538needs to fit the types of `except` branches, but the type of the `finally`
4539branch always has to be `void`:
4540
4541.. code-block:: nim
4542  from std/strutils import parseInt
4543
4544  let x = try: parseInt("133a")
4545          except: -1
4546          finally: echo "hi"
4547
4548
4549To prevent confusing code there is a parsing limitation; if the `try`
4550follows a `(` it has to be written as a one liner:
4551
4552.. code-block:: nim
4553  let x = (try: parseInt("133a") except: -1)
4554
4555
4556Except clauses
4557--------------
4558
4559Within an `except` clause it is possible to access the current exception
4560using the following syntax:
4561
4562.. code-block:: nim
4563  try:
4564    # ...
4565  except IOError as e:
4566    # Now use "e"
4567    echo "I/O error: " & e.msg
4568
4569Alternatively, it is possible to use `getCurrentException` to retrieve the
4570exception that has been raised:
4571
4572.. code-block:: nim
4573  try:
4574    # ...
4575  except IOError:
4576    let e = getCurrentException()
4577    # Now use "e"
4578
4579Note that `getCurrentException` always returns a `ref Exception`
4580type. If a variable of the proper type is needed (in the example
4581above, `IOError`), one must convert it explicitly:
4582
4583.. code-block:: nim
4584  try:
4585    # ...
4586  except IOError:
4587    let e = (ref IOError)(getCurrentException())
4588    # "e" is now of the proper type
4589
4590However, this is seldom needed. The most common case is to extract an
4591error message from `e`, and for such situations, it is enough to use
4592`getCurrentExceptionMsg`:
4593
4594.. code-block:: nim
4595  try:
4596    # ...
4597  except:
4598    echo getCurrentExceptionMsg()
4599
4600Custom exceptions
4601-----------------
4602
4603It is possible to create custom exceptions. A custom exception is a custom type:
4604
4605.. code-block:: nim
4606  type
4607    LoadError* = object of Exception
4608
4609Ending the custom exception's name with `Error` is recommended.
4610
4611Custom exceptions can be raised just like any other exception, e.g.:
4612
4613.. code-block:: nim
4614  raise newException(LoadError, "Failed to load data")
4615
4616Defer statement
4617---------------
4618
4619Instead of a `try finally` statement a `defer` statement can be used, which
4620avoids lexical nesting and offers more flexibility in terms of scoping as shown
4621below.
4622
4623Any statements following the `defer` in the current block will be considered
4624to be in an implicit try block:
4625
4626.. code-block:: nim
4627    :test: "nim c $1"
4628
4629  proc main =
4630    var f = open("numbers.txt", fmWrite)
4631    defer: close(f)
4632    f.write "abc"
4633    f.write "def"
4634
4635Is rewritten to:
4636
4637.. code-block:: nim
4638    :test: "nim c $1"
4639
4640  proc main =
4641    var f = open("numbers.txt")
4642    try:
4643      f.write "abc"
4644      f.write "def"
4645    finally:
4646      close(f)
4647
4648When `defer` is at the outermost scope of a template/macro, its scope extends
4649to the block where the template is called from:
4650
4651.. code-block:: nim
4652    :test: "nim c $1"
4653
4654  template safeOpenDefer(f, path) =
4655    var f = open(path, fmWrite)
4656    defer: close(f)
4657
4658  template safeOpenFinally(f, path, body) =
4659    var f = open(path, fmWrite)
4660    try: body # without `defer`, `body` must be specified as parameter
4661    finally: close(f)
4662
4663  block:
4664    safeOpenDefer(f, "/tmp/z01.txt")
4665    f.write "abc"
4666  block:
4667    safeOpenFinally(f, "/tmp/z01.txt"):
4668      f.write "abc" # adds a lexical scope
4669  block:
4670    var f = open("/tmp/z01.txt", fmWrite)
4671    try:
4672      f.write "abc" # adds a lexical scope
4673    finally: close(f)
4674
4675Top-level `defer` statements are not supported
4676since it's unclear what such a statement should refer to.
4677
4678
4679Raise statement
4680---------------
4681
4682Example:
4683
4684.. code-block:: nim
4685  raise newException(IOError, "IO failed")
4686
4687Apart from built-in operations like array indexing, memory allocation, etc.
4688the `raise` statement is the only way to raise an exception.
4689
4690.. XXX document this better!
4691
4692If no exception name is given, the current exception is `re-raised`:idx:. The
4693`ReraiseDefect`:idx: exception is raised if there is no exception to
4694re-raise. It follows that the `raise` statement *always* raises an
4695exception.
4696
4697
4698Exception hierarchy
4699-------------------
4700
4701The exception tree is defined in the `system <system.html>`_ module.
4702Every exception inherits from `system.Exception`. Exceptions that indicate
4703programming bugs inherit from `system.Defect` (which is a subtype of `Exception`)
4704and are strictly speaking not catchable as they can also be mapped to an operation
4705that terminates the whole process. If panics are turned into exceptions, these
4706exceptions inherit from `Defect`.
4707
4708Exceptions that indicate any other runtime error that can be caught inherit from
4709`system.CatchableError` (which is a subtype of `Exception`).
4710
4711
4712Imported exceptions
4713-------------------
4714
4715It is possible to raise/catch imported C++ exceptions. Types imported using
4716`importcpp` can be raised or caught. Exceptions are raised by value and
4717caught by reference. Example:
4718
4719.. code-block:: nim
4720    :test: "nim cpp -r $1"
4721
4722  type
4723    CStdException {.importcpp: "std::exception", header: "<exception>", inheritable.} = object
4724      ## does not inherit from `RootObj`, so we use `inheritable` instead
4725    CRuntimeError {.requiresInit, importcpp: "std::runtime_error", header: "<stdexcept>".} = object of CStdException
4726      ## `CRuntimeError` has no default constructor => `requiresInit`
4727  proc what(s: CStdException): cstring {.importcpp: "((char *)#.what())".}
4728  proc initRuntimeError(a: cstring): CRuntimeError {.importcpp: "std::runtime_error(@)", constructor.}
4729  proc initStdException(): CStdException {.importcpp: "std::exception()", constructor.}
4730
4731  proc fn() =
4732    let a = initRuntimeError("foo")
4733    doAssert $a.what == "foo"
4734    var b: cstring
4735    try: raise initRuntimeError("foo2")
4736    except CStdException as e:
4737      doAssert e is CStdException
4738      b = e.what()
4739    doAssert $b == "foo2"
4740
4741    try: raise initStdException()
4742    except CStdException: discard
4743
4744    try: raise initRuntimeError("foo3")
4745    except CRuntimeError as e:
4746      b = e.what()
4747    except CStdException:
4748      doAssert false
4749    doAssert $b == "foo3"
4750
4751  fn()
4752
4753**Note:** `getCurrentException()` and `getCurrentExceptionMsg()` are not available
4754for imported exceptions from C++. One needs to use the `except ImportedException as x:` syntax
4755and rely on functionality of the `x` object to get exception details.
4756
4757
4758Effect system
4759=============
4760
4761**Note**: The rules for effect tracking changed with the release of version
47621.6 of the Nim compiler. This section describes the new rules that are activated
4763via `--experimental:strictEffects`.
4764
4765
4766Exception tracking
4767------------------
4768
4769Nim supports exception tracking. The `raises`:idx: pragma can be used
4770to explicitly define which exceptions a proc/iterator/method/converter is
4771allowed to raise. The compiler verifies this:
4772
4773.. code-block:: nim
4774    :test: "nim c $1"
4775
4776  proc p(what: bool) {.raises: [IOError, OSError].} =
4777    if what: raise newException(IOError, "IO")
4778    else: raise newException(OSError, "OS")
4779
4780An empty `raises` list (`raises: []`) means that no exception may be raised:
4781
4782.. code-block:: nim
4783  proc p(): bool {.raises: [].} =
4784    try:
4785      unsafeCall()
4786      result = true
4787    except:
4788      result = false
4789
4790
4791A `raises` list can also be attached to a proc type. This affects type
4792compatibility:
4793
4794.. code-block:: nim
4795    :test: "nim c $1"
4796    :status: 1
4797
4798  type
4799    Callback = proc (s: string) {.raises: [IOError].}
4800  var
4801    c: Callback
4802
4803  proc p(x: string) =
4804    raise newException(OSError, "OS")
4805
4806  c = p # type error
4807
4808
4809For a routine `p`, the compiler uses inference rules to determine the set of
4810possibly raised exceptions; the algorithm operates on `p`'s call graph:
4811
48121. Every indirect call via some proc type `T` is assumed to
4813   raise `system.Exception` (the base type of the exception hierarchy) and
4814   thus any exception unless `T` has an explicit `raises` list.
4815   However, if the call is of the form `f(...)` where `f` is a parameter of
4816   the currently analyzed routine it is ignored that is marked as `.effectsOf: f`.
4817   The call is optimistically assumed to have no effect.
4818   Rule 2 compensates for this case.
48192. Every expression `e` of some proc type within a call that is passed to parameter
4820   marked as `.effectsOf` is assumed to be called indirectly and thus
4821   its raises list is added to `p`'s raises list.
48223. Every call to a proc `q` which has an unknown body (due to a forward
4823   declaration) is assumed to
4824   raise `system.Exception` unless `q` has an explicit `raises` list.
4825   Procs that are `importc`'ed are assumed to have `.raises: []`, unless explicitly
4826   declared otherwise.
48274. Every call to a method `m` is assumed to
4828   raise `system.Exception` unless `m` has an explicit `raises` list.
48295. For every other call, the analysis can determine an exact `raises` list.
48306. For determining a `raises` list, the `raise` and `try` statements
4831   of `p` are taken into consideration.
4832
4833
4834Exceptions inheriting from `system.Defect` are not tracked with
4835the `.raises: []` exception tracking mechanism. This is more consistent with the
4836built-in operations. The following code is valid:
4837
4838.. code-block:: nim
4839
4840  proc mydiv(a, b): int {.raises: [].} =
4841    a div b # can raise an DivByZeroDefect
4842
4843And so is:
4844
4845.. code-block:: nim
4846
4847  proc mydiv(a, b): int {.raises: [].} =
4848    if b == 0: raise newException(DivByZeroDefect, "division by zero")
4849    else: result = a div b
4850
4851
4852The reason for this is that `DivByZeroDefect` inherits from `Defect` and
4853with `--panics:on`:option: Defects become unrecoverable errors.
4854(Since version 1.4 of the language.)
4855
4856
4857EffectsOf annotation
4858--------------------
4859
4860Rules 1-2 of the exception tracking inference rules (see the previous section)
4861ensure the following works:
4862
4863.. code-block:: nim
4864  proc weDontRaiseButMaybeTheCallback(callback: proc()) {.raises: [], effectsOf: callback.} =
4865    callback()
4866
4867  proc doRaise() {.raises: [IOError].} =
4868    raise newException(IOError, "IO")
4869
4870  proc use() {.raises: [].} =
4871    # doesn't compile! Can raise IOError!
4872    weDontRaiseButMaybeTheCallback(doRaise)
4873
4874As can be seen from the example, a parameter of type `proc (...)` can be
4875annotated as `.effectsOf`. Such a parameter allows for effect polymorphism:
4876The proc `weDontRaiseButMaybeTheCallback` raises the exceptions
4877that `callback` raises.
4878
4879So in many cases a callback does not cause the compiler to be overly
4880conservative in its effect analysis:
4881
4882.. code-block:: nim
4883    :test: "nim c $1"
4884    :status: 1
4885
4886  {.push warningAsError[Effect]: on.}
4887  {.experimental: "strictEffects".}
4888
4889  import algorithm
4890
4891  type
4892    MyInt = distinct int
4893
4894  var toSort = @[MyInt 1, MyInt 2, MyInt 3]
4895
4896  proc cmpN(a, b: MyInt): int =
4897    cmp(a.int, b.int)
4898
4899  proc harmless {.raises: [].} =
4900    toSort.sort cmpN
4901
4902  proc cmpE(a, b: MyInt): int {.raises: [Exception].} =
4903    cmp(a.int, b.int)
4904
4905  proc harmfull {.raises: [].} =
4906    # does not compile, `sort` can now raise Exception
4907    toSort.sort cmpE
4908
4909
4910
4911Tag tracking
4912------------
4913
4914Exception tracking is part of Nim's `effect system`:idx:. Raising an exception
4915is an *effect*. Other effects can also be defined. A user defined effect is a
4916means to *tag* a routine and to perform checks against this tag:
4917
4918.. code-block:: nim
4919    :test: "nim c --warningAsError:Effect:on $1"
4920    :status: 1
4921
4922  type IO = object ## input/output effect
4923  proc readLine(): string {.tags: [IO].} = discard
4924
4925  proc no_IO_please() {.tags: [].} =
4926    # the compiler prevents this:
4927    let x = readLine()
4928
4929A tag has to be a type name. A `tags` list - like a `raises` list - can
4930also be attached to a proc type. This affects type compatibility.
4931
4932The inference for tag tracking is analogous to the inference for
4933exception tracking.
4934
4935
4936Side effects
4937------------
4938
4939The `noSideEffect` pragma is used to mark a proc/iterator that can have only
4940side effects through parameters. This means that the proc/iterator only changes locations that are
4941reachable from its parameters and the return value only depends on the
4942parameters. If none of its parameters have the type `var`, `ref`, `ptr`, `cstring`, or `proc`,
4943then no locations are modified.
4944
4945In other words, a routine has no side effects if it does not access a threadlocal
4946or global variable and it does not call any routine that has a side effect.
4947
4948It is a static error to mark a proc/iterator to have no side effect if the compiler cannot verify this.
4949
4950As a special semantic rule, the built-in `debugEcho
4951<system.html#debugEcho,varargs[typed,]>`_ pretends to be free of side effects
4952so that it can be used for debugging routines marked as `noSideEffect`.
4953
4954`func` is syntactic sugar for a proc with no side effects:
4955
4956.. code-block:: nim
4957  func `+` (x, y: int): int
4958
4959
4960To override the compiler's side effect analysis a `{.noSideEffect.}`
4961`cast` pragma block can be used:
4962
4963.. code-block:: nim
4964
4965  func f() =
4966    {.cast(noSideEffect).}:
4967      echo "test"
4968
4969**Side effects are usually inferred. The inference for side effects is
4970analogous to the inference for exception tracking.**
4971
4972
4973GC safety effect
4974----------------
4975
4976We call a proc `p` `GC safe`:idx: when it doesn't access any global variable
4977that contains GC'ed memory (`string`, `seq`, `ref` or a closure) either
4978directly or indirectly through a call to a GC unsafe proc.
4979
4980**The GC safety property is usually inferred. The inference for GC safety is
4981analogous to the inference for exception tracking.**
4982
4983The `gcsafe`:idx: annotation can be used to mark a proc to be gcsafe,
4984otherwise this property is inferred by the compiler. Note that `noSideEffect`
4985implies `gcsafe`.
4986
4987Routines that are imported from C are always assumed to be `gcsafe`.
4988
4989To override the compiler's gcsafety analysis a `{.cast(gcsafe).}` pragma block can
4990be used:
4991
4992.. code-block:: nim
4993
4994  var
4995    someGlobal: string = "some string here"
4996    perThread {.threadvar.}: string
4997
4998  proc setPerThread() =
4999    {.cast(gcsafe).}:
5000      deepCopy(perThread, someGlobal)
5001
5002
5003See also:
5004
5005- `Shared heap memory management <gc.html>`_.
5006
5007
5008
5009Effects pragma
5010--------------
5011
5012The `effects` pragma has been designed to assist the programmer with the
5013effects analysis. It is a statement that makes the compiler output all inferred
5014effects up to the `effects`'s position:
5015
5016.. code-block:: nim
5017  proc p(what: bool) =
5018    if what:
5019      raise newException(IOError, "IO")
5020      {.effects.}
5021    else:
5022      raise newException(OSError, "OS")
5023
5024The compiler produces a hint message that `IOError` can be raised. `OSError`
5025is not listed as it cannot be raised in the branch the `effects` pragma
5026appears in.
5027
5028
5029Generics
5030========
5031
5032Generics are Nim's means to parametrize procs, iterators or types with
5033`type parameters`:idx:. Depending on the context, the brackets are used either to
5034introduce type parameters or to instantiate a generic proc, iterator, or type.
5035
5036The following example shows how a generic binary tree can be modeled:
5037
5038.. code-block:: nim
5039    :test: "nim c $1"
5040
5041  type
5042    BinaryTree*[T] = ref object # BinaryTree is a generic type with
5043                                # generic param `T`
5044      le, ri: BinaryTree[T]     # left and right subtrees; may be nil
5045      data: T                   # the data stored in a node
5046
5047  proc newNode*[T](data: T): BinaryTree[T] =
5048    # constructor for a node
5049    result = BinaryTree[T](le: nil, ri: nil, data: data)
5050
5051  proc add*[T](root: var BinaryTree[T], n: BinaryTree[T]) =
5052    # insert a node into the tree
5053    if root == nil:
5054      root = n
5055    else:
5056      var it = root
5057      while it != nil:
5058        # compare the data items; uses the generic `cmp` proc
5059        # that works for any type that has a `==` and `<` operator
5060        var c = cmp(it.data, n.data)
5061        if c < 0:
5062          if it.le == nil:
5063            it.le = n
5064            return
5065          it = it.le
5066        else:
5067          if it.ri == nil:
5068            it.ri = n
5069            return
5070          it = it.ri
5071
5072  proc add*[T](root: var BinaryTree[T], data: T) =
5073    # convenience proc:
5074    add(root, newNode(data))
5075
5076  iterator preorder*[T](root: BinaryTree[T]): T =
5077    # Preorder traversal of a binary tree.
5078    # This uses an explicit stack (which is more efficient than
5079    # a recursive iterator factory).
5080    var stack: seq[BinaryTree[T]] = @[root]
5081    while stack.len > 0:
5082      var n = stack.pop()
5083      while n != nil:
5084        yield n.data
5085        add(stack, n.ri)  # push right subtree onto the stack
5086        n = n.le          # and follow the left pointer
5087
5088  var
5089    root: BinaryTree[string] # instantiate a BinaryTree with `string`
5090  add(root, newNode("hello")) # instantiates `newNode` and `add`
5091  add(root, "world")          # instantiates the second `add` proc
5092  for str in preorder(root):
5093    stdout.writeLine(str)
5094
5095The `T` is called a `generic type parameter`:idx: or
5096a `type variable`:idx:.
5097
5098Is operator
5099-----------
5100
5101The `is` operator is evaluated during semantic analysis to check for type
5102equivalence. It is therefore very useful for type specialization within generic
5103code:
5104
5105.. code-block:: nim
5106  type
5107    Table[Key, Value] = object
5108      keys: seq[Key]
5109      values: seq[Value]
5110      when not (Key is string): # empty value for strings used for optimization
5111        deletedKeys: seq[bool]
5112
5113
5114Type Classes
5115------------
5116
5117A type class is a special pseudo-type that can be used to match against
5118types in the context of overload resolution or the `is` operator.
5119Nim supports the following built-in type classes:
5120
5121==================   ===================================================
5122type class           matches
5123==================   ===================================================
5124`object`             any object type
5125`tuple`              any tuple type
5126
5127`enum`               any enumeration
5128`proc`               any proc type
5129`ref`                any `ref` type
5130`ptr`                any `ptr` type
5131`var`                any `var` type
5132`distinct`           any distinct type
5133`array`              any array type
5134`set`                any set type
5135`seq`                any seq type
5136`auto`               any type
5137==================   ===================================================
5138
5139Furthermore, every generic type automatically creates a type class of the same
5140name that will match any instantiation of the generic type.
5141
5142Type classes can be combined using the standard boolean operators to form
5143more complex type classes:
5144
5145.. code-block:: nim
5146  # create a type class that will match all tuple and object types
5147  type RecordType = tuple or object
5148
5149  proc printFields[T: RecordType](rec: T) =
5150    for key, value in fieldPairs(rec):
5151      echo key, " = ", value
5152
5153Type constraints on generic parameters can be grouped with `,` and propagation
5154stops with `;`, similarly to parameters for macros and templates:
5155
5156.. code-block:: nim
5157  proc fn1[T; U, V: SomeFloat]() = discard # T is unconstrained
5158  template fn2(t; u, v: SomeFloat) = discard # t is unconstrained
5159
5160Whilst the syntax of type classes appears to resemble that of ADTs/algebraic data
5161types in ML-like languages, it should be understood that type classes are static
5162constraints to be enforced at type instantiations. Type classes are not really
5163types in themselves but are instead a system of providing generic "checks" that
5164ultimately *resolve* to some singular type. Type classes do not allow for
5165runtime type dynamism, unlike object variants or methods.
5166
5167As an example, the following would not compile:
5168
5169.. code-block:: nim
5170  type TypeClass = int | string
5171  var foo: TypeClass = 2 # foo's type is resolved to an int here
5172  foo = "this will fail" # error here, because foo is an int
5173
5174Nim allows for type classes and regular types to be specified
5175as `type constraints`:idx: of the generic type parameter:
5176
5177.. code-block:: nim
5178  proc onlyIntOrString[T: int|string](x, y: T) = discard
5179
5180  onlyIntOrString(450, 616) # valid
5181  onlyIntOrString(5.0, 0.0) # type mismatch
5182  onlyIntOrString("xy", 50) # invalid as 'T' cannot be both at the same time
5183
5184
5185Implicit generics
5186-----------------
5187
5188A type class can be used directly as the parameter's type.
5189
5190.. code-block:: nim
5191
5192  # create a type class that will match all tuple and object types
5193  type RecordType = tuple or object
5194
5195  proc printFields(rec: RecordType) =
5196    for key, value in fieldPairs(rec):
5197      echo key, " = ", value
5198
5199
5200Procedures utilizing type classes in such a manner are considered to be
5201`implicitly generic`:idx:. They will be instantiated once for each unique
5202combination of param types used within the program.
5203
5204By default, during overload resolution, each named type class will bind to
5205exactly one concrete type. We call such type classes `bind once`:idx: types.
5206Here is an example taken directly from the system module to illustrate this:
5207
5208.. code-block:: nim
5209  proc `==`*(x, y: tuple): bool =
5210    ## requires `x` and `y` to be of the same tuple type
5211    ## generic `==` operator for tuples that is lifted from the components
5212    ## of `x` and `y`.
5213    result = true
5214    for a, b in fields(x, y):
5215      if a != b: result = false
5216
5217Alternatively, the `distinct` type modifier can be applied to the type class
5218to allow each param matching the type class to bind to a different type. Such
5219type classes are called `bind many`:idx: types.
5220
5221Procs written with the implicitly generic style will often need to refer to the
5222type parameters of the matched generic type. They can be easily accessed using
5223the dot syntax:
5224
5225.. code-block:: nim
5226  type Matrix[T, Rows, Columns] = object
5227    ...
5228
5229  proc `[]`(m: Matrix, row, col: int): Matrix.T =
5230    m.data[col * high(Matrix.Columns) + row]
5231
5232
5233Here are more examples that illustrate implicit generics:
5234
5235.. code-block:: nim
5236
5237  proc p(t: Table; k: Table.Key): Table.Value
5238
5239  # is roughly the same as:
5240
5241  proc p[Key, Value](t: Table[Key, Value]; k: Key): Value
5242
5243
5244.. code-block:: nim
5245
5246  proc p(a: Table, b: Table)
5247
5248  # is roughly the same as:
5249
5250  proc p[Key, Value](a, b: Table[Key, Value])
5251
5252
5253.. code-block:: nim
5254
5255  proc p(a: Table, b: distinct Table)
5256
5257  # is roughly the same as:
5258
5259  proc p[Key, Value, KeyB, ValueB](a: Table[Key, Value], b: Table[KeyB, ValueB])
5260
5261
5262`typedesc` used as a parameter type also introduces an implicit
5263generic. `typedesc` has its own set of rules:
5264
5265.. code-block:: nim
5266
5267  proc p(a: typedesc)
5268
5269  # is roughly the same as:
5270
5271  proc p[T](a: typedesc[T])
5272
5273
5274`typedesc` is a "bind many" type class:
5275
5276.. code-block:: nim
5277
5278  proc p(a, b: typedesc)
5279
5280  # is roughly the same as:
5281
5282  proc p[T, T2](a: typedesc[T], b: typedesc[T2])
5283
5284
5285A parameter of type `typedesc` is itself usable as a type. If it is used
5286as a type, it's the underlying type. (In other words, one level
5287of "typedesc"-ness is stripped off:
5288
5289.. code-block:: nim
5290
5291  proc p(a: typedesc; b: a) = discard
5292
5293  # is roughly the same as:
5294  proc p[T](a: typedesc[T]; b: T) = discard
5295
5296  # hence this is a valid call:
5297  p(int, 4)
5298  # as parameter 'a' requires a type, but 'b' requires a value.
5299
5300
5301Generic inference restrictions
5302------------------------------
5303
5304The types `var T` and `typedesc[T]` cannot be inferred in a generic
5305instantiation. The following is not allowed:
5306
5307.. code-block:: nim
5308    :test: "nim c $1"
5309    :status: 1
5310
5311  proc g[T](f: proc(x: T); x: T) =
5312    f(x)
5313
5314  proc c(y: int) = echo y
5315  proc v(y: var int) =
5316    y += 100
5317  var i: int
5318
5319  # allowed: infers 'T' to be of type 'int'
5320  g(c, 42)
5321
5322  # not valid: 'T' is not inferred to be of type 'var int'
5323  g(v, i)
5324
5325  # also not allowed: explicit instantiation via 'var int'
5326  g[var int](v, i)
5327
5328
5329
5330Symbol lookup in generics
5331-------------------------
5332
5333Open and Closed symbols
5334~~~~~~~~~~~~~~~~~~~~~~~
5335
5336The symbol binding rules in generics are slightly subtle: There are "open" and
5337"closed" symbols. A "closed" symbol cannot be re-bound in the instantiation
5338context, an "open" symbol can. Per default, overloaded symbols are open
5339and every other symbol is closed.
5340
5341Open symbols are looked up in two different contexts: Both the context
5342at definition and the context at instantiation are considered:
5343
5344.. code-block:: nim
5345    :test: "nim c $1"
5346
5347  type
5348    Index = distinct int
5349
5350  proc `==` (a, b: Index): bool {.borrow.}
5351
5352  var a = (0, 0.Index)
5353  var b = (0, 0.Index)
5354
5355  echo a == b # works!
5356
5357In the example, the generic `==` for tuples (as defined in the system module)
5358uses the `==` operators of the tuple's components. However, the `==` for
5359the `Index` type is defined *after* the `==` for tuples; yet the example
5360compiles as the instantiation takes the currently defined symbols into account
5361too.
5362
5363Mixin statement
5364---------------
5365
5366A symbol can be forced to be open by a `mixin`:idx: declaration:
5367
5368.. code-block:: nim
5369    :test: "nim c $1"
5370
5371  proc create*[T](): ref T =
5372    # there is no overloaded 'init' here, so we need to state that it's an
5373    # open symbol explicitly:
5374    mixin init
5375    new result
5376    init result
5377
5378`mixin` statements only make sense in templates and generics.
5379
5380
5381Bind statement
5382--------------
5383
5384The `bind` statement is the counterpart to the `mixin` statement. It
5385can be used to explicitly declare identifiers that should be bound early (i.e.
5386the identifiers should be looked up in the scope of the template/generic
5387definition):
5388
5389.. code-block:: nim
5390  # Module A
5391  var
5392    lastId = 0
5393
5394  template genId*: untyped =
5395    bind lastId
5396    inc(lastId)
5397    lastId
5398
5399.. code-block:: nim
5400  # Module B
5401  import A
5402
5403  echo genId()
5404
5405But a `bind` is rarely useful because symbol binding from the definition
5406scope is the default.
5407
5408`bind` statements only make sense in templates and generics.
5409
5410
5411Delegating bind statements
5412--------------------------
5413
5414The following example outlines a problem that can arise when generic
5415instantiations cross multiple different modules:
5416
5417.. code-block:: nim
5418
5419  # module A
5420  proc genericA*[T](x: T) =
5421    mixin init
5422    init(x)
5423
5424
5425.. code-block:: nim
5426
5427  import C
5428
5429  # module B
5430  proc genericB*[T](x: T) =
5431    # Without the `bind init` statement C's init proc is
5432    # not available when `genericB` is instantiated:
5433    bind init
5434    genericA(x)
5435
5436.. code-block:: nim
5437
5438  # module C
5439  type O = object
5440  proc init*(x: var O) = discard
5441
5442.. code-block:: nim
5443
5444  # module main
5445  import B, C
5446
5447  genericB O()
5448
5449In module B has an `init` proc from module C in its scope that is not
5450taken into account when `genericB` is instantiated which leads to the
5451instantiation of `genericA`. The solution is to `forward`:idx: these
5452symbols by a `bind` statement inside `genericB`.
5453
5454
5455Templates
5456=========
5457
5458A template is a simple form of a macro: It is a simple substitution
5459mechanism that operates on Nim's abstract syntax trees. It is processed in
5460the semantic pass of the compiler.
5461
5462The syntax to *invoke* a template is the same as calling a procedure.
5463
5464Example:
5465
5466.. code-block:: nim
5467  template `!=` (a, b: untyped): untyped =
5468    # this definition exists in the System module
5469    not (a == b)
5470
5471  assert(5 != 6) # the compiler rewrites that to: assert(not (5 == 6))
5472
5473The `!=`, `>`, `>=`, `in`, `notin`, `isnot` operators are in fact
5474templates:
5475
5476| `a > b` is transformed into `b < a`.
5477| `a in b` is transformed into `contains(b, a)`.
5478| `notin` and `isnot` have the obvious meanings.
5479
5480The "types" of templates can be the symbols `untyped`,
5481`typed` or `typedesc`. These are "meta types", they can only be used in certain
5482contexts. Regular types can be used too; this implies that `typed` expressions
5483are expected.
5484
5485
5486Typed vs untyped parameters
5487---------------------------
5488
5489An `untyped` parameter means that symbol lookups and type resolution is not
5490performed before the expression is passed to the template. This means that
5491*undeclared* identifiers, for example, can be passed to the template:
5492
5493.. code-block:: nim
5494    :test: "nim c $1"
5495
5496  template declareInt(x: untyped) =
5497    var x: int
5498
5499  declareInt(x) # valid
5500  x = 3
5501
5502
5503.. code-block:: nim
5504    :test: "nim c $1"
5505    :status: 1
5506
5507  template declareInt(x: typed) =
5508    var x: int
5509
5510  declareInt(x) # invalid, because x has not been declared and so it has no type
5511
5512A template where every parameter is `untyped` is called an `immediate`:idx:
5513template. For historical reasons, templates can be explicitly annotated with
5514an `immediate` pragma and then these templates do not take part in
5515overloading resolution and the parameters' types are *ignored* by the
5516compiler. Explicit immediate templates are now deprecated.
5517
5518**Note**: For historical reasons, `stmt` was an alias for `typed` and
5519`expr` was an alias for `untyped`, but they are removed.
5520
5521
5522Passing a code block to a template
5523----------------------------------
5524
5525One can pass a block of statements as the last argument to a template
5526following the special `:` syntax:
5527
5528.. code-block:: nim
5529    :test: "nim c $1"
5530
5531  template withFile(f, fn, mode, actions: untyped): untyped =
5532    var f: File
5533    if open(f, fn, mode):
5534      try:
5535        actions
5536      finally:
5537        close(f)
5538    else:
5539      quit("cannot open: " & fn)
5540
5541  withFile(txt, "ttempl3.txt", fmWrite):  # special colon
5542    txt.writeLine("line 1")
5543    txt.writeLine("line 2")
5544
5545In the example, the two `writeLine` statements are bound to the `actions`
5546parameter.
5547
5548
5549Usually, to pass a block of code to a template, the parameter that accepts
5550the block needs to be of type `untyped`. Because symbol lookups are then
5551delayed until template instantiation time:
5552
5553.. code-block:: nim
5554    :test: "nim c $1"
5555    :status: 1
5556
5557  template t(body: typed) =
5558    proc p = echo "hey"
5559    block:
5560      body
5561
5562  t:
5563    p()  # fails with 'undeclared identifier: p'
5564
5565The above code fails with the error message that `p` is not declared.
5566The reason for this is that the `p()` body is type-checked before getting
5567passed to the `body` parameter and type checking in Nim implies symbol lookups.
5568The same code works with `untyped` as the passed body is not required to be
5569type-checked:
5570
5571.. code-block:: nim
5572    :test: "nim c $1"
5573
5574  template t(body: untyped) =
5575    proc p = echo "hey"
5576    block:
5577      body
5578
5579  t:
5580    p()  # compiles
5581
5582
5583Varargs of untyped
5584------------------
5585
5586In addition to the `untyped` meta-type that prevents type checking, there is
5587also `varargs[untyped]` so that not even the number of parameters is fixed:
5588
5589.. code-block:: nim
5590    :test: "nim c $1"
5591
5592  template hideIdentifiers(x: varargs[untyped]) = discard
5593
5594  hideIdentifiers(undeclared1, undeclared2)
5595
5596However, since a template cannot iterate over varargs, this feature is
5597generally much more useful for macros.
5598
5599
5600Symbol binding in templates
5601---------------------------
5602
5603A template is a `hygienic`:idx: macro and so opens a new scope. Most symbols are
5604bound from the definition scope of the template:
5605
5606.. code-block:: nim
5607  # Module A
5608  var
5609    lastId = 0
5610
5611  template genId*: untyped =
5612    inc(lastId)
5613    lastId
5614
5615.. code-block:: nim
5616  # Module B
5617  import A
5618
5619  echo genId() # Works as 'lastId' has been bound in 'genId's defining scope
5620
5621As in generics, symbol binding can be influenced via `mixin` or `bind`
5622statements.
5623
5624
5625
5626Identifier construction
5627-----------------------
5628
5629In templates, identifiers can be constructed with the backticks notation:
5630
5631.. code-block:: nim
5632    :test: "nim c $1"
5633
5634  template typedef(name: untyped, typ: typedesc) =
5635    type
5636      `T name`* {.inject.} = typ
5637      `P name`* {.inject.} = ref `T name`
5638
5639  typedef(myint, int)
5640  var x: PMyInt
5641
5642In the example, `name` is instantiated with `myint`, so \`T name\` becomes
5643`Tmyint`.
5644
5645
5646Lookup rules for template parameters
5647------------------------------------
5648
5649A parameter `p` in a template is even substituted in the expression `x.p`.
5650Thus, template arguments can be used as field names and a global symbol can be
5651shadowed by the same argument name even when fully qualified:
5652
5653.. code-block:: nim
5654  # module 'm'
5655
5656  type
5657    Lev = enum
5658      levA, levB
5659
5660  var abclev = levB
5661
5662  template tstLev(abclev: Lev) =
5663    echo abclev, " ", m.abclev
5664
5665  tstLev(levA)
5666  # produces: 'levA levA'
5667
5668But the global symbol can properly be captured by a `bind` statement:
5669
5670.. code-block:: nim
5671  # module 'm'
5672
5673  type
5674    Lev = enum
5675      levA, levB
5676
5677  var abclev = levB
5678
5679  template tstLev(abclev: Lev) =
5680    bind m.abclev
5681    echo abclev, " ", m.abclev
5682
5683  tstLev(levA)
5684  # produces: 'levA levB'
5685
5686
5687Hygiene in templates
5688--------------------
5689
5690Per default, templates are `hygienic`:idx:\: Local identifiers declared in a
5691template cannot be accessed in the instantiation context:
5692
5693.. code-block:: nim
5694    :test: "nim c $1"
5695
5696  template newException*(exceptn: typedesc, message: string): untyped =
5697    var
5698      e: ref exceptn  # e is implicitly gensym'ed here
5699    new(e)
5700    e.msg = message
5701    e
5702
5703  # so this works:
5704  let e = "message"
5705  raise newException(IoError, e)
5706
5707
5708Whether a symbol that is declared in a template is exposed to the instantiation
5709scope is controlled by the `inject`:idx: and `gensym`:idx: pragmas:
5710`gensym`'ed symbols are not exposed but `inject`'ed symbols are.
5711
5712The default for symbols of entity `type`, `var`, `let` and `const`
5713is `gensym` and for `proc`, `iterator`, `converter`, `template`,
5714`macro` is `inject`. However, if the name of the entity is passed as a
5715template parameter, it is an `inject`'ed symbol:
5716
5717.. code-block:: nim
5718  template withFile(f, fn, mode: untyped, actions: untyped): untyped =
5719    block:
5720      var f: File  # since 'f' is a template param, it's injected implicitly
5721      ...
5722
5723  withFile(txt, "ttempl3.txt", fmWrite):
5724    txt.writeLine("line 1")
5725    txt.writeLine("line 2")
5726
5727
5728The `inject` and `gensym` pragmas are second class annotations; they have
5729no semantics outside of a template definition and cannot be abstracted over:
5730
5731.. code-block:: nim
5732  {.pragma myInject: inject.}
5733
5734  template t() =
5735    var x {.myInject.}: int # does NOT work
5736
5737
5738To get rid of hygiene in templates, one can use the `dirty`:idx: pragma for
5739a template. `inject` and `gensym` have no effect in `dirty` templates.
5740
5741`gensym`'ed symbols cannot be used as `field` in the `x.field` syntax.
5742Nor can they be used in the `ObjectConstruction(field: value)`
5743and `namedParameterCall(field = value)` syntactic constructs.
5744
5745The reason for this is that code like
5746
5747.. code-block:: nim
5748    :test: "nim c $1"
5749
5750  type
5751    T = object
5752      f: int
5753
5754  template tmp(x: T) =
5755    let f = 34
5756    echo x.f, T(f: 4)
5757
5758
5759should work as expected.
5760
5761However, this means that the method call syntax is not available for
5762`gensym`'ed symbols:
5763
5764.. code-block:: nim
5765    :test: "nim c $1"
5766    :status: 1
5767
5768  template tmp(x) =
5769    type
5770      T {.gensym.} = int
5771
5772    echo x.T # invalid: instead use:  'echo T(x)'.
5773
5774  tmp(12)
5775
5776
5777**Note**: The Nim compiler prior to version 1 was more lenient about this
5778requirement. Use the `--useVersion:0.19`:option: switch for a transition period.
5779
5780
5781
5782Limitations of the method call syntax
5783-------------------------------------
5784
5785The expression `x` in `x.f` needs to be semantically checked (that means
5786symbol lookup and type checking) before it can be decided that it needs to be
5787rewritten to `f(x)`. Therefore the dot syntax has some limitations when it
5788is used to invoke templates/macros:
5789
5790.. code-block:: nim
5791    :test: "nim c $1"
5792    :status: 1
5793
5794  template declareVar(name: untyped) =
5795    const name {.inject.} = 45
5796
5797  # Doesn't compile:
5798  unknownIdentifier.declareVar
5799
5800
5801It is also not possible to use fully qualified identifiers with module
5802symbol in method call syntax. The order in which the dot operator
5803binds to symbols prohibits this.
5804
5805.. code-block:: nim
5806    :test: "nim c $1"
5807    :status: 1
5808
5809   import std/sequtils
5810
5811   var myItems = @[1,3,3,7]
5812   let N1 = count(myItems, 3) # OK
5813   let N2 = sequtils.count(myItems, 3) # fully qualified, OK
5814   let N3 = myItems.count(3) # OK
5815   let N4 = myItems.sequtils.count(3) # illegal, `myItems.sequtils` can't be resolved
5816
5817This means that when for some reason a procedure needs a
5818disambiguation through the module name, the call needs to be
5819written in function call syntax.
5820
5821Macros
5822======
5823
5824A macro is a special function that is executed at compile time.
5825Normally, the input for a macro is an abstract syntax
5826tree (AST) of the code that is passed to it. The macro can then do
5827transformations on it and return the transformed AST. This can be used to
5828add custom language features and implement `domain-specific languages`:idx:.
5829
5830Macro invocation is a case where semantic analysis does **not** entirely proceed
5831top to bottom and left to right. Instead, semantic analysis happens at least
5832twice:
5833
5834* Semantic analysis recognizes and resolves the macro invocation.
5835* The compiler executes the macro body (which may invoke other procs).
5836* It replaces the AST of the macro invocation with the AST returned by the macro.
5837* It repeats semantic analysis of that region of the code.
5838* If the AST returned by the macro contains other macro invocations,
5839  this process iterates.
5840
5841While macros enable advanced compile-time code transformations, they
5842cannot change Nim's syntax.
5843
5844Debug Example
5845-------------
5846
5847The following example implements a powerful `debug` command that accepts a
5848variable number of arguments:
5849
5850.. code-block:: nim
5851    :test: "nim c $1"
5852
5853  # to work with Nim syntax trees, we need an API that is defined in the
5854  # `macros` module:
5855  import std/macros
5856
5857  macro debug(args: varargs[untyped]): untyped =
5858    # `args` is a collection of `NimNode` values that each contain the
5859    # AST for an argument of the macro. A macro always has to
5860    # return a `NimNode`. A node of kind `nnkStmtList` is suitable for
5861    # this use case.
5862    result = nnkStmtList.newTree()
5863    # iterate over any argument that is passed to this macro:
5864    for n in args:
5865      # add a call to the statement list that writes the expression;
5866      # `toStrLit` converts an AST to its string representation:
5867      result.add newCall("write", newIdentNode("stdout"), newLit(n.repr))
5868      # add a call to the statement list that writes ": "
5869      result.add newCall("write", newIdentNode("stdout"), newLit(": "))
5870      # add a call to the statement list that writes the expressions value:
5871      result.add newCall("writeLine", newIdentNode("stdout"), n)
5872
5873  var
5874    a: array[0..10, int]
5875    x = "some string"
5876  a[0] = 42
5877  a[1] = 45
5878
5879  debug(a[0], a[1], x)
5880
5881The macro call expands to:
5882
5883.. code-block:: nim
5884  write(stdout, "a[0]")
5885  write(stdout, ": ")
5886  writeLine(stdout, a[0])
5887
5888  write(stdout, "a[1]")
5889  write(stdout, ": ")
5890  writeLine(stdout, a[1])
5891
5892  write(stdout, "x")
5893  write(stdout, ": ")
5894  writeLine(stdout, x)
5895
5896
5897Arguments that are passed to a `varargs` parameter are wrapped in an array
5898constructor expression. This is why `debug` iterates over all of `args`'s
5899children.
5900
5901
5902BindSym
5903-------
5904
5905The above `debug` macro relies on the fact that `write`, `writeLine` and
5906`stdout` are declared in the system module and are thus visible in the
5907instantiating context. There is a way to use bound identifiers
5908(aka `symbols`:idx:) instead of using unbound identifiers. The `bindSym`
5909builtin can be used for that:
5910
5911.. code-block:: nim
5912    :test: "nim c $1"
5913
5914  import std/macros
5915
5916  macro debug(n: varargs[typed]): untyped =
5917    result = newNimNode(nnkStmtList, n)
5918    for x in n:
5919      # we can bind symbols in scope via 'bindSym':
5920      add(result, newCall(bindSym"write", bindSym"stdout", toStrLit(x)))
5921      add(result, newCall(bindSym"write", bindSym"stdout", newStrLitNode(": ")))
5922      add(result, newCall(bindSym"writeLine", bindSym"stdout", x))
5923
5924  var
5925    a: array[0..10, int]
5926    x = "some string"
5927  a[0] = 42
5928  a[1] = 45
5929
5930  debug(a[0], a[1], x)
5931
5932The macro call expands to:
5933
5934.. code-block:: nim
5935  write(stdout, "a[0]")
5936  write(stdout, ": ")
5937  writeLine(stdout, a[0])
5938
5939  write(stdout, "a[1]")
5940  write(stdout, ": ")
5941  writeLine(stdout, a[1])
5942
5943  write(stdout, "x")
5944  write(stdout, ": ")
5945  writeLine(stdout, x)
5946
5947However, the symbols `write`, `writeLine` and `stdout` are already bound
5948and are not looked up again. As the example shows, `bindSym` does work with
5949overloaded symbols implicitly.
5950
5951Case-Of Macro
5952-------------
5953
5954In Nim, it is possible to have a macro with the syntax of a *case-of*
5955expression just with the difference that all *of-branches* are passed to
5956and processed by the macro implementation. It is then up the macro
5957implementation to transform the *of-branches* into a valid Nim
5958statement. The following example should show how this feature could be
5959used for a lexical analyzer.
5960
5961.. code-block:: nim
5962  import std/macros
5963
5964  macro case_token(args: varargs[untyped]): untyped =
5965    echo args.treeRepr
5966    # creates a lexical analyzer from regular expressions
5967    # ... (implementation is an exercise for the reader ;-)
5968    discard
5969
5970  case_token: # this colon tells the parser it is a macro statement
5971  of r"[A-Za-z_]+[A-Za-z_0-9]*":
5972    return tkIdentifier
5973  of r"0-9+":
5974    return tkInteger
5975  of r"[\+\-\*\?]+":
5976    return tkOperator
5977  else:
5978    return tkUnknown
5979
5980
5981**Style note**: For code readability, it is best to use the least powerful
5982programming construct that still suffices. So the "check list" is:
5983
5984(1) Use an ordinary proc/iterator, if possible.
5985(2) Else: Use a generic proc/iterator, if possible.
5986(3) Else: Use a template, if possible.
5987(4) Else: Use a macro.
5988
5989
5990For loop macro
5991--------------
5992
5993A macro that takes as its only input parameter an expression of the special
5994type `system.ForLoopStmt` can rewrite the entirety of a `for` loop:
5995
5996.. code-block:: nim
5997    :test: "nim c $1"
5998
5999  import std/macros
6000
6001  macro example(loop: ForLoopStmt) =
6002    result = newTree(nnkForStmt)    # Create a new For loop.
6003    result.add loop[^3]             # This is "item".
6004    result.add loop[^2][^1]         # This is "[1, 2, 3]".
6005    result.add newCall(bindSym"echo", loop[0])
6006
6007  for item in example([1, 2, 3]): discard
6008
6009Expands to:
6010
6011.. code-block:: nim
6012  for item in items([1, 2, 3]):
6013    echo item
6014
6015Another example:
6016
6017.. code-block:: nim
6018    :test: "nim c $1"
6019
6020  import std/macros
6021
6022  macro enumerate(x: ForLoopStmt): untyped =
6023    expectKind x, nnkForStmt
6024    # check if the starting count is specified:
6025    var countStart = if x[^2].len == 2: newLit(0) else: x[^2][1]
6026    result = newStmtList()
6027    # we strip off the first for loop variable and use it as an integer counter:
6028    result.add newVarStmt(x[0], countStart)
6029    var body = x[^1]
6030    if body.kind != nnkStmtList:
6031      body = newTree(nnkStmtList, body)
6032    body.add newCall(bindSym"inc", x[0])
6033    var newFor = newTree(nnkForStmt)
6034    for i in 1..x.len-3:
6035      newFor.add x[i]
6036    # transform enumerate(X) to 'X'
6037    newFor.add x[^2][^1]
6038    newFor.add body
6039    result.add newFor
6040    # now wrap the whole macro in a block to create a new scope
6041    result = quote do:
6042      block: `result`
6043
6044  for a, b in enumerate(items([1, 2, 3])):
6045    echo a, " ", b
6046
6047  # without wrapping the macro in a block, we'd need to choose different
6048  # names for `a` and `b` here to avoid redefinition errors
6049  for a, b in enumerate(10, [1, 2, 3, 5]):
6050    echo a, " ", b
6051
6052
6053Special Types
6054=============
6055
6056static[T]
6057---------
6058
6059As their name suggests, static parameters must be constant expressions:
6060
6061.. code-block:: nim
6062
6063  proc precompiledRegex(pattern: static string): RegEx =
6064    var res {.global.} = re(pattern)
6065    return res
6066
6067  precompiledRegex("/d+") # Replaces the call with a precompiled
6068                          # regex, stored in a global variable
6069
6070  precompiledRegex(paramStr(1)) # Error, command-line options
6071                                # are not constant expressions
6072
6073
6074For the purposes of code generation, all static params are treated as
6075generic params - the proc will be compiled separately for each unique
6076supplied value (or combination of values).
6077
6078Static params can also appear in the signatures of generic types:
6079
6080.. code-block:: nim
6081
6082  type
6083    Matrix[M,N: static int; T: Number] = array[0..(M*N - 1), T]
6084      # Note how `Number` is just a type constraint here, while
6085      # `static int` requires us to supply an int value
6086
6087    AffineTransform2D[T] = Matrix[3, 3, T]
6088    AffineTransform3D[T] = Matrix[4, 4, T]
6089
6090  var m1: AffineTransform3D[float]  # OK
6091  var m2: AffineTransform2D[string] # Error, `string` is not a `Number`
6092
6093Please note that `static T` is just a syntactic convenience for the underlying
6094generic type `static[T]`. The type param can be omitted to obtain the type
6095class of all constant expressions. A more specific type class can be created by
6096instantiating `static` with another type class.
6097
6098One can force an expression to be evaluated at compile time as a constant
6099expression by coercing it to a corresponding `static` type:
6100
6101.. code-block:: nim
6102  import std/math
6103
6104  echo static(fac(5)), " ", static[bool](16.isPowerOfTwo)
6105
6106The compiler will report any failure to evaluate the expression or a
6107possible type mismatch error.
6108
6109typedesc[T]
6110-----------
6111
6112In many contexts, Nim treats the names of types as regular
6113values. These values exist only during the compilation phase, but since
6114all values must have a type, `typedesc` is considered their special type.
6115
6116`typedesc` acts as a generic type. For instance, the type of the symbol
6117`int` is `typedesc[int]`. Just like with regular generic types, when the
6118generic param is omitted, `typedesc` denotes the type class of all types.
6119As a syntactic convenience, one can also use `typedesc` as a modifier.
6120
6121Procs featuring `typedesc` params are considered implicitly generic.
6122They will be instantiated for each unique combination of supplied types,
6123and within the body of the proc, the name of each param will refer to
6124the bound concrete type:
6125
6126.. code-block:: nim
6127
6128  proc new(T: typedesc): ref T =
6129    echo "allocating ", T.name
6130    new(result)
6131
6132  var n = Node.new
6133  var tree = new(BinaryTree[int])
6134
6135When multiple type params are present, they will bind freely to different
6136types. To force a bind-once behavior, one can use an explicit generic param:
6137
6138.. code-block:: nim
6139  proc acceptOnlyTypePairs[T, U](A, B: typedesc[T]; C, D: typedesc[U])
6140
6141Once bound, type params can appear in the rest of the proc signature:
6142
6143.. code-block:: nim
6144    :test: "nim c $1"
6145
6146  template declareVariableWithType(T: typedesc, value: T) =
6147    var x: T = value
6148
6149  declareVariableWithType int, 42
6150
6151
6152Overload resolution can be further influenced by constraining the set
6153of types that will match the type param. This works in practice by
6154attaching attributes to types via templates. The constraint can be a
6155concrete type or a type class.
6156
6157.. code-block:: nim
6158    :test: "nim c $1"
6159
6160  template maxval(T: typedesc[int]): int = high(int)
6161  template maxval(T: typedesc[float]): float = Inf
6162
6163  var i = int.maxval
6164  var f = float.maxval
6165  when false:
6166    var s = string.maxval # error, maxval is not implemented for string
6167
6168  template isNumber(t: typedesc[object]): string = "Don't think so."
6169  template isNumber(t: typedesc[SomeInteger]): string = "Yes!"
6170  template isNumber(t: typedesc[SomeFloat]): string = "Maybe, could be NaN."
6171
6172  echo "is int a number? ", isNumber(int)
6173  echo "is float a number? ", isNumber(float)
6174  echo "is RootObj a number? ", isNumber(RootObj)
6175
6176Passing `typedesc` is almost identical, just with the difference that
6177the macro is not instantiated generically. The type expression is
6178simply passed as a `NimNode` to the macro, like everything else.
6179
6180.. code-block:: nim
6181
6182  import std/macros
6183
6184  macro forwardType(arg: typedesc): typedesc =
6185    # `arg` is of type `NimNode`
6186    let tmp: NimNode = arg
6187    result = tmp
6188
6189  var tmp: forwardType(int)
6190
6191typeof operator
6192---------------
6193
6194**Note**: `typeof(x)` can for historical reasons also be written as
6195`type(x)` but `type(x)` is discouraged.
6196
6197One can obtain the type of a given expression by constructing a `typeof`
6198value from it (in many other languages this is known as the `typeof`:idx:
6199operator):
6200
6201.. code-block:: nim
6202
6203  var x = 0
6204  var y: typeof(x) # y has type int
6205
6206
6207If `typeof` is used to determine the result type of a proc/iterator/converter
6208call `c(X)` (where `X` stands for a possibly empty list of arguments), the
6209interpretation, where `c` is an iterator, is preferred over the
6210other interpretations, but this behavior can be changed by
6211passing `typeOfProc` as the second argument to `typeof`:
6212
6213.. code-block:: nim
6214    :test: "nim c $1"
6215
6216  iterator split(s: string): string = discard
6217  proc split(s: string): seq[string] = discard
6218
6219  # since an iterator is the preferred interpretation, `y` has the type `string`:
6220  assert typeof("a b c".split) is string
6221
6222  assert typeof("a b c".split, typeOfProc) is seq[string]
6223
6224
6225
6226Modules
6227=======
6228Nim supports splitting a program into pieces by a module concept.
6229Each module needs to be in its own file and has its own `namespace`:idx:.
6230Modules enable `information hiding`:idx: and `separate compilation`:idx:.
6231A module may gain access to symbols of another module by the `import`:idx:
6232statement. `Recursive module dependencies`:idx: are allowed, but are slightly
6233subtle. Only top-level symbols that are marked with an asterisk (`*`) are
6234exported. A valid module name can only be a valid Nim identifier (and thus its
6235filename is ``identifier.nim``).
6236
6237The algorithm for compiling modules is:
6238
6239- Compile the whole module as usual, following import statements recursively.
6240
6241- If there is a cycle, only import the already parsed symbols (that are
6242  exported); if an unknown identifier occurs then abort.
6243
6244This is best illustrated by an example:
6245
6246.. code-block:: nim
6247  # Module A
6248  type
6249    T1* = int  # Module A exports the type `T1`
6250  import B     # the compiler starts parsing B
6251
6252  proc main() =
6253    var i = p(3) # works because B has been parsed completely here
6254
6255  main()
6256
6257
6258.. code-block:: nim
6259  # Module B
6260  import A  # A is not parsed here! Only the already known symbols
6261            # of A are imported.
6262
6263  proc p*(x: A.T1): A.T1 =
6264    # this works because the compiler has already
6265    # added T1 to A's interface symbol table
6266    result = x + 1
6267
6268
6269Import statement
6270----------------
6271
6272After the `import` statement, a list of module names can follow or a single
6273module name followed by an `except` list to prevent some symbols from being
6274imported:
6275
6276.. code-block:: nim
6277    :test: "nim c $1"
6278    :status: 1
6279
6280  import std/strutils except `%`, toUpperAscii
6281
6282  # doesn't work then:
6283  echo "$1" % "abc".toUpperAscii
6284
6285
6286It is not checked that the `except` list is really exported from the module.
6287This feature allows us to compile against an older version of the module that
6288does not export these identifiers.
6289
6290The `import` statement is only allowed at the top level.
6291
6292
6293Include statement
6294-----------------
6295
6296The `include` statement does something fundamentally different than
6297importing a module: it merely includes the contents of a file. The `include`
6298statement is useful to split up a large module into several files:
6299
6300.. code-block:: nim
6301  include fileA, fileB, fileC
6302
6303The `include` statement can be used outside of the top level, as such:
6304
6305.. code-block:: nim
6306  # Module A
6307  echo "Hello World!"
6308
6309.. code-block:: nim
6310  # Module B
6311  proc main() =
6312    include A
6313
6314  main() # => Hello World!
6315
6316
6317Module names in imports
6318-----------------------
6319
6320A module alias can be introduced via the `as` keyword:
6321
6322.. code-block:: nim
6323  import std/strutils as su, std/sequtils as qu
6324
6325  echo su.format("$1", "lalelu")
6326
6327The original module name is then not accessible. The notations
6328`path/to/module` or `"path/to/module"` can be used to refer to a module
6329in subdirectories:
6330
6331.. code-block:: nim
6332  import lib/pure/os, "lib/pure/times"
6333
6334Note that the module name is still `strutils` and not `lib/pure/strutils`
6335and so one **cannot** do:
6336
6337.. code-block:: nim
6338  import lib/pure/strutils
6339  echo lib/pure/strutils.toUpperAscii("abc")
6340
6341Likewise, the following does not make sense as the name is `strutils` already:
6342
6343.. code-block:: nim
6344  import lib/pure/strutils as strutils
6345
6346
6347Collective imports from a directory
6348-----------------------------------
6349
6350The syntax `import dir / [moduleA, moduleB]` can be used to import multiple modules
6351from the same directory.
6352
6353Path names are syntactically either Nim identifiers or string literals. If the path
6354name is not a valid Nim identifier it needs to be a string literal:
6355
6356.. code-block:: nim
6357  import "gfx/3d/somemodule" # in quotes because '3d' is not a valid Nim identifier
6358
6359
6360Pseudo import/include paths
6361---------------------------
6362
6363A directory can also be a so-called "pseudo directory". They can be used to
6364avoid ambiguity when there are multiple modules with the same path.
6365
6366There are two pseudo directories:
6367
63681. `std`: The `std` pseudo directory is the abstract location of Nim's standard
6369   library. For example, the syntax `import std / strutils` is used to unambiguously
6370   refer to the standard library's `strutils` module.
63712. `pkg`: The `pkg` pseudo directory is used to unambiguously refer to a Nimble
6372   package. However, for technical details that lie outside the scope of this document,
6373   its semantics are: *Use the search path to look for module name but ignore the standard
6374   library locations*. In other words, it is the opposite of `std`.
6375
6376It is recommended and preferred but not currently enforced that all stdlib module imports include the std/ "pseudo directory" as part of the import name.
6377
6378From import statement
6379---------------------
6380
6381After the `from` statement, a module name follows followed by
6382an `import` to list the symbols one likes to use without explicit
6383full qualification:
6384
6385.. code-block:: nim
6386    :test: "nim c $1"
6387
6388  from std/strutils import `%`
6389
6390  echo "$1" % "abc"
6391  # always possible: full qualification:
6392  echo strutils.replace("abc", "a", "z")
6393
6394It's also possible to use `from module import nil` if one wants to import
6395the module but wants to enforce fully qualified access to every symbol
6396in `module`.
6397
6398
6399Export statement
6400----------------
6401
6402An `export` statement can be used for symbol forwarding so that client
6403modules don't need to import a module's dependencies:
6404
6405.. code-block:: nim
6406  # module B
6407  type MyObject* = object
6408
6409.. code-block:: nim
6410  # module A
6411  import B
6412  export B.MyObject
6413
6414  proc `$`*(x: MyObject): string = "my object"
6415
6416
6417.. code-block:: nim
6418  # module C
6419  import A
6420
6421  # B.MyObject has been imported implicitly here:
6422  var x: MyObject
6423  echo $x
6424
6425When the exported symbol is another module, all of its definitions will
6426be forwarded. One can use an `except` list to exclude some of the symbols.
6427
6428Notice that when exporting, one needs to specify only the module name:
6429
6430.. code-block:: nim
6431  import foo/bar/baz
6432  export baz
6433
6434
6435
6436Scope rules
6437-----------
6438Identifiers are valid from the point of their declaration until the end of
6439the block in which the declaration occurred. The range where the identifier
6440is known is the scope of the identifier. The exact scope of an
6441identifier depends on the way it was declared.
6442
6443Block scope
6444~~~~~~~~~~~
6445The *scope* of a variable declared in the declaration part of a block
6446is valid from the point of declaration until the end of the block. If a
6447block contains a second block, in which the identifier is redeclared,
6448then inside this block, the second declaration will be valid. Upon
6449leaving the inner block, the first declaration is valid again. An
6450identifier cannot be redefined in the same block, except if valid for
6451procedure or iterator overloading purposes.
6452
6453
6454Tuple or object scope
6455~~~~~~~~~~~~~~~~~~~~~
6456The field identifiers inside a tuple or object definition are valid in the
6457following places:
6458
6459* To the end of the tuple/object definition.
6460* Field designators of a variable of the given tuple/object type.
6461* In all descendant types of the object type.
6462
6463Module scope
6464~~~~~~~~~~~~
6465All identifiers of a module are valid from the point of declaration until
6466the end of the module. Identifiers from indirectly dependent modules are *not*
6467available. The `system`:idx: module is automatically imported in every module.
6468
6469If a module imports an identifier by two different modules, each occurrence of
6470the identifier has to be qualified unless it is an overloaded procedure or
6471iterator in which case the overloading resolution takes place:
6472
6473.. code-block:: nim
6474  # Module A
6475  var x*: string
6476
6477.. code-block:: nim
6478  # Module B
6479  var x*: int
6480
6481.. code-block:: nim
6482  # Module C
6483  import A, B
6484  write(stdout, x) # error: x is ambiguous
6485  write(stdout, A.x) # no error: qualifier used
6486
6487  var x = 4
6488  write(stdout, x) # not ambiguous: uses the module C's x
6489
6490
6491Compiler Messages
6492=================
6493
6494The Nim compiler emits different kinds of messages: `hint`:idx:,
6495`warning`:idx:, and `error`:idx: messages. An *error* message is emitted if
6496the compiler encounters any static error.
6497
6498
6499
6500Pragmas
6501=======
6502
6503Pragmas are Nim's method to give the compiler additional information /
6504commands without introducing a massive number of new keywords. Pragmas are
6505processed on the fly during semantic checking. Pragmas are enclosed in the
6506special `{.` and `.}` curly brackets. Pragmas are also often used as a
6507first implementation to play with a language feature before a nicer syntax
6508to access the feature becomes available.
6509
6510
6511deprecated pragma
6512-----------------
6513
6514The deprecated pragma is used to mark a symbol as deprecated:
6515
6516.. code-block:: nim
6517  proc p() {.deprecated.}
6518  var x {.deprecated.}: char
6519
6520This pragma can also take in an optional warning string to relay to developers.
6521
6522.. code-block:: nim
6523  proc thing(x: bool) {.deprecated: "use thong instead".}
6524
6525
6526
6527compileTime pragma
6528------------------
6529The `compileTime` pragma is used to mark a proc or variable to be used only
6530during compile-time execution. No code will be generated for it. Compile-time
6531procs are useful as helpers for macros. Since version 0.12.0 of the language, a
6532proc that uses `system.NimNode` within its parameter types is implicitly
6533declared `compileTime`:
6534
6535.. code-block:: nim
6536  proc astHelper(n: NimNode): NimNode =
6537    result = n
6538
6539Is the same as:
6540
6541.. code-block:: nim
6542  proc astHelper(n: NimNode): NimNode {.compileTime.} =
6543    result = n
6544
6545`compileTime` variables are available at runtime too. This simplifies certain
6546idioms where variables are filled at compile-time (for example, lookup tables)
6547but accessed at runtime:
6548
6549.. code-block:: nim
6550    :test: "nim c -r $1"
6551
6552  import std/macros
6553
6554  var nameToProc {.compileTime.}: seq[(string, proc (): string {.nimcall.})]
6555
6556  macro registerProc(p: untyped): untyped =
6557    result = newTree(nnkStmtList, p)
6558
6559    let procName = p[0]
6560    let procNameAsStr = $p[0]
6561    result.add quote do:
6562      nameToProc.add((`procNameAsStr`, `procName`))
6563
6564  proc foo: string {.registerProc.} = "foo"
6565  proc bar: string {.registerProc.} = "bar"
6566  proc baz: string {.registerProc.} = "baz"
6567
6568  doAssert nameToProc[2][1]() == "baz"
6569
6570
6571noReturn pragma
6572---------------
6573The `noreturn` pragma is used to mark a proc that never returns.
6574
6575
6576acyclic pragma
6577--------------
6578The `acyclic` pragma can be used for object types to mark them as acyclic
6579even though they seem to be cyclic. This is an **optimization** for the garbage
6580collector to not consider objects of this type as part of a cycle:
6581
6582.. code-block:: nim
6583  type
6584    Node = ref NodeObj
6585    NodeObj {.acyclic.} = object
6586      left, right: Node
6587      data: string
6588
6589Or if we directly use a ref object:
6590
6591.. code-block:: nim
6592  type
6593    Node {.acyclic.} = ref object
6594      left, right: Node
6595      data: string
6596
6597In the example, a tree structure is declared with the `Node` type. Note that
6598the type definition is recursive and the GC has to assume that objects of
6599this type may form a cyclic graph. The `acyclic` pragma passes the
6600information that this cannot happen to the GC. If the programmer uses the
6601`acyclic` pragma for data types that are in reality cyclic, this may result
6602in memory leaks, but memory safety is preserved.
6603
6604
6605
6606final pragma
6607------------
6608The `final` pragma can be used for an object type to specify that it
6609cannot be inherited from. Note that inheritance is only available for
6610objects that inherit from an existing object (via the `object of SuperType`
6611syntax) or that have been marked as `inheritable`.
6612
6613
6614shallow pragma
6615--------------
6616The `shallow` pragma affects the semantics of a type: The compiler is
6617allowed to make a shallow copy. This can cause serious semantic issues and
6618break memory safety! However, it can speed up assignments considerably,
6619because the semantics of Nim require deep copying of sequences and strings.
6620This can be expensive, especially if sequences are used to build a tree
6621structure:
6622
6623.. code-block:: nim
6624  type
6625    NodeKind = enum nkLeaf, nkInner
6626    Node {.shallow.} = object
6627      case kind: NodeKind
6628      of nkLeaf:
6629        strVal: string
6630      of nkInner:
6631        children: seq[Node]
6632
6633
6634pure pragma
6635-----------
6636An object type can be marked with the `pure` pragma so that its type field
6637which is used for runtime type identification is omitted. This used to be
6638necessary for binary compatibility with other compiled languages.
6639
6640An enum type can be marked as `pure`. Then access of its fields always
6641requires full qualification.
6642
6643
6644asmNoStackFrame pragma
6645----------------------
6646A proc can be marked with the `asmNoStackFrame` pragma to tell the compiler
6647it should not generate a stack frame for the proc. There are also no exit
6648statements like `return result;` generated and the generated C function is
6649declared as `__declspec(naked)`:c: or `__attribute__((naked))`:c: (depending on
6650the used C compiler).
6651
6652**Note**: This pragma should only be used by procs which consist solely of
6653assembler statements.
6654
6655error pragma
6656------------
6657The `error` pragma is used to make the compiler output an error message
6658with the given content. The compilation does not necessarily abort after an error
6659though.
6660
6661The `error` pragma can also be used to
6662annotate a symbol (like an iterator or proc). The *usage* of the symbol then
6663triggers a static error. This is especially useful to rule out that some
6664operation is valid due to overloading and type conversions:
6665
6666.. code-block:: nim
6667  ## check that underlying int values are compared and not the pointers:
6668  proc `==`(x, y: ptr int): bool {.error.}
6669
6670
6671fatal pragma
6672------------
6673The `fatal` pragma is used to make the compiler output an error message
6674with the given content. In contrast to the `error` pragma, the compilation
6675is guaranteed to be aborted by this pragma. Example:
6676
6677.. code-block:: nim
6678  when not defined(objc):
6679    {.fatal: "Compile this program with the objc command!".}
6680
6681warning pragma
6682--------------
6683The `warning` pragma is used to make the compiler output a warning message
6684with the given content. Compilation continues after the warning.
6685
6686hint pragma
6687-----------
6688The `hint` pragma is used to make the compiler output a hint message with
6689the given content. Compilation continues after the hint.
6690
6691line pragma
6692-----------
6693The `line` pragma can be used to affect line information of the annotated
6694statement, as seen in stack backtraces:
6695
6696.. code-block:: nim
6697
6698  template myassert*(cond: untyped, msg = "") =
6699    if not cond:
6700      # change run-time line information of the 'raise' statement:
6701      {.line: instantiationInfo().}:
6702        raise newException(AssertionDefect, msg)
6703
6704If the `line` pragma is used with a parameter, the parameter needs be a
6705`tuple[filename: string, line: int]`. If it is used without a parameter,
6706`system.instantiationInfo()` is used.
6707
6708
6709linearScanEnd pragma
6710--------------------
6711The `linearScanEnd` pragma can be used to tell the compiler how to
6712compile a Nim `case`:idx: statement. Syntactically it has to be used as a
6713statement:
6714
6715.. code-block:: nim
6716  case myInt
6717  of 0:
6718    echo "most common case"
6719  of 1:
6720    {.linearScanEnd.}
6721    echo "second most common case"
6722  of 2: echo "unlikely: use branch table"
6723  else: echo "unlikely too: use branch table for ", myInt
6724
6725In the example, the case branches `0` and `1` are much more common than
6726the other cases. Therefore the generated assembler code should test for these
6727values first so that the CPU's branch predictor has a good chance to succeed
6728(avoiding an expensive CPU pipeline stall). The other cases might be put into a
6729jump table for O(1) overhead but at the cost of a (very likely) pipeline
6730stall.
6731
6732The `linearScanEnd` pragma should be put into the last branch that should be
6733tested against via linear scanning. If put into the last branch of the
6734whole `case` statement, the whole `case` statement uses linear scanning.
6735
6736
6737computedGoto pragma
6738-------------------
6739The `computedGoto` pragma can be used to tell the compiler how to
6740compile a Nim `case`:idx: in a `while true` statement.
6741Syntactically it has to be used as a statement inside the loop:
6742
6743.. code-block:: nim
6744
6745  type
6746    MyEnum = enum
6747      enumA, enumB, enumC, enumD, enumE
6748
6749  proc vm() =
6750    var instructions: array[0..100, MyEnum]
6751    instructions[2] = enumC
6752    instructions[3] = enumD
6753    instructions[4] = enumA
6754    instructions[5] = enumD
6755    instructions[6] = enumC
6756    instructions[7] = enumA
6757    instructions[8] = enumB
6758
6759    instructions[12] = enumE
6760    var pc = 0
6761    while true:
6762      {.computedGoto.}
6763      let instr = instructions[pc]
6764      case instr
6765      of enumA:
6766        echo "yeah A"
6767      of enumC, enumD:
6768        echo "yeah CD"
6769      of enumB:
6770        echo "yeah B"
6771      of enumE:
6772        break
6773      inc(pc)
6774
6775  vm()
6776
6777As the example shows, `computedGoto` is mostly useful for interpreters. If
6778the underlying backend (C compiler) does not support the computed goto
6779extension the pragma is simply ignored.
6780
6781
6782immediate pragma
6783----------------
6784
6785The immediate pragma is obsolete. See `Typed vs untyped parameters
6786<#templates-typed-vs-untyped-parameters>`_.
6787
6788
6789compilation option pragmas
6790--------------------------
6791The listed pragmas here can be used to override the code generation options
6792for a proc/method/converter.
6793
6794The implementation currently provides the following possible options (various
6795others may be added later).
6796
6797===============  ===============  ============================================
6798pragma           allowed values   description
6799===============  ===============  ============================================
6800checks           on|off           Turns the code generation for all runtime
6801                                  checks on or off.
6802boundChecks      on|off           Turns the code generation for array bound
6803                                  checks on or off.
6804overflowChecks   on|off           Turns the code generation for over- or
6805                                  underflow checks on or off.
6806nilChecks        on|off           Turns the code generation for nil pointer
6807                                  checks on or off.
6808assertions       on|off           Turns the code generation for assertions
6809                                  on or off.
6810warnings         on|off           Turns the warning messages of the compiler
6811                                  on or off.
6812hints            on|off           Turns the hint messages of the compiler
6813                                  on or off.
6814optimization     none|speed|size  Optimize the code for speed or size, or
6815                                  disable optimization.
6816patterns         on|off           Turns the term rewriting templates/macros
6817                                  on or off.
6818callconv         cdecl|...        Specifies the default calling convention for
6819                                  all procedures (and procedure types) that
6820                                  follow.
6821===============  ===============  ============================================
6822
6823Example:
6824
6825.. code-block:: nim
6826  {.checks: off, optimization: speed.}
6827  # compile without runtime checks and optimize for speed
6828
6829
6830push and pop pragmas
6831--------------------
6832The `push/pop`:idx: pragmas are very similar to the option directive,
6833but are used to override the settings temporarily. Example:
6834
6835.. code-block:: nim
6836  {.push checks: off.}
6837  # compile this section without runtime checks as it is
6838  # speed critical
6839  # ... some code ...
6840  {.pop.} # restore old settings
6841
6842`push/pop`:idx: can switch on/off some standard library pragmas, example:
6843
6844.. code-block:: nim
6845  {.push inline.}
6846  proc thisIsInlined(): int = 42
6847  func willBeInlined(): float = 42.0
6848  {.pop.}
6849  proc notInlined(): int = 9
6850
6851  {.push discardable, boundChecks: off, compileTime, noSideEffect, experimental.}
6852  template example(): string = "https://nim-lang.org"
6853  {.pop.}
6854
6855  {.push deprecated, hint[LineTooLong]: off, used, stackTrace: off.}
6856  proc sample(): bool = true
6857  {.pop.}
6858
6859For third party pragmas, it depends on its implementation but uses the same syntax.
6860
6861
6862register pragma
6863---------------
6864The `register` pragma is for variables only. It declares the variable as
6865`register`, giving the compiler a hint that the variable should be placed
6866in a hardware register for faster access. C compilers usually ignore this
6867though and for good reasons: Often they do a better job without it anyway.
6868
6869However, in highly specific cases (a dispatch loop of a bytecode interpreter
6870for example) it may provide benefits.
6871
6872
6873global pragma
6874-------------
6875The `global` pragma can be applied to a variable within a proc to instruct
6876the compiler to store it in a global location and initialize it once at program
6877startup.
6878
6879.. code-block:: nim
6880  proc isHexNumber(s: string): bool =
6881    var pattern {.global.} = re"[0-9a-fA-F]+"
6882    result = s.match(pattern)
6883
6884When used within a generic proc, a separate unique global variable will be
6885created for each instantiation of the proc. The order of initialization of
6886the created global variables within a module is not defined, but all of them
6887will be initialized after any top-level variables in their originating module
6888and before any variable in a module that imports it.
6889
6890Disabling certain messages
6891--------------------------
6892Nim generates some warnings and hints ("line too long") that may annoy the
6893user. A mechanism for disabling certain messages is provided: Each hint
6894and warning message contains a symbol in brackets. This is the message's
6895identifier that can be used to enable or disable it:
6896
6897.. code-block:: Nim
6898  {.hint[LineTooLong]: off.} # turn off the hint about too long lines
6899
6900This is often better than disabling all warnings at once.
6901
6902
6903used pragma
6904-----------
6905
6906Nim produces a warning for symbols that are not exported and not used either.
6907The `used` pragma can be attached to a symbol to suppress this warning. This
6908is particularly useful when the symbol was generated by a macro:
6909
6910.. code-block:: nim
6911  template implementArithOps(T) =
6912    proc echoAdd(a, b: T) {.used.} =
6913      echo a + b
6914    proc echoSub(a, b: T) {.used.} =
6915      echo a - b
6916
6917  # no warning produced for the unused 'echoSub'
6918  implementArithOps(int)
6919  echoAdd 3, 5
6920
6921`used` can also be used as a top-level statement to mark a module as "used".
6922This prevents the "Unused import" warning:
6923
6924.. code-block:: nim
6925
6926  # module: debughelper.nim
6927  when defined(nimHasUsed):
6928    # 'import debughelper' is so useful for debugging
6929    # that Nim shouldn't produce a warning for that import,
6930    # even if currently unused:
6931    {.used.}
6932
6933
6934experimental pragma
6935-------------------
6936
6937The `experimental` pragma enables experimental language features. Depending
6938on the concrete feature, this means that the feature is either considered
6939too unstable for an otherwise stable release or that the future of the feature
6940is uncertain (it may be removed at any time).
6941
6942Example:
6943
6944.. code-block:: nim
6945  import std/threadpool
6946  {.experimental: "parallel".}
6947
6948  proc threadedEcho(s: string, i: int) =
6949    echo(s, " ", $i)
6950
6951  proc useParallel() =
6952    parallel:
6953      for i in 0..4:
6954        spawn threadedEcho("echo in parallel", i)
6955
6956  useParallel()
6957
6958
6959As a top-level statement, the experimental pragma enables a feature for the
6960rest of the module it's enabled in. This is problematic for macro and generic
6961instantiations that cross a module scope. Currently, these usages have to be
6962put into a `.push/pop` environment:
6963
6964.. code-block:: nim
6965
6966  # client.nim
6967  proc useParallel*[T](unused: T) =
6968    # use a generic T here to show the problem.
6969    {.push experimental: "parallel".}
6970    parallel:
6971      for i in 0..4:
6972        echo "echo in parallel"
6973
6974    {.pop.}
6975
6976
6977.. code-block:: nim
6978
6979  import client
6980  useParallel(1)
6981
6982
6983Implementation Specific Pragmas
6984===============================
6985
6986This section describes additional pragmas that the current Nim implementation
6987supports but which should not be seen as part of the language specification.
6988
6989Bitsize pragma
6990--------------
6991
6992The `bitsize` pragma is for object field members. It declares the field as
6993a bitfield in C/C++.
6994
6995.. code-block:: Nim
6996  type
6997    mybitfield = object
6998      flag {.bitsize:1.}: cuint
6999
7000generates:
7001
7002.. code-block:: C
7003  struct mybitfield {
7004    unsigned int flag:1;
7005  };
7006
7007
7008Align pragma
7009------------
7010
7011The `align`:idx: pragma is for variables and object field members. It
7012modifies the alignment requirement of the entity being declared. The
7013argument must be a constant power of 2. Valid non-zero
7014alignments that are weaker than other align pragmas on the same
7015declaration are ignored. Alignments that are weaker than the
7016alignment requirement of the type are ignored.
7017
7018.. code-block:: Nim
7019
7020   type
7021     sseType = object
7022       sseData {.align(16).}: array[4, float32]
7023
7024     # every object will be aligned to 128-byte boundary
7025     Data = object
7026       x: char
7027       cacheline {.align(128).}: array[128, char] # over-aligned array of char,
7028
7029   proc main() =
7030     echo "sizeof(Data) = ", sizeof(Data), " (1 byte + 127 bytes padding + 128-byte array)"
7031     # output: sizeof(Data) = 256 (1 byte + 127 bytes padding + 128-byte array)
7032     echo "alignment of sseType is ", alignof(sseType)
7033     # output: alignment of sseType is 16
7034     var d {.align(2048).}: Data # this instance of data is aligned even stricter
7035
7036   main()
7037
7038This pragma has no effect on the JS backend.
7039
7040
7041Volatile pragma
7042---------------
7043The `volatile` pragma is for variables only. It declares the variable as
7044`volatile`:c:, whatever that means in C/C++ (its semantics are not well defined
7045in C/C++).
7046
7047**Note**: This pragma will not exist for the LLVM backend.
7048
7049
7050nodecl pragma
7051-------------
7052The `nodecl` pragma can be applied to almost any symbol (variable, proc,
7053type, etc.) and is sometimes useful for interoperability with C:
7054It tells Nim that it should not generate a declaration for the symbol in
7055the C code. For example:
7056
7057.. code-block:: Nim
7058  var
7059    EACCES {.importc, nodecl.}: cint # pretend EACCES was a variable, as
7060                                     # Nim does not know its value
7061
7062However, the `header` pragma is often the better alternative.
7063
7064**Note**: This will not work for the LLVM backend.
7065
7066
7067Header pragma
7068-------------
7069The `header` pragma is very similar to the `nodecl` pragma: It can be
7070applied to almost any symbol and specifies that it should not be declared
7071and instead, the generated code should contain an `#include`:c:\:
7072
7073.. code-block:: Nim
7074  type
7075    PFile {.importc: "FILE*", header: "<stdio.h>".} = distinct pointer
7076      # import C's FILE* type; Nim will treat it as a new pointer type
7077
7078The `header` pragma always expects a string constant. The string constant
7079contains the header file: As usual for C, a system header file is enclosed
7080in angle brackets: `<>`:c:. If no angle brackets are given, Nim
7081encloses the header file in `""`:c: in the generated C code.
7082
7083**Note**: This will not work for the LLVM backend.
7084
7085
7086IncompleteStruct pragma
7087-----------------------
7088The `incompleteStruct` pragma tells the compiler to not use the
7089underlying C `struct`:c: in a `sizeof` expression:
7090
7091.. code-block:: Nim
7092  type
7093    DIR* {.importc: "DIR", header: "<dirent.h>",
7094           pure, incompleteStruct.} = object
7095
7096
7097Compile pragma
7098--------------
7099The `compile` pragma can be used to compile and link a C/C++ source file
7100with the project:
7101
7102.. code-block:: Nim
7103  {.compile: "myfile.cpp".}
7104
7105**Note**: Nim computes a SHA1 checksum and only recompiles the file if it
7106has changed. One can use the `-f`:option: command-line option to force
7107the recompilation of the file.
7108
7109Since 1.4 the `compile` pragma is also available with this syntax:
7110
7111.. code-block:: Nim
7112  {.compile("myfile.cpp", "--custom flags here").}
7113
7114As can be seen in the example, this new variant allows for custom flags
7115that are passed to the C compiler when the file is recompiled.
7116
7117
7118Link pragma
7119-----------
7120The `link` pragma can be used to link an additional file with the project:
7121
7122.. code-block:: Nim
7123  {.link: "myfile.o".}
7124
7125
7126PassC pragma
7127------------
7128The `passc` pragma can be used to pass additional parameters to the C
7129compiler like one would using the command-line switch `--passc`:option:\:
7130
7131.. code-block:: Nim
7132  {.passc: "-Wall -Werror".}
7133
7134Note that one can use `gorge` from the `system module <system.html>`_ to
7135embed parameters from an external command that will be executed
7136during semantic analysis:
7137
7138.. code-block:: Nim
7139  {.passc: gorge("pkg-config --cflags sdl").}
7140
7141
7142LocalPassc pragma
7143-----------------
7144The `localPassc` pragma can be used to pass additional parameters to the C
7145compiler, but only for the C/C++ file that is produced from the Nim module
7146the pragma resides in:
7147
7148.. code-block:: Nim
7149  # Module A.nim
7150  # Produces: A.nim.cpp
7151  {.localPassc: "-Wall -Werror".} # Passed when compiling A.nim.cpp
7152
7153
7154PassL pragma
7155------------
7156The `passL` pragma can be used to pass additional parameters to the linker
7157like one would be using the command-line switch `--passL`:option:\:
7158
7159.. code-block:: Nim
7160  {.passL: "-lSDLmain -lSDL".}
7161
7162Note that one can use `gorge` from the `system module <system.html>`_ to
7163embed parameters from an external command that will be executed
7164during semantic analysis:
7165
7166.. code-block:: Nim
7167  {.passL: gorge("pkg-config --libs sdl").}
7168
7169
7170Emit pragma
7171-----------
7172The `emit` pragma can be used to directly affect the output of the
7173compiler's code generator. The code is then unportable to other code
7174generators/backends. Its usage is highly discouraged! However, it can be
7175extremely useful for interfacing with `C++`:idx: or `Objective C`:idx: code.
7176
7177Example:
7178
7179.. code-block:: Nim
7180  {.emit: """
7181  static int cvariable = 420;
7182  """.}
7183
7184  {.push stackTrace:off.}
7185  proc embedsC() =
7186    var nimVar = 89
7187    # access Nim symbols within an emit section outside of string literals:
7188    {.emit: ["""fprintf(stdout, "%d\n", cvariable + (int)""", nimVar, ");"].}
7189  {.pop.}
7190
7191  embedsC()
7192
7193``nimbase.h`` defines `NIM_EXTERNC`:c: C macro that can be used for
7194`extern "C"`:cpp: code to work with both `nim c`:cmd: and `nim cpp`:cmd:, e.g.:
7195
7196.. code-block:: Nim
7197  proc foobar() {.importc:"$1".}
7198  {.emit: """
7199  #include <stdio.h>
7200  NIM_EXTERNC
7201  void fun(){}
7202  """.}
7203
7204.. note:: For backward compatibility, if the argument to the `emit` statement
7205  is a single string literal, Nim symbols can be referred to via backticks.
7206  This usage is however deprecated.
7207
7208For a top-level emit statement, the section where in the generated C/C++ file
7209the code should be emitted can be influenced via the prefixes
7210`/*TYPESECTION*/`:c: or `/*VARSECTION*/`:c: or `/*INCLUDESECTION*/`:c:\:
7211
7212.. code-block:: Nim
7213  {.emit: """/*TYPESECTION*/
7214  struct Vector3 {
7215  public:
7216    Vector3(): x(5) {}
7217    Vector3(float x_): x(x_) {}
7218    float x;
7219  };
7220  """.}
7221
7222  type Vector3 {.importcpp: "Vector3", nodecl} = object
7223    x: cfloat
7224
7225  proc constructVector3(a: cfloat): Vector3 {.importcpp: "Vector3(@)", nodecl}
7226
7227
7228ImportCpp pragma
7229----------------
7230
7231**Note**: `c2nim <https://github.com/nim-lang/c2nim/blob/master/doc/c2nim.rst>`_ can parse a large subset of C++ and knows
7232about the `importcpp` pragma pattern language. It is not necessary
7233to know all the details described here.
7234
7235
7236Similar to the `importc pragma for C
7237<#foreign-function-interface-importc-pragma>`_, the
7238`importcpp` pragma can be used to import `C++`:idx: methods or C++ symbols
7239in general. The generated code then uses the C++ method calling
7240syntax: `obj->method(arg)`:cpp:. In combination with the `header` and `emit`
7241pragmas this allows *sloppy* interfacing with libraries written in C++:
7242
7243.. code-block:: Nim
7244  # Horrible example of how to interface with a C++ engine ... ;-)
7245
7246  {.link: "/usr/lib/libIrrlicht.so".}
7247
7248  {.emit: """
7249  using namespace irr;
7250  using namespace core;
7251  using namespace scene;
7252  using namespace video;
7253  using namespace io;
7254  using namespace gui;
7255  """.}
7256
7257  const
7258    irr = "<irrlicht/irrlicht.h>"
7259
7260  type
7261    IrrlichtDeviceObj {.header: irr,
7262                        importcpp: "IrrlichtDevice".} = object
7263    IrrlichtDevice = ptr IrrlichtDeviceObj
7264
7265  proc createDevice(): IrrlichtDevice {.
7266    header: irr, importcpp: "createDevice(@)".}
7267  proc run(device: IrrlichtDevice): bool {.
7268    header: irr, importcpp: "#.run(@)".}
7269
7270The compiler needs to be told to generate C++ (command `cpp`:option:) for
7271this to work. The conditional symbol `cpp` is defined when the compiler
7272emits C++ code.
7273
7274Namespaces
7275~~~~~~~~~~
7276
7277The *sloppy interfacing* example uses `.emit` to produce `using namespace`:cpp:
7278declarations. It is usually much better to instead refer to the imported name
7279via the `namespace::identifier`:cpp: notation:
7280
7281.. code-block:: nim
7282  type
7283    IrrlichtDeviceObj {.header: irr,
7284                        importcpp: "irr::IrrlichtDevice".} = object
7285
7286
7287Importcpp for enums
7288~~~~~~~~~~~~~~~~~~~
7289
7290When `importcpp` is applied to an enum type the numerical enum values are
7291annotated with the C++ enum type, like in this example:
7292`((TheCppEnum)(3))`:cpp:.
7293(This turned out to be the simplest way to implement it.)
7294
7295
7296Importcpp for procs
7297~~~~~~~~~~~~~~~~~~~
7298
7299Note that the `importcpp` variant for procs uses a somewhat cryptic pattern
7300language for maximum flexibility:
7301
7302- A hash ``#`` symbol is replaced by the first or next argument.
7303- A dot following the hash ``#.`` indicates that the call should use C++'s dot
7304  or arrow notation.
7305- An at symbol ``@`` is replaced by the remaining arguments,
7306  separated by commas.
7307
7308For example:
7309
7310.. code-block:: nim
7311  proc cppMethod(this: CppObj, a, b, c: cint) {.importcpp: "#.CppMethod(@)".}
7312  var x: ptr CppObj
7313  cppMethod(x[], 1, 2, 3)
7314
7315Produces:
7316
7317.. code-block:: C
7318  x->CppMethod(1, 2, 3)
7319
7320As a special rule to keep backward compatibility with older versions of the
7321`importcpp` pragma, if there is no special pattern
7322character (any of ``# ' @``) at all, C++'s
7323dot or arrow notation is assumed, so the above example can also be written as:
7324
7325.. code-block:: nim
7326  proc cppMethod(this: CppObj, a, b, c: cint) {.importcpp: "CppMethod".}
7327
7328Note that the pattern language naturally also covers C++'s operator overloading
7329capabilities:
7330
7331.. code-block:: nim
7332  proc vectorAddition(a, b: Vec3): Vec3 {.importcpp: "# + #".}
7333  proc dictLookup(a: Dict, k: Key): Value {.importcpp: "#[#]".}
7334
7335
7336- An apostrophe ``'`` followed by an integer ``i`` in the range 0..9
7337  is replaced by the i'th parameter *type*. The 0th position is the result
7338  type. This can be used to pass types to C++ function templates. Between
7339  the ``'`` and the digit, an asterisk can be used to get to the base type
7340  of the type. (So it "takes away a star" from the type; `T*`:c: becomes `T`.)
7341  Two stars can be used to get to the element type of the element type etc.
7342
7343For example:
7344
7345.. code-block:: nim
7346
7347  type Input {.importcpp: "System::Input".} = object
7348  proc getSubsystem*[T](): ptr T {.importcpp: "SystemManager::getSubsystem<'*0>()", nodecl.}
7349
7350  let x: ptr Input = getSubsystem[Input]()
7351
7352Produces:
7353
7354.. code-block:: C
7355  x = SystemManager::getSubsystem<System::Input>()
7356
7357
7358- ``#@`` is a special case to support a `cnew` operation. It is required so
7359  that the call expression is inlined directly, without going through a
7360  temporary location. This is only required to circumvent a limitation of the
7361  current code generator.
7362
7363For example C++'s `new`:cpp: operator can be "imported" like this:
7364
7365.. code-block:: nim
7366  proc cnew*[T](x: T): ptr T {.importcpp: "(new '*0#@)", nodecl.}
7367
7368  # constructor of 'Foo':
7369  proc constructFoo(a, b: cint): Foo {.importcpp: "Foo(@)".}
7370
7371  let x = cnew constructFoo(3, 4)
7372
7373Produces:
7374
7375.. code-block:: C
7376  x = new Foo(3, 4)
7377
7378However, depending on the use case `new Foo`:cpp: can also be wrapped like this
7379instead:
7380
7381.. code-block:: nim
7382  proc newFoo(a, b: cint): ptr Foo {.importcpp: "new Foo(@)".}
7383
7384  let x = newFoo(3, 4)
7385
7386
7387Wrapping constructors
7388~~~~~~~~~~~~~~~~~~~~~
7389
7390Sometimes a C++ class has a private copy constructor and so code like
7391`Class c = Class(1,2);`:cpp: must not be generated but instead
7392`Class c(1,2);`:cpp:.
7393For this purpose the Nim proc that wraps a C++ constructor needs to be
7394annotated with the `constructor`:idx: pragma. This pragma also helps to generate
7395faster C++ code since construction then doesn't invoke the copy constructor:
7396
7397.. code-block:: nim
7398  # a better constructor of 'Foo':
7399  proc constructFoo(a, b: cint): Foo {.importcpp: "Foo(@)", constructor.}
7400
7401
7402Wrapping destructors
7403~~~~~~~~~~~~~~~~~~~~
7404
7405Since Nim generates C++ directly, any destructor is called implicitly by the
7406C++ compiler at the scope exits. This means that often one can get away with
7407not wrapping the destructor at all! However, when it needs to be invoked
7408explicitly, it needs to be wrapped. The pattern language provides
7409everything that is required:
7410
7411.. code-block:: nim
7412  proc destroyFoo(this: var Foo) {.importcpp: "#.~Foo()".}
7413
7414
7415Importcpp for objects
7416~~~~~~~~~~~~~~~~~~~~~
7417
7418Generic `importcpp`'ed objects are mapped to C++ templates. This means that
7419one can import C++'s templates rather easily without the need for a pattern
7420language for object types:
7421
7422.. code-block:: nim
7423    :test: "nim cpp $1"
7424
7425  type
7426    StdMap[K, V] {.importcpp: "std::map", header: "<map>".} = object
7427  proc `[]=`[K, V](this: var StdMap[K, V]; key: K; val: V) {.
7428    importcpp: "#[#] = #", header: "<map>".}
7429
7430  var x: StdMap[cint, cdouble]
7431  x[6] = 91.4
7432
7433
7434Produces:
7435
7436.. code-block:: C
7437  std::map<int, double> x;
7438  x[6] = 91.4;
7439
7440
7441- If more precise control is needed, the apostrophe `'` can be used in the
7442  supplied pattern to denote the concrete type parameters of the generic type.
7443  See the usage of the apostrophe operator in proc patterns for more details.
7444
7445  .. code-block:: nim
7446
7447    type
7448      VectorIterator {.importcpp: "std::vector<'0>::iterator".} [T] = object
7449
7450    var x: VectorIterator[cint]
7451
7452
7453  Produces:
7454
7455  .. code-block:: C
7456
7457    std::vector<int>::iterator x;
7458
7459
7460ImportJs pragma
7461---------------
7462
7463Similar to the `importcpp pragma for C++ <#implementation-specific-pragmas-importcpp-pragma>`_,
7464the `importjs` pragma can be used to import Javascript methods or
7465symbols in general. The generated code then uses the Javascript method
7466calling syntax: ``obj.method(arg)``.
7467
7468
7469ImportObjC pragma
7470-----------------
7471Similar to the `importc pragma for C
7472<#foreign-function-interface-importc-pragma>`_, the `importobjc` pragma can
7473be used to import `Objective C`:idx: methods. The generated code then uses the
7474Objective C method calling syntax: ``[obj method param1: arg]``.
7475In addition with the `header` and `emit` pragmas this
7476allows *sloppy* interfacing with libraries written in Objective C:
7477
7478.. code-block:: Nim
7479  # horrible example of how to interface with GNUStep ...
7480
7481  {.passL: "-lobjc".}
7482  {.emit: """
7483  #include <objc/Object.h>
7484  @interface Greeter:Object
7485  {
7486  }
7487
7488  - (void)greet:(long)x y:(long)dummy;
7489  @end
7490
7491  #include <stdio.h>
7492  @implementation Greeter
7493
7494  - (void)greet:(long)x y:(long)dummy
7495  {
7496    printf("Hello, World!\n");
7497  }
7498  @end
7499
7500  #include <stdlib.h>
7501  """.}
7502
7503  type
7504    Id {.importc: "id", header: "<objc/Object.h>", final.} = distinct int
7505
7506  proc newGreeter: Id {.importobjc: "Greeter new", nodecl.}
7507  proc greet(self: Id, x, y: int) {.importobjc: "greet", nodecl.}
7508  proc free(self: Id) {.importobjc: "free", nodecl.}
7509
7510  var g = newGreeter()
7511  g.greet(12, 34)
7512  g.free()
7513
7514The compiler needs to be told to generate Objective C (command `objc`:option:) for
7515this to work. The conditional symbol ``objc`` is defined when the compiler
7516emits Objective C code.
7517
7518
7519CodegenDecl pragma
7520------------------
7521
7522The `codegenDecl` pragma can be used to directly influence Nim's code
7523generator. It receives a format string that determines how the variable
7524or proc is declared in the generated code.
7525
7526For variables, $1 in the format string represents the type of the variable
7527and $2 is the name of the variable.
7528
7529The following Nim code:
7530
7531.. code-block:: nim
7532  var
7533    a {.codegenDecl: "$# progmem $#".}: int
7534
7535will generate this C code:
7536
7537.. code-block:: c
7538  int progmem a
7539
7540For procedures, $1 is the return type of the procedure, $2 is the name of
7541the procedure, and $3 is the parameter list.
7542
7543The following nim code:
7544
7545.. code-block:: nim
7546  proc myinterrupt() {.codegenDecl: "__interrupt $# $#$#".} =
7547    echo "realistic interrupt handler"
7548
7549will generate this code:
7550
7551.. code-block:: c
7552  __interrupt void myinterrupt()
7553
7554
7555`cppNonPod` pragma
7556------------------
7557
7558The `.cppNonPod` pragma should be used for non-POD `importcpp` types so that they
7559work properly (in particular regarding constructor and destructor) for
7560`.threadvar` variables. This requires `--tlsEmulation:off`:option:.
7561
7562.. code-block:: nim
7563  type Foo {.cppNonPod, importcpp, header: "funs.h".} = object
7564    x: cint
7565  proc main()=
7566    var a {.threadvar.}: Foo
7567
7568
7569compile-time define pragmas
7570---------------------------
7571
7572The pragmas listed here can be used to optionally accept values from
7573the `-d/--define`:option: option at compile time.
7574
7575The implementation currently provides the following possible options (various
7576others may be added later).
7577
7578=================  ============================================
7579pragma             description
7580=================  ============================================
7581`intdefine`:idx:   Reads in a build-time define as an integer
7582`strdefine`:idx:   Reads in a build-time define as a string
7583`booldefine`:idx:  Reads in a build-time define as a bool
7584=================  ============================================
7585
7586.. code-block:: nim
7587   const FooBar {.intdefine.}: int = 5
7588   echo FooBar
7589
7590.. code:: cmd
7591   nim c -d:FooBar=42 foobar.nim
7592
7593In the above example, providing the `-d`:option: flag causes the symbol
7594`FooBar` to be overwritten at compile-time, printing out 42. If the
7595`-d:FooBar=42`:option: were to be omitted, the default value of 5 would be
7596used. To see if a value was provided, `defined(FooBar)` can be used.
7597
7598The syntax `-d:flag`:option: is actually just a shortcut for
7599`-d:flag=true`:option:.
7600
7601User-defined pragmas
7602====================
7603
7604
7605pragma pragma
7606-------------
7607
7608The `pragma` pragma can be used to declare user-defined pragmas. This is
7609useful because Nim's templates and macros do not affect pragmas.
7610User-defined pragmas are in a different module-wide scope than all other symbols.
7611They cannot be imported from a module.
7612
7613Example:
7614
7615.. code-block:: nim
7616  when appType == "lib":
7617    {.pragma: rtl, exportc, dynlib, cdecl.}
7618  else:
7619    {.pragma: rtl, importc, dynlib: "client.dll", cdecl.}
7620
7621  proc p*(a, b: int): int {.rtl.} =
7622    result = a+b
7623
7624In the example, a new pragma named `rtl` is introduced that either imports
7625a symbol from a dynamic library or exports the symbol for dynamic library
7626generation.
7627
7628
7629Custom annotations
7630------------------
7631It is possible to define custom typed pragmas. Custom pragmas do not affect
7632code generation directly, but their presence can be detected by macros.
7633Custom pragmas are defined using templates annotated with pragma `pragma`:
7634
7635.. code-block:: nim
7636  template dbTable(name: string, table_space: string = "") {.pragma.}
7637  template dbKey(name: string = "", primary_key: bool = false) {.pragma.}
7638  template dbForeignKey(t: typedesc) {.pragma.}
7639  template dbIgnore {.pragma.}
7640
7641
7642Consider this stylized example of a possible Object Relation Mapping (ORM)
7643implementation:
7644
7645.. code-block:: nim
7646  const tblspace {.strdefine.} = "dev" # switch for dev, test and prod environments
7647
7648  type
7649    User {.dbTable("users", tblspace).} = object
7650      id {.dbKey(primary_key = true).}: int
7651      name {.dbKey"full_name".}: string
7652      is_cached {.dbIgnore.}: bool
7653      age: int
7654
7655    UserProfile {.dbTable("profiles", tblspace).} = object
7656      id {.dbKey(primary_key = true).}: int
7657      user_id {.dbForeignKey: User.}: int
7658      read_access: bool
7659      write_access: bool
7660      admin_acess: bool
7661
7662In this example, custom pragmas are used to describe how Nim objects are
7663mapped to the schema of the relational database. Custom pragmas can have
7664zero or more arguments. In order to pass multiple arguments use one of
7665template call syntaxes. All arguments are typed and follow standard
7666overload resolution rules for templates. Therefore, it is possible to have
7667default values for arguments, pass by name, varargs, etc.
7668
7669Custom pragmas can be used in all locations where ordinary pragmas can be
7670specified. It is possible to annotate procs, templates, type and variable
7671definitions, statements, etc.
7672
7673The macros module includes helpers which can be used to simplify custom pragma
7674access `hasCustomPragma`, `getCustomPragmaVal`. Please consult the
7675`macros <macros.html>`_ module documentation for details. These macros are not
7676magic, everything they do can also be achieved by walking the AST of the object
7677representation.
7678
7679More examples with custom pragmas:
7680
7681- Better serialization/deserialization control:
7682
7683  .. code-block:: nim
7684    type MyObj = object
7685      a {.dontSerialize.}: int
7686      b {.defaultDeserialize: 5.}: int
7687      c {.serializationKey: "_c".}: string
7688
7689- Adopting type for gui inspector in a game engine:
7690
7691  .. code-block:: nim
7692    type MyComponent = object
7693      position {.editable, animatable.}: Vector3
7694      alpha {.editRange: [0.0..1.0], animatable.}: float32
7695
7696
7697Macro pragmas
7698-------------
7699
7700All macros and templates can also be used as pragmas. They can be attached
7701to routines (procs, iterators, etc), type names, or type expressions. The
7702compiler will perform the following simple syntactic transformations:
7703
7704.. code-block:: nim
7705  template command(name: string, def: untyped) = discard
7706
7707  proc p() {.command("print").} = discard
7708
7709This is translated to:
7710
7711.. code-block:: nim
7712  command("print"):
7713    proc p() = discard
7714
7715------
7716
7717.. code-block:: nim
7718  type
7719    AsyncEventHandler = proc (x: Event) {.async.}
7720
7721This is translated to:
7722
7723.. code-block:: nim
7724  type
7725    AsyncEventHandler = async(proc (x: Event))
7726
7727------
7728
7729.. code-block:: nim
7730  type
7731    MyObject {.schema: "schema.protobuf".} = object
7732
7733This is translated to a call to the `schema` macro with a `nnkTypeDef`
7734AST node capturing both the left-hand side and right-hand side of the
7735definition. The macro can return a potentially modified `nnkTypeDef` tree
7736which will replace the original row in the type section.
7737
7738When multiple macro pragmas are applied to the same definition, the
7739compiler will apply them consequently from left to right. Each macro
7740will receive as input the output of the previous one.
7741
7742
7743
7744Foreign function interface
7745==========================
7746
7747Nim's `FFI`:idx: (foreign function interface) is extensive and only the
7748parts that scale to other future backends (like the LLVM/JavaScript backends)
7749are documented here.
7750
7751
7752Importc pragma
7753--------------
7754The `importc` pragma provides a means to import a proc or a variable
7755from C. The optional argument is a string containing the C identifier. If
7756the argument is missing, the C name is the Nim identifier *exactly as
7757spelled*:
7758
7759.. code-block::
7760  proc printf(formatstr: cstring) {.header: "<stdio.h>", importc: "printf", varargs.}
7761
7762When `importc` is applied to a `let` statement it can omit its value which
7763will then be expected to come from C. This can be used to import a C `const`:c:\:
7764
7765.. code-block::
7766  {.emit: "const int cconst = 42;".}
7767
7768  let cconst {.importc, nodecl.}: cint
7769
7770  assert cconst == 42
7771
7772Note that this pragma has been abused in the past to also work in the
7773JS backend for JS objects and functions. Other backends do provide
7774the same feature under the same name. Also, when the target language
7775is not set to C, other pragmas are available:
7776
7777 * `importcpp <manual.html#implementation-specific-pragmas-importcpp-pragma>`_
7778 * `importobjc <manual.html#implementation-specific-pragmas-importobjc-pragma>`_
7779 * `importjs <manual.html#implementation-specific-pragmas-importjs-pragma>`_
7780
7781.. code-block:: Nim
7782  proc p(s: cstring) {.importc: "prefix$1".}
7783
7784In the example, the external name of `p` is set to `prefixp`. Only ``$1``
7785is available and a literal dollar sign must be written as ``$$``.
7786
7787
7788Exportc pragma
7789--------------
7790The `exportc` pragma provides a means to export a type, a variable, or a
7791procedure to C. Enums and constants can't be exported. The optional argument
7792is a string containing the C identifier. If the argument is missing, the C
7793name is the Nim identifier *exactly as spelled*:
7794
7795.. code-block:: Nim
7796  proc callme(formatstr: cstring) {.exportc: "callMe", varargs.}
7797
7798Note that this pragma is somewhat of a misnomer: Other backends do provide
7799the same feature under the same name.
7800
7801The string literal passed to `exportc` can be a format string:
7802
7803.. code-block:: Nim
7804  proc p(s: string) {.exportc: "prefix$1".} =
7805    echo s
7806
7807In the example, the external name of `p` is set to `prefixp`. Only ``$1``
7808is available and a literal dollar sign must be written as ``$$``.
7809
7810If the symbol should also be exported to a dynamic library, the `dynlib`
7811pragma should be used in addition to the `exportc` pragma. See
7812`Dynlib pragma for export <#foreign-function-interface-dynlib-pragma-for-export>`_.
7813
7814
7815Extern pragma
7816-------------
7817Like `exportc` or `importc`, the `extern` pragma affects name
7818mangling. The string literal passed to `extern` can be a format string:
7819
7820.. code-block:: Nim
7821  proc p(s: string) {.extern: "prefix$1".} =
7822    echo s
7823
7824In the example, the external name of `p` is set to `prefixp`. Only ``$1``
7825is available and a literal dollar sign must be written as ``$$``.
7826
7827
7828Bycopy pragma
7829-------------
7830
7831The `bycopy` pragma can be applied to an object or tuple type and
7832instructs the compiler to pass the type by value to procs:
7833
7834.. code-block:: nim
7835  type
7836    Vector {.bycopy.} = object
7837      x, y, z: float
7838
7839
7840Byref pragma
7841------------
7842
7843The `byref` pragma can be applied to an object or tuple type and instructs
7844the compiler to pass the type by reference (hidden pointer) to procs.
7845
7846
7847Varargs pragma
7848--------------
7849The `varargs` pragma can be applied to procedures only (and procedure
7850types). It tells Nim that the proc can take a variable number of parameters
7851after the last specified parameter. Nim string values will be converted to C
7852strings automatically:
7853
7854.. code-block:: Nim
7855  proc printf(formatstr: cstring) {.nodecl, varargs.}
7856
7857  printf("hallo %s", "world") # "world" will be passed as C string
7858
7859
7860Union pragma
7861------------
7862The `union` pragma can be applied to any `object` type. It means all
7863of the object's fields are overlaid in memory. This produces a `union`:c:
7864instead of a `struct`:c: in the generated C/C++ code. The object declaration
7865then must not use inheritance or any GC'ed memory but this is currently not
7866checked.
7867
7868**Future directions**: GC'ed memory should be allowed in unions and the GC
7869should scan unions conservatively.
7870
7871
7872Packed pragma
7873-------------
7874The `packed` pragma can be applied to any `object` type. It ensures
7875that the fields of an object are packed back-to-back in memory. It is useful
7876to store packets or messages from/to network or hardware drivers, and for
7877interoperability with C. Combining packed pragma with inheritance is not
7878defined, and it should not be used with GC'ed memory (ref's).
7879
7880**Future directions**: Using GC'ed memory in packed pragma will result in
7881a static error. Usage with inheritance should be defined and documented.
7882
7883
7884Dynlib pragma for import
7885------------------------
7886With the `dynlib` pragma, a procedure or a variable can be imported from
7887a dynamic library (``.dll`` files for Windows, ``lib*.so`` files for UNIX).
7888The non-optional argument has to be the name of the dynamic library:
7889
7890.. code-block:: Nim
7891  proc gtk_image_new(): PGtkWidget
7892    {.cdecl, dynlib: "libgtk-x11-2.0.so", importc.}
7893
7894In general, importing a dynamic library does not require any special linker
7895options or linking with import libraries. This also implies that no *devel*
7896packages need to be installed.
7897
7898The `dynlib` import mechanism supports a versioning scheme:
7899
7900.. code-block:: nim
7901  proc Tcl_Eval(interp: pTcl_Interp, script: cstring): int {.cdecl,
7902    importc, dynlib: "libtcl(|8.5|8.4|8.3).so.(1|0)".}
7903
7904At runtime, the dynamic library is searched for (in this order)::
7905
7906  libtcl.so.1
7907  libtcl.so.0
7908  libtcl8.5.so.1
7909  libtcl8.5.so.0
7910  libtcl8.4.so.1
7911  libtcl8.4.so.0
7912  libtcl8.3.so.1
7913  libtcl8.3.so.0
7914
7915The `dynlib` pragma supports not only constant strings as an argument but also
7916string expressions in general:
7917
7918.. code-block:: nim
7919  import std/os
7920
7921  proc getDllName: string =
7922    result = "mylib.dll"
7923    if fileExists(result): return
7924    result = "mylib2.dll"
7925    if fileExists(result): return
7926    quit("could not load dynamic library")
7927
7928  proc myImport(s: cstring) {.cdecl, importc, dynlib: getDllName().}
7929
7930**Note**: Patterns like ``libtcl(|8.5|8.4).so`` are only supported in constant
7931strings, because they are precompiled.
7932
7933**Note**: Passing variables to the `dynlib` pragma will fail at runtime
7934because of order of initialization problems.
7935
7936**Note**: A `dynlib` import can be overridden with
7937the `--dynlibOverride:name`:option: command-line option. The
7938`Compiler User Guide <nimc.html>`_ contains further information.
7939
7940
7941Dynlib pragma for export
7942------------------------
7943
7944With the `dynlib` pragma, a procedure can also be exported to
7945a dynamic library. The pragma then has no argument and has to be used in
7946conjunction with the `exportc` pragma:
7947
7948.. code-block:: Nim
7949  proc exportme(): int {.cdecl, exportc, dynlib.}
7950
7951This is only useful if the program is compiled as a dynamic library via the
7952`--app:lib`:option: command-line option.
7953
7954
7955
7956Threads
7957=======
7958
7959To enable thread support the `--threads:on`:option: command-line switch needs to
7960be used. The system_ module then contains several threading primitives.
7961See the `channels <channels_builtin.html>`_ modules
7962for the low-level thread API. There are also high-level parallelism constructs
7963available. See `spawn <manual_experimental.html#parallel-amp-spawn>`_ for
7964further details.
7965
7966Nim's memory model for threads is quite different than that of other common
7967programming languages (C, Pascal, Java): Each thread has its own (garbage
7968collected) heap, and sharing of memory is restricted to global variables. This
7969helps to prevent race conditions. GC efficiency is improved quite a lot,
7970because the GC never has to stop other threads and see what they reference.
7971
7972The only way to create a thread is via `spawn` or
7973`createThread`. The invoked proc must not use `var` parameters nor must
7974any of its parameters contain a `ref` or `closure` type. This enforces
7975the *no heap sharing restriction*.
7976
7977Thread pragma
7978-------------
7979
7980A proc that is executed as a new thread of execution should be marked by the
7981`thread` pragma for reasons of readability. The compiler checks for
7982violations of the `no heap sharing restriction`:idx:\: This restriction implies
7983that it is invalid to construct a data structure that consists of memory
7984allocated from different (thread-local) heaps.
7985
7986A thread proc is passed to `createThread` or `spawn` and invoked
7987indirectly; so the `thread` pragma implies `procvar`.
7988
7989
7990
7991Threadvar pragma
7992----------------
7993
7994A variable can be marked with the `threadvar` pragma, which makes it a
7995`thread-local`:idx: variable; Additionally, this implies all the effects
7996of the `global` pragma.
7997
7998.. code-block:: nim
7999  var checkpoints* {.threadvar.}: seq[string]
8000
8001Due to implementation restrictions, thread-local variables cannot be
8002initialized within the `var` section. (Every thread-local variable needs to
8003be replicated at thread creation.)
8004
8005
8006Threads and exceptions
8007----------------------
8008
8009The interaction between threads and exceptions is simple: A *handled* exception
8010in one thread cannot affect any other thread. However, an *unhandled* exception
8011in one thread terminates the whole *process*.
8012