diff options
author | Simon Hafner <hafnersimon@gmail.com> | 2015-05-08 06:40:34 +0500 |
---|---|---|
committer | Simon Hafner <hafnersimon@gmail.com> | 2015-05-08 06:40:34 +0500 |
commit | f5cca89610905f35b50259cfe81e6d1d4153d39c (patch) | |
tree | 3c49f45590875e4eab78ae976d6ac254030e62af /compiler | |
parent | 2474c1bb111b38ddef64659c893722b357a27384 (diff) | |
parent | c384f05e49e0716cc99042491f65bcc7d415d4c3 (diff) | |
download | Nim-f5cca89610905f35b50259cfe81e6d1d4153d39c.tar.gz |
merged devel into epc
Diffstat (limited to 'compiler')
44 files changed, 1141 insertions, 517 deletions
diff --git a/compiler/ast.nim b/compiler/ast.nim index b0e9577fc..3798410e8 100644 --- a/compiler/ast.nim +++ b/compiler/ast.nim @@ -1,7 +1,7 @@ # # # The Nim Compiler -# (c) Copyright 2013 Andreas Rumpf +# (c) Copyright 2015 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. @@ -296,6 +296,7 @@ const sfCompileToCpp* = sfInfixCall # compile the module as C++ code sfCompileToObjc* = sfNamedParamCall # compile the module as Objective-C code sfExperimental* = sfOverriden # module uses the .experimental switch + sfGoto* = sfOverriden # var is used for 'goto' code generation const # getting ready for the future expr/stmt merge @@ -529,19 +530,20 @@ type TMagic* = enum # symbols that require compiler magic: mNone, mDefined, mDefinedInScope, mCompiles, - mLow, mHigh, mSizeOf, mTypeTrait, mIs, mOf, mAddr, mTypeOf, mRoof, + mLow, mHigh, mSizeOf, mTypeTrait, mIs, mOf, mAddr, mTypeOf, mRoof, mPlugin, mEcho, mShallowCopy, mSlurp, mStaticExec, mParseExprToAst, mParseStmtToAst, mExpandToAst, mQuoteAst, mUnaryLt, mInc, mDec, mOrd, mNew, mNewFinalize, mNewSeq, mLengthOpenArray, - mLengthStr, mLengthArray, mLengthSeq, mIncl, mExcl, mCard, mChr, mGCref, - mGCunref, + mLengthStr, mLengthArray, mLengthSeq, mXLenStr, mXLenSeq, + mIncl, mExcl, mCard, mChr, + mGCref, mGCunref, mAddI, mSubI, mMulI, mDivI, mModI, mAddI64, mSubI64, mMulI64, mDivI64, mModI64, mSucc, mPred, mAddF64, mSubF64, mMulF64, mDivF64, mShrI, mShlI, mBitandI, mBitorI, mBitxorI, mMinI, mMaxI, - mShrI64, mShlI64, mBitandI64, mBitorI64, mBitxorI64, mMinI64, mMaxI64, + mShrI64, mShlI64, mBitandI64, mBitorI64, mBitxorI64, mMinF64, mMaxF64, mAddU, mSubU, mMulU, mDivU, mModU, mEqI, mLeI, mLtI, @@ -550,7 +552,7 @@ type mEqEnum, mLeEnum, mLtEnum, mEqCh, mLeCh, mLtCh, mEqB, mLeB, mLtB, mEqRef, mEqUntracedRef, mLePtr, mLtPtr, mEqCString, mXor, mEqProc, mUnaryMinusI, mUnaryMinusI64, mAbsI, mAbsI64, mNot, - mUnaryPlusI, mBitnotI, mUnaryPlusI64, + mUnaryPlusI, mBitnotI, mBitnotI64, mUnaryPlusF64, mUnaryMinusF64, mAbsF64, mZe8ToI, mZe8ToI64, mZe16ToI, mZe16ToI64, mZe32ToI64, mZeIToI64, mToU8, mToU16, mToU32, mToFloat, mToBiggestFloat, mToInt, mToBiggestInt, mCharToStr, mBoolToStr, @@ -589,11 +591,12 @@ type const ctfeWhitelist* = {mNone, mUnaryLt, mSucc, mPred, mInc, mDec, mOrd, mLengthOpenArray, - mLengthStr, mLengthArray, mLengthSeq, mIncl, mExcl, mCard, mChr, + mLengthStr, mLengthArray, mLengthSeq, mXLenStr, mXLenSeq, + mIncl, mExcl, mCard, mChr, mAddI, mSubI, mMulI, mDivI, mModI, mAddI64, mSubI64, mMulI64, mDivI64, mModI64, mAddF64, mSubF64, mMulF64, mDivF64, mShrI, mShlI, mBitandI, mBitorI, mBitxorI, mMinI, mMaxI, - mShrI64, mShlI64, mBitandI64, mBitorI64, mBitxorI64, mMinI64, mMaxI64, + mShrI64, mShlI64, mBitandI64, mBitorI64, mBitxorI64, mMinF64, mMaxF64, mAddU, mSubU, mMulU, mDivU, mModU, mEqI, mLeI, mLtI, @@ -602,7 +605,7 @@ const mEqEnum, mLeEnum, mLtEnum, mEqCh, mLeCh, mLtCh, mEqB, mLeB, mLtB, mEqRef, mEqProc, mEqUntracedRef, mLePtr, mLtPtr, mEqCString, mXor, mUnaryMinusI, mUnaryMinusI64, mAbsI, mAbsI64, mNot, - mUnaryPlusI, mBitnotI, mUnaryPlusI64, + mUnaryPlusI, mBitnotI, mBitnotI64, mUnaryPlusF64, mUnaryMinusF64, mAbsF64, mZe8ToI, mZe8ToI64, mZe16ToI, mZe16ToI64, mZe32ToI64, mZeIToI64, mToU8, mToU16, mToU32, mToFloat, mToBiggestFloat, mToInt, mToBiggestInt, mCharToStr, mBoolToStr, @@ -1170,7 +1173,9 @@ proc newType*(kind: TTypeKind, owner: PSym): PType = result.lockLevel = UnspecifiedLockLevel when debugIds: registerId(result) - #if result.id < 2000: + #if result.id == 92231: + # echo "KNID ", kind + # writeStackTrace() # messageOut(typeKindToStr[kind] & ' has id: ' & toString(result.id)) proc mergeLoc(a: var TLoc, b: TLoc) = diff --git a/compiler/ccgexprs.nim b/compiler/ccgexprs.nim index 11c9d2d50..05a3602d1 100644 --- a/compiler/ccgexprs.nim +++ b/compiler/ccgexprs.nim @@ -566,8 +566,6 @@ proc binaryArith(p: BProc, e: PNode, d: var TLoc, op: TMagic) = "($4)($1 & $2)", # BitandI64 "($4)($1 | $2)", # BitorI64 "($4)($1 ^ $2)", # BitxorI64 - "(($1 <= $2) ? $1 : $2)", # MinI64 - "(($1 >= $2) ? $1 : $2)", # MaxI64 "(($1 <= $2) ? $1 : $2)", # MinF64 "(($1 >= $2) ? $1 : $2)", # MaxF64 "($4)((NU$3)($1) + (NU$3)($2))", # AddU @@ -640,7 +638,6 @@ proc unaryArith(p: BProc, e: PNode, d: var TLoc, op: TMagic) = unArithTab: array[mNot..mToBiggestInt, string] = ["!($1)", # Not "$1", # UnaryPlusI "($3)((NU$2) ~($1))", # BitnotI - "$1", # UnaryPlusI64 "($3)((NU$2) ~($1))", # BitnotI64 "$1", # UnaryPlusF64 "-($1)", # UnaryMinusF64 @@ -676,7 +673,7 @@ proc isCppRef(p: BProc; typ: PType): bool {.inline.} = proc genDeref(p: BProc, e: PNode, d: var TLoc; enforceDeref=false) = let mt = mapType(e.sons[0].typ) - if (mt in {ctArray, ctPtrToArray} and not enforceDeref): + if mt in {ctArray, ctPtrToArray} and not enforceDeref: # XXX the amount of hacks for C's arrays is incredible, maybe we should # simply wrap them in a struct? --> Losing auto vectorization then? #if e[0].kind != nkBracketExpr: @@ -685,19 +682,29 @@ proc genDeref(p: BProc, e: PNode, d: var TLoc; enforceDeref=false) = else: var a: TLoc initLocExprSingleUse(p, e.sons[0], a) - let typ = skipTypes(a.t, abstractInst) - case typ.kind - of tyRef: - d.s = OnHeap - of tyVar: - d.s = OnUnknown - if tfVarIsPtr notin typ.flags and p.module.compileToCpp and - e.kind == nkHiddenDeref: + if d.k == locNone: + let typ = skipTypes(a.t, abstractInst) + # dest = *a; <-- We do not know that 'dest' is on the heap! + # It is completely wrong to set 'd.s' here, unless it's not yet + # been assigned to. + case typ.kind + of tyRef: + d.s = OnHeap + of tyVar: + d.s = OnUnknown + if tfVarIsPtr notin typ.flags and p.module.compileToCpp and + e.kind == nkHiddenDeref: + putIntoDest(p, d, e.typ, rdLoc(a)) + return + of tyPtr: + d.s = OnUnknown # BUGFIX! + else: internalError(e.info, "genDeref " & $a.t.kind) + elif p.module.compileToCpp: + let typ = skipTypes(a.t, abstractInst) + if typ.kind == tyVar and tfVarIsPtr notin typ.flags and + e.kind == nkHiddenDeref: putIntoDest(p, d, e.typ, rdLoc(a)) return - of tyPtr: - d.s = OnUnknown # BUGFIX! - else: internalError(e.info, "genDeref " & $a.t.kind) if enforceDeref and mt == ctPtrToArray: # we lie about the type for better C interop: 'ptr array[3,T]' is # translated to 'ptr T', but for deref'ing this produces wrong code. @@ -957,8 +964,11 @@ proc genEcho(p: BProc, n: PNode) = var args: Rope = nil var a: TLoc for i in countup(0, n.len-1): - initLocExpr(p, n.sons[i], a) - addf(args, ", $1? ($1)->data:\"nil\"", [rdLoc(a)]) + if n.sons[i].skipConv.kind == nkNilLit: + add(args, ", \"nil\"") + else: + initLocExpr(p, n.sons[i], a) + addf(args, ", $1? ($1)->data:\"nil\"", [rdLoc(a)]) linefmt(p, cpsStmts, "printf($1$2);$n", makeCString(repeat("%s", n.len) & tnl), args) @@ -1345,15 +1355,15 @@ proc genArrayLen(p: BProc, e: PNode, d: var TLoc, op: TMagic) = else: unaryExpr(p, e, d, "$1Len0") of tyCString: useStringh(p.module) - if op == mHigh: unaryExpr(p, e, d, "(strlen($1)-1)") - else: unaryExpr(p, e, d, "strlen($1)") + if op == mHigh: unaryExpr(p, e, d, "($1 ? (strlen($1)-1) : -1)") + else: unaryExpr(p, e, d, "($1 ? strlen($1) : 0)") of tyString, tySequence: if not p.module.compileToCpp: - if op == mHigh: unaryExpr(p, e, d, "($1->Sup.len-1)") - else: unaryExpr(p, e, d, "$1->Sup.len") + if op == mHigh: unaryExpr(p, e, d, "($1 ? ($1->Sup.len-1) : -1)") + else: unaryExpr(p, e, d, "($1 ? $1->Sup.len : 0)") else: - if op == mHigh: unaryExpr(p, e, d, "($1->len-1)") - else: unaryExpr(p, e, d, "$1->len") + if op == mHigh: unaryExpr(p, e, d, "($1 ? ($1->len-1) : -1)") + else: unaryExpr(p, e, d, "($1 ? $1->len : 0)") of tyArray, tyArrayConstr: # YYY: length(sideeffect) is optimized away incorrectly? if op == mHigh: putIntoDest(p, d, e.typ, rope(lastOrd(typ))) @@ -1714,6 +1724,11 @@ proc genMagicExpr(p: BProc, e: PNode, d: var TLoc, op: TMagic) = of mOrd: genOrd(p, e, d) of mLengthArray, mHigh, mLengthStr, mLengthSeq, mLengthOpenArray: genArrayLen(p, e, d, op) + of mXLenStr, mXLenSeq: + if not p.module.compileToCpp: + unaryExpr(p, e, d, "($1->Sup.len-1)") + else: + unaryExpr(p, e, d, "$1->len") of mGCref: unaryStmt(p, e, d, "#nimGCref($1);$n") of mGCunref: unaryStmt(p, e, d, "#nimGCunref($1);$n") of mSetLengthStr: genSetLengthStr(p, e, d) diff --git a/compiler/ccgstmts.nim b/compiler/ccgstmts.nim index 1277f7154..6d29b1684 100644 --- a/compiler/ccgstmts.nim +++ b/compiler/ccgstmts.nim @@ -175,9 +175,18 @@ proc genBreakState(p: BProc, n: PNode) = proc genVarPrototypeAux(m: BModule, sym: PSym) +proc genGotoVar(p: BProc; value: PNode) = + if value.kind notin {nkCharLit..nkUInt64Lit}: + localError(value.info, "'goto' target must be a literal value") + else: + lineF(p, cpsStmts, "goto NIMSTATE_$#;$n", [value.intVal.rope]) + proc genSingleVar(p: BProc, a: PNode) = var v = a.sons[0].sym - if sfCompileTime in v.flags: return + if {sfCompileTime, sfGoto} * v.flags != {}: + # translate 'var state {.goto.} = X' into 'goto LX': + if sfGoto in v.flags: genGotoVar(p, a.sons[2]) + return var targetProc = p if sfGlobal in v.flags: if v.flags * {sfImportc, sfExportc} == {sfImportc} and @@ -365,6 +374,19 @@ proc genReturnStmt(p: BProc, t: PNode) = linefmt(p, cpsStmts, "if ($1.status != 0) #popCurrentException();$n", safePoint) lineF(p, cpsStmts, "goto BeforeRet;$n", []) +proc genGotoForCase(p: BProc; caseStmt: PNode) = + for i in 1 .. <caseStmt.len: + startBlock(p) + let it = caseStmt.sons[i] + for j in 0 .. it.len-2: + if it.sons[j].kind == nkRange: + localError(it.info, "range notation not available for computed goto") + return + let val = getOrdValue(it.sons[j]) + lineF(p, cpsStmts, "NIMSTATE_$#:$n", [val.rope]) + genStmts(p, it.lastSon) + endBlock(p) + proc genComputedGoto(p: BProc; n: PNode) = # first pass: Generate array of computed labels: var casePos = -1 @@ -529,12 +551,7 @@ proc genBreakStmt(p: BProc, t: PNode) = lineF(p, cpsStmts, "goto $1;$n", [label]) proc getRaiseFrmt(p: BProc): string = - if p.module.compileToCpp: - result = "throw NimException($1, $2);$n" - elif getCompilerProc("Exception") != nil: - result = "#raiseException((#Exception*)$1, $2);$n" - else: - result = "#raiseException((#E_Base*)$1, $2);$n" + result = "#raiseException((#Exception*)$1, $2);$n" proc genRaiseStmt(p: BProc, t: PNode) = if p.inExceptBlock > 0: @@ -737,7 +754,10 @@ proc genCase(p: BProc, t: PNode, d: var TLoc) = genCaseGeneric(p, t, d, "if ($1 >= $2 && $1 <= $3) goto $4;$n", "if ($1 == $2) goto $3;$n") else: - genOrdinalCase(p, t, d) + if t.sons[0].kind == nkSym and sfGoto in t.sons[0].sym.flags: + genGotoForCase(p, t) + else: + genOrdinalCase(p, t, d) proc hasGeneralExceptSection(t: PNode): bool = var length = sonsLen(t) @@ -772,11 +792,8 @@ proc genTryCpp(p: BProc, t: PNode, d: var TLoc) = # finallyPart(); if not isEmptyType(t.typ) and d.k == locNone: getTemp(p, t.typ, d) - var - exc: Rope - i, length, blen: int genLineDir(p, t) - exc = getTempName() + let exc = getTempName() if getCompilerProc("Exception") != nil: discard cgsym(p.module, "Exception") else: @@ -784,20 +801,23 @@ proc genTryCpp(p: BProc, t: PNode, d: var TLoc) = add(p.nestedTryStmts, t) startBlock(p, "try {$n") expr(p, t.sons[0], d) - length = sonsLen(t) + let length = sonsLen(t) endBlock(p, ropecg(p.module, "} catch (NimException& $1) {$n", [exc])) if optStackTrace in p.options: - linefmt(p, cpsStmts, "#setFrame((TFrame*)&F);$n") + linefmt(p, cpsStmts, "#setFrame((TFrame*)&FR);$n") inc p.inExceptBlock - i = 1 + var i = 1 var catchAllPresent = false while (i < length) and (t.sons[i].kind == nkExceptBranch): - blen = sonsLen(t.sons[i]) + let blen = sonsLen(t.sons[i]) if i > 1: addf(p.s(cpsStmts), "else ", []) if blen == 1: # general except section: catchAllPresent = true - exprBlock(p, t.sons[i].sons[0], d) + startBlock(p) + expr(p, t.sons[i].sons[0], d) + linefmt(p, cpsStmts, "#popCurrentException();$n") + endBlock(p) else: var orExpr: Rope = nil for j in countup(0, blen - 2): @@ -807,7 +827,10 @@ proc genTryCpp(p: BProc, t: PNode, d: var TLoc) = "#isObj($1.exp->m_type, $2)", [exc, genTypeInfo(p.module, t.sons[i].sons[j].typ)]) lineF(p, cpsStmts, "if ($1) ", [orExpr]) - exprBlock(p, t.sons[i].sons[blen-1], d) + startBlock(p) + expr(p, t.sons[i].sons[blen-1], d) + linefmt(p, cpsStmts, "#popCurrentException();$n") + endBlock(p) inc(i) # reraise the exception if there was no catch all @@ -887,7 +910,7 @@ proc genTry(p: BProc, t: PNode, d: var TLoc) = startBlock(p, "else {$n") linefmt(p, cpsStmts, "#popSafePoint();$n") if optStackTrace in p.options: - linefmt(p, cpsStmts, "#setFrame((TFrame*)&F);$n") + linefmt(p, cpsStmts, "#setFrame((TFrame*)&FR);$n") inc p.inExceptBlock var i = 1 while (i < length) and (t.sons[i].kind == nkExceptBranch): @@ -976,12 +999,19 @@ proc genAsmStmt(p: BProc, t: PNode) = else: lineF(p, cpsStmts, CC[cCompiler].asmStmtFrmt, [s]) +proc determineSection(n: PNode): TCFileSection = + result = cfsProcHeaders + if n.len >= 1 and n.sons[0].kind in {nkStrLit..nkTripleStrLit}: + if n.sons[0].strVal.startsWith("/*TYPESECTION*/"): result = cfsTypes + elif n.sons[0].strVal.startsWith("/*VARSECTION*/"): result = cfsVars + proc genEmit(p: BProc, t: PNode) = var s = genAsmOrEmitStmt(p, t.sons[1]) if p.prc == nil: # top level emit pragma? - genCLineDir(p.module.s[cfsProcHeaders], t.info) - add(p.module.s[cfsProcHeaders], s) + let section = determineSection(t[1]) + genCLineDir(p.module.s[section], t.info) + add(p.module.s[section], s) else: genLineDir(p, t) line(p, cpsStmts, s) @@ -1065,7 +1095,9 @@ proc asgnFieldDiscriminant(p: BProc, e: PNode) = proc genAsgn(p: BProc, e: PNode, fastAsgn: bool) = genLineDir(p, e) - if not fieldDiscriminantCheckNeeded(p, e): + if e.sons[0].kind == nkSym and sfGoto in e.sons[0].sym.flags: + genGotoVar(p, e.sons[1]) + elif not fieldDiscriminantCheckNeeded(p, e): var a: TLoc initLocExpr(p, e.sons[0], a) if fastAsgn: incl(a.flags, lfNoDeepCopy) diff --git a/compiler/ccgtypes.nim b/compiler/ccgtypes.nim index 60ebf591b..3742fd2fd 100644 --- a/compiler/ccgtypes.nim +++ b/compiler/ccgtypes.nim @@ -11,20 +11,21 @@ # ------------------------- Name Mangling -------------------------------- -proc mangleField(name: string): string = - result = mangle(name) - result[0] = result[0].toUpper # Mangling makes everything lowercase, - # but some identifiers are C keywords - proc isKeyword(w: PIdent): bool = - # nimrod and C++ share some keywords - # it's more efficient to test the whole nimrod keywords range + # Nim and C++ share some keywords + # it's more efficient to test the whole Nim keywords range case w.id of ccgKeywordsLow..ccgKeywordsHigh, nimKeywordsLow..nimKeywordsHigh, ord(wInline): return true else: return false +proc mangleField(name: PIdent): string = + result = mangle(name.s) + if isKeyword(name): + result[0] = result[0].toUpper # Mangling makes everything lowercase, + # but some identifiers are C keywords + proc mangleName(s: PSym): Rope = result = s.loc.r if result == nil: @@ -110,7 +111,7 @@ proc mapSetType(typ: PType): TCTypeKind = else: result = ctArray proc mapType(typ: PType): TCTypeKind = - ## Maps a nimrod type to a C type + ## Maps a Nim type to a C type case typ.kind of tyNone, tyStmt: result = ctVoid of tyBool: result = ctBool @@ -379,7 +380,7 @@ proc mangleRecFieldName(field: PSym, rectype: PType): Rope = ({sfImportc, sfExportc} * rectype.sym.flags != {}): result = field.loc.r else: - result = rope(mangleField(field.name.s)) + result = rope(mangleField(field.name)) if result == nil: internalError(field.info, "mangleRecFieldName") proc genRecordFieldsAux(m: BModule, n: PNode, @@ -642,7 +643,7 @@ proc getTypeDescAux(m: BModule, typ: PType, check: var IntSet): Rope = result.add getTypeDescAux(m, typeInSlot, check) else: inc i - + if chunkStart != 0: result.add cppName.data.substr(chunkStart) else: diff --git a/compiler/ccgutils.nim b/compiler/ccgutils.nim index 4e94c1867..4ba6643ec 100644 --- a/compiler/ccgutils.nim +++ b/compiler/ccgutils.nim @@ -176,7 +176,7 @@ proc mangle*(name: string): string = result = newStringOfCap(name.len) case name[0] of Letters: - result.add(name[0].toLower) + result.add(name[0]) of Digits: result.add("N" & name[0]) else: diff --git a/compiler/commands.nim b/compiler/commands.nim index 5b5f461ef..b6ebb6bcb 100644 --- a/compiler/commands.nim +++ b/compiler/commands.nim @@ -319,7 +319,7 @@ proc processSwitch(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = undefSymbol(arg) of "symbol": expectArg(switch, arg, pass, info) - declareSymbol(arg) + # deprecated, do nothing of "compile": expectArg(switch, arg, pass, info) if pass in {passCmd2, passPP}: processCompile(arg) @@ -488,7 +488,6 @@ proc processSwitch(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = if theOS == osNone: localError(info, errUnknownOS, arg) elif theOS != platform.hostOS: setTarget(theOS, targetCPU) - condsyms.initDefines() of "cpu": expectArg(switch, arg, pass, info) if pass in {passCmd1, passPP}: @@ -496,7 +495,6 @@ proc processSwitch(switch, arg: string, pass: TCmdLinePass, info: TLineInfo) = if cpu == cpuNone: localError(info, errUnknownCPU, arg) elif cpu != platform.hostCPU: setTarget(targetOS, cpu) - condsyms.initDefines() of "run", "r": expectNoArg(switch, arg, pass, info) incl(gGlobalOptions, optRun) diff --git a/compiler/condsyms.nim b/compiler/condsyms.nim index 7ddf44d4a..ad7d80c85 100644 --- a/compiler/condsyms.nim +++ b/compiler/condsyms.nim @@ -9,71 +9,69 @@ # This module handles the conditional symbols. -import +import strtabs, platform, strutils, idents -# We need to use a PStringTable here as defined symbols are always guaranteed +# We need to use a StringTableRef here as defined symbols are always guaranteed # to be style insensitive. Otherwise hell would break lose. var gSymbols: StringTableRef -proc defineSymbol*(symbol: string) = - gSymbols[symbol] = "true" +const + catNone = "false" -proc declareSymbol*(symbol: string) = - gSymbols[symbol] = "unknown" +proc defineSymbol*(symbol: string) = + gSymbols[symbol] = "true" -proc undefSymbol*(symbol: string) = - gSymbols[symbol] = "false" +proc undefSymbol*(symbol: string) = + gSymbols[symbol] = catNone -proc isDefined*(symbol: string): bool = +proc isDefined*(symbol: string): bool = if gSymbols.hasKey(symbol): - result = gSymbols[symbol] == "true" - + result = gSymbols[symbol] != catNone + elif cmpIgnoreStyle(symbol, CPU[targetCPU].name) == 0: + result = true + elif cmpIgnoreStyle(symbol, platform.OS[targetOS].name) == 0: + result = true + else: + case symbol.normalize + of "x86": result = targetCPU == cpuI386 + of "itanium": result = targetCPU == cpuIa64 + of "x8664": result = targetCPU == cpuAmd64 + of "posix", "unix": + result = targetOS in {osLinux, osMorphos, osSkyos, osIrix, osPalmos, + osQnx, osAtari, osAix, + osHaiku, osVxWorks, osSolaris, osNetbsd, + osFreebsd, osOpenbsd, osMacosx} + of "bsd": + result = targetOS in {osNetbsd, osFreebsd, osOpenbsd} + of "emulatedthreadvars": + result = platform.OS[targetOS].props.contains(ospLacksThreadVars) + of "msdos": result = targetOS == osDos + of "mswindows", "win32": result = targetOS == osWindows + of "macintosh": result = targetOS in {osMacos, osMacosx} + of "sunos": result = targetOS == osSolaris + of "littleendian": result = CPU[targetCPU].endian == platform.littleEndian + of "bigendian": result = CPU[targetCPU].endian == platform.bigEndian + of "cpu8": result = CPU[targetCPU].bit == 8 + of "cpu16": result = CPU[targetCPU].bit == 16 + of "cpu32": result = CPU[targetCPU].bit == 32 + of "cpu64": result = CPU[targetCPU].bit == 64 + of "nimrawsetjmp": + result = targetOS in {osSolaris, osNetbsd, osFreebsd, osOpenbsd, osMacosx} + else: discard + proc isDefined*(symbol: PIdent): bool = isDefined(symbol.s) -proc isDeclared*(symbol: PIdent): bool = gSymbols.hasKey(symbol.s) iterator definedSymbolNames*: string = for key, val in pairs(gSymbols): - if val == "true": yield key + if val != catNone: yield key -proc countDefinedSymbols*(): int = +proc countDefinedSymbols*(): int = result = 0 for key, val in pairs(gSymbols): - if val == "true": inc(result) - -# For ease of bootstrapping, we keep them here and not in the global config -# file for now: -const - additionalSymbols = """ - x86 itanium x8664 - msdos mswindows win32 unix posix sunos bsd macintosh RISCOS hpux - mac - - hppa hp9000 hp9000s300 hp9000s700 hp9000s800 hp9000s820 ELATE sparcv9 + if val != catNone: inc(result) - ecmascript js nimrodvm nimffi nimdoc cpp objc - gcc llvmgcc clang lcc bcc dmc wcc vcc tcc pcc ucc icl - boehmgc gcmarkandsweep gcgenerational nogc gcUseBitvectors - endb profiler - executable guiapp consoleapp library dll staticlib - - quick - release debug - useWinAnsi useFork useNimRtl useMalloc useRealtimeGC ssl memProfiler - nodejs kwin nimfix - - usesysassert usegcassert tinyC useFFI - useStdoutAsStdmsg createNimRtl - booting fulldebug corruption nimsuperops noSignalHandler useGnuReadline - noCaas noDocGen noBusyWaiting nativeStackTrace useNodeIds selftest - reportMissedDeadlines avoidTimeMachine useClone ignoreAllocationSize - debugExecProcesses pcreDll useLipzipSrc - preventDeadlocks UNICODE winUnicode trackGcHeaders posixRealtime - - nimStdSetjmp nimRawSetjmp nimSigSetjmp - """.split - -proc initDefines*() = +proc initDefines*() = gSymbols = newStringTable(modeStyleInsensitive) defineSymbol("nimrod") # 'nimrod' is always defined # for bootstrapping purposes and old code: @@ -90,58 +88,3 @@ proc initDefines*() = defineSymbol("nimalias") defineSymbol("nimlocks") defineSymbol("nimnode") - - # add platform specific symbols: - for c in low(CPU)..high(CPU): - declareSymbol("cpu" & $CPU[c].bit) - declareSymbol(normalize(EndianToStr[CPU[c].endian])) - declareSymbol(CPU[c].name) - for o in low(platform.OS)..high(platform.OS): - declareSymbol(platform.OS[o].name) - - for a in additionalSymbols: - declareSymbol(a) - - # ----------------------------------------------------------- - case targetCPU - of cpuI386: defineSymbol("x86") - of cpuIa64: defineSymbol("itanium") - of cpuAmd64: defineSymbol("x8664") - else: discard - case targetOS - of osDos: - defineSymbol("msdos") - of osWindows: - defineSymbol("mswindows") - defineSymbol("win32") - of osLinux, osMorphos, osSkyos, osIrix, osPalmos, osQnx, osAtari, osAix, - osHaiku, osVxWorks: - # these are all 'unix-like' - defineSymbol("unix") - defineSymbol("posix") - of osSolaris: - defineSymbol("sunos") - defineSymbol("unix") - defineSymbol("posix") - of osNetbsd, osFreebsd, osOpenbsd: - defineSymbol("unix") - defineSymbol("bsd") - defineSymbol("posix") - of osMacos: - defineSymbol("macintosh") - of osMacosx: - defineSymbol("macintosh") - defineSymbol("unix") - defineSymbol("posix") - else: discard - defineSymbol("cpu" & $CPU[targetCPU].bit) - defineSymbol(normalize(EndianToStr[CPU[targetCPU].endian])) - defineSymbol(CPU[targetCPU].name) - defineSymbol(platform.OS[targetOS].name) - declareSymbol("emulatedthreadvars") - if platform.OS[targetOS].props.contains(ospLacksThreadVars): - defineSymbol("emulatedthreadvars") - case targetOS - of osSolaris, osNetbsd, osFreebsd, osOpenbsd, osMacosx: - defineSymbol("nimRawSetjmp") - else: discard diff --git a/compiler/extccomp.nim b/compiler/extccomp.nim index 499d9ae52..75cb1ef27 100644 --- a/compiler/extccomp.nim +++ b/compiler/extccomp.nim @@ -15,9 +15,9 @@ import lists, ropes, os, strutils, osproc, platform, condsyms, options, msgs, crc -type - TSystemCC* = enum - ccNone, ccGcc, ccLLVM_Gcc, ccCLang, ccLcc, ccBcc, ccDmc, ccWcc, ccVcc, +type + TSystemCC* = enum + ccNone, ccGcc, ccLLVM_Gcc, ccCLang, ccLcc, ccBcc, ccDmc, ccWcc, ccVcc, ccTcc, ccPcc, ccUcc, ccIcl TInfoCCProp* = enum # properties of the C compiler: hasSwitchRange, # CC allows ranges in switch statements (GNU C) @@ -54,7 +54,7 @@ type props: TInfoCCProps] # properties of the C compiler -# Configuration settings for various compilers. +# Configuration settings for various compilers. # When adding new compilers, the cmake sources could be a good reference: # http://cmake.org/gitweb?p=cmake.git;a=tree;f=Modules/Platform; @@ -136,7 +136,7 @@ compiler icl: result = vcc() else: result = gcc() - + result.name = "icl" result.compilerExe = "icl" result.linkerExe = "icl" @@ -317,7 +317,7 @@ compiler ucc: packedPragma: "", # XXX: not supported yet props: {}) -const +const CC*: array[succ(low(TSystemCC))..high(TSystemCC), TInfoCC] = [ gcc(), llvmGcc(), @@ -346,7 +346,7 @@ var proc libNameTmpl(): string {.inline.} = result = if targetOS == osWindows: "$1.lib" else: "lib$1.a" -var +var toLink, toCompile, externalToCompile: TLinkedList linkOptions: string = "" compileOptions: string = "" @@ -355,8 +355,8 @@ var proc nameToCC*(name: string): TSystemCC = ## Returns the kind of compiler referred to by `name`, or ccNone ## if the name doesn't refer to any known compiler. - for i in countup(succ(ccNone), high(TSystemCC)): - if cmpIgnoreStyle(name, CC[i].name) == 0: + for i in countup(succ(ccNone), high(TSystemCC)): + if cmpIgnoreStyle(name, CC[i].name) == 0: return i result = ccNone @@ -375,8 +375,8 @@ proc getConfigVar(c: TSystemCC, suffix: string): string = if (platform.hostOS != targetOS or platform.hostCPU != targetCPU) and optCompileOnly notin gGlobalOptions: - let fullCCname = platform.CPU[targetCPU].name & '.' & - platform.OS[targetOS].name & '.' & + let fullCCname = platform.CPU[targetCPU].name & '.' & + platform.OS[targetOS].name & '.' & CC[c].name & fullSuffix result = getConfigVar(fullCCname) if result.len == 0: @@ -385,7 +385,7 @@ proc getConfigVar(c: TSystemCC, suffix: string): string = else: result = getConfigVar(CC[c].name & fullSuffix) -proc setCC*(ccname: string) = +proc setCC*(ccname: string) = cCompiler = nameToCC(ccname) if cCompiler == ccNone: rawMessage(errUnknownCcompiler, ccname) compileOptions = getConfigVar(cCompiler, ".options.always") @@ -394,18 +394,18 @@ proc setCC*(ccname: string) = for i in countup(low(CC), high(CC)): undefSymbol(CC[i].name) defineSymbol(CC[cCompiler].name) -proc addOpt(dest: var string, src: string) = +proc addOpt(dest: var string, src: string) = if len(dest) == 0 or dest[len(dest)-1] != ' ': add(dest, " ") add(dest, src) proc addLinkOption*(option: string) = addOpt(linkOptions, option) -proc addCompileOption*(option: string) = - if strutils.find(compileOptions, option, 0) < 0: +proc addCompileOption*(option: string) = + if strutils.find(compileOptions, option, 0) < 0: addOpt(compileOptions, option) -proc initVars*() = +proc initVars*() = # we need to define the symbol here, because ``CC`` may have never been set! for i in countup(low(CC), high(CC)): undefSymbol(CC[i].name) defineSymbol(CC[cCompiler].name) @@ -414,10 +414,10 @@ proc initVars*() = if len(ccompilerpath) == 0: ccompilerpath = getConfigVar(cCompiler, ".path") -proc completeCFilePath*(cfile: string, createSubDir: bool = true): string = +proc completeCFilePath*(cfile: string, createSubDir: bool = true): string = result = completeGeneratedFilePath(cfile, createSubDir) -proc toObjFile*(filename: string): string = +proc toObjFile*(filename: string): string = # Object file for compilation result = changeFileExt(filename, CC[cCompiler].objExt) @@ -449,22 +449,22 @@ proc execExternalProgram*(cmd: string, prettyCmd = "") = if execWithEcho(cmd, prettyCmd) != 0: rawMessage(errExecutionOfProgramFailed, "") -proc generateScript(projectFile: string, script: Rope) = +proc generateScript(projectFile: string, script: Rope) = let (dir, name, ext) = splitFile(projectFile) - writeRope(script, dir / addFileExt("compile_" & name, + writeRope(script, dir / addFileExt("compile_" & name, platform.OS[targetOS].scriptExt)) -proc getOptSpeed(c: TSystemCC): string = +proc getOptSpeed(c: TSystemCC): string = result = getConfigVar(c, ".options.speed") if result == "": result = CC[c].optSpeed # use default settings from this file -proc getDebug(c: TSystemCC): string = +proc getDebug(c: TSystemCC): string = result = getConfigVar(c, ".options.debug") if result == "": result = CC[c].debug # use default settings from this file -proc getOptSize(c: TSystemCC): string = +proc getOptSize(c: TSystemCC): string = result = getConfigVar(c, ".options.size") if result == "": result = CC[c].optSize # use default settings from this file @@ -476,7 +476,7 @@ proc noAbsolutePaths: bool {.inline.} = # `optGenMapping` is included here for niminst. result = gGlobalOptions * {optGenScript, optGenMapping} != {} -const +const specialFileA = 42 specialFileB = 42 @@ -488,7 +488,7 @@ proc add(s: var string, many: openArray[string]) = proc cFileSpecificOptions(cfilename: string): string = result = compileOptions var trunk = splitFile(cfilename).name - if optCDebug in gGlobalOptions: + if optCDebug in gGlobalOptions: var key = trunk & ".debug" if existsConfigVar(key): addOpt(result, getConfigVar(key)) else: addOpt(result, getDebug(cCompiler)) @@ -528,17 +528,17 @@ proc getLinkerExe(compiler: TSystemCC): string = elif gMixedMode and gCmd != cmdCompileToCpp: CC[compiler].cppCompiler else: compiler.getCompilerExe -proc getCompileCFileCmd*(cfilename: string, isExternal = false): string = +proc getCompileCFileCmd*(cfilename: string, isExternal = false): string = var c = cCompiler var options = cFileSpecificOptions(cfilename) var exe = getConfigVar(c, ".exe") if exe.len == 0: exe = c.getCompilerExe - + if needsExeExt(): exe = addFileExt(exe, "exe") if optGenDynLib in gGlobalOptions and ospNeedsPIC in platform.OS[targetOS].props: add(options, ' ' & CC[c].pic) - + var includeCmd, compilePattern: string if not noAbsolutePaths(): # compute include paths: @@ -551,7 +551,7 @@ proc getCompileCFileCmd*(cfilename: string, isExternal = false): string = else: includeCmd = "" compilePattern = c.getCompilerExe - + var cfile = if noAbsolutePaths(): extractFilename(cfilename) else: cfilename var objfile = if not isExternal or noAbsolutePaths(): @@ -580,14 +580,14 @@ proc footprint(filename: string): TCrc32 = extccomp.CC[extccomp.cCompiler].name >< getCompileCFileCmd(filename, true) -proc externalFileChanged(filename: string): bool = +proc externalFileChanged(filename: string): bool = if gCmd notin {cmdCompileToC, cmdCompileToCpp, cmdCompileToOC, cmdCompileToLLVM}: return false var crcFile = toGeneratedFile(filename.withPackageName, "crc") var currentCrc = int(footprint(filename)) var f: File - if open(f, crcFile, fmRead): + if open(f, crcFile, fmRead): var line = newStringOfCap(40) if not f.readLine(line): line = "0" close(f) @@ -595,7 +595,7 @@ proc externalFileChanged(filename: string): bool = result = oldCrc != currentCrc else: result = true - if result: + if result: if open(f, crcFile, fmWrite): f.writeln($currentCrc) close(f) @@ -607,22 +607,22 @@ proc addExternalFileToCompile*(filename: string) = proc compileCFile(list: TLinkedList, script: var Rope, cmds: var TStringSeq, prettyCmds: var TStringSeq, isExternal: bool) = var it = PStrEntry(list.head) - while it != nil: + while it != nil: inc(fileCounter) # call the C compiler for the .c file: var compileCmd = getCompileCFileCmd(it.data, isExternal) - if optCompileOnly notin gGlobalOptions: + if optCompileOnly notin gGlobalOptions: add(cmds, compileCmd) let (dir, name, ext) = splitFile(it.data) add(prettyCmds, "CC: " & name) - if optGenScript in gGlobalOptions: + if optGenScript in gGlobalOptions: add(script, compileCmd) add(script, tnl) it = PStrEntry(it.next) proc callCCompiler*(projectfile: string) = - var + var linkCmd, buildgui, builddll: string - if gGlobalOptions * {optCompileOnly, optGenScript} == {optCompileOnly}: + if gGlobalOptions * {optCompileOnly, optGenScript} == {optCompileOnly}: return # speed up that call if only compiling and no script shall be # generated fileCounter = 0 @@ -634,11 +634,11 @@ proc callCCompiler*(projectfile: string) = echo prettyCmds[idx] compileCFile(toCompile, script, cmds, prettyCmds, false) compileCFile(externalToCompile, script, cmds, prettyCmds, true) - if optCompileOnly notin gGlobalOptions: + if optCompileOnly notin gGlobalOptions: if gNumberOfProcessors == 0: gNumberOfProcessors = countProcessors() var res = 0 - if gNumberOfProcessors <= 1: - for i in countup(0, high(cmds)): + if gNumberOfProcessors <= 1: + for i in countup(0, high(cmds)): res = execWithEcho(cmds[i]) if res != 0: rawMessage(errExecutionOfProgramFailed, []) elif optListCmd in gGlobalOptions or gVerbosity > 1: @@ -668,7 +668,8 @@ proc callCCompiler*(projectfile: string) = it = PStrEntry(it.next) if optGenStaticLib in gGlobalOptions: - linkCmd = CC[c].buildLib % ["libfile", (libNameTmpl() % gProjectName), + let name = splitFile(gProjectName).name + linkCmd = CC[c].buildLib % ["libfile", (libNameTmpl() % name), "objfiles", objfiles] else: var linkerExe = getConfigVar(c, ".linkerexe") @@ -685,13 +686,13 @@ proc callCCompiler*(projectfile: string) = else: exefile = splitFile(projectfile).name & platform.OS[targetOS].exeExt builddll = "" - if options.outFile.len > 0: + if options.outFile.len > 0: exefile = options.outFile.expandTilde if not noAbsolutePaths(): if not exefile.isAbsolute(): exefile = joinPath(splitFile(projectfile).dir, exefile) exefile = quoteShell(exefile) - let linkOptions = getLinkOptions() & " " & + let linkOptions = getLinkOptions() & " " & getConfigVar(cCompiler, ".options.linker") linkCmd = quoteShell(linkCmd % ["builddll", builddll, "buildgui", buildgui, "options", linkOptions, "objfiles", objfiles, @@ -714,26 +715,26 @@ proc callCCompiler*(projectfile: string) = add(script, tnl) generateScript(projectfile, script) -proc genMappingFiles(list: TLinkedList): Rope = +proc genMappingFiles(list: TLinkedList): Rope = var it = PStrEntry(list.head) - while it != nil: + while it != nil: addf(result, "--file:r\"$1\"$N", [rope(it.data)]) it = PStrEntry(it.next) -proc writeMapping*(gSymbolMapping: Rope) = - if optGenMapping notin gGlobalOptions: return +proc writeMapping*(gSymbolMapping: Rope) = + if optGenMapping notin gGlobalOptions: return var code = rope("[C_Files]\n") add(code, genMappingFiles(toCompile)) add(code, genMappingFiles(externalToCompile)) add(code, "\n[C_Compiler]\nFlags=") add(code, strutils.escape(getCompileOptions())) - + add(code, "\n[Linker]\nFlags=") - add(code, strutils.escape(getLinkOptions() & " " & + add(code, strutils.escape(getLinkOptions() & " " & getConfigVar(cCompiler, ".options.linker"))) add(code, "\n[Environment]\nlibpath=") add(code, strutils.escape(libpath)) - + addf(code, "\n[Symbols]$n$1", [gSymbolMapping]) writeRope(code, joinPath(gProjectPath, "mapping.txt")) diff --git a/compiler/guards.nim b/compiler/guards.nim index cedd2be2b..df2c1dd75 100644 --- a/compiler/guards.nim +++ b/compiler/guards.nim @@ -22,7 +22,8 @@ const someLt = {mLtI, mLtI64, mLtF64, mLtU, mLtU64, mLtEnum, mLtCh, mLtB, mLtPtr, mLtStr} - someLen = {mLengthOpenArray, mLengthStr, mLengthArray, mLengthSeq} + someLen = {mLengthOpenArray, mLengthStr, mLengthArray, mLengthSeq, + mXLenStr, mXLenSeq} someIn = {mInRange, mInSet} @@ -34,8 +35,8 @@ const someMul = {mMulI, mMulI64, mMulF64} someDiv = {mDivI, mDivI64, mDivF64} someMod = {mModI, mModI64} - someMax = {mMaxI, mMaxI64, mMaxF64} - someMin = {mMinI, mMinI64, mMinF64} + someMax = {mMaxI, mMaxF64} + someMin = {mMinI, mMinF64} proc isValue(n: PNode): bool = n.kind in {nkCharLit..nkNilLit} proc isLocation(n: PNode): bool = not n.isValue @@ -122,7 +123,7 @@ proc neg(n: PNode): PNode = let eAsNode = newIntNode(nkIntLit, e.sym.position) if not inSet(n.sons[1], eAsNode): s.add eAsNode result.sons[1] = s - elif lengthOrd(t) < 1000: + elif t.kind notin {tyString, tySequence} and lengthOrd(t) < 1000: result.sons[1] = complement(n.sons[1]) else: # not ({2, 3, 4}.contains(x)) x != 2 and x != 3 and x != 4 @@ -907,5 +908,5 @@ proc buildProperFieldCheck(access, check: PNode): PNode = proc checkFieldAccess*(m: TModel, n: PNode) = for i in 1..n.len-1: let check = buildProperFieldCheck(n.sons[0], n.sons[i]) - if m.doesImply(check) != impYes: + if check != nil and m.doesImply(check) != impYes: message(n.info, warnProveField, renderTree(n.sons[0])); break diff --git a/compiler/installer.ini b/compiler/installer.ini index 12a8e702d..fff82cb5b 100644 --- a/compiler/installer.ini +++ b/compiler/installer.ini @@ -47,7 +47,7 @@ Start: "doc/overview.html" [Other] Files: "readme.txt;install.txt;contributors.txt;copying.txt" -Files: "configure;makefile" +Files: "makefile" Files: "*.ini" Files: "koch.nim" @@ -70,6 +70,10 @@ Files: "doc/*.nim" Files: "doc/*.cfg" Files: "compiler/nimfix/*.nim" Files: "compiler/nimfix/*.cfg" +Files: "compiler/nimsuggest/*.nim" +Files: "compiler/nimsuggest/*.cfg" +Files: "compiler/plugins/locals/*.nim" +Files: "compiler/plugins/active.nim" Files: "tools/*.nim" Files: "tools/*.cfg" Files: "tools/*.tmpl" @@ -97,13 +101,8 @@ Files: "lib/pure/concurrency/*.cfg" Files: "lib/impure/*.nim" Files: "lib/wrappers/*.nim" -Files: "lib/wrappers/cairo/*.nim" -Files: "lib/wrappers/gtk/*.nim" -Files: "lib/wrappers/lua/*.nim" -Files: "lib/wrappers/opengl/*.nim" Files: "lib/wrappers/readline/*.nim" Files: "lib/wrappers/sdl/*.nim" -Files: "lib/wrappers/x11/*.nim" Files: "lib/wrappers/zip/*.nim" Files: "lib/wrappers/zip/libzip_all.c" @@ -115,8 +114,6 @@ Files: "lib/packages/docutils/*.nim" [Other] Files: "examples/*.nim" -Files: "examples/gtk/*.nim" -Files: "examples/0mq/*.nim" Files: "examples/c++iface/*.nim" Files: "examples/objciface/*.nim" Files: "examples/cross_calculator/" @@ -126,12 +123,109 @@ Files: "examples/*.txt" Files: "examples/*.cfg" Files: "examples/*.tmpl" +Files: "tests/actiontable/*.nim" +Files: "tests/alias/*.nim" +Files: "tests/ambsym/*.nim" +Files: "tests/array/*.nim" +Files: "tests/assign/*.nim" +Files: "tests/astoverload/*.nim" +Files: "tests/async/*.nim" +Files: "tests/benchmarks/*.nim" +Files: "tests/bind/*.nim" +Files: "tests/borrow/*.nim" +Files: "tests/casestmt/*.nim" +Files: "tests/ccgbugs/*.nim" +Files: "tests/clearmsg/*.nim" +Files: "tests/closure/*.nim" +Files: "tests/cnstseq/*.nim" +Files: "tests/collections/*.nim" +Files: "tests/compiles/*.nim" +Files: "tests/concat/*.nim" +Files: "tests/concepts/*.nim" +Files: "tests/constr/*.nim" +Files: "tests/constraints/*.nim" +Files: "tests/controlflow/*.nim" +Files: "tests/converter/*.nim" +Files: "tests/cpp/*.nim" +Files: "tests/defaultprocparam/*.nim" +Files: "tests/deprecated/*.nim" +Files: "tests/destructor/*.nim" +Files: "tests/dir with space/*.nim" +Files: "tests/discard/*.nim" +Files: "tests/distinct/*.nim" +Files: "tests/dll/*.nim" +Files: "tests/effects/*.nim" +Files: "tests/enum/*.nim" +Files: "tests/exception/*.nim" +Files: "tests/exprs/*.nim" +Files: "tests/fields/*.nim" +Files: "tests/float/*.nim" +Files: "tests/friends/*.nim" +Files: "tests/gc/*.nim" +Files: "tests/generics/*.nim" +Files: "tests/gensym/*.nim" +Files: "tests/global/*.nim" +Files: "tests/implicit/*.nim" +Files: "tests/init/*.nim" +Files: "tests/iter/*.nim" +Files: "tests/js/*.nim" +Files: "tests/js/*.cfg" +Files: "tests/let/*.nim" +Files: "tests/lexer/*.nim" +Files: "tests/lookups/*.nim" +Files: "tests/macros/*.nim" +Files: "tests/magics/*.nim" +Files: "tests/metatype/*.nim" +Files: "tests/method/*.nim" +Files: "tests/misc/*.nim" +Files: "tests/modules/*.nim" +Files: "tests/namedparams/*.nim" +Files: "tests/notnil/*.nim" +Files: "tests/objects/*.nim" +Files: "tests/objvariant/*.nim" +Files: "tests/openarray/*.nim" +Files: "tests/osproc/*.nim" +Files: "tests/overflw/*.nim" +Files: "tests/overload/*.nim" +Files: "tests/parallel/*.nim" +Files: "tests/parallel/*.cfg" +Files: "tests/parser/*.nim" +Files: "tests/pragmas/*.nim" +Files: "tests/proc/*.nim" +Files: "tests/procvar/*.nim" +Files: "tests/range/*.nim" +Files: "tests/rodfiles/*.nim" +Files: "tests/seq/*.nim" +Files: "tests/sets/*.nim" +Files: "tests/showoff/*.nim" +Files: "tests/specialops/*.nim" +Files: "tests/stdlib/*.nim" +Files: "tests/system/*.nim" +Files: "tests/template/*.nim" +Files: "tests/testament/*.nim" +Files: "tests/testdata/*.nim" +Files: "tests/threads/*.nim" +Files: "tests/threads/*.cfg" +Files: "tests/trmacros/*.nim" +Files: "tests/tuples/*.nim" +Files: "tests/typerel/*.nim" +Files: "tests/types/*.nim" +Files: "tests/usingstmt/*.nim" +Files: "tests/varres/*.nim" +Files: "tests/varstmt/*.nim" +Files: "tests/vm/*.nim" +Files: "tests/readme.txt" +Files: "tests/testament/css/*.css" +Files: "tests/testament/*.cfg" +Files: "lib/pure/unidecode/unidecode.dat" [Windows] Files: "bin/nim.exe" -Files: "bin/nim_debug.exe" Files: "bin/c2nim.exe" Files: "bin/nimgrep.exe" +Files: "bin/nimsuggest.exe" +Files: "bin/nimble.exe" +Files: "bin/*.dll" Files: "dist/*.dll" Files: "koch.exe" @@ -142,7 +236,7 @@ BinPath: r"bin;dist\mingw\bin;dist" ; Section | dir | zipFile | size hint (in KB) | url | exe start menu entry Download: r"Documentation|doc|docs.zip|13824|http://nim-lang.org/download/docs-${version}.zip|overview.html" Download: r"C Compiler (MingW)|dist|mingw.zip|82944|http://nim-lang.org/download/${mingw}.zip" -Download: r"Aporia IDE|dist|aporia.zip|97997|http://nim-lang.org/download/aporia-0.1.3.zip|aporia\bin\aporia.exe" +Download: r"Aporia IDE|dist|aporia.zip|97997|http://nim-lang.org/download/aporia-0.3.0.zip|aporia-0.3.0\bin\aporia.exe" ; for now only NSIS supports optional downloads [UnixBin] diff --git a/compiler/jsgen.nim b/compiler/jsgen.nim index 6c667a3a7..704713243 100644 --- a/compiler/jsgen.nim +++ b/compiler/jsgen.nim @@ -124,7 +124,7 @@ proc newProc(globals: PGlobals, module: BModule, procDef: PNode, const MappedToObject = {tyObject, tyArray, tyArrayConstr, tyTuple, tyOpenArray, - tySet, tyVar, tyRef, tyPtr, tyBigNum, tyVarargs} + tySet, tyBigNum, tyVarargs} proc mapType(typ: PType): TJSTypeKind = let t = skipTypes(typ, abstractInst) @@ -163,7 +163,8 @@ proc mangleName(s: PSym): Rope = add(result, rope(s.id)) s.loc.r = result -proc makeJSString(s: string): Rope = strutils.escape(s).rope +proc makeJSString(s: string): Rope = + (if s.isNil: "null".rope else: strutils.escape(s).rope) include jstypes @@ -280,8 +281,6 @@ const # magic checked op; magic unchecked op; checked op; unchecked op ["", "", "($1 & $2)", "($1 & $2)"], # BitandI64 ["", "", "($1 | $2)", "($1 | $2)"], # BitorI64 ["", "", "($1 ^ $2)", "($1 ^ $2)"], # BitxorI64 - ["nimMin", "nimMin", "nimMin($1, $2)", "nimMin($1, $2)"], # MinI64 - ["nimMax", "nimMax", "nimMax($1, $2)", "nimMax($1, $2)"], # MaxI64 ["nimMin", "nimMin", "nimMin($1, $2)", "nimMin($1, $2)"], # MinF64 ["nimMax", "nimMax", "nimMax($1, $2)", "nimMax($1, $2)"], # MaxF64 ["addU", "addU", "addU($1, $2)", "addU($1, $2)"], # addU @@ -325,7 +324,6 @@ const # magic checked op; magic unchecked op; checked op; unchecked op ["", "", "!($1)", "!($1)"], # Not ["", "", "+($1)", "+($1)"], # UnaryPlusI ["", "", "~($1)", "~($1)"], # BitnotI - ["", "", "+($1)", "+($1)"], # UnaryPlusI64 ["", "", "~($1)", "~($1)"], # BitnotI64 ["", "", "+($1)", "+($1)"], # UnaryPlusF64 ["", "", "-($1)", "-($1)"], # UnaryMinusF64 @@ -382,8 +380,6 @@ const # magic checked op; magic unchecked op; checked op; unchecked op ["", "", "($1 & $2)", "($1 & $2)"], # BitandI64 ["", "", "($1 | $2)", "($1 | $2)"], # BitorI64 ["", "", "($1 ^ $2)", "($1 ^ $2)"], # BitxorI64 - ["nimMin", "nimMin", "nimMin($1, $2)", "nimMin($1, $2)"], # MinI64 - ["nimMax", "nimMax", "nimMax($1, $2)", "nimMax($1, $2)"], # MaxI64 ["nimMin", "nimMin", "nimMin($1, $2)", "nimMin($1, $2)"], # MinF64 ["nimMax", "nimMax", "nimMax($1, $2)", "nimMax($1, $2)"], # MaxF64 ["addU", "addU", "addU($1, $2)", "addU($1, $2)"], # addU @@ -427,7 +423,6 @@ const # magic checked op; magic unchecked op; checked op; unchecked op ["", "", "not ($1)", "not ($1)"], # Not ["", "", "+($1)", "+($1)"], # UnaryPlusI ["", "", "~($1)", "~($1)"], # BitnotI - ["", "", "+($1)", "+($1)"], # UnaryPlusI64 ["", "", "~($1)", "~($1)"], # BitnotI64 ["", "", "+($1)", "+($1)"], # UnaryPlusF64 ["", "", "-($1)", "-($1)"], # UnaryMinusF64 @@ -937,6 +932,13 @@ proc genArrayAccess(p: PProc, n: PNode, r: var TCompRes) = r.address = nil r.kind = resExpr +proc isIndirect(v: PSym): bool = + result = {sfAddrTaken, sfGlobal} * v.flags != {} and + #(mapType(v.typ) != etyObject) and + {sfImportc, sfVolatile, sfExportc} * v.flags == {} and + v.kind notin {skProc, skConverter, skMethod, skIterator, skClosureIterator, + skConst, skTemp, skLet} + proc genAddr(p: PProc, n: PNode, r: var TCompRes) = case n.sons[0].kind of nkSym: @@ -945,12 +947,16 @@ proc genAddr(p: PProc, n: PNode, r: var TCompRes) = case s.kind of skVar, skLet, skResult: r.kind = resExpr - if mapType(n.sons[0].typ) == etyObject: + let jsType = mapType(n.typ) + if jsType == etyObject: # make addr() a no-op: r.typ = etyNone - r.res = s.loc.r + if isIndirect(s): + r.res = s.loc.r & "[0]" + else: + r.res = s.loc.r r.address = nil - elif {sfGlobal, sfAddrTaken} * s.flags != {}: + elif {sfGlobal, sfAddrTaken} * s.flags != {} or jsType == etyBaseIndex: # for ease of code generation, we do not distinguish between # sfAddrTaken and sfGlobal. r.typ = etyBaseIndex @@ -992,7 +998,7 @@ proc genSym(p: PProc, n: PNode, r: var TCompRes) = else: r.address = s.loc.r r.res = s.loc.r & "_Idx" - elif k != etyObject and {sfAddrTaken, sfGlobal} * s.flags != {}: + elif isIndirect(s): r.res = "$1[0]" % [s.loc.r] else: r.res = s.loc.r @@ -1124,7 +1130,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = of tyRange, tyGenericInst: result = createVar(p, lastSon(typ), indirect) of tySet: - result = rope("{}") + result = putToSeq("{}", indirect) of tyBool: result = putToSeq("false", indirect) of tyArray, tyArrayConstr: @@ -1144,6 +1150,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = add(result, createVar(p, e, false)) inc(i) add(result, "]") + if indirect: result = "[$1]" % [result] of tyTuple: result = rope("{") for i in 0.. <t.sonsLen: @@ -1151,6 +1158,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = addf(result, "Field$1: $2" | "Field$# = $#", [i.rope, createVar(p, t.sons[i], false)]) add(result, "}") + if indirect: result = "[$1]" % [result] of tyObject: result = rope("{") var c = 0 @@ -1161,6 +1169,7 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = add(result, createRecordVarAux(p, t.n, c)) t = t.sons[0] add(result, "}") + if indirect: result = "[$1]" % [result] of tyVar, tyPtr, tyRef: if mapType(t) == etyBaseIndex: result = putToSeq("[null, 0]" | "{nil, 0}", indirect) @@ -1172,11 +1181,6 @@ proc createVar(p: PProc, typ: PType, indirect: bool): Rope = internalError("createVar: " & $t.kind) result = nil -proc isIndirect(v: PSym): bool = - result = {sfAddrTaken, sfGlobal} * v.flags != {} and - (mapType(v.typ) != etyObject) and - v.kind notin {skProc, skConverter, skMethod, skIterator, skClosureIterator} - proc genVarInit(p: PProc, v: PSym, n: PNode) = var a: TCompRes @@ -1207,7 +1211,7 @@ proc genVarInit(p: PProc, v: PSym, n: PNode) = else: s = a.res if isIndirect(v): - addf(p.body, "var $1 = [$2];$n" | "local $1 = {$2};$n", [v.loc.r, s]) + addf(p.body, "var $1 = /**/[$2];$n" | "local $1 = {$2};$n", [v.loc.r, s]) else: addf(p.body, "var $1 = $2;$n" | "local $1 = $2;$n", [v.loc.r, s]) @@ -1239,7 +1243,7 @@ proc genNew(p: PProc, n: PNode) = var a: TCompRes gen(p, n.sons[1], a) var t = skipTypes(n.sons[1].typ, abstractVar).sons[0] - addf(p.body, "$1 = $2;$n", [a.res, createVar(p, t, true)]) + addf(p.body, "$1 = $2;$n", [a.res, createVar(p, t, false)]) proc genNewSeq(p: PProc, n: PNode) = var x, y: TCompRes @@ -1325,14 +1329,17 @@ proc genMagic(p: PProc, n: PNode, r: var TCompRes) = # XXX: range checking? if not (optOverflowCheck in p.options): unaryExpr(p, n, r, "", "$1 - 1") else: unaryExpr(p, n, r, "subInt", "subInt($1, 1)") - of mAppendStrCh: binaryExpr(p, n, r, "addChar", "addChar($1, $2)") + of mAppendStrCh: binaryExpr(p, n, r, "addChar", + "if ($1 != null) { addChar($1, $2); } else { $1 = [$2, 0]; }") of mAppendStrStr: if skipTypes(n.sons[1].typ, abstractVarRange).kind == tyCString: - binaryExpr(p, n, r, "", "$1 += $2") + binaryExpr(p, n, r, "", "if ($1 != null) { $1 += $2; } else { $1 = $2; }") else: - binaryExpr(p, n, r, "", "$1 = ($1.slice(0, -1)).concat($2)") + binaryExpr(p, n, r, "", + "if ($1 != null) { $1 = ($1.slice(0, -1)).concat($2); } else { $1 = $2;}") # XXX: make a copy of $2, because of Javascript's sucking semantics - of mAppendSeqElem: binaryExpr(p, n, r, "", "$1.push($2)") + of mAppendSeqElem: binaryExpr(p, n, r, "", + "if ($1 != null) { $1.push($2); } else { $1 = [$2]; }") of mConStrStr: genConStrStr(p, n, r) of mEqStr: binaryExpr(p, n, r, "eqStrings", "eqStrings($1, $2)") of mLeStr: binaryExpr(p, n, r, "cmpStrings", "(cmpStrings($1, $2) <= 0)") @@ -1343,14 +1350,17 @@ proc genMagic(p: PProc, n: PNode, r: var TCompRes) = of mSizeOf: r.res = rope(getSize(n.sons[1].typ)) of mChr, mArrToSeq: gen(p, n.sons[1], r) # nothing to do of mOrd: genOrd(p, n, r) - of mLengthStr: unaryExpr(p, n, r, "", "($1.length-1)") + of mLengthStr: unaryExpr(p, n, r, "", "($1 != null ? $1.length-1 : 0)") + of mXLenStr: unaryExpr(p, n, r, "", "$1.length-1") of mLengthSeq, mLengthOpenArray, mLengthArray: + unaryExpr(p, n, r, "", "($1 != null ? $1.length : 0)") + of mXLenSeq: unaryExpr(p, n, r, "", "$1.length") of mHigh: if skipTypes(n.sons[1].typ, abstractVar).kind == tyString: - unaryExpr(p, n, r, "", "($1.length-2)") + unaryExpr(p, n, r, "", "($1 != null ? ($1.length-2) : -1)") else: - unaryExpr(p, n, r, "", "($1.length-1)") + unaryExpr(p, n, r, "", "($1 != null ? ($1.length-1) : -1)") of mInc: if optOverflowCheck notin p.options: binaryExpr(p, n, r, "", "$1 += $2") else: binaryExpr(p, n, r, "addInt", "$1 = addInt($1, $2)") diff --git a/compiler/lexer.nim b/compiler/lexer.nim index 694d6f4d7..8080e0e8c 100644 --- a/compiler/lexer.nim +++ b/compiler/lexer.nim @@ -61,7 +61,7 @@ type tkComma, tkSemiColon, tkColon, tkColonColon, tkEquals, tkDot, tkDotDot, tkOpr, tkComment, tkAccent, - tkSpaces, tkInfixOpr, tkPrefixOpr, tkPostfixOpr, + tkSpaces, tkInfixOpr, tkPrefixOpr, tkPostfixOpr TTokTypes* = set[TTokType] @@ -221,6 +221,10 @@ proc dispMessage(L: TLexer; info: TLineInfo; msg: TMsgKind; arg: string) = proc lexMessage*(L: TLexer, msg: TMsgKind, arg = "") = L.dispMessage(getLineInfo(L), msg, arg) +proc lexMessageTok*(L: TLexer, msg: TMsgKind, tok: TToken, arg = "") = + var info = newLineInfo(L.fileIdx, tok.line, tok.col) + L.dispMessage(info, msg, arg) + proc lexMessagePos(L: var TLexer, msg: TMsgKind, pos: int, arg = "") = var info = newLineInfo(L.fileIdx, L.lineNumber, pos - L.lineStart) L.dispMessage(info, msg, arg) @@ -863,6 +867,15 @@ proc rawGetTok*(L: var TLexer, tok: var TToken) = of '`': tok.tokType = tkAccent inc(L.bufpos) + of '_': + inc(L.bufpos) + if L.buf[L.bufpos] notin SymChars: + tok.tokType = tkSymbol + tok.ident = getIdent("_") + else: + tok.literal = $c + tok.tokType = tkInvalid + lexMessage(L, errInvalidToken, c & " (\\" & $(ord(c)) & ')') of '\"': # check for extended raw string literal: var rawMode = L.bufpos > 0 and L.buf[L.bufpos-1] in SymChars diff --git a/compiler/lowerings.nim b/compiler/lowerings.nim index 0b4f97ead..b6b01d558 100644 --- a/compiler/lowerings.nim +++ b/compiler/lowerings.nim @@ -15,6 +15,10 @@ const import ast, astalgo, types, idents, magicsys, msgs, options from trees import getMagic +proc newDeref*(n: PNode): PNode {.inline.} = + result = newNodeIT(nkHiddenDeref, n.info, n.typ.sons[0]) + addSon(result, n) + proc newTupleAccess*(tup: PNode, i: int): PNode = result = newNodeIT(nkBracketExpr, tup.info, tup.typ.skipTypes( abstractInst).sons[i]) diff --git a/compiler/msgs.nim b/compiler/msgs.nim index 778b839f3..041a181be 100644 --- a/compiler/msgs.nim +++ b/compiler/msgs.nim @@ -738,7 +738,7 @@ proc writeContext(lastinfo: TLineInfo) = if msgContext[i] != lastinfo and msgContext[i] != info: msgWriteln(PosContextFormat % [toMsgFilename(msgContext[i]), coordToStr(msgContext[i].line), - coordToStr(msgContext[i].col), + coordToStr(msgContext[i].col+1), getMessageStr(errInstantiationFrom, "")]) info = msgContext[i] @@ -781,7 +781,7 @@ proc formatMsg*(info: TLineInfo, msg: TMsgKind, arg: string): string = of hintMin..hintMax: PosHintFormat else: PosErrorFormat result = frmt % [toMsgFilename(info), coordToStr(info.line), - coordToStr(info.col), getMessageStr(msg, arg)] + coordToStr(info.col+1), getMessageStr(msg, arg)] proc liMessage(info: TLineInfo, msg: TMsgKind, arg: string, eh: TErrorHandling) = @@ -804,8 +804,11 @@ proc liMessage(info: TLineInfo, msg: TMsgKind, arg: string, ignoreMsg = optHints notin gOptions or msg notin gNotes frmt = PosHintFormat inc(gHintCounter) + # NOTE: currently line info line numbers start with 1, + # but column numbers start with 0, however most editors expect + # first column to be 1, so we need to +1 here let s = frmt % [toMsgFilename(info), coordToStr(info.line), - coordToStr(info.col), getMessageStr(msg, arg)] + coordToStr(info.col+1), getMessageStr(msg, arg)] if not ignoreMsg and not ignoreMsgBecauseOfIdeTools(msg): msgWriteln(s) if optPrintSurroundingSrc and msg in errMin..errMax: diff --git a/compiler/nimfix/nimfix.nim.cfg b/compiler/nimfix/nimfix.nim.cfg index 533563a98..73219d6f8 100644 --- a/compiler/nimfix/nimfix.nim.cfg +++ b/compiler/nimfix/nimfix.nim.cfg @@ -5,7 +5,7 @@ hint[XDeclaredButNotUsed]:off path:"$projectPath/.." path:"$lib/packages/docutils" -path:"$nim/compiler" +path:"../../compiler" define:useStdoutAsStdmsg symbol:nimfix diff --git a/compiler/nimsuggest/nimsuggest.nim.cfg b/compiler/nimsuggest/nimsuggest.nim.cfg index 062092f16..acca17396 100644 --- a/compiler/nimsuggest/nimsuggest.nim.cfg +++ b/compiler/nimsuggest/nimsuggest.nim.cfg @@ -6,7 +6,7 @@ hint[XDeclaredButNotUsed]:off path:"$projectPath/../.." path:"$lib/packages/docutils" -path:"$nim/compiler" +path:"../../compiler" define:useStdoutAsStdmsg define:nimsuggest diff --git a/compiler/options.nim b/compiler/options.nim index 709959cc4..d07342fce 100644 --- a/compiler/options.nim +++ b/compiler/options.nim @@ -1,7 +1,7 @@ # # # The Nim Compiler -# (c) Copyright 2013 Andreas Rumpf +# (c) Copyright 2015 Andreas Rumpf # # See the file "copying.txt", included in this # distribution, for details about the copyright. diff --git a/compiler/parampatterns.nim b/compiler/parampatterns.nim index 3f67005b9..b7fe269df 100644 --- a/compiler/parampatterns.nim +++ b/compiler/parampatterns.nim @@ -190,6 +190,8 @@ proc isAssignable*(owner: PSym, n: PNode): TAssignableResult = result = arLocalLValue else: result = arLValue + elif n.sym.kind == skParam and n.sym.typ.kind == tyVar: + result = arLValue elif n.sym.kind == skType: let t = n.sym.typ.skipTypes({tyTypeDesc}) if t.kind == tyVar: result = arStrange diff --git a/compiler/parser.nim b/compiler/parser.nim index d2831ea46..0d2ba7cfc 100644 --- a/compiler/parser.nim +++ b/compiler/parser.nim @@ -91,7 +91,7 @@ proc closeParser(p: var TParser) = proc parMessage(p: TParser, msg: TMsgKind, arg = "") = ## Produce and emit the parser message `arg` to output. - lexMessage(p.lex, msg, arg) + lexMessageTok(p.lex, msg, p.tok, arg) proc parMessage(p: TParser, msg: TMsgKind, tok: TToken) = ## Produce and emit a parser message to output about the token `tok` @@ -154,7 +154,7 @@ proc eat(p: var TParser, tokType: TTokType) = if p.tok.tokType == tokType: getTok(p) else: - lexMessage(p.lex, errTokenExpected, TokTypeToStr[tokType]) + lexMessageTok(p.lex, errTokenExpected, p.tok, TokTypeToStr[tokType]) proc parLineInfo(p: TParser): TLineInfo = ## Retrieve the line information associated with the parser's current state. @@ -212,7 +212,8 @@ proc getPrecedence(tok: TToken, strongSpaces: bool): int = let relevantChar = tok.ident.s[0] # arrow like? - if L > 1 and tok.ident.s[L-1] == '>': return considerStrongSpaces(1) + if L > 1 and tok.ident.s[L-1] == '>' and + tok.ident.s[L-2] in {'-', '~', '='}: return considerStrongSpaces(1) template considerAsgn(value: expr) = result = if tok.ident.s[L-1] == '=': 1 else: value @@ -388,7 +389,6 @@ proc exprList(p: var TParser, endTok: TTokType, result: PNode) = if p.tok.tokType != tkComma: break getTok(p) optInd(p, a) - eat(p, endTok) proc dotExpr(p: var TParser, a: PNode): PNode = #| dotExpr = expr '.' optInd symbol @@ -944,8 +944,7 @@ proc parseDoBlock(p: var TParser): PNode = getTok(p) let params = parseParamList(p, retColon=false) let pragmas = optPragmas(p) - eat(p, tkColon) - skipComment(p, result) + colcom(p, result) result = newProcNode(nkDo, info, parseStmt(p), params = params, pragmas = pragmas) @@ -1139,9 +1138,11 @@ proc parseMacroColon(p: var TParser, x: PNode): PNode = result = makeCall(result) getTok(p) skipComment(p, result) + let stmtList = newNodeP(nkStmtList, p) if p.tok.tokType notin {tkOf, tkElif, tkElse, tkExcept}: let body = parseStmt(p) - addSon(result, makeStmtList(body)) + stmtList.add body + #addSon(result, makeStmtList(body)) while sameInd(p): var b: PNode case p.tok.tokType @@ -1153,19 +1154,22 @@ proc parseMacroColon(p: var TParser, x: PNode): PNode = getTok(p) optInd(p, b) addSon(b, parseExpr(p)) - eat(p, tkColon) of tkExcept: b = newNodeP(nkExceptBranch, p) exprList(p, tkColon, b) - skipComment(p, b) of tkElse: b = newNodeP(nkElse, p) getTok(p) - eat(p, tkColon) else: break + eat(p, tkColon) addSon(b, parseStmt(p)) - addSon(result, b) + addSon(stmtList, b) if b.kind == nkElse: break + if stmtList.len == 1 and stmtList[0].kind == nkStmtList: + # to keep backwards compatibility (see tests/vm/tstringnil) + result.add stmtList[0] + else: + result.add stmtList proc parseExprStmt(p: var TParser): PNode = #| exprStmt = simpleExpr @@ -1310,8 +1314,7 @@ proc parseIfOrWhen(p: var TParser, kind: TNodeKind): PNode = var branch = newNodeP(nkElifBranch, p) optInd(p, branch) addSon(branch, parseExpr(p)) - eat(p, tkColon) - skipComment(p, branch) + colcom(p, branch) addSon(branch, parseStmt(p)) skipComment(p, branch) addSon(result, branch) @@ -1319,8 +1322,7 @@ proc parseIfOrWhen(p: var TParser, kind: TNodeKind): PNode = if p.tok.tokType == tkElse and sameOrNoInd(p): var branch = newNodeP(nkElse, p) eat(p, tkElse) - eat(p, tkColon) - skipComment(p, branch) + colcom(p, branch) addSon(branch, parseStmt(p)) addSon(result, branch) @@ -1368,13 +1370,11 @@ proc parseCase(p: var TParser): PNode = getTok(p) optInd(p, b) addSon(b, parseExpr(p)) - eat(p, tkColon) of tkElse: b = newNodeP(nkElse, p) getTok(p) - eat(p, tkColon) else: break - skipComment(p, b) + colcom(p, b) addSon(b, parseStmt(p)) addSon(result, b) if b.kind == nkElse: break @@ -1391,8 +1391,7 @@ proc parseTry(p: var TParser; isExpr: bool): PNode = #| (optInd 'finally' colcom stmt)? result = newNodeP(nkTryStmt, p) getTok(p) - eat(p, tkColon) - skipComment(p, result) + colcom(p, result) addSon(result, parseStmt(p)) var b: PNode = nil while sameOrNoInd(p) or isExpr: @@ -1402,10 +1401,9 @@ proc parseTry(p: var TParser; isExpr: bool): PNode = exprList(p, tkColon, b) of tkFinally: b = newNodeP(nkFinally, p) - getTokNoInd(p) - eat(p, tkColon) + getTok(p) else: break - skipComment(p, b) + colcom(p, b) addSon(b, parseStmt(p)) addSon(result, b) if b.kind == nkFinally: break @@ -1414,7 +1412,7 @@ proc parseTry(p: var TParser; isExpr: bool): PNode = proc parseExceptBlock(p: var TParser, kind: TNodeKind): PNode = #| exceptBlock = 'except' colcom stmt result = newNodeP(kind, p) - getTokNoInd(p) + getTok(p) colcom(p, result) addSon(result, parseStmt(p)) @@ -1447,7 +1445,7 @@ proc parseStaticOrDefer(p: var TParser; k: TNodeKind): PNode = #| staticStmt = 'static' colcom stmt #| deferStmt = 'defer' colcom stmt result = newNodeP(k, p) - getTokNoInd(p) + getTok(p) colcom(p, result) addSon(result, parseStmt(p)) @@ -1628,7 +1626,7 @@ proc parseEnum(p: var TParser): PNode = p.tok.tokType == tkEof: break if result.len <= 1: - lexMessage(p.lex, errIdentifierExpected, prettyTok(p.tok)) + lexMessageTok(p.lex, errIdentifierExpected, p.tok, prettyTok(p.tok)) proc parseObjectPart(p: var TParser): PNode proc parseObjectWhen(p: var TParser): PNode = @@ -1686,9 +1684,8 @@ proc parseObjectCase(p: var TParser): PNode = of tkElse: b = newNodeP(nkElse, p) getTok(p) - eat(p, tkColon) else: break - skipComment(p, b) + colcom(p, b) var fields = parseObjectPart(p) if fields.kind == nkEmpty: parMessage(p, errIdentifierExpected, p.tok) @@ -1884,7 +1881,7 @@ proc simpleStmt(p: var TParser): PNode = proc complexOrSimpleStmt(p: var TParser): PNode = #| complexOrSimpleStmt = (ifStmt | whenStmt | whileStmt - #| | tryStmt | finallyStmt | exceptStmt | forStmt + #| | tryStmt | forStmt #| | blockStmt | staticStmt | deferStmt | asmStmt #| | 'proc' routine #| | 'method' routine diff --git a/compiler/plugins.nim b/compiler/plugins.nim new file mode 100644 index 000000000..1c9b7b77b --- /dev/null +++ b/compiler/plugins.nim @@ -0,0 +1,43 @@ +# +# +# The Nim Compiler +# (c) Copyright 2015 Andreas Rumpf +# +# See the file "copying.txt", included in this +# distribution, for details about the copyright. +# + +## Plugin support for the Nim compiler. Right now there are no plugins and they +## need to be build with the compiler, no DLL support. + +import ast, semdata, idents + +type + Transformation* = proc (c: PContext; n: PNode): PNode {.nimcall.} + Plugin = ref object + fn, module, package: PIdent + t: Transformation + next: Plugin + +proc pluginMatches(p: Plugin; s: PSym): bool = + if s.name.id != p.fn.id: return false + let module = s.owner + if module == nil or module.kind != skModule or + module.name.id != p.module.id: return false + let package = module.owner + if package == nil or package.kind != skPackage or + package.name.id != p.package.id: return false + return true + +var head: Plugin + +proc getPlugin*(fn: PSym): Transformation = + var it = head + while it != nil: + if pluginMatches(it, fn): return it.t + it = it.next + +proc registerPlugin*(package, module, fn: string; t: Transformation) = + let oldHead = head + head = Plugin(fn: getIdent(fn), module: getIdent(module), + package: getIdent(package), t: t, next: oldHead) diff --git a/compiler/plugins/active.nim b/compiler/plugins/active.nim new file mode 100644 index 000000000..e9c11c2ea --- /dev/null +++ b/compiler/plugins/active.nim @@ -0,0 +1,13 @@ +# +# +# The Nim Compiler +# (c) Copyright 2015 Andreas Rumpf +# +# See the file "copying.txt", included in this +# distribution, for details about the copyright. +# + +## Include file that imports all plugins that are active. + +import + locals.locals diff --git a/compiler/plugins/locals/locals.nim b/compiler/plugins/locals/locals.nim new file mode 100644 index 000000000..d89149f33 --- /dev/null +++ b/compiler/plugins/locals/locals.nim @@ -0,0 +1,42 @@ +# +# +# The Nim Compiler +# (c) Copyright 2015 Andreas Rumpf +# +# See the file "copying.txt", included in this +# distribution, for details about the copyright. +# + +## The builtin 'system.locals' implemented as a plugin. + +import plugins, ast, astalgo, magicsys, lookups, semdata, lowerings + +proc semLocals(c: PContext, n: PNode): PNode = + var counter = 0 + var tupleType = newTypeS(tyTuple, c) + result = newNodeIT(nkPar, n.info, tupleType) + tupleType.n = newNodeI(nkRecList, n.info) + # for now we skip openarrays ... + for scope in walkScopes(c.currentScope): + if scope == c.topLevelScope: break + for it in items(scope.symbols): + # XXX parameters' owners are wrong for generics; this caused some pain + # for closures too; we should finally fix it. + #if it.owner != c.p.owner: return result + if it.kind in skLocalVars and + it.typ.skipTypes({tyGenericInst, tyVar}).kind notin + {tyVarargs, tyOpenArray, tyTypeDesc, tyStatic, tyExpr, tyStmt, tyEmpty}: + + var field = newSym(skField, it.name, getCurrOwner(), n.info) + field.typ = it.typ.skipTypes({tyGenericInst, tyVar}) + field.position = counter + inc(counter) + + addSon(tupleType.n, newSymNode(field)) + addSonSkipIntLit(tupleType, field.typ) + + var a = newSymNode(it, result.info) + if it.typ.skipTypes({tyGenericInst}).kind == tyVar: a = newDeref(a) + result.add(a) + +registerPlugin("stdlib", "system", "locals", semLocals) diff --git a/compiler/pragmas.nim b/compiler/pragmas.nim index ec594069e..c048d78e9 100644 --- a/compiler/pragmas.nim +++ b/compiler/pragmas.nim @@ -60,7 +60,7 @@ const varPragmas* = {wImportc, wExportc, wVolatile, wRegister, wThreadVar, wNodecl, wMagic, wHeader, wDeprecated, wCompilerproc, wDynlib, wExtern, wImportCpp, wImportObjC, wError, wNoInit, wCompileTime, wGlobal, - wGensym, wInject, wCodegenDecl, wGuard} + wGensym, wInject, wCodegenDecl, wGuard, wGoto} constPragmas* = {wImportc, wExportc, wHeader, wDeprecated, wMagic, wNodecl, wExtern, wImportCpp, wImportObjC, wError, wGensym, wInject} letPragmas* = varPragmas @@ -843,6 +843,11 @@ proc singlePragma(c: PContext, sym: PSym, n: PNode, i: int, invalidPragma(it) else: sym.guard = pragmaGuard(c, it, sym.kind) + of wGoto: + if sym == nil or sym.kind notin {skVar, skLet}: + invalidPragma(it) + else: + sym.flags.incl sfGoto of wInjectStmt: if it.kind != nkExprColonExpr: localError(it.info, errExprExpected) diff --git a/compiler/sem.nim b/compiler/sem.nim index 7eabaf491..346a17df1 100644 --- a/compiler/sem.nim +++ b/compiler/sem.nim @@ -16,7 +16,7 @@ import procfind, lookups, rodread, pragmas, passes, semdata, semtypinst, sigmatch, intsets, transf, vmdef, vm, idgen, aliases, cgmeth, lambdalifting, evaltempl, patterns, parampatterns, sempass2, nimfix.pretty, semmacrosanity, - semparallel, lowerings + semparallel, lowerings, plugins, plugins.active when defined(nimfix): import nimfix.prettybase @@ -89,6 +89,10 @@ proc fitNode(c: PContext, formal: PType, arg: PNode): PNode = let x = result.skipConv if x.kind == nkPar and formal.kind != tyExpr: changeType(x, formal, check=true) + else: + result = skipHiddenSubConv(result) + #result.typ = takeType(formal, arg.typ) + #echo arg.info, " picked ", result.typ.typeToString proc inferWithMetatype(c: PContext, formal: PType, arg: PNode, coerceDistincts = false): PNode diff --git a/compiler/semdata.nim b/compiler/semdata.nim index cf7a52ff5..345a8c0d1 100644 --- a/compiler/semdata.nim +++ b/compiler/semdata.nim @@ -118,7 +118,6 @@ proc newOptionEntry*(): POptionEntry proc newLib*(kind: TLibKind): PLib proc addToLib*(lib: PLib, sym: PSym) proc makePtrType*(c: PContext, baseType: PType): PType -proc makeVarType*(c: PContext, baseType: PType): PType proc newTypeS*(kind: TTypeKind, c: PContext): PType proc fillTypeS*(dest: PType, kind: TTypeKind, c: PContext) @@ -213,9 +212,12 @@ proc makePtrType(c: PContext, baseType: PType): PType = result = newTypeS(tyPtr, c) addSonSkipIntLit(result, baseType.assertNotNil) -proc makeVarType(c: PContext, baseType: PType): PType = - result = newTypeS(tyVar, c) - addSonSkipIntLit(result, baseType.assertNotNil) +proc makeVarType*(c: PContext, baseType: PType): PType = + if baseType.kind == tyVar: + result = baseType + else: + result = newTypeS(tyVar, c) + addSonSkipIntLit(result, baseType.assertNotNil) proc makeTypeDesc*(c: PContext, typ: PType): PType = result = newTypeS(tyTypeDesc, c) @@ -247,6 +249,7 @@ proc makeAndType*(c: PContext, t1, t2: PType): PType = propagateToOwner(result, t1) propagateToOwner(result, t2) result.flags.incl((t1.flags + t2.flags) * {tfHasStatic}) + result.flags.incl tfHasMeta proc makeOrType*(c: PContext, t1, t2: PType): PType = result = newTypeS(tyOr, c) @@ -254,12 +257,14 @@ proc makeOrType*(c: PContext, t1, t2: PType): PType = propagateToOwner(result, t1) propagateToOwner(result, t2) result.flags.incl((t1.flags + t2.flags) * {tfHasStatic}) + result.flags.incl tfHasMeta proc makeNotType*(c: PContext, t1: PType): PType = result = newTypeS(tyNot, c) result.sons = @[t1] propagateToOwner(result, t1) result.flags.incl(t1.flags * {tfHasStatic}) + result.flags.incl tfHasMeta proc nMinusOne*(n: PNode): PNode = result = newNode(nkCall, n.info, @[ diff --git a/compiler/semexprs.nim b/compiler/semexprs.nim index c5bfbfa92..cd6ba3753 100644 --- a/compiler/semexprs.nim +++ b/compiler/semexprs.nim @@ -24,7 +24,7 @@ proc semFieldAccess(c: PContext, n: PNode, flags: TExprFlags = {}): PNode proc semOperand(c: PContext, n: PNode, flags: TExprFlags = {}): PNode = # same as 'semExprWithType' but doesn't check for proc vars result = semExpr(c, n, flags + {efOperand}) - if result.kind == nkEmpty: + if result.kind == nkEmpty and result.typ.isNil: # do not produce another redundant error message: #raiseRecoverableError("") result = errorNode(c, n) @@ -389,7 +389,7 @@ proc isOpImpl(c: PContext, n: PNode): PNode = maybeLiftType(t2, c, n.info) var m: TCandidate initCandidate(c, m, t2) - let match = typeRel(m, t2, t1) != isNone + let match = typeRel(m, t2, t1) >= isSubtype # isNone result = newIntNode(nkIntLit, ord(match)) result.typ = n.typ @@ -447,6 +447,7 @@ proc changeType(n: PNode, newType: PType, check: bool) = of nkPar: let tup = newType.skipTypes({tyGenericInst}) if tup.kind != tyTuple: + if tup.kind == tyObject: return internalError(n.info, "changeType: no tuple type for constructor") elif sonsLen(n) > 0 and n.sons[0].kind == nkExprColonExpr: # named tuple? @@ -535,43 +536,55 @@ proc semArrayConstr(c: PContext, n: PNode, flags: TExprFlags): PNode = result.typ.sons[0] = makeRangeType(c, 0, sonsLen(result) - 1, n.info) proc fixAbstractType(c: PContext, n: PNode) = - # XXX finally rewrite that crap! - for i in countup(1, sonsLen(n) - 1): - var it = n.sons[i] - case it.kind - of nkHiddenStdConv, nkHiddenSubConv: - if it.sons[1].kind == nkBracket: - it.sons[1].typ = arrayConstrType(c, it.sons[1]) - #it.sons[1] = semArrayConstr(c, it.sons[1]) - if skipTypes(it.typ, abstractVar).kind in {tyOpenArray, tyVarargs}: - #if n.sons[0].kind == nkSym and IdentEq(n.sons[0].sym.name, "[]="): - # debug(n) - - var s = skipTypes(it.sons[1].typ, abstractVar) - if s.kind == tyArrayConstr and s.sons[1].kind == tyEmpty: - s = copyType(s, getCurrOwner(), false) - skipTypes(s, abstractVar).sons[1] = elemType( - skipTypes(it.typ, abstractVar)) - it.sons[1].typ = s - elif s.kind == tySequence and s.sons[0].kind == tyEmpty: - s = copyType(s, getCurrOwner(), false) - skipTypes(s, abstractVar).sons[0] = elemType( - skipTypes(it.typ, abstractVar)) - it.sons[1].typ = s - - elif skipTypes(it.sons[1].typ, abstractVar).kind in - {tyNil, tyArrayConstr, tyTuple, tySet}: + for i in 1 .. < n.len: + let it = n.sons[i] + # do not get rid of nkHiddenSubConv for OpenArrays, the codegen needs it: + if it.kind == nkHiddenSubConv and + skipTypes(it.typ, abstractVar).kind notin {tyOpenArray, tyVarargs}: + if skipTypes(it.sons[1].typ, abstractVar).kind in + {tyNil, tyArrayConstr, tyTuple, tySet}: var s = skipTypes(it.typ, abstractVar) if s.kind != tyExpr: changeType(it.sons[1], s, check=true) n.sons[i] = it.sons[1] - of nkBracket: - # an implicitly constructed array (passed to an open array): - n.sons[i] = semArrayConstr(c, it, {}) - else: - discard - #if (it.typ == nil): - # InternalError(it.info, "fixAbstractType: " & renderTree(it)) + when false: + # XXX finally rewrite that crap! + for i in countup(1, sonsLen(n) - 1): + var it = n.sons[i] + case it.kind + of nkHiddenStdConv, nkHiddenSubConv: + if it.sons[1].kind == nkBracket: + it.sons[1].typ = arrayConstrType(c, it.sons[1]) + #it.sons[1] = semArrayConstr(c, it.sons[1]) + if skipTypes(it.typ, abstractVar).kind in {tyOpenArray, tyVarargs}: + #if n.sons[0].kind == nkSym and IdentEq(n.sons[0].sym.name, "[]="): + # debug(n) + + var s = skipTypes(it.sons[1].typ, abstractVar) + if s.kind == tyArrayConstr and s.sons[1].kind == tyEmpty: + s = copyType(s, getCurrOwner(), false) + skipTypes(s, abstractVar).sons[1] = elemType( + skipTypes(it.typ, abstractVar)) + it.sons[1].typ = s + elif s.kind == tySequence and s.sons[0].kind == tyEmpty: + s = copyType(s, getCurrOwner(), false) + skipTypes(s, abstractVar).sons[0] = elemType( + skipTypes(it.typ, abstractVar)) + it.sons[1].typ = s + + elif skipTypes(it.sons[1].typ, abstractVar).kind in + {tyNil, tyArrayConstr, tyTuple, tySet}: + var s = skipTypes(it.typ, abstractVar) + if s.kind != tyExpr: + changeType(it.sons[1], s, check=true) + n.sons[i] = it.sons[1] + of nkBracket: + # an implicitly constructed array (passed to an open array): + n.sons[i] = semArrayConstr(c, it, {}) + else: + discard + #if (it.typ == nil): + # InternalError(it.info, "fixAbstractType: " & renderTree(it)) proc skipObjConv(n: PNode): PNode = case n.kind @@ -2040,7 +2053,7 @@ proc semExpr(c: PContext, n: PNode, flags: TExprFlags = {}): PNode = of nkEmpty, nkNone, nkCommentStmt: discard of nkNilLit: - result.typ = getSysType(tyNil) + if result.typ == nil: result.typ = getSysType(tyNil) of nkIntLit: if result.typ == nil: setIntLitType(result) of nkInt8Lit: diff --git a/compiler/semfold.nim b/compiler/semfold.nim index 52931bc2b..da24005c2 100644 --- a/compiler/semfold.nim +++ b/compiler/semfold.nim @@ -118,6 +118,9 @@ proc makeRange(typ: PType, first, last: BiggestInt): PType = let lowerNode = newIntNode(nkIntLit, minA) if typ.kind == tyInt and minA == maxA: result = getIntLitType(lowerNode) + elif typ.kind in {tyUint, tyUInt64}: + # these are not ordinal types, so you get no subrange type for these: + result = typ else: var n = newNode(nkRange) addSon(n, lowerNode) @@ -135,8 +138,9 @@ proc makeRangeF(typ: PType, first, last: BiggestFloat): PType = addSonSkipIntLit(result, skipTypes(typ, {tyRange})) proc getIntervalType*(m: TMagic, n: PNode): PType = - # Nimrod requires interval arithmetic for ``range`` types. Lots of tedious + # Nim requires interval arithmetic for ``range`` types. Lots of tedious # work but the feature is very nice for reducing explicit conversions. + const ordIntLit = {nkIntLit..nkUInt64Lit} result = n.typ template commutativeOp(opr: expr) {.immediate.} = @@ -208,15 +212,15 @@ proc getIntervalType*(m: TMagic, n: PNode): PType = var a = n.sons[1] var b = n.sons[2] # symmetrical: - if b.kind notin {nkIntLit..nkUInt32Lit}: swap(a, b) - if b.kind in {nkIntLit..nkUInt32Lit}: + if b.kind notin ordIntLit: swap(a, b) + if b.kind in ordIntLit: let x = b.intVal|+|1 if (x and -x) == x and x >= 0: result = makeRange(a.typ, 0, b.intVal) of mModU: let a = n.sons[1] let b = n.sons[2] - if b.kind in {nkIntLit..nkUInt32Lit}: + if a.kind in ordIntLit: if b.intVal >= 0: result = makeRange(a.typ, 0, b.intVal-1) else: @@ -232,9 +236,9 @@ proc getIntervalType*(m: TMagic, n: PNode): PType = result = makeRange(a.typ, b.intVal+1, -(b.intVal+1)) of mDivI, mDivI64, mDivU: binaryOp(`|div|`) - of mMinI, mMinI64: + of mMinI: commutativeOp(min) - of mMaxI, mMaxI64: + of mMaxI: commutativeOp(max) else: discard @@ -282,10 +286,14 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode = of mNot: result = newIntNodeT(1 - getInt(a), n) of mCard: result = newIntNodeT(nimsets.cardSet(a), n) of mBitnotI, mBitnotI64: result = newIntNodeT(not getInt(a), n) - of mLengthStr: result = newIntNodeT(len(getStr(a)), n) + of mLengthStr, mXLenStr: + if a.kind == nkNilLit: result = newIntNodeT(0, n) + else: result = newIntNodeT(len(getStr(a)), n) of mLengthArray: result = newIntNodeT(lengthOrd(a.typ), n) - of mLengthSeq, mLengthOpenArray: result = newIntNodeT(sonsLen(a), n) # BUGFIX - of mUnaryPlusI, mUnaryPlusI64, mUnaryPlusF64: result = a # throw `+` away + of mLengthSeq, mLengthOpenArray, mXLenSeq: + if a.kind == nkNilLit: result = newIntNodeT(0, n) + else: result = newIntNodeT(sonsLen(a), n) # BUGFIX + of mUnaryPlusI, mUnaryPlusF64: result = a # throw `+` away of mToFloat, mToBiggestFloat: result = newFloatNodeT(toFloat(int(getInt(a))), n) of mToInt, mToBiggestInt: result = newIntNodeT(system.toInt(getFloat(a)), n) @@ -305,10 +313,10 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode = of mAddI, mAddI64: result = newIntNodeT(getInt(a) + getInt(b), n) of mSubI, mSubI64: result = newIntNodeT(getInt(a) - getInt(b), n) of mMulI, mMulI64: result = newIntNodeT(getInt(a) * getInt(b), n) - of mMinI, mMinI64: + of mMinI: if getInt(a) > getInt(b): result = newIntNodeT(getInt(b), n) else: result = newIntNodeT(getInt(a), n) - of mMaxI, mMaxI64: + of mMaxI: if getInt(a) > getInt(b): result = newIntNodeT(getInt(a), n) else: result = newIntNodeT(getInt(b), n) of mShlI, mShlI64: @@ -426,7 +434,8 @@ proc evalOp(m: TMagic, n, a, b, c: PNode): PNode = mExit, mInc, ast.mDec, mEcho, mSwap, mAppendStrCh, mAppendStrStr, mAppendSeqElem, mSetLengthStr, mSetLengthSeq, mParseExprToAst, mParseStmtToAst, mExpandToAst, mTypeTrait, mDotDot, - mNLen..mNError, mEqRef, mSlurp, mStaticExec, mNGenSym, mSpawn, mParallel: + mNLen..mNError, mEqRef, mSlurp, mStaticExec, mNGenSym, mSpawn, + mParallel, mPlugin: discard else: internalError(a.info, "evalOp(" & $m & ')') @@ -519,7 +528,7 @@ proc rangeCheck(n: PNode, value: BiggestInt) = proc foldConv*(n, a: PNode; check = false): PNode = # XXX range checks? case skipTypes(n.typ, abstractRange).kind - of tyInt..tyInt64: + of tyInt..tyInt64, tyUInt..tyUInt64: case skipTypes(a.typ, abstractRange).kind of tyFloat..tyFloat64: result = newIntNodeT(int(getFloat(a)), n) @@ -646,7 +655,7 @@ proc getConstExpr(m: PSym, n: PNode): PNode = result = copyNode(n) of nkIfExpr: result = getConstIfExpr(m, n) - of nkCall, nkCommand, nkCallStrLit, nkPrefix, nkInfix: + of nkCallKinds: if n.sons[0].kind != nkSym: return var s = n.sons[0].sym if s.kind != skProc: return diff --git a/compiler/seminst.nim b/compiler/seminst.nim index f72e2dc5b..b2aef63a8 100644 --- a/compiler/seminst.nim +++ b/compiler/seminst.nim @@ -187,7 +187,9 @@ proc instantiateProcType(c: PContext, pt: TIdTable, let param = copySym(oldParam) param.owner = prc param.typ = result.sons[i] - param.ast = oldParam.ast.copyTree + if oldParam.ast != nil: + param.ast = fitNode(c, param.typ, oldParam.ast) + # don't be lazy here and call replaceTypeVarsN(cl, originalParams[i])! result.n.sons[i] = newSymNode(param) addDecl(c, param) diff --git a/compiler/semmacrosanity.nim b/compiler/semmacrosanity.nim index 2ef7a54e7..bb9814a16 100644 --- a/compiler/semmacrosanity.nim +++ b/compiler/semmacrosanity.nim @@ -16,9 +16,9 @@ proc ithField(n: PNode, field: int): PSym = result = nil case n.kind of nkRecList: - for i in countup(0, sonsLen(n) - 1): + for i in countup(0, sonsLen(n) - 1): result = ithField(n.sons[i], field-i) - if result != nil: return + if result != nil: return of nkRecCase: if n.sons[0].kind != nkSym: internalError(n.info, "ithField") result = ithField(n.sons[0], field-1) @@ -34,7 +34,7 @@ proc ithField(n: PNode, field: int): PSym = else: discard proc annotateType*(n: PNode, t: PType) = - let x = t.skipTypes(abstractInst) + let x = t.skipTypes(abstractInst+{tyRange}) # Note: x can be unequal to t and we need to be careful to use 't' # to not to skip tyGenericInst case n.kind @@ -80,7 +80,7 @@ proc annotateType*(n: PNode, t: PType) = if x.kind in {tyString, tyCString}: n.typ = t else: - globalError(n.info, "string literal must be of some string type") + globalError(n.info, "string literal must be of some string type") of nkNilLit: if x.kind in NilableTypes: n.typ = t diff --git a/compiler/semmagic.nim b/compiler/semmagic.nim index de7700be6..0a7846f1d 100644 --- a/compiler/semmagic.nim +++ b/compiler/semmagic.nim @@ -54,7 +54,7 @@ proc evalTypeTrait(trait: PNode, operand: PType, context: PSym): PNode = result.typ = newType(tyString, context) result.info = trait.info of "arity": - result = newIntNode(nkIntLit, typ.n.len-1) + result = newIntNode(nkIntLit, typ.len - ord(typ.kind==tyProc)) result.typ = newType(tyInt, context) result.info = trait.info else: @@ -101,34 +101,6 @@ proc semBindSym(c: PContext, n: PNode): PNode = else: localError(n.sons[1].info, errUndeclaredIdentifier, sl.strVal) -proc semLocals(c: PContext, n: PNode): PNode = - var counter = 0 - var tupleType = newTypeS(tyTuple, c) - result = newNodeIT(nkPar, n.info, tupleType) - tupleType.n = newNodeI(nkRecList, n.info) - # for now we skip openarrays ... - for scope in walkScopes(c.currentScope): - if scope == c.topLevelScope: break - for it in items(scope.symbols): - # XXX parameters' owners are wrong for generics; this caused some pain - # for closures too; we should finally fix it. - #if it.owner != c.p.owner: return result - if it.kind in skLocalVars and - it.typ.skipTypes({tyGenericInst, tyVar}).kind notin - {tyVarargs, tyOpenArray, tyTypeDesc, tyStatic, tyExpr, tyStmt, tyEmpty}: - - var field = newSym(skField, it.name, getCurrOwner(), n.info) - field.typ = it.typ.skipTypes({tyGenericInst, tyVar}) - field.position = counter - inc(counter) - - addSon(tupleType.n, newSymNode(field)) - addSonSkipIntLit(tupleType, field.typ) - - var a = newSymNode(it, result.info) - if it.typ.skipTypes({tyGenericInst}).kind == tyVar: a = newDeref(a) - result.add(a) - proc semShallowCopy(c: PContext, n: PNode, flags: TExprFlags): PNode proc isStrangeArray(t: PType): bool = @@ -161,7 +133,6 @@ proc magicsAfterOverloadResolution(c: PContext, n: PNode, of mHigh, mLow: result = semLowHigh(c, n, n[0].sym.magic) of mShallowCopy: result = semShallowCopy(c, n, flags) of mNBindSym: result = semBindSym(c, n) - of mLocals: result = semLocals(c, n) of mProcCall: result = n result.typ = n[1].typ @@ -196,4 +167,11 @@ proc magicsAfterOverloadResolution(c: PContext, n: PNode, result.add newSymNode(createMagic("-", mSubI), n.info) result.add lenExprB result.add n.sons[1] + of mPlugin: + let plugin = getPlugin(n[0].sym) + if plugin.isNil: + localError(n.info, "cannot find plugin " & n[0].sym.name.s) + result = n + else: + result = plugin(c, n) else: result = n diff --git a/compiler/sempass2.nim b/compiler/sempass2.nim index 5a243afa0..adf03be64 100644 --- a/compiler/sempass2.nim +++ b/compiler/sempass2.nim @@ -560,7 +560,10 @@ proc trackCase(tracked: PEffects, n: PNode) = track(tracked, n.sons[0]) let oldState = tracked.init.len let oldFacts = tracked.guards.len - let interesting = interestingCaseExpr(n.sons[0]) and warnProveField in gNotes + let stringCase = skipTypes(n.sons[0].typ, + abstractVarRange-{tyTypeDesc}).kind in {tyFloat..tyFloat128, tyString} + let interesting = not stringCase and interestingCaseExpr(n.sons[0]) and + warnProveField in gNotes var inter: TIntersection = @[] var toCover = 0 for i in 1.. <n.len: @@ -575,13 +578,8 @@ proc trackCase(tracked: PEffects, n: PNode) = for i in oldState.. <tracked.init.len: addToIntersection(inter, tracked.init[i]) - let exh = case skipTypes(n.sons[0].typ, abstractVarRange-{tyTypeDesc}).kind - of tyFloat..tyFloat128, tyString: - lastSon(n).kind == nkElse - else: - true setLen(tracked.init, oldState) - if exh: + if not stringCase or lastSon(n).kind == nkElse: for id, count in items(inter): if count >= toCover: tracked.init.add id # else we can't merge @@ -714,8 +712,8 @@ proc track(tracked: PEffects, n: PNode) = of nkVarSection, nkLetSection: for child in n: let last = lastSon(child) + if last.kind != nkEmpty: track(tracked, last) if child.kind == nkIdentDefs and last.kind != nkEmpty: - track(tracked, last) for i in 0 .. child.len-3: initVar(tracked, child.sons[i], volatileCheck=false) addAsgnFact(tracked.guards, child.sons[i], last) diff --git a/compiler/semstmts.nim b/compiler/semstmts.nim index a8463cbed..c355a5bf1 100644 --- a/compiler/semstmts.nim +++ b/compiler/semstmts.nim @@ -102,10 +102,6 @@ proc semDestructorCheck(c: PContext, n: PNode, flags: TExprFlags) {.inline.} = c.p.owner.kind notin {skTemplate, skMacro}: localError(n.info, errGenerated, "value expected, but got a type") -proc newDeref(n: PNode): PNode {.inline.} = - result = newNodeIT(nkHiddenDeref, n.info, n.typ.sons[0]) - addSon(result, n) - proc semExprBranch(c: PContext, n: PNode): PNode = result = semExpr(c, n) if result.typ != nil: @@ -373,6 +369,11 @@ proc addToVarSection(c: PContext; result: var PNode; orig, identDefs: PNode) = else: result.add identDefs +proc isDiscardUnderscore(v: PSym): bool = + if v.name.s == "_": + v.flags.incl(sfGenSym) + result = true + proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode = var b: PNode result = copyNode(n) @@ -436,7 +437,8 @@ proc semVarOrLet(c: PContext, n: PNode, symkind: TSymKind): PNode = for j in countup(0, length-3): var v = semIdentDef(c, a.sons[j], symkind) - if sfGenSym notin v.flags: addInterfaceDecl(c, v) + if sfGenSym notin v.flags and not isDiscardUnderscore(v): + addInterfaceDecl(c, v) when oKeepVariableNames: if c.inUnrolledContext > 0: v.flags.incl(sfShadowed) else: @@ -551,7 +553,8 @@ proc semForVars(c: PContext, n: PNode): PNode = if getCurrOwner().kind == skModule: incl(v.flags, sfGlobal) v.typ = iter.sons[i] n.sons[i] = newSymNode(v) - if sfGenSym notin v.flags: addForVarDecl(c, v) + if sfGenSym notin v.flags and not isDiscardUnderscore(v): + addForVarDecl(c, v) inc(c.p.nestedLoopCounter) n.sons[length-1] = semStmt(c, n.sons[length-1]) dec(c.p.nestedLoopCounter) diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim index 4a45da2f9..8c7bd7243 100644 --- a/compiler/semtypes.nim +++ b/compiler/semtypes.nim @@ -261,7 +261,8 @@ proc semArray(c: PContext, n: PNode, prev: PType): PType = if not isOrdinalType(indx): localError(n.sons[1].info, errOrdinalTypeExpected) elif enumHasHoles(indx): - localError(n.sons[1].info, errEnumXHasHoles, indx.sym.name.s) + localError(n.sons[1].info, errEnumXHasHoles, + typeToString(indx.skipTypes({tyRange}))) base = semTypeNode(c, n.sons[2], nil) addSonSkipIntLit(result, base) else: @@ -628,7 +629,7 @@ proc skipGenericInvocation(t: PType): PType {.inline.} = result = t if result.kind == tyGenericInvocation: result = result.sons[0] - if result.kind == tyGenericBody: + while result.kind in {tyGenericInst, tyGenericBody}: result = lastSon(result) proc addInheritedFields(c: PContext, check: var IntSet, pos: var int, @@ -834,7 +835,7 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode, cp.kind = tyUserTypeClassInst return addImplicitGeneric(cp) - for i in 1 .. (paramType.sons.len - 2): + for i in 1 .. paramType.len-2: var lifted = liftingWalk(paramType.sons[i]) if lifted != nil: paramType.sons[i] = lifted @@ -847,7 +848,7 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode, result.shouldHaveMeta of tyGenericInvocation: - for i in 1 .. <paramType.sonsLen: + for i in 1 .. <paramType.len: let lifted = liftingWalk(paramType.sons[i]) if lifted != nil: paramType.sons[i] = lifted when false: diff --git a/compiler/semtypinst.nim b/compiler/semtypinst.nim index 914b92fc8..c5caf8b92 100644 --- a/compiler/semtypinst.nim +++ b/compiler/semtypinst.nim @@ -233,7 +233,9 @@ proc instCopyType*(cl: var TReplTypeVars, t: PType): PType = # XXX: relying on allowMetaTypes is a kludge result = copyType(t, t.owner, cl.allowMetaTypes) result.flags.incl tfFromGeneric - result.flags.excl tfInstClearedFlags + if not (t.kind in tyMetaTypes or + (t.kind == tyStatic and t.n == nil)): + result.flags.excl tfInstClearedFlags proc handleGenericInvocation(cl: var TReplTypeVars, t: PType): PType = # tyGenericInvocation[A, tyGenericInvocation[A, B]] diff --git a/compiler/sigmatch.nim b/compiler/sigmatch.nim index faa84de15..2a9d15b5a 100644 --- a/compiler/sigmatch.nim +++ b/compiler/sigmatch.nim @@ -147,6 +147,7 @@ proc copyCandidate(a: var TCandidate, b: TCandidate) = proc sumGeneric(t: PType): int = var t = t + var isvar = 1 while true: case t.kind of tyGenericInst, tyArray, tyRef, tyPtr, tyDistinct, tyArrayConstr, @@ -154,18 +155,20 @@ proc sumGeneric(t: PType): int = t = t.lastSon inc result of tyVar: - # but do not make 'var T' more specific than 'T'! t = t.sons[0] + inc result + inc isvar of tyGenericInvocation, tyTuple: - result = ord(t.kind == tyGenericInvocation) + result += ord(t.kind == tyGenericInvocation) for i in 0 .. <t.len: result += t.sons[i].sumGeneric break of tyGenericParam, tyExpr, tyStatic, tyStmt, tyTypeDesc: break of tyBool, tyChar, tyEnum, tyObject, tyProc, tyPointer, tyString, tyCString, tyInt..tyInt64, tyFloat..tyFloat128, tyUInt..tyUInt64: - return 1 - else: return 0 + return isvar + else: + return 0 #var ggDebug: bool @@ -919,6 +922,7 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation = of tyAnd: considerPreviousT: + result = isEqual for branch in f.sons: let x = typeRel(c, branch, aOrig) if x < isSubtype: return isNone @@ -1108,8 +1112,10 @@ proc typeRel(c: var TCandidate, f, aOrig: PType, doBind = true): TTypeRelation = localError(f.n.info, errTypeExpected) result = isNone + of tyNone: + if a.kind == tyNone: result = isEqual else: - internalAssert false + internalError " unknown type kind " & $f.kind proc cmpTypes*(c: PContext, f, a: PType): TTypeRelation = var m: TCandidate @@ -1194,15 +1200,6 @@ proc isInlineIterator*(t: PType): bool = result = t.kind == tyIter or (t.kind == tyBuiltInTypeClass and t.base.kind == tyIter) -proc isEmptyContainer*(t: PType): bool = - case t.kind - of tyExpr, tyNil: result = true - of tyArray, tyArrayConstr: result = t.sons[1].kind == tyEmpty - of tySet, tySequence, tyOpenArray, tyVarargs: - result = t.sons[0].kind == tyEmpty - of tyGenericInst: result = isEmptyContainer(t.lastSon) - else: result = false - proc incMatches(m: var TCandidate; r: TTypeRelation; convMatch = 1) = case r of isConvertible, isIntConv: inc(m.convMatches, convMatch) @@ -1307,7 +1304,7 @@ proc paramTypesMatchAux(m: var TCandidate, f, argType: PType, if arg.typ == nil: result = arg elif skipTypes(arg.typ, abstractVar-{tyTypeDesc}).kind == tyTuple: - result = implicitConv(nkHiddenStdConv, f, copyTree(arg), m, c) + result = implicitConv(nkHiddenSubConv, f, arg, m, c) elif arg.typ.isEmptyContainer: result = arg.copyTree result.typ = getInstantiatedType(c, arg, m, f) @@ -1322,7 +1319,7 @@ proc paramTypesMatchAux(m: var TCandidate, f, argType: PType, inc(m.exactMatches) result = arg if skipTypes(f, abstractVar-{tyTypeDesc}).kind in {tyTuple}: - result = implicitConv(nkHiddenStdConv, f, arg, m, c) + result = implicitConv(nkHiddenSubConv, f, arg, m, c) of isNone: # do not do this in ``typeRel`` as it then can't infere T in ``ref T``: if a.kind in {tyProxy, tyUnknown}: @@ -1468,9 +1465,7 @@ proc matchesAux(c: PContext, n, nOrig: PNode, m.state = csNoMatch return if formal.typ.kind == tyVar: - if n.isLValue: - inc(m.genericMatches, 100) - else: + if not n.isLValue: m.state = csNoMatch return @@ -1576,6 +1571,8 @@ proc matchesAux(c: PContext, n, nOrig: PNode, #assert(container == nil) if container.isNil: container = newNodeIT(nkBracket, n.sons[a].info, arrayConstr(c, arg)) + else: + incrIndexType(container.typ) addSon(container, arg) setSon(m.call, formal.position + 1, implicitConv(nkHiddenStdConv, formal.typ, container, m, c)) diff --git a/compiler/transf.nim b/compiler/transf.nim index 2143b6bec..57547b682 100644 --- a/compiler/transf.nim +++ b/compiler/transf.nim @@ -379,6 +379,9 @@ proc transformConv(c: PTransf, n: PNode): PTransNode = result = transformSons(c, n) of tyOpenArray, tyVarargs: result = transform(c, n.sons[1]) + PNode(result).typ = takeType(n.typ, n.sons[1].typ) + #echo n.info, " came here and produced ", typeToString(PNode(result).typ), + # " from ", typeToString(n.typ), " and ", typeToString(n.sons[1].typ) of tyCString: if source.kind == tyString: result = newTransNode(nkStringToCString, n, 1) @@ -713,8 +716,7 @@ proc transform(c: PTransf, n: PNode): PTransNode = add(result, PTransNode(newSymNode(labl))) of nkBreakStmt: result = transformBreak(c, n) of nkWhileStmt: result = transformWhile(c, n) - of nkCall, nkHiddenCallConv, nkCommand, nkInfix, nkPrefix, nkPostfix, - nkCallStrLit: + of nkCallKinds: result = transformCall(c, n) of nkAddr, nkHiddenAddr: result = transformAddrDeref(c, n, nkDerefExpr, nkHiddenDeref) diff --git a/compiler/trees.nim b/compiler/trees.nim index 86a1139a0..2c631af99 100644 --- a/compiler/trees.nim +++ b/compiler/trees.nim @@ -9,40 +9,40 @@ # tree helper routines -import +import ast, astalgo, lexer, msgs, strutils, wordrecg -proc hasSon(father, son: PNode): bool = - for i in countup(0, sonsLen(father) - 1): - if father.sons[i] == son: +proc hasSon(father, son: PNode): bool = + for i in countup(0, sonsLen(father) - 1): + if father.sons[i] == son: return true result = false -proc cyclicTreeAux(n, s: PNode): bool = - if n == nil: +proc cyclicTreeAux(n, s: PNode): bool = + if n == nil: return false - if hasSon(s, n): + if hasSon(s, n): return true var m = sonsLen(s) addSon(s, n) - if not (n.kind in {nkEmpty..nkNilLit}): - for i in countup(0, sonsLen(n) - 1): - if cyclicTreeAux(n.sons[i], s): + if not (n.kind in {nkEmpty..nkNilLit}): + for i in countup(0, sonsLen(n) - 1): + if cyclicTreeAux(n.sons[i], s): return true result = false delSon(s, m) -proc cyclicTree*(n: PNode): bool = +proc cyclicTree*(n: PNode): bool = var s = newNodeI(nkEmpty, n.info) result = cyclicTreeAux(n, s) -proc exprStructuralEquivalent*(a, b: PNode): bool = +proc exprStructuralEquivalent*(a, b: PNode): bool = result = false - if a == b: + if a == b: result = true - elif (a != nil) and (b != nil) and (a.kind == b.kind): + elif (a != nil) and (b != nil) and (a.kind == b.kind): case a.kind - of nkSym: + of nkSym: # don't go nuts here: same symbol as string is enough: result = a.sym.name.id == b.sym.name.id of nkIdent: result = a.ident.id == b.ident.id @@ -50,12 +50,12 @@ proc exprStructuralEquivalent*(a, b: PNode): bool = of nkFloatLit..nkFloat64Lit: result = a.floatVal == b.floatVal of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal of nkEmpty, nkNilLit, nkType: result = true - else: - if sonsLen(a) == sonsLen(b): - for i in countup(0, sonsLen(a) - 1): - if not exprStructuralEquivalent(a.sons[i], b.sons[i]): return + else: + if sonsLen(a) == sonsLen(b): + for i in countup(0, sonsLen(a) - 1): + if not exprStructuralEquivalent(a.sons[i], b.sons[i]): return result = true - + proc sameTree*(a, b: PNode): bool = result = false if a == b: @@ -66,7 +66,7 @@ proc sameTree*(a, b: PNode): bool = if a.info.col != b.info.col: return #if a.info.fileIndex <> b.info.fileIndex then exit; case a.kind - of nkSym: + of nkSym: # don't go nuts here: same symbol as string is enough: result = a.sym.name.id == b.sym.name.id of nkIdent: result = a.ident.id == b.ident.id @@ -75,15 +75,15 @@ proc sameTree*(a, b: PNode): bool = of nkStrLit..nkTripleStrLit: result = a.strVal == b.strVal of nkEmpty, nkNilLit, nkType: result = true else: - if sonsLen(a) == sonsLen(b): - for i in countup(0, sonsLen(a) - 1): - if not sameTree(a.sons[i], b.sons[i]): return + if sonsLen(a) == sonsLen(b): + for i in countup(0, sonsLen(a) - 1): + if not sameTree(a.sons[i], b.sons[i]): return result = true - -proc getProcSym*(call: PNode): PSym = + +proc getProcSym*(call: PNode): PSym = result = call.sons[0].sym -proc getOpSym*(op: PNode): PSym = +proc getOpSym*(op: PNode): PSym = if op.kind notin {nkCall, nkHiddenCallConv, nkCommand, nkCallStrLit}: result = nil else: @@ -91,25 +91,25 @@ proc getOpSym*(op: PNode): PSym = elif op.sons[0].kind == nkSym: result = op.sons[0].sym else: result = nil -proc getMagic*(op: PNode): TMagic = +proc getMagic*(op: PNode): TMagic = case op.kind of nkCallKinds: case op.sons[0].kind of nkSym: result = op.sons[0].sym.magic else: result = mNone else: result = mNone - -proc treeToSym*(t: PNode): PSym = + +proc treeToSym*(t: PNode): PSym = result = t.sym -proc isConstExpr*(n: PNode): bool = +proc isConstExpr*(n: PNode): bool = result = (n.kind in - {nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, + {nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, nkFloatLit..nkFloat64Lit, nkNilLit}) or (nfAllConst in n.flags) proc isDeepConstExpr*(n: PNode): bool = case n.kind - of nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, + of nkCharLit..nkInt64Lit, nkStrLit..nkTripleStrLit, nkFloatLit..nkFloat64Lit, nkNilLit: result = true of nkExprEqExpr, nkExprColonExpr, nkHiddenStdConv, nkHiddenSubConv: @@ -122,33 +122,33 @@ proc isDeepConstExpr*(n: PNode): bool = result = n.typ.isNil or n.typ.skipTypes({tyGenericInst, tyDistinct}).kind != tyObject else: discard -proc flattenTreeAux(d, a: PNode, op: TMagic) = +proc flattenTreeAux(d, a: PNode, op: TMagic) = if (getMagic(a) == op): # a is a "leaf", so add it: for i in countup(1, sonsLen(a) - 1): # BUGFIX flattenTreeAux(d, a.sons[i], op) - else: + else: addSon(d, copyTree(a)) - -proc flattenTree*(root: PNode, op: TMagic): PNode = + +proc flattenTree*(root: PNode, op: TMagic): PNode = result = copyNode(root) if getMagic(root) == op: # BUGFIX: forget to copy prc addSon(result, copyNode(root.sons[0])) flattenTreeAux(result, root, op) -proc swapOperands*(op: PNode) = +proc swapOperands*(op: PNode) = var tmp = op.sons[1] op.sons[1] = op.sons[2] op.sons[2] = tmp -proc isRange*(n: PNode): bool {.inline.} = - if n.kind == nkInfix: +proc isRange*(n: PNode): bool {.inline.} = + if n.kind in nkCallKinds: if n[0].kind == nkIdent and n[0].ident.id == ord(wDotDot) or - n[0].kind in {nkClosedSymChoice, nkOpenSymChoice} and + n[0].kind in {nkClosedSymChoice, nkOpenSymChoice} and n[0][1].sym.name.id == ord(wDotDot): result = true -proc whichPragma*(n: PNode): TSpecialWord = +proc whichPragma*(n: PNode): TSpecialWord = let key = if n.kind == nkExprColonExpr: n.sons[0] else: n if key.kind == nkIdent: result = whichKeyword(key.ident) diff --git a/compiler/types.nim b/compiler/types.nim index 153c26a42..e205f5722 100644 --- a/compiler/types.nim +++ b/compiler/types.nim @@ -541,6 +541,9 @@ proc typeToString(typ: PType, prefer: TPreferedDesc = preferName): string = of tyProc: result = if tfIterator in t.flags: "iterator (" else: "proc (" for i in countup(1, sonsLen(t) - 1): + if t.n != nil and i < t.n.len and t.n[i].kind == nkSym: + add(result, t.n[i].sym.name.s) + add(result, ": ") add(result, typeToString(t.sons[i])) if i < sonsLen(t) - 1: add(result, ", ") add(result, ')') @@ -1436,3 +1439,45 @@ proc skipConv*(n: PNode): PNode = proc skipConvTakeType*(n: PNode): PNode = result = n.skipConv result.typ = n.typ + +proc isEmptyContainer*(t: PType): bool = + case t.kind + of tyExpr, tyNil: result = true + of tyArray, tyArrayConstr: result = t.sons[1].kind == tyEmpty + of tySet, tySequence, tyOpenArray, tyVarargs: + result = t.sons[0].kind == tyEmpty + of tyGenericInst: result = isEmptyContainer(t.lastSon) + else: result = false + +proc takeType*(formal, arg: PType): PType = + # param: openArray[string] = [] + # [] is an array constructor of length 0 of type string! + if arg.kind == tyNil: + # and not (formal.kind == tyProc and formal.callConv == ccClosure): + result = formal + elif formal.kind in {tyOpenArray, tyVarargs, tySequence} and + arg.isEmptyContainer: + let a = copyType(arg.skipTypes({tyGenericInst}), arg.owner, keepId=false) + a.sons[ord(arg.kind in {tyArray, tyArrayConstr})] = formal.sons[0] + result = a + elif formal.kind in {tyTuple, tySet} and arg.kind == formal.kind: + result = formal + else: + result = arg + +proc skipHiddenSubConv*(n: PNode): PNode = + if n.kind == nkHiddenSubConv: + # param: openArray[string] = [] + # [] is an array constructor of length 0 of type string! + let formal = n.typ + result = n.sons[1] + let arg = result.typ + let dest = takeType(formal, arg) + if dest == arg and formal.kind != tyExpr: + #echo n.info, " came here for ", formal.typeToString + result = n + else: + result = copyTree(result) + result.typ = dest + else: + result = n diff --git a/compiler/vm.nim b/compiler/vm.nim index 3b5c8e7f3..1c6c9a30b 100644 --- a/compiler/vm.nim +++ b/compiler/vm.nim @@ -16,7 +16,8 @@ import ast except getstr import strutils, astalgo, msgs, vmdef, vmgen, nimsets, types, passes, unsigned, - parser, vmdeps, idents, trees, renderer, options, transf, parseutils + parser, vmdeps, idents, trees, renderer, options, transf, parseutils, + vmmarshal from semfold import leValueConv, ordinalValToString from evaltempl import evalTemplate @@ -371,11 +372,6 @@ template handleJmpBack() {.dirty.} = globalError(c.debug[pc], errTooManyIterations) dec(c.loopIterations) -proc skipColon(n: PNode): PNode = - result = n - if n.kind == nkExprColonExpr: - result = n.sons[1] - proc rawExecute(c: PCtx, start: int, tos: PStackFrame): TFullReg = var pc = start var tos = tos @@ -1043,7 +1039,14 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): TFullReg = decodeB(rkNode) let newLen = regs[rb].intVal.int if regs[ra].node.isNil: stackTrace(c, tos, pc, errNilAccess) - else: setLen(regs[ra].node.sons, newLen) + else: + let oldLen = regs[ra].node.len + setLen(regs[ra].node.sons, newLen) + if oldLen < newLen: + # XXX This is still not entirely correct + # set to default value: + for i in oldLen .. <newLen: + regs[ra].node.sons[i] = newNodeI(nkEmpty, c.debug[pc]) of opcSwap: let rb = instr.regB if regs[ra].kind == regs[rb].kind: @@ -1362,6 +1365,19 @@ proc rawExecute(c: PCtx, start: int, tos: PStackFrame): TFullReg = while typ.kind == tyTypeDesc and typ.len > 0: typ = typ.sons[0] createStr regs[ra] regs[ra].node.strVal = typ.typeToString(preferExported) + of opcMarshalLoad: + let ra = instr.regA + let rb = instr.regB + inc pc + let typ = c.types[c.code[pc].regBx - wordExcess] + putIntoReg(regs[ra], loadAny(regs[rb].node.strVal, typ)) + of opcMarshalStore: + decodeB(rkNode) + inc pc + let typ = c.types[c.code[pc].regBx - wordExcess] + createStrKeepNode(regs[ra]) + if regs[ra].node.strVal.isNil: regs[ra].node.strVal = newStringOfCap(1000) + storeAny(regs[ra].node.strVal, typ, regs[rb].regToNode) inc pc proc execute(c: PCtx, start: int): PNode = diff --git a/compiler/vmdef.nim b/compiler/vmdef.nim index 90b9f2517..047009f01 100644 --- a/compiler/vmdef.nim +++ b/compiler/vmdef.nim @@ -16,7 +16,7 @@ const byteExcess* = 128 # we use excess-K for immediates wordExcess* = 32768 - MaxLoopIterations* = 500_000 # max iterations of all loops + MaxLoopIterations* = 1500_000 # max iterations of all loops type @@ -29,7 +29,7 @@ type opcRet, # return opcYldYoid, # yield with no value opcYldVal, # yield with a value - + opcAsgnInt, opcAsgnStr, opcAsgnFloat, @@ -48,8 +48,8 @@ type opcWrDeref, opcWrStrIdx, opcLdStrIdx, # a = b[c] - - opcAddInt, + + opcAddInt, opcAddImmInt, opcSubInt, opcSubImmInt, @@ -58,36 +58,37 @@ type opcIncl, opcInclRange, opcExcl, opcCard, opcMulInt, opcDivInt, opcModInt, opcAddFloat, opcSubFloat, opcMulFloat, opcDivFloat, opcShrInt, opcShlInt, - opcBitandInt, opcBitorInt, opcBitxorInt, opcAddu, opcSubu, opcMulu, - opcDivu, opcModu, opcEqInt, opcLeInt, opcLtInt, opcEqFloat, - opcLeFloat, opcLtFloat, opcLeu, opcLtu, opcEqRef, opcEqNimrodNode, opcXor, - opcNot, opcUnaryMinusInt, opcUnaryMinusFloat, opcBitnotInt, + opcBitandInt, opcBitorInt, opcBitxorInt, opcAddu, opcSubu, opcMulu, + opcDivu, opcModu, opcEqInt, opcLeInt, opcLtInt, opcEqFloat, + opcLeFloat, opcLtFloat, opcLeu, opcLtu, opcEqRef, opcEqNimrodNode, opcXor, + opcNot, opcUnaryMinusInt, opcUnaryMinusFloat, opcBitnotInt, opcEqStr, opcLeStr, opcLtStr, opcEqSet, opcLeSet, opcLtSet, opcMulSet, opcPlusSet, opcMinusSet, opcSymdiffSet, opcConcatStr, opcContainsSet, opcRepr, opcSetLenStr, opcSetLenSeq, opcSwap, opcIsNil, opcOf, opcIs, - opcSubStr, opcParseFloat, opcConv, opcCast, opcQuit, opcReset, + opcSubStr, opcParseFloat, opcConv, opcCast, + opcQuit, opcReset, opcNarrowS, opcNarrowU, - + opcAddStrCh, opcAddStrStr, opcAddSeqElem, opcRangeChck, - + opcNAdd, opcNAddMultiple, - opcNKind, - opcNIntVal, - opcNFloatVal, - opcNSymbol, + opcNKind, + opcNIntVal, + opcNFloatVal, + opcNSymbol, opcNIdent, opcNGetType, opcNStrVal, - + opcNSetIntVal, opcNSetFloatVal, opcNSetSymbol, opcNSetIdent, opcNSetType, opcNSetStrVal, opcNNewNimNode, opcNCopyNimNode, opcNCopyNimTree, opcNDel, opcGenSym, - + opcSlurp, opcGorge, opcParseExprToAst, @@ -100,7 +101,7 @@ type opcEqIdent, opcStrToIdent, opcIdentToStr, - + opcEcho, opcIndCall, # dest = call regStart, n; where regStart = fn, arg1, ... opcIndCallAsgn, # dest = call regStart, n; where regStart = fn, arg1, ... @@ -110,7 +111,7 @@ type opcNSetChild, opcCallSite, opcNewStr, - + opcTJmp, # jump Bx if A != 0 opcFJmp, # jump Bx if A == 0 opcJmp, # jump Bx @@ -132,7 +133,8 @@ type opcLdImmInt, # dest = immediate value opcNBindSym, opcSetType, # dest.typ = types[Bx] - opcTypeTrait + opcTypeTrait, + opcMarshalLoad, opcMarshalStore TBlock* = object label*: PSym @@ -178,13 +180,13 @@ type slots*: pointer currentException*: PNode VmCallback* = proc (args: VmArgs) {.closure.} - + PCtx* = ref TCtx TCtx* = object of passes.TPassContext # code gen context code*: seq[TInstr] debug*: seq[TLineInfo] # line info for every instruction; kept separate # to not slow down interpretation - globals*: PNode # + globals*: PNode # constants*: PNode # constant data types*: seq[PType] # some instructions reference types (e.g. 'except') currentExceptionA*, currentExceptionB*: PNode @@ -203,7 +205,7 @@ type TPosition* = distinct int PEvalContext* = PCtx - + proc newCtx*(module: PSym): PCtx = PCtx(code: @[], debug: @[], globals: newNode(nkStmtListExpr), constants: newNode(nkStmtList), types: @[], @@ -221,7 +223,8 @@ proc registerCallback*(c: PCtx; name: string; callback: VmCallback) = const firstABxInstr* = opcTJmp largeInstrs* = { # instructions which use 2 int32s instead of 1: - opcSubStr, opcConv, opcCast, opcNewSeq, opcOf} + opcSubStr, opcConv, opcCast, opcNewSeq, opcOf, + opcMarshalLoad, opcMarshalStore} slotSomeTemp* = slotTempUnknown relativeJumps* = {opcTJmp, opcFJmp, opcJmp, opcJmpBack} diff --git a/compiler/vmdeps.nim b/compiler/vmdeps.nim index 6148ed319..21ee4967b 100644 --- a/compiler/vmdeps.nim +++ b/compiler/vmdeps.nim @@ -144,7 +144,9 @@ proc mapTypeToAst(t: PType, info: TLineInfo; allowRecursion=false): PNode = of tyIter: result = mapTypeToBracket("iter", t, info) of tyProxy: result = atomicType"error" of tyBuiltInTypeClass: result = mapTypeToBracket("builtinTypeClass", t, info) - of tyUserTypeClass: result = mapTypeToBracket("userTypeClass", t, info) + of tyUserTypeClass: + result = mapTypeToBracket("concept", t, info) + result.add t.n.copyTree of tyCompositeTypeClass: result = mapTypeToBracket("compositeTypeClass", t, info) of tyAnd: result = mapTypeToBracket("and", t, info) of tyOr: result = mapTypeToBracket("or", t, info) diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim index c3013852d..0743a4502 100644 --- a/compiler/vmgen.nim +++ b/compiler/vmgen.nim @@ -76,6 +76,11 @@ proc codeListing(c: PCtx, result: var string, start=0; last = -1) = elif opc in {opcLdConst, opcAsgnConst}: result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, c.constants[x.regBx-wordExcess].renderTree) + elif opc in {opcMarshalLoad, opcMarshalStore}: + let y = c.code[i+1] + result.addf("\t$#\tr$#, r$#, $#", ($opc).substr(3), x.regA, x.regB, + c.types[y.regBx-wordExcess].typeToString) + inc i else: result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, x.regBx-wordExcess) result.add("\t#") @@ -696,8 +701,7 @@ proc genCard(c: PCtx; n: PNode; dest: var TDest) = c.gABC(n, opcCard, dest, tmp) c.freeTemp(tmp) -proc genMagic(c: PCtx; n: PNode; dest: var TDest) = - let m = n.sons[0].sym.magic +proc genMagic(c: PCtx; n: PNode; dest: var TDest; m: TMagic) = case m of mAnd: c.genAndOr(n, opcFJmp, dest) of mOr: c.genAndOr(n, opcTJmp, dest) @@ -742,9 +746,9 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = c.gABC(n, opcNewStr, dest, tmp) c.freeTemp(tmp) # XXX buggy - of mLengthOpenArray, mLengthArray, mLengthSeq: + of mLengthOpenArray, mLengthArray, mLengthSeq, mXLenSeq: genUnaryABI(c, n, dest, opcLenSeq) - of mLengthStr: + of mLengthStr, mXLenStr: genUnaryABI(c, n, dest, opcLenStr) of mIncl, mExcl: unused(n, dest) @@ -791,7 +795,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = genUnaryABC(c, n, dest, opcUnaryMinusInt) genNarrow(c, n, dest) of mUnaryMinusF64: genUnaryABC(c, n, dest, opcUnaryMinusFloat) - of mUnaryPlusI, mUnaryPlusI64, mUnaryPlusF64: gen(c, n.sons[1], dest) + of mUnaryPlusI, mUnaryPlusF64: gen(c, n.sons[1], dest) of mBitnotI, mBitnotI64: genUnaryABC(c, n, dest, opcBitnotInt) genNarrowU(c, n, dest) @@ -1008,7 +1012,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = if dest < 0: dest = c.getTemp(n.typ) c.gABC(n, opcCallSite, dest) of mNGenSym: genBinaryABC(c, n, dest, opcGenSym) - of mMinI, mMaxI, mMinI64, mMaxI64, mAbsF64, mMinF64, mMaxF64, mAbsI, + of mMinI, mMaxI, mAbsF64, mMinF64, mMaxF64, mAbsI, mAbsI64, mDotDot: c.genCall(n, dest) of mExpandToAst: @@ -1028,6 +1032,22 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = # mGCref, mGCunref, internalError(n.info, "cannot generate code for: " & $m) +proc genMarshalLoad(c: PCtx, n: PNode, dest: var TDest) = + ## Signature: proc to*[T](data: string): T + if dest < 0: dest = c.getTemp(n.typ) + var tmp = c.genx(n.sons[1]) + c.gABC(n, opcMarshalLoad, dest, tmp) + c.gABx(n, opcMarshalLoad, 0, c.genType(n.typ)) + c.freeTemp(tmp) + +proc genMarshalStore(c: PCtx, n: PNode, dest: var TDest) = + ## Signature: proc `$$`*[T](x: T): string + if dest < 0: dest = c.getTemp(n.typ) + var tmp = c.genx(n.sons[1]) + c.gABC(n, opcMarshalStore, dest, tmp) + c.gABx(n, opcMarshalStore, 0, c.genType(n.sons[1].typ)) + c.freeTemp(tmp) + const atomicTypes = {tyBool, tyChar, tyExpr, tyStmt, tyTypeDesc, tyStatic, @@ -1364,7 +1384,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode = of tyCString, tyString: result = newNodeIT(nkStrLit, info, t) of tyVar, tyPointer, tyPtr, tySequence, tyExpr, - tyStmt, tyTypeDesc, tyStatic, tyRef: + tyStmt, tyTypeDesc, tyStatic, tyRef, tyNil: result = newNodeIT(nkNilLit, info, t) of tyProc: if t.callConv != ccClosure: @@ -1391,7 +1411,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode = addSon(result, getNullValue(t.sons[i], info)) of tySet: result = newNodeIT(nkCurly, info, t) - else: internalError("getNullValue: " & $t.kind) + else: internalError(info, "getNullValue: " & $t.kind) proc ldNullOpcode(t: PType): TOpcode = if fitsRegister(t): opcLdNullReg else: opcLdNull @@ -1533,6 +1553,15 @@ proc matches(s: PSym; x: string): bool = dec L result = true +proc matches(s: PSym; y: varargs[string]): bool = + var s = s + var L = y.len-1 + while L >= 0: + if s == nil or y[L].cmpIgnoreStyle(s.name.s) != 0: return false + s = if sfFromGeneric in s.flags: s.owner.owner else: s.owner + dec L + result = true + proc procIsCallback(c: PCtx; s: PSym): bool = if s.offset < -1: return true var i = -2 @@ -1570,8 +1599,17 @@ proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) = else: internalError(n.info, "cannot generate code for: " & s.name.s) of nkCallKinds: - if n.sons[0].kind == nkSym and n.sons[0].sym.magic != mNone: - genMagic(c, n, dest) + if n.sons[0].kind == nkSym: + let s = n.sons[0].sym + if s.magic != mNone: + genMagic(c, n, dest, s.magic) + elif matches(s, "stdlib", "marshal", "to"): + genMarshalLoad(c, n, dest) + elif matches(s, "stdlib", "marshal", "$$"): + genMarshalStore(c, n, dest) + else: + genCall(c, n, dest) + clearDest(c, n, dest) else: genCall(c, n, dest) clearDest(c, n, dest) @@ -1610,7 +1648,8 @@ proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) = genBreak(c, n) of nkTryStmt: genTry(c, n, dest) of nkStmtList: - unused(n, dest) + #unused(n, dest) + # XXX Fix this bug properly, lexim triggers it for x in n: gen(c, x) of nkStmtListExpr: let L = n.len-1 diff --git a/compiler/vmmarshal.nim b/compiler/vmmarshal.nim new file mode 100644 index 000000000..293d0d949 --- /dev/null +++ b/compiler/vmmarshal.nim @@ -0,0 +1,283 @@ +# +# +# The Nim Compiler +# (c) Copyright 2015 Andreas Rumpf +# +# See the file "copying.txt", included in this +# distribution, for details about the copyright. +# + +## Implements marshaling for the VM. + +import streams, json, intsets, tables, ast, astalgo, idents, types, msgs + +proc ptrToInt(x: PNode): int {.inline.} = + result = cast[int](x) # don't skip alignment + +proc getField(n: PNode; position: int): PSym = + case n.kind + of nkRecList: + for i in countup(0, sonsLen(n) - 1): + result = getField(n.sons[i], position) + if result != nil: return + of nkRecCase: + result = getField(n.sons[0], position) + if result != nil: return + for i in countup(1, sonsLen(n) - 1): + case n.sons[i].kind + of nkOfBranch, nkElse: + result = getField(lastSon(n.sons[i]), position) + if result != nil: return + else: internalError(n.info, "getField(record case branch)") + of nkSym: + if n.sym.position == position: result = n.sym + else: discard + +proc storeAny(s: var string; t: PType; a: PNode; stored: var IntSet) + +proc storeObj(s: var string; typ: PType; x: PNode; stored: var IntSet) = + internalAssert x.kind in {nkObjConstr, nkPar} + let start = ord(x.kind == nkObjConstr) + for i in countup(start, sonsLen(x) - 1): + if i > start: s.add(", ") + var it = x.sons[i] + if it.kind == nkExprColonExpr: + internalAssert it.sons[0].kind == nkSym + let field = it.sons[0].sym + s.add(escapeJson(field.name.s)) + s.add(": ") + storeAny(s, field.typ, it.sons[1], stored) + elif typ.n != nil: + let field = getField(typ.n, i) + s.add(escapeJson(field.name.s)) + s.add(": ") + storeAny(s, field.typ, it, stored) + +proc skipColon*(n: PNode): PNode = + result = n + if n.kind == nkExprColonExpr: + result = n.sons[1] + +proc storeAny(s: var string; t: PType; a: PNode; stored: var IntSet) = + case t.kind + of tyNone: assert false + of tyBool: s.add($(a.intVal != 0)) + of tyChar: + let ch = char(a.intVal) + if ch < '\128': + s.add(escapeJson($ch)) + else: + s.add($int(ch)) + of tyArray, tySequence: + if t.kind == tySequence and a.kind == nkNilLit: s.add("null") + else: + s.add("[") + for i in 0 .. a.len-1: + if i > 0: s.add(", ") + storeAny(s, t.elemType, a[i], stored) + s.add("]") + of tyTuple: + s.add("{") + for i in 0.. <t.len: + if i > 0: s.add(", ") + s.add("\"Field" & $i) + s.add("\": ") + storeAny(s, t.sons[i], a[i].skipColon, stored) + s.add("}") + of tyObject: + s.add("{") + storeObj(s, t, a, stored) + s.add("}") + of tySet: + s.add("[") + for i in 0.. <a.len: + if i > 0: s.add(", ") + if a[i].kind == nkRange: + var x = copyNode(a[i][0]) + storeAny(s, t.lastSon, x, stored) + while x.intVal+1 <= a[i][1].intVal: + s.add(", ") + storeAny(s, t.lastSon, x, stored) + inc x.intVal + else: + storeAny(s, t.lastSon, a[i], stored) + s.add("]") + of tyRange, tyGenericInst: storeAny(s, t.lastSon, a, stored) + of tyEnum: + # we need a slow linear search because of enums with holes: + for e in items(t.n): + if e.sym.position == a.intVal: + s.add e.sym.name.s.escapeJson + break + of tyPtr, tyRef: + var x = a + if isNil(x) or x.kind == nkNilLit: s.add("null") + elif stored.containsOrIncl(x.ptrToInt): + # already stored, so we simply write out the pointer as an int: + s.add($x.ptrToInt) + else: + # else as a [value, key] pair: + # (reversed order for convenient x[0] access!) + s.add("[") + s.add($x.ptrToInt) + s.add(", ") + storeAny(s, t.lastSon, a, stored) + s.add("]") + of tyString, tyCString: + if a.kind == nkNilLit or a.strVal.isNil: s.add("null") + else: s.add(escapeJson(a.strVal)) + of tyInt..tyInt64, tyUInt..tyUInt64: s.add($a.intVal) + of tyFloat..tyFloat128: s.add($a.floatVal) + else: + internalError a.info, "cannot marshal at compile-time " & t.typeToString + +proc storeAny*(s: var string; t: PType; a: PNode) = + var stored = initIntSet() + storeAny(s, t, a, stored) + +proc loadAny(p: var JsonParser, t: PType, + tab: var Table[BiggestInt, PNode]): PNode = + case t.kind + of tyNone: assert false + of tyBool: + case p.kind + of jsonFalse: result = newIntNode(nkIntLit, 0) + of jsonTrue: result = newIntNode(nkIntLit, 1) + else: raiseParseErr(p, "'true' or 'false' expected for a bool") + next(p) + of tyChar: + if p.kind == jsonString: + var x = p.str + if x.len == 1: + result = newIntNode(nkIntLit, ord(x[0])) + next(p) + return + elif p.kind == jsonInt: + result = newIntNode(nkIntLit, getInt(p)) + next(p) + return + raiseParseErr(p, "string of length 1 expected for a char") + of tyEnum: + if p.kind == jsonString: + for e in items(t.n): + if e.sym.name.s == p.str: + result = newIntNode(nkIntLit, e.sym.position) + next(p) + return + raiseParseErr(p, "string expected for an enum") + of tyArray: + if p.kind != jsonArrayStart: raiseParseErr(p, "'[' expected for an array") + next(p) + result = newNode(nkBracket) + while p.kind != jsonArrayEnd and p.kind != jsonEof: + result.add loadAny(p, t.elemType, tab) + if p.kind == jsonArrayEnd: next(p) + else: raiseParseErr(p, "']' end of array expected") + of tySequence: + case p.kind + of jsonNull: + result = newNode(nkNilLit) + next(p) + of jsonArrayStart: + next(p) + result = newNode(nkBracket) + while p.kind != jsonArrayEnd and p.kind != jsonEof: + result.add loadAny(p, t.elemType, tab) + if p.kind == jsonArrayEnd: next(p) + else: raiseParseErr(p, "") + else: + raiseParseErr(p, "'[' expected for a seq") + of tyTuple: + if p.kind != jsonObjectStart: raiseParseErr(p, "'{' expected for an object") + next(p) + result = newNode(nkPar) + var i = 0 + while p.kind != jsonObjectEnd and p.kind != jsonEof: + if p.kind != jsonString: + raiseParseErr(p, "string expected for a field name") + next(p) + if i >= t.len: + raiseParseErr(p, "too many fields to tuple type " & typeToString(t)) + result.add loadAny(p, t.sons[i], tab) + inc i + if p.kind == jsonObjectEnd: next(p) + else: raiseParseErr(p, "'}' end of object expected") + of tyObject: + if p.kind != jsonObjectStart: raiseParseErr(p, "'{' expected for an object") + next(p) + result = newNode(nkPar) + result.sons = @[] + while p.kind != jsonObjectEnd and p.kind != jsonEof: + if p.kind != jsonString: + raiseParseErr(p, "string expected for a field name") + let field = lookupInRecord(t.n, getIdent(p.str)) + if field.isNil: + raiseParseErr(p, "unknown field for object of type " & typeToString(t)) + next(p) + if field.position >= result.sons.len: + setLen(result.sons, field.position+1) + result.sons[field.position] = loadAny(p, field.typ, tab) + if p.kind == jsonObjectEnd: next(p) + else: raiseParseErr(p, "'}' end of object expected") + of tySet: + if p.kind != jsonArrayStart: raiseParseErr(p, "'[' expected for a set") + next(p) + result = newNode(nkCurly) + while p.kind != jsonArrayEnd and p.kind != jsonEof: + result.add loadAny(p, t.lastSon, tab) + next(p) + if p.kind == jsonArrayEnd: next(p) + else: raiseParseErr(p, "']' end of array expected") + of tyPtr, tyRef: + case p.kind + of jsonNull: + result = newNode(nkNilLit) + next(p) + of jsonInt: + result = tab[p.getInt] + if result.isNil: + raiseParseErr(p, "cannot load object with address " & $p.getInt) + next(p) + of jsonArrayStart: + next(p) + if p.kind == jsonInt: + let idx = p.getInt + next(p) + result = loadAny(p, t.lastSon, tab) + tab[idx] = result + else: raiseParseErr(p, "index for ref type expected") + if p.kind == jsonArrayEnd: next(p) + else: raiseParseErr(p, "']' end of ref-address pair expected") + else: raiseParseErr(p, "int for pointer type expected") + of tyString, tyCString: + case p.kind + of jsonNull: + result = newNode(nkNilLit) + next(p) + of jsonString: + result = newStrNode(nkStrLit, p.str) + next(p) + else: raiseParseErr(p, "string expected") + of tyInt..tyInt64, tyUInt..tyUInt64: + if p.kind == jsonInt: + result = newIntNode(nkIntLit, getInt(p)) + next(p) + return + raiseParseErr(p, "int expected") + of tyFloat..tyFloat128: + if p.kind == jsonFloat: + result = newFloatNode(nkFloatLit, getFloat(p)) + next(p) + return + raiseParseErr(p, "float expected") + of tyRange, tyGenericInst: result = loadAny(p, t.lastSon, tab) + else: + internalError "cannot marshal at compile-time " & t.typeToString + +proc loadAny*(s: string; t: PType): PNode = + var tab = initTable[BiggestInt, PNode]() + var p: JsonParser + open(p, newStringStream(s), "unknown file") + next(p) + result = loadAny(p, t, tab) + close(p) diff --git a/compiler/vmops.nim b/compiler/vmops.nim index 502ad8ecc..1023d4783 100644 --- a/compiler/vmops.nim +++ b/compiler/vmops.nim @@ -10,7 +10,7 @@ # Unforunately this cannot be a module yet: #import vmdeps, vm from math import sqrt, ln, log10, log2, exp, round, arccos, arcsin, - arctan, arctan2, cos, cosh, hypot, sinh, sin, tan, tanh, pow, trunc, + arctan, arctan2, cos, cosh, hypot, sinh, sin, tan, tanh, pow, trunc, floor, ceil, fmod from os import getEnv, existsEnv, dirExists, fileExists |