diff --git a/com.oracle.truffle.r.library/src/com/oracle/truffle/r/library/fastrShiny/shiny/R/fastr-imageutils.R b/com.oracle.truffle.r.library/src/com/oracle/truffle/r/library/fastrShiny/shiny/R/fastr-imageutils.R deleted file mode 100644 index b4eb62f1486e0ea0dee9e2fb25e19c5847d4ab6f..0000000000000000000000000000000000000000 --- a/com.oracle.truffle.r.library/src/com/oracle/truffle/r/library/fastrShiny/shiny/R/fastr-imageutils.R +++ /dev/null @@ -1,38 +0,0 @@ -eval(expression({ -plotPNG <- function(func, filename=tempfile(fileext='.png'), - width=400, height=400, res=72, ...) { - - # If quartz is available, use png() (which will default to quartz). - # Otherwise, if the Cairo package is installed, use CairoPNG(). - # Finally, if neither quartz nor Cairo, use png(). - if (capabilities("aqua")) { - pngfun <- grDevices::png - } else if ((getOption('shiny.usecairo') %OR% TRUE) && - nchar(system.file(package = "Cairo"))) { - pngfun <- Cairo::CairoPNG - } else { - pngfun <- grDevices::png - } - - pngfun(filename=filename, width=width, height=height, res=res, ...) - # Call plot.new() so that even if no plotting operations are performed at - # least we have a blank background. N.B. we need to set the margin to 0 - # temporarily before plot.new() because when the plot size is small (e.g. - # 200x50), we will get an error "figure margin too large", which is triggered - # by plot.new() with the default (large) margin. However, this does not - # guarantee user's code in func() will not trigger the error -- they may have - # to set par(mar = smaller_value) before they draw base graphics. - ## TODO: - #op <- graphics::par(mar = rep(0, 4)) - #tryCatch( - #graphics::plot.new(), - #finally = graphics::par(op) - #) - - dv <- grDevices::dev.cur() - on.exit(grDevices::dev.off(dv), add = TRUE) - func() - - filename -} -}), asNamespace("shiny")) \ No newline at end of file diff --git a/com.oracle.truffle.r.library/src/com/oracle/truffle/r/library/fastrShiny/shiny/R/fastr-render-plot.R b/com.oracle.truffle.r.library/src/com/oracle/truffle/r/library/fastrShiny/shiny/R/fastr-render-plot.R deleted file mode 100644 index 82b949a45d39043ecb40bcf3a91ce2ff209f6b9e..0000000000000000000000000000000000000000 --- a/com.oracle.truffle.r.library/src/com/oracle/truffle/r/library/fastrShiny/shiny/R/fastr-render-plot.R +++ /dev/null @@ -1,230 +0,0 @@ -eval(expression({ -renderPlot <- function(expr, width='auto', height='auto', res=72, ..., - env=parent.frame(), quoted=FALSE, - execOnResize=FALSE, outputArgs=list() -) { - - ## TODO: always exec until the display list is re-enabled - execOnResize=TRUE - - # This ..stacktraceon is matched by a ..stacktraceoff.. when plotFunc - # is called - installExprFunction(expr, "func", env, quoted, ..stacktraceon = TRUE) - - args <- list(...) - - if (is.function(width)) - widthWrapper <- reactive({ width() }) - else - widthWrapper <- function() { width } - - if (is.function(height)) - heightWrapper <- reactive({ height() }) - else - heightWrapper <- function() { height } - - # A modified version of print.ggplot which returns the built ggplot object - # as well as the gtable grob. This overrides the ggplot::print.ggplot - # method, but only within the context of renderPlot. The reason this needs - # to be a (pseudo) S3 method is so that, if an object has a class in - # addition to ggplot, and there's a print method for that class, that we - # won't override that method. https://github.com/rstudio/shiny/issues/841 - print.ggplot <- function(x) { - grid::grid.newpage() - - build <- ggplot2::ggplot_build(x) - - gtable <- ggplot2::ggplot_gtable(build) - grid::grid.draw(gtable) - - structure(list( - build = build, - gtable = gtable - ), class = "ggplot_build_gtable") - } - - - getDims <- function() { - width <- widthWrapper() - height <- heightWrapper() - - # Note that these are reactive calls. A change to the width and height - # will inherently cause a reactive plot to redraw (unless width and - # height were explicitly specified). - if (width == 'auto') - width <- session$clientData[[paste0('output_', outputName, '_width')]] - if (height == 'auto') - height <- session$clientData[[paste0('output_', outputName, '_height')]] - - list(width = width, height = height) - } - - # Vars to store session and output, so that they can be accessed from - # the plotObj() reactive. - session <- NULL - outputName <- NULL - - # This function is the one that's returned from renderPlot(), and gets - # wrapped in an observer when the output value is assigned. The expression - # passed to renderPlot() is actually run in plotObj(); this function can only - # replay a plot if the width/height changes. - renderFunc <- function(shinysession, name, ...) { - session <<- shinysession - outputName <<- name - - dims <- getDims() - - if (is.null(dims$width) || is.null(dims$height) || - dims$width <= 0 || dims$height <= 0) { - return(NULL) - } - - # The reactive that runs the expr in renderPlot() - plotData <- plotObj() - - img <- plotData$img - - # If only the width/height have changed, simply replay the plot and make a - # new img. - if (dims$width != img$width || dims$height != img$height) { - pixelratio <- session$clientData$pixelratio %OR% 1 - - coordmap <- NULL - plotFunc <- function() { - ## TODO: display list - #..stacktraceon..(grDevices::replayPlot(plotData$recordedPlot)) - - # Coordmap must be recalculated after replaying plot, because pixel - # dimensions will have changed. - - if (inherits(plotData$plotResult, "ggplot_build_gtable")) { - coordmap <<- getGgplotCoordmap(plotData$plotResult, pixelratio, res) - } else { - coordmap <<- getPrevPlotCoordmap(dims$width, dims$height) - } - } - outfile <- ..stacktraceoff..( - plotPNG(plotFunc, width = dims$width*pixelratio, height = dims$height*pixelratio, - res = res*pixelratio) - ) - on.exit(unlink(outfile)) - - img <- dropNulls(list( - src = session$fileUrl(name, outfile, contentType='image/png'), - width = dims$width, - height = dims$height, - coordmap = coordmap, - # Get coordmap error message if present - error = attr(coordmap, "error", exact = TRUE) - )) - } - - img - } - - - plotObj <- reactive(label = "plotObj", { - if (execOnResize) { - dims <- getDims() - } else { - isolate({ dims <- getDims() }) - } - - if (is.null(dims$width) || is.null(dims$height) || - dims$width <= 0 || dims$height <= 0) { - return(NULL) - } - - # Resolution multiplier - pixelratio <- session$clientData$pixelratio %OR% 1 - - plotResult <- NULL - recordedPlot <- NULL - coordmap <- NULL - plotFunc <- function() { - success <-FALSE - tryCatch( - { - # This is necessary to enable displaylist recording - #grDevices::dev.control(displaylist = "enable") - - # Actually perform the plotting - result <- withVisible(func()) - success <- TRUE - }, - finally = { - if (!success) { - # If there was an error in making the plot, there's a good chance - # it's "Error in plot.new: figure margins too large". We need to - # take a reactive dependency on the width and height, so that the - # user's plotting code will re-execute when the plot is resized, - # instead of just replaying the previous plot (which errored). - getDims() - } - } - ) - - if (result$visible) { - # Use capture.output to squelch printing to the actual console; we - # are only interested in plot output - utils::capture.output({ - # This ..stacktraceon.. negates the ..stacktraceoff.. that wraps - # the call to plotFunc. The value needs to be printed just in case - # it's an object that requires printing to generate plot output, - # similar to ggplot2. But for base graphics, it would already have - # been rendered when func was called above, and the print should - # have no effect. - plotResult <<- ..stacktraceon..(print(result$value)) - }) - } - - ## TODO: display list - #recordedPlot <<- grDevices::recordPlot() - - if (inherits(plotResult, "ggplot_build_gtable")) { - coordmap <<- getGgplotCoordmap(plotResult, pixelratio, res) - } else { - coordmap <<- getPrevPlotCoordmap(dims$width, dims$height) - } - } - - # This ..stacktraceoff.. is matched by the `func` function's - # wrapFunctionLabel(..stacktraceon=TRUE) call near the beginning of - # renderPlot, and by the ..stacktraceon.. in plotFunc where ggplot objects - # are printed - outfile <- ..stacktraceoff..( - do.call(plotPNG, c(plotFunc, width=dims$width*pixelratio, - height=dims$height*pixelratio, res=res*pixelratio, args)) - ) - on.exit(unlink(outfile)) - - list( - # img is the content that gets sent to the client. - img = dropNulls(list( - src = session$fileUrl(outputName, outfile, contentType='image/png'), - width = dims$width, - height = dims$height, - coordmap = coordmap, - # Get coordmap error message if present. - error = attr(coordmap, "error", exact = TRUE) - )), - # Returned value from expression in renderPlot() -- may be a printable - # object like ggplot2. Needed just in case we replayPlot and need to get - # a coordmap again. - plotResult = plotResult, - recordedPlot = recordedPlot - ) - }) - - - # If renderPlot isn't going to adapt to the height of the div, then the - # div needs to adapt to the height of renderPlot. By default, plotOutput - # sets the height to 400px, so to make it adapt we need to override it - # with NULL. - outputFunc <- plotOutput - if (!identical(height, 'auto')) formals(outputFunc)['height'] <- list(NULL) - - markRenderFunction(outputFunc, renderFunc, outputArgs = outputArgs) - -} -}), asNamespace("shiny")) \ No newline at end of file diff --git a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Repeat.java b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Repeat.java index 83f22bc1cda9ac45a2c3e828750a9722a7d436f2..2f2187d7e1176349bdf376577096eabc8d2a5a4f 100644 --- a/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Repeat.java +++ b/com.oracle.truffle.r.nodes.builtin/src/com/oracle/truffle/r/nodes/builtin/base/Repeat.java @@ -115,7 +115,9 @@ public abstract class Repeat extends RBuiltinNode.Arg2 { RError.Message.FIRST_ELEMENT_USED, "each").findFirst(1, RError.Message.FIRST_ELEMENT_USED, "each").replaceNA(1).mustBe(gte(0)); - ArgumentsSignature signature = ArgumentsSignature.get("times", "length.out", "each"); + // "..." in signature ensures that the matcher will not report additional arguments which + // are also ignored by GNUR + ArgumentsSignature signature = ArgumentsSignature.get("times", "length.out", "each", "..."); ARG_IDX_TIMES = 0; ARG_IDX_LENGHT_OUT = 1; ARG_IDX_EACH = 2; diff --git a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/vector/PositionCastNode.java b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/vector/PositionCastNode.java index 85fd7dccbb97a442e24ae7df633603bd622f2937..da1209899414caafc038cfb733b68ba8dbcd0867 100644 --- a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/vector/PositionCastNode.java +++ b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/access/vector/PositionCastNode.java @@ -23,6 +23,7 @@ package com.oracle.truffle.r.nodes.access.vector; import com.oracle.truffle.api.dsl.Cached; +import com.oracle.truffle.api.dsl.Fallback; import com.oracle.truffle.api.dsl.Specialization; import com.oracle.truffle.r.nodes.binary.BoxPrimitiveNode; import com.oracle.truffle.r.nodes.unary.CastIntegerNode; @@ -37,10 +38,13 @@ import com.oracle.truffle.r.runtime.data.RInteger; import com.oracle.truffle.r.runtime.data.RLogical; import com.oracle.truffle.r.runtime.data.RMissing; import com.oracle.truffle.r.runtime.data.RNull; +import com.oracle.truffle.r.runtime.data.RObject; +import com.oracle.truffle.r.runtime.data.RS4Object; import com.oracle.truffle.r.runtime.data.RString; import com.oracle.truffle.r.runtime.data.RSymbol; import com.oracle.truffle.r.runtime.data.RTypedValue; import com.oracle.truffle.r.runtime.data.model.RAbstractComplexVector; +import com.oracle.truffle.r.runtime.data.model.RAbstractContainer; import com.oracle.truffle.r.runtime.data.model.RAbstractDoubleVector; import com.oracle.truffle.r.runtime.data.model.RAbstractIntVector; import com.oracle.truffle.r.runtime.data.model.RAbstractListVector; @@ -170,23 +174,14 @@ abstract class PositionCastNode extends RBaseNode { return RDataFactory.createEmptyIntVector(); } - @Specialization(guards = "getInvalidType(position) != null") + @Fallback protected RAbstractVector doInvalidType(Object position) { - throw error(RError.Message.INVALID_SUBSCRIPT_TYPE, getInvalidType(position).getName()); + RType type = getInvalidType(position); + String name = type == null ? "unknown" : type.getName(); + throw error(RError.Message.INVALID_SUBSCRIPT_TYPE, name); } protected static RType getInvalidType(Object positionValue) { - if (positionValue instanceof RAbstractRawVector) { - return RType.Raw; - } else if (positionValue instanceof RAbstractListVector) { - return RType.List; - } else if (positionValue instanceof RFunction) { - return RType.Closure; - } else if (positionValue instanceof REnvironment) { - return RType.Environment; - } else if (positionValue instanceof RAbstractComplexVector) { - return RType.Complex; - } - return null; + return positionValue instanceof RTypedValue ? ((RTypedValue) positionValue).getRType() : null; } } diff --git a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/unary/CastSymbolNode.java b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/unary/CastSymbolNode.java index 034b53109fddd47662cb8d0d4807a7398de58876..6f2ac0b11545308c569f3c75100fe53711471cc0 100644 --- a/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/unary/CastSymbolNode.java +++ b/com.oracle.truffle.r.nodes/src/com/oracle/truffle/r/nodes/unary/CastSymbolNode.java @@ -24,19 +24,27 @@ package com.oracle.truffle.r.nodes.unary; import com.oracle.truffle.api.CompilerDirectives; import com.oracle.truffle.api.CompilerDirectives.TruffleBoundary; +import com.oracle.truffle.api.dsl.Cached; import com.oracle.truffle.api.dsl.Specialization; +import com.oracle.truffle.api.profiles.ConditionProfile; import com.oracle.truffle.r.runtime.RError; import com.oracle.truffle.r.runtime.RError.Message; +import com.oracle.truffle.r.runtime.RInternalError; import com.oracle.truffle.r.runtime.RType; +import com.oracle.truffle.r.runtime.data.RComplex; import com.oracle.truffle.r.runtime.data.RDataFactory; import com.oracle.truffle.r.runtime.data.RDoubleVector; import com.oracle.truffle.r.runtime.data.RIntVector; import com.oracle.truffle.r.runtime.data.RList; import com.oracle.truffle.r.runtime.data.RLogicalVector; import com.oracle.truffle.r.runtime.data.RNull; +import com.oracle.truffle.r.runtime.data.RRaw; import com.oracle.truffle.r.runtime.data.RStringVector; import com.oracle.truffle.r.runtime.data.RSymbol; +import com.oracle.truffle.r.runtime.data.model.RAbstractAtomicVector; import com.oracle.truffle.r.runtime.data.model.RAbstractVector; +import com.oracle.truffle.r.runtime.data.nodes.VectorAccess; +import com.oracle.truffle.r.runtime.data.nodes.VectorAccess.SequentialIterator; public abstract class CastSymbolNode extends CastBaseNode { @@ -55,8 +63,6 @@ public abstract class CastSymbolNode extends CastBaseNode { return RType.Symbol; } - public abstract Object executeSymbol(Object o); - private String toString(Object value) { return toString.executeString(value, ToStringNode.DEFAULT_SEPARATOR); } @@ -86,6 +92,16 @@ public abstract class CastSymbolNode extends CastBaseNode { return asSymbol(toString(value)); } + @Specialization + protected RSymbol doRaw(RRaw value) { + return asSymbol(toString(value)); + } + + @Specialization + protected RSymbol doComplex(RComplex value) { + return asSymbol(toString(value)); + } + @Specialization @TruffleBoundary protected RSymbol doString(String value) { @@ -93,33 +109,44 @@ public abstract class CastSymbolNode extends CastBaseNode { CompilerDirectives.transferToInterpreter(); throw error(RError.Message.ZERO_LENGTH_VARIABLE); } - return RDataFactory.createSymbolInterned(value); - } - - @Specialization(guards = "value.getLength() > 0") - protected RSymbol doStringVector(RStringVector value) { - // Only element 0 interpreted - return doString(value.getDataAt(0)); + return asSymbol(value); } - @Specialization(guards = "value.getLength() > 0") - protected RSymbol doIntegerVector(RIntVector value) { - return doInteger(value.getDataAt(0)); - } - - @Specialization(guards = "value.getLength() > 0") - protected RSymbol doDoubleVector(RDoubleVector value) { - return doDouble(value.getDataAt(0)); + @Specialization(guards = "access.supports(vector)") + protected RSymbol doVector(RAbstractAtomicVector vector, + @Cached("createBinaryProfile()") ConditionProfile emptyProfile, + @Cached("vector.access()") VectorAccess access) { + SequentialIterator it = access.access(vector); + if (emptyProfile.profile(!access.next(it))) { + throw doEmptyVector(vector); + } + switch (access.getType()) { + case Raw: + return asSymbol(toString(RRaw.valueOf(access.getRaw(it)))); + case Logical: + return doLogical(access.getLogical(it)); + case Integer: + return doInteger(access.getInt(it)); + case Double: + return doDouble(access.getDouble(it)); + case Complex: + return doComplex(access.getComplex(it)); + case Character: + return doString(access.getString(it)); + default: + CompilerDirectives.transferToInterpreter(); + throw RInternalError.shouldNotReachHere("unexpected atomic type " + access.getType()); + } } - @Specialization(guards = "value.getLength() > 0") - protected RSymbol doLogicalVector(RLogicalVector value) { - return doLogical(value.getDataAt(0)); + @Specialization(replaces = "doVector") + protected RSymbol doVectorGeneric(RAbstractAtomicVector vector, + @Cached("createBinaryProfile()") ConditionProfile emptyProfile) { + return doVector(vector, emptyProfile, vector.slowPathAccess()); } - @Specialization(guards = "vector.getLength() == 0") @TruffleBoundary - protected RSymbol doEmptyVector(RAbstractVector vector) { + protected RError doEmptyVector(RAbstractVector vector) { if (vector instanceof RList) { throw error(RError.Message.INVALID_TYPE_LENGTH, "symbol", 0); } else { diff --git a/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/ops/BinaryArithmetic.java b/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/ops/BinaryArithmetic.java index b7883f38067abbca3ed847c407596f6df09b8ad6..d81c83297eed4a585e94eeb8bccebbec6cbc6413 100644 --- a/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/ops/BinaryArithmetic.java +++ b/com.oracle.truffle.r.runtime/src/com/oracle/truffle/r/runtime/ops/BinaryArithmetic.java @@ -68,7 +68,7 @@ public abstract class BinaryArithmetic extends Operation { public static class MultiplyBuiltin { } - @RBuiltin(name = "^", kind = PRIMITIVE, parameterNames = {"", ""}, alwaysSplit = true, dispatch = OPS_GROUP_GENERIC, behavior = PURE_ARITHMETIC) + @RBuiltin(name = "^", aliases = "**", kind = PRIMITIVE, parameterNames = {"", ""}, alwaysSplit = true, dispatch = OPS_GROUP_GENERIC, behavior = PURE_ARITHMETIC) public static class PowBuiltin { } 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 eff3d08836737fed6f3054a831b4088f97ce71a8..68c0f9b81be958762a9e3d56baf9cc788e57433e 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 @@ -7908,6 +7908,14 @@ name #{ as.symbol(123) } `123` +##com.oracle.truffle.r.test.builtins.TestBuiltin_asvector.testAsSymbol# +#{ as.symbol(3+2i) } +`3+2i` + +##com.oracle.truffle.r.test.builtins.TestBuiltin_asvector.testAsSymbol# +#{ as.symbol(as.raw(16)) } +`10` + ##com.oracle.truffle.r.test.builtins.TestBuiltin_asvector.testAsSymbol# #{ as.symbol(as.symbol(123)) } `123` @@ -51300,6 +51308,11 @@ attr(,"useBytes") #argv <- structure(list(x = c('A', 'B', 'C'), m = structure(c(1L, -1L, 1L), match.length = c(1L, -1L, 1L), useBytes = TRUE), value = c('A', 'C')), .Names = c('x', 'm', 'value'));do.call('regmatches<-', argv) [1] "A" "B" "C" +##com.oracle.truffle.r.test.builtins.TestBuiltin_rep.testRep# +#rep(' ', 20L, collapse = ' ') + [1] " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " " +[20] " " + ##com.oracle.truffle.r.test.builtins.TestBuiltin_rep.testRep# #rep(x<-42) [1] 42 @@ -85967,6 +85980,10 @@ Error in x + y : non-conformable arrays #{ x <- 1:2 ; dim(x) <- 1:2 ; y <- 2:3 ; dim(y) <- c(1,1,2) ; x + y } Error in x + y : non-conformable arrays +##com.oracle.truffle.r.test.library.base.TestSimpleArithmetic.testVectorsOperations# +#3 ** 4 +[1] 81 + ##com.oracle.truffle.r.test.library.base.TestSimpleArithmetic.testVectorsOperations# #{ -2:2 / 0:0 } [1] -Inf -Inf NaN Inf Inf diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_asvector.java b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_asvector.java index 67ae5bdcae30836bcd3ca9d60de8b0551b7ad765..c66c7d7df15635fe005e845e5910c4a3896e5b26 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_asvector.java +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_asvector.java @@ -452,5 +452,7 @@ public class TestBuiltin_asvector extends TestBase { assertEval("{ as.symbol(\"name\") }"); assertEval("{ as.symbol(123) }"); assertEval("{ as.symbol(as.symbol(123)) }"); + assertEval("{ as.symbol(as.raw(16)) }"); + assertEval("{ as.symbol(3+2i) }"); } } diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_rep.java b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_rep.java index 0d31bcabae80de7fd0b243076eaccd85b213046e..01f86871e8cad4e923c8c993ea1f46017d932923 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_rep.java +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/builtins/TestBuiltin_rep.java @@ -239,5 +239,7 @@ public class TestBuiltin_rep extends TestBase { assertEval("{ rep(paste0('hello', 1:10), 10) }"); assertEval("{ rep(paste0('hello', 1:10), 1:10) }"); + + assertEval("rep(' ', 20L, collapse = ' ')"); } } diff --git a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/library/base/TestSimpleArithmetic.java b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/library/base/TestSimpleArithmetic.java index be6e824235926015ff454a9860433841958c6413..5f458da3dff54f52edbb86e3d888717eca5127c3 100644 --- a/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/library/base/TestSimpleArithmetic.java +++ b/com.oracle.truffle.r.test/src/com/oracle/truffle/r/test/library/base/TestSimpleArithmetic.java @@ -288,6 +288,7 @@ public class TestSimpleArithmetic extends TestBase { assertEval("{ c(1,3) / c(2,4) }"); assertEval("{ 1:1 / 0:0 }"); assertEval("{ -2:2 / 0:0 }"); + assertEval("3 ** 4"); } @Test