From b5fd24b48efff8574ca56b19f0a03b0e5462d38c Mon Sep 17 00:00:00 2001 From: maltelueken Date: Fri, 3 Nov 2023 15:42:43 +0100 Subject: [PATCH] Add mediation and total effects for all factor levels --- R/classicProcess.R | 250 +- ...lassic-process-integration-custom-models.R | 512 +- ...test-classic-process-integration-general.R | 120 +- ...classic-process-integration-hayes-models.R | 9990 +++++------------ tests/testthat/test-classic-process-unit.R | 83 +- 5 files changed, 3554 insertions(+), 7401 deletions(-) diff --git a/R/classicProcess.R b/R/classicProcess.R index 666e005..78ad609 100644 --- a/R/classicProcess.R +++ b/R/classicProcess.R @@ -303,15 +303,17 @@ ClassicProcess <- function(jaspResults, dataset = NULL, options) { # Set all edges from var interacting with sourceNode to target as isMod igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$isMod <- TRUE # Store unique moderating variables - if (any(is.na(igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars))) { - igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars <- sourceNodeIntVars[sourceNodeIntVars != v] - } else { - igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars <- list( - unique(c( - igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars[[1]], - sourceNodeIntVars[sourceNodeIntVars != v] - )) - ) + if (length(sourceNodeIntVars[sourceNodeIntVars != v]) > 0) { + if (any(is.na(igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars))) { + igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars <- sourceNodeIntVars[sourceNodeIntVars != v] + } else { + igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars <- list( + unique(c( + igraph::E(graph)[source == v & target == igraph::E(graph)$target[i]]$modVars[[1]], + sourceNodeIntVars[sourceNodeIntVars != v] + )) + ) + } } } } @@ -806,101 +808,165 @@ ClassicProcess <- function(jaspResults, dataset = NULL, options) { return(paste(regLines, collapse = "\n")) } -.procMedEffectsSyntax <- function(graph, modProbs, contrasts) { - # Get all simple paths from X to Y - medPaths <- igraph::all_simple_paths(graph, - from = igraph::V(graph)[isTreat]$name, - to = igraph::V(graph)[isDep]$name, - mode = "out" - ) +.procMedEffectsSyntaxModPars <- function(pathEdge, sourceNode, graph, modProbes) { + # Get moderator parameters for two-way interactions + modPars <- lapply(pathEdge$modVars[[1]], function(v) { + # Get edge for two way interaction between X and M + twoWayEdge <- igraph::E(graph)[paste(sourceNode, v, sep = ":") %--% pathEdge$target]$parName + + # Concatenate two way edge parName with moderator probes + return(apply(expand.grid( + twoWayEdge, + format(modProbes[[v]], digits = 3) + ), 1, paste, collapse = "*")) + }) - medEffects <- lapply(medPaths, function(path) { - # Left hand side of lavaan syntax - lhs <- paste(names(path), collapse = "__") - - # Get moderators on path - modName <- na.omit(unlist(sapply(2:length(path), function(i) { - return(igraph::E(graph)[.from(names(path)[i-1]) & .to(names(path)[i])]$modVars) - }))) - - # Right hand side of lavaan syntax - rhs <- lapply(2:length(path), function(i) { - # Get edge from path[-1] to path[i] - pathEdge <- igraph::E(graph)[.from(names(path)[i-1]) & .to(names(path)[i])] + # Get all possible combinations of probes from different moderators + modPars <- apply(expand.grid(modPars), 1, paste, collapse = "+") + + # Get name of potential three-way interaction + threeWayInt <- paste(c(pathEdge$source, pathEdge$modVars[[1]]), collapse = "__") + + if (threeWayInt %in% igraph::E(graph)$source) { # If three-way int + # Get edge of three way interaction X x M1 x M2 + threeWayEdge <- igraph::E(graph)[threeWayInt %--% pathEdge$target] + # Combine three way int parName with moderator probes + threeWayModPars <- paste( + threeWayEdge$parName, + apply( + expand.grid(lapply(pathEdge$modVars[[1]], function(v) format(modProbes[[v]], digits = 3))), + 1, paste, collapse = "*" + ), + sep = "*" + ) + # Add to previous moderator probes + modPars <- paste(modPars, threeWayModPars, sep = "+") + } + return(modPars) +} - # If no moderators on edge, return only parName - if(any(is.na(pathEdge$modVars[[1]]))) return(pathEdge$parName) - - modPars <- lapply(pathEdge$modVars[[1]], function(v) { # If moderators - # Get edge for two way interaction between X and M - twoWayEdge <- igraph::E(graph)[ - .from(paste(names(path)[i-1], v, sep = ":")) & - .to(names(path)[i]) - ]$parName - - # Concatenate two way edge parName with moderator probes - return(paste( - twoWayEdge, - format(modProbs[[v]], digits = 3), - sep = "*" - )) - }) - # Get all possible combinations of probes from different moderators - modPars <- apply(expand.grid(modPars), 1, paste, collapse = "+") - - # Get name of potential three-way interaction - threeWayInt <- paste(c(pathEdge$source, pathEdge$modVars[[1]]), collapse = "__") - - if (threeWayInt %in% igraph::E(graph)$source) { # If three-way int - # Get edge of three way interaction X x M1 x M2 - threeWayEdge <- igraph::E(graph)[.from(threeWayInt) & .to(names(path)[i])] - # Combine three way int parName with moderator probes - threeWayModPars <- paste( - threeWayEdge$parName, - apply( - expand.grid(lapply(pathEdge$modVars[[1]], function(v) format(modProbs[[v]], digits = 3))), - 1, paste, collapse = "*" - ), - sep = "*" - ) - # Add to previous moderator probes - modPars <- paste(modPars, threeWayModPars, sep = "+") - } - - # If indirect path add parentheses - if (i > 1) { - return(paste0("(", pathEdge$parName, " + ", modPars, ")")) - } - # Concanenate path edge parName with moderator probes - return(paste(pathEdge$parName, modPars, sep = " + ")) +.procContrFacVars <- function(contrasts) { + # Concatenate factor names with levels + return(lapply(names(contrasts), function(contr) paste0(contr, colnames(contrasts[[contr]])))) +} + +.procMedEffectsSyntaxGetLhs <- function(path, graph, modProbes, contrasts) { + # Get factor names with level names + contrFacVars <- .procContrFacVars(contrasts) + # Is source node a factor with contrast + sourceInContrFacVars <- sapply(contrFacVars, function(v) names(path)[1] %in% v) + + if (any(sourceInContrFacVars)) { + # Replace factor in lhs with factor with level names appended + facContr <- names(contrasts)[sourceInContrFacVars] + facContrLevels <- paste(facContr, colnames(contrasts[[facContr]]), sep = "__") + lhs <- paste(c(facContr, names(path)[-1]), collapse = "__") + lhs <- apply(expand.grid(lhs, facContrLevels), 1, paste, collapse = ".") + } else { + # Just concatenate path vars to lhs + lhs <- paste(names(path), collapse = "__") + } + + # Get moderators on path + modsOnPath <- unique(na.omit(unlist(sapply(2:length(path), function(i) { + return(igraph::E(graph)[names(path)[i-1] %--% names(path)[i]]$modVars) + })))) + + if (!is.null(modsOnPath) && length(modsOnPath) > 0) { # If path is moderated + # Get combinations of moderators + modsOnPath <- lapply(modsOnPath, function(v) { + return(apply( + expand.grid(v, gsub("\\%", "", names(modProbes[[v]]))), # Remove `%` from quantile name strings + 1, paste, collapse = "__" + )) }) - # If indirect paths, multiply their steps - rhs <- .doCallPaste(rhs, sep = "*") - - if (!is.null(modName) && length(modName) > 0) { # If path is moderated - # Get combinations of moderators - modName <- lapply(modName, function(v) { - return(apply( - expand.grid(v, gsub("\\%", "", names(modProbs[[v]]))), # Remove `%` from quantile name strings - 1, paste, collapse = "__" - )) - }) - # Add moderator combinations to left hand side - lhs <- apply(expand.grid(lhs, apply(expand.grid(modName), 1, paste, collapse = ".")), 1, paste, collapse = ".") + # Add moderator combinations to left hand side + lhs <- apply(expand.grid(lhs, apply(expand.grid(modsOnPath), 1, paste, collapse = ".")), 1, paste, collapse = ".") + } + + return(lhs) +} + +.procMedEffectsSyntaxGetRhs <- function(path, graph, modProbes, contrasts) { + # Get factor names with level names + contrFacVars <- .procContrFacVars(contrasts) + # Is source node a factor with contrast + sourceInContrFacVars <- sapply(contrFacVars, function(v) names(path)[1] %in% v) + + if (any(sourceInContrFacVars)) { + sourceFacVars <- contrFacVars[[which(sourceInContrFacVars)]] + } else { + sourceFacVars <- numeric(0) + } + + # Right hand side of lavaan syntax + rhs <- lapply(2:length(path), function(i) { + # Get edge from path[-1] to path[i] + if (any(sourceInContrFacVars) && names(path)[i-1] %in% sourceFacVars) { + # Get all vars with factor levels as source nodes + sourceNode <- sourceFacVars + } else { + # Just get previous node as source node + sourceNode <- names(path)[i-1] } - return(list(lhs = lhs, rhs = rhs, modName = modName)) + # Edge from previous node to current node + pathEdge <- igraph::E(graph)[sourceNode %--% names(path)[i]] + + # If no moderators on edge, return only parName + if(any(is.na(unlist(pathEdge$modVars)))) return(pathEdge$parName) + + # Get pars from moderators + modPars <- .procMedEffectsSyntaxModPars(pathEdge, sourceNode, graph, modProbes) + + # If indirect path add parentheses + if (i > 1) { + return(paste0("(", pathEdge$parName, " + ", modPars, ")")) + } + # Concanenate path edge parName with moderator probes + return(paste(pathEdge$parName, modPars, sep = " + ")) }) + + # If indirect paths, multiply their steps + rhs <- .doCallPaste(rhs, sep = "*") + + return(rhs) +} + +.procMedEffectsSyntaxSinglePath <- function(path, graph, modProbes, contrasts) { + # Right hand side of lavaan syntax + rhs <- .procMedEffectsSyntaxGetRhs(path, graph, modProbes, contrasts) + + # Left hand side of lavaan syntax + lhs <- .procMedEffectsSyntaxGetLhs(path, graph, modProbes, contrasts) + + return(list(lhs = lhs, rhs = rhs)) +} + +.procMedEffectsSyntax <- function(graph, modProbes, contrasts) { + # Get all simple paths from X to Y + medPaths <- igraph::all_simple_paths(graph, + from = igraph::V(graph)[isTreat]$name, + to = igraph::V(graph)[isDep]$name, + mode = "out" + ) + # Get lhs and rhs plus moderator names for each path + medEffects <- lapply(medPaths, .procMedEffectsSyntaxSinglePath, graph = graph, modProbes = modProbes, contrasts = contrasts) + # Sort effects according to path length to preserve order + medEffects <- medEffects[sort.int(sapply(medPaths, length), index.return = TRUE)$ix] # All rhs effects totRhs <- lapply(medEffects, function(path) path$rhs) - # All moderators of total effects - totLhsMods <- lapply(medEffects, function(path) apply(expand.grid(path$modName), 1, paste, collapse = ".")) # Add rhs effects totEffects <- .doCallPaste(totRhs, sep = " + ") # Concatenate rhs and lhs effects medEffectsLabeled <- unlist(lapply(medEffects, function(path) paste(path$lhs, path$rhs, sep = " := "))) + # Get conditional effect labels from lhs of each path + totEffectsConditional <- Filter(function(x) !is.null(x) & all(x != ""), lapply(medEffects, function(path) { + # Split lhs and remove first chunk, then paste together again + return(sapply(strsplit(path$lhs, "\\."), function(path) paste(path[-1], collapse = "."))) + })) # Concatenate total effects - totEffectsLabeled <- paste(paste("tot", unlist(totLhsMods), sep = "."), totEffects, sep = " := ") + totEffectsLabeled <- paste(paste0("tot.", unlist(totEffectsConditional)), totEffects, sep = " := ") # Only return total effects when no indirect path if (length(medEffects) < 2) { return(paste(c(medEffectsLabeled, totEffectsLabeled), collapse = "\n")) @@ -908,7 +974,7 @@ ClassicProcess <- function(jaspResults, dataset = NULL, options) { # Add rhs indirect effects totIndEffects <- .doCallPaste(totRhs[-1], sep = " + ") # Concatenate indirect effects - totIndEffectsLabeled <- paste(paste("totInd", unlist(totLhsMods[-1]), sep = "."), totIndEffects, sep = " := ") + totIndEffectsLabeled <- paste(paste("totInd", unlist(totEffectsConditional[-1]), sep = "."), totIndEffects, sep = " := ") return(paste(c(medEffectsLabeled, totEffectsLabeled, totIndEffectsLabeled), collapse = "\n")) } diff --git a/tests/testthat/test-classic-process-integration-custom-models.R b/tests/testthat/test-classic-process-integration-custom-models.R index 9247487..b231bee 100644 --- a/tests/testthat/test-classic-process-integration-custom-models.R +++ b/tests/testthat/test-classic-process-integration-custom-models.R @@ -2,7 +2,7 @@ test_that("Test that model number one_confounder - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -13,19 +13,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -77,9 +77,9 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.0338982352403213, 0.370786700700972, 0.168444232730325, "Total", - 0.102761008338914, 0.10323785006597, 1.63161314016795, -0.0420059521826613, - 0.367482204548676, 0.162738126183007, "Total indirect", 0.11926845840203, - 0.1044631840078, 1.55785148355095)) + 0.102761008338914, 0.10323785006597, 1.63161314016795, -0.027115002941041, + 0.0385272160356765, 0.00570610654731776, "Total indirect", 0.733292476299653, + 0.0167457717321581, 0.34074909407489)) @@ -95,7 +95,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number one_confounder - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -106,19 +106,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -147,10 +147,10 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.329844405685614, 0.496024877188678, 0.0830902357515322, "facExperimexperimental", - "contNormal", "", "", "", 0.693299245993837, 0.210684810891589, - 0.394381708865987, -0.0500653809891558, 0.0303840547660915, - -0.00984066311153218, "facExperimexperimental", "contGamma", + list(-0.329844405685614, 0.496024877188678, 0.0830902357515322, "experimental", + "facExperim", "contNormal", "", "", "", 0.693299245993837, + 0.210684810891589, 0.394381708865987, -0.0500653809891558, 0.0303840547660915, + -0.00984066311153218, "experimental", "facExperim", "contGamma", "contNormal", "", "", 0.63159016355888, 0.0205231923621613, -0.479489883341709)) @@ -170,10 +170,13 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.339311551617825, 0.485810696897825, 0.07324957264, "Total", - 0.727848824673947, 0.210494237400306, 0.347988493864076, -0.329844405685614, - 0.496024877188678, 0.0830902357515322, "Total indirect", 0.693299245993837, - 0.210684810891589, 0.394381708865987)) + list(-0.339311551617825, 0.485810696897825, 0.07324957264, "experimental", + "Total", 0.727848824673947, 0.210494237400306, 0.347988493864076, + -0.339311551617825, 0.485810696897825, 0.07324957264, "experimental", + "Total", 0.727848824673947, 0.210494237400306, 0.347988493864076, + -0.0500653809891558, 0.0303840547660915, -0.00984066311153218, + "experimental", "Total indirect", 0.63159016355888, 0.0205231923621613, + -0.479489883341709)) @@ -189,7 +192,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number one_direct - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -200,19 +203,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "directs", - processVariable = "")), residualCovariances = TRUE, statisticalPathPlot = TRUE, - totalEffects = TRUE, localTests = FALSE, localTestType = "cis", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "directs", + processVariable = "")), residualCovariances = TRUE, statisticalPathPlot = TRUE, + totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -271,7 +274,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number one_direct - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -282,19 +285,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "directs", - processVariable = "")), residualCovariances = TRUE, statisticalPathPlot = TRUE, - totalEffects = TRUE, localTests = FALSE, localTestType = "cis", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "directs", + processVariable = "")), residualCovariances = TRUE, statisticalPathPlot = TRUE, + totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -353,7 +356,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number two_confounder - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -364,21 +367,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -438,9 +441,9 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.00931723446549082, 0.524832920777229, 0.257757843155869, "Total", - 0.0585458573430464, 0.136265298611614, 1.89158828977093, -0.0183967830162192, - 0.521461905534409, 0.251532561259095, "Total indirect", 0.067792370251071, - 0.137721583868113, 1.8263844649069)) + 0.0585458573430464, 0.136265298611614, 1.89158828977093, -0.0345845435803312, + 0.0470351073738792, 0.00622528189677404, "Total indirect", 0.7649551805981, + 0.0208217221331657, 0.298980163934575)) @@ -456,7 +459,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number two_confounder - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -467,21 +470,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "facGender")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "facGender")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -514,12 +517,12 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.397396510584462, 0.416025502052742, 0.0093144957341401, "facExperimexperimental", - "contNormal", "", "", "", 0.964197302009531, 0.207509428503119, - 0.0448870964627041, -0.0543727189027194, 0.0333398342079703, - -0.0105164423473746, "facExperimexperimental", "contGamma", - "contNormal", "", "", 0.63836482029219, 0.0223760624691461, - -0.469986279394574)) + list(-0.397396510584462, 0.416025502052742, 0.0093144957341401, "experimental", + "facExperim", "contNormal", "", "", "", 0.964197302009531, + 0.207509428503119, 0.0448870964627041, -0.0543727189027194, + 0.0333398342079703, -0.0105164423473746, "experimental", "facExperim", + "contGamma", "contNormal", "", "", 0.63836482029219, + 0.0223760624691461, -0.469986279394574)) @@ -542,10 +545,13 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.409075392315575, 0.406671499089106, -0.00120194661323445, "Total", - 0.995391649700707, 0.208102520719562, -0.005775742692008, -0.397396510584462, - 0.416025502052742, 0.0093144957341401, "Total indirect", 0.964197302009531, - 0.207509428503119, 0.0448870964627041)) + list(-0.409075392315575, 0.406671499089106, -0.00120194661323445, "experimental", + "Total", 0.995391649700707, 0.208102520719562, -0.005775742692008, + -0.409075392315575, 0.406671499089106, -0.00120194661323445, + "experimental", "Total", 0.995391649700707, 0.208102520719562, + -0.005775742692008, -0.0543727189027194, 0.0333398342079703, + -0.0105164423473746, "experimental", "Total indirect", 0.63836482029219, + 0.0223760624691461, -0.469986279394574)) @@ -561,7 +567,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_X_Y - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -572,21 +578,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -651,9 +657,9 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.172816800526246, 0.240148499061018, 0.0336658492673863, "Total", - 0.749300959047747, 0.105350226546172, 0.319561242259233, -0.17738968874516, - 0.235906781207678, 0.0292585462312589, "Total indirect", 0.78139319035638, - 0.105434710334697, 0.277503927675992)) + 0.749300959047747, 0.105350226546172, 0.319561242259233, -0.0179628726375066, + 0.0242572794460163, 0.00314720340425485, "Total indirect", 0.770132222942081, + 0.0107706448732094, 0.292201947172458)) @@ -669,7 +675,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_X_Y - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -680,21 +686,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "facGender")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "facGender")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -727,13 +733,13 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0859003151554296, 0.895699802278834, 0.490800058717132, "facGenderm", - "contNormal", "", "", "", "", "", 0.0175121668886125, + list(0.0859003151554296, 0.895699802278834, 0.490800058717132, "m", + "facGender", "contNormal", "", "", "", "", "", 0.0175121668886125, 0.206585297870522, 2.37577438363858, -0.0953627168761149, 0.0411095548346247, - -0.0271265810207451, "facGenderm", "contGamma", "contNormal", + -0.0271265810207451, "m", "facGender", "contGamma", "contNormal", "", "", "", "", 0.435883275295673, 0.0348149947619486, -0.779163725464449, -0.0210117568450086, 0.0239241658212091, - 0.00145620448810027, "facGenderm", "contGamma", "debCollin1", + 0.00145620448810027, "m", "facGender", "contGamma", "debCollin1", "contNormal", "", "", "", 0.898916540794359, 0.0114634562218149, 0.127030143433454)) @@ -758,10 +764,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0625107971036305, 0.867748567265343, 0.465129682184487, "Total", - 0.0235575803680084, 0.205421573180254, 2.264268912868, 0.0874078079953342, - 0.89710471841513, 0.492256263205232, "Total indirect", 0.0171663559416233, - 0.206559129863248, 2.3831251783987)) + list(0.0625107971036305, 0.867748567265343, 0.465129682184487, "m", + "Total", 0.0235575803680084, 0.205421573180254, 2.264268912868, + 0.0625107971036305, 0.867748567265343, 0.465129682184487, "m", + "Total", 0.0235575803680084, 0.205421573180254, 2.264268912868, + 0.0625107971036305, 0.867748567265343, 0.465129682184487, "m", + "Total", 0.0235575803680084, 0.205421573180254, 2.264268912868, + -0.0941334753506578, 0.0427927222853681, -0.0256703765326449, + "m", "Total indirect", 0.462405005295899, 0.0349307943197126, + -0.734892436103528, -0.0941334753506578, 0.0427927222853681, + -0.0256703765326449, "m", "Total indirect", 0.462405005295899, + 0.0349307943197126, -0.734892436103528)) @@ -777,7 +790,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_X_M - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -788,21 +801,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "confounders", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "confounders", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -887,7 +900,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_X_M - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -898,21 +911,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "confounders", - processVariable = "facGender")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "confounders", + processVariable = "facGender")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -943,13 +956,14 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.0812046417471832, 0.0448619220894113, -0.018171359828886, "facGenderm", - "contGamma", "contNormal", "", "", "", "", - 0.572058586763452, 0.0321604286688407, -0.565022314099054, "", - "", 0.00130342699162342, "facGenderm", "debCollin1", "contNormal", - "", "", "", "", "", "", "", "", "", 0.000970569137243933, - "facGenderm", "contGamma", "debCollin1", "contNormal", "", - "", "", "", "", "")) + list(-0.0812046417471832, 0.0448619220894113, -0.018171359828886, "m", + "facGender", "contGamma", "contNormal", "", "", "", + "", 0.572058586763452, 0.0321604286688407, -0.565022314099054, + "", "", 0.00130342699162342, "m", "facGender", "debCollin1", + "contNormal", "", "", "", "", "", "", "", + "", "", 0.000970569137243933, "m", "facGender", "contGamma", + "debCollin1", "contNormal", "", "", "", + "", "", "")) @@ -970,10 +984,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.079416444198823, 0.0476217167987858, -0.0158973637000186, "Total", - 0.623756169473329, 0.0324082896419704, -0.490533868823201, -0.0216391957105213, - 0.0261871879682561, 0.00227399612886735, "Total indirect", 0.852146453356244, - 0.0122008322744769, 0.18638041059087)) + list(-0.079416444198823, 0.0476217167987858, -0.0158973637000186, "m", + "Total", 0.623756169473329, 0.0324082896419704, -0.490533868823201, + -0.079416444198823, 0.0476217167987858, -0.0158973637000186, + "m", "Total", 0.623756169473329, 0.0324082896419704, -0.490533868823201, + -0.079416444198823, 0.0476217167987858, -0.0158973637000186, + "m", "Total", 0.623756169473329, 0.0324082896419704, -0.490533868823201, + -0.0216391957105213, 0.0261871879682561, 0.00227399612886735, + "m", "Total indirect", 0.852146453356244, 0.0122008322744769, + 0.18638041059087, -0.0216391957105213, 0.0261871879682561, 0.00227399612886735, + "m", "Total indirect", 0.852146453356244, 0.0122008322744769, + 0.18638041059087)) @@ -989,7 +1010,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_M_Y - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1000,21 +1021,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "confounders", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "confounders", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1094,7 +1115,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_M_Y - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1105,21 +1126,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "confounders", - processVariable = "facGender")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "confounders", + processVariable = "facGender")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1198,7 +1219,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_moderator - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1209,21 +1230,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1258,16 +1279,16 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.396528663809054, 0.156057671983207, 16, -0.120235495912924, + list(-0.396528663809054, 0.156057671983207, "", -0.120235495912924, "contcor2", "contNormal", "", "", "", 0.393701114822503, 0.140968492316949, -0.85292460702914, -0.0206079744902215, 0.0187008168621928, - 50, -0.00095357881401436, "contcor2", "contGamma", "contNormal", + 16, -0.00095357881401436, "contcor2", "contGamma", "contNormal", "", "", 0.924241577037212, 0.0100279371617226, -0.0950922207265357, -0.0132920341139206, 0.0180760774799312, - 84, 0.00239202168300531, "contcor2", "contGamma", "contNormal", + 50, 0.00239202168300531, "contcor2", "contGamma", "contNormal", "", "", 0.765001164933273, 0.00800221632674874, 0.298919897355134, -0.0215739037623553, 0.0336605425836526, - "", 0.00604331941064863, "contcor2", "contGamma", "contNormal", + 84, 0.00604331941064863, "contcor2", "contGamma", "contNormal", "", "", 0.668004923764089, 0.014090678905758, 0.428887738558792)) @@ -1298,8 +1319,13 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.405319255104091, 0.14161174406949, -0.832158907470919, -0.396174412496076, 0.167790059491526, 84, -0.114192176502275, "Total", 0.427363383697888, 0.143871131417741, -0.79371153460043, - -0.396528663809054, 0.156057671983207, -0.120235495912924, "Total indirect", - 0.393701114822503, 0.140968492316949, -0.85292460702914)) + -0.0215739037623553, 0.0336605425836526, 0.00604331941064863, + "Total indirect", 0.668004923764089, 0.014090678905758, 0.428887738558792, + -0.0215739037623553, 0.0336605425836526, 0.00604331941064863, + "Total indirect", 0.668004923764089, 0.014090678905758, 0.428887738558792, + -0.0215739037623553, 0.0336605425836526, 0.00604331941064863, + "Total indirect", 0.668004923764089, 0.014090678905758, 0.428887738558792 + )) @@ -1315,7 +1341,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number confounder_moderator - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1326,21 +1352,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "confounders", - processVariable = "facGender")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "confounders", + processVariable = "facGender")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1376,14 +1402,15 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.108832957868417, 0.914012147270688, 0.511422552569552, 0, "facGenderm", - "contNormal", "", "", "", 0.0127813022805476, 0.205406628834362, - 2.48980549202216, -0.198988505343462, 0.0527669505225173, -0.0731107774104725, - 1, "facGenderm", "contGamma", "contNormal", "", "", - 0.254969127608045, 0.0642245107185118, -1.1383625440279, -0.0618215513880583, - 0.132974655309278, 0.0355765519606098, "", "facGenderm", "contGamma", - "contNormal", "", "", 0.474043852370205, 0.0496938230074287, - 0.715914973080085)) + list(0.108832957868417, 0.914012147270688, 0.511422552569552, "", "m", + "facGender", "contNormal", "", "", "", 0.0127813022805476, + 0.205406628834362, 2.48980549202216, -0.198988505343462, 0.0527669505225173, + -0.0731107774104725, 0, "m", "facGender", "contGamma", "contNormal", + "", "", 0.254969127608045, 0.0642245107185118, + -1.1383625440279, -0.0618215513880583, 0.132974655309278, 0.0355765519606098, + 1, "m", "facGender", "contGamma", "contNormal", "", + "", 0.474043852370205, 0.0496938230074287, 0.715914973080085 + )) @@ -1406,12 +1433,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0256784470944819, 0.850945103223677, 0.43831177515908, 0, "Total", - 0.037348512364032, 0.210531076754163, 2.08193384994129, 0.13633783786735, - 0.957660371192974, 0.546999104530162, 1, "Total", 0.00903666574412432, - 0.20952490448909, 2.61066390109555, 0.108832957868417, 0.914012147270688, - 0.511422552569552, "Total indirect", 0.0127813022805476, 0.205406628834362, - 2.48980549202216)) + list(0.0256784470944819, 0.850945103223677, 0.43831177515908, "", "m", + "Total", 0.037348512364032, 0.210531076754163, 2.08193384994129, + 0.13633783786735, 0.957660371192974, 0.546999104530162, 0, "m", + "Total", 0.00903666574412432, 0.20952490448909, 2.61066390109555, + 0.0256784470944819, 0.850945103223677, 0.43831177515908, 1, + "m", "Total", 0.037348512364032, 0.210531076754163, 2.08193384994129, + -0.198988505343462, 0.0527669505225173, -0.0731107774104725, + 0, "m", "Total indirect", 0.254969127608045, 0.0642245107185118, + -1.1383625440279, -0.0618215513880583, 0.132974655309278, 0.0355765519606098, + 1, "m", "Total indirect", 0.474043852370205, 0.0496938230074287, + 0.715914973080085)) diff --git a/tests/testthat/test-classic-process-integration-general.R b/tests/testthat/test-classic-process-integration-general.R index 60329f8..1f66d31 100644 --- a/tests/testthat/test-classic-process-integration-general.R +++ b/tests/testthat/test-classic-process-integration-general.R @@ -111,13 +111,20 @@ test_that("Factors with more than two levels work", { table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.830256392676731, 0.671610737591095, 16, -0.0793228275428182, - "facThreeB", "contNormal", "", 0.835982155918959, 0.383136410187729, - -0.207035472050155, -0.419840075271681, 0.605570327467686, 50, - 0.0928651260980023, "facThreeB", "contNormal", "", - 0.722586733024018, 0.261589093174077, 0.355003815224835, -0.539700679220641, - 1.2482888689735, 84, 0.354294094876428, "facThreeB", "contNormal", - "", 0.437310753173408, 0.456128164164641, 0.776742421782455 - )) + "B", "facThree", "contNormal", "", 0.835982155918959, + 0.383136410187729, -0.207035472050155, -0.525905203875692, 1.15334878334855, + 16, 0.313721789736431, "C", "facThree", "contNormal", "", + 0.463967628519699, 0.428388990938096, 0.732329253021736, -0.419840075271681, + 0.605570327467686, 50, 0.0928651260980023, "B", "facThree", + "contNormal", "", 0.722586733024018, 0.261589093174077, + 0.355003815224835, -0.343080242598669, 0.839989902178562, 50, + 0.248454829789947, "C", "facThree", "contNormal", "", + 0.410383843368507, 0.301809154175571, 0.823218336331221, -0.539700679220641, + 1.2482888689735, 84, 0.354294094876428, "B", "facThree", "contNormal", + "", 0.437310753173408, 0.456128164164641, 0.776742421782455, + -0.891019364021505, 1.18974240632265, 84, 0.149361521150572, + "C", "facThree", "contNormal", "", 0.778418345536092, + 0.530816327941977, 0.281380796498216)) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_pathCoefficientsTable"]][["data"]] jaspTools::expect_equal_tables(table, @@ -136,11 +143,17 @@ test_that("Factors with more than two levels work", { table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.830256392676731, 0.671610737591095, 16, -0.0793228275428182, - "Total", 0.835982155918959, 0.383136410187729, -0.207035472050155, + "B", "Total", 0.835982155918959, 0.383136410187729, -0.207035472050155, + -0.525905203875692, 1.15334878334855, 16, 0.313721789736431, + "C", "Total", 0.463967628519699, 0.428388990938096, 0.732329253021736, -0.419840075271681, 0.605570327467686, 50, 0.0928651260980023, - "Total", 0.722586733024018, 0.261589093174077, 0.355003815224835, + "B", "Total", 0.722586733024018, 0.261589093174077, 0.355003815224835, + -0.343080242598669, 0.839989902178562, 50, 0.248454829789947, + "C", "Total", 0.410383843368507, 0.301809154175571, 0.823218336331221, -0.539700679220641, 1.2482888689735, 84, 0.354294094876428, - "Total", 0.437310753173408, 0.456128164164641, 0.776742421782455 + "B", "Total", 0.437310753173408, 0.456128164164641, 0.776742421782455, + -0.891019364021505, 1.18974240632265, 84, 0.149361521150572, + "C", "Total", 0.778418345536092, 0.530816327941977, 0.281380796498216 )) plotName <- results[["results"]][["pathPlotContainer"]][["collection"]][["pathPlotContainer_Model 1"]][["collection"]][["pathPlotContainer_Model 1_conceptPathPlot"]][["data"]] @@ -210,11 +223,16 @@ test_that("Interactions between three-level and two-level factors work", { table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.79179509702597, 0.581685251376472, -0.105054922824749, 0, "facThreeB", - "contNormal", "", 0.76430843174253, 0.350384078288244, - -0.299827901250483, -0.346979683280772, 1.19016835503621, 0.421594335877721, - 1, "facThreeB", "contNormal", "", 0.282320764613395, - 0.39213680721733, 1.07512053986828)) + list(-0.79179509702597, 0.581685251376472, -0.105054922824749, "B", + 0, "facThree", "contNormal", "", 0.76430843174253, + 0.350384078288244, -0.299827901250483, -0.835536962301828, 0.956997866716982, + 0.0607304522075771, "C", 0, "facThree", "contNormal", "", + 0.894346977764828, 0.457287695885765, 0.132805786715827, -0.346979683280772, + 1.19016835503621, 0.421594335877721, "B", 1, "facThree", "contNormal", + "", 0.282320764613395, 0.39213680721733, 1.07512053986828, + -0.273316897248801, 1.39971560986316, 0.563199356307179, "C", + 1, "facThree", "contNormal", "", 0.186975149551964, + 0.426801849500457, 1.31958040239602)) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_pathCoefficientsTable"]][["data"]] jaspTools::expect_equal_tables(table, @@ -232,10 +250,15 @@ test_that("Interactions between three-level and two-level factors work", { table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(-0.79179509702597, 0.581685251376472, -0.105054922824749, 0, "Total", - 0.76430843174253, 0.350384078288244, -0.299827901250483, -0.346979683280772, - 1.19016835503621, 0.421594335877721, 1, "Total", 0.282320764613395, - 0.39213680721733, 1.07512053986828)) + list(-0.79179509702597, 0.581685251376472, -0.105054922824749, "B", + 0, "Total", 0.76430843174253, 0.350384078288244, -0.299827901250483, + -0.835536962301828, 0.956997866716982, 0.0607304522075771, "C", + 0, "Total", 0.894346977764828, 0.457287695885765, 0.132805786715827, + -0.346979683280772, 1.19016835503621, 0.421594335877721, "B", + 1, "Total", 0.282320764613395, 0.39213680721733, 1.07512053986828, + -0.273316897248801, 1.39971560986316, 0.563199356307179, "C", + 1, "Total", 0.186975149551964, 0.426801849500457, 1.31958040239602 + )) plotName <- results[["results"]][["pathPlotContainer"]][["collection"]][["pathPlotContainer_Model 1"]][["collection"]][["pathPlotContainer_Model 1_conceptPathPlot"]][["data"]] testPlot <- results[["state"]][["figures"]][[plotName]][["obj"]] @@ -304,26 +327,27 @@ test_that("Interactions between two-level and three-level factors work", { table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-1.50982658901334, 0.360680618815769, -0.574572985098788, 0, 0, - "facTwoE", "contNormal", "", 0.228549486656783, 0.477178974354487, - -1.20410373461247, -0.481073569262345, 0.385226116469709, -0.0479237263963183, - 1, 0, "facTwoE", "contNormal", "", 0.828324822977639, - 0.220998878695046, -0.216850540958842, -1.50982658901334, 0.360680618815769, - -0.574572985098788, 0, 0, "facTwoE", "contNormal", "", - 0.228549486656783, 0.477178974354487, -1.20410373461247, -1.50982658901334, - 0.360680618815769, -0.574572985098788, 0, 0, "facTwoE", "contNormal", - "", 0.228549486656783, 0.477178974354487, -1.20410373461247, - -0.481073569262345, 0.385226116469709, -0.0479237263963183, - 1, 0, "facTwoE", "contNormal", "", 0.828324822977639, - 0.220998878695046, -0.216850540958842, -1.50982658901334, 0.360680618815769, - -0.574572985098788, 0, 0, "facTwoE", "contNormal", "", - 0.228549486656783, 0.477178974354487, -1.20410373461247, -0.864792807812527, - 0.720584645814155, -0.0721040809991859, 0, 1, "facTwoE", "contNormal", - "", 0.858502237173678, 0.404440455572637, -0.178281079465939, - -0.845713837967434, 1.754804193374, 0.454545177703284, 1, 1, - "facTwoE", "contNormal", "", 0.493239705610856, 0.663409647282805, - 0.685165160870077, -0.864792807812527, 0.720584645814155, -0.0721040809991859, - 0, 1, "facTwoE", "contNormal", "", 0.858502237173678, - 0.404440455572637, -0.178281079465939)) + "E", "facTwo", "contNormal", "", 0.228549486656783, + 0.477178974354487, -1.20410373461247, -0.481073569262345, 0.385226116469709, + -0.0479237263963183, 1, 0, "E", "facTwo", "contNormal", "", + 0.828324822977639, 0.220998878695046, -0.216850540958842, -1.50982658901334, + 0.360680618815769, -0.574572985098788, 0, 0, "E", "facTwo", + "contNormal", "", 0.228549486656783, 0.477178974354487, + -1.20410373461247, -1.50982658901334, 0.360680618815769, -0.574572985098788, + 0, 0, "E", "facTwo", "contNormal", "", 0.228549486656783, + 0.477178974354487, -1.20410373461247, -0.481073569262345, 0.385226116469709, + -0.0479237263963183, 1, 0, "E", "facTwo", "contNormal", "", + 0.828324822977639, 0.220998878695046, -0.216850540958842, -1.50982658901334, + 0.360680618815769, -0.574572985098788, 0, 0, "E", "facTwo", + "contNormal", "", 0.228549486656783, 0.477178974354487, + -1.20410373461247, -0.864792807812527, 0.720584645814155, -0.0721040809991859, + 0, 1, "E", "facTwo", "contNormal", "", 0.858502237173678, + 0.404440455572637, -0.178281079465939, -0.845713837967434, 1.754804193374, + 0.454545177703284, 1, 1, "E", "facTwo", "contNormal", "", + 0.493239705610856, 0.663409647282805, 0.685165160870077, -0.864792807812527, + 0.720584645814155, -0.0721040809991859, 0, 1, "E", "facTwo", + "contNormal", "", 0.858502237173678, 0.404440455572637, + -0.178281079465939)) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_pathCoefficientsTable"]][["data"]] jaspTools::expect_equal_tables(table, @@ -342,23 +366,23 @@ test_that("Interactions between two-level and three-level factors work", { table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-1.50982658901334, 0.360680618815769, -0.574572985098788, 0, 0, - "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, + "E", "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, -0.481073569262345, 0.385226116469709, -0.0479237263963183, - 1, 0, "Total", 0.828324822977639, 0.220998878695046, -0.216850540958842, + 1, 0, "E", "Total", 0.828324822977639, 0.220998878695046, -0.216850540958842, -1.50982658901334, 0.360680618815769, -0.574572985098788, 0, - 0, "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, + 0, "E", "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, -1.50982658901334, 0.360680618815769, -0.574572985098788, 0, - 0, "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, + 0, "E", "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, -0.481073569262345, 0.385226116469709, -0.0479237263963183, - 1, 0, "Total", 0.828324822977639, 0.220998878695046, -0.216850540958842, + 1, 0, "E", "Total", 0.828324822977639, 0.220998878695046, -0.216850540958842, -1.50982658901334, 0.360680618815769, -0.574572985098788, 0, - 0, "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, + 0, "E", "Total", 0.228549486656783, 0.477178974354487, -1.20410373461247, -0.864792807812527, 0.720584645814155, -0.0721040809991859, - 0, 1, "Total", 0.858502237173678, 0.404440455572637, -0.178281079465939, + 0, 1, "E", "Total", 0.858502237173678, 0.404440455572637, -0.178281079465939, -0.845713837967434, 1.754804193374, 0.454545177703284, 1, 1, - "Total", 0.493239705610856, 0.663409647282805, 0.685165160870077, + "E", "Total", 0.493239705610856, 0.663409647282805, 0.685165160870077, -0.864792807812527, 0.720584645814155, -0.0721040809991859, - 0, 1, "Total", 0.858502237173678, 0.404440455572637, -0.178281079465939 + 0, 1, "E", "Total", 0.858502237173678, 0.404440455572637, -0.178281079465939 )) plotName <- results[["results"]][["pathPlotContainer"]][["collection"]][["pathPlotContainer_Model 1"]][["collection"]][["pathPlotContainer_Model 1_conceptPathPlot"]][["data"]] diff --git a/tests/testthat/test-classic-process-integration-hayes-models.R b/tests/testthat/test-classic-process-integration-hayes-models.R index 7d3e6c0..da7fae1 100644 --- a/tests/testthat/test-classic-process-integration-hayes-models.R +++ b/tests/testthat/test-classic-process-integration-hayes-models.R @@ -2,7 +2,7 @@ test_that("Test that model number 1 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -13,19 +13,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -104,7 +104,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 1 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -115,19 +115,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -158,10 +158,10 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0389573762499846, 1.18963781752013, 0.614297596885057, 0, "facGenderm", - "contNormal", "", 0.036378010371507, 0.293546322878014, + list(0.0389573762499846, 1.18963781752013, 0.614297596885057, 0, "m", + "facGender", "contNormal", "", 0.036378010371507, 0.293546322878014, 2.09267685884226, -0.258993824622392, 0.891686616803016, 0.316346396090312, - 1, "facGenderm", "contNormal", "", 0.281180548821822, + 1, "m", "facGender", "contNormal", "", 0.281180548821822, 0.293546322917622, 1.07767112510923)) @@ -181,10 +181,11 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0389573762499846, 1.18963781752013, 0.614297596885057, 0, "Total", - 0.036378010371507, 0.293546322878014, 2.09267685884226, -0.258993824622392, - 0.891686616803016, 0.316346396090312, 1, "Total", 0.281180548821822, - 0.293546322917622, 1.07767112510923)) + list(0.0389573762499846, 1.18963781752013, 0.614297596885057, 0, "m", + "Total", 0.036378010371507, 0.293546322878014, 2.09267685884226, + -0.258993824622392, 0.891686616803016, 0.316346396090312, 1, + "m", "Total", 0.281180548821822, 0.293546322917622, 1.07767112510923 + )) @@ -200,7 +201,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 2 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -211,21 +212,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -341,7 +342,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 2 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -352,21 +353,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -405,20 +406,20 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.161065462166927, 1.33098043660259, 16, 0.584957487217831, 0, - "facGenderm", "contNormal", "", 0.124339818079468, + "m", "facGender", "contNormal", "", 0.124339818079468, 0.380630947950723, 1.5368101053453, -0.358875044036943, 1.00789206259432, - 16, 0.32450850927869, 1, "facGenderm", "contNormal", "", + 16, 0.32450850927869, 1, "m", "facGender", "contNormal", "", 0.352008831944638, 0.348671485142623, 0.930699879704677, 0.0267424851786442, - 1.18684632303876, 50, 0.606794404108703, 0, "facGenderm", "contNormal", - "", 0.0403326883329289, 0.295950294753085, 2.0503253920222, - -0.238349615464404, 0.931040467803529, 50, 0.346345426169562, - 1, "facGenderm", "contNormal", "", 0.245646338204931, - 0.298319278438771, 1.16098908519132, -0.0593588649528981, 1.32414010991594, - 84, 0.632390622481523, 0, "facGenderm", "contNormal", "", - 0.0731682258788371, 0.352939897309773, 1.79177992429254, -0.399560650456646, - 1.14344393954141, 84, 0.371941644542382, 1, "facGenderm", "contNormal", - "", 0.34471012405264, 0.393630852956758, 0.944899622955218 - )) + 1.18684632303876, 50, 0.606794404108703, 0, "m", "facGender", + "contNormal", "", 0.0403326883329289, 0.295950294753085, + 2.0503253920222, -0.238349615464404, 0.931040467803529, 50, + 0.346345426169562, 1, "m", "facGender", "contNormal", "", + 0.245646338204931, 0.298319278438771, 1.16098908519132, -0.0593588649528981, + 1.32414010991594, 84, 0.632390622481523, 0, "m", "facGender", + "contNormal", "", 0.0731682258788371, 0.352939897309773, + 1.79177992429254, -0.399560650456646, 1.14344393954141, 84, + 0.371941644542382, 1, "m", "facGender", "contNormal", "", + 0.34471012405264, 0.393630852956758, 0.944899622955218)) @@ -442,17 +443,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.161065462166927, 1.33098043660259, 16, 0.584957487217831, 0, - "Total", 0.124339818079468, 0.380630947950723, 1.5368101053453, + "m", "Total", 0.124339818079468, 0.380630947950723, 1.5368101053453, -0.358875044036943, 1.00789206259432, 16, 0.32450850927869, - 1, "Total", 0.352008831944638, 0.348671485142623, 0.930699879704677, + 1, "m", "Total", 0.352008831944638, 0.348671485142623, 0.930699879704677, 0.0267424851786442, 1.18684632303876, 50, 0.606794404108703, - 0, "Total", 0.0403326883329289, 0.295950294753085, 2.0503253920222, + 0, "m", "Total", 0.0403326883329289, 0.295950294753085, 2.0503253920222, -0.238349615464404, 0.931040467803529, 50, 0.346345426169562, - 1, "Total", 0.245646338204931, 0.298319278438771, 1.16098908519132, + 1, "m", "Total", 0.245646338204931, 0.298319278438771, 1.16098908519132, -0.0593588649528981, 1.32414010991594, 84, 0.632390622481523, - 0, "Total", 0.0731682258788371, 0.352939897309773, 1.79177992429254, + 0, "m", "Total", 0.0731682258788371, 0.352939897309773, 1.79177992429254, -0.399560650456646, 1.14344393954141, 84, 0.371941644542382, - 1, "Total", 0.34471012405264, 0.393630852956758, 0.944899622955218 + 1, "m", "Total", 0.34471012405264, 0.393630852956758, 0.944899622955218 )) @@ -469,7 +470,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 3 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -480,21 +481,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -615,7 +616,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 3 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -626,21 +627,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -679,20 +680,20 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.879096135794025, 0.893322475661732, 16, 0.00711316993385364, - 0, "facGenderm", "contNormal", "", 0.987448457029138, + 0, "m", "facGender", "contNormal", "", 0.987448457029138, 0.452155913434218, 0.0157316751202647, -0.226236100911908, 1.45144461323237, - 16, 0.61260425616023, 1, "facGenderm", "contNormal", "", + 16, 0.61260425616023, 1, "m", "facGender", "contNormal", "", 0.152327153088125, 0.427987638389687, 1.43135969642761, -0.0706048609407803, - 1.07522417225395, 50, 0.502309655656585, 0, "facGenderm", "contNormal", - "", 0.0857196943308809, 0.292308696035459, 1.71842186862498, - -0.295309938992243, 0.864575094385034, 50, 0.284632577696396, - 1, "facGenderm", "contNormal", "", 0.336080006943378, - 0.295894476257294, 0.961939476858953, 0.299944751940104, 1.86556713860983, - 84, 1.08275594527497, 0, "facGenderm", "contNormal", "", - 0.00670905737302419, 0.399400805070695, 2.7109508331695, -1.0144280267332, - 0.814826886209518, 84, -0.0998005702618417, 1, "facGenderm", - "contNormal", "", 0.830653424048315, 0.466655236364456, - -0.21386360311598)) + 1.07522417225395, 50, 0.502309655656585, 0, "m", "facGender", + "contNormal", "", 0.0857196943308809, 0.292308696035459, + 1.71842186862498, -0.295309938992243, 0.864575094385034, 50, + 0.284632577696396, 1, "m", "facGender", "contNormal", "", + 0.336080006943378, 0.295894476257294, 0.961939476858953, 0.299944751940104, + 1.86556713860983, 84, 1.08275594527497, 0, "m", "facGender", + "contNormal", "", 0.00670905737302419, 0.399400805070695, + 2.7109508331695, -1.0144280267332, 0.814826886209518, 84, -0.0998005702618417, + 1, "m", "facGender", "contNormal", "", 0.830653424048315, + 0.466655236364456, -0.21386360311598)) @@ -721,17 +722,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.879096135794025, 0.893322475661732, 16, 0.00711316993385364, - 0, "Total", 0.987448457029138, 0.452155913434218, 0.0157316751202647, + 0, "m", "Total", 0.987448457029138, 0.452155913434218, 0.0157316751202647, -0.226236100911908, 1.45144461323237, 16, 0.61260425616023, - 1, "Total", 0.152327153088125, 0.427987638389687, 1.43135969642761, + 1, "m", "Total", 0.152327153088125, 0.427987638389687, 1.43135969642761, -0.0706048609407803, 1.07522417225395, 50, 0.502309655656585, - 0, "Total", 0.0857196943308809, 0.292308696035459, 1.71842186862498, + 0, "m", "Total", 0.0857196943308809, 0.292308696035459, 1.71842186862498, -0.295309938992243, 0.864575094385034, 50, 0.284632577696396, - 1, "Total", 0.336080006943378, 0.295894476257294, 0.961939476858953, + 1, "m", "Total", 0.336080006943378, 0.295894476257294, 0.961939476858953, 0.299944751940104, 1.86556713860983, 84, 1.08275594527497, 0, - "Total", 0.00670905737302419, 0.399400805070695, 2.7109508331695, + "m", "Total", 0.00670905737302419, 0.399400805070695, 2.7109508331695, -1.0144280267332, 0.814826886209518, 84, -0.0998005702618417, - 1, "Total", 0.830653424048315, 0.466655236364456, -0.21386360311598 + 1, "m", "Total", 0.830653424048315, 0.466655236364456, -0.21386360311598 )) @@ -748,7 +749,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 4 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -759,19 +760,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -842,7 +843,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 4 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -853,19 +854,19 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -893,12 +894,12 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0622024991965639, 0.868598726146002, 0.465400612671283, "facGenderm", - "contNormal", "", "", "", 0.0236768306591097, 0.205717103301435, - 2.26233310309321, -0.0219205602251843, 0.0213787048213383, -0.000270927701922977, - "facGenderm", "debCollin1", "contNormal", "", "", - 0.980431952510507, 0.0110459338508416, -0.0245273695806476 - )) + list(0.0622024991965639, 0.868598726146002, 0.465400612671283, "m", + "facGender", "contNormal", "", "", "", 0.0236768306591097, + 0.205717103301435, 2.26233310309321, -0.0219205602251843, 0.0213787048213383, + -0.000270927701922977, "m", "facGender", "debCollin1", "contNormal", + "", "", 0.980431952510507, 0.0110459338508416, + -0.0245273695806476)) @@ -916,11 +917,13 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0625107998260226, 0.867748570112698, 0.46512968496936, "Total", - 0.0235575795563017, 0.205421573212132, 2.26426892607348, -0.0219205602251843, - 0.0213787048213383, -0.000270927701922977, "Total indirect", - 0.980431952510507, 0.0110459338508416, -0.0245273695806476 - )) + list(0.0625107998260226, 0.867748570112698, 0.46512968496936, "m", + "Total", 0.0235575795563017, 0.205421573212132, 2.26426892607348, + 0.0625107998260226, 0.867748570112698, 0.46512968496936, "m", + "Total", 0.0235575795563017, 0.205421573212132, 2.26426892607348, + -0.0219205602251843, 0.0213787048213383, -0.000270927701922977, + "m", "Total indirect", 0.980431952510507, 0.0110459338508416, + -0.0245273695806476)) @@ -936,7 +939,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 5 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -947,21 +950,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1051,7 +1054,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 5 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1062,21 +1065,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1110,14 +1113,15 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0389876732996416, 1.18993239606349, 0.614460034681565, 0, "facGenderm", - "contNormal", "", "", "", 0.0363715155500868, 0.293613742865265, - 2.09274957188748, -0.261259762109523, 0.89279798255157, 0.315769110221023, - 1, "facGenderm", "contNormal", "", "", "", 0.283470138708214, - 0.294407895697103, 1.07255652730828, -0.0214503308222069, 0.0220182200677286, - 0.000283944622760887, "", "facGenderm", "debCollin1", "contNormal", - "", "", 0.979571843382763, 0.0110891198085296, - 0.0256056952818275)) + list(0.0389876732996416, 1.18993239606349, 0.614460034681565, 0, "m", + "facGender", "contNormal", "", "", "", 0.0363715155500868, + 0.293613742865265, 2.09274957188748, -0.261259762109523, 0.89279798255157, + 0.315769110221023, 1, "m", "facGender", "contNormal", "", "", + "", 0.283470138708214, 0.294407895697103, 1.07255652730828, + -0.0214503308222069, 0.0220182200677286, 0.000283944622760887, + "", "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979571843382763, 0.0110891198085296, 0.0256056952818275 + )) @@ -1140,11 +1144,14 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.038393337805159, 1.19109462080349, 0.614743979304326, 0, "Total", - 0.0365705663010119, 0.294061853200032, 2.0905261005961, -0.259723189210586, - 0.891829298898155, 0.316053054843784, 1, "Total", 0.28199144682767, - 0.293768787894074, 1.07585648260817, -0.0214503308222069, 0.0220182200677286, - 0.000283944622760887, "Total indirect", 0.979571843382763, 0.0110891198085296, + list(0.038393337805159, 1.19109462080349, 0.614743979304326, 0, "m", + "Total", 0.0365705663010119, 0.294061853200032, 2.0905261005961, + -0.259723189210586, 0.891829298898155, 0.316053054843784, 1, + "m", "Total", 0.28199144682767, 0.293768787894074, 1.07585648260817, + 0.038393337805159, 1.19109462080349, 0.614743979304326, "", + "m", "Total", 0.0365705663010119, 0.294061853200032, 2.0905261005961, + -0.0214503308222069, 0.0220182200677286, 0.000283944622760887, + "", "m", "Total indirect", 0.979571843382763, 0.0110891198085296, 0.0256056952818275)) @@ -1161,7 +1168,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 7 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1172,21 +1179,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1259,11 +1266,11 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.553609428213643, 0.0689480737953325, -0.592360175476169, -0.175382476672515, 0.095909680846968, 84, -0.0397363979127734, "Total", 0.565862745895811, 0.0692084547622816, -0.574155253852448, - -0.0129246594659768, 0.0157306912130232, 16, 0.00140301587352322, - "Total indirect", 0.847799779268132, 0.00731017276466042, 0.191926500055624, - -0.0215673931237313, 0.0263996712180194, 50, 0.00241613904714404, - "Total indirect", 0.843475500378468, 0.0122367208581659, 0.197449878537653, - -0.0314505030469635, 0.0384941714999988, 84, 0.00352183422651761, + -0.0314505030469635, 0.0384941714999988, 0.00352183422651761, + "Total indirect", 0.84353402088629, 0.0178433570970378, 0.197375090761496, + -0.0314505030469635, 0.0384941714999988, 0.00352183422651761, + "Total indirect", 0.84353402088629, 0.0178433570970378, 0.197375090761496, + -0.0314505030469635, 0.0384941714999988, 0.00352183422651761, "Total indirect", 0.84353402088629, 0.0178433570970378, 0.197375090761496 )) @@ -1281,7 +1288,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 7 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1292,21 +1299,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1339,14 +1346,15 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0622024992016066, 0.86859872614096, 0.465400612671283, "", "facGenderm", - "contNormal", "", "", "", 0.0236768306573629, 0.205717103298863, - 2.26233310312151, -0.0122966566756132, 0.0126066279449722, 0.000154985634679501, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.980536995391145, 0.00635299546752372, 0.0243956784593633, - -0.0445413897110322, 0.0434397906359828, -0.000550799537524732, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.980421548403501, 0.022444591084581, -0.0245404131199842)) + list(0.0622024992016066, 0.86859872614096, 0.465400612671283, "", "m", + "facGender", "contNormal", "", "", "", 0.0236768306573629, + 0.205717103298863, 2.26233310312151, -0.0122966566756132, 0.0126066279449722, + 0.000154985634679501, 0, "m", "facGender", "debCollin1", "contNormal", + "", "", 0.980536995391145, 0.00635299546752372, + 0.0243956784593633, -0.0445413897110322, 0.0434397906359828, + -0.000550799537524732, 1, "m", "facGender", "debCollin1", "contNormal", + "", "", 0.980421548403501, 0.022444591084581, + -0.0245404131199842)) @@ -1370,14 +1378,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0615025124506953, 0.86960868416123, 0.465555598305963, 0, "Total", - 0.0239270977275898, 0.20615332171529, 2.25829782626022, 0.0616103170585399, - 0.868089309208977, 0.464849813133758, 1, "Total", 0.0238570388065877, - 0.205738217261093, 2.25942374402826, -0.0122966566756132, 0.0126066279449722, - 0.000154985634679501, 0, "Total indirect", 0.980536995391145, - 0.00635299546752372, 0.0243956784593633, -0.0445413897110322, - 0.0434397906359828, -0.000550799537524732, 1, "Total indirect", - 0.980421548403501, 0.022444591084581, -0.0245404131199842)) + list(0.0615025124506953, 0.86960868416123, 0.465555598305963, "", "m", + "Total", 0.0239270977275898, 0.20615332171529, 2.25829782626022, + 0.0616103170585399, 0.868089309208977, 0.464849813133758, 0, + "m", "Total", 0.0238570388065877, 0.205738217261093, 2.25942374402826, + 0.0615025124506953, 0.86960868416123, 0.465555598305963, 1, + "m", "Total", 0.0239270977275898, 0.20615332171529, 2.25829782626022, + -0.0122966566756132, 0.0126066279449722, 0.000154985634679501, + 0, "m", "Total indirect", 0.980536995391145, 0.00635299546752372, + 0.0243956784593633, -0.0445413897110322, 0.0434397906359828, + -0.000550799537524732, 1, "m", "Total indirect", 0.980421548403501, + 0.022444591084581, -0.0245404131199842)) @@ -1393,7 +1404,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 8 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1404,23 +1415,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1531,7 +1542,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 8 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1542,23 +1553,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1592,17 +1603,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0389876734574709, 1.18993239590566, 0.614460034681565, 0, "facGenderm", - "contNormal", "", "", "", 0.036371515498824, 0.293613742784738, - 2.09274957246144, -0.261259761975917, 0.892797982417963, 0.315769110221023, - 1, "facGenderm", "contNormal", "", "", "", 0.283470138596737, - 0.294407895628935, 1.07255652755662, -0.0126694778620506, 0.0123445955233525, - -0.00016244116934909, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.979691262161339, 0.00638125842686675, - -0.0254559772513163, -0.0435841095532679, 0.0447386598161608, - 0.000577275131446476, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.979560003906632, 0.0225317327425676, - 0.0256205387327301)) + list(0.0389876734574709, 1.18993239590566, 0.614460034681565, 0, "m", + "facGender", "contNormal", "", "", "", 0.036371515498824, + 0.293613742784738, 2.09274957246144, -0.261259761975917, 0.892797982417963, + 0.315769110221023, 1, "m", "facGender", "contNormal", "", "", + "", 0.283470138596737, 0.294407895628935, 1.07255652755662, + -0.0126694778620506, 0.0123445955233525, -0.00016244116934909, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979691262161339, 0.00638125842686675, -0.0254559772513163, + -0.0435841095532679, 0.0447386598161608, 0.000577275131446476, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979560003906632, 0.0225317327425676, 0.0256205387327301 + )) @@ -1630,17 +1642,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0389573728877487, 1.18963781413668, 0.614297593512216, 0, "Total", - 0.0363780113944387, 0.293546322872603, 2.09267684739085, -0.2589938353015, - 0.891686606006439, 0.31634638535247, 1, "Total", 0.281180565102892, - 0.293546322887655, 1.07767108863953, 0.0389573728877487, 1.18963781413668, - 0.614297593512216, 0, "Total", 0.0363780113944387, 0.293546322872603, - 2.09267684739085, -0.2589938353015, 0.891686606006439, 0.31634638535247, - 1, "Total", 0.281180565102892, 0.293546322887655, 1.07767108863953, + list(0.0389573728877487, 1.18963781413668, 0.614297593512216, 0, "m", + "Total", 0.0363780113944387, 0.293546322872603, 2.09267684739085, + -0.2589938353015, 0.891686606006439, 0.31634638535247, 1, "m", + "Total", 0.281180565102892, 0.293546322887655, 1.07767108863953, + 0.0389573728877487, 1.18963781413668, 0.614297593512216, 0, + "m", "Total", 0.0363780113944387, 0.293546322872603, 2.09267684739085, + -0.2589938353015, 0.891686606006439, 0.31634638535247, 1, "m", + "Total", 0.281180565102892, 0.293546322887655, 1.07767108863953, -0.0126694778620506, 0.0123445955233525, -0.00016244116934909, - 0, "Total indirect", 0.979691262161339, 0.00638125842686675, + 0, "m", "Total indirect", 0.979691262161339, 0.00638125842686675, -0.0254559772513163, -0.0435841095532679, 0.0447386598161608, - 0.000577275131446476, 1, "Total indirect", 0.979560003906632, + 0.000577275131446476, 1, "m", "Total indirect", 0.979560003906632, 0.0225317327425676, 0.0256205387327301)) @@ -1657,7 +1670,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 9 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1668,23 +1681,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1798,23 +1811,23 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.555570583522043, 0.0690088327060871, -0.589433389655344, -0.175369820469393, 0.0966134828379493, 84, 84, -0.0393781688157218, "Total", 0.57035189990021, 0.0693847707031129, -0.567533313386811, - -0.0112823578372222, 0.013697450136648, 16, 16, 0.00120754614971293, - "Total indirect", 0.849706592315187, 0.00637251708983118, 0.189492806796838, - -0.0217864646337114, 0.0265801048309022, 50, 16, 0.00239682009859541, - "Total indirect", 0.845977608319149, 0.0123386373030635, 0.194253225840452, - -0.033959347798064, 0.0413488707200262, 84, 16, 0.00369476146098112, - "Total indirect", 0.847492362211712, 0.019211633252476, 0.192318966973041, - -0.0125633341927989, 0.015146747875033, 16, 50, 0.00129170684111702, - "Total indirect", 0.855011730868061, 0.00706902838174719, 0.182727635448785, - -0.0221379396607771, 0.0270999012407761, 50, 50, 0.0024809807899995, - "Total indirect", 0.843423688677146, 0.0125609045089438, 0.197516093545091, - -0.0339443314234804, 0.0415021757282509, 84, 50, 0.0037789221523852, - "Total indirect", 0.844344725040594, 0.0192469116133877, 0.19633914408152, - -0.0155176014689822, 0.0182983136477349, 16, 84, 0.00139035608937636, - "Total indirect", 0.87195986547754, 0.00862666747538545, 0.161169547028847, - -0.023550280163801, 0.0287095402403187, 50, 84, 0.00257963003825885, - "Total indirect", 0.846572070896425, 0.0133318318133237, 0.193494043007712, - -0.0346050743640666, 0.0423602171653558, 84, 84, 0.00387757140064455, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, + "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125, + -0.0346050743640666, 0.0423602171653558, 0.00387757140064455, "Total indirect", 0.843444867042652, 0.0196343637272202, 0.197489027631125 )) @@ -1832,7 +1845,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 9 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -1843,23 +1856,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -1900,25 +1913,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0622024991960345, 0.868598726146532, "", 0.465400612671283, - "", "facGenderm", "contNormal", "", "", "", 0.0236768306592932, + "", "m", "facGender", "contNormal", "", "", "", 0.0236768306592932, 0.205717103301706, 2.26233310309024, -0.0234805716729502, 0.0240745476005247, - 16, 0.000296987963787239, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980469365838342, 0.0121316308994919, + 16, 0.000296987963787239, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980469365838342, 0.0121316308994919, 0.0244804648482734, -0.0327171718179227, 0.031908672568233, - 16, -0.000404249624844824, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980437785068855, 0.0164864877354676, + 16, -0.000404249624844824, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980437785068855, 0.0164864877354676, -0.0245200573543118, -0.0138827148944902, 0.0142331283695509, - 50, 0.000175206737530344, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980511668942837, 0.00717254079304909, + 50, 0.000175206737530344, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980511668942837, 0.00717254079304909, 0.0244274299143948, -0.0425413075557195, 0.0414892458535161, - 50, -0.000526030851101718, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980422891086795, 0.0214367595711089, + 50, -0.000526030851101718, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980422891086795, 0.0214367595711089, -0.0245387298092697, -0.00306290247311634, 0.00312782336911389, - 84, 3.24604479987777e-05, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.983601636527509, 0.00157929581641854, + 84, 3.24604479987777e-05, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.983601636527509, 0.00157929581641854, 0.0205537478547814, -0.0540879144054593, 0.0527503601241927, - 84, -0.000668777140633285, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980423767086204, 0.0272551626898195, + 84, -0.000668777140633285, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980423767086204, 0.0272551626898195, -0.0245376315762404)) @@ -1947,31 +1960,33 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0605315476462935, 0.870863653623847, 16, 0.46569760063507, 0, - "Total", 0.0242729391292758, 0.206721172523921, 2.25278134285534, + list(0.0605315476462935, 0.870863653623847, "", 0.46569760063507, "", + "m", "Total", 0.0242729391292758, 0.206721172523921, 2.25278134285534, 0.0622345831299339, 0.867758142962943, 16, 0.464996363046438, - 1, "Total", 0.0236469844630725, 0.205494480048326, 2.2628168062572, - 0.0613836654269441, 0.869767973390683, 50, 0.465575819408813, - 0, "Total", 0.0239694305294997, 0.206224276144912, 2.25761888033811, + 0, "m", "Total", 0.0236469844630725, 0.205494480048326, 2.2628168062572, + 0.0613836654269441, 0.869767973390683, 16, 0.465575819408813, + 1, "m", "Total", 0.0239694305294997, 0.206224276144912, 2.25761888033811, 0.0617397111812278, 0.868009452459135, 50, 0.464874581820181, - 1, "Total", 0.0238131494725367, 0.205684835955574, 2.26013055197025, - 0.0620841183034912, 0.868782027935073, 84, 0.465433073119282, - 0, "Total", 0.02371935861357, 0.205794064583511, 2.26164478582622, + 0, "m", "Total", 0.0238131494725367, 0.205684835955574, 2.26013055197025, + 0.0620841183034912, 0.868782027935073, 50, 0.465433073119282, + 1, "m", "Total", 0.02371935861357, 0.205794064583511, 2.26164478582622, 0.0608591197226557, 0.868604551338644, 84, 0.46473183553065, - 1, "Total", 0.0241139573028737, 0.206061294489945, 2.25530872588654, + 0, "m", "Total", 0.0241139573028737, 0.206061294489945, 2.25530872588654, + 0.0605315476462935, 0.870863653623847, 84, 0.46569760063507, + 1, "m", "Total", 0.0242729391292758, 0.206721172523921, 2.25278134285534, -0.0234805716729502, 0.0240745476005247, 16, 0.000296987963787239, - 0, "Total indirect", 0.980469365838342, 0.0121316308994919, + 0, "m", "Total indirect", 0.980469365838342, 0.0121316308994919, 0.0244804648482734, -0.0327171718179227, 0.031908672568233, - 16, -0.000404249624844824, 1, "Total indirect", 0.980437785068855, + 16, -0.000404249624844824, 1, "m", "Total indirect", 0.980437785068855, 0.0164864877354676, -0.0245200573543118, -0.0138827148944902, - 0.0142331283695509, 50, 0.000175206737530344, 0, "Total indirect", + 0.0142331283695509, 50, 0.000175206737530344, 0, "m", "Total indirect", 0.980511668942837, 0.00717254079304909, 0.0244274299143948, -0.0425413075557195, 0.0414892458535161, 50, -0.000526030851101718, - 1, "Total indirect", 0.980422891086795, 0.0214367595711089, + 1, "m", "Total indirect", 0.980422891086795, 0.0214367595711089, -0.0245387298092697, -0.00306290247311634, 0.00312782336911389, - 84, 3.24604479987777e-05, 0, "Total indirect", 0.983601636527509, + 84, 3.24604479987777e-05, 0, "m", "Total indirect", 0.983601636527509, 0.00157929581641854, 0.0205537478547814, -0.0540879144054593, - 0.0527503601241927, 84, -0.000668777140633285, 1, "Total indirect", + 0.0527503601241927, 84, -0.000668777140633285, 1, "m", "Total indirect", 0.980423767086204, 0.0272551626898195, -0.0245376315762404 )) @@ -1989,7 +2004,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 10 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -2000,27 +2015,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -2216,7 +2231,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 10 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -2227,27 +2242,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -2289,38 +2304,39 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.160966936882472, 1.33182551367605, 16, 0.58542928839679, 0, - "facGenderm", "contNormal", "", "", "", 0.124224648229917, + "m", "facGender", "contNormal", "", "", "", 0.124224648229917, 0.380821398335245, 1.53728044420819, -0.360278235735231, 1.0080108561311, - 16, 0.323866310197933, 1, "facGenderm", "contNormal", "", "", - "", 0.353498436753044, 0.349059753816708, 0.927824839892589, + 16, 0.323866310197933, 1, "m", "facGender", "contNormal", "", + "", "", 0.353498436753044, 0.349059753816708, 0.927824839892589, 0.0268555790493255, 1.18728990326231, 50, 0.607072741155815, - 0, "facGenderm", "contNormal", "", "", "", 0.0402979555318521, + 0, "m", "facGender", "contNormal", "", "", "", 0.0402979555318521, 0.296034604045365, 2.05068168673547, -0.240696017862408, 0.931715543776325, - 50, 0.345509762956958, 1, "facGenderm", "contNormal", "", "", - "", 0.248007295971046, 0.299090077901065, 1.15520302572942, + 50, 0.345509762956958, 1, "m", "facGender", "contNormal", "", + "", "", 0.248007295971046, 0.299090077901065, 1.15520302572942, -0.0593069506129866, 1.32419133035509, 84, 0.632442189871049, - 0, "facGenderm", "contNormal", "", "", "", 0.0731446713359649, + 0, "m", "facGender", "contNormal", "", "", "", 0.0731446713359649, 0.352939720291018, 1.79192693117557, -0.402473478079912, 1.1442319014243, - 84, 0.370879211672192, 1, "facGenderm", "contNormal", "", "", - "", 0.347245173937405, 0.394574949260401, 0.939946168319544, + 84, 0.370879211672192, 1, "m", "facGender", "contNormal", "", + "", "", 0.347245173937405, 0.394574949260401, 0.939946168319544, -0.0244283163085191, 0.0234847144242383, 16, -0.000471800942140402, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.969209589795566, 0.0122229365209487, -0.0385996394018566, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.969209589795566, 0.0122229365209487, -0.0385996394018566, -0.0318355292516048, 0.033119927916608, 16, 0.000642199332501614, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.969085398826703, 0.0165705741739576, 0.0387554061651586, -0.0144875372254733, - 0.0139308636248141, 50, -0.000278336800329581, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.969374551226098, - 0.00724972526904785, -0.0383927376555797, -0.0413456780600054, - 0.0430170050086302, 50, 0.000835663474312435, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.969026515646823, - 0.0215214880819438, 0.0388292608359895, -0.00379203726602771, - 0.00368890300389759, 84, -5.15671310650621e-05, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.978443309502044, - 0.00190843819808272, -0.0270205926064927, -0.0525714502863859, - 0.0546963165735398, 84, 0.00106243314357695, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.969029984491913, - 0.0273647290730952, 0.0388249100051032)) + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.969085398826703, 0.0165705741739576, 0.0387554061651586, + -0.0144875372254733, 0.0139308636248141, 50, -0.000278336800329581, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.969374551226098, 0.00724972526904785, -0.0383927376555797, + -0.0413456780600054, 0.0430170050086302, 50, 0.000835663474312435, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.969026515646823, 0.0215214880819438, 0.0388292608359895, + -0.00379203726602771, 0.00368890300389759, 84, -5.15671310650621e-05, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.978443309502044, 0.00190843819808272, -0.0270205926064927, + -0.0525714502863859, 0.0546963165735398, 84, 0.00106243314357695, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.969029984491913, 0.0273647290730952, 0.0388249100051032 + )) @@ -2358,42 +2374,42 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.161065461858297, 1.3309804367676, 16, 0.58495748745465, 0, - "Total", 0.124339817890827, 0.380630947914085, 1.5368101061154, + "m", "Total", 0.124339817890827, 0.380630947914085, 1.5368101061154, -0.358875043779641, 1.00789206284051, 16, 0.324508509530435, - 1, "Total", 0.352008831567136, 0.348671485139787, 0.930699880434257, + 1, "m", "Total", 0.352008831567136, 0.348671485139787, 0.930699880434257, 0.026742485486911, 1.18684632322406, 50, 0.606794404355486, - 0, "Total", 0.0403326882304174, 0.295950294721715, 2.05032539307339, + 0, "m", "Total", 0.0403326882304174, 0.295950294721715, 2.05032539307339, -0.238349615156111, 0.931040468018653, 50, 0.346345426431271, - 1, "Total", 0.245646337810546, 0.298319278415003, 1.16098908616109, + 1, "m", "Total", 0.245646337810546, 0.298319278415003, 1.16098908616109, -0.0593588646633562, 1.32414011014332, 84, 0.632390622739984, - 0, "Total", 0.0731682257485846, 0.352939897293916, 1.79177992510536, + 0, "m", "Total", 0.0731682257485846, 0.352939897293916, 1.79177992510536, -0.399560650103491, 1.14344393973503, 84, 0.371941644815769, - 1, "Total", 0.344710123648147, 0.39363085291606, 0.944899623747441, + 1, "m", "Total", 0.344710123648147, 0.39363085291606, 0.944899623747441, -0.161065461858297, 1.3309804367676, 16, 0.58495748745465, 0, - "Total", 0.124339817890827, 0.380630947914085, 1.5368101061154, + "m", "Total", 0.124339817890827, 0.380630947914085, 1.5368101061154, -0.358875043779641, 1.00789206284051, 16, 0.324508509530435, - 1, "Total", 0.352008831567136, 0.348671485139787, 0.930699880434257, + 1, "m", "Total", 0.352008831567136, 0.348671485139787, 0.930699880434257, 0.026742485486911, 1.18684632322406, 50, 0.606794404355486, - 0, "Total", 0.0403326882304174, 0.295950294721715, 2.05032539307339, + 0, "m", "Total", 0.0403326882304174, 0.295950294721715, 2.05032539307339, -0.238349615156111, 0.931040468018653, 50, 0.346345426431271, - 1, "Total", 0.245646337810546, 0.298319278415003, 1.16098908616109, + 1, "m", "Total", 0.245646337810546, 0.298319278415003, 1.16098908616109, -0.0593588646633562, 1.32414011014332, 84, 0.632390622739984, - 0, "Total", 0.0731682257485846, 0.352939897293916, 1.79177992510536, + 0, "m", "Total", 0.0731682257485846, 0.352939897293916, 1.79177992510536, -0.399560650103491, 1.14344393973503, 84, 0.371941644815769, - 1, "Total", 0.344710123648147, 0.39363085291606, 0.944899623747441, + 1, "m", "Total", 0.344710123648147, 0.39363085291606, 0.944899623747441, -0.0244283163085191, 0.0234847144242383, 16, -0.000471800942140402, - 0, "Total indirect", 0.969209589795566, 0.0122229365209487, + 0, "m", "Total indirect", 0.969209589795566, 0.0122229365209487, -0.0385996394018566, -0.0318355292516048, 0.033119927916608, - 16, 0.000642199332501614, 1, "Total indirect", 0.969085398826703, + 16, 0.000642199332501614, 1, "m", "Total indirect", 0.969085398826703, 0.0165705741739576, 0.0387554061651586, -0.0144875372254733, - 0.0139308636248141, 50, -0.000278336800329581, 0, "Total indirect", + 0.0139308636248141, 50, -0.000278336800329581, 0, "m", "Total indirect", 0.969374551226098, 0.00724972526904785, -0.0383927376555797, -0.0413456780600054, 0.0430170050086302, 50, 0.000835663474312435, - 1, "Total indirect", 0.969026515646823, 0.0215214880819438, + 1, "m", "Total indirect", 0.969026515646823, 0.0215214880819438, 0.0388292608359895, -0.00379203726602771, 0.00368890300389759, - 84, -5.15671310650621e-05, 0, "Total indirect", 0.978443309502044, + 84, -5.15671310650621e-05, 0, "m", "Total indirect", 0.978443309502044, 0.00190843819808272, -0.0270205926064927, -0.0525714502863859, - 0.0546963165735398, 84, 0.00106243314357695, 1, "Total indirect", + 0.0546963165735398, 84, 0.00106243314357695, 1, "m", "Total indirect", 0.969029984491913, 0.0273647290730952, 0.0388249100051032)) @@ -2410,7 +2426,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 11 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -2421,23 +2437,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -2556,23 +2572,23 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.541026398758971, 0.0695098371365996, -0.611261614564372, -0.175370090297307, 0.0962926193307853, 84, 84, -0.0395387354832607, "Total", 0.568325096064287, 0.0693029850984337, -0.570519948413511, - -0.0182490048294261, 0.022270434192922, 16, 16, 0.00201071468174793, - "Total indirect", 0.845768438730284, 0.01033678152812, 0.194520381056523, - -0.0189871780752168, 0.0231274055423588, 50, 16, 0.00207011373357102, - "Total indirect", 0.847208495009883, 0.0107437136472328, 0.192681395050417, - -0.0212171785979163, 0.0254870590963387, 84, 16, 0.00213494024921119, - "Total indirect", 0.857790538899785, 0.0119145652835083, 0.17918742299111, - -0.00635092664172057, 0.00674081319211249, 16, 50, 0.00019494327519596, - "Total indirect", 0.953453987043079, 0.00333979091888908, 0.0583699039641691, - -0.0135227618404186, 0.0164655116432874, 50, 50, 0.0014713749014344, - "Total indirect", 0.847482702061777, 0.00765021034066176, 0.192331300175352, - -0.0260583020096531, 0.0317871775920513, 84, 50, 0.00286443779119912, - "Total indirect", 0.846089700680365, 0.0147567710575251, 0.194110065137754, - -0.0250044388260874, 0.0211375997893015, 16, 84, -0.00193341951839295, - "Total indirect", 0.869533737246054, 0.0117711445157542, -0.164250767272911, - -0.009955133764027, 0.0114942559419666, 50, 84, 0.000769561088969798, - "Total indirect", 0.888155014681053, 0.00547188363540954, 0.140639154676066, - -0.033219418610941, 0.0406584603748081, 84, 84, 0.00371952088193355, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, + "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409, + -0.033219418610941, 0.0406584603748081, 0.00371952088193355, "Total indirect", 0.843548840135208, 0.0188467440137902, 0.197356152299409 )) @@ -2590,7 +2606,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 11 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -2601,23 +2617,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -2658,25 +2674,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0622024992020542, 0.868598726140512, "", 0.465400612671283, - "", "facGenderm", "contNormal", "", "", "", 0.0236768306572079, + "", "m", "facGender", "contNormal", "", "", "", 0.0236768306572079, 0.205717103298634, 2.26233310312402, -0.00502186744432948, 0.00513639658203032, - 16, 5.72645688504206e-05, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982370122140312, 0.0025914415026212, + 16, 5.72645688504206e-05, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.982370122140312, 0.0025914415026212, 0.0220975734132909, -0.0157840291533143, 0.016181006251643, - 16, 0.000198488549164307, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980580612317733, 0.00815449560734112, + 16, 0.000198488549164307, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980580612317733, 0.00815449560734112, 0.0243409965155438, -0.011149058111866, 0.0114296246961494, - 50, 0.000140283292141703, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980569563261315, 0.00575997390414138, + 50, 0.000140283292141703, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980569563261315, 0.00575997390414138, 0.0243548485594423, -0.0349764678843367, 0.0341117434797597, - 50, -0.000432362202288511, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980428759128093, 0.0176248675764084, + 50, -0.000432362202288511, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980428759128093, 0.0176248675764084, -0.0245313730962294, -0.0188291244993071, 0.0193043124562885, - 84, 0.000237593978490679, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980514818600596, 0.00972809634676639, + 84, 0.000237593978490679, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980514818600596, 0.00972809634676639, 0.0244234812260731, -0.0947410135891975, 0.0923973813630137, - 84, -0.00117181611309188, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.980417366068978, 0.0477402637059494, + 84, -0.00117181611309188, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.980417366068978, 0.0477402637059494, -0.0245456564779269)) @@ -2711,31 +2727,33 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0619826744391681, 0.868933080041099, 16, 0.465457877240134, - 0, "Total", 0.0237556901799967, 0.205858478004456, 2.26105760497295, + list(0.0619826744391681, 0.868933080041099, "", 0.465457877240134, + "", "m", "Total", 0.0237556901799967, 0.205858478004456, 2.26105760497295, 0.0612360212538626, 0.869962181187032, 16, 0.465599101220447, - 1, "Total", 0.0240219861554143, 0.206311484882452, 2.25677742315571, - 0.06158478720509, 0.86949700472176, 50, 0.465540895963425, 0, - "Total", 0.0238977803654057, 0.206103842695422, 2.25876863757168, + 0, "m", "Total", 0.0240219861554143, 0.206311484882452, 2.25677742315571, + 0.06158478720509, 0.86949700472176, 16, 0.465540895963425, 1, + "m", "Total", 0.0238977803654057, 0.206103842695422, 2.25876863757168, 0.0621417932928844, 0.867794707645105, 50, 0.464968250468995, - 1, "Total", 0.0236778428085556, 0.205527479256534, 2.26231670894301, - 0.0609746149230449, 0.870301798376503, 84, 0.465638206649774, - 0, "Total", 0.024115075622728, 0.206464810026441, 2.25529089722428, + 0, "m", "Total", 0.0236778428085556, 0.205527479256534, 2.26231670894301, + 0.0609746149230449, 0.870301798376503, 50, 0.465638206649774, + 1, "m", "Total", 0.024115075622728, 0.206464810026441, 2.25529089722428, 0.0552326240750896, 0.873224969041293, 84, 0.464228796558191, - 1, "Total", 0.0261050082820293, 0.208675351031555, 2.22464605552762, + 0, "m", "Total", 0.0261050082820293, 0.208675351031555, 2.22464605552762, + 0.0619826744391681, 0.868933080041099, 84, 0.465457877240134, + 1, "m", "Total", 0.0237556901799967, 0.205858478004456, 2.26105760497295, -0.00502186744432948, 0.00513639658203032, 16, 5.72645688504206e-05, - 0, "Total indirect", 0.982370122140312, 0.0025914415026212, + 0, "m", "Total indirect", 0.982370122140312, 0.0025914415026212, 0.0220975734132909, -0.0157840291533143, 0.016181006251643, - 16, 0.000198488549164307, 1, "Total indirect", 0.980580612317733, + 16, 0.000198488549164307, 1, "m", "Total indirect", 0.980580612317733, 0.00815449560734112, 0.0243409965155438, -0.011149058111866, - 0.0114296246961494, 50, 0.000140283292141703, 0, "Total indirect", + 0.0114296246961494, 50, 0.000140283292141703, 0, "m", "Total indirect", 0.980569563261315, 0.00575997390414138, 0.0243548485594423, -0.0349764678843367, 0.0341117434797597, 50, -0.000432362202288511, - 1, "Total indirect", 0.980428759128093, 0.0176248675764084, + 1, "m", "Total indirect", 0.980428759128093, 0.0176248675764084, -0.0245313730962294, -0.0188291244993071, 0.0193043124562885, - 84, 0.000237593978490679, 0, "Total indirect", 0.980514818600596, + 84, 0.000237593978490679, 0, "m", "Total indirect", 0.980514818600596, 0.00972809634676639, 0.0244234812260731, -0.0947410135891975, - 0.0923973813630137, 84, -0.00117181611309188, 1, "Total indirect", + 0.0923973813630137, 84, -0.00117181611309188, 1, "m", "Total indirect", 0.980417366068978, 0.0477402637059494, -0.0245456564779269 )) @@ -2753,7 +2771,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 12 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -2764,27 +2782,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -2989,7 +3007,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 12 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -3000,27 +3018,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -3061,38 +3079,39 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.878861262130587, 0.893506224549961, 16, 0.00732248120968704, - 0, "facGenderm", "contNormal", "", "", "", 0.987078775998107, + 0, "m", "facGender", "contNormal", "", "", "", 0.987078775998107, 0.452142871160072, 0.0161950606251949, -0.225620138867185, 1.45227966471852, - 16, 0.613329762925667, 1, "facGenderm", "contNormal", "", "", - "", 0.15189563934561, 0.42804352958033, 1.4328677355011, -0.0701739101694813, - 1.07581873989779, 50, 0.502822414864154, 0, "facGenderm", "contNormal", - "", "", "", 0.0854450857996136, 0.292350435800534, - 1.7199304440484, -0.297857186939633, 0.863961645448948, 50, - 0.283052229254658, 1, "facGenderm", "contNormal", "", "", - "", 0.339574491110516, 0.296387801396572, 0.95500633940035, - 0.3006239527811, 1.8666248312892, 84, 1.08362439203515, 0, "facGenderm", - "contNormal", "", "", "", 0.00667839343786802, 0.39949736088533, - 2.71246946321176, -1.02328146791015, 0.815113998039957, 84, - -0.104083734935097, 1, "facGenderm", "contNormal", "", "", - "", 0.824365988783905, 0.468987052938508, -0.221933066772195, + 16, 0.613329762925667, 1, "m", "facGender", "contNormal", "", + "", "", 0.15189563934561, 0.42804352958033, 1.4328677355011, + -0.0701739101694813, 1.07581873989779, 50, 0.502822414864154, + 0, "m", "facGender", "contNormal", "", "", "", 0.0854450857996136, + 0.292350435800534, 1.7199304440484, -0.297857186939633, 0.863961645448948, + 50, 0.283052229254658, 1, "m", "facGender", "contNormal", "", + "", "", 0.339574491110516, 0.296387801396572, 0.95500633940035, + 0.3006239527811, 1.8666248312892, 84, 1.08362439203515, 0, "m", + "facGender", "contNormal", "", "", "", 0.00667839343786802, + 0.39949736088533, 2.71246946321176, -1.02328146791015, 0.815113998039957, + 84, -0.104083734935097, 1, "m", "facGender", "contNormal", "", + "", "", 0.824365988783905, 0.468987052938508, -0.221933066772195, -0.00946512820932726, 0.00904650124377593, 16, -0.000209313482775664, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.964646816773848, 0.00472244122828801, -0.0443231525088867, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.964646816773848, 0.00472244122828801, -0.0443231525088867, -0.0180790050005119, 0.0166279854774981, 16, -0.000725509761506888, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.934693161078461, 0.00885398679561828, -0.0819415906364275, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.934693161078461, 0.00885398679561828, -0.0819415906364275, -0.0126981879898938, 0.011672668935515, 50, -0.000512759527189366, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.934269193892388, 0.00621716958006449, -0.0824747532757579, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.934269193892388, 0.00621716958006449, -0.0824747532757579, -0.0327491847142696, 0.0359098803609505, 50, 0.00158034782334045, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.928107428809268, 0.0175153894706214, 0.0902262450967002, -0.0208313638609613, - 0.0190944741258224, 84, -0.000868444867569445, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.932051418009093, - 0.0101853499099253, -0.085264117114246, -0.0880239699181569, - 0.0965903036018672, 84, 0.00428316684185515, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.92753646395841, - 0.0470963433451426, 0.0909447854680826)) + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.928107428809268, 0.0175153894706214, 0.0902262450967002, + -0.0208313638609613, 0.0190944741258224, 84, -0.000868444867569445, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.932051418009093, 0.0101853499099253, -0.085264117114246, + -0.0880239699181569, 0.0965903036018672, 84, 0.00428316684185515, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.92753646395841, 0.0470963433451426, 0.0909447854680826 + )) @@ -3142,42 +3161,42 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.879096137926492, 0.893322473380314, 16, 0.00711316772691137, - 0, "Total", 0.987448460922022, 0.45215591339622, 0.0157316702406547, + 0, "m", "Total", 0.987448460922022, 0.45215591339622, 0.0157316702406547, -0.226236103881886, 1.45144461021021, 16, 0.61260425316416, - 1, "Total", 0.152327155080635, 0.427987638376374, 1.43135968947176, + 1, "m", "Total", 0.152327155080635, 0.427987638376374, 1.43135968947176, -0.0706048612258585, 1.07522417189979, 50, 0.502309655336965, - 0, "Total", 0.0857196945112946, 0.292308696017835, 1.71842186763515, + 0, "m", "Total", 0.0857196945112946, 0.292308696017835, 1.71842186763515, -0.295309939589727, 0.864575093745723, 50, 0.284632577077998, - 1, "Total", 0.336080007975829, 0.295894476246624, 0.961939474803717, + 1, "m", "Total", 0.336080007975829, 0.295894476246624, 0.961939474803717, 0.299944753987687, 1.86556714034747, 84, 1.08275594716758, 0, - "Total", 0.00670905726628668, 0.399400804991626, 2.71095083844481, + "m", "Total", 0.00670905726628668, 0.399400804991626, 2.71095083844481, -1.01442802461674, 0.814826888430255, 84, -0.0998005680932418, - 1, "Total", 0.83065342768185, 0.466655236391057, -0.213863598456675, + 1, "m", "Total", 0.83065342768185, 0.466655236391057, -0.213863598456675, -0.879096137926492, 0.893322473380314, 16, 0.00711316772691137, - 0, "Total", 0.987448460922022, 0.45215591339622, 0.0157316702406547, + 0, "m", "Total", 0.987448460922022, 0.45215591339622, 0.0157316702406547, -0.226236103881886, 1.45144461021021, 16, 0.61260425316416, - 1, "Total", 0.152327155080635, 0.427987638376374, 1.43135968947176, + 1, "m", "Total", 0.152327155080635, 0.427987638376374, 1.43135968947176, -0.0706048612258585, 1.07522417189979, 50, 0.502309655336965, - 0, "Total", 0.0857196945112946, 0.292308696017835, 1.71842186763515, + 0, "m", "Total", 0.0857196945112946, 0.292308696017835, 1.71842186763515, -0.295309939589727, 0.864575093745723, 50, 0.284632577077998, - 1, "Total", 0.336080007975829, 0.295894476246624, 0.961939474803717, + 1, "m", "Total", 0.336080007975829, 0.295894476246624, 0.961939474803717, 0.299944753987687, 1.86556714034747, 84, 1.08275594716758, 0, - "Total", 0.00670905726628668, 0.399400804991626, 2.71095083844481, + "m", "Total", 0.00670905726628668, 0.399400804991626, 2.71095083844481, -1.01442802461674, 0.814826888430255, 84, -0.0998005680932418, - 1, "Total", 0.83065342768185, 0.466655236391057, -0.213863598456675, + 1, "m", "Total", 0.83065342768185, 0.466655236391057, -0.213863598456675, -0.00946512820932726, 0.00904650124377593, 16, -0.000209313482775664, - 0, "Total indirect", 0.964646816773848, 0.00472244122828801, + 0, "m", "Total indirect", 0.964646816773848, 0.00472244122828801, -0.0443231525088867, -0.0180790050005119, 0.0166279854774981, - 16, -0.000725509761506888, 1, "Total indirect", 0.934693161078461, + 16, -0.000725509761506888, 1, "m", "Total indirect", 0.934693161078461, 0.00885398679561828, -0.0819415906364275, -0.0126981879898938, - 0.011672668935515, 50, -0.000512759527189366, 0, "Total indirect", + 0.011672668935515, 50, -0.000512759527189366, 0, "m", "Total indirect", 0.934269193892388, 0.00621716958006449, -0.0824747532757579, -0.0327491847142696, 0.0359098803609505, 50, 0.00158034782334045, - 1, "Total indirect", 0.928107428809268, 0.0175153894706214, + 1, "m", "Total indirect", 0.928107428809268, 0.0175153894706214, 0.0902262450967002, -0.0208313638609613, 0.0190944741258224, - 84, -0.000868444867569445, 0, "Total indirect", 0.932051418009093, + 84, -0.000868444867569445, 0, "m", "Total indirect", 0.932051418009093, 0.0101853499099253, -0.085264117114246, -0.0880239699181569, - 0.0965903036018672, 84, 0.00428316684185515, 1, "Total indirect", + 0.0965903036018672, 84, 0.00428316684185515, 1, "m", "Total indirect", 0.92753646395841, 0.0470963433451426, 0.0909447854680826)) @@ -3194,7 +3213,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 13 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -3205,25 +3224,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -3392,7 +3411,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 13 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -3403,25 +3422,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -3462,28 +3481,29 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0389876734115612, 1.18993239595157, "", 0.614460034681565, 0, - "facGenderm", "contNormal", "", "", "", 0.0363715155137354, + "m", "facGender", "contNormal", "", "", "", 0.0363715155137354, 0.293613742808162, 2.09274957229449, -0.261259761966587, 0.892797982408634, - "", 0.315769110221023, 1, "facGenderm", "contNormal", "", "", - "", 0.283470138588953, 0.294407895624175, 1.07255652757396, - -0.00520211784329566, 0.00508208285320103, 16, -6.00174950473189e-05, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.981748961047472, 0.00262356879453326, -0.0228762802684564, - -0.0162645022638133, 0.0158484377006518, 16, -0.000208032281580749, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.979740807114921, 0.00819222705564179, -0.0253938617872514, - -0.0114880482262254, 0.011193991106291, 50, -0.000147028559967234, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.979728260294143, 0.00578634084897209, -0.0254095919692239, - -0.0342268317573894, 0.0351331373610994, 50, 0.000453152801854978, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.979568208213754, 0.0176941948080657, 0.0256102527846259, -0.0193982813953672, - 0.0189002436283779, 84, -0.000249018883494665, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.979666068202633, - 0.00977021142374016, -0.0254875634410108, -0.0927040977441078, - 0.0951604241557044, 84, 0.0012281632057983, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.979555244264738, - 0.0479255035760003, 0.0256265060178383)) + "", 0.315769110221023, 1, "m", "facGender", "contNormal", "", + "", "", 0.283470138588953, 0.294407895624175, 1.07255652757396, + -0.00520211784329566, 0.00508208285320103, "", -6.00174950473189e-05, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.981748961047472, 0.00262356879453326, -0.0228762802684564, + -0.0162645022638133, 0.0158484377006518, "", -0.000208032281580749, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979740807114921, 0.00819222705564179, -0.0253938617872514, + -0.0114880482262254, 0.011193991106291, 16, -0.000147028559967234, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979728260294143, 0.00578634084897209, -0.0254095919692239, + -0.0342268317573894, 0.0351331373610994, 16, 0.000453152801854978, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979568208213754, 0.0176941948080657, 0.0256102527846259, + -0.0193982813953672, 0.0189002436283779, 50, -0.000249018883494665, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979666068202633, 0.00977021142374016, -0.0254875634410108, + -0.0927040977441078, 0.0951604241557044, 50, 0.0012281632057983, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.979555244264738, 0.0479255035760003, 0.0256265060178383 + )) @@ -3523,35 +3543,36 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0390037194536534, 1.18979631491938, "", 0.614400017186518, 0, - "Total", 0.0363650665347719, 0.293574934167932, 2.09282178305817, + "m", "Total", 0.0363650665347719, 0.293574934167932, 2.09282178305817, -0.26290602806488, 0.894028183943765, "", 0.315561077939442, - 1, "Total", 0.284986320299432, 0.295141701871666, 1.06918499127126, - 0.0389715139185325, 1.18965449832466, 16, 0.614313006121598, - 0, "Total", 0.0363737346110711, 0.293546971649115, 2.09272472705289, - -0.259196346614675, 0.891640872660431, 16, 0.316222263022878, - 1, "Total", 0.281434923758643, 0.293586318001954, 1.07710149837696, - 0.0388309531739891, 1.18959107842215, 50, 0.61421101579807, - 0, "Total", 0.0364173180559209, 0.293566650796956, 2.09223702396253, - -0.260494199128902, 0.894488745982545, 50, 0.316997273426822, - 1, "Total", 0.28198734578731, 0.294643920557165, 1.0758656510794, - 0.0390037194536534, 1.18979631491938, 84, 0.614400017186518, - 0, "Total", 0.0363650665347719, 0.293574934167932, 2.09282178305817, - -0.26290602806488, 0.894028183943765, 84, 0.315561077939442, - 1, "Total", 0.284986320299432, 0.295141701871666, 1.06918499127126, - -0.00520211784329566, 0.00508208285320103, 16, -6.00174950473189e-05, - 0, "Total indirect", 0.981748961047472, 0.00262356879453326, + 1, "m", "Total", 0.284986320299432, 0.295141701871666, 1.06918499127126, + 0.0389715139185325, 1.18965449832466, "", 0.614313006121598, + 0, "m", "Total", 0.0363737346110711, 0.293546971649115, 2.09272472705289, + -0.259196346614675, 0.891640872660431, "", 0.316222263022878, + 1, "m", "Total", 0.281434923758643, 0.293586318001954, 1.07710149837696, + 0.0388309531739891, 1.18959107842215, 16, 0.61421101579807, + 0, "m", "Total", 0.0364173180559209, 0.293566650796956, 2.09223702396253, + -0.260494199128902, 0.894488745982545, 16, 0.316997273426822, + 1, "m", "Total", 0.28198734578731, 0.294643920557165, 1.0758656510794, + 0.0390037194536534, 1.18979631491938, 50, 0.614400017186518, + 0, "m", "Total", 0.0363650665347719, 0.293574934167932, 2.09282178305817, + -0.26290602806488, 0.894028183943765, 50, 0.315561077939442, + 1, "m", "Total", 0.284986320299432, 0.295141701871666, 1.06918499127126, + -0.00520211784329566, 0.00508208285320103, 84, -6.00174950473189e-05, + 0, "m", "Total indirect", 0.981748961047472, 0.00262356879453326, -0.0228762802684564, -0.0162645022638133, 0.0158484377006518, - 16, -0.000208032281580749, 1, "Total indirect", 0.979740807114921, + 84, -0.000208032281580749, 1, "m", "Total indirect", 0.979740807114921, 0.00819222705564179, -0.0253938617872514, -0.0114880482262254, - 0.011193991106291, 50, -0.000147028559967234, 0, "Total indirect", + 0.011193991106291, 16, -0.000147028559967234, 0, "m", "Total indirect", 0.979728260294143, 0.00578634084897209, -0.0254095919692239, - -0.0342268317573894, 0.0351331373610994, 50, 0.000453152801854978, - 1, "Total indirect", 0.979568208213754, 0.0176941948080657, + -0.0342268317573894, 0.0351331373610994, 16, 0.000453152801854978, + 1, "m", "Total indirect", 0.979568208213754, 0.0176941948080657, 0.0256102527846259, -0.0193982813953672, 0.0189002436283779, - 84, -0.000249018883494665, 0, "Total indirect", 0.979666068202633, + 50, -0.000249018883494665, 0, "m", "Total indirect", 0.979666068202633, 0.00977021142374016, -0.0254875634410108, -0.0927040977441078, - 0.0951604241557044, 84, 0.0012281632057983, 1, "Total indirect", - 0.979555244264738, 0.0479255035760003, 0.0256265060178383)) + 0.0951604241557044, 50, 0.0012281632057983, 1, "m", "Total indirect", + 0.979555244264738, 0.0479255035760003, 0.0256265060178383, 84, + 84)) @@ -3567,7 +3588,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 14 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -3578,21 +3599,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -3667,11 +3688,11 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.804166275556364, 0.0683258981509054, -0.247958811286497, -0.171505611689224, 0.100194720704048, 84, -0.0356554454925879, "Total", 0.606961741572253, 0.0693125829189746, -0.514415189724911, - -0.0186973017941751, 0.0556659659407027, 16, 0.0184843320732638, - "Total indirect", 0.329873439543783, 0.0189705699496128, 0.974368831424651, - -0.0215735578449936, 0.0242488343679387, 50, 0.00133763826147251, - "Total indirect", 0.908897118846133, 0.0116896005677588, 0.114429766331098, - -0.0566796630335963, 0.021928065542527, 84, -0.0173757987455346, + -0.0566796630335963, 0.021928065542527, -0.0173757987455346, + "Total indirect", 0.386228001825847, 0.0200533604689094, -0.866478153248876, + -0.0566796630335963, 0.021928065542527, -0.0173757987455346, + "Total indirect", 0.386228001825847, 0.0200533604689094, -0.866478153248876, + -0.0566796630335963, 0.021928065542527, -0.0173757987455346, "Total indirect", 0.386228001825847, 0.0200533604689094, -0.866478153248876 )) @@ -3689,7 +3710,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 14 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -3700,21 +3721,21 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -3751,13 +3772,14 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0581216478201232, 0.876434140268832, 0.467277894044478, "", - "facGenderm", "contNormal", "", "", "", 0.0251961761086923, + "m", "facGender", "contNormal", "", "", "", 0.0251961761086923, 0.208757022808443, 2.2383816733833, -0.029612452321592, 0.0316945053564423, - 0.00104102651742515, 0, "facGenderm", "debCollin1", "contNormal", + 0.00104102651742515, 0, "m", "facGender", "debCollin1", "contNormal", "", "", 0.946929940544045, 0.0156398174052217, 0.0665625748979385, -0.03325288367973, 0.0299903817501172, -0.00163125096480638, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.919464900720464, 0.0161337825410829, -0.101107781802102)) + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.919464900720464, 0.0161337825410829, -0.101107781802102 + )) @@ -3780,14 +3802,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0573677096736821, 0.879270131450124, 0.468318920561903, 0, "Total", - 0.0255113922789543, 0.209672837934652, 2.23356980892233, 0.0576673996184482, - 0.873625886540895, 0.465646643079671, 1, "Total", 0.0252861666506017, - 0.208156500159856, 2.23700265291775, -0.029612452321592, 0.0316945053564423, - 0.00104102651742515, 0, "Total indirect", 0.946929940544045, - 0.0156398174052217, 0.0665625748979385, -0.03325288367973, 0.0299903817501172, - -0.00163125096480638, 1, "Total indirect", 0.919464900720464, - 0.0161337825410829, -0.101107781802102)) + list(0.0573677096736821, 0.879270131450124, 0.468318920561903, "", + "m", "Total", 0.0255113922789543, 0.209672837934652, 2.23356980892233, + 0.0576673996184482, 0.873625886540895, 0.465646643079671, 0, + "m", "Total", 0.0252861666506017, 0.208156500159856, 2.23700265291775, + 0.0573677096736821, 0.879270131450124, 0.468318920561903, 1, + "m", "Total", 0.0255113922789543, 0.209672837934652, 2.23356980892233, + -0.029612452321592, 0.0316945053564423, 0.00104102651742515, + 0, "m", "Total indirect", 0.946929940544045, 0.0156398174052217, + 0.0665625748979385, -0.03325288367973, 0.0299903817501172, -0.00163125096480638, + 1, "m", "Total indirect", 0.919464900720464, 0.0161337825410829, + -0.101107781802102)) @@ -3803,7 +3828,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 15 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -3814,23 +3839,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -3940,7 +3965,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 15 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -3951,23 +3976,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -4003,17 +4028,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0394515151154701, 1.19060350292156, 0.615027509018516, 0, "facGenderm", - "contNormal", "", "", "", 0.0362328060356722, 0.293666617572117, - 2.09430514814126, -0.260888183281027, 0.896654610515889, 0.317883213617431, - 1, "facGenderm", "contNormal", "", "", "", 0.281709693122984, - 0.295296955180673, 1.07648659439424, -0.0294254304617834, 0.0319773338212055, - 0.00127595167971108, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.935079119781431, 0.0156642583147767, - 0.0814562460648022, -0.0319483383453816, 0.0304364764961899, - -0.00075593092459585, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96211580258074, 0.0159147860199613, - -0.0474986546251841)) + list(0.0394515151154701, 1.19060350292156, 0.615027509018516, 0, "m", + "facGender", "contNormal", "", "", "", 0.0362328060356722, + 0.293666617572117, 2.09430514814126, -0.260888183281027, 0.896654610515889, + 0.317883213617431, 1, "m", "facGender", "contNormal", "", "", + "", 0.281709693122984, 0.295296955180673, 1.07648659439424, + -0.0294254304617834, 0.0319773338212055, 0.00127595167971108, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.935079119781431, 0.0156642583147767, 0.0814562460648022, + -0.0319483383453816, 0.0304364764961899, -0.00075593092459585, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.96211580258074, 0.0159147860199613, -0.0474986546251841 + )) @@ -4039,17 +4065,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0389959973859365, 1.19361092401052, 0.616303460698227, 0, "Total", - 0.0364067046401961, 0.294550036564967, 2.09235574330779, -0.259088061157634, - 0.893342626543304, 0.317127282692835, 1, "Total", 0.280725694804147, - 0.293992822518976, 1.07869056113561, 0.0389959973859365, 1.19361092401052, - 0.616303460698227, 0, "Total", 0.0364067046401961, 0.294550036564967, - 2.09235574330779, -0.259088061157634, 0.893342626543304, 0.317127282692835, - 1, "Total", 0.280725694804147, 0.293992822518976, 1.07869056113561, + list(0.0389959973859365, 1.19361092401052, 0.616303460698227, 0, "m", + "Total", 0.0364067046401961, 0.294550036564967, 2.09235574330779, + -0.259088061157634, 0.893342626543304, 0.317127282692835, 1, + "m", "Total", 0.280725694804147, 0.293992822518976, 1.07869056113561, + 0.0389959973859365, 1.19361092401052, 0.616303460698227, 0, + "m", "Total", 0.0364067046401961, 0.294550036564967, 2.09235574330779, + -0.259088061157634, 0.893342626543304, 0.317127282692835, 1, + "m", "Total", 0.280725694804147, 0.293992822518976, 1.07869056113561, -0.0294254304617834, 0.0319773338212055, 0.00127595167971108, - 0, "Total indirect", 0.935079119781431, 0.0156642583147767, + 0, "m", "Total indirect", 0.935079119781431, 0.0156642583147767, 0.0814562460648022, -0.0319483383453816, 0.0304364764961899, - -0.00075593092459585, 1, "Total indirect", 0.96211580258074, + -0.00075593092459585, 1, "m", "Total indirect", 0.96211580258074, 0.0159147860199613, -0.0474986546251841)) @@ -4066,7 +4093,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 16 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -4077,23 +4104,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -4211,23 +4238,23 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.95596217464935, 0.0701462042045045, 0.055221281459228, -0.161121184799628, 0.107903689682853, 84, 84, -0.0266087475583874, "Total", 0.698228619670629, 0.0686300556042138, -0.38771274952535, - -0.0235237393843932, 0.0469048390609559, 16, 16, 0.0116905498382814, - "Total indirect", 0.515256322884239, 0.0179668042374454, 0.650674971674516, - -0.0585994716811879, 0.0261200845296767, 50, 16, -0.0162396935757556, - "Total indirect", 0.452410865401193, 0.0216125288217339, -0.751401823900623, - -0.127745735617899, 0.0343017267782665, 84, 16, -0.0467220044198164, - "Total indirect", 0.258389750306886, 0.0413393979875078, -1.13020524473857, - -0.0188121193544891, 0.0717942240461896, 16, 50, 0.0264910523458503, - "Total indirect", 0.25175794720327, 0.0231142878428813, 1.14608992178009, - -0.0244468665829715, 0.0215684844465981, 50, 50, -0.00143919106818671, - "Total indirect", 0.902423109525533, 0.0117388256601991, -0.122600940660218, - -0.0869915201587274, 0.0231485163342323, 84, 50, -0.0319215019122475, - "Total indirect", 0.255915122720189, 0.0280974643824403, -1.13609902579669, - -0.0308375673575464, 0.118516593423669, 16, 84, 0.0438395130330615, - "Total indirect", 0.249894529464843, 0.0381012513391323, 1.15060559672578, - -0.0243237244970188, 0.0561422637350677, 50, 84, 0.0159092696190245, - "Total indirect", 0.438324605046442, 0.0205274150103757, 0.775025477439953, - -0.0528432778551859, 0.0236971954051132, 84, 84, -0.0145730412250363, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, + "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558, + -0.0528432778551859, 0.0236971954051132, -0.0145730412250363, "Total indirect", 0.455461619440356, 0.0195259897283931, -0.746340719612558 )) @@ -4245,7 +4272,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 16 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -4256,23 +4283,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -4319,25 +4346,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0715438299978369, 0.892289575881436, "", 0.481916702939637, - "", "facGenderm", "contNormal", "", "", "", 0.0213542773563125, + "", "m", "facGender", "contNormal", "", "", "", 0.0213542773563125, 0.209377762131737, 2.30166135139233, -0.0360412388561742, 0.0452239043461729, - 16, 0.00459133274499938, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.824727428432538, 0.0207312848203733, + 16, 0.00459133274499938, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.824727428432538, 0.0207312848203733, 0.221468798715617, -0.0368483585191957, 0.0426809487614308, - 16, 0.00291629512111753, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.885704550663031, 0.0202884613972358, + 16, 0.00291629512111753, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.885704550663031, 0.0202884613972358, 0.143741561472713, -0.0295028956100662, 0.0318509207699986, - 50, 0.00117401257996621, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.940208117350952, 0.0156517713753966, + 50, 0.00117401257996621, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.940208117350952, 0.0156517713753966, 0.0750082883149995, -0.0317184176690603, 0.030716367581229, - 50, -0.000501025043915644, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974905454057705, 0.0159275338074493, + 50, -0.000501025043915644, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.974905454057705, 0.0159275338074493, -0.0314565362078413, -0.0415552923337116, 0.0358920699689909, - 84, -0.00283161118236036, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.886037910796878, 0.019757343225079, + 84, -0.00283161118236036, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.886037910796878, 0.019757343225079, -0.143319430659384, -0.0451757904832907, 0.0361624928708063, - 84, -0.00450664880624222, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.828061456542636, 0.0207499433652055, + 84, -0.00450664880624222, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.828061456542636, 0.0207499433652055, -0.217188487068316)) @@ -4365,32 +4392,34 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0731884353865058, 0.899827635982766, 16, 0.486508035684636, - 0, "Total", 0.0210534834671383, 0.210881222082825, 2.30702397719203, + list(0.0731884353865058, 0.899827635982766, "", 0.486508035684636, + "", "m", "Total", 0.0210534834671383, 0.210881222082825, 2.30702397719203, 0.0743381953163758, 0.895327800805132, 16, 0.484832998060754, - 1, "Total", 0.0206182992462751, 0.209439972357813, 2.31490193874, - 0.0709442619941575, 0.895237169045048, 50, 0.483090715519603, - 0, "Total", 0.0215993995978774, 0.210282666812454, 2.29733968492258, + 0, "m", "Total", 0.0206182992462751, 0.209439972357813, 2.31490193874, + 0.0709442619941575, 0.895237169045048, 16, 0.483090715519603, + 1, "m", "Total", 0.0215993995978774, 0.210282666812454, 2.29733968492258, 0.0719760347917035, 0.890855320999738, 50, 0.481415677895721, - 1, "Total", 0.0211940811802391, 0.208901615710097, 2.30450911669254, - 0.0666287964377364, 0.891541387076816, 84, 0.479085091757276, - 0, "Total", 0.0228113512798522, 0.210440752265318, 2.27657944861011, + 0, "m", "Total", 0.0211940811802391, 0.208901615710097, 2.30450911669254, + 0.0666287964377364, 0.891541387076816, 50, 0.479085091757276, + 1, "m", "Total", 0.0228113512798522, 0.210440752265318, 2.27657944861011, 0.0675108952700392, 0.887309212996749, 84, 0.477410054133394, - 1, "Total", 0.0224437748935551, 0.20913606683418, 2.28277246177687, + 0, "m", "Total", 0.0224437748935551, 0.20913606683418, 2.28277246177687, + 0.0731884353865058, 0.899827635982766, 84, 0.486508035684636, + 1, "m", "Total", 0.0210534834671383, 0.210881222082825, 2.30702397719203, -0.0360412388561742, 0.0452239043461729, 16, 0.00459133274499938, - 0, "Total indirect", 0.824727428432538, 0.0207312848203733, + 0, "m", "Total indirect", 0.824727428432538, 0.0207312848203733, 0.221468798715617, -0.0368483585191957, 0.0426809487614308, - 16, 0.00291629512111753, 1, "Total indirect", 0.885704550663031, + 16, 0.00291629512111753, 1, "m", "Total indirect", 0.885704550663031, 0.0202884613972358, 0.143741561472713, -0.0295028956100662, - 0.0318509207699986, 50, 0.00117401257996621, 0, "Total indirect", + 0.0318509207699986, 50, 0.00117401257996621, 0, "m", "Total indirect", 0.940208117350952, 0.0156517713753966, 0.0750082883149995, -0.0317184176690603, - 0.030716367581229, 50, -0.000501025043915644, 1, "Total indirect", + 0.030716367581229, 50, -0.000501025043915644, 1, "m", "Total indirect", 0.974905454057705, 0.0159275338074493, -0.0314565362078413, -0.0415552923337116, 0.0358920699689909, 84, -0.00283161118236036, - 0, "Total indirect", 0.886037910796878, 0.019757343225079, -0.143319430659384, - -0.0451757904832907, 0.0361624928708063, 84, -0.00450664880624222, - 1, "Total indirect", 0.828061456542636, 0.0207499433652055, - -0.217188487068316)) + 0, "m", "Total indirect", 0.886037910796878, 0.019757343225079, + -0.143319430659384, -0.0451757904832907, 0.0361624928708063, + 84, -0.00450664880624222, 1, "m", "Total indirect", 0.828061456542636, + 0.0207499433652055, -0.217188487068316)) @@ -4406,7 +4435,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 17 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -4417,27 +4446,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -4632,7 +4661,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 17 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -4643,27 +4672,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -4710,38 +4739,39 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.175783430172798, 1.32274378011761, 16, 0.573480174972405, 0, - "facGenderm", "contNormal", "", "", "", 0.133578077760397, + "m", "facGender", "contNormal", "", "", "", 0.133578077760397, 0.382284374128963, 1.50014024580283, -0.362716053039095, 1.00606619822194, - 16, 0.321675072591422, 1, "facGenderm", "contNormal", "", "", - "", 0.356938046380561, 0.349185562096501, 0.921215272075092, + 16, 0.321675072591422, 1, "m", "facGender", "contNormal", "", + "", "", 0.356938046380561, 0.349185562096501, 0.921215272075092, 0.0235481261613413, 1.18422554836211, 50, 0.603886837261728, - 0, "facGenderm", "contNormal", "", "", "", 0.0414008984745873, + 0, "m", "facGender", "contNormal", "", "", "", 0.0414008984745873, 0.296096619977726, 2.0394925052071, -0.236088085491044, 0.940251555252534, - 50, 0.352081734880745, 1, "facGenderm", "contNormal", "", "", - "", 0.240697421752358, 0.300092157310643, 1.17324537247498, + 50, 0.352081734880745, 1, "m", "facGender", "contNormal", "", + "", "", 0.240697421752358, 0.300092157310643, 1.17324537247498, -0.0534551055573028, 1.33251133080305, 84, 0.639528112622876, - 0, "facGenderm", "contNormal", "", "", "", 0.0704856635299571, + 0, "m", "facGender", "contNormal", "", "", "", 0.0704856635299571, 0.353569363338481, 1.80877694431528, -0.392737323202819, 1.16818334368661, - 84, 0.387723010241893, 1, "facGenderm", "contNormal", "", "", - "", 0.33021257516287, 0.398201364719395, 0.973685789638401, + 84, 0.387723010241893, 1, "m", "facGender", "contNormal", "", + "", "", 0.33021257516287, 0.398201364719395, 0.973685789638401, -0.0361714029143399, 0.0456722151469467, 16, 0.00475040611630338, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.820017615999381, 0.020878857649135, 0.227522319282644, -0.0368270025396428, - 0.0435667725957297, 16, 0.00336988502804347, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.869485098803298, - 0.0205089929635208, 0.164312554694297, -0.029345078777716, 0.0321960169103273, - 50, 0.00142546906630562, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.927654033346503, 0.0156995475869637, - 0.090796824456857, -0.0311480112557322, 0.0312379072118236, - 50, 4.49479780457052e-05, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.997746585120974, 0.0159150675623756, - 0.00282424047962985, -0.0408893807530128, 0.0359456457426224, - 84, -0.00247186750519522, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.899646115084083, 0.0196011322406177, - -0.126108404088667, -0.0438734778277331, 0.0361687006408228, - 84, -0.00385238859345513, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.850356088001227, 0.020419298288111, - -0.188664102903975)) + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.820017615999381, 0.020878857649135, 0.227522319282644, + -0.0368270025396428, 0.0435667725957297, 16, 0.00336988502804347, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.869485098803298, 0.0205089929635208, 0.164312554694297, + -0.029345078777716, 0.0321960169103273, 50, 0.00142546906630562, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.927654033346503, 0.0156995475869637, 0.090796824456857, + -0.0311480112557322, 0.0312379072118236, 50, 4.49479780457052e-05, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.997746585120974, 0.0159150675623756, 0.00282424047962985, + -0.0408893807530128, 0.0359456457426224, 84, -0.00247186750519522, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.899646115084083, 0.0196011322406177, -0.126108404088667, + -0.0438734778277331, 0.0361687006408228, 84, -0.00385238859345513, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.850356088001227, 0.020419298288111, -0.188664102903975 + )) @@ -4774,42 +4804,42 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.170579079787034, 1.32704024196445, 16, 0.578230581088709, 0, - "Total", 0.13015687318591, 0.382052765653991, 1.5134835631903, + "m", "Total", 0.13015687318591, 0.382052765653991, 1.5134835631903, -0.35815859976861, 1.00824851500754, 16, 0.325044957619466, - 1, "Total", 0.351086433295297, 0.348579648798192, 0.932484035542904, + 1, "m", "Total", 0.351086433295297, 0.348579648798192, 0.932484035542904, 0.023364618952273, 1.18725999370379, 50, 0.605312306328034, - 0, "Total", 0.0414845135488668, 0.296917541325295, 2.03865458277142, + 0, "m", "Total", 0.0414845135488668, 0.296917541325295, 2.03865458277142, -0.233846290398492, 0.938099656116074, 50, 0.352126682858791, - 1, "Total", 0.238878629390655, 0.298971296350016, 1.17779428044672, + 1, "m", "Total", 0.238878629390655, 0.298971296350016, 1.17779428044672, -0.0568896131255175, 1.33100210336088, 84, 0.637056245117681, - 0, "Total", 0.071973399332891, 0.354060515252808, 1.79928633008627, + 0, "m", "Total", 0.071973399332891, 0.354060515252808, 1.79928633008627, -0.391948323951254, 1.15968956724813, 84, 0.383870621648438, - 1, "Total", 0.332156873396777, 0.395833266182059, 0.969778577103929, + 1, "m", "Total", 0.332156873396777, 0.395833266182059, 0.969778577103929, -0.170579079787034, 1.32704024196445, 16, 0.578230581088709, - 0, "Total", 0.13015687318591, 0.382052765653991, 1.5134835631903, + 0, "m", "Total", 0.13015687318591, 0.382052765653991, 1.5134835631903, -0.35815859976861, 1.00824851500754, 16, 0.325044957619466, - 1, "Total", 0.351086433295297, 0.348579648798192, 0.932484035542904, + 1, "m", "Total", 0.351086433295297, 0.348579648798192, 0.932484035542904, 0.023364618952273, 1.18725999370379, 50, 0.605312306328034, - 0, "Total", 0.0414845135488668, 0.296917541325295, 2.03865458277142, + 0, "m", "Total", 0.0414845135488668, 0.296917541325295, 2.03865458277142, -0.233846290398492, 0.938099656116074, 50, 0.352126682858791, - 1, "Total", 0.238878629390655, 0.298971296350016, 1.17779428044672, + 1, "m", "Total", 0.238878629390655, 0.298971296350016, 1.17779428044672, -0.0568896131255175, 1.33100210336088, 84, 0.637056245117681, - 0, "Total", 0.071973399332891, 0.354060515252808, 1.79928633008627, + 0, "m", "Total", 0.071973399332891, 0.354060515252808, 1.79928633008627, -0.391948323951254, 1.15968956724813, 84, 0.383870621648438, - 1, "Total", 0.332156873396777, 0.395833266182059, 0.969778577103929, + 1, "m", "Total", 0.332156873396777, 0.395833266182059, 0.969778577103929, -0.0361714029143399, 0.0456722151469467, 16, 0.00475040611630338, - 0, "Total indirect", 0.820017615999381, 0.020878857649135, 0.227522319282644, - -0.0368270025396428, 0.0435667725957297, 16, 0.00336988502804347, - 1, "Total indirect", 0.869485098803298, 0.0205089929635208, - 0.164312554694297, -0.029345078777716, 0.0321960169103273, 50, - 0.00142546906630562, 0, "Total indirect", 0.927654033346503, + 0, "m", "Total indirect", 0.820017615999381, 0.020878857649135, + 0.227522319282644, -0.0368270025396428, 0.0435667725957297, + 16, 0.00336988502804347, 1, "m", "Total indirect", 0.869485098803298, + 0.0205089929635208, 0.164312554694297, -0.029345078777716, 0.0321960169103273, + 50, 0.00142546906630562, 0, "m", "Total indirect", 0.927654033346503, 0.0156995475869637, 0.090796824456857, -0.0311480112557322, - 0.0312379072118236, 50, 4.49479780457052e-05, 1, "Total indirect", + 0.0312379072118236, 50, 4.49479780457052e-05, 1, "m", "Total indirect", 0.997746585120974, 0.0159150675623756, 0.00282424047962985, -0.0408893807530128, 0.0359456457426224, 84, -0.00247186750519522, - 0, "Total indirect", 0.899646115084083, 0.0196011322406177, + 0, "m", "Total indirect", 0.899646115084083, 0.0196011322406177, -0.126108404088667, -0.0438734778277331, 0.0361687006408228, - 84, -0.00385238859345513, 1, "Total indirect", 0.850356088001227, + 84, -0.00385238859345513, 1, "m", "Total indirect", 0.850356088001227, 0.020419298288111, -0.188664102903975)) @@ -4826,7 +4856,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 18 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -4837,23 +4867,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -4976,23 +5006,23 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.851360205688193, 0.0736065543138548, 0.18738318479121, -0.170440335919156, 0.102640831538931, 84, 84, -0.0338997521901123, "Total", 0.626533282431522, 0.0696648432349054, -0.486612050152822, - -0.0325359194023129, 0.0381599592664842, 16, 16, 0.00281201993208567, - "Total indirect", 0.876095922296221, 0.0180349943229664, 0.155920200568333, - -0.0395946801992444, 0.0407818806366346, 50, 16, 0.000593600218695108, - "Total indirect", 0.976904779021978, 0.0205046014798943, 0.0289496101290806, - -0.0757043123735975, 0.0720492664843998, 84, 16, -0.00182752294459886, - "Total indirect", 0.961330117604415, 0.0376929321210641, -0.0484844993944521, - -0.0173893277292483, 0.0868914123727865, 16, 50, 0.0347510423217691, - "Total indirect", 0.191451691679357, 0.0266027184490603, 1.30629666243739, - -0.0175030973019086, 0.0443748919451536, 50, 50, 0.0134358973216225, - "Total indirect", 0.394683348298215, 0.0157854914006451, 0.851154834563681, - -0.057341771137327, 0.0376880224153352, 84, 50, -0.0098268743609959, - "Total indirect", 0.685217838880612, 0.02424273973967, -0.405353292017384, - -0.0319588347375502, 0.176335792586511, 16, 84, 0.0721884789244804, - "Total indirect", 0.174296882849354, 0.0531373609329209, 1.35852585934046, - -0.0223677767832182, 0.0793458581974273, 50, 84, 0.0284890407071046, - "Total indirect", 0.272232754641171, 0.0259478326599238, 1.09793527191601, - -0.0596399566721842, 0.0212332725684941, 84, 84, -0.019203342051845, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, + "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145, + -0.0596399566721842, 0.0212332725684941, -0.019203342051845, "Total indirect", 0.351963965575443, 0.0206313049317732, -0.930786594224145 )) @@ -5010,7 +5040,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 18 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -5021,23 +5051,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -5083,25 +5113,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0393124070952489, 0.866239581585079, "", 0.452775994340164, - "", "facGenderm", "contNormal", "", "", "", 0.0318475581749429, + "", "m", "facGender", "contNormal", "", "", "", 0.0318475581749429, 0.210954686160696, 2.14631873119547, -0.0405388501179339, 0.050085864678084, - 16, 0.00477350728007508, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.836419316164305, 0.0231189745094436, + 16, 0.00477350728007508, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.836419316164305, 0.0231189745094436, 0.206475736115597, -0.0447186669191563, 0.0457106778571771, - 16, 0.000496005469010433, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982846143650779, 0.0230691343028822, + 16, 0.000496005469010433, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.982846143650779, 0.0230691343028822, 0.0215008271441058, -0.0295132413255326, 0.0314629197034827, - 50, 0.000974839188975022, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.950030287432815, 0.0155554289543041, + 50, 0.000974839188975022, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.950030287432815, 0.0155554289543041, 0.0626687436160535, -0.033648903438917, 0.0301542928283708, - 50, -0.00174730530527313, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.914510849214756, 0.0162766246651876, + 50, -0.00174730530527313, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.914510849214756, 0.0162766246651876, -0.107350592719034, -0.0476763963164938, 0.0407208305639136, - 84, -0.00347778287629009, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.877435933844351, 0.0225507273546028, + 84, -0.00347778287629009, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.877435933844351, 0.0225507273546028, -0.154220430303781, -0.0502585475059402, 0.0415049277831083, - 84, -0.00437680986141595, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.851686184666792, 0.0234094799733227, + 84, -0.00437680986141595, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.851686184666792, 0.0234094799733227, -0.186967410912319)) @@ -5135,30 +5165,32 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0414774275871795, 0.873621575653298, 16, 0.457549501620239, - 0, "Total", 0.0311345311368554, 0.212285571222218, 2.1553490375532, + list(0.0414774275871795, 0.873621575653298, "", 0.457549501620239, + "", "m", "Total", 0.0311345311368554, 0.212285571222218, 2.1553490375532, 0.0374784622651567, 0.869065537353192, 16, 0.453271999809174, - 1, "Total", 0.0326281271794273, 0.212143458157264, 2.13662963612651, - 0.0385346475128719, 0.868967019545406, 50, 0.453750833529139, - 0, "Total", 0.0322046813525745, 0.21184888563843, 2.1418608465261, + 0, "m", "Total", 0.0326281271794273, 0.212143458157264, 2.13662963612651, + 0.0385346475128719, 0.868967019545406, 16, 0.453750833529139, + 1, "m", "Total", 0.0322046813525745, 0.21184888563843, 2.1418608465261, 0.0379306736707378, 0.864126704399043, 50, 0.451028689034891, - 1, "Total", 0.0323605904431219, 0.210768166467658, 2.13992794354977, - 0.0322710736398888, 0.866325349287859, 84, 0.449298211463874, - 0, "Total", 0.034717930195997, 0.212772857620569, 2.11163311189387, + 0, "m", "Total", 0.0323605904431219, 0.210768166467658, 2.13992794354977, + 0.0322710736398888, 0.866325349287859, 50, 0.449298211463874, + 1, "m", "Total", 0.034717930195997, 0.212772857620569, 2.11163311189387, 0.0356985040196386, 0.861099864937857, 84, 0.448399184478748, - 1, "Total", 0.0332128841978341, 0.210565440852199, 2.12950037130495, + 0, "m", "Total", 0.0332128841978341, 0.210565440852199, 2.12950037130495, + 0.0414774275871795, 0.873621575653298, 84, 0.457549501620239, + 1, "m", "Total", 0.0311345311368554, 0.212285571222218, 2.1553490375532, -0.0405388501179339, 0.050085864678084, 16, 0.00477350728007508, - 0, "Total indirect", 0.836419316164305, 0.0231189745094436, + 0, "m", "Total indirect", 0.836419316164305, 0.0231189745094436, 0.206475736115597, -0.0447186669191563, 0.0457106778571771, - 16, 0.000496005469010433, 1, "Total indirect", 0.982846143650779, + 16, 0.000496005469010433, 1, "m", "Total indirect", 0.982846143650779, 0.0230691343028822, 0.0215008271441058, -0.0295132413255326, - 0.0314629197034827, 50, 0.000974839188975022, 0, "Total indirect", + 0.0314629197034827, 50, 0.000974839188975022, 0, "m", "Total indirect", 0.950030287432815, 0.0155554289543041, 0.0626687436160535, -0.033648903438917, - 0.0301542928283708, 50, -0.00174730530527313, 1, "Total indirect", + 0.0301542928283708, 50, -0.00174730530527313, 1, "m", "Total indirect", 0.914510849214756, 0.0162766246651876, -0.107350592719034, -0.0476763963164938, - 0.0407208305639136, 84, -0.00347778287629009, 0, "Total indirect", + 0.0407208305639136, 84, -0.00347778287629009, 0, "m", "Total indirect", 0.877435933844351, 0.0225507273546028, -0.154220430303781, -0.0502585475059402, - 0.0415049277831083, 84, -0.00437680986141595, 1, "Total indirect", + 0.0415049277831083, 84, -0.00437680986141595, 1, "m", "Total indirect", 0.851686184666792, 0.0234094799733227, -0.186967410912319)) @@ -5175,7 +5207,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 21 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -5186,23 +5218,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -5319,23 +5351,11 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.578658749394111, 0.0691537287040139, -0.555344934457365, -0.181429429944216, 0.0962553597968531, 84, 84, -0.0425870350736813, "Total", 0.547721139996501, 0.0708392582545932, -0.601178444311561, - -0.0180243258240925, 0.0250910933642123, 16, 16, 0.00353338377005991, - "Total indirect", 0.748024784986812, 0.0109990335354103, 0.321244931082767, - -0.0212620770293893, 0.0269988168258479, 50, 16, 0.00286836989822931, - "Total indirect", 0.8157772524997, 0.0123116787440772, 0.232979592617229, - -0.0498459331913346, 0.0472169487096567, 84, 16, -0.00131449224083895, + -0.0498459331913346, 0.0472169487096567, -0.00131449224083895, "Total indirect", 0.957663100841287, 0.0247613942568871, -0.0530863580298325, - -0.0180243258240925, 0.0250910933642123, 16, 50, 0.00353338377005991, - "Total indirect", 0.748024784986812, 0.0109990335354103, 0.321244931082767, - -0.0212620770293893, 0.0269988168258479, 50, 50, 0.00286836989822931, - "Total indirect", 0.8157772524997, 0.0123116787440772, 0.232979592617229, - -0.0498459331913346, 0.0472169487096567, 84, 50, -0.00131449224083895, + -0.0498459331913346, 0.0472169487096567, -0.00131449224083895, "Total indirect", 0.957663100841287, 0.0247613942568871, -0.0530863580298325, - -0.0180243258240925, 0.0250910933642123, 16, 84, 0.00353338377005991, - "Total indirect", 0.748024784986812, 0.0109990335354103, 0.321244931082767, - -0.0212620770293893, 0.0269988168258479, 50, 84, 0.00286836989822931, - "Total indirect", 0.8157772524997, 0.0123116787440772, 0.232979592617229, - -0.0498459331913346, 0.0472169487096567, 84, 84, -0.00131449224083895, + -0.0498459331913346, 0.0472169487096567, -0.00131449224083895, "Total indirect", 0.957663100841287, 0.0247613942568871, -0.0530863580298325 )) @@ -5353,7 +5373,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 21 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -5364,23 +5384,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -5424,25 +5444,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0770109554094963, 0.887908037142156, "", 0.482459496275826, - "", "facGenderm", "contNormal", "", "", "", 0.019688077827914, + "", "m", "facGender", "contNormal", "", "", "", 0.019688077827914, 0.206865301640467, 2.33223983166758, -0.0289108673078605, 0.0244708899497198, - 16, -0.00221998867907034, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.870504138263035, 0.0136180454535514, + 16, -0.00221998867907034, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.870504138263035, 0.0136180454535514, -0.163018157535331, -0.0433035776853076, 0.044969023175739, - 16, 0.000832722745215685, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970501924440653, 0.0225189344185224, + 16, 0.000832722745215685, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.970501924440653, 0.0225189344185224, 0.0369787810443974, -0.0236113638306395, 0.0277977666045881, - 50, 0.00209320138697429, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.873191559689371, 0.013114815078424, + 50, 0.00209320138697429, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.873191559689371, 0.013114815078424, 0.159605863632645, -0.0289108673078605, 0.0244708899497198, - 50, -0.00221998867907034, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.870504138263035, 0.0136180454535514, + 50, -0.00221998867907034, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.870504138263035, 0.0136180454535514, -0.163018157535331, -0.0433035776853076, 0.044969023175739, - 84, 0.000832722745215685, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970501924440653, 0.0225189344185224, + 84, 0.000832722745215685, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.970501924440653, 0.0225189344185224, 0.0369787810443974, -0.0236113638306395, 0.0277977666045881, - 84, 0.00209320138697429, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.873191559689371, 0.013114815078424, + 84, 0.00209320138697429, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.873191559689371, 0.013114815078424, 0.159605863632645)) @@ -5471,30 +5491,32 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.073450173355631, 0.887028841837881, 16, 0.480239507596756, 0, - "Total", 0.0206755957764275, 0.207549392463243, 2.31385648445975, + list(0.073450173355631, 0.887028841837881, "", 0.480239507596756, "", + "m", "Total", 0.0206755957764275, 0.207549392463243, 2.31385648445975, 0.0774644536131626, 0.889119984428921, 16, 0.483292219021042, - 1, "Total", 0.0195914207636234, 0.207058787104762, 2.33408215018916, - 0.0776001673990077, 0.891505227926593, 50, 0.4845526976628, - 0, "Total", 0.0196113438846157, 0.207632657270125, 2.33370175979788, + 0, "m", "Total", 0.0195914207636234, 0.207058787104762, 2.33408215018916, + 0.0776001673990077, 0.891505227926593, 16, 0.4845526976628, + 1, "m", "Total", 0.0196113438846157, 0.207632657270125, 2.33370175979788, 0.073450173355631, 0.887028841837881, 50, 0.480239507596756, - 1, "Total", 0.0206755957764275, 0.207549392463243, 2.31385648445975, - 0.0774644536131626, 0.889119984428921, 84, 0.483292219021042, - 0, "Total", 0.0195914207636234, 0.207058787104762, 2.33408215018916, + 0, "m", "Total", 0.0206755957764275, 0.207549392463243, 2.31385648445975, + 0.0774644536131626, 0.889119984428921, 50, 0.483292219021042, + 1, "m", "Total", 0.0195914207636234, 0.207058787104762, 2.33408215018916, 0.0776001673990077, 0.891505227926593, 84, 0.4845526976628, - 1, "Total", 0.0196113438846157, 0.207632657270125, 2.33370175979788, + 0, "m", "Total", 0.0196113438846157, 0.207632657270125, 2.33370175979788, + 0.073450173355631, 0.887028841837881, 84, 0.480239507596756, + 1, "m", "Total", 0.0206755957764275, 0.207549392463243, 2.31385648445975, -0.0289108673078605, 0.0244708899497198, 16, -0.00221998867907034, - 0, "Total indirect", 0.870504138263035, 0.0136180454535514, + 0, "m", "Total indirect", 0.870504138263035, 0.0136180454535514, -0.163018157535331, -0.0433035776853076, 0.044969023175739, - 16, 0.000832722745215685, 1, "Total indirect", 0.970501924440653, + 16, 0.000832722745215685, 1, "m", "Total indirect", 0.970501924440653, 0.0225189344185224, 0.0369787810443974, -0.0236113638306395, - 0.0277977666045881, 50, 0.00209320138697429, 0, "Total indirect", + 0.0277977666045881, 50, 0.00209320138697429, 0, "m", "Total indirect", 0.873191559689371, 0.013114815078424, 0.159605863632645, -0.0289108673078605, - 0.0244708899497198, 50, -0.00221998867907034, 1, "Total indirect", + 0.0244708899497198, 50, -0.00221998867907034, 1, "m", "Total indirect", 0.870504138263035, 0.0136180454535514, -0.163018157535331, -0.0433035776853076, - 0.044969023175739, 84, 0.000832722745215685, 0, "Total indirect", + 0.044969023175739, 84, 0.000832722745215685, 0, "m", "Total indirect", 0.970501924440653, 0.0225189344185224, 0.0369787810443974, -0.0236113638306395, - 0.0277977666045881, 84, 0.00209320138697429, 1, "Total indirect", + 0.0277977666045881, 84, 0.00209320138697429, 1, "m", "Total indirect", 0.873191559689371, 0.013114815078424, 0.159605863632645)) @@ -5511,7 +5533,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 22 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -5522,25 +5544,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -5706,7 +5728,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 22 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -5717,25 +5739,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -5779,28 +5801,29 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0351291107062669, 1.18425461416693, "", 0.609691862436596, 0, - "facGenderm", "contNormal", "", "", "", 0.0375441237093244, + "m", "facGender", "contNormal", "", "", "", 0.0375441237093244, 0.293149647780473, 2.07979735624028, -0.23765542360327, 0.932487101485949, - "", 0.347415838941339, 1, "facGenderm", "contNormal", "", "", - "", 0.24449357386863, 0.298511231410157, 1.16382836685963, -0.0291865473785372, - 0.0246863621243192, 16, -0.00225009262710903, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.869949697699492, - 0.0137433416960207, -0.163722381126602, -0.042859313877257, - 0.0460167745987393, 16, 0.00157873036074112, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.944487556006922, - 0.0226728881696397, 0.0696307567403402, -0.0213676901386402, - 0.0247127152820957, 50, 0.00167251257172773, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.886862122067604, - 0.0117554214731016, 0.142275849109683, -0.0291865473785372, - 0.0246863621243192, 50, -0.00225009262710903, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.869949697699492, - 0.0137433416960207, -0.163722381126602, -0.042859313877257, - 0.0460167745987393, 84, 0.00157873036074112, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.944487556006922, - 0.0226728881696397, 0.0696307567403402, -0.0213676901386402, - 0.0247127152820957, 84, 0.00167251257172773, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.886862122067604, - 0.0117554214731016, 0.142275849109683)) + "", 0.347415838941339, 1, "m", "facGender", "contNormal", "", + "", "", 0.24449357386863, 0.298511231410157, 1.16382836685963, + -0.0291865473785372, 0.0246863621243192, "", -0.00225009262710903, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.869949697699492, 0.0137433416960207, -0.163722381126602, + -0.042859313877257, 0.0460167745987393, "", 0.00157873036074112, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.944487556006922, 0.0226728881696397, 0.0696307567403402, + -0.0213676901386402, 0.0247127152820957, 16, 0.00167251257172773, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.886862122067604, 0.0117554214731016, 0.142275849109683, + -0.0291865473785372, 0.0246863621243192, 16, -0.00225009262710903, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.869949697699492, 0.0137433416960207, -0.163722381126602, + -0.042859313877257, 0.0460167745987393, 50, 0.00157873036074112, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.944487556006922, 0.0226728881696397, 0.0696307567403402, + -0.0213676901386402, 0.0247127152820957, 50, 0.00167251257172773, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.886862122067604, 0.0117554214731016, 0.142275849109683 + )) @@ -5834,34 +5857,35 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0322737801525189, 1.18260975946646, "", 0.607441769809487, 0, - "Total", 0.0384578392745616, 0.293458448315286, 2.06994132660602, + "m", "Total", 0.0384578392745616, 0.293458448315286, 2.06994132660602, -0.234846657099298, 0.932835795703459, "", 0.348994569302081, - 1, "Total", 0.24136566481911, 0.297883650417377, 1.17158014148507, - 0.0368285352366526, 1.18590021478, 16, 0.611364375008324, 0, - "Total", 0.0370148383767157, 0.293135916937014, 2.0856003638056, - 0.0322737801525189, 1.18260975946646, 16, 0.607441769809487, - 1, "Total", 0.0384578392745616, 0.293458448315286, 2.06994132660602, + 1, "m", "Total", 0.24136566481911, 0.297883650417377, 1.17158014148507, + 0.0368285352366526, 1.18590021478, "", 0.611364375008324, 0, + "m", "Total", 0.0370148383767157, 0.293135916937014, 2.0856003638056, + 0.0322737801525189, 1.18260975946646, "", 0.607441769809487, + 1, "m", "Total", 0.0384578392745616, 0.293458448315286, 2.06994132660602, + -0.234846657099298, 0.932835795703459, 16, 0.348994569302081, + 0, "m", "Total", 0.24136566481911, 0.297883650417377, 1.17158014148507, + 0.0368285352366526, 1.18590021478, 16, 0.611364375008324, 1, + "m", "Total", 0.0370148383767157, 0.293135916937014, 2.0856003638056, + 0.0322737801525189, 1.18260975946646, 50, 0.607441769809487, + 0, "m", "Total", 0.0384578392745616, 0.293458448315286, 2.06994132660602, -0.234846657099298, 0.932835795703459, 50, 0.348994569302081, - 0, "Total", 0.24136566481911, 0.297883650417377, 1.17158014148507, - 0.0368285352366526, 1.18590021478, 50, 0.611364375008324, 1, - "Total", 0.0370148383767157, 0.293135916937014, 2.0856003638056, - 0.0322737801525189, 1.18260975946646, 84, 0.607441769809487, - 0, "Total", 0.0384578392745616, 0.293458448315286, 2.06994132660602, - -0.234846657099298, 0.932835795703459, 84, 0.348994569302081, - 1, "Total", 0.24136566481911, 0.297883650417377, 1.17158014148507, - -0.0291865473785372, 0.0246863621243192, 16, -0.00225009262710903, - 0, "Total indirect", 0.869949697699492, 0.0137433416960207, + 1, "m", "Total", 0.24136566481911, 0.297883650417377, 1.17158014148507, + -0.0291865473785372, 0.0246863621243192, 84, -0.00225009262710903, + 0, "m", "Total indirect", 0.869949697699492, 0.0137433416960207, -0.163722381126602, -0.042859313877257, 0.0460167745987393, - 16, 0.00157873036074112, 1, "Total indirect", 0.944487556006922, + 84, 0.00157873036074112, 1, "m", "Total indirect", 0.944487556006922, 0.0226728881696397, 0.0696307567403402, -0.0213676901386402, - 0.0247127152820957, 50, 0.00167251257172773, 0, "Total indirect", + 0.0247127152820957, 16, 0.00167251257172773, 0, "m", "Total indirect", 0.886862122067604, 0.0117554214731016, 0.142275849109683, -0.0291865473785372, - 0.0246863621243192, 50, -0.00225009262710903, 1, "Total indirect", + 0.0246863621243192, 16, -0.00225009262710903, 1, "m", "Total indirect", 0.869949697699492, 0.0137433416960207, -0.163722381126602, -0.042859313877257, - 0.0460167745987393, 84, 0.00157873036074112, 0, "Total indirect", + 0.0460167745987393, 50, 0.00157873036074112, 0, "m", "Total indirect", 0.944487556006922, 0.0226728881696397, 0.0696307567403402, -0.0213676901386402, - 0.0247127152820957, 84, 0.00167251257172773, 1, "Total indirect", - 0.886862122067604, 0.0117554214731016, 0.142275849109683)) + 0.0247127152820957, 50, 0.00167251257172773, 1, "m", "Total indirect", + 0.886862122067604, 0.0117554214731016, 0.142275849109683, 84, + 84)) @@ -5877,7 +5901,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 28 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -5888,25 +5912,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -6069,7 +6093,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 28 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -6080,25 +6104,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -6142,30 +6166,30 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.135444582762512, 1.00628609571759, 16, 0.43542075647754, "", - "facGenderm", "contNormal", "", "", "", 0.13493029810259, + "m", "facGender", "contNormal", "", "", "", 0.13493029810259, 0.291263178172132, 1.49493924776242, 0.0757137061439992, 0.886683891071008, - 50, 0.481198798607504, "", "facGenderm", "contNormal", "", "", - "", 0.0200219729812672, 0.206883950757218, 2.32593585363323, + 50, 0.481198798607504, "", "m", "facGender", "contNormal", "", + "", "", 0.0200219729812672, 0.206883950757218, 2.32593585363323, -0.0691339820255702, 1.13884936305542, 84, 0.534857690514926, - "", "facGenderm", "contNormal", "", "", "", 0.0826305247516859, + "", "m", "facGender", "contNormal", "", "", "", 0.0826305247516859, 0.30816467920059, 1.73562295296917, -0.0303424105849761, 0.0255524279872925, - 16, -0.00239499129884181, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.866613392056803, 0.0142591494061013, + 16, -0.00239499129884181, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.866613392056803, 0.0142591494061013, -0.167961722724991, -0.0432540528715142, 0.0450103493320848, - 16, 0.000878148230285331, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.968890694620871, 0.0225168428858431, + 16, 0.000878148230285331, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.968890694620871, 0.0225168428858431, 0.0389996161867543, -0.0246862544664141, 0.0292273891561552, - 50, 0.00227056734487058, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.868875231292622, 0.0137537332440375, + 50, 0.00227056734487058, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.868875231292622, 0.0137537332440375, 0.165087347891884, -0.0303424105849761, 0.0255524279872925, - 50, -0.00239499129884181, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.866613392056803, 0.0142591494061013, + 50, -0.00239499129884181, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.866613392056803, 0.0142591494061013, -0.167961722724991, -0.0432540528715142, 0.0450103493320848, - 84, 0.000878148230285331, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.968890694620871, 0.0225168428858431, + 84, 0.000878148230285331, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.968890694620871, 0.0225168428858431, 0.0389996161867543, -0.0246862544664141, 0.0292273891561552, - 84, 0.00227056734487058, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.868875231292622, 0.0137537332440375, + 84, 0.00227056734487058, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.868875231292622, 0.0137537332440375, 0.165087347891884)) @@ -6197,36 +6221,37 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.139902729661894, 1.00595426001929, 16, 0.433025765178698, "", - "Total", 0.138509947695741, 0.292315827923258, 1.48136270367262, + "m", "Total", 0.138509947695741, 0.292315827923258, 1.48136270367262, 0.0762223526994046, 0.887931540976173, 50, 0.482076946837789, - "", "Total", 0.0199089692971641, 0.207072475484097, 2.32805903204074, + "", "m", "Total", 0.0199089692971641, 0.207072475484097, 2.32805903204074, -0.0690489717749763, 1.14330548749457, 84, 0.537128257859796, - "", "Total", 0.082438959087817, 0.309279779840967, 1.73670667424812, + "", "m", "Total", 0.082438959087817, 0.309279779840967, 1.73670667424812, -0.139902729661894, 1.00595426001929, 16, 0.433025765178698, - 0, "Total", 0.138509947695741, 0.292315827923258, 1.48136270367262, + "", "m", "Total", 0.138509947695741, 0.292315827923258, 1.48136270367262, 0.0762223526994046, 0.887931540976173, 16, 0.482076946837789, - 1, "Total", 0.0199089692971641, 0.207072475484097, 2.32805903204074, + "", "m", "Total", 0.0199089692971641, 0.207072475484097, 2.32805903204074, -0.0690489717749763, 1.14330548749457, 50, 0.537128257859796, - 0, "Total", 0.082438959087817, 0.309279779840967, 1.73670667424812, + "", "m", "Total", 0.082438959087817, 0.309279779840967, 1.73670667424812, -0.139902729661894, 1.00595426001929, 50, 0.433025765178698, - 1, "Total", 0.138509947695741, 0.292315827923258, 1.48136270367262, + 0, "m", "Total", 0.138509947695741, 0.292315827923258, 1.48136270367262, 0.0762223526994046, 0.887931540976173, 84, 0.482076946837789, - 0, "Total", 0.0199089692971641, 0.207072475484097, 2.32805903204074, + 1, "m", "Total", 0.0199089692971641, 0.207072475484097, 2.32805903204074, -0.0690489717749763, 1.14330548749457, 84, 0.537128257859796, - 1, "Total", 0.082438959087817, 0.309279779840967, 1.73670667424812, + 0, "m", "Total", 0.082438959087817, 0.309279779840967, 1.73670667424812, -0.0303424105849761, 0.0255524279872925, 16, -0.00239499129884181, - 0, "Total indirect", 0.866613392056803, 0.0142591494061013, + 1, "m", "Total indirect", 0.866613392056803, 0.0142591494061013, -0.167961722724991, -0.0432540528715142, 0.0450103493320848, - 16, 0.000878148230285331, 1, "Total indirect", 0.968890694620871, + 16, 0.000878148230285331, 0, "m", "Total indirect", 0.968890694620871, 0.0225168428858431, 0.0389996161867543, -0.0246862544664141, - 0.0292273891561552, 50, 0.00227056734487058, 0, "Total indirect", + 0.0292273891561552, 50, 0.00227056734487058, 1, "m", "Total indirect", 0.868875231292622, 0.0137537332440375, 0.165087347891884, -0.0303424105849761, - 0.0255524279872925, 50, -0.00239499129884181, 1, "Total indirect", + 0.0255524279872925, 50, -0.00239499129884181, 0, "m", "Total indirect", 0.866613392056803, 0.0142591494061013, -0.167961722724991, -0.0432540528715142, - 0.0450103493320848, 84, 0.000878148230285331, 0, "Total indirect", + 0.0450103493320848, 84, 0.000878148230285331, 1, "m", "Total indirect", 0.968890694620871, 0.0225168428858431, 0.0389996161867543, -0.0246862544664141, - 0.0292273891561552, 84, 0.00227056734487058, 1, "Total indirect", - 0.868875231292622, 0.0137537332440375, 0.165087347891884)) + 0.0292273891561552, 84, 0.00227056734487058, 0, "m", "Total indirect", + 0.868875231292622, 0.0137537332440375, 0.165087347891884, 1, + 0, 1)) @@ -6242,7 +6267,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 29 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -6253,27 +6278,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -6468,7 +6493,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 29 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -6479,27 +6504,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -6543,38 +6568,39 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.175482581170277, 1.32297873645118, 16, 0.57374807764045, 0, - "facGenderm", "contNormal", "", "", "", 0.13337960774978, + "m", "facGender", "contNormal", "", "", "", 0.13337960774978, 0.382267564465757, 1.50090703730592, -0.363072059171158, 1.00492534413716, - 16, 0.320926642483002, 1, "facGenderm", "contNormal", "", "", - "", 0.357782243334385, 0.348985342102944, 0.919599203075797, + 16, 0.320926642483002, 1, "m", "facGender", "contNormal", "", + "", "", 0.357782243334385, 0.348985342102944, 0.919599203075797, 0.0233150064530619, 1.18386387735802, 50, 0.60358944190554, - 0, "facGenderm", "contNormal", "", "", "", 0.0414785879109525, + 0, "m", "facGender", "contNormal", "", "", "", 0.0414785879109525, 0.296063825677211, 2.03871391759834, -0.235957380348608, 0.937493393844792, - 50, 0.350768006748092, 1, "facGenderm", "contNormal", "", "", - "", 0.241299367173489, 0.299355188016063, 1.17174520699895, + 50, 0.350768006748092, 1, "m", "facGender", "contNormal", "", + "", "", 0.241299367173489, 0.299355188016063, 1.17174520699895, -0.0537692189237937, 1.33090542135171, 84, 0.63856810121396, - 0, "facGenderm", "contNormal", "", "", "", 0.0706459384626275, + 0, "m", "facGender", "contNormal", "", "", "", 0.0706459384626275, 0.353239817465434, 1.80774666286438, -0.392244909489302, 1.16373824160232, - 84, 0.385746666056511, 1, "facGenderm", "contNormal", "", "", - "", 0.33115174467542, 0.396941771217488, 0.971796606019469, + 84, 0.385746666056511, 1, "m", "facGender", "contNormal", "", + "", "", 0.33115174467542, 0.396941771217488, 0.971796606019469, -0.0299389527461722, 0.0252558973239065, 16, -0.00234152771113284, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.867924909427806, 0.0140805776293464, -0.166294861813956, -0.0428931392010744, - 0.0459615780154078, 16, 0.00153421940716667, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.946037303751614, - 0.022667436217542, 0.0676838523970067, -0.0221215354336881, - 0.0257353556623201, 50, 0.001806910114316, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.882340498915573, - 0.0122086149218805, 0.148002875500448, -0.0299389527461722, - 0.0252558973239065, 50, -0.00234152771113284, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.867924909427806, - 0.0140805776293464, -0.166294861813956, -0.0428931392010744, - 0.0459615780154078, 84, 0.00153421940716667, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.946037303751614, - 0.022667436217542, 0.0676838523970067, -0.0221215354336881, - 0.0257353556623201, 84, 0.001806910114316, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.882340498915573, - 0.0122086149218805, 0.148002875500448)) + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.867924909427806, 0.0140805776293464, -0.166294861813956, + -0.0428931392010744, 0.0459615780154078, 16, 0.00153421940716667, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.946037303751614, 0.022667436217542, 0.0676838523970067, + -0.0221215354336881, 0.0257353556623201, 50, 0.001806910114316, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.882340498915573, 0.0122086149218805, 0.148002875500448, + -0.0299389527461722, 0.0252558973239065, 50, -0.00234152771113284, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.867924909427806, 0.0140805776293464, -0.166294861813956, + -0.0428931392010744, 0.0459615780154078, 84, 0.00153421940716667, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.946037303751614, 0.022667436217542, 0.0676838523970067, + -0.0221215354336881, 0.0257353556623201, 84, 0.001806910114316, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.882340498915573, 0.0122086149218805, 0.148002875500448 + )) @@ -6610,41 +6636,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.17909700535665, 1.32191010521528, 16, 0.571406549929317, 0, - "Total", 0.13563455206165, 0.382917013376696, 1.4922464397454, + "m", "Total", 0.13563455206165, 0.382917013376696, 1.4922464397454, -0.360794894604935, 1.00571661838527, 16, 0.322460861890169, - 1, "Total", 0.35496583057686, 0.348606281485037, 0.92500014777849, + 1, "m", "Total", 0.35496583057686, 0.348606281485037, 0.92500014777849, 0.0253656274445384, 1.18542707659517, 50, 0.605396352019856, - 0, "Total", 0.0407882392253354, 0.295939481108085, 2.04567619620428, + 0, "m", "Total", 0.0407882392253354, 0.295939481108085, 2.04567619620428, -0.239170905172086, 0.936023863246004, 50, 0.348426479036959, - 1, "Total", 0.24515584483408, 0.299800092677181, 1.16219603511643, + 1, "m", "Total", 0.24515584483408, 0.299800092677181, 1.16219603511643, -0.0540304842502298, 1.33423512549248, 84, 0.640102320621126, - 0, "Total", 0.0706995157202452, 0.354155897938221, 1.80740268437598, + 0, "m", "Total", 0.0706995157202452, 0.354155897938221, 1.80740268437598, -0.393047063635854, 1.16815421597751, 84, 0.387553576170827, - 1, "Total", 0.330510881596838, 0.398272950913364, 0.973085355864731, + 1, "m", "Total", 0.330510881596838, 0.398272950913364, 0.973085355864731, -0.17909700535665, 1.32191010521528, 16, 0.571406549929317, - 0, "Total", 0.13563455206165, 0.382917013376696, 1.4922464397454, + 0, "m", "Total", 0.13563455206165, 0.382917013376696, 1.4922464397454, -0.360794894604935, 1.00571661838527, 16, 0.322460861890169, - 1, "Total", 0.35496583057686, 0.348606281485037, 0.92500014777849, + 1, "m", "Total", 0.35496583057686, 0.348606281485037, 0.92500014777849, 0.0253656274445384, 1.18542707659517, 50, 0.605396352019856, - 0, "Total", 0.0407882392253354, 0.295939481108085, 2.04567619620428, + 0, "m", "Total", 0.0407882392253354, 0.295939481108085, 2.04567619620428, -0.239170905172086, 0.936023863246004, 50, 0.348426479036959, - 1, "Total", 0.24515584483408, 0.299800092677181, 1.16219603511643, + 1, "m", "Total", 0.24515584483408, 0.299800092677181, 1.16219603511643, -0.0540304842502298, 1.33423512549248, 84, 0.640102320621126, - 0, "Total", 0.0706995157202452, 0.354155897938221, 1.80740268437598, + 0, "m", "Total", 0.0706995157202452, 0.354155897938221, 1.80740268437598, -0.393047063635854, 1.16815421597751, 84, 0.387553576170827, - 1, "Total", 0.330510881596838, 0.398272950913364, 0.973085355864731, + 1, "m", "Total", 0.330510881596838, 0.398272950913364, 0.973085355864731, -0.0299389527461722, 0.0252558973239065, 16, -0.00234152771113284, - 0, "Total indirect", 0.867924909427806, 0.0140805776293464, + 0, "m", "Total indirect", 0.867924909427806, 0.0140805776293464, -0.166294861813956, -0.0428931392010744, 0.0459615780154078, - 16, 0.00153421940716667, 1, "Total indirect", 0.946037303751614, + 16, 0.00153421940716667, 1, "m", "Total indirect", 0.946037303751614, 0.022667436217542, 0.0676838523970067, -0.0221215354336881, - 0.0257353556623201, 50, 0.001806910114316, 0, "Total indirect", + 0.0257353556623201, 50, 0.001806910114316, 0, "m", "Total indirect", 0.882340498915573, 0.0122086149218805, 0.148002875500448, -0.0299389527461722, - 0.0252558973239065, 50, -0.00234152771113284, 1, "Total indirect", + 0.0252558973239065, 50, -0.00234152771113284, 1, "m", "Total indirect", 0.867924909427806, 0.0140805776293464, -0.166294861813956, -0.0428931392010744, - 0.0459615780154078, 84, 0.00153421940716667, 0, "Total indirect", + 0.0459615780154078, 84, 0.00153421940716667, 0, "m", "Total indirect", 0.946037303751614, 0.022667436217542, 0.0676838523970067, -0.0221215354336881, - 0.0257353556623201, 84, 0.001806910114316, 1, "Total indirect", + 0.0257353556623201, 84, 0.001806910114316, 1, "m", "Total indirect", 0.882340498915573, 0.0122086149218805, 0.148002875500448)) @@ -6661,7 +6687,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 58 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -6672,23 +6698,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -6728,29 +6754,11 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.0693544827200475, -0.263567106484947, -0.0232783700689727, 0.0451693480545924, 16, 0.0109454889928099, "contGamma", "debCollin1", "contNormal", "", "", 0.530766411414661, 0.0174614734412142, - 0.62683650550218, -0.0219985213892134, 0.0247266069688974, 16, - 0.00136404278984198, "contGamma", "debCollin1", "contNormal", - "", "", 0.908893658673861, 0.0119198946324199, - 0.114434131500797, -0.0845460897661474, 0.0328913082466424, - 50, -0.0258273907597525, "contGamma", "debCollin1", "contNormal", - "", "", 0.388638439155159, 0.029959070406171, - -0.86208919067237, -0.0232783700689727, 0.0451693480545924, - 16, 0.0109454889928099, "contGamma", "debCollin1", "contNormal", - "", "", 0.530766411414661, 0.0174614734412142, - 0.62683650550218, -0.0219985213892134, 0.0247266069688974, 84, - 0.00136404278984198, "contGamma", "debCollin1", "contNormal", - "", "", 0.908893658673861, 0.0119198946324199, - 0.114434131500797, -0.0845460897661474, 0.0328913082466424, - 16, -0.0258273907597525, "contGamma", "debCollin1", "contNormal", - "", "", 0.388638439155159, 0.029959070406171, - -0.86208919067237, -0.0232783700689727, 0.0451693480545924, - 16, 0.0109454889928099, "contGamma", "debCollin1", "contNormal", - "", "", 0.530766411414661, 0.0174614734412142, 0.62683650550218, -0.0219985213892134, 0.0247266069688974, 50, 0.00136404278984198, "contGamma", "debCollin1", "contNormal", "", "", 0.908893658673861, 0.0119198946324199, 0.114434131500797, -0.0845460897661474, 0.0328913082466424, - 50, -0.0258273907597525, "contGamma", "debCollin1", "contNormal", + 84, -0.0258273907597525, "contGamma", "debCollin1", "contNormal", "", "", 0.388638439155159, 0.029959070406171, -0.86208919067237)) @@ -6781,43 +6789,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.146208793987558, 0.131540651308612, 16, -0.00733407133947334, - "Total", 0.917560538318064, 0.0708557523217319, -0.103507070338789, - -0.150831017897368, 0.116999982812486, 16, -0.0169155175424412, - "Total", 0.804465132744912, 0.0683254903718819, -0.24757257431119, - -0.184093076916658, 0.0958791747325862, 50, -0.0441069510920357, - "Total", 0.536873879537097, 0.0714228051784699, -0.617547168328408, - -0.146208793987558, 0.131540651308612, 16, -0.00733407133947334, - "Total", 0.917560538318064, 0.0708557523217319, -0.103507070338789, - -0.150831017897368, 0.116999982812486, 84, -0.0169155175424412, - "Total", 0.804465132744912, 0.0683254903718819, -0.24757257431119, - -0.184093076916658, 0.0958791747325862, 16, -0.0441069510920357, - "Total", 0.536873879537097, 0.0714228051784699, -0.617547168328408, - -0.146208793987558, 0.131540651308612, 16, -0.00733407133947334, "Total", 0.917560538318064, 0.0708557523217319, -0.103507070338789, -0.150831017897368, 0.116999982812486, 50, -0.0169155175424412, "Total", 0.804465132744912, 0.0683254903718819, -0.24757257431119, - -0.184093076916658, 0.0958791747325862, 50, -0.0441069510920357, + -0.184093076916658, 0.0958791747325862, 84, -0.0441069510920357, "Total", 0.536873879537097, 0.0714228051784699, -0.617547168328408, - -0.0232783700689727, 0.0451693480545924, 50, 0.0109454889928099, - "Total indirect", 0.530766411414661, 0.0174614734412142, 0.62683650550218, - -0.0219985213892134, 0.0247266069688974, 84, 0.00136404278984198, - "Total indirect", 0.908893658673861, 0.0119198946324199, 0.114434131500797, - -0.0845460897661474, 0.0328913082466424, 50, -0.0258273907597525, + -0.0845460897661474, 0.0328913082466424, -0.0258273907597525, "Total indirect", 0.388638439155159, 0.029959070406171, -0.86208919067237, - -0.0232783700689727, 0.0451693480545924, 16, 0.0109454889928099, - "Total indirect", 0.530766411414661, 0.0174614734412142, 0.62683650550218, - -0.0219985213892134, 0.0247266069688974, 84, 0.00136404278984198, - "Total indirect", 0.908893658673861, 0.0119198946324199, 0.114434131500797, - -0.0845460897661474, 0.0328913082466424, 50, -0.0258273907597525, + -0.0845460897661474, 0.0328913082466424, -0.0258273907597525, "Total indirect", 0.388638439155159, 0.029959070406171, -0.86208919067237, - -0.0232783700689727, 0.0451693480545924, 84, 0.0109454889928099, - "Total indirect", 0.530766411414661, 0.0174614734412142, 0.62683650550218, - -0.0219985213892134, 0.0247266069688974, 84, 0.00136404278984198, - "Total indirect", 0.908893658673861, 0.0119198946324199, 0.114434131500797, - -0.0845460897661474, 0.0328913082466424, 84, -0.0258273907597525, - "Total indirect", 0.388638439155159, 0.029959070406171, -0.86208919067237, - 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 84, 50, - 84, 84, 84)) + -0.0845460897661474, 0.0328913082466424, -0.0258273907597525, + "Total indirect", 0.388638439155159, 0.029959070406171, -0.86208919067237 + )) @@ -6833,7 +6816,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 58 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -6844,23 +6827,23 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -6897,18 +6880,12 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0581216477891692, 0.876434140299787, 0.467277894044478, "", - "facGenderm", "contNormal", "", "", "", 0.0251961761197259, + "m", "facGender", "contNormal", "", "", "", 0.0251961761197259, 0.208757022824236, 2.23838167321396, -0.0188161934453592, 0.0176251719168027, - -0.000595510764278248, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.948924081012459, 0.00929643749824148, - -0.0640579538550004, -0.0670190515778879, 0.0603864836764719, - -0.00331628395070801, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.918730324348602, 0.0325020092867314, - -0.102033198054061, -0.0188161934453592, 0.0176251719168027, - -0.000595510764278248, 1, "facGenderm", "debCollin1", "contNormal", + -0.000595510764278248, 0, "m", "facGender", "debCollin1", "contNormal", "", "", 0.948924081012459, 0.00929643749824148, -0.0640579538550004, -0.0670190515778879, 0.0603864836764719, - -0.00331628395070801, 0, "facGenderm", "debCollin1", "contNormal", + -0.00331628395070801, 1, "m", "facGender", "debCollin1", "contNormal", "", "", 0.918730324348602, 0.0325020092867314, -0.102033198054061)) @@ -6939,23 +6916,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0574926278847326, 0.875872138675666, 0.4666823832802, 0, "Total", - 0.0253946454404903, 0.208774119638475, 2.23534595230641, 0.0547198687779226, - 0.873203351409617, 0.46396161009377, 0, "Total", 0.0262811759469663, - 0.208800643554623, 2.2220315138655, 0.0574926278847326, 0.875872138675666, - 0.4666823832802, 1, "Total", 0.0253946454404903, 0.208774119638475, - 2.23534595230641, 0.0547198687779226, 0.873203351409617, 0.46396161009377, - 0, "Total", 0.0262811759469663, 0.208800643554623, 2.2220315138655, + list(0.0574926278847326, 0.875872138675666, 0.4666823832802, "", "m", + "Total", 0.0253946454404903, 0.208774119638475, 2.23534595230641, + 0.0547198687779226, 0.873203351409617, 0.46396161009377, 0, + "m", "Total", 0.0262811759469663, 0.208800643554623, 2.2220315138655, + 0.0574926278847326, 0.875872138675666, 0.4666823832802, 1, "m", + "Total", 0.0253946454404903, 0.208774119638475, 2.23534595230641, -0.0188161934453592, 0.0176251719168027, -0.000595510764278248, - 0, "Total indirect", 0.948924081012459, 0.00929643749824148, + 0, "m", "Total indirect", 0.948924081012459, 0.00929643749824148, -0.0640579538550004, -0.0670190515778879, 0.0603864836764719, - -0.00331628395070801, 1, "Total indirect", 0.918730324348602, - 0.0325020092867314, -0.102033198054061, -0.0188161934453592, - 0.0176251719168027, -0.000595510764278248, 1, "Total indirect", - 0.948924081012459, 0.00929643749824148, -0.0640579538550004, - -0.0670190515778879, 0.0603864836764719, -0.00331628395070801, - 1, "Total indirect", 0.918730324348602, 0.0325020092867314, - -0.102033198054061, 0, 0, 1, 0, 0, 1, 1, 1)) + -0.00331628395070801, 1, "m", "Total indirect", 0.918730324348602, + 0.0325020092867314, -0.102033198054061)) @@ -6971,7 +6942,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 59 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -6982,25 +6953,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -7046,28 +7017,10 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) -0.023172578106807, 0.0445488723194967, 16, 0.0106881471063448, "contGamma", "debCollin1", "contNormal", "", "", 0.536138281570805, 0.017276197664978, 0.618663163828674, -0.0219696261639075, - 0.0250246157540351, 16, 0.00152749479506379, "contGamma", "debCollin1", + 0.0250246157540351, 50, 0.00152749479506379, "contGamma", "debCollin1", "contNormal", "", "", 0.898613658537253, 0.0119885473122535, 0.127412834539389, -0.0852940839382829, 0.0360454313067229, - 50, -0.02462432631578, "contGamma", "debCollin1", "contNormal", - "", "", 0.426322705842423, 0.0309545267673581, - -0.795500008798281, -0.023172578106807, 0.0445488723194967, - 16, 0.0106881471063448, "contGamma", "debCollin1", "contNormal", - "", "", 0.536138281570805, 0.017276197664978, - 0.618663163828674, -0.0219696261639075, 0.0250246157540351, - 84, 0.00152749479506379, "contGamma", "debCollin1", "contNormal", - "", "", 0.898613658537253, 0.0119885473122535, - 0.127412834539389, -0.0852940839382829, 0.0360454313067229, - 16, -0.02462432631578, "contGamma", "debCollin1", "contNormal", - "", "", 0.426322705842423, 0.0309545267673581, - -0.795500008798281, -0.023172578106807, 0.0445488723194967, - 16, 0.0106881471063448, "contGamma", "debCollin1", "contNormal", - "", "", 0.536138281570805, 0.017276197664978, - 0.618663163828674, -0.0219696261639075, 0.0250246157540351, - 50, 0.00152749479506379, "contGamma", "debCollin1", "contNormal", - "", "", 0.898613658537253, 0.0119885473122535, - 0.127412834539389, -0.0852940839382829, 0.0360454313067229, - 50, -0.02462432631578, "contGamma", "debCollin1", "contNormal", + 84, -0.02462432631578, "contGamma", "debCollin1", "contNormal", "", "", 0.426322705842423, 0.0309545267673581, -0.795500008798281)) @@ -7107,42 +7060,17 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.603666487696113, 0.104556542308847, -0.519135164894186, -0.185877072908425, 0.188224354729382, 16, 0.00117364091047894, "Total", 0.990188100850379, 0.0954357913177669, 0.0122977018817933, - -0.151919274913335, 0.116685037647779, 16, -0.0176171186327778, - "Total", 0.797102533687855, 0.0685227674283383, -0.257098761389081, - -0.259206035105647, 0.150648079441109, 50, -0.054278977832269, - "Total", 0.603666487696113, 0.104556542308847, -0.519135164894186, - -0.185877072908425, 0.188224354729382, 16, 0.00117364091047894, - "Total", 0.990188100850379, 0.0954357913177669, 0.0122977018817933, - -0.151919274913335, 0.116685037647779, 84, -0.0176171186327778, - "Total", 0.797102533687855, 0.0685227674283383, -0.257098761389081, - -0.259206035105647, 0.150648079441109, 16, -0.054278977832269, - "Total", 0.603666487696113, 0.104556542308847, -0.519135164894186, - -0.185877072908425, 0.188224354729382, 16, 0.00117364091047894, - "Total", 0.990188100850379, 0.0954357913177669, 0.0122977018817933, -0.151919274913335, 0.116685037647779, 50, -0.0176171186327778, "Total", 0.797102533687855, 0.0685227674283383, -0.257098761389081, - -0.259206035105647, 0.150648079441109, 50, -0.054278977832269, + -0.259206035105647, 0.150648079441109, 84, -0.054278977832269, "Total", 0.603666487696113, 0.104556542308847, -0.519135164894186, - -0.023172578106807, 0.0445488723194967, 50, 0.0106881471063448, - "Total indirect", 0.536138281570805, 0.017276197664978, 0.618663163828674, - -0.0219696261639075, 0.0250246157540351, 84, 0.00152749479506379, - "Total indirect", 0.898613658537253, 0.0119885473122535, 0.127412834539389, - -0.0852940839382829, 0.0360454313067229, 50, -0.02462432631578, - "Total indirect", 0.426322705842423, 0.0309545267673581, -0.795500008798281, -0.023172578106807, 0.0445488723194967, 16, 0.0106881471063448, "Total indirect", 0.536138281570805, 0.017276197664978, 0.618663163828674, - -0.0219696261639075, 0.0250246157540351, 84, 0.00152749479506379, - "Total indirect", 0.898613658537253, 0.0119885473122535, 0.127412834539389, - -0.0852940839382829, 0.0360454313067229, 50, -0.02462432631578, - "Total indirect", 0.426322705842423, 0.0309545267673581, -0.795500008798281, - -0.023172578106807, 0.0445488723194967, 84, 0.0106881471063448, - "Total indirect", 0.536138281570805, 0.017276197664978, 0.618663163828674, - -0.0219696261639075, 0.0250246157540351, 84, 0.00152749479506379, + -0.0219696261639075, 0.0250246157540351, 50, 0.00152749479506379, "Total indirect", 0.898613658537253, 0.0119885473122535, 0.127412834539389, -0.0852940839382829, 0.0360454313067229, 84, -0.02462432631578, - "Total indirect", 0.426322705842423, 0.0309545267673581, -0.795500008798281, - 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 84, 50, - 84, 84, 84)) + "Total indirect", 0.426322705842423, 0.0309545267673581, -0.795500008798281 + )) @@ -7158,7 +7086,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 59 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -7169,25 +7097,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -7223,23 +7151,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0394515150885608, 1.19060350294847, 0.615027509018516, 0, "facGenderm", - "contNormal", "", "", "", 0.0362328060443888, 0.293666617585846, - 2.09430514804335, -0.260888183343639, 0.896654610578501, 0.317883213617431, - 1, "facGenderm", "contNormal", "", "", "", 0.281709693175039, - 0.295296955212619, 1.07648659427778, -0.0193101999638056, 0.0178505006722907, - -0.000729849645757428, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.938632448608744, 0.00947994476664245, - -0.0769888078172761, -0.0648264180318342, 0.0617527105345801, - -0.00153685374862704, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.962040135354011, 0.0322911873801902, - -0.0475935966842105, -0.0193101999638056, 0.0178505006722907, - -0.000729849645757428, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.938632448608744, 0.00947994476664245, - -0.0769888078172761, -0.0648264180318342, 0.0617527105345801, - -0.00153685374862704, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.962040135354011, 0.0322911873801902, - -0.0475935966842105)) + list(0.0394515150885608, 1.19060350294847, 0.615027509018516, 0, "m", + "facGender", "contNormal", "", "", "", 0.0362328060443888, + 0.293666617585846, 2.09430514804335, -0.260888183343639, 0.896654610578501, + 0.317883213617431, 1, "m", "facGender", "contNormal", "", "", + "", 0.281709693175039, 0.295296955212619, 1.07648659427778, + -0.0193101999638056, 0.0178505006722907, -0.000729849645757428, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.938632448608744, 0.00947994476664245, -0.0769888078172761, + -0.0648264180318342, 0.0617527105345801, -0.00153685374862704, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.962040135354011, 0.0322911873801902, -0.0475935966842105 + )) @@ -7270,27 +7193,19 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.038945344423192, 1.18964997432232, 0.614297659372758, 0, "Total", - 0.0363819210373773, 0.293552493560021, 2.09263308215489, -0.258981182497387, - 0.891673902234994, 0.316346359868804, 1, "Total", 0.281170002126905, - 0.293539854254619, 1.07769475007779, 0.038945344423192, 1.18964997432232, - 0.614297659372758, 0, "Total", 0.0363819210373773, 0.293552493560021, - 2.09263308215489, -0.258981182497387, 0.891673902234994, 0.316346359868804, - 0, "Total", 0.281170002126905, 0.293539854254619, 1.07769475007779, - 0.038945344423192, 1.18964997432232, 0.614297659372758, 1, "Total", - 0.0363819210373773, 0.293552493560021, 2.09263308215489, -0.258981182497387, - 0.891673902234994, 0.316346359868804, 0, "Total", 0.281170002126905, - 0.293539854254619, 1.07769475007779, -0.0193101999638056, 0.0178505006722907, - -0.000729849645757428, 0, "Total indirect", 0.938632448608744, - 0.00947994476664245, -0.0769888078172761, -0.0648264180318342, - 0.0617527105345801, -0.00153685374862704, 1, "Total indirect", - 0.962040135354011, 0.0322911873801902, -0.0475935966842105, + list(0.038945344423192, 1.18964997432232, 0.614297659372758, 0, "m", + "Total", 0.0363819210373773, 0.293552493560021, 2.09263308215489, + -0.258981182497387, 0.891673902234994, 0.316346359868804, 1, + "m", "Total", 0.281170002126905, 0.293539854254619, 1.07769475007779, + 0.038945344423192, 1.18964997432232, 0.614297659372758, 0, "m", + "Total", 0.0363819210373773, 0.293552493560021, 2.09263308215489, + -0.258981182497387, 0.891673902234994, 0.316346359868804, 1, + "m", "Total", 0.281170002126905, 0.293539854254619, 1.07769475007779, -0.0193101999638056, 0.0178505006722907, -0.000729849645757428, - 1, "Total indirect", 0.938632448608744, 0.00947994476664245, + 0, "m", "Total indirect", 0.938632448608744, 0.00947994476664245, -0.0769888078172761, -0.0648264180318342, 0.0617527105345801, - -0.00153685374862704, 1, "Total indirect", 0.962040135354011, - 0.0322911873801902, -0.0475935966842105, 0, 0, 1, 0, 0, 1, 1, - 1)) + -0.00153685374862704, 1, "m", "Total indirect", 0.962040135354011, + 0.0322911873801902, -0.0475935966842105)) @@ -7306,7 +7221,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 60 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -7317,25 +7232,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -7383,72 +7298,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.042690031780011, 16, 16, 0.00942052862240607, "contGamma", "debCollin1", "contNormal", "", "", 0.578908588115149, 0.0169745482162073, 0.554979637891708, -0.0219513917765559, - 0.0246576621301181, 16, 16, 0.00135313517678114, "contGamma", + 0.0246576621301181, 50, 16, 0.00135313517678114, "contGamma", "debCollin1", "contNormal", "", "", 0.909394942379237, 0.0118902832588558, 0.113801761263621, -0.114566136111851, 0.0603750258968596, - 50, 16, -0.0270955551074955, "contGamma", "debCollin1", "contNormal", - "", "", 0.543762379306674, 0.04462866751344, - -0.607133410365335, -0.0355938877553156, 0.0557480876744999, - 16, 50, 0.0100770999595921, "contGamma", "debCollin1", "contNormal", - "", "", 0.665409064993194, 0.0233019525231865, - 0.432457320886092, -0.0225861619050029, 0.0253874592099394, - 84, 50, 0.00140064865246823, "contGamma", "debCollin1", "contNormal", - "", "", 0.908883378604548, 0.0122383935351241, - 0.114447100303514, -0.0967822154854486, 0.041356713728694, 16, - 50, -0.0277127508783773, "contGamma", "debCollin1", "contNormal", - "", "", 0.431635161999922, 0.0352401703051089, - -0.786396621765465, -0.0683989305221845, 0.0900923352117064, - 16, 84, 0.010846702344761, "contGamma", "debCollin1", "contNormal", - "", "", 0.788492273475872, 0.0404321882912262, - 0.268268990702012, -0.0236594911008135, 0.0265721745785706, - 16, 84, 0.00145634173887856, "contGamma", "debCollin1", "contNormal", - "", "", 0.909516419096589, 0.012814435896681, - 0.113648525040088, -0.0923681412112868, 0.0354957430992253, - 50, 84, -0.0284361990560307, "contGamma", "debCollin1", "contNormal", - "", "", 0.383334061861697, 0.0326189372149402, - -0.871769637025646, -0.0238489745351989, 0.042690031780011, - 16, 16, 0.00942052862240607, "contGamma", "debCollin1", "contNormal", - "", "", 0.578908588115149, 0.0169745482162073, - 0.554979637891708, -0.0219513917765559, 0.0246576621301181, - 84, 16, 0.00135313517678114, "contGamma", "debCollin1", "contNormal", - "", "", 0.909394942379237, 0.0118902832588558, - 0.113801761263621, -0.114566136111851, 0.0603750258968596, 16, - 16, -0.0270955551074955, "contGamma", "debCollin1", "contNormal", + 84, 16, -0.0270955551074955, "contGamma", "debCollin1", "contNormal", "", "", 0.543762379306674, 0.04462866751344, -0.607133410365335, -0.0355938877553156, 0.0557480876744999, 16, 50, 0.0100770999595921, "contGamma", "debCollin1", "contNormal", "", "", 0.665409064993194, 0.0233019525231865, 0.432457320886092, -0.0225861619050029, 0.0253874592099394, - 16, 50, 0.00140064865246823, "contGamma", "debCollin1", "contNormal", - "", "", 0.908883378604548, 0.0122383935351241, - 0.114447100303514, -0.0967822154854486, 0.041356713728694, 50, - 50, -0.0277127508783773, "contGamma", "debCollin1", "contNormal", - "", "", 0.431635161999922, 0.0352401703051089, - -0.786396621765465, -0.0683989305221845, 0.0900923352117064, - 16, 84, 0.010846702344761, "contGamma", "debCollin1", "contNormal", - "", "", 0.788492273475872, 0.0404321882912262, - 0.268268990702012, -0.0236594911008135, 0.0265721745785706, - 84, 84, 0.00145634173887856, "contGamma", "debCollin1", "contNormal", - "", "", 0.909516419096589, 0.012814435896681, - 0.113648525040088, -0.0923681412112868, 0.0354957430992253, - 16, 84, -0.0284361990560307, "contGamma", "debCollin1", "contNormal", - "", "", 0.383334061861697, 0.0326189372149402, - -0.871769637025646, -0.0238489745351989, 0.042690031780011, - 16, 16, 0.00942052862240607, "contGamma", "debCollin1", "contNormal", - "", "", 0.578908588115149, 0.0169745482162073, - 0.554979637891708, -0.0219513917765559, 0.0246576621301181, - 50, 16, 0.00135313517678114, "contGamma", "debCollin1", "contNormal", - "", "", 0.909394942379237, 0.0118902832588558, - 0.113801761263621, -0.114566136111851, 0.0603750258968596, 50, - 16, -0.0270955551074955, "contGamma", "debCollin1", "contNormal", - "", "", 0.543762379306674, 0.04462866751344, - -0.607133410365335, -0.0355938877553156, 0.0557480876744999, - 50, 50, 0.0100770999595921, "contGamma", "debCollin1", "contNormal", - "", "", 0.665409064993194, 0.0233019525231865, - 0.432457320886092, -0.0225861619050029, 0.0253874592099394, - 84, 50, 0.00140064865246823, "contGamma", "debCollin1", "contNormal", + 50, 50, 0.00140064865246823, "contGamma", "debCollin1", "contNormal", "", "", 0.908883378604548, 0.0122383935351241, - 0.114447100303514, -0.0967822154854486, 0.041356713728694, 50, + 0.114447100303514, -0.0967822154854486, 0.041356713728694, 84, 50, -0.0277127508783773, "contGamma", "debCollin1", "contNormal", "", "", 0.431635161999922, 0.0352401703051089, -0.786396621765465, -0.0683989305221845, 0.0900923352117064, @@ -7458,7 +7319,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 50, 84, 0.00145634173887856, "contGamma", "debCollin1", "contNormal", "", "", 0.909516419096589, 0.012814435896681, 0.113648525040088, -0.0923681412112868, 0.0354957430992253, - 50, 84, -0.0284361990560307, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0284361990560307, "contGamma", "debCollin1", "contNormal", "", "", 0.383334061861697, 0.0326189372149402, -0.871769637025646)) @@ -7493,117 +7354,42 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.147683777314975, 0.129965673424241, 16, 16, -0.0088590519453667, - "Total", 0.90046462989647, 0.0708302430374434, -0.125074425350814, - -0.150864376358687, 0.117011485576704, 16, 16, -0.0169264453909916, - "Total", 0.804373476861831, 0.0683369347723635, -0.247691024588316, - -0.199274314911969, 0.108524043561433, 50, 16, -0.0453751356752682, - "Total", 0.563352272530683, 0.0785214322562242, -0.577869434770422, - -0.150433028069666, 0.134028066853305, 16, 50, -0.00820248060818063, - "Total", 0.910005389818184, 0.0725679393006105, -0.113031742216106, - -0.150795571822097, 0.117037707991488, 84, 50, -0.0168789319153045, - "Total", 0.804881128498322, 0.0683260717865787, -0.247035011291547, - -0.190036703939707, 0.0980520410474066, 16, 50, -0.0459923314461501, - "Total", 0.531444561167309, 0.0734933772404801, -0.625802394352583, - -0.163631660602083, 0.14876590415606, 16, 84, -0.00743287822301181, - "Total", 0.925691540617363, 0.0796947207250477, -0.0932668833692981, - -0.150780690701665, 0.117134213043877, 16, 84, -0.0168232388288942, - "Total", 0.805570074883638, 0.0683468946008245, -0.246144889642013, - -0.188137970843097, 0.0947064115954896, 50, 84, -0.0467157796238035, - "Total", 0.517352420908711, 0.072155505067855, -0.647431953804107, - -0.147683777314975, 0.129965673424241, 16, 16, -0.0088590519453667, - "Total", 0.90046462989647, 0.0708302430374434, -0.125074425350814, - -0.150864376358687, 0.117011485576704, 84, 16, -0.0169264453909916, - "Total", 0.804373476861831, 0.0683369347723635, -0.247691024588316, - -0.199274314911969, 0.108524043561433, 16, 16, -0.0453751356752682, - "Total", 0.563352272530683, 0.0785214322562242, -0.577869434770422, - -0.150433028069666, 0.134028066853305, 16, 50, -0.00820248060818063, - "Total", 0.910005389818184, 0.0725679393006105, -0.113031742216106, - -0.150795571822097, 0.117037707991488, 16, 50, -0.0168789319153045, - "Total", 0.804881128498322, 0.0683260717865787, -0.247035011291547, - -0.190036703939707, 0.0980520410474066, 50, 50, -0.0459923314461501, - "Total", 0.531444561167309, 0.0734933772404801, -0.625802394352583, - -0.163631660602083, 0.14876590415606, 16, 84, -0.00743287822301181, - "Total", 0.925691540617363, 0.0796947207250477, -0.0932668833692981, - -0.150780690701665, 0.117134213043877, 84, 84, -0.0168232388288942, - "Total", 0.805570074883638, 0.0683468946008245, -0.246144889642013, - -0.188137970843097, 0.0947064115954896, 16, 84, -0.0467157796238035, - "Total", 0.517352420908711, 0.072155505067855, -0.647431953804107, - -0.147683777314975, 0.129965673424241, 16, 16, -0.0088590519453667, "Total", 0.90046462989647, 0.0708302430374434, -0.125074425350814, -0.150864376358687, 0.117011485576704, 50, 16, -0.0169264453909916, "Total", 0.804373476861831, 0.0683369347723635, -0.247691024588316, - -0.199274314911969, 0.108524043561433, 50, 16, -0.0453751356752682, + -0.199274314911969, 0.108524043561433, 84, 16, -0.0453751356752682, "Total", 0.563352272530683, 0.0785214322562242, -0.577869434770422, - -0.150433028069666, 0.134028066853305, 50, 50, -0.00820248060818063, + -0.150433028069666, 0.134028066853305, 16, 50, -0.00820248060818063, "Total", 0.910005389818184, 0.0725679393006105, -0.113031742216106, - -0.150795571822097, 0.117037707991488, 84, 50, -0.0168789319153045, + -0.150795571822097, 0.117037707991488, 50, 50, -0.0168789319153045, "Total", 0.804881128498322, 0.0683260717865787, -0.247035011291547, - -0.190036703939707, 0.0980520410474066, 50, 50, -0.0459923314461501, + -0.190036703939707, 0.0980520410474066, 84, 50, -0.0459923314461501, "Total", 0.531444561167309, 0.0734933772404801, -0.625802394352583, -0.163631660602083, 0.14876590415606, 16, 84, -0.00743287822301181, "Total", 0.925691540617363, 0.0796947207250477, -0.0932668833692981, -0.150780690701665, 0.117134213043877, 50, 84, -0.0168232388288942, "Total", 0.805570074883638, 0.0683468946008245, -0.246144889642013, - -0.188137970843097, 0.0947064115954896, 50, 84, -0.0467157796238035, + -0.188137970843097, 0.0947064115954896, 84, 84, -0.0467157796238035, "Total", 0.517352420908711, 0.072155505067855, -0.647431953804107, - -0.0238489745351989, 0.042690031780011, 50, 16, 0.00942052862240607, - "Total indirect", 0.578908588115149, 0.0169745482162073, 0.554979637891708, - -0.0219513917765559, 0.0246576621301181, 84, 16, 0.00135313517678114, - "Total indirect", 0.909394942379237, 0.0118902832588558, 0.113801761263621, - -0.114566136111851, 0.0603750258968596, 50, 16, -0.0270955551074955, - "Total indirect", 0.543762379306674, 0.04462866751344, -0.607133410365335, - -0.0355938877553156, 0.0557480876744999, 16, 50, 0.0100770999595921, - "Total indirect", 0.665409064993194, 0.0233019525231865, 0.432457320886092, - -0.0225861619050029, 0.0253874592099394, 50, 50, 0.00140064865246823, - "Total indirect", 0.908883378604548, 0.0122383935351241, 0.114447100303514, - -0.0967822154854486, 0.041356713728694, 50, 50, -0.0277127508783773, - "Total indirect", 0.431635161999922, 0.0352401703051089, -0.786396621765465, - -0.0683989305221845, 0.0900923352117064, 50, 84, 0.010846702344761, - "Total indirect", 0.788492273475872, 0.0404321882912262, 0.268268990702012, - -0.0236594911008135, 0.0265721745785706, 84, 84, 0.00145634173887856, - "Total indirect", 0.909516419096589, 0.012814435896681, 0.113648525040088, - -0.0923681412112868, 0.0354957430992253, 50, 84, -0.0284361990560307, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, + "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, + "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, - -0.0238489745351989, 0.042690031780011, 16, 16, 0.00942052862240607, - "Total indirect", 0.578908588115149, 0.0169745482162073, 0.554979637891708, - -0.0219513917765559, 0.0246576621301181, 84, 16, 0.00135313517678114, - "Total indirect", 0.909394942379237, 0.0118902832588558, 0.113801761263621, - -0.114566136111851, 0.0603750258968596, 50, 16, -0.0270955551074955, - "Total indirect", 0.543762379306674, 0.04462866751344, -0.607133410365335, - -0.0355938877553156, 0.0557480876744999, 84, 50, 0.0100770999595921, - "Total indirect", 0.665409064993194, 0.0233019525231865, 0.432457320886092, - -0.0225861619050029, 0.0253874592099394, 84, 50, 0.00140064865246823, - "Total indirect", 0.908883378604548, 0.0122383935351241, 0.114447100303514, - -0.0967822154854486, 0.041356713728694, 84, 50, -0.0277127508783773, - "Total indirect", 0.431635161999922, 0.0352401703051089, -0.786396621765465, - -0.0683989305221845, 0.0900923352117064, 16, 84, 0.010846702344761, - "Total indirect", 0.788492273475872, 0.0404321882912262, 0.268268990702012, - -0.0236594911008135, 0.0265721745785706, 84, 84, 0.00145634173887856, - "Total indirect", 0.909516419096589, 0.012814435896681, 0.113648525040088, - -0.0923681412112868, 0.0354957430992253, 50, 84, -0.0284361990560307, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, - -0.0238489745351989, 0.042690031780011, 84, 16, 0.00942052862240607, - "Total indirect", 0.578908588115149, 0.0169745482162073, 0.554979637891708, - -0.0219513917765559, 0.0246576621301181, 84, 16, 0.00135313517678114, - "Total indirect", 0.909394942379237, 0.0118902832588558, 0.113801761263621, - -0.114566136111851, 0.0603750258968596, 84, 16, -0.0270955551074955, - "Total indirect", 0.543762379306674, 0.04462866751344, -0.607133410365335, - -0.0355938877553156, 0.0557480876744999, 16, 50, 0.0100770999595921, - "Total indirect", 0.665409064993194, 0.0233019525231865, 0.432457320886092, - -0.0225861619050029, 0.0253874592099394, 84, 50, 0.00140064865246823, - "Total indirect", 0.908883378604548, 0.0122383935351241, 0.114447100303514, - -0.0967822154854486, 0.041356713728694, 50, 50, -0.0277127508783773, - "Total indirect", 0.431635161999922, 0.0352401703051089, -0.786396621765465, - -0.0683989305221845, 0.0900923352117064, 84, 84, 0.010846702344761, - "Total indirect", 0.788492273475872, 0.0404321882912262, 0.268268990702012, - -0.0236594911008135, 0.0265721745785706, 84, 84, 0.00145634173887856, - "Total indirect", 0.909516419096589, 0.012814435896681, 0.113648525040088, - -0.0923681412112868, 0.0354957430992253, 84, 84, -0.0284361990560307, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, - 16, 16, 50, 16, 84, 16, 16, 16, 50, 16, 84, 16, 16, 16, 50, - 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 50, 50, 50, 84, 50, - 16, 50, 50, 50, 84, 50, 16, 84, 50, 84, 84, 84, 16, 84, 50, - 84, 84, 84, 16, 84, 50, 84, 84, 84)) + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, + "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, + "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, + "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646, + -0.0923681412112868, 0.0354957430992253, -0.0284361990560307, + "Total indirect", 0.383334061861697, 0.0326189372149402, -0.871769637025646 + )) @@ -7619,7 +7405,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 60 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -7630,25 +7416,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -7692,43 +7478,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0581216477750737, 0.876434140313882, "", 0.467277894044478, - "", "facGenderm", "contNormal", "", "", "", 0.0251961761247501, + "", "m", "facGender", "contNormal", "", "", "", 0.0251961761247501, 0.208757022831428, 2.23838167313684, -0.0352135525930009, 0.0329312897864334, - 16, -0.00114113140328377, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.94766297667838, 0.0173842078009984, - -0.0656418409367054, -0.0498539759508892, 0.0449861161782882, - 16, -0.00243392988630046, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.919868695074559, 0.0241943456301401, - -0.100599120286534, -0.0210858662121282, 0.0197394496518428, - 50, -0.000673208280142693, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.948461034754266, 0.0104148127684988, - -0.0646394990583908, -0.0640772689736427, 0.0577429719234073, - 50, -0.00316714852511768, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.9188262011312, 0.031077163115739, - -0.101912407941563, -0.00758194855537576, 0.0073324874399881, - 84, -0.000124730557693829, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.973847910513748, 0.00380477297363805, - -0.0327826544600805, -0.0815251893436663, 0.0734720027186823, - 84, -0.00402659331249202, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.918888582809418, 0.0395408265878727, - -0.101833817346828, -0.0352135525930009, 0.0329312897864334, - 16, -0.00114113140328377, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.94766297667838, 0.0173842078009984, + 16, -0.00114113140328377, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.94766297667838, 0.0173842078009984, -0.0656418409367054, -0.0498539759508892, 0.0449861161782882, - 16, -0.00243392988630046, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.919868695074559, 0.0241943456301401, + 16, -0.00243392988630046, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.919868695074559, 0.0241943456301401, -0.100599120286534, -0.0210858662121282, 0.0197394496518428, - 50, -0.000673208280142693, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.948461034754266, 0.0104148127684988, + 50, -0.000673208280142693, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.948461034754266, 0.0104148127684988, -0.0646394990583908, -0.0640772689736427, 0.0577429719234073, - 50, -0.00316714852511768, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.9188262011312, 0.031077163115739, + 50, -0.00316714852511768, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.9188262011312, 0.031077163115739, -0.101912407941563, -0.00758194855537576, 0.0073324874399881, - 84, -0.000124730557693829, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.973847910513748, 0.00380477297363805, + 84, -0.000124730557693829, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.973847910513748, 0.00380477297363805, -0.0327826544600805, -0.0815251893436663, 0.0734720027186823, - 84, -0.00402659331249202, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.918888582809418, 0.0395408265878727, + 84, -0.00402659331249202, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.918888582809418, 0.0395408265878727, -0.101833817346828)) @@ -7762,58 +7530,34 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0562756429896958, 0.875997882292692, 16, 0.466136762641194, - 0, "Total", 0.0258089001719735, 0.2091166587164, 2.22907522290397, - 0.056517481800642, 0.873170446515713, 16, 0.464843964158177, - 0, "Total", 0.0256647415514002, 0.208333666117522, 2.23124746384464, - 0.0573600141758646, 0.875849357352806, 50, 0.466604685764335, - 1, "Total", 0.0254387664643043, 0.208802138619148, 2.2346738824137, - 0.0550751123046838, 0.873146378734037, 50, 0.46411074551936, - 0, "Total", 0.0261574762684427, 0.208695484427825, 2.22386577645319, - 0.0580069168972354, 0.876299410076333, 84, 0.467153163486784, - 0, "Total", 0.0252315643645875, 0.208751920860201, 2.2378388738259, - 0.0526753714182566, 0.873827230045715, 84, 0.463251300731986, - 0, "Total", 0.0270067587827412, 0.20948136422521, 2.21142010624846, - 0.0562756429896958, 0.875997882292692, 16, 0.466136762641194, - 1, "Total", 0.0258089001719735, 0.2091166587164, 2.22907522290397, + list(0.0562756429896958, 0.875997882292692, "", 0.466136762641194, + "", "m", "Total", 0.0258089001719735, 0.2091166587164, 2.22907522290397, 0.056517481800642, 0.873170446515713, 16, 0.464843964158177, - 0, "Total", 0.0256647415514002, 0.208333666117522, 2.23124746384464, - 0.0573600141758646, 0.875849357352806, 50, 0.466604685764335, - 0, "Total", 0.0254387664643043, 0.208802138619148, 2.2346738824137, + 0, "m", "Total", 0.0256647415514002, 0.208333666117522, 2.23124746384464, + 0.0573600141758646, 0.875849357352806, 16, 0.466604685764335, + 1, "m", "Total", 0.0254387664643043, 0.208802138619148, 2.2346738824137, 0.0550751123046838, 0.873146378734037, 50, 0.46411074551936, - 0, "Total", 0.0261574762684427, 0.208695484427825, 2.22386577645319, - 0.0580069168972354, 0.876299410076333, 84, 0.467153163486784, - 1, "Total", 0.0252315643645875, 0.208751920860201, 2.2378388738259, + 0, "m", "Total", 0.0261574762684427, 0.208695484427825, 2.22386577645319, + 0.0580069168972354, 0.876299410076333, 50, 0.467153163486784, + 1, "m", "Total", 0.0252315643645875, 0.208751920860201, 2.2378388738259, 0.0526753714182566, 0.873827230045715, 84, 0.463251300731986, - 0, "Total", 0.0270067587827412, 0.20948136422521, 2.21142010624846, + 0, "m", "Total", 0.0270067587827412, 0.20948136422521, 2.21142010624846, + 0.0562756429896958, 0.875997882292692, 84, 0.466136762641194, + 1, "m", "Total", 0.0258089001719735, 0.2091166587164, 2.22907522290397, -0.0352135525930009, 0.0329312897864334, 16, -0.00114113140328377, - 0, "Total indirect", 0.94766297667838, 0.0173842078009984, -0.0656418409367054, - -0.0498539759508892, 0.0449861161782882, 16, -0.00243392988630046, - 1, "Total indirect", 0.919868695074559, 0.0241943456301401, - -0.100599120286534, -0.0210858662121282, 0.0197394496518428, - 50, -0.000673208280142693, 1, "Total indirect", 0.948461034754266, - 0.0104148127684988, -0.0646394990583908, -0.0640772689736427, - 0.0577429719234073, 50, -0.00316714852511768, 1, "Total indirect", - 0.9188262011312, 0.031077163115739, -0.101912407941563, -0.00758194855537576, - 0.0073324874399881, 84, -0.000124730557693829, 0, "Total indirect", - 0.973847910513748, 0.00380477297363805, -0.0327826544600805, - -0.0815251893436663, 0.0734720027186823, 84, -0.00402659331249202, - 1, "Total indirect", 0.918888582809418, 0.0395408265878727, - -0.101833817346828, -0.0352135525930009, 0.0329312897864334, - 16, -0.00114113140328377, 1, "Total indirect", 0.94766297667838, - 0.0173842078009984, -0.0656418409367054, -0.0498539759508892, - 0.0449861161782882, 16, -0.00243392988630046, 1, "Total indirect", - 0.919868695074559, 0.0241943456301401, -0.100599120286534, -0.0210858662121282, - 0.0197394496518428, 50, -0.000673208280142693, 0, "Total indirect", + 0, "m", "Total indirect", 0.94766297667838, 0.0173842078009984, + -0.0656418409367054, -0.0498539759508892, 0.0449861161782882, + 16, -0.00243392988630046, 1, "m", "Total indirect", 0.919868695074559, + 0.0241943456301401, -0.100599120286534, -0.0210858662121282, + 0.0197394496518428, 50, -0.000673208280142693, 0, "m", "Total indirect", 0.948461034754266, 0.0104148127684988, -0.0646394990583908, -0.0640772689736427, 0.0577429719234073, 50, -0.00316714852511768, - 1, "Total indirect", 0.9188262011312, 0.031077163115739, -0.101912407941563, - -0.00758194855537576, 0.0073324874399881, 84, -0.000124730557693829, - 1, "Total indirect", 0.973847910513748, 0.00380477297363805, - -0.0327826544600805, -0.0815251893436663, 0.0734720027186823, - 84, -0.00402659331249202, 1, "Total indirect", 0.918888582809418, - 0.0395408265878727, -0.101833817346828, 0, 0, 1, 0, 0, 0, 1, - 0, 0, 0, 1, 0, 0, 1, 1, 1, 0, 1, 1, 1, 0, 1, 1, 1)) + 1, "m", "Total indirect", 0.9188262011312, 0.031077163115739, + -0.101912407941563, -0.00758194855537576, 0.0073324874399881, + 84, -0.000124730557693829, 0, "m", "Total indirect", 0.973847910513748, + 0.00380477297363805, -0.0327826544600805, -0.0815251893436663, + 0.0734720027186823, 84, -0.00402659331249202, 1, "m", "Total indirect", + 0.918888582809418, 0.0395408265878727, -0.101833817346828)) @@ -7829,7 +7573,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 61 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -7840,27 +7584,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -7913,73 +7657,19 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) -0.0236252035630213, 0.0420224671176733, 16, 16, 0.00919863177732597, "contGamma", "debCollin1", "contNormal", "", "", 0.58282353868201, 0.0167471624985242, 0.549265093602368, -0.021954242825116, - 0.0249847711876894, 16, 16, 0.00151526418128672, "contGamma", + 0.0249847711876894, 50, 16, 0.00151526418128672, "contGamma", "debCollin1", "contNormal", "", "", 0.899303415416492, 0.0119744583020541, 0.126541355196568, -0.112761926367508, 0.0610949530168969, - 50, 16, -0.0258334866753056, "contGamma", "debCollin1", "contNormal", - "", "", 0.560254053476262, 0.044352059720425, - -0.582464193053222, -0.0350385407516562, 0.0547181475628596, - 16, 50, 0.0098398034056017, "contGamma", "debCollin1", "contNormal", - "", "", 0.667390607798634, 0.0228975351135289, - 0.429731993282888, -0.0225556956012239, 0.0256926434093449, - 84, 50, 0.00156847390406051, "contGamma", "debCollin1", "contNormal", - "", "", 0.898599763437687, 0.0123084759187275, - 0.127430391416216, -0.0968912045024092, 0.0440472792136955, - 16, 50, -0.0264219626443568, "contGamma", "debCollin1", "contNormal", - "", "", 0.462415529433845, 0.0359543554952564, - -0.734875157137577, -0.0669792494269835, 0.088161959363396, - 16, 84, 0.0105913549682063, "contGamma", "debCollin1", "contNormal", - "", "", 0.788999484691611, 0.0395775662242045, - 0.267610062433018, -0.0236709468035401, 0.0269326345363017, - 16, 84, 0.00163084386638079, "contGamma", "debCollin1", "contNormal", - "", "", 0.899470083390859, 0.0129093140840843, - 0.12633079153225, -0.0932789714188982, 0.0390554778068479, 50, - 84, -0.0271117468060252, "contGamma", "debCollin1", "contNormal", - "", "", 0.421924369070983, 0.033759408404844, - -0.803087141839103, -0.0236252035630213, 0.0420224671176733, - 16, 16, 0.00919863177732597, "contGamma", "debCollin1", "contNormal", - "", "", 0.58282353868201, 0.0167471624985242, - 0.549265093602368, -0.021954242825116, 0.0249847711876894, 84, - 16, 0.00151526418128672, "contGamma", "debCollin1", "contNormal", - "", "", 0.899303415416492, 0.0119744583020541, - 0.126541355196568, -0.112761926367508, 0.0610949530168969, 16, - 16, -0.0258334866753056, "contGamma", "debCollin1", "contNormal", + 84, 16, -0.0258334866753056, "contGamma", "debCollin1", "contNormal", "", "", 0.560254053476262, 0.044352059720425, -0.582464193053222, -0.0350385407516562, 0.0547181475628596, 16, 50, 0.0098398034056017, "contGamma", "debCollin1", "contNormal", "", "", 0.667390607798634, 0.0228975351135289, 0.429731993282888, -0.0225556956012239, 0.0256926434093449, - 16, 50, 0.00156847390406051, "contGamma", "debCollin1", "contNormal", - "", "", 0.898599763437687, 0.0123084759187275, - 0.127430391416216, -0.0968912045024092, 0.0440472792136955, - 50, 50, -0.0264219626443568, "contGamma", "debCollin1", "contNormal", - "", "", 0.462415529433845, 0.0359543554952564, - -0.734875157137577, -0.0669792494269835, 0.088161959363396, - 16, 84, 0.0105913549682063, "contGamma", "debCollin1", "contNormal", - "", "", 0.788999484691611, 0.0395775662242045, - 0.267610062433018, -0.0236709468035401, 0.0269326345363017, - 84, 84, 0.00163084386638079, "contGamma", "debCollin1", "contNormal", - "", "", 0.899470083390859, 0.0129093140840843, - 0.12633079153225, -0.0932789714188982, 0.0390554778068479, 16, - 84, -0.0271117468060252, "contGamma", "debCollin1", "contNormal", - "", "", 0.421924369070983, 0.033759408404844, - -0.803087141839103, -0.0236252035630213, 0.0420224671176733, - 16, 16, 0.00919863177732597, "contGamma", "debCollin1", "contNormal", - "", "", 0.58282353868201, 0.0167471624985242, - 0.549265093602368, -0.021954242825116, 0.0249847711876894, 50, - 16, 0.00151526418128672, "contGamma", "debCollin1", "contNormal", - "", "", 0.899303415416492, 0.0119744583020541, - 0.126541355196568, -0.112761926367508, 0.0610949530168969, 50, - 16, -0.0258334866753056, "contGamma", "debCollin1", "contNormal", - "", "", 0.560254053476262, 0.044352059720425, - -0.582464193053222, -0.0350385407516562, 0.0547181475628596, - 50, 50, 0.0098398034056017, "contGamma", "debCollin1", "contNormal", - "", "", 0.667390607798634, 0.0228975351135289, - 0.429731993282888, -0.0225556956012239, 0.0256926434093449, - 84, 50, 0.00156847390406051, "contGamma", "debCollin1", "contNormal", + 50, 50, 0.00156847390406051, "contGamma", "debCollin1", "contNormal", "", "", 0.898599763437687, 0.0123084759187275, 0.127430391416216, -0.0968912045024092, 0.0440472792136955, - 50, 50, -0.0264219626443568, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0264219626443568, "contGamma", "debCollin1", "contNormal", "", "", 0.462415529433845, 0.0359543554952564, -0.734875157137577, -0.0669792494269835, 0.088161959363396, 16, 84, 0.0105913549682063, "contGamma", "debCollin1", "contNormal", @@ -7987,7 +7677,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.267610062433018, -0.0236709468035401, 0.0269326345363017, 50, 84, 0.00163084386638079, "contGamma", "debCollin1", "contNormal", "", "", 0.899470083390859, 0.0129093140840843, - 0.12633079153225, -0.0932789714188982, 0.0390554778068479, 50, + 0.12633079153225, -0.0932789714188982, 0.0390554778068479, 84, 84, -0.0271117468060252, "contGamma", "debCollin1", "contNormal", "", "", 0.421924369070983, 0.033759408404844, -0.803087141839103)) @@ -8033,116 +7723,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.610004701841313, 0.108789699461788, -0.510066745409302, -0.189305242021853, 0.189968229334885, 16, 16, 0.000331493656515861, "Total", 0.99726636797262, 0.0967552144703677, 0.0034261063688447, - -0.151872143310645, 0.116724543378289, 16, 16, -0.0175737999661781, - "Total", 0.797584959415183, 0.0685208220170346, -0.256473863693712, - -0.262660200480341, 0.150503232665178, 50, 16, -0.0560784839075816, - "Total", 0.594691344318279, 0.105400771750017, -0.532050031289952, - -0.198593644832474, 0.200759735270715, 16, 50, 0.00108304521912045, - "Total", 0.991517981938092, 0.101877734298497, 0.0106308333864903, - -0.151851475833007, 0.116828615825291, 84, 50, -0.0175114300038578, - "Total", 0.798349070705501, 0.0685420991859065, -0.255484296685481, - -0.261356539561211, 0.147820003422711, 16, 50, -0.0567682680692499, - "Total", 0.586549981563949, 0.104383689244153, -0.543842323262489, - -0.18767563768044, 0.187056281736921, 16, 84, -0.000309677971759863, - "Total", 0.997415318615663, 0.0955966340129713, -0.00323942338511462, - -0.151958637452524, 0.11670461807462, 16, 84, -0.0176270096889518, - "Total", 0.797034673072234, 0.0685378041755678, -0.257186670932704, - -0.268713900772571, 0.157733884895511, 50, 84, -0.0554900079385304, - "Total", 0.610004701841313, 0.108789699461788, -0.510066745409302, - -0.189305242021853, 0.189968229334885, 16, 16, 0.000331493656515861, - "Total", 0.99726636797262, 0.0967552144703677, 0.0034261063688447, - -0.151872143310645, 0.116724543378289, 84, 16, -0.0175737999661781, + -0.151872143310645, 0.116724543378289, 50, 16, -0.0175737999661781, "Total", 0.797584959415183, 0.0685208220170346, -0.256473863693712, - -0.262660200480341, 0.150503232665178, 16, 16, -0.0560784839075816, + -0.262660200480341, 0.150503232665178, 84, 16, -0.0560784839075816, "Total", 0.594691344318279, 0.105400771750017, -0.532050031289952, -0.198593644832474, 0.200759735270715, 16, 50, 0.00108304521912045, "Total", 0.991517981938092, 0.101877734298497, 0.0106308333864903, - -0.151851475833007, 0.116828615825291, 16, 50, -0.0175114300038578, + -0.151851475833007, 0.116828615825291, 50, 50, -0.0175114300038578, "Total", 0.798349070705501, 0.0685420991859065, -0.255484296685481, - -0.261356539561211, 0.147820003422711, 50, 50, -0.0567682680692499, + -0.261356539561211, 0.147820003422711, 84, 50, -0.0567682680692499, "Total", 0.586549981563949, 0.104383689244153, -0.543842323262489, -0.18767563768044, 0.187056281736921, 16, 84, -0.000309677971759863, "Total", 0.997415318615663, 0.0955966340129713, -0.00323942338511462, - -0.151958637452524, 0.11670461807462, 84, 84, -0.0176270096889518, + -0.151958637452524, 0.11670461807462, 50, 84, -0.0176270096889518, "Total", 0.797034673072234, 0.0685378041755678, -0.257186670932704, - -0.268713900772571, 0.157733884895511, 16, 84, -0.0554900079385304, + -0.268713900772571, 0.157733884895511, 84, 84, -0.0554900079385304, "Total", 0.610004701841313, 0.108789699461788, -0.510066745409302, - -0.189305242021853, 0.189968229334885, 16, 16, 0.000331493656515861, - "Total", 0.99726636797262, 0.0967552144703677, 0.0034261063688447, - -0.151872143310645, 0.116724543378289, 50, 16, -0.0175737999661781, - "Total", 0.797584959415183, 0.0685208220170346, -0.256473863693712, - -0.262660200480341, 0.150503232665178, 50, 16, -0.0560784839075816, - "Total", 0.594691344318279, 0.105400771750017, -0.532050031289952, - -0.198593644832474, 0.200759735270715, 50, 50, 0.00108304521912045, - "Total", 0.991517981938092, 0.101877734298497, 0.0106308333864903, - -0.151851475833007, 0.116828615825291, 84, 50, -0.0175114300038578, - "Total", 0.798349070705501, 0.0685420991859065, -0.255484296685481, - -0.261356539561211, 0.147820003422711, 50, 50, -0.0567682680692499, - "Total", 0.586549981563949, 0.104383689244153, -0.543842323262489, - -0.18767563768044, 0.187056281736921, 16, 84, -0.000309677971759863, - "Total", 0.997415318615663, 0.0955966340129713, -0.00323942338511462, - -0.151958637452524, 0.11670461807462, 50, 84, -0.0176270096889518, - "Total", 0.797034673072234, 0.0685378041755678, -0.257186670932704, - -0.268713900772571, 0.157733884895511, 50, 84, -0.0554900079385304, - "Total", 0.610004701841313, 0.108789699461788, -0.510066745409302, - -0.0236252035630213, 0.0420224671176733, 50, 16, 0.00919863177732597, + -0.0236252035630213, 0.0420224671176733, 16, 16, 0.00919863177732597, "Total indirect", 0.58282353868201, 0.0167471624985242, 0.549265093602368, - -0.021954242825116, 0.0249847711876894, 84, 16, 0.00151526418128672, + -0.021954242825116, 0.0249847711876894, 50, 16, 0.00151526418128672, "Total indirect", 0.899303415416492, 0.0119744583020541, 0.126541355196568, - -0.112761926367508, 0.0610949530168969, 50, 16, -0.0258334866753056, + -0.112761926367508, 0.0610949530168969, 84, 16, -0.0258334866753056, "Total indirect", 0.560254053476262, 0.044352059720425, -0.582464193053222, -0.0350385407516562, 0.0547181475628596, 16, 50, 0.0098398034056017, "Total indirect", 0.667390607798634, 0.0228975351135289, 0.429731993282888, -0.0225556956012239, 0.0256926434093449, 50, 50, 0.00156847390406051, "Total indirect", 0.898599763437687, 0.0123084759187275, 0.127430391416216, - -0.0968912045024092, 0.0440472792136955, 50, 50, -0.0264219626443568, - "Total indirect", 0.462415529433845, 0.0359543554952564, -0.734875157137577, - -0.0669792494269835, 0.088161959363396, 50, 84, 0.0105913549682063, - "Total indirect", 0.788999484691611, 0.0395775662242045, 0.267610062433018, - -0.0236709468035401, 0.0269326345363017, 84, 84, 0.00163084386638079, - "Total indirect", 0.899470083390859, 0.0129093140840843, 0.12633079153225, - -0.0932789714188982, 0.0390554778068479, 50, 84, -0.0271117468060252, - "Total indirect", 0.421924369070983, 0.033759408404844, -0.803087141839103, - -0.0236252035630213, 0.0420224671176733, 16, 16, 0.00919863177732597, - "Total indirect", 0.58282353868201, 0.0167471624985242, 0.549265093602368, - -0.021954242825116, 0.0249847711876894, 84, 16, 0.00151526418128672, - "Total indirect", 0.899303415416492, 0.0119744583020541, 0.126541355196568, - -0.112761926367508, 0.0610949530168969, 50, 16, -0.0258334866753056, - "Total indirect", 0.560254053476262, 0.044352059720425, -0.582464193053222, - -0.0350385407516562, 0.0547181475628596, 84, 50, 0.0098398034056017, - "Total indirect", 0.667390607798634, 0.0228975351135289, 0.429731993282888, - -0.0225556956012239, 0.0256926434093449, 84, 50, 0.00156847390406051, - "Total indirect", 0.898599763437687, 0.0123084759187275, 0.127430391416216, -0.0968912045024092, 0.0440472792136955, 84, 50, -0.0264219626443568, "Total indirect", 0.462415529433845, 0.0359543554952564, -0.734875157137577, -0.0669792494269835, 0.088161959363396, 16, 84, 0.0105913549682063, "Total indirect", 0.788999484691611, 0.0395775662242045, 0.267610062433018, - -0.0236709468035401, 0.0269326345363017, 84, 84, 0.00163084386638079, - "Total indirect", 0.899470083390859, 0.0129093140840843, 0.12633079153225, - -0.0932789714188982, 0.0390554778068479, 50, 84, -0.0271117468060252, - "Total indirect", 0.421924369070983, 0.033759408404844, -0.803087141839103, - -0.0236252035630213, 0.0420224671176733, 84, 16, 0.00919863177732597, - "Total indirect", 0.58282353868201, 0.0167471624985242, 0.549265093602368, - -0.021954242825116, 0.0249847711876894, 84, 16, 0.00151526418128672, - "Total indirect", 0.899303415416492, 0.0119744583020541, 0.126541355196568, - -0.112761926367508, 0.0610949530168969, 84, 16, -0.0258334866753056, - "Total indirect", 0.560254053476262, 0.044352059720425, -0.582464193053222, - -0.0350385407516562, 0.0547181475628596, 16, 50, 0.0098398034056017, - "Total indirect", 0.667390607798634, 0.0228975351135289, 0.429731993282888, - -0.0225556956012239, 0.0256926434093449, 84, 50, 0.00156847390406051, - "Total indirect", 0.898599763437687, 0.0123084759187275, 0.127430391416216, - -0.0968912045024092, 0.0440472792136955, 50, 50, -0.0264219626443568, - "Total indirect", 0.462415529433845, 0.0359543554952564, -0.734875157137577, - -0.0669792494269835, 0.088161959363396, 84, 84, 0.0105913549682063, - "Total indirect", 0.788999484691611, 0.0395775662242045, 0.267610062433018, - -0.0236709468035401, 0.0269326345363017, 84, 84, 0.00163084386638079, + -0.0236709468035401, 0.0269326345363017, 50, 84, 0.00163084386638079, "Total indirect", 0.899470083390859, 0.0129093140840843, 0.12633079153225, -0.0932789714188982, 0.0390554778068479, 84, 84, -0.0271117468060252, - "Total indirect", 0.421924369070983, 0.033759408404844, -0.803087141839103, - 16, 16, 50, 16, 84, 16, 16, 16, 50, 16, 84, 16, 16, 16, 50, - 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 50, 50, 50, 84, 50, - 16, 50, 50, 50, 84, 50, 16, 84, 50, 84, 84, 84, 16, 84, 50, - 84, 84, 84, 16, 84, 50, 84, 84, 84)) + "Total indirect", 0.421924369070983, 0.033759408404844, -0.803087141839103 + )) @@ -8158,7 +7773,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 61 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -8169,27 +7784,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -8233,46 +7848,29 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.039451515200102, 1.19060350283693, "", 0.615027509018516, 0, - "facGenderm", "contNormal", "", "", "", 0.0362328060082577, + "m", "facGender", "contNormal", "", "", "", 0.0362328060082577, 0.293666617528936, 2.09430514844921, -0.260888183320162, 0.896654610555023, - "", 0.317883213617431, 1, "facGenderm", "contNormal", "", "", - "", 0.281709693155521, 0.29529695520064, 1.07648659432145, -0.0357576352088553, - 0.0329602721170154, 16, -0.00139868154591997, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.936407413397748, - 0.0175304005246802, -0.0797860575946814, -0.0477218060568078, - 0.0454659731231758, 16, -0.00112791646681602, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.962158076033123, - 0.0237728294792754, -0.0474456129759108, -0.0215577583028228, - 0.0199074657955391, 50, -0.000825146253641861, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.937823709807349, - 0.0105780576646904, -0.0780054599622958, -0.061925213988326, - 0.0589898050634176, 50, -0.00146770446245416, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.962049922556566, - 0.0308462349322503, -0.0475813163479363, -0.008917010350421, - 0.00861126063359005, 84, -0.000152874858415474, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.972727148902378, - 0.00447157986633219, -0.0341881086741876, -0.0787424861008131, - 0.075010509805128, 84, -0.00186598814784254, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.962056302471345, - 0.0392234237768462, -0.0475733112555067, -0.0357576352088553, - 0.0329602721170154, 16, -0.00139868154591997, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.936407413397748, - 0.0175304005246802, -0.0797860575946814, -0.0477218060568078, - 0.0454659731231758, 16, -0.00112791646681602, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.962158076033123, - 0.0237728294792754, -0.0474456129759108, -0.0215577583028228, - 0.0199074657955391, 50, -0.000825146253641861, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.937823709807349, - 0.0105780576646904, -0.0780054599622958, -0.061925213988326, - 0.0589898050634176, 50, -0.00146770446245416, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.962049922556566, - 0.0308462349322503, -0.0475813163479363, -0.008917010350421, - 0.00861126063359005, 84, -0.000152874858415474, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.972727148902378, - 0.00447157986633219, -0.0341881086741876, -0.0787424861008131, - 0.075010509805128, 84, -0.00186598814784254, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.962056302471345, - 0.0392234237768462, -0.0475733112555067)) + "", 0.317883213617431, 1, "m", "facGender", "contNormal", "", + "", "", 0.281709693155521, 0.29529695520064, 1.07648659432145, + -0.0357576352088553, 0.0329602721170154, "", -0.00139868154591997, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.936407413397748, 0.0175304005246802, -0.0797860575946814, + -0.0477218060568078, 0.0454659731231758, "", -0.00112791646681602, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.962158076033123, 0.0237728294792754, -0.0474456129759108, + -0.0215577583028228, 0.0199074657955391, 16, -0.000825146253641861, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.937823709807349, 0.0105780576646904, -0.0780054599622958, + -0.061925213988326, 0.0589898050634176, 16, -0.00146770446245416, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.962049922556566, 0.0308462349322503, -0.0475813163479363, + -0.008917010350421, 0.00861126063359005, 50, -0.000152874858415474, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.972727148902378, 0.00447157986633219, -0.0341881086741876, + -0.0787424861008131, 0.075010509805128, 50, -0.00186598814784254, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.962056302471345, 0.0392234237768462, -0.0475733112555067 + )) @@ -8309,63 +7907,36 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.03803060687691, 1.18922704806828, "", 0.613628827472596, 0, - "Total", 0.036666187593297, 0.293677957929805, 2.08946163953941, + "m", "Total", 0.036666187593297, 0.293677957929805, 2.08946163953941, -0.258823203740407, 0.892333798041636, "", 0.316755297150615, - 1, "Total", 0.280758330477552, 0.293667896671118, 1.07861737949978, - 0.0388449021132654, 1.18955982341648, 16, 0.614202362764874, - 0, "Total", 0.0364126051938256, 0.293555118966448, 2.09228973736641, - -0.258919506615524, 0.891750524925477, 16, 0.316415509154977, - 0, "Total", 0.281071102285855, 0.293543667286067, 1.07791631848293, - 0.0393415773666859, 1.19040769095352, 50, 0.6148746341601, 1, - "Total", 0.0362652559373391, 0.293644710480981, 2.0939407801794, - -0.25948010430035, 0.891514555239526, 50, 0.316017225469588, - 0, "Total", 0.281812838239467, 0.293626482072828, 1.07625587187741, - 0.03803060687691, 1.18922704806828, 84, 0.613628827472596, 0, - "Total", 0.036666187593297, 0.293677957929805, 2.08946163953941, - -0.258823203740407, 0.892333798041636, 84, 0.316755297150615, - 0, "Total", 0.280758330477552, 0.293667896671118, 1.07861737949978, - 0.0388449021132654, 1.18955982341648, 16, 0.614202362764874, - 1, "Total", 0.0364126051938256, 0.293555118966448, 2.09228973736641, - -0.258919506615524, 0.891750524925477, 16, 0.316415509154977, - 0, "Total", 0.281071102285855, 0.293543667286067, 1.07791631848293, - 0.0393415773666859, 1.19040769095352, 50, 0.6148746341601, 0, - "Total", 0.0362652559373391, 0.293644710480981, 2.0939407801794, - -0.25948010430035, 0.891514555239526, 50, 0.316017225469588, - 0, "Total", 0.281812838239467, 0.293626482072828, 1.07625587187741, - 0.03803060687691, 1.18922704806828, 84, 0.613628827472596, 1, - "Total", 0.036666187593297, 0.293677957929805, 2.08946163953941, - -0.258823203740407, 0.892333798041636, 84, 0.316755297150615, - 0, "Total", 0.280758330477552, 0.293667896671118, 1.07861737949978, - -0.0357576352088553, 0.0329602721170154, 16, -0.00139868154591997, - 0, "Total indirect", 0.936407413397748, 0.0175304005246802, - -0.0797860575946814, -0.0477218060568078, 0.0454659731231758, - 16, -0.00112791646681602, 1, "Total indirect", 0.962158076033123, - 0.0237728294792754, -0.0474456129759108, -0.0215577583028228, - 0.0199074657955391, 50, -0.000825146253641861, 1, "Total indirect", - 0.937823709807349, 0.0105780576646904, -0.0780054599622958, - -0.061925213988326, 0.0589898050634176, 50, -0.00146770446245416, - 1, "Total indirect", 0.962049922556566, 0.0308462349322503, - -0.0475813163479363, -0.008917010350421, 0.00861126063359005, - 84, -0.000152874858415474, 0, "Total indirect", 0.972727148902378, - 0.00447157986633219, -0.0341881086741876, -0.0787424861008131, - 0.075010509805128, 84, -0.00186598814784254, 1, "Total indirect", - 0.962056302471345, 0.0392234237768462, -0.0475733112555067, - -0.0357576352088553, 0.0329602721170154, 16, -0.00139868154591997, - 1, "Total indirect", 0.936407413397748, 0.0175304005246802, + 1, "m", "Total", 0.280758330477552, 0.293667896671118, 1.07861737949978, + 0.0388449021132654, 1.18955982341648, "", 0.614202362764874, + 0, "m", "Total", 0.0364126051938256, 0.293555118966448, 2.09228973736641, + -0.258919506615524, 0.891750524925477, "", 0.316415509154977, + 1, "m", "Total", 0.281071102285855, 0.293543667286067, 1.07791631848293, + 0.0393415773666859, 1.19040769095352, 16, 0.6148746341601, 0, + "m", "Total", 0.0362652559373391, 0.293644710480981, 2.0939407801794, + -0.25948010430035, 0.891514555239526, 16, 0.316017225469588, + 1, "m", "Total", 0.281812838239467, 0.293626482072828, 1.07625587187741, + 0.03803060687691, 1.18922704806828, 50, 0.613628827472596, 0, + "m", "Total", 0.036666187593297, 0.293677957929805, 2.08946163953941, + -0.258823203740407, 0.892333798041636, 50, 0.316755297150615, + 1, "m", "Total", 0.280758330477552, 0.293667896671118, 1.07861737949978, + -0.0357576352088553, 0.0329602721170154, 84, -0.00139868154591997, + 0, "m", "Total indirect", 0.936407413397748, 0.0175304005246802, -0.0797860575946814, -0.0477218060568078, 0.0454659731231758, - 16, -0.00112791646681602, 1, "Total indirect", 0.962158076033123, + 84, -0.00112791646681602, 1, "m", "Total indirect", 0.962158076033123, 0.0237728294792754, -0.0474456129759108, -0.0215577583028228, - 0.0199074657955391, 50, -0.000825146253641861, 0, "Total indirect", + 0.0199074657955391, 16, -0.000825146253641861, 0, "m", "Total indirect", 0.937823709807349, 0.0105780576646904, -0.0780054599622958, - -0.061925213988326, 0.0589898050634176, 50, -0.00146770446245416, - 1, "Total indirect", 0.962049922556566, 0.0308462349322503, + -0.061925213988326, 0.0589898050634176, 16, -0.00146770446245416, + 1, "m", "Total indirect", 0.962049922556566, 0.0308462349322503, -0.0475813163479363, -0.008917010350421, 0.00861126063359005, - 84, -0.000152874858415474, 1, "Total indirect", 0.972727148902378, + 50, -0.000152874858415474, 0, "m", "Total indirect", 0.972727148902378, 0.00447157986633219, -0.0341881086741876, -0.0787424861008131, - 0.075010509805128, 84, -0.00186598814784254, 1, "Total indirect", + 0.075010509805128, 50, -0.00186598814784254, 1, "m", "Total indirect", 0.962056302471345, 0.0392234237768462, -0.0475733112555067, - 0, 0, 1, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, 1, 1, 0, 1, 1, 1, - 0, 1, 1, 1)) + 84, 84)) @@ -8381,7 +7952,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 62 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -8392,27 +7963,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -8465,73 +8036,19 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) -0.0233878220055953, 0.0416922047357785, 16, 16, 0.00915219136509161, "contGamma", "debCollin1", "contNormal", "", "", 0.581456345993643, 0.0166023527102326, 0.551258699584836, -0.0224390039726656, - 0.0239564126001832, 16, 16, 0.000758704313758788, "contGamma", + 0.0239564126001832, 50, 16, 0.000758704313758788, "contGamma", "debCollin1", "contNormal", "", "", 0.948888541398985, 0.0118357829375463, 0.0641025877005546, -0.118491951120062, - 0.0622598723529721, 50, 16, -0.0281160393835451, "contGamma", + 0.0622598723529721, 84, 16, -0.0281160393835451, "contGamma", "debCollin1", "contNormal", "", "", 0.542029535893431, 0.0461110063498059, -0.60974681771749, -0.034762142155311, 0.0543422323534684, 16, 50, 0.00979004509907866, "contGamma", "debCollin1", "contNormal", "", "", 0.666694537309026, 0.0227311254726167, 0.430688973622197, -0.0231840189907873, 0.0247547078235187, - 84, 50, 0.000785344416365697, "contGamma", "debCollin1", "contNormal", - "", "", 0.948797236607138, 0.0122294917642469, - 0.0642172570622816, -0.0999112865838791, 0.0423983640311969, - 16, 50, -0.0287564612763411, "contGamma", "debCollin1", "contNormal", - "", "", 0.428303260798277, 0.0363041493970288, - -0.792098472322135, -0.0665724728388061, 0.0876478879994241, - 16, 84, 0.010537707580309, "contGamma", "debCollin1", "contNormal", - "", "", 0.788819119336337, 0.0393426517157205, - 0.26784436535828, -0.0241611134918251, 0.0257942549031149, 16, - 84, 0.00081657070564492, "contGamma", "debCollin1", "contNormal", - "", "", 0.948910378647849, 0.0127439506003635, - 0.0640751625027196, -0.095259533046235, 0.0362452649784638, - 50, 84, -0.0295071340338856, "contGamma", "debCollin1", "contNormal", - "", "", 0.37909985961747, 0.03354775880118, - -0.879556044526221, -0.0233878220055953, 0.0416922047357785, - 16, 16, 0.00915219136509161, "contGamma", "debCollin1", "contNormal", - "", "", 0.581456345993643, 0.0166023527102326, - 0.551258699584836, -0.0224390039726656, 0.0239564126001832, - 84, 16, 0.000758704313758788, "contGamma", "debCollin1", "contNormal", - "", "", 0.948888541398985, 0.0118357829375463, - 0.0641025877005546, -0.118491951120062, 0.0622598723529721, - 16, 16, -0.0281160393835451, "contGamma", "debCollin1", "contNormal", - "", "", 0.542029535893431, 0.0461110063498059, - -0.60974681771749, -0.034762142155311, 0.0543422323534684, 16, - 50, 0.00979004509907866, "contGamma", "debCollin1", "contNormal", - "", "", 0.666694537309026, 0.0227311254726167, - 0.430688973622197, -0.0231840189907873, 0.0247547078235187, - 16, 50, 0.000785344416365697, "contGamma", "debCollin1", "contNormal", - "", "", 0.948797236607138, 0.0122294917642469, - 0.0642172570622816, -0.0999112865838791, 0.0423983640311969, - 50, 50, -0.0287564612763411, "contGamma", "debCollin1", "contNormal", - "", "", 0.428303260798277, 0.0363041493970288, - -0.792098472322135, -0.0665724728388061, 0.0876478879994241, - 16, 84, 0.010537707580309, "contGamma", "debCollin1", "contNormal", - "", "", 0.788819119336337, 0.0393426517157205, - 0.26784436535828, -0.0241611134918251, 0.0257942549031149, 84, - 84, 0.00081657070564492, "contGamma", "debCollin1", "contNormal", - "", "", 0.948910378647849, 0.0127439506003635, - 0.0640751625027196, -0.095259533046235, 0.0362452649784638, - 16, 84, -0.0295071340338856, "contGamma", "debCollin1", "contNormal", - "", "", 0.37909985961747, 0.03354775880118, - -0.879556044526221, -0.0233878220055953, 0.0416922047357785, - 16, 16, 0.00915219136509161, "contGamma", "debCollin1", "contNormal", - "", "", 0.581456345993643, 0.0166023527102326, - 0.551258699584836, -0.0224390039726656, 0.0239564126001832, - 50, 16, 0.000758704313758788, "contGamma", "debCollin1", "contNormal", - "", "", 0.948888541398985, 0.0118357829375463, - 0.0641025877005546, -0.118491951120062, 0.0622598723529721, - 50, 16, -0.0281160393835451, "contGamma", "debCollin1", "contNormal", - "", "", 0.542029535893431, 0.0461110063498059, - -0.60974681771749, -0.034762142155311, 0.0543422323534684, 50, - 50, 0.00979004509907866, "contGamma", "debCollin1", "contNormal", - "", "", 0.666694537309026, 0.0227311254726167, - 0.430688973622197, -0.0231840189907873, 0.0247547078235187, - 84, 50, 0.000785344416365697, "contGamma", "debCollin1", "contNormal", + 50, 50, 0.000785344416365697, "contGamma", "debCollin1", "contNormal", "", "", 0.948797236607138, 0.0122294917642469, 0.0642172570622816, -0.0999112865838791, 0.0423983640311969, - 50, 50, -0.0287564612763411, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0287564612763411, "contGamma", "debCollin1", "contNormal", "", "", 0.428303260798277, 0.0363041493970288, -0.792098472322135, -0.0665724728388061, 0.0876478879994241, 16, 84, 0.010537707580309, "contGamma", "debCollin1", "contNormal", @@ -8540,7 +8057,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 84, 0.00081657070564492, "contGamma", "debCollin1", "contNormal", "", "", 0.948910378647849, 0.0127439506003635, 0.0640751625027196, -0.095259533046235, 0.0362452649784638, - 50, 84, -0.0295071340338856, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0295071340338856, "contGamma", "debCollin1", "contNormal", "", "", 0.37909985961747, 0.03354775880118, -0.879556044526221)) @@ -8587,116 +8104,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.62434342201583, 0.111403735339878, -0.48970392783913, -0.177377254804496, 0.186008819099454, 16, 16, 0.00431578214747878, "Total", 0.9628676424387, 0.0927022324824061, 0.0465553205344636, - -0.14820790387821, 0.119527062189761, 16, 16, -0.0143404208442248, - "Total", 0.833699524289928, 0.0683009912885722, -0.209959190542879, - -0.265949063962711, 0.155558526633341, 50, 16, -0.0551952686646854, - "Total", 0.607738777445379, 0.107529422458997, -0.513303869791847, - -0.187069009057491, 0.197195898314909, 16, 50, 0.00506344462870914, - "Total", 0.95880538900277, 0.098028563382652, 0.0516527474644723, - -0.148183721497768, 0.119565332387877, 84, 50, -0.0143091945549456, - "Total", 0.834064975340113, 0.0683045851856502, -0.209490980964946, - -0.264506487364336, 0.152614604519876, 16, 50, -0.0559459414222299, - "Total", 0.599057509891868, 0.106410397123215, -0.525756344630955, - -0.175588008611627, 0.18294386543861, 16, 84, 0.00367792841349174, - "Total", 0.967924264767223, 0.0914638934384232, 0.0402118068149794, - -0.148249856796754, 0.11951573490309, 16, 84, -0.0143670609468317, - "Total", 0.833413890506173, 0.0683088040933265, -0.210325171660198, - -0.272902155781283, 0.163792462237504, 50, 84, -0.0545548467718894, - "Total", 0.62434342201583, 0.111403735339878, -0.48970392783913, - -0.177377254804496, 0.186008819099454, 16, 16, 0.00431578214747878, - "Total", 0.9628676424387, 0.0927022324824061, 0.0465553205344636, - -0.14820790387821, 0.119527062189761, 84, 16, -0.0143404208442248, - "Total", 0.833699524289928, 0.0683009912885722, -0.209959190542879, - -0.265949063962711, 0.155558526633341, 16, 16, -0.0551952686646854, - "Total", 0.607738777445379, 0.107529422458997, -0.513303869791847, - -0.187069009057491, 0.197195898314909, 16, 50, 0.00506344462870914, - "Total", 0.95880538900277, 0.098028563382652, 0.0516527474644723, - -0.148183721497768, 0.119565332387877, 16, 50, -0.0143091945549456, - "Total", 0.834064975340113, 0.0683045851856502, -0.209490980964946, - -0.264506487364336, 0.152614604519876, 50, 50, -0.0559459414222299, - "Total", 0.599057509891868, 0.106410397123215, -0.525756344630955, - -0.175588008611627, 0.18294386543861, 16, 84, 0.00367792841349174, - "Total", 0.967924264767223, 0.0914638934384232, 0.0402118068149794, - -0.148249856796754, 0.11951573490309, 84, 84, -0.0143670609468317, - "Total", 0.833413890506173, 0.0683088040933265, -0.210325171660198, - -0.272902155781283, 0.163792462237504, 16, 84, -0.0545548467718894, - "Total", 0.62434342201583, 0.111403735339878, -0.48970392783913, - -0.177377254804496, 0.186008819099454, 16, 16, 0.00431578214747878, - "Total", 0.9628676424387, 0.0927022324824061, 0.0465553205344636, -0.14820790387821, 0.119527062189761, 50, 16, -0.0143404208442248, "Total", 0.833699524289928, 0.0683009912885722, -0.209959190542879, - -0.265949063962711, 0.155558526633341, 50, 16, -0.0551952686646854, + -0.265949063962711, 0.155558526633341, 84, 16, -0.0551952686646854, "Total", 0.607738777445379, 0.107529422458997, -0.513303869791847, - -0.187069009057491, 0.197195898314909, 50, 50, 0.00506344462870914, + -0.187069009057491, 0.197195898314909, 16, 50, 0.00506344462870914, "Total", 0.95880538900277, 0.098028563382652, 0.0516527474644723, - -0.148183721497768, 0.119565332387877, 84, 50, -0.0143091945549456, + -0.148183721497768, 0.119565332387877, 50, 50, -0.0143091945549456, "Total", 0.834064975340113, 0.0683045851856502, -0.209490980964946, - -0.264506487364336, 0.152614604519876, 50, 50, -0.0559459414222299, + -0.264506487364336, 0.152614604519876, 84, 50, -0.0559459414222299, "Total", 0.599057509891868, 0.106410397123215, -0.525756344630955, -0.175588008611627, 0.18294386543861, 16, 84, 0.00367792841349174, "Total", 0.967924264767223, 0.0914638934384232, 0.0402118068149794, -0.148249856796754, 0.11951573490309, 50, 84, -0.0143670609468317, "Total", 0.833413890506173, 0.0683088040933265, -0.210325171660198, - -0.272902155781283, 0.163792462237504, 50, 84, -0.0545548467718894, + -0.272902155781283, 0.163792462237504, 84, 84, -0.0545548467718894, "Total", 0.62434342201583, 0.111403735339878, -0.48970392783913, - -0.0233878220055953, 0.0416922047357785, 50, 16, 0.00915219136509161, + -0.0233878220055953, 0.0416922047357785, 16, 16, 0.00915219136509161, "Total indirect", 0.581456345993643, 0.0166023527102326, 0.551258699584836, - -0.0224390039726656, 0.0239564126001832, 84, 16, 0.000758704313758788, + -0.0224390039726656, 0.0239564126001832, 50, 16, 0.000758704313758788, "Total indirect", 0.948888541398985, 0.0118357829375463, 0.0641025877005546, - -0.118491951120062, 0.0622598723529721, 50, 16, -0.0281160393835451, + -0.118491951120062, 0.0622598723529721, 84, 16, -0.0281160393835451, "Total indirect", 0.542029535893431, 0.0461110063498059, -0.60974681771749, -0.034762142155311, 0.0543422323534684, 16, 50, 0.00979004509907866, "Total indirect", 0.666694537309026, 0.0227311254726167, 0.430688973622197, -0.0231840189907873, 0.0247547078235187, 50, 50, 0.000785344416365697, "Total indirect", 0.948797236607138, 0.0122294917642469, 0.0642172570622816, - -0.0999112865838791, 0.0423983640311969, 50, 50, -0.0287564612763411, - "Total indirect", 0.428303260798277, 0.0363041493970288, -0.792098472322135, - -0.0665724728388061, 0.0876478879994241, 50, 84, 0.010537707580309, - "Total indirect", 0.788819119336337, 0.0393426517157205, 0.26784436535828, - -0.0241611134918251, 0.0257942549031149, 84, 84, 0.00081657070564492, - "Total indirect", 0.948910378647849, 0.0127439506003635, 0.0640751625027196, - -0.095259533046235, 0.0362452649784638, 50, 84, -0.0295071340338856, - "Total indirect", 0.37909985961747, 0.03354775880118, -0.879556044526221, - -0.0233878220055953, 0.0416922047357785, 16, 16, 0.00915219136509161, - "Total indirect", 0.581456345993643, 0.0166023527102326, 0.551258699584836, - -0.0224390039726656, 0.0239564126001832, 84, 16, 0.000758704313758788, - "Total indirect", 0.948888541398985, 0.0118357829375463, 0.0641025877005546, - -0.118491951120062, 0.0622598723529721, 50, 16, -0.0281160393835451, - "Total indirect", 0.542029535893431, 0.0461110063498059, -0.60974681771749, - -0.034762142155311, 0.0543422323534684, 84, 50, 0.00979004509907866, - "Total indirect", 0.666694537309026, 0.0227311254726167, 0.430688973622197, - -0.0231840189907873, 0.0247547078235187, 84, 50, 0.000785344416365697, - "Total indirect", 0.948797236607138, 0.0122294917642469, 0.0642172570622816, -0.0999112865838791, 0.0423983640311969, 84, 50, -0.0287564612763411, "Total indirect", 0.428303260798277, 0.0363041493970288, -0.792098472322135, -0.0665724728388061, 0.0876478879994241, 16, 84, 0.010537707580309, "Total indirect", 0.788819119336337, 0.0393426517157205, 0.26784436535828, - -0.0241611134918251, 0.0257942549031149, 84, 84, 0.00081657070564492, - "Total indirect", 0.948910378647849, 0.0127439506003635, 0.0640751625027196, - -0.095259533046235, 0.0362452649784638, 50, 84, -0.0295071340338856, - "Total indirect", 0.37909985961747, 0.03354775880118, -0.879556044526221, - -0.0233878220055953, 0.0416922047357785, 84, 16, 0.00915219136509161, - "Total indirect", 0.581456345993643, 0.0166023527102326, 0.551258699584836, - -0.0224390039726656, 0.0239564126001832, 84, 16, 0.000758704313758788, - "Total indirect", 0.948888541398985, 0.0118357829375463, 0.0641025877005546, - -0.118491951120062, 0.0622598723529721, 84, 16, -0.0281160393835451, - "Total indirect", 0.542029535893431, 0.0461110063498059, -0.60974681771749, - -0.034762142155311, 0.0543422323534684, 16, 50, 0.00979004509907866, - "Total indirect", 0.666694537309026, 0.0227311254726167, 0.430688973622197, - -0.0231840189907873, 0.0247547078235187, 84, 50, 0.000785344416365697, - "Total indirect", 0.948797236607138, 0.0122294917642469, 0.0642172570622816, - -0.0999112865838791, 0.0423983640311969, 50, 50, -0.0287564612763411, - "Total indirect", 0.428303260798277, 0.0363041493970288, -0.792098472322135, - -0.0665724728388061, 0.0876478879994241, 84, 84, 0.010537707580309, - "Total indirect", 0.788819119336337, 0.0393426517157205, 0.26784436535828, - -0.0241611134918251, 0.0257942549031149, 84, 84, 0.00081657070564492, + -0.0241611134918251, 0.0257942549031149, 50, 84, 0.00081657070564492, "Total indirect", 0.948910378647849, 0.0127439506003635, 0.0640751625027196, -0.095259533046235, 0.0362452649784638, 84, 84, -0.0295071340338856, - "Total indirect", 0.37909985961747, 0.03354775880118, -0.879556044526221, - 16, 16, 50, 16, 84, 16, 16, 16, 50, 16, 84, 16, 16, 16, 50, - 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 50, 50, 50, 84, 50, - 16, 50, 50, 50, 84, 50, 16, 84, 50, 84, 84, 84, 16, 84, 50, - 84, 84, 84, 16, 84, 50, 84, 84, 84)) + "Total indirect", 0.37909985961747, 0.03354775880118, -0.879556044526221 + )) @@ -8712,7 +8154,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 62 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -8723,27 +8165,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -8787,48 +8229,30 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.14361020904034, 1.01999494403653, 16, 0.438192367498097, "", - "facGenderm", "contNormal", "", "", "", 0.139897454044454, + "m", "facGender", "contNormal", "", "", "", 0.139897454044454, 0.296843503823346, 1.47617300649728, 0.0679150327056879, 0.889736447515249, - 50, 0.478825740110468, "", "facGenderm", "contNormal", "", "", - "", 0.0223770880750054, 0.209652172512348, 2.28390545336355, + 50, 0.478825740110468, "", "m", "facGender", "contNormal", "", + "", "", 0.0223770880750054, 0.209652172512348, 2.28390545336355, -0.0768017820425038, 1.12971036140505, 84, 0.526454289681271, - "", "facGenderm", "contNormal", "", "", "", 0.0871851118017952, + "", "m", "facGender", "contNormal", "", "", "", 0.0871851118017952, 0.307789365764974, 1.71043690340903, -0.0350111801968114, 0.0328538804008177, - 16, -0.00107864989799686, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.950321151845348, 0.0173128335859587, - -0.0623034867539928, -0.0485078945298809, 0.0452387479712615, - 16, -0.00163457327930967, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.945508496138255, 0.0239153992727938, - -0.0683481492683741, -0.0209347798859799, 0.0196620766933927, - 50, -0.000636351596293605, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.951005235649467, 0.0103565312678181, - -0.0614444720763802, -0.062758571874601, 0.0585046489310939, - 50, -0.00212696147175355, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.945184093138401, 0.0309350635425456, - -0.0687556845916381, -0.00726315695143317, 0.00702733675591923, - 84, -0.000117910097756974, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974198425894715, 0.00364560109779414, - -0.0323431156053573, -0.0798153039994503, 0.0744070719782492, - 84, -0.00270411601060053, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.945203319608379, 0.0393431657913579, - -0.0687315307807416, -0.0350111801968114, 0.0328538804008177, - 16, -0.00107864989799686, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.950321151845348, 0.0173128335859587, + 16, -0.00107864989799686, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.950321151845348, 0.0173128335859587, -0.0623034867539928, -0.0485078945298809, 0.0452387479712615, - 16, -0.00163457327930967, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.945508496138255, 0.0239153992727938, + 16, -0.00163457327930967, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.945508496138255, 0.0239153992727938, -0.0683481492683741, -0.0209347798859799, 0.0196620766933927, - 50, -0.000636351596293605, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.951005235649467, 0.0103565312678181, + 50, -0.000636351596293605, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.951005235649467, 0.0103565312678181, -0.0614444720763802, -0.062758571874601, 0.0585046489310939, - 50, -0.00212696147175355, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.945184093138401, 0.0309350635425456, + 50, -0.00212696147175355, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.945184093138401, 0.0309350635425456, -0.0687556845916381, -0.00726315695143317, 0.00702733675591923, - 84, -0.000117910097756974, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974198425894715, 0.00364560109779414, + 84, -0.000117910097756974, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.974198425894715, 0.00364560109779414, -0.0323431156053573, -0.0798153039994503, 0.0744070719782492, - 84, -0.00270411601060053, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.945203319608379, 0.0393431657913579, + 84, -0.00270411601060053, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.945203319608379, 0.0393431657913579, -0.0687315307807416)) @@ -8867,65 +8291,38 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.145651123385784, 1.01987855858598, 16, 0.4371137176001, "", - "Total", 0.141532557678635, 0.297334464093554, 1.47010780917265, + "m", "Total", 0.141532557678635, 0.297334464093554, 1.47010780917265, 0.0667448896656013, 0.887637443996716, 50, 0.477191166831159, - "", "Total", 0.0226858368096772, 0.209415213954494, 2.27868433157322, - -0.07724122941283, 1.12887710558279, 84, 0.525817938084978, - "", "Total", 0.087464433396498, 0.30768890257916, 1.70892721082035, - -0.147665837320681, 1.01979664937337, 16, 0.436065406026343, - 0, "Total", 0.143151849452702, 0.297827535583012, 1.46415409566723, - 0.0678046313902036, 0.889611028635219, 16, 0.478707830012711, - 0, "Total", 0.0224077135468204, 0.209648341430587, 2.28338477064083, - -0.0785176150729263, 1.12601796241427, 50, 0.523750173670671, - 1, "Total", 0.0882982445714293, 0.307285130489238, 1.70444359880607, - -0.145651123385784, 1.01987855858598, 50, 0.4371137176001, 0, - "Total", 0.141532557678635, 0.297334464093554, 1.47010780917265, - 0.0667448896656013, 0.887637443996716, 84, 0.477191166831159, - 0, "Total", 0.0226858368096772, 0.209415213954494, 2.27868433157322, + "", "m", "Total", 0.0226858368096772, 0.209415213954494, 2.27868433157322, -0.07724122941283, 1.12887710558279, 84, 0.525817938084978, - 0, "Total", 0.087464433396498, 0.30768890257916, 1.70892721082035, + "", "m", "Total", 0.087464433396498, 0.30768890257916, 1.70892721082035, -0.147665837320681, 1.01979664937337, 16, 0.436065406026343, - 1, "Total", 0.143151849452702, 0.297827535583012, 1.46415409566723, + "", "m", "Total", 0.143151849452702, 0.297827535583012, 1.46415409566723, 0.0678046313902036, 0.889611028635219, 16, 0.478707830012711, - 0, "Total", 0.0224077135468204, 0.209648341430587, 2.28338477064083, + "", "m", "Total", 0.0224077135468204, 0.209648341430587, 2.28338477064083, -0.0785176150729263, 1.12601796241427, 50, 0.523750173670671, - 0, "Total", 0.0882982445714293, 0.307285130489238, 1.70444359880607, + "", "m", "Total", 0.0882982445714293, 0.307285130489238, 1.70444359880607, -0.145651123385784, 1.01987855858598, 50, 0.4371137176001, 0, - "Total", 0.141532557678635, 0.297334464093554, 1.47010780917265, + "m", "Total", 0.141532557678635, 0.297334464093554, 1.47010780917265, 0.0667448896656013, 0.887637443996716, 84, 0.477191166831159, - 1, "Total", 0.0226858368096772, 0.209415213954494, 2.27868433157322, + 1, "m", "Total", 0.0226858368096772, 0.209415213954494, 2.27868433157322, -0.07724122941283, 1.12887710558279, 84, 0.525817938084978, - 0, "Total", 0.087464433396498, 0.30768890257916, 1.70892721082035, - -0.0350111801968114, 0.0328538804008177, 16, -0.00107864989799686, - 0, "Total indirect", 0.950321151845348, 0.0173128335859587, - -0.0623034867539928, -0.0485078945298809, 0.0452387479712615, - 16, -0.00163457327930967, 1, "Total indirect", 0.945508496138255, - 0.0239153992727938, -0.0683481492683741, -0.0209347798859799, - 0.0196620766933927, 50, -0.000636351596293605, 1, "Total indirect", - 0.951005235649467, 0.0103565312678181, -0.0614444720763802, - -0.062758571874601, 0.0585046489310939, 50, -0.00212696147175355, - 1, "Total indirect", 0.945184093138401, 0.0309350635425456, - -0.0687556845916381, -0.00726315695143317, 0.00702733675591923, - 84, -0.000117910097756974, 0, "Total indirect", 0.974198425894715, - 0.00364560109779414, -0.0323431156053573, -0.0798153039994503, - 0.0744070719782492, 84, -0.00270411601060053, 1, "Total indirect", - 0.945203319608379, 0.0393431657913579, -0.0687315307807416, + 0, "m", "Total", 0.087464433396498, 0.30768890257916, 1.70892721082035, -0.0350111801968114, 0.0328538804008177, 16, -0.00107864989799686, - 1, "Total indirect", 0.950321151845348, 0.0173128335859587, + 1, "m", "Total indirect", 0.950321151845348, 0.0173128335859587, -0.0623034867539928, -0.0485078945298809, 0.0452387479712615, - 16, -0.00163457327930967, 1, "Total indirect", 0.945508496138255, + 16, -0.00163457327930967, 0, "m", "Total indirect", 0.945508496138255, 0.0239153992727938, -0.0683481492683741, -0.0209347798859799, - 0.0196620766933927, 50, -0.000636351596293605, 0, "Total indirect", + 0.0196620766933927, 50, -0.000636351596293605, 1, "m", "Total indirect", 0.951005235649467, 0.0103565312678181, -0.0614444720763802, -0.062758571874601, 0.0585046489310939, 50, -0.00212696147175355, - 1, "Total indirect", 0.945184093138401, 0.0309350635425456, + 0, "m", "Total indirect", 0.945184093138401, 0.0309350635425456, -0.0687556845916381, -0.00726315695143317, 0.00702733675591923, - 84, -0.000117910097756974, 1, "Total indirect", 0.974198425894715, + 84, -0.000117910097756974, 1, "m", "Total indirect", 0.974198425894715, 0.00364560109779414, -0.0323431156053573, -0.0798153039994503, - 0.0744070719782492, 84, -0.00270411601060053, 1, "Total indirect", + 0.0744070719782492, 84, -0.00270411601060053, 0, "m", "Total indirect", 0.945203319608379, 0.0393431657913579, -0.0687315307807416, - 0, 0, 1, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, 1, 1, 0, 1, 1, 1, - 0, 1, 1, 1)) + 1, 0, 1)) @@ -8941,7 +8338,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 63 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -8952,29 +8349,29 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -9042,73 +8439,19 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) -0.0248324882116126, 0.0446237382592549, 16, 16, 0.00989562502382118, "contGamma", "debCollin1", "contNormal", "", "", 0.576514456785037, 0.0177187507063215, 0.558483224231533, -0.0228856326702364, - 0.0235230968199597, 16, 16, 0.000318732074861623, "contGamma", - "debCollin1", "contNormal", "", "", 0.978522101785064, - 0.0118391791523371, 0.0269218051995358, -0.131956850430316, - 0.0679234868112827, 50, 16, -0.0320166818095164, "contGamma", - "debCollin1", "contNormal", "", "", 0.530075276160649, - 0.0509908189176508, -0.627891108421357, -0.0372063868126804, - 0.0583771561780609, 16, 50, 0.0105853846826902, "contGamma", - "debCollin1", "contNormal", "", "", 0.664207245045633, - 0.0243840049472062, 0.434111816562072, -0.0236817623816606, - 0.0243416127651469, 84, 50, 0.000329925191743137, "contGamma", - "debCollin1", "contNormal", "", "", 0.978515341533349, - 0.0122510861234211, 0.0269302809905483, -0.109779539138069, - 0.0442874234788054, 16, 50, -0.0327460578296317, "contGamma", - "debCollin1", "contNormal", "", "", 0.404755386421777, - 0.0393035187973184, -0.833158425292595, -0.0717265177819474, - 0.0945142955319276, 16, 84, 0.0113938888749901, "contGamma", - "debCollin1", "contNormal", "", "", 0.788186860119483, - 0.0424091500214191, 0.268665815495842, -0.0246332547487223, - 0.0253193452342709, 16, 84, 0.00034304524277431, "contGamma", - "debCollin1", "contNormal", "", "", 0.978523722825756, - 0.0127432443598487, 0.0269197727899792, -0.103898163722159, - 0.0366961667660008, 50, 84, -0.0336009984780789, "contGamma", - "debCollin1", "contNormal", "", "", 0.348844155405007, - 0.0358665596911855, -0.936833606774294, -0.0248324882116126, - 0.0446237382592549, 16, 16, 0.00989562502382118, "contGamma", - "debCollin1", "contNormal", "", "", 0.576514456785037, - 0.0177187507063215, 0.558483224231533, -0.0228856326702364, - 0.0235230968199597, 84, 16, 0.000318732074861623, "contGamma", - "debCollin1", "contNormal", "", "", 0.978522101785064, - 0.0118391791523371, 0.0269218051995358, -0.131956850430316, - 0.0679234868112827, 16, 16, -0.0320166818095164, "contGamma", - "debCollin1", "contNormal", "", "", 0.530075276160649, - 0.0509908189176508, -0.627891108421357, -0.0372063868126804, - 0.0583771561780609, 16, 50, 0.0105853846826902, "contGamma", - "debCollin1", "contNormal", "", "", 0.664207245045633, - 0.0243840049472062, 0.434111816562072, -0.0236817623816606, - 0.0243416127651469, 16, 50, 0.000329925191743137, "contGamma", - "debCollin1", "contNormal", "", "", 0.978515341533349, - 0.0122510861234211, 0.0269302809905483, -0.109779539138069, - 0.0442874234788054, 50, 50, -0.0327460578296317, "contGamma", - "debCollin1", "contNormal", "", "", 0.404755386421777, - 0.0393035187973184, -0.833158425292595, -0.0717265177819474, - 0.0945142955319276, 16, 84, 0.0113938888749901, "contGamma", - "debCollin1", "contNormal", "", "", 0.788186860119483, - 0.0424091500214191, 0.268665815495842, -0.0246332547487223, - 0.0253193452342709, 84, 84, 0.00034304524277431, "contGamma", - "debCollin1", "contNormal", "", "", 0.978523722825756, - 0.0127432443598487, 0.0269197727899792, -0.103898163722159, - 0.0366961667660008, 16, 84, -0.0336009984780789, "contGamma", - "debCollin1", "contNormal", "", "", 0.348844155405007, - 0.0358665596911855, -0.936833606774294, -0.0248324882116126, - 0.0446237382592549, 16, 16, 0.00989562502382118, "contGamma", - "debCollin1", "contNormal", "", "", 0.576514456785037, - 0.0177187507063215, 0.558483224231533, -0.0228856326702364, 0.0235230968199597, 50, 16, 0.000318732074861623, "contGamma", "debCollin1", "contNormal", "", "", 0.978522101785064, 0.0118391791523371, 0.0269218051995358, -0.131956850430316, - 0.0679234868112827, 50, 16, -0.0320166818095164, "contGamma", + 0.0679234868112827, 84, 16, -0.0320166818095164, "contGamma", "debCollin1", "contNormal", "", "", 0.530075276160649, 0.0509908189176508, -0.627891108421357, -0.0372063868126804, - 0.0583771561780609, 50, 50, 0.0105853846826902, "contGamma", + 0.0583771561780609, 16, 50, 0.0105853846826902, "contGamma", "debCollin1", "contNormal", "", "", 0.664207245045633, 0.0243840049472062, 0.434111816562072, -0.0236817623816606, - 0.0243416127651469, 84, 50, 0.000329925191743137, "contGamma", + 0.0243416127651469, 50, 50, 0.000329925191743137, "contGamma", "debCollin1", "contNormal", "", "", 0.978515341533349, 0.0122510861234211, 0.0269302809905483, -0.109779539138069, - 0.0442874234788054, 50, 50, -0.0327460578296317, "contGamma", + 0.0442874234788054, 84, 50, -0.0327460578296317, "contGamma", "debCollin1", "contNormal", "", "", 0.404755386421777, 0.0393035187973184, -0.833158425292595, -0.0717265177819474, 0.0945142955319276, 16, 84, 0.0113938888749901, "contGamma", @@ -9117,7 +8460,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.0253193452342709, 50, 84, 0.00034304524277431, "contGamma", "debCollin1", "contNormal", "", "", 0.978523722825756, 0.0127432443598487, 0.0269197727899792, -0.103898163722159, - 0.0366961667660008, 50, 84, -0.0336009984780789, "contGamma", + 0.0366961667660008, 84, 84, -0.0336009984780789, "contGamma", "debCollin1", "contNormal", "", "", 0.348844155405007, 0.0358665596911855, -0.936833606774294)) @@ -9179,116 +8522,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.688259920750873, 0.109822166770149, -0.401217604292962, -0.199820595710048, 0.178989505461128, 16, 16, -0.0104155451244605, "Total", 0.914170137068872, 0.0966370056182618, -0.107780089602572, - -0.216647887923485, 0.291695291552998, 16, 16, 0.0375237018147563, - "Total", 0.772311883680793, 0.129681765452383, 0.2893521821195, - -0.413966666553048, 0.5498863555641, 50, 16, 0.0679598445055262, - "Total", 0.782249844491653, 0.245885391190833, 0.276388296906921, - -0.337688962868951, 0.216552023082224, 16, 50, -0.0605684698933632, - "Total", 0.668376734933398, 0.141390604705739, -0.428376906792484, - -0.147107535606151, 0.120491956613883, 84, 50, -0.013307789496134, - "Total", 0.845440705645669, 0.0682664309984327, -0.1949389956601, - -0.280740151961404, 0.313515720076682, 16, 50, 0.0163877840576391, - "Total", 0.91391653726386, 0.151598671385163, 0.108099786811476, - -0.620246430594848, 0.381535639074775, 16, 84, -0.119355395760037, - "Total", 0.640476790455143, 0.255561346425636, -0.467032270057189, - -0.366254492457911, 0.220474293449759, 16, 84, -0.0728900995040762, - "Total", 0.626274007348856, 0.149678461067579, -0.486977879009371, - -0.259310078223426, 0.171184904923863, 50, 84, -0.0440625866497815, - "Total", 0.688259920750873, 0.109822166770149, -0.401217604292962, - -0.199820595710048, 0.178989505461128, 16, 16, -0.0104155451244605, - "Total", 0.914170137068872, 0.0966370056182618, -0.107780089602572, - -0.216647887923485, 0.291695291552998, 84, 16, 0.0375237018147563, - "Total", 0.772311883680793, 0.129681765452383, 0.2893521821195, - -0.413966666553048, 0.5498863555641, 16, 16, 0.0679598445055262, - "Total", 0.782249844491653, 0.245885391190833, 0.276388296906921, - -0.337688962868951, 0.216552023082224, 16, 50, -0.0605684698933632, - "Total", 0.668376734933398, 0.141390604705739, -0.428376906792484, - -0.147107535606151, 0.120491956613883, 16, 50, -0.013307789496134, - "Total", 0.845440705645669, 0.0682664309984327, -0.1949389956601, - -0.280740151961404, 0.313515720076682, 50, 50, 0.0163877840576391, - "Total", 0.91391653726386, 0.151598671385163, 0.108099786811476, - -0.620246430594848, 0.381535639074775, 16, 84, -0.119355395760037, - "Total", 0.640476790455143, 0.255561346425636, -0.467032270057189, - -0.366254492457911, 0.220474293449759, 84, 84, -0.0728900995040762, - "Total", 0.626274007348856, 0.149678461067579, -0.486977879009371, - -0.259310078223426, 0.171184904923863, 16, 84, -0.0440625866497815, - "Total", 0.688259920750873, 0.109822166770149, -0.401217604292962, - -0.199820595710048, 0.178989505461128, 16, 16, -0.0104155451244605, - "Total", 0.914170137068872, 0.0966370056182618, -0.107780089602572, -0.216647887923485, 0.291695291552998, 50, 16, 0.0375237018147563, "Total", 0.772311883680793, 0.129681765452383, 0.2893521821195, - -0.413966666553048, 0.5498863555641, 50, 16, 0.0679598445055262, + -0.413966666553048, 0.5498863555641, 84, 16, 0.0679598445055262, "Total", 0.782249844491653, 0.245885391190833, 0.276388296906921, - -0.337688962868951, 0.216552023082224, 50, 50, -0.0605684698933632, + -0.337688962868951, 0.216552023082224, 16, 50, -0.0605684698933632, "Total", 0.668376734933398, 0.141390604705739, -0.428376906792484, - -0.147107535606151, 0.120491956613883, 84, 50, -0.013307789496134, + -0.147107535606151, 0.120491956613883, 50, 50, -0.013307789496134, "Total", 0.845440705645669, 0.0682664309984327, -0.1949389956601, - -0.280740151961404, 0.313515720076682, 50, 50, 0.0163877840576391, + -0.280740151961404, 0.313515720076682, 84, 50, 0.0163877840576391, "Total", 0.91391653726386, 0.151598671385163, 0.108099786811476, -0.620246430594848, 0.381535639074775, 16, 84, -0.119355395760037, "Total", 0.640476790455143, 0.255561346425636, -0.467032270057189, -0.366254492457911, 0.220474293449759, 50, 84, -0.0728900995040762, "Total", 0.626274007348856, 0.149678461067579, -0.486977879009371, - -0.259310078223426, 0.171184904923863, 50, 84, -0.0440625866497815, + -0.259310078223426, 0.171184904923863, 84, 84, -0.0440625866497815, "Total", 0.688259920750873, 0.109822166770149, -0.401217604292962, - -0.0248324882116126, 0.0446237382592549, 50, 16, 0.00989562502382118, + -0.0248324882116126, 0.0446237382592549, 16, 16, 0.00989562502382118, "Total indirect", 0.576514456785037, 0.0177187507063215, 0.558483224231533, - -0.0228856326702364, 0.0235230968199597, 84, 16, 0.000318732074861623, + -0.0228856326702364, 0.0235230968199597, 50, 16, 0.000318732074861623, "Total indirect", 0.978522101785064, 0.0118391791523371, 0.0269218051995358, - -0.131956850430316, 0.0679234868112827, 50, 16, -0.0320166818095164, + -0.131956850430316, 0.0679234868112827, 84, 16, -0.0320166818095164, "Total indirect", 0.530075276160649, 0.0509908189176508, -0.627891108421357, -0.0372063868126804, 0.0583771561780609, 16, 50, 0.0105853846826902, "Total indirect", 0.664207245045633, 0.0243840049472062, 0.434111816562072, -0.0236817623816606, 0.0243416127651469, 50, 50, 0.000329925191743137, "Total indirect", 0.978515341533349, 0.0122510861234211, 0.0269302809905483, - -0.109779539138069, 0.0442874234788054, 50, 50, -0.0327460578296317, - "Total indirect", 0.404755386421777, 0.0393035187973184, -0.833158425292595, - -0.0717265177819474, 0.0945142955319276, 50, 84, 0.0113938888749901, - "Total indirect", 0.788186860119483, 0.0424091500214191, 0.268665815495842, - -0.0246332547487223, 0.0253193452342709, 84, 84, 0.00034304524277431, - "Total indirect", 0.978523722825756, 0.0127432443598487, 0.0269197727899792, - -0.103898163722159, 0.0366961667660008, 50, 84, -0.0336009984780789, - "Total indirect", 0.348844155405007, 0.0358665596911855, -0.936833606774294, - -0.0248324882116126, 0.0446237382592549, 16, 16, 0.00989562502382118, - "Total indirect", 0.576514456785037, 0.0177187507063215, 0.558483224231533, - -0.0228856326702364, 0.0235230968199597, 84, 16, 0.000318732074861623, - "Total indirect", 0.978522101785064, 0.0118391791523371, 0.0269218051995358, - -0.131956850430316, 0.0679234868112827, 50, 16, -0.0320166818095164, - "Total indirect", 0.530075276160649, 0.0509908189176508, -0.627891108421357, - -0.0372063868126804, 0.0583771561780609, 84, 50, 0.0105853846826902, - "Total indirect", 0.664207245045633, 0.0243840049472062, 0.434111816562072, - -0.0236817623816606, 0.0243416127651469, 84, 50, 0.000329925191743137, - "Total indirect", 0.978515341533349, 0.0122510861234211, 0.0269302809905483, -0.109779539138069, 0.0442874234788054, 84, 50, -0.0327460578296317, "Total indirect", 0.404755386421777, 0.0393035187973184, -0.833158425292595, -0.0717265177819474, 0.0945142955319276, 16, 84, 0.0113938888749901, "Total indirect", 0.788186860119483, 0.0424091500214191, 0.268665815495842, - -0.0246332547487223, 0.0253193452342709, 84, 84, 0.00034304524277431, - "Total indirect", 0.978523722825756, 0.0127432443598487, 0.0269197727899792, - -0.103898163722159, 0.0366961667660008, 50, 84, -0.0336009984780789, - "Total indirect", 0.348844155405007, 0.0358665596911855, -0.936833606774294, - -0.0248324882116126, 0.0446237382592549, 84, 16, 0.00989562502382118, - "Total indirect", 0.576514456785037, 0.0177187507063215, 0.558483224231533, - -0.0228856326702364, 0.0235230968199597, 84, 16, 0.000318732074861623, - "Total indirect", 0.978522101785064, 0.0118391791523371, 0.0269218051995358, - -0.131956850430316, 0.0679234868112827, 84, 16, -0.0320166818095164, - "Total indirect", 0.530075276160649, 0.0509908189176508, -0.627891108421357, - -0.0372063868126804, 0.0583771561780609, 16, 50, 0.0105853846826902, - "Total indirect", 0.664207245045633, 0.0243840049472062, 0.434111816562072, - -0.0236817623816606, 0.0243416127651469, 84, 50, 0.000329925191743137, - "Total indirect", 0.978515341533349, 0.0122510861234211, 0.0269302809905483, - -0.109779539138069, 0.0442874234788054, 50, 50, -0.0327460578296317, - "Total indirect", 0.404755386421777, 0.0393035187973184, -0.833158425292595, - -0.0717265177819474, 0.0945142955319276, 84, 84, 0.0113938888749901, - "Total indirect", 0.788186860119483, 0.0424091500214191, 0.268665815495842, - -0.0246332547487223, 0.0253193452342709, 84, 84, 0.00034304524277431, + -0.0246332547487223, 0.0253193452342709, 50, 84, 0.00034304524277431, "Total indirect", 0.978523722825756, 0.0127432443598487, 0.0269197727899792, -0.103898163722159, 0.0366961667660008, 84, 84, -0.0336009984780789, - "Total indirect", 0.348844155405007, 0.0358665596911855, -0.936833606774294, - 16, 16, 50, 16, 84, 16, 16, 16, 50, 16, 84, 16, 16, 16, 50, - 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 50, 50, 50, 84, 50, - 16, 50, 50, 50, 84, 50, 16, 84, 50, 84, 84, 84, 16, 84, 50, - 84, 84, 84, 16, 84, 50, 84, 84, 84)) + "Total indirect", 0.348844155405007, 0.0358665596911855, -0.936833606774294 + )) @@ -9304,7 +8572,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 63 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -9315,29 +8583,29 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -9381,56 +8649,39 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.161366436353673, 1.33152243745725, 16, 0.585078000551786, 0, - "facGenderm", "contNormal", "", "", "", 0.12447492829389, + "m", "facGender", "contNormal", "", "", "", 0.12447492829389, 0.380845996555711, 1.53625876559845, -0.359834842992371, 1.00920730483864, - 16, 0.324686230923135, 1, "facGenderm", "contNormal", "", "", - "", 0.352546048460177, 0.349251863460207, 0.929662128947034, + 16, 0.324686230923135, 1, "m", "facGender", "contNormal", "", + "", "", 0.352546048460177, 0.349251863460207, 0.929662128947034, 0.0271162727619306, 1.18765979862106, 50, 0.607388035691498, - 0, "facGenderm", "contNormal", "", "", "", 0.0402130570350507, + 0, "m", "facGender", "contNormal", "", "", "", 0.0402130570350507, 0.296062462120058, 2.05155368682029, -0.24070133247017, 0.934693864595862, - 50, 0.346996266062846, 1, "facGenderm", "contNormal", "", "", - "", 0.247179173844201, 0.299851223373848, 1.15722811519171, + 50, 0.346996266062846, 1, "m", "facGender", "contNormal", "", + "", "", 0.247179173844201, 0.299851223373848, 1.15722811519171, -0.0588887745340271, 1.32596641707701, 84, 0.633538821271491, - 0, "facGenderm", "contNormal", "", "", "", 0.0729289222784604, + 0, "m", "facGender", "contNormal", "", "", "", 0.0729289222784604, 0.35328587732596, 1.79327525364665, -0.402842727057081, 1.14913683034276, - 84, 0.37314705164284, 1, "facGenderm", "contNormal", "", "", - "", 0.345946988481685, 0.395920427528684, 0.942479916916653, + 84, 0.37314705164284, 1, "m", "facGender", "contNormal", "", + "", "", 0.345946988481685, 0.395920427528684, 0.942479916916653, -0.0354530304939376, 0.032868752124858, 16, -0.0012921391845398, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.940902300025973, 0.0174293464465952, -0.0741358368484447, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.940902300025973, 0.0174293464465952, -0.0741358368484447, -0.0470138676666278, 0.045944736912738, 16, -0.000534565376944914, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.982015738852068, 0.0237143654966651, -0.0225418376477367, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.982015738852068, 0.0237143654966651, -0.0225418376477367, -0.0213124660323288, 0.0197879341423478, 50, -0.000762265944990481, - 1, "facGenderm", "debCollin1", "contNormal", "", "", - 0.942044296643037, 0.0104849886270542, -0.0727006935442565, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.942044296643037, 0.0104849886270542, -0.0727006935442565, -0.0611393760345112, 0.0597481360156187, 50, -0.000695620009446261, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.982004167242887, 0.0308392177110588, -0.0225563441966563, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.982004167242887, 0.0308392177110588, -0.0225563441966563, -0.00835369928821007, 0.00807135293359531, 84, -0.00014117317730738, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.973122961037564, 0.00419014133712764, -0.0336917459219059, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.973122961037564, 0.00419014133712764, -0.0336917459219059, -0.0777345829315063, 0.0759657814130614, 84, -0.000884400759222426, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.9820048473692, 0.0392099971114104, -0.022555491567865, -0.0354530304939376, - 0.032868752124858, 16, -0.0012921391845398, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.940902300025973, - 0.0174293464465952, -0.0741358368484447, -0.0470138676666278, - 0.045944736912738, 16, -0.000534565376944914, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.982015738852068, - 0.0237143654966651, -0.0225418376477367, -0.0213124660323288, - 0.0197879341423478, 50, -0.000762265944990481, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.942044296643037, - 0.0104849886270542, -0.0727006935442565, -0.0611393760345112, - 0.0597481360156187, 50, -0.000695620009446261, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.982004167242887, - 0.0308392177110588, -0.0225563441966563, -0.00835369928821007, - 0.00807135293359531, 84, -0.00014117317730738, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.973122961037564, - 0.00419014133712764, -0.0336917459219059, -0.0777345829315063, - 0.0759657814130614, 84, -0.000884400759222426, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.9820048473692, - 0.0392099971114104, -0.022555491567865)) + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.9820048473692, 0.0392099971114104, -0.022555491567865 + )) @@ -9471,70 +8722,43 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.162991457492319, 1.33056318022681, 16, 0.583785861367246, 0, - "Total", 0.125477364907223, 0.381015837408264, 1.53218266552451, + "m", "Total", 0.125477364907223, 0.381015837408264, 1.53218266552451, -0.359288419650063, 1.00759175074244, 16, 0.32415166554619, - 1, "Total", 0.35257846481062, 0.34870032846886, 0.929599541731253, + 1, "m", "Total", 0.35257846481062, 0.34870032846886, 0.929599541731253, 0.0265396598642635, 1.18671187962875, 50, 0.606625769746507, - 0, "Total", 0.0404000847089072, 0.295967739436994, 2.04963477066948, + 0, "m", "Total", 0.0404000847089072, 0.295967739436994, 2.04963477066948, -0.238380372526911, 0.930981664633712, 50, 0.3463006460534, - 1, "Total", 0.245696064481406, 0.298312123688089, 1.1608668188608, + 1, "m", "Total", 0.245696064481406, 0.298312123688089, 1.1608668188608, -0.0589553389409698, 1.32575063512934, 84, 0.633397648094184, - 0, "Total", 0.0729619148375513, 0.353247810927316, 1.79306885563266, + 0, "m", "Total", 0.0729619148375513, 0.353247810927316, 1.79306885563266, -0.399272750464709, 1.14379805223194, 84, 0.372262650883617, - 1, "Total", 0.344314610360438, 0.39364774426168, 0.945674543574047, + 1, "m", "Total", 0.344314610360438, 0.39364774426168, 0.945674543574047, -0.162991457492319, 1.33056318022681, 16, 0.583785861367246, - 0, "Total", 0.125477364907223, 0.381015837408264, 1.53218266552451, + 0, "m", "Total", 0.125477364907223, 0.381015837408264, 1.53218266552451, -0.359288419650063, 1.00759175074244, 16, 0.32415166554619, - 0, "Total", 0.35257846481062, 0.34870032846886, 0.929599541731253, + 1, "m", "Total", 0.35257846481062, 0.34870032846886, 0.929599541731253, 0.0265396598642635, 1.18671187962875, 50, 0.606625769746507, - 1, "Total", 0.0404000847089072, 0.295967739436994, 2.04963477066948, + 0, "m", "Total", 0.0404000847089072, 0.295967739436994, 2.04963477066948, -0.238380372526911, 0.930981664633712, 50, 0.3463006460534, - 0, "Total", 0.245696064481406, 0.298312123688089, 1.1608668188608, + 1, "m", "Total", 0.245696064481406, 0.298312123688089, 1.1608668188608, -0.0589553389409698, 1.32575063512934, 84, 0.633397648094184, - 0, "Total", 0.0729619148375513, 0.353247810927316, 1.79306885563266, + 0, "m", "Total", 0.0729619148375513, 0.353247810927316, 1.79306885563266, -0.399272750464709, 1.14379805223194, 84, 0.372262650883617, - 0, "Total", 0.344314610360438, 0.39364774426168, 0.945674543574047, - -0.162991457492319, 1.33056318022681, 16, 0.583785861367246, - 1, "Total", 0.125477364907223, 0.381015837408264, 1.53218266552451, - -0.359288419650063, 1.00759175074244, 16, 0.32415166554619, - 0, "Total", 0.35257846481062, 0.34870032846886, 0.929599541731253, - 0.0265396598642635, 1.18671187962875, 50, 0.606625769746507, - 0, "Total", 0.0404000847089072, 0.295967739436994, 2.04963477066948, - -0.238380372526911, 0.930981664633712, 50, 0.3463006460534, - 0, "Total", 0.245696064481406, 0.298312123688089, 1.1608668188608, - -0.0589553389409698, 1.32575063512934, 84, 0.633397648094184, - 1, "Total", 0.0729619148375513, 0.353247810927316, 1.79306885563266, - -0.399272750464709, 1.14379805223194, 84, 0.372262650883617, - 0, "Total", 0.344314610360438, 0.39364774426168, 0.945674543574047, + 1, "m", "Total", 0.344314610360438, 0.39364774426168, 0.945674543574047, -0.0354530304939376, 0.032868752124858, 16, -0.0012921391845398, - 0, "Total indirect", 0.940902300025973, 0.0174293464465952, + 0, "m", "Total indirect", 0.940902300025973, 0.0174293464465952, -0.0741358368484447, -0.0470138676666278, 0.045944736912738, - 16, -0.000534565376944914, 1, "Total indirect", 0.982015738852068, + 16, -0.000534565376944914, 1, "m", "Total indirect", 0.982015738852068, 0.0237143654966651, -0.0225418376477367, -0.0213124660323288, - 0.0197879341423478, 50, -0.000762265944990481, 1, "Total indirect", + 0.0197879341423478, 50, -0.000762265944990481, 0, "m", "Total indirect", 0.942044296643037, 0.0104849886270542, -0.0727006935442565, -0.0611393760345112, 0.0597481360156187, 50, -0.000695620009446261, - 1, "Total indirect", 0.982004167242887, 0.0308392177110588, + 1, "m", "Total indirect", 0.982004167242887, 0.0308392177110588, -0.0225563441966563, -0.00835369928821007, 0.00807135293359531, - 84, -0.00014117317730738, 0, "Total indirect", 0.973122961037564, + 84, -0.00014117317730738, 0, "m", "Total indirect", 0.973122961037564, 0.00419014133712764, -0.0336917459219059, -0.0777345829315063, - 0.0759657814130614, 84, -0.000884400759222426, 1, "Total indirect", - 0.9820048473692, 0.0392099971114104, -0.022555491567865, -0.0354530304939376, - 0.032868752124858, 16, -0.0012921391845398, 1, "Total indirect", - 0.940902300025973, 0.0174293464465952, -0.0741358368484447, - -0.0470138676666278, 0.045944736912738, 16, -0.000534565376944914, - 1, "Total indirect", 0.982015738852068, 0.0237143654966651, - -0.0225418376477367, -0.0213124660323288, 0.0197879341423478, - 50, -0.000762265944990481, 0, "Total indirect", 0.942044296643037, - 0.0104849886270542, -0.0727006935442565, -0.0611393760345112, - 0.0597481360156187, 50, -0.000695620009446261, 1, "Total indirect", - 0.982004167242887, 0.0308392177110588, -0.0225563441966563, - -0.00835369928821007, 0.00807135293359531, 84, -0.00014117317730738, - 1, "Total indirect", 0.973122961037564, 0.00419014133712764, - -0.0336917459219059, -0.0777345829315063, 0.0759657814130614, - 84, -0.000884400759222426, 1, "Total indirect", 0.9820048473692, - 0.0392099971114104, -0.022555491567865, 0, 0, 1, 0, 0, 0, 1, - 0, 0, 0, 1, 0, 0, 1, 1, 1, 0, 1, 1, 1, 0, 1, 1, 1)) + 0.0759657814130614, 84, -0.000884400759222426, 1, "m", "Total indirect", + 0.9820048473692, 0.0392099971114104, -0.022555491567865)) @@ -9550,7 +8774,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 64 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -9561,25 +8785,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -9629,82 +8853,28 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.0335574821122979, 16, 16, 0.00692254302528905, "contGamma", "debCollin1", "contNormal", "", "", 0.610469323102829, 0.0135895043465604, 0.50940364333753, -0.0596847893861401, 0.026564315679089, - 16, 16, -0.0165602368535256, "contGamma", "debCollin1", "contNormal", - "", "", 0.451663422395782, 0.0220027270259941, - -0.752644744170175, -0.190922426763855, 0.0520274368673578, - 50, 16, -0.0694474949482487, "contGamma", "debCollin1", "contNormal", - "", "", 0.262493993598183, 0.0619781448913272, - -1.1205158700703, -0.0304623607151841, 0.0618356408128377, 16, - 16, 0.0156866400488268, "contGamma", "debCollin1", "contNormal", - "", "", 0.505272398804618, 0.0235458412134245, - 0.666217014998095, -0.0249283744808502, 0.0219931780803527, - 84, 16, -0.00146759820024873, "contGamma", "debCollin1", "contNormal", - "", "", 0.90241884376002, 0.0119700037682616, - -0.122606327338013, -0.130019219987446, 0.0351231051014406, - 16, 16, -0.0474480574430029, "contGamma", "debCollin1", "contNormal", - "", "", 0.260056066716109, 0.042128918284088, - -1.126258621763, -0.0503104050140313, 0.102229418960113, 16, - 16, 0.0259595069730407, "contGamma", "debCollin1", "contNormal", - "", "", 0.504707921516913, 0.0389139354542631, - 0.667100530182864, -0.0247317508796848, 0.0571783326598615, - 50, 16, 0.0162232908900883, "contGamma", "debCollin1", "contNormal", - "", "", 0.437519021482305, 0.0208958134398496, - 0.776389535482239, -0.0787611676171151, 0.03543848768784, 50, - 16, -0.0216613399646376, "contGamma", "debCollin1", "contNormal", - "", "", 0.45716074544629, 0.0291331004563725, - -0.743530198479078, -0.0197123960617198, 0.0335574821122979, - 50, 50, 0.00692254302528905, "contGamma", "debCollin1", "contNormal", - "", "", 0.610469323102829, 0.0135895043465604, - 0.50940364333753, -0.0596847893861401, 0.026564315679089, 84, - 50, -0.0165602368535256, "contGamma", "debCollin1", "contNormal", + 50, 16, -0.0165602368535256, "contGamma", "debCollin1", "contNormal", "", "", 0.451663422395782, 0.0220027270259941, -0.752644744170175, -0.190922426763855, 0.0520274368673578, - 50, 50, -0.0694474949482487, "contGamma", "debCollin1", "contNormal", + 84, 16, -0.0694474949482487, "contGamma", "debCollin1", "contNormal", "", "", 0.262493993598183, 0.0619781448913272, -1.1205158700703, -0.0304623607151841, 0.0618356408128377, 16, 50, 0.0156866400488268, "contGamma", "debCollin1", "contNormal", "", "", 0.505272398804618, 0.0235458412134245, 0.666217014998095, -0.0249283744808502, 0.0219931780803527, - 84, 50, -0.00146759820024873, "contGamma", "debCollin1", "contNormal", + 50, 50, -0.00146759820024873, "contGamma", "debCollin1", "contNormal", "", "", 0.90241884376002, 0.0119700037682616, -0.122606327338013, -0.130019219987446, 0.0351231051014406, - 50, 50, -0.0474480574430029, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0474480574430029, "contGamma", "debCollin1", "contNormal", "", "", 0.260056066716109, 0.042128918284088, - -1.126258621763, -0.0503104050140313, 0.102229418960113, 84, - 50, 0.0259595069730407, "contGamma", "debCollin1", "contNormal", + -1.126258621763, -0.0503104050140313, 0.102229418960113, 16, + 84, 0.0259595069730407, "contGamma", "debCollin1", "contNormal", "", "", 0.504707921516913, 0.0389139354542631, 0.667100530182864, -0.0247317508796848, 0.0571783326598615, - 84, 50, 0.0162232908900883, "contGamma", "debCollin1", "contNormal", + 50, 84, 0.0162232908900883, "contGamma", "debCollin1", "contNormal", "", "", 0.437519021482305, 0.0208958134398496, 0.776389535482239, -0.0787611676171151, 0.03543848768784, 84, - 50, -0.0216613399646376, "contGamma", "debCollin1", "contNormal", - "", "", 0.45716074544629, 0.0291331004563725, - -0.743530198479078, -0.0197123960617198, 0.0335574821122979, - 16, 84, 0.00692254302528905, "contGamma", "debCollin1", "contNormal", - "", "", 0.610469323102829, 0.0135895043465604, - 0.50940364333753, -0.0596847893861401, 0.026564315679089, 16, - 84, -0.0165602368535256, "contGamma", "debCollin1", "contNormal", - "", "", 0.451663422395782, 0.0220027270259941, - -0.752644744170175, -0.190922426763855, 0.0520274368673578, - 50, 84, -0.0694474949482487, "contGamma", "debCollin1", "contNormal", - "", "", 0.262493993598183, 0.0619781448913272, - -1.1205158700703, -0.0304623607151841, 0.0618356408128377, 16, - 84, 0.0156866400488268, "contGamma", "debCollin1", "contNormal", - "", "", 0.505272398804618, 0.0235458412134245, - 0.666217014998095, -0.0249283744808502, 0.0219931780803527, - 84, 84, -0.00146759820024873, "contGamma", "debCollin1", "contNormal", - "", "", 0.90241884376002, 0.0119700037682616, - -0.122606327338013, -0.130019219987446, 0.0351231051014406, - 16, 84, -0.0474480574430029, "contGamma", "debCollin1", "contNormal", - "", "", 0.260056066716109, 0.042128918284088, - -1.126258621763, -0.0503104050140313, 0.102229418960113, 16, - 84, 0.0259595069730407, "contGamma", "debCollin1", "contNormal", - "", "", 0.504707921516913, 0.0389139354542631, - 0.667100530182864, -0.0247317508796848, 0.0571783326598615, - 50, 84, 0.0162232908900883, "contGamma", "debCollin1", "contNormal", - "", "", 0.437519021482305, 0.0208958134398496, - 0.776389535482239, -0.0787611676171151, 0.03543848768784, 50, - 84, -0.0216613399646376, "contGamma", "debCollin1", "contNormal", + 84, -0.0216613399646376, "contGamma", "debCollin1", "contNormal", "", "", 0.45716074544629, 0.0291331004563725, -0.743530198479078)) @@ -9740,116 +8910,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) jaspTools::expect_equal_tables(table, list(-0.140911167468105, 0.130684838950309, 16, 16, -0.00511316425889836, "Total", 0.941171137478644, 0.0692859686608348, -0.0737979760942373, - -0.165281757277899, 0.108089869002473, 16, 16, -0.028595944137713, - "Total", 0.681774620682036, 0.0697389412348117, -0.410042705429527, - -0.254697078749648, 0.0917306742847761, 50, 16, -0.0814832022324361, - "Total", 0.35652572218276, 0.088376050725167, -0.922005470529948, - -0.137699026773362, 0.145000892302641, 16, 16, 0.00365093276463939, - "Total", 0.959625158532497, 0.0721186514920435, 0.0506239743687135, - -0.146083825554599, 0.119077214585727, 84, 16, -0.0135033054844361, - "Total", 0.84177619788745, 0.0676443654658662, -0.199622028995896, - -0.209023383571298, 0.0900558541169175, 16, 16, -0.0594837647271903, - "Total", 0.435606867425769, 0.0762971258776474, -0.77963309945096, - -0.140368024024915, 0.168215623402621, 16, 16, 0.0139237996888533, - "Total", 0.859607698163818, 0.0787217647522109, 0.176873571529813, - -0.133447825815141, 0.141822993026943, 50, 16, 0.00418758360590092, - "Total", 0.952448509673842, 0.0702234380359501, 0.0596322783820002, - -0.172090941674101, 0.104696847176451, 50, 16, -0.033697047248825, - "Total", 0.633202051089031, 0.0706104272919859, -0.477224802924391, - -0.140911167468105, 0.130684838950309, 50, 50, -0.00511316425889836, - "Total", 0.941171137478644, 0.0692859686608348, -0.0737979760942373, - -0.165281757277899, 0.108089869002473, 84, 50, -0.028595944137713, + -0.165281757277899, 0.108089869002473, 50, 16, -0.028595944137713, "Total", 0.681774620682036, 0.0697389412348117, -0.410042705429527, - -0.254697078749648, 0.0917306742847761, 50, 50, -0.0814832022324361, + -0.254697078749648, 0.0917306742847761, 84, 16, -0.0814832022324361, "Total", 0.35652572218276, 0.088376050725167, -0.922005470529948, -0.137699026773362, 0.145000892302641, 16, 50, 0.00365093276463939, "Total", 0.959625158532497, 0.0721186514920435, 0.0506239743687135, - -0.146083825554599, 0.119077214585727, 84, 50, -0.0135033054844361, - "Total", 0.84177619788745, 0.0676443654658662, -0.199622028995896, - -0.209023383571298, 0.0900558541169175, 50, 50, -0.0594837647271903, - "Total", 0.435606867425769, 0.0762971258776474, -0.77963309945096, - -0.140368024024915, 0.168215623402621, 84, 50, 0.0139237996888533, - "Total", 0.859607698163818, 0.0787217647522109, 0.176873571529813, - -0.133447825815141, 0.141822993026943, 84, 50, 0.00418758360590092, - "Total", 0.952448509673842, 0.0702234380359501, 0.0596322783820002, - -0.172090941674101, 0.104696847176451, 84, 50, -0.033697047248825, - "Total", 0.633202051089031, 0.0706104272919859, -0.477224802924391, - -0.140911167468105, 0.130684838950309, 16, 84, -0.00511316425889836, - "Total", 0.941171137478644, 0.0692859686608348, -0.0737979760942373, - -0.165281757277899, 0.108089869002473, 16, 84, -0.028595944137713, - "Total", 0.681774620682036, 0.0697389412348117, -0.410042705429527, - -0.254697078749648, 0.0917306742847761, 50, 84, -0.0814832022324361, - "Total", 0.35652572218276, 0.088376050725167, -0.922005470529948, - -0.137699026773362, 0.145000892302641, 16, 84, 0.00365093276463939, - "Total", 0.959625158532497, 0.0721186514920435, 0.0506239743687135, - -0.146083825554599, 0.119077214585727, 84, 84, -0.0135033054844361, + -0.146083825554599, 0.119077214585727, 50, 50, -0.0135033054844361, "Total", 0.84177619788745, 0.0676443654658662, -0.199622028995896, - -0.209023383571298, 0.0900558541169175, 16, 84, -0.0594837647271903, + -0.209023383571298, 0.0900558541169175, 84, 50, -0.0594837647271903, "Total", 0.435606867425769, 0.0762971258776474, -0.77963309945096, -0.140368024024915, 0.168215623402621, 16, 84, 0.0139237996888533, "Total", 0.859607698163818, 0.0787217647522109, 0.176873571529813, -0.133447825815141, 0.141822993026943, 50, 84, 0.00418758360590092, "Total", 0.952448509673842, 0.0702234380359501, 0.0596322783820002, - -0.172090941674101, 0.104696847176451, 50, 84, -0.033697047248825, + -0.172090941674101, 0.104696847176451, 84, 84, -0.033697047248825, "Total", 0.633202051089031, 0.0706104272919859, -0.477224802924391, - -0.0197123960617198, 0.0335574821122979, 50, 16, 0.00692254302528905, - "Total indirect", 0.610469323102829, 0.0135895043465604, 0.50940364333753, - -0.0596847893861401, 0.026564315679089, 84, 16, -0.0165602368535256, - "Total indirect", 0.451663422395782, 0.0220027270259941, -0.752644744170175, - -0.190922426763855, 0.0520274368673578, 50, 16, -0.0694474949482487, - "Total indirect", 0.262493993598183, 0.0619781448913272, -1.1205158700703, - -0.0304623607151841, 0.0618356408128377, 16, 16, 0.0156866400488268, - "Total indirect", 0.505272398804618, 0.0235458412134245, 0.666217014998095, - -0.0249283744808502, 0.0219931780803527, 84, 16, -0.00146759820024873, - "Total indirect", 0.90241884376002, 0.0119700037682616, -0.122606327338013, - -0.130019219987446, 0.0351231051014406, 50, 16, -0.0474480574430029, - "Total indirect", 0.260056066716109, 0.042128918284088, -1.126258621763, - -0.0503104050140313, 0.102229418960113, 84, 16, 0.0259595069730407, - "Total indirect", 0.504707921516913, 0.0389139354542631, 0.667100530182864, - -0.0247317508796848, 0.0571783326598615, 84, 16, 0.0162232908900883, - "Total indirect", 0.437519021482305, 0.0208958134398496, 0.776389535482239, - -0.0787611676171151, 0.03543848768784, 84, 16, -0.0216613399646376, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, + "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, + "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, - -0.0197123960617198, 0.0335574821122979, 16, 50, 0.00692254302528905, - "Total indirect", 0.610469323102829, 0.0135895043465604, 0.50940364333753, - -0.0596847893861401, 0.026564315679089, 16, 50, -0.0165602368535256, - "Total indirect", 0.451663422395782, 0.0220027270259941, -0.752644744170175, - -0.190922426763855, 0.0520274368673578, 50, 50, -0.0694474949482487, - "Total indirect", 0.262493993598183, 0.0619781448913272, -1.1205158700703, - -0.0304623607151841, 0.0618356408128377, 16, 50, 0.0156866400488268, - "Total indirect", 0.505272398804618, 0.0235458412134245, 0.666217014998095, - -0.0249283744808502, 0.0219931780803527, 84, 50, -0.00146759820024873, - "Total indirect", 0.90241884376002, 0.0119700037682616, -0.122606327338013, - -0.130019219987446, 0.0351231051014406, 16, 50, -0.0474480574430029, - "Total indirect", 0.260056066716109, 0.042128918284088, -1.126258621763, - -0.0503104050140313, 0.102229418960113, 16, 50, 0.0259595069730407, - "Total indirect", 0.504707921516913, 0.0389139354542631, 0.667100530182864, - -0.0247317508796848, 0.0571783326598615, 50, 50, 0.0162232908900883, - "Total indirect", 0.437519021482305, 0.0208958134398496, 0.776389535482239, - -0.0787611676171151, 0.03543848768784, 50, 50, -0.0216613399646376, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, - -0.0197123960617198, 0.0335574821122979, 50, 84, 0.00692254302528905, - "Total indirect", 0.610469323102829, 0.0135895043465604, 0.50940364333753, - -0.0596847893861401, 0.026564315679089, 84, 84, -0.0165602368535256, - "Total indirect", 0.451663422395782, 0.0220027270259941, -0.752644744170175, - -0.190922426763855, 0.0520274368673578, 50, 84, -0.0694474949482487, - "Total indirect", 0.262493993598183, 0.0619781448913272, -1.1205158700703, - -0.0304623607151841, 0.0618356408128377, 16, 84, 0.0156866400488268, - "Total indirect", 0.505272398804618, 0.0235458412134245, 0.666217014998095, - -0.0249283744808502, 0.0219931780803527, 84, 84, -0.00146759820024873, - "Total indirect", 0.90241884376002, 0.0119700037682616, -0.122606327338013, - -0.130019219987446, 0.0351231051014406, 50, 84, -0.0474480574430029, - "Total indirect", 0.260056066716109, 0.042128918284088, -1.126258621763, - -0.0503104050140313, 0.102229418960113, 84, 84, 0.0259595069730407, - "Total indirect", 0.504707921516913, 0.0389139354542631, 0.667100530182864, - -0.0247317508796848, 0.0571783326598615, 84, 84, 0.0162232908900883, - "Total indirect", 0.437519021482305, 0.0208958134398496, 0.776389535482239, - -0.0787611676171151, 0.03543848768784, 84, 84, -0.0216613399646376, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, - 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 84, 50, - 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, - 16, 84, 50, 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, - 50, 84, 50, 16, 84, 50, 84, 84, 84)) + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, + "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, + "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, + "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078, + -0.0787611676171151, 0.03543848768784, -0.0216613399646376, + "Total indirect", 0.45716074544629, 0.0291331004563725, -0.743530198479078 + )) @@ -9865,7 +8960,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 64 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -9876,25 +8971,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -9941,43 +9036,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0715438299845629, 0.89228957589471, "", 0.481916702939636, "", - "facGenderm", "contNormal", "", "", "", 0.0213542773605142, + "m", "facGender", "contNormal", "", "", "", 0.0213542773605142, 0.20937776213851, 2.30166135131788, -0.034519170517936, 0.0292662052076017, - 16, -0.00262648265516714, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.871770178403145, 0.0162720785250822, - -0.161410397025715, -0.0734243120109146, 0.0852820766397347, - 16, 0.00592888231441005, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.883574907433269, 0.0404870675947377, - 0.146438916588285, -0.0190873283460819, 0.0177441350514605, - 16, -0.000671596647310668, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.943017956803194, 0.00939595413182698, - -0.0714772164580672, -0.0644286397540538, 0.0623914532564063, - 16, -0.00101859324882376, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974883499419583, 0.0323526590311865, - -0.0314840658952293, -0.0243048101707133, 0.027544469794489, - 50, 0.00161982981188784, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.902532380524236, 0.01322710018505, - 0.122462957808292, -0.0883233870186384, 0.0699991850466873, - 50, -0.00916210098597558, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.820543818628052, 0.0403891534013263, - -0.226845581409853, -0.034519170517936, 0.0292662052076017, - 50, -0.00262648265516714, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.871770178403145, 0.0162720785250822, + 16, -0.00262648265516714, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.871770178403145, 0.0162720785250822, -0.161410397025715, -0.0734243120109146, 0.0852820766397347, - 50, 0.00592888231441005, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.883574907433269, 0.0404870675947377, + 16, 0.00592888231441005, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.883574907433269, 0.0404870675947377, 0.146438916588285, -0.0190873283460819, 0.0177441350514605, - 84, -0.000671596647310668, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.943017956803194, 0.00939595413182698, + 50, -0.000671596647310668, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.943017956803194, 0.00939595413182698, -0.0714772164580672, -0.0644286397540538, 0.0623914532564063, - 84, -0.00101859324882376, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974883499419583, 0.0323526590311865, + 50, -0.00101859324882376, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.974883499419583, 0.0323526590311865, -0.0314840658952293, -0.0243048101707133, 0.027544469794489, - 84, 0.00161982981188784, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.902532380524236, 0.01322710018505, + 84, 0.00161982981188784, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.902532380524236, 0.01322710018505, 0.122462957808292, -0.0883233870186384, 0.0699991850466873, - 84, -0.00916210098597558, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.820543818628052, 0.0403891534013263, + 84, -0.00916210098597558, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.820543818628052, 0.0403891534013263, -0.226845581409853)) @@ -10010,58 +9087,34 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0682196468459138, 0.890360793723025, 16, 0.479290220284469, - 0, "Total", 0.022299236158368, 0.209733738314085, 2.28523185700677, + list(0.0682196468459138, 0.890360793723025, "", 0.479290220284469, + "", "m", "Total", 0.022299236158368, 0.209733738314085, 2.28523185700677, 0.0734886856259528, 0.90220248488214, 16, 0.487845585254047, - 0, "Total", 0.0210227655757247, 0.211410466159832, 2.30757537275956, + 0, "m", "Total", 0.0210227655757247, 0.211410466159832, 2.30757537275956, 0.0708198823493951, 0.891670330235257, 16, 0.481245106292326, - 1, "Total", 0.0215526506315085, 0.209404472316998, 2.29816059307374, - 0.0699357130251398, 0.891860506356486, 16, 0.480898109690813, - 0, "Total", 0.021819134824125, 0.209678545068834, 2.29350174827349, + 1, "m", "Total", 0.0215526506315085, 0.209404472316998, 2.29816059307374, + 0.0699357130251398, 0.891860506356486, 50, 0.480898109690813, + 0, "m", "Total", 0.021819134824125, 0.209678545068834, 2.29350174827349, 0.0724950287427826, 0.894578036760266, 50, 0.483536532751524, - 0, "Total", 0.0211306942147007, 0.209718906699809, 2.30564110961944, - 0.0598141041702392, 0.885695099737082, 50, 0.472754601953661, - 1, "Total", 0.0248412035066181, 0.210687798878267, 2.24386321595591, - 0.0682196468459138, 0.890360793723025, 50, 0.479290220284469, - 1, "Total", 0.022299236158368, 0.209733738314085, 2.28523185700677, - 0.0734886856259528, 0.90220248488214, 50, 0.487845585254047, - 1, "Total", 0.0210227655757247, 0.211410466159832, 2.30757537275956, - 0.0708198823493951, 0.891670330235257, 84, 0.481245106292326, - 0, "Total", 0.0215526506315085, 0.209404472316998, 2.29816059307374, - 0.0699357130251398, 0.891860506356486, 84, 0.480898109690813, - 0, "Total", 0.021819134824125, 0.209678545068834, 2.29350174827349, - 0.0724950287427826, 0.894578036760266, 84, 0.483536532751524, - 1, "Total", 0.0211306942147007, 0.209718906699809, 2.30564110961944, + 1, "m", "Total", 0.0211306942147007, 0.209718906699809, 2.30564110961944, 0.0598141041702392, 0.885695099737082, 84, 0.472754601953661, - 0, "Total", 0.0248412035066181, 0.210687798878267, 2.24386321595591, + 0, "m", "Total", 0.0248412035066181, 0.210687798878267, 2.24386321595591, + 0.0682196468459138, 0.890360793723025, 84, 0.479290220284469, + 1, "m", "Total", 0.022299236158368, 0.209733738314085, 2.28523185700677, -0.034519170517936, 0.0292662052076017, 16, -0.00262648265516714, - 0, "Total indirect", 0.871770178403145, 0.0162720785250822, + 0, "m", "Total indirect", 0.871770178403145, 0.0162720785250822, -0.161410397025715, -0.0734243120109146, 0.0852820766397347, - 16, 0.00592888231441005, 1, "Total indirect", 0.883574907433269, + 16, 0.00592888231441005, 1, "m", "Total indirect", 0.883574907433269, 0.0404870675947377, 0.146438916588285, -0.0190873283460819, - 0.0177441350514605, 16, -0.000671596647310668, 1, "Total indirect", - 0.943017956803194, 0.00939595413182698, -0.0714772164580672, - -0.0644286397540538, 0.0623914532564063, 16, -0.00101859324882376, - 1, "Total indirect", 0.974883499419583, 0.0323526590311865, - -0.0314840658952293, -0.0243048101707133, 0.027544469794489, - 50, 0.00161982981188784, 0, "Total indirect", 0.902532380524236, - 0.01322710018505, 0.122462957808292, -0.0883233870186384, 0.0699991850466873, - 50, -0.00916210098597558, 0, "Total indirect", 0.820543818628052, - 0.0403891534013263, -0.226845581409853, -0.034519170517936, - 0.0292662052076017, 50, -0.00262648265516714, 1, "Total indirect", - 0.871770178403145, 0.0162720785250822, -0.161410397025715, -0.0734243120109146, - 0.0852820766397347, 50, 0.00592888231441005, 0, "Total indirect", - 0.883574907433269, 0.0404870675947377, 0.146438916588285, -0.0190873283460819, - 0.0177441350514605, 84, -0.000671596647310668, 0, "Total indirect", + 0.0177441350514605, 50, -0.000671596647310668, 0, "m", "Total indirect", 0.943017956803194, 0.00939595413182698, -0.0714772164580672, - -0.0644286397540538, 0.0623914532564063, 84, -0.00101859324882376, - 1, "Total indirect", 0.974883499419583, 0.0323526590311865, + -0.0644286397540538, 0.0623914532564063, 50, -0.00101859324882376, + 1, "m", "Total indirect", 0.974883499419583, 0.0323526590311865, -0.0314840658952293, -0.0243048101707133, 0.027544469794489, - 84, 0.00161982981188784, 1, "Total indirect", 0.902532380524236, + 84, 0.00161982981188784, 0, "m", "Total indirect", 0.902532380524236, 0.01322710018505, 0.122462957808292, -0.0883233870186384, 0.0699991850466873, - 84, -0.00916210098597558, 1, "Total indirect", 0.820543818628052, - 0.0403891534013263, -0.226845581409853, 0, 0, 1, 0, 0, 1, 1, - 1, 0, 0, 1, 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, 1, 1, 1)) + 84, -0.00916210098597558, 1, "m", "Total indirect", 0.820543818628052, + 0.0403891534013263, -0.226845581409853)) @@ -10077,7 +9130,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 65 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -10088,27 +9141,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -10163,73 +9216,19 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) -0.0202406826589298, 0.0348493983916433, 16, 16, 0.00730435786635676, "contGamma", "debCollin1", "contNormal", "", "", 0.603244322981952, 0.0140538503475361, 0.519740689257968, -0.0607600723038735, - 0.0265459103585403, 16, 16, -0.0171070809726666, "contGamma", + 0.0265459103585403, 50, 16, -0.0171070809726666, "contGamma", "debCollin1", "contNormal", "", "", 0.442435942877486, 0.022272343612197, -0.768086253989823, -0.198019710798753, 0.0536984002696761, - 50, 16, -0.0721606552645382, "contGamma", "debCollin1", "contNormal", - "", "", 0.261125262541102, 0.0642149838093835, - -1.12373547393145, -0.0313509251283666, 0.063714505999987, 16, - 16, 0.0161817904358102, "contGamma", "debCollin1", "contNormal", - "", "", 0.504618880650379, 0.024251831125015, - 0.667239943754978, -0.0255102614302318, 0.0218718107168498, - 84, 16, -0.00181922535669103, "contGamma", "debCollin1", "contNormal", - "", "", 0.880366312979328, 0.0120874854132079, - -0.150504864701071, -0.137012862848958, 0.0372595875748886, - 16, 16, -0.0498766376370346, "contGamma", "debCollin1", "contNormal", - "", "", 0.261913342931348, 0.0444580746887406, - -1.12188028802935, -0.0513792243261781, 0.104554232357893, 16, - 16, 0.0265875040158574, "contGamma", "debCollin1", "contNormal", - "", "", 0.503898029011322, 0.0397796739924953, - 0.668369077656928, -0.0247998786072625, 0.0570008545633303, - 50, 16, 0.0161004879780339, "contGamma", "debCollin1", "contNormal", - "", "", 0.440385361948436, 0.0208679174249697, - 0.77154263409001, -0.0848234230106755, 0.0373107258610538, 50, - 16, -0.0237563485748108, "contGamma", "debCollin1", "contNormal", - "", "", 0.445781736267872, 0.0311572431521977, - -0.762466321515201, -0.0202406826589298, 0.0348493983916433, - 50, 50, 0.00730435786635676, "contGamma", "debCollin1", "contNormal", - "", "", 0.603244322981952, 0.0140538503475361, - 0.519740689257968, -0.0607600723038735, 0.0265459103585403, - 84, 50, -0.0171070809726666, "contGamma", "debCollin1", "contNormal", - "", "", 0.442435942877486, 0.022272343612197, - -0.768086253989823, -0.198019710798753, 0.0536984002696761, - 50, 50, -0.0721606552645382, "contGamma", "debCollin1", "contNormal", + 84, 16, -0.0721606552645382, "contGamma", "debCollin1", "contNormal", "", "", 0.261125262541102, 0.0642149838093835, -1.12373547393145, -0.0313509251283666, 0.063714505999987, 16, 50, 0.0161817904358102, "contGamma", "debCollin1", "contNormal", "", "", 0.504618880650379, 0.024251831125015, 0.667239943754978, -0.0255102614302318, 0.0218718107168498, - 84, 50, -0.00181922535669103, "contGamma", "debCollin1", "contNormal", - "", "", 0.880366312979328, 0.0120874854132079, - -0.150504864701071, -0.137012862848958, 0.0372595875748886, - 50, 50, -0.0498766376370346, "contGamma", "debCollin1", "contNormal", - "", "", 0.261913342931348, 0.0444580746887406, - -1.12188028802935, -0.0513792243261781, 0.104554232357893, 84, - 50, 0.0265875040158574, "contGamma", "debCollin1", "contNormal", - "", "", 0.503898029011322, 0.0397796739924953, - 0.668369077656928, -0.0247998786072625, 0.0570008545633303, - 84, 50, 0.0161004879780339, "contGamma", "debCollin1", "contNormal", - "", "", 0.440385361948436, 0.0208679174249697, - 0.77154263409001, -0.0848234230106755, 0.0373107258610538, 84, - 50, -0.0237563485748108, "contGamma", "debCollin1", "contNormal", - "", "", 0.445781736267872, 0.0311572431521977, - -0.762466321515201, -0.0202406826589298, 0.0348493983916433, - 16, 84, 0.00730435786635676, "contGamma", "debCollin1", "contNormal", - "", "", 0.603244322981952, 0.0140538503475361, - 0.519740689257968, -0.0607600723038735, 0.0265459103585403, - 16, 84, -0.0171070809726666, "contGamma", "debCollin1", "contNormal", - "", "", 0.442435942877486, 0.022272343612197, - -0.768086253989823, -0.198019710798753, 0.0536984002696761, - 50, 84, -0.0721606552645382, "contGamma", "debCollin1", "contNormal", - "", "", 0.261125262541102, 0.0642149838093835, - -1.12373547393145, -0.0313509251283666, 0.063714505999987, 16, - 84, 0.0161817904358102, "contGamma", "debCollin1", "contNormal", - "", "", 0.504618880650379, 0.024251831125015, - 0.667239943754978, -0.0255102614302318, 0.0218718107168498, - 84, 84, -0.00181922535669103, "contGamma", "debCollin1", "contNormal", + 50, 50, -0.00181922535669103, "contGamma", "debCollin1", "contNormal", "", "", 0.880366312979328, 0.0120874854132079, -0.150504864701071, -0.137012862848958, 0.0372595875748886, - 16, 84, -0.0498766376370346, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0498766376370346, "contGamma", "debCollin1", "contNormal", "", "", 0.261913342931348, 0.0444580746887406, -1.12188028802935, -0.0513792243261781, 0.104554232357893, 16, 84, 0.0265875040158574, "contGamma", "debCollin1", "contNormal", @@ -10237,7 +9236,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.668369077656928, -0.0247998786072625, 0.0570008545633303, 50, 84, 0.0161004879780339, "contGamma", "debCollin1", "contNormal", "", "", 0.440385361948436, 0.0208679174249697, - 0.77154263409001, -0.0848234230106755, 0.0373107258610538, 50, + 0.77154263409001, -0.0848234230106755, 0.0373107258610538, 84, 84, -0.0237563485748108, "contGamma", "debCollin1", "contNormal", "", "", 0.445781736267872, 0.0311572431521977, -0.762466321515201)) @@ -10282,116 +9281,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.58434496891388, 0.117754232562312, -0.547049145289628, -0.200335112242471, 0.179096746051909, 16, 16, -0.0106191830952811, "Total", 0.912641535642733, 0.0967956200438607, -0.109707268680848, - -0.145233690021939, 0.121028315760376, 16, 16, -0.0121026871307815, - "Total", 0.858584277647633, 0.0679252292089438, -0.178176610837081, - -0.257062012294916, 0.172795342995025, 50, 16, -0.0421333346499454, - "Total", 0.70081566519625, 0.109659503613485, -0.384219636799123, - -0.199321145408945, 0.198894206378477, 16, 16, -0.000213469515234006, - "Total", 0.998323375941562, 0.101587415617964, -0.00210133818185505, - -0.132519453675427, 0.144153506083314, 84, 16, 0.00581702620394346, - "Total", 0.934315783660471, 0.0705811336180414, 0.082416162871838, - -0.225081248980546, 0.193055157805103, 16, 16, -0.0160130455877217, - "Total", 0.880671171494568, 0.10666941078608, -0.150118440419954, - -0.205600323483521, 0.166607092154051, 16, 16, -0.0194966156647346, - "Total", 0.837314347906967, 0.0949526161127186, -0.205329947324359, - -0.16454347522722, 0.109762389733706, 50, 16, -0.027390542746757, - "Total", 0.695486399304519, 0.0699772718082108, -0.39142055754656, - -0.295211407126735, 0.166376702571837, 50, 16, -0.064417352277449, - "Total", 0.58434496891388, 0.117754232562312, -0.547049145289628, - -0.200335112242471, 0.179096746051909, 50, 50, -0.0106191830952811, - "Total", 0.912641535642733, 0.0967956200438607, -0.109707268680848, - -0.145233690021939, 0.121028315760376, 84, 50, -0.0121026871307815, + -0.145233690021939, 0.121028315760376, 50, 16, -0.0121026871307815, "Total", 0.858584277647633, 0.0679252292089438, -0.178176610837081, - -0.257062012294916, 0.172795342995025, 50, 50, -0.0421333346499454, + -0.257062012294916, 0.172795342995025, 84, 16, -0.0421333346499454, "Total", 0.70081566519625, 0.109659503613485, -0.384219636799123, -0.199321145408945, 0.198894206378477, 16, 50, -0.000213469515234006, "Total", 0.998323375941562, 0.101587415617964, -0.00210133818185505, - -0.132519453675427, 0.144153506083314, 84, 50, 0.00581702620394346, + -0.132519453675427, 0.144153506083314, 50, 50, 0.00581702620394346, "Total", 0.934315783660471, 0.0705811336180414, 0.082416162871838, - -0.225081248980546, 0.193055157805103, 50, 50, -0.0160130455877217, - "Total", 0.880671171494568, 0.10666941078608, -0.150118440419954, - -0.205600323483521, 0.166607092154051, 84, 50, -0.0194966156647346, - "Total", 0.837314347906967, 0.0949526161127186, -0.205329947324359, - -0.16454347522722, 0.109762389733706, 84, 50, -0.027390542746757, - "Total", 0.695486399304519, 0.0699772718082108, -0.39142055754656, - -0.295211407126735, 0.166376702571837, 84, 50, -0.064417352277449, - "Total", 0.58434496891388, 0.117754232562312, -0.547049145289628, - -0.200335112242471, 0.179096746051909, 16, 84, -0.0106191830952811, - "Total", 0.912641535642733, 0.0967956200438607, -0.109707268680848, - -0.145233690021939, 0.121028315760376, 16, 84, -0.0121026871307815, - "Total", 0.858584277647633, 0.0679252292089438, -0.178176610837081, - -0.257062012294916, 0.172795342995025, 50, 84, -0.0421333346499454, - "Total", 0.70081566519625, 0.109659503613485, -0.384219636799123, - -0.199321145408945, 0.198894206378477, 16, 84, -0.000213469515234006, - "Total", 0.998323375941562, 0.101587415617964, -0.00210133818185505, - -0.132519453675427, 0.144153506083314, 84, 84, 0.00581702620394346, - "Total", 0.934315783660471, 0.0705811336180414, 0.082416162871838, - -0.225081248980546, 0.193055157805103, 16, 84, -0.0160130455877217, + -0.225081248980546, 0.193055157805103, 84, 50, -0.0160130455877217, "Total", 0.880671171494568, 0.10666941078608, -0.150118440419954, -0.205600323483521, 0.166607092154051, 16, 84, -0.0194966156647346, "Total", 0.837314347906967, 0.0949526161127186, -0.205329947324359, -0.16454347522722, 0.109762389733706, 50, 84, -0.027390542746757, "Total", 0.695486399304519, 0.0699772718082108, -0.39142055754656, - -0.295211407126735, 0.166376702571837, 50, 84, -0.064417352277449, + -0.295211407126735, 0.166376702571837, 84, 84, -0.064417352277449, "Total", 0.58434496891388, 0.117754232562312, -0.547049145289628, - -0.0202406826589298, 0.0348493983916433, 50, 16, 0.00730435786635676, - "Total indirect", 0.603244322981952, 0.0140538503475361, 0.519740689257968, - -0.0607600723038735, 0.0265459103585403, 84, 16, -0.0171070809726666, - "Total indirect", 0.442435942877486, 0.022272343612197, -0.768086253989823, - -0.198019710798753, 0.0536984002696761, 50, 16, -0.0721606552645382, - "Total indirect", 0.261125262541102, 0.0642149838093835, -1.12373547393145, - -0.0313509251283666, 0.063714505999987, 16, 16, 0.0161817904358102, - "Total indirect", 0.504618880650379, 0.024251831125015, 0.667239943754978, - -0.0255102614302318, 0.0218718107168498, 84, 16, -0.00181922535669103, - "Total indirect", 0.880366312979328, 0.0120874854132079, -0.150504864701071, - -0.137012862848958, 0.0372595875748886, 50, 16, -0.0498766376370346, - "Total indirect", 0.261913342931348, 0.0444580746887406, -1.12188028802935, - -0.0513792243261781, 0.104554232357893, 84, 16, 0.0265875040158574, - "Total indirect", 0.503898029011322, 0.0397796739924953, 0.668369077656928, - -0.0247998786072625, 0.0570008545633303, 84, 16, 0.0161004879780339, - "Total indirect", 0.440385361948436, 0.0208679174249697, 0.77154263409001, - -0.0848234230106755, 0.0373107258610538, 84, 16, -0.0237563485748108, - "Total indirect", 0.445781736267872, 0.0311572431521977, -0.762466321515201, - -0.0202406826589298, 0.0348493983916433, 16, 50, 0.00730435786635676, + -0.0202406826589298, 0.0348493983916433, 16, 16, 0.00730435786635676, "Total indirect", 0.603244322981952, 0.0140538503475361, 0.519740689257968, - -0.0607600723038735, 0.0265459103585403, 16, 50, -0.0171070809726666, + -0.0607600723038735, 0.0265459103585403, 50, 16, -0.0171070809726666, "Total indirect", 0.442435942877486, 0.022272343612197, -0.768086253989823, - -0.198019710798753, 0.0536984002696761, 50, 50, -0.0721606552645382, + -0.198019710798753, 0.0536984002696761, 84, 16, -0.0721606552645382, "Total indirect", 0.261125262541102, 0.0642149838093835, -1.12373547393145, -0.0313509251283666, 0.063714505999987, 16, 50, 0.0161817904358102, "Total indirect", 0.504618880650379, 0.024251831125015, 0.667239943754978, - -0.0255102614302318, 0.0218718107168498, 84, 50, -0.00181922535669103, - "Total indirect", 0.880366312979328, 0.0120874854132079, -0.150504864701071, - -0.137012862848958, 0.0372595875748886, 16, 50, -0.0498766376370346, - "Total indirect", 0.261913342931348, 0.0444580746887406, -1.12188028802935, - -0.0513792243261781, 0.104554232357893, 16, 50, 0.0265875040158574, - "Total indirect", 0.503898029011322, 0.0397796739924953, 0.668369077656928, - -0.0247998786072625, 0.0570008545633303, 50, 50, 0.0161004879780339, - "Total indirect", 0.440385361948436, 0.0208679174249697, 0.77154263409001, - -0.0848234230106755, 0.0373107258610538, 50, 50, -0.0237563485748108, - "Total indirect", 0.445781736267872, 0.0311572431521977, -0.762466321515201, - -0.0202406826589298, 0.0348493983916433, 50, 84, 0.00730435786635676, - "Total indirect", 0.603244322981952, 0.0140538503475361, 0.519740689257968, - -0.0607600723038735, 0.0265459103585403, 84, 84, -0.0171070809726666, - "Total indirect", 0.442435942877486, 0.022272343612197, -0.768086253989823, - -0.198019710798753, 0.0536984002696761, 50, 84, -0.0721606552645382, - "Total indirect", 0.261125262541102, 0.0642149838093835, -1.12373547393145, - -0.0313509251283666, 0.063714505999987, 16, 84, 0.0161817904358102, - "Total indirect", 0.504618880650379, 0.024251831125015, 0.667239943754978, - -0.0255102614302318, 0.0218718107168498, 84, 84, -0.00181922535669103, + -0.0255102614302318, 0.0218718107168498, 50, 50, -0.00181922535669103, "Total indirect", 0.880366312979328, 0.0120874854132079, -0.150504864701071, - -0.137012862848958, 0.0372595875748886, 50, 84, -0.0498766376370346, + -0.137012862848958, 0.0372595875748886, 84, 50, -0.0498766376370346, "Total indirect", 0.261913342931348, 0.0444580746887406, -1.12188028802935, - -0.0513792243261781, 0.104554232357893, 84, 84, 0.0265875040158574, + -0.0513792243261781, 0.104554232357893, 16, 84, 0.0265875040158574, "Total indirect", 0.503898029011322, 0.0397796739924953, 0.668369077656928, - -0.0247998786072625, 0.0570008545633303, 84, 84, 0.0161004879780339, + -0.0247998786072625, 0.0570008545633303, 50, 84, 0.0161004879780339, "Total indirect", 0.440385361948436, 0.0208679174249697, 0.77154263409001, -0.0848234230106755, 0.0373107258610538, 84, 84, -0.0237563485748108, - "Total indirect", 0.445781736267872, 0.0311572431521977, -0.762466321515201, - 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 84, 50, - 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, - 16, 84, 50, 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, - 50, 84, 50, 16, 84, 50, 84, 84, 84)) + "Total indirect", 0.445781736267872, 0.0311572431521977, -0.762466321515201 + )) @@ -10407,7 +9331,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 65 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -10418,27 +9342,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -10485,46 +9409,29 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0353601423811067, 1.18476148862187, "", 0.61006081550149, 0, - "facGenderm", "contNormal", "", "", "", 0.0374745181089187, + "m", "facGender", "contNormal", "", "", "", 0.0374745181089187, 0.293220017129676, 2.0805565100001, -0.237849469605329, 0.934914944994686, - "", 0.348532737694679, 1, "facGenderm", "contNormal", "", "", - "", 0.244035324611168, 0.299180093065646, 1.16495965397739, - -0.0341650769106585, 0.0289963182028025, 16, -0.00258437935392797, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.872572310728322, 0.0161128968725114, -0.160391975097719, -0.0729506665205528, - 0.0863053166632494, 16, 0.00667732507134832, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.869451112257992, - 0.0406272728580712, 0.164355729577891, -0.0195493083484164, - 0.0179747913516262, 16, -0.000787258498395074, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.934455555357992, - 0.00957265031297205, -0.0822403903470962, -0.0630819329241026, - 0.0636629763452924, 16, 0.000290521710594861, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.992830970420113, - 0.0323334791529698, 0.00898516702209501, -0.0231427275647059, - 0.0257812135381103, 50, 0.0013192429867022, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.915819133087903, - 0.012480826558223, 0.10570157197105, -0.0851235785298863, 0.0707319942359945, - 50, -0.00719579214694589, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.856382038893699, 0.039759805280926, - -0.180981574132556, -0.0341650769106585, 0.0289963182028025, - 50, -0.00258437935392797, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.872572310728322, 0.0161128968725114, - -0.160391975097719, -0.0729506665205528, 0.0863053166632494, - 50, 0.00667732507134832, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.869451112257992, 0.0406272728580712, - 0.164355729577891, -0.0195493083484164, 0.0179747913516262, - 84, -0.000787258498395074, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.934455555357992, 0.00957265031297205, - -0.0822403903470962, -0.0630819329241026, 0.0636629763452924, - 84, 0.000290521710594861, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.992830970420113, 0.0323334791529698, - 0.00898516702209501, -0.0231427275647059, 0.0257812135381103, - 84, 0.0013192429867022, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.915819133087903, 0.012480826558223, - 0.10570157197105, -0.0851235785298863, 0.0707319942359945, 84, - -0.00719579214694589, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.856382038893699, 0.039759805280926, - -0.180981574132556)) + "", 0.348532737694679, 1, "m", "facGender", "contNormal", "", + "", "", 0.244035324611168, 0.299180093065646, 1.16495965397739, + -0.0341650769106585, 0.0289963182028025, "", -0.00258437935392797, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.872572310728322, 0.0161128968725114, -0.160391975097719, + -0.0729506665205528, 0.0863053166632494, "", 0.00667732507134832, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.869451112257992, 0.0406272728580712, 0.164355729577891, + -0.0195493083484164, 0.0179747913516262, 16, -0.000787258498395074, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.934455555357992, 0.00957265031297205, -0.0822403903470962, + -0.0630819329241026, 0.0636629763452924, 16, 0.000290521710594861, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.992830970420113, 0.0323334791529698, 0.00898516702209501, + -0.0231427275647059, 0.0257812135381103, 50, 0.0013192429867022, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.915819133087903, 0.012480826558223, 0.10570157197105, + -0.0851235785298863, 0.0707319942359945, 50, -0.00719579214694589, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.856382038893699, 0.039759805280926, -0.180981574132556 + )) @@ -10561,61 +9468,35 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0322002428158382, 1.18275262947929, "", 0.607476436147562, 0, - "Total", 0.0384832486248525, 0.293513655286234, 2.0696700995228, + "m", "Total", 0.0384832486248525, 0.293513655286234, 2.0696700995228, -0.232334868722909, 0.942754994254963, "", 0.355210062766027, - 1, "Total", 0.236045586242455, 0.299773330593529, 1.18492883293766, - 0.0347785925064743, 1.18376852149971, 16, 0.609273557003095, - 0, "Total", 0.0376526906703707, 0.293115061821627, 2.07861565767597, - -0.235026621272866, 0.932673140083414, 16, 0.348823259405274, - 0, "Total", 0.241603723670882, 0.297888065945841, 1.17098769397729, + 1, "m", "Total", 0.236045586242455, 0.299773330593529, 1.18492883293766, + 0.0347785925064743, 1.18376852149971, "", 0.609273557003095, + 0, "m", "Total", 0.0376526906703707, 0.293115061821627, 2.07861565767597, + -0.235026621272866, 0.932673140083414, "", 0.348823259405274, + 1, "m", "Total", 0.241603723670882, 0.297888065945841, 1.17098769397729, 0.0369286765494852, 1.1858314404269, 16, 0.611380058488192, - 1, "Total", 0.0369822006665697, 0.293092825414092, 2.08596050628128, + 0, "m", "Total", 0.0369822006665697, 0.293092825414092, 2.08596050628128, -0.242262726411015, 0.924936617506481, 16, 0.341336945547733, - 0, "Total", 0.25165132896972, 0.297760406090167, 1.14634766263843, + 1, "m", "Total", 0.25165132896972, 0.297760406090167, 1.14634766263843, 0.0322002428158382, 1.18275262947929, 50, 0.607476436147562, - 0, "Total", 0.0384832486248525, 0.293513655286234, 2.0696700995228, + 0, "m", "Total", 0.0384832486248525, 0.293513655286234, 2.0696700995228, -0.232334868722909, 0.942754994254963, 50, 0.355210062766027, - 1, "Total", 0.236045586242455, 0.299773330593529, 1.18492883293766, - 0.0347785925064743, 1.18376852149971, 50, 0.609273557003095, - 1, "Total", 0.0376526906703707, 0.293115061821627, 2.07861565767597, - -0.235026621272866, 0.932673140083414, 50, 0.348823259405274, - 1, "Total", 0.241603723670882, 0.297888065945841, 1.17098769397729, - 0.0369286765494852, 1.1858314404269, 84, 0.611380058488192, - 0, "Total", 0.0369822006665697, 0.293092825414092, 2.08596050628128, - -0.242262726411015, 0.924936617506481, 84, 0.341336945547733, - 0, "Total", 0.25165132896972, 0.297760406090167, 1.14634766263843, - 0.0322002428158382, 1.18275262947929, 84, 0.607476436147562, - 1, "Total", 0.0384832486248525, 0.293513655286234, 2.0696700995228, - -0.232334868722909, 0.942754994254963, 84, 0.355210062766027, - 0, "Total", 0.236045586242455, 0.299773330593529, 1.18492883293766, - -0.0341650769106585, 0.0289963182028025, 16, -0.00258437935392797, - 0, "Total indirect", 0.872572310728322, 0.0161128968725114, + 1, "m", "Total", 0.236045586242455, 0.299773330593529, 1.18492883293766, + -0.0341650769106585, 0.0289963182028025, 84, -0.00258437935392797, + 0, "m", "Total indirect", 0.872572310728322, 0.0161128968725114, -0.160391975097719, -0.0729506665205528, 0.0863053166632494, - 16, 0.00667732507134832, 1, "Total indirect", 0.869451112257992, + 84, 0.00667732507134832, 1, "m", "Total indirect", 0.869451112257992, 0.0406272728580712, 0.164355729577891, -0.0195493083484164, - 0.0179747913516262, 16, -0.000787258498395074, 1, "Total indirect", + 0.0179747913516262, 16, -0.000787258498395074, 0, "m", "Total indirect", 0.934455555357992, 0.00957265031297205, -0.0822403903470962, -0.0630819329241026, 0.0636629763452924, 16, 0.000290521710594861, - 1, "Total indirect", 0.992830970420113, 0.0323334791529698, - 0.00898516702209501, -0.0231427275647059, 0.0257812135381103, - 50, 0.0013192429867022, 0, "Total indirect", 0.915819133087903, - 0.012480826558223, 0.10570157197105, -0.0851235785298863, 0.0707319942359945, - 50, -0.00719579214694589, 0, "Total indirect", 0.856382038893699, - 0.039759805280926, -0.180981574132556, -0.0341650769106585, - 0.0289963182028025, 50, -0.00258437935392797, 1, "Total indirect", - 0.872572310728322, 0.0161128968725114, -0.160391975097719, -0.0729506665205528, - 0.0863053166632494, 50, 0.00667732507134832, 0, "Total indirect", - 0.869451112257992, 0.0406272728580712, 0.164355729577891, -0.0195493083484164, - 0.0179747913516262, 84, -0.000787258498395074, 0, "Total indirect", - 0.934455555357992, 0.00957265031297205, -0.0822403903470962, - -0.0630819329241026, 0.0636629763452924, 84, 0.000290521710594861, - 1, "Total indirect", 0.992830970420113, 0.0323334791529698, + 1, "m", "Total indirect", 0.992830970420113, 0.0323334791529698, 0.00898516702209501, -0.0231427275647059, 0.0257812135381103, - 84, 0.0013192429867022, 1, "Total indirect", 0.915819133087903, + 50, 0.0013192429867022, 0, "m", "Total indirect", 0.915819133087903, 0.012480826558223, 0.10570157197105, -0.0851235785298863, 0.0707319942359945, - 84, -0.00719579214694589, 1, "Total indirect", 0.856382038893699, - 0.039759805280926, -0.180981574132556, 0, 0, 1, 0, 0, 1, 1, - 1, 0, 0, 1, 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, 1, 1, 1)) + 50, -0.00719579214694589, 1, "m", "Total indirect", 0.856382038893699, + 0.039759805280926, -0.180981574132556, 84, 84)) @@ -10631,7 +9512,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 66 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -10642,27 +9523,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -10717,73 +9598,19 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) -0.019639260060957, 0.0330747963789523, 16, 16, 0.00671776815899763, "contGamma", "debCollin1", "contNormal", "", "", 0.617393836996679, 0.0134477104823637, 0.499547351782133, -0.0595342627878137, - 0.0266309719847771, 16, 16, -0.0164516454015183, "contGamma", + 0.0266309719847771, 50, 16, -0.0164516454015183, "contGamma", "debCollin1", "contNormal", "", "", 0.454196506076532, 0.021981331150024, -0.748437175584807, -0.189731398522699, 0.0526203176057261, - 50, 16, -0.0685555404584863, "contGamma", "debCollin1", "contNormal", - "", "", 0.267492973728177, 0.061825553438753, - -1.10885445653795, -0.0302741736895144, 0.0613296087735036, - 16, 16, 0.0155277175419946, "contGamma", "debCollin1", "contNormal", - "", "", 0.506392554415519, 0.0233687412589152, - 0.664465294469841, -0.0248122133313827, 0.0222521678534295, - 84, 16, -0.0012800227389766, "contGamma", "debCollin1", "contNormal", - "", "", 0.915097318620563, 0.0120064403111614, - -0.106611344062292, -0.128969979862088, 0.0360880599438141, - 16, 16, -0.0464409599591368, "contGamma", "debCollin1", "contNormal", - "", "", 0.270063474697908, 0.0421074165412881, - -1.10291639273569, -0.0501710343612898, 0.101879695300156, 16, - 16, 0.0258543304694329, "contGamma", "debCollin1", "contNormal", - "", "", 0.505069283995214, 0.0387891642042411, - 0.666534868689078, -0.0247007185331131, 0.0577076140002671, - 50, 16, 0.016503447733577, "contGamma", "debCollin1", "contNormal", - "", "", 0.432440866675431, 0.0210229201106262, - 0.785021664294639, -0.0784011233706981, 0.0373625689342295, - 50, 16, -0.0205192772182343, "contGamma", "debCollin1", "contNormal", - "", "", 0.487172660768907, 0.0295320968186295, - -0.694812743715857, -0.019639260060957, 0.0330747963789523, - 50, 50, 0.00671776815899763, "contGamma", "debCollin1", "contNormal", - "", "", 0.617393836996679, 0.0134477104823637, - 0.499547351782133, -0.0595342627878137, 0.0266309719847771, - 84, 50, -0.0164516454015183, "contGamma", "debCollin1", "contNormal", - "", "", 0.454196506076532, 0.021981331150024, - -0.748437175584807, -0.189731398522699, 0.0526203176057261, - 50, 50, -0.0685555404584863, "contGamma", "debCollin1", "contNormal", + 84, 16, -0.0685555404584863, "contGamma", "debCollin1", "contNormal", "", "", 0.267492973728177, 0.061825553438753, -1.10885445653795, -0.0302741736895144, 0.0613296087735036, 16, 50, 0.0155277175419946, "contGamma", "debCollin1", "contNormal", "", "", 0.506392554415519, 0.0233687412589152, 0.664465294469841, -0.0248122133313827, 0.0222521678534295, - 84, 50, -0.0012800227389766, "contGamma", "debCollin1", "contNormal", - "", "", 0.915097318620563, 0.0120064403111614, - -0.106611344062292, -0.128969979862088, 0.0360880599438141, - 50, 50, -0.0464409599591368, "contGamma", "debCollin1", "contNormal", - "", "", 0.270063474697908, 0.0421074165412881, - -1.10291639273569, -0.0501710343612898, 0.101879695300156, 84, - 50, 0.0258543304694329, "contGamma", "debCollin1", "contNormal", - "", "", 0.505069283995214, 0.0387891642042411, - 0.666534868689078, -0.0247007185331131, 0.0577076140002671, - 84, 50, 0.016503447733577, "contGamma", "debCollin1", "contNormal", - "", "", 0.432440866675431, 0.0210229201106262, - 0.785021664294639, -0.0784011233706981, 0.0373625689342295, - 84, 50, -0.0205192772182343, "contGamma", "debCollin1", "contNormal", - "", "", 0.487172660768907, 0.0295320968186295, - -0.694812743715857, -0.019639260060957, 0.0330747963789523, - 16, 84, 0.00671776815899763, "contGamma", "debCollin1", "contNormal", - "", "", 0.617393836996679, 0.0134477104823637, - 0.499547351782133, -0.0595342627878137, 0.0266309719847771, - 16, 84, -0.0164516454015183, "contGamma", "debCollin1", "contNormal", - "", "", 0.454196506076532, 0.021981331150024, - -0.748437175584807, -0.189731398522699, 0.0526203176057261, - 50, 84, -0.0685555404584863, "contGamma", "debCollin1", "contNormal", - "", "", 0.267492973728177, 0.061825553438753, - -1.10885445653795, -0.0302741736895144, 0.0613296087735036, - 16, 84, 0.0155277175419946, "contGamma", "debCollin1", "contNormal", - "", "", 0.506392554415519, 0.0233687412589152, - 0.664465294469841, -0.0248122133313827, 0.0222521678534295, - 84, 84, -0.0012800227389766, "contGamma", "debCollin1", "contNormal", + 50, 50, -0.0012800227389766, "contGamma", "debCollin1", "contNormal", "", "", 0.915097318620563, 0.0120064403111614, -0.106611344062292, -0.128969979862088, 0.0360880599438141, - 16, 84, -0.0464409599591368, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0464409599591368, "contGamma", "debCollin1", "contNormal", "", "", 0.270063474697908, 0.0421074165412881, -1.10291639273569, -0.0501710343612898, 0.101879695300156, 16, 84, 0.0258543304694329, "contGamma", "debCollin1", "contNormal", @@ -10792,7 +9619,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 50, 84, 0.016503447733577, "contGamma", "debCollin1", "contNormal", "", "", 0.432440866675431, 0.0210229201106262, 0.785021664294639, -0.0784011233706981, 0.0373625689342295, - 50, 84, -0.0205192772182343, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0205192772182343, "contGamma", "debCollin1", "contNormal", "", "", 0.487172660768907, 0.0295320968186295, -0.694812743715857)) @@ -10836,116 +9663,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.420185396889656, 0.118866761483266, -0.806099643915941, -0.167261612433686, 0.19542784630907, 16, 16, 0.014083116937692, "Total", 0.879021651761045, 0.0925245212676366, 0.152209562878528, - -0.147716352841562, 0.118495017169814, 16, 16, -0.0146106678358741, - "Total", 0.829658018120303, 0.0679123116830763, -0.215140192901357, - -0.28884209001517, 0.141434342803665, 50, 16, -0.0737038736057523, - "Total", 0.501926849341373, 0.109766413110853, -0.671461073719506, - -0.167533542850355, 0.216353002580615, 16, 16, 0.0244097298651303, - "Total", 0.803166072565421, 0.0979320407055992, 0.249251722819809, - -0.134926929204896, 0.141272534478255, 84, 16, 0.0031728026366795, - "Total", 0.96408369694426, 0.070460341583258, 0.0450296232658824, - -0.254380563755482, 0.158816182025783, 16, 16, -0.0477821908648499, - "Total", 0.650331580130385, 0.105409270027538, -0.453301601010677, - -0.171500149637237, 0.182046484746627, 16, 16, 0.00527316755469502, - "Total", 0.953377490499848, 0.0901921252565338, 0.0584659418956648, - -0.167041091334296, 0.107476510337465, 50, 16, -0.0297822904984158, - "Total", 0.670638976123402, 0.0700312872678072, -0.42527121320111, - -0.328793025571216, 0.137156117361012, 50, 16, -0.0958184541051018, - "Total", 0.420185396889656, 0.118866761483266, -0.806099643915941, - -0.167261612433686, 0.19542784630907, 50, 50, 0.014083116937692, - "Total", 0.879021651761045, 0.0925245212676366, 0.152209562878528, - -0.147716352841562, 0.118495017169814, 84, 50, -0.0146106678358741, + -0.147716352841562, 0.118495017169814, 50, 16, -0.0146106678358741, "Total", 0.829658018120303, 0.0679123116830763, -0.215140192901357, - -0.28884209001517, 0.141434342803665, 50, 50, -0.0737038736057523, + -0.28884209001517, 0.141434342803665, 84, 16, -0.0737038736057523, "Total", 0.501926849341373, 0.109766413110853, -0.671461073719506, -0.167533542850355, 0.216353002580615, 16, 50, 0.0244097298651303, "Total", 0.803166072565421, 0.0979320407055992, 0.249251722819809, - -0.134926929204896, 0.141272534478255, 84, 50, 0.0031728026366795, - "Total", 0.96408369694426, 0.070460341583258, 0.0450296232658824, - -0.254380563755482, 0.158816182025783, 50, 50, -0.0477821908648499, - "Total", 0.650331580130385, 0.105409270027538, -0.453301601010677, - -0.171500149637237, 0.182046484746627, 84, 50, 0.00527316755469502, - "Total", 0.953377490499848, 0.0901921252565338, 0.0584659418956648, - -0.167041091334296, 0.107476510337465, 84, 50, -0.0297822904984158, - "Total", 0.670638976123402, 0.0700312872678072, -0.42527121320111, - -0.328793025571216, 0.137156117361012, 84, 50, -0.0958184541051018, - "Total", 0.420185396889656, 0.118866761483266, -0.806099643915941, - -0.167261612433686, 0.19542784630907, 16, 84, 0.014083116937692, - "Total", 0.879021651761045, 0.0925245212676366, 0.152209562878528, - -0.147716352841562, 0.118495017169814, 16, 84, -0.0146106678358741, - "Total", 0.829658018120303, 0.0679123116830763, -0.215140192901357, - -0.28884209001517, 0.141434342803665, 50, 84, -0.0737038736057523, - "Total", 0.501926849341373, 0.109766413110853, -0.671461073719506, - -0.167533542850355, 0.216353002580615, 16, 84, 0.0244097298651303, - "Total", 0.803166072565421, 0.0979320407055992, 0.249251722819809, - -0.134926929204896, 0.141272534478255, 84, 84, 0.0031728026366795, + -0.134926929204896, 0.141272534478255, 50, 50, 0.0031728026366795, "Total", 0.96408369694426, 0.070460341583258, 0.0450296232658824, - -0.254380563755482, 0.158816182025783, 16, 84, -0.0477821908648499, + -0.254380563755482, 0.158816182025783, 84, 50, -0.0477821908648499, "Total", 0.650331580130385, 0.105409270027538, -0.453301601010677, -0.171500149637237, 0.182046484746627, 16, 84, 0.00527316755469502, "Total", 0.953377490499848, 0.0901921252565338, 0.0584659418956648, -0.167041091334296, 0.107476510337465, 50, 84, -0.0297822904984158, "Total", 0.670638976123402, 0.0700312872678072, -0.42527121320111, - -0.328793025571216, 0.137156117361012, 50, 84, -0.0958184541051018, + -0.328793025571216, 0.137156117361012, 84, 84, -0.0958184541051018, "Total", 0.420185396889656, 0.118866761483266, -0.806099643915941, - -0.019639260060957, 0.0330747963789523, 50, 16, 0.00671776815899763, - "Total indirect", 0.617393836996679, 0.0134477104823637, 0.499547351782133, - -0.0595342627878137, 0.0266309719847771, 84, 16, -0.0164516454015183, - "Total indirect", 0.454196506076532, 0.021981331150024, -0.748437175584807, - -0.189731398522699, 0.0526203176057261, 50, 16, -0.0685555404584863, - "Total indirect", 0.267492973728177, 0.061825553438753, -1.10885445653795, - -0.0302741736895144, 0.0613296087735036, 16, 16, 0.0155277175419946, - "Total indirect", 0.506392554415519, 0.0233687412589152, 0.664465294469841, - -0.0248122133313827, 0.0222521678534295, 84, 16, -0.0012800227389766, - "Total indirect", 0.915097318620563, 0.0120064403111614, -0.106611344062292, - -0.128969979862088, 0.0360880599438141, 50, 16, -0.0464409599591368, - "Total indirect", 0.270063474697908, 0.0421074165412881, -1.10291639273569, - -0.0501710343612898, 0.101879695300156, 84, 16, 0.0258543304694329, - "Total indirect", 0.505069283995214, 0.0387891642042411, 0.666534868689078, - -0.0247007185331131, 0.0577076140002671, 84, 16, 0.016503447733577, - "Total indirect", 0.432440866675431, 0.0210229201106262, 0.785021664294639, - -0.0784011233706981, 0.0373625689342295, 84, 16, -0.0205192772182343, - "Total indirect", 0.487172660768907, 0.0295320968186295, -0.694812743715857, - -0.019639260060957, 0.0330747963789523, 16, 50, 0.00671776815899763, + -0.019639260060957, 0.0330747963789523, 16, 16, 0.00671776815899763, "Total indirect", 0.617393836996679, 0.0134477104823637, 0.499547351782133, - -0.0595342627878137, 0.0266309719847771, 16, 50, -0.0164516454015183, + -0.0595342627878137, 0.0266309719847771, 50, 16, -0.0164516454015183, "Total indirect", 0.454196506076532, 0.021981331150024, -0.748437175584807, - -0.189731398522699, 0.0526203176057261, 50, 50, -0.0685555404584863, + -0.189731398522699, 0.0526203176057261, 84, 16, -0.0685555404584863, "Total indirect", 0.267492973728177, 0.061825553438753, -1.10885445653795, -0.0302741736895144, 0.0613296087735036, 16, 50, 0.0155277175419946, "Total indirect", 0.506392554415519, 0.0233687412589152, 0.664465294469841, - -0.0248122133313827, 0.0222521678534295, 84, 50, -0.0012800227389766, - "Total indirect", 0.915097318620563, 0.0120064403111614, -0.106611344062292, - -0.128969979862088, 0.0360880599438141, 16, 50, -0.0464409599591368, - "Total indirect", 0.270063474697908, 0.0421074165412881, -1.10291639273569, - -0.0501710343612898, 0.101879695300156, 16, 50, 0.0258543304694329, - "Total indirect", 0.505069283995214, 0.0387891642042411, 0.666534868689078, - -0.0247007185331131, 0.0577076140002671, 50, 50, 0.016503447733577, - "Total indirect", 0.432440866675431, 0.0210229201106262, 0.785021664294639, - -0.0784011233706981, 0.0373625689342295, 50, 50, -0.0205192772182343, - "Total indirect", 0.487172660768907, 0.0295320968186295, -0.694812743715857, - -0.019639260060957, 0.0330747963789523, 50, 84, 0.00671776815899763, - "Total indirect", 0.617393836996679, 0.0134477104823637, 0.499547351782133, - -0.0595342627878137, 0.0266309719847771, 84, 84, -0.0164516454015183, - "Total indirect", 0.454196506076532, 0.021981331150024, -0.748437175584807, - -0.189731398522699, 0.0526203176057261, 50, 84, -0.0685555404584863, - "Total indirect", 0.267492973728177, 0.061825553438753, -1.10885445653795, - -0.0302741736895144, 0.0613296087735036, 16, 84, 0.0155277175419946, - "Total indirect", 0.506392554415519, 0.0233687412589152, 0.664465294469841, - -0.0248122133313827, 0.0222521678534295, 84, 84, -0.0012800227389766, + -0.0248122133313827, 0.0222521678534295, 50, 50, -0.0012800227389766, "Total indirect", 0.915097318620563, 0.0120064403111614, -0.106611344062292, - -0.128969979862088, 0.0360880599438141, 50, 84, -0.0464409599591368, + -0.128969979862088, 0.0360880599438141, 84, 50, -0.0464409599591368, "Total indirect", 0.270063474697908, 0.0421074165412881, -1.10291639273569, - -0.0501710343612898, 0.101879695300156, 84, 84, 0.0258543304694329, + -0.0501710343612898, 0.101879695300156, 16, 84, 0.0258543304694329, "Total indirect", 0.505069283995214, 0.0387891642042411, 0.666534868689078, - -0.0247007185331131, 0.0577076140002671, 84, 84, 0.016503447733577, + -0.0247007185331131, 0.0577076140002671, 50, 84, 0.016503447733577, "Total indirect", 0.432440866675431, 0.0210229201106262, 0.785021664294639, -0.0784011233706981, 0.0373625689342295, 84, 84, -0.0205192772182343, - "Total indirect", 0.487172660768907, 0.0295320968186295, -0.694812743715857, - 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 84, 50, - 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, - 16, 84, 50, 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, - 50, 84, 50, 16, 84, 50, 84, 84, 84)) + "Total indirect", 0.487172660768907, 0.0295320968186295, -0.694812743715857 + )) @@ -10961,7 +9713,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 66 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -10972,27 +9724,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -11038,48 +9790,30 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.152134720186446, 1.01350311054209, 16, 0.430684195177824, "", - "facGenderm", "contNormal", "", "", "", 0.147519317744498, + "m", "facGender", "contNormal", "", "", "", 0.147519317744498, 0.297362053569081, 1.44834954564157, 0.0689843003479009, 0.890308554047518, - 50, 0.47964642719771, "", "facGenderm", "contNormal", "", "", - "", 0.0220674543381432, 0.209525343368072, 2.28920482595329, + 50, 0.47964642719771, "", "m", "facGender", "contNormal", "", + "", "", 0.0220674543381432, 0.209525343368072, 2.28920482595329, -0.068502305279583, 1.1425776620827, 84, 0.53703767840156, "", - "facGenderm", "contNormal", "", "", "", 0.0821683338966261, + "m", "facGender", "contNormal", "", "", "", 0.0821683338966261, 0.308954648380055, 1.73824113415162, -0.0362335879660736, 0.0305569310986389, - 16, -0.00283832843371733, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.867699608445428, 0.0170387108108995, - -0.166581173025231, -0.0732830017106599, 0.0857898593920737, - 16, 0.00625342884070688, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.877531568730838, 0.0405805571830605, - 0.154099136995517, -0.0193025655637214, 0.0178547358547148, - 16, -0.000723914854503306, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.939124929622951, 0.00947907760334582, - -0.0763697571425923, -0.0647109530394989, 0.0621891744441291, - 16, -0.0012608892976849, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96893128758117, 0.0323730763638006, - -0.0389487018013161, -0.0249001646080846, 0.0284091694169251, - 50, 0.00175450240442023, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.897348461613857, 0.0135995697996256, - 0.129011610681136, -0.0902600841445575, 0.0701224370679086, - 50, -0.0100688235383245, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.805610013812014, 0.040914660289052, - -0.246093294364189, -0.0362335879660736, 0.0305569310986389, - 50, -0.00283832843371733, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.867699608445428, 0.0170387108108995, + 16, -0.00283832843371733, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.867699608445428, 0.0170387108108995, -0.166581173025231, -0.0732830017106599, 0.0857898593920737, - 50, 0.00625342884070688, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.877531568730838, 0.0405805571830605, + 16, 0.00625342884070688, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.877531568730838, 0.0405805571830605, 0.154099136995517, -0.0193025655637214, 0.0178547358547148, - 84, -0.000723914854503306, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.939124929622951, 0.00947907760334582, + 50, -0.000723914854503306, "", "m", "facGender", "debCollin1", + "contNormal", "", "", 0.939124929622951, 0.00947907760334582, -0.0763697571425923, -0.0647109530394989, 0.0621891744441291, - 84, -0.0012608892976849, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96893128758117, 0.0323730763638006, + 50, -0.0012608892976849, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.96893128758117, 0.0323730763638006, -0.0389487018013161, -0.0249001646080846, 0.0284091694169251, - 84, 0.00175450240442023, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.897348461613857, 0.0135995697996256, + 84, 0.00175450240442023, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.897348461613857, 0.0135995697996256, 0.129011610681136, -0.0902600841445575, 0.0701224370679086, - 84, -0.0100688235383245, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.805610013812014, 0.040914660289052, + 84, -0.0100688235383245, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.805610013812014, 0.040914660289052, -0.246093294364189)) @@ -11116,63 +9850,38 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.156762001922874, 1.01245373541109, 16, 0.427845866744106, "", - "Total", 0.151457677882929, 0.298274801617934, 1.43440164715001, + "m", "Total", 0.151457677882929, 0.298274801617934, 1.43440164715001, 0.0713352645706684, 0.900464447506165, 50, 0.485899856038416, - "", "Total", 0.0216062025326385, 0.211516433331317, 2.297220354871, + "", "m", "Total", 0.0216062025326385, 0.211516433331317, 2.297220354871, -0.0689558739649857, 1.1415834010591, 84, 0.536313763547057, - "", "Total", 0.0824448408475518, 0.308816714126551, 1.73667336971689, + "", "m", "Total", 0.0824448408475518, 0.308816714126551, 1.73667336971689, -0.15520494066984, 1.01405155243012, 16, 0.429423305880139, - 0, "Total", 0.14996927432948, 0.298285198688063, 1.43964000818296, + "", "m", "Total", 0.14996927432948, 0.298285198688063, 1.43964000818296, 0.0700724197473102, 0.892729439456949, 16, 0.48140092960213, - 0, "Total", 0.0217987556055002, 0.209865340944694, 2.29385627676841, - -0.0750551378088081, 1.12899284753528, 16, 0.526968854863235, - 1, "Total", 0.0862329619358753, 0.307160742452786, 1.71561264846284, - -0.156762001922874, 1.01245373541109, 16, 0.427845866744106, - 0, "Total", 0.151457677882929, 0.298274801617934, 1.43440164715001, - 0.0713352645706684, 0.900464447506165, 50, 0.485899856038416, - 0, "Total", 0.0216062025326385, 0.211516433331317, 2.297220354871, - -0.0689558739649857, 1.1415834010591, 50, 0.536313763547057, - 1, "Total", 0.0824448408475518, 0.308816714126551, 1.73667336971689, - -0.15520494066984, 1.01405155243012, 50, 0.429423305880139, - 1, "Total", 0.14996927432948, 0.298285198688063, 1.43964000818296, - 0.0700724197473102, 0.892729439456949, 50, 0.48140092960213, - 1, "Total", 0.0217987556055002, 0.209865340944694, 2.29385627676841, - -0.0750551378088081, 1.12899284753528, 84, 0.526968854863235, - 0, "Total", 0.0862329619358753, 0.307160742452786, 1.71561264846284, - -0.156762001922874, 1.01245373541109, 84, 0.427845866744106, - 0, "Total", 0.151457677882929, 0.298274801617934, 1.43440164715001, + "", "m", "Total", 0.0217987556055002, 0.209865340944694, 2.29385627676841, + -0.0750551378088081, 1.12899284753528, 50, 0.526968854863235, + "", "m", "Total", 0.0862329619358753, 0.307160742452786, 1.71561264846284, + -0.156762001922874, 1.01245373541109, 50, 0.427845866744106, + 0, "m", "Total", 0.151457677882929, 0.298274801617934, 1.43440164715001, 0.0713352645706684, 0.900464447506165, 84, 0.485899856038416, - 1, "Total", 0.0216062025326385, 0.211516433331317, 2.297220354871, + 1, "m", "Total", 0.0216062025326385, 0.211516433331317, 2.297220354871, -0.0689558739649857, 1.1415834010591, 84, 0.536313763547057, - 0, "Total", 0.0824448408475518, 0.308816714126551, 1.73667336971689, + 0, "m", "Total", 0.0824448408475518, 0.308816714126551, 1.73667336971689, -0.0362335879660736, 0.0305569310986389, 16, -0.00283832843371733, - 0, "Total indirect", 0.867699608445428, 0.0170387108108995, + 1, "m", "Total indirect", 0.867699608445428, 0.0170387108108995, -0.166581173025231, -0.0732830017106599, 0.0857898593920737, - 16, 0.00625342884070688, 1, "Total indirect", 0.877531568730838, + 16, 0.00625342884070688, 0, "m", "Total indirect", 0.877531568730838, 0.0405805571830605, 0.154099136995517, -0.0193025655637214, - 0.0178547358547148, 16, -0.000723914854503306, 1, "Total indirect", - 0.939124929622951, 0.00947907760334582, -0.0763697571425923, - -0.0647109530394989, 0.0621891744441291, 16, -0.0012608892976849, - 1, "Total indirect", 0.96893128758117, 0.0323730763638006, -0.0389487018013161, - -0.0249001646080846, 0.0284091694169251, 50, 0.00175450240442023, - 0, "Total indirect", 0.897348461613857, 0.0135995697996256, - 0.129011610681136, -0.0902600841445575, 0.0701224370679086, - 50, -0.0100688235383245, 0, "Total indirect", 0.805610013812014, - 0.040914660289052, -0.246093294364189, -0.0362335879660736, - 0.0305569310986389, 50, -0.00283832843371733, 1, "Total indirect", - 0.867699608445428, 0.0170387108108995, -0.166581173025231, -0.0732830017106599, - 0.0857898593920737, 50, 0.00625342884070688, 0, "Total indirect", - 0.877531568730838, 0.0405805571830605, 0.154099136995517, -0.0193025655637214, - 0.0178547358547148, 84, -0.000723914854503306, 0, "Total indirect", + 0.0178547358547148, 50, -0.000723914854503306, 1, "m", "Total indirect", 0.939124929622951, 0.00947907760334582, -0.0763697571425923, - -0.0647109530394989, 0.0621891744441291, 84, -0.0012608892976849, - 1, "Total indirect", 0.96893128758117, 0.0323730763638006, -0.0389487018013161, - -0.0249001646080846, 0.0284091694169251, 84, 0.00175450240442023, - 1, "Total indirect", 0.897348461613857, 0.0135995697996256, - 0.129011610681136, -0.0902600841445575, 0.0701224370679086, - 84, -0.0100688235383245, 1, "Total indirect", 0.805610013812014, - 0.040914660289052, -0.246093294364189, 0, 0, 1, 0, 0, 1, 1, - 1, 0, 0, 1, 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, 1, 1, 1)) + -0.0647109530394989, 0.0621891744441291, 50, -0.0012608892976849, + 0, "m", "Total indirect", 0.96893128758117, 0.0323730763638006, + -0.0389487018013161, -0.0249001646080846, 0.0284091694169251, + 84, 0.00175450240442023, 1, "m", "Total indirect", 0.897348461613857, + 0.0135995697996256, 0.129011610681136, -0.0902600841445575, + 0.0701224370679086, 84, -0.0100688235383245, 0, "m", "Total indirect", + 0.805610013812014, 0.040914660289052, -0.246093294364189, 1, + 0, 1)) @@ -11188,7 +9897,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 67 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -11199,29 +9908,29 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -11290,73 +9999,19 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) -0.0204602368277774, 0.0355989836855878, 16, 16, 0.00756937342890517, "contGamma", "debCollin1", "contNormal", "", "", 0.596606595480347, 0.0143010843453128, 0.529286678278074, -0.0631275108152892, - 0.0260139855994758, 16, 16, -0.0185567626079067, "contGamma", + 0.0260139855994758, 50, 16, -0.0185567626079067, "contGamma", "debCollin1", "contNormal", "", "", 0.414489153432761, 0.0227405955206069, -0.816019201919802, -0.208094805223042, - 0.0534832879548465, 50, 16, -0.0773057586340977, "contGamma", + 0.0534832879548465, 84, 16, -0.0773057586340977, "contGamma", "debCollin1", "contNormal", "", "", 0.246668183754547, 0.0667303315880248, -1.15848006138142, -0.0327770998713117, - 0.0670642084016534, 16, 16, 0.0171435542651708, "contGamma", + 0.0670642084016534, 16, 50, 0.0171435542651708, "contGamma", "debCollin1", "contNormal", "", "", 0.500894421245465, 0.0254701895189148, 0.673083105739736, -0.0257553471872748, - 0.0216171597149908, 84, 16, -0.00206909373614201, "contGamma", + 0.0216171597149908, 50, 50, -0.00206909373614201, "contGamma", "debCollin1", "contNormal", "", "", 0.864057789944843, 0.012085045254896, -0.17121108713298, -0.143621720865794, 0.0370759283592992, - 16, 16, -0.0532728962532472, "contGamma", "debCollin1", "contNormal", - "", "", 0.247818283805566, 0.0460971861346466, - -1.15566481862127, -0.0540509281351965, 0.110782855652632, 16, - 16, 0.0283659637587177, "contGamma", "debCollin1", "contNormal", - "", "", 0.499946649674671, 0.0420502073221795, - 0.674573695710556, -0.0243380698833921, 0.0588520396739156, - 50, 16, 0.0172569848952618, "contGamma", "debCollin1", "contNormal", - "", "", 0.416131372110597, 0.0212223566895873, - 0.813151204066269, -0.0869450461058388, 0.0367396606905392, - 50, 16, -0.0251026927076498, "contGamma", "debCollin1", "contNormal", - "", "", 0.426277754808023, 0.0315528009116461, - -0.795577317460408, -0.0204602368277774, 0.0355989836855878, - 50, 50, 0.00756937342890517, "contGamma", "debCollin1", "contNormal", - "", "", 0.596606595480347, 0.0143010843453128, - 0.529286678278074, -0.0631275108152892, 0.0260139855994758, - 84, 50, -0.0185567626079067, "contGamma", "debCollin1", "contNormal", - "", "", 0.414489153432761, 0.0227405955206069, - -0.816019201919802, -0.208094805223042, 0.0534832879548465, - 50, 50, -0.0773057586340977, "contGamma", "debCollin1", "contNormal", - "", "", 0.246668183754547, 0.0667303315880248, - -1.15848006138142, -0.0327770998713117, 0.0670642084016534, - 16, 50, 0.0171435542651708, "contGamma", "debCollin1", "contNormal", - "", "", 0.500894421245465, 0.0254701895189148, - 0.673083105739736, -0.0257553471872748, 0.0216171597149908, - 84, 50, -0.00206909373614201, "contGamma", "debCollin1", "contNormal", - "", "", 0.864057789944843, 0.012085045254896, - -0.17121108713298, -0.143621720865794, 0.0370759283592992, 50, - 50, -0.0532728962532472, "contGamma", "debCollin1", "contNormal", - "", "", 0.247818283805566, 0.0460971861346466, - -1.15566481862127, -0.0540509281351965, 0.110782855652632, 84, - 50, 0.0283659637587177, "contGamma", "debCollin1", "contNormal", - "", "", 0.499946649674671, 0.0420502073221795, - 0.674573695710556, -0.0243380698833921, 0.0588520396739156, - 84, 50, 0.0172569848952618, "contGamma", "debCollin1", "contNormal", - "", "", 0.416131372110597, 0.0212223566895873, - 0.813151204066269, -0.0869450461058388, 0.0367396606905392, - 84, 50, -0.0251026927076498, "contGamma", "debCollin1", "contNormal", - "", "", 0.426277754808023, 0.0315528009116461, - -0.795577317460408, -0.0204602368277774, 0.0355989836855878, - 16, 84, 0.00756937342890517, "contGamma", "debCollin1", "contNormal", - "", "", 0.596606595480347, 0.0143010843453128, - 0.529286678278074, -0.0631275108152892, 0.0260139855994758, - 16, 84, -0.0185567626079067, "contGamma", "debCollin1", "contNormal", - "", "", 0.414489153432761, 0.0227405955206069, - -0.816019201919802, -0.208094805223042, 0.0534832879548465, - 50, 84, -0.0773057586340977, "contGamma", "debCollin1", "contNormal", - "", "", 0.246668183754547, 0.0667303315880248, - -1.15848006138142, -0.0327770998713117, 0.0670642084016534, - 16, 84, 0.0171435542651708, "contGamma", "debCollin1", "contNormal", - "", "", 0.500894421245465, 0.0254701895189148, - 0.673083105739736, -0.0257553471872748, 0.0216171597149908, - 84, 84, -0.00206909373614201, "contGamma", "debCollin1", "contNormal", - "", "", 0.864057789944843, 0.012085045254896, - -0.17121108713298, -0.143621720865794, 0.0370759283592992, 16, - 84, -0.0532728962532472, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0532728962532472, "contGamma", "debCollin1", "contNormal", "", "", 0.247818283805566, 0.0460971861346466, -1.15566481862127, -0.0540509281351965, 0.110782855652632, 16, 84, 0.0283659637587177, "contGamma", "debCollin1", "contNormal", @@ -11365,7 +10020,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 50, 84, 0.0172569848952618, "contGamma", "debCollin1", "contNormal", "", "", 0.416131372110597, 0.0212223566895873, 0.813151204066269, -0.0869450461058388, 0.0367396606905392, - 50, 84, -0.0251026927076498, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0251026927076498, "contGamma", "debCollin1", "contNormal", "", "", 0.426277754808023, 0.0315528009116461, -0.795577317460408)) @@ -11424,116 +10079,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.780581209968886, 0.109136350010663, -0.278561698212551, -0.200654285466873, 0.172678971265861, 16, 16, -0.013987657100506, "Total", 0.883236422678532, 0.0952398257512738, -0.146867730911603, - -0.214129678407239, 0.292553517579138, 16, 16, 0.0392119195859496, - "Total", 0.761614794746939, 0.129258292494921, 0.303360959123689, - -0.413463984130964, 0.547537698049384, 50, 16, 0.0670368569592103, - "Total", 0.784512328572413, 0.245157995187821, 0.273443486547733, - -0.349501510723353, 0.202893199298426, 16, 16, -0.0733041557124639, - "Total", 0.60293518409837, 0.140919607293552, -0.520184217940395, - -0.1461231379321, 0.119740955951082, 84, 16, -0.0131910909905092, - "Total", 0.845791580454098, 0.0678237192061396, -0.19449082334186, - -0.275830918784333, 0.320188998568007, 16, 16, 0.0221790398918372, - "Total", 0.884025586366787, 0.152048691214142, 0.145868009219499, - -0.6410949755493, 0.355430582245218, 16, 16, -0.142832196652041, - "Total", 0.574222299076952, 0.254220374878055, -0.561844017107422, - -0.366665512205914, 0.217434586621455, 50, 16, -0.0746154627922297, - "Total", 0.616548144936909, 0.149007865306372, -0.50074848491262, - -0.244304522420746, 0.183502108429367, 50, 16, -0.0304012069956896, - "Total", 0.780581209968886, 0.109136350010663, -0.278561698212551, - -0.200654285466873, 0.172678971265861, 50, 50, -0.013987657100506, - "Total", 0.883236422678532, 0.0952398257512738, -0.146867730911603, - -0.214129678407239, 0.292553517579138, 84, 50, 0.0392119195859496, + -0.214129678407239, 0.292553517579138, 50, 16, 0.0392119195859496, "Total", 0.761614794746939, 0.129258292494921, 0.303360959123689, - -0.413463984130964, 0.547537698049384, 50, 50, 0.0670368569592103, + -0.413463984130964, 0.547537698049384, 84, 16, 0.0670368569592103, "Total", 0.784512328572413, 0.245157995187821, 0.273443486547733, -0.349501510723353, 0.202893199298426, 16, 50, -0.0733041557124639, "Total", 0.60293518409837, 0.140919607293552, -0.520184217940395, - -0.1461231379321, 0.119740955951082, 84, 50, -0.0131910909905092, - "Total", 0.845791580454098, 0.0678237192061396, -0.19449082334186, - -0.275830918784333, 0.320188998568007, 50, 50, 0.0221790398918372, - "Total", 0.884025586366787, 0.152048691214142, 0.145868009219499, - -0.6410949755493, 0.355430582245218, 84, 50, -0.142832196652041, - "Total", 0.574222299076952, 0.254220374878055, -0.561844017107422, - -0.366665512205914, 0.217434586621455, 84, 50, -0.0746154627922297, - "Total", 0.616548144936909, 0.149007865306372, -0.50074848491262, - -0.244304522420746, 0.183502108429367, 84, 50, -0.0304012069956896, - "Total", 0.780581209968886, 0.109136350010663, -0.278561698212551, - -0.200654285466873, 0.172678971265861, 16, 84, -0.013987657100506, - "Total", 0.883236422678532, 0.0952398257512738, -0.146867730911603, - -0.214129678407239, 0.292553517579138, 16, 84, 0.0392119195859496, - "Total", 0.761614794746939, 0.129258292494921, 0.303360959123689, - -0.413463984130964, 0.547537698049384, 50, 84, 0.0670368569592103, - "Total", 0.784512328572413, 0.245157995187821, 0.273443486547733, - -0.349501510723353, 0.202893199298426, 16, 84, -0.0733041557124639, - "Total", 0.60293518409837, 0.140919607293552, -0.520184217940395, - -0.1461231379321, 0.119740955951082, 84, 84, -0.0131910909905092, + -0.1461231379321, 0.119740955951082, 50, 50, -0.0131910909905092, "Total", 0.845791580454098, 0.0678237192061396, -0.19449082334186, - -0.275830918784333, 0.320188998568007, 16, 84, 0.0221790398918372, + -0.275830918784333, 0.320188998568007, 84, 50, 0.0221790398918372, "Total", 0.884025586366787, 0.152048691214142, 0.145868009219499, -0.6410949755493, 0.355430582245218, 16, 84, -0.142832196652041, "Total", 0.574222299076952, 0.254220374878055, -0.561844017107422, -0.366665512205914, 0.217434586621455, 50, 84, -0.0746154627922297, "Total", 0.616548144936909, 0.149007865306372, -0.50074848491262, - -0.244304522420746, 0.183502108429367, 50, 84, -0.0304012069956896, + -0.244304522420746, 0.183502108429367, 84, 84, -0.0304012069956896, "Total", 0.780581209968886, 0.109136350010663, -0.278561698212551, - -0.0204602368277774, 0.0355989836855878, 50, 16, 0.00756937342890517, - "Total indirect", 0.596606595480347, 0.0143010843453128, 0.529286678278074, - -0.0631275108152892, 0.0260139855994758, 84, 16, -0.0185567626079067, - "Total indirect", 0.414489153432761, 0.0227405955206069, -0.816019201919802, - -0.208094805223042, 0.0534832879548465, 50, 16, -0.0773057586340977, - "Total indirect", 0.246668183754547, 0.0667303315880248, -1.15848006138142, - -0.0327770998713117, 0.0670642084016534, 16, 16, 0.0171435542651708, - "Total indirect", 0.500894421245465, 0.0254701895189148, 0.673083105739736, - -0.0257553471872748, 0.0216171597149908, 84, 16, -0.00206909373614201, - "Total indirect", 0.864057789944843, 0.012085045254896, -0.17121108713298, - -0.143621720865794, 0.0370759283592992, 50, 16, -0.0532728962532472, - "Total indirect", 0.247818283805566, 0.0460971861346466, -1.15566481862127, - -0.0540509281351965, 0.110782855652632, 84, 16, 0.0283659637587177, - "Total indirect", 0.499946649674671, 0.0420502073221795, 0.674573695710556, - -0.0243380698833921, 0.0588520396739156, 84, 16, 0.0172569848952618, - "Total indirect", 0.416131372110597, 0.0212223566895873, 0.813151204066269, - -0.0869450461058388, 0.0367396606905392, 84, 16, -0.0251026927076498, - "Total indirect", 0.426277754808023, 0.0315528009116461, -0.795577317460408, - -0.0204602368277774, 0.0355989836855878, 16, 50, 0.00756937342890517, + -0.0204602368277774, 0.0355989836855878, 16, 16, 0.00756937342890517, "Total indirect", 0.596606595480347, 0.0143010843453128, 0.529286678278074, - -0.0631275108152892, 0.0260139855994758, 16, 50, -0.0185567626079067, + -0.0631275108152892, 0.0260139855994758, 50, 16, -0.0185567626079067, "Total indirect", 0.414489153432761, 0.0227405955206069, -0.816019201919802, - -0.208094805223042, 0.0534832879548465, 50, 50, -0.0773057586340977, + -0.208094805223042, 0.0534832879548465, 84, 16, -0.0773057586340977, "Total indirect", 0.246668183754547, 0.0667303315880248, -1.15848006138142, -0.0327770998713117, 0.0670642084016534, 16, 50, 0.0171435542651708, "Total indirect", 0.500894421245465, 0.0254701895189148, 0.673083105739736, - -0.0257553471872748, 0.0216171597149908, 84, 50, -0.00206909373614201, - "Total indirect", 0.864057789944843, 0.012085045254896, -0.17121108713298, - -0.143621720865794, 0.0370759283592992, 16, 50, -0.0532728962532472, - "Total indirect", 0.247818283805566, 0.0460971861346466, -1.15566481862127, - -0.0540509281351965, 0.110782855652632, 16, 50, 0.0283659637587177, - "Total indirect", 0.499946649674671, 0.0420502073221795, 0.674573695710556, - -0.0243380698833921, 0.0588520396739156, 50, 50, 0.0172569848952618, - "Total indirect", 0.416131372110597, 0.0212223566895873, 0.813151204066269, - -0.0869450461058388, 0.0367396606905392, 50, 50, -0.0251026927076498, - "Total indirect", 0.426277754808023, 0.0315528009116461, -0.795577317460408, - -0.0204602368277774, 0.0355989836855878, 50, 84, 0.00756937342890517, - "Total indirect", 0.596606595480347, 0.0143010843453128, 0.529286678278074, - -0.0631275108152892, 0.0260139855994758, 84, 84, -0.0185567626079067, - "Total indirect", 0.414489153432761, 0.0227405955206069, -0.816019201919802, - -0.208094805223042, 0.0534832879548465, 50, 84, -0.0773057586340977, - "Total indirect", 0.246668183754547, 0.0667303315880248, -1.15848006138142, - -0.0327770998713117, 0.0670642084016534, 16, 84, 0.0171435542651708, - "Total indirect", 0.500894421245465, 0.0254701895189148, 0.673083105739736, - -0.0257553471872748, 0.0216171597149908, 84, 84, -0.00206909373614201, + -0.0257553471872748, 0.0216171597149908, 50, 50, -0.00206909373614201, "Total indirect", 0.864057789944843, 0.012085045254896, -0.17121108713298, - -0.143621720865794, 0.0370759283592992, 50, 84, -0.0532728962532472, + -0.143621720865794, 0.0370759283592992, 84, 50, -0.0532728962532472, "Total indirect", 0.247818283805566, 0.0460971861346466, -1.15566481862127, - -0.0540509281351965, 0.110782855652632, 84, 84, 0.0283659637587177, + -0.0540509281351965, 0.110782855652632, 16, 84, 0.0283659637587177, "Total indirect", 0.499946649674671, 0.0420502073221795, 0.674573695710556, - -0.0243380698833921, 0.0588520396739156, 84, 84, 0.0172569848952618, + -0.0243380698833921, 0.0588520396739156, 50, 84, 0.0172569848952618, "Total indirect", 0.416131372110597, 0.0212223566895873, 0.813151204066269, -0.0869450461058388, 0.0367396606905392, 84, 84, -0.0251026927076498, - "Total indirect", 0.426277754808023, 0.0315528009116461, -0.795577317460408, - 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 84, 50, - 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, - 16, 84, 50, 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, - 50, 84, 50, 16, 84, 50, 84, 84, 84)) + "Total indirect", 0.426277754808023, 0.0315528009116461, -0.795577317460408 + )) @@ -11549,7 +10129,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 67 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -11560,29 +10140,29 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -11629,56 +10209,39 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.175783429967622, 1.32274377991243, 16, 0.573480174972406, 0, - "facGenderm", "contNormal", "", "", "", 0.133578077654009, + "m", "facGender", "contNormal", "", "", "", 0.133578077654009, 0.38228437402428, 1.50014024621363, -0.362716053006733, 1.00606619818958, - 16, 0.321675072591423, 1, "facGenderm", "contNormal", "", "", - "", 0.356938046357823, 0.34918556207999, 0.921215272118653, + 16, 0.321675072591423, 1, "m", "facGender", "contNormal", "", + "", "", 0.356938046357823, 0.34918556207999, 0.921215272118653, 0.0235481261364956, 1.18422554838696, 50, 0.603886837261728, - 0, "facGenderm", "contNormal", "", "", "", 0.041400898483293, + 0, "m", "facGender", "contNormal", "", "", "", 0.041400898483293, 0.296096619990403, 2.03949250511978, -0.236088085491443, 0.940251555252934, - 50, 0.352081734880746, 1, "facGenderm", "contNormal", "", "", - "", 0.240697421752677, 0.300092157310847, 1.17324537247418, + 50, 0.352081734880746, 1, "m", "facGender", "contNormal", "", + "", "", 0.240697421752677, 0.300092157310847, 1.17324537247418, -0.0534551058212815, 1.33251133106703, 84, 0.639528112622876, - 0, "facGenderm", "contNormal", "", "", "", 0.0704856636370439, + 0, "m", "facGender", "contNormal", "", "", "", 0.0704856636370439, 0.353569363473166, 1.80877694362626, -0.392737323200112, 1.1681833436839, - 84, 0.387723010241893, 1, "facGenderm", "contNormal", "", "", - "", 0.330212575161192, 0.398201364718014, 0.973685789641779, + 84, 0.387723010241893, 1, "m", "facGender", "contNormal", "", + "", "", 0.330212575161192, 0.398201364718014, 0.973685789641779, -0.0352516329244926, 0.0298167103814208, 16, -0.00271746127153589, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.869960485896639, 0.0165993721872351, -0.163708677706836, -0.0728976436985679, - 0.0865997813174653, 16, 0.0068510688094487, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.866286709435109, - 0.0406888662940055, 0.168376989418799, -0.0196782118438645, - 0.0180473378147309, 16, -0.000815437014566771, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.932476708201224, - 0.00962404155284734, -0.0847291660254229, -0.0633243155084779, - 0.0635070764560316, 16, 9.13804737768101e-05, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746569244602, - 0.0323555414703891, 0.00282426037779151, -0.0235097125923341, - 0.0263377673098801, 50, 0.001414027358773, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.911460207369007, - 0.0127164275199455, 0.111196903104675, -0.0865963827886001, - 0.0709323591706658, 50, -0.00783201180896713, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.845478339223415, - 0.0401866420000144, -0.194890924426189, -0.0352516329244926, - 0.0298167103814208, 50, -0.00271746127153589, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.869960485896639, - 0.0165993721872351, -0.163708677706836, -0.0728976436985679, - 0.0865997813174653, 50, 0.0068510688094487, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.866286709435109, - 0.0406888662940055, 0.168376989418799, -0.0196782118438645, - 0.0180473378147309, 84, -0.000815437014566771, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.932476708201224, - 0.00962404155284734, -0.0847291660254229, -0.0633243155084779, - 0.0635070764560316, 84, 9.13804737768101e-05, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746569244602, - 0.0323555414703891, 0.00282426037779151, -0.0235097125923341, - 0.0263377673098801, 84, 0.001414027358773, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.911460207369007, - 0.0127164275199455, 0.111196903104675, -0.0865963827886001, - 0.0709323591706658, 84, -0.00783201180896713, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.845478339223415, - 0.0401866420000144, -0.194890924426189)) + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.869960485896639, 0.0165993721872351, -0.163708677706836, + -0.0728976436985679, 0.0865997813174653, 16, 0.0068510688094487, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.866286709435109, 0.0406888662940055, 0.168376989418799, + -0.0196782118438645, 0.0180473378147309, 50, -0.000815437014566771, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.932476708201224, 0.00962404155284734, -0.0847291660254229, + -0.0633243155084779, 0.0635070764560316, 50, 9.13804737768101e-05, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.997746569244602, 0.0323555414703891, 0.00282426037779151, + -0.0235097125923341, 0.0263377673098801, 84, 0.001414027358773, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.911460207369007, 0.0127164275199455, 0.111196903104675, + -0.0865963827886001, 0.0709323591706658, 84, -0.00783201180896713, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.845478339223415, 0.0401866420000144, -0.194890924426189 + )) @@ -11717,70 +10280,43 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.180104376639895, 1.32162980404163, 16, 0.57076271370087, 0, - "Total", 0.136265422341246, 0.383102493853718, 1.48984337835923, + "m", "Total", 0.136265422341246, 0.383102493853718, 1.48984337835923, -0.35569915831231, 1.01275144111405, 16, 0.328526141400872, - 1, "Total", 0.346672356522605, 0.34910095548197, 0.941063426616256, + 1, "m", "Total", 0.346672356522605, 0.34910095548197, 0.941063426616256, 0.0228811969274294, 1.18326160356689, 50, 0.603071400247162, - 0, "Total", 0.0416240059222333, 0.296020849309578, 2.03725988103112, + 0, "m", "Total", 0.0416240059222333, 0.296020849309578, 2.03725988103112, -0.233269567660012, 0.937615798369057, 50, 0.352173115354522, - 1, "Total", 0.238391578912738, 0.29870073513209, 1.17901656719655, + 1, "m", "Total", 0.238391578912738, 0.29870073513209, 1.17901656719655, -0.052547206421394, 1.33443148638469, 84, 0.640942139981649, - 0, "Total", 0.0700707239268883, 0.353827596768716, 1.81145322138513, + 0, "m", "Total", 0.0700707239268883, 0.353827596768716, 1.81145322138513, -0.393013086743393, 1.15279508360925, 84, 0.379890998432926, - 1, "Total", 0.335374814116495, 0.394346065168997, 0.963344209533633, + 1, "m", "Total", 0.335374814116495, 0.394346065168997, 0.963344209533633, -0.180104376639895, 1.32162980404163, 16, 0.57076271370087, - 0, "Total", 0.136265422341246, 0.383102493853718, 1.48984337835923, + 0, "m", "Total", 0.136265422341246, 0.383102493853718, 1.48984337835923, -0.35569915831231, 1.01275144111405, 16, 0.328526141400872, - 0, "Total", 0.346672356522605, 0.34910095548197, 0.941063426616256, - 0.0228811969274294, 1.18326160356689, 16, 0.603071400247162, - 1, "Total", 0.0416240059222333, 0.296020849309578, 2.03725988103112, - -0.233269567660012, 0.937615798369057, 16, 0.352173115354522, - 0, "Total", 0.238391578912738, 0.29870073513209, 1.17901656719655, - -0.052547206421394, 1.33443148638469, 50, 0.640942139981649, - 0, "Total", 0.0700707239268883, 0.353827596768716, 1.81145322138513, - -0.393013086743393, 1.15279508360925, 50, 0.379890998432926, - 1, "Total", 0.335374814116495, 0.394346065168997, 0.963344209533633, - -0.180104376639895, 1.32162980404163, 50, 0.57076271370087, - 1, "Total", 0.136265422341246, 0.383102493853718, 1.48984337835923, - -0.35569915831231, 1.01275144111405, 50, 0.328526141400872, - 1, "Total", 0.346672356522605, 0.34910095548197, 0.941063426616256, - 0.0228811969274294, 1.18326160356689, 84, 0.603071400247162, - 0, "Total", 0.0416240059222333, 0.296020849309578, 2.03725988103112, - -0.233269567660012, 0.937615798369057, 84, 0.352173115354522, - 0, "Total", 0.238391578912738, 0.29870073513209, 1.17901656719655, + 1, "m", "Total", 0.346672356522605, 0.34910095548197, 0.941063426616256, + 0.0228811969274294, 1.18326160356689, 50, 0.603071400247162, + 0, "m", "Total", 0.0416240059222333, 0.296020849309578, 2.03725988103112, + -0.233269567660012, 0.937615798369057, 50, 0.352173115354522, + 1, "m", "Total", 0.238391578912738, 0.29870073513209, 1.17901656719655, -0.052547206421394, 1.33443148638469, 84, 0.640942139981649, - 1, "Total", 0.0700707239268883, 0.353827596768716, 1.81145322138513, + 0, "m", "Total", 0.0700707239268883, 0.353827596768716, 1.81145322138513, -0.393013086743393, 1.15279508360925, 84, 0.379890998432926, - 0, "Total", 0.335374814116495, 0.394346065168997, 0.963344209533633, + 1, "m", "Total", 0.335374814116495, 0.394346065168997, 0.963344209533633, -0.0352516329244926, 0.0298167103814208, 16, -0.00271746127153589, - 0, "Total indirect", 0.869960485896639, 0.0165993721872351, + 0, "m", "Total indirect", 0.869960485896639, 0.0165993721872351, -0.163708677706836, -0.0728976436985679, 0.0865997813174653, - 16, 0.0068510688094487, 1, "Total indirect", 0.866286709435109, + 16, 0.0068510688094487, 1, "m", "Total indirect", 0.866286709435109, 0.0406888662940055, 0.168376989418799, -0.0196782118438645, - 0.0180473378147309, 16, -0.000815437014566771, 1, "Total indirect", - 0.932476708201224, 0.00962404155284734, -0.0847291660254229, - -0.0633243155084779, 0.0635070764560316, 16, 9.13804737768101e-05, - 1, "Total indirect", 0.997746569244602, 0.0323555414703891, - 0.00282426037779151, -0.0235097125923341, 0.0263377673098801, - 50, 0.001414027358773, 0, "Total indirect", 0.911460207369007, - 0.0127164275199455, 0.111196903104675, -0.0865963827886001, - 0.0709323591706658, 50, -0.00783201180896713, 0, "Total indirect", - 0.845478339223415, 0.0401866420000144, -0.194890924426189, -0.0352516329244926, - 0.0298167103814208, 50, -0.00271746127153589, 1, "Total indirect", - 0.869960485896639, 0.0165993721872351, -0.163708677706836, -0.0728976436985679, - 0.0865997813174653, 50, 0.0068510688094487, 0, "Total indirect", - 0.866286709435109, 0.0406888662940055, 0.168376989418799, -0.0196782118438645, - 0.0180473378147309, 84, -0.000815437014566771, 0, "Total indirect", + 0.0180473378147309, 50, -0.000815437014566771, 0, "m", "Total indirect", 0.932476708201224, 0.00962404155284734, -0.0847291660254229, - -0.0633243155084779, 0.0635070764560316, 84, 9.13804737768101e-05, - 1, "Total indirect", 0.997746569244602, 0.0323555414703891, + -0.0633243155084779, 0.0635070764560316, 50, 9.13804737768101e-05, + 1, "m", "Total indirect", 0.997746569244602, 0.0323555414703891, 0.00282426037779151, -0.0235097125923341, 0.0263377673098801, - 84, 0.001414027358773, 1, "Total indirect", 0.911460207369007, + 84, 0.001414027358773, 0, "m", "Total indirect", 0.911460207369007, 0.0127164275199455, 0.111196903104675, -0.0865963827886001, - 0.0709323591706658, 84, -0.00783201180896713, 1, "Total indirect", - 0.845478339223415, 0.0401866420000144, -0.194890924426189, 0, - 0, 1, 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, - 1, 1, 1)) + 0.0709323591706658, 84, -0.00783201180896713, 1, "m", "Total indirect", + 0.845478339223415, 0.0401866420000144, -0.194890924426189)) @@ -11796,7 +10332,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 68 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -11807,25 +10343,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -11873,72 +10409,18 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.0572297247254793, 16, 16, 0.0156862988746817, "contGamma", "debCollin1", "contNormal", "", "", 0.459264273264167, 0.0211960149158285, 0.740058871300739, -0.0190157271601051, - 0.0213531073835556, 16, 16, 0.00116869011172527, "contGamma", + 0.0213531073835556, 50, 16, 0.00116869011172527, "contGamma", "debCollin1", "contNormal", "", "", 0.909647549600649, 0.0102983613122703, 0.11348311408853, -0.0957997958678833, 0.0644866150865313, - 50, 16, -0.015656590390676, "contGamma", "debCollin1", "contNormal", - "", "", 0.70179835318219, 0.0408901419155488, - -0.382894009588225, -0.0473587614025879, 0.0504004702871598, - 16, 50, 0.00152085444228595, "contGamma", "debCollin1", "contNormal", - "", "", 0.951372840441777, 0.0249390377733622, - 0.0609828837867355, -0.0135249104203352, 0.0151862549340702, - 84, 50, 0.000830672256867517, "contGamma", "debCollin1", "contNormal", - "", "", 0.909704348167413, 0.00732441146390328, - 0.11341146806966, -0.0823003405183491, 0.0402875765052841, 16, - 50, -0.0210063820065325, "contGamma", "debCollin1", "contNormal", - "", "", 0.501768465788776, 0.0312730024609103, - -0.671709792904902, -0.119454009490891, 0.0892875680810227, - 16, 84, -0.015083220704934, "contGamma", "debCollin1", "contNormal", - "", "", 0.776988555658382, 0.0532513809484359, - -0.283245625489775, -0.00813481790160179, 0.00900374479795171, - 16, 84, 0.000434463448174957, "contGamma", "debCollin1", "contNormal", - "", "", 0.920844202735654, 0.00437216266082956, - 0.0993703761452744, -0.0894053536290372, 0.0348510357754866, - 50, 84, -0.0272771589267753, "contGamma", "debCollin1", "contNormal", - "", "", 0.389505168623458, 0.031698640991529, - -0.860515090664761, -0.0258571269761159, 0.0572297247254793, - 16, 16, 0.0156862988746817, "contGamma", "debCollin1", "contNormal", - "", "", 0.459264273264167, 0.0211960149158285, - 0.740058871300739, -0.0190157271601051, 0.0213531073835556, - 84, 16, 0.00116869011172527, "contGamma", "debCollin1", "contNormal", - "", "", 0.909647549600649, 0.0102983613122703, - 0.11348311408853, -0.0957997958678833, 0.0644866150865313, 16, - 16, -0.015656590390676, "contGamma", "debCollin1", "contNormal", + 84, 16, -0.015656590390676, "contGamma", "debCollin1", "contNormal", "", "", 0.70179835318219, 0.0408901419155488, -0.382894009588225, -0.0473587614025879, 0.0504004702871598, 16, 50, 0.00152085444228595, "contGamma", "debCollin1", "contNormal", "", "", 0.951372840441777, 0.0249390377733622, 0.0609828837867355, -0.0135249104203352, 0.0151862549340702, - 16, 50, 0.000830672256867517, "contGamma", "debCollin1", "contNormal", + 50, 50, 0.000830672256867517, "contGamma", "debCollin1", "contNormal", "", "", 0.909704348167413, 0.00732441146390328, - 0.11341146806966, -0.0823003405183491, 0.0402875765052841, 50, - 50, -0.0210063820065325, "contGamma", "debCollin1", "contNormal", - "", "", 0.501768465788776, 0.0312730024609103, - -0.671709792904902, -0.119454009490891, 0.0892875680810227, - 16, 84, -0.015083220704934, "contGamma", "debCollin1", "contNormal", - "", "", 0.776988555658382, 0.0532513809484359, - -0.283245625489775, -0.00813481790160179, 0.00900374479795171, - 84, 84, 0.000434463448174957, "contGamma", "debCollin1", "contNormal", - "", "", 0.920844202735654, 0.00437216266082956, - 0.0993703761452744, -0.0894053536290372, 0.0348510357754866, - 16, 84, -0.0272771589267753, "contGamma", "debCollin1", "contNormal", - "", "", 0.389505168623458, 0.031698640991529, - -0.860515090664761, -0.0258571269761159, 0.0572297247254793, - 16, 16, 0.0156862988746817, "contGamma", "debCollin1", "contNormal", - "", "", 0.459264273264167, 0.0211960149158285, - 0.740058871300739, -0.0190157271601051, 0.0213531073835556, - 50, 16, 0.00116869011172527, "contGamma", "debCollin1", "contNormal", - "", "", 0.909647549600649, 0.0102983613122703, - 0.11348311408853, -0.0957997958678833, 0.0644866150865313, 50, - 16, -0.015656590390676, "contGamma", "debCollin1", "contNormal", - "", "", 0.70179835318219, 0.0408901419155488, - -0.382894009588225, -0.0473587614025879, 0.0504004702871598, - 50, 50, 0.00152085444228595, "contGamma", "debCollin1", "contNormal", - "", "", 0.951372840441777, 0.0249390377733622, - 0.0609828837867355, -0.0135249104203352, 0.0151862549340702, - 84, 50, 0.000830672256867517, "contGamma", "debCollin1", "contNormal", - "", "", 0.909704348167413, 0.00732441146390328, - 0.11341146806966, -0.0823003405183491, 0.0402875765052841, 50, + 0.11341146806966, -0.0823003405183491, 0.0402875765052841, 84, 50, -0.0210063820065325, "contGamma", "debCollin1", "contNormal", "", "", 0.501768465788776, 0.0312730024609103, -0.671709792904902, -0.119454009490891, 0.0892875680810227, @@ -11948,7 +10430,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 50, 84, 0.000434463448174957, "contGamma", "debCollin1", "contNormal", "", "", 0.920844202735654, 0.00437216266082956, 0.0993703761452744, -0.0894053536290372, 0.0348510357754866, - 50, 84, -0.0272771589267753, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0272771589267753, "contGamma", "debCollin1", "contNormal", "", "", 0.389505168623458, 0.031698640991529, -0.860515090664761)) @@ -11989,117 +10471,42 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.142891922331902, 0.13770521927689, 16, 16, -0.00259335152750616, - "Total", 0.971099770057003, 0.0715822188116991, -0.0362289905308484, - -0.151092574983456, 0.116870654402531, 16, 16, -0.0171109602904626, - "Total", 0.802348039610881, 0.0683592227968595, -0.250309462138131, - -0.187195699482598, 0.119323217896871, 50, 16, -0.0339362407928638, - "Total", 0.664292209554505, 0.0781950382244907, -0.433994810456337, - -0.16103773216229, 0.127520140242487, 16, 50, -0.0167587959599019, - "Total", 0.819910065288812, 0.0736130548012323, -0.227660650752145, - -0.151687058599366, 0.116789102308726, 84, 50, -0.0174489781453203, - "Total", 0.798903434622111, 0.0684900750793887, -0.254766520917005, - -0.181904344951175, 0.103332280133734, 16, 50, -0.0392860324087203, - "Total", 0.58926802083061, 0.0727657822630463, -0.539897066820534, - -0.206194061195661, 0.139468318981417, 16, 84, -0.0333628711071218, - "Total", 0.705173421344888, 0.0881807989594756, -0.378346210295215, - -0.152766759699305, 0.117076385791279, 16, 84, -0.0178451869540129, - "Total", 0.795456616426251, 0.0688388020440867, -0.259231515135667, - -0.186544002375317, 0.0954303837173904, 50, 84, -0.0455568093289631, - "Total", 0.52652610108744, 0.0719335631462836, -0.633317846862655, - -0.142891922331902, 0.13770521927689, 16, 16, -0.00259335152750616, - "Total", 0.971099770057003, 0.0715822188116991, -0.0362289905308484, - -0.151092574983456, 0.116870654402531, 84, 16, -0.0171109602904626, - "Total", 0.802348039610881, 0.0683592227968595, -0.250309462138131, - -0.187195699482598, 0.119323217896871, 16, 16, -0.0339362407928638, - "Total", 0.664292209554505, 0.0781950382244907, -0.433994810456337, - -0.16103773216229, 0.127520140242487, 16, 50, -0.0167587959599019, - "Total", 0.819910065288812, 0.0736130548012323, -0.227660650752145, - -0.151687058599366, 0.116789102308726, 16, 50, -0.0174489781453203, - "Total", 0.798903434622111, 0.0684900750793887, -0.254766520917005, - -0.181904344951175, 0.103332280133734, 50, 50, -0.0392860324087203, - "Total", 0.58926802083061, 0.0727657822630463, -0.539897066820534, - -0.206194061195661, 0.139468318981417, 16, 84, -0.0333628711071218, - "Total", 0.705173421344888, 0.0881807989594756, -0.378346210295215, - -0.152766759699305, 0.117076385791279, 84, 84, -0.0178451869540129, - "Total", 0.795456616426251, 0.0688388020440867, -0.259231515135667, - -0.186544002375317, 0.0954303837173904, 16, 84, -0.0455568093289631, - "Total", 0.52652610108744, 0.0719335631462836, -0.633317846862655, - -0.142891922331902, 0.13770521927689, 16, 16, -0.00259335152750616, "Total", 0.971099770057003, 0.0715822188116991, -0.0362289905308484, -0.151092574983456, 0.116870654402531, 50, 16, -0.0171109602904626, "Total", 0.802348039610881, 0.0683592227968595, -0.250309462138131, - -0.187195699482598, 0.119323217896871, 50, 16, -0.0339362407928638, + -0.187195699482598, 0.119323217896871, 84, 16, -0.0339362407928638, "Total", 0.664292209554505, 0.0781950382244907, -0.433994810456337, - -0.16103773216229, 0.127520140242487, 50, 50, -0.0167587959599019, + -0.16103773216229, 0.127520140242487, 16, 50, -0.0167587959599019, "Total", 0.819910065288812, 0.0736130548012323, -0.227660650752145, - -0.151687058599366, 0.116789102308726, 84, 50, -0.0174489781453203, + -0.151687058599366, 0.116789102308726, 50, 50, -0.0174489781453203, "Total", 0.798903434622111, 0.0684900750793887, -0.254766520917005, - -0.181904344951175, 0.103332280133734, 50, 50, -0.0392860324087203, + -0.181904344951175, 0.103332280133734, 84, 50, -0.0392860324087203, "Total", 0.58926802083061, 0.0727657822630463, -0.539897066820534, -0.206194061195661, 0.139468318981417, 16, 84, -0.0333628711071218, "Total", 0.705173421344888, 0.0881807989594756, -0.378346210295215, -0.152766759699305, 0.117076385791279, 50, 84, -0.0178451869540129, "Total", 0.795456616426251, 0.0688388020440867, -0.259231515135667, - -0.186544002375317, 0.0954303837173904, 50, 84, -0.0455568093289631, + -0.186544002375317, 0.0954303837173904, 84, 84, -0.0455568093289631, "Total", 0.52652610108744, 0.0719335631462836, -0.633317846862655, - -0.0258571269761159, 0.0572297247254793, 50, 16, 0.0156862988746817, - "Total indirect", 0.459264273264167, 0.0211960149158285, 0.740058871300739, - -0.0190157271601051, 0.0213531073835556, 84, 16, 0.00116869011172527, - "Total indirect", 0.909647549600649, 0.0102983613122703, 0.11348311408853, - -0.0957997958678833, 0.0644866150865313, 50, 16, -0.015656590390676, - "Total indirect", 0.70179835318219, 0.0408901419155488, -0.382894009588225, - -0.0473587614025879, 0.0504004702871598, 16, 50, 0.00152085444228595, - "Total indirect", 0.951372840441777, 0.0249390377733622, 0.0609828837867355, - -0.0135249104203352, 0.0151862549340702, 50, 50, 0.000830672256867517, - "Total indirect", 0.909704348167413, 0.00732441146390328, 0.11341146806966, - -0.0823003405183491, 0.0402875765052841, 50, 50, -0.0210063820065325, - "Total indirect", 0.501768465788776, 0.0312730024609103, -0.671709792904902, - -0.119454009490891, 0.0892875680810227, 50, 84, -0.015083220704934, - "Total indirect", 0.776988555658382, 0.0532513809484359, -0.283245625489775, - -0.00813481790160179, 0.00900374479795171, 84, 84, 0.000434463448174957, - "Total indirect", 0.920844202735654, 0.00437216266082956, 0.0993703761452744, - -0.0894053536290372, 0.0348510357754866, 50, 84, -0.0272771589267753, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, + "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, + "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, + "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, - -0.0258571269761159, 0.0572297247254793, 16, 16, 0.0156862988746817, - "Total indirect", 0.459264273264167, 0.0211960149158285, 0.740058871300739, - -0.0190157271601051, 0.0213531073835556, 84, 16, 0.00116869011172527, - "Total indirect", 0.909647549600649, 0.0102983613122703, 0.11348311408853, - -0.0957997958678833, 0.0644866150865313, 50, 16, -0.015656590390676, - "Total indirect", 0.70179835318219, 0.0408901419155488, -0.382894009588225, - -0.0473587614025879, 0.0504004702871598, 84, 50, 0.00152085444228595, - "Total indirect", 0.951372840441777, 0.0249390377733622, 0.0609828837867355, - -0.0135249104203352, 0.0151862549340702, 84, 50, 0.000830672256867517, - "Total indirect", 0.909704348167413, 0.00732441146390328, 0.11341146806966, - -0.0823003405183491, 0.0402875765052841, 84, 50, -0.0210063820065325, - "Total indirect", 0.501768465788776, 0.0312730024609103, -0.671709792904902, - -0.119454009490891, 0.0892875680810227, 16, 84, -0.015083220704934, - "Total indirect", 0.776988555658382, 0.0532513809484359, -0.283245625489775, - -0.00813481790160179, 0.00900374479795171, 84, 84, 0.000434463448174957, - "Total indirect", 0.920844202735654, 0.00437216266082956, 0.0993703761452744, - -0.0894053536290372, 0.0348510357754866, 50, 84, -0.0272771589267753, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, - -0.0258571269761159, 0.0572297247254793, 84, 16, 0.0156862988746817, - "Total indirect", 0.459264273264167, 0.0211960149158285, 0.740058871300739, - -0.0190157271601051, 0.0213531073835556, 84, 16, 0.00116869011172527, - "Total indirect", 0.909647549600649, 0.0102983613122703, 0.11348311408853, - -0.0957997958678833, 0.0644866150865313, 84, 16, -0.015656590390676, - "Total indirect", 0.70179835318219, 0.0408901419155488, -0.382894009588225, - -0.0473587614025879, 0.0504004702871598, 16, 50, 0.00152085444228595, - "Total indirect", 0.951372840441777, 0.0249390377733622, 0.0609828837867355, - -0.0135249104203352, 0.0151862549340702, 84, 50, 0.000830672256867517, - "Total indirect", 0.909704348167413, 0.00732441146390328, 0.11341146806966, - -0.0823003405183491, 0.0402875765052841, 50, 50, -0.0210063820065325, - "Total indirect", 0.501768465788776, 0.0312730024609103, -0.671709792904902, - -0.119454009490891, 0.0892875680810227, 84, 84, -0.015083220704934, - "Total indirect", 0.776988555658382, 0.0532513809484359, -0.283245625489775, - -0.00813481790160179, 0.00900374479795171, 84, 84, 0.000434463448174957, - "Total indirect", 0.920844202735654, 0.00437216266082956, 0.0993703761452744, - -0.0894053536290372, 0.0348510357754866, 84, 84, -0.0272771589267753, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, - 16, 16, 50, 16, 84, 16, 16, 16, 50, 16, 84, 16, 16, 16, 50, - 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 50, 50, 50, 84, 50, - 16, 50, 50, 50, 84, 50, 16, 84, 50, 84, 84, 84, 16, 84, 50, - 84, 84, 84, 16, 84, 50, 84, 84, 84)) + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, + "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, + "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761, + -0.0894053536290372, 0.0348510357754866, -0.0272771589267753, + "Total indirect", 0.389505168623458, 0.031698640991529, -0.860515090664761 + )) @@ -12115,7 +10522,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 68 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -12126,25 +10533,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -12188,43 +10595,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0581216477992607, 0.876434140289695, "", 0.467277894044478, - "", "facGenderm", "contNormal", "", "", "", 0.0251961761161286, + "", "m", "facGender", "contNormal", "", "", "", 0.0251961761161286, 0.208757022819087, 2.23838167326917, -0.0108831762516817, 0.0104431001662529, - 16, -0.00022003804271438, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.967738652775068, 0.00544047660726258, - -0.0404446261970226, -0.0248218258367533, 0.027211992737034, - 16, 0.00119508345014035, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.928262819854489, 0.0132741772257611, - 0.0900306986877546, -0.017221137210671, 0.0161430852765094, - 50, -0.000539025967080797, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.949504043286334, 0.00851143764639378, - -0.0633296029971126, -0.0529253954032223, 0.0477190440472555, - 50, -0.00260317567798344, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.919241494080271, 0.0256750736861362, - -0.101389219357492, -0.028625571608521, 0.0267997140559034, - 84, -0.000912928776308784, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.948519182046454, 0.0141393632999412, - -0.0645664699988703, -0.142080163718872, 0.127969526967136, - 84, -0.00705531837586812, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.918429627066259, 0.0688914931131708, - -0.102412040399212, -0.0108831762516817, 0.0104431001662529, - 16, -0.00022003804271438, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.967738652775068, 0.00544047660726258, + 16, -0.00022003804271438, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.967738652775068, 0.00544047660726258, -0.0404446261970226, -0.0248218258367533, 0.027211992737034, - 16, 0.00119508345014035, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.928262819854489, 0.0132741772257611, + 16, 0.00119508345014035, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.928262819854489, 0.0132741772257611, 0.0900306986877546, -0.017221137210671, 0.0161430852765094, - 50, -0.000539025967080797, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.949504043286334, 0.00851143764639378, + 50, -0.000539025967080797, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.949504043286334, 0.00851143764639378, -0.0633296029971126, -0.0529253954032223, 0.0477190440472555, - 50, -0.00260317567798344, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.919241494080271, 0.0256750736861362, + 50, -0.00260317567798344, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.919241494080271, 0.0256750736861362, -0.101389219357492, -0.028625571608521, 0.0267997140559034, - 84, -0.000912928776308784, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.948519182046454, 0.0141393632999412, + 84, -0.000912928776308784, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.948519182046454, 0.0141393632999412, -0.0645664699988703, -0.142080163718872, 0.127969526967136, - 84, -0.00705531837586812, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.918429627066259, 0.0688914931131708, + 84, -0.00705531837586812, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.918429627066259, 0.0688914931131708, -0.102412040399212)) @@ -12264,59 +10653,34 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0579001859917599, 0.876215526011767, 16, 0.467057856001763, - 0, "Total", 0.0252654428384138, 0.208757749243041, 2.23731984894129, - 0.056741404104764, 0.880204550884472, 16, 0.468472977494618, - 0, "Total", 0.025742806771504, 0.210070989384264, 2.23006983909464, - 0.0575794317186985, 0.875898304436096, 50, 0.466738868077397, - 1, "Total", 0.025366043578402, 0.208758650457915, 2.23578216784598, - 0.0562501221439309, 0.873099314589058, 50, 0.464674718366494, - 0, "Total", 0.0257541302971214, 0.20838372513177, 2.22989927871123, - 0.056840959560106, 0.875888970976232, 84, 0.466364965268169, - 0, "Total", 0.0256148088341648, 0.208944658645943, 2.23200233157635, - 0.0393235293813693, 0.88112162195585, 84, 0.46022257566861, - 0, "Total", 0.0321068000388056, 0.214748357422503, 2.14307844396292, - 0.0579001859917599, 0.876215526011767, 16, 0.467057856001763, - 1, "Total", 0.0252654428384138, 0.208757749243041, 2.23731984894129, + list(0.0579001859917599, 0.876215526011767, "", 0.467057856001763, + "", "m", "Total", 0.0252654428384138, 0.208757749243041, 2.23731984894129, 0.056741404104764, 0.880204550884472, 16, 0.468472977494618, - 0, "Total", 0.025742806771504, 0.210070989384264, 2.23006983909464, - 0.0575794317186985, 0.875898304436096, 50, 0.466738868077397, - 0, "Total", 0.025366043578402, 0.208758650457915, 2.23578216784598, + 0, "m", "Total", 0.025742806771504, 0.210070989384264, 2.23006983909464, + 0.0575794317186985, 0.875898304436096, 16, 0.466738868077397, + 1, "m", "Total", 0.025366043578402, 0.208758650457915, 2.23578216784598, 0.0562501221439309, 0.873099314589058, 50, 0.464674718366494, - 0, "Total", 0.0257541302971214, 0.20838372513177, 2.22989927871123, - 0.056840959560106, 0.875888970976232, 84, 0.466364965268169, - 1, "Total", 0.0256148088341648, 0.208944658645943, 2.23200233157635, + 0, "m", "Total", 0.0257541302971214, 0.20838372513177, 2.22989927871123, + 0.056840959560106, 0.875888970976232, 50, 0.466364965268169, + 1, "m", "Total", 0.0256148088341648, 0.208944658645943, 2.23200233157635, 0.0393235293813693, 0.88112162195585, 84, 0.46022257566861, - 0, "Total", 0.0321068000388056, 0.214748357422503, 2.14307844396292, + 0, "m", "Total", 0.0321068000388056, 0.214748357422503, 2.14307844396292, + 0.0579001859917599, 0.876215526011767, 84, 0.467057856001763, + 1, "m", "Total", 0.0252654428384138, 0.208757749243041, 2.23731984894129, -0.0108831762516817, 0.0104431001662529, 16, -0.00022003804271438, - 0, "Total indirect", 0.967738652775068, 0.00544047660726258, + 0, "m", "Total indirect", 0.967738652775068, 0.00544047660726258, -0.0404446261970226, -0.0248218258367533, 0.027211992737034, - 16, 0.00119508345014035, 1, "Total indirect", 0.928262819854489, + 16, 0.00119508345014035, 1, "m", "Total indirect", 0.928262819854489, 0.0132741772257611, 0.0900306986877546, -0.017221137210671, - 0.0161430852765094, 50, -0.000539025967080797, 1, "Total indirect", + 0.0161430852765094, 50, -0.000539025967080797, 0, "m", "Total indirect", 0.949504043286334, 0.00851143764639378, -0.0633296029971126, -0.0529253954032223, 0.0477190440472555, 50, -0.00260317567798344, - 1, "Total indirect", 0.919241494080271, 0.0256750736861362, + 1, "m", "Total indirect", 0.919241494080271, 0.0256750736861362, -0.101389219357492, -0.028625571608521, 0.0267997140559034, - 84, -0.000912928776308784, 0, "Total indirect", 0.948519182046454, + 84, -0.000912928776308784, 0, "m", "Total indirect", 0.948519182046454, 0.0141393632999412, -0.0645664699988703, -0.142080163718872, - 0.127969526967136, 84, -0.00705531837586812, 1, "Total indirect", - 0.918429627066259, 0.0688914931131708, -0.102412040399212, -0.0108831762516817, - 0.0104431001662529, 16, -0.00022003804271438, 1, "Total indirect", - 0.967738652775068, 0.00544047660726258, -0.0404446261970226, - -0.0248218258367533, 0.027211992737034, 16, 0.00119508345014035, - 1, "Total indirect", 0.928262819854489, 0.0132741772257611, - 0.0900306986877546, -0.017221137210671, 0.0161430852765094, - 50, -0.000539025967080797, 0, "Total indirect", 0.949504043286334, - 0.00851143764639378, -0.0633296029971126, -0.0529253954032223, - 0.0477190440472555, 50, -0.00260317567798344, 1, "Total indirect", - 0.919241494080271, 0.0256750736861362, -0.101389219357492, -0.028625571608521, - 0.0267997140559034, 84, -0.000912928776308784, 1, "Total indirect", - 0.948519182046454, 0.0141393632999412, -0.0645664699988703, - -0.142080163718872, 0.127969526967136, 84, -0.00705531837586812, - 1, "Total indirect", 0.918429627066259, 0.0688914931131708, - -0.102412040399212, 0, 0, 1, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 1, - 1, 1, 0, 1, 1, 1, 0, 1, 1, 1)) + 0.127969526967136, 84, -0.00705531837586812, 1, "m", "Total indirect", + 0.918429627066259, 0.0688914931131708, -0.102412040399212)) @@ -12332,7 +10696,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 70 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -12343,25 +10707,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -12411,81 +10775,27 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.0229725600648764, 16, 16, 0.00166513755637771, "contGamma", "debCollin1", "contNormal", "", "", 0.878266001307125, 0.0108713336962153, 0.153167734788364, -0.0403761531103848, - 0.0415867899768524, 16, 16, 0.000605318433233805, "contGamma", + 0.0415867899768524, 50, 16, 0.000605318433233805, "contGamma", "debCollin1", "contNormal", "", "", 0.976904687464378, 0.020909298266129, 0.0289497249276109, -0.112528609093363, 0.107095747731377, - 50, 16, -0.00271643068099307, "contGamma", "debCollin1", "contNormal", - "", "", 0.961330714134549, 0.0560276511602021, - -0.0484837508755431, -0.0375580018593202, 0.078713622427919, - 16, 16, 0.0205778102842994, "contGamma", "debCollin1", "contNormal", - "", "", 0.487838492769507, 0.0296616736849184, - 0.69375081470073, -0.0177817206913118, 0.0451839469999532, 84, - 16, 0.0137011131543207, "contGamma", "debCollin1", "contNormal", - "", "", 0.393679894706849, 0.0160629654901647, - 0.852962870567696, -0.0853116350827885, 0.05609830698335, 16, - 16, -0.0146066640497193, "contGamma", "debCollin1", "contNormal", - "", "", 0.685550054615717, 0.0360746276925398, - -0.404901311087957, -0.0767281326832792, 0.162220863987496, - 16, 16, 0.0427463656521086, "contGamma", "debCollin1", "contNormal", - "", "", 0.483147819744687, 0.060957496810037, - 0.701248704245843, -0.0226262576716071, 0.0807290469875354, - 50, 16, 0.0290513946579642, "contGamma", "debCollin1", "contNormal", - "", "", 0.270538113297266, 0.0263666336408209, - 1.10182418634538, -0.0890017924408171, 0.0319141072303785, 50, - 16, -0.0285438426052193, "contGamma", "debCollin1", "contNormal", - "", "", 0.354782677439143, 0.0308464595841977, - -0.925352309146104, -0.019642284952121, 0.0229725600648764, - 50, 50, 0.00166513755637771, "contGamma", "debCollin1", "contNormal", - "", "", 0.878266001307125, 0.0108713336962153, - 0.153167734788364, -0.0403761531103848, 0.0415867899768524, - 84, 50, 0.000605318433233805, "contGamma", "debCollin1", "contNormal", - "", "", 0.976904687464378, 0.020909298266129, - 0.0289497249276109, -0.112528609093363, 0.107095747731377, 50, - 50, -0.00271643068099307, "contGamma", "debCollin1", "contNormal", + 84, 16, -0.00271643068099307, "contGamma", "debCollin1", "contNormal", "", "", 0.961330714134549, 0.0560276511602021, -0.0484837508755431, -0.0375580018593202, 0.078713622427919, 16, 50, 0.0205778102842994, "contGamma", "debCollin1", "contNormal", "", "", 0.487838492769507, 0.0296616736849184, - 0.69375081470073, -0.0177817206913118, 0.0451839469999532, 84, + 0.69375081470073, -0.0177817206913118, 0.0451839469999532, 50, 50, 0.0137011131543207, "contGamma", "debCollin1", "contNormal", "", "", 0.393679894706849, 0.0160629654901647, - 0.852962870567696, -0.0853116350827885, 0.05609830698335, 50, + 0.852962870567696, -0.0853116350827885, 0.05609830698335, 84, 50, -0.0146066640497193, "contGamma", "debCollin1", "contNormal", "", "", 0.685550054615717, 0.0360746276925398, -0.404901311087957, -0.0767281326832792, 0.162220863987496, - 84, 50, 0.0427463656521086, "contGamma", "debCollin1", "contNormal", - "", "", 0.483147819744687, 0.060957496810037, - 0.701248704245843, -0.0226262576716071, 0.0807290469875354, - 84, 50, 0.0290513946579642, "contGamma", "debCollin1", "contNormal", - "", "", 0.270538113297266, 0.0263666336408209, - 1.10182418634538, -0.0890017924408171, 0.0319141072303785, 84, - 50, -0.0285438426052193, "contGamma", "debCollin1", "contNormal", - "", "", 0.354782677439143, 0.0308464595841977, - -0.925352309146104, -0.019642284952121, 0.0229725600648764, - 16, 84, 0.00166513755637771, "contGamma", "debCollin1", "contNormal", - "", "", 0.878266001307125, 0.0108713336962153, - 0.153167734788364, -0.0403761531103848, 0.0415867899768524, - 16, 84, 0.000605318433233805, "contGamma", "debCollin1", "contNormal", - "", "", 0.976904687464378, 0.020909298266129, - 0.0289497249276109, -0.112528609093363, 0.107095747731377, 50, - 84, -0.00271643068099307, "contGamma", "debCollin1", "contNormal", - "", "", 0.961330714134549, 0.0560276511602021, - -0.0484837508755431, -0.0375580018593202, 0.078713622427919, - 16, 84, 0.0205778102842994, "contGamma", "debCollin1", "contNormal", - "", "", 0.487838492769507, 0.0296616736849184, - 0.69375081470073, -0.0177817206913118, 0.0451839469999532, 84, - 84, 0.0137011131543207, "contGamma", "debCollin1", "contNormal", - "", "", 0.393679894706849, 0.0160629654901647, - 0.852962870567696, -0.0853116350827885, 0.05609830698335, 16, - 84, -0.0146066640497193, "contGamma", "debCollin1", "contNormal", - "", "", 0.685550054615717, 0.0360746276925398, - -0.404901311087957, -0.0767281326832792, 0.162220863987496, 16, 84, 0.0427463656521086, "contGamma", "debCollin1", "contNormal", "", "", 0.483147819744687, 0.060957496810037, 0.701248704245843, -0.0226262576716071, 0.0807290469875354, 50, 84, 0.0290513946579642, "contGamma", "debCollin1", "contNormal", "", "", 0.270538113297266, 0.0263666336408209, - 1.10182418634538, -0.0890017924408171, 0.0319141072303785, 50, + 1.10182418634538, -0.0890017924408171, 0.0319141072303785, 84, 84, -0.0285438426052193, "contGamma", "debCollin1", "contNormal", "", "", 0.354782677439143, 0.0308464595841977, -0.925352309146104)) @@ -12527,116 +10837,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) jaspTools::expect_equal_tables(table, list(-0.146752551706188, 0.120689857874141, 16, 16, -0.0130313469160234, "Total", 0.848524301202308, 0.0682263581601195, -0.191001649031893, - -0.150779372881113, 0.122597040802778, 16, 16, -0.0140911660391673, - "Total", 0.839875772789888, 0.069740162533661, -0.202052383120931, - -0.187037795453683, 0.152211965146895, 50, 16, -0.0174129151533941, - "Total", 0.840541450965573, 0.0865448965584411, -0.201200947090343, - -0.140699154901597, 0.152461806525394, 16, 16, 0.00588132581189832, - "Total", 0.937318440094887, 0.0747873337825102, 0.0786406670012045, - -0.137221912192342, 0.135231169556181, 84, 16, -0.000995371318080373, - "Total", 0.988573934715014, 0.0695046143443447, -0.0143209386523466, - -0.176163336884279, 0.117557039840038, 16, 16, -0.0293031485221203, - "Total", 0.695742968971403, 0.0749300443888627, -0.391073417360418, - -0.154092297053674, 0.210192059413089, 16, 16, 0.0280498811797075, - "Total", 0.762778381903612, 0.0929313904082402, 0.301834300084036, - -0.130200279559876, 0.158910099931003, 50, 16, 0.0143549101855631, - "Total", 0.845680826181258, 0.07375400307642, 0.194632285527462, - -0.184851526497271, 0.0983708723420303, 50, 16, -0.0432403270776203, - "Total", 0.549529059152149, 0.0722519395951465, -0.598465969493849, - -0.146752551706188, 0.120689857874141, 50, 50, -0.0130313469160234, - "Total", 0.848524301202308, 0.0682263581601195, -0.191001649031893, - -0.150779372881113, 0.122597040802778, 84, 50, -0.0140911660391673, + -0.150779372881113, 0.122597040802778, 50, 16, -0.0140911660391673, "Total", 0.839875772789888, 0.069740162533661, -0.202052383120931, - -0.187037795453683, 0.152211965146895, 50, 50, -0.0174129151533941, + -0.187037795453683, 0.152211965146895, 84, 16, -0.0174129151533941, "Total", 0.840541450965573, 0.0865448965584411, -0.201200947090343, -0.140699154901597, 0.152461806525394, 16, 50, 0.00588132581189832, "Total", 0.937318440094887, 0.0747873337825102, 0.0786406670012045, - -0.137221912192342, 0.135231169556181, 84, 50, -0.000995371318080373, - "Total", 0.988573934715014, 0.0695046143443447, -0.0143209386523466, - -0.176163336884279, 0.117557039840038, 50, 50, -0.0293031485221203, - "Total", 0.695742968971403, 0.0749300443888627, -0.391073417360418, - -0.154092297053674, 0.210192059413089, 84, 50, 0.0280498811797075, - "Total", 0.762778381903612, 0.0929313904082402, 0.301834300084036, - -0.130200279559876, 0.158910099931003, 84, 50, 0.0143549101855631, - "Total", 0.845680826181258, 0.07375400307642, 0.194632285527462, - -0.184851526497271, 0.0983708723420303, 84, 50, -0.0432403270776203, - "Total", 0.549529059152149, 0.0722519395951465, -0.598465969493849, - -0.146752551706188, 0.120689857874141, 16, 84, -0.0130313469160234, - "Total", 0.848524301202308, 0.0682263581601195, -0.191001649031893, - -0.150779372881113, 0.122597040802778, 16, 84, -0.0140911660391673, - "Total", 0.839875772789888, 0.069740162533661, -0.202052383120931, - -0.187037795453683, 0.152211965146895, 50, 84, -0.0174129151533941, - "Total", 0.840541450965573, 0.0865448965584411, -0.201200947090343, - -0.140699154901597, 0.152461806525394, 16, 84, 0.00588132581189832, - "Total", 0.937318440094887, 0.0747873337825102, 0.0786406670012045, - -0.137221912192342, 0.135231169556181, 84, 84, -0.000995371318080373, + -0.137221912192342, 0.135231169556181, 50, 50, -0.000995371318080373, "Total", 0.988573934715014, 0.0695046143443447, -0.0143209386523466, - -0.176163336884279, 0.117557039840038, 16, 84, -0.0293031485221203, + -0.176163336884279, 0.117557039840038, 84, 50, -0.0293031485221203, "Total", 0.695742968971403, 0.0749300443888627, -0.391073417360418, -0.154092297053674, 0.210192059413089, 16, 84, 0.0280498811797075, "Total", 0.762778381903612, 0.0929313904082402, 0.301834300084036, -0.130200279559876, 0.158910099931003, 50, 84, 0.0143549101855631, "Total", 0.845680826181258, 0.07375400307642, 0.194632285527462, - -0.184851526497271, 0.0983708723420303, 50, 84, -0.0432403270776203, + -0.184851526497271, 0.0983708723420303, 84, 84, -0.0432403270776203, "Total", 0.549529059152149, 0.0722519395951465, -0.598465969493849, - -0.019642284952121, 0.0229725600648764, 50, 16, 0.00166513755637771, - "Total indirect", 0.878266001307125, 0.0108713336962153, 0.153167734788364, - -0.0403761531103848, 0.0415867899768524, 84, 16, 0.000605318433233805, - "Total indirect", 0.976904687464378, 0.020909298266129, 0.0289497249276109, - -0.112528609093363, 0.107095747731377, 50, 16, -0.00271643068099307, - "Total indirect", 0.961330714134549, 0.0560276511602021, -0.0484837508755431, - -0.0375580018593202, 0.078713622427919, 16, 16, 0.0205778102842994, - "Total indirect", 0.487838492769507, 0.0296616736849184, 0.69375081470073, - -0.0177817206913118, 0.0451839469999532, 84, 16, 0.0137011131543207, - "Total indirect", 0.393679894706849, 0.0160629654901647, 0.852962870567696, - -0.0853116350827885, 0.05609830698335, 50, 16, -0.0146066640497193, - "Total indirect", 0.685550054615717, 0.0360746276925398, -0.404901311087957, - -0.0767281326832792, 0.162220863987496, 84, 16, 0.0427463656521086, - "Total indirect", 0.483147819744687, 0.060957496810037, 0.701248704245843, - -0.0226262576716071, 0.0807290469875354, 84, 16, 0.0290513946579642, - "Total indirect", 0.270538113297266, 0.0263666336408209, 1.10182418634538, - -0.0890017924408171, 0.0319141072303785, 84, 16, -0.0285438426052193, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, + "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, + "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, - -0.019642284952121, 0.0229725600648764, 16, 50, 0.00166513755637771, - "Total indirect", 0.878266001307125, 0.0108713336962153, 0.153167734788364, - -0.0403761531103848, 0.0415867899768524, 16, 50, 0.000605318433233805, - "Total indirect", 0.976904687464378, 0.020909298266129, 0.0289497249276109, - -0.112528609093363, 0.107095747731377, 50, 50, -0.00271643068099307, - "Total indirect", 0.961330714134549, 0.0560276511602021, -0.0484837508755431, - -0.0375580018593202, 0.078713622427919, 16, 50, 0.0205778102842994, - "Total indirect", 0.487838492769507, 0.0296616736849184, 0.69375081470073, - -0.0177817206913118, 0.0451839469999532, 84, 50, 0.0137011131543207, - "Total indirect", 0.393679894706849, 0.0160629654901647, 0.852962870567696, - -0.0853116350827885, 0.05609830698335, 16, 50, -0.0146066640497193, - "Total indirect", 0.685550054615717, 0.0360746276925398, -0.404901311087957, - -0.0767281326832792, 0.162220863987496, 16, 50, 0.0427463656521086, - "Total indirect", 0.483147819744687, 0.060957496810037, 0.701248704245843, - -0.0226262576716071, 0.0807290469875354, 50, 50, 0.0290513946579642, - "Total indirect", 0.270538113297266, 0.0263666336408209, 1.10182418634538, - -0.0890017924408171, 0.0319141072303785, 50, 50, -0.0285438426052193, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, - -0.019642284952121, 0.0229725600648764, 50, 84, 0.00166513755637771, - "Total indirect", 0.878266001307125, 0.0108713336962153, 0.153167734788364, - -0.0403761531103848, 0.0415867899768524, 84, 84, 0.000605318433233805, - "Total indirect", 0.976904687464378, 0.020909298266129, 0.0289497249276109, - -0.112528609093363, 0.107095747731377, 50, 84, -0.00271643068099307, - "Total indirect", 0.961330714134549, 0.0560276511602021, -0.0484837508755431, - -0.0375580018593202, 0.078713622427919, 16, 84, 0.0205778102842994, - "Total indirect", 0.487838492769507, 0.0296616736849184, 0.69375081470073, - -0.0177817206913118, 0.0451839469999532, 84, 84, 0.0137011131543207, - "Total indirect", 0.393679894706849, 0.0160629654901647, 0.852962870567696, - -0.0853116350827885, 0.05609830698335, 50, 84, -0.0146066640497193, - "Total indirect", 0.685550054615717, 0.0360746276925398, -0.404901311087957, - -0.0767281326832792, 0.162220863987496, 84, 84, 0.0427463656521086, - "Total indirect", 0.483147819744687, 0.060957496810037, 0.701248704245843, - -0.0226262576716071, 0.0807290469875354, 84, 84, 0.0290513946579642, - "Total indirect", 0.270538113297266, 0.0263666336408209, 1.10182418634538, - -0.0890017924408171, 0.0319141072303785, 84, 84, -0.0285438426052193, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, - 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, 16, 84, 50, - 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, 50, 84, 50, - 16, 84, 50, 84, 84, 84, 16, 16, 50, 16, 84, 16, 16, 50, 50, - 50, 84, 50, 16, 84, 50, 84, 84, 84)) + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, + "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, + "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, + "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104, + -0.0890017924408171, 0.0319141072303785, -0.0285438426052193, + "Total indirect", 0.354782677439143, 0.0308464595841977, -0.925352309146104 + )) @@ -12652,7 +10887,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 70 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -12663,25 +10898,25 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -12728,43 +10963,25 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0393120760749306, 0.866238685862601, "", 0.452775380968766, - "", "facGenderm", "contNormal", "", "", "", 0.0318476731345994, + "", "m", "facGender", "contNormal", "", "", "", 0.0318476731345994, 0.210954542101376, 2.14631728930103, -0.0371909715558107, 0.0317287948254582, - 16, -0.00273108836517626, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.876557021350743, 0.0175818961279134, + 16, -0.00273108836517626, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.876557021350743, 0.0175818961279134, -0.155335257659743, -0.090871277089043, 0.092888630713797, 16, - 0.00100867681237701, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982833335840767, 0.0468783889021214, - 0.0215168830670152, -0.0186050573231307, 0.0174888865610851, - 16, -0.000558085381022809, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.951669797065079, 0.00920780794160511, - -0.0606100153871719, -0.0677418693740053, 0.0606376222422335, - 16, -0.00355212356588592, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.913630630378014, 0.0327504721078754, - -0.108460224762126, -0.0282215593137867, 0.0321995746206938, - 50, 0.00198900765345355, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.897325688802829, 0.0154138378080094, - 0.129040390733839, -0.0992466145898641, 0.0814504512851043, - 50, -0.00889808165237989, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846935973825096, 0.0460970373181048, - -0.193029360888777, -0.0371909715558107, 0.0317287948254582, - 50, -0.00273108836517626, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.876557021350743, 0.0175818961279134, - -0.155335257659743, -0.090871277089043, 0.092888630713797, 50, - 0.00100867681237701, 1, "facGenderm", "debCollin1", "contNormal", + 0.00100867681237701, 1, "m", "facGender", "debCollin1", "contNormal", "", "", 0.982833335840767, 0.0468783889021214, 0.0215168830670152, -0.0186050573231307, 0.0174888865610851, - 84, -0.000558085381022809, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.951669797065079, 0.00920780794160511, + 50, -0.000558085381022809, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.951669797065079, 0.00920780794160511, -0.0606100153871719, -0.0677418693740053, 0.0606376222422335, - 84, -0.00355212356588592, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.913630630378014, 0.0327504721078754, + 50, -0.00355212356588592, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.913630630378014, 0.0327504721078754, -0.108460224762126, -0.0282215593137867, 0.0321995746206938, - 84, 0.00198900765345355, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.897325688802829, 0.0154138378080094, + 84, 0.00198900765345355, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.897325688802829, 0.0154138378080094, 0.129040390733839, -0.0992466145898641, 0.0814504512851043, - 84, -0.00889808165237989, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846935973825096, 0.0460970373181048, + 84, -0.00889808165237989, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.846935973825096, 0.0460970373181048, -0.193029360888777)) @@ -12803,59 +11020,34 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0352237189036005, 0.864864866303578, 16, 0.450044292603589, - 0, "Total", 0.0334707425135468, 0.21164703891094, 2.12639068762482, + list(0.0352237189036005, 0.864864866303578, "", 0.450044292603589, + "", "m", "Total", 0.0334707425135468, 0.21164703891094, 2.12639068762482, 0.0305044113811538, 0.877063704181132, 16, 0.453784057781143, - 0, "Total", 0.0356223319482172, 0.215962971635584, 2.10121232517053, + 0, "m", "Total", 0.0356223319482172, 0.215962971635584, 2.10121232517053, 0.0387217946557514, 0.865712796519734, 16, 0.452217295587743, - 1, "Total", 0.0320725818989174, 0.210970968953303, 2.14350485202463, - 0.0340256776406291, 0.86442083716513, 16, 0.44922325740288, - 0, "Total", 0.0339568133765946, 0.211839392477248, 2.12058414702604, + 1, "m", "Total", 0.0320725818989174, 0.210970968953303, 2.14350485202463, + 0.0340256776406291, 0.86442083716513, 50, 0.44922325740288, + 0, "m", "Total", 0.0339568133765946, 0.211839392477248, 2.12058414702604, 0.0408934741099858, 0.868635303134453, 50, 0.454764388622219, - 0, "Total", 0.0312697675262177, 0.211162510013855, 2.15362276472458, - 0.0272792958822077, 0.860475302750564, 50, 0.443877299316386, - 1, "Total", 0.0367703682341305, 0.212553907480061, 2.08830458389961, - 0.0352237189036005, 0.864864866303578, 50, 0.450044292603589, - 1, "Total", 0.0334707425135468, 0.21164703891094, 2.12639068762482, - 0.0305044113811538, 0.877063704181132, 50, 0.453784057781143, - 1, "Total", 0.0356223319482172, 0.215962971635584, 2.10121232517053, - 0.0387217946557514, 0.865712796519734, 84, 0.452217295587743, - 0, "Total", 0.0320725818989174, 0.210970968953303, 2.14350485202463, - 0.0340256776406291, 0.86442083716513, 84, 0.44922325740288, - 0, "Total", 0.0339568133765946, 0.211839392477248, 2.12058414702604, - 0.0408934741099858, 0.868635303134453, 84, 0.454764388622219, - 1, "Total", 0.0312697675262177, 0.211162510013855, 2.15362276472458, + 1, "m", "Total", 0.0312697675262177, 0.211162510013855, 2.15362276472458, 0.0272792958822077, 0.860475302750564, 84, 0.443877299316386, - 0, "Total", 0.0367703682341305, 0.212553907480061, 2.08830458389961, + 0, "m", "Total", 0.0367703682341305, 0.212553907480061, 2.08830458389961, + 0.0352237189036005, 0.864864866303578, 84, 0.450044292603589, + 1, "m", "Total", 0.0334707425135468, 0.21164703891094, 2.12639068762482, -0.0371909715558107, 0.0317287948254582, 16, -0.00273108836517626, - 0, "Total indirect", 0.876557021350743, 0.0175818961279134, + 0, "m", "Total indirect", 0.876557021350743, 0.0175818961279134, -0.155335257659743, -0.090871277089043, 0.092888630713797, 16, - 0.00100867681237701, 1, "Total indirect", 0.982833335840767, + 0.00100867681237701, 1, "m", "Total indirect", 0.982833335840767, 0.0468783889021214, 0.0215168830670152, -0.0186050573231307, - 0.0174888865610851, 16, -0.000558085381022809, 1, "Total indirect", - 0.951669797065079, 0.00920780794160511, -0.0606100153871719, - -0.0677418693740053, 0.0606376222422335, 16, -0.00355212356588592, - 1, "Total indirect", 0.913630630378014, 0.0327504721078754, - -0.108460224762126, -0.0282215593137867, 0.0321995746206938, - 50, 0.00198900765345355, 0, "Total indirect", 0.897325688802829, - 0.0154138378080094, 0.129040390733839, -0.0992466145898641, - 0.0814504512851043, 50, -0.00889808165237989, 0, "Total indirect", - 0.846935973825096, 0.0460970373181048, -0.193029360888777, -0.0371909715558107, - 0.0317287948254582, 50, -0.00273108836517626, 1, "Total indirect", - 0.876557021350743, 0.0175818961279134, -0.155335257659743, -0.090871277089043, - 0.092888630713797, 50, 0.00100867681237701, 0, "Total indirect", - 0.982833335840767, 0.0468783889021214, 0.0215168830670152, -0.0186050573231307, - 0.0174888865610851, 84, -0.000558085381022809, 0, "Total indirect", + 0.0174888865610851, 50, -0.000558085381022809, 0, "m", "Total indirect", 0.951669797065079, 0.00920780794160511, -0.0606100153871719, - -0.0677418693740053, 0.0606376222422335, 84, -0.00355212356588592, - 1, "Total indirect", 0.913630630378014, 0.0327504721078754, + -0.0677418693740053, 0.0606376222422335, 50, -0.00355212356588592, + 1, "m", "Total indirect", 0.913630630378014, 0.0327504721078754, -0.108460224762126, -0.0282215593137867, 0.0321995746206938, - 84, 0.00198900765345355, 1, "Total indirect", 0.897325688802829, + 84, 0.00198900765345355, 0, "m", "Total indirect", 0.897325688802829, 0.0154138378080094, 0.129040390733839, -0.0992466145898641, - 0.0814504512851043, 84, -0.00889808165237989, 1, "Total indirect", - 0.846935973825096, 0.0460970373181048, -0.193029360888777, 0, - 0, 1, 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, 1, 1, 1, 0, 0, 1, 0, 0, - 1, 1, 1)) + 0.0814504512851043, 84, -0.00889808165237989, 1, "m", "Total indirect", + 0.846935973825096, 0.0460970373181048, -0.193029360888777)) @@ -12871,7 +11063,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 72 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -12882,27 +11074,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "debCollin1", - processIndependent = "contcor1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "debCollin1", + processIndependent = "contcor1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -12952,244 +11144,28 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.0326629517547097, 16, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", "", "", 0.877234633035097, 0.0154475681064834, 0.154475746656278, -0.0346117186822631, - 0.0356489428424167, 16, 16, 0.000518612080076799, "contGamma", + 0.0356489428424167, 50, 16, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", "", "", 0.976917228691988, 0.01792396750116, 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 50, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 16, 16, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 84, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 16, - 16, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 16, - 50, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 16, 16, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 50, 50, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 16, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 84, 50, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 16, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 16, 84, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 16, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 50, - 84, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 16, - 16, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 84, 84, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 16, 16, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 16, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 50, 16, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 50, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 50, 16, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 84, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 50, - 16, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 16, - 50, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 50, 16, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 50, 50, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 50, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 84, 50, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 50, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 16, 84, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 50, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 50, - 84, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 50, - 16, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 84, 84, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 50, 16, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 16, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 84, 16, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 50, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 84, 16, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 84, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 84, - 16, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 16, - 50, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 84, 16, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 50, 50, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 84, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 84, 50, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, 84, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", "", "", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 16, 84, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 84, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 50, - 84, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 84, - 16, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 84, 84, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 84, 16, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 16, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 16, 50, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 50, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, 16, 50, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", "", "", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 84, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 16, - 50, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 16, - 50, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 16, 50, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 50, 50, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 16, 50, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 84, 50, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 16, 50, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 16, 84, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 16, 50, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", - "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 50, - 84, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", - "", "", 0.704861618647392, 0.0313654592316955, - -0.378766025377505, -0.458061689054963, 0.340253590331556, 16, - 50, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", - "", "", 0.772402593824734, 0.203655599205784, - -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 84, 84, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", - "", "", 0.843707862393721, 0.0469375968625982, - 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 16, 50, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", - "", "", 0.355793034582295, 0.0326469494972734, - -0.923411051573397, -0.0278904025201642, 0.0326629517547097, - 16, 16, 0.00238627461727272, "contGamma", "debCollin1", "contNormal", - "", "", 0.877234633035097, 0.0154475681064834, - 0.154475746656278, -0.0346117186822631, 0.0356489428424167, - 50, 50, 0.000518612080076799, "contGamma", "debCollin1", "contNormal", - "", "", 0.976917228691988, 0.01792396750116, - 0.028934000245383, -0.0686408210570276, 0.0653474803946728, - 50, 16, -0.0016466703311774, "contGamma", "debCollin1", "contNormal", - "", "", 0.961577115187317, 0.0341813172355674, - -0.0481745720865303, -0.0889559687929595, 0.0946742595980475, - 50, 50, 0.00285914540254402, "contGamma", "debCollin1", "contNormal", - "", "", 0.951332319349748, 0.0468453068116197, - 0.0610337640447436, -0.0188141723702083, 0.0355015162763122, - 84, 16, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", + 50, 50, 0.00834367195305195, "contGamma", "debCollin1", "contNormal", "", "", 0.547069379083243, 0.0138562976347922, - 0.602157385252866, -0.073355340780012, 0.049595000125353, 50, + 0.602157385252866, -0.073355340780012, 0.049595000125353, 84, 50, -0.0118801703273295, "contGamma", "debCollin1", "contNormal", "", "", 0.704861618647392, 0.0313654592316955, -0.378766025377505, -0.458061689054963, 0.340253590331556, 16, - 50, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", + 84, -0.0589040493617038, "contGamma", "debCollin1", "contNormal", "", "", 0.772402593824734, 0.203655599205784, -0.289233635566211, -0.0827421145252915, 0.101249884217814, - 50, 50, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", + 50, 84, 0.00925388484626113, "contGamma", "debCollin1", "contNormal", "", "", 0.843707862393721, 0.0469375968625982, 0.197152932080232, -0.0941333991856948, 0.0338402912538131, - 50, 50, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0301465539659408, "contGamma", "debCollin1", "contNormal", "", "", 0.355793034582295, 0.0326469494972734, -0.923411051573397)) @@ -13240,351 +11216,42 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.146409400498154, 0.1217900505765, 16, 16, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 16, 16, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 50, 16, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 16, 16, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 84, 16, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 16, 16, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 16, 50, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 16, 16, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 50, 50, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 16, 16, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 84, 50, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 16, 16, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 16, 84, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 16, 16, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 50, 84, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 16, 16, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 84, 84, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 16, 16, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 16, 16, -0.0123096749608267, "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, -0.149891860315254, 0.121537185319209, 50, 16, -0.0141773374980226, "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 50, 16, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 50, 16, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 84, 16, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 50, 16, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 16, 50, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 50, 16, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 50, 50, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 50, 16, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 84, 50, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 50, 16, -0.0163426199092768, + -0.164030137065439, 0.131344897246885, 84, 16, -0.0163426199092768, "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 16, 84, -0.0118368041755554, + -0.175146315934754, 0.151472707583644, 16, 50, -0.0118368041755554, "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 50, 16, -0.00635227762504746, + -0.142645510876497, 0.129940955626402, 50, 50, -0.00635227762504746, "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 50, 84, -0.0265761199054289, + -0.170325593437807, 0.117173353626949, 84, 50, -0.0265761199054289, "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 50, 16, -0.0735999989398033, + -0.493964676572102, 0.346764678692496, 16, 84, -0.0735999989398033, "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 84, 84, -0.00544206473183828, + -0.168884402048933, 0.158000272585256, 50, 84, -0.00544206473183828, "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 50, 16, -0.0448425035440402, + -0.187630030436484, 0.0979450233484032, 84, 84, -0.0448425035440402, "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 16, 16, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 84, 16, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 50, 16, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 84, 16, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 84, 16, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 84, 16, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 16, 50, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 84, 16, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 50, 50, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 84, 16, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 84, 50, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 84, 16, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 16, 84, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 84, 16, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 50, 84, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 84, 16, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 84, 84, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 84, 16, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 16, 16, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 16, 50, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 50, 16, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 16, 50, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 84, 16, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 16, 50, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 16, 50, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 16, 50, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 50, 50, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 16, 50, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 84, 50, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 16, 50, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 16, 84, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 16, 50, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 50, 84, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 16, 50, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 84, 84, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 16, 50, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.146409400498154, 0.1217900505765, 16, 16, -0.0123096749608267, - "Total", 0.857219489536558, 0.0684194845390469, -0.179914757378822, - -0.149891860315254, 0.121537185319209, 50, 50, -0.0141773374980226, - "Total", 0.837770203454924, 0.0692433758414593, -0.204746480450105, - -0.164030137065439, 0.131344897246885, 50, 16, -0.0163426199092768, - "Total", 0.828299343469638, 0.0753521586728645, -0.216883234629376, - -0.175146315934754, 0.151472707583644, 50, 50, -0.0118368041755554, - "Total", 0.887032803438525, 0.0833227105433384, -0.142059758958499, - -0.142645510876497, 0.129940955626402, 84, 16, -0.00635227762504746, - "Total", 0.927215372951487, 0.0695386416926604, -0.0913488884802005, - -0.170325593437807, 0.117173353626949, 50, 50, -0.0265761199054289, - "Total", 0.717087295959886, 0.0733429158220535, -0.362354286130491, - -0.493964676572102, 0.346764678692496, 16, 50, -0.0735999989398033, - "Total", 0.731476297514221, 0.214475715343793, -0.343162389372738, - -0.168884402048933, 0.158000272585256, 50, 50, -0.00544206473183828, - "Total", 0.947966970591584, 0.0833904799304001, -0.0652600241224222, - -0.187630030436484, 0.0979450233484032, 50, 50, -0.0448425035440402, - "Total", 0.538206217617767, 0.0728521177015156, -0.615527797390403, - -0.0278904025201642, 0.0326629517547097, 50, 50, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 84, 50, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 50, 50, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 16, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 50, 50, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 50, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 50, 50, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 84, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 50, 50, -0.0301465539659408, - "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 16, 16, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 84, 50, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 50, 16, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 84, 50, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 84, 16, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 84, 50, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 16, 50, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 84, 50, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 50, 50, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 84, 50, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 84, 50, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 84, 50, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 16, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 84, 50, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 50, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 84, 50, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 84, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 84, 50, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 16, 16, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 16, 84, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 50, 16, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 16, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 84, 16, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 16, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 16, 50, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 16, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 50, 50, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 16, 84, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 84, 50, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 16, 84, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 16, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 16, 84, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 50, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 16, 84, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 84, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 16, 84, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 16, 16, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 50, 84, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 50, 16, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 50, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 84, 16, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 50, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 16, 50, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 50, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 50, 50, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 50, 84, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 84, 50, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 50, 84, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 16, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 50, 84, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 50, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 50, 84, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 84, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 50, 84, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 16, 16, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 84, 84, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 50, 16, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 84, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 84, 16, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 84, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 16, 50, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 84, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 50, 50, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - -0.0278904025201642, 0.0326629517547097, 84, 84, 0.00238627461727272, - "Total indirect", 0.877234633035097, 0.0154475681064834, 0.154475746656278, - -0.0346117186822631, 0.0356489428424167, 84, 50, 0.000518612080076799, - "Total indirect", 0.976917228691988, 0.01792396750116, 0.028934000245383, - -0.0686408210570276, 0.0653474803946728, 84, 84, -0.0016466703311774, - "Total indirect", 0.961577115187317, 0.0341813172355674, -0.0481745720865303, - -0.0889559687929595, 0.0946742595980475, 16, 84, 0.00285914540254402, - "Total indirect", 0.951332319349748, 0.0468453068116197, 0.0610337640447436, - -0.0188141723702083, 0.0355015162763122, 84, 84, 0.00834367195305195, - "Total indirect", 0.547069379083243, 0.0138562976347922, 0.602157385252866, - -0.073355340780012, 0.049595000125353, 50, 84, -0.0118801703273295, - "Total indirect", 0.704861618647392, 0.0313654592316955, -0.378766025377505, - -0.458061689054963, 0.340253590331556, 84, 84, -0.0589040493617038, - "Total indirect", 0.772402593824734, 0.203655599205784, -0.289233635566211, - -0.0827421145252915, 0.101249884217814, 84, 84, 0.00925388484626113, - "Total indirect", 0.843707862393721, 0.0469375968625982, 0.197152932080232, - -0.0941333991856948, 0.0338402912538131, 84, 84, -0.0301465539659408, + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397, - 16, 16, 16, 16, 50, 16, 16, 16, 84, 16, 16, 16, 16, 50, 16, - 16, 50, 50, 16, 16, 84, 50, 16, 16, 16, 84, 16, 16, 50, 84, - 16, 16, 84, 84, 16, 16, 16, 16, 50, 16, 50, 16, 50, 16, 84, - 16, 50, 16, 16, 50, 50, 16, 50, 50, 50, 16, 84, 50, 50, 16, - 16, 84, 50, 16, 50, 84, 50, 16, 84, 84, 50, 16, 16, 16, 84, - 16, 50, 16, 84, 16, 84, 16, 84, 16, 16, 50, 84, 16, 50, 50, - 84, 16, 84, 50, 84, 16, 16, 84, 84, 16, 50, 84, 84, 16, 84, - 84, 84, 16, 16, 16, 16, 50, 50, 16, 16, 50, 84, 16, 16, 50, - 16, 50, 16, 50, 50, 50, 16, 50, 84, 50, 16, 50, 16, 84, 16, - 50, 50, 84, 16, 50, 84, 84, 16, 50, 16, 16, 50, 50, 50, 16, - 50, 50, 84, 16, 50, 50, 16, 50, 50, 50, 50, 50, 50, 50, 84, - 50, 50, 50, 16, 84, 50, 50, 50, 84, 50, 50, 84, 84, 50, 50, - 16, 16, 84, 50, 50, 16, 84, 50, 84, 16, 84, 50, 16, 50, 84, - 50, 50, 50, 84, 50, 84, 50, 84, 50, 16, 84, 84, 50, 50, 84, - 84, 50, 84, 84, 84, 50, 16, 16, 16, 84, 50, 16, 16, 84, 84, - 16, 16, 84, 16, 50, 16, 84, 50, 50, 16, 84, 84, 50, 16, 84, - 16, 84, 16, 84, 50, 84, 16, 84, 84, 84, 16, 84, 16, 16, 50, - 84, 50, 16, 50, 84, 84, 16, 50, 84, 16, 50, 50, 84, 50, 50, - 50, 84, 84, 50, 50, 84, 16, 84, 50, 84, 50, 84, 50, 84, 84, - 84, 50, 84, 16, 16, 84, 84, 50, 16, 84, 84, 84, 16, 84, 84, - 16, 50, 84, 84, 50, 50, 84, 84, 84, 50, 84, 84, 16, 84, 84, - 84, 50, 84, 84, 84, 84, 84, 84, 84)) + -0.0941333991856948, 0.0338402912538131, -0.0301465539659408, + "Total indirect", 0.355793034582295, 0.0326469494972734, -0.923411051573397 + )) @@ -13600,7 +11267,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 72 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -13611,27 +11278,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "debCollin1", - processIndependent = "facExperim", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "debCollin1", + processIndependent = "facExperim", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -13678,114 +11345,24 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0393124070633408, 0.866239581616987, "", 0.452775994340164, - "", "facGenderm", "contNormal", "", "", "", 0.0318475581881488, + "", "m", "facGender", "contNormal", "", "", "", 0.0318475581881488, 0.210954686176976, 2.14631873102983, -0.041004511445679, 0.0389869992606428, - 16, -0.00100875609251809, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96057392253919, 0.020406372601049, + 16, -0.00100875609251809, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.96057392253919, 0.020406372601049, -0.0494333859446551, -0.0336791611766571, 0.032952491450213, - 16, -0.000363334863222026, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982946576964628, 0.016998182913679, + 16, -0.000363334863222026, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.982946576964628, 0.016998182913679, -0.0213749237237374, -0.0170059896105399, 0.0159965629112176, - 16, -0.000504713349661143, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.952196978774148, 0.00841917320473168, + 50, -0.000504713349661143, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.952196978774148, 0.00841917320473168, -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, - 16, -0.00278838415445784, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.914243479950521, 0.0258932625642878, + 50, -0.00278838415445784, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.914243479950521, 0.0258932625642878, -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 50, 0.00304969201739596, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.893899204026309, 0.0228660623793037, - 0.133371980134029, -0.208587453574171, 0.170728106648831, 16, - -0.0189296734626701, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.8449050325553, 0.096765951623345, - -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 50, -0.00100875609251809, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96057392253919, 0.020406372601049, - -0.0494333859446551, -0.0336791611766571, 0.032952491450213, - 16, -0.000363334863222026, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982946576964628, 0.016998182913679, - -0.0213749237237374, -0.0170059896105399, 0.0159965629112176, - 84, -0.000504713349661143, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.952196978774148, 0.00841917320473168, - -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, - 16, -0.00278838415445784, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 84, 0.00304969201739596, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.893899204026309, 0.0228660623793037, - 0.133371980134029, -0.208587453574171, 0.170728106648831, 16, - -0.0189296734626701, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.8449050325553, 0.096765951623345, - -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 16, -0.00100875609251809, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96057392253919, 0.020406372601049, - -0.0494333859446551, -0.0336791611766571, 0.032952491450213, - 16, -0.000363334863222026, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982946576964628, 0.016998182913679, - -0.0213749237237374, -0.0170059896105399, 0.0159965629112176, - 16, -0.000504713349661143, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.952196978774148, 0.00841917320473168, - -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, - 16, -0.00278838415445784, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 50, 0.00304969201739596, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.893899204026309, 0.0228660623793037, - 0.133371980134029, -0.208587453574171, 0.170728106648831, 16, - -0.0189296734626701, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.8449050325553, 0.096765951623345, - -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 50, -0.00100875609251809, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96057392253919, 0.020406372601049, - -0.0494333859446551, -0.0336791611766571, 0.032952491450213, - 16, -0.000363334863222026, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982946576964628, 0.016998182913679, - -0.0213749237237374, -0.0170059896105399, 0.0159965629112176, - 84, -0.000504713349661143, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.952196978774148, 0.00841917320473168, - -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, - 16, -0.00278838415445784, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 84, 0.00304969201739596, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.893899204026309, 0.0228660623793037, - 0.133371980134029, -0.208587453574171, 0.170728106648831, 16, - -0.0189296734626701, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.8449050325553, 0.096765951623345, - -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 16, -0.00100875609251809, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96057392253919, 0.020406372601049, - -0.0494333859446551, -0.0336791611766571, 0.032952491450213, - 50, -0.000363334863222026, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982946576964628, 0.016998182913679, - -0.0213749237237374, -0.0170059896105399, 0.0159965629112176, - 16, -0.000504713349661143, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.952196978774148, 0.00841917320473168, - -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, - 50, -0.00278838415445784, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 50, 0.00304969201739596, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.893899204026309, 0.0228660623793037, - 0.133371980134029, -0.208587453574171, 0.170728106648831, 50, - -0.0189296734626701, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.8449050325553, 0.096765951623345, - -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 50, -0.00100875609251809, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.96057392253919, 0.020406372601049, - -0.0494333859446551, -0.0336791611766571, 0.032952491450213, - 50, -0.000363334863222026, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.982946576964628, 0.016998182913679, - -0.0213749237237374, -0.0170059896105399, 0.0159965629112176, - 84, -0.000504713349661143, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.952196978774148, 0.00841917320473168, - -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, - 50, -0.00278838415445784, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 84, 0.00304969201739596, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.893899204026309, 0.0228660623793037, - 0.133371980134029, -0.208587453574171, 0.170728106648831, 50, - -0.0189296734626701, 0, "facGenderm", "debCollin1", "contNormal", + 84, 0.00304969201739596, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.893899204026309, 0.0228660623793037, + 0.133371980134029, -0.208587453574171, 0.170728106648831, 84, + -0.0189296734626701, 1, "m", "facGender", "debCollin1", "contNormal", "", "", 0.8449050325553, 0.096765951623345, -0.195623286343037)) @@ -13835,164 +11412,34 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0364018314532675, 0.867132645042024, 16, 0.451767238247646, - 0, "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, - 0.0375099002797826, 0.867315418674101, 16, 0.452412659476942, - 0, "Total", 0.0325851883473824, 0.21168897105756, 2.13715744007243, - 0.0388057501458435, 0.865736811835162, 16, 0.452271280990503, - 1, "Total", 0.0320396072927975, 0.210955677811441, 2.14391613291754, - 0.0359569390881448, 0.864018281283267, 16, 0.449987610185706, - 0, "Total", 0.0331568244532998, 0.211244019973521, 2.13017916550779, - 0.0410022039736253, 0.870649168741494, 50, 0.45582568635756, - 0, "Total", 0.031264350387127, 0.211648522960631, 2.1536917904329, - -0.00784535595501767, 0.875537997710005, 16, 0.433846320877494, - 0, "Total", 0.0542104728891539, 0.225357037331563, 1.92515097826382, - 0.0364018314532675, 0.867132645042024, 50, 0.451767238247646, - 1, "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, - 0.0375099002797826, 0.867315418674101, 16, 0.452412659476942, - 0, "Total", 0.0325851883473824, 0.21168897105756, 2.13715744007243, - 0.0388057501458435, 0.865736811835162, 84, 0.452271280990503, - 0, "Total", 0.0320396072927975, 0.210955677811441, 2.14391613291754, - 0.0359569390881448, 0.864018281283267, 16, 0.449987610185706, - 0, "Total", 0.0331568244532998, 0.211244019973521, 2.13017916550779, - 0.0410022039736253, 0.870649168741494, 84, 0.45582568635756, - 1, "Total", 0.031264350387127, 0.211648522960631, 2.1536917904329, - -0.00784535595501767, 0.875537997710005, 16, 0.433846320877494, - 0, "Total", 0.0542104728891539, 0.225357037331563, 1.92515097826382, - 0.0364018314532675, 0.867132645042024, 16, 0.451767238247646, - 0, "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, + list(0.0364018314532675, 0.867132645042024, "", 0.451767238247646, + "", "m", "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, 0.0375099002797826, 0.867315418674101, 16, 0.452412659476942, - 1, "Total", 0.0325851883473824, 0.21168897105756, 2.13715744007243, + 0, "m", "Total", 0.0325851883473824, 0.21168897105756, 2.13715744007243, 0.0388057501458435, 0.865736811835162, 16, 0.452271280990503, - 1, "Total", 0.0320396072927975, 0.210955677811441, 2.14391613291754, - 0.0359569390881448, 0.864018281283267, 16, 0.449987610185706, - 1, "Total", 0.0331568244532998, 0.211244019973521, 2.13017916550779, - 0.0410022039736253, 0.870649168741494, 50, 0.45582568635756, - 0, "Total", 0.031264350387127, 0.211648522960631, 2.1536917904329, - -0.00784535595501767, 0.875537997710005, 16, 0.433846320877494, - 1, "Total", 0.0542104728891539, 0.225357037331563, 1.92515097826382, - 0.0364018314532675, 0.867132645042024, 50, 0.451767238247646, - 1, "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, - 0.0375099002797826, 0.867315418674101, 16, 0.452412659476942, - 1, "Total", 0.0325851883473824, 0.21168897105756, 2.13715744007243, - 0.0388057501458435, 0.865736811835162, 84, 0.452271280990503, - 0, "Total", 0.0320396072927975, 0.210955677811441, 2.14391613291754, - 0.0359569390881448, 0.864018281283267, 16, 0.449987610185706, - 1, "Total", 0.0331568244532998, 0.211244019973521, 2.13017916550779, - 0.0410022039736253, 0.870649168741494, 84, 0.45582568635756, - 1, "Total", 0.031264350387127, 0.211648522960631, 2.1536917904329, - -0.00784535595501767, 0.875537997710005, 16, 0.433846320877494, - 1, "Total", 0.0542104728891539, 0.225357037331563, 1.92515097826382, - 0.0364018314532675, 0.867132645042024, 16, 0.451767238247646, - 0, "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, - 0.0375099002797826, 0.867315418674101, 50, 0.452412659476942, - 0, "Total", 0.0325851883473824, 0.21168897105756, 2.13715744007243, - 0.0388057501458435, 0.865736811835162, 16, 0.452271280990503, - 1, "Total", 0.0320396072927975, 0.210955677811441, 2.14391613291754, + 1, "m", "Total", 0.0320396072927975, 0.210955677811441, 2.14391613291754, 0.0359569390881448, 0.864018281283267, 50, 0.449987610185706, - 0, "Total", 0.0331568244532998, 0.211244019973521, 2.13017916550779, + 0, "m", "Total", 0.0331568244532998, 0.211244019973521, 2.13017916550779, 0.0410022039736253, 0.870649168741494, 50, 0.45582568635756, - 0, "Total", 0.031264350387127, 0.211648522960631, 2.1536917904329, - -0.00784535595501767, 0.875537997710005, 50, 0.433846320877494, - 0, "Total", 0.0542104728891539, 0.225357037331563, 1.92515097826382, - 0.0364018314532675, 0.867132645042024, 50, 0.451767238247646, - 1, "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, - 0.0375099002797826, 0.867315418674101, 50, 0.452412659476942, - 0, "Total", 0.0325851883473824, 0.21168897105756, 2.13715744007243, - 0.0388057501458435, 0.865736811835162, 84, 0.452271280990503, - 0, "Total", 0.0320396072927975, 0.210955677811441, 2.14391613291754, - 0.0359569390881448, 0.864018281283267, 50, 0.449987610185706, - 0, "Total", 0.0331568244532998, 0.211244019973521, 2.13017916550779, - 0.0410022039736253, 0.870649168741494, 84, 0.45582568635756, - 1, "Total", 0.031264350387127, 0.211648522960631, 2.1536917904329, - -0.00784535595501767, 0.875537997710005, 50, 0.433846320877494, - 0, "Total", 0.0542104728891539, 0.225357037331563, 1.92515097826382, + 1, "m", "Total", 0.031264350387127, 0.211648522960631, 2.1536917904329, + -0.00784535595501767, 0.875537997710005, 84, 0.433846320877494, + 0, "m", "Total", 0.0542104728891539, 0.225357037331563, 1.92515097826382, + 0.0364018314532675, 0.867132645042024, 84, 0.451767238247646, + 1, "m", "Total", 0.0330289267614747, 0.211925020087475, 2.13173148720794, -0.041004511445679, 0.0389869992606428, 16, -0.00100875609251809, - 0, "Total indirect", 0.96057392253919, 0.020406372601049, -0.0494333859446551, - -0.0336791611766571, 0.032952491450213, 50, -0.000363334863222026, - 1, "Total indirect", 0.982946576964628, 0.016998182913679, -0.0213749237237374, - -0.0170059896105399, 0.0159965629112176, 16, -0.000504713349661143, - 1, "Total indirect", 0.952196978774148, 0.00841917320473168, - -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, - 50, -0.00278838415445784, 1, "Total indirect", 0.914243479950521, - 0.0258932625642878, -0.107687632932885, -0.0417669667142856, - 0.0478663507490775, 50, 0.00304969201739596, 0, "Total indirect", - 0.893899204026309, 0.0228660623793037, 0.133371980134029, -0.208587453574171, - 0.170728106648831, 50, -0.0189296734626701, 1, "Total indirect", - 0.8449050325553, 0.096765951623345, -0.195623286343037, -0.041004511445679, - 0.0389869992606428, 50, -0.00100875609251809, 1, "Total indirect", - 0.96057392253919, 0.020406372601049, -0.0494333859446551, -0.0336791611766571, - 0.032952491450213, 50, -0.000363334863222026, 1, "Total indirect", - 0.982946576964628, 0.016998182913679, -0.0213749237237374, -0.0170059896105399, - 0.0159965629112176, 84, -0.000504713349661143, 0, "Total indirect", + 0, "m", "Total indirect", 0.96057392253919, 0.020406372601049, + -0.0494333859446551, -0.0336791611766571, 0.032952491450213, + 16, -0.000363334863222026, 1, "m", "Total indirect", 0.982946576964628, + 0.016998182913679, -0.0213749237237374, -0.0170059896105399, + 0.0159965629112176, 50, -0.000504713349661143, 0, "m", "Total indirect", 0.952196978774148, 0.00841917320473168, -0.0599480896030845, -0.0535382462227012, 0.0479614779137855, 50, -0.00278838415445784, - 1, "Total indirect", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 84, 0.00304969201739596, 1, "Total indirect", 0.893899204026309, - 0.0228660623793037, 0.133371980134029, -0.208587453574171, 0.170728106648831, - 50, -0.0189296734626701, 1, "Total indirect", 0.8449050325553, - 0.096765951623345, -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 16, -0.00100875609251809, 0, "Total indirect", 0.96057392253919, - 0.020406372601049, -0.0494333859446551, -0.0336791611766571, - 0.032952491450213, 84, -0.000363334863222026, 0, "Total indirect", - 0.982946576964628, 0.016998182913679, -0.0213749237237374, -0.0170059896105399, - 0.0159965629112176, 16, -0.000504713349661143, 1, "Total indirect", - 0.952196978774148, 0.00841917320473168, -0.0599480896030845, - -0.0535382462227012, 0.0479614779137855, 84, -0.00278838415445784, - 0, "Total indirect", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 50, 0.00304969201739596, 0, "Total indirect", 0.893899204026309, - 0.0228660623793037, 0.133371980134029, -0.208587453574171, 0.170728106648831, - 84, -0.0189296734626701, 0, "Total indirect", 0.8449050325553, - 0.096765951623345, -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 50, -0.00100875609251809, 1, "Total indirect", 0.96057392253919, - 0.020406372601049, -0.0494333859446551, -0.0336791611766571, - 0.032952491450213, 84, -0.000363334863222026, 0, "Total indirect", - 0.982946576964628, 0.016998182913679, -0.0213749237237374, -0.0170059896105399, - 0.0159965629112176, 84, -0.000504713349661143, 0, "Total indirect", - 0.952196978774148, 0.00841917320473168, -0.0599480896030845, - -0.0535382462227012, 0.0479614779137855, 84, -0.00278838415445784, - 0, "Total indirect", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 84, 0.00304969201739596, 1, "Total indirect", 0.893899204026309, - 0.0228660623793037, 0.133371980134029, -0.208587453574171, 0.170728106648831, - 84, -0.0189296734626701, 0, "Total indirect", 0.8449050325553, - 0.096765951623345, -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 16, -0.00100875609251809, 0, "Total indirect", 0.96057392253919, - 0.020406372601049, -0.0494333859446551, -0.0336791611766571, - 0.032952491450213, 84, -0.000363334863222026, 1, "Total indirect", - 0.982946576964628, 0.016998182913679, -0.0213749237237374, -0.0170059896105399, - 0.0159965629112176, 16, -0.000504713349661143, 1, "Total indirect", - 0.952196978774148, 0.00841917320473168, -0.0599480896030845, - -0.0535382462227012, 0.0479614779137855, 84, -0.00278838415445784, - 1, "Total indirect", 0.914243479950521, 0.0258932625642878, - -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 50, 0.00304969201739596, 0, "Total indirect", 0.893899204026309, - 0.0228660623793037, 0.133371980134029, -0.208587453574171, 0.170728106648831, - 84, -0.0189296734626701, 1, "Total indirect", 0.8449050325553, - 0.096765951623345, -0.195623286343037, -0.041004511445679, 0.0389869992606428, - 50, -0.00100875609251809, 1, "Total indirect", 0.96057392253919, - 0.020406372601049, -0.0494333859446551, -0.0336791611766571, - 0.032952491450213, 84, -0.000363334863222026, 1, "Total indirect", - 0.982946576964628, 0.016998182913679, -0.0213749237237374, -0.0170059896105399, - 0.0159965629112176, 84, -0.000504713349661143, 0, "Total indirect", - 0.952196978774148, 0.00841917320473168, -0.0599480896030845, - -0.0535382462227012, 0.0479614779137855, 84, -0.00278838415445784, - 1, "Total indirect", 0.914243479950521, 0.0258932625642878, + 1, "m", "Total indirect", 0.914243479950521, 0.0258932625642878, -0.107687632932885, -0.0417669667142856, 0.0478663507490775, - 84, 0.00304969201739596, 1, "Total indirect", 0.893899204026309, + 84, 0.00304969201739596, 0, "m", "Total indirect", 0.893899204026309, 0.0228660623793037, 0.133371980134029, -0.208587453574171, 0.170728106648831, - 84, -0.0189296734626701, 1, "Total indirect", 0.8449050325553, - 0.096765951623345, -0.195623286343037, 16, 0, 16, 0, 16, 1, - 16, 0, 50, 0, 16, 0, 50, 1, 16, 0, 84, 0, 16, 0, 84, 1, 16, - 0, 16, 0, 16, 1, 16, 1, 16, 1, 50, 0, 16, 1, 50, 1, 16, 1, 84, - 0, 16, 1, 84, 1, 16, 1, 16, 0, 50, 0, 16, 1, 50, 0, 50, 0, 50, - 0, 50, 1, 50, 0, 84, 0, 50, 0, 84, 1, 50, 0, 16, 0, 50, 1, 16, - 1, 50, 1, 50, 0, 50, 1, 50, 1, 50, 1, 84, 0, 50, 1, 84, 1, 50, - 1, 16, 0, 84, 0, 16, 1, 84, 0, 50, 0, 84, 0, 50, 1, 84, 0, 84, - 0, 84, 0, 84, 1, 84, 0, 16, 0, 84, 1, 16, 1, 84, 1, 50, 0, 84, - 1, 50, 1, 84, 1, 84, 0, 84, 1, 84, 1, 84, 1)) + 84, -0.0189296734626701, 1, "m", "Total indirect", 0.8449050325553, + 0.096765951623345, -0.195623286343037)) @@ -14008,7 +11455,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 75 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -14019,27 +11466,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -14089,244 +11536,28 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) 0.0308819064008094, 16, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", "", "", 0.639407030643892, 0.0127164949318627, 0.468528030459383, -0.0685081685432086, - 0.0356526797931053, 16, 16, -0.0164277443750517, "contGamma", + 0.0356526797931053, 50, 16, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", "", "", 0.53642238701918, 0.0265721332529376, -0.618232048540383, -0.282911778956314, - 0.137197311638812, 50, 16, -0.072857233658751, "contGamma", + 0.137197311638812, 84, 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", "", "", 0.496623647827288, 0.107172655699006, -0.679811778326836, -0.0491996620797185, - 0.078083782491989, 16, 16, 0.0144420602061352, "contGamma", + 0.078083782491989, 16, 50, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", "", "", 0.656486100924554, 0.0324708631321042, 0.444769827872429, -0.0255941683713346, - 0.0225802090927629, 84, 16, -0.00150697963928586, "contGamma", + 0.0225802090927629, 50, 50, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", "", "", 0.902406216705429, 0.0122896078305752, -0.12262227241594, -0.153639154511662, 0.0518159814080455, - 16, 16, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 16, - 50, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 16, 16, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 50, 50, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 16, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 84, 50, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 16, - 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 16, 84, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 16, 16, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 50, - 84, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 16, - 16, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 84, 84, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 16, 16, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 16, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 50, 16, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 50, - 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 50, 16, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 84, 16, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 50, - 16, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 16, - 50, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 50, 16, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 50, 50, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 50, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 84, 50, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 50, - 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 16, 84, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 50, 16, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 50, - 84, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 50, - 16, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 84, 84, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 50, 16, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 16, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 84, 16, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 50, - 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 84, 16, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 84, 16, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 84, - 16, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 16, - 50, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 84, 16, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 50, 50, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 84, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 84, 50, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 84, - 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 16, 84, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 84, 16, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 50, - 84, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 84, - 16, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 84, 84, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 84, 16, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 16, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 16, 50, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 50, - 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 16, 50, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 84, 16, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 16, - 50, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 16, - 50, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 16, 50, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 50, 50, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 16, 50, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 84, 50, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 16, - 50, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 16, 84, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 16, 50, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 50, - 84, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", - "", "", 0.331371823388933, 0.0524129875702592, - -0.971354408743854, -0.160196665334113, 0.211647145932007, 16, - 50, 0.025725240298947, "contGamma", "debCollin1", "contNormal", - "", "", 0.786243319892928, 0.0948598581910629, - 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 84, 84, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", - "", "", 0.544170061601725, 0.028558118929487, - 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 16, 50, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", - "", "", 0.453426985677416, 0.0318112250353054, - -0.749713980346022, -0.0189658377512647, 0.0308819064008094, - 16, 16, 0.00595803432477236, "contGamma", "debCollin1", "contNormal", - "", "", 0.639407030643892, 0.0127164949318627, - 0.468528030459383, -0.0685081685432086, 0.0356526797931053, - 50, 50, -0.0164277443750517, "contGamma", "debCollin1", "contNormal", - "", "", 0.53642238701918, 0.0265721332529376, - -0.618232048540383, -0.282911778956314, 0.137197311638812, 50, - 16, -0.072857233658751, "contGamma", "debCollin1", "contNormal", - "", "", 0.496623647827288, 0.107172655699006, - -0.679811778326836, -0.0491996620797185, 0.078083782491989, - 50, 50, 0.0144420602061352, "contGamma", "debCollin1", "contNormal", - "", "", 0.656486100924554, 0.0324708631321042, - 0.444769827872429, -0.0255941683713346, 0.0225802090927629, - 84, 16, -0.00150697963928586, "contGamma", "debCollin1", "contNormal", - "", "", 0.902406216705429, 0.0122896078305752, - -0.12262227241594, -0.153639154511662, 0.0518159814080455, 50, - 50, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0509115865518081, "contGamma", "debCollin1", "contNormal", "", "", 0.331371823388933, 0.0524129875702592, -0.971354408743854, -0.160196665334113, 0.211647145932007, 16, - 50, 0.025725240298947, "contGamma", "debCollin1", "contNormal", + 84, 0.025725240298947, "contGamma", "debCollin1", "contNormal", "", "", 0.786243319892928, 0.0948598581910629, 0.271192059418139, -0.0386518381937185, 0.0732939309422937, - 50, 50, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", + 50, 84, 0.0173210463742876, "contGamma", "debCollin1", "contNormal", "", "", 0.544170061601725, 0.028558118929487, 0.606519162450968, -0.0861981755141994, 0.0384995352323957, - 50, 50, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0238493201409018, "contGamma", "debCollin1", "contNormal", "", "", 0.453426985677416, 0.0318112250353054, -0.749713980346022)) @@ -14366,351 +11597,42 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.141761913548368, 0.129606560178665, 16, 16, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 16, 16, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 50, 16, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 16, 16, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 84, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 16, 16, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 16, 50, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 16, 16, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 50, 50, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 16, 16, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 84, 50, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 16, 16, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 16, 84, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 16, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 50, 84, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 16, 16, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 84, 84, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 16, 16, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 16, 16, -0.00607767668485123, "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, -0.168271233597136, 0.111344322827785, 50, 16, -0.0284634553846752, "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 50, 16, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 50, 16, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 84, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 50, 16, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 16, 50, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 50, 16, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 50, 50, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 50, 16, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 84, 50, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 50, 16, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 16, 84, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 50, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 50, 84, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 50, 16, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 84, 84, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 50, 16, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 16, 16, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 84, 16, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 50, 16, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 84, 16, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 84, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 84, 16, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 16, 50, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 84, 16, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 50, 50, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 84, 16, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 84, 50, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, -0.328260150002978, 0.158474260666229, 84, 16, -0.0848929446683746, "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 16, 84, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 84, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 50, 84, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 84, 16, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 84, 84, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 84, 16, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 16, 16, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 16, 50, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 50, 16, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, -0.145659867985989, 0.150472566379012, 16, 50, 0.00240634919651163, "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 84, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 16, 50, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 16, 50, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 16, 50, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 50, 50, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 16, 50, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 84, 50, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 16, 50, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 16, 84, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 16, 50, -0.0135426906489094, + -0.146122598796297, 0.119037217498478, 50, 50, -0.0135426906489094, "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 50, 84, -0.0629472975614317, + -0.223904838546689, 0.098010243423826, 84, 50, -0.0629472975614317, "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 16, 50, 0.0136895292893234, + -0.215564074827307, 0.242943133405954, 16, 84, 0.0136895292893234, "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 84, 84, 0.00528533536466401, + -0.137332376915948, 0.147903047645276, 50, 84, 0.00528533536466401, "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 16, 50, -0.0358850311505254, + -0.175715351830675, 0.103945289529625, 84, 84, -0.0358850311505254, "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.141761913548368, 0.129606560178665, 16, 16, -0.00607767668485123, - "Total", 0.930041780198284, 0.0692279235403184, -0.0877922718758361, - -0.168271233597136, 0.111344322827785, 50, 50, -0.0284634553846752, - "Total", 0.689871891538227, 0.0713318098267349, -0.399028924876756, - -0.328260150002978, 0.158474260666229, 50, 16, -0.0848929446683746, - "Total", 0.494172523860313, 0.12416922313586, -0.683687491347906, - -0.145659867985989, 0.150472566379012, 50, 50, 0.00240634919651163, - "Total", 0.974589255696737, 0.0755453765224403, 0.0318530306854297, - -0.146122598796297, 0.119037217498478, 84, 16, -0.0135426906489094, - "Total", 0.841320106988898, 0.0676440532546318, -0.200205191695578, - -0.223904838546689, 0.098010243423826, 50, 50, -0.0629472975614317, - "Total", 0.443377074506089, 0.08212270340418, -0.766502988237327, - -0.215564074827307, 0.242943133405954, 16, 50, 0.0136895292893234, - "Total", 0.906831319748152, 0.116968273868782, 0.117036259803924, - -0.137332376915948, 0.147903047645276, 50, 50, 0.00528533536466401, - "Total", 0.942096410084897, 0.072765476001377, 0.0726352063520342, - -0.175715351830675, 0.103945289529625, 50, 50, -0.0358850311505254, - "Total", 0.614970721450913, 0.0713433112971023, -0.50299082700389, - -0.0189658377512647, 0.0308819064008094, 50, 50, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 84, 50, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 50, 50, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 16, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 50, 50, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 50, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 50, 50, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 84, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 50, 50, -0.0238493201409018, - "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 16, 16, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 84, 50, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 50, 16, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 84, 50, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 84, 16, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 84, 50, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 16, 50, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 84, 50, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 50, 50, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 84, 50, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 84, 50, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 84, 50, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 16, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 84, 50, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 50, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 84, 50, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 84, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 84, 50, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 16, 16, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 16, 84, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 50, 16, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 16, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 84, 16, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 16, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 16, 50, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 16, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 50, 50, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 16, 84, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 84, 50, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 16, 84, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 16, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 16, 84, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 50, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 16, 84, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 84, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 16, 84, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 16, 16, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 50, 84, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 50, 16, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 50, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 84, 16, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 50, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 16, 50, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 50, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 50, 50, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 50, 84, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 84, 50, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 50, 84, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 16, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 50, 84, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 50, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 50, 84, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 84, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 50, 84, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 16, 16, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 84, 84, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 50, 16, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 84, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 84, 16, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 84, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 16, 50, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 84, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 50, 50, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - -0.0189658377512647, 0.0308819064008094, 84, 84, 0.00595803432477236, - "Total indirect", 0.639407030643892, 0.0127164949318627, 0.468528030459383, - -0.0685081685432086, 0.0356526797931053, 84, 50, -0.0164277443750517, - "Total indirect", 0.53642238701918, 0.0265721332529376, -0.618232048540383, - -0.282911778956314, 0.137197311638812, 84, 84, -0.072857233658751, - "Total indirect", 0.496623647827288, 0.107172655699006, -0.679811778326836, - -0.0491996620797185, 0.078083782491989, 16, 84, 0.0144420602061352, - "Total indirect", 0.656486100924554, 0.0324708631321042, 0.444769827872429, - -0.0255941683713346, 0.0225802090927629, 84, 84, -0.00150697963928586, - "Total indirect", 0.902406216705429, 0.0122896078305752, -0.12262227241594, - -0.153639154511662, 0.0518159814080455, 50, 84, -0.0509115865518081, - "Total indirect", 0.331371823388933, 0.0524129875702592, -0.971354408743854, - -0.160196665334113, 0.211647145932007, 84, 84, 0.025725240298947, - "Total indirect", 0.786243319892928, 0.0948598581910629, 0.271192059418139, - -0.0386518381937185, 0.0732939309422937, 84, 84, 0.0173210463742876, - "Total indirect", 0.544170061601725, 0.028558118929487, 0.606519162450968, - -0.0861981755141994, 0.0384995352323957, 84, 84, -0.0238493201409018, + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022, - 16, 16, 16, 16, 50, 16, 16, 16, 84, 16, 16, 16, 16, 50, 16, - 16, 50, 50, 16, 16, 84, 50, 16, 16, 16, 84, 16, 16, 50, 84, - 16, 16, 84, 84, 16, 16, 16, 16, 50, 16, 50, 16, 50, 16, 84, - 16, 50, 16, 16, 50, 50, 16, 50, 50, 50, 16, 84, 50, 50, 16, - 16, 84, 50, 16, 50, 84, 50, 16, 84, 84, 50, 16, 16, 16, 84, - 16, 50, 16, 84, 16, 84, 16, 84, 16, 16, 50, 84, 16, 50, 50, - 84, 16, 84, 50, 84, 16, 16, 84, 84, 16, 50, 84, 84, 16, 84, - 84, 84, 16, 16, 16, 16, 50, 50, 16, 16, 50, 84, 16, 16, 50, - 16, 50, 16, 50, 50, 50, 16, 50, 84, 50, 16, 50, 16, 84, 16, - 50, 50, 84, 16, 50, 84, 84, 16, 50, 16, 16, 50, 50, 50, 16, - 50, 50, 84, 16, 50, 50, 16, 50, 50, 50, 50, 50, 50, 50, 84, - 50, 50, 50, 16, 84, 50, 50, 50, 84, 50, 50, 84, 84, 50, 50, - 16, 16, 84, 50, 50, 16, 84, 50, 84, 16, 84, 50, 16, 50, 84, - 50, 50, 50, 84, 50, 84, 50, 84, 50, 16, 84, 84, 50, 50, 84, - 84, 50, 84, 84, 84, 50, 16, 16, 16, 84, 50, 16, 16, 84, 84, - 16, 16, 84, 16, 50, 16, 84, 50, 50, 16, 84, 84, 50, 16, 84, - 16, 84, 16, 84, 50, 84, 16, 84, 84, 84, 16, 84, 16, 16, 50, - 84, 50, 16, 50, 84, 84, 16, 50, 84, 16, 50, 50, 84, 50, 50, - 50, 84, 84, 50, 50, 84, 16, 84, 50, 84, 50, 84, 50, 84, 84, - 84, 50, 84, 16, 16, 84, 84, 50, 16, 84, 84, 84, 16, 84, 84, - 16, 50, 84, 84, 50, 50, 84, 84, 84, 50, 84, 84, 16, 84, 84, - 84, 50, 84, 84, 84, 84, 84, 84, 84)) + -0.0861981755141994, 0.0384995352323957, -0.0238493201409018, + "Total indirect", 0.453426985677416, 0.0318112250353054, -0.749713980346022 + )) @@ -14726,7 +11648,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 75 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -14737,27 +11659,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -14803,114 +11725,24 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(0.0715438300028005, 0.892289575876473, "", 0.481916702939637, - "", "facGenderm", "contNormal", "", "", "", 0.0213542773547413, + "", "m", "facGender", "contNormal", "", "", "", 0.0213542773547413, 0.209377762129205, 2.30166135142017, -0.0560644004179153, 0.0459987548048033, - 16, -0.00503282280655598, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846727901291906, 0.0260369976254104, - -0.193295051870507, -0.0555869444398369, 0.0642898960559021, - 16, 0.00435147580803259, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.886849652981579, 0.0305813885972682, - 0.142291635783383, -0.0213440026029491, 0.0198255778940844, - 16, -0.000759212354432364, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.942372886213193, 0.0105026369927647, - -0.0722877840065682, -0.0615383274028843, 0.0595927466508237, - 16, -0.000972790376030281, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 50, 0.000339303905389171, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970936804446966, 0.00931299746138703, - 0.0364333724771183, -0.10816733883345, 0.0859184213847258, 16, - -0.0111244587243619, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.822228672322329, 0.0495125833303824, - -0.224679424422915, -0.0560644004179153, 0.0459987548048033, - 50, -0.00503282280655598, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846727901291906, 0.0260369976254104, - -0.193295051870507, -0.0555869444398369, 0.0642898960559021, - 16, 0.00435147580803259, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.886849652981579, 0.0305813885972682, - 0.142291635783383, -0.0213440026029491, 0.0198255778940844, - 84, -0.000759212354432364, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.942372886213193, 0.0105026369927647, - -0.0722877840065682, -0.0615383274028843, 0.0595927466508237, - 16, -0.000972790376030281, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 84, 0.000339303905389171, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970936804446966, 0.00931299746138703, - 0.0364333724771183, -0.10816733883345, 0.0859184213847258, 16, - -0.0111244587243619, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.822228672322329, 0.0495125833303824, - -0.224679424422915, -0.0560644004179153, 0.0459987548048033, - 16, -0.00503282280655598, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846727901291906, 0.0260369976254104, - -0.193295051870507, -0.0555869444398369, 0.0642898960559021, - 16, 0.00435147580803259, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.886849652981579, 0.0305813885972682, - 0.142291635783383, -0.0213440026029491, 0.0198255778940844, - 16, -0.000759212354432364, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.942372886213193, 0.0105026369927647, - -0.0722877840065682, -0.0615383274028843, 0.0595927466508237, - 16, -0.000972790376030281, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 50, 0.000339303905389171, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970936804446966, 0.00931299746138703, - 0.0364333724771183, -0.10816733883345, 0.0859184213847258, 16, - -0.0111244587243619, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.822228672322329, 0.0495125833303824, - -0.224679424422915, -0.0560644004179153, 0.0459987548048033, - 50, -0.00503282280655598, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846727901291906, 0.0260369976254104, + 16, -0.00503282280655598, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.846727901291906, 0.0260369976254104, -0.193295051870507, -0.0555869444398369, 0.0642898960559021, - 16, 0.00435147580803259, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.886849652981579, 0.0305813885972682, + 16, 0.00435147580803259, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.886849652981579, 0.0305813885972682, 0.142291635783383, -0.0213440026029491, 0.0198255778940844, - 84, -0.000759212354432364, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.942372886213193, 0.0105026369927647, + 50, -0.000759212354432364, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.942372886213193, 0.0105026369927647, -0.0722877840065682, -0.0615383274028843, 0.0595927466508237, - 16, -0.000972790376030281, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974886333792357, 0.0309013520169693, + 50, -0.000972790376030281, 1, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.974886333792357, 0.0309013520169693, -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 84, 0.000339303905389171, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970936804446966, 0.00931299746138703, - 0.0364333724771183, -0.10816733883345, 0.0859184213847258, 16, - -0.0111244587243619, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.822228672322329, 0.0495125833303824, - -0.224679424422915, -0.0560644004179153, 0.0459987548048033, - 16, -0.00503282280655598, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846727901291906, 0.0260369976254104, - -0.193295051870507, -0.0555869444398369, 0.0642898960559021, - 50, 0.00435147580803259, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.886849652981579, 0.0305813885972682, - 0.142291635783383, -0.0213440026029491, 0.0198255778940844, - 16, -0.000759212354432364, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.942372886213193, 0.0105026369927647, - -0.0722877840065682, -0.0615383274028843, 0.0595927466508237, - 50, -0.000972790376030281, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 50, 0.000339303905389171, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970936804446966, 0.00931299746138703, - 0.0364333724771183, -0.10816733883345, 0.0859184213847258, 50, - -0.0111244587243619, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.822228672322329, 0.0495125833303824, - -0.224679424422915, -0.0560644004179153, 0.0459987548048033, - 50, -0.00503282280655598, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.846727901291906, 0.0260369976254104, - -0.193295051870507, -0.0555869444398369, 0.0642898960559021, - 50, 0.00435147580803259, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.886849652981579, 0.0305813885972682, - 0.142291635783383, -0.0213440026029491, 0.0198255778940844, - 84, -0.000759212354432364, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.942372886213193, 0.0105026369927647, - -0.0722877840065682, -0.0615383274028843, 0.0595927466508237, - 50, -0.000972790376030281, 0, "facGenderm", "debCollin1", "contNormal", - "", "", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 84, 0.000339303905389171, 1, "facGenderm", "debCollin1", "contNormal", - "", "", 0.970936804446966, 0.00931299746138703, - 0.0364333724771183, -0.10816733883345, 0.0859184213847258, 50, - -0.0111244587243619, 0, "facGenderm", "debCollin1", "contNormal", + 84, 0.000339303905389171, 0, "m", "facGender", "debCollin1", + "contNormal", "", "", 0.970936804446966, 0.00931299746138703, + 0.0364333724771183, -0.10816733883345, 0.0859184213847258, 84, + -0.0111244587243619, 1, "m", "facGender", "debCollin1", "contNormal", "", "", 0.822228672322329, 0.0495125833303824, -0.224679424422915)) @@ -14949,165 +11781,34 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, - list(0.0643801964874038, 0.889387563778757, 16, 0.476883880133081, - 0, "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, - 0.0742142205600816, 0.898322136935257, 16, 0.486268178747669, - 0, "Total", 0.0207243321827093, 0.210235474446376, 2.31296920763817, - 0.0706762840519884, 0.89163869711842, 16, 0.481157490585204, - 1, "Total", 0.0215943194880837, 0.209433035387915, 2.29742881629919, - 0.0702171505907353, 0.891670674536477, 16, 0.480943912563606, - 0, "Total", 0.0217310553667567, 0.209558321077648, 2.29503610303025, - 0.0715087173730635, 0.893003296316988, 50, 0.482256006845026, - 0, "Total", 0.0213813272239098, 0.209568794483921, 2.3011823302826, - 0.0551225863409189, 0.88646190208963, 16, 0.470792244215275, - 0, "Total", 0.0264270643174027, 0.212080253082763, 2.21987779329719, - 0.0643801964874038, 0.889387563778757, 50, 0.476883880133081, - 1, "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, - 0.0742142205600816, 0.898322136935257, 16, 0.486268178747669, - 0, "Total", 0.0207243321827093, 0.210235474446376, 2.31296920763817, - 0.0706762840519884, 0.89163869711842, 84, 0.481157490585204, - 0, "Total", 0.0215943194880837, 0.209433035387915, 2.29742881629919, - 0.0702171505907353, 0.891670674536477, 16, 0.480943912563606, - 0, "Total", 0.0217310553667567, 0.209558321077648, 2.29503610303025, - 0.0715087173730635, 0.893003296316988, 84, 0.482256006845026, - 1, "Total", 0.0213813272239098, 0.209568794483921, 2.3011823302826, - 0.0551225863409189, 0.88646190208963, 16, 0.470792244215275, - 0, "Total", 0.0264270643174027, 0.212080253082763, 2.21987779329719, - 0.0643801964874038, 0.889387563778757, 16, 0.476883880133081, - 0, "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, - 0.0742142205600816, 0.898322136935257, 16, 0.486268178747669, - 1, "Total", 0.0207243321827093, 0.210235474446376, 2.31296920763817, - 0.0706762840519884, 0.89163869711842, 16, 0.481157490585204, - 1, "Total", 0.0215943194880837, 0.209433035387915, 2.29742881629919, - 0.0702171505907353, 0.891670674536477, 16, 0.480943912563606, - 1, "Total", 0.0217310553667567, 0.209558321077648, 2.29503610303025, - 0.0715087173730635, 0.893003296316988, 50, 0.482256006845026, - 0, "Total", 0.0213813272239098, 0.209568794483921, 2.3011823302826, - 0.0551225863409189, 0.88646190208963, 16, 0.470792244215275, - 1, "Total", 0.0264270643174027, 0.212080253082763, 2.21987779329719, - 0.0643801964874038, 0.889387563778757, 50, 0.476883880133081, - 1, "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, + list(0.0643801964874038, 0.889387563778757, "", 0.476883880133081, + "", "m", "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, 0.0742142205600816, 0.898322136935257, 16, 0.486268178747669, - 1, "Total", 0.0207243321827093, 0.210235474446376, 2.31296920763817, - 0.0706762840519884, 0.89163869711842, 84, 0.481157490585204, - 0, "Total", 0.0215943194880837, 0.209433035387915, 2.29742881629919, - 0.0702171505907353, 0.891670674536477, 16, 0.480943912563606, - 1, "Total", 0.0217310553667567, 0.209558321077648, 2.29503610303025, - 0.0715087173730635, 0.893003296316988, 84, 0.482256006845026, - 1, "Total", 0.0213813272239098, 0.209568794483921, 2.3011823302826, - 0.0551225863409189, 0.88646190208963, 16, 0.470792244215275, - 1, "Total", 0.0264270643174027, 0.212080253082763, 2.21987779329719, - 0.0643801964874038, 0.889387563778757, 16, 0.476883880133081, - 0, "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, - 0.0742142205600816, 0.898322136935257, 50, 0.486268178747669, - 0, "Total", 0.0207243321827093, 0.210235474446376, 2.31296920763817, + 0, "m", "Total", 0.0207243321827093, 0.210235474446376, 2.31296920763817, 0.0706762840519884, 0.89163869711842, 16, 0.481157490585204, - 1, "Total", 0.0215943194880837, 0.209433035387915, 2.29742881629919, + 1, "m", "Total", 0.0215943194880837, 0.209433035387915, 2.29742881629919, 0.0702171505907353, 0.891670674536477, 50, 0.480943912563606, - 0, "Total", 0.0217310553667567, 0.209558321077648, 2.29503610303025, + 0, "m", "Total", 0.0217310553667567, 0.209558321077648, 2.29503610303025, 0.0715087173730635, 0.893003296316988, 50, 0.482256006845026, - 0, "Total", 0.0213813272239098, 0.209568794483921, 2.3011823302826, - 0.0551225863409189, 0.88646190208963, 50, 0.470792244215275, - 0, "Total", 0.0264270643174027, 0.212080253082763, 2.21987779329719, - 0.0643801964874038, 0.889387563778757, 50, 0.476883880133081, - 1, "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, - 0.0742142205600816, 0.898322136935257, 50, 0.486268178747669, - 0, "Total", 0.0207243321827093, 0.210235474446376, 2.31296920763817, - 0.0706762840519884, 0.89163869711842, 84, 0.481157490585204, - 0, "Total", 0.0215943194880837, 0.209433035387915, 2.29742881629919, - 0.0702171505907353, 0.891670674536477, 50, 0.480943912563606, - 0, "Total", 0.0217310553667567, 0.209558321077648, 2.29503610303025, - 0.0715087173730635, 0.893003296316988, 84, 0.482256006845026, - 1, "Total", 0.0213813272239098, 0.209568794483921, 2.3011823302826, - 0.0551225863409189, 0.88646190208963, 50, 0.470792244215275, - 0, "Total", 0.0264270643174027, 0.212080253082763, 2.21987779329719, + 1, "m", "Total", 0.0213813272239098, 0.209568794483921, 2.3011823302826, + 0.0551225863409189, 0.88646190208963, 84, 0.470792244215275, + 0, "m", "Total", 0.0264270643174027, 0.212080253082763, 2.21987779329719, + 0.0643801964874038, 0.889387563778757, 84, 0.476883880133081, + 1, "m", "Total", 0.0234600108206691, 0.210464930427015, 2.26585911090045, -0.0560644004179153, 0.0459987548048033, 16, -0.00503282280655598, - 0, "Total indirect", 0.846727901291906, 0.0260369976254104, + 0, "m", "Total indirect", 0.846727901291906, 0.0260369976254104, -0.193295051870507, -0.0555869444398369, 0.0642898960559021, - 50, 0.00435147580803259, 1, "Total indirect", 0.886849652981579, + 16, 0.00435147580803259, 1, "m", "Total indirect", 0.886849652981579, 0.0305813885972682, 0.142291635783383, -0.0213440026029491, - 0.0198255778940844, 16, -0.000759212354432364, 1, "Total indirect", - 0.942372886213193, 0.0105026369927647, -0.0722877840065682, - -0.0615383274028843, 0.0595927466508237, 50, -0.000972790376030281, - 1, "Total indirect", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 50, 0.000339303905389171, 0, "Total indirect", 0.970936804446966, - 0.00931299746138703, 0.0364333724771183, -0.10816733883345, - 0.0859184213847258, 50, -0.0111244587243619, 1, "Total indirect", - 0.822228672322329, 0.0495125833303824, -0.224679424422915, -0.0560644004179153, - 0.0459987548048033, 50, -0.00503282280655598, 1, "Total indirect", - 0.846727901291906, 0.0260369976254104, -0.193295051870507, -0.0555869444398369, - 0.0642898960559021, 50, 0.00435147580803259, 1, "Total indirect", - 0.886849652981579, 0.0305813885972682, 0.142291635783383, -0.0213440026029491, - 0.0198255778940844, 84, -0.000759212354432364, 0, "Total indirect", + 0.0198255778940844, 50, -0.000759212354432364, 0, "m", "Total indirect", 0.942372886213193, 0.0105026369927647, -0.0722877840065682, -0.0615383274028843, 0.0595927466508237, 50, -0.000972790376030281, - 1, "Total indirect", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 84, 0.000339303905389171, 1, "Total indirect", 0.970936804446966, - 0.00931299746138703, 0.0364333724771183, -0.10816733883345, - 0.0859184213847258, 50, -0.0111244587243619, 1, "Total indirect", - 0.822228672322329, 0.0495125833303824, -0.224679424422915, -0.0560644004179153, - 0.0459987548048033, 16, -0.00503282280655598, 0, "Total indirect", - 0.846727901291906, 0.0260369976254104, -0.193295051870507, -0.0555869444398369, - 0.0642898960559021, 84, 0.00435147580803259, 0, "Total indirect", - 0.886849652981579, 0.0305813885972682, 0.142291635783383, -0.0213440026029491, - 0.0198255778940844, 16, -0.000759212354432364, 1, "Total indirect", - 0.942372886213193, 0.0105026369927647, -0.0722877840065682, - -0.0615383274028843, 0.0595927466508237, 84, -0.000972790376030281, - 0, "Total indirect", 0.974886333792357, 0.0309013520169693, + 1, "m", "Total indirect", 0.974886333792357, 0.0309013520169693, -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 50, 0.000339303905389171, 0, "Total indirect", 0.970936804446966, + 84, 0.000339303905389171, 0, "m", "Total indirect", 0.970936804446966, 0.00931299746138703, 0.0364333724771183, -0.10816733883345, - 0.0859184213847258, 84, -0.0111244587243619, 0, "Total indirect", - 0.822228672322329, 0.0495125833303824, -0.224679424422915, -0.0560644004179153, - 0.0459987548048033, 50, -0.00503282280655598, 1, "Total indirect", - 0.846727901291906, 0.0260369976254104, -0.193295051870507, -0.0555869444398369, - 0.0642898960559021, 84, 0.00435147580803259, 0, "Total indirect", - 0.886849652981579, 0.0305813885972682, 0.142291635783383, -0.0213440026029491, - 0.0198255778940844, 84, -0.000759212354432364, 0, "Total indirect", - 0.942372886213193, 0.0105026369927647, -0.0722877840065682, - -0.0615383274028843, 0.0595927466508237, 84, -0.000972790376030281, - 0, "Total indirect", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 84, 0.000339303905389171, 1, "Total indirect", 0.970936804446966, - 0.00931299746138703, 0.0364333724771183, -0.10816733883345, - 0.0859184213847258, 84, -0.0111244587243619, 0, "Total indirect", - 0.822228672322329, 0.0495125833303824, -0.224679424422915, -0.0560644004179153, - 0.0459987548048033, 16, -0.00503282280655598, 0, "Total indirect", - 0.846727901291906, 0.0260369976254104, -0.193295051870507, -0.0555869444398369, - 0.0642898960559021, 84, 0.00435147580803259, 1, "Total indirect", - 0.886849652981579, 0.0305813885972682, 0.142291635783383, -0.0213440026029491, - 0.0198255778940844, 16, -0.000759212354432364, 1, "Total indirect", - 0.942372886213193, 0.0105026369927647, -0.0722877840065682, - -0.0615383274028843, 0.0595927466508237, 84, -0.000972790376030281, - 1, "Total indirect", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 50, 0.000339303905389171, 0, "Total indirect", 0.970936804446966, - 0.00931299746138703, 0.0364333724771183, -0.10816733883345, - 0.0859184213847258, 84, -0.0111244587243619, 1, "Total indirect", - 0.822228672322329, 0.0495125833303824, -0.224679424422915, -0.0560644004179153, - 0.0459987548048033, 50, -0.00503282280655598, 1, "Total indirect", - 0.846727901291906, 0.0260369976254104, -0.193295051870507, -0.0555869444398369, - 0.0642898960559021, 84, 0.00435147580803259, 1, "Total indirect", - 0.886849652981579, 0.0305813885972682, 0.142291635783383, -0.0213440026029491, - 0.0198255778940844, 84, -0.000759212354432364, 0, "Total indirect", - 0.942372886213193, 0.0105026369927647, -0.0722877840065682, - -0.0615383274028843, 0.0595927466508237, 84, -0.000972790376030281, - 1, "Total indirect", 0.974886333792357, 0.0309013520169693, - -0.0314805117748919, -0.0179138357070423, 0.0185924435178207, - 84, 0.000339303905389171, 1, "Total indirect", 0.970936804446966, - 0.00931299746138703, 0.0364333724771183, -0.10816733883345, - 0.0859184213847258, 84, -0.0111244587243619, 1, "Total indirect", - 0.822228672322329, 0.0495125833303824, -0.224679424422915, 16, - 0, 16, 0, 16, 1, 16, 0, 50, 0, 16, 0, 50, 1, 16, 0, 84, 0, 16, - 0, 84, 1, 16, 0, 16, 0, 16, 1, 16, 1, 16, 1, 50, 0, 16, 1, 50, - 1, 16, 1, 84, 0, 16, 1, 84, 1, 16, 1, 16, 0, 50, 0, 16, 1, 50, - 0, 50, 0, 50, 0, 50, 1, 50, 0, 84, 0, 50, 0, 84, 1, 50, 0, 16, - 0, 50, 1, 16, 1, 50, 1, 50, 0, 50, 1, 50, 1, 50, 1, 84, 0, 50, - 1, 84, 1, 50, 1, 16, 0, 84, 0, 16, 1, 84, 0, 50, 0, 84, 0, 50, - 1, 84, 0, 84, 0, 84, 0, 84, 1, 84, 0, 16, 0, 84, 1, 16, 1, 84, - 1, 50, 0, 84, 1, 50, 1, 84, 1, 84, 0, 84, 1, 84, 1, 84, 1)) + 0.0859184213847258, 84, -0.0111244587243619, 1, "m", "Total indirect", + 0.822228672322329, 0.0495125833303824, -0.224679424422915)) @@ -15123,7 +11824,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 76 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -15134,31 +11835,31 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "debCollin1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "debCollin1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -15200,272 +11901,56 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) - table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] - jaspTools::expect_equal_tables(table, - list(-0.209487052571584, 0.166373313108294, 16, 16, -0.0215568697316452, - "contGamma", "contNormal", "", "", "", 0.822118376858699, - 0.0958845082472475, -0.224821195057482, -0.198507156295151, - 0.314044882590122, 50, 16, 0.0577688631474854, "contGamma", - "contNormal", "", "", "", 0.658627879059944, 0.130755473806718, - 0.441808373031321, -0.344935429635909, 0.633621066724908, 84, - 16, 0.1443428185445, "contGamma", "contNormal", "", "", - "", 0.563120761663243, 0.249636346402165, 0.578212350183827, - -0.366989137192483, 0.186094127828773, 16, 50, -0.0904475046818552, - "contGamma", "contNormal", "", "", "", 0.521497626330998, - 0.141095262306835, -0.641038566448548, -0.146446744676708, 0.124203201071259, - 50, 50, -0.0111217718027246, "contGamma", "contNormal", "", - "", "", 0.872029661530486, 0.06904462221827, -0.161080927745038, - -0.233445962934013, 0.384350330122593, 84, 50, 0.0754521835942898, - "contGamma", "contNormal", "", "", "", 0.632119773636923, - 0.157603991177824, 0.478745386017271, -0.669519488667256, 0.3271236827543, - 16, 84, -0.171197902956478, "contGamma", "contNormal", "", "", - "", 0.500728626972581, 0.254250378905671, -0.673343747581958, - -0.385811827615258, 0.202067487460564, 50, 84, -0.091872170077347, - "contGamma", "contNormal", "", "", "", 0.540143760071537, - 0.149971968799667, -0.612595612451219, -0.229492994523592, 0.218896565162927, - 84, 84, -0.00529821468033251, "contGamma", "contNormal", "", - "", "", 0.963056593187583, 0.114387193648291, -0.0463182504207861, - -0.0198745141502388, 0.0329039942745475, 16, 16, 0.00651474006215433, - "contGamma", "debCollin1", "contNormal", "", "", - 0.628486538374031, 0.0134641526173686, 0.483858156342524, -0.0737508294034688, - 0.0369338283476415, 16, 16, -0.0184085005279136, "contGamma", - "debCollin1", "contNormal", "", "", 0.514438478732355, - 0.0282364009298581, -0.651942171158502, -0.312135653893738, - 0.149930530967953, 50, 16, -0.0811025614628925, "contGamma", - "debCollin1", "contNormal", "", "", 0.491432796834181, - 0.117876192753135, -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 16, 16, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 84, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 16, 16, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, - 50, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 16, - 16, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 50, 50, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 16, 16, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 84, 50, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 16, - 16, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 16, 84, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 16, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 50, 84, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, - 16, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 84, - 84, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 16, 16, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 16, 16, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 50, 16, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 50, - 16, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 50, 16, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 84, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 50, 16, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, - 50, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 50, - 16, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 50, 50, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 50, 16, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 84, 50, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 50, - 16, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 16, 84, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 50, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 50, 84, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 50, - 16, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 84, - 84, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 50, 16, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 16, 16, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 84, 16, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 50, - 16, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 84, 16, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 84, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 84, 16, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, - 50, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 84, - 16, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 50, 50, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 84, 16, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 84, 50, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 84, - 16, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 16, 84, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 84, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 50, 84, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 84, - 16, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 84, - 84, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 84, 16, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 16, 16, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 16, 50, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 50, - 16, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, + table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] + jaspTools::expect_equal_tables(table, + list(-0.209487052571584, 0.166373313108294, 16, 16, -0.0215568697316452, + "contGamma", "contNormal", "", "", "", 0.822118376858699, + 0.0958845082472475, -0.224821195057482, -0.198507156295151, + 0.314044882590122, 50, 16, 0.0577688631474854, "contGamma", + "contNormal", "", "", "", 0.658627879059944, 0.130755473806718, + 0.441808373031321, -0.344935429635909, 0.633621066724908, 84, + 16, 0.1443428185445, "contGamma", "contNormal", "", "", + "", 0.563120761663243, 0.249636346402165, 0.578212350183827, + -0.366989137192483, 0.186094127828773, 16, 50, -0.0904475046818552, + "contGamma", "contNormal", "", "", "", 0.521497626330998, + 0.141095262306835, -0.641038566448548, -0.146446744676708, 0.124203201071259, + 50, 50, -0.0111217718027246, "contGamma", "contNormal", "", + "", "", 0.872029661530486, 0.06904462221827, -0.161080927745038, + -0.233445962934013, 0.384350330122593, 84, 50, 0.0754521835942898, + "contGamma", "contNormal", "", "", "", 0.632119773636923, + 0.157603991177824, 0.478745386017271, -0.669519488667256, 0.3271236827543, + 16, 84, -0.171197902956478, "contGamma", "contNormal", "", "", + "", 0.500728626972581, 0.254250378905671, -0.673343747581958, + -0.385811827615258, 0.202067487460564, 50, 84, -0.091872170077347, + "contGamma", "contNormal", "", "", "", 0.540143760071537, + 0.149971968799667, -0.612595612451219, -0.229492994523592, 0.218896565162927, + 84, 84, -0.00529821468033251, "contGamma", "contNormal", "", + "", "", 0.963056593187583, 0.114387193648291, -0.0463182504207861, + -0.0198745141502388, 0.0329039942745475, 16, 16, 0.00651474006215433, + "contGamma", "debCollin1", "contNormal", "", "", + 0.628486538374031, 0.0134641526173686, 0.483858156342524, -0.0737508294034688, + 0.0369338283476415, 50, 16, -0.0184085005279136, "contGamma", + "debCollin1", "contNormal", "", "", 0.514438478732355, + 0.0282364009298581, -0.651942171158502, -0.312135653893738, + 0.149930530967953, 84, 16, -0.0811025614628925, "contGamma", + "debCollin1", "contNormal", "", "", 0.491432796834181, + 0.117876192753135, -0.68803173540516, -0.0534540233955156, 0.0850202546172222, 16, 50, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", "", "", 0.655027976839516, 0.0353257200400123, 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 84, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", + 50, 50, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", "", "", 0.86402361971876, 0.0124062149782668, -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 16, 50, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", + 84, 50, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", "", "", 0.322156782040888, 0.0577374771766478, -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, - 50, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 16, - 50, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 50, 50, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 16, 50, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 84, 50, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 16, - 50, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 16, 84, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 16, 50, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 50, 84, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, - 50, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", - "", "", 0.785869449023718, 0.103464433358305, - 0.271678220662647, -0.039486753857856, 0.0763358431781959, 84, - 84, 0.01842454466017, "contGamma", "debCollin1", "contNormal", - "", "", 0.532913471186987, 0.0295471238118776, - 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 16, 50, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", - "", "", 0.421878392890796, 0.034411729649451, - -0.803166694660131, -0.0198745141502388, 0.0329039942745475, - 16, 16, 0.00651474006215433, "contGamma", "debCollin1", "contNormal", - "", "", 0.628486538374031, 0.0134641526173686, - 0.483858156342524, -0.0737508294034688, 0.0369338283476415, - 50, 50, -0.0184085005279136, "contGamma", "debCollin1", "contNormal", - "", "", 0.514438478732355, 0.0282364009298581, - -0.651942171158502, -0.312135653893738, 0.149930530967953, 50, - 16, -0.0811025614628925, "contGamma", "debCollin1", "contNormal", - "", "", 0.491432796834181, 0.117876192753135, - -0.68803173540516, -0.0534540233955156, 0.0850202546172222, - 50, 50, 0.0157831156108533, "contGamma", "debCollin1", "contNormal", - "", "", 0.655027976839516, 0.0353257200400123, - 0.446788220961279, -0.0264403552509462, 0.0221911138327824, - 84, 16, -0.00212462070908189, "contGamma", "debCollin1", "contNormal", - "", "", 0.86402361971876, 0.0124062149782668, - -0.171254545629251, -0.170325526205234, 0.0560012254436319, - 50, 50, -0.0571621503808012, "contGamma", "debCollin1", "contNormal", - "", "", 0.322156782040888, 0.0577374771766478, - -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, - 50, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", + 84, 0.0281090331566532, "contGamma", "debCollin1", "contNormal", "", "", 0.785869449023718, 0.103464433358305, 0.271678220662647, -0.039486753857856, 0.0763358431781959, 50, - 50, 0.01842454466017, "contGamma", "debCollin1", "contNormal", + 84, 0.01842454466017, "contGamma", "debCollin1", "contNormal", "", "", 0.532913471186987, 0.0295471238118776, 0.623564742797859, -0.0950841059187408, 0.0398073955985655, - 50, 50, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", + 84, 84, -0.0276383551600876, "contGamma", "debCollin1", "contNormal", "", "", 0.421878392890796, 0.034411729649451, -0.803166694660131)) @@ -15529,350 +12014,41 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, -0.201939371322057, 0.171855111983075, 16, 16, -0.0150421296694909, "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 16, 16, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 50, 16, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 16, 16, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 84, 16, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 16, 16, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 16, 50, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 16, 16, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 50, 50, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 16, 16, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 84, 50, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 16, 16, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 16, 84, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 16, 16, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 50, 84, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 16, 16, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 84, 84, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 16, 16, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 16, 16, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, -0.21615091205307, 0.294871637292213, 50, 16, 0.0393603626195717, "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 50, 16, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 50, 16, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 84, 16, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 50, 16, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 16, 50, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 50, 16, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 50, 50, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 50, 16, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 84, 50, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 50, 16, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 16, 84, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 50, 16, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 50, 84, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 50, 16, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 84, 84, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 50, 16, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 16, 16, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 84, 16, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 50, 16, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 84, 16, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 84, 16, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 84, 16, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 16, 50, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 84, 16, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 50, 50, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 84, 16, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 84, 50, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, -0.452408257127035, 0.578888771290249, 84, 16, 0.0632402570816074, "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 16, 84, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 84, 16, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 50, 84, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 84, 16, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 84, 84, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 84, 16, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 16, 16, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 16, 50, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 50, 16, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, -0.355376974351899, 0.206048196209895, 16, 50, -0.0746643890710019, "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 84, 16, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 16, 50, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 16, 50, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 16, 50, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 50, 50, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 16, 50, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 84, 50, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 16, 50, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 16, 84, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 16, 50, -0.0132463925118065, - "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 50, 84, 0.0182900332134886, - "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 16, 50, -0.143088869799824, - "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 84, 84, -0.073447625417177, - "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 16, 50, -0.0329365698404201, - "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.201939371322057, 0.171855111983075, 16, 16, -0.0150421296694909, - "Total", 0.874658047226888, 0.095357487753238, -0.157744609510018, - -0.21615091205307, 0.294871637292213, 50, 50, 0.0393603626195717, - "Total", 0.762710276972218, 0.130365290733953, 0.301923636252977, - -0.452408257127035, 0.578888771290249, 50, 16, 0.0632402570816074, - "Total", 0.810040136519876, 0.263090810992453, 0.240374252688823, - -0.355376974351899, 0.206048196209895, 50, 50, -0.0746643890710019, - "Total", 0.602147769909651, 0.143223338538423, -0.521314401919009, - -0.146170671428372, 0.119677886404759, 84, 16, -0.0132463925118065, + -0.146170671428372, 0.119677886404759, 50, 50, -0.0132463925118065, "Total", 0.845144313070626, 0.0678197558552378, -0.195317608339392, - -0.285641873868809, 0.322221940295786, 50, 50, 0.0182900332134886, + -0.285641873868809, 0.322221940295786, 84, 50, 0.0182900332134886, "Total", 0.906109783565435, 0.155070148982162, 0.117946834600595, - -0.674744508744466, 0.388566769144817, 16, 50, -0.143088869799824, + -0.674744508744466, 0.388566769144817, 16, 84, -0.143088869799824, "Total", 0.597845526048728, 0.271257861439431, -0.527501282508542, - -0.36793843105186, 0.221043180217506, 50, 50, -0.073447625417177, + -0.36793843105186, 0.221043180217506, 50, 84, -0.073447625417177, "Total", 0.624965038118574, 0.150253171975398, -0.488825789509476, - -0.246565549780865, 0.180692410100025, 50, 50, -0.0329365698404201, + -0.246565549780865, 0.180692410100025, 84, 84, -0.0329365698404201, "Total", 0.762514544602994, 0.108996380354702, -0.302180400241147, - -0.0198745141502388, 0.0329039942745475, 50, 50, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 84, 50, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 50, 50, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 16, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 50, 50, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 50, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 50, 50, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 84, 84, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 50, 50, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, -0.0198745141502388, 0.0329039942745475, 16, 16, 0.00651474006215433, "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 84, 50, -0.0184085005279136, + -0.0737508294034688, 0.0369338283476415, 50, 16, -0.0184085005279136, "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 50, 16, -0.0811025614628925, + -0.312135653893738, 0.149930530967953, 84, 16, -0.0811025614628925, "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 84, 50, 0.0157831156108533, + -0.0534540233955156, 0.0850202546172222, 16, 50, 0.0157831156108533, "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 84, 16, -0.00212462070908189, + -0.0264403552509462, 0.0221911138327824, 50, 50, -0.00212462070908189, "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, -0.170325526205234, 0.0560012254436319, 84, 50, -0.0571621503808012, "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 16, 50, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 84, 50, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 50, 50, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - -0.0198745141502388, 0.0329039942745475, 84, 50, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 84, 50, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 84, 50, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 16, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 84, 50, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 50, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 84, 50, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 84, 84, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 84, 50, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - -0.0198745141502388, 0.0329039942745475, 16, 16, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 16, 84, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 50, 16, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 16, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 84, 16, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 16, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 16, 50, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 16, 84, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 50, 50, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - -0.0198745141502388, 0.0329039942745475, 16, 84, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 84, 50, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 16, 84, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 16, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 16, 84, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 50, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, -0.174677529906469, 0.230895596219775, 16, 84, 0.0281090331566532, "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 84, 84, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 16, 84, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - -0.0198745141502388, 0.0329039942745475, 16, 16, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 50, 84, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 50, 16, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 50, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 84, 16, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 50, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 16, 50, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, -0.039486753857856, 0.0763358431781959, 50, 84, 0.01842454466017, "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 50, 50, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - -0.0198745141502388, 0.0329039942745475, 50, 84, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 84, 50, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 50, 84, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 16, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 50, 84, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 50, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 50, 84, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 84, 84, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 50, 84, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - -0.0198745141502388, 0.0329039942745475, 16, 16, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 84, 84, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 50, 16, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 84, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 84, 16, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 84, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 16, 50, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 84, 84, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, - -0.0950841059187408, 0.0398073955985655, 50, 50, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - -0.0198745141502388, 0.0329039942745475, 84, 84, 0.00651474006215433, - "Total indirect", 0.628486538374031, 0.0134641526173686, 0.483858156342524, - -0.0737508294034688, 0.0369338283476415, 84, 50, -0.0184085005279136, - "Total indirect", 0.514438478732355, 0.0282364009298581, -0.651942171158502, - -0.312135653893738, 0.149930530967953, 84, 84, -0.0811025614628925, - "Total indirect", 0.491432796834181, 0.117876192753135, -0.68803173540516, - -0.0534540233955156, 0.0850202546172222, 16, 84, 0.0157831156108533, - "Total indirect", 0.655027976839516, 0.0353257200400123, 0.446788220961279, - -0.0264403552509462, 0.0221911138327824, 84, 84, -0.00212462070908189, - "Total indirect", 0.86402361971876, 0.0124062149782668, -0.171254545629251, - -0.170325526205234, 0.0560012254436319, 50, 84, -0.0571621503808012, - "Total indirect", 0.322156782040888, 0.0577374771766478, -0.990035470478101, - -0.174677529906469, 0.230895596219775, 84, 84, 0.0281090331566532, - "Total indirect", 0.785869449023718, 0.103464433358305, 0.271678220662647, - -0.039486753857856, 0.0763358431781959, 84, 84, 0.01842454466017, - "Total indirect", 0.532913471186987, 0.0295471238118776, 0.623564742797859, -0.0950841059187408, 0.0398073955985655, 84, 84, -0.0276383551600876, - "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131, - 16, 16, 16, 16, 50, 16, 16, 16, 84, 16, 16, 16, 16, 50, 16, - 16, 50, 50, 16, 16, 84, 50, 16, 16, 16, 84, 16, 16, 50, 84, - 16, 16, 84, 84, 16, 16, 16, 16, 50, 16, 50, 16, 50, 16, 84, - 16, 50, 16, 16, 50, 50, 16, 50, 50, 50, 16, 84, 50, 50, 16, - 16, 84, 50, 16, 50, 84, 50, 16, 84, 84, 50, 16, 16, 16, 84, - 16, 50, 16, 84, 16, 84, 16, 84, 16, 16, 50, 84, 16, 50, 50, - 84, 16, 84, 50, 84, 16, 16, 84, 84, 16, 50, 84, 84, 16, 84, - 84, 84, 16, 16, 16, 16, 50, 50, 16, 16, 50, 84, 16, 16, 50, - 16, 50, 16, 50, 50, 50, 16, 50, 84, 50, 16, 50, 16, 84, 16, - 50, 50, 84, 16, 50, 84, 84, 16, 50, 16, 16, 50, 50, 50, 16, - 50, 50, 84, 16, 50, 50, 16, 50, 50, 50, 50, 50, 50, 50, 84, - 50, 50, 50, 16, 84, 50, 50, 50, 84, 50, 50, 84, 84, 50, 50, - 16, 16, 84, 50, 50, 16, 84, 50, 84, 16, 84, 50, 16, 50, 84, - 50, 50, 50, 84, 50, 84, 50, 84, 50, 16, 84, 84, 50, 50, 84, - 84, 50, 84, 84, 84, 50, 16, 16, 16, 84, 50, 16, 16, 84, 84, - 16, 16, 84, 16, 50, 16, 84, 50, 50, 16, 84, 84, 50, 16, 84, - 16, 84, 16, 84, 50, 84, 16, 84, 84, 84, 16, 84, 16, 16, 50, - 84, 50, 16, 50, 84, 84, 16, 50, 84, 16, 50, 50, 84, 50, 50, - 50, 84, 84, 50, 50, 84, 16, 84, 50, 84, 50, 84, 50, 84, 84, - 84, 50, 84, 16, 16, 84, 84, 50, 16, 84, 84, 84, 16, 84, 84, - 16, 50, 84, 84, 50, 50, 84, 84, 84, 50, 84, 84, 16, 84, 84, - 84, 50, 84, 84, 84, 84, 84, 84, 84)) + "Total indirect", 0.421878392890796, 0.034411729649451, -0.803166694660131 + )) @@ -15888,7 +12064,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 76 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -15899,31 +12075,31 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", - processVariable = "debCollin1"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "facExperim"), list(processDependent = "debCollin1", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "debCollin1", processType = "moderators", - processVariable = "contcor2"), list(processDependent = "contNormal", - processIndependent = "facGender", processType = "moderators", - processVariable = "contcor2")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", + processVariable = "debCollin1"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "facExperim"), list(processDependent = "debCollin1", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "debCollin1", processType = "moderators", + processVariable = "contcor2"), list(processDependent = "contNormal", + processIndependent = "facGender", processType = "moderators", + processVariable = "contcor2")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -15970,128 +12146,39 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_mediationEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.175783430370312, 1.32274378031512, 16, 0.573480174972406, 0, - "facGenderm", "contNormal", "", "", "", 0.133578077862812, + "m", "facGender", "contNormal", "", "", "", 0.133578077862812, 0.382284374229738, 1.50014024540738, -0.362716053008532, 1.00606619819138, - 16, 0.321675072591423, 1, "facGenderm", "contNormal", "", "", - "", 0.356938046359087, 0.349185562080908, 0.921215272116231, + 16, 0.321675072591423, 1, "m", "facGender", "contNormal", "", + "", "", 0.356938046359087, 0.349185562080908, 0.921215272116231, 0.0235481260619423, 1.18422554846151, 50, 0.603886837261728, - 0, "facGenderm", "contNormal", "", "", "", 0.0414008985094156, + 0, "m", "facGender", "contNormal", "", "", "", 0.0414008985094156, 0.296096620028441, 2.03949250485778, -0.236088085529856, 0.940251555291348, - 50, 0.352081734880746, 1, "facGenderm", "contNormal", "", "", - "", 0.240697421783395, 0.300092157330446, 1.17324537239756, + 50, 0.352081734880746, 1, "m", "facGender", "contNormal", "", + "", "", 0.240697421783395, 0.300092157330446, 1.17324537239756, -0.0534551055770377, 1.33251133082279, 84, 0.639528112622876, - 0, "facGenderm", "contNormal", "", "", "", 0.0704856635379627, + 0, "m", "facGender", "contNormal", "", "", "", 0.0704856635379627, 0.35356936334855, 1.80877694426377, -0.392737323377006, 1.16818334386079, - 84, 0.387723010241894, 1, "facGenderm", "contNormal", "", "", - "", 0.330212575270802, 0.398201364808268, 0.973685789421091, + 84, 0.387723010241894, 1, "m", "facGender", "contNormal", "", + "", "", 0.330212575270802, 0.398201364808268, 0.973685789421091, -0.056938399914368, 0.0465244819870263, 16, -0.00520695896367084, - 0, "facGenderm", "debCollin1", "contNormal", "", "", - 0.84361034497157, 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 16, 0.00502850532842074, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.871181679630224, - 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 16, -0.0009217737969145, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.931396220985835, - 0.0107073057745262, -0.0860883042219167, -0.06047820206868, - 0.060652748660656, 16, 8.72732959880079e-05, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746571291635, - 0.0309013205560922, 0.00282425781220543, -0.0157871436682365, - 0.0163794388900215, 50, 0.000296147610892528, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 16, -0.00950958242840603, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.846557714792424, - 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 50, -0.00520695896367084, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.84361034497157, - 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 16, 0.00502850532842074, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.871181679630224, - 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 84, -0.0009217737969145, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.931396220985835, - 0.0107073057745262, -0.0860883042219167, -0.06047820206868, - 0.060652748660656, 16, 8.72732959880079e-05, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746571291635, - 0.0309013205560922, 0.00282425781220543, -0.0157871436682365, - 0.0163794388900215, 84, 0.000296147610892528, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 16, -0.00950958242840603, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.846557714792424, - 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 16, -0.00520695896367084, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.84361034497157, - 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 16, 0.00502850532842074, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.871181679630224, - 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 16, -0.0009217737969145, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.931396220985835, - 0.0107073057745262, -0.0860883042219167, -0.06047820206868, - 0.060652748660656, 16, 8.72732959880079e-05, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746571291635, - 0.0309013205560922, 0.00282425781220543, -0.0157871436682365, - 0.0163794388900215, 50, 0.000296147610892528, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 16, -0.00950958242840603, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.846557714792424, - 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 50, -0.00520695896367084, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.84361034497157, - 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 16, 0.00502850532842074, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.871181679630224, - 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 84, -0.0009217737969145, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.931396220985835, - 0.0107073057745262, -0.0860883042219167, -0.06047820206868, - 0.060652748660656, 16, 8.72732959880079e-05, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746571291635, - 0.0309013205560922, 0.00282425781220543, -0.0157871436682365, - 0.0163794388900215, 84, 0.000296147610892528, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 16, -0.00950958242840603, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.846557714792424, - 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 16, -0.00520695896367084, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.84361034497157, - 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 50, 0.00502850532842074, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.871181679630224, - 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 16, -0.0009217737969145, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.931396220985835, - 0.0107073057745262, -0.0860883042219167, -0.06047820206868, - 0.060652748660656, 50, 8.72732959880079e-05, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746571291635, - 0.0309013205560922, 0.00282425781220543, -0.0157871436682365, - 0.0163794388900215, 50, 0.000296147610892528, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 50, -0.00950958242840603, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.846557714792424, - 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 50, -0.00520695896367084, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.84361034497157, - 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 50, 0.00502850532842074, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.871181679630224, - 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 84, -0.0009217737969145, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.931396220985835, - 0.0107073057745262, -0.0860883042219167, -0.06047820206868, - 0.060652748660656, 50, 8.72732959880079e-05, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.997746571291635, - 0.0309013205560922, 0.00282425781220543, -0.0157871436682365, - 0.0163794388900215, 84, 0.000296147610892528, 1, "facGenderm", - "debCollin1", "contNormal", "", "", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 50, -0.00950958242840603, 0, "facGenderm", - "debCollin1", "contNormal", "", "", 0.846557714792424, - 0.0491419858386659, -0.193512375743752)) + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.84361034497157, 0.0263940773191488, -0.197277552107995, + -0.0557499229035051, 0.0658069335603466, 16, 0.00502850532842074, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.871181679630224, 0.0310099719746579, 0.162157686970184, + -0.0219077074864437, 0.0200641598926147, 50, -0.0009217737969145, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.931396220985835, 0.0107073057745262, -0.0860883042219167, + -0.06047820206868, 0.060652748660656, 50, 8.72732959880079e-05, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.997746571291635, 0.0309013205560922, 0.00282425781220543, + -0.0157871436682365, 0.0163794388900215, 84, 0.000296147610892528, + 0, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.971210959420073, 0.00820591164225055, 0.0360895441973473, + -0.105826104800968, 0.0868069399441564, 84, -0.00950958242840603, + 1, "m", "facGender", "debCollin1", "contNormal", "", + "", 0.846557714792424, 0.0491419858386659, -0.193512375743752 + )) @@ -16134,176 +12221,43 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) table <- results[["results"]][["parEstContainer"]][["collection"]][["parEstContainer_Model 1"]][["collection"]][["parEstContainer_Model 1_totalEffectsTable"]][["data"]] jaspTools::expect_equal_tables(table, list(-0.184490377888482, 1.32103680990595, 16, 0.568273216008735, 0, - "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, + "m", "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, -0.356853796700267, 1.01026095253995, 16, 0.326703577919844, - 1, "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, + 1, "m", "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, 0.0227613028808017, 1.18316882404883, 50, 0.602965063464814, - 0, "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, + 0, "m", "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, -0.233249105342029, 0.937587121695497, 50, 0.352169008176734, - 1, "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, + 1, "m", "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, -0.0533577366790818, 1.33300625714662, 84, 0.639824260233769, - 0, "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, + 0, "m", "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, -0.394192438580395, 1.15061929420737, 84, 0.378213427813488, - 1, "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, - -0.184490377888482, 1.32103680990595, 16, 0.568273216008735, - 0, "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, - -0.356853796700267, 1.01026095253995, 16, 0.326703577919844, - 0, "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, - 0.0227613028808017, 1.18316882404883, 16, 0.602965063464814, - 1, "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, - -0.233249105342029, 0.937587121695497, 16, 0.352169008176734, - 0, "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, - -0.0533577366790818, 1.33300625714662, 50, 0.639824260233769, - 0, "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, - -0.394192438580395, 1.15061929420737, 16, 0.378213427813488, - 0, "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, - -0.184490377888482, 1.32103680990595, 50, 0.568273216008735, - 1, "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, - -0.356853796700267, 1.01026095253995, 16, 0.326703577919844, - 0, "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, - 0.0227613028808017, 1.18316882404883, 84, 0.602965063464814, - 0, "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, - -0.233249105342029, 0.937587121695497, 16, 0.352169008176734, - 0, "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, - -0.0533577366790818, 1.33300625714662, 84, 0.639824260233769, - 1, "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, - -0.394192438580395, 1.15061929420737, 16, 0.378213427813488, - 0, "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, + 1, "m", "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, -0.184490377888482, 1.32103680990595, 16, 0.568273216008735, - 0, "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, - -0.356853796700267, 1.01026095253995, 16, 0.326703577919844, - 1, "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, - 0.0227613028808017, 1.18316882404883, 16, 0.602965063464814, - 1, "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, - -0.233249105342029, 0.937587121695497, 16, 0.352169008176734, - 1, "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, - -0.0533577366790818, 1.33300625714662, 50, 0.639824260233769, - 0, "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, - -0.394192438580395, 1.15061929420737, 16, 0.378213427813488, - 1, "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, - -0.184490377888482, 1.32103680990595, 50, 0.568273216008735, - 1, "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, + 0, "m", "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, -0.356853796700267, 1.01026095253995, 16, 0.326703577919844, - 1, "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, - 0.0227613028808017, 1.18316882404883, 84, 0.602965063464814, - 0, "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, - -0.233249105342029, 0.937587121695497, 16, 0.352169008176734, - 1, "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, - -0.0533577366790818, 1.33300625714662, 84, 0.639824260233769, - 1, "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, - -0.394192438580395, 1.15061929420737, 16, 0.378213427813488, - 1, "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, - -0.184490377888482, 1.32103680990595, 16, 0.568273216008735, - 0, "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, - -0.356853796700267, 1.01026095253995, 50, 0.326703577919844, - 0, "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, - 0.0227613028808017, 1.18316882404883, 16, 0.602965063464814, - 1, "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, - -0.233249105342029, 0.937587121695497, 50, 0.352169008176734, - 0, "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, - -0.0533577366790818, 1.33300625714662, 50, 0.639824260233769, - 0, "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, - -0.394192438580395, 1.15061929420737, 50, 0.378213427813488, - 0, "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, - -0.184490377888482, 1.32103680990595, 50, 0.568273216008735, - 1, "Total", 0.138977889898212, 0.384070115489325, 1.4796080014836, - -0.356853796700267, 1.01026095253995, 50, 0.326703577919844, - 0, "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, - 0.0227613028808017, 1.18316882404883, 84, 0.602965063464814, - 0, "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, + 1, "m", "Total", 0.348883500311954, 0.348760171111268, 0.936757132785134, + 0.0227613028808017, 1.18316882404883, 50, 0.602965063464814, + 0, "m", "Total", 0.0416647686901808, 0.296027766408253, 2.03685306544273, -0.233249105342029, 0.937587121695497, 50, 0.352169008176734, - 0, "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, + 1, "m", "Total", 0.238377351325861, 0.298688199444717, 1.17905229878998, -0.0533577366790818, 1.33300625714662, 84, 0.639824260233769, - 1, "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, - -0.394192438580395, 1.15061929420737, 50, 0.378213427813488, - 0, "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, + 0, "m", "Total", 0.0704361512258098, 0.35367078292284, 1.80909560848106, + -0.394192438580395, 1.15061929420737, 84, 0.378213427813488, + 1, "m", "Total", 0.337201799708859, 0.394091867241706, 0.959708786838579, -0.056938399914368, 0.0465244819870263, 16, -0.00520695896367084, - 0, "Total indirect", 0.84361034497157, 0.0263940773191488, -0.197277552107995, - -0.0557499229035051, 0.0658069335603466, 50, 0.00502850532842074, - 1, "Total indirect", 0.871181679630224, 0.0310099719746579, - 0.162157686970184, -0.0219077074864437, 0.0200641598926147, - 16, -0.0009217737969145, 1, "Total indirect", 0.931396220985835, - 0.0107073057745262, -0.0860883042219167, -0.06047820206868, - 0.060652748660656, 50, 8.72732959880079e-05, 1, "Total indirect", - 0.997746571291635, 0.0309013205560922, 0.00282425781220543, - -0.0157871436682365, 0.0163794388900215, 50, 0.000296147610892528, - 0, "Total indirect", 0.971210959420073, 0.00820591164225055, - 0.0360895441973473, -0.105826104800968, 0.0868069399441564, - 50, -0.00950958242840603, 1, "Total indirect", 0.846557714792424, - 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 50, -0.00520695896367084, 1, "Total indirect", - 0.84361034497157, 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 50, 0.00502850532842074, 1, "Total indirect", - 0.871181679630224, 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 84, -0.0009217737969145, 0, "Total indirect", + 0, "m", "Total indirect", 0.84361034497157, 0.0263940773191488, + -0.197277552107995, -0.0557499229035051, 0.0658069335603466, + 16, 0.00502850532842074, 1, "m", "Total indirect", 0.871181679630224, + 0.0310099719746579, 0.162157686970184, -0.0219077074864437, + 0.0200641598926147, 50, -0.0009217737969145, 0, "m", "Total indirect", 0.931396220985835, 0.0107073057745262, -0.0860883042219167, -0.06047820206868, 0.060652748660656, 50, 8.72732959880079e-05, - 1, "Total indirect", 0.997746571291635, 0.0309013205560922, - 0.00282425781220543, -0.0157871436682365, 0.0163794388900215, - 84, 0.000296147610892528, 1, "Total indirect", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 50, -0.00950958242840603, 1, "Total indirect", - 0.846557714792424, 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 16, -0.00520695896367084, 0, "Total indirect", - 0.84361034497157, 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 84, 0.00502850532842074, 0, "Total indirect", - 0.871181679630224, 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 16, -0.0009217737969145, 1, "Total indirect", - 0.931396220985835, 0.0107073057745262, -0.0860883042219167, - -0.06047820206868, 0.060652748660656, 84, 8.72732959880079e-05, - 0, "Total indirect", 0.997746571291635, 0.0309013205560922, - 0.00282425781220543, -0.0157871436682365, 0.0163794388900215, - 50, 0.000296147610892528, 0, "Total indirect", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 84, -0.00950958242840603, 0, "Total indirect", - 0.846557714792424, 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 50, -0.00520695896367084, 1, "Total indirect", - 0.84361034497157, 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 84, 0.00502850532842074, 0, "Total indirect", - 0.871181679630224, 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 84, -0.0009217737969145, 0, "Total indirect", - 0.931396220985835, 0.0107073057745262, -0.0860883042219167, - -0.06047820206868, 0.060652748660656, 84, 8.72732959880079e-05, - 0, "Total indirect", 0.997746571291635, 0.0309013205560922, - 0.00282425781220543, -0.0157871436682365, 0.0163794388900215, - 84, 0.000296147610892528, 1, "Total indirect", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 84, -0.00950958242840603, 0, "Total indirect", - 0.846557714792424, 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 16, -0.00520695896367084, 0, "Total indirect", - 0.84361034497157, 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 84, 0.00502850532842074, 1, "Total indirect", - 0.871181679630224, 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 16, -0.0009217737969145, 1, "Total indirect", - 0.931396220985835, 0.0107073057745262, -0.0860883042219167, - -0.06047820206868, 0.060652748660656, 84, 8.72732959880079e-05, - 1, "Total indirect", 0.997746571291635, 0.0309013205560922, - 0.00282425781220543, -0.0157871436682365, 0.0163794388900215, - 50, 0.000296147610892528, 0, "Total indirect", 0.971210959420073, - 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 84, -0.00950958242840603, 1, "Total indirect", - 0.846557714792424, 0.0491419858386659, -0.193512375743752, -0.056938399914368, - 0.0465244819870263, 50, -0.00520695896367084, 1, "Total indirect", - 0.84361034497157, 0.0263940773191488, -0.197277552107995, -0.0557499229035051, - 0.0658069335603466, 84, 0.00502850532842074, 1, "Total indirect", - 0.871181679630224, 0.0310099719746579, 0.162157686970184, -0.0219077074864437, - 0.0200641598926147, 84, -0.0009217737969145, 0, "Total indirect", - 0.931396220985835, 0.0107073057745262, -0.0860883042219167, - -0.06047820206868, 0.060652748660656, 84, 8.72732959880079e-05, - 1, "Total indirect", 0.997746571291635, 0.0309013205560922, + 1, "m", "Total indirect", 0.997746571291635, 0.0309013205560922, 0.00282425781220543, -0.0157871436682365, 0.0163794388900215, - 84, 0.000296147610892528, 1, "Total indirect", 0.971210959420073, + 84, 0.000296147610892528, 0, "m", "Total indirect", 0.971210959420073, 0.00820591164225055, 0.0360895441973473, -0.105826104800968, - 0.0868069399441564, 84, -0.00950958242840603, 1, "Total indirect", - 0.846557714792424, 0.0491419858386659, -0.193512375743752, 16, - 0, 16, 0, 16, 1, 16, 0, 50, 0, 16, 0, 50, 1, 16, 0, 84, 0, 16, - 0, 84, 1, 16, 0, 16, 0, 16, 1, 16, 1, 16, 1, 50, 0, 16, 1, 50, - 1, 16, 1, 84, 0, 16, 1, 84, 1, 16, 1, 16, 0, 50, 0, 16, 1, 50, - 0, 50, 0, 50, 0, 50, 1, 50, 0, 84, 0, 50, 0, 84, 1, 50, 0, 16, - 0, 50, 1, 16, 1, 50, 1, 50, 0, 50, 1, 50, 1, 50, 1, 84, 0, 50, - 1, 84, 1, 50, 1, 16, 0, 84, 0, 16, 1, 84, 0, 50, 0, 84, 0, 50, - 1, 84, 0, 84, 0, 84, 0, 84, 1, 84, 0, 16, 0, 84, 1, 16, 1, 84, - 1, 50, 0, 84, 1, 50, 1, 84, 1, 84, 0, 84, 1, 84, 1, 84, 1)) + 0.0868069399441564, 84, -0.00950958242840603, 1, "m", "Total indirect", + 0.846557714792424, 0.0491419858386659, -0.193512375743752)) @@ -16319,7 +12273,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 82 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16330,30 +12284,30 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded3"), - list(processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded3", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded3"), + list(processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded3", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16378,7 +12332,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 82 - factor works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16389,30 +12343,30 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "facGender", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "facGender", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "facGender", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "facGender", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded3"), - list(processDependent = "contNormal", processIndependent = "facGender", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded3", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "facGender", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "facGender", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded3"), + list(processDependent = "contNormal", processIndependent = "facGender", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded3", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded4")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16437,7 +12391,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 83 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16448,26 +12402,26 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "JaspProcess_Mediator_Encoded1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "JaspProcess_Mediator_Encoded1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16493,7 +12447,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 84 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16504,28 +12458,28 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "JaspProcess_Mediator_Encoded1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "JaspProcess_Mediator_Encoded1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16551,7 +12505,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 85 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16562,30 +12516,30 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "JaspProcess_Mediator_Encoded1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "JaspProcess_Mediator_Encoded1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16611,7 +12565,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 86 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16622,28 +12576,28 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "JaspProcess_Mediator_Encoded1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1")), residualCovariances = TRUE, - statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "JaspProcess_Mediator_Encoded1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1")), residualCovariances = TRUE, + statisticalPathPlot = TRUE, totalEffects = TRUE, localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16669,7 +12623,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 87 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16680,26 +12634,26 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", - processType = "moderators", processVariable = "contcor1")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", + processType = "moderators", processVariable = "contcor1")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16725,7 +12679,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 88 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16736,28 +12690,28 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "moderators", processVariable = "contcor1"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", - processType = "moderators", processVariable = "contcor1")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "moderators", processVariable = "contcor1"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", + processType = "moderators", processVariable = "contcor1")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16783,7 +12737,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 89 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16794,30 +12748,30 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "moderators", processVariable = "contcor1"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", - processType = "moderators", processVariable = "contcor1"), - list(processDependent = "contNormal", processIndependent = "contGamma", - processType = "moderators", processVariable = "contcor1")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "moderators", processVariable = "contcor1"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", + processType = "moderators", processVariable = "contcor1"), + list(processDependent = "contNormal", processIndependent = "contGamma", + processType = "moderators", processVariable = "contcor1")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16843,7 +12797,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 90 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16854,28 +12808,28 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", - processType = "moderators", processVariable = "contcor1"), - list(processDependent = "contNormal", processIndependent = "contGamma", - processType = "moderators", processVariable = "contcor1")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", + processType = "moderators", processVariable = "contcor1"), + list(processDependent = "contNormal", processIndependent = "contGamma", + processType = "moderators", processVariable = "contcor1")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16901,7 +12855,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 91 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16912,27 +12866,27 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "JaspProcess_Mediator_Encoded2", - processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "moderators", processVariable = "contcor1")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "JaspProcess_Mediator_Encoded2", + processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "moderators", processVariable = "contcor1")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) @@ -16958,7 +12912,7 @@ results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) }) test_that("Test that model number 92 - continuous works", { - + options <- jaspTools::analysisOptions("ClassicProcess") options$dependent <- "contNormal" options$covariates <- list("contGamma", "contcor1", "contcor2", "debCollin1") @@ -16969,37 +12923,37 @@ options$errorCalculationMethod <- "standard" options$naAction <- "fiml" options$emulation <- "lavaan" options$estimator <- "default" -options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, +options$moderationProbes <- list(list(probePercentile = 16, value = "16"), list(probePercentile = 50, value = "50"), list(probePercentile = 84, value = "84")) options$pathPlotsLegend <- TRUE options$pathPlotsColorPalette <- "colorblind" -options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, - inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, - modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", - modelNumberMediators = list(), modelNumberModeratorW = "", - modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, - processRelationships = list(list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "mediators", +options$processModels <- list(list(conceptualPathPlot = TRUE, independentCovariances = TRUE, + inputType = "inputVariables", mediationEffects = TRUE, mediatorCovariances = TRUE, + modelNumber = 1, modelNumberCovariates = list(), modelNumberIndependent = "", + modelNumberMediators = list(), modelNumberModeratorW = "", + modelNumberModeratorZ = "", name = "Model 1", pathCoefficients = TRUE, + processRelationships = list(list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded1"), list( - processDependent = "contNormal", processIndependent = "contGamma", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), - list(processDependent = "JaspProcess_Mediator_Encoded1", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "contNormal", - processIndependent = "contGamma", processType = "moderators", - processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", - processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "moderators", processVariable = "contcor1"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", - processType = "moderators", processVariable = "contcor1"), - list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", - processType = "moderators", processVariable = "contcor1")), - residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, - localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, + processDependent = "contNormal", processIndependent = "contGamma", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "mediators", processVariable = "JaspProcess_Mediator_Encoded2"), + list(processDependent = "JaspProcess_Mediator_Encoded1", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "contNormal", + processIndependent = "contGamma", processType = "moderators", + processVariable = "contcor1"), list(processDependent = "JaspProcess_Mediator_Encoded2", + processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "moderators", processVariable = "contcor1"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded1", + processType = "moderators", processVariable = "contcor1"), + list(processDependent = "contNormal", processIndependent = "JaspProcess_Mediator_Encoded2", + processType = "moderators", processVariable = "contcor1")), + residualCovariances = TRUE, statisticalPathPlot = TRUE, totalEffects = TRUE, + localTests = FALSE, localTestType = "cis", localTestBootstrap = FALSE, localTestBootstrapSamples = 1000)) set.seed(1) results <- jaspTools::runAnalysis("ClassicProcess", "debug", options) diff --git a/tests/testthat/test-classic-process-unit.R b/tests/testthat/test-classic-process-unit.R index 63643c5..12cb876 100644 --- a/tests/testthat/test-classic-process-unit.R +++ b/tests/testthat/test-classic-process-unit.R @@ -280,7 +280,7 @@ test_that("Test that .procGraphAddAttributes works", { expect_equal(igraph::V(graph)$isPartOfInt, c(FALSE, FALSE, FALSE, TRUE, FALSE)) expect_equal(igraph::V(graph)$isTreat, c(TRUE, FALSE, FALSE, FALSE, FALSE)) expect_equal(igraph::E(graph)$isMod, c(TRUE, FALSE, FALSE, TRUE, FALSE)) - expect_equal(igraph::E(graph)$modVars, list("contcor2", NULL, NULL, "contGamma", NULL)) + expect_equal(igraph::E(graph)$modVars, c("contcor2", NA, NA, "contGamma", NA)) }) test_that("Test that .procGraphAddAttributes works - moderated moderation", { @@ -302,6 +302,7 @@ test_that("Test that .procGraphAddAttributes works - moderated moderation", { expect_equal(igraph::V(graph)$intLength, c(1, 1, 1, 1, 2, 2, 2, 3)) expect_equal(igraph::V(graph)$isNestedInt, c(FALSE, FALSE, FALSE, FALSE, TRUE, TRUE, TRUE, FALSE)) expect_equal(igraph::V(graph)$isHigherOrderInt, c(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, TRUE)) + expect_equal(igraph::E(graph)$modVars, list(c("contcor1", "contcor2"), c("contGamma", "contcor2"), c("contGamma", "contcor1"), as.character(NA), as.character(NA), as.character(NA), as.character(NA))) }) test_that("Test that .procEncodePath works", { @@ -472,13 +473,89 @@ test_that("Test that .procRegSyntax works", { expect_equal(syntax, "contNormal ~ c1*contGamma + b1*contcor1 + c2*contcor2 + c3*contGamma:contcor2\ncontcor1 ~ a1*contGamma") }) +test_that("Test that .procMedEffectsSyntaxModPars", { + graph <- createDummyGraphModelModeratedMediation() + graph <- jaspProcess:::.procGraphAddParNamesSingleModel(graph) + modProbes <- list(contcor2 = c("2.5%" = 0.1, "50%" = 0.5, "97.5%" = 0.9)) + + pathEdge <- igraph::E(graph)["contGamma" %--% "contNormal"] + sourceNode <- "contGamma" + + modPars <- jaspProcess:::.procMedEffectsSyntaxModPars(pathEdge, sourceNode, graph, modProbes) + expect_equal(modPars, c("c3*0.1", "c3*0.5", "c3*0.9")) +}) + +test_that("Test that .procMedEffectsSyntaxGetLhs works - no contrasts", { + graph <- createDummyGraphModelModeratedMediation() + graph <- jaspProcess:::.procGraphAddParNamesSingleModel(graph) + modProbes <- list(contcor2 = c("2.5%" = 0.1, "50%" = 0.5, "97.5%" = 0.9)) + contrasts <- list() + path <- c(contGamma = 1, contNormal = 2) + lhs <- jaspProcess:::.procMedEffectsSyntaxGetLhs(path, graph, modProbes, contrasts) + expect_equal(lhs, c("contGamma__contNormal.contcor2__2.5", "contGamma__contNormal.contcor2__50", "contGamma__contNormal.contcor2__97.5")) +}) + +test_that("Test that .procMedEffectsSyntaxGetLhs works - with contrasts", { + edgeList <- matrix(c("contGammaA", "contNormal", + "contGammaB", "contNormal", + "contGammaA", "contcor1", + "contGammaB", "contcor1", + "contcor1", "contNormal", + "contcor2", "contNormal", + "contGammaA:contcor2", "contNormal", + "contGammaB:contcor2", "contNormal" + ), ncol = 2, byrow = TRUE) + graph <- create_graph_from_edgeList(edgeList) + graph <- jaspProcess:::.procGraphAddParNamesSingleModel(graph) + modProbes <- list(contcor2 = c("2.5%" = 0.1, "50%" = 0.5, "97.5%" = 0.9)) + contrasts <- list(contGamma = matrix(c(0, 1, 0, 0, 0, 1), 3, 2, dimnames = list(NULL, c("A", "B")))) + path <- c(contGammaA = 1, contNormal = 2) + lhs <- jaspProcess:::.procMedEffectsSyntaxGetLhs(path, graph, modProbes, contrasts) + expect_equal(lhs, c("contGamma__contNormal.contGamma__A.contcor2__2.5", + "contGamma__contNormal.contGamma__B.contcor2__2.5", + "contGamma__contNormal.contGamma__A.contcor2__50", + "contGamma__contNormal.contGamma__B.contcor2__50", + "contGamma__contNormal.contGamma__A.contcor2__97.5", + "contGamma__contNormal.contGamma__B.contcor2__97.5")) +}) + +test_that("Test that .procMedEffectsSyntaxGetRhs works - no contrasts", { + graph <- createDummyGraphModelModeratedMediation() + graph <- jaspProcess:::.procGraphAddParNamesSingleModel(graph) + modProbes <- list(contcor2 = c("2.5%" = 0.1, "50%" = 0.5, "97.5%" = 0.9)) + contrasts <- list() + path <- c(contGamma = 1, contNormal = 2) + rhs <- jaspProcess:::.procMedEffectsSyntaxGetRhs(path, graph, modProbes, contrasts) + expect_equal(rhs, c("(c1 + c3*0.1)", "(c1 + c3*0.5)", "(c1 + c3*0.9)")) +}) + +test_that("Test that .procMedEffectsSyntaxGetRhs works - with contrasts", { + edgeList <- matrix(c("contGammaA", "contNormal", + "contGammaB", "contNormal", + "contGammaA", "contcor1", + "contGammaB", "contcor1", + "contcor1", "contNormal", + "contcor2", "contNormal", + "contGammaA:contcor2", "contNormal", + "contGammaB:contcor2", "contNormal" + ), ncol = 2, byrow = TRUE) + graph <- create_graph_from_edgeList(edgeList) + graph <- jaspProcess:::.procGraphAddParNamesSingleModel(graph) + modProbes <- list(contcor2 = c("2.5%" = 0.1, "50%" = 0.5, "97.5%" = 0.9)) + contrasts <- list(contGamma = matrix(c(0, 1, 0, 0, 0, 1), 3, 2, dimnames = list(NULL, c("A", "B")))) + path <- c(contGammaA = 1, contNormal = 2) + rhs <- jaspProcess:::.procMedEffectsSyntaxGetRhs(path, graph, modProbes, contrasts) + expect_equal(rhs, c("(c1 + c4*0.1)", "(c2 + c5*0.1)", "(c1 + c4*0.5)", + "(c2 + c5*0.5)", "(c1 + c4*0.9)", "(c2 + c5*0.9)")) +}) + test_that("Test that .procMedEffectsSyntax works", { graph <- createDummyGraphModelModeratedMediation() graph <- jaspProcess:::.procGraphAddParNamesSingleModel(graph) - modProbs <- list(contcor2 = c("2.5%" = 0.1, "50%" = 0.5, "97.5%" = 0.9)) + modProbes <- list(contcor2 = c("2.5%" = 0.1, "50%" = 0.5, "97.5%" = 0.9)) contrasts <- list() - syntax <- jaspProcess:::.procMedEffectsSyntax(graph, modProbs, contrasts) + syntax <- jaspProcess:::.procMedEffectsSyntax(graph, modProbes, contrasts) expect_equal(syntax, "contGamma__contNormal.contcor2__2.5 := (c1 + c3*0.1)\ncontGamma__contNormal.contcor2__50 := (c1 + c3*0.5)\ncontGamma__contNormal.contcor2__97.5 := (c1 + c3*0.9)\ncontGamma__contcor1__contNormal := a1*b1\ntot.contcor2__2.5 := (c1 + c3*0.1) + a1*b1\ntot.contcor2__50 := (c1 + c3*0.5) + a1*b1\ntot.contcor2__97.5 := (c1 + c3*0.9) + a1*b1\ntotInd. := a1*b1") })