Revision da8174e204c4b3c8aff0fa179a0b53656129ef8e authored by Martin Schlather on 01 March 2004, 00:00:00 UTC, committed by Gabor Csardi on 01 March 2004, 00:00:00 UTC
1 parent 3e1677b
Raw File
extremes.R

## it does not make sense to me at the moment that a space-time model
## for extremes is defined.

"InitMaxStableRF" <-
function(x, y = NULL, z = NULL, grid, model, param, maxstable,
         method = NULL, register = 0, gridtriple = FALSE) 
{
  MaxStableList <- c("extremalGauss","BooleanFunction")
  stopifnot(length(maxstable)==1)
  MaxStableNr <- pmatch(maxstable,MaxStableList)
  if (is.na(MaxStableNr)) stop(paste("Unknown max-stable random field",
                                     "\nPossible values for `maxstable': \"",
                                     paste(MaxStableList,collapse="\", \""),
                                     "\"",sep=""))
    if (MaxStableNr==2) {
    if (is.null(method)) method <- "max.MPP"
    else{
      if (!is.character(method) || (length(method)==0))
        stop("Method must be a string.")
      if (.C("GetMethodNr",as.character(method),
             as.integer(1), nr = integer(1), PACKAGE="RandomFields")$nr
          !=
          .C("GetMethodNr",as.character("max.MPP"),
             as.integer(1), nr = integer(1), PACKAGE="RandomFields")$nr) { 
        warning("Method does not match max-stable random field definition. Set to `max.MPP'.")  
        method <- "max.MPP"
      }
    }
  }
  return(InitSimulateRF(x=x, y=y, z=z, grid=grid, model=model, param=param,
                        method=method, register=register,
                        gridtriple=gridtriple,
                        distribution="MaxStable")
          )
}

"MaxStableRF" <-
function (x, y = NULL, z = NULL, grid, model, param,  maxstable,
          method = NULL, n = 1, register = 0, gridtriple = FALSE) 
{
    if (InitMaxStableRF(x=x, y=y, z=z, grid=grid, model=model, param=param,
                        maxstable=maxstable,
                        method=method, register=register, gridtriple=gridtriple)
        <= 0) {
        return(DoSimulateRF(n=n, reg=register))
    }
    else {
        return(NULL)
    }
}








back to top