Git Product home page Git Product logo

nim-works / nimskull Goto Github PK

View Code? Open in Web Editor NEW
253.0 253.0 37.0 528.42 MB

An in development statically typed systems programming language; with sustainability at its core. We, the community of users, maintain it.

Home Page: https://nim-works.github.io/nimskull/index.html

License: Other

Shell 0.03% Batchfile 0.01% Nim 97.45% Assembly 0.04% C 0.36% C++ 0.16% Python 0.31% HTML 1.25% CSS 0.29% NSIS 0.09% JavaScript 0.02% CMake 0.01%
compiler language programming-language

nimskull's Introduction

nim-works

nimskull's People

Contributors

alaviss avatar apense avatar araq avatar arnetheduck avatar bors[bot] avatar cheatfate avatar clyybber avatar cooldome avatar def- avatar dom96 avatar federicoceratto avatar flaviut avatar gradha avatar gulpf avatar haxscramper avatar juancarlospaco avatar krux02 avatar lemonboy avatar nanoant avatar narimiran avatar nc-x avatar reactormonk avatar ringabout avatar saem avatar timotheecour avatar tmm1 avatar varriount avatar yglukhov avatar zah avatar zerbina avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar

nimskull's Issues

specification to merge documentation with code

Not fully formal yet, but these were my comments on IRC

I think documentation is attached to nodes, and it would be nice is this documentation to node attachment would be specified clearly and is extended generally.
for example documentation for functions contain documentation for function arguments.
this means a doc comment doesn.t just document one fucntion, it does document a whole tree of nodes
therefore it is good to specifiy a grammer how subnodes can be documented in a doc comment
so that you can attach documentation to everything from everywhere
and at the end the parser merges all these possible sources of documentation is a specified order to have the full documentation.
this means you can put function documentation including arguments documentation at the top level module documentation, or in the seperate documention file
runnable examples could just be normal example code in the mymodule.doc file

Will `nimskull` embrace breaking changes?

For instance, some features I want to see:

  • identifier sensitive and _ can be used among identifier names for C interoperability
  • implement nim-lang/Nim#18422 (breaking change)
  • remove some nasty or unused features (remove concepts or not; remove method (at least generic based method) and implement vtable instead)

Or nimskull will be compatible with Nim as far as possible?

semchecked ast passed down as untyped macro argument

Specification

Whenever symbols and semchecked ast nodes get passed to a macro as "untyped" it is a bug. Typechecked nodes are structured very differently than untyped nodes and therefore will cause unexpected behavior in the macro.

Example

import macros

macro check(args: varargs[untyped]): untyped =
  echo args.treeRepr
  
proc foo1() = 
  let check = 123
  var a = 1
  var b = 1
  # for some reason this is fully semchecked
  check(a == b)

# ArgList
#   Infix
#    Sym "=="
#    Sym "a"
#    Sym "b"

proc foo2() =
  let check = 123
  # this "untyped" ast contains Error nodes
  check(a == b)

# ArgList
#   Error
#     Error
#       Infix
#         Ident "=="
#         Error
#           Ident "a"
#           IntLit 365
#           StrLit "lookups.nim"
#         Ident "b"
#       IntLit 202
#       StrLit "semcall.nim"
#     IntLit 372
#     StrLit "semexprs.nim"
#     Infix
#       Ident "=="
#       Error
#         Ident "a"
#         IntLit 365
#         StrLit "lookups.nim"
#       Ident "b"

proc foo3() =
  var a = 1
  var b = 1
  # this is what it should be
  check(a == b)

# ArgList
#   Infix
#     Ident "=="
#     Ident "a"
#     Ident "b"

proc foo4() =
  # this is fine, too
  check(a == b)

# ArgList
#   Infix
#     Ident "=="
#     Ident "a"
#     Ident "b"

Actual Output

ArgList
  Infix
    Sym "=="
    Sym "a"
    Sym "b"
ArgList
  Error
    Error
      Infix
        Ident "=="
        Error
          Ident "a"
          IntLit 365
          StrLit "lookups.nim"
        Ident "b"
      IntLit 202
      StrLit "semcall.nim"
    IntLit 372
    StrLit "semexprs.nim"
    Infix
      Ident "=="
      Error
        Ident "a"
        IntLit 365
        StrLit "lookups.nim"
      Ident "b"
ArgList
  Infix
    Ident "=="
    Ident "a"
    Ident "b"
/tmp/scratch.nim(47, 7) Hint: 'a' is declared but not used [XDeclaredButNotUsed]
/tmp/scratch.nim(48, 7) Hint: 'b' is declared but not used [XDeclaredButNotUsed]
ArgList
  Infix
    Ident "=="
    Ident "a"
    Ident "b"

Expected Output

ArgList
  Infix
    Ident "=="
    Ident "a"
    Ident "b"
ArgList
  Infix
    Ident "=="
    Ident "a"
    Ident "b"
ArgList
  Infix
    Ident "=="
    Ident "a"
    Ident "b"
ArgList
  Infix
    Ident "=="
    Ident "a"
    Ident "b"

Additional Information

This bug prevents the removal of the deprecated feature callsite from unittest.nim.

raise might eat errors when used with strformat

Example

import std/strformat

proc exec(cmd: string, args: varargs[string]) =
  let x = @[cmd] & args
  raise newException(CatchableError):
    fmt"{x}"
  # Only referring to a "broken" variable would this issue happen

Actual Output

test.nim(5, 3) Error: only a 'ref object' can be raised

Expected Output

The real cause of the error (invalid expression for x) should show up instead

test.nim(4, 18) Error: type mismatch: got <seq[string], varargs[string]>
but expected one of:
proc `&`[T](x, y: seq[T]): seq[T]
  first type mismatch at position: 2
  required type for y: seq[T]
  but expression 'args' is of type: varargs[string]
proc `&`[T](x: T; y: seq[T]): seq[T]
  first type mismatch at position: 2
  required type for y: seq[T]
  but expression 'args' is of type: varargs[string]
proc `&`[T](x: seq[T]; y: T): seq[T]
  first type mismatch at position: 2
  required type for y: T
  but expression 'args' is of type: varargs[string]
5 other mismatching symbols have been suppressed; compile with --showAllMismatches:on to see them

expression: @[cmd] & args

Additional information

  • Mainline does not have this issue

Spec - comments on reviews

To-dos that were uncovered when during PR reviews

Move away from the `string` for handling executed commands

Most of the commands executed in the compiler go through the execProcesses*(cmds: openArray[string], or execCmdEx*(command: string, and as a consequence, most of the code handles strings by immediately joining them, using string template interpolation all over the place. While by itself it is not too bad, it makes it harder to reason about the code, because semi-random string joins all over the place, like

proc addOpt(dest: var string, src: string) =
if dest.len == 0 or dest[^1] != ' ': dest.add(" ")
dest.add(src)

proc getLinkOptions(conf: ConfigRef): string =
result = conf.linkOptions & " " & conf.linkOptionsCmd & " "

let (s, exitCode) = try: execCmdEx(exe & " --version") except: ("", 1)

As well as weird handling of the shell execution results, where (again), premature string formatting completely conceals the purpose and data flow in the code.

givenmsg = "$ " & given.cmd & '\n' & given.nimout

proc getCmd*(s: TSpec): string =
if s.cmd.len == 0:
result = compilerPrefix & " $target --hints:on -d:testing --clearNimblePath --nimblePath:build/deps/pkgs $options $file"
else:
result = s.cmd

proc prepareTestCmd(cmdTemplate, filename, options, nimcache: string,
target: TTarget, extraOptions = ""): string =
var options = target.defaultOptions & ' ' & options
if nimcache.len > 0: options.add(" --nimCache:$#" % nimcache.quoteShell)
options.add ' ' & extraOptions
# we avoid using `parseCmdLine` which is buggy, refs bug #14343
result = cmdTemplate % ["target", target.cmd,
"options", options, "file", filename.quoteShell,
"filedir", filename.getFileDir(), "nim", compilerPrefix]

Instead, several helper types should be introduced to abstract away the command handling logic - ShellCmd, ShellResult, ShellCmdPart.

execExternalProgram(
graph.config,
(
"dot -Tpng -o" &
changeFileExt(project, "png").string &
' ' &
changeFileExt(project, "dot").string
),
rcmdExecuting
)

proc execExternalProgram*(conf: ConfigRef; cmd: string, kind: ReportKind) =
if execWithEcho(conf, cmd, kind) != 0:
conf.localReport CmdReport(kind: rcmdFailedExecution, cmd: cmd)

compileTmpl: "-c $options $include -o $objfile $file",
buildGui: "-Wl,-subsystem=gui",
buildDll: " -shared",
buildLib: "", # XXX: not supported yet
linkerExe: "tcc",
linkTmpl: "-o $exefile $options $buildgui $builddll $objfiles",

compileTmpl: "-w -MMD -MP -MF $dfile -c $options $include -o $objfile $file",

Move predicate logic out of `cli_reporter` report hook

Move predicate logic out of direct implementation of the cli_reporter.reportHook, and instead add WritabilityClassification or something similar - enum CanWrite, Ignore, CanForceWrite - for regular allowed/ignored reports, and mandatory force debugging reports that can't be filtered out.

Spec - templates

  • Basic template features - code generation
  • Typed and untyped argument passing
  • {.dirty.} template annotation
  • New symbol injection
  • Name concatenation using `A B`

Make it easy to contribute docs/ux suggestions

It might be a good idea to think about people contributing suggestions to the documentation and user experience. At the very least we can have a GitHub discussion thread for discussion about nuances of the documentation (manual, spec, or stdlib parts) and suggestions about improving error messages.

Most likely people won't open issues about ambiguous phrasing in documentation, and "edit" button is almost useless, but if we make it easier for a beginner to contribute their view on the matter it could make a difference in the long run (it is beneficial for us to know about bad documentation as soon as possible).

Alternatively it can be a #docs/ux-team channel on matrix, or any place where we can get to details about missing explanations.

Bad documentation has been repeatedly brought up as an important issue, but when asked about specifics people usually can't recall which part exactly it was. We need to make it easier for people to tell us something is missing when they realize it is missing.

I think I repeated the same idea at least twice, but tldr version is - we need to make sure people without the curse of knowledge are given the easiest way possible to contribute to documentation.

structure gc memory statistics data

The GC memory statistics data is generated in the gc.nim and then printed when the compiler is executed. This is a compiler report, it must also be structured and have the data accessible.

  proc GC_getStatistics(): string =
    result = "[GC] total memory: " & $(getTotalMem()) & "\n" &
             "[GC] occupied memory: " & $(getOccupiedMem()) & "\n" &
             "[GC] stack scans: " & $gch.stat.stackScans & "\n" &

Right now the data is not structured, and it is printed in the

  when declared(GC_setMaxPause):
    echo GC_getStatistics()

in the nim.nim

  • refactor the GC_getStatistics into "get data" (add NimGcStats or similarly-named objet (to avoid clashes) and make GC_getStatisticsData() procedure that returns this) and "format data" stages. Old GC_getStatistics can be implemented as getGcData().formatGcData()
  • Store the GC report in the reports.InternalReport field. Add rintGcStatistics report kind and put this field under the branch in report definition.
  • Format report just like any other in the cli_reporter.reportBody for the InternalReport

Make testament actually understand the test specification

Follow-up on (required to be completed)

Write ActiveConfiguration -> ShellCmd (#213) and 'join' forActiveConf + ActiveConf merge, refactor testament spec parser to actually understand thecmd, matrix and other parts. Handle all compiler invocations only using active configuration instead of passing around random strings.

  • because we can now use CLI parser separately (#210) we can validate spec and options when they are declared, not a million lines later when the compiler reports to you that something is wrong with the cli parameters. This is not really a goal, but I find failures like this extremely annoying
  • This would be a start of the proper test handling pipeline. 'matrix' field will be aseq[ActiveConf] and 'generate runs for tests' will be a'matrix' x 'main' -> seq[ActiveConf].
  • 'run test' isActiveConf -> ShellCmd -> ShellResult

Convert all non-documentation comments to documentation

Most of the compiler modules use single comment for documentation of the different procedures, fields, toplevel modules and so on. They won't show up in the generated documentation for modules.

type
  Ctx = object
    g: ModuleGraph
    fn: PSym
    stateVarSym: PSym # :state variable. nil if env already introduced by lambdalifting
    tmpResultSym: PSym # Used when we return, but finally has to interfere
    unrollFinallySym: PSym # Indicates that we're unrolling finally states (either exception happened or premature return)
    curExcSym: PSym # Current exception

    states: seq[PNode] # The resulting states. Every state is an nkState node.
    blockLevel: int # Temp used to transform break and continue stmts
    stateLoopLabel: PSym # Label to break on, when jumping between states.
    exitStateIdx: int # index of the last state
    tempVarId: int # unique name counter
    tempVars: PNode # Temp var decls, nkVarSection
    exceptionTable: seq[int] # For state `i` jump to state `exceptionTable[i]` if exception is raised
    hasExceptions: bool # Does closure have yield in try?
    curExcHandlingState: int # Negative for except, positive for finally
    nearestFinally: int # Index of the nearest finally block. For try/except it
                    # is their finally. For finally it is parent finally. Otherwise -1
    idgen: IdGenerator

Convert comments like these into documentation ones where applicable (not every single comment is actually a documentation, sometimes they are TODO etc.)

This also applies to the discard """ comments.

discard """

one major problem:
  spawn f(a[i])
  inc i
  spawn f(a[i])
is valid, but
  spawn f(a[i])
  spawn f(a[i])
  inc i
is not! However,
  spawn f(a[i])
  if guard: inc i
  spawn f(a[i])
is not valid either! --> We need a flow dependent analysis here.

However:
  while foo:
    spawn f(a[i])
    inc i
    spawn f(a[i])

Is not valid either! --> We should really restrict 'inc' to loop endings?

The heuristic that we implement here (that has no false positives) is: Usage
of 'i' in a slice *after* we determined the stride is invalid!
"""

Spec - user-defined types

  • Built-in magic types
    • ptr
    • ref
    • set
    • seq
    • enum
    • range
    • array and different combinations of uses from the list above (range and array, enum and array)
    • Different syntaxes for construction of the array literals. [], [:], {:}, {,:}. For the latter case - check how many times each value expression is executed.
  • User-defined types
    • checking for runtime type relations using of operator
    • Type conversions
    • tuples
      • named tuple de-structuring tests. It's pretty easy to trip up (CPS did trip up on some)
    • Plain objects
      • ref object
      • object
      • default state of the object
    • Variant objects
      • Branch assignment
      • Default state of the object
      • cast(uncheckedAssign)
    • Inheritance
      • Inherited fields
      • of operator checks
      • procedure dispatch of inherited types(both generic, and not)
      • Inherit from variant object
      • Inherit from regular object and make it a variant
      • Inheriting from an object in another module, with field of the same name while parent type field was not exported.
      • Error for field override
    • ref object of CatchableError
      • Catching specific type of exception
      • Catching multiple types of exception at once
      • Catching parent type of exception
    • Object pragmas
      • {.inheritable.}
      • {.pure.}?
      • {.bycopy.}
    • Type aliases
      • distinct
      • Generic distinct
      • Regular type alias
      • Typeclass
      • Built-in typeclasses like object, proc, distinct, iterator, enum, ref object
      • Multiple aliases on the same type (B = A; C = A; D = A)
  • Generic types
    • Regular type parameters (test all generic parameters constraints, don't dismiss it as "should work the same way as with procs")
    • Generic types with when branch in the body

Clean up `ast.TIdTable` type definition

ast defines TIdTable type that is used in several parts of the semantic pass. Type defined as follows:

  TIdPair* = object
    key*: PIdObj
    val*: RootRef

  TIdPairSeq* = seq[TIdPair]
  TIdTable* = object # the same as table[PIdent] of PObject
    counter*: int
    data*: TIdPairSeq

All the uses of the val: RootRef field are either converted to PType or PSym (result = PType(idTableGet(c.bindings, t)) etc.). This means RootRef can be easily replaced with

type
  PSymOrTyp = object
    case isSym*: bool
      of true:
        sym*: PSym

      of false:
        typ*: PType

This would not create any functional difference, but will clean up the code a little.

Refactor `.cfg` file processing

The current implementation of the .cfg file processing does not have any form of AST and instead evaluates code directly during lexing, mutating the global configuration values in-place. Refactoring the .cfg file parser would allow:

  • make testing simpler - instead of mutating whole global configuration in-place, test can be separated into parser (can test and assert structure of the AST) and evaluation (can properly assert changed values).

  • Together with #158 .cfg parser can now be seen as a simple function of the input (config: string, oldOptions: ActiveOptions) -> ActiveOptions

  • std/parsecfg can be used in regular code, but the compiler has nonstandard implementation that cannot be used or understood by external tooling, requiring full reimplementation. Having proper AST will address this issue at least as far as reading is concerned

  • Compiler implementation uses nim lexer to "save space and work", which causes more syntax discrepancies: path=$config/test is valid in one syntax, but for .cfg you need to use `path="$config/test" only

  • Testament uses parsecfg with support for ''' for multiline string literals implemented via s.substr(a, b-1).multiReplace({"'''": tripleQuote, "\\31": "\31"})

  • Changes can be made either by improving the current std/parsecfg parser to include events for @if, @command etc., or rewriting the current nimconf.nim to use the implementation from parsecfg - in that case new module can be added into experimental/parsecfg and used only for compiler needs for the time being.

Spec - iterators

  • Core iterator features
    • yield in the iterators
    • break (with and without labels)
    • continue (with and without labels)
    • try/finally checks
    • defer
  • Different kinds of return types
    • Unpacking iterators that yield tuples
    • Implicit tuple iterator unpacking
    • Iterators with mutable return values
    • Iterators with multiple return values (mpairs). Don't forget to test for N > 2 values, with more than one, being mutable at that.
    • Implicit items and pairs
  • How control flow is transferred when an exception is raised in the for loop body. Is it possible to catch an exception from within the iterator itself?
  • Dot operators (..) as iterators (using operators as iterators in general).
  • Overload resolution when there is an iterator and proc with identical names and signatures
  • Nested iterator invocation (both for nested loops, and one iterator calling another iterator)

Refactor active configuration handling

Refactor active configuration handling in the options.ConfigRef - right now every single field is placed on the same level, including both mutable non-configuration values (error counter, list of symbols) and active/passive configurations (list of active notes, local and global options).

Field that are used to store explicit configuration values (backend/target/options/globalOptions) need to be factored out into a separate type definition.

  • This would allow treating compiler (at least on conceptual level) as a function proc compile(config: ActiveOptions).
  • This type can be reused in testament to serve as a configuration cell in test matrix
  • Command-line configuration reading can be simplified as well - instead of using a whole ConfigRef object and mutating it in-place, it can simply return ActiveOptions object

Old code should continue to work using getters and setters. Additional upside - this change would provide a single point of tracing for the active configuration and reduce number of direct access to fields (which cannot be debugged with echo, cannot be asserted and so on).

type
+ ActiveOptions = object
+   options*: TOptions

  ConfigRef* {.acyclic.} = ref object 
-   options*: TOptions
+   active: ActiveOptions

+ func options*(conf: ConfigRef): TOptions = conf.active.options
+ proc `options=`*(conf: ConfigRef, opts: TOptions) = conf.active.options = opts

Repeated for all "input" fields: backend, target, options, filenamesOption

Clean up and reorder tests

Moved to documentation https://nim-works.github.io/nimskull/contributing.html#writing-or-improving-tests

Original issue description

Todo list/guide for cleaning up existing tests

  • Check if test name makes sense - t123123_b.nim does not make sense, change it to something matching what is being tested
  • Reduce number of echo-based error testing. If you see direct echo in test consider changing it to the doAssert check instead
  • If possible, provide explanation to the test logic
  • Link relevant issues in the test description (description: field) or in comments
  • Add test labels link

  • Get rid of completely illegible file names like t10489_a.nim, t10489_b.nim - if you want to help someone to get to a concrete issue easier, you can make a comment in a file with a proper link. And that' where you can get a proper file name - original issue title.

  • Structure tests around categories, not around some barely navigable mountain of folders that people won't ever be able to figure out which tool/language/stdlib this part belongs to. Top-level tool categories should be

  • Provide description: field for the test, more documentation comments and general explanation of the features tested.

  • Reduce usage of echo in tests - doAssert, == are more than sufficient in a lot of cases. Not all of them, but their usage increase locality of the code - no need to look at this header in the 289-line file when this could've been replaced with return "some string" and that is later checked with doAssert(). link of how things should not be tested.

    discard """
    output:
    '''
    Not found!
    Found!
    1
    compiles for 1
    i am always two
    default for 3
    set is 4 not 5
    array is 6 not 7
    default for 8
    an identifier
    OK
    OK
    OK
    ayyydd
    '''
    """

Tests should be easy to understand for a new contributor, because you change something, then the test fails, and you have no idea what this thing was even testing - what could be more frustrating than trying to not only why it fails but what fails in the first place.

Note this is a parallel task to the #10 - language specification most likely will not supersede existing tests, because it is means to specify the language, not check if of branch works with when expression, with const, with proc call, with set join, with set intersect ...

Streamline development and build processes for CI and users

There are a few issues with the compiler development/build processes:

  • Requires PATH modification to run all tests.
  • Requires a bootstrap compiler, but further build invocations will replace it, hiding bootstrap bugs until they hit CI. This might also frustrate developers who start from an old tree cluttered with build artifacts.
  • It is a PITA to build the bootstrap compiler.
  • Build artifacts are littered all over the tree.

This issue tracks the efforts in reducing friction and increasing build reliability.

  • #85
  • Remove bootstrapping (implicit) dependency on users configuration
  • Remove main test suite dependency on nim in PATH
  • #126
  • Easy generation of a compiler source archive
  • Easy generation of a release compiler binary archive

sem trace segfaults when executed without `--stacktrace` enabled (ex: `-d:release`, `-d:danger`).

The current implementation assumes that stacktrace exists, but this is not the case for release/danger builds, and those sometimes need to be debugged as well. This is a follow-up todo for the #191 - it adds another debug utils step kind, the template implementation needs to be refactored into a more manageable structure where check can be added in a single place, right now it is impossible to do cleanly.

Linux CI

Meta issue for tracking Linux CI progress

Targets:

More will be added in the future.

Spec - pragma annotations

  • Pragmas
    • Procedure pragmas
    • Type field annotation template pragmas
    • User-defined pragmas via {.pragma:
    • Block pragmas
    • disabling/enabling errors/warnings
    • Full list
      • magic
      • final
      • objchecks
      • intdefine
      • strdefine
      • booldefine
      • cursor
      • noalias
      • constructor
      • importcpp
      • importobjc
      • importcompilerproc
      • importc
      • importjs
      • exportc
      • exportcpp
      • exportnims
      • incompleteStruct
      • completeStruct
      • requiresInit
      • align
      • nodecl
      • pure
      • sideEffect
      • header
      • noSideEffect
      • gcsafe
      • noreturn
      • nosinks
      • lib
      • dynlib
      • compilerproc
      • core
      • procvar
      • base
      • used
      • fatal
      • error
      • warning
      • hint
      • line
      • push
      • pop
      • link
      • compile
      • linksys
      • deprecated
      • varargs
      • callconv
      • nimcall
      • stdcall
      • cdecl
      • safecall
      • syscall
      • inline
      • noinline
      • fastcall
      • thiscall
      • closure
      • noconv
      • checks
      • rangeChecks
      • boundChecks
      • overflowChecks
      • nilChecks
      • floatChecks
      • nanChecks
      • infChecks
      • styleChecks
      • staticBoundChecks
      • nonReloadable
      • executeOnReload
      • assertions
      • patterns
      • trmacros
      • sinkInference
      • warnings
      • hints
      • optimization
      • raises
      • writes
      • reads
      • size
      • effects
      • tags
      • noforward
      • reorder
      • norewrite
      • nodestroy
      • pragma
      • compileTime
      • noinit
      • passc
      • passl
      • localPassC
      • borrow
      • discardable
      • fieldChecks
      • acyclic
      • shallow
      • experimental
      • inject
      • dirty
      • inheritable
      • threadvar
      • emit
      • implicitStatic
      • global
      • codegenDecl
      • unchecked
      • guard
      • locks
      • union
      • packed
      • alignas
      • alignof
      • constexpr
      • decltype
      • nullptr
      • noexcept
      • bycopy
      • byref
      • bitsize
  • C and C++ interop. I'm not fully sure how to properly test this in the first place, but this is a part of language specification, so it must be constrained somehow.

Language specification - generics

  • Generic procedures
  • Specifying generic parameters
  • Specifying generic parameters with constraints
    • In-place typeclass like A | B
    • Named typeclass
    • inverted generic constraints like not A
  • Static parameters
    • Passing trivial data to the static parameters
    • Passing compound data like objects to the
  • Overload resolution. Selecting best overload resolution candidate in presence of multiple matching overloads
  • Overload resolution for generic procedures in presence of user-defined converters
  • Overload resolution for mixin, bind procedures
  • Inter-module relations for mixin and bind statements in generic bodies
  • Generic types
  • static type parameters
  • Regular type parameters (test all generic parameters constraints, don't dismiss it as "should work the same way as with procs")
  • Generic types with when branch in the body

Spec - module system

  • Importing exported symbol
  • Importing non-exported symbol
  • export
  • include
  • Magic value interpolation for include strings (it supports "$home" and maybe couple other patterns on top of that)
  • Ambiguous call resolution
  • import A/[X, Y, Z]
  • import except
  • from A import B
  • import A as B
  • Explicitly specifying module names when importing
  • import A as nil
  • Execution order of the toplevel statements in modules
  • Order of semantic checking of the modules, visibility of auto-generated entries (related to macros, but probably should be specified as a part of the module specification).
  • what happens when module is imported twice
  • what happens if the module imported twice while having different environment (for example var state {.compiletime.} in when check)
  • {.define(flag).} before the module import

1e100 is considered convertible to int64 and the result is invalid

Example

This was extracted from tcompiletime_range_checks.nim:45, where the declaration should have produced an error but didn't.

echo int64(1e100)

Current Output

0

Expected Output

A compile-time error

Possible Solution

There are two parts to this issue:

First is this conditional:

elif src.kind in nkFloatLit..nkFloat64Lit and
(classify(src.floatVal) in {fcNan, fcNegInf, fcInf} or
src.floatVal.int64 notin firstOrd(c.config, targetTyp)..lastOrd(c.config, targetTyp)):
result = convNotInRange

Since this value won't fit in int64, converting become low(int64), which of course, is a valid int64 value (though do note that in C standard this is undefined). I think either we do the comparison in floats, or int128 it, which leads to this second portion:

of tyFloat..tyFloat64:
result = newIntNodeT(toInt128(getFloat(a)), n, idgen, g)

toInt128(1e100) produced 0 here, which is invalid, and also means we can't use int128 to perform our checks.

Tagging @krux02 here, as he is the author of this code. I'm not sure what is the best to do here, though I think we should code in a range check for numbers that won't fit in int128 (as a fallback in case the check prior fails).

Additional Information

  • Found while testing nimskull on ARM machines
$ nim -v
Nim Compiler Version 1.6.0 [Linux: amd64]
Copyright (c) 2006-2021 by Andreas Rumpf

Source hash: ffb7dc7223ff0eb6768add1e065e406af3397ed6
Source date: 2021-12-03

active boot switches: -d:release

Split documentation publisher out

Currently docs are published as part of the CI run, which means that we can only publish docs when CI runs on devel. This requires a re-run of the CI on the same commit, which is rather inefficient.

A revised scheme should be:

  • Tests and artifacts are produced during main CI, which is run during push to staging by bors.

  • Once devel is fast-forwarded to staging, publish artifacts produced during the run.

This publisher will be extended to handle binary artifacts once we start building them.

Tidy up stdlib's js backend specific modules

The current stdlib has a few js backend specific modules which should be sorted.

They can be sorted into two folders, nodejs and js.
Certain js modules cannot be used by nodejs and vice versa, so this must be done.

add `debugAst()`, `debugType()` and `debugSym()` procs back to `astrepr`

  • Add overload of the treeRepr that does not accept ConfigRef object
  • Allow passing nil conf to the treeRepr
  • Add helper procedures - debugAst(), debugType() and debugSym() with {.exportc.} annotations to be used in the debugging

#191 removed API a little too aggressively - the no-argument debug still needs to be present

`when`

sorry this was an accidental click, I don't know how this happened yet.

Refactor `stackTrace` in the `vm` implementation

VM rawExecute uses an implicitly injected return statement that is added by template stackTrace(). This makes code much harder to read, since you can't properly see where the loop is terminated.

template stackTrace(
    c: PCtx,
    tos: PStackFrame,
    pc: int,
    sem: ReportTypes,
  ) =
  stackTraceImpl(c, tos, pc, c.debug[pc], instLoc())
  localReport(c.config, c.debug[pc], sem)
- return

Remove implicitly injected return and add it in a way that is visible to the reader.

    of opcLdArr:
      # a = b[c]
      decodeBC(rkNode)
      if regs[rc].intVal > high(int):
        stackTrace(c, tos, pc, reportVmIdx(regs[rc].intVal, high(int)))
+       return

Hint: in order to track all the usages of the stackTrace template, you can add {.hint: "used here".} or {.warning: "used here".}

Spec - procedures

  • Builtin magics
    • sizeof
    • is
    • fieldPairs
    • field
    • Implicitly defined == (magic == via fieldPairs)
    • $
    • defined() check
    • declared
    • declaredInScope()
  • Procedure calls
    • Default arguments
    • Default arguments with nontrivial expressions
    • Trailing arguments
    • Block syntax for trailing arguments (including new syntax with support for trailing body and optional arguments)
    • var arguments
    • regular arguments
    • varargs conversion (with generic converters, magical procs, regular procs, operator procs, methods)
    • Multiple varargs
    • Infix operators - define, call, call using backtick notation.
    • []=, [], {} and {}= operators
    • Test all supported infix operator overloads, including from, as etc. Also check for "noverloadable built-ins" - they should explicitly fail. Only tested operators defined using procedures - things for template, macro and iterator should be tested in their respective sections.
    • Unicode operators
    • AST based overloading
    • Overloaded call resolution (without generic constraints)
    • Overloaded call resolution in presence of user-defined implicit converters
    • Overloaded call resolution in presence of static paremters. What exactly "can be evaluated at compile-time" means? Related #94 (comment)
    • Argument evaluation order
    • Implicit conversion between procvar types with different calling conventions
    • Multiple value return using procs
    • sink, lent arguments, copying,
    • Type-bound operations such as =destroy, =copy, =sink, =trace
  • Procedure body
    • result variable
    • defer statement.
    • defer interactions with exceptions
    • using declaration for arguments
    • ; for argument declarations
  • Generic procedures
    • Specifying generic parameters
    • Specifying generic parameters with constraints
      • In-place typeclass like A | B
      • Named typeclass
      • inverted generic constraints like not A
    • Static parameters
      • Passing trivial data to the static parameters
      • Passing compound data like objects to the
    • Overload resolution. Selecting best overload resolution candidate in presence of multiple matching overloads
    • Overload resolution for generic procedures in presence of user-defined converters
    • Overload resolution for mixin, bind procedures
    • Inter-module relations for mixin and bind statements in generic bodies
  • Dynamic dispatch - methods

structure vm profiler data output

Implement vm profiler data reporting as a structured data. Formatter proc is located in vmprofiler.dump - it outputs string, so can be almost directly moved to cli_reporter.nim. The profiler data itself is already structured in the ProfileData, so it just has to be moved to the reports definition

+ ProfileInfo* = object
+   time*: float
+   count*: int

+ ProfileData* = ref object
+   data*: TableRef[TLineInfo, ProfileInfo]

  InternalReport* = object of ReportBase
    ## Report generated for the internal compiler workings
    msg*: string
    case kind*: ReportKind
+     of rintVmProfile:
+       profileData: ProfileData

Refactor: move all string formatting for `P(Node|Sym|Type)` to `cli_reporter`

Search through sem* and types modules in order to find leftover procs that were used for error message "formatting". If these procs are only used in cli_reporter, move them to this module instead.

Example: getProcHeader - defined in types.nim, used only in cli_reporter.nim

Procs like these are likely to return string type, so it can be used as a starting hint.

Can't install nimskull compiler on my mac

Description

Can't install nimskull compiler on my mac.

What I Did

I followed the section in https://github.com/nim-works/nimskull where it says "Note: The following commands are for the development version of the compiler."
ie:

git clone https://github.com/nim-works/nimskull.git
cd nimskull
./koch.py boot -d:release
./koch.py tools -d:release

Note that ./koch.py boot -d:release worked with executables are equal: SUCCESS!
... but ./koch.py tools -d:release failed with:

....................................................
Error: system needs: 'nimGCvisit' [rsemSystemNeeds]
cgen.nim(850, 16) compiler msg instantiated here [MsgOrigin]
No stack traceback available
To create a stacktrace, rerun compilation with './koch temp $1 <file>'

FAILURE

My Mac Specs

MacOS Monterey
Version 12.1
MacBook Pro (Retina, 13-inch, Early 2015)
Processor 2.7 GHz Dual-Core Intel Core i5
Memory 16 GB 1867 MHz DDR3
... ie just a laptop

Full Output

[2022-01-21 12:15:34] nblaxall:~$ git clone https://github.com/nim-works/nimskull.git
Cloning into 'nimskull'...
remote: Enumerating objects: 148792, done.
remote: Counting objects: 100% (9542/9542), done.
remote: Compressing objects: 100% (2766/2766), done.
remote: Total 148792 (delta 8480), reused 7643 (delta 6756), pack-reused 139250
Receiving objects: 100% (148792/148792), 105.76 MiB | 9.97 MiB/s, done.
Resolving deltas: 100% (116248/116248), done.
Updating files: 100% (2944/2944), done.
[2022-01-30 13:12:29] nblaxall:~$ cd nimskull
[2022-01-30 13:12:31] nblaxall:~/nimskull$ ./koch.py boot -d:release
Building koch.nim
Bootstrap compiler /Users/nblaxall/nimskull/build/csources/bin/nim-561b417c65791cd8356b5f73620914ceff845d10 not found, building
Fetching bootstrap compiler source
Running: ['git', 'clone', '--depth=1', '--single-branch', 'https://github.com/nim-lang/csources_v1.git', '/Users/nblaxall/nimskull/build/csources']
Cloning into '/Users/nblaxall/nimskull/build/csources'...
remote: Enumerating objects: 1289, done.
remote: Counting objects: 100% (1289/1289), done.
remote: Compressing objects: 100% (260/260), done.
remote: Total 1289 (delta 1185), reused 1106 (delta 1026), pack-reused 0
Receiving objects: 100% (1289/1289), 2.88 MiB | 7.67 MiB/s, done.
Resolving deltas: 100% (1185/1185), done.
Updating files: 100% (8442/8442), done.
Running: ['make', '-s', '-C', '/Users/nblaxall/nimskull/build/csources', '-j', '4']
SUCCESS
Instantiating /Users/nblaxall/nimskull/build/csources/bin/nim-561b417c65791cd8356b5f73620914ceff845d10 as /Users/nblaxall/nimskull/bin/nim-boot
Running: ['/Users/nblaxall/nimskull/bin/nim-boot', 'c', '--hints:off', '--hint:CC:off', '--warning:UnknownMagic:off', '--skipParentCfg', '--skipUserCfg', '--nimcache:/Users/nblaxall/nimskull/nimcache/koch', '--out:/Users/nblaxall/nimskull/tools/koch/koch', '/Users/nblaxall/nimskull/tools/koch/koch.nim']
Running koch.nim
Running: ['/Users/nblaxall/nimskull/tools/koch/koch', 'boot', '-d:release']
iteration: 1
bin/nim-boot c  --skipUserCfg --skipParentCfg -d:nimSourceHash=dce4c78dd0cfac013dbb8e89c1eeccb4d046c04d -d:nimSourceDate=2022-01-29 -d:CompilerVersionSuffix=-dev.20030 -d:nimKochBootstrap --warning[UnknownMagic]:off --nimcache:nimcache/r_macosx_amd64_boot -d:release --compileOnly compiler/nim.nim
Hint: used config file '/Users/nblaxall/nimskull/config/nim.cfg' [Conf]
Hint: used config file '/Users/nblaxall/nimskull/compiler/nim.cfg' [Conf]
Hint: used config file '/Users/nblaxall/nimskull/config/config.nims' [Conf]
Hint: system [Processing]
Hint: since [Processing]
Hint: ansi_c [Processing]
Hint: memory [Processing]
Hint: assertions [Processing]
Hint: miscdollars [Processing]
Hint: digitsutils [Processing]
Hint: iterators [Processing]
Hint: dollars [Processing]
Hint: formatfloat [Processing]
Hint: dragonbox [Processing]
Hint: schubfach [Processing]
Hint: stacktraces [Processing]
Hint: countbits_impl [Processing]
Hint: bitops_utils [Processing]
Hint: widestrs [Processing]
Hint: io [Processing]
Hint: nim [Processing]
Hint: os [Processing]
Hint: strutils [Processing]
Hint: parseutils [Processing]
Hint: math [Processing]
Hint: bitops [Processing]
Hint: macros [Processing]
Hint: fenv [Processing]
Hint: algorithm [Processing]
Hint: enumutils [Processing]
Hint: typetraits [Processing]
Hint: unicode [Processing]
Hint: strimpl [Processing]
Hint: pathnorm [Processing]
Hint: osseps [Processing]
Hint: posix [Processing]
Hint: times [Processing]
Hint: options [Processing]
Hint: extccomp [Processing]
Hint: ropes [Processing]
Hint: hashes [Processing]
Hint: pathutils [Processing]
Hint: platform [Processing]
Hint: lineinfos [Processing]
Hint: tables [Processing]
Hint: ast_types [Processing]
Hint: reports [Processing]
Hint: packedsets [Processing]
Hint: vm_enums [Processing]
Hint: int128 [Processing]
Hint: nilcheck_enums [Processing]
Hint: condsyms [Processing]
Hint: strtabs [Processing]
Hint: options [Processing]
Hint: sets [Processing]
Hint: prefixmatches [Processing]
Hint: nimpaths [Processing]
Hint: terminal [Processing]
Hint: strformat [Processing]
Hint: colors [Processing]
Hint: termios [Processing]
Hint: globs [Processing]
Hint: msgs [Processing]
Hint: strutils2 [Processing]
/Users/nblaxall/nimskull/compiler/front/msgs.nim(431, 16) Warning: [IMPLEMENT] Convert report to string message ? [User]
Hint: osproc [Processing]
Hint: streams [Processing]
Hint: cpuinfo [Processing]
Hint: streamwrapper [Processing]
Hint: deques [Processing]
Hint: kqueue [Processing]
Hint: sha1 [Processing]
Hint: endians [Processing]
Hint: sequtils [Processing]
Hint: json [Processing]
Hint: lexbase [Processing]
Hint: parsejson [Processing]
Hint: decode_helpers [Processing]
Hint: jsonutils [Processing]
Hint: sugar [Processing]
Hint: underscored_calls [Processing]
Hint: main [Processing]
Hint: with [Processing]
Hint: llstream [Processing]
Hint: ast [Processing]
Hint: idents [Processing]
Hint: wordrecg [Processing]
Hint: lexer [Processing]
Hint: nimlexbase [Processing]
Hint: syntaxes [Processing]
Hint: parser [Processing]
Hint: filters [Processing]
Hint: renderer [Processing]
Hint: filter_tmpl [Processing]
Hint: nimconf [Processing]
Hint: commands [Processing]
Hint: parseopt [Processing]
Hint: nimblecmd [Processing]
Hint: nversion [Processing]
Hint: strscans [Processing]
Hint: scriptconfig [Processing]
Hint: modules [Processing]
Hint: astalgo [Processing]
Hint: intsets [Processing]
Hint: passes [Processing]
Hint: modulegraphs [Processing]
Hint: md5 [Processing]
Hint: btrees [Processing]
Hint: packed_ast [Processing]
Hint: bitabs [Processing]
Hint: rodfiles [Processing]
Hint: ic [Processing]
Hint: reorder [Processing]
Hint: modulepaths [Processing]
Hint: magicsys [Processing]
Hint: errorhandling [Processing]
Hint: debugutils [Processing]
Hint: replayer [Processing]
Hint: trees [Processing]
Hint: cgmeth [Processing]
Hint: types [Processing]
Hint: sempass2 [Processing]
Hint: errorreporting [Processing]
Hint: varpartitions [Processing]
Hint: typeallowed [Processing]
Hint: semdata [Processing]
Hint: vmdef [Processing]
Hint: isolation_check [Processing]
Hint: guards [Processing]
Hint: nimsets [Processing]
Hint: bitsets [Processing]
Hint: saturate [Processing]
Hint: semfold [Processing]
Hint: nilcheck [Processing]
Hint: treetab [Processing]
Hint: liftdestructors [Processing]
Hint: sighashes [Processing]
Hint: lowerings [Processing]
Hint: ccgutils [Processing]
Hint: cgendata [Processing]
Hint: ndi [Processing]
Hint: sem [Processing]
Hint: astmsgs [Processing]
Hint: enumtostr [Processing]
Hint: linter [Processing]
Hint: importer [Processing]
Hint: lookups [Processing]
Hint: prettybase [Processing]
Hint: editdistance [Processing]
Hint: heapqueue [Processing]
Hint: sigmatch [Processing]
Hint: typesrenderer [Processing]
Hint: semtypinst [Processing]
Hint: concepts [Processing]
Hint: parampatterns [Processing]
Hint: astrepr [Processing]
Hint: colortext [Processing]
Hint: semmacrosanity [Processing]
Hint: procfind [Processing]
Hint: pragmas [Processing]
Hint: transf [Processing]
Hint: liftlocals [Processing]
Hint: closureiters [Processing]
Hint: lambdalifting [Processing]
Hint: aliases [Processing]
Hint: patterns [Processing]
Hint: evaltempl [Processing]
Hint: active [Processing]
Hint: pluginsupport [Processing]
Hint: locals [Processing]
Hint: itersgen [Processing]
Hint: vm [Processing]
Hint: cli_reporter [Processing]
Hint: macrocacheimpl [Processing]
Hint: vmprofiler [Processing]
Hint: gorgeimpl [Processing]
Hint: vmdeps [Processing]
Hint: vmgen [Processing]
/Users/nblaxall/nimskull/compiler/vm/vmgen.nim(52, 8) Warning: imported and not used: 'debugutils' [UnusedImport]
Hint: vmconv [Processing]
Hint: spawn [Processing]
/Users/nblaxall/nimskull/compiler/sem/semstmts.nim(631, 23) Warning: transition proc, remove usage as soon as possible; wrapIfErrorInSubTree is deprecated [Deprecated]
Hint: passaux [Processing]
Hint: depends [Processing]
Hint: cgen [Processing]
Hint: rodutils [Processing]
Hint: injectdestructors [Processing]
Hint: dfa [Processing]
Hint: asciitables [Processing]
Hint: optimizer [Processing]
Hint: semparallel [Processing]
Hint: dynlib [Processing]
Hint: cbackend [Processing]
Hint: dce [Processing]
Hint: integrity [Processing]
Hint: navigator [Processing]
Hint: jsgen [Processing]
Hint: sourcemap [Processing]
Hint: docgen [Processing]
Hint: xmltree [Processing]
Hint: renderverbatim [Processing]
Hint: rst [Processing]
Hint: rstast [Processing]
Hint: lists [Processing]
Hint: highlite [Processing]
Hint: rstgen [Processing]
Hint: strbasics [Processing]
Hint: uri [Processing]
Hint: base64 [Processing]
Hint: nodejs [Processing]
Hint: docgen2 [Processing]
Hint: cmdlinehelper [Processing]
Hint: browsers [Processing]
Hint: operation successful (198605 lines compiled; 17.330 sec total; 805.723MiB peakmem; Release Build) [SuccessX]
bin/nim-boot jsonscript  --skipUserCfg --skipParentCfg -d:nimSourceHash=dce4c78dd0cfac013dbb8e89c1eeccb4d046c04d -d:nimSourceDate=2022-01-29 -d:CompilerVersionSuffix=-dev.20030 -d:nimKochBootstrap --warning[UnknownMagic]:off --nimcache:nimcache/r_macosx_amd64_boot -d:release compiler/nim.nim
Hint: used config file '/Users/nblaxall/nimskull/config/nim.cfg' [Conf]
Hint: used config file '/Users/nblaxall/nimskull/compiler/nim.cfg' [Conf]
Hint: used config file '/Users/nblaxall/nimskull/config/config.nims' [Conf]
CC: stdlib_digitsutils.nim
CC: stdlib_assertions.nim
CC: stdlib_dragonbox.nim
CC: stdlib_schubfach.nim
CC: stdlib_formatfloat.nim
CC: stdlib_dollars.nim
CC: stdlib_io.nim
CC: stdlib_system.nim
CC: stdlib_parseutils.nim
CC: stdlib_math.nim
CC: stdlib_algorithm.nim
CC: stdlib_enumutils.nim
CC: stdlib_unicode.nim
CC: stdlib_strutils.nim
CC: stdlib_pathnorm.nim
CC: stdlib_posix.nim
CC: stdlib_options.nim
CC: stdlib_times.nim
CC: stdlib_os.nim
CC: stdlib_hashes.nim
CC: utils/pathutils.nim
CC: utils/ropes.nim
CC: utils/platform.nim
CC: stdlib_tables.nim
CC: ast/ast_types.nim
CC: stdlib_packedsets.nim
CC: vm/vm_enums.nim
CC: utils/int128.nim
CC: sem/nilcheck_enums.nim
CC: ast/reports.nim
CC: ast/lineinfos.nim
CC: stdlib_strtabs.nim
CC: stdlib_sets.nim
CC: utils/prefixmatches.nim
CC: modules/nimpaths.nim
CC: stdlib_strformat.nim
CC: stdlib_terminal.nim
CC: stdlib_globs.nim
CC: front/options.nim
CC: front/condsyms.nim
CC: utils/strutils2.nim
CC: front/msgs.nim
CC: stdlib_streams.nim
CC: stdlib_cpuinfo.nim
CC: stdlib_osproc.nim
CC: stdlib_sha1.nim
CC: stdlib_lexbase.nim
CC: stdlib_parsejson.nim
CC: stdlib_json.nim
CC: stdlib_jsonutils.nim
CC: backend/extccomp.nim
CC: ast/llstream.nim
CC: ast/wordrecg.nim
CC: ast/idents.nim
CC: ast/ast.nim
CC: ast/nimlexbase.nim
CC: ast/lexer.nim
CC: ast/parser.nim
CC: ast/renderer.nim
CC: ast/filters.nim
CC: ast/filter_tmpl.nim
CC: ast/syntaxes.nim
CC: stdlib_parseopt.nim
CC: modules/nimblecmd.nim
CC: front/commands.nim
CC: ast/astalgo.nim
CC: stdlib_md5.nim
CC: utils/btrees.nim
CC: ic/rodfiles.nim
CC: ic/bitabs.nim
CC: ic/packed_ast.nim
CC: ic/ic.nim
CC: modules/modulegraphs.nim
CC: modules/modulepaths.nim
CC: sem/reorder.nim
CC: sem/passes.nim
CC: ast/errorhandling.nim
CC: modules/magicsys.nim
CC: ast/trees.nim
CC: ast/types.nim
CC: ast/errorreporting.nim
CC: vm/vmdef.nim
CC: sem/semdata.nim
CC: sem/typeallowed.nim
CC: sem/isolation_check.nim
CC: sem/varpartitions.nim
CC: utils/bitsets.nim
CC: ast/nimsets.nim
CC: utils/saturate.nim
CC: sem/guards.nim
CC: sem/semfold.nim
CC: ast/treetab.nim
CC: sem/nilcheck.nim
CC: sem/sighashes.nim
CC: sem/lowerings.nim
CC: ast/ndi.nim
CC: backend/cgendata.nim
CC: backend/ccgutils.nim
CC: sem/liftdestructors.nim
CC: sem/sempass2.nim
CC: backend/cgmeth.nim
CC: ic/replayer.nim
CC: modules/modules.nim
CC: ast/astmsgs.nim
CC: ast/enumtostr.nim
CC: ast/linter.nim
CC: nimfix/prettybase.nim
CC: stdlib_editdistance.nim
CC: stdlib_heapqueue.nim
CC: sem/lookups.nim
CC: ast/typesrenderer.nim
CC: sem/concepts.nim
CC: sem/semtypinst.nim
CC: sem/parampatterns.nim
CC: sem/sigmatch.nim
CC: modules/importer.nim
CC: stdlib_colortext.nim
CC: utils/astrepr.nim
CC: sem/semmacrosanity.nim
CC: sem/procfind.nim
CC: sem/pragmas.nim
CC: sem/liftlocals.nim
CC: sem/lambdalifting.nim
CC: sem/closureiters.nim
CC: sem/transf.nim
CC: sem/aliases.nim
CC: sem/patterns.nim
CC: sem/evaltempl.nim
CC: utils/pluginsupport.nim
CC: plugins/locals.nim
CC: plugins/itersgen.nim
CC: plugins/active.nim
CC: front/cli_reporter.nim
CC: sem/macrocacheimpl.nim
CC: vm/vmprofiler.nim
CC: vm/gorgeimpl.nim
CC: vm/vmdeps.nim
CC: vm/vmgen.nim
CC: vm/vmconv.nim
CC: vm/vm.nim
CC: sem/spawn.nim
CC: sem/sem.nim
CC: front/scriptconfig.nim
CC: front/nimconf.nim
CC: sem/passaux.nim
CC: modules/depends.nim
CC: sem/rodutils.nim
CC: sem/dfa.nim
CC: sem/optimizer.nim
CC: sem/injectdestructors.nim
CC: sem/semparallel.nim
CC: stdlib_dynlib.nim
CC: backend/cgen.nim
CC: ic/dce.nim
CC: ic/cbackend.nim
CC: ic/integrity.nim
CC: ic/navigator.nim
CC: sem/sourcemap.nim
CC: backend/jsgen.nim
CC: stdlib_xmltree.nim
CC: ast/renderverbatim.nim
CC: stdlib_rstast.nim
CC: stdlib_lists.nim
CC: stdlib_highlite.nim
CC: stdlib_rst.nim
CC: stdlib_rstgen.nim
CC: stdlib_base64.nim
CC: stdlib_uri.nim
CC: tools/docgen.nim
CC: tools/docgen2.nim
CC: front/main.nim
CC: front/cmdlinehelper.nim
CC: stdlib_browsers.nim
CC: nim.nim
Hint:  [Link]
Hint: operation successful (9901 lines compiled; 76.376 sec total; 10.59MiB peakmem; Release Build) [SuccessX]
iteration: 2
compiler/nim1 c  --skipUserCfg --skipParentCfg -d:nimSourceHash=dce4c78dd0cfac013dbb8e89c1eeccb4d046c04d -d:nimSourceDate=2022-01-29 -d:CompilerVersionSuffix=-dev.20030 --nimcache:nimcache/r_macosx_amd64 -d:release --compileOnly compiler/nim.nim
.....................................................................................................................
/Users/nblaxall/nimskull/compiler/front/msgs.nim(431, 16) Warning: [IMPLEMENT] Convert report to string message ? [User]
.......................................................................................................................
/Users/nblaxall/nimskull/compiler/vm/vmgen.nim(52, 8) Warning: imported and not used: 'debugutils' [UnusedImport]
............
/Users/nblaxall/nimskull/compiler/sem/semstmts.nim(631, 23) Warning: transition proc, remove usage as soon as possible; wrapIfErrorInSubTree is deprecated [Deprecated]
............................................
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(1277, 26) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(755, 15) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(755, 15) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(1059, 28) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(235, 62) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/lib/pure/parsejson.nim(143, 25) Hint: Implicit conversion: Receiver 'BaseLexer' will not receive fields of sub-type 'JsonParser' [ImplicitObjConv]
Hint: gc: refc; opt: speed; release 0 lines; 28.184s; 840.828MiB peakmem; proj: /Users/nblaxall/nimskull/compiler/nim.nim; out: /Users/nblaxall/nimskull/nimcache/r_macosx_amd64/nim.json [SuccessX]
compiler/nim1 jsonscript  --skipUserCfg --skipParentCfg -d:nimSourceHash=dce4c78dd0cfac013dbb8e89c1eeccb4d046c04d -d:nimSourceDate=2022-01-29 -d:CompilerVersionSuffix=-dev.20030 --nimcache:nimcache/r_macosx_amd64 -d:release compiler/nim.nim
Hint: 9901 lines; 113.293s; 10.773MiB peakmem; proj: /Users/nblaxall/nimskull/compiler/nim.nim; out: /Users/nblaxall/nimskull/compiler/nim [SuccessX]
msgs.nim(792, 15) compiler msg instantiated here [MsgOrigin]
(0, 1) compiler report submitted here [MsgOrigin]
[GC] total memory: 11296768
[GC] occupied memory: 9863216
[GC] stack scans: 1003
[GC] stack cells: 1544
[GC] cycle collections: 0
[GC] max threshold: 0
[GC] zct capacity: 1024
[GC] max cycle table size: 0
[GC] max pause time [ms]: 0
[GC] max stack size: 53632

iteration: 3
compiler/nim2 c  --skipUserCfg --skipParentCfg -d:nimSourceHash=dce4c78dd0cfac013dbb8e89c1eeccb4d046c04d -d:nimSourceDate=2022-01-29 -d:CompilerVersionSuffix=-dev.20030 --nimcache:nimcache/r_macosx_amd64 -d:release --compileOnly compiler/nim.nim
.....................................................................................................................
/Users/nblaxall/nimskull/compiler/front/msgs.nim(431, 16) Warning: [IMPLEMENT] Convert report to string message ? [User]
.......................................................................................................................
/Users/nblaxall/nimskull/compiler/vm/vmgen.nim(52, 8) Warning: imported and not used: 'debugutils' [UnusedImport]
............
/Users/nblaxall/nimskull/compiler/sem/semstmts.nim(631, 23) Warning: transition proc, remove usage as soon as possible; wrapIfErrorInSubTree is deprecated [Deprecated]
............................................
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(1277, 26) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(755, 15) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(755, 15) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(1059, 28) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/compiler/ast/lexer.nim(235, 62) Hint: Implicit conversion: Receiver 'TBaseLexer' will not receive fields of sub-type 'Lexer' [ImplicitObjConv]
/Users/nblaxall/nimskull/lib/pure/parsejson.nim(143, 25) Hint: Implicit conversion: Receiver 'BaseLexer' will not receive fields of sub-type 'JsonParser' [ImplicitObjConv]
Hint: gc: refc; opt: speed; release 0 lines; 20.917s; 839.039MiB peakmem; proj: /Users/nblaxall/nimskull/compiler/nim.nim; out: /Users/nblaxall/nimskull/nimcache/r_macosx_amd64/nim.json [SuccessX]
compiler/nim2 jsonscript  --skipUserCfg --skipParentCfg -d:nimSourceHash=dce4c78dd0cfac013dbb8e89c1eeccb4d046c04d -d:nimSourceDate=2022-01-29 -d:CompilerVersionSuffix=-dev.20030 --nimcache:nimcache/r_macosx_amd64 -d:release compiler/nim.nim
Hint: 9901 lines; 0.285s; 10.742MiB peakmem; proj: /Users/nblaxall/nimskull/compiler/nim.nim; out: /Users/nblaxall/nimskull/compiler/nim [SuccessX]
msgs.nim(792, 15) compiler msg instantiated here [MsgOrigin]
(0, 1) compiler report submitted here [MsgOrigin]
[GC] total memory: 11264000
[GC] occupied memory: 9760752
[GC] stack scans: 880
[GC] stack cells: 1759
[GC] cycle collections: 0
[GC] max threshold: 0
[GC] zct capacity: 1536
[GC] max cycle table size: 0
[GC] max pause time [ms]: 0
[GC] max stack size: 57968

executables are equal: SUCCESS!
[2022-01-30 13:18:04] nblaxall:~/nimskull$ ./koch.py tools -d:release
Building koch.nim
Instantiating /Users/nblaxall/nimskull/build/csources/bin/nim-561b417c65791cd8356b5f73620914ceff845d10 as /Users/nblaxall/nimskull/bin/nim-boot
Running: ['/Users/nblaxall/nimskull/bin/nim-boot', 'c', '--hints:off', '--hint:CC:off', '--warning:UnknownMagic:off', '--skipParentCfg', '--skipUserCfg', '--nimcache:/Users/nblaxall/nimskull/nimcache/koch', '--out:/Users/nblaxall/nimskull/tools/koch/koch', '/Users/nblaxall/nimskull/tools/koch/koch.nim']
Running koch.nim
Running: ['/Users/nblaxall/nimskull/tools/koch/koch', 'tools', '-d:release']
bin/nim c -o:bin/nimsuggest -d:danger -d:nimSourceHash=dce4c78dd0cfac013dbb8e89c1eeccb4d046c04d -d:nimSourceDate=2022-01-29 -d:CompilerVersionSuffix=-dev.20030 -d:release nimsuggest/nimsuggest.nim
....................................................
Error: system needs: 'nimGCvisit' [rsemSystemNeeds]
cgen.nim(850, 16) compiler msg instantiated here [MsgOrigin]
No stack traceback available
To create a stacktrace, rerun compilation with './koch temp $1 <file>'

FAILURE

Spec - remove, redesign or make non-experimental

  • Experimental features that make sense to keep around
    • View types
    • Dot operators
    • not nil annotation
    • User-defined numeric literals
    • Ast-based overloading. This is related to term rewriting macros, but easier to specify correctly, so might work properly
    • noalias
    • Do notation
    • Term rewriting macros - current implementation is broken with dysfunctional {.noRewrite.} pragma annotation, but other parts need to be specified.
    • Concepts - old concept implementation was broken due to the bad sem implementation, but current plan is to make old concepts work again, so as much as possible (read - anything that happened to work now) need to be specified.
  • Questionable if these experimental feature should even be in the language.
    • Named argument overloading
    • Package level objects
    • Case statement macros - absolutely useless feature
  • Already in the language but should be checked for sanity
    • {.push.} and {.pop.} system
    • --multimethods:on - does anyone even use these?

Related - Spec - comments on reviews_

refactor compiler CLI parser

Follow-up on

CLI parser for the compiler itself should be a proc parseArgs(seq[string], var ActiveConfiguration): seq[ExternalReport] and would allow it to be reused elsewhere.ExternalReport should represent errors and failures in the CLI processing. It does not contain any special nodes and can be moved from reports.ExternalReport to report_enums.ExternalReport and reused later.

Clean up the CLI parser implementation - parseopt is good enough for now except theproc initOptParser(cmdline = ""; part where it forces you to join elements together.

Spec - macros, `untyped`, `typed`, macro API

  • static[T] for macro arguments
  • How macro expansions affect line information for stack traces - {.line.}, lineInfoObj() and other elements
  • bindSym interaction with variables in general and {.strdefine.} specifically

Spec - core concepts

  • Core language concepts
    • expression
    • statement
    • errors
    • type inference
    • resolution, dispatch, and overloads
    • module resolution
    • type tagging, untagging, and comparison
    • differences between backends
    • core defines and the environment
    • compile time
    • side effect
    • typed and untyped macros - this one is tricky, but the whole concept of semantic analysis is not something an average user probably familiar with, so it warrants special attention.
    • variables, scopes, assignments (to a single variable, to multiple variables, how many times an expression for a multivar assign is evaluated?)
    • destructors, sinks, moves? I'm not sure which part of the specification it belongs to - procedures (because of sink arguments), regular variables, scoping, something else? How {.global.} destructor is handled btw
    • literals - preferably tests should include a solution that would also test things separately from the lexer, in a way that would allow specification to ensure changes to the lexer don't propagate bugs. Something like int(2f) == 2, for i in 0 .. 2: inc tmp; tmp == 2, 1 + 1 == 2 etc.
  • Core compilation concepts
    • Project file/module
    • Package (not much more than a directory with a nim file/module(s))
  • Basic control flow constructs
    • while + continue/break
      • while statement scoping
    • if
      • Using as a statement
      • Using as expression
      • if statement scoping
    • case
      • Case expressions
      • Allowed types of variables to be used
      • Case for strings
      • Case for enums, enum sets, enum ranges
      • else, elif branches for case statements
      • Using case as an expression
      • of branch variable scoping
    • block
      • break to labeled block
      • break to block
      • block variable scoping
    • try/catch/finally (with and without user-defined exceptions)
      • Try expression
      • finally in contexts different from simple exception
    • Control flow transfer between procedure calls

testament add `knownIssue` and simplify `disabled`

Testament presently treats disabled to mean two things:

  1. this tests isn't working for some reason (issue, CI woes, etc) don't run it
  2. disable it in certain parts of the test execution matrix.

The idea here is to:

  • create a knownIssue (to be finalized) field in the testament spec that allows either:
    • a truth-y value, including a reference to an issue
    • a false-y value, which is also the default
  • this field is interpreted as disable due to a broader issue
  • while the existing disabled field will now no longer accept booleans, and instead only carry build matrix related disabling

See original discussion link for full context below.


Q&A distilled:

How will this be used?

This is follow-on work, but the intention is to enable:

  • CI can then run knownIssue tests and if they start working as expected it can take actions to update issues/PRs referencing it or other such nice to haves
  • this also allows for a fast path of issue to tests case, where manual correlation is less burdensome; instead effort can be spent on refining the analysis (likely multi-factor) and development of associated specifications and test cases

How do knownIssue and disabled fit together with everything else?

This handy diagram helps explain much of this:


Links and References

Originally posted by @haxscramper in #60 (comment)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.