summary refs log tree commit diff stats
diff options
context:
space:
mode:
-rw-r--r--compiler/ast.nim4
-rw-r--r--compiler/cgen.nim15
-rw-r--r--compiler/jsgen.nim11
-rw-r--r--compiler/lambdalifting.nim11
-rw-r--r--compiler/sempass2.nim26
-rw-r--r--compiler/transf.nim29
-rw-r--r--compiler/vm.nim22
-rw-r--r--compiler/vmgen.nim3
-rw-r--r--tests/destructor/tmove_objconstr.nim6
9 files changed, 65 insertions, 62 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim
index 1ad7249d4..723a4a1de 100644
--- a/compiler/ast.nim
+++ b/compiler/ast.nim
@@ -228,7 +228,7 @@ type
   TNodeKinds* = set[TNodeKind]
 
 type
-  TSymFlag* = enum    # 39 flags!
+  TSymFlag* = enum    # 40 flags!
     sfUsed,           # read access of sym (for warnings) or simply used
     sfExported,       # symbol is exported from module
     sfFromGeneric,    # symbol is instantiation of a generic; this is needed
@@ -285,7 +285,7 @@ type
                       # destruction for --newruntime.
     sfTemplateParam   # symbol is a template parameter
     sfCursor          # variable/field is a cursor, see RFC 177 for details
-
+    sfInjectDestructors # whether the proc needs the 'injectdestructors' transformation
 
   TSymFlags* = set[TSymFlag]
 
diff --git a/compiler/cgen.nim b/compiler/cgen.nim
index 1e25f44d1..0e88c39d8 100644
--- a/compiler/cgen.nim
+++ b/compiler/cgen.nim
@@ -14,7 +14,8 @@ import
   nversion, nimsets, msgs, bitsets, idents, types,
   ccgutils, os, ropes, math, passes, wordrecg, treetab, cgmeth,
   rodutils, renderer, cgendata, ccgmerge, aliases,
-  lowerings, tables, sets, ndi, lineinfos, pathutils, transf, enumtostr
+  lowerings, tables, sets, ndi, lineinfos, pathutils, transf, enumtostr,
+  injectdestructors
 
 when not defined(leanCompiler):
   import spawn, semparallel
@@ -531,7 +532,7 @@ proc assignGlobalVar(p: BProc, n: PNode) =
       var decl: Rope = nil
       var td = getTypeDesc(p.module, s.loc.t)
       if s.constraint.isNil:
-        if s.alignment > 0:
+        if s.kind in {skLet, skVar, skField, skForVar} and s.alignment > 0:
           decl.addf "alignas($1) ", [rope(s.alignment)]
         if p.hcrOn: add(decl, "static ")
         elif sfImportc in s.flags: add(decl, "extern ")
@@ -957,7 +958,10 @@ proc genProcAux(m: BModule, prc: PSym) =
   var header = genProcHeader(m, prc)
   var returnStmt: Rope = nil
   assert(prc.ast != nil)
-  let procBody = transformBody(m.g.graph, prc, cache = false)
+
+  var procBody = transformBody(m.g.graph, prc, cache = false)
+  if sfInjectDestructors in prc.flags:
+    procBody = injectDestructorCalls(m.g.graph, prc, procBody)
 
   if sfPure notin prc.flags and prc.typ.sons[0] != nil:
     if resultPos >= prc.ast.len:
@@ -1857,7 +1861,10 @@ proc myProcess(b: PPassContext, n: PNode): PNode =
   m.initProc.options = initProcOptions(m)
   #softRnl = if optLineDir in m.config.options: noRnl else: rnl
   # XXX replicate this logic!
-  let transformedN = transformStmt(m.g.graph, m.module, n)
+  var transformedN = transformStmt(m.g.graph, m.module, n)
+  if sfInjectDestructors in m.module.flags:
+    transformedN = injectDestructorCalls(m.g.graph, m.module, transformedN)
+
   if m.hcrOn:
     addHcrInitGuards(m.initProc, transformedN, m.inHcrInitGuard)
   else:
diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim
index 6310a45a6..4b3862cff 100644
--- a/compiler/jsgen.nim
+++ b/compiler/jsgen.nim
@@ -33,7 +33,7 @@ import
   nversion, msgs, idents, types, tables,
   ropes, math, passes, ccgutils, wordrecg, renderer,
   intsets, cgmeth, lowerings, sighashes, modulegraphs, lineinfos, rodutils,
-  transf
+  transf, injectdestructors
 
 
 from modulegraphs import ModuleGraph, PPassContext
@@ -2259,7 +2259,10 @@ proc genProc(oldProc: PProc, prc: PSym): Rope =
     else:
       returnStmt = "return $#;$n" % [a.res]
 
-  let transformedBody = transformBody(oldProc.module.graph, prc, cache = false)
+  var transformedBody = transformBody(oldProc.module.graph, prc, cache = false)
+  if sfInjectDestructors in prc.flags:
+    transformedBody = injectDestructorCalls(oldProc.module.graph, prc, transformedBody)
+
   p.nested: genStmt(p, transformedBody)
 
   var def: Rope
@@ -2540,7 +2543,9 @@ proc genModule(p: PProc, n: PNode) =
     add(p.body, frameCreate(p,
         makeJSString("module " & p.module.module.name.s),
         makeJSString(toFilename(p.config, p.module.module.info))))
-  let transformedN = transformStmt(p.module.graph, p.module.module, n)
+  var transformedN = transformStmt(p.module.graph, p.module.module, n)
+  if sfInjectDestructors in p.module.module.flags:
+    transformedN = injectDestructorCalls(p.module.graph, p.module.module, transformedN)
   if p.config.hcrOn and n.kind == nkStmtList:
     let moduleSym = p.module.module
     var moduleLoadedVar = rope(moduleSym.name.s) & "_loaded" &
diff --git a/compiler/lambdalifting.nim b/compiler/lambdalifting.nim
index a3535010d..15ab7ec0a 100644
--- a/compiler/lambdalifting.nim
+++ b/compiler/lambdalifting.nim
@@ -296,7 +296,7 @@ type
   DetectionPass = object
     processed, capturedVars: IntSet
     ownerToType: Table[int, PType]
-    somethingToDo, noDestructors: bool
+    somethingToDo: bool
     graph: ModuleGraph
 
 proc initDetectionPass(g: ModuleGraph; fn: PSym): DetectionPass =
@@ -423,8 +423,7 @@ proc detectCapturedVars(n: PNode; owner: PSym; c: var DetectionPass) =
     if innerProc:
       if s.isIterator: c.somethingToDo = true
       if not c.processed.containsOrIncl(s.id):
-        let body = transformBody(c.graph, s, cache = true,
-                                 noDestructors = c.noDestructors)
+        let body = transformBody(c.graph, s, cache = true)
         detectCapturedVars(body, s, c)
     let ow = s.skipGenericOwner
     if ow == owner:
@@ -714,7 +713,7 @@ proc liftCapturedVars(n: PNode; owner: PSym; d: DetectionPass;
         #  echo renderTree(s.getBody, {renderIds})
         let oldInContainer = c.inContainer
         c.inContainer = 0
-        var body = transformBody(d.graph, s)
+        var body = transformBody(d.graph, s, cache = false)
         body = liftCapturedVars(body, s, d, c)
         if c.envVars.getOrDefault(s.id).isNil:
           s.transformedBody = body
@@ -833,8 +832,7 @@ proc liftIterToProc*(g: ModuleGraph; fn: PSym; body: PNode; ptrType: PType): PNo
   fn.kind = oldKind
   fn.typ.callConv = oldCC
 
-proc liftLambdas*(g: ModuleGraph; fn: PSym, body: PNode; tooEarly: var bool;
-                  noDestructors: bool): PNode =
+proc liftLambdas*(g: ModuleGraph; fn: PSym, body: PNode; tooEarly: var bool): PNode =
   # XXX gCmd == cmdCompileToJS does not suffice! The compiletime stuff needs
   # the transformation even when compiling to JS ...
 
@@ -850,7 +848,6 @@ proc liftLambdas*(g: ModuleGraph; fn: PSym, body: PNode; tooEarly: var bool;
     tooEarly = true
   else:
     var d = initDetectionPass(g, fn)
-    d.noDestructors = noDestructors
     detectCapturedVars(body, fn, d)
     if not d.somethingToDo and fn.isIterator:
       addClosureParam(d, fn, body.info)
diff --git a/compiler/sempass2.nim b/compiler/sempass2.nim
index a67da53b2..a05ea6829 100644
--- a/compiler/sempass2.nim
+++ b/compiler/sempass2.nim
@@ -671,6 +671,12 @@ proc cstringCheck(tracked: PEffects; n: PNode) =
       a.typ.kind == tyString and a.kind notin {nkStrLit..nkTripleStrLit}):
     message(tracked.config, n.info, warnUnsafeCode, renderTree(n))
 
+proc createTypeBoundOps(tracked: PEffects, typ: PType; info: TLineInfo) =
+  createTypeBoundOps(tracked.graph, tracked.c, typ, info)
+  if (typ != nil and tfHasAsgn in typ.flags) or
+      optSeqDestructors in tracked.config.globalOptions:
+    tracked.owner.flags.incl sfInjectDestructors
+
 proc track(tracked: PEffects, n: PNode) =
   template gcsafeAndSideeffectCheck() =
     if notGcSafe(op) and not importedFromC(a):
@@ -693,7 +699,7 @@ proc track(tracked: PEffects, n: PNode) =
       addEffect(tracked, n.sons[0], useLineInfo=false)
       for i in 0 ..< safeLen(n):
         track(tracked, n.sons[i])
-      createTypeBoundOps(tracked.graph, tracked.c, n[0].typ, n.info)
+      createTypeBoundOps(tracked, n[0].typ, n.info)
     else:
       # A `raise` with no arguments means we're going to re-raise the exception
       # being handled or, if outside of an `except` block, a `ReraiseError`.
@@ -707,7 +713,7 @@ proc track(tracked: PEffects, n: PNode) =
       return
     if n.typ != nil:
       if tracked.owner.kind != skMacro and n.typ.skipTypes(abstractVar).kind != tyOpenArray:
-        createTypeBoundOps(tracked.graph, tracked.c, n.typ, n.info)
+        createTypeBoundOps(tracked, n.typ, n.info)
     if a.kind == nkCast and a[1].typ.kind == tyProc:
       a = a[1]
     # XXX: in rare situations, templates and macros will reach here after
@@ -750,7 +756,7 @@ proc track(tracked: PEffects, n: PNode) =
           message(tracked.config, arg.info, warnProveInit, $arg)
       # check required for 'nim check':
       if n[1].typ.len > 0:
-        createTypeBoundOps(tracked.graph, tracked.c, n[1].typ.lastSon, n.info)
+        createTypeBoundOps(tracked, n[1].typ.lastSon, n.info)
     for i in 0 ..< safeLen(n):
       track(tracked, n.sons[i])
   of nkDotExpr:
@@ -771,18 +777,18 @@ proc track(tracked: PEffects, n: PNode) =
     notNilCheck(tracked, n.sons[1], n.sons[0].typ)
     when false: cstringCheck(tracked, n)
     if tracked.owner.kind != skMacro:
-      createTypeBoundOps(tracked.graph, tracked.c, n[0].typ, n.info)
+      createTypeBoundOps(tracked, n[0].typ, n.info)
   of nkVarSection, nkLetSection:
     for child in n:
       let last = lastSon(child)
       if last.kind != nkEmpty: track(tracked, last)
       if tracked.owner.kind != skMacro:
         if child.kind == nkVarTuple:
-          createTypeBoundOps(tracked.graph, tracked.c, child[^1].typ, child.info)
+          createTypeBoundOps(tracked, child[^1].typ, child.info)
           for i in 0..child.len-3:
-            createTypeBoundOps(tracked.graph, tracked.c, child[i].typ, child.info)
+            createTypeBoundOps(tracked, child[i].typ, child.info)
         else:
-          createTypeBoundOps(tracked.graph, tracked.c, child[0].typ, child.info)
+          createTypeBoundOps(tracked, child[0].typ, child.info)
       if child.kind == nkIdentDefs and last.kind != nkEmpty:
         for i in 0 .. child.len-3:
           initVar(tracked, child.sons[i], volatileCheck=false)
@@ -828,15 +834,15 @@ proc track(tracked: PEffects, n: PNode) =
       if tracked.owner.kind != skMacro:
         if it.kind == nkVarTuple:
           for x in it:
-            createTypeBoundOps(tracked.graph, tracked.c, x.typ, x.info)
+            createTypeBoundOps(tracked, x.typ, x.info)
         else:
-          createTypeBoundOps(tracked.graph, tracked.c, it.typ, it.info)
+          createTypeBoundOps(tracked, it.typ, it.info)
     let iterCall = n[n.len-2]
     let loopBody = n[n.len-1]
     if tracked.owner.kind != skMacro and iterCall.safeLen > 1:
       # XXX this is a bit hacky:
       if iterCall[1].typ != nil and iterCall[1].typ.skipTypes(abstractVar).kind notin {tyVarargs, tyOpenArray}:
-        createTypeBoundOps(tracked.graph, tracked.c, iterCall[1].typ, iterCall[1].info)
+        createTypeBoundOps(tracked, iterCall[1].typ, iterCall[1].info)
     track(tracked, iterCall)
     track(tracked, loopBody)
     setLen(tracked.init, oldState)
diff --git a/compiler/transf.nim b/compiler/transf.nim
index c63a26d10..c998b53b5 100644
--- a/compiler/transf.nim
+++ b/compiler/transf.nim
@@ -21,11 +21,10 @@
 import
   options, ast, astalgo, trees, msgs,
   idents, renderer, types, semfold, magicsys, cgmeth,
-  lowerings, injectdestructors, liftlocals,
+  lowerings, liftlocals,
   modulegraphs, lineinfos
 
-proc transformBody*(g: ModuleGraph, prc: PSym, cache = true;
-                    noDestructors = false): PNode
+proc transformBody*(g: ModuleGraph, prc: PSym, cache: bool): PNode
 
 import closureiters, lambdalifting
 
@@ -49,7 +48,7 @@ type
     inlining: int            # > 0 if we are in inlining context (copy vars)
     nestedProcs: int         # > 0 if we are in a nested proc
     contSyms, breakSyms: seq[PSym]  # to transform 'continue' and 'break'
-    deferDetected, tooEarly, needsDestroyPass, noDestructors: bool
+    deferDetected, tooEarly: bool
     graph: ModuleGraph
   PTransf = ref TTransfContext
 
@@ -131,7 +130,7 @@ proc transformSymAux(c: PTransf, n: PNode): PNode =
   let s = n.sym
   if s.typ != nil and s.typ.callConv == ccClosure:
     if s.kind in routineKinds:
-      discard transformBody(c.graph, s, true, c.noDestructors)
+      discard transformBody(c.graph, s, true)
     if s.kind == skIterator:
       if c.tooEarly: return n
       else: return liftIterSym(c.graph, n, getCurrOwner(c))
@@ -678,7 +677,7 @@ proc transformFor(c: PTransf, n: PNode): PTransNode =
       add(stmtList, newAsgnStmt(c, nkFastAsgn, temp, arg.PTransNode))
       idNodeTablePut(newC.mapping, formal, temp)
 
-  let body = transformBody(c.graph, iter, true, c.noDestructors)
+  let body = transformBody(c.graph, iter, true)
   pushInfoContext(c.graph.config, n.info)
   inc(c.inlining)
   add(stmtList, transform(c, body))
@@ -913,9 +912,6 @@ proc transform(c: PTransf, n: PNode): PTransNode =
                   nkBlockStmt, nkBlockExpr}:
       oldDeferAnchor = c.deferAnchor
       c.deferAnchor = n
-  if (n.typ != nil and tfHasAsgn in n.typ.flags) or
-      optSeqDestructors in c.graph.config.globalOptions:
-    c.needsDestroyPass = true
   case n.kind
   of nkSym:
     result = transformSym(c, n)
@@ -1113,8 +1109,7 @@ template liftDefer(c, root) =
   if c.deferDetected:
     liftDeferAux(root)
 
-proc transformBody*(g: ModuleGraph, prc: PSym, cache = true;
-                    noDestructors = false): PNode =
+proc transformBody*(g: ModuleGraph, prc: PSym, cache: bool): PNode =
   assert prc.kind in routineKinds
 
   if prc.transformedBody != nil:
@@ -1124,13 +1119,10 @@ proc transformBody*(g: ModuleGraph, prc: PSym, cache = true;
   else:
     prc.transformedBody = newNode(nkEmpty) # protects from recursion
     var c = openTransf(g, prc.getModule, "")
-    c.noDestructors = noDestructors
-    result = liftLambdas(g, prc, prc.ast[bodyPos], c.tooEarly, noDestructors)
+    result = liftLambdas(g, prc, prc.ast[bodyPos], c.tooEarly)
     result = processTransf(c, result, prc)
     liftDefer(c, result)
     result = liftLocalsIfRequested(prc, result, g.cache, g.config)
-    if c.needsDestroyPass and not noDestructors:
-      result = injectDestructorCalls(g, prc, result)
 
     if prc.isIterator:
       result = g.transformClosureIterator(prc, result)
@@ -1152,12 +1144,9 @@ proc transformStmt*(g: ModuleGraph; module: PSym, n: PNode): PNode =
     result = processTransf(c, n, module)
     liftDefer(c, result)
     #result = liftLambdasForTopLevel(module, result)
-    if c.needsDestroyPass:
-      result = injectDestructorCalls(g, module, result)
     incl(result.flags, nfTransf)
 
-proc transformExpr*(g: ModuleGraph; module: PSym, n: PNode;
-                    noDestructors = false): PNode =
+proc transformExpr*(g: ModuleGraph; module: PSym, n: PNode): PNode =
   if nfTransf in n.flags:
     result = n
   else:
@@ -1166,6 +1155,4 @@ proc transformExpr*(g: ModuleGraph; module: PSym, n: PNode;
     liftDefer(c, result)
     # expressions are not to be injected with destructor calls as that
     # the list of top level statements needs to be collected before.
-    if c.needsDestroyPass and not noDestructors:
-      result = injectDestructorCalls(g, module, result)
     incl(result.flags, nfTransf)
diff --git a/compiler/vm.nim b/compiler/vm.nim
index 922208034..ae8cc25af 100644
--- a/compiler/vm.nim
+++ b/compiler/vm.nim
@@ -1005,13 +1005,15 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): TFullReg =
       decodeB(rkNode)
       let a = regs[rb].node
       if a.kind == nkSym:
-        regs[ra].node = if a.sym.ast.isNil: newNode(nkNilLit)
-                        else:
-                          let ast = a.sym.ast.shallowCopy
-                          for i in 0..<a.sym.ast.len:
-                            ast[i] = a.sym.ast[i]
-                          ast[bodyPos] = transformBody(c.graph, a.sym)
-                          ast.copyTree()
+        regs[ra].node =
+          if a.sym.ast.isNil:
+            newNode(nkNilLit)
+          else:
+            let ast = a.sym.ast.shallowCopy
+            for i in 0..<a.sym.ast.len:
+              ast[i] = a.sym.ast[i]
+            ast[bodyPos] = transformBody(c.graph, a.sym, cache=true)
+            ast.copyTree()
     of opcSymOwner:
       decodeB(rkNode)
       let a = regs[rb].node
@@ -1983,7 +1985,7 @@ proc execProc*(c: PCtx; sym: PSym; args: openArray[PNode]): PNode =
       "NimScript: attempt to call non-routine: " & sym.name.s)
 
 proc evalStmt*(c: PCtx, n: PNode) =
-  let n = transformExpr(c.graph, c.module, n, noDestructors = true)
+  let n = transformExpr(c.graph, c.module, n)
   let start = genStmt(c, n)
   # execute new instructions; this redundant opcEof check saves us lots
   # of allocations in 'execute':
@@ -1991,7 +1993,7 @@ proc evalStmt*(c: PCtx, n: PNode) =
     discard execute(c, start)
 
 proc evalExpr*(c: PCtx, n: PNode): PNode =
-  let n = transformExpr(c.graph, c.module, n, noDestructors = true)
+  let n = transformExpr(c.graph, c.module, n)
   let start = genExpr(c, n)
   assert c.code[start].opcode != opcEof
   result = execute(c, start)
@@ -2037,7 +2039,7 @@ proc evalConstExprAux(module: PSym;
                       g: ModuleGraph; prc: PSym, n: PNode,
                       mode: TEvalMode): PNode =
   if g.config.errorCounter > 0: return n
-  let n = transformExpr(g, module, n, noDestructors = true)
+  let n = transformExpr(g, module, n)
   setupGlobalCtx(module, g)
   var c = PCtx g.vm
   let oldMode = c.mode
diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim
index 0dc55862c..88ac57962 100644
--- a/compiler/vmgen.nim
+++ b/compiler/vmgen.nim
@@ -2243,8 +2243,7 @@ proc genProc(c: PCtx; s: PSym): int =
     s.ast.sons[miscPos] = x
     # thanks to the jmp we can add top level statements easily and also nest
     # procs easily:
-    let body = transformBody(c.graph, s, cache = not isCompileTimeProc(s),
-                             noDestructors = true)
+    let body = transformBody(c.graph, s, cache = not isCompileTimeProc(s))
     let procStart = c.xjmp(body, opcJmp, 0)
     var p = PProc(blocks: @[], sym: s)
     let oldPrc = c.prc
diff --git a/tests/destructor/tmove_objconstr.nim b/tests/destructor/tmove_objconstr.nim
index be92d1503..5b2198e51 100644
--- a/tests/destructor/tmove_objconstr.nim
+++ b/tests/destructor/tmove_objconstr.nim
@@ -58,9 +58,9 @@ iterator items(p: Pony): int =
 
 for x in getPony():
   echo x
-# XXX this needs to be enabled once top level statements
-# produce destructor calls again.
-#echo "Pony is dying!"
+
+
+
 
 
 #------------------------------------------------------------