TABLE OF CONTENTS


fortranwrappers/fmakeSens2 [ Functions ]

NAME

    fmakeSens2 --- construct sensitivity matrix

FUNCTION

Construct the sensitivity matrix at the end of the procedure. This is a wrapper for the FORTRAN routine fmksens2 or fmksens2full. It only gest called with full=FALSE, because for full=TRUE the function fmkstderr uses a faster method.

SYNOPSIS

2208 fmakeSens2 <- function(m, Ji, datamat, datamatd, alphars, alpharsd, betahat, betadhat,
2209                 as, asd, frailtyoutput, dispersionoutput, K, Kd, full = FALSE)

INPUTS

    m              number of clusters
    Ji             cluster sizes
    datamat        data matrix generated by makedatamat for event 1
    datamatd       data matrix generated by makedatamat for event 2
    alphars            matrix of baseline hazard parameters for event 1
    alpharsd           matrix of baseline hazard parameters for event 2
    betahat            regression coefficient estimates for event 
    betadhat           regression coefficient estimates for event 2
    as                 matrix of discretization breakpoints for event 1
    asd                matrix of discretization breakpoints for event 2
    frailtyoutput  output from fupdatefrailties4
    dispersionoutput  output from one of the dispersion estimation routines
    K                  number of discretization intervals for event 1
    Kd                 number of discretization intervals for event 2
    full           boolean indicating whether full matrix should be computed.
                   If FALSE, only the sensitivity for betahat is returned. 

OUTPUTS

    S              Sensitivity matrix

SOURCE

2212 {
2213     # Extract intermediate values
2214     pi <- frailtyoutput$pqrs$pi; qi <- frailtyoutput$pqrs$qi;
2215     ri <- frailtyoutput$pqrs$ri; si <- frailtyoutput$pqrs$si;
2216     wij <- frailtyoutput$pqrs$wij;zij <- frailtyoutput$pqrs$zij;
2217     wi <- frailtyoutput$pqrs$wi
2218     sigma2hat <- dispersionoutput$sigma2hat;
2219     sigma2dhat <- dispersionoutput$sigma2dhat
2220     nu2hat <- dispersionoutput$nu2hat; nu2dhat <- dispersionoutput$nu2dhat
2221     thetahat <- dispersionoutput$thetahat
2222    
2223     ncovs1 <- length(betahat)
2224     ncovs2 <- length(betadhat)
2225     
2226     # Prepare data for submission to Fortran function fmksens2 or fmksens2full
2227     Z <- matrix(datamat[, -(1:8)], dim(datamat)[1], dim(datamat)[2] - 8)
2228     d1 <- dim(Z)[1]
2229     index1 <- datamat[, c("i", "j", "k", "r", "smin", "smax")]
2230     times1 <- datamat[, "time"]
2231     Zd <- matrix(datamatd[, -(1:8)], dim(datamatd)[1], dim(datamatd)[2] - 8)
2232     d2 <- dim(Zd)[1]
2233     index2 <- datamatd[, c("i", "j", "k", "r", "smin", "smax")]
2234     times2 <- datamatd[, "time"]
2235     nr = dim(alphars)[1]
2236     ns = dim(alphars)[2]
2237     nsd = dim(alpharsd)[2]
2238     
2239     if(full){
2240         Kcum <- cumsum(c(1, K))
2241         Kdcum <- cumsum(c(1, Kd))
2242         np <- sum(K) + ncovs1
2243         npd <- sum(Kd) + ncovs2
2244         S <- matrix(0, np + npd, np + npd)
2245         # Fortran call
2246         out <- try(.Fortran("fmksens2full",
2247             Smat = as.double(S),
2248             index1 = as.integer(index1), index2 = as.integer(index2),
2249             Z = as.double(Z), Zd = as.double(Zd),
2250             alphars = as.double(alphars), alpharsd = as.double(alpharsd),
2251             as = as.double(as), asd = as.double(asd),
2252             betahat = as.double(betahat), betadhat = as.double(betadhat),
2253             times1 = as.double(times1), times2 = as.double(times2),
2254             pi = as.double(pi), qi = as.double(qi),
2255             ri = as.double(ri), si = as.double(si),
2256             wi = as.double(wi), wij = as.double(wij), zij = as.double(zij),
2257             sig2 = as.double(sigma2hat), sig2d = as.double(sigma2dhat),
2258             nu2 = as.double(nu2hat), nu2d = as.double(nu2dhat),
2259             theta = as.double(thetahat),
2260             ncovs1 = as.integer(ncovs1), ncovs2 = as.integer(ncovs2),
2261             nr = as.integer(nr), ns = as.integer(ns), nsd = as.integer(nsd),
2262             np = as.integer(np), npd = as.integer(npd),
2263             d1 = as.integer(d1), d2 = as.integer(d2),
2264             m = as.integer(m), Ji = as.integer(Ji), maxj = as.integer(max(Ji)),
2265             Kcum = as.integer(Kcum), Kdcum = as.integer(Kdcum), DUP = FALSE))
2266         
2267         S <- matrix(out$Smat, np + npd, np + npd)
2268     }else{
2269         S <- matrix(0, ncovs1 + ncovs2, ncovs1 + ncovs2)
2270     
2271         # Submit to Fortran
2272         out <- try(.Fortran("fmksens2",
2273             Smat = as.double(S),
2274             index1 = as.integer(index1), index2 = as.integer(index2),
2275             Z = as.double(Z), Zd = as.double(Zd),
2276             alphars = as.double(alphars), alpharsd = as.double(alpharsd),
2277             as = as.double(as), asd = as.double(asd),
2278             betahat = as.double(betahat), betadhat = as.double(betadhat),
2279             times1 = as.double(times1), times2 = as.double(times2),
2280             pi = as.double(pi), qi = as.double(qi),
2281             ri = as.double(ri), si = as.double(si),
2282             wi = as.double(wi), wij = as.double(wij), zij = as.double(zij),
2283             sig2 = as.double(sigma2hat), sig2d = as.double(sigma2dhat),
2284             nu2 = as.double(nu2hat), nu2d = as.double(nu2dhat),
2285             theta = as.double(thetahat),
2286             ncovs1 = as.integer(ncovs1), ncovs2 = as.integer(ncovs2),
2287             nr = as.integer(nr), ns = as.integer(ns), nsd = as.integer(nsd),
2288             d1 = as.integer(d1), d2 = as.integer(d2),
2289             m = as.integer(m), Ji = as.integer(Ji), maxj = as.integer(max(Ji))))
2290         
2291         S <- matrix(out$Smat, ncovs1 + ncovs2, ncovs1 + ncovs2)    
2292     }
2293     return(S)
2294 }