diff --git a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/is.R b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/is.R index 7cb4967c72c430bfe28fcd135d60b60f19a563f0..d393453d9513430047d30dc309128538cdf36d2e 100644 --- a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/is.R +++ b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/is.R @@ -27,4 +27,4 @@ is.vector <- function(x, mode="any") .Internal(is.vector(x,mode)) #} is.primitive <- function(x) - switch(typeof(x), "special" = , "builtin" = TRUE, FALSE) \ No newline at end of file + switch(typeof(x), "special" = , "builtin" = TRUE, FALSE) diff --git a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/rm.R b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/rm.R new file mode 100644 index 0000000000000000000000000000000000000000..c3826cc929ae6d7819630b2afcb33fe05649ef56 --- /dev/null +++ b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/rm.R @@ -0,0 +1,37 @@ +# File src/library/base/R/rm.R +# Part of the R package, http://www.R-project.org +# +# Copyright (C) 1995-2012 The R Core Team +# +# This program is free software; you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation; either version 2 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# A copy of the GNU General Public License is available at +# http://www.r-project.org/Licenses/ + +rm <- + function (..., list = character(), pos = -1, envir = as.environment(pos), + inherits = FALSE) +{ + # TODO fix match.call +# dots <- match.call(expand.dots=FALSE)$... + dots <- list(...) + if(length(dots) && + !all(sapply(dots, function(x) is.symbol(x) || is.character(x)))) + stop("... must contain names or character strings") + names <- sapply(dots, as.character) + if (length(names) == 0L) names <- character() + # TODO add support for .Primitive +# list <- .Primitive("c")(list, names) + list <- c(list, names) + .Internal(remove(list, envir, inherits)) +} + +remove <- rm diff --git a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/sets.R b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/sets.R new file mode 100644 index 0000000000000000000000000000000000000000..63b11b7528fc8771897456d15c4bfc44ad6d6b35 --- /dev/null +++ b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/sets.R @@ -0,0 +1,44 @@ +# File src/library/base/R/sets.R +# Part of the R package, http://www.R-project.org +# +# Copyright (C) 1995-2012 The R Core Team +# +# This program is free software; you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation; either version 2 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# A copy of the GNU General Public License is available at +# http://www.r-project.org/Licenses/ + +## See the help for why as.vector is used: +## it includes coercing factors. +union <- function(x, y) unique(c(as.vector(x), as.vector(y))) + +intersect <- function(x, y) +{ + y <- as.vector(y) + unique(y[match(as.vector(x), y, 0L)]) +} + +setdiff <- function(x, y) +{ + x <- as.vector(x) + y <- as.vector(y) + unique(if(length(x) || length(y)) x[match(x, y, 0L) == 0L] else x) +} +## Faster versions, see R-devel, Jan.4-6, 2000; optimize later... +setequal <- function(x, y) +{ + x <- as.vector(x) + y <- as.vector(y) + all(c(match(x, y, 0L) > 0L, match(y, x, 0L) > 0L)) +} + +## same as %in% ( ./match.R ) but different arg names: +is.element <- function(el, set) match(el, set, 0L) > 0L diff --git a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/unname.R b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/unname.R new file mode 100644 index 0000000000000000000000000000000000000000..c878c4ed73113ea83145c1af682340dd30a6d98f --- /dev/null +++ b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/R/unname.R @@ -0,0 +1,26 @@ +# File src/library/base/R/unname.R +# Part of the R package, http://www.R-project.org +# +# Copyright (C) 1995-2012 The R Core Team +# +# This program is free software; you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation; either version 2 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# A copy of the GNU General Public License is available at +# http://www.r-project.org/Licenses/ + +unname <- function (obj, force = FALSE) +{ + if (!is.null(names(obj))) + names(obj) <- NULL + if (!is.null(dimnames(obj)) && (force || !is.data.frame(obj))) + dimnames(obj) <- NULL + obj +} diff --git a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Rm.java b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Rm.java index db7288ba676d44e9ba208e0224407ca9073a16a4..fb39b400f774f63617e26f533af37925fbfe94c2 100644 --- a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Rm.java +++ b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Rm.java @@ -34,29 +34,26 @@ import com.oracle.truffle.r.runtime.RArguments; import com.oracle.truffle.r.runtime.RBuiltin; import com.oracle.truffle.r.runtime.RError; import com.oracle.truffle.r.runtime.RRuntime; -import com.oracle.truffle.r.runtime.data.RDataFactory; import com.oracle.truffle.r.runtime.data.RMissing; import com.oracle.truffle.r.runtime.data.RNull; -import com.oracle.truffle.r.runtime.data.RStringVector; +import com.oracle.truffle.r.runtime.data.model.*; import com.oracle.truffle.r.runtime.env.REnvironment; import com.oracle.truffle.r.runtime.env.REnvironment.PutException; import static com.oracle.truffle.api.CompilerDirectives.TruffleBoundary; -import static com.oracle.truffle.r.runtime.RBuiltinKind.SUBSTITUTE; +import static com.oracle.truffle.r.runtime.RBuiltinKind.INTERNAL; -@RBuiltin(name = "rm", aliases = {"remove"}, kind = SUBSTITUTE, parameterNames = {"name", "list", "pos", "envir", "inherits"}) -// TODO remove should be INTERNAL and rm is in R +@RBuiltin(name = "remove", kind = INTERNAL, parameterNames = {"list", "envir", "inherits"}) public abstract class Rm extends RInvisibleBuiltinNode { public static Rm create(String name) { RNode[] args = getParameterValues0(); args[0] = ConstantNode.create(name); - return RmFactory.create(args, RBuiltinPackages.lookupBuiltin("rm"), null); + return RmFactory.create(args, RBuiltinPackages.lookupBuiltin("remove"), null); } private static RNode[] getParameterValues0() { - return new RNode[]{ConstantNode.create(RMissing.instance), ConstantNode.create(RDataFactory.createStringVector(0)), ConstantNode.create(-1), ConstantNode.create(RMissing.instance), - ConstantNode.create(RRuntime.LOGICAL_FALSE)}; + return new RNode[]{ConstantNode.create(RMissing.instance), ConstantNode.create(RMissing.instance), ConstantNode.create(RRuntime.LOGICAL_FALSE)}; } @Override @@ -64,46 +61,27 @@ public abstract class Rm extends RInvisibleBuiltinNode { return getParameterValues0(); } + // this specialization is for internal use only @Specialization @SuppressWarnings("unused") - protected Object rm(VirtualFrame frame, String name, RStringVector list, Object pos, RMissing envir, byte inherits) { + protected Object rm(VirtualFrame frame, String name, RMissing envir, byte inherits) { controlVisibility(); - removeFromCurrentFrame(frame, name); - return RNull.instance; - } - - @Specialization - @SuppressWarnings("unused") - protected Object rm(VirtualFrame frame, Object[] names, RStringVector list, Object pos, RMissing envir, byte inherits) { - controlVisibility(); - for (Object o : names) { - assert o instanceof String; - removeFromCurrentFrame(frame, (String) o); - } - return RNull.instance; - } - - @Specialization - @TruffleBoundary - @SuppressWarnings("unused") - protected Object rm(String name, RStringVector list, Object pos, REnvironment envir, byte inherits) { - controlVisibility(); - try { - envir.rm(name); - } catch (PutException ex) { - throw RError.error(getEncapsulatingSourceSection(), ex); - } + removeFromFrame(frame, name); return RNull.instance; } @Specialization @TruffleBoundary @SuppressWarnings("unused") - protected Object rm(Object[] names, RStringVector list, Object pos, REnvironment envir, byte inherits) { + protected Object rm(RAbstractStringVector list, REnvironment envir, byte inherits) { controlVisibility(); try { - for (Object o : names) { - envir.rm((String) (o)); + for (int i = 0; i < list.getLength(); i++) { + if (envir == REnvironment.globalEnv()) { + removeFromFrame(envir.getFrame(), list.getDataAt(i)); + } else { + envir.rm(list.getDataAt(i)); + } } } catch (PutException ex) { throw RError.error(getEncapsulatingSourceSection(), ex); @@ -111,7 +89,7 @@ public abstract class Rm extends RInvisibleBuiltinNode { return RNull.instance; } - private void removeFromCurrentFrame(VirtualFrame frame, String x) { + private void removeFromFrame(Frame frame, String x) { // standard case for lookup in current frame Frame frm = frame; FrameSlot fs = frame.getFrameDescriptor().findFrameSlot(x); diff --git a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/RTruffleVisitor.java b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/RTruffleVisitor.java index b8230cc0cfeefa6f1c5e8a7a9091d20758ae1b55..465b4146242ee2e5bcd8a3a3805783af42e4adb9 100644 --- a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/RTruffleVisitor.java +++ b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/RTruffleVisitor.java @@ -368,7 +368,7 @@ public final class RTruffleVisitor extends BasicVisitor<RNode> { return replacement; } - private RNode constructRecursiveUpdateSuffix(RNode[] seq, RNode updateOp, AccessVector vecAST, SourceSection source, boolean isSuper) { + private RNode constructRecursiveVectorUpdateSuffix(RNode[] seq, RNode updateOp, AccessVector vecAST, SourceSection source, boolean isSuper) { seq[2] = updateOp; SequenceNode vecUpdate = new SequenceNode(seq); @@ -377,6 +377,15 @@ public final class RTruffleVisitor extends BasicVisitor<RNode> { return createVectorUpdate(vecAST, vecUpdate, isSuper, source, true); } + private RNode constructRecursiveFieldUpdateSuffix(RNode[] seq, RNode updateOp, FieldAccess accessAST, SourceSection source, boolean isSuper) { + seq[2] = updateOp; + + SequenceNode fieldUpdate = new SequenceNode(seq); + fieldUpdate.assignSourceSection(source); + + return createFieldUpdate(accessAST, fieldUpdate, isSuper, source); + } + private static SimpleAccessVariable getVectorVariable(AccessVector v) { if (v.getVector() instanceof SimpleAccessVariable) { return (SimpleAccessVariable) v.getVector(); @@ -439,22 +448,23 @@ public final class RTruffleVisitor extends BasicVisitor<RNode> { CoerceVector coerceVector = CoerceVectorFactory.create(null, null, null); UpdateArrayHelperNode updateOp = UpdateArrayHelperNodeFactory.create(a.isSubset(), vecAST.accept(this), rhsAccess, ConstantNode.create(0), (PositionsArrayNodeValue) positions, coerceVector); - return constructRecursiveUpdateSuffix(seq, updateOp, vecAST, source, isSuper); + return constructRecursiveVectorUpdateSuffix(seq, updateOp, vecAST, source, isSuper); } else if (a.getVector() instanceof FieldAccess) { FieldAccess accessAST = (FieldAccess) a.getVector(); SimpleAccessVariable varAST = getFieldAccessVariable(accessAST); String vSymbol = RRuntime.toString(varAST.getVariable()); - RNode[] seq = createReplacementSequence(); + RNode[] seq = new RNode[3]; ReadVariableNode v = isSuper ? ReadVariableSuperMaterializedNode.create(varAST.getSource(), vSymbol, RType.Any) : ReadVariableNode.create(varAST.getSource(), vSymbol, RType.Any, varAST.shouldCopyValue()); final Object rhsSymbol = constructReplacementPrefix(seq, rhs, v, WriteVariableNode.Mode.INVISIBLE); - String rhsSymbolString = RRuntime.toString(rhsSymbol); - RNode rhsAccess = ReadVariableNode.create(null, rhsSymbolString, RType.Any, false); - RNode tmpVarAccess = ReadVariableNode.create(null, varSymbol, RType.Any, false); - UpdateFieldNode ufn = UpdateFieldNodeFactory.create(tmpVarAccess, rhsAccess, RRuntime.toString(accessAST.getFieldName())); - RNode assignFromTemp = WriteVariableNode.create(vSymbol, ufn, false, isSuper, WriteVariableNode.Mode.TEMP); - return constructReplacementSuffix(seq, assignFromTemp, rhsSymbol, source); + RNode rhsAccess = AccessVariable.create(null, rhsSymbol).accept(this); + + RNode positions = createPositions(a.getArguments(), argLength, a.isSubset(), true); + CoerceVector coerceVector = CoerceVectorFactory.create(null, null, null); + UpdateArrayHelperNode updateOp = UpdateArrayHelperNodeFactory.create(a.isSubset(), accessAST.accept(this), rhsAccess, ConstantNode.create(0), (PositionsArrayNodeValue) positions, + coerceVector); + return constructRecursiveFieldUpdateSuffix(seq, updateOp, accessAST, source, isSuper); } else if (a.getVector() instanceof FunctionCall) { FunctionCall callAST = (FunctionCall) a.getVector(); RNode positions = createPositions(a.getArguments(), argLength, a.isSubset(), true); @@ -628,25 +638,55 @@ public final class RTruffleVisitor extends BasicVisitor<RNode> { return afn; } - private static RNode createFieldUpdate(FieldAccess a, RNode rhs, boolean isSuper, SourceSection source) { - SimpleAccessVariable varAST = null; + private RNode createFieldUpdate(FieldAccess a, RNode rhs, boolean isSuper, SourceSection source) { if (a.getLhs() instanceof SimpleAccessVariable) { - varAST = (SimpleAccessVariable) a.getLhs(); + SimpleAccessVariable varAST = (SimpleAccessVariable) a.getLhs(); + String vSymbol = RRuntime.toString(varAST.getVariable()); + + RNode[] seq = createReplacementSequence(); + ReadVariableNode v = isSuper ? ReadVariableSuperMaterializedNode.create(varAST.getSource(), vSymbol, RType.Any) : ReadVariableNode.create(varAST.getSource(), vSymbol, RType.Any, + varAST.shouldCopyValue()); + final Object rhsSymbol = constructReplacementPrefix(seq, rhs, v, WriteVariableNode.Mode.INVISIBLE); + String rhsSymbolString = RRuntime.toString(rhsSymbol); + RNode rhsAccess = ReadVariableNode.create(null, rhsSymbolString, RType.Any, false); + RNode tmpVarAccess = ReadVariableNode.create(null, varSymbol, RType.Any, false); + UpdateFieldNode ufn = UpdateFieldNodeFactory.create(tmpVarAccess, rhsAccess, RRuntime.toString(a.getFieldName())); + RNode assignFromTemp = WriteVariableNode.create(vSymbol, ufn, false, isSuper, WriteVariableNode.Mode.TEMP); + return constructReplacementSuffix(seq, assignFromTemp, rhsSymbol, source); + } else if (a.getLhs() instanceof AccessVector) { + AccessVector vecAST = (AccessVector) a.getLhs(); + SimpleAccessVariable varAST = getVectorVariable(vecAST); + String vSymbol = RRuntime.toString(varAST.getVariable()); + RNode[] seq = new RNode[3]; + + ReadVariableNode v = isSuper ? ReadVariableSuperMaterializedNode.create(varAST.getSource(), vSymbol, RType.Any) : ReadVariableNode.create(varAST.getSource(), vSymbol, RType.Any, + varAST.shouldCopyValue()); + final Object rhsSymbol = constructReplacementPrefix(seq, rhs, v, WriteVariableNode.Mode.INVISIBLE); + + RNode rhsAccess = AccessVariable.create(null, rhsSymbol).accept(this); + + List<ArgNode> arguments = new ArrayList<>(2); + arguments.add(ArgNode.create(null, (String) null, Constant.createStringConstant(null, new String[]{a.getFieldName().toString()}))); + RNode positions = createPositions(arguments, arguments.size(), false, true); + CoerceVector coerceVector = CoerceVectorFactory.create(null, null, null); + UpdateArrayHelperNode updateOp = UpdateArrayHelperNodeFactory.create(false, vecAST.accept(this), rhsAccess, ConstantNode.create(0), (PositionsArrayNodeValue) positions, coerceVector); + return constructRecursiveVectorUpdateSuffix(seq, updateOp, vecAST, source, isSuper); + } else if (a.getLhs() instanceof FieldAccess) { + FieldAccess accessAST = (FieldAccess) a.getLhs(); + SimpleAccessVariable varAST = getFieldAccessVariable(accessAST); + + String vSymbol = RRuntime.toString(varAST.getVariable()); + RNode[] seq = new RNode[3]; + ReadVariableNode v = isSuper ? ReadVariableSuperMaterializedNode.create(varAST.getSource(), vSymbol, RType.Any) : ReadVariableNode.create(varAST.getSource(), vSymbol, RType.Any, + varAST.shouldCopyValue()); + final Object rhsSymbol = constructReplacementPrefix(seq, rhs, v, WriteVariableNode.Mode.INVISIBLE); + RNode rhsAccess = AccessVariable.create(null, rhsSymbol).accept(this); + UpdateFieldNode ufn = UpdateFieldNodeFactory.create(accessAST.accept(this), rhsAccess, RRuntime.toString(a.getFieldName())); + return constructRecursiveFieldUpdateSuffix(seq, ufn, accessAST, source, isSuper); } else { Utils.nyi(); + return null; } - String vSymbol = RRuntime.toString(varAST.getVariable()); - - RNode[] seq = createReplacementSequence(); - ReadVariableNode v = isSuper ? ReadVariableSuperMaterializedNode.create(varAST.getSource(), vSymbol, RType.Any) : ReadVariableNode.create(varAST.getSource(), vSymbol, RType.Any, - varAST.shouldCopyValue()); - final Object rhsSymbol = constructReplacementPrefix(seq, rhs, v, WriteVariableNode.Mode.INVISIBLE); - String rhsSymbolString = RRuntime.toString(rhsSymbol); - RNode rhsAccess = ReadVariableNode.create(null, rhsSymbolString, RType.Any, false); - RNode tmpVarAccess = ReadVariableNode.create(null, varSymbol, RType.Any, false); - UpdateFieldNode ufn = UpdateFieldNodeFactory.create(tmpVarAccess, rhsAccess, RRuntime.toString(a.getFieldName())); - RNode assignFromTemp = WriteVariableNode.create(vSymbol, ufn, false, isSuper, WriteVariableNode.Mode.TEMP); - return constructReplacementSuffix(seq, assignFromTemp, rhsSymbol, source); } @Override diff --git a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/AccessFieldNode.java b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/AccessFieldNode.java index 40e3baeee3c39457ded339f53a55ae403231f314..5c2553b70633275c033fe82acd42706fdd5fe894 100644 --- a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/AccessFieldNode.java +++ b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/AccessFieldNode.java @@ -56,6 +56,23 @@ public abstract class AccessFieldNode extends RNode { return RNull.instance; } + // TODO: this should ultimately be a generic function + @Specialization(guards = "hasNames") + protected Object accessField(RDataFrame object) { + int index = object.getElementIndexByName(getField()); + if (index == -1) { + inexactMatch.enter(); + index = object.getElementIndexByNameInexact(getField()); + // TODO: add warning if index found (disabled by default using options) + } + return index == -1 ? RNull.instance : object.getDataAtAsObject(index); + } + + @Specialization(guards = "!hasNames") + protected Object accessFieldNoNames(@SuppressWarnings("unused") RDataFrame object) { + return RNull.instance; + } + @Specialization protected Object accessField(REnvironment env) { Object obj = env.get(getField()); @@ -67,7 +84,7 @@ public abstract class AccessFieldNode extends RNode { throw RError.error(RError.Message.DOLLAR_ATOMIC_VECTORS); } - protected static boolean hasNames(RList object) { + protected static boolean hasNames(RAbstractContainer object) { return object.getNames() != RNull.instance; } diff --git a/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RDataFrame.java b/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RDataFrame.java index 78076d2f595790f30413aca4db37fb2611515dc4..234e6cd0b70a3d8836e111ad45eb45197aea50e8 100644 --- a/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RDataFrame.java +++ b/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RDataFrame.java @@ -128,4 +128,13 @@ public final class RDataFrame implements RShareable, RAbstractContainer { public RShareable materializeToShareable() { return this; } + + public int getElementIndexByName(String name) { + return vector.getElementIndexByName(name); + } + + public int getElementIndexByNameInexact(String name) { + return vector.getElementIndexByNameInexact(name); + } + } diff --git a/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RVector.java b/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RVector.java index 2c1b69796ac696d9c52d50d330254069437e7000..a1d351e9e228ef8e1f4f896a38686ded66172208 100644 --- a/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RVector.java +++ b/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/data/RVector.java @@ -596,9 +596,6 @@ public abstract class RVector extends RBounded implements RShareable, RAbstractV this.names = null; this.dimNames = null; if (this.dimensions != null) { - if (this.attributes != null) { - this.attributes.clear(); - } putAttribute(RRuntime.DIM_ATTR_KEY, RDataFactory.createIntVector(this.dimensions, true)); } else { // nullifying dimensions does not reset regular attributes diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/ExpectedTestOutput.test b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/ExpectedTestOutput.test index 89c676f64912cd159a25b450081c32ac6883b689..bd88572dd47440de8d4fa3ecdaf8dfa255da5f3b 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/ExpectedTestOutput.test +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/ExpectedTestOutput.test @@ -3510,6 +3510,20 @@ a b attr(,"myatt") [1] 1 +##com.oracle.truffle.r.test.simple.TestSimpleAttributes.testBuiltinPropagation +#{ a <- c(1,2,3,4); attr(a, "x") <- "attrib"; dim(a) <- NULL; a } +[1] 1 2 3 4 +attr(,"x") +[1] "attrib" + +##com.oracle.truffle.r.test.simple.TestSimpleAttributes.testBuiltinPropagation +#{ a <- c(1,2,3,4); attr(a, "x") <- "attrib"; dim(a) <- c(2,2); a } + [,1] [,2] +[1,] 1 3 +[2,] 2 4 +attr(,"x") +[1] "attrib" + ##com.oracle.truffle.r.test.simple.TestSimpleAttributes.testBuiltinPropagation #{ m <- 1:3 ; attr(m,"a") <- 1 ; t(m) } [,1] [,2] [,3] @@ -13092,6 +13106,14 @@ Error: object 'x' not found ##com.oracle.truffle.r.test.simple.TestSimpleBuiltins.testSimpleRm #{ x <- 200 ; rm("x") } +##com.oracle.truffle.r.test.simple.TestSimpleBuiltins.testSimpleRm +#{ x<-200; y<-100; rm("x", "y"); x } +Error: object 'x' not found + +##com.oracle.truffle.r.test.simple.TestSimpleBuiltins.testSimpleRm +#{ x<-200; y<-100; rm("x", "y"); y } +Error: object 'y' not found + ##com.oracle.truffle.r.test.simple.TestSimpleBuiltins.testSort #{ sort(c(1L,10L,2L)) } [1] 1 2 10 @@ -50677,6 +50699,49 @@ Error in x$b : $ operator is invalid for atomic vectors #{ x <- list(a=1, b=2) ; f <- function(x) { x$b } ; f(x) ; x <- list(c=2,b=10) ; f(x) } [1] 10 +##com.oracle.truffle.r.test.simple.TestSimpleVectors.testFieldAccess +#{ x<-data.frame(a=list(1,2)); y<-list(bb=x, c=NULL); y$b$a.1 } +[1] 1 + +##com.oracle.truffle.r.test.simple.TestSimpleVectors.testFieldAccess +#{ x<-data.frame(a=list(1,2)); y<-list(bb=x, c=NULL); y$b$a.2 } +[1] 2 + +##com.oracle.truffle.r.test.simple.TestSimpleVectors.testFieldAccess +#{ x<-list(a=list(b=7)); x$a$b<-42; x } +$a +$a$b +[1] 42 + + + +##com.oracle.truffle.r.test.simple.TestSimpleVectors.testFieldAccess +#{ x<-list(a=list(b=7)); x$a[["b"]]<-42; x } +$a +$a$b +[1] 42 + + + +##com.oracle.truffle.r.test.simple.TestSimpleVectors.testFieldAccess +#{ x<-list(a=list(b=7)); x[["a"]]$b<-42; x } +$a +$a$b +[1] 42 + + + +##com.oracle.truffle.r.test.simple.TestSimpleVectors.testFieldAccess +#{ x<-list(list(a=7), NULL); x[[1]]$a<-42; x } +[[1]] +[[1]]$a +[1] 42 + + +[[2]] +NULL + + ##com.oracle.truffle.r.test.simple.TestSimpleVectors.testGenericUpdate #{ a <- TRUE; a[[2]] <- FALSE; a; } [1] TRUE FALSE diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/all/AllTests.java b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/all/AllTests.java index 08bedbfeb4603869961003a96dc46e82f1a37788..88e8c8372a67efccca65021f1c1a21c9a13de9bb 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/all/AllTests.java +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/all/AllTests.java @@ -3998,6 +3998,16 @@ public class AllTests extends TestBase { assertEval("{ x <- c(a=1, b=2) ; attr(x, \"myatt\") <- 1; seq(x) }"); } + @Test + public void TestSimpleAttributes_testBuiltinPropagation_bdbce9dc51ead906ffe3abd5d3c92918() { + assertEval("{ a <- c(1,2,3,4); attr(a, \"x\") <- \"attrib\"; dim(a) <- c(2,2); a }"); + } + + @Test + public void TestSimpleAttributes_testBuiltinPropagation_fc7ec3d913ed7cc4163fe6821cb8b39a() { + assertEval("{ a <- c(1,2,3,4); attr(a, \"x\") <- \"attrib\"; dim(a) <- NULL; a }"); + } + @Test public void TestSimpleAttributes_testBuiltinPropagationIgnore_df9b3724960b222fffd20b6a1ef94ed5() { assertEval("{ m <- matrix(c(1,1,1,1), nrow=2) ; attr(m,\"a\") <- 1 ; r <- eigen(m) ; r$vectors <- round(r$vectors, digits=5) ; r }"); @@ -13333,6 +13343,16 @@ public class AllTests extends TestBase { assertEvalError("{ x <- 200 ; rm(\"x\") ; x }"); } + @Test + public void TestSimpleBuiltins_testSimpleRm_8662a5030633d2cb14450cd771888e2b() { + assertEvalError("{ x<-200; y<-100; rm(\"x\", \"y\"); x }"); + } + + @Test + public void TestSimpleBuiltins_testSimpleRm_9f23e805abd852e0d37f62b2941a1ed5() { + assertEvalError("{ x<-200; y<-100; rm(\"x\", \"y\"); y }"); + } + @Test public void TestSimpleBuiltins_testSimpleRm_638fe08c6d320c8475e37234929ca562() { assertEvalWarning("{ rm(\"ieps\") }"); @@ -19363,6 +19383,36 @@ public class AllTests extends TestBase { assertEval("{ f <- function(v) { v$x } ; f(list(xa=1, xb=2, hello=3)) ; l <- list(y=2,x=3) ; f(l) ; l[[2]] <- 4 ; f(l) }"); } + @Test + public void TestSimpleVectors_testFieldAccess_c4d56667f58ee4170ef99e31cc81ca13() { + assertEval("{ x<-data.frame(a=list(1,2)); y<-list(bb=x, c=NULL); y$b$a.1 }"); + } + + @Test + public void TestSimpleVectors_testFieldAccess_b636b36007783ed1d56ac9a7b512d721() { + assertEval("{ x<-data.frame(a=list(1,2)); y<-list(bb=x, c=NULL); y$b$a.2 }"); + } + + @Test + public void TestSimpleVectors_testFieldAccess_a81bb4b69ece4ce2f037203158ffb0eb() { + assertEval("{ x<-list(list(a=7), NULL); x[[1]]$a<-42; x }"); + } + + @Test + public void TestSimpleVectors_testFieldAccess_62c26169224b454b2b2ec33711c551e7() { + assertEval("{ x<-list(a=list(b=7)); x$a$b<-42; x }"); + } + + @Test + public void TestSimpleVectors_testFieldAccess_da61b86eadc3490615eccc8f5a79e0c4() { + assertEval("{ x<-list(a=list(b=7)); x[[\"a\"]]$b<-42; x }"); + } + + @Test + public void TestSimpleVectors_testFieldAccess_187f49c0f59c0658dd2b0298c277c0c2() { + assertEval("{ x<-list(a=list(b=7)); x$a[[\"b\"]]<-42; x }"); + } + @Test public void TestSimpleVectors_testFieldAccess_5323930bd315d7a9d640f80f09658876() { assertEvalError("{ x <- list(a=1, b=2) ; f <- function(x) { x$b } ; f(x) ; f(1:3) }"); diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleAttributes.java b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleAttributes.java index 53e388990a0dc53ac9b448ab81f516326b6db3b4..d6dc6574fe097dfe09d3523eac9b7a3d69e4fb67 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleAttributes.java +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleAttributes.java @@ -76,10 +76,6 @@ public class TestSimpleAttributes extends TestBase { assertEval("{ x <- c(a=1, b=2) ; attr(x, \"myatt\") <- 1 ; as.integer(x) }"); } - @Test - public void testCastsIgnore() { - } - @Test public void testArrayPropagation() { assertEval("{ x <- c(a=1, b=2) ; attr(x, \"myatt\") <- 1; x[c(1,1)] }"); @@ -133,6 +129,9 @@ public class TestSimpleAttributes extends TestBase { assertEval("{ x <- c(1,2) ; dim(x)<-c(1,2); attr(x, \"myatt\") <- 1; round(exp(x), digits=5) }"); assertEval("{ x <- c(a=TRUE) ; attr(x, \"myatt\") <- 1; rep(x,2) }"); assertEval("{ x <- c(a=1, b=2) ; attr(x, \"myatt\") <- 1; seq(x) }"); + + assertEval("{ a <- c(1,2,3,4); attr(a, \"x\") <- \"attrib\"; dim(a) <- c(2,2); a }"); + assertEval("{ a <- c(1,2,3,4); attr(a, \"x\") <- \"attrib\"; dim(a) <- NULL; a }"); } @Test diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleBuiltins.java b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleBuiltins.java index a9d5d6cc86e29ff73994dfcdf660706a56e8fe1d..1faa2e5c7c9149070c2f239c8cb793936a67561d 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleBuiltins.java +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleBuiltins.java @@ -3131,6 +3131,8 @@ public class TestSimpleBuiltins extends TestBase { assertEvalError("{ x <- 200 ; rm(\"x\") ; x }"); assertEvalWarning("{ rm(\"ieps\") }"); assertEval("{ x <- 200 ; rm(\"x\") }"); + assertEvalError("{ x<-200; y<-100; rm(\"x\", \"y\"); x }"); + assertEvalError("{ x<-200; y<-100; rm(\"x\", \"y\"); y }"); } @Test diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleVectors.java b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleVectors.java index 8d8a6ade2e4ac194532c363d94f131f8a7eb7b90..5b9b8a0cde6477ccf2de32643df4747701881cab 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleVectors.java +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/simple/TestSimpleVectors.java @@ -2026,6 +2026,16 @@ public class TestSimpleVectors extends TestBase { assertEvalError("{ a <- c(a=1,b=2); a$a; }"); // make sure that coercion returns warning assertEvalWarning("{ a <- c(1,2); a$a = 3; a; }"); + + assertEval("{ x<-data.frame(a=list(1,2)); y<-list(bb=x, c=NULL); y$b$a.1 }"); + assertEval("{ x<-data.frame(a=list(1,2)); y<-list(bb=x, c=NULL); y$b$a.2 }"); + + assertEval("{ x<-list(list(a=7), NULL); x[[1]]$a<-42; x }"); + + assertEval("{ x<-list(a=list(b=7)); x$a$b<-42; x }"); + assertEval("{ x<-list(a=list(b=7)); x[[\"a\"]]$b<-42; x }"); + assertEval("{ x<-list(a=list(b=7)); x$a[[\"b\"]]<-42; x }"); + } @Test