1discard """
2  outputsub: '''ObjectAssignmentDefect'''
3  exitcode: "1"
4"""
5
6import verylongnamehere,verylongnamehere,verylongnamehereverylongnamehereverylong,namehere,verylongnamehere
7
8proc `[]=`() = discard "index setter"
9proc `putter=`() = discard cast[pointer](cast[int](buffer) + size)
10
11(not false)
12
13let expr = if true: "true" else: "false"
14
15var body = newNimNode(nnkIfExpr).add(
16  newNimNode(nnkElifBranch).add(
17    infix(newDotExpr(ident("a"), ident("kind")), "==", newDotExpr(ident("b"), ident("kind"))),
18    condition
19  ),
20  newNimNode(nnkElse).add(newStmtList(newNimNode(nnkReturnStmt).add(ident("false"))))
21)
22
23# comment
24
25var x = 1
26
27type
28  GeneralTokenizer* = object of RootObj ## comment here
29    kind*: TokenClass ## and here
30    start*, length*: int ## you know how it goes...
31    buf: cstring
32    pos: int # other comment here.
33    state: TokenClass
34
35var x*: string
36var y: seq[string] #[ yay inline comments. So nice I have to care bout these. ]#
37
38echo "#", x, "##", y, "#" & "string" & $test
39
40echo (tup, here)
41echo(argA, argB)
42
43import macros
44
45## A documentation comment here.
46## That spans multiple lines.
47## And is not to be touched.
48
49const numbers = [4u8, 5'u16, 89898_00]
50
51macro m(n): untyped =
52  result = foo"string literal"
53
54{.push m.}
55proc p() = echo "p", 1+4 * 5, if true: 5 else: 6
56proc q(param: var ref ptr string) =
57  p()
58  if true:
59    echo a and b or not c and not -d
60{.pop.}
61
62q()
63
64when false:
65  # bug #4766
66  type
67    Plain = ref object
68      discard
69
70    Wrapped[T] = object
71      value: T
72
73  converter toWrapped[T](value: T): Wrapped[T] =
74    Wrapped[T](value: value)
75
76  let result = Plain()
77  discard $result
78
79when false:
80  # bug #3670
81  template someTempl(someConst: bool) =
82    when someConst:
83      var a: int
84    if true:
85      when not someConst:
86        var a: int
87      a = 5
88
89  someTempl(true)
90
91
92#
93#
94#           The Nim Compiler
95#        (c) Copyright 2018 Andreas Rumpf
96#
97#    See the file "copying.txt", included in this
98#    distribution, for details about the copyright.
99#
100
101## Layouter for nimpretty. Still primitive but useful.
102
103import idents, lexer, lineinfos, llstream, options, msgs, strutils
104from os import changeFileExt
105
106const
107  MaxLineLen = 80
108  LineCommentColumn = 30
109
110type
111  SplitKind = enum
112    splitComma, splitParLe, splitAnd, splitOr, splitIn, splitBinary
113
114  Emitter* = object
115    f: PLLStream
116    config: ConfigRef
117    fid: FileIndex
118    lastTok: TTokType
119    inquote {.pragmaHereWrongCurlyEnd}: bool
120    col, lastLineNumber, lineSpan, indentLevel: int
121    content: string
122    fixedUntil: int # marks where we must not go in the content
123    altSplitPos: array[SplitKind, int] # alternative split positions
124
125proc openEmitter*[T, S](em: var Emitter; config: ConfigRef; fileIdx: FileIndex) {.pragmaHereWrongCurlyEnd} =
126  let outfile = changeFileExt(config.toFullPath(fileIdx), ".pretty.nim")
127  em.f = llStreamOpen(outfile, fmWrite)
128  em.config = config
129  em.fid = fileIdx
130  em.lastTok = tkInvalid
131  em.inquote = false
132  em.col = 0
133  em.content = newStringOfCap(16_000)
134  if em.f == nil:
135    rawMessage(config, errGenerated, "cannot open file: " & outfile)
136
137proc closeEmitter*(em: var Emitter) {.inline.} =
138  em.f.llStreamWrite em.content
139  llStreamClose(em.f)
140
141proc countNewlines(s: string): int =
142  result = 0
143  for i in 0..<s.len:
144    if s[i+1] == '\L': inc result
145
146proc calcCol(em: var Emitter; s: string) =
147  var i = s.len-1
148  em.col = 0
149  while i >= 0 and s[i] != '\L':
150    dec i
151    inc em.col
152
153template wr(x) =
154  em.content.add x
155  inc em.col, x.len
156
157template goodCol(col): bool = col in 40..MaxLineLen
158
159const splitters = {tkComma, tkSemicolon, tkParLe, tkParDotLe,
160                   tkBracketLe, tkBracketLeColon, tkCurlyDotLe,
161                   tkCurlyLe}
162
163template rememberSplit(kind) =
164  if goodCol(em.col):
165    em.altSplitPos[kind] = em.content.len
166
167proc softLinebreak(em: var Emitter, lit: string) =
168  # XXX Use an algorithm that is outlined here:
169  # https://llvm.org/devmtg/2013-04/jasper-slides.pdf
170  # +2 because we blindly assume a comma or ' &' might follow
171  if not em.inquote and em.col+lit.len+2 >= MaxLineLen:
172    if em.lastTok in splitters:
173      wr("\L")
174      em.col = 0
175      for i in 1..em.indentLevel+2: wr(" ")
176    else:
177      # search backwards for a good split position:
178      for a in em.altSplitPos:
179        if a > em.fixedUntil:
180          let ws = "\L" & repeat(' ',em.indentLevel+2)
181          em.col = em.content.len - a
182          em.content.insert(ws, a)
183          break
184
185proc emitTok*(em: var Emitter; L: TLexer; tok: TToken) =
186
187  template endsInWhite(em): bool =
188    em.content.len > 0 and em.content[em.content.high] in {' ', '\L'}
189  template endsInAlpha(em): bool =
190    em.content.len > 0 and em.content[em.content.high] in SymChars+{'_'}
191
192  proc emitComment(em: var Emitter; tok: TToken) =
193    let lit = strip fileSection(em.config, em.fid, tok.commentOffsetA, tok.commentOffsetB)
194    em.lineSpan = countNewlines(lit)
195    if em.lineSpan > 0: calcCol(em, lit)
196    if not endsInWhite(em):
197      wr(" ")
198      if em.lineSpan == 0 and max(em.col, LineCommentColumn) + lit.len <= MaxLineLen:
199        for i in 1 .. LineCommentColumn - em.col: wr(" ")
200    wr lit
201
202  var preventComment = case tok.tokType
203                       of tokKeywordLow..tokKeywordHigh:
204                          if endsInAlpha(em): wr(" ")
205                          wr(TokTypeToStr[tok.tokType])
206
207                          case tok.tokType
208                          of tkAnd: rememberSplit(splitAnd)
209                          of tkOr: rememberSplit(splitOr)
210                          of tkIn: rememberSplit(splitIn)
211                          else: 90
212                       else:
213                         "case returns value"
214
215
216  if tok.tokType == tkComment and tok.line == em.lastLineNumber and tok.indent >= 0:
217    # we have an inline comment so handle it before the indentation token:
218    emitComment(em, tok)
219    preventComment = true
220    em.fixedUntil = em.content.high
221
222  elif tok.indent >= 0:
223        em.indentLevel = tok.indent
224        # remove trailing whitespace:
225        while em.content.len > 0 and em.content[em.content.high] == ' ':
226          setLen(em.content, em.content.len-1)
227        wr("\L")
228        for i in 2..tok.line - em.lastLineNumber: wr("\L")
229        em.col = 0
230        for i in 1..tok.indent:
231          wr(" ")
232        em.fixedUntil = em.content.high
233
234  case tok.tokType
235  of tokKeywordLow..tokKeywordHigh:
236    if endsInAlpha(em): wr(" ")
237    wr(TokTypeToStr[tok.tokType])
238
239    case tok.tokType
240    of tkAnd: rememberSplit(splitAnd)
241    of tkOr: rememberSplit(splitOr)
242    of tkIn: rememberSplit(splitIn)
243    else: discard
244
245  of tkColon:
246    wr(TokTypeToStr[tok.tokType])
247    wr(" ")
248  of tkSemicolon,
249     tkComma:
250    wr(TokTypeToStr[tok.tokType])
251    wr(" ")
252    rememberSplit(splitComma)
253  of tkParLe, tkParRi, tkBracketLe,
254     tkBracketRi, tkCurlyLe, tkCurlyRi,
255     tkBracketDotLe, tkBracketDotRi,
256     tkCurlyDotLe, tkCurlyDotRi,
257     tkParDotLe, tkParDotRi,
258     tkColonColon, tkDot, tkBracketLeColon:
259    wr(TokTypeToStr[tok.tokType])
260    if tok.tokType in splitters:
261      rememberSplit(splitParLe)
262  of tkEquals:
263    if not em.endsInWhite: wr(" ")
264    wr(TokTypeToStr[tok.tokType])
265    wr(" ")
266  of tkOpr, tkDotDot:
267    if not em.endsInWhite: wr(" ")
268    wr(tok.ident.s)
269    template isUnary(tok): bool =
270      tok.strongSpaceB == 0 and tok.strongSpaceA > 0
271
272    if not isUnary(tok) or em.lastTok in {tkOpr, tkDotDot}:
273      wr(" ")
274      rememberSplit(splitBinary)
275  of tkAccent:
276    wr(TokTypeToStr[tok.tokType])
277    em.inquote = not em.inquote
278  of tkComment:
279    if not preventComment:
280      emitComment(em, tok)
281  of tkIntLit..tkStrLit, tkRStrLit, tkTripleStrLit, tkGStrLit, tkGTripleStrLit, tkCharLit:
282    let lit = fileSection(em.config, em.fid, tok.offsetA, tok.offsetB)
283    softLinebreak(em, lit)
284    if endsInAlpha(em) and tok.tokType notin {tkGStrLit, tkGTripleStrLit}: wr(" ")
285    em.lineSpan = countNewlines(lit)
286    if em.lineSpan > 0: calcCol(em, lit)
287    wr lit
288  of tkEof: discard
289  else:
290    let lit = if tok.ident != nil: tok.ident.s else: tok.literal
291    softLinebreak(em, lit)
292    if endsInAlpha(em): wr(" ")
293    wr lit
294
295  em.lastTok = tok.tokType
296  em.lastLineNumber = tok.line + em.lineSpan
297  em.lineSpan = 0
298
299proc starWasExportMarker*(em: var Emitter) =
300  if em.content.endsWith(" * "):
301    setLen(em.content, em.content.len-3)
302    em.content.add("*")
303    dec em.col, 2
304
305type
306  Thing = ref object
307    grade: string
308    # this name is great
309    name: string
310
311proc f() =
312  var c: char
313  var str: string
314  if c == '\\':
315    # escape char
316    str &= c
317
318proc getKeyAndData(cursor: int, op: int):
319    tuple[key, data: string, success: bool] {.noInit.} =
320  var keyVal: string
321  var dataVal: string
322
323#!nimpretty off
324  when stuff:
325    echo "so nice"
326    echo "more"
327  else:
328     echo "misaligned"
329#!nimpretty on
330
331const test = r"C:\Users\-\Desktop\test.txt"
332
333proc abcdef*[T:not (tuple|object|string|cstring|char|ref|ptr|array|seq|distinct)]() =
334  # bug #9504
335  type T2 = a.type
336  discard
337
338proc fun() =
339  #[
340  this one here
341  ]#
342  discard
343
344proc fun2() =
345  ##[
346  foobar
347  ]##
348  discard
349
350#[
351foobar
352]#
353
354proc fun3() =
355  discard
356
357##[
358foobar
359]##
360
361# bug #9673
362discard `* `(1, 2)
363
364proc fun4() =
365  var a = "asdf"
366  var i = 0
367  while i<a.len and i<a.len:
368    return
369
370
371# bug #10295
372
373import osproc
374let res = execProcess(
375    "echo | openssl s_client -connect example.com:443 2>/dev/null | openssl x509 -noout -dates")
376
377let res = execProcess("echo | openssl s_client -connect example.com:443 2>/dev/null | openssl x509 -noout -dates")
378
379
380# bug #10177
381
382proc foo  *  () =
383  discard
384
385proc foo* [T]() =
386  discard
387
388
389# bug #10159
390
391proc fun() =
392  discard
393
394proc main() =
395    echo "foo"; echo "bar";
396    discard
397
398main()
399
400type
401  TCallingConvention* = enum
402    ccDefault,                # proc has no explicit calling convention
403    ccStdCall,    # procedure is stdcall
404    ccCDecl,                  # cdecl
405    ccSafeCall,               # safecall
406    ccSysCall, # system call
407    ccInline,                 # proc should be inlined
408    ccNoInline,               # proc should not be inlined
409    ccFastCall,               # fastcall (pass parameters in registers)
410    ccClosure,        # proc has a closure
411    ccNoConvention       # needed for generating proper C procs sometimes
412
413
414proc isValid1*[A](s: HashSet[A]): bool {.deprecated:
415    "Deprecated since v0.20; sets are initialized by default".} =
416  ## Returns `true` if the set has been initialized (with `initHashSet proc
417  ## <#initHashSet,int>`_ or `init proc <#init,HashSet[A],int>`_).
418  result = s.data.len > 0
419  # bug #11468
420
421assert $typeof(a) == "Option[system.int]"
422foo(a, $typeof(b), c)
423foo(typeof(b), c) # this is ok
424
425proc `<`*[A](s, t: A): bool = discard
426proc `==`*[A](s, t: HashSet[A]): bool = discard
427proc `<=`*[A](s, t: HashSet[A]): bool = discard
428
429# these are ok:
430proc `$`*[A](s: HashSet[A]): string = discard
431proc `*`*[A](s1, s2: HashSet[A]): HashSet[A] {.inline.} = discard
432proc `-+-`*[A](s1, s2: HashSet[A]): HashSet[A] {.inline.} = discard
433
434# bug #11470
435
436
437# bug #11467
438
439type
440  FirstEnum = enum ## doc comment here
441    first,  ## this is first
442    second, ## second doc
443    third,  ## third one
444    fourth  ## the last one
445
446
447type
448  SecondEnum = enum ## doc comment here
449    first,  ## this is first
450    second, ## second doc
451    third,  ## third one
452    fourth, ## the last one
453
454
455type
456  ThirdEnum = enum ## doc comment here
457    first    ## this is first
458    second   ## second doc
459    third    ## third one
460    fourth   ## the last one
461
462
463type
464  HttpMethod* = enum  ## the requested HttpMethod
465    HttpHead,         ## Asks for the response identical to the one that would
466                      ## correspond to a GET request, but without the response
467                      ## body.
468    HttpGet,          ## Retrieves the specified resource.
469    HttpPost,         ## Submits data to be processed to the identified
470                      ## resource. The data is included in the body of the
471                      ## request.
472    HttpPut,          ## Uploads a representation of the specified resource.
473    HttpDelete,       ## Deletes the specified resource.
474    HttpTrace,        ## Echoes back the received request, so that a client
475                      ## can see what intermediate servers are adding or
476                      ## changing in the request.
477    HttpOptions,      ## Returns the HTTP methods that the server supports
478                      ## for specified address.
479    HttpConnect,      ## Converts the request connection to a transparent
480                      ## TCP/IP tunnel, usually used for proxies.
481    HttpPatch         ## Applies partial modifications to a resource.
482
483type
484  HtmlTag* = enum  ## list of all supported HTML tags; order will always be
485                   ## alphabetically
486    tagUnknown,    ## unknown HTML element
487    tagA,          ## the HTML ``a`` element
488    tagAbbr,       ## the deprecated HTML ``abbr`` element
489    tagAcronym,    ## the HTML ``acronym`` element
490    tagAddress,    ## the HTML ``address`` element
491    tagApplet,     ## the deprecated HTML ``applet`` element
492    tagArea,       ## the HTML ``area`` element
493    tagArticle,    ## the HTML ``article`` element
494    tagAside,      ## the HTML ``aside`` element
495    tagAudio,      ## the HTML ``audio`` element
496    tagB,          ## the HTML ``b`` element
497    tagBase,       ## the HTML ``base`` element
498    tagBdi,        ## the HTML ``bdi`` element
499    tagBdo,        ## the deprecated HTML ``dbo`` element
500    tagBasefont,   ## the deprecated HTML ``basefont`` element
501    tagBig,        ## the HTML ``big`` element
502    tagBlockquote, ## the HTML ``blockquote`` element
503    tagBody,       ## the HTML ``body`` element
504    tagBr,         ## the HTML ``br`` element
505    tagButton,     ## the HTML ``button`` element
506    tagCanvas,     ## the HTML ``canvas`` element
507    tagCaption,    ## the HTML ``caption`` element
508    tagCenter,     ## the deprecated HTML ``center`` element
509    tagCite,       ## the HTML ``cite`` element
510    tagCode,       ## the HTML ``code`` element
511    tagCol,        ## the HTML ``col`` element
512    tagColgroup,   ## the HTML ``colgroup`` element
513    tagCommand,    ## the HTML ``command`` element
514    tagDatalist,   ## the HTML ``datalist`` element
515    tagDd,         ## the HTML ``dd`` element
516    tagDel,        ## the HTML ``del`` element
517    tagDetails,    ## the HTML ``details`` element
518    tagDfn,        ## the HTML ``dfn`` element
519    tagDialog,     ## the HTML ``dialog`` element
520    tagDiv,        ## the HTML ``div`` element
521    tagDir,        ## the deprecated HTLM ``dir`` element
522    tagDl,         ## the HTML ``dl`` element
523    tagDt,         ## the HTML ``dt`` element
524    tagEm,         ## the HTML ``em`` element
525    tagEmbed,      ## the HTML ``embed`` element
526    tagFieldset,   ## the HTML ``fieldset`` element
527    tagFigcaption, ## the HTML ``figcaption`` element
528    tagFigure,     ## the HTML ``figure`` element
529    tagFont,       ## the deprecated HTML ``font`` element
530    tagFooter,     ## the HTML ``footer`` element
531    tagForm,       ## the HTML ``form`` element
532    tagFrame,      ## the HTML ``frame`` element
533    tagFrameset,   ## the deprecated HTML ``frameset`` element
534    tagH1,         ## the HTML ``h1`` element
535    tagH2,         ## the HTML ``h2`` element
536    tagH3,         ## the HTML ``h3`` element
537    tagH4,         ## the HTML ``h4`` element
538    tagH5,         ## the HTML ``h5`` element
539    tagH6,         ## the HTML ``h6`` element
540    tagHead,       ## the HTML ``head`` element
541    tagHeader,     ## the HTML ``header`` element
542    tagHgroup,     ## the HTML ``hgroup`` element
543    tagHtml,       ## the HTML ``html`` element
544    tagHr,         ## the HTML ``hr`` element
545    tagI,          ## the HTML ``i`` element
546    tagIframe,     ## the deprecated HTML ``iframe`` element
547    tagImg,        ## the HTML ``img`` element
548    tagInput,      ## the HTML ``input`` element
549    tagIns,        ## the HTML ``ins`` element
550    tagIsindex,    ## the deprecated HTML ``isindex`` element
551    tagKbd,        ## the HTML ``kbd`` element
552    tagKeygen,     ## the HTML ``keygen`` element
553    tagLabel,      ## the HTML ``label`` element
554    tagLegend,     ## the HTML ``legend`` element
555    tagLi,         ## the HTML ``li`` element
556    tagLink,       ## the HTML ``link`` element
557    tagMap,        ## the HTML ``map`` element
558    tagMark,       ## the HTML ``mark`` element
559    tagMenu,       ## the deprecated HTML ``menu`` element
560    tagMeta,       ## the HTML ``meta`` element
561    tagMeter,      ## the HTML ``meter`` element
562    tagNav,        ## the HTML ``nav`` element
563    tagNobr,       ## the deprecated HTML ``nobr`` element
564    tagNoframes,   ## the deprecated HTML ``noframes`` element
565    tagNoscript,   ## the HTML ``noscript`` element
566    tagObject,     ## the HTML ``object`` element
567    tagOl,         ## the HTML ``ol`` element
568    tagOptgroup,   ## the HTML ``optgroup`` element
569    tagOption,     ## the HTML ``option`` element
570    tagOutput,     ## the HTML ``output`` element
571    tagP,          ## the HTML ``p`` element
572    tagParam,      ## the HTML ``param`` element
573    tagPre,        ## the HTML ``pre`` element
574    tagProgress,   ## the HTML ``progress`` element
575    tagQ,          ## the HTML ``q`` element
576    tagRp,         ## the HTML ``rp`` element
577    tagRt,         ## the HTML ``rt`` element
578    tagRuby,       ## the HTML ``ruby`` element
579    tagS,          ## the deprecated HTML ``s`` element
580    tagSamp,       ## the HTML ``samp`` element
581    tagScript,     ## the HTML ``script`` element
582    tagSection,    ## the HTML ``section`` element
583    tagSelect,     ## the HTML ``select`` element
584    tagSmall,      ## the HTML ``small`` element
585    tagSource,     ## the HTML ``source`` element
586    tagSpan,       ## the HTML ``span`` element
587    tagStrike,     ## the deprecated HTML ``strike`` element
588    tagStrong,     ## the HTML ``strong`` element
589    tagStyle,      ## the HTML ``style`` element
590    tagSub,        ## the HTML ``sub`` element
591    tagSummary,    ## the HTML ``summary`` element
592    tagSup,        ## the HTML ``sup`` element
593    tagTable,      ## the HTML ``table`` element
594    tagTbody,      ## the HTML ``tbody`` element
595    tagTd,         ## the HTML ``td`` element
596    tagTextarea,   ## the HTML ``textarea`` element
597    tagTfoot,      ## the HTML ``tfoot`` element
598    tagTh,         ## the HTML ``th`` element
599    tagThead,      ## the HTML ``thead`` element
600    tagTime,       ## the HTML ``time`` element
601    tagTitle,      ## the HTML ``title`` element
602    tagTr,         ## the HTML ``tr`` element
603    tagTrack,      ## the HTML ``track`` element
604    tagTt,         ## the HTML ``tt`` element
605    tagU,          ## the deprecated HTML ``u`` element
606    tagUl,         ## the HTML ``ul`` element
607    tagVar,        ## the HTML ``var`` element
608    tagVideo,      ## the HTML ``video`` element
609    tagWbr         ## the HTML ``wbr`` element
610
611
612# bug #11469
613const lookup: array[32, uint8] = [0'u8, 1, 28, 2, 29, 14, 24, 3, 30, 22, 20, 15, 16, 17,
614    25, 17, 4, 8, 31, 27, 13, 23]
615
616veryLongVariableName.createVar("future" & $node[1][0].toStrLit, node[1], futureValue1,
617    futureValue2, node)
618
619veryLongVariableName.createVar("future" & $node[1][0].toStrLit, node[1], futureValue1,
620                               futureValue2, node)
621
622type
623  CmdLineKind* = enum         ## The detected command line token.
624    cmdEnd,                   ## End of command line reached
625    cmdArgument,              ## An argument such as a filename
626    cmdLongOption,            ## A long option such as --option
627    cmdShortOption            ## A short option such as -c
628  OptParser* = object of RootObj ## \
629    ## Implementation of the command line parser. Here is even more text yad.
630    ##
631    ## To initialize it, use the
632    ## `initOptParser proc<#initOptParser,string,set[char],seq[string]>`_.
633    pos*: int
634    inShortState: bool
635    allowWhitespaceAfterColon: bool
636    shortNoVal: set[char]
637    longNoVal: seq[string]
638    cmds: seq[string]
639    idx: int
640    kind*: CmdLineKind        ## The detected command line token
641    key*, val*: TaintedString ## Key and value pair; the key is the option
642                              ## or the argument, and the value is not "" if
643                              ## the option was given a value
644
645  OptParserDifferently* = object of RootObj ## Implementation of the command line parser.
646    ##
647    ## To initialize it, use the
648    ## `initOptParser proc<#initOptParser,string,set[char],seq[string]>`_.
649    pos*: int
650    inShortState: bool
651    allowWhitespaceAfterColon: bool
652    shortNoVal: set[char]
653    longNoVal: seq[string]
654    cmds: seq[string]
655    idx: int
656    kind*: CmdLineKind        ## The detected command line token
657    key*, val*: TaintedString ## Key and value pair; the key is the option
658                              ## or the argument, and the value is not "" if
659                              ## the option was given a value
660
661block:
662  var t = 3
663
664## This MUST be a multiline comment,
665## single line comment would be ok.
666block:
667  var x = 7
668
669
670block:
671  var t = 3
672  ## another
673  ## multi
674
675## This MUST be a multiline comment,
676## single line comment would be ok.
677block:
678  var x = 7
679
680
681proc newRecordGen(ctx: Context; typ: TypRef): PNode =
682  result = nkTypeDef.t(
683    newId(typ.optSym.name, true, pragmas = [id(if typ.isUnion: "cUnion" else: "cStruct")]),
684    empty(),
685    nkObjectTy.t(
686      empty(),
687      empty(),
688      nkRecList.t(
689        typ.recFields.map(newRecFieldGen))))
690
691
692##[
693String `interpolation`:idx: / `format`:idx: inspired by
694Python's ``f``-strings.
695
696.. code-block:: nim
697
698    import strformat
699    let msg = "hello"
700    doAssert fmt"{msg}\n" == "hello\\n"
701
702Because the literal is a raw string literal, the ``\n`` is not interpreted as
703an escape sequence.
704
705
706=================        ====================================================
707  Sign                   Meaning
708=================        ====================================================
709``+``                    Indicates that a sign should be used for both
710                         positive as well as negative numbers.
711``-``                    Indicates that a sign should be used only for
712                         negative numbers (this is the default behavior).
713(space)                  Indicates that a leading space should be used on
714                         positive numbers.
715=================        ====================================================
716
717]##
718
719
720let
721  lla = 42394219 - 42429849 + 1293293 - 13918391 + 424242 # this here is an okayish comment
722  llb = 42394219 - 42429849 + 1293293 - 13918391 + 424242 # this here is a very long comment which should be split
723  llc = 42394219 - 42429849 + 1293293 - 13918391 + 424242 - 3429424 + 4239489 - 42399
724  lld = 42394219 - 42429849 + 1293293 - 13918391 + 424242 - 342949924 + 423948999 - 42399
725
726type
727  MyLongEnum = enum ## doc comment here
728    first, ## this is a long comment here, but please align it
729    secondWithAVeryLongNameMightBreak, ## this is a short one
730    thirdOne ## it's ok
731
732if true: # just one space before comment
733  echo 7
734
735# colors.nim:18
736proc `==` *(a, b: Color): bool
737  ## Compares two colors.
738  ##
739
740# colors.nim:18
741proc `==` *(a, b: Color): bool {.borrow.}
742  ## Compares two colors.
743  ##
744
745
746var rows1 = await pool.rows(sql"""
747    SELECT STUFF
748    WHERE fffffffffffffffffffffffffffffff
749  """,
750  @[
751    "AAAA",
752    "BBBB"
753  ]
754)
755
756var rows2 = await pool.rows(sql"""
757    SELECT STUFF
758    WHERE fffffffffffffffffffffffffffffffgggggggggggggggggggggggggghhhhhhhhhhhhhhhheeeeeeiiiijklm""",
759  @[
760    "AAAA",
761    "BBBB"
762  ]
763)
764
765
766# bug #11699
767
768const keywords = @[
769  "foo", "bar", "foo", "bar", "foo", "bar", "foo", "bar", "foo", "bar", "foo", "bar", "foo", "bar",
770  "zzz", "ggg", "ddd",
771]
772
773let keywords1 = @[
774  "foo1", "bar1", "foo2", "bar2", "foo3", "bar3", "foo4", "bar4", "foo5", "bar5", "foo6", "bar6", "foo7",
775  "zzz", "ggg", "ddd",
776]
777
778let keywords2 = @[
779  "foo1", "bar1", "foo2", "bar2", "foo3", "bar3", "foo4", "bar4", "foo5", "bar5", "foo6", "bar6", "foo7",
780  "foo1", "bar1", "foo2", "bar2", "foo3", "bar3", "foo4", "bar4", "foo5", "bar5", "foo6", "bar6", "foo7",
781  "zzz", "ggg", "ddd",
782]
783
784if true:
785  let keywords3 = @[
786    "foo1", "bar1", "foo2", "bar2", "foo3", "bar3", "foo4", "bar4", "foo5", "bar5", "foo6", "bar6", "foo7",
787    "zzz", "ggg", "ddd",
788  ]
789
790const b = true
791let fooB =
792  if true:
793    if b: 7 else: 8
794  else: ord(b)
795
796let foo = if cond:
797            if b: T else: F
798          else: b
799
800let a =
801  [[aaadsfas, bbb],
802   [ccc, ddd]]
803
804let b = [
805  [aaa, bbb],
806  [ccc, ddd]
807]
808
809# bug #11616
810proc newRecordGen(ctx: Context; typ: TypRef): PNode =
811  result = nkTypeDef.t(
812    newId(typ.optSym.name, true, pragmas = [id(if typ.isUnion: "cUnion"
813                                               else: "cStruct")]),
814    empty(),
815    nkObjectTy.t(
816      empty(),
817      empty(),
818      nkRecList.t(
819        typ.recFields.map(newRecFieldGen))))
820
821proc f =
822  # doesn't break the code, but leaving indentation as is would be nice.
823  let x = if true: callingProcWhatever()
824          else: callingADifferentProc()
825
826
827type
828  EventKind = enum
829    Stop, StopSuccess, StopError,
830    SymbolChange, TextChange,
831
832  SpinnyEvent = tuple
833    kind: EventKind
834    payload: string
835
836
837type
838  EventKind2 = enum
839    Stop2, StopSuccess2, StopError2,
840    SymbolChange2, TextChange2,
841
842type
843  SpinnyEvent2 = tuple
844    kind: EventKind
845    payload: string
846
847
848proc hid_open*(vendor_id: cushort; product_id: cushort; serial_number: cstring): ptr HidDevice {.
849    importc: "hid_open", dynlib: hidapi.}
850