search for: cummax

Displaying 20 results from an estimated 33 matches for "cummax".

Did you mean: cumm
2014 Jul 14
2
cummax / cummin for complex numbers
Dear all, in R 3.1.0, this is happening: > cummin(c(1+1i,2-3i,4+5i)) Error in cummin(c(1 + (0+1i), 2 - (0+3i), 4 + (0+5i))) : 'cummax' not defined for complex numbers > cummax(c(1+1i,2-3i,4+5i)) Error in cummax(c(1 + (0+1i), 2 - (0+3i), 4 + (0+5i))) : 'cummin' not defined for complex numbers It may be fixed in R-devel, but I thought I'd mention it to make sure ... Best, Michael -- Dr. Michael Haupt Prin...
2015 May 17
1
The function cummax() seems to have a bug.
Hi, The function cummax() seems to have a bug. > x <- c(NA, 0) > storage.mode(x) <- "integer" > cummax(x) [1] NA 0 The correct result of this case should be NA NA. The mistake in [ https://github.com/wch/r-source/blob/trunk/src/main/cum.c#L130-L136] may be the reason. Best Regards, Dongcan --...
2008 Jan 07
3
Seeking a more efficient way to find partition maxima
...in the example, I could do the following: partiCmax <- function( values, seriesIdx ) { # assume seriesIdx is increasing integer sequence beginning with 1, ending at less than or equal to length(values) parti <- cbind( seriesIdx, c( ( seriesIdx[ -1 ] - 1 ), length( values ) ) ) return( cummax( values )[ parti[ , 2 ] ] ) } The use of cummax makes that pretty efficient, but if the subvector maxima are not non-decreasing, it doesn't work. The following function works (at least it did on the examples I tried): partiMax <- function( values, seriesIdx ) { # assume seriesIdx is...
2006 May 17
5
Convention difference in tseries.maxdrawdown (PR#8872)
...he current version. It has the flaw that it does not check for zero or negative values. maximumdrawdown <- function (x) { if (NCOL(x) > 1) stop("x is not a vector or univariate time series") if (any(is.na(x))) stop("NAs in x") cminx <- x/cummax(x) mdd <- min(cminx) to <- which(mdd == cminx) from <- double(NROW(to)) for (i in 1:NROW(to)) { from[i] <- max( which(cminx[1:to[i]] == 1) ) } return(list(maximumdrawdown = 1-mdd, maxdrawdown = (1-mdd)*x[from], from = from, to = to)) }
2011 Feb 11
3
How can we make a vector call a function element-wise efficiently?
Hello I have a time-comsuming program which need to simplify, I have tested the annotated program as follow: > #define function which will be call > calsta <- function(c, n=100000) + { + i <- seq(from=0, length=c) + logx <- lchoose(NT-n, CT-i) + lchoose(n, i) + logmax <- max(logx) + logmax + log(sum(exp(logx - logmax))) + } > CT=6000 #assignment to CT >
2017 Jan 20
1
NaN behavior of cumsum
Hi! I noticed that cumsum behaves different than the other cumulative functions wrt. NaN values: > values <- c(1,2,NaN,1) > for ( f in c(cumsum, cumprod, cummin, cummax)) print(f(values)) [1] 1 3 NA NA [1] 1 2 NaN NaN [1] 1 1 NaN NaN [1] 1 2 NaN NaN The reason is that cumsum (in cum.c:33) contains an explicit check for ISNAN. Is that intentional? IMHO, ISNA would be better (because it would make the behavior consistent with the other functions). -...
2005 May 13
1
Lowest data level since DateX
...0) I need to come up with a vector that would look like this AA AXP T ... 2000-12-21 2000-12-20 2000-12-29 i.e. the last date at which the stocks were trading at a lower level than the most recent closing. I know it has to do with min/max, pmin/pmax, cummin/cummax or rev(), but I can't figure it out. Any help? Regards, Pierre Lapointe Assistant Market Strategist *********************************************************************************** AVIS DE NON-RESPONSABILITE:\ Ce document transmis par courri...{{dropped}}
2010 May 05
1
testInstalledBasic question
...gical" "as.numeric" "as.raw" "as.real" "asin" "asinh" [36] "atan" "atanh" "c" "ceiling" "cos" "cosh" "cummax" [43] "cummin" "cumprod" "cumsum" "digamma" "dim" "dim<-" "dimnames" [50] "dimnames<-" "exp" "expm1" "floor"...
2007 Nov 20
1
Vectorization/Speed Problem
Hi, I cannot find a 'vectorized' solution to this 'for loop' kind of problem. Do you see a vectorized, fast-running solution? Objective: Take the value of X at each timepoint and calculate the corresponding value of Y. Leading 0's and all 1's for X are assigned to Y; otherwise Y is incremented by the number of 0's adjacent to the last 1. The frequency and
2009 Feb 11
1
p.adjust; n > length(p) (PR#13519)
...ssion from: (NULL) (194.171.7.39) p.adjust in stats seems to have a bug in handling n>length(p) for (at least) the methods 'holm' and 'hochberg'. For method 'holm' the relevant code: i <- 1:n o <- order(p) ro <- order(o) pmin(1, cummax((n - i + 1) * p[o]))[ro] where p is the supplied vector of pvalues and n is the supplied number of comparisons. If n>length(p) p.adjust() gives a warning: Warning message: In (n - i + 1) * p[o] : longer object length is not a multiple of shorter object length to me it seems that instead of &...
2008 Dec 22
3
row sum question
Dear helpers, I'm using R version 2.8.0. Suppose that I have a small data set like below. [,1] [,2] [,3] [,4] a 1 1 0 0 b 0 1 1 0 c 1 1 1 0 d 0 1 1 1 First, I'd like to find row sum of values uniquely present in each row, but only sequentially from the top row, meaning that if the value is shown in the above row(s) already, the
2009 Dec 03
4
Replace values in a vector
Hi all, I have a vector like this: x<- c(0.7, 0.1, 0, 0.2, 0.2, 0, 0, 0 , 0, 0.4, 0, 0.8, 1.8) I would like to replace the zero values with the first previous non zero value. my returning vector should look like this: y<-c( 0.7, 0.1, 0.1,0.2,0.2,0.2,0.2,0.2, 0.4, 0.4, 0.8, 1.8) How can I do this in R without using for loop? Thank you
2009 Jul 01
2
?max (so far...)
Hi, I have a data.frame that is date ordered by row number - earliest date first and most current last. I want to create a couple of new columns that show the max and min values from other columns *so far* - not for the whole data.frame. It seems this sort of question is really coming from my lack of understanding about how R intends me to limit myself to portions of a data.frame. I get the
2011 Oct 04
1
a question about sort and BH
...gt;= lp) if (n <= 1) return(p0) if (n == 2 && method == "hommel") method <- "hochberg" p0[nna] <- switch(method, bonferroni = pmin(1, n * p), holm = { i <- seq_len(lp) o <- order(p) ro <- order(o) pmin(1, cummax( (n - i + 1L) * p[o] ))[ro] }, hommel = { ## needs n-1 >= 2 in for() below if(n > lp) p <- c(p, rep.int(1, n-lp)) i <- seq_len(n) o <- order(p) p <- p[o] ro <- order(o) q <- pa <- rep.int( min(n*p/i), n) for (j in (n-1):2...
2008 Dec 15
5
how to create duplicated ID in multi-records per subject dataset
Hi R helpers, If I have a dataset looks like: ID record 1 20 . 30 . 25 2 26 . 15 3 21 4..................... And I want it becomes ID record 1 20 1 30 1 25 2 26 2 15 3 21 4..................... That is, I have to duplicate IDs for those with multiple records. I am wondering it is possible to be
2011 Jun 19
4
For loop by factor.
I have a data.frame as follows: a 3 a 2 a 1 b 3 b 2 c 2 c 3 c 1 c 1 Each factor (a, b, c) should be monotonically decreasing, notice that factor 'c' is not. I could use some help to figure out how to form a logical structure (mostly just syntax), that will check each 'next value' for each factor to see if it is less than the previous value. If it is less than the
2010 Jun 01
0
selecting monotone pattern of missing data from a dataframe with mixed pattern of missingness
...function (x) {     stopifnot(is.data.frame(x))     o <- do.call(order, c(list(rowSums(is.na(x))), lapply(x[,         order(-sapply(x, function(x) sum(is.na(x))))], function(x) is.na(x))))     xo <- x[o, , drop = FALSE]     isNonterminalNA <- function(x) is.na(x) &                rev(cummax(!is.na(rev(x))) > 0)     good <- rep(TRUE, nrow(x))     for (j in seq(along = x)) {         good <- good & !isNonterminalNA(xo[, j, drop = TRUE])     }     xo[good, , drop = FALSE] } The function works well when the measurement occassions are just 3. When the measurement occassion bec...
2011 Sep 30
1
last observation carried forward +1
Hi R-helpers I'm looking for a vectorised function which does missing value replacement as in last observation carried forward in the zoo package but instead of a locf, I would like the locf function to add +1 to each time a missing value occurred. See below for an example. > require(zoo) > x <- 5:15 > x[4:7] <- NA > coredata(na.locf(zoo(x))) [1] 5 6 7 7 7 7 7 12 13
2011 Nov 24
1
Need some vectorizing help
So I have a problem that I'm trying to get through, and I just can't seem to get it to run very fast in R. What I'm trying to do is to find in a vector a local peak, then the next time that value is crossed later. I don't care about peaks that may be lower than this first one - they can be ignored. I've tried some sapply methods along the way, but they all are slower.
2012 Mar 12
2
Maximum of remaining elements of vector
Dear community I have the following problem. I'd like to have the maximum of the remaining elements of a vector. ex. x<-c(1,2,3,4,1,2,3,1,2,1) f(x) = c(4,4,4,4,3,3,3,2,2,1) where the first element is: max(x[1:length(x]) the second one: max(x[2:length(x)]) the third one: max(x[3:length(x)]) and so on Of course this can be done with a loop, but isn't there a nicer and faster way to