Skip to content

Commit

Permalink
updates to landmarkreg and smooth.basis.sparse
Browse files Browse the repository at this point in the history
  • Loading branch information
gileshooker committed Mar 21, 2023
1 parent 46a3713 commit f4286ba
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 7 deletions.
2 changes: 1 addition & 1 deletion R/landmarkreg.R
Expand Up @@ -103,7 +103,7 @@ landmarkreg <- function(unregfd, ximarks, x0marks, x0lim=NULL,

if (is.null(WfdPar)) {
Wnbasis <- length(x0marks) + 2
Ybasis <- create.bspline.basis(rangeval, Wnbasis)
Wbasis <- create.bspline.basis(rangeval, Wnbasis)
Wfd <- fd(matrix(0,Wnbasis,1), Wbasis)
WfdPar <- fdPar(Wfd, 2, 1e-10)
} else {
Expand Down
23 changes: 17 additions & 6 deletions R/smooth.basis.sparse.R
Expand Up @@ -72,14 +72,25 @@ smooth.basis.sparse <- function(argvals, y, fdParobj, fdnames=NULL, covariates=N
}
}
}
coefs = matrix(0, nrow = basisobj$nbasis, ncol = dim(data)[2])
for(i in 1:dim(data)[2]){
curve = data[,i]
curve.smooth = smooth.basis(time[!is.na(curve)],curve[!is.na(curve)],
if(length(dim(y)) == 2){
coefs = matrix(0, nrow = basisobj$nbasis, ncol = dim(y)[2])
for(i in 1:dim(y)[2]){
curve = y[,i]
curve.smooth = smooth.basis(time[!is.na(curve)],curve[!is.na(curve)],
basisobj, covariates, method)
coefs[,i] = curve.smooth$fd$coefs
coefs[,i] = curve.smooth$fd$coefs
}
} else if(length(dim(y) == 3){
coefs = array(0, c(basisobj$nbasis,dim(y)[2:3]))
for(i in 1:dim(y)[2]){
for(j in 1:dim(y)[3]){
curve = y[,i,j]
curve.smooth = smooth.basis(time[!is.na(curve)],curve[!is.na(curve)],
basisobj, covariates, method)
coefs[,i,j] = curve.smooth$fd$coefs
}
}
}
datafd = fd(coefs,basisobj, fdnames)

return(datafd)
}

0 comments on commit f4286ba

Please sign in to comment.