# # # The Nim Compiler # (c) Copyright 2013 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. # ## this module does the semantic checking of statements # included from sem.nim const errNoSymbolToBorrowFromFound = "no symbol to borrow from found" errDiscardValueX = "value of type '$1' has to be used (or discarded)" errInvalidDiscard = "statement returns no value that can be discarded" errInvalidControlFlowX = "invalid control flow: $1" errSelectorMustBeOfCertainTypes = "selector must be of an ordinal type, float or string" errExprCannotBeRaised = "only a 'ref object' can be raised" errBreakOnlyInLoop = "'break' only allowed in loop construct" errExceptionAlreadyHandled = "exception already handled" errYieldNotAllowedHere = "'yield' only allowed in an iterator" errYieldNotAllowedInTryStmt = "'yield' cannot be used within 'try' in a non-inlined iterator" errInvalidNumberOfYieldExpr = "invalid number of 'yield' expressions" errCannotReturnExpr = "current routine cannot return an expression" errGenericLambdaNotAllowed = "A nested proc can have generic parameters only when " & "it is used as an operand to another routine and the types " & "of the generic paramers can be inferred from the expected signature." errCannotInferTypeOfTheLiteral = "cannot infer the type of the $1" errCannotInferReturnType = "cannot infer the return type of '$1'" errCannotInferStaticParam = "cannot infer the value of the static param '$1'" errProcHasNoConcreteType = "'$1' doesn't have a concrete type, due to unspecified generic parameters." errLetNeedsInit = "'let' symbol requires an initialization" errThreadvarCannotInit = "a thread var cannot be initialized explicitly; this would only run for the main thread" errImplOfXexpected = "implementation of '$1' expected" errRecursiveDependencyX = "recursive dependency: '$1'" errRecursiveDependencyIteratorX = "recursion is not supported in iterators: '$1'" errPragmaOnlyInHeaderOfProcX = "pragmas are only allowed in the header of a proc; redefinition of $1" proc semDiscard(c: PContext, n: PNode): PNode = result = n checkSonsLen(n, 1, c.config) if n[0].kind != nkEmpty: n[0] = semExprWithType(c, n[0]) let sonType = n[0].typ let sonKind = n[0].kind if isEmptyType(sonType) or sonType.kind in {tyNone, tyTypeDesc} or sonKind == nkTypeOfExpr: localError(c.config, n.info, errInvalidDiscard) if sonType.kind == tyProc and sonKind notin nkCallKinds: # tyProc is disallowed to prevent ``discard foo`` to be valid, when ``discard foo()`` is meant. localError(c.config, n.info, "illegal discard proc, did you mean: " & $n[0] & "()") proc semBreakOrContinue(c: PContext, n: PNode): PNode = result = n checkSonsLen(n, 1, c.config) if n[0].kind != nkEmpty: if n.kind != nkContinueStmt: var s: PSym case n[0].kind of nkIdent: s = lookUp(c, n[0]) of nkSym: s = n[0].sym else: illFormedAst(n, c.config) s = getGenSym(c, s) if s.kind == skLabel and s.owner.id == c.p.owner.id: var x = newSymNode(s) x.info = n.info incl(s.flags, sfUsed) n[0] = x suggestSym(c.graph, x.info, s, c.graph.usageSym) onUse(x.info, s) else: localError(c.config, n.info, errInvalidControlFlowX % s.name.s) else: localError(c.config, n.info, errGenerated, "'continue' cannot have a label") elif (c.p.nestedLoopCounter <= 0) and ((c.p.nestedBlockCounter <= 0) or n.kind == nkContinueStmt): localError(c.config, n.info, errInvalidControlFlowX % renderTree(n, {renderNoComments})) proc semAsm(c: PContext, n: PNode): PNode = checkSonsLen(n, 2, c.config) var marker = pragmaAsm(c, n[0]) if marker == '\0': marker = '`' # default marker result = semAsmOrEmit(c, n, marker) proc semWhile(c: PContext, n: PNode; flags: TExprFlags): PNode = result = n checkSonsLen(n, 2, c.config) openScope(c) n[0] = forceBool(c, semExprWithType(c, n[0])) inc(c.p.nestedLoopCounter) n[1] = semStmt(c, n[1], flags) dec(c.p.nestedLoopCounter) closeScope(c) if n[1].typ == c.enforceVoidContext: result.typ = c.enforceVoidContext elif efInTypeof in flags: result.typ = n[1].typ proc semProc(c: PContext, n: PNode): PNode proc semExprBranch(c: PContext, n: PNode; flags: TExprFlags = {}): PNode = result = semExpr(c, n, flags) if result.typ != nil: # XXX tyGenericInst here? if result.typ.kind in {tyVar, tyLent}: result = newDeref(result) proc semExprBranchScope(c: PContext, n: PNode): PNode = openScope(c) result = semExprBranch(c, n) closeScope(c) const skipForDiscardable = {nkIfStmt, nkIfExpr, nkCaseStmt, nkOfBranch, nkElse, nkStmtListExpr, nkTryStmt, nkFinally, nkExceptBranch, nkElifBranch, nkElifExpr, nkElseExpr, nkBlockStmt, nkBlockExpr, nkHiddenStdConv, nkHiddenDeref} proc implicitlyDiscardable(n: PNode): bool = var n = n while n.kind in skipForDiscardable: n = n.lastSon result = n.kind in nkLastBlockStmts or (isCallExpr(n) and n[0].kind == nkSym and sfDiscardable in n[0].sym.flags) proc fixNilType(c: PContext; n: PNode) = if isAtom(n): if n.kind != nkNilLit and n.typ != nil: localError(c.config, n.info, errDiscardValueX % n.typ.typeToString) elif n.kind in {nkStmtList, nkStmtListExpr}: n.transitionSonsKind(nkStmtList) for it in n: fixNilType(c, it) n.typ = nil proc discardCheck(c: PContext, result: PNode, flags: TExprFlags) = if c.matchedConcept != nil or efInTypeof in flags: return if result.typ != nil and result.typ.kind notin {tyTyped, tyVoid}: if implicitlyDiscardable(result): var n = newNodeI(nkDiscardStmt, result.info, 1) n[0] = result elif result.typ.kind != tyError and c.config.cmd != cmdInteractive: var n = result while n.kind in skipForDiscardable: n = n.lastSon var s = "expression '" & $n & "' is of type '" & result.typ.typeToString & "' and has to be used (or discarded)" if result.info.line != n.info.line or result.info.fileIndex != n.info.fileIndex: s.add "; start of expression here: " & c.config$result.info if result.typ.kind == tyProc: s.add "; for a function call use ()" localError(c.config, n.info, s) proc semIf(c: PContext, n: PNode; flags: TExprFlags): PNode = result = n var typ = commonTypeBegin var hasElse = false for i in 0.. ```except a, b, c: body``` a.sons[0..0] = a[0].sons if a.len == 2 and a[0].isInfixAs(): # support ``except Exception as ex: body`` let isImported = semExceptBranchType(a[0][1]) let symbol = newSymG(skLet, a[0][2], c) symbol.typ = if isImported: a[0][1].typ else: a[0][1].typ.toRef(c.idgen) addDecl(c, symbol) # Overwrite symbol in AST with the symbol in the symbol table. a[0][2] = newSymNode(symbol, a[0][2].info) elif a.len == 1: # count number of ``except: body`` blocks inc catchAllExcepts else: # support ``except KeyError, ValueError, ... : body`` if catchAllExcepts > 0: # if ``except: body`` already encountered, # cannot be followed by a ``except KeyError, ... : body`` block inc catchAllExcepts var isNative, isImported: bool for j in 0.. 1: # if number of ``except: body`` blocks is greater than 1 # or more specific exception follows a general except block, it is invalid localError(c.config, a.info, "Only one general except clause is allowed after more specific exceptions") # last child of an nkExcept/nkFinally branch is a statement: a[^1] = semExprBranchScope(c, a[^1]) if a.kind != nkFinally: typ = commonType(c, typ, a[^1]) else: dec last closeScope(c) if isEmptyType(typ) or typ.kind in {tyNil, tyUntyped}: discardCheck(c, n[0], flags) for i in 1.. 1: return getLineInfo(n[1]) of nkAccQuoted, nkPragmaExpr: if len(n) > 0: return getLineInfo(n[0]) else: discard result = n.info let info = getLineInfo(n) suggestSym(c.graph, info, result, c.graph.usageSym) proc checkNilable(c: PContext; v: PSym) = if {sfGlobal, sfImportc} * v.flags == {sfGlobal} and v.typ.requiresInit: if v.astdef.isNil: message(c.config, v.info, warnProveInit, v.name.s) elif tfNotNil in v.typ.flags and not v.astdef.typ.isNil and tfNotNil notin v.astdef.typ.flags: message(c.config, v.info, warnProveInit, v.name.s) #include liftdestructors proc addToVarSection(c: PContext; result: PNode; orig, identDefs: PNode) = let value = identDefs[^1] if result.kind == nkStmtList: let o = copyNode(orig) o.add identDefs result.add o else: result.add identDefs proc isDiscardUnderscore(v: PSym): bool = if v.name.s == "_": v.flags.incl(sfGenSym) result = true proc semUsing(c: PContext; n: PNode): PNode = result = c.graph.emptyNode if not isTopLevel(c): localError(c.config, n.info, errXOnlyAtModuleScope % "using") for i in 0.. 3: message(c.config, a.info, warnEachIdentIsTuple) for j in 0.. 0: v.flags.incl(sfShadowed) else: let shadowed = findShadowedVar(c, v) if shadowed != nil: shadowed.flags.incl(sfShadowed) if shadowed.kind == skResult and sfGenSym notin v.flags: message(c.config, a.info, warnResultShadowed) if a.kind != nkVarTuple: if def.kind != nkEmpty: if sfThread in v.flags: localError(c.config, def.info, errThreadvarCannotInit) setVarType(c, v, typ) b = newNodeI(nkIdentDefs, a.info) if importantComments(c.config): # keep documentation information: b.comment = a.comment b.add newSymNode(v) # keep type desc for doc generator b.add a[^2] b.add copyTree(def) addToVarSection(c, result, n, b) # this is needed for the evaluation pass, guard checking # and custom pragmas: var ast = newNodeI(nkIdentDefs, a.info) if a[j].kind == nkPragmaExpr: var p = newNodeI(nkPragmaExpr, a.info) p.add newSymNode(v) p.add a[j][1].copyTree ast.add p else: ast.add newSymNode(v) ast.add a[^2].copyTree ast.add def v.ast = ast else: if def.kind in {nkPar, nkTupleConstr}: v.ast = def[j] # bug #7663, for 'nim check' this can be a non-tuple: if tup.kind == tyTuple: setVarType(c, v, tup[j]) else: v.typ = tup b[j] = newSymNode(v) if def.kind == nkEmpty: let actualType = v.typ.skipTypes({tyGenericInst, tyAlias, tyUserTypeClassInst}) if actualType.kind in {tyObject, tyDistinct} and actualType.requiresInit: defaultConstructionError(c, v.typ, v.info) else: checkNilable(c, v) # allow let to not be initialised if imported from C: if v.kind == skLet and sfImportc notin v.flags: localError(c.config, a.info, errLetNeedsInit) if sfCompileTime in v.flags: var x = newNodeI(result.kind, v.info) x.add result[i] vm.setupCompileTimeVar(c.module, c.idgen, c.graph, x) if v.flags * {sfGlobal, sfThread} == {sfGlobal}: message(c.config, v.info, hintGlobalVar) proc semConst(c: PContext, n: PNode): PNode = result = copyNode(n) inc c.inStaticContext for i in 0.. 0 and not isException(typ.lastSon): localError(c.config, n.info, "raised object of type $1 does not inherit from Exception" % typeToString(typ)) proc addGenericParamListToScope(c: PContext, n: PNode) = if n.kind != nkGenericParams: illFormedAst(n, c.config) for i in 0.. 0: x = x.lastSon # we need the 'safeSkipTypes' here because illegally recursive types # can enter at this point, see bug #13763 if x.kind notin {nkObjectTy, nkDistinctTy, nkEnumTy, nkEmpty} and s.typ.safeSkipTypes(abstractPtrs).kind notin {tyObject, tyEnum}: # type aliases are hard: var t = semTypeNode(c, x, nil) assert t != nil if s.typ != nil and s.typ.kind notin {tyAlias, tySink}: if t.kind in {tyProc, tyGenericInst} and not t.isMetaType: assignType(s.typ, t) s.typ.itemId = t.itemId elif t.kind in {tyObject, tyEnum, tyDistinct}: assert s.typ != nil assignType(s.typ, t) s.typ.itemId = t.itemId # same id checkConstructedType(c.config, s.info, s.typ) if s.typ.kind in {tyObject, tyTuple} and not s.typ.n.isNil: checkForMetaFields(c, s.typ.n) # fix bug #5170, bug #17162, bug #15526: ensure locally scoped types get a unique name: if s.typ.kind in {tyEnum, tyRef, tyObject} and not isTopLevel(c): incl(s.flags, sfGenSym) #instAllTypeBoundOp(c, n.info) proc semAllTypeSections(c: PContext; n: PNode): PNode = proc gatherStmts(c: PContext; n: PNode; result: PNode) {.nimcall.} = case n.kind of nkIncludeStmt: for i in 0.. 0: s.typ.n[0] = b.typ.n[0] s.typ.flags = b.typ.flags else: localError(c.config, n.info, errNoSymbolToBorrowFromFound) proc swapResult(n: PNode, sRes: PSym, dNode: PNode) = ## Swap nodes that are (skResult) symbols to d(estination)Node. for i in 0.. resultPos and n[resultPos] != nil: if n[resultPos].sym.kind != skResult: localError(c.config, n.info, "incorrect result proc symbol") if n[resultPos].sym.owner != getCurrOwner(c): # re-write result with new ownership, and re-write the proc accordingly let sResSym = n[resultPos].sym genResSym(s) n[resultPos] = newSymNode(s) swapResult(n, sResSym, n[resultPos]) c.p.resultSym = n[resultPos].sym else: genResSym(s) c.p.resultSym = s n.add newSymNode(c.p.resultSym) addParamOrResult(c, c.p.resultSym, owner) proc copyExcept(n: PNode, i: int): PNode = result = copyNode(n) for j in 0..= 1: it[0] else: it if whichPragma(it) != wInvalid: # Not a custom pragma continue else: let ident = considerQuotedIdent(c, key) if strTableGet(c.userPragmas, ident) != nil: continue # User defined pragma else: var amb = false let sym = searchInScopes(c, ident, amb) if sym != nil and sfCustomPragma in sym.flags: continue # User custom pragma # we transform ``proc p {.m, rest.}`` into ``m(do: proc p {.rest.})`` and # let the semantic checker deal with it: var x = newNodeI(nkCall, key.info) x.add(key) if it.kind in nkPragmaCallKinds and it.len > 1: # pass pragma arguments to the macro too: for i in 1..= 2 and t[0] == nil if cond: var obj = t[1].skipTypes({tyVar}) while true: incl(obj.flags, tfHasAsgn) if obj.kind in {tyGenericBody, tyGenericInst}: obj = obj.lastSon elif obj.kind == tyGenericInvocation: obj = obj[0] else: break if obj.kind in {tyObject, tyDistinct, tySequence, tyString}: obj = canonType(c, obj) let ao = getAttachedOp(c.graph, obj, op) if ao == s: discard "forward declared destructor" elif ao.isNil and tfCheckedForDestructor notin obj.flags: setAttachedOp(c.graph, c.module.position, obj, op, s) else: prevDestructor(c, ao, obj, n.info) noError = true if obj.owner.getModule != s.getModule: localError(c.config, n.info, errGenerated, "type bound operation `" & s.name.s & "` can be defined only in the same module with its type (" & obj.typeToString() & ")") if not noError and sfSystemModule notin s.owner.flags: if op == attachedTrace: localError(c.config, n.info, errGenerated, "signature for '=trace' must be proc[T: object](x: var T; env: pointer)") else: localError(c.config, n.info, errGenerated, "signature for '" & s.name.s & "' must be proc[T: object](x: var T)") incl(s.flags, sfUsed) incl(s.flags, sfOverriden) proc semOverride(c: PContext, s: PSym, n: PNode) = let name = s.name.s.normalize case name of "=destroy": bindTypeHook(c, s, n, attachedDestructor) of "deepcopy", "=deepcopy": if s.typ.len == 2 and s.typ[1].skipTypes(abstractInst).kind in {tyRef, tyPtr} and sameType(s.typ[1], s.typ[0]): # Note: we store the deepCopy in the base of the pointer to mitigate # the problem that pointers are structural types: var t = s.typ[1].skipTypes(abstractInst).lastSon.skipTypes(abstractInst) while true: if t.kind == tyGenericBody: t = t.lastSon elif t.kind == tyGenericInvocation: t = t[0] else: break if t.kind in {tyObject, tyDistinct, tyEnum, tySequence, tyString}: if getAttachedOp(c.graph, t, attachedDeepCopy).isNil: setAttachedOp(c.graph, c.module.position, t, attachedDeepCopy, s) else: localError(c.config, n.info, errGenerated, "cannot bind another 'deepCopy' to: " & typeToString(t)) else: localError(c.config, n.info, errGenerated, "cannot bind 'deepCopy' to: " & typeToString(t)) if t.owner.getModule != s.getModule: localError(c.config, n.info, errGenerated, "type bound operation `" & name & "` can be defined only in the same module with its type (" & t.typeToString() & ")") else: localError(c.config, n.info, errGenerated, "signature for 'deepCopy' must be proc[T: ptr|ref](x: T): T") incl(s.flags, sfUsed) incl(s.flags, sfOverriden) of "=", "=copy", "=sink": if s.magic == mAsgn: return incl(s.flags, sfUsed) incl(s.flags, sfOverriden) let t = s.typ if t.len == 3 and t[0] == nil and t[1].kind == tyVar: var obj = t[1][0] while true: incl(obj.flags, tfHasAsgn) if obj.kind == tyGenericBody: obj = obj.lastSon elif obj.kind == tyGenericInvocation: obj = obj[0] else: break var objB = t[2] while true: if objB.kind == tyGenericBody: objB = objB.lastSon elif objB.kind in {tyGenericInvocation, tyGenericInst}: objB = objB[0] else: break if obj.kind in {tyObject, tyDistinct, tySequence, tyString} and sameType(obj, objB): # attach these ops to the canonical tySequence obj = canonType(c, obj) #echo "ATTACHING TO ", obj.id, " ", s.name.s, " ", cast[int](obj) let k = if name == "=" or name == "=copy": attachedAsgn else: attachedSink let ao = getAttachedOp(c.graph, obj, k) if ao == s: discard "forward declared op" elif ao.isNil and tfCheckedForDestructor notin obj.flags: setAttachedOp(c.graph, c.module.position, obj, k, s) else: prevDestructor(c, ao, obj, n.info) if obj.owner.getModule != s.getModule: localError(c.config, n.info, errGenerated, "type bound operation `" & name & "` can be defined only in the same module with its type (" & obj.typeToString() & ")") return if sfSystemModule notin s.owner.flags: localError(c.config, n.info, errGenerated, "signature for '" & s.name.s & "' must be proc[T: object](x: var T; y: T)") of "=trace": if s.magic != mTrace: bindTypeHook(c, s, n, attachedTrace) else: if sfOverriden in s.flags: localError(c.config, n.info, errGenerated, "'destroy' or 'deepCopy' expected for 'override'") proc cursorInProcAux(conf: ConfigRef; n: PNode): bool = if inCheckpoint(n.info, conf.m.trackPos) != cpNone: return true for i in 0.. 0: n.comment = proto.ast.comment proto.ast = n # needed for code generation popOwner(c) pushOwner(c, s) if not isAnon: if sfOverriden in s.flags or s.name.s[0] == '=': semOverride(c, s, n) elif s.name.s[0] in {'.', '('}: if s.name.s in [".", ".()", ".="] and {Feature.destructor, dotOperators} * c.features == {}: localError(c.config, n.info, "the overloaded " & s.name.s & " operator has to be enabled with {.experimental: \"dotOperators\".}") elif s.name.s == "()" and callOperator notin c.features: localError(c.config, n.info, "the overloaded " & s.name.s & " operator has to be enabled with {.experimental: \"callOperator\".}") if n[bodyPos].kind != nkEmpty and sfError notin s.flags: # for DLL generation we allow sfImportc to have a body, for use in VM if sfBorrow in s.flags: localError(c.config, n[bodyPos].info, errImplOfXNotAllowed % s.name.s) if c.config.ideCmd in {ideSug, ideCon} and s.kind notin {skMacro, skTemplate} and not cursorInProc(c.config, n[bodyPos]): # speed up nimsuggest if s.kind == skMethod: semMethodPrototype(c, s, n) elif isAnon: let gp = n[genericParamsPos] if gp.kind == nkEmpty or (gp.len == 1 and tfRetType in gp[0].typ.flags): # absolutely no generics (empty) or a single generic return type are # allowed, everything else, including a nullary generic is an error. pushProcCon(c, s) addResult(c, n, s.typ[0], skProc) s.ast[bodyPos] = hloBody(c, semProcBody(c, n[bodyPos])) trackProc(c, s, s.ast[bodyPos]) popProcCon(c) elif efOperand notin flags: localError(c.config, n.info, errGenericLambdaNotAllowed) else: pushProcCon(c, s) if n[genericParamsPos].kind == nkEmpty or s.kind in {skMacro, skTemplate}: # Macros and Templates can have generic parameters, but they are only # used for overload resolution (there is no instantiation of the symbol) if s.kind notin {skMacro, skTemplate} and s.magic == mNone: paramsTypeCheck(c, s.typ) maybeAddResult(c, s, n) # semantic checking also needed with importc in case used in VM s.ast[bodyPos] = hloBody(c, semProcBody(c, n[bodyPos])) # unfortunately we cannot skip this step when in 'system.compiles' # context as it may even be evaluated in 'system.compiles': trackProc(c, s, s.ast[bodyPos]) else: if (s.typ[0] != nil and s.kind != skIterator): addDecl(c, newSym(skUnknown, getIdent(c.cache, "result"), nextSymId c.idgen, nil, n.info)) openScope(c) n[bodyPos] = semGenericStmt(c, n[bodyPos]) closeScope(c) if s.magic == mNone: fixupInstantiatedSymbols(c, s) if s.kind == skMethod: semMethodPrototype(c, s, n) popProcCon(c) else: if s.kind == skMethod: semMethodPrototype(c, s, n) if hasProto: localError(c.config, n.info, errImplOfXexpected % proto.name.s) if {sfImportc, sfBorrow, sfError} * s.flags == {} and s.magic == mNone: # this is a forward declaration and we're building the prototype if s.kind in {skProc, skFunc} and s.typ[0] != nil and s.typ[0].kind == tyUntyped: # `auto` is represented as `tyUntyped` at this point in compilation. localError(c.config, n[paramsPos][0].info, "return type 'auto' cannot be used in forward declarations") incl(s.flags, sfForward) incl(s.flags, sfWasForwarded) elif sfBorrow in s.flags: semBorrow(c, n, s) sideEffectsCheck(c, s) closeScope(c) # close scope for parameters # c.currentScope = oldScope popOwner(c) if n[patternPos].kind != nkEmpty: c.patterns.add(s) if isAnon: n.transitionSonsKind(nkLambda) result.typ = s.typ if optOwnedRefs in c.config.globalOptions: result.typ = makeVarType(c, result.typ, tyOwned) elif isTopLevel(c) and s.kind != skIterator and s.typ.callConv == ccClosure: localError(c.config, s.info, "'.closure' calling convention for top level routines is invalid") proc determineType(c: PContext, s: PSym) = if s.typ != nil: return #if s.magic != mNone: return #if s.ast.isNil: return discard semProcAux(c, s.ast, s.kind, {}) proc semIterator(c: PContext, n: PNode): PNode = # gensym'ed iterator? if n[namePos].kind == nkSym: # gensym'ed iterators might need to become closure iterators: n[namePos].sym.owner = getCurrOwner(c) n[namePos].sym.transitionRoutineSymKind(skIterator) result = semProcAux(c, n, skIterator, iteratorPragmas) # bug #7093: if after a macro transformation we don't have an # nkIteratorDef aynmore, return. The iterator then might have been # sem'checked already. (Or not, if the macro skips it.) if result.kind != n.kind: return var s = result[namePos].sym var t = s.typ if t[0] == nil and s.typ.callConv != ccClosure: localError(c.config, n.info, "iterator needs a return type") # iterators are either 'inline' or 'closure'; for backwards compatibility, # we require first class iterators to be marked with 'closure' explicitly # -- at least for 0.9.2. if s.typ.callConv == ccClosure: incl(s.typ.flags, tfCapturesEnv) else: s.typ.callConv = ccInline if n[bodyPos].kind == nkEmpty and s.magic == mNone and c.inConceptDecl == 0: localError(c.config, n.info, errImplOfXexpected % s.name.s) if optOwnedRefs in c.config.globalOptions and result.typ != nil: result.typ = makeVarType(c, result.typ, tyOwned) result.typ.callConv = ccClosure proc semProc(c: PContext, n: PNode): PNode = result = semProcAux(c, n, skProc, procPragmas) proc semFunc(c: PContext, n: PNode): PNode = let validPragmas = if n[namePos].kind != nkEmpty: procPragmas else: lambdaPragmas result = semProcAux(c, n, skFunc, validPragmas) proc semMethod(c: PContext, n: PNode): PNode = if not isTopLevel(c): localError(c.config, n.info, errXOnlyAtModuleScope % "method") result = semProcAux(c, n, skMethod, methodPragmas) # macros can transform converters to nothing: if namePos >= result.safeLen: return result # bug #7093: if after a macro transformation we don't have an # nkIteratorDef aynmore, return. The iterator then might have been # sem'checked already. (Or not, if the macro skips it.) if result.kind != nkMethodDef: return var s = result[namePos].sym # we need to fix the 'auto' return type for the dispatcher here (see tautonotgeneric # test case): let disp = getDispatcher(s) # auto return type? if disp != nil and disp.typ[0] != nil and disp.typ[0].kind == tyUntyped: let ret = s.typ[0] disp.typ[0] = ret if disp.ast[resultPos].kind == nkSym: if isEmptyType(ret): disp.ast[resultPos] = c.graph.emptyNode else: disp.ast[resultPos].sym.typ = ret proc semConverterDef(c: PContext, n: PNode): PNode = if not isTopLevel(c): localError(c.config, n.info, errXOnlyAtModuleScope % "converter") checkSonsLen(n, bodyPos + 1, c.config) result = semProcAux(c, n, skConverter, converterPragmas) # macros can transform converters to nothing: if namePos >= result.safeLen: return result # bug #7093: if after a macro transformation we don't have an # nkIteratorDef aynmore, return. The iterator then might have been # sem'checked already. (Or not, if the macro skips it.) if result.kind != nkConverterDef: return var s = result[namePos].sym var t = s.typ if t[0] == nil: localError(c.config, n.info, errXNeedsReturnType % "converter") if t.len != 2: localError(c.config, n.info, "a converter takes exactly one argument") addConverterDef(c, LazySym(sym: s)) proc semMacroDef(c: PContext, n: PNode): PNode = checkSonsLen(n, bodyPos + 1, c.config) result = semProcAux(c, n, skMacro, macroPragmas) # macros can transform macros to nothing: if namePos >= result.safeLen: return result # bug #7093: if after a macro transformation we don't have an # nkIteratorDef aynmore, return. The iterator then might have been # sem'checked already. (Or not, if the macro skips it.) if result.kind != nkMacroDef: return var s = result[namePos].sym var t = s.typ var allUntyped = true for i in 1.. 0 and n[last].kind in {nkPragma, nkCommentStmt, # nkNilLit, nkEmpty}: # dec last for i in 0..