Title: | An S4 Class for Functional Data |
---|---|
Description: | S4 classes for univariate and multivariate functional data with utility functions. See <doi:10.18637/jss.v093.i05> for a detailed description of the package functionalities and its interplay with the MFPCA package for multivariate functional principal component analysis <https://CRAN.R-project.org/package=MFPCA>. |
Authors: | Clara Happ-Kurz [aut, cre] |
Maintainer: | Clara Happ-Kurz <[email protected]> |
License: | GPL-2 |
Version: | 1.3-9 |
Built: | 2024-11-12 03:56:12 UTC |
Source: | https://github.com/clarahapp/fundata |
This function calculates the weights for numerical integration
.intWeights(argvals, method = "trapezoidal")
.intWeights(argvals, method = "trapezoidal")
argvals |
A numeric vector of x-Values |
method |
A character string, giving the numerical integration method to use (default is |
A vector of integration weights
Generic method for scalar products, based on integrate
.scalarProduct(object1, object2, ...)
.scalarProduct(object1, object2, ...)
object1 , object2
|
Generic objects |
... |
Further objects passed to |
This function generates an artificial noisy version of a functional data
object of class funData
(univariate) or
multiFunData
(multivariate) by adding iid. realizations
of Gaussian random variables to the observations. The standard deviation
can be supplied by the user.
addError(funDataObject, sd)
addError(funDataObject, sd)
funDataObject |
A functional data object of class
|
sd |
The standard deviation |
An object of the same class as funDataObject
, which is a noisy
version of the original data.
funData
, multiFunData
,
simFunData
, simMultiFunData
.
oldPar <- par(no.readonly = TRUE) set.seed(1) # Univariate functional data plain <- simFunData(argvals = seq(0,1,0.01), M = 10, eFunType = "Fourier", eValType = "linear", N = 1)$simData noisy <- addError(plain , sd = 0.5) veryNoisy <- addError(plain, sd = 2) plot(plain, main = "Add error", ylim = range(veryNoisy@X)) plot(noisy, type = "p", pch = 20, add = TRUE) plot(veryNoisy, type = "p", pch = 4, add = TRUE) legend("topright", c("Plain", "Noisy", "Very Noisy"), lty = c(1, NA, NA), pch = c(NA, 20 ,4)) # Multivariate functional data plain <- simMultiFunData(type = "split", argvals = list(seq(0,1,0.01), seq(-.5,.5,0.02)), M = 10, eFunType = "Fourier", eValType = "linear", N = 1)$simData noisy <- addError(plain , sd = 0.5) veryNoisy <- addError(plain, sd = 2) par(mfrow = c(1,2)) plot(plain[[1]], main = "Add error (multivariate)", ylim = range(veryNoisy[[1]]@X)) plot(noisy[[1]], type = "p", pch = 20, add = TRUE) plot(veryNoisy[[1]], type = "p", pch = 4, add = TRUE) plot(plain[[2]], main = "Add error (multivariate)", ylim = range(veryNoisy[[2]]@X)) plot(noisy[[2]], type = "p", pch = 20, add = TRUE) plot(veryNoisy[[2]], type = "p", pch = 4, add = TRUE) legend("topright", c("Plain", "Noisy", "Very Noisy"), lty = c(1, NA, NA), pch = c(NA, 20 ,4)) par(oldPar)
oldPar <- par(no.readonly = TRUE) set.seed(1) # Univariate functional data plain <- simFunData(argvals = seq(0,1,0.01), M = 10, eFunType = "Fourier", eValType = "linear", N = 1)$simData noisy <- addError(plain , sd = 0.5) veryNoisy <- addError(plain, sd = 2) plot(plain, main = "Add error", ylim = range(veryNoisy@X)) plot(noisy, type = "p", pch = 20, add = TRUE) plot(veryNoisy, type = "p", pch = 4, add = TRUE) legend("topright", c("Plain", "Noisy", "Very Noisy"), lty = c(1, NA, NA), pch = c(NA, 20 ,4)) # Multivariate functional data plain <- simMultiFunData(type = "split", argvals = list(seq(0,1,0.01), seq(-.5,.5,0.02)), M = 10, eFunType = "Fourier", eValType = "linear", N = 1)$simData noisy <- addError(plain , sd = 0.5) veryNoisy <- addError(plain, sd = 2) par(mfrow = c(1,2)) plot(plain[[1]], main = "Add error (multivariate)", ylim = range(veryNoisy[[1]]@X)) plot(noisy[[1]], type = "p", pch = 20, add = TRUE) plot(veryNoisy[[1]], type = "p", pch = 4, add = TRUE) plot(plain[[2]], main = "Add error (multivariate)", ylim = range(veryNoisy[[2]]@X)) plot(noisy[[2]], type = "p", pch = 20, add = TRUE) plot(veryNoisy[[2]], type = "p", pch = 4, add = TRUE) legend("topright", c("Plain", "Noisy", "Very Noisy"), lty = c(1, NA, NA), pch = c(NA, 20 ,4)) par(oldPar)
This function approximates missing values for funData
objects based on
the na.approx interpolation method from the package zoo.
approxNA(object)
approxNA(object)
object |
An object of class |
A funData
object where missing values have been imputed.
This function requires the package zoo to be installed, otherwise it will throw a warning.
# Simulate some data f <- simFunData(N = 10, M = 8, eVal = "linear", eFun = "Poly", argvals = seq(0, 1, 0.01))$simData # Sparsify, i.e. generate artificial missings in the data fSparse <- sparsify(f, minObs = 10, maxObs = 50) # plot oldpar <- par(no.readonly = TRUE) par(mfrow = c(1,3)) plot(f, main = "Original Data") plot(fSparse, main = "Sparse Data") plot(approxNA(fSparse), main = "Reconstructed Data") # faster with plot(fSparse, plotNA = TRUE, main = "Reconstructed Data") par(oldpar)
# Simulate some data f <- simFunData(N = 10, M = 8, eVal = "linear", eFun = "Poly", argvals = seq(0, 1, 0.01))$simData # Sparsify, i.e. generate artificial missings in the data fSparse <- sparsify(f, minObs = 10, maxObs = 50) # plot oldpar <- par(no.readonly = TRUE) par(mfrow = c(1,3)) plot(f, main = "Original Data") plot(fSparse, main = "Sparse Data") plot(approxNA(fSparse), main = "Reconstructed Data") # faster with plot(fSparse, plotNA = TRUE, main = "Reconstructed Data") par(oldpar)
These functions allow basic arithmetics (such as '+', '-', '*', 'sqrt') for
functional data and numerics based on Arith
. The
operations are made pointwise for each observation. See examples below.
## S4 method for signature 'funData,funData' Arith(e1, e2) ## S4 method for signature 'funData,numeric' Arith(e1, e2) ## S4 method for signature 'numeric,funData' Arith(e1, e2) ## S4 method for signature 'multiFunData,multiFunData' Arith(e1, e2) ## S4 method for signature 'multiFunData,numeric' Arith(e1, e2) ## S4 method for signature 'numeric,multiFunData' Arith(e1, e2) ## S4 method for signature 'irregFunData,numeric' Arith(e1, e2) ## S4 method for signature 'numeric,irregFunData' Arith(e1, e2) ## S4 method for signature 'irregFunData,irregFunData' Arith(e1, e2) ## S4 method for signature 'irregFunData,funData' Arith(e1, e2) ## S4 method for signature 'funData,irregFunData' Arith(e1, e2)
## S4 method for signature 'funData,funData' Arith(e1, e2) ## S4 method for signature 'funData,numeric' Arith(e1, e2) ## S4 method for signature 'numeric,funData' Arith(e1, e2) ## S4 method for signature 'multiFunData,multiFunData' Arith(e1, e2) ## S4 method for signature 'multiFunData,numeric' Arith(e1, e2) ## S4 method for signature 'numeric,multiFunData' Arith(e1, e2) ## S4 method for signature 'irregFunData,numeric' Arith(e1, e2) ## S4 method for signature 'numeric,irregFunData' Arith(e1, e2) ## S4 method for signature 'irregFunData,irregFunData' Arith(e1, e2) ## S4 method for signature 'irregFunData,funData' Arith(e1, e2) ## S4 method for signature 'funData,irregFunData' Arith(e1, e2)
e1 , e2
|
Objects of class |
If two objects of a functional data class (funData
,
irregFunData
or multiFunData
) are used, they normally must be
of the same class, have the same domain and the same number of observations.
Exceptions are accepted if
one object has only one
observation. In this case, the arithmetic operations ('+', '-', '*', ...) are
done pairwise for this single function and all functions of the other object.
A typical example would be when subtracting the mean function from all
observations in a funData
object. This single function must be defined
on the same domain as the other functions (or, in case of
irregFunData
, on the union of all observation grids).
one of the
two objects is of class irregFunData
. Then, the other object can be of
class funData
, too, if it is defined on the union of all observation
grids. The result is an irregFunData
object which is defined on the
same observation grid as the original irregFunData
object.
An object of the same functional data class as e1
or
e2
, respectively.
Note that not all combinations of operations and classes
make sense, e.g. e1 ^ e2
is sensible if e1
is of class
funData
, irregFunData
or multiFunData
and e2
is
numeric. The reverse is not true.
funData
, irregFunData
,
multiFunData
, Arith
oldpar <- par(no.readonly = TRUE) par(mfrow = c(3,2), mar = rep(2.1,4)) argvals <- seq(0, 2*pi, 0.01) object1 <- funData(argvals, outer(seq(0.75, 1.25, by = 0.05), sin(argvals))) object2 <- funData(argvals, outer(seq(0.75, 1.25, by = 0.05), cos(argvals))) plot(object1, main = "Object1") plot(object2, main = "Object2") # Only functional data objects plot(object1 + object2, main = "Sum") plot(object1 - object2, main = "Difference") # Mixed plot(4 * object1 + 5, main = "4 * Object1 + 5") # Note y-axis! plot(object1^2 + object2^2, main = "Pythagoras") ### Irregular ind <- replicate(11, sort(sample(1:length(argvals), sample(5:10, 1)))) i1 <- irregFunData( argvals = lapply(1:11, function(i, ind, x){x[ind[[i]]]}, ind = ind, x = object1@argvals[[1]]), X = lapply(1:11, function(i, ind, y){y[i, ind[[i]]]}, ind = ind, y = object1@X)) i2 <- irregFunData( argvals = lapply(1:11, function(i, ind, x){x[ind[[i]]]}, ind = ind, x = object2@argvals[[1]]), X = lapply(1:11, function(i, ind, y){y[i, ind[[i]]]}, ind = ind, y = object2@X)) plot(i1, main = "Object 1 (irregular)") plot(i2, main = "Object 2 (irregular)") # Irregular and regular functional data objects plot(i1 + i2, main = "Sum") plot(i1 - object2, main = "Difference") # Mixed plot(4 * i1 + 5, main = "4 * i1 + 5") # Note y-axis! plot(i1^2 + i2^2, main = "Pythagoras") par(oldpar)
oldpar <- par(no.readonly = TRUE) par(mfrow = c(3,2), mar = rep(2.1,4)) argvals <- seq(0, 2*pi, 0.01) object1 <- funData(argvals, outer(seq(0.75, 1.25, by = 0.05), sin(argvals))) object2 <- funData(argvals, outer(seq(0.75, 1.25, by = 0.05), cos(argvals))) plot(object1, main = "Object1") plot(object2, main = "Object2") # Only functional data objects plot(object1 + object2, main = "Sum") plot(object1 - object2, main = "Difference") # Mixed plot(4 * object1 + 5, main = "4 * Object1 + 5") # Note y-axis! plot(object1^2 + object2^2, main = "Pythagoras") ### Irregular ind <- replicate(11, sort(sample(1:length(argvals), sample(5:10, 1)))) i1 <- irregFunData( argvals = lapply(1:11, function(i, ind, x){x[ind[[i]]]}, ind = ind, x = object1@argvals[[1]]), X = lapply(1:11, function(i, ind, y){y[i, ind[[i]]]}, ind = ind, y = object1@X)) i2 <- irregFunData( argvals = lapply(1:11, function(i, ind, x){x[ind[[i]]]}, ind = ind, x = object2@argvals[[1]]), X = lapply(1:11, function(i, ind, y){y[i, ind[[i]]]}, ind = ind, y = object2@X)) plot(i1, main = "Object 1 (irregular)") plot(i2, main = "Object 2 (irregular)") # Irregular and regular functional data objects plot(i1 + i2, main = "Sum") plot(i1 - object2, main = "Difference") # Mixed plot(4 * i1 + 5, main = "4 * i1 + 5") # Note y-axis! plot(i1^2 + i2^2, main = "Pythagoras") par(oldpar)
Coerce objects of class funData
, multiFunData
and
irregFunData
to a data frame.
## S4 method for signature 'funData' as.data.frame(x) ## S4 method for signature 'multiFunData' as.data.frame(x) ## S4 method for signature 'irregFunData' as.data.frame(x)
## S4 method for signature 'funData' as.data.frame(x) ## S4 method for signature 'multiFunData' as.data.frame(x) ## S4 method for signature 'irregFunData' as.data.frame(x)
x |
The functional data object that is to be transformed to a
|
A data frame with columns obs
(gives index/name of
observed curve), argvals1, ... argvalsd
with d
the
dimension of the support and X
for the observed values.
One-dimensional functions have only argvals1
, two-dimensional
functions (images) have argvals1
and argvals2
, etc.
funData
,
irregFunData
, multiFunData
,
data.frame
# one-dimensional domain f1 <- funData(argvals = 1:5, X = matrix(1:20, nrow = 4)) head(as.data.frame(f1)) # two-dimensional domain f2 <- funData(argvals = list(1:5, 1:6), X = array(1:120, c(4,5,6))) head(as.data.frame(f2)) # multivariate functional data m1 <- multiFunData(f1, f2) str(as.data.frame(m1)) # irregular functional data i1 <- irregFunData(argvals = list(1:5, 2:4, 3:5), X = list(1:5, 2:4, -(3:1))) head(as.data.frame(i1))
# one-dimensional domain f1 <- funData(argvals = 1:5, X = matrix(1:20, nrow = 4)) head(as.data.frame(f1)) # two-dimensional domain f2 <- funData(argvals = list(1:5, 1:6), X = array(1:120, c(4,5,6))) head(as.data.frame(f2)) # multivariate functional data m1 <- multiFunData(f1, f2) str(as.data.frame(m1)) # irregular functional data i1 <- irregFunData(argvals = list(1:5, 2:4, 3:5), X = list(1:5, 2:4, -(3:1))) head(as.data.frame(i1))
This function coerces an object of class irregFunData
to a
funData
object with missing values, which is defined on the union of
all observation points.
as.funData(object) ## S4 method for signature 'irregFunData' as.funData(object)
as.funData(object) ## S4 method for signature 'irregFunData' as.funData(object)
object |
The |
This function coerces an object of class funData
to a
irregFunData
object.
as.irregFunData(object) ## S4 method for signature 'funData' as.irregFunData(object)
as.irregFunData(object) ## S4 method for signature 'funData' as.irregFunData(object)
object |
The |
Coerce a funData
object to class multiFunData
with one element.
as.multiFunData(object) ## S4 method for signature 'funData' as.multiFunData(object)
as.multiFunData(object) ## S4 method for signature 'funData' as.multiFunData(object)
object |
The |
# create funData object with 5 observations x <- seq(0,1,0.01) f1 <- funData(argvals = x, X = 1:5 %o% x) f1 class(f1) # coerce to multiFunData object (of length 1) m1 <- as.multiFunData(f1) m1 class(m1)
# create funData object with 5 observations x <- seq(0,1,0.01) f1 <- funData(argvals = x, X = 1:5 %o% x) f1 class(f1) # coerce to multiFunData object (of length 1) m1 <- as.multiFunData(f1) m1 class(m1)
This function allows to plot funData
objects based on the
ggplot2 package. The function provides a wrapper that rearranges the
data in a funData
object on a one- or two-dimensional domain and
provides a basic ggplot
object, which can be
customized using all functionalities of the ggplot2 package.
autoplot.funData( object, obs = seq_len(nObs(object)), geom = "line", plotNA = FALSE, ... ) autolayer.funData( object, obs = seq_len(nObs(object)), geom = "line", plotNA = FALSE, ... )
autoplot.funData( object, obs = seq_len(nObs(object)), geom = "line", plotNA = FALSE, ... ) autolayer.funData( object, obs = seq_len(nObs(object)), geom = "line", plotNA = FALSE, ... )
object |
A |
obs |
A vector of numerics giving the observations to plot. Defaults to
all observations in |
geom |
A character string describing the geometric object to use.
Defaults to |
plotNA |
Logical. If |
... |
Further parameters passed to |
If some observations contain missing values (coded via NA
), the
functions can be interpolated using the option plotNA = TRUE
. This
option relies on the na.approx
function in package
zoo
and is currently implemented for one-dimensional
functions only in the function approxNA
.
A ggplot
object that can be customized using
all functionalities of the ggplot2 package.
# Install / load package ggplot2 before running the examples library("ggplot2") # One-dimensional argvals <- seq(0,2*pi,0.01) object <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) g <- autoplot(object) # returns ggplot object g # plot the object # add the mean function in red g + autolayer(meanFunction(object), col = 2) # Two-dimensional X <- array(0, dim = c(2, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) X[2,,] <- outer(argvals, argvals, function(x,y){sin(2*x*pi) * cos(2*y*pi)}) object2D <- funData(list(argvals, argvals), X) autoplot(object2D, obs = 1) autoplot(object2D, obs = 2) ## Not run: autoplot(object2D) # must specify obs! ### More examples ### par(mfrow = c(1,1)) # using plotNA (needs packages zoo and gridExtra) objectMissing <- funData(1:5, rbind(c(1, NA, 5, 4, 3), c(10, 9, NA, NA, 6))) g1 <- autoplot(objectMissing) # the default g2 <- autoplot(objectMissing, plotNA = TRUE) # requires zoo gridExtra::grid.arrange(g1 + ggtitle("plotNA = FALSE (default)"), g2 + ggtitle("plotNA = TRUE")) # requires gridExtra # Customizing plots (see ggplot2 documentation for more details) # parameters passed to geom_line are passed via the ... argument gFancy <- autoplot(object, color = "red", linetype = 2) gFancy # new layers can be added directly to the ggplot object gFancy + theme_bw() # add new layers to the ggplot object gFancy + ggtitle("Fancy Plot with Title and Axis Legends") + xlab("The x-Axis") + ylab("The y-Axis") autoplot(object2D, obs = 1) + ggtitle("Customized 2D plot") + theme_minimal() + scale_fill_gradient(high = "green", low = "blue", name = "Legend here")
# Install / load package ggplot2 before running the examples library("ggplot2") # One-dimensional argvals <- seq(0,2*pi,0.01) object <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) g <- autoplot(object) # returns ggplot object g # plot the object # add the mean function in red g + autolayer(meanFunction(object), col = 2) # Two-dimensional X <- array(0, dim = c(2, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) X[2,,] <- outer(argvals, argvals, function(x,y){sin(2*x*pi) * cos(2*y*pi)}) object2D <- funData(list(argvals, argvals), X) autoplot(object2D, obs = 1) autoplot(object2D, obs = 2) ## Not run: autoplot(object2D) # must specify obs! ### More examples ### par(mfrow = c(1,1)) # using plotNA (needs packages zoo and gridExtra) objectMissing <- funData(1:5, rbind(c(1, NA, 5, 4, 3), c(10, 9, NA, NA, 6))) g1 <- autoplot(objectMissing) # the default g2 <- autoplot(objectMissing, plotNA = TRUE) # requires zoo gridExtra::grid.arrange(g1 + ggtitle("plotNA = FALSE (default)"), g2 + ggtitle("plotNA = TRUE")) # requires gridExtra # Customizing plots (see ggplot2 documentation for more details) # parameters passed to geom_line are passed via the ... argument gFancy <- autoplot(object, color = "red", linetype = 2) gFancy # new layers can be added directly to the ggplot object gFancy + theme_bw() # add new layers to the ggplot object gFancy + ggtitle("Fancy Plot with Title and Axis Legends") + xlab("The x-Axis") + ylab("The y-Axis") autoplot(object2D, obs = 1) + ggtitle("Customized 2D plot") + theme_minimal() + scale_fill_gradient(high = "green", low = "blue", name = "Legend here")
This function allows to plot irregFunData
objects on their domain
based on the ggplot2 package. The function provides a wrapper that
returns a basic
ggplot
object, which can be customized using all
functionalities of the ggplot2 package.
autoplot.irregFunData(object, obs = seq_len(nObs(object)), geom = "line", ...) autolayer.irregFunData(object, obs = seq_len(nObs(object)), geom = "line", ...)
autoplot.irregFunData(object, obs = seq_len(nObs(object)), geom = "line", ...) autolayer.irregFunData(object, obs = seq_len(nObs(object)), geom = "line", ...)
object |
A |
obs |
A vector of numerics giving the observations to plot. Defaults to
all observations in |
geom |
A character string describing the geometric object to use.
Defaults to |
... |
Further parameters passed to |
A ggplot
object that can be customized using
all functionalities of the ggplot2 package.
irregFunData
, ggplot
,
plot.irregFunData
# Install / load package ggplot2 before running the examples library("ggplot2") # Generate data argvals <- seq(0,2*pi,0.01) ind <- replicate(5, sort(sample(1:length(argvals), sample(5:10,1)))) object <- irregFunData(argvals = lapply(ind, function(i){argvals[i]}), X = lapply(ind, function(i){sample(1:10,1) / 10 * argvals[i]^2})) # Plot the data autoplot(object) # Parameters passed to geom_line are passed via the ... argument autoplot(object, color = "red", linetype = 3) # Plot the data and add green dots for the 2nd function autoplot(object) + autolayer(object, obs = 2, geom = "point", color = "green") # New layers can be added directly to the ggplot object using functions from the ggplot2 package g <- autoplot(object) g + theme_bw() + ggtitle("Plot with minimal theme and axis labels") + xlab("The x-Axis") + ylab("The y-Axis")
# Install / load package ggplot2 before running the examples library("ggplot2") # Generate data argvals <- seq(0,2*pi,0.01) ind <- replicate(5, sort(sample(1:length(argvals), sample(5:10,1)))) object <- irregFunData(argvals = lapply(ind, function(i){argvals[i]}), X = lapply(ind, function(i){sample(1:10,1) / 10 * argvals[i]^2})) # Plot the data autoplot(object) # Parameters passed to geom_line are passed via the ... argument autoplot(object, color = "red", linetype = 3) # Plot the data and add green dots for the 2nd function autoplot(object) + autolayer(object, obs = 2, geom = "point", color = "green") # New layers can be added directly to the ggplot object using functions from the ggplot2 package g <- autoplot(object) g + theme_bw() + ggtitle("Plot with minimal theme and axis labels") + xlab("The x-Axis") + ylab("The y-Axis")
This function allows to plot multiFunData
objects based on the ggplot2 package. The
function applies the autoplot.funData
function to each element and returns either a
combined plot with all elements plotted in one row or a list containing the different subplots as
ggplot
objects. The individual objects can be customized using all
functionalities of the ggplot2 package.
autoplot.multiFunData( object, obs = seq_len(nObs(object)), dim = seq_len(length(object)), plotGrid = FALSE, ... )
autoplot.multiFunData( object, obs = seq_len(nObs(object)), dim = seq_len(length(object)), plotGrid = FALSE, ... )
object |
A |
obs |
A vector of numerics giving the observations to plot. Defaults to all observations in
|
dim |
The dimensions to plot. Defaults to |
plotGrid |
Logical. If |
... |
Further parameters passed to the univariate |
A list of ggplot
objects that are also printed directly as a grid
if plotGrid = TRUE
.
Currently, the function does not accept different parameters for the univariate elements.
multiFunData
, ggplot
,
plot.multiFunData
# Load packages ggplot2 and gridExtra before running the examples library("ggplot2"); library("gridExtra") # One-dimensional elements argvals <- seq(0, 2*pi, 0.01) f1 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) f2 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), cos(argvals))) m1 <- multiFunData(f1, f2) g <- autoplot(m1) # default g[[1]] # plot first element g[[2]] # plot second element gridExtra::grid.arrange(grobs = g, nrow = 1) # requires gridExtra package autoplot(m1, plotGrid = TRUE) # the same directly with plotGrid = TRUE # Mixed-dimensional elements X <- array(0, dim = c(11, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) f2 <- funData(list(argvals, argvals), X) m2 <- multiFunData(f1, f2) autoplot(m2, obs = 1, plotGrid = TRUE) # Customizing plots (see ggplot2 documentation for more details) g2 <- autoplot(m2, obs = 1) g2[[1]] <- g2[[1]] + ggtitle("First element") + theme_bw() g2[[2]] <- g2[[2]] + ggtitle("Second element") + scale_fill_gradient(high = "green", low = "blue") gridExtra::grid.arrange(grobs = g2, nrow = 1) # requires gridExtra package
# Load packages ggplot2 and gridExtra before running the examples library("ggplot2"); library("gridExtra") # One-dimensional elements argvals <- seq(0, 2*pi, 0.01) f1 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) f2 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), cos(argvals))) m1 <- multiFunData(f1, f2) g <- autoplot(m1) # default g[[1]] # plot first element g[[2]] # plot second element gridExtra::grid.arrange(grobs = g, nrow = 1) # requires gridExtra package autoplot(m1, plotGrid = TRUE) # the same directly with plotGrid = TRUE # Mixed-dimensional elements X <- array(0, dim = c(11, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) f2 <- funData(list(argvals, argvals), X) m2 <- multiFunData(f1, f2) autoplot(m2, obs = 1, plotGrid = TRUE) # Customizing plots (see ggplot2 documentation for more details) g2 <- autoplot(m2, obs = 1) g2[[1]] <- g2[[1]] + ggtitle("First element") + theme_bw() g2[[2]] <- g2[[2]] + ggtitle("Second element") + scale_fill_gradient(high = "green", low = "blue") gridExtra::grid.arrange(grobs = g2, nrow = 1) # requires gridExtra package
This function returns the support dimension of an object of class
funData
, irregFunData
or multiFunData
.
dimSupp(object)
dimSupp(object)
object |
An object of class |
If object
is univariate (i.e. of class funData
or irregFunData
), the
function returns the dimension of the support of object
. If
object
is multivariate (i.e. of class multiFunData
), the
function returns a vector, giving the support dimension of each element.
funData
, irregFunData
, multiFunData
# Univariate (one-dimensional) object1 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) dimSupp(object1) # Univariate (two-dimensional) object2 <- funData(argvals = list(1:10, 1:5), X = array(rnorm(100), dim = c(2,10,5))) dimSupp(object2) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) dimSupp(irregObject) # Multivariate multiObject <- multiFunData(object1, object2) dimSupp(multiObject)
# Univariate (one-dimensional) object1 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) dimSupp(object1) # Univariate (two-dimensional) object2 <- funData(argvals = list(1:10, 1:5), X = array(rnorm(100), dim = c(2,10,5))) dimSupp(object2) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) dimSupp(irregObject) # Multivariate multiObject <- multiFunData(object1, object2) dimSupp(multiObject)
This function calculates (orthonormal) basis functions on a given
interval, that can be interpreted as the first
eigenfunctions of an
appropriate data generating process of functional data.
eFun(argvals, M, ignoreDeg = NULL, type)
eFun(argvals, M, ignoreDeg = NULL, type)
argvals |
A vector of numerics, defining a (fine) grid on the interval for which the basis functions are computed. |
M |
An integer, specifying the number of functions that are calculated. |
ignoreDeg |
A vector of numerics, specifying the degrees to be ignored
for type |
type |
A character string, specifying the type of functions that are calculated. See Details. |
The function implements three families of orthonormal basis functions plus
variations of them. The parameter type
, that specifies the functions
to be calculated, can have the following values:
"Poly"
: Calculate orthonormal Legendre polynomials of degree
0,...,M-1.
"PolyHigh"
: Calculate orthonormal Legendre
Polynomials of higher degree. The vector of indices
ignoreDeg
specifies the functions to be ignored. If ignoreDeg
is not specified,
the function returns an error.
"Fourier"
: Calculate the first
Fourier basis functions.
"FourierLin"
: Calculate the
first Fourier basis functions plus the linear function,
orthonormalized to the previous functions via Gram-Schmidts method. This type
is currently implemented for functions on the unit interval
only.
If the function is called with other
argvals
, an error is thrown.
"Wiener"
: Calculate the first orthonormal eigenfunctions
of the Wiener process.
A univariate functional data object of class
funData
containing the basis functions on the given
interval.
funData
, simFunData
,
simMultiFunData
oldPar <- par(no.readonly = TRUE) argvals <- seq(0,1,0.01) par(mfrow = c(3,2)) plot(eFun(argvals, M = 4, type = "Poly"), main = "Poly", ylim = c(-3,3)) plot(eFun(argvals, M = 4, ignoreDeg = 1:2, type = "PolyHigh"), main = "PolyHigh", ylim = c(-3,3)) plot(eFun(argvals, M = 4, type = "Fourier"), main = "Fourier", ylim = c(-3,3)) plot(eFun(argvals, M = 4, type = "FourierLin"), main = "FourierLin", ylim = c(-3,3)) plot(eFun(argvals, M = 4, type = "Wiener"), main = "Wiener", ylim = c(-3,3)) par(oldPar)
oldPar <- par(no.readonly = TRUE) argvals <- seq(0,1,0.01) par(mfrow = c(3,2)) plot(eFun(argvals, M = 4, type = "Poly"), main = "Poly", ylim = c(-3,3)) plot(eFun(argvals, M = 4, ignoreDeg = 1:2, type = "PolyHigh"), main = "PolyHigh", ylim = c(-3,3)) plot(eFun(argvals, M = 4, type = "Fourier"), main = "Fourier", ylim = c(-3,3)) plot(eFun(argvals, M = 4, type = "FourierLin"), main = "FourierLin", ylim = c(-3,3)) plot(eFun(argvals, M = 4, type = "Wiener"), main = "Wiener", ylim = c(-3,3)) par(oldPar)
This function generates decreasing eigenvalues.
eVal(M, type)
eVal(M, type)
M |
An integer, the number of eigenvalues to be generated. |
type |
A character string specifying the type of eigenvalues that should be calculated. See Details. |
The function implements three types of eigenvalues:
"linear":
The eigenvalues start at and decrease linearly
towards
:
"exponential":
The eigenvalues start at and decrease
exponentially towards
:
"wiener":
The eigenvalues correspond to the eigenvalues of the Wiener
process:
A vector containing the M
decreasing eigenvalues.
oldpar <- par(no.readonly = TRUE) # simulate M = 10 eigenvalues M <- 10 eLin <- eVal(M = M, type = "linear") eExp <- eVal(M = M, type = "exponential") eWien <- eVal(M = M, type = "wiener") par(mfrow = c(1,1)) plot(1:M, eLin, pch = 20, xlab = "m", ylab = expression(nu[m]), ylim = c(0,1)) points(1:M, eExp, pch = 20, col = 3) points(1:M, eWien, pch = 20, col = 4) legend("topright", legend = c("linear", "exponential", "wiener"), pch = 20, col = c(1,3,4)) par(oldpar)
oldpar <- par(no.readonly = TRUE) # simulate M = 10 eigenvalues M <- 10 eLin <- eVal(M = M, type = "linear") eExp <- eVal(M = M, type = "exponential") eWien <- eVal(M = M, type = "wiener") par(mfrow = c(1,1)) plot(1:M, eLin, pch = 20, xlab = "m", ylab = expression(nu[m]), ylim = c(0,1)) points(1:M, eExp, pch = 20, col = 3) points(1:M, eWien, pch = 20, col = 4) legend("topright", legend = c("linear", "exponential", "wiener"), pch = 20, col = c(1,3,4)) par(oldpar)
This function extracts one or more observations and/or observations on
a part of the domain from a funData
, irregFunData
or
multiFunData
object.
extractObs( object, obs = seq_len(nObs(object)), argvals = funData::argvals(object) ) ## S4 method for signature 'funData' subset(x, obs = seq_len(nObs(x)), argvals = funData::argvals(x)) ## S4 method for signature 'multiFunData' subset(x, obs = seq_len(nObs(x)), argvals = funData::argvals(x)) ## S4 method for signature 'irregFunData' subset(x, obs = seq_len(nObs(x)), argvals = funData::argvals(x)) ## S4 method for signature 'funData,ANY,missing,missing' x[i, j, ..., drop = TRUE] ## S4 method for signature 'multiFunData,ANY,missing,missing' x[i, j, ..., drop = TRUE] ## S4 method for signature 'irregFunData,ANY,missing,missing' x[i = seq_len(nObs(x)), j, ..., drop = TRUE]
extractObs( object, obs = seq_len(nObs(object)), argvals = funData::argvals(object) ) ## S4 method for signature 'funData' subset(x, obs = seq_len(nObs(x)), argvals = funData::argvals(x)) ## S4 method for signature 'multiFunData' subset(x, obs = seq_len(nObs(x)), argvals = funData::argvals(x)) ## S4 method for signature 'irregFunData' subset(x, obs = seq_len(nObs(x)), argvals = funData::argvals(x)) ## S4 method for signature 'funData,ANY,missing,missing' x[i, j, ..., drop = TRUE] ## S4 method for signature 'multiFunData,ANY,missing,missing' x[i, j, ..., drop = TRUE] ## S4 method for signature 'irregFunData,ANY,missing,missing' x[i = seq_len(nObs(x)), j, ..., drop = TRUE]
object |
An object of class |
obs |
A numeric vector, giving the indices of the observations to extract (default: all observations). |
argvals |
The part of the domain to be extracted (default: the
whole domain |
x |
An object of class |
i |
A numeric vector, giving the indices of the observations to
extract when using |
j , drop
|
not used |
... |
Used to pass further arguments to |
In case of an irregFunData
object, some functions may not have
observation points in the given part of the domain. In this case, the
functions are removed from the extracted dataset and a warning is
thrown.
If only observations are to be extracted, the usual notation
object[1:3]
is equivalent to extractObs(object, obs =
1:3)
. This works only if the domain remains unchanged.
An object of class funData
, irregFunData
or
multiFunData
containing the desired observations.
x[i
:
The function is currently implemented only for functional data with up to three-dimensional domains.
The function subset
is an alias for
extractObs
.
funData
,
irregFunData
, multiFunData
# Univariate - one-dimensional domain object1 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) extractObs(object1, obs = 1) extractObs(object1, argvals = 1:3) extractObs(object1, argvals = list(1:3)) # the same as the statement before # alias subset(object1, argvals = 1:3) # Univariate - two-dimensional domains object2 <- funData(argvals = list(1:5, 1:6), X = array(1:60, dim = c(2, 5, 6))) extractObs(object2, obs = 1) extractObs(object2, argvals = list(1:3, c(2,4,6))) # argvals must be supplied as list # Univariate - irregular irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) extractObs(irregObject, obs = 2) extractObs(irregObject, argvals = 1:3) extractObs(irregObject, argvals = c(1,5)) # throws a warning, as second function has no observations # Multivariate multiObject <- multiFunData(object1, object2) extractObs(multiObject, obs = 2) multiObject[2] # shorthand extractObs(multiObject, argvals = list(1:3, list(1:3, c(2,4,6)))) ### Shorthand via "[]" object1[1] object1[argvals = 1:3] object2[1] object2[argvals = list(1:3, c(2,4,6))] irregObject[2] irregObject[argvals = 1:3]
# Univariate - one-dimensional domain object1 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) extractObs(object1, obs = 1) extractObs(object1, argvals = 1:3) extractObs(object1, argvals = list(1:3)) # the same as the statement before # alias subset(object1, argvals = 1:3) # Univariate - two-dimensional domains object2 <- funData(argvals = list(1:5, 1:6), X = array(1:60, dim = c(2, 5, 6))) extractObs(object2, obs = 1) extractObs(object2, argvals = list(1:3, c(2,4,6))) # argvals must be supplied as list # Univariate - irregular irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) extractObs(irregObject, obs = 2) extractObs(irregObject, argvals = 1:3) extractObs(irregObject, argvals = c(1,5)) # throws a warning, as second function has no observations # Multivariate multiObject <- multiFunData(object1, object2) extractObs(multiObject, obs = 2) multiObject[2] # shorthand extractObs(multiObject, argvals = list(1:3, list(1:3, c(2,4,6)))) ### Shorthand via "[]" object1[1] object1[argvals = 1:3] object2[1] object2[argvals = list(1:3, c(2,4,6))] irregObject[2] irregObject[argvals = 1:3]
This function converts an object of class fd
(from
package fda) to an object of class funData
. It
heavily builds on the function eval.fd
from the
fda package. The fd
representation assumes a
basis representation for the observed functions and therefore
implicitly smoothes the data. In funData
objects, the data is
saved in 'raw' format.
fd2funData(fdobj, argvals, ...)
fd2funData(fdobj, argvals, ...)
fdobj |
An |
argvals |
A vector or a list of length one, containing a vector
with argument values at which the functions in |
... |
Other parameters passed to |
An object of class funData
.
Time names in fdobj$fdnames$time
are not
preserved.
# Install / load package fda before running the examples library("fda") # from Data2fd help daybasis <- create.fourier.basis(c(0, 365), nbasis=65) # fd object of daily temperatures tempfd <- Data2fd(argvals = day.5, y = CanadianWeather$dailyAv[,,"Temperature.C"], daybasis) # convert to funData tempFun <- fd2funData(tempfd, argvals = day.5) # plot to compare par(mfrow = c(1,2)) plot(tempfd, main = "fd object") plot(tempFun, main = "funData object")
# Install / load package fda before running the examples library("fda") # from Data2fd help daybasis <- create.fourier.basis(c(0, 365), nbasis=65) # fd object of daily temperatures tempfd <- Data2fd(argvals = day.5, y = CanadianWeather$dailyAv[,,"Temperature.C"], daybasis) # convert to funData tempFun <- fd2funData(tempfd, argvals = day.5) # plot to compare par(mfrow = c(1,2)) plot(tempfd, main = "fd object") plot(tempFun, main = "funData object")
This function flips an object newObject
of class funData
,
irregFunData
or multiFunData
with respect to a reference object
refObject
of the same class (or of class funData
, if
newObject
is irregular). This is particularly useful when dealing with
functional principal components, as they are only defined up to a sign
change. For details, see below.
flipFuns(refObject, newObject, ...)
flipFuns(refObject, newObject, ...)
refObject |
An object of class |
newObject |
An object of class |
... |
Further parameters passed to |
Functional principal component analysis is an important tool in functional
data analysis. Just as eigenvectors, eigenfunctions (or functional principal
components) are only defined up to a sign change. This may lead to
difficulties in simulation studies or when bootstrapping pointwise confidence
bands, as in these cases one wants the estimates to have the same
"orientation" as the true function (in simulation settings) or the
non-bootstrapped estimate (when calculating bootstrap confidence bands). This
function allows to flip (i.e. multiply by ) all observations in
newObject
that have a different orientation than their counterparts in
refData
.
Technically, the function compares the distance between newObject
and
refObject
and the distance between newObject
and
-1 * refObject
If newObject
is closer to -1 * refObject
, it is
flipped, i.e. multiplied by -1.
An object of the same class as newData
with flipped
observations.
The function is currently implemented only for functional data with one- and two-dimensional domains.
funData
, irregFunData
,
multiFunData
, Arith.funData
### Univariate argvals <- seq(0,2*pi,0.01) refData <- funData(argvals, rbind(sin(argvals))) # one observation as reference newData <- funData(argvals, outer(sample(c(-1,1), 11, replace = TRUE) * seq(0.75, 1.25, by = 0.05), sin(argvals))) oldpar <- par(no.readonly = TRUE) par(mfrow = c(1,2)) plot(newData, col = "grey", main = "Original data") plot(refData, col = "red", lwd = 2, add = TRUE) plot(flipFuns(refData, newData), col = "grey", main = "Flipped data") plot(refData, col = "red", lwd = 2, add = TRUE) ### Univariate (irregular) ind <- replicate(11, sort(sample(1:length(argvals), sample(5:10,1)))) # sample observation points argvalsIrreg <- lapply(ind, function(i){argvals[i]}) argvalsIrregAll <- unique(sort(unlist(argvalsIrreg))) # one observation as reference (fully observed) refDataFull <- funData(argvals, rbind(sin(argvals))) # one observation as reference (irregularly observed) refDataIrreg <- irregFunData(argvals = list(argvalsIrregAll), X = list(sin(argvalsIrregAll))) newData <- irregFunData(argvals = argvalsIrreg, X = mapply(function(x, a, s){s * a * sin(x)}, x = argvalsIrreg, a = seq(0.75, 1.25, by = 0.05), s = sample(c(-1,1), 11, replace = TRUE))) plot(newData, col = "grey", main = "Original data (regular reference)") plot(refDataFull, col = "red", lwd = 2, add = TRUE) plot(flipFuns(refDataFull, newData), col = "grey", main = "Flipped data") plot(refDataFull, col = "red", lwd = 2, add = TRUE) plot(newData, col = "grey", main = "Original data (irregular reference)") plot(refDataIrreg, col = "red", lwd = 2, add = TRUE) plot(flipFuns(refDataIrreg, newData), col = "grey", main = "Flipped data") plot(refDataIrreg, col = "red", lwd = 2, add = TRUE) ### Multivariate refData <- multiFunData(funData(argvals, rbind(sin(argvals))), # one observation as reference funData(argvals, rbind(cos(argvals)))) sig <- sample(c(-1,1), 11, replace = TRUE) newData <- multiFunData(funData(argvals, outer(sig * seq(0.75, 1.25, by = 0.05), sin(argvals))), funData(argvals, outer(sig * seq(0.75, 1.25, by = 0.05), cos(argvals)))) par(mfrow = c(2,2)) plot(newData[[1]], col = topo.colors(11), main = "Original data") plot(refData[[1]], col = "red", lwd = 2, add = TRUE) plot(newData[[2]], col = topo.colors(11), main = "Original data") plot(refData[[2]], col = "red", lwd = 2, add = TRUE) plot(flipFuns(refData, newData)[[1]], col = topo.colors(11), main = "Flipped data") plot(refData[[1]], col = "red", lwd = 2, add = TRUE) plot(flipFuns(refData, newData)[[2]], col = topo.colors(11), main = "Flipped data") plot(refData[[2]], col = "red", lwd = 2, add = TRUE) par(oldpar)
### Univariate argvals <- seq(0,2*pi,0.01) refData <- funData(argvals, rbind(sin(argvals))) # one observation as reference newData <- funData(argvals, outer(sample(c(-1,1), 11, replace = TRUE) * seq(0.75, 1.25, by = 0.05), sin(argvals))) oldpar <- par(no.readonly = TRUE) par(mfrow = c(1,2)) plot(newData, col = "grey", main = "Original data") plot(refData, col = "red", lwd = 2, add = TRUE) plot(flipFuns(refData, newData), col = "grey", main = "Flipped data") plot(refData, col = "red", lwd = 2, add = TRUE) ### Univariate (irregular) ind <- replicate(11, sort(sample(1:length(argvals), sample(5:10,1)))) # sample observation points argvalsIrreg <- lapply(ind, function(i){argvals[i]}) argvalsIrregAll <- unique(sort(unlist(argvalsIrreg))) # one observation as reference (fully observed) refDataFull <- funData(argvals, rbind(sin(argvals))) # one observation as reference (irregularly observed) refDataIrreg <- irregFunData(argvals = list(argvalsIrregAll), X = list(sin(argvalsIrregAll))) newData <- irregFunData(argvals = argvalsIrreg, X = mapply(function(x, a, s){s * a * sin(x)}, x = argvalsIrreg, a = seq(0.75, 1.25, by = 0.05), s = sample(c(-1,1), 11, replace = TRUE))) plot(newData, col = "grey", main = "Original data (regular reference)") plot(refDataFull, col = "red", lwd = 2, add = TRUE) plot(flipFuns(refDataFull, newData), col = "grey", main = "Flipped data") plot(refDataFull, col = "red", lwd = 2, add = TRUE) plot(newData, col = "grey", main = "Original data (irregular reference)") plot(refDataIrreg, col = "red", lwd = 2, add = TRUE) plot(flipFuns(refDataIrreg, newData), col = "grey", main = "Flipped data") plot(refDataIrreg, col = "red", lwd = 2, add = TRUE) ### Multivariate refData <- multiFunData(funData(argvals, rbind(sin(argvals))), # one observation as reference funData(argvals, rbind(cos(argvals)))) sig <- sample(c(-1,1), 11, replace = TRUE) newData <- multiFunData(funData(argvals, outer(sig * seq(0.75, 1.25, by = 0.05), sin(argvals))), funData(argvals, outer(sig * seq(0.75, 1.25, by = 0.05), cos(argvals)))) par(mfrow = c(2,2)) plot(newData[[1]], col = topo.colors(11), main = "Original data") plot(refData[[1]], col = "red", lwd = 2, add = TRUE) plot(newData[[2]], col = topo.colors(11), main = "Original data") plot(refData[[2]], col = "red", lwd = 2, add = TRUE) plot(flipFuns(refData, newData)[[1]], col = topo.colors(11), main = "Flipped data") plot(refData[[1]], col = "red", lwd = 2, add = TRUE) plot(flipFuns(refData, newData)[[2]], col = topo.colors(11), main = "Flipped data") plot(refData[[2]], col = "red", lwd = 2, add = TRUE) par(oldpar)
The funData
class represents functional data on -dimensional
domains. The two slots represent the domain (x-values) and the values of the
different observations (y-values).
funData(argvals, X) ## S4 method for signature 'list,array' funData(argvals, X) ## S4 method for signature 'numeric,array' funData(argvals, X) ## S4 method for signature 'funData' show(object) ## S4 method for signature 'funData' names(x) ## S4 replacement method for signature 'funData' names(x) <- value ## S4 method for signature 'funData' str(object, ...) ## S4 method for signature 'funData' summary(object, ...)
funData(argvals, X) ## S4 method for signature 'list,array' funData(argvals, X) ## S4 method for signature 'numeric,array' funData(argvals, X) ## S4 method for signature 'funData' show(object) ## S4 method for signature 'funData' names(x) ## S4 replacement method for signature 'funData' names(x) <- value ## S4 method for signature 'funData' str(object, ...) ## S4 method for signature 'funData' summary(object, ...)
argvals |
A list of numeric vectors or a single numeric vector, giving the sampling points in the domains. See Details. |
X |
An array of dimension |
object |
A |
x |
The |
value |
The names to be given to the |
... |
Other parameters passed to |
Functional data can be seen as realizations of a random process
on a -dimensional
domain
. The data is usually sampled on a fine grid
, which is represented in the
argvals
slot of a funData
object. All observations are assumed
to be sampled over the same grid , but can contain missing values
(see below). If
is one-dimensional,
argvals
can be supplied either as a numeric vector, containing the x-values or as a
list, containing such a vector. If is
higher-dimensional,
argvals
must always be supplied as a list,
containing numeric vectors of the x-values in dimensions
.
The observed values are represented in the X
slot of a funData
object, which is an array of dimension (for
one-dimensional domains, or
for higher-dimensional domains). Here
equals
the number of observations and
denotes the number of sampling
points (for higher dimensional domains
denotes the number of
sampling points in dimension
).
Missing values in the observations are allowed and must be marked by
NA
. If missing values occur due to irregular observation points, the
data can be stored alternatively as an object of class
irregFunData
.
Generic functions for the funData
class include a print method,
plotting and basic arithmetics.
Further methods for funData
:
dimSupp
,
nObs
: Informations about the support dimensions and the number
of observations,
getArgvals
, extractObs
:
Getting/Setting slot values (instead of accessing them directly via
funData@argvals, funData@X
) and extracting single observations or
data on a subset of the domain,
integrate
,
norm
: Integrate all observations over their domain or
calculating the norm.
A funData
object can be coerced to a multiFunData
object using
as.multiFunData(funDataObject).
funData(argvals = list, X = array)
: Constructor for functional data objects with argvals
given as list.
funData(argvals = numeric, X = array)
: Constructor for functional data objects with argvals
given as vector of numerics (only valid for one-dimensional domains).
show(funData)
: Print basic information about the funData
object
in the console. The default console output for funData
objects.
names(funData)
: Get the names of the funData
object.
names(funData) <- value
: Set the names of the funData
object.
str(funData)
: A str
method for funData
objects, giving a compact overview of the structure.
summary(funData)
: A summary
method for funData
objects.
funData()
: Constructor for functional data objects, first argument (argvals) passed as list or vector of numerics
argvals
The domain of the data. See Details.
X
The functional data samples. See Details.
### Creating a one-dimensional funData object with 2 observations # Basic f1 <- new("funData", argvals = list(1:5), X = rbind(1:5,6:10)) # Using the constructor with first argument supplied as array f2 <- funData(argvals = list(1:5), X = rbind(1:5, 6:10)) # Using the constructor with first argument supplied as numeric vector f3 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) # Test if all the same all.equal(f1,f2) all.equal(f1,f3) # Display funData object in the console f3 # A more realistic object argvals <- seq(0,2*pi,0.01) object <- funData(argvals, outer(seq(0.75, 1.25, by = 0.05), sin(argvals))) # Display / summary give basic information object summary(object) # Use the plot function to get an impression of the data plot(object) ### Higher-dimensional funData objects with 2 observations # Basic g1 <- new("funData", argvals = list(1:5, 1:3), X = array(1:30, dim = c(2,5,3))) # Using the constructor g2 <- funData(argvals = list(1:5, 1:3), X = array(1:30, dim = c(2,5,3))) # Test if the same all.equal(g1,g2) # Display funData object in the console g2 # Summarize information summary(g2)
### Creating a one-dimensional funData object with 2 observations # Basic f1 <- new("funData", argvals = list(1:5), X = rbind(1:5,6:10)) # Using the constructor with first argument supplied as array f2 <- funData(argvals = list(1:5), X = rbind(1:5, 6:10)) # Using the constructor with first argument supplied as numeric vector f3 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) # Test if all the same all.equal(f1,f2) all.equal(f1,f3) # Display funData object in the console f3 # A more realistic object argvals <- seq(0,2*pi,0.01) object <- funData(argvals, outer(seq(0.75, 1.25, by = 0.05), sin(argvals))) # Display / summary give basic information object summary(object) # Use the plot function to get an impression of the data plot(object) ### Higher-dimensional funData objects with 2 observations # Basic g1 <- new("funData", argvals = list(1:5, 1:3), X = array(1:30, dim = c(2,5,3))) # Using the constructor g2 <- funData(argvals = list(1:5, 1:3), X = array(1:30, dim = c(2,5,3))) # Test if the same all.equal(g1,g2) # Display funData object in the console g2 # Summarize information summary(g2)
This function converts an object of class funData
to an
object of class fd
(from package fda). It
heavily builds on the function Data2fd
from the
fda package. The fd
representation assumes a
basis representation for the observed functions and therefore
implicitly smoothes the data. In funData
objects, the data is
saved in 'raw' format.
funData2fd(object, ...)
funData2fd(object, ...)
object |
A |
... |
Other parameters passed to |
An object of class fd
.
This function works only for funData objects on one-dimensional domains.
funData
, fd
,
Data2fd
, fd2funData
# Install / load package fda before running the examples library("fda") # from Data2fd help daybasis <- create.fourier.basis(c(0, 365), nbasis=65) # funData object with temperature tempFun <- funData(day.5, t(CanadianWeather$dailyAv[, , "Temperature.C"])) # convert to fd tempfd <- funData2fd(tempFun, daybasis) # plot to compare par(mfrow = c(1,2)) plot(tempFun, main = "funData object (raw data)") plot(tempfd, main = "fd object (smoothed)")
# Install / load package fda before running the examples library("fda") # from Data2fd help daybasis <- create.fourier.basis(c(0, 365), nbasis=65) # funData object with temperature tempFun <- funData(day.5, t(CanadianWeather$dailyAv[, , "Temperature.C"])) # convert to fd tempfd <- funData2fd(tempFun, daybasis) # plot to compare par(mfrow = c(1,2)) plot(tempFun, main = "funData object (raw data)") plot(tempfd, main = "fd object (smoothed)")
This function is deprecated. Use autoplot.funData
/
autolayer.funData
for funData
objects,
autoplot.multiFunData
for multiFunData
objects and
autoplot.irregFunData
/
autolayer.irregFunData
for irregFunData
objects
instead.
ggplot(data, ...) ## S4 method for signature 'funData' ggplot(data, add = FALSE, ...) ## S4 method for signature 'multiFunData' ggplot(data, ...) ## S4 method for signature 'irregFunData' ggplot(data, add = FALSE, ...)
ggplot(data, ...) ## S4 method for signature 'funData' ggplot(data, add = FALSE, ...) ## S4 method for signature 'multiFunData' ggplot(data, ...) ## S4 method for signature 'irregFunData' ggplot(data, add = FALSE, ...)
data |
A |
... |
Further parameters passed to the class-specific methods. |
add |
Logical. If |
In the default case, this function calls ggplot (if available).
A ggplot
object
ggplot
,
autoplot
, autolayer
from package ggplot2
Integrate all observations of a funData
, irregFunData
or
multiFunData
object over their domain.
integrate(object, ...)
integrate(object, ...)
object |
An object of class |
... |
Further parameters (see Details). |
Further parameters passed to this function may include:
method
: Character string. The integration rule to be used, passed to
the internal function .intWeights
. Defaults to "trapezoidal"
(alternative: "midpoint"
).
fullDom
: Logical. If
object
is of class irregFunData
, setting fullDom = TRUE
extrapolates all functions linearly to the full domain before calculating the
integrals. Defaults to FALSE
. For details on the extrapolation, see
extrapolateIrreg
.
A vector of numerics, containing the integral values for each observation.
The function is currently implemented only for functional data with up to three-dimensional domains. In the default case, this function calls integrate.
funData
, irregFunData
,
multiFunData
# Univariate object <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) integrate(object) # Univariate (irregular) irregObject <-irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) integrate(irregObject) # fullDom = FALSE integrate(irregObject, fullDom = TRUE) # Multivariate multiObject <- multiFunData(object, funData(argvals = 1:3, X = rbind(3:5, 6:8))) integrate(multiObject)
# Univariate object <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) integrate(object) # Univariate (irregular) irregObject <-irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) integrate(irregObject) # fullDom = FALSE integrate(irregObject, fullDom = TRUE) # Multivariate multiObject <- multiFunData(object, funData(argvals = 1:3, X = rbind(3:5, 6:8))) integrate(multiObject)
The irregFunData
class represents functional data that is sampled
irregularly on one-dimensional domains. The two slots represent the
observation points (x-values) and the observed function values (y-values).
irregFunData(argvals, X) ## S4 method for signature 'list,list' irregFunData(argvals, X) ## S4 method for signature 'irregFunData' show(object) ## S4 method for signature 'irregFunData' names(x) ## S4 replacement method for signature 'irregFunData' names(x) <- value ## S4 method for signature 'irregFunData' str(object, ...) ## S4 method for signature 'irregFunData' summary(object, ...)
irregFunData(argvals, X) ## S4 method for signature 'list,list' irregFunData(argvals, X) ## S4 method for signature 'irregFunData' show(object) ## S4 method for signature 'irregFunData' names(x) ## S4 replacement method for signature 'irregFunData' names(x) <- value ## S4 method for signature 'irregFunData' str(object, ...) ## S4 method for signature 'irregFunData' summary(object, ...)
argvals |
A list of numerics, corresponding to the observation points for each realization |
X |
A list of numerics, corresponding to the observed functions |
object |
An |
x |
The |
value |
The names to be given to the |
... |
Other parameters passed to |
Irregular functional data are realizations of a random process
where each realization
of
is given on an individual grid
of observation points. As for the
funData
class, each object of the irregFunData
class has two slots; the argvals
slot represents the observation
points and the X
slot represents the observed data. In contrast to the
regularly sampled data, both slots are defined as lists of vectors, where
each entry corresponds to one observed function:
argvals[[i]]
contains the vector of observation points for
the i-th function,
X[[i]]
contains the corresponding observed
data .
Generic functions for the irregFunData
class include a print method,
plotting and basic
arithmetics. Further methods for irregFunData
:
dimSupp
, nObs
: Informations about the support
dimensions and the number of observations,
getArgvals
,
extractObs
: Getting/setting slot values (instead of accessing
them directly via irregObject@argvals, irregObject@X
) and extracting
single observations or data on a subset of the domain,
integrate
, norm
: Integrate all observations over
their domain or calculating the norm.
An irregFunData
object can be coerced to a funData
object using
as.funData(irregObject)
. The regular functional data object is defined
on the union of all observation grids of the irregular object. The value of
the new object is marked as missing (NA
) for observation points that
are in the union, but not in the original observation grid.
irregFunData(argvals = list, X = list)
: Constructor for irregular functional data
objects.
show(irregFunData)
: Print basic information about the irregFunData
object
in the console. The default console output for irregFunData
objects.
names(irregFunData)
: Get the names of the irregFunData
object.
names(irregFunData) <- value
: Set the names of the irregFunData
object.
str(irregFunData)
: A str
method for irregFunData
objects, giving a compact overview of the structure.
summary(irregFunData)
: A summary
method for irregFunData
objects.
irregFunData()
: Constructor for irregular functional data objects
argvals
A list of numerics, representing the observation grid
for each realization
of
.
X
A list of numerics, representing the values of each observation
of
on the corresponding observation points
.
Currently, the class is implemented only for functional
data on one-dimensional domains .
# Construct an irregular functional data object i1 <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) # Display in the console i1 # Summarize summary(i1) # A more realistic object argvals <- seq(0,2*pi, 0.01) ind <- replicate(11, sort(sample(1:length(argvals), sample(5:10,1)))) # sample observation points argvalsIrreg <- lapply(ind, function(i){argvals[i]}) i2 <- irregFunData(argvals = argvalsIrreg, X = mapply(function(x, a){a * sin(x)}, x = argvalsIrreg, a = seq(0.75, 1.25, by = 0.05))) # Display/summary gives basic information i2 summary(i2) # Use the plot function to get an impression of the data plot(i2)
# Construct an irregular functional data object i1 <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) # Display in the console i1 # Summarize summary(i1) # A more realistic object argvals <- seq(0,2*pi, 0.01) ind <- replicate(11, sort(sample(1:length(argvals), sample(5:10,1)))) # sample observation points argvalsIrreg <- lapply(ind, function(i){argvals[i]}) i2 <- irregFunData(argvals = argvalsIrreg, X = mapply(function(x, a){a * sin(x)}, x = argvalsIrreg, a = seq(0.75, 1.25, by = 0.05))) # Display/summary gives basic information i2 summary(i2) # Use the plot function to get an impression of the data plot(i2)
These functions allow to apply mathematical operations (such as or
to functional data objects based on
Math
. The operations are made pointwise for each
observation.
## S4 method for signature 'funData' Math(x) ## S4 method for signature 'multiFunData' Math(x) ## S4 method for signature 'irregFunData' Math(x)
## S4 method for signature 'funData' Math(x) ## S4 method for signature 'multiFunData' Math(x) ## S4 method for signature 'irregFunData' Math(x)
x |
An object of class |
An object of the same functional data class as x
.
funData
, irregFunData
,
multiFunData
, Math
oldpar <- par(no.readonly = TRUE) par(mfrow = c(1,2)) # simulate a funData object on 0..1 with 10 observations argvals <- seq(0, 1, 0.01) f <- simFunData(argvals = argvals, N = 10, M = 5, eFunType = "Fourier", eValType = "linear")$simData ### FunData plot(f, main = "Original data") plot(abs(f), main = "Absolute values") ### Irregular # create an irrgFunData object by sparsifying f i <- as.irregFunData(sparsify(f, minObs = 5, maxObs = 10)) plot(i, main = "Sparse data") plot(cumsum(i), main = "'cumsum' of sparse data") ### Multivariate m <- multiFunData(f, -1*f) plot(m, main = "Multivariate Data") plot(exp(m), main = "Exponential") par(oldpar)
oldpar <- par(no.readonly = TRUE) par(mfrow = c(1,2)) # simulate a funData object on 0..1 with 10 observations argvals <- seq(0, 1, 0.01) f <- simFunData(argvals = argvals, N = 10, M = 5, eFunType = "Fourier", eValType = "linear")$simData ### FunData plot(f, main = "Original data") plot(abs(f), main = "Absolute values") ### Irregular # create an irrgFunData object by sparsifying f i <- as.irregFunData(sparsify(f, minObs = 5, maxObs = 10)) plot(i, main = "Sparse data") plot(cumsum(i), main = "'cumsum' of sparse data") ### Multivariate m <- multiFunData(f, -1*f) plot(m, main = "Multivariate Data") plot(exp(m), main = "Exponential") par(oldpar)
This function calculates the pointwise mean function for objects of class
funData
, irregFunData
or multiFunData
.
meanFunction(object, na.rm = FALSE)
meanFunction(object, na.rm = FALSE)
object |
An object of class |
na.rm |
Logical. If |
An object of the same class as object
with one observation
that corresponds to the pointwise mean function of the functions in
object
.
If object
is of class irregFunData
, the option na.rm =
TRUE
is not implemented and throws an error. If na.rm = FALSE
, the
functions must be observed on the same domain.
funData
, irregFunData
,
multiFunData
, Arith.funData
### Univariate (one-dimensional support) x <- seq(0, 2*pi, 0.01) f1 <- funData(x, outer(seq(0.75, 1.25, 0.05), sin(x))) plot(f1) plot(meanFunction(f1), col = 1, lwd = 2, add = TRUE) ### Univariate (two-dimensional support) f2 <- funData(list(1:5, 1:3), array(rep(1:5,each = 11, times = 3), dim = c(11,5,3))) all.equal(f2[1], meanFunction(f2)) # f2 has 11 identical observations ### Multivariate m1 <- multiFunData(f1,f2) all.equal(m1[6], meanFunction(m1)) # observation 6 equals the pointwise mean ### Irregular i1 <- irregFunData(argvals = list(1:3,1:3,1:3), X = list(1:3,2:4,3:5)) all.equal(meanFunction(i1), i1[2]) # don't run: functions are not defined on the same domain ## Not run: meanFunction(irregFunData(argvals = list(1:3,1:5), X = list(1:3,1:5)))
### Univariate (one-dimensional support) x <- seq(0, 2*pi, 0.01) f1 <- funData(x, outer(seq(0.75, 1.25, 0.05), sin(x))) plot(f1) plot(meanFunction(f1), col = 1, lwd = 2, add = TRUE) ### Univariate (two-dimensional support) f2 <- funData(list(1:5, 1:3), array(rep(1:5,each = 11, times = 3), dim = c(11,5,3))) all.equal(f2[1], meanFunction(f2)) # f2 has 11 identical observations ### Multivariate m1 <- multiFunData(f1,f2) all.equal(m1[6], meanFunction(m1)) # observation 6 equals the pointwise mean ### Irregular i1 <- irregFunData(argvals = list(1:3,1:3,1:3), X = list(1:3,2:4,3:5)) all.equal(meanFunction(i1), i1[2]) # don't run: functions are not defined on the same domain ## Not run: meanFunction(irregFunData(argvals = list(1:3,1:5), X = list(1:3,1:5)))
The multiFunData
class represents multivariate functional data on
(potentially) different domains, i.e. a multivariate functional data object
is a vector of (univariate) functional data objects, just as a vector in
is a vector of
scalars. In this implementation, a
multiFunData
object is represented as a list of univariate
funData
objects, see Details.
multiFunData(...) ## S4 method for signature 'ANY' multiFunData(...) ## S4 method for signature 'multiFunData' names(x) ## S4 replacement method for signature 'multiFunData' names(x) <- value ## S4 method for signature 'multiFunData' str(object, ...) ## S4 method for signature 'multiFunData' summary(object, ...)
multiFunData(...) ## S4 method for signature 'ANY' multiFunData(...) ## S4 method for signature 'multiFunData' names(x) ## S4 replacement method for signature 'multiFunData' names(x) <- value ## S4 method for signature 'multiFunData' str(object, ...) ## S4 method for signature 'multiFunData' summary(object, ...)
... |
A list of funData objects or several funData objects passed as one argument, each. See Details. |
x |
The |
value |
The names to be given to the |
object |
A |
A multiFunData
object is represented as a list of univariate
funData
objects, each having a argvals
and X
slot,
representing the x-values and the observed y-values (see the
funData
class). When constructing a multiFunData
object,
the elements can be supplied as a list of funData
objects or can be
passed directly as arguments to the constructor function.
Most functions implemented for the funData
class are also
implemented for multiFunData
objects. In most cases, they simply apply
the corresponding univariate method to each element of the multivariate
object and return it as a vector (if the result of the univariate function is
scalar, such as dimSupp
) or as a multiFunData
object (if
the result of the univariate function is a funData
object, such as
extractObs
).
The norm of a multivariate functional data is defined as
A funData
object can be coerced to a multiFunData
object with
one element using as.multiFunData(funDataObject).
multiFunData(ANY)
: Constructor for multivariate functional data
objects.
names(multiFunData)
: Get the names of the multiFunData
object.
names(multiFunData) <- value
: Set the names of the multiFunData
object.
str(multiFunData)
: A str
method for multiFunData
objects, giving a compact overview of the structure.
summary(multiFunData)
: A summary
method for multiFunData
objects.
multiFunData()
: Constructor for multivariate functional data objects
### Creating a multifunData object with 2 observations on the same domain # Univariate elements x <- 1:5 f1 <- funData(x, rbind(x, x+1)) f2 <- funData(x,rbind(x^2, sin(x))) # Basic m1 <- new("multiFunData", list(f1,f2)) # Using the constructor, passing the elements as list m2 <- multiFunData(list(f1,f2)) # Using the constructor, passing the elements directly m3 <- multiFunData(f1,f2) # Test if all the same all.equal(m1,m2) all.equal(m1,m3) # Display multiFunData object in the console m3 # Summarize summary(m3) ### Creating a multifunData object with 2 observations on different domains (both 1D) # A new element y <- 1:3 g1 <- funData(y, rbind(3*y, y+4)) # Create the multiFunData object m4 <- multiFunData(f1,g1) # Display multiFunData object in the console m4 ### Creating a multifunData object with 2 observations on different domains (1D and 2D) # A new element y <- 1:3; z <- 1:4 g2 <- funData(list(y,z), array(rnorm(24), dim = c(2,3,4))) # Create the multiFunData object m5 <- multiFunData(f1,g2) # Display multiFunData object in the console m5 ### A more realistic object # element 1 x <- seq(0,2*pi, 0.01) f1 <- funData(x, outer(seq(0.75, 1.25, length.out = 6), sin(x))) # element 2 y <- seq(-1,1, 0.01); z <- seq(-0.5, 0.5, 0.01) X2 <- array(NA, c(6, length(y), length(z))) for(i in 1:6) X2[i,,] <- outer(y, z, function(x,y){sin(i*pi*y)*cos(i*pi*z)}) f2 <- funData(list(y,z), X2) # MultiFunData Object m6 <- multiFunData(f1,f2) # Display multiFunData object in the console for basic information m6 # Summarize summary(m6) # Use the plot function to get an impression of the data ## Not run: plot(m6) # m6 has 2D element, must specify one observation for plotting plot(m6, obs = 1, main = c("1st element (obs 1)", "2nd element (obs 1)")) plot(m6, obs = 6, main = c("1st element (obs 6)", "2nd element (obs 6)"))
### Creating a multifunData object with 2 observations on the same domain # Univariate elements x <- 1:5 f1 <- funData(x, rbind(x, x+1)) f2 <- funData(x,rbind(x^2, sin(x))) # Basic m1 <- new("multiFunData", list(f1,f2)) # Using the constructor, passing the elements as list m2 <- multiFunData(list(f1,f2)) # Using the constructor, passing the elements directly m3 <- multiFunData(f1,f2) # Test if all the same all.equal(m1,m2) all.equal(m1,m3) # Display multiFunData object in the console m3 # Summarize summary(m3) ### Creating a multifunData object with 2 observations on different domains (both 1D) # A new element y <- 1:3 g1 <- funData(y, rbind(3*y, y+4)) # Create the multiFunData object m4 <- multiFunData(f1,g1) # Display multiFunData object in the console m4 ### Creating a multifunData object with 2 observations on different domains (1D and 2D) # A new element y <- 1:3; z <- 1:4 g2 <- funData(list(y,z), array(rnorm(24), dim = c(2,3,4))) # Create the multiFunData object m5 <- multiFunData(f1,g2) # Display multiFunData object in the console m5 ### A more realistic object # element 1 x <- seq(0,2*pi, 0.01) f1 <- funData(x, outer(seq(0.75, 1.25, length.out = 6), sin(x))) # element 2 y <- seq(-1,1, 0.01); z <- seq(-0.5, 0.5, 0.01) X2 <- array(NA, c(6, length(y), length(z))) for(i in 1:6) X2[i,,] <- outer(y, z, function(x,y){sin(i*pi*y)*cos(i*pi*z)}) f2 <- funData(list(y,z), X2) # MultiFunData Object m6 <- multiFunData(f1,f2) # Display multiFunData object in the console for basic information m6 # Summarize summary(m6) # Use the plot function to get an impression of the data ## Not run: plot(m6) # m6 has 2D element, must specify one observation for plotting plot(m6, obs = 1, main = c("1st element (obs 1)", "2nd element (obs 1)")) plot(m6, obs = 6, main = c("1st element (obs 6)", "2nd element (obs 6)"))
This functions returns the number of observations in a funData
, irregFunData
or multiFunData
object.
nObs(object)
nObs(object)
object |
An object of class |
The number of observations in object
.
funData
, irregFunData
, multiFunData
# Univariate object <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) nObs(object) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) nObs(irregObject) # Multivariate multiObject <- multiFunData(object, funData(argvals = 1:3, X = rbind(3:5, 6:8))) nObs(multiObject)
# Univariate object <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) nObs(object) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) nObs(irregObject) # Multivariate multiObject <- multiFunData(object, funData(argvals = 1:3, X = rbind(3:5, 6:8))) nObs(multiObject)
This functions returns the number of observation points in an object of class
funData
, multiFunData
or irregFunData
.
nObsPoints(object)
nObsPoints(object)
object |
An object of class |
Depending on the class of object
, the function returns different
values:
If object
is of class funData
, the
function returns a vector of length dimSupp(object)
, giving the number
of observations in each dimension.
If object
is of class
multiFunData
, the function returns a list of the same length as
object
, where the j
-th entry is a vector, corresponding to the
observations point of object[[j]]
.
If object
is of class
irregFunData
, the function returns an array of length
nObs(object)
, where the j
-th entry corresponds to the number of
observations in the j
-th observed function.
The number of observation points in object
. See Details.
Do not confound with nObs
, which returns the
number of observations (i.e. the number of observed functions) in an object
of a functional data class.
# Univariate (one-dimensional) object1 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) nObsPoints(object1) # Univariate (two-dimensional) object2 <- funData(argvals = list(1:5, 1:6), X = array(1:60, dim = c(2, 5, 6))) nObsPoints(object2) # Multivariate multiObject <- multiFunData(object1, object2) nObsPoints(multiObject) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) nObsPoints(irregObject)
# Univariate (one-dimensional) object1 <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) nObsPoints(object1) # Univariate (two-dimensional) object2 <- funData(argvals = list(1:5, 1:6), X = array(1:60, dim = c(2, 5, 6))) nObsPoints(object2) # Multivariate multiObject <- multiFunData(object1, object2) nObsPoints(multiObject) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) nObsPoints(irregObject)
This function calculates the norm for each observation of a funData
,
irregFunData
or multiFunData
object.
object |
An object of class |
... |
Further parameters (see Details). |
For funData
objects, the standard norm is calculated:
For irregFunData
objects, each observed function is
integrated only on the observed grid points (unless fullDom = TRUE
).
The (weighted) norm of a multivariate functional data object is defined as
Further parameters passed to this function may include:
squared
: Logical. If TRUE
(default), the function calculates
the squared norm, otherwise the result is not squared.
obs
: A
numeric vector, giving the indices of the observations, for which the norm is
to be calculated. Defaults to all observations.
method
: A
character string, giving the integration method to be used. See
integrate
for details.
weight
: An optional vector
of weights for the scalar product; particularly useful for multivariate
functional data, where each entry can be weighted in the scalar product /
norm. Defaults to 1
for each element.
fullDom
: Logical.
If object
is of class irregFunData
and
fullDom = TRUE
, all functions are extrapolated to the same domain.
Defaults to FALSE
. See integrate
for details.
A numeric vector representing the norm of each observation.
The function is currently implemented only for functional data with one- and two-dimensional domains.
funData
, irregFunData
,
multiFunData
, integrate
# Univariate object <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) norm(object) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) norm(irregObject) # no extrapolation norm(irregObject, fullDom = TRUE) # extrapolation (of second function) # Multivariate multiObject <- multiFunData(object, funData(argvals = 1:3, X = rbind(3:5, 6:8))) norm(multiObject) norm(multiObject, weight = c(2,1)) # with weight vector, giving more weight to the first element
# Univariate object <- funData(argvals = 1:5, X = rbind(1:5, 6:10)) norm(object) # Univariate (irregular) irregObject <- irregFunData(argvals = list(1:5, 2:4), X = list(2:6, 3:5)) norm(irregObject) # no extrapolation norm(irregObject, fullDom = TRUE) # extrapolation (of second function) # Multivariate multiObject <- multiFunData(object, funData(argvals = 1:3, X = rbind(3:5, 6:8))) norm(multiObject) norm(multiObject, weight = c(2,1)) # with weight vector, giving more weight to the first element
This function plots observations of univariate functional data on their domain.
## S3 method for class 'funData' plot( x, y, obs = seq_len(nObs(x)), type = "l", lty = 1, lwd = 1, col = NULL, xlab = "argvals", ylab = "", legend = TRUE, plotNA = FALSE, add = FALSE, ... ) ## S4 method for signature 'funData,missing' plot(x, y, ...)
## S3 method for class 'funData' plot( x, y, obs = seq_len(nObs(x)), type = "l", lty = 1, lwd = 1, col = NULL, xlab = "argvals", ylab = "", legend = TRUE, plotNA = FALSE, add = FALSE, ... ) ## S4 method for signature 'funData,missing' plot(x, y, ...)
x |
An object of class |
y |
Missing. |
obs |
A vector of numerics giving the observations to plot. Defaults to
all observations in |
type |
The type of plot. Defaults to |
lty |
The line type. Defaults to |
lwd |
The line width. Defaults to |
col |
The color of the functions. If not supplied ( |
xlab , ylab
|
The titles for x- and y-axis. Defaults to |
legend |
Logical. If |
plotNA |
Logical. If |
add |
Logical. If |
... |
Additional arguments to |
If some observations contain missing values (coded via NA
), the
functions can be interpolated using the option plotNA = TRUE
. This
option relies on the na.approx
function in package
zoo
and is currently implemented for one-dimensional
functions only in the function approxNA
.
The function is currently implemented only for functional data with one- and two-dimensional domains.
funData
, matplot
,
image.plot
, image
oldpar <- par(no.readonly = TRUE) # One-dimensional argvals <- seq(0,2*pi,0.01) object <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) plot(object, main = "One-dimensional functional data") # Two-dimensional X <- array(0, dim = c(2, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) X[2,,] <- outer(argvals, argvals, function(x,y){sin(2*x*pi) * cos(2*y*pi)}) object2D <- funData(list(argvals, argvals), X) plot(object2D, main = "Two-dimensional functional data (obs 1)", obs = 1) plot(object2D, main = "Two-dimensional functional data (obs 2)", obs = 2) ## Not run: plot(object2D, main = "Two-dimensional functional data") # must specify obs! ### More examples ### par(mfrow = c(1,1)) # using plotNA if(requireNamespace("zoo", quietly = TRUE)) { objectMissing <- funData(1:5, rbind(c(1, NA, 5, 4, 3), c(10, 9, NA, NA, 6))) par(mfrow = c(1,2)) plot(objectMissing, type = "b", pch = 20, main = "plotNA = FALSE") # the default plot(objectMissing, type = "b", pch = 20, plotNA = TRUE, main = "plotNA = TRUE") # requires zoo } # Changing colors plot(object, main = "1D functional data in grey", col = "grey") plot(object, main = "1D functional data in heat.colors", col = heat.colors(nObs(object))) plot(object2D, main = "2D functional data in topo.colors", obs = 1, col = topo.colors(64)) par(oldpar)
oldpar <- par(no.readonly = TRUE) # One-dimensional argvals <- seq(0,2*pi,0.01) object <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) plot(object, main = "One-dimensional functional data") # Two-dimensional X <- array(0, dim = c(2, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) X[2,,] <- outer(argvals, argvals, function(x,y){sin(2*x*pi) * cos(2*y*pi)}) object2D <- funData(list(argvals, argvals), X) plot(object2D, main = "Two-dimensional functional data (obs 1)", obs = 1) plot(object2D, main = "Two-dimensional functional data (obs 2)", obs = 2) ## Not run: plot(object2D, main = "Two-dimensional functional data") # must specify obs! ### More examples ### par(mfrow = c(1,1)) # using plotNA if(requireNamespace("zoo", quietly = TRUE)) { objectMissing <- funData(1:5, rbind(c(1, NA, 5, 4, 3), c(10, 9, NA, NA, 6))) par(mfrow = c(1,2)) plot(objectMissing, type = "b", pch = 20, main = "plotNA = FALSE") # the default plot(objectMissing, type = "b", pch = 20, plotNA = TRUE, main = "plotNA = TRUE") # requires zoo } # Changing colors plot(object, main = "1D functional data in grey", col = "grey") plot(object, main = "1D functional data in heat.colors", col = heat.colors(nObs(object))) plot(object2D, main = "2D functional data in topo.colors", obs = 1, col = topo.colors(64)) par(oldpar)
This function plots observations of irregular functional data on their domain.
## S3 method for class 'irregFunData' plot( x, y, obs = seq_len(nObs(x)), type = "b", pch = 20, col = grDevices::rainbow(length(obs)), xlab = "argvals", ylab = "", xlim = range(x@argvals[obs]), ylim = range(x@X[obs]), log = "", add = FALSE, ... ) ## S4 method for signature 'irregFunData,missing' plot(x, y, ...)
## S3 method for class 'irregFunData' plot( x, y, obs = seq_len(nObs(x)), type = "b", pch = 20, col = grDevices::rainbow(length(obs)), xlab = "argvals", ylab = "", xlim = range(x@argvals[obs]), ylim = range(x@X[obs]), log = "", add = FALSE, ... ) ## S4 method for signature 'irregFunData,missing' plot(x, y, ...)
x |
An object of class |
y |
Missing. |
obs |
A vector of numerics giving the observations to plot. Defaults to all observations in
|
type |
The type of plot. Defaults to |
pch |
The point type. Defaults to |
col |
The color of the functions. Defaults to the |
xlab , ylab
|
The titles for x- and y-axis. Defaults to |
xlim , ylim
|
The limits for x- and y-axis. Defaults to the total range of the data that is to
plot. See |
log |
A character string, specifying the axis that is to be logarithmic. Can be |
add |
Logical. If |
... |
Additional arguments to |
plot.funData
, irregFunData
,
plot
oldpar <- par(no.readonly = TRUE) # Generate data argvals <- seq(0,2*pi,0.01) ind <- replicate(5, sort(sample(1:length(argvals), sample(5:10,1)))) object <- irregFunData(argvals = lapply(ind, function(i){argvals[i]}), X = lapply(ind, function(i){sample(1:10,1) / 10 * argvals[i]^2})) plot(object, main = "Irregular functional data") par(oldpar)
oldpar <- par(no.readonly = TRUE) # Generate data argvals <- seq(0,2*pi,0.01) ind <- replicate(5, sort(sample(1:length(argvals), sample(5:10,1)))) object <- irregFunData(argvals = lapply(ind, function(i){argvals[i]}), X = lapply(ind, function(i){sample(1:10,1) / 10 * argvals[i]^2})) plot(object, main = "Irregular functional data") par(oldpar)
This function plots observations of multivariate functional data on their domain. The graphic
device is split in a number of subplots (specified by dim
) via mfrow
(par
) and the univariate elements are plotted using plot
.
## S3 method for class 'multiFunData' plot( x, y, obs = seq_len(nObs(x)), dim = seq_len(length(x)), par.plot = NULL, main = names(x), xlab = "argvals", ylab = "", log = "", ylim = NULL, ... ) ## S4 method for signature 'multiFunData,missing' plot(x, y, ...)
## S3 method for class 'multiFunData' plot( x, y, obs = seq_len(nObs(x)), dim = seq_len(length(x)), par.plot = NULL, main = names(x), xlab = "argvals", ylab = "", log = "", ylim = NULL, ... ) ## S4 method for signature 'multiFunData,missing' plot(x, y, ...)
x |
An object of class |
y |
Missing. |
obs |
A vector of numerics giving the observations to plot. Defaults to
all observations in |
dim |
The dimensions to plot. Defaults to |
par.plot |
Graphic parameters to be passed to the plotting regions. The
option |
main |
A string vector, giving the title of the plot. Can have the same
length as |
xlab , ylab
|
The titles for x- and y-axis. Defaults to |
log |
A character string, specifying the axis that is to be logarithmic.
Can be |
ylim |
Specifies the limits of the y-Axis. Can be either |
... |
Additional arguments to |
The function is currently implemented only for functional data with one- and two-dimensional domains.
funData
, multiFunData
,
plot.funData
oldpar <- par(no.readonly = TRUE) argvals <- seq(0, 2*pi, 0.1) # One-dimensional elements f1 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) f2 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), cos(argvals))) m1 <- multiFunData(f1, f2) plot(m1, main = c("1st element", "2nd element")) # different titles plot(m1, main = "Multivariate Functional Data") # one title for all # Mixed-dimensional elements X <- array(0, dim = c(11, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) g <- funData(list(argvals, argvals), X) m2 <- multiFunData(f1, g) # different titles and labels plot(m2, main = c("1st element", "2nd element"), obs = 1, xlab = c("xlab1", "xlab2"), ylab = "one ylab for all") # one title for all plot(m2, main = "Multivariate Functional Data", obs = 1) ## Not run: plot(m2, main = c("1st element", "2nd element")) # must specify obs! par(oldpar)
oldpar <- par(no.readonly = TRUE) argvals <- seq(0, 2*pi, 0.1) # One-dimensional elements f1 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), sin(argvals))) f2 <- funData(argvals, outer(seq(0.75, 1.25, length.out = 11), cos(argvals))) m1 <- multiFunData(f1, f2) plot(m1, main = c("1st element", "2nd element")) # different titles plot(m1, main = "Multivariate Functional Data") # one title for all # Mixed-dimensional elements X <- array(0, dim = c(11, length(argvals), length(argvals))) X[1,,] <- outer(argvals, argvals, function(x,y){sin((x-pi)^2 + (y-pi)^2)}) g <- funData(list(argvals, argvals), X) m2 <- multiFunData(f1, g) # different titles and labels plot(m2, main = c("1st element", "2nd element"), obs = 1, xlab = c("xlab1", "xlab2"), ylab = "one ylab for all") # one title for all plot(m2, main = "Multivariate Functional Data", obs = 1) ## Not run: plot(m2, main = c("1st element", "2nd element")) # must specify obs! par(oldpar)
This function calculates the scalar product between two objects of the class
funData
, irregFunData
and
multiFunData
. For univariate functions on a
domain
, the scalar product is defined as
and
for multivariate functions on domains
, it is defined as
As seen in the formula, the objects
must be defined on the same domain. The scalar product is calculated pairwise
for all observations, thus the objects must also have the same number of
observations or one object may have only one observation (for which the
scalar product is calculated with all observations of the other object)).
Objects of the classes funData
and irregFunData
can be combined, see integrate
for details.
scalarProduct(object1, object2, ...)
scalarProduct(object1, object2, ...)
object1 , object2
|
Two objects of class |
... |
Additional parameters passed to |
For multiFunData
one can pass an optional vector
weight
for calculating a weighted scalar product. This vector must
have the same number of elements as the multiFunData
objects
and have to be non-negative with at least one weight that is different from
0. Defaults to 1
for each element. See also norm
.
A vector of length nObs(object1)
(or nObs(object2)
, if
object1
has only one observation), containing the pairwise scalar
product for each observation.
# create two funData objectw with 5 observations on [0,1] f <- simFunData(N = 5, M = 7, eValType = "linear", eFunType = "Fourier", argvals = seq(0,1,0.01))$simData g <- simFunData(N = 5, M = 4, eValType = "linear", eFunType = "Poly", argvals = seq(0,1,0.01))$simData # calculate the scalar product scalarProduct(f,g) # the scalar product of an object with itself equals the squared norm all.equal(scalarProduct(f,f), norm(f, squared = TRUE)) # This works of course also for multiFunData objects... m <- multiFunData(f,g) all.equal(scalarProduct(m,m), norm(m, squared = TRUE)) # ...and for irregFunData objects i <- as.irregFunData(sparsify(f, minObs = 5, maxObs = 10)) all.equal(scalarProduct(i,i), norm(i, squared = TRUE)) # Scalar product between funData and irregFunData objects scalarProduct(i,f) # Weighted scalar product for multiFunData objects scalarProduct(m,m, weight = c(1,2))
# create two funData objectw with 5 observations on [0,1] f <- simFunData(N = 5, M = 7, eValType = "linear", eFunType = "Fourier", argvals = seq(0,1,0.01))$simData g <- simFunData(N = 5, M = 4, eValType = "linear", eFunType = "Poly", argvals = seq(0,1,0.01))$simData # calculate the scalar product scalarProduct(f,g) # the scalar product of an object with itself equals the squared norm all.equal(scalarProduct(f,f), norm(f, squared = TRUE)) # This works of course also for multiFunData objects... m <- multiFunData(f,g) all.equal(scalarProduct(m,m), norm(m, squared = TRUE)) # ...and for irregFunData objects i <- as.irregFunData(sparsify(f, minObs = 5, maxObs = 10)) all.equal(scalarProduct(i,i), norm(i, squared = TRUE)) # Scalar product between funData and irregFunData objects scalarProduct(i,f) # Weighted scalar product for multiFunData objects scalarProduct(m,m, weight = c(1,2))
This functions simulates (univariate) functional data based on a truncated
Karhunen-Loeve representation:
on one- or
higher-dimensional domains. The eigenfunctions (basis functions) are generated
using
eFun
, the scores are simulated independently from a normal
distribution with zero mean and decreasing variance based on the
eVal
function. For
higher-dimensional domains, the eigenfunctions are constructed as tensors of marginal orthonormal
function systems.
simFunData(argvals, M, eFunType, ignoreDeg = NULL, eValType, N)
simFunData(argvals, M, eFunType, ignoreDeg = NULL, eValType, N)
argvals |
A numeric vector, containing the observation points (a fine grid on a real interval) of the functional data that is to be simulated or a list of the marginal observation points. |
M |
An integer, giving the number of univariate basis functions to use. For higher-dimensional data, |
eFunType |
A character string specifying the type of univariate orthonormal basis functions
to use. For data on higher-dimensional domains, |
ignoreDeg |
A vector of integers, specifying the degrees to ignore when generating the
univariate orthonormal bases. Defaults to |
eValType |
A character string, specifying the type of eigenvalues/variances used for the
generation of the simulated functions based on the truncated Karhunen-Loeve representation. See
|
N |
An integer, specifying the number of multivariate functions to be generated. |
simData |
A |
trueFuns |
A |
trueVals |
A vector of numerics, representing the true eigenvalues used for simulating the data. |
funData
, eFun
, eVal
,
addError
, sparsify
oldPar <- par(no.readonly = TRUE) # Use Legendre polynomials as eigenfunctions and a linear eigenvalue decrease test <- simFunData(seq(0,1,0.01), M = 10, eFunType = "Poly", eValType = "linear", N = 10) plot(test$trueFuns, main = "True Eigenfunctions") plot(test$simData, main = "Simulated Data") # The use of ignoreDeg for eFunType = "PolyHigh" test <- simFunData(seq(0,1,0.01), M = 4, eFunType = "Poly", eValType = "linear", N = 10) test_noConst <- simFunData(seq(0,1,0.01), M = 4, eFunType = "PolyHigh", ignoreDeg = 1, eValType = "linear", N = 10) test_noLinear <- simFunData(seq(0,1,0.01), M = 4, eFunType = "PolyHigh", ignoreDeg = 2, eValType = "linear", N = 10) test_noBoth <- simFunData(seq(0,1,0.01), M = 4, eFunType = "PolyHigh", ignoreDeg = 1:2, eValType = "linear", N = 10) par(mfrow = c(2,2)) plot(test$trueFuns, main = "Standard polynomial basis (M = 4)") plot(test_noConst$trueFuns, main = "No constant basis function") plot(test_noLinear$trueFuns, main = "No linear basis function") plot(test_noBoth$trueFuns, main = "Neither linear nor constant basis function") # Higher-dimensional domains simImages <- simFunData(argvals = list(seq(0,1,0.01), seq(-pi/2, pi/2, 0.02)), M = c(5,4), eFunType = c("Wiener","Fourier"), eValType = "linear", N = 4) for(i in 1:4) plot(simImages$simData, obs = i, main = paste("Observation", i)) par(oldPar)
oldPar <- par(no.readonly = TRUE) # Use Legendre polynomials as eigenfunctions and a linear eigenvalue decrease test <- simFunData(seq(0,1,0.01), M = 10, eFunType = "Poly", eValType = "linear", N = 10) plot(test$trueFuns, main = "True Eigenfunctions") plot(test$simData, main = "Simulated Data") # The use of ignoreDeg for eFunType = "PolyHigh" test <- simFunData(seq(0,1,0.01), M = 4, eFunType = "Poly", eValType = "linear", N = 10) test_noConst <- simFunData(seq(0,1,0.01), M = 4, eFunType = "PolyHigh", ignoreDeg = 1, eValType = "linear", N = 10) test_noLinear <- simFunData(seq(0,1,0.01), M = 4, eFunType = "PolyHigh", ignoreDeg = 2, eValType = "linear", N = 10) test_noBoth <- simFunData(seq(0,1,0.01), M = 4, eFunType = "PolyHigh", ignoreDeg = 1:2, eValType = "linear", N = 10) par(mfrow = c(2,2)) plot(test$trueFuns, main = "Standard polynomial basis (M = 4)") plot(test_noConst$trueFuns, main = "No constant basis function") plot(test_noLinear$trueFuns, main = "No linear basis function") plot(test_noBoth$trueFuns, main = "Neither linear nor constant basis function") # Higher-dimensional domains simImages <- simFunData(argvals = list(seq(0,1,0.01), seq(-pi/2, pi/2, 0.02)), M = c(5,4), eFunType = c("Wiener","Fourier"), eValType = "linear", N = 4) for(i in 1:4) plot(simImages$simData, obs = i, main = paste("Observation", i)) par(oldPar)
This function provides a unified simulation structure for multivariate
functional data on one- or two-dimensional domains,
based on a truncated multivariate Karhunen-Loeve representation:
The multivariate eigenfunctions
(basis functions) are constructed from univariate orthonormal
bases. There are two different concepts for the construction, that can be
chosen by the parameter
type
: A split orthonormal basis (split
,
only one-dimensional domains) and weighted univariate orthonormal bases
(weighted
, one- and two-dimensional domains). The scores
in the Karhunen-Loeve representation are simulated
independently from a normal distribution with zero mean and decreasing
variance. See Details.
simMultiFunData(type, argvals, M, eFunType, ignoreDeg = NULL, eValType, N)
simMultiFunData(type, argvals, M, eFunType, ignoreDeg = NULL, eValType, N)
type |
A character string, specifying the construction method for the
multivariate eigenfunctions (either |
argvals |
A list, containing the observation points for each element of
the multivariate functional data that is to be simulated. The length of
|
M |
An integer ( |
eFunType |
A character string ( |
ignoreDeg |
A vector of integers ( |
eValType |
A character string, specifying the type of
eigenvalues/variances used for the simulation of the multivariate functions
based on the truncated Karhunen-Loeve representation. See
|
N |
An integer, specifying the number of multivariate functions to be generated. |
The parameter type
defines how the eigenfunction basis for the
multivariate Karhunen-Loeve representation is constructed:
type = "split"
: The basis functions of an underlying 'big' orthonormal
basis are split in M
parts, translated and possibly reflected. This
yields an orthonormal basis of multivariate functions with M
elements. This option is implemented only for one-dimensional domains.
type = "weighted":
The multivariate eigenfunction basis consists of
weighted univariate orthonormal bases. This yields an orthonormal basis of
multivariate functions with M
elements. For data on two-dimensional
domains (images), the univariate basis is constructed as a tensor product of
univariate bases in each direction (x- and y-direction).
Depending on type
, the other parameters have to be specified as
follows:
The parameters M
(integer), eFunType
(character string) and ignoreDeg
(integer
vector or NULL
) are passed to the function eFun
to
generate a univariate orthonormal basis on a 'big' interval. Subsequently,
the basis functions are split and translated, such that the -th part
of the split function is defined on the interval corresponding to
argvals[[j]]
. The elements of the multivariate basis functions are
given by these split parts of the original basis functions multiplied by a
random sign .
The parameters argvals, M,
eFunType
and ignoreDeg
are all lists of a similar structure. They are
passed element-wise to the function eFun
to generate
orthonormal basis functions for each element of the multivariate functional
data to be simulated. In case of bivariate elements (images), the
corresponding basis functions are constructed as tensor products of
orthonormal basis functions in each direction (x- and y-direction).
If the -th element of the simulated data should be defined on a
one-dimensional domain, then
argvals[[j]]
is a list,
containing one vector of observation points.
M[[j]]
is an
integer, specifying the number of basis functions to use for this entry.
eFunType[[j]]
is a character string, specifying the type of
orthonormal basis functions to use for this entry (see eFun
for
possible options).
ignoreDeg[[j]]
is a vector of integers,
specifying the degrees to ignore when constructing the orthonormal basis
functions. The default value is NULL
.
If the -th element of the simulated data should be defined on a
two-dimensional domain, then
argvals[[j]]
is a list,
containing two vectors of observation points, one for each direction
(observation points in x-direction and in y-direction).
M[[j]]
is a vector of two integers, giving the number of basis functions for each
direction (x- and y-direction).
eFunType[[j]]
is a vector of two
character strings, giving the type of orthonormal basis functions for each
direction (x- and y-direction, see eFun
for possible options).
The corresponding basis functions are constructed as tensor products of
orthonormal basis functions in each direction.
ignoreDeg[[j]]
is
a list, containing two integer vectors that specify the degrees to ignore
when constructing the orthonormal basis functions in each direction. The
default value is NULL
.
The total number of basis functions (i.e. the
product of M[[j]]
for all j
) must be equal!
simData |
A |
trueFuns |
A |
trueVals |
A vector of numerics, representing the eigenvalues used for simulating the data. |
C. Happ, S. Greven (2018): Multivariate Functional Principal Component Analysis for Data Observed on Different (Dimensional) Domains. Journal of the American Statistical Association, 113(522): 649-659.
multiFunData
, eFun
,
eVal
, simFunData
, addError
,
sparsify
.
oldPar <- par(no.readonly = TRUE) # split split <- simMultiFunData(type = "split", argvals = list(seq(0,1,0.01), seq(-0.5,0.5,0.02)), M = 5, eFunType = "Poly", eValType = "linear", N = 7) par(mfrow = c(1,2)) plot(split$trueFuns, main = "Split: True Eigenfunctions", ylim = c(-2,2)) plot(split$simData, main = "Split: Simulated Data") # weighted (one-dimensional domains) weighted1D <- simMultiFunData(type = "weighted", argvals = list(list(seq(0,1,0.01)), list(seq(-0.5,0.5,0.02))), M = c(5,5), eFunType = c("Poly", "Fourier"), eValType = "linear", N = 7) plot(weighted1D$trueFuns, main = "Weighted (1D): True Eigenfunctions", ylim = c(-2,2)) plot(weighted1D$simData, main = "Weighted (1D): Simulated Data") # weighted (one- and two-dimensional domains) weighted <- simMultiFunData(type = "weighted", argvals = list(list(seq(0,1,0.01), seq(0,10,0.1)), list(seq(-0.5,0.5,0.01))), M = list(c(5,4), 20), eFunType = list(c("Poly", "Fourier"), "Wiener"), eValType = "linear", N = 7) plot(weighted$trueFuns, main = "Weighted: True Eigenfunctions (m = 2)", obs = 2) plot(weighted$trueFuns, main = "Weighted: True Eigenfunctions (m = 15)", obs = 15) plot(weighted$simData, main = "Weighted: Simulated Data (1st observation)", obs = 1) plot(weighted$simData, main = "Weighted: Simulated Data (2nd observation)", obs = 2) par(oldPar)
oldPar <- par(no.readonly = TRUE) # split split <- simMultiFunData(type = "split", argvals = list(seq(0,1,0.01), seq(-0.5,0.5,0.02)), M = 5, eFunType = "Poly", eValType = "linear", N = 7) par(mfrow = c(1,2)) plot(split$trueFuns, main = "Split: True Eigenfunctions", ylim = c(-2,2)) plot(split$simData, main = "Split: Simulated Data") # weighted (one-dimensional domains) weighted1D <- simMultiFunData(type = "weighted", argvals = list(list(seq(0,1,0.01)), list(seq(-0.5,0.5,0.02))), M = c(5,5), eFunType = c("Poly", "Fourier"), eValType = "linear", N = 7) plot(weighted1D$trueFuns, main = "Weighted (1D): True Eigenfunctions", ylim = c(-2,2)) plot(weighted1D$simData, main = "Weighted (1D): Simulated Data") # weighted (one- and two-dimensional domains) weighted <- simMultiFunData(type = "weighted", argvals = list(list(seq(0,1,0.01), seq(0,10,0.1)), list(seq(-0.5,0.5,0.01))), M = list(c(5,4), 20), eFunType = list(c("Poly", "Fourier"), "Wiener"), eValType = "linear", N = 7) plot(weighted$trueFuns, main = "Weighted: True Eigenfunctions (m = 2)", obs = 2) plot(weighted$trueFuns, main = "Weighted: True Eigenfunctions (m = 15)", obs = 15) plot(weighted$simData, main = "Weighted: Simulated Data (1st observation)", obs = 1) plot(weighted$simData, main = "Weighted: Simulated Data (2nd observation)", obs = 2) par(oldPar)
This function generates an artificially sparsified version of a functional
data object of class funData
(univariate) or
multiFunData
(multivariate). The minimal and maximal number
of observation points for all observations can be supplied by the user.
sparsify(funDataObject, minObs, maxObs)
sparsify(funDataObject, minObs, maxObs)
funDataObject |
A functional data object of class
|
minObs , maxObs
|
The minimal/maximal number of observation points. Must be a scalar for
univariate functional data ( |
The technique for artificially sparsifying the data is as described in Yao et
al. (2005): For each element of an observed
(multivariate) functional data object
, a random number
of observation points is generated. The points
are sampled uniformly from the full grid
, resulting in
observations
An object of the same class as funDataObject
, which is a
sparse version of the original data.
This function is currently implemented for 1D data only.
Yao, F., H.-G. Mueller and J.-L. Wang (2005): Functional Data Analysis for Sparse Longitudinal Data. Journal of the American Statistical Association, 100 (470), 577–590.
funData
, multiFunData
,
simFunData
, simMultiFunData
,
addError
.
oldPar <- par(no.readonly = TRUE) par(mfrow = c(1,1)) set.seed(1) # univariate functional data full <- simFunData(argvals = seq(0,1, 0.01), M = 10, eFunType = "Fourier", eValType = "linear", N = 3)$simData sparse <- sparsify(full, minObs = 4, maxObs = 10) plot(full, main = "Sparsify") plot(sparse, type = "p", pch = 20, add = TRUE) legend("topright", c("Full", "Sparse"), lty = c(1, NA), pch = c(NA, 20)) # Multivariate full <- simMultiFunData(type = "split", argvals = list(seq(0,1, 0.01), seq(-.5,.5, 0.02)), M = 10, eFunType = "Fourier", eValType = "linear", N = 3)$simData sparse <- sparsify(full, minObs = c(4, 30), maxObs = c(10, 40)) par(mfrow = c(1,2)) plot(full[[1]], main = "Sparsify (multivariate)", sub = "minObs = 4, maxObs = 10") plot(sparse[[1]], type = "p", pch = 20, add = TRUE) plot(full[[2]], main = "Sparsify (multivariate)", sub = "minObs = 30, maxObs = 40") plot(sparse[[2]], type = "p", pch = 20, add = TRUE) legend("bottomright", c("Full", "Sparse"), lty = c(1, NA), pch = c(NA, 20)) par(oldPar)
oldPar <- par(no.readonly = TRUE) par(mfrow = c(1,1)) set.seed(1) # univariate functional data full <- simFunData(argvals = seq(0,1, 0.01), M = 10, eFunType = "Fourier", eValType = "linear", N = 3)$simData sparse <- sparsify(full, minObs = 4, maxObs = 10) plot(full, main = "Sparsify") plot(sparse, type = "p", pch = 20, add = TRUE) legend("topright", c("Full", "Sparse"), lty = c(1, NA), pch = c(NA, 20)) # Multivariate full <- simMultiFunData(type = "split", argvals = list(seq(0,1, 0.01), seq(-.5,.5, 0.02)), M = 10, eFunType = "Fourier", eValType = "linear", N = 3)$simData sparse <- sparsify(full, minObs = c(4, 30), maxObs = c(10, 40)) par(mfrow = c(1,2)) plot(full[[1]], main = "Sparsify (multivariate)", sub = "minObs = 4, maxObs = 10") plot(sparse[[1]], type = "p", pch = 20, add = TRUE) plot(full[[2]], main = "Sparsify (multivariate)", sub = "minObs = 30, maxObs = 40") plot(sparse[[2]], type = "p", pch = 20, add = TRUE) legend("bottomright", c("Full", "Sparse"), lty = c(1, NA), pch = c(NA, 20)) par(oldPar)
This function calculates tensor product functions for up to three objects of
class funData
defined on one-dimensional domains.
tensorProduct(...)
tensorProduct(...)
... |
Two or three objects of class |
An object of class as funData
that corresponds to the tensor
product of the input functions.
The function is only implemented for up to three functions on one-dimensional domains.
### Tensor product of two functional data objects x <- seq(0, 2*pi, 0.1) f1 <- funData(x, outer(seq(0.75, 1.25, 0.1), sin(x))) y <- seq(-pi, pi, 0.1) f2 <- funData(y, outer(seq(0.25, 0.75, 0.1), sin(y))) plot(f1, main = "f1") plot(f2, main = "f2") tP <- tensorProduct(f1, f2) dimSupp(tP) plot(tP, obs = 1) ### Tensor product of three functional data objects z <- seq(-1, 1, 0.05) f3 <- funData(z, outer(seq(0.75, 1.25, 0.1), z^2)) plot(f1, main = "f1") plot(f2, main = "f2") plot(f3, main = "f3") tP2 <- tensorProduct(f1, f2, f3) dimSupp(tP2)
### Tensor product of two functional data objects x <- seq(0, 2*pi, 0.1) f1 <- funData(x, outer(seq(0.75, 1.25, 0.1), sin(x))) y <- seq(-pi, pi, 0.1) f2 <- funData(y, outer(seq(0.25, 0.75, 0.1), sin(y))) plot(f1, main = "f1") plot(f2, main = "f2") tP <- tensorProduct(f1, f2) dimSupp(tP) plot(tP, obs = 1) ### Tensor product of three functional data objects z <- seq(-1, 1, 0.05) f3 <- funData(z, outer(seq(0.75, 1.25, 0.1), z^2)) plot(f1, main = "f1") plot(f2, main = "f2") plot(f3, main = "f3") tP2 <- tensorProduct(f1, f2, f3) dimSupp(tP2)