diff --git a/DESCRIPTION b/DESCRIPTION
index b18889f..94d2e87 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -1,8 +1,8 @@
Package: TAM
Type: Package
Title: Test Analysis Modules
-Version: 3.7-5
-Date: 2021-05-16 13:48:06
+Version: 3.7-13
+Date: 2021-06-23 14:35:26
Author:
Alexander Robitzsch [aut,cre] (),
Thomas Kiefer [aut],
diff --git a/NAMESPACE b/NAMESPACE
index 34fae0d..1544154 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -136,6 +136,7 @@ export(plotDevianceTAM)
export(require_namespace_msg)
export(Scale)
export(tam)
+export(tam.cb)
export(tam.ctt)
export(tam.ctt2)
export(tam.ctt3)
diff --git a/R/RcppExports.R b/R/RcppExports.R
index 0dc7bde..334e261 100644
--- a/R/RcppExports.R
+++ b/R/RcppExports.R
@@ -1,5 +1,5 @@
## File Name: RcppExports.R
-## File Version: 3.007005
+## File Version: 3.007013
# Generated by using Rcpp::compileAttributes() -> do not edit by hand
# Generator token: 10BE3573-1514-4C36-9D1C-5A225CD40393
diff --git a/R/designMatrices.mfr2.R b/R/designMatrices.mfr2.R
index 16c5379..efceb21 100644
--- a/R/designMatrices.mfr2.R
+++ b/R/designMatrices.mfr2.R
@@ -1,5 +1,5 @@
## File Name: designMatrices.mfr2.R
-## File Version: 9.448
+## File Version: 9.480
##*** create design matrices
@@ -69,9 +69,12 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
# A Matrix
if( is.null(A) ){
- AX <- tam_A_matrix2( resp=resp, formulaA=formulaA, facets=facets,
+ #AX <- tam_A_matrix2( resp=resp, formulaA=formulaA, facets=facets,
+ # constraint=constraint, progress=progress, Q=Q)
+ AX <- .A.matrix2( resp=resp, formulaA=formulaA, facets=facets,
constraint=constraint, progress=progress, Q=Q)
A <- AX$A
+
X <- AX$X
otherFacets <- AX$otherFacets
xsi.elim <- AX$xsi.elim
@@ -176,7 +179,6 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
colnames(gresp) <- rownames(X)
# X$empty <- 1* (colSums( gresp, na.rm=TRUE )==0)
X$empty <- tam_rcpp_mml_mfr_colsums_gresp( gresp )
-
colnames(gresp.noStep) <- rownames(X.noStep)
# X.noStep$empty <- 1* (colSums( gresp.noStep, na.rm=TRUE )==0)
X.noStep$empty <- tam_rcpp_mml_mfr_colsums_gresp( gresp.noStep)
@@ -213,6 +215,11 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
str.ss2 <- gsub( paste0("(^|-)+",str.ss), "", rownames(x)[iss] )
ind_str_ss2 <- intersect( str.ss2, dimnames(x2)[[2]] )
x2[ss+1,ind_str_ss2,] <- x[ iss, ]
+
+ # version 3.4
+ # iss <- grep( paste0(str.ss,"+(-|$)"), rownames(x) )#, fixed=TRUE )
+ # str.ss2 <- gsub( paste0("(^|-)+",str.ss), "", rownames(x)[iss] )
+ # x2[ss+1,str.ss2,] <- x[ iss, ]
}
x2 <- aperm( x2, c(2,1,3) )
@@ -275,8 +282,8 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
}
# cat(".....\nbefore rename A" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
# print("g100")
- A <- .rename.items( matr=A, itemren )
+ A <- .rename.items( matr=A, itemren )
dimnames(A)[[1]] <- .rename.items2aa( vec=dimnames(A)[[1]],
facet.list=facet.list, I=I )
@@ -284,9 +291,12 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
xsi.table <- xsi.constr$xsi.table
# A <- .rename.items3( matr=A, facet.list, I )
#cat(".rename.items3 (A)" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
+
A <- .rename.items3a( matr=A, facet.list, I, cols=TRUE, xsi.table )
+
#cat(".rename.items3a (A)" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
B <- .rename.items( matr=B, itemren )
+
# cat(".rename.items (B)" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
dimnames(B)[[1]] <- dimnames(A)[[1]]
# B <- .rename.items3( matr=B, facet.list )
@@ -307,6 +317,7 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
# Q <- .rename.items3( matr=Q, facet.list, cols=FALSE)
X <- .rename.items( matr=X, itemren, cols=FALSE)
dimnames(X)[[1]] <- dimnames(A)[[1]]
+
# X <- .rename.items3( matr=X, facet.list, cols=FALSE)
# cat(".rename.items (Q,X)" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
X.noStep <- .rename.items( matr=X.noStep, itemren, cols=FALSE)
@@ -319,6 +330,7 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
#cat(".rename.items2a (G1$parameter) " ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
G1$parameter <- .rename.items2b( paste( G1$parameter), facet.list, I, xsi.table )
xsi.constr$xsi.table <- G1
+
# cat(".rename.items2b (G1$parameter) " ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
#***
G1 <- xsi.constr$xsi.constraints
@@ -347,6 +359,7 @@ designMatrices.mfr2 <- function( resp, formulaA=~ item + item:step, facets=NULL,
# B
B.flat.0 <- B.flat <- B; B.flat.0[ind,] <- 0
B.3d <- .generateB.3d( B.flat )
+
B.flat <- B.flat[!ind,]
B.3d.0 <- .generateB.3d( B.flat.0 )
if(!is.null(B.store.in)) B.3d.0[] <- B.store.in
diff --git a/R/designMatrices_aux2.R b/R/designMatrices_aux2.R
index 18e95d3..4c4fcca 100644
--- a/R/designMatrices_aux2.R
+++ b/R/designMatrices_aux2.R
@@ -1,8 +1,9 @@
## File Name: designMatrices_aux2.R
-## File Version: 9.167
+## File Version: 9.201
-## function tam_A_matrix2
+###########################################################
+## function .A.matrix
.A.matrix2 <- function( resp, formulaA=~ item + item*step, facets=NULL,
constraint=c("cases", "items"), progress=FALSE,
maxKi=NULL, Q=Q )
@@ -25,7 +26,6 @@
}
}
#cat(" +++ v62" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
-
### Basic Information and Initializations
constraint <- match.arg(constraint)
if ( is.null(maxKi) ){
@@ -70,9 +70,10 @@
expand.list[[vv]] <- paste( expand.list[[vv]] )
}
+
# cat(" +++ v110" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
g2 <- g1 <- expand.grid(expand.list)
- diffK <- ( stats::sd( maxKi) > 1e-10 )
+ diffK <- ( stats::sd( maxKi) > 0 )
# diffK <- FALSE
diffK <- TRUE
# reduced combinations of items
@@ -137,8 +138,8 @@
}
A <- NULL
- stepgroups <- unique( gsub( "(^|-)+step([[:digit:]])*", "\\1step([[:digit:]])*",
- x=rownames(X), perl=TRUE ) )
+
+ stepgroups <- unique( gsub( "(^|-)+step([[:digit:]])*", "\\1step([[:digit:]])*", rownames(X) ) )
X.out <- data.frame(as.matrix(X), stringsAsFactors=FALSE)
#cat(" +++ v150" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
if (progress){
@@ -155,21 +156,23 @@
}
}
#******
-
-
# collect xsi parameters to be excluded
xsi.elim.index <- xsi.elim <- NULL
ii <- 0 ; vv <- 1
- for( sg in stepgroups ){
- mm1 <- grep(paste0("(", sg, ")+$"), rownames(mm))
- ind2 <- grep( paste0("(", sg, ")+$"), rownames(mm))
- mm.sg.temp <- rbind( 0, apply( mm[ ind2,,drop=FALSE], 2, cumsum ) )
- if ( is.null(rownames(mm.sg.temp)) ){
- rownames(mm.sg.temp) <- paste0("rn", seq(0,nrow(mm.sg.temp)-1) )
- }
+ for( sg in stepgroups ){
+# sg <- stepgroups[2]
+ # mm1 <- mm[ grep(sg, rownames(mm)),]
+ mm1 <- grep(paste0("(", sg, ")+$"), rownames(mm))
+ # ind2 <- grep(sg, rownames(mm))
+ ind2 <- grep( paste0("(", sg, ")+$"), rownames(mm))
+# if (length(ind2)>0){
+ mm.sg.temp <- rbind( 0, apply( mm[ ind2,,drop=FALSE], 2, cumsum ) )
+# }
+ if ( is.null(rownames(mm.sg.temp)) ){
+ rownames(mm.sg.temp) <- paste0("rn", seq(0,nrow(mm.sg.temp)-1) )
+ }
# substitute the following line later if ...
- rownames(mm.sg.temp)[1] <- gsub("step([[:digit:]])*", "step0", sg, fixed=TRUE)
- # rownames(mm.sg.temp)[1] <- gsub("step([[:digit:]])*", "step0", sg, fixed=FALSE, perl=TRUE)
+ rownames(mm.sg.temp)[1] <- gsub("step([[:digit:]])*", "step0", sg, fixed=T)
rownames(mm.sg.temp)[-1] <- rownames(mm[ind2,,drop=FALSE])
#****
# set entries to zero if there are no categories in data
@@ -255,10 +258,7 @@
facet.design <- list( "facets"=facets, "facets.orig"=facets0,
"facet.list"=facet.list[otherFacets])
A <- A[ ! duplicated( rownames(A) ), ]
-
- if ( max(apply(resp,2,max,na.rm=TRUE)) > 9 ){
- A <- A[order(rownames(A)),,drop=FALSE]
- }
+ A <- A[order(rownames(A)),,drop=FALSE]
X.out <- X.out[order(rownames(X.out)),,drop=FALSE]
@@ -269,9 +269,12 @@
xsi.elim <- data.frame( xsi.elim, xsi.elim.index )
xsi.elim <- xsi.elim[ ! duplicated( xsi.elim[,2] ), ]
xsi.elim <- xsi.elim[ order( xsi.elim[,2] ), ]
- }
+# A <- A[,-xsi.elim[,2] ]
+ }
+
- #--- clean xsi.constr
+ #@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ ARb 2015-10-16
+ #@@@@ clean xsi.constr
xsi1 <- xsi.constr$xsi.constraints
xsi.constr$intercept_included <- FALSE
ind <- grep("(Intercept", rownames(xsi1), fixed=TRUE)
@@ -279,20 +282,19 @@
xsi1 <- xsi1[ - ind, ]
xsi.constr$xsi.constraints <- xsi1
xsi.constr$intercept_included <- TRUE
- }
+ }
xsi1 <- xsi.constr$xsi.table
ind <- grep("(Intercept", paste(xsi1$parameter), fixed=TRUE)
if ( length(ind) > 0 ){
xsi1 <- xsi1[ - ind, ]
xsi.constr$xsi.table <- xsi1
- }
+ }
+ #@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
#cat(" +++ out .A.matrix" ) ; z1 <- Sys.time() ; print(z1-z0) ; z0 <- z1
- res <- list( "A"=A, "X"=X.out, "otherFacets"=otherFacets, "xsi.constr"=xsi.constr,
- "facet.design"=facet.design, "xsi.elim"=xsi.elim )
- return(res)
+ return(list( "A"=A, "X"=X.out, "otherFacets"=otherFacets, "xsi.constr"=xsi.constr,
+ "facet.design"=facet.design, "xsi.elim"=xsi.elim ) )
}
+## end .A.matrix
+#####################################################
-
-
-.A.matrix2 -> tam_A_matrix2
diff --git a/R/tam.cb.R b/R/tam.cb.R
new file mode 100644
index 0000000..54b6592
--- /dev/null
+++ b/R/tam.cb.R
@@ -0,0 +1,119 @@
+## File Name: tam.cb.R
+## File Version: 0.16
+
+
+
+tam.cb <- function( dat, wlescore=NULL, group=NULL, max_ncat=30, progress=TRUE,
+ pweights=NULL, digits_freq=5)
+{
+ resp <- dat
+ wgt <- pweights
+ if (is.null(wgt)){
+ wgt <- rep(1,nrow(resp))
+ }
+ I <- ncol(resp)
+ if ( is.null(wlescore) ){
+ est_wle <- 0
+ wlescore <- rep(1, nrow(resp) )
+ } else {
+ est_wle <- 1
+ }
+
+ resp0 <- resp
+ wlescore0 <- wlescore
+
+ # define progress bar
+ if ( is.null(group) ){
+ group <- rep(1, nrow(resp) )
+ }
+ groups <- sort( unique( group ) )
+ G <- length(groups)
+ I <- ncol(resp)
+ dfr <- NULL
+ for (gg in 1:G){
+ ind.gg <- which( group==groups[gg] )
+ resp <- resp0[ ind.gg, ]
+ wlescore <- wlescore0[ ind.gg ]
+ wgt1 <- wgt[ind.gg]
+ prg <- round( seq( 1, I, len=10 ) )
+ prg[ prg==I ] <- I-1
+ if (progress){
+ cat("|")
+ cat( paste( rep("*", 10 ), collapse="") )
+ cat("| Group", groups[gg], "\n|")
+ prg <- round( seq( 1, I, len=10 ) )
+ prg[ prg==I ] <- I-1
+ }
+
+ if ( ! progress ){
+ prg <- 1
+ }
+
+ dfr.gg <- data.frame( "group"=groups[gg], "groupindex"=gg,
+ "itemno"=1:I, "item"=colnames(resp0))
+ nar <- is.na(resp)
+ dfr.gg$N <- colSums(1-nar)
+ dfr.gg$W <- colSums(wgt1*(1-nar))
+ dfr.gg$miss_prop <- colSums(wgt1*nar)/sum(wgt1)
+ dfr.gg$is_numeric <- 0
+ dfr.gg$M <- NA
+ dfr.gg$kurtosis <- dfr.gg$skewness <- dfr.gg$SD <- NA
+ dfr.gg$Min <- NA
+ dfr.gg$Max <- NA
+ dfr.gg$N_unique_val <- NA
+ dfr.gg$freq <- ""
+ if (est_wle){
+ dfr.gg$r.WLE <- NA
+ }
+
+ resp1 <- data.matrix(frame=resp)
+ for (ii in 1:I){
+ v1 <- resp[,ii]
+ v2 <- paste(v1)
+ v3 <- suppressWarnings(as.numeric(v2))
+ is_num <- FALSE
+ if ( mean(is.na(v3))<1 ){
+ v2 <- v3
+ is_num <- TRUE
+ dfr.gg$is_numeric[ii] <- 1
+ }
+ if ( is_num ){
+ dfr.gg$M[ii] <- weighted_mean(x=v3, w=wgt1)
+ dfr.gg$SD[ii] <- weighted_sd(x=v3, w=wgt1)
+ dfr.gg$skewness[ii] <- weighted_skewness(x=v3, w=wgt1)
+ dfr.gg$kurtosis[ii] <- weighted_kurtosis(x=v3, w=wgt1)
+ dfr.gg$Min[ii] <- min(v2, na.rm=TRUE)
+ dfr.gg$Max[ii] <- max(v2, na.rm=TRUE)
+ if (est_wle){
+ x2 <- data.frame( v3, wlescore )
+ ind <- which(rowSums(is.na(x2))==0)
+ c1 <- stats::cov.wt(x2[ind,], wt=wgt1[ind], method="ML")$cov
+ eps <- 1e-15
+ diag(c1) <- diag(c1) + eps
+ dfr.gg$r.WLE[ii] <- stats::cov2cor(c1)[1,2]
+ }
+ }
+ l1 <- length(setdiff(unique(v1),NA))
+ dfr.gg$N_unique_val[ii] <- l1
+ if (l1 < max_ncat){
+ wt <- weighted_table(v2, w=wgt1)
+ wt <- wt / sum(wt)
+ dfr.gg$freq[ii] <- paste0( " ", paste0( paste0( names(wt), " : ", round(wt,digits_freq)),
+ collapse=" # " ) )
+ }
+ if ( ii %in% prg){
+ cat("-")
+ utils::flush.console()
+ }
+
+ }
+ dfr <- rbind( dfr, dfr.gg )
+ if (progress){
+ cat("|\n")
+ }
+ } # end group
+ dfr <- dfr[ order( paste0( 10000+ dfr$itemno, dfr$group ) ), ]
+ dfr <- data.frame( "index"=seq(1,nrow(dfr) ), dfr )
+ return(dfr)
+}
+
diff --git a/R/tam.mml.2pl.R b/R/tam.mml.2pl.R
index 17f3da4..cfcc6c7 100644
--- a/R/tam.mml.2pl.R
+++ b/R/tam.mml.2pl.R
@@ -1,5 +1,5 @@
## File Name: tam.mml.2pl.R
-## File Version: 9.588
+## File Version: 9.589
tam.mml.2pl <- function( resp, Y=NULL, group=NULL, irtmodel="2PL",
formulaY=NULL, dataY=NULL,
@@ -338,7 +338,7 @@ tam.mml.2pl <- function( resp, Y=NULL, group=NULL, irtmodel="2PL",
# cat("m step regression") ; a1 <- Sys.time(); print(a1-a0) ; a0 <- a1
beta <- resr$beta
- variance <- resr$variance
+ variance <- resr$variance
itemwt <- resr$itemwt
variance_acceleration <- resr$variance_acceleration
variance_change <- resr$variance_change
diff --git a/R/tam.mml.3pl.R b/R/tam.mml.3pl.R
index 3f30c7a..786efd8 100644
--- a/R/tam.mml.3pl.R
+++ b/R/tam.mml.3pl.R
@@ -1,5 +1,5 @@
## File Name: tam.mml.3pl.R
-## File Version: 9.878
+## File Version: 9.879
tam.mml.3pl <- function( resp, Y=NULL, group=NULL,
formulaY=NULL, dataY=NULL,
@@ -720,7 +720,7 @@ tam.mml.3pl <- function( resp, Y=NULL, group=NULL,
#*** include NAs in AXsi
AXsi <- tam_mml_include_NA_AXsi(AXsi=AXsi, maxcat=maxcat, A=A, xsi=xsi)
-
+
#**** standard errors AXsi
se.AXsi <- tam_mml_se_AXsi( AXsi=AXsi, A=A, se.xsi=se.xsi, maxK=maxK )
diff --git a/R/tam.mml.mfr.R b/R/tam.mml.mfr.R
index 8116930..121826a 100644
--- a/R/tam.mml.mfr.R
+++ b/R/tam.mml.mfr.R
@@ -1,5 +1,5 @@
## File Name: tam.mml.mfr.R
-## File Version: 9.944
+## File Version: 9.955
tam.mml.mfr <- function( resp, Y=NULL, group=NULL, irtmodel="1PL",
formulaY=NULL, dataY=NULL, ndim=1, pid=NULL, xsi.fixed=NULL,
diff --git a/R/tam.mml.wle.R b/R/tam.mml.wle.R
index 7a6d2a0..aa8cf2a 100644
--- a/R/tam.mml.wle.R
+++ b/R/tam.mml.wle.R
@@ -1,5 +1,5 @@
## File Name: tam.mml.wle.R
-## File Version: 0.271
+## File Version: 0.272
tam.mml.wle <- function( tamobj, score.resp=NULL, WLE=TRUE, adj=.3, Msteps=20,
@@ -20,7 +20,7 @@ tam.mml.wle <- function( tamobj, score.resp=NULL, WLE=TRUE, adj=.3, Msteps=20,
pweights <- res$pweights
pid <- res$pid
pweights <- tam_mml_wle_pweights(score.resp=score.resp, pweights=pweights)
-
+
#--- initial values and some design matrices
res <- tam_mml_wle_theta_inits( WLE=WLE, adj=adj, nitems=nitems, maxK=maxK,
resp=resp, resp.ind=resp.ind, B=B, ndim=ndim )
diff --git a/R/tam_A_matrix2.R b/R/tam_A_matrix2.R
index 2743d25..efaaf45 100644
--- a/R/tam_A_matrix2.R
+++ b/R/tam_A_matrix2.R
@@ -1,9 +1,9 @@
## File Name: tam_A_matrix2.R
-## File Version: 9.168
+## File Version: 9.171
## function tam_A_matrix2
-tam_A_matrix2 <- function( resp, formulaA=~ item + item*step, facets=NULL,
+tam_A_matrix2__INACTIVE <- function( resp, formulaA=~ item + item*step, facets=NULL,
constraint=c("cases", "items"), progress=FALSE, maxKi=NULL, Q=Q )
{
z0 <- Sys.time()
diff --git a/R/tam_linking_chain.R b/R/tam_linking_chain.R
index 0dab8d8..eb3dad4 100644
--- a/R/tam_linking_chain.R
+++ b/R/tam_linking_chain.R
@@ -1,5 +1,5 @@
## File Name: tam_linking_chain.R
-## File Version: 0.04
+## File Version: 0.09
tam_linking_chain <- function(NM, parameters_list, entries, verbose,
linking_args, linking_list)
@@ -21,6 +21,8 @@ tam_linking_chain <- function(NM, parameters_list, entries, verbose,
linking_args <- tam_linking_include_list( list1=linking_args, list2=out1 )
linking_args <- tam_linking_include_list( list1=linking_args, list2=out2 )
#-- call linking function
+ linking_args$eps_rob_hae <- NULL
+ linking_args$par_init <- NULL
link_mm <- do.call( "tam_linking_2studies", args=linking_args)
linking_list_mm <- list()
linking_list_mm$common_items <- items_sel
diff --git a/R/tam_mml_mfr_proc_create_design_matrices.R b/R/tam_mml_mfr_proc_create_design_matrices.R
index 5ee06de..d86a56c 100644
--- a/R/tam_mml_mfr_proc_create_design_matrices.R
+++ b/R/tam_mml_mfr_proc_create_design_matrices.R
@@ -1,5 +1,5 @@
## File Name: tam_mml_mfr_proc_create_design_matrices.R
-## File Version: 0.151
+## File Version: 0.154
tam_mml_mfr_proc_create_design_matrices <- function(pid, maxKi, resp, formulaA,
facets, constraint, ndim, Q, A, B, progress, xsi.fixed, resp00, B00,
diff --git a/R/tam_model_implied_means.R b/R/tam_model_implied_means.R
index 9419547..9d3b1db 100644
--- a/R/tam_model_implied_means.R
+++ b/R/tam_model_implied_means.R
@@ -1,9 +1,9 @@
## File Name: tam_model_implied_means.R
-## File Version: 0.01
+## File Version: 0.02
tam_model_implied_means <- function(mod)
-{
+{
hwt <- mod$hwt
pweights <- mod$pweights
rprobs <- mod$rprobs
@@ -15,14 +15,14 @@ tam_model_implied_means <- function(mod)
names(M_implied) <- colnames(resp)
N <- nrow(hwt)
W <- sum(pweights)
-
+
for (ii in 1:I){
for (uu in 2:K){
rpr <- matrix( rprobs[ii,uu,], nrow=N, ncol=TP, byrow=TRUE)
M_implied[ii] <- M_implied[ii] + sum( rpr*(uu-1)*pweights*hwt, na.rm=TRUE)
}
M_implied[ii] <- M_implied[ii] / W
- }
+ }
return(M_implied)
}
-
+
diff --git a/README.md b/README.md
index 680d161..a89a9d5 100644
--- a/README.md
+++ b/README.md
@@ -22,9 +22,9 @@ The CRAN version can be installed from within R using:
utils::install.packages("TAM")
```
-#### GitHub version `TAM` 3.7-5 (2021-05-16)
+#### GitHub version `TAM` 3.7-13 (2021-06-23)
-[![](https://img.shields.io/badge/github%20version-3.7--5-orange.svg)](https://github.com/alexanderrobitzsch/TAM)
+[![](https://img.shields.io/badge/github%20version-3.7--13-orange.svg)](https://github.com/alexanderrobitzsch/TAM)
The version hosted [here](https://github.com/alexanderrobitzsch/TAM) is the development version of `TAM`.
The GitHub version can be installed using `devtools` as:
diff --git a/docs/404.html b/docs/404.html
index 7b058c5..b27ba65 100644
--- a/docs/404.html
+++ b/docs/404.html
@@ -71,7 +71,7 @@
TAM
- 3.7-5
+ 3.7-13
diff --git a/docs/authors.html b/docs/authors.html
index b9daa7d..8f716d2 100644
--- a/docs/authors.html
+++ b/docs/authors.html
@@ -71,7 +71,7 @@
TAM
- 3.7-5
+ 3.7-13
@@ -111,12 +111,12 @@ Citation
Source: inst/CITATION
- Robitzsch, A., Kiefer, T., & Wu, M. (2021). TAM: Test Analysis Modules. R package version 3.7-5. https://CRAN.R-project.org/package=TAM
- @Manual{TAM_3.7-5,
+ Robitzsch, A., Kiefer, T., & Wu, M. (2021). TAM: Test Analysis Modules. R package version 3.7-13. https://CRAN.R-project.org/package=TAM
+ @Manual{TAM_3.7-13,
title = {TAM: Test Analysis Modules},
author = {Alexander Robitzsch and Thomas Kiefer and Margaret Wu},
year = {2021},
- note = {R package version 3.7-5},
+ note = {R package version 3.7-13},
url = {https://CRAN.R-project.org/package=TAM},
}
diff --git a/docs/index.html b/docs/index.html
index a6af804..f7b4da6 100644
--- a/docs/index.html
+++ b/docs/index.html
@@ -43,7 +43,7 @@
TAM
- 3.7-5
+ 3.7-13
diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml
index b8736e2..e3c3613 100644
--- a/docs/pkgdown.yml
+++ b/docs/pkgdown.yml
@@ -2,5 +2,5 @@ pandoc: 1.13.1
pkgdown: 1.5.1
pkgdown_sha: ~
articles: []
-last_built: 2021-05-16T12:09Z
+last_built: 2021-06-23T12:52Z
diff --git a/docs/reference/data.fims.Aus.Jpn.html b/docs/reference/data.fims.Aus.Jpn.html
index bbb27a6..0801efb 100644
--- a/docs/reference/data.fims.Aus.Jpn.html
+++ b/docs/reference/data.fims.Aus.Jpn.html
@@ -128,7 +128,7 @@ Dataset FIMS Study with Responses of Australian and Japanese Students
A data frame with 6371 observations on the following 16 variables.
- SEX
Gender: 1 -- female, 2 -- male
+ SEX
Gender: 1 -- male, 2 -- female
M1PTI1
A Mathematics item
M1PTI2
A Mathematics item
M1PTI3
A Mathematics item
diff --git a/docs/reference/index.html b/docs/reference/index.html
index b23a023..1e1afd5 100644
--- a/docs/reference/index.html
+++ b/docs/reference/index.html
@@ -391,7 +391,7 @@
+ tam.ctt()
tam.ctt2()
tam.ctt3()
tam.cb()
plotctt()
Classical Test Theory Based Statistics and Plots |
diff --git a/docs/reference/tam.ctt.html b/docs/reference/tam.ctt.html
index 6fc76b2..927b745 100644
--- a/docs/reference/tam.ctt.html
+++ b/docs/reference/tam.ctt.html
@@ -40,7 +40,7 @@
-
@@ -115,7 +115,7 @@ Classical Test Theory Based Statistics and Plots
-
This function computes some item statistics based on classical test
+
The functions computes some item statistics based on classical test
theory.
@@ -124,6 +124,9 @@ Classical Test Theory Based Statistics and Plots
tam.ctt3(resp, wlescore=NULL, group=NULL, allocate=30, progress=TRUE, max_ncat=30,
pweights=NULL)
+tam.cb( dat, wlescore=NULL, group=NULL, max_ncat=30, progress=TRUE,
+ pweights=NULL, digits_freq=5)
+
plotctt( resp, theta, Ncuts=NULL, ask=FALSE, col.list=NULL,
package="lattice", ... )
@@ -170,6 +173,14 @@ Arg
pweights |
Optional vector of person weights |
+
+ dat |
+ Data frame |
+
+
+ digits_freq |
+ Number of digits for rounding in frequency table |
+
theta |
A score to be conditioned |
diff --git a/inst/NEWS b/inst/NEWS
index 2334e68..befa78b 100644
--- a/inst/NEWS
+++ b/inst/NEWS
@@ -42,7 +42,7 @@ http://www.edmeasurementsurveys.com/TAM/Tutorials/
-------------------------------------------------------------
-VERSIONS TAM 3.7 | 2021-05-16 | Last: TAM 3.7-5
+VERSIONS TAM 3.7 | 2021-06-23 | Last: TAM 3.7-13
-------------------------------------------------------------
NOTE * changed computation of AXsi and xsi.item in outputs to
@@ -52,7 +52,13 @@ NOTE * included utility function tam_model_implied_means() for
computation of model-implied means
FIXED * fixed a bug in tam.mml.wle() and tam.mml.wle2() if argument
'score.resp' is used (thanks to Fu Liu)
-
+ADDED * added function tam.cb() that generates most important
+ descriptive statistics for a data frame
+FIXED * fixed a bug in tam.linking() with method='chain'
+FIXED * fixed a recently introduced bug (since TAM 3.5) in
+ faceted models with polytomous items
+ (thanks to Nguyen Thi Kim Cuc)
+
DATA * included/modified datasets: ---
EXAMP * included/modified examples: ---
diff --git a/man/data.fims.Aus.Jpn.Rd b/man/data.fims.Aus.Jpn.Rd
index a41358b..c0003be 100644
--- a/man/data.fims.Aus.Jpn.Rd
+++ b/man/data.fims.Aus.Jpn.Rd
@@ -1,5 +1,5 @@
%% File Name: data.fims.Aus.Jpn.Rd
-%% File Version: 2.13
+%% File Version: 2.14
\name{data.fims.Aus.Jpn.scored}
\alias{data.fims.Aus.Jpn.raw}
@@ -21,7 +21,7 @@ data(data.fims.Aus.Jpn.scored)
\format{
A data frame with 6371 observations on the following 16 variables.
\describe{
- \item{\code{SEX}}{Gender: 1 -- female, 2 -- male}
+ \item{\code{SEX}}{Gender: 1 -- male, 2 -- female}
\item{\code{M1PTI1}}{A Mathematics item}
\item{\code{M1PTI2}}{A Mathematics item}
\item{\code{M1PTI3}}{A Mathematics item}
diff --git a/man/tam.ctt.Rd b/man/tam.ctt.Rd
index 28d5d4b..ce9d18b 100644
--- a/man/tam.ctt.Rd
+++ b/man/tam.ctt.Rd
@@ -1,18 +1,19 @@
%% File Name: tam.ctt.Rd
-%% File Version: 3.16
+%% File Version: 3.182
\name{tam.ctt}
\alias{tam.ctt}
\alias{tam.ctt2}
\alias{tam.ctt3}
\alias{plotctt}
+\alias{tam.cb}
%- Also NEED an '\alias' for EACH other topic documented here.
\title{
Classical Test Theory Based Statistics and Plots
}
\description{
-This function computes some item statistics based on classical test
+The functions computes some item statistics based on classical test
theory.
}
\usage{
@@ -21,6 +22,9 @@ tam.ctt2(resp, wlescore=NULL, group=NULL, allocate=30, progress=TRUE)
tam.ctt3(resp, wlescore=NULL, group=NULL, allocate=30, progress=TRUE, max_ncat=30,
pweights=NULL)
+tam.cb( dat, wlescore=NULL, group=NULL, max_ncat=30, progress=TRUE,
+ pweights=NULL, digits_freq=5)
+
plotctt( resp, theta, Ncuts=NULL, ask=FALSE, col.list=NULL,
package="lattice", ... )
}
@@ -51,6 +55,8 @@ should be displayed.
\item{max_ncat}{Maximum number of categories of variables for which
frequency tables should be computed}
\item{pweights}{Optional vector of person weights}
+\item{dat}{Data frame}
+\item{digits_freq}{Number of digits for rounding in frequency table}
\item{theta}{A score to be conditioned}
\item{Ncuts}{Number of break points for \code{theta}}
\item{ask}{
diff --git a/src/RcppExports.cpp b/src/RcppExports.cpp
index 306018b..42b5879 100644
--- a/src/RcppExports.cpp
+++ b/src/RcppExports.cpp
@@ -1,5 +1,5 @@
//// File Name: RcppExports.cpp
-//// File Version: 3.007005
+//// File Version: 3.007013
// Generated by using Rcpp::compileAttributes() -> do not edit by hand
// Generator token: 10BE3573-1514-4C36-9D1C-5A225CD40393
diff --git a/src/init.c b/src/init.c
index cd07912..bec5cd6 100644
--- a/src/init.c
+++ b/src/init.c
@@ -1,5 +1,5 @@
//// File Name: init.c
-//// File Version: 3.007005
+//// File Version: 3.007013
#include
#include
#include // for NULL