nim-lang / Nim

Nim is a statically typed compiled systems programming language. It combines successful concepts from mature languages like Python, Ada and Modula. Its design focuses on efficiency, expressiveness, and elegance (in that order of priority).
https://nim-lang.org
Other
16.43k stars 1.47k forks source link

Make emit pragma work as expected for JS target with sections #13376

Open kristianmandrup opened 4 years ago

kristianmandrup commented 4 years ago

Summary

Currently there seems to be no way to direct emits to certain sections of the output when the target is js.

Another issue is that the pragma import form of:

var
  x {.importjs: "@ = x$$".}: JsObject

Does not seem to be currently possible, as it is for proc.

Description

Adds support for generating include statements for various compiler targets, including both C and Ecmascript/Javascript family

According to the docs, it should support the following special variants:

I've tried the following

import macros, jsffi
{.emit: """/*INCLUDESECTION*/import { x as x$$  } from './aba'""".}
var
  x {.importjs: "@ = x$$".}: JsObject

Compiling with nim js -d:nodejs var.nim

Getting the output:

var object_id_51437 = [0];
/*INCLUDESECTION*/import { x as x$$  } from './aba'

Additional Information

There are no unit tests for either determineSection or genEmit

proc determineSection(n: PNode): TCFileSection =
  result = cfsProcHeaders
  if n.len >= 1 and n.sons[0].kind in {nkStrLit..nkTripleStrLit}:
    let sec = n.sons[0].strVal
    if sec.startsWith("/*TYPESECTION*/"): result = cfsTypes
    elif sec.startsWith("/*VARSECTION*/"): result = cfsVars
    elif sec.startsWith("/*INCLUDESECTION*/"): result = cfsHeaders

proc genEmit(p: BProc, t: PNode) =
  var s = genAsmOrEmitStmt(p, t.sons[1])
  if p.prc == nil:
    # top level emit pragma?
    let section = determineSection(t[1])
    genCLineDir(p.module.s[section], t.info, p.config)
    add(p.module.s[section], s)
  else:
    genLineDir(p, t)
    line(p, cpsStmts, s)

I believe, that if p.prc == nil in my example, so that it never consults if there is a section identifier. Not sure why it shouldn't always ask this question before emitting?

proc registerGcRoot(p: BProc, v: PSym) =
  if p.config.selectedGC in {gcMarkAndSweep, gcDestructors, gcV2, gcRefc} and
      containsGarbageCollectedRef(v.loc.t):
    # we register a specialized marked proc here; this has the advantage
    # that it works out of the box for thread local storage then :-)
    let prc = genTraverseProcForGlobal(p.module, v, v.info)

prc seems to be linked to the Garbage Collector somehow? Looks like this is a very brittle approach for the emit case. Instead it should likely determine if the target supports sections.

links

kristianmandrup commented 4 years ago

I found the following on the Nim support for ES modules topic:

The Js backend support was my main draw to Nim (one ring to rule them all, back to front) so sad to see that little attention is given to the JS backend

kristianmandrup commented 4 years ago

I would propose changing the genEmit to sth like this, leveraging the options of p

proc genEmit(p: BProc, t: PNode) =
  var options = p.options
  var s = genAsmOrEmitStmt(p, t.sons[1])
  var withSections = options.sections or p.prc == nil
  if withSections:
    # top level emit pragma?
    let section = determineSection(t[1])

Then in jsgen.nim set options.sections to true

proc gen(p: PProc, n: PNode, r: var TCompRes) =
  p.options.sections = true
  r.typ = etyNone
kristianmandrup commented 4 years ago

My current best attempt at fixing this behavior

In options.nim add optSections flag

TOption* = enum      # **keep binary compatible**
    optNone, optObjCheck, optFieldCheck, optRangeCheck, optBoundsCheck,
    optOverflowCheck, optNilCheck, optRefCheck,
    optNaNCheck, optInfCheck, optStyleCheck,
    optAssert, optLineDir, optWarns, optHints,
    optOptimizeSpeed, optOptimizeSize, optStackTrace, # stack tracing support
    optLineTrace,      # line tracing support (includes stack tracing)
    optByRef,          # use pass by ref for objects
                       # (for interfacing with C)
    optProfiler,       # profiler turned on
    optImplicitStatic, # optimization: implicit at compile time
                       # evaluation
    optTrMacros,       # en/disable pattern matching
    optMemTracker,
    optLaxStrings,
    optNilSeqs,
    optOldAst,
    optSections

Then in genEmit of ccstmts.nim, add something like the following...

proc genEmit(p: BProc, t: PNode) =
  var s = genAsmOrEmitStmt(p, t[1])
  echo "genEmit: options"
  echo p.options

  var prc = p.prc
  var hasSectionsOpt = prc and prc.options and optSections in prc.options
  echo "hasSectionsOpt:" & $hasSectionsOpt    
  var hasNoPrc = prc == nil
  echo "hasNoPrc:" & $hasNoPrc  
  var useSections = hasSectionsOpt or hasNoPrc
  echo "useSections:" & $useSections

  if useSections:
    # top level emit pragma?
    let section = determineSection(t[1])

In jsgen/nim add optSections option flag to prc.options

proc genModule(p: PProc, n: PNode) =
  p.prc.options.incl optSections

Then compile to js on sandbox/try.nim:

var x = 2

$ nim js sandbox/try.nim

Unfortunately I keep getting this weird error:

nim js sandbox/try.nim 
Hint: used config file '/Users/kristianmandrup/repos/nim-projects/Nim/config/nim.cfg' [Conf]
Hint: used config file '/Users/kristianmandrup/repos/nim-projects/Nim/config/config.nims' [Conf]
Hint: system [Processing]
SIGSEGV: Illegal storage access. (Attempt to read from nil?)
ghost commented 4 years ago

@kristianmandrup you should use "./koch temp js path/to/try.nim" to (re)compile the compiler in debug mode and it will show full stack trace for crashes

Araq commented 4 years ago

I can see where you're coming from but

According to the docs, it should support the following special variants

These variants make no sense for JS as JS has no "type sections".

The Js backend support was my main draw to Nim (one ring to rule them all, back to front) so sad to see that little attention is given to the JS backend

Well we keep supporting it but Nim is open source, stuff that people work on/with is what gets improved. Your PR is really welcome!

kristianmandrup commented 4 years ago

Hi @Araq. Thanks for the quick reply. You are right, but most "real life" JS imports modules so at least the include section should be open for emit. Also, why not allows TypeScript as the target and allow us to emit interfaces. Just an idea.

On that note, it would be awesome if there was an option to set the extension of the file being output. Modern node (with ES module support) requires files be named .mjs to work with ES modules.

kristianmandrup commented 4 years ago

Any suggestions for how to best allow for this in Nim (how to pick up and pass on config/options) greatly appreciated and I will work on PR

kristianmandrup commented 4 years ago

I would think I could leverage this part then? It calls genModule and has access to globals (config) and module options which I could use to populate p or p.prc being passed down to the generators. newProc looks to be the key in this regard.

proc myProcess(b: PPassContext, n: PNode): PNode =
  result = n
  let m = BModule(b)
  if passes.skipCodegen(m.config, n): return n
  if m.module == nil: internalError(m.config, n.info, "myProcess")
  let globals = PGlobals(m.graph.backend)
  var p = newProc(globals, m, nil, m.module.options)
  p.unique = globals.unique
  genModule(p, n)
kristianmandrup commented 4 years ago

From what I can see, the best way would likely be to leverage ConfigRef available on m.config How/where is this config object populated?

  ConfigRef* = ref object          ## every global configuration
                                   ## fields marked with '*' are subject to
                                   ## the incremental compilation mechanisms
                                   ## (+) means "part of the dependency"
    target*: Target                # (+)
    linesCompiled*: int            # all lines that have been compiled
    options*: TOptions             # (+)
    globalOptions*: TGlobalOptions # (+)
    macrosToExpand*: StringTableRef
    m*: MsgConfig
    evalTemplateCounter*: int
    evalMacroCounter*: int
    exitcode*: int8
    cmd*: TCommands                # the command
    selectedGC*: TGCMode           # the selected GC (+)
    exc*: ExceptionSystem
    verbosity*: int                # how verbose the compiler is
    numberOfProcessors*: int       # number of processors
    evalExpr*: string              # expression for idetools --eval
    lastCmdTime*: float            # when caas is enabled, we measure each command
    symbolFiles*: SymbolFilesOption

    cppDefines*: HashSet[string]   # (*)
    headerFile*: string
    features*: set[Feature]
    legacyFeatures*: set[LegacyFeature]
    arguments*: string             ## the arguments to be passed to the program that
                                   ## should be run
    ideCmd*: IdeCmd
    oldNewlines*: bool
    cCompiler*: TSystemCC
    enableNotes*: TNoteKinds
    disableNotes*: TNoteKinds
    foreignPackageNotes*: TNoteKinds
    notes*: TNoteKinds
    mainPackageNotes*: TNoteKinds
    mainPackageId*: int
    errorCounter*: int
    hintCounter*: int
    warnCounter*: int
    errorMax*: int
    maxLoopIterationsVM*: int      ## VM: max iterations of all loops
    configVars*: StringTableRef
    symbols*: StringTableRef       ## We need to use a StringTableRef here as defined
                                   ## symbols are always guaranteed to be style
                                   ## insensitive. Otherwise hell would break lose.
    packageCache*: StringTableRef
    nimblePaths*: seq[AbsoluteDir]
    searchPaths*: seq[AbsoluteDir]
    lazyPaths*: seq[AbsoluteDir]
    outFile*: RelativeFile
    outDir*: AbsoluteDir
    prefixDir*, libpath*, nimcacheDir*: AbsoluteDir
    dllOverrides, moduleOverrides*, cfileSpecificOptions*: StringTableRef
    projectName*: string           # holds a name like 'nim'
    projectPath*: AbsoluteDir      # holds a path like /home/alice/projects/nim/compiler/
    projectFull*: AbsoluteFile     # projectPath/projectName
    projectIsStdin*: bool          # whether we're compiling from stdin
    projectMainIdx*: FileIndex     # the canonical path id of the main module
    command*: string               # the main command (e.g. cc, check, scan, etc)
    commandArgs*: seq[string]      # any arguments after the main command
    commandLine*: string
    extraCmds*: seq[string]        # for writeJsonBuildInstructions
    keepComments*: bool            # whether the parser needs to keep comments
    implicitImports*: seq[string]  # modules that are to be implicitly imported
    implicitIncludes*: seq[string] # modules that are to be implicitly included
    docSeeSrcUrl*: string          # if empty, no seeSrc will be generated. \
    # The string uses the formatting variables `path` and `line`.
    docRoot*: string               ## see nim --fullhelp for --docRoot

      # the used compiler
    cIncludes*: seq[AbsoluteDir]   # directories to search for included files
    cLibs*: seq[AbsoluteDir]       # directories to search for lib files
    cLinkedLibs*: seq[string]      # libraries to link

    externalToLink*: seq[string]   # files to link in addition to the file
                                   # we compiled (*)
    linkOptionsCmd*: string
    compileOptionsCmd*: seq[string]
    linkOptions*: string           # (*)
    compileOptions*: string        # (*)
    cCompilerPath*: string
    toCompile*: CfileList          # (*)
    suggestionResultHook*: proc (result: Suggest) {.closure.}
    suggestVersion*: int
    suggestMaxResults*: int
    lastLineInfo*: TLineInfo
    writelnHook*: proc (output: string) {.
        closure.}                  # cannot make this gcsafe yet because of Nimble
    structuredErrorHook*: proc (config: ConfigRef; info: TLineInfo; msg: string;
                                severity: Severity) {.closure, gcsafe.}
    cppCustomNamespace*: string
kristianmandrup commented 4 years ago

My issue now is that genEmit does not seem to be triggered with:

{.emit: "/*INCLUDESECTION*/import { x } from './abc'" .}
var x = 2
echo x

Strange, why not?

proc genPragma(p: BProc, n: PNode) =
  for it in n.sons:
    case whichPragma(it)
    of wEmit: genEmit(p, it)
kristianmandrup commented 4 years ago

My best attempt so far:

specs.nim

  TTarget* = enum
    targetC = "C"
    targetCpp = "C++"
    targetObjC = "ObjC"
    targetJS = "JS"
    targetMJS = "MJS"
    targetTS = "TS"

const
  targetToExt*: array[TTarget, string] = ["nim.c", "nim.cpp", "nim.m", "js", "mjs", "ts"]
  targetToCmd*: array[TTarget, string] = ["c", "cpp", "objc", "js", "mjs", "ts"]

testament.nim

proc generatedFile(test: TTest, target: TTarget): string =
  if target == targetJS:
    result = test.name.changeFileExt("js")
  elif target == targetMJS:
    result = test.name.changeFileExt("mjs")
  elif target == targetTS:
    result = test.name.changeFileExt("ts")  
  else:

compiler/ccgstmts.nim

proc isSectionAvailableInTarget(sectionId: string, targetSections: seq[auto] = @[]): bool =
  sectionId in targetSections

proc useSection(secStr: string, sectionMarker: string, targetSections: seq[auto] = @[]): bool =
  var isAvailable = isSectionAvailableInTarget(secStr, targetSections)
  secStr.startsWith("/*" & sectionMarker & "SECTION*/") and isAvailable

proc determineSection(n: PNode, targetSections: seq[auto] = @[]): TCFileSection =
  result = cfsProcHeaders
  if n.len >= 1 and n[0].kind in {nkStrLit..nkTripleStrLit}:
    let sec = n[0].strVal
    if useSection(sec, "TYPE", targetSections): result = cfsTypes
    elif useSection(sec, "VAR", targetSections): result = cfsVars
    elif useSection(sec, "INCLUDE", targetSections): result = cfsHeaders

proc genEmit(p: BProc, t: PNode) =
  var s = genAsmOrEmitStmt(p, t[1])
  echo "genEmit"
  echo p.config.options

  let config = p.config

  echo "include sections and Include"
  p.options.incl optSections
  p.options.incl optIncludeSection
  echo p.options
  let opts = p.options
  echo opts
  var hasSections, hasVarSection, hasIncludeSection, hasTypeSection = false
  if opts.len > 0:
    echo "has options"
    hasSections = optSections in opts
    hasVarSection = optVarSection in opts
    hasIncludeSection = optIncludeSection in opts
    hasTypeSection = optTypeSection in opts

  var targetSections: seq[string] = @[]
  if hasIncludeSection:
    targetSections.add "INCLUDE" 
  if hasTypeSection:
    targetSections.add "TYPE" 
  if hasVarSection:
    targetSections.add "VAR" 

  echo "hasSections: " & $hasSections    
  var hasNoPrc = p.prc == nil
  echo "hasNoPrc:" & $hasNoPrc  

  var useSections = hasSections or hasNoPrc
  echo "useSections:" & $useSections
  echo targetSections

  if useSections:
    echo "using sections for emit"
    # top level emit pragma?
    let section = determineSection(t[1], targetSections)
    genCLineDir(p.module.s[section], t.info, p.config)
    p.module.s[section].add(s)
  else:
    echo "NOT using sections for emit"
    genLineDir(p, t)
    line(p, cpsStmts, s)
kristianmandrup commented 4 years ago

I now understand that for js generation genAsmOrEmitStmt in jsgen.nim is used, not genEmit of ccgstmts.nim as I thought. Not sure how I managed initially to get output from genEmit when compiling a js file with nim?

I see that genEmit calls genAsmOrEmitStmt so I would think a similar design could be used for js

alehander92 commented 4 years ago

yes jsgen is used , the other one-s are for other backends, also you should know nim generates a single javascript file .. so if you need many, this also requires more stuff

this is one plan to refactor it .. i did some part of this refactor in a branch somewhere, but its huge, so one can do it more easily im ohttps://github.com/nim-lang/Nim/pull/7508

alehander92 commented 4 years ago

however i'd hesitate to target typescript.. nim is like an equivalent of typescript , also waiting for both compilers doesnt make a lot of sense to me : do you just need to use nim in typescript? it might be much easier to write a separate tool to generate typescript defs from nim ones !

kristianmandrup commented 4 years ago

Thanks, I will have a look. I see that the BModule used in jsgen is using TJSGen where module is the PSym of type TSym

  TJSGen = object of PPassContext
    module: PSym
    graph: ModuleGraph
    config: ConfigRef
    sigConflicts: CountTable[SigHash]

  BModule = ref TJSGen

TSym* {.acyclic.} = object of TIdObj
    # proc and type instantiations are cached in the generic symbol
    case kind*: TSymKind
    of skType, skGenericParam:
      typeInstCache*: seq[PType]
    of routineKinds:
      procInstCache*: seq[PInstantiation]
      gcUnsafetyReason*: PSym  # for better error messages wrt gcsafe
      transformedBody*: PNode  # cached body after transf pass
    of skModule, skPackage:
      # modules keep track of the generic symbols they use from other modules.
      # this is because in incremental compilation, when a module is about to
      # be replaced with a newer version, we must decrement the usage count
      # of all previously used generics.
      # For 'import as' we copy the module symbol but shallowCopy the 'tab'
      # and set the 'usedGenerics' to ... XXX gah! Better set module.name
      # instead? But this doesn't work either. --> We need an skModuleAlias?
      # No need, just leave it as skModule but set the owner accordingly and
      # check for the owner when touching 'usedGenerics'.
      usedGenerics*: seq[PInstantiation]
      tab*: TStrTable         # interface table for modules
    of skLet, skVar, skField, skForVar:
      guard*: PSym
      bitsize*: int
      alignment*: int # for alignment
    else: nil
    magic*: TMagic
    typ*: PType
    name*: PIdent
    info*: TLineInfo
    owner*: PSym
    flags*: TSymFlags
    ast*: PNode               # syntax tree of proc, iterator, etc.:
                              # the whole proc including header; this is used
                              # for easy generation of proper error messages
                              # for variant record fields the discriminant
                              # expression
                              # for modules, it's a placeholder for compiler
                              # generated code that will be appended to the
                              # module after the sem pass (see appendToModule)
    options*: TOptions
    position*: int            # used for many different things:
                              # for enum fields its position;
                              # for fields its offset
                              # for parameters its position
                              # for a conditional:
                              # 1 iff the symbol is defined, else 0
                              # (or not in symbol table)
                              # for modules, an unique index corresponding
                              # to the module's fileIdx
                              # for variables a slot index for the evaluator
    offset*: int              # offset of record field
    loc*: TLoc
    annex*: PLib              # additional fields (seldom used, so we use a
                              # reference to another object to save space)
    when hasFFI:
      cname*: string          # resolved C declaration name in importc decl, eg:
                              # proc fun() {.importc: "$1aux".} => cname = funaux
    constraint*: PNode        # additional constraints like 'lit|result'; also
                              # misused for the codegenDecl pragma in the hope
                              # it won't cause problems
                              # for skModule the string literal to output for
                              # deprecated modules.
    when defined(nimsuggest):
      allUsages*: seq[TLineInfo]

The key for the sections to work for the c generator is this bit:

    let section = determineSection(t[1], targetSections)
    genCLineDir(p.module.s[section], t.info, p.config)
    p.module.s[section].add(s)

But in the js context, there is no such p.module.s collection (which would need to be added somehow).

I never thought of TypeScript as a "separate Nim target". Would be nice to have the option to emit "TypeScript like" code and then optionally set ts or even tsx (JSX/TSX) as the file extension would be nice. Could also add macros to emit proc/function decorators which are very common in modern Javascript (via bable or typescript) such as for NestJS and many other modern libraries, front to back.

I'll have a look in your PR

alehander92 commented 4 years ago

my PR is totally unfinished but mostly the conversation is useful

but why would you need to produce typescript? nim doesnt generate pretty code by design, so it wouldnt be useful unless you import it in typescript

kristianmandrup commented 4 years ago

TypeScript is just a superset of Javascript (constantly evolving). TypeScript is often at the front with support for new experimental features.

Sometimes it is just convenient to be able to output a specific extension (such as ts) and perhaps sprinkle some extra "fairy dust" for better interop. Ideally like source maps, it could also spit out a typedef file (d.ts). So I guess you have added some basic infrastructure for outputting to multiple files then.

Sounds great :)

kristianmandrup commented 4 years ago

Do you know where I can find the module.s Nim type def used to add sections for c code?

p.module.s[section].add(s)

alehander92 commented 4 years ago

i havent tho, this was planned to be done : it shouldn't be too hard but its not existing here

kristianmandrup commented 4 years ago

Found this:

  TCProc = object             # represents C proc that is currently generated
    prc*: PSym                # the Nim proc that this C proc belongs to
    flags*: set[TCProcFlag]
    lastLineInfo*: TLineInfo  # to avoid generating excessive 'nimln' statements
    currLineInfo*: TLineInfo  # AST codegen will make this superfluous
    nestedTryStmts*: seq[tuple[fin: PNode, inExcept: bool, label: Natural]]
                              # in how many nested try statements we are
                              # (the vars must be volatile then)
                              # bool is true when are in the except part of a try block
    finallySafePoints*: seq[Rope]  # For correctly cleaning up exceptions when
                                   # using return in finally statements
    labels*: Natural          # for generating unique labels in the C proc
    blocks*: seq[TBlock]      # nested blocks
    breakIdx*: int            # the block that will be exited
                              # with a regular break
    options*: TOptions        # options that should be used for code
                              # generation; this is the same as prc.options
                              # unless prc == nil
    module*: BModule          # used to prevent excessive parameter passing
    withinLoop*: int          # > 0 if we are within a loop
    splitDecls*: int          # > 0 if we are in some context for C++ that
                              # requires 'T x = T()' to become 'T x; x = T()'
                              # (yes, C++ is weird like that)
    sigConflicts*: CountTable[string]

Similar to TJSProc :)

  BModule* = ref TCGen

  TCGen = object of PPassContext # represents a C source file
    s*: TCFileSections        # sections of the C file.  <--- HERE WE GO!!!
    flags*: set[CodegenFlag]
    module*: PSym
    filename*: AbsoluteFile
    cfilename*: AbsoluteFile  # filename of the module (including path,
                              # without extension)
    tmpBase*: Rope            # base for temp identifier generation
    typeCache*: TypeCache     # cache the generated types
    forwTypeCache*: TypeCache # cache for forward declarations of types
    declaredThings*: IntSet   # things we have declared in this .c file
    declaredProtos*: IntSet   # prototypes we have declared in this .c file
    headerFiles*: seq[string] # needed headers to include
    typeInfoMarker*: TypeCache # needed for generating type information
    initProc*: BProc          # code for init procedure
    preInitProc*: BProc       # code executed before the init proc
    hcrCreateTypeInfosProc*: Rope # type info globals are in here when HCR=on
    inHcrInitGuard*: bool     # We are currently within a HCR reloading guard.
    typeStack*: TTypeSeq      # used for type generation
    dataCache*: TNodeTable
    typeNodes*, nimTypes*: int # used for type info generation
    typeNodesName*, nimTypesName*: Rope # used for type info generation
    labels*: Natural          # for generating unique module-scope names
    extensionLoaders*: array['0'..'9', Rope] # special procs for the
                                             # OpenGL wrapper
    injectStmt*: Rope
    sigConflicts*: CountTable[SigHash]
    g*: BModuleList
    ndi*: NdiFile

So essentially we could in part mirror the TCGen type:

  TCGen = object of PPassContext # represents a C source file
    s*: TCFileSections        # sections of the C file.  <--- HERE WE GO!!!
alehander92 commented 4 years ago

better interop is not bad, but you mostly need to generate compatible types to interop: not really code, if you target a language X backend, its often easier to just target a much older version if possible , because you can already create features in the source language(and for interop, you need only signatures/types to match!) imho

you can enter #nim on irc as well but if its easier for you here, thats also amazing!

kristianmandrup commented 4 years ago

OK, which irc client would you recommend for OSX? Limechat?

IRC Mac mIrc alternatives

I think the following refactoring, adding outputFiles to TCGen and TJSGen would do "miracles":

  TCGen = object of PPassContext # represents a C source file
    outputFiles: # HashMap of TCGen (extra files being generated as side effect of compiling any given nim file)
    module*: PSym
    s*: TCFileSections        # sections of the C file.  <--- HERE WE GO!!! 
    filename*: AbsoluteFile 
    cfilename*: AbsoluteFile  # filename of the main output module (including path, without extension)

For JS

  TJSGen = object of PPassContext # represents a C source file
    outputFiles: # HashMap of TCGen (extra files being generated as side effect of compiling any given nim file)
    module*: PSym
    s*: TJSFileSections        # sections of the JS file.
    filename*: AbsoluteFile
    jsfilename*: AbsoluteFile  # filename of the main output module (including path, without extension)

Ideally jsfilename and cfilename should be named sth more generic like targetFilename IMO

alehander92 commented 4 years ago

you can also just use discord or gitter

alehander92 commented 4 years ago

please, dont change the c backend if not sure, i really doubt this would be required : there are probably many assumptions for the way files are generated there already

kristianmandrup commented 4 years ago

I've been a bit on the main Nim gitter channel lately. OK, I won't touch the c backend

kristianmandrup commented 4 years ago

My current proposal:

  TJSGen = object of PPassContext
    module: PSym
    s*: TJSFileSections        # sections of the JS file    
    graph: ModuleGraph
    config: ConfigRef
    sigConflicts: CountTable[SigHash]

  TJSFileSection* = enum       # the sections a generated C file consists of
    jsfsHeaders,               # top file section typically used for JS require/import statements
    jsfsTypes,                 # type section (such as interfaces/types for TypeScript interop)
    jsfsMain,                  # main code
    jsfsFooters                # bottom section often used for exports 

  TJSFileSections* = array[TJSFileSection, Rope] # represents a generated JS file

  BModule = ref TJSGen
kristianmandrup commented 4 years ago

Then copying the genEmit from ccgstmts.nim to jsgen.nim and call genEmit from genPragma instead of directly calling the lower level AST emit proc

kristianmandrup commented 4 years ago

I've come very far now. Almost there :)

timotheecour commented 4 years ago

this seems like a perfect use case for https://github.com/nim-lang/Nim/pull/13953