Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
18 changes: 9 additions & 9 deletions src/between.c
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@
*/
SEXP between(SEXP x, SEXP lower, SEXP upper, SEXP incbounds, SEXP NAboundsArg, SEXP checkArg) {
int nprotect = 0;
R_len_t nx = length(x), nl = length(lower), nu = length(upper);
const R_len_t nx = length(x), nl = length(lower), nu = length(upper);
if (!nx || !nl || !nu)
return (allocVector(LGLSXP, 0));
const int longest = MAX(MAX(nx, nl), nu);
Expand All @@ -20,13 +20,13 @@ SEXP between(SEXP x, SEXP lower, SEXP upper, SEXP incbounds, SEXP NAboundsArg, S
const int longestBound = MAX(nl, nu); // just for when check=TRUE
if (!IS_TRUE_OR_FALSE(incbounds))
error(_("'%s' must be TRUE or FALSE"), "incbounds");
const bool open = !LOGICAL(incbounds)[0];
if (!isLogical(NAboundsArg) || LOGICAL(NAboundsArg)[0]==FALSE)
const bool open = !LOGICAL_RO(incbounds)[0];
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Hi @badasahog thanks for the change. Funnily enough, I think we started down the same rabbit hole independently -- much of the changes in the original PR wound up covered by #7611 and #7615.

I think there is still some value to what's left here, but it's mixed in with something that we decided against in those PRs:

#7611 (comment)

Basically, code like LOGICAL(x)[0] is functionally idiomatic in R. While LOGICAL_RO(x)[0] is more technically correct, it will be visually distracting for R developers. And anyway, these cases can easily be found by regex & restored if we decide differently in the future.

There might be some cases in very hot loops where there is a performance reason to switch, but we'd want thorough benchmarking if so.

If you wouldn't mind please reverting these changes, it will make reviewing the rest of the PR much easier.

if (!isLogical(NAboundsArg) || LOGICAL_RO(NAboundsArg)[0]==FALSE)
error(_("NAbounds must be TRUE or NA"));
const bool NAbounds = LOGICAL(NAboundsArg)[0]==TRUE;
const bool NAbounds = LOGICAL_RO(NAboundsArg)[0]==TRUE;
if (!IS_TRUE_OR_FALSE(checkArg))
error(_("'%s' must be TRUE or FALSE"), "check");
const bool check = LOGICAL(checkArg)[0];
const bool check = LOGICAL_RO(checkArg)[0];
const bool verbose = GetVerbose();

// check before potential coercion which ignores methods, #7164
Expand Down Expand Up @@ -70,7 +70,7 @@ SEXP between(SEXP x, SEXP lower, SEXP upper, SEXP incbounds, SEXP NAboundsArg, S
const int uppMask = recycleUpp ? 0 : INT_MAX;
SEXP ans = PROTECT(allocVector(LGLSXP, longest)); nprotect++;
int *restrict ansp = LOGICAL(ans);
double tic=omp_get_wtime();
const double tic=omp_get_wtime();

switch (TYPEOF(x)) {
case INTSXP: {
Expand Down Expand Up @@ -103,9 +103,9 @@ SEXP between(SEXP x, SEXP lower, SEXP upper, SEXP incbounds, SEXP NAboundsArg, S

case REALSXP:
if (INHERITS(x, char_integer64)) {
const int64_t *lp = (int64_t *)REAL(lower);
const int64_t *up = (int64_t *)REAL(upper);
const int64_t *xp = (int64_t *)REAL(x);
const int64_t *lp = (const int64_t*)REAL_RO(lower);
const int64_t* up = (const int64_t*)REAL_RO(upper);
const int64_t* xp = (const int64_t*)REAL_RO(x);
if (check) for (int i=0; i<longestBound; ++i) {
const int64_t l=lp[i & lowMask], u=up[i & uppMask];
if (l!=NA_INTEGER64 && u!=NA_INTEGER64 && l>u)
Expand Down
5 changes: 3 additions & 2 deletions src/bmerge.c
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,8 @@ Differences over standard binary search (e.g. bsearch in stdlib.h) :
static const SEXP *idtVec, *xdtVec;
static const int *icols, *xcols;
static SEXP nqgrp;
static int ncol, *o, *xo, *retFirst, *retLength, *retIndex, *allLen1, *allGrp1, *rollends, ilen, anslen;
static int ncol, *o, *xo, *retFirst, *retLength, *retIndex, *allLen1, *allGrp1, ilen, anslen;
static const int* rollends;
static int *op, nqmaxgrp;
static int ctr, nomatch; // populating matches for non-equi joins
enum {ALL, FIRST, LAST, ERR} mult = ALL;
Expand Down Expand Up @@ -94,7 +95,7 @@ SEXP bmerge(SEXP idt, SEXP xdt, SEXP icolsArg, SEXP xcolsArg, SEXP xoArg, SEXP r
rollabs = fabs(roll);
if (!isLogical(rollendsArg) || LENGTH(rollendsArg) != 2)
error(_("rollends must be a length 2 logical vector"));
rollends = LOGICAL(rollendsArg);
rollends = LOGICAL_RO(rollendsArg);

if (isNull(nomatchArg)) {
nomatch=0;
Expand Down
10 changes: 5 additions & 5 deletions src/coalesce.c
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ SEXP coalesce(SEXP x, SEXP inplaceArg, SEXP nan_is_na_arg) {
if (TYPEOF(x)!=VECSXP) internal_error(__func__, "input is list(...) at R level"); // # nocov
if (!IS_TRUE_OR_FALSE(inplaceArg)) internal_error(__func__, "argument 'inplaceArg' must be TRUE or FALSE"); // # nocov
if (!IS_TRUE_OR_FALSE(nan_is_na_arg)) internal_error(__func__, "argument 'nan_is_na_arg' must be TRUE or FALSE"); // # nocov
const bool inplace = LOGICAL(inplaceArg)[0];
const bool nan_is_na = LOGICAL(nan_is_na_arg)[0];
const bool inplace = LOGICAL_RO(inplaceArg)[0];
const bool nan_is_na = LOGICAL_RO(nan_is_na_arg)[0];
const bool verbose = GetVerbose();
int nprotect = 0;
if (length(x)==0 || isNull(VECTOR_ELT(x,0))) return R_NilValue; // coalesce(NULL, "foo") return NULL even though character type mismatches type NULL
Expand Down Expand Up @@ -63,7 +63,7 @@ SEXP coalesce(SEXP x, SEXP inplaceArg, SEXP nan_is_na_arg) {
for (int j=0; j<nval; ++j) {
SEXP item = VECTOR_ELT(x, j+off);
if (length(item)==1) {
int tt = INTEGER(item)[0];
int tt = INTEGER_RO(item)[0];
if (tt==NA_INTEGER) continue; // singleton NA can be skipped
finalVal = tt;
break; // stop early on the first singleton that is not NA; minimizes deepest loop body below
Expand Down Expand Up @@ -108,7 +108,7 @@ SEXP coalesce(SEXP x, SEXP inplaceArg, SEXP nan_is_na_arg) {
for (int j=0; j<nval; ++j) {
SEXP item = VECTOR_ELT(x, j+off);
if (length(item)==1) {
double tt = REAL(item)[0];
double tt = REAL_RO(item)[0];
if (ISNAN(tt)) continue;
finalVal = tt;
break;
Expand All @@ -127,7 +127,7 @@ SEXP coalesce(SEXP x, SEXP inplaceArg, SEXP nan_is_na_arg) {
for (int j=0; j<nval; ++j) {
SEXP item = VECTOR_ELT(x, j+off);
if (length(item)==1) {
double tt = REAL(item)[0];
double tt = REAL_RO(item)[0];
if (ISNA(tt)) continue;
finalVal = tt;
break;
Expand Down
38 changes: 19 additions & 19 deletions src/dogroups.c
Original file line number Diff line number Diff line change
Expand Up @@ -79,16 +79,16 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
int nprotect=0;
SEXP ans=NULL, jval, thiscol, BY, N, I, GRP, iSD, xSD, RHS, target, source;
Rboolean wasvector, firstalloc=FALSE, NullWarnDone=FALSE;
const bool verbose = LOGICAL(verboseArg)[0]==1;
const bool verbose = LOGICAL_RO(verboseArg)[0]==1;
double tstart=0, tblock[10]={0}; int nblock[10]={0}; // For verbose printing, tstart is updated each block
bool hasPrinted = false;

if (!isInteger(order)) internal_error(__func__, "order not integer vector"); // # nocov
if (TYPEOF(starts) != INTSXP) internal_error(__func__, "starts not integer"); // # nocov
if (TYPEOF(lens) != INTSXP) internal_error(__func__, "lens not integer"); // # nocov
// starts can now be NA (<0): if (INTEGER(starts)[0]<0 || INTEGER(lens)[0]<0) error(_("starts[1]<0 or lens[1]<0"));
if (!isNull(jiscols) && LENGTH(order) && !LOGICAL(on)[0]) internal_error(__func__, "jiscols not NULL but o__ has length"); // # nocov
if (!isNull(xjiscols) && LENGTH(order) && !LOGICAL(on)[0]) internal_error(__func__, "xjiscols not NULL but o__ has length"); // # nocov
if (!isNull(jiscols) && LENGTH(order) && !LOGICAL_RO(on)[0]) internal_error(__func__, "jiscols not NULL but o__ has length"); // # nocov
if (!isNull(xjiscols) && LENGTH(order) && !LOGICAL_RO(on)[0]) internal_error(__func__, "xjiscols not NULL but o__ has length"); // # nocov
if(!isEnvironment(env)) error(_("env is not an environment"));
ngrp = length(starts); // the number of groups (nrow(groups) will be larger when by)
ngrpcols = length(grpcols);
Expand All @@ -97,7 +97,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
SEXP SDall = PROTECT(R_getVar(install(".SDall"), env, false)); nprotect++; // PROTECT for rchk
SEXP SD = PROTECT(R_getVar(install(".SD"), env, false)); nprotect++;

int updateTime = INTEGER(showProgressArg)[0];
int updateTime = INTEGER_RO(showProgressArg)[0];
const bool showProgress = updateTime > 0 && ngrp > 1; // showProgress only if more than 1 group
double startTime = (showProgress) ? wallclock() : 0; // For progress printing, startTime is set at the beginning
double nextTime = (showProgress) ? startTime + MAX(updateTime, 3) : 0; // wait at least 3 seconds before starting to print progress
Expand All @@ -108,7 +108,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
defineVar(sym_BY, BY = PROTECT(allocVector(VECSXP, ngrpcols)), env); nprotect++; // PROTECT for rchk
SEXP bynames = PROTECT(allocVector(STRSXP, ngrpcols)); nprotect++; // TO DO: do we really need bynames, can we assign names afterwards in one step?
for (int i=0; i<ngrpcols; ++i) {
int j = INTEGER(grpcols)[i]-1;
const int j = INTEGER_RO(grpcols)[i]-1;
SET_VECTOR_ELT(BY, i, allocVector(TYPEOF(VECTOR_ELT(groups, j)),
nrowgroups ? 1 : 0)); // TODO: might be able to be 1 always but 0 when 'groups' are integer(0) seem sensible. #2440 was involved in the past.
// Fix for #36, by cols with attributes when also used in `j` lost the attribute.
Expand Down Expand Up @@ -146,7 +146,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
// non data.table aware package that uses rownames
SEXP rownames = PROTECT(R_mapAttrib(SD, findRowNames, NULL)); nprotect++;
if (rownames == NULL) error(_("row.names attribute of .SD not found"));
if (!isInteger(rownames) || LENGTH(rownames)!=2 || INTEGER(rownames)[0]!=NA_INTEGER) error(_("row.names of .SD isn't integer length 2 with NA as first item; i.e., .set_row_names(). [%s %d %d]"),type2char(TYPEOF(rownames)),LENGTH(rownames),INTEGER(rownames)[0]);
if (!isInteger(rownames) || LENGTH(rownames)!=2 || INTEGER_RO(rownames)[0]!=NA_INTEGER) error(_("row.names of .SD isn't integer length 2 with NA as first item; i.e., .set_row_names(). [%s %d %d]"),type2char(TYPEOF(rownames)),LENGTH(rownames),INTEGER(rownames)[0]);

// fetch names of .SD and prepare symbols. In case they are copied-on-write by user assigning to those variables
// using <- in j (which is valid, useful and tested), they are repointed to the .SD cols for each group.
Expand All @@ -163,7 +163,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
internal_error(__func__, "SDall %d length = %d != %d", i+1, LENGTH(this), maxGrpSize); // # nocov
nameSyms[i] = install(CHAR(STRING_ELT(names, i)));
// fixes http://stackoverflow.com/questions/14753411/why-does-data-table-lose-class-definition-in-sd-after-group-by
copyMostAttrib(VECTOR_ELT(dt,INTEGER(dtcols)[i]-1), this); // not names, otherwise test 778 would fail
copyMostAttrib(VECTOR_ELT(dt,INTEGER_RO(dtcols)[i]-1), this); // not names, otherwise test 778 would fail
hash_set(specials, this, -maxGrpSize); // marker for anySpecialStatic(); see its comments
}

Expand Down Expand Up @@ -219,15 +219,15 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
}

if (length(iSD) && length(VECTOR_ELT(iSD, 0))/*#4364*/) for (int j=0; j<length(iSD); ++j) { // either this or the next for() will run, not both
memrecycle(VECTOR_ELT(iSD,j), R_NilValue, 0, 1, VECTOR_ELT(groups, INTEGER(jiscols)[j]-1), i, 1, j+1, "Internal error assigning to iSD");
memrecycle(VECTOR_ELT(iSD,j), R_NilValue, 0, 1, VECTOR_ELT(groups, INTEGER_RO(jiscols)[j]-1), i, 1, j+1, "Internal error assigning to iSD");
// we're just use memrecycle here to assign a single value
}
// igrp determines the start of the current group in rows of dt (0 based).
// if jiscols is not null, we have a by = .EACHI, so the start is exactly i.
// Otherwise, igrp needs to be determined from starts, potentially taking care about the order if present.
igrp = !isNull(jiscols) ? i : (length(grporder) ? INTEGER(grporder)[istarts[i]-1]-1 : istarts[i]-1);
igrp = !isNull(jiscols) ? i : (length(grporder) ? INTEGER_RO(grporder)[istarts[i]-1]-1 : istarts[i]-1);
if (igrp>=0 && nrowgroups) for (int j=0; j<length(BY); ++j) { // igrp can be -1 so 'if' is important, otherwise memcpy crash
memrecycle(VECTOR_ELT(BY,j), R_NilValue, 0, 1, VECTOR_ELT(groups, INTEGER(grpcols)[j]-1), igrp, 1, j+1, "Internal error assigning to BY");
memrecycle(VECTOR_ELT(BY,j), R_NilValue, 0, 1, VECTOR_ELT(groups, INTEGER_RO(grpcols)[j]-1), igrp, 1, j+1, "Internal error assigning to BY");
}
if (istarts[i] == NA_INTEGER || (LENGTH(order) && iorder[ istarts[i]-1 ]==NA_INTEGER)) {
for (int j=0; j<length(SDall); ++j) {
Expand Down Expand Up @@ -257,17 +257,17 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
for (int j=0; j<grpn; ++j) iI[j] = rownum+j+1;
if (rownum>=0) {
for (int j=0; j<length(SDall); ++j)
memrecycle(VECTOR_ELT(SDall,j), R_NilValue, 0, grpn, VECTOR_ELT(dt, INTEGER(dtcols)[j]-1), rownum, grpn, j+1, "Internal error assigning to SDall");
memrecycle(VECTOR_ELT(SDall,j), R_NilValue, 0, grpn, VECTOR_ELT(dt, INTEGER_RO(dtcols)[j]-1), rownum, grpn, j+1, "Internal error assigning to SDall");
for (int j=0; j<length(xSD); ++j)
memrecycle(VECTOR_ELT(xSD,j), R_NilValue, 0, 1, VECTOR_ELT(dt, INTEGER(xjiscols)[j]-1), rownum, 1, j+1, "Internal error assigning to xSD");
memrecycle(VECTOR_ELT(xSD,j), R_NilValue, 0, 1, VECTOR_ELT(dt, INTEGER_RO(xjiscols)[j]-1), rownum, 1, j+1, "Internal error assigning to xSD");
}
if (verbose) { tblock[0] += wallclock()-tstart; nblock[0]++; }
} else {
const int rownum = istarts[i]-1;
for (int k=0; k<grpn; ++k) iI[k] = iorder[rownum+k];
for (int j=0; j<length(SDall); ++j) {
// this is the main non-contiguous gather, and is parallel (within-column) for non-SEXP
subsetVectorRaw(VECTOR_ELT(SDall,j), VECTOR_ELT(dt,INTEGER(dtcols)[j]-1), I, anyNA);
subsetVectorRaw(VECTOR_ELT(SDall,j), VECTOR_ELT(dt,INTEGER_RO(dtcols)[j]-1), I, anyNA);
}
if (verbose) { tblock[1] += wallclock()-tstart; nblock[1]++; }
// The two blocks have separate timing statements to make sure which is running
Expand Down Expand Up @@ -303,7 +303,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
if (isArray(thiscol)) {
SEXP dims = PROTECT(getAttrib(thiscol, R_DimSymbol));
int nDimensions=0;
for (int d=0; d<LENGTH(dims); ++d) if (INTEGER(dims)[d] > 1) ++nDimensions;
for (int d=0; d<LENGTH(dims); ++d) if (INTEGER_RO(dims)[d] > 1) ++nDimensions;
UNPROTECT(1);
if (nDimensions > 1)
error(_("Entry %d for group %d in j=list(...) is an array with %d dimensions > 1, which is disallowed. \"Break\" the array yourself with c() or as.vector() if that is intentional."), j+1, i+1, nDimensions);
Expand All @@ -319,14 +319,14 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
error(_("RHS of := is NULL during grouped assignment, but it's not possible to delete parts of a column."));
int vlen = length(RHS);
if (vlen>1 && vlen!=grpn) {
SEXP colname = INTEGER(lhs)[j] > LENGTH(dt) ? STRING_ELT(newnames, INTEGER(lhs)[j]-origncol-1) : STRING_ELT(dtnames,INTEGER(lhs)[j]-1);
SEXP colname = INTEGER_RO(lhs)[j] > LENGTH(dt) ? STRING_ELT(newnames, INTEGER_RO(lhs)[j]-origncol-1) : STRING_ELT(dtnames,INTEGER_RO(lhs)[j]-1);
error(_("Supplied %d items to be assigned to group %d of size %d in column '%s'. The RHS length must either be 1 (single values are ok) or match the LHS length exactly. If you wish to 'recycle' the RHS please use rep() explicitly to make this intent clear to readers of your code."),vlen,i+1,grpn,CHAR(colname));
// e.g. in #91 `:=` did not issue recycling warning during grouping. Now it is error not warning.
}
}
int n = LENGTH(VECTOR_ELT(dt, 0));
for (int j=0; j<length(lhs); ++j) {
int colj = INTEGER(lhs)[j]-1;
int colj = INTEGER_RO(lhs)[j]-1;
RHS = VECTOR_ELT(jval,j%LENGTH(jval));
if (colj >= LENGTH(dt)) {
// first time adding to new column
Expand All @@ -349,7 +349,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
RHS = PROTECT(copyAsPlain(RHS));
copied = true;
}
const char *warn = memrecycle(target, order, INTEGER(starts)[i]-1, grpn, RHS, 0, -1, 0, "");
const char *warn = memrecycle(target, order, INTEGER_RO(starts)[i]-1, grpn, RHS, 0, -1, 0, "");
// can't error here because length mismatch already checked for all jval columns before starting to add any new columns
if (copied) UNPROTECT(1);
if (warn)
Expand Down Expand Up @@ -387,7 +387,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
nprotect++;
firstalloc=TRUE;
for(int j=0; j<ngrpcols; ++j) {
thiscol = VECTOR_ELT(groups, INTEGER(grpcols)[j]-1);
thiscol = VECTOR_ELT(groups, INTEGER_RO(grpcols)[j]-1);
SET_VECTOR_ELT(ans, j, allocVector(TYPEOF(thiscol), estn));
copyMostAttrib(thiscol, VECTOR_ELT(ans,j)); // not names, otherwise test 778 would fail
}
Expand Down Expand Up @@ -427,7 +427,7 @@ SEXP dogroups(SEXP dt, SEXP dtcols, SEXP groups, SEXP grpcols, SEXP jiscols, SEX
}
// write the group values to ans, recycled to match the nrow of the result for this group ...
for (int j=0; j<ngrpcols; ++j) {
memrecycle(VECTOR_ELT(ans,j), R_NilValue, ansloc, maxn, VECTOR_ELT(groups, INTEGER(grpcols)[j]-1), igrp, 1, j+1, "Internal error recycling group values");
memrecycle(VECTOR_ELT(ans,j), R_NilValue, ansloc, maxn, VECTOR_ELT(groups, INTEGER_RO(grpcols)[j]-1), igrp, 1, j+1, "Internal error recycling group values");
}
// Now copy jval into ans ...
for (int j=0; j<njval; ++j) {
Expand Down
16 changes: 8 additions & 8 deletions src/fcast.c
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@

// TO DO: margins
SEXP fcast(SEXP lhs, SEXP val, SEXP nrowArg, SEXP ncolArg, SEXP idxArg, SEXP fill, SEXP fill_d, SEXP is_agg, SEXP some_fillArg) {
int nrows=INTEGER(nrowArg)[0], ncols=INTEGER(ncolArg)[0];
int nlhs=length(lhs), nval=length(val), *idx = INTEGER(idxArg);
const int nrows=INTEGER_RO(nrowArg)[0], ncols=INTEGER_RO(ncolArg)[0];
const int nlhs=length(lhs), nval=length(val), *idx = INTEGER(idxArg);
SEXP target;

SEXP ans = PROTECT(allocVector(VECSXP, nlhs + (nval * ncols)));
Expand All @@ -15,7 +15,7 @@ SEXP fcast(SEXP lhs, SEXP val, SEXP nrowArg, SEXP ncolArg, SEXP idxArg, SEXP fil
SET_VECTOR_ELT(ans, i, VECTOR_ELT(lhs, i));
}
// get val cols
bool some_fill = LOGICAL(some_fillArg)[0];
const bool some_fill = LOGICAL_RO(some_fillArg)[0];
for (int i=0; i<nval; ++i) {
const SEXP thiscol = VECTOR_ELT(val, i);
SEXP thisfill = fill;
Expand Down Expand Up @@ -45,7 +45,7 @@ SEXP fcast(SEXP lhs, SEXP val, SEXP nrowArg, SEXP ncolArg, SEXP idxArg, SEXP fil
int *itarget = INTEGER(target);
copyMostAttrib(thiscol, target);
for (int k=0; k<nrows; ++k) {
int thisidx = idx[k*ncols + j];
const int thisidx = idx[k*ncols + j];
itarget[k] = (thisidx == NA_INTEGER) ? ithisfill[0] : ithiscol[thisidx-1];
}
}
Expand All @@ -59,7 +59,7 @@ SEXP fcast(SEXP lhs, SEXP val, SEXP nrowArg, SEXP ncolArg, SEXP idxArg, SEXP fil
double *dtarget = REAL(target);
copyMostAttrib(thiscol, target);
for (int k=0; k<nrows; ++k) {
int thisidx = idx[k*ncols + j];
const int thisidx = idx[k*ncols + j];
dtarget[k] = (thisidx == NA_INTEGER) ? dthisfill[0] : dthiscol[thisidx-1];
}
}
Expand All @@ -73,7 +73,7 @@ SEXP fcast(SEXP lhs, SEXP val, SEXP nrowArg, SEXP ncolArg, SEXP idxArg, SEXP fil
Rcomplex *ztarget = COMPLEX(target);
copyMostAttrib(thiscol, target);
for (int k=0; k<nrows; ++k) {
int thisidx = idx[k*ncols + j];
const int thisidx = idx[k*ncols + j];
ztarget[k] = (thisidx == NA_INTEGER) ? zthisfill[0] : zthiscol[thisidx-1];
}
}
Expand All @@ -83,7 +83,7 @@ SEXP fcast(SEXP lhs, SEXP val, SEXP nrowArg, SEXP ncolArg, SEXP idxArg, SEXP fil
SET_VECTOR_ELT(ans, nlhs+j+i*ncols, target=allocVector(thistype, nrows) );
copyMostAttrib(thiscol, target);
for (int k=0; k<nrows; ++k) {
int thisidx = idx[k*ncols + j];
const int thisidx = idx[k*ncols + j];
SET_STRING_ELT(target, k, (thisidx == NA_INTEGER) ? STRING_ELT(thisfill, 0) : STRING_ELT(thiscol, thisidx-1));
}
}
Expand All @@ -93,7 +93,7 @@ SEXP fcast(SEXP lhs, SEXP val, SEXP nrowArg, SEXP ncolArg, SEXP idxArg, SEXP fil
SET_VECTOR_ELT(ans, nlhs+j+i*ncols, target=allocVector(thistype, nrows) );
copyMostAttrib(thiscol, target);
for (int k=0; k<nrows; ++k) {
int thisidx = idx[k*ncols + j];
const int thisidx = idx[k*ncols + j];
SET_VECTOR_ELT(target, k, (thisidx == NA_INTEGER) ? VECTOR_ELT(thisfill, 0) : VECTOR_ELT(thiscol, thisidx-1));
}
}
Expand Down
Loading
Loading