diff options
-rw-r--r-- | compiler/parampatterns.nim | 8 | ||||
-rw-r--r-- | compiler/sem.nim | 1 | ||||
-rw-r--r-- | compiler/semtypes.nim | 4 | ||||
-rw-r--r-- | compiler/semtypinst.nim | 53 | ||||
-rw-r--r-- | compiler/vmgen.nim | 88 | ||||
-rw-r--r-- | tests/concepts/tmanual.nim (renamed from tests/metatype/udtcmanual.nim) | 1 | ||||
-rw-r--r-- | tests/concepts/tswizzle.nim (renamed from tests/metatype/swizzle.nim) | 49 | ||||
-rw-r--r-- | tests/concepts/tusertypeclasses.nim (renamed from tests/metatype/tusertypeclasses.nim) | 0 | ||||
-rw-r--r-- | tests/concepts/tusertypeclasses2.nim (renamed from tests/metatype/tusertypeclasses2.nim) | 0 |
9 files changed, 107 insertions, 97 deletions
diff --git a/compiler/parampatterns.nim b/compiler/parampatterns.nim index 58b5c5681..8c0875ab1 100644 --- a/compiler/parampatterns.nim +++ b/compiler/parampatterns.nim @@ -174,7 +174,8 @@ type arLValue, # is an l-value arLocalLValue, # is an l-value, but local var; must not escape # its stack frame! - arDiscriminant # is a discriminant + arDiscriminant, # is a discriminant + arStrange # it is a strange beast like 'typedesc[var T]' proc isAssignable*(owner: PSym, n: PNode): TAssignableResult = ## 'owner' can be nil! @@ -188,6 +189,9 @@ proc isAssignable*(owner: PSym, n: PNode): TAssignableResult = result = arLocalLValue else: result = arLValue + elif n.sym.kind == skType: + let t = n.sym.typ.skipTypes({tyTypeDesc}) + if t.kind == tyVar: result = arStrange of nkDotExpr: if skipTypes(n.sons[0].typ, abstractInst-{tyTypeDesc}).kind in {tyVar, tyPtr, tyRef}: @@ -222,7 +226,7 @@ proc isAssignable*(owner: PSym, n: PNode): TAssignableResult = discard proc isLValue*(n: PNode): bool = - isAssignable(nil, n) in {arLValue, arLocalLValue} + isAssignable(nil, n) in {arLValue, arLocalLValue, arStrange} proc matchNodeKinds*(p, n: PNode): bool = # matches the parameter constraint 'p' against the concrete AST 'n'. diff --git a/compiler/sem.nim b/compiler/sem.nim index 36c0342cd..2d2f15fab 100644 --- a/compiler/sem.nim +++ b/compiler/sem.nim @@ -287,6 +287,7 @@ proc semConstExpr(c: PContext, n: PNode): PNode = return n result = getConstExpr(c.module, e) if result == nil: + #if e.kind == nkEmpty: globalError(n.info, errConstExprExpected) result = evalConstExpr(c.module, e) if result == nil or result.kind == nkEmpty: if e.info != n.info: diff --git a/compiler/semtypes.nim b/compiler/semtypes.nim index 902ac52b0..245f86427 100644 --- a/compiler/semtypes.nim +++ b/compiler/semtypes.nim @@ -800,7 +800,9 @@ proc liftParamType(c: PContext, procKind: TSymKind, genericParams: PNode, for i in 0 .. paramType.sonsLen - 2: if paramType.sons[i].kind == tyStatic: - result.rawAddSon makeTypeFromExpr(c, ast.emptyNode) # aka 'tyUnknown' + var x = copyNode(ast.emptyNode) + x.typ = paramType.sons[i] + result.rawAddSon makeTypeFromExpr(c, x) # aka 'tyUnknown' else: result.rawAddSon newTypeS(tyAnything, c) diff --git a/compiler/semtypinst.nim b/compiler/semtypinst.nim index 012782730..9e0716114 100644 --- a/compiler/semtypinst.nim +++ b/compiler/semtypinst.nim @@ -34,9 +34,9 @@ proc checkPartialConstructedType(info: TLineInfo, t: PType) = proc checkConstructedType*(info: TLineInfo, typ: PType) = var t = typ.skipTypes({tyDistinct}) if t.kind in tyTypeClasses: discard - elif tfAcyclic in t.flags and skipTypes(t, abstractInst).kind != tyObject: + elif tfAcyclic in t.flags and skipTypes(t, abstractInst).kind != tyObject: localError(info, errInvalidPragmaX, "acyclic") - elif t.kind == tyVar and t.sons[0].kind == tyVar: + elif t.kind == tyVar and t.sons[0].kind == tyVar: localError(info, errVarVarTypeNotAllowed) elif computeSize(t) == szIllegalRecursion: localError(info, errIllegalRecursionInTypeX, typeToString(t)) @@ -44,7 +44,7 @@ proc checkConstructedType*(info: TLineInfo, typ: PType) = sharedPtrCheck(info, t) when false: if t.kind == tyObject and t.sons[0] != nil: - if t.sons[0].kind != tyObject or tfFinal in t.sons[0].flags: + if t.sons[0].kind != tyObject or tfFinal in t.sons[0].flags: localError(info, errInheritanceOnlyWithNonFinalObjects) proc searchInstTypes*(key: PType): PType = @@ -69,7 +69,7 @@ proc searchInstTypes*(key: PType): PType = if not compareTypes(inst.sons[j], key.sons[j], flags = {ExactGenericParams}): break matchType - + return inst proc cacheTypeInst*(inst: PType) = @@ -79,7 +79,7 @@ proc cacheTypeInst*(inst: PType) = genericTyp.sym.typeInstCache.safeAdd(inst) type - TReplTypeVars* {.final.} = object + TReplTypeVars* {.final.} = object c*: PContext typeMap*: TIdTable # map PType to PType symMap*: TIdTable # map PSym to PSym @@ -151,7 +151,7 @@ proc reResolveCallsWithTypedescParams(cl: var TReplTypeVars, n: PNode): PNode = if needsFixing: n.sons[0] = newSymNode(n.sons[0].sym.owner) return cl.c.semOverloadedCall(cl.c, n, n, {skProc}) - + for i in 0 .. <n.safeLen: n.sons[i] = reResolveCallsWithTypedescParams(cl, n[i]) @@ -203,18 +203,18 @@ proc replaceTypeVarsN(cl: var TReplTypeVars, n: PNode): PNode = newSons(result, length) for i in countup(0, length - 1): result.sons[i] = replaceTypeVarsN(cl, n.sons[i]) - -proc replaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym = + +proc replaceTypeVarsS(cl: var TReplTypeVars, s: PSym): PSym = if s == nil: return nil result = PSym(idTableGet(cl.symMap, s)) - if result == nil: + if result == nil: result = copySym(s, false) incl(result.flags, sfFromGeneric) idTablePut(cl.symMap, s, result) result.owner = s.owner result.typ = replaceTypeVarsT(cl, s.typ) result.ast = replaceTypeVarsN(cl, s.ast) - + proc lookupTypeVar(cl: var TReplTypeVars, t: PType): PType = result = PType(idTableGet(cl.typeMap, t)) if result == nil: @@ -234,7 +234,7 @@ proc instCopyType*(cl: var TReplTypeVars, t: PType): PType = result.flags.incl tfFromGeneric result.flags.excl tfInstClearedFlags -proc handleGenericInvocation(cl: var TReplTypeVars, t: PType): PType = +proc handleGenericInvocation(cl: var TReplTypeVars, t: PType): PType = # tyGenericInvocation[A, tyGenericInvocation[A, B]] # is difficult to handle: var body = t.sons[0] @@ -256,7 +256,7 @@ proc handleGenericInvocation(cl: var TReplTypeVars, t: PType): PType = propagateToOwner(header, x) else: propagateToOwner(header, x) - + if header != t: # search again after first pass: result = searchInstTypes(header) @@ -282,7 +282,7 @@ proc handleGenericInvocation(cl: var TReplTypeVars, t: PType): PType = header.sons[i] = x propagateToOwner(header, x) idTablePut(cl.typeMap, body.sons[i-1], x) - + for i in countup(1, sonsLen(t) - 1): # if one of the params is not concrete, we cannot do anything # but we already raised an error! @@ -310,7 +310,7 @@ proc eraseVoidParams*(t: PType) = # don't deal with '(): void': if t.sons[0] != nil and t.sons[0].kind == tyEmpty: t.sons[0] = nil - + for i in 1 .. <t.sonsLen: # don't touch any memory unless necessary if t.sons[i].kind == tyEmpty: @@ -332,7 +332,7 @@ proc skipIntLiteralParams*(t: PType) = if skipped != p: t.sons[i] = skipped if i > 0: t.n.sons[i].sym.typ = skipped - + # when the typeof operator is used on a static input # param, the results gets infected with static as well: if t.sons[0] != nil and t.sons[0].kind == tyStatic: @@ -359,7 +359,7 @@ proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType = if t.kind in {tyStatic, tyGenericParam, tyIter} + tyTypeClasses: let lookup = PType(idTableGet(cl.typeMap, t)) if lookup != nil: return lookup - + case t.kind of tyGenericInvocation: result = handleGenericInvocation(cl, t) @@ -373,7 +373,8 @@ proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType = if cl.allowMetaTypes: return assert t.n.typ != t var n = prepareNode(cl, t.n) - n = cl.c.semConstExpr(cl.c, n) + if n.kind != nkEmpty: + n = cl.c.semConstExpr(cl.c, n) if n.typ.kind == tyTypeDesc: # XXX: sometimes, chained typedescs enter here. # It may be worth investigating why this is happening, @@ -394,7 +395,7 @@ proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType = of tyInt, tyFloat: result = skipIntLit(t) - + of tyTypeDesc: let lookup = PType(idTableGet(cl.typeMap, t)) # lookupTypeVar(cl, t) if lookup != nil: @@ -402,7 +403,7 @@ proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType = if tfUnresolved in t.flags: result = result.base elif t.sons[0].kind != tyNone: result = makeTypeDesc(cl.c, replaceTypeVarsT(cl, t.sons[0])) - + of tyUserTypeClass: result = t @@ -411,31 +412,31 @@ proc replaceTypeVarsTAux(cl: var TReplTypeVars, t: PType): PType = for i in 1 .. <result.sonsLen: result.sons[i] = replaceTypeVarsT(cl, result.sons[i]) propagateToOwner(result, result.lastSon) - + else: if containsGenericType(t): result = instCopyType(cl, t) result.size = -1 # needs to be recomputed - + for i in countup(0, sonsLen(result) - 1): if result.sons[i] != nil: result.sons[i] = replaceTypeVarsT(cl, result.sons[i]) propagateToOwner(result, result.sons[i]) result.n = replaceTypeVarsN(cl, result.n) - + case result.kind of tyArray: let idx = result.sons[0] internalAssert idx.kind != tyStatic - + of tyObject, tyTuple: propagateFieldFlags(result, result.n) - + of tyProc: eraseVoidParams(result) skipIntLiteralParams(result) - + else: discard proc initTypeVars*(p: PContext, pt: TIdTable, info: TLineInfo): TReplTypeVars = @@ -450,7 +451,7 @@ proc replaceTypesInBody*(p: PContext, pt: TIdTable, n: PNode): PNode = pushInfoContext(n.info) result = replaceTypeVarsN(cl, n) popInfoContext() - + proc generateTypeInstance*(p: PContext, pt: TIdTable, info: TLineInfo, t: PType): PType = var cl = initTypeVars(p, pt, info) diff --git a/compiler/vmgen.nim b/compiler/vmgen.nim index 5b7b0b0fd..2383e2542 100644 --- a/compiler/vmgen.nim +++ b/compiler/vmgen.nim @@ -15,7 +15,7 @@ # this doesn't matter. However it matters for strings and other complex # types that use the 'node' field; the reason is that slots are # re-used in a register based VM. Example: -# +# # .. code-block:: nim # let s = a & b # no matter what, create fresh node # s = a & b # no matter what, keep the node @@ -64,17 +64,17 @@ proc codeListing(c: PCtx, result: var string, start=0; last = -1) = let y = c.code[i+1] let z = c.code[i+2] result.addf("\t$#\tr$#, r$#, $#, $#", ($opc).substr(3), x.regA, x.regB, - c.types[y.regBx-wordExcess].typeToString, + c.types[y.regBx-wordExcess].typeToString, c.types[z.regBx-wordExcess].typeToString) inc i, 2 elif opc < firstABxInstr: - result.addf("\t$#\tr$#, r$#, r$#", ($opc).substr(3), x.regA, + result.addf("\t$#\tr$#, r$#, r$#", ($opc).substr(3), x.regA, x.regB, x.regC) elif opc in relativeJumps: result.addf("\t$#\tr$#, L$#", ($opc).substr(3), x.regA, i+x.regBx-wordExcess) elif opc in {opcLdConst, opcAsgnConst}: - result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, + result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, c.constants[x.regBx-wordExcess].renderTree) else: result.addf("\t$#\tr$#, $#", ($opc).substr(3), x.regA, x.regBx-wordExcess) @@ -117,7 +117,7 @@ proc gABx(c: PCtx; n: PNode; opc: TOpcode; a: TRegister = 0; bx: int) = # Applies `opc` to `bx` and stores it into register `a` # `bx` must be signed and in the range [-32767, 32768] if bx >= -32767 and bx <= 32768: - let ins = (opc.uint32 or a.uint32 shl 8'u32 or + let ins = (opc.uint32 or a.uint32 shl 8'u32 or (bx+wordExcess).uint32 shl 16'u32).TInstr c.code.add(ins) c.debug.add(n.info) @@ -174,7 +174,7 @@ proc getTemp(c: PCtx; typ: PType): TRegister = if c.slots[i].kind == k and not c.slots[i].inUse: c.slots[i].inUse = true return TRegister(i) - + # if register pressure is high, we re-use more aggressively: if c.maxSlots >= HighRegisterPressure: for i in 0 .. c.maxSlots-1: @@ -208,7 +208,7 @@ proc getTempRange(c: PCtx; n: int; kind: TSlotKind): TRegister = result = TRegister(c.maxSlots) inc c.maxSlots, n for k in result .. result+n-1: c.slots[k] = (inUse: true, kind: kind) - + proc freeTempRange(c: PCtx; start: TRegister, n: int) = for i in start .. start+n-1: c.freeTemp(TRegister(i)) @@ -217,7 +217,7 @@ template withTemp(tmp, typ: expr, body: stmt) {.immediate, dirty.} = body c.freeTemp(tmp) -proc popBlock(c: PCtx; oldLen: int) = +proc popBlock(c: PCtx; oldLen: int) = for f in c.prc.blocks[oldLen].fixups: c.patch(f) c.prc.blocks.setLen(oldLen) @@ -386,7 +386,7 @@ proc genLiteral(c: PCtx; n: PNode): int = result = rawGenLiteral(c, n) proc unused(n: PNode; x: TDest) {.inline.} = - if x >= 0: + if x >= 0: #debug(n) internalError(n.info, "not unused") @@ -446,11 +446,11 @@ proc genTry(c: PCtx; n: PNode; dest: var TDest) = var blen = len(it) # first opcExcept contains the end label of the 'except' block: let endExcept = c.xjmp(it, opcExcept, 0) - for j in countup(0, blen - 2): + for j in countup(0, blen - 2): assert(it.sons[j].kind == nkType) let typ = it.sons[j].typ.skipTypes(abstractPtrs-{tyTypeDesc}) c.gABx(it, opcExcept, 0, c.genType(typ)) - if blen == 1: + if blen == 1: # general except section: c.gABx(it, opcExcept, 0, 0) c.gen(it.lastSon, dest) @@ -498,7 +498,7 @@ proc genCall(c: PCtx; n: PNode; dest: var TDest) = template isGlobal(s: PSym): bool = sfGlobal in s.flags and s.kind != skForVar proc isGlobal(n: PNode): bool = n.kind == nkSym and isGlobal(n.sym) -proc needsAsgnPatch(n: PNode): bool = +proc needsAsgnPatch(n: PNode): bool = n.kind in {nkBracketExpr, nkDotExpr, nkCheckedFieldExpr, nkDerefExpr, nkHiddenDeref} or (n.kind == nkSym and n.sym.isGlobal) @@ -552,9 +552,9 @@ proc genAsgnPatch(c: PCtx; le: PNode, value: TRegister) = proc genNew(c: PCtx; n: PNode) = let dest = if needsAsgnPatch(n.sons[1]): c.getTemp(n.sons[1].typ) else: c.genx(n.sons[1]) - # we use the ref's base type here as the VM conflates 'ref object' + # we use the ref's base type here as the VM conflates 'ref object' # and 'object' since internally we already have a pointer. - c.gABx(n, opcNew, dest, + c.gABx(n, opcNew, dest, c.genType(n.sons[1].typ.skipTypes(abstractVar-{tyTypeDesc}).sons[0])) c.genAsgnPatch(n.sons[1], dest) c.freeTemp(dest) @@ -657,7 +657,7 @@ proc genUnaryStmt(c: PCtx; n: PNode; opc: TOpcode) = proc genVarargsABC(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) = if dest < 0: dest = getTemp(c, n.typ) var x = c.getTempRange(n.len-1, slotTempStr) - for i in 1..n.len-1: + for i in 1..n.len-1: var r: TRegister = x+i-1 c.gen(n.sons[i], r) c.gABC(n, opc, dest, x, n.len-1) @@ -681,7 +681,7 @@ proc genAddSubInt(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode) = genBinaryABC(c, n, dest, opc) c.genNarrow(n, dest) -proc genConv(c: PCtx; n, arg: PNode; dest: var TDest; opc=opcConv) = +proc genConv(c: PCtx; n, arg: PNode; dest: var TDest; opc=opcConv) = let tmp = c.genx(arg) if dest < 0: dest = c.getTemp(n.typ) c.gABC(n, opc, dest, tmp) @@ -792,12 +792,12 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = genNarrow(c, n, dest) of mUnaryMinusF64: genUnaryABC(c, n, dest, opcUnaryMinusFloat) of mUnaryPlusI, mUnaryPlusI64, mUnaryPlusF64: gen(c, n.sons[1], dest) - of mBitnotI, mBitnotI64: + of mBitnotI, mBitnotI64: genUnaryABC(c, n, dest, opcBitnotInt) genNarrowU(c, n, dest) of mZe8ToI, mZe8ToI64, mZe16ToI, mZe16ToI64, mZe32ToI64, mZeIToI64, - mToU8, mToU16, mToU32, mToFloat, mToBiggestFloat, mToInt, - mToBiggestInt, mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, + mToU8, mToU16, mToU32, mToFloat, mToBiggestFloat, mToInt, + mToBiggestInt, mCharToStr, mBoolToStr, mIntToStr, mInt64ToStr, mFloatToStr, mCStrToStr, mStrToStr, mEnumToStr: genConv(c, n, n.sons[1], dest) of mEqStr: genBinaryABC(c, n, dest, opcEqStr) @@ -825,7 +825,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = c.gABC(n, if m == mSetLengthStr: opcSetLenStr else: opcSetLenSeq, d, tmp) c.genAsgnPatch(n.sons[1], d) c.freeTemp(tmp) - of mSwap: + of mSwap: unused(n, dest) var d1 = c.genx(n.sons[1]) @@ -874,7 +874,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = c.freeTemp(tmp1) c.freeTemp(tmp3) c.genAsgnPatch(d2AsNode, d2) - c.freeTemp(d2) + c.freeTemp(d2) of mReset: unused(n, dest) var d = c.genx(n.sons[1]) @@ -913,7 +913,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = of mAppendStrCh: unused(n, dest) genBinaryStmtVar(c, n, opcAddStrCh) - of mAppendStrStr: + of mAppendStrStr: unused(n, dest) genBinaryStmtVar(c, n, opcAddStrStr) of mAppendSeqElem: @@ -923,7 +923,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = genUnaryABC(c, n, dest, opcParseExprToAst) of mParseStmtToAst: genUnaryABC(c, n, dest, opcParseStmtToAst) - of mTypeTrait: + of mTypeTrait: let tmp = c.genx(n.sons[1]) if dest < 0: dest = c.getTemp(n.typ) c.gABx(n, opcSetType, tmp, c.genType(n.sons[1].typ)) @@ -960,19 +960,19 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = of mNSetIntVal: unused(n, dest) genBinaryStmt(c, n, opcNSetIntVal) - of mNSetFloatVal: + of mNSetFloatVal: unused(n, dest) genBinaryStmt(c, n, opcNSetFloatVal) of mNSetSymbol: unused(n, dest) genBinaryStmt(c, n, opcNSetSymbol) - of mNSetIdent: + of mNSetIdent: unused(n, dest) genBinaryStmt(c, n, opcNSetIdent) of mNSetType: unused(n, dest) genBinaryStmt(c, n, opcNSetType) - of mNSetStrVal: + of mNSetStrVal: unused(n, dest) genBinaryStmt(c, n, opcNSetStrVal) of mNNewNimNode: genBinaryABC(c, n, dest, opcNNewNimNode) @@ -990,10 +990,10 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = of mEqIdent: genBinaryABC(c, n, dest, opcEqIdent) of mEqNimrodNode: genBinaryABC(c, n, dest, opcEqNimrodNode) of mNLineInfo: genUnaryABC(c, n, dest, opcNLineInfo) - of mNHint: + of mNHint: unused(n, dest) genUnaryStmt(c, n, opcNHint) - of mNWarning: + of mNWarning: unused(n, dest) genUnaryStmt(c, n, opcNWarning) of mNError: @@ -1024,7 +1024,7 @@ proc genMagic(c: PCtx; n: PNode; dest: var TDest) = else: globalError(n.info, "expandToAst requires a call expression") else: - # mGCref, mGCunref, + # mGCref, mGCunref, internalError(n.info, "cannot generate code for: " & $m) const @@ -1056,7 +1056,7 @@ proc unneededIndirection(n: PNode): bool = n.typ.skipTypes(abstractInst-{tyTypeDesc}).kind == tyRef proc genAddrDeref(c: PCtx; n: PNode; dest: var TDest; opc: TOpcode; - flags: TGenFlags) = + flags: TGenFlags) = # a nop for certain types let isAddr = opc in {opcAddrNode, opcAddrReg} let newflags = if isAddr: flags+{gfAddrOf} else: flags @@ -1144,7 +1144,7 @@ proc checkCanEval(c: PCtx; n: PNode) = # proc foo() = var x ... let s = n.sym if {sfCompileTime, sfGlobal} <= s.flags: return - if s.kind in {skVar, skTemp, skLet, skParam, skResult} and + if s.kind in {skVar, skTemp, skLet, skParam, skResult} and not s.isOwnedBy(c.prc.sym) and s.owner != c.module: cannotEval(n) @@ -1338,27 +1338,27 @@ proc genArrAccess(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags) = else: genArrAccess2(c, n, dest, opcLdArr, flags) -proc getNullValueAux(obj: PNode, result: PNode) = +proc getNullValueAux(obj: PNode, result: PNode) = case obj.kind of nkRecList: for i in countup(0, sonsLen(obj) - 1): getNullValueAux(obj.sons[i], result) of nkRecCase: getNullValueAux(obj.sons[0], result) - for i in countup(1, sonsLen(obj) - 1): + for i in countup(1, sonsLen(obj) - 1): getNullValueAux(lastSon(obj.sons[i]), result) of nkSym: addSon(result, getNullValue(obj.sym.typ, result.info)) else: internalError(result.info, "getNullValueAux") - -proc getNullValue(typ: PType, info: TLineInfo): PNode = + +proc getNullValue(typ: PType, info: TLineInfo): PNode = var t = skipTypes(typ, abstractRange-{tyTypeDesc}) result = emptyNode case t.kind - of tyBool, tyEnum, tyChar, tyInt..tyInt64: + of tyBool, tyEnum, tyChar, tyInt..tyInt64: result = newNodeIT(nkIntLit, info, t) of tyUInt..tyUInt64: result = newNodeIT(nkUIntLit, info, t) - of tyFloat..tyFloat128: + of tyFloat..tyFloat128: result = newNodeIT(nkFloatLit, info, t) of tyCString, tyString: result = newNodeIT(nkStrLit, info, t) @@ -1372,7 +1372,7 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode = result = newNodeIT(nkPar, info, t) result.add(newNodeIT(nkNilLit, info, t)) result.add(newNodeIT(nkNilLit, info, t)) - of tyObject: + of tyObject: result = newNodeIT(nkPar, info, t) getNullValueAux(t.n, result) # initialize inherited fields: @@ -1380,9 +1380,9 @@ proc getNullValue(typ: PType, info: TLineInfo): PNode = while base != nil: getNullValueAux(skipTypes(base, skipPtrs).n, result) base = base.sons[0] - of tyArray, tyArrayConstr: + of tyArray, tyArrayConstr: result = newNodeIT(nkBracket, info, t) - for i in countup(0, int(lengthOrd(t)) - 1): + for i in countup(0, int(lengthOrd(t)) - 1): addSon(result, getNullValue(elemType(t), info)) of tyTuple: result = newNodeIT(nkPar, info, t) @@ -1459,7 +1459,7 @@ proc genArrayConstr(c: PCtx, n: PNode, dest: var TDest) = c.gABx(n, opcNewSeq, dest, c.genType(seqType)) c.gABx(n, opcNewSeq, tmp, 0) c.freeTemp(tmp) - + if n.len > 0: var tmp = getTemp(c, intType) c.gABx(n, opcLdNullReg, tmp, c.genType(intType)) @@ -1536,7 +1536,7 @@ proc procIsCallback(c: PCtx; s: PSym): bool = if s.offset < -1: return true var i = -2 for key, value in items(c.callbacks): - if s.matches(key): + if s.matches(key): doAssert s.offset == -1 s.offset = i return true @@ -1584,7 +1584,7 @@ proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) = of nkNilLit: if not n.typ.isEmptyType: genLit(c, getNullValue(n.typ, n.info), dest) else: unused(n, dest) - of nkAsgn, nkFastAsgn: + of nkAsgn, nkFastAsgn: unused(n, dest) genAsgn(c, n.sons[0], n.sons[1], n.kind == nkAsgn) of nkDotExpr: genObjAccess(c, n, dest, flags) @@ -1633,7 +1633,7 @@ proc gen(c: PCtx; n: PNode; dest: var TDest; flags: TGenFlags = {}) = let s = n.sons[namePos].sym discard genProc(c, s) genLit(c, n.sons[namePos], dest) - of nkChckRangeF, nkChckRange64, nkChckRange: + of nkChckRangeF, nkChckRange64, nkChckRange: let tmp0 = c.genx(n.sons[0]) tmp1 = c.genx(n.sons[1]) diff --git a/tests/metatype/udtcmanual.nim b/tests/concepts/tmanual.nim index dd44298dc..243992aed 100644 --- a/tests/metatype/udtcmanual.nim +++ b/tests/concepts/tmanual.nim @@ -12,6 +12,7 @@ e s t ''' + disabled: "true" """ template accept(e: expr) = diff --git a/tests/metatype/swizzle.nim b/tests/concepts/tswizzle.nim index ce18fa234..9bbdb67e6 100644 --- a/tests/metatype/swizzle.nim +++ b/tests/concepts/tswizzle.nim @@ -3,6 +3,7 @@ discard """ [1, 3] [2, 1, 2] ''' + disabled: "true" """ import macros, strutils @@ -18,14 +19,14 @@ proc swizzleIdx(c: char): int = of 'x': 0 of 'y': 1 of 'z': 2 - of 'w': 3 + of 'w': 3 of 'r': 0 of 'g': 1 of 'b': 2 - of 'a': 3 + of 'a': 3 else: 0 -proc isSwizzle(s: string): bool = +proc isSwizzle(s: string): bool {.compileTime.} = template trySet(name, set) = block search: for c in s: @@ -35,10 +36,10 @@ proc isSwizzle(s: string): bool = trySet coords, {'x', 'y', 'z', 'w'} trySet colors, {'r', 'g', 'b', 'a'} - + return false -type +type StringIsSwizzle = generic value value.isSwizzle @@ -47,33 +48,33 @@ type proc foo(x: SwizzleStr) = echo "sw" -accept foo("xx") +#foo("xx") reject foo("xe") -type +type Vec[N: static[int]; T] = array[N, T] +when false: + proc card(x: Vec): int = x.N + proc `$`(x: Vec): string = x.repr.strip -proc card(x: Vec): int = x.N -proc `$`(x: Vec): string = x.repr.strip + macro `.`(x: Vec, swizzle: SwizzleStr): expr = + var + cardinality = swizzle.len + values = newNimNode(nnkBracket) + v = genSym() -macro `.`(x: Vec, swizzle: SwizzleStr): expr = - var - cardinality = swizzle.len - values = newNimNode(nnkBracket) - v = genSym() + for c in swizzle: + values.add newNimNode(nnkBracketExpr).add( + v, c.swizzleIdx.newIntLitNode) - for c in swizzle: - values.add newNimNode(nnkBracketExpr).add( - v, c.swizzleIdx.newIntLitNode) - - return quote do: - let `v` = `x` - Vec[`cardinality`, `v`.T](`values`) + return quote do: + let `v` = `x` + Vec[`cardinality`, `v`.T](`values`) var z = Vec([1, 2, 3]) -echo z.card -echo z.xz -echo z.yxy +#echo z.card +#echo z.xz +#echo z.yxy diff --git a/tests/metatype/tusertypeclasses.nim b/tests/concepts/tusertypeclasses.nim index 4e5e6221c..4e5e6221c 100644 --- a/tests/metatype/tusertypeclasses.nim +++ b/tests/concepts/tusertypeclasses.nim diff --git a/tests/metatype/tusertypeclasses2.nim b/tests/concepts/tusertypeclasses2.nim index 77c70d7a6..77c70d7a6 100644 --- a/tests/metatype/tusertypeclasses2.nim +++ b/tests/concepts/tusertypeclasses2.nim |