# # # The Nim Compiler # (c) Copyright 2015 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. # # This file implements lambda lifting for the transformator. import options, ast, astalgo, msgs, idents, renderer, types, magicsys, lowerings, modulegraphs, lineinfos, transf, liftdestructors, typeallowed import std/[strutils, tables, intsets] when defined(nimPreviewSlimSystem): import std/assertions discard """ The basic approach is that captured vars need to be put on the heap and that the calling chain needs to be explicitly modelled. Things to consider: proc a = var v = 0 proc b = var w = 2 for x in 0..3: proc c = capture v, w, x c() b() for x in 0..4: proc d = capture x d() Needs to be translated into: proc a = var cl: * new cl cl.v = 0 proc b(cl) = var bcl: * new bcl bcl.w = 2 bcl.up = cl for x in 0..3: var bcl2: * new bcl2 bcl2.up = bcl bcl2.up2 = cl bcl2.x = x proc c(cl) = capture cl.up2.v, cl.up.w, cl.x c(bcl2) c(bcl) b(cl) for x in 0..4: var acl2: * new acl2 acl2.x = x proc d(cl) = capture cl.x d(acl2) Closures as interfaces: proc outer: T = var captureMe: TObject # value type required for efficiency proc getter(): int = result = captureMe.x proc setter(x: int) = captureMe.x = x result = (getter, setter) Is translated to: proc outer: T = var cl: * new cl proc getter(cl): int = result = cl.captureMe.x proc setter(cl: *, x: int) = cl.captureMe.x = x result = ((cl, getter), (cl, setter)) For 'byref' capture, the outer proc needs to access the captured var through the indirection too. For 'bycopy' capture, the outer proc accesses the var not through the indirection. Possible optimizations: 1) If the closure contains a single 'ref' and this reference is not re-assigned (check ``sfAddrTaken`` flag) make this the closure. This is an important optimization if closures are used as interfaces. 2) If the closure does not escape, put it onto the stack, not on the heap. 3) Dataflow analysis would help to eliminate the 'up' indirections. 4) If the captured var is not actually used in the outer proc (common?), put it into an inner proc. """ # Important things to keep in mind: # * Don't base the analysis on nkProcDef et al. This doesn't work for # instantiated (formerly generic) procs. The analysis has to look at nkSym. # This also means we need to prevent the same proc is processed multiple # times via the 'processed' set. # * Keep in mind that the owner of some temporaries used to be unreliable. # * For closure iterators we merge the "real" potential closure with the # local storage requirements for efficiency. This means closure iterators # have slightly different semantics from ordinary closures. # ---------------- essential helpers ------------------------------------- const upName* = ":up" # field name for the 'up' reference paramName* = ":envP" envName* = ":env" proc newCall(a: PSym, b: PNode): PNode = result = newNodeI(nkCall, a.info) result.add newSymNode(a) result.add b proc createClosureIterStateType*(g: ModuleGraph; iter: PSym; idgen: IdGenerator): PType = var n = newNodeI(nkRange, iter.info) n.add newIntNode(nkIntLit, -1) n.add newIntNode(nkIntLit, 0) result = newType(tyRange, idgen, iter) result.n = n var intType = nilOrSysInt(g) if intType.isNil: intType = newType(tyInt, idgen, iter) rawAddSon(result, intType) proc createStateField(g: ModuleGraph; iter: PSym; idgen: IdGenerator): PSym = result = newSym(skField, getIdent(g.cache, ":state"), idgen, iter, iter.info) result.typ = createClosureIterStateType(g, iter, idgen) template isIterator*(owner: PSym): bool = owner.kind == skIterator and owner.typ.callConv == ccClosure proc createEnvObj(g: ModuleGraph; idgen: IdGenerator; owner: PSym; info: TLineInfo): PType = result = createObj(g, idgen, owner, info, final=false) if owner.isIterator or not isDefined(g.config, "nimOptIters"): rawAddField(result, createStateField(g, owner, idgen)) proc getClosureIterResult*(g: ModuleGraph; iter: PSym; idgen: IdGenerator): PSym = if resultPos < iter.ast.len: result = iter.ast[resultPos].sym else: # XXX a bit hacky: result = newSym(skResult, getIdent(g.cache, ":result"), idgen, iter, iter.info, {}) result.typ = iter.typ.returnType incl(result.flags, sfUsed) iter.ast.add newSymNode(result) proc addHiddenParam(routine: PSym, param: PSym) = assert param.kind == skParam var params = routine.ast[paramsPos] # -1 is correct here as param.position is 0 based but we have at position 0 # some nkEffect node: param.position = routine.typ.n.len-1 params.add newSymNode(param) #incl(routine.typ.flags, tfCapturesEnv) assert sfFromGeneric in param.flags #echo "produced environment: ", param.id, " for ", routine.id proc getEnvParam*(routine: PSym): PSym = let params = routine.ast[paramsPos] let hidden = lastSon(params) if hidden.kind == nkSym and hidden.sym.kind == skParam and hidden.sym.name.s == paramName: result = hidden.sym assert sfFromGeneric in result.flags else: result = nil proc getHiddenParam(g: ModuleGraph; routine: PSym): PSym = result = getEnvParam(routine) if result.isNil: # writeStackTrace() localError(g.config, routine.info, "internal error: could not find env param for " & routine.name.s) result = routine proc interestingVar(s: PSym): bool {.inline.} = result = s.kind in {skVar, skLet, skTemp, skForVar, skParam, skResult} and sfGlobal notin s.flags and s.typ.kind notin {tyStatic, tyTypeDesc} proc illegalCapture(s: PSym): bool {.inline.} = result = classifyViewType(s.typ) != noView or s.kind == skResult proc isInnerProc(s: PSym): bool = if s.kind in {skProc, skFunc, skMethod, skConverter, skIterator} and s.magic == mNone: result = s.skipGenericOwner.kind in routineKinds else: result = false proc newAsgnStmt(le, ri: PNode, info: TLineInfo): PNode = # Bugfix: unfortunately we cannot use 'nkFastAsgn' here as that would # mean to be able to capture string literals which have no GC header. # However this can only happen if the capture happens through a parameter, # which is however the only case when we generate an assignment in the first # place. result = newNodeI(nkAsgn, info, 2) result[0] = le result[1] = ri proc makeClosure*(g: ModuleGraph; idgen: IdGenerator; prc: PSym; env: PNode; info: TLineInfo): PNode = result = newNodeIT(nkClosure, info, prc.typ) result.add(newSymNode(prc)) if env == nil: result.add(newNodeIT(nkNilLit, info, getSysType(g, info, tyNil))) else: if env.skipConv.kind == nkClosure: localError(g.config, info, "internal error: taking closure of closure") result.add(env) #if isClosureIterator(result.typ): createTypeBoundOps(g, nil, result.typ, info, idgen) if tfHasAsgn in result.typ.flags or optSeqDestructors in g.config.globalOptions: prc.flags.incl sfInjectDestructors proc interestingIterVar(s: PSym): bool {.inline.} = # unused with -d:nimOptIters # XXX optimization: Only lift the variable if it lives across # yield/return boundaries! This can potentially speed up # closure iterators quite a bit. result = s.kind in {skResult, skVar, skLet, skTemp, skForVar} and sfGlobal notin s.flags template liftingHarmful(conf: ConfigRef; owner: PSym): bool = ## lambda lifting can be harmful for JS-like code generators. let isCompileTime = sfCompileTime in owner.flags or owner.kind == skMacro jsNoLambdaLifting in conf.legacyFeatures and conf.backend == backendJs and not isCompileTime proc createTypeBoundOpsLL(g: ModuleGraph; refType: PType; info: TLineInfo; idgen: IdGenerator; owner: PSym) = if owner.kind != skMacro: createTypeBoundOps(g, nil, refType.elementType, info, idgen) createTypeBoundOps(g, nil, refType, info, idgen) if tfHasAsgn in refType.flags or optSeqDestructors in g.config.globalOptions: owner.flags.incl sfInjectDestructors proc genCreateEnv(env: PNode): PNode = var c = newNodeIT(nkObjConstr, env.info, env.typ) c.add newNodeIT(nkType, env.info, env.typ) let e = copyTree(env) e.flags.incl nfFirstWrite result = newAsgnStmt(e, c) proc liftIterSym*(g: ModuleGraph; n: PNode; idgen: IdGenerator; owner: PSym): PNode = # transforms (iter) to (let env = newClosure[iter](); (iter, env)) if liftingHarmful(g.config, owner): return n let iter = n.sym assert iter.isIterator result = newNodeIT(nkStmtListExpr, n.info, iter.typ) let hp = getHiddenParam(g, iter) var env: PNode if owner.isIterator: let it = getHiddenParam(g, owner) addUniqueField(it.typ.skipTypes({tyOwned})[0], hp, g.cache, idgen) env = indirectAccess(newSymNode(it), hp, hp.info) else: let e = newSym(skLet, iter.name, idgen, owner, n.info) e.typ = hp.typ e.flags = hp.flags env = newSymNode(e) var v = newNodeI(nkVarSection, n.info) addVar(v, env) result.add(v) # add 'new' statement: #result.add newCall(getSysSym(g, n.info, "internalNew"), env) result.add genCreateEnv(env) createTypeBoundOpsLL(g, env.typ, n.info, idgen, owner) result.add makeClosure(g, idgen, iter, env, n.info) proc freshVarForClosureIter*(g: ModuleGraph; s: PSym; idgen: IdGenerator; owner: PSym): PNode = # unused with -d:nimOptIters let envParam = getHiddenParam(g, owner) let obj = envParam.typ.skipTypes({tyOwned, tyRef, tyPtr}) let field = addField(obj, s, g.cache, idgen) var access = newSymNode(envParam) assert obj.kind == tyObject result = rawIndirectAccess(access, field, s.info) # ------------------ new stuff ------------------------------------------- proc markAsClosure(g: ModuleGraph; owner: PSym; n: PNode) = let s = n.sym let isEnv = s.name.id == getIdent(g.cache, ":env").id if illegalCapture(s): localError(g.config, n.info, ("'$1' is of type <$2> which cannot be captured as it would violate memory" & " safety, declared here: $3; using '-d:nimNoLentIterators' helps in some cases." & " Consider using a which can be captured.") % [s.name.s, typeToString(s.typ), g.config$s.info]) elif not (owner.typ.isClosure or owner.isNimcall and not owner.isExplicitCallConv or isEnv): localError(g.config, n.info, "illegal capture '$1' because '$2' has the calling convention: <$3>" % [s.name.s, owner.name.s, $owner.typ.callConv]) incl(owner.typ.flags, tfCapturesEnv) if not isEnv: owner.typ.callConv = ccClosure type DetectionPass = object processed, capturedVars: IntSet ownerToType: Table[int, PType] somethingToDo: bool inTypeOf: bool graph: ModuleGraph idgen: IdGenerator proc initDetectionPass(g: ModuleGraph; fn: PSym; idgen: IdGenerator): DetectionPass = result = DetectionPass(processed: toIntSet([fn.id]), capturedVars: initIntSet(), ownerToType: initTable[int, PType](), graph: g, idgen: idgen ) discard """ proc outer = var a, b: int proc innerA = use(a) proc innerB = use(b); innerA() # --> innerA and innerB need to *share* the closure type! This is why need to store the 'ownerToType' table and use it during .closure'fication. """ proc getEnvTypeForOwner(c: var DetectionPass; owner: PSym; info: TLineInfo): PType = result = c.ownerToType.getOrDefault(owner.id) if result.isNil: let env = getEnvParam(owner) if env.isNil or not owner.isIterator or not isDefined(c.graph.config, "nimOptIters"): result = newType(tyRef, c.idgen, owner) let obj = createEnvObj(c.graph, c.idgen, owner, info) rawAddSon(result, obj) else: result = env.typ c.ownerToType[owner.id] = result proc asOwnedRef(c: var DetectionPass; t: PType): PType = if optOwnedRefs in c.graph.config.globalOptions: assert t.kind == tyRef result = newType(tyOwned, c.idgen, t.owner) result.flags.incl tfHasOwned result.rawAddSon t else: result = t proc getEnvTypeForOwnerUp(c: var DetectionPass; owner: PSym; info: TLineInfo): PType = var r = c.getEnvTypeForOwner(owner, info) result = newType(tyPtr, c.idgen, owner) rawAddSon(result, r.skipTypes({tyOwned, tyRef, tyPtr})) proc createUpField(c: var DetectionPass; dest, dep: PSym; info: TLineInfo) = let refObj = c.getEnvTypeForOwner(dest, info) # getHiddenParam(dest).typ let obj = refObj.skipTypes({tyOwned, tyRef, tyPtr}) # The assumption here is that gcDestructors means we cannot deal # with cycles properly, so it's better to produce a weak ref (=ptr) here. # This seems to be generally correct but since it's a bit risky it's disabled # for now. # XXX This is wrong for the 'hamming' test, so remove this logic again. let fieldType = if isDefined(c.graph.config, "nimCycleBreaker"): c.getEnvTypeForOwnerUp(dep, info) #getHiddenParam(dep).typ else: c.getEnvTypeForOwner(dep, info) if refObj == fieldType: localError(c.graph.config, dep.info, "internal error: invalid up reference computed") let upIdent = getIdent(c.graph.cache, upName) let upField = lookupInRecord(obj.n, upIdent) if upField != nil: if upField.typ.skipTypes({tyOwned, tyRef, tyPtr}) != fieldType.skipTypes({tyOwned, tyRef, tyPtr}): localError(c.graph.config, dep.info, "internal error: up references do not agree") when false: if c.graph.config.selectedGC == gcDestructors and sfCursor notin upField.flags: localError(c.graph.config, dep.info, "internal error: up reference is not a .cursor") else: let result = newSym(skField, upIdent, c.idgen, obj.owner, obj.owner.info) result.typ = fieldType when false: if c.graph.config.selectedGC == gcDestructors: result.flags.incl sfCursor rawAddField(obj, result) discard """ There are a couple of possibilities of how to implement closure iterators that capture outer variables in a traditional sense (aka closure closure iterators). 1. Transform iter() to iter(state, capturedEnv). So use 2 hidden parameters. 2. Add the captured vars directly to 'state'. 3. Make capturedEnv an up-reference of 'state'. We do (3) here because (2) is obviously wrong and (1) is wrong too. Consider: proc outer = var xx = 9 iterator foo() = var someState = 3 proc bar = echo someState proc baz = someState = 0 baz() bar() """ proc isTypeOf(n: PNode): bool = n.kind == nkSym and n.sym.magic in {mTypeOf, mType} proc addClosureParam(c: var DetectionPass; fn: PSym; info: TLineInfo) = var cp = getEnvParam(fn) let owner = if fn.kind == skIterator: fn else: fn.skipGenericOwner let t = c.getEnvTypeForOwner(owner, info) if cp == nil: cp = newSym(skParam, getIdent(c.graph.cache, paramName), c.idgen, fn, fn.info) incl(cp.flags, sfFromGeneric) cp.typ = t addHiddenParam(fn, cp) elif cp.typ != t and fn.kind != skIterator: localError(c.graph.config, fn.info, "internal error: inconsistent environment type") #echo "adding closure to ", fn.name.s proc detectCapturedVars(n: PNode; owner: PSym; c: var DetectionPass) = case n.kind of nkSym: let s = n.sym if s.kind in {skProc, skFunc, skMethod, skConverter, skIterator} and s.typ != nil and s.typ.callConv == ccClosure: # this handles the case that the inner proc was declared as # .closure but does not actually capture anything: addClosureParam(c, s, n.info) c.somethingToDo = true let innerProc = isInnerProc(s) if innerProc: if s.isIterator: c.somethingToDo = true if not c.processed.containsOrIncl(s.id): let body = transformBody(c.graph, c.idgen, s, {useCache}) detectCapturedVars(body, s, c) let ow = s.skipGenericOwner let innerClosure = innerProc and s.typ.callConv == ccClosure and not s.isIterator let interested = interestingVar(s) if ow == owner: if owner.isIterator: c.somethingToDo = true addClosureParam(c, owner, n.info) if not isDefined(c.graph.config, "nimOptIters") and interestingIterVar(s): if not c.capturedVars.contains(s.id): if not c.inTypeOf: c.capturedVars.incl(s.id) let obj = getHiddenParam(c.graph, owner).typ.skipTypes({tyOwned, tyRef, tyPtr}) #let obj = c.getEnvTypeForOwner(s.owner).skipTypes({tyOwned, tyRef, tyPtr}) if s.name.id == getIdent(c.graph.cache, ":state").id: obj.n[0].sym.flags.incl sfNoInit obj.n[0].sym.itemId = ItemId(module: s.itemId.module, item: -s.itemId.item) else: discard addField(obj, s, c.graph.cache, c.idgen) # direct or indirect dependency: elif innerClosure or interested: discard """ proc outer() = var x: int proc inner() = proc innerInner() = echo x innerInner() inner() # inner() takes a closure too! """ # mark 'owner' as taking a closure: c.somethingToDo = true markAsClosure(c.graph, owner, n) addClosureParam(c, owner, n.info) #echo "capturing ", n.info # variable 's' is actually captured: if interestingVar(s): if not c.capturedVars.contains(s.id): if not c.inTypeOf: c.capturedVars.incl(s.id) let obj = c.getEnvTypeForOwner(ow, n.info).skipTypes({tyOwned, tyRef, tyPtr}) #getHiddenParam(owner).typ.skipTypes({tyOwned, tyRef, tyPtr}) discard addField(obj, s, c.graph.cache, c.idgen) # create required upFields: var w = owner.skipGenericOwner if isInnerProc(w) or owner.isIterator: if owner.isIterator: w = owner let last = if ow.isIterator: ow.skipGenericOwner else: ow while w != nil and w.kind != skModule and last != w: discard """ proc outer = var a, b: int proc outerB = proc innerA = use(a) proc innerB = use(b); innerA() # --> make outerB of calling convention .closure and # give it the same env type that outer's env var gets: """ let up = w.skipGenericOwner #echo "up for ", w.name.s, " up ", up.name.s markAsClosure(c.graph, w, n) addClosureParam(c, w, n.info) # , ow createUpField(c, w, up, n.info) w = up of nkEmpty..pred(nkSym), succ(nkSym)..nkNilLit, nkTemplateDef, nkTypeSection, nkProcDef, nkMethodDef, nkConverterDef, nkMacroDef, nkFuncDef, nkCommentStmt, nkTypeOfExpr, nkMixinStmt, nkBindStmt: discard of nkLambdaKinds, nkIteratorDef: if n.typ != nil: detectCapturedVars(n[namePos], owner, c) of nkReturnStmt: detectCapturedVars(n[0], owner, c) of nkIdentDefs: detectCapturedVars(n[^1], owner, c) else: if n.isCallExpr and n[0].isTypeOf: c.inTypeOf = true for i in 0.. When to create the closure? --> for the (count) occurrence! discard """ for i in foo(): ... Is transformed to: cl = createClosure() while true: let i = foo(cl) if (nkBreakState(cl.state)): break ... """ if liftingHarmful(g.config, owner): return body if not (body.kind == nkForStmt and body[^2].kind in nkCallKinds): localError(g.config, body.info, "ignored invalid for loop") return body var call = body[^2] result = newNodeI(nkStmtList, body.info) # static binding? var env: PSym = nil let op = call[0] if op.kind == nkSym and op.sym.isIterator: # createClosure() let iter = op.sym let hp = getHiddenParam(g, iter) env = newSym(skLet, iter.name, idgen, owner, body.info) env.typ = hp.typ env.flags = hp.flags var v = newNodeI(nkVarSection, body.info) addVar(v, newSymNode(env)) result.add(v) # add 'new' statement: result.add genCreateEnv(env.newSymNode) createTypeBoundOpsLL(g, env.typ, body.info, idgen, owner) elif op.kind == nkStmtListExpr: let closure = op.lastSon if closure.kind == nkClosure: call[0] = closure for i in 0..