diff --git a/.Rbuildignore b/.Rbuildignore index 4f1ae1ab..e4e5d139 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -1,3 +1,5 @@ +^renv$ +^renv\.lock$ ^.*\.Rproj$ ^\.Rproj\.user$ ^tests/upgrades$ diff --git a/.gitignore b/.gitignore index 9df2ee70..977ab6a0 100644 --- a/.gitignore +++ b/.gitignore @@ -48,3 +48,5 @@ Thumbs.db # RStudio files .Rproj.user _processedLockFile.lock +renv/activate.R +.Rprofile diff --git a/DESCRIPTION b/DESCRIPTION index 7ccfc52e..1e1cedf3 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -28,7 +28,12 @@ Imports: RoBMA, metamisc (>= 0.2.5), ggmcmc, - pema + pema, + clubSandwich, + CompQuadForm, + sp, + dfoptim, + patchwork Remotes: jasp-stats/jaspBase, jasp-stats/jaspGraphs diff --git a/NAMESPACE b/NAMESPACE index 0aa4b33d..cedc4374 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,5 +1,6 @@ import(jaspBase) export(ClassicalMetaAnalysis) +export(ClassicalMetaAnalysisMultilevelMultivariate) export(SelectionModels) export(WaapWls) export(PetPeese) @@ -11,3 +12,5 @@ export(.ClassicalMetaAnalysisCommon) export(.BayesianMetaAnalysisCommon) export(PenalizedMetaAnalysis) export(BayesianBinomialMetaAnalysis) +export(EffectSizeComputation) +export(FunnelPlot) diff --git a/R/classicalmetaanalysis.R b/R/classicalmetaanalysis.R index 5a8f5101..e29c8a0a 100644 --- a/R/classicalmetaanalysis.R +++ b/R/classicalmetaanalysis.R @@ -15,83 +15,181 @@ # along with this program. If not, see . # -# This is a temporary fix -# TODO: remove it when R will solve this problem! -gettextf <- function(fmt, ..., domain = NULL) { - return(sprintf(gettext(fmt, domain = domain), ...)) -} ClassicalMetaAnalysis <- function(jaspResults, dataset = NULL, options, ...) { options[["module"]] <- "metaAnalysis" - ready <- options$effectSize != "" && options$effectSizeSe != "" && (options$interceptTerm || length(options$modelTerms) > 0) - if(ready) { - dataset <- .metaAnalysisReadData(dataset, options) - .metaAnalysisCheckErrors(dataset, options) + if (.maReady(options)) { + dataset <- .maCheckData(dataset, options) + .maCheckErrors(dataset, options) } - container <- .metaAnalysisGetOutputContainer(jaspResults) - .ClassicalMetaAnalysisCommon(container, dataset, ready, options) + .ClassicalMetaAnalysisCommon(jaspResults, dataset, options) return() } -.metaAnalysisGetOutputContainer <- function(jaspResults) { - if (!is.null(jaspResults[["modelContainer"]])) { - modelContainer <- jaspResults[["modelContainer"]] - } else { - modelContainer <- createJaspContainer() - modelContainer$dependOn(c("effectSize", "effectSizeSe", "method", "studyLabel", "covariates", "estimateTest", - "factors", "modelTerms", "interceptTerm", "coefficientCiLevel")) - jaspResults[["modelContainer"]] <- modelContainer - } - return(modelContainer) -} +.maDependencies <- c( + "effectSize", "effectSizeStandardError", "predictors", "predictors.types", "clustering", "method", "fixedEffectTest", + "effectSizeModelTerms", "effectSizeModelIncludeIntercept", + "clusteringUseClubSandwich", "clusteringSmallSampleCorrection", + "confidenceIntervalsLevel", + "fixParametersTau2", "fixParametersTau2Value", + "fixParametersWeights", "fixParametersWeightsVariable", + "weightedEstimation", + "diagnosticsCasewiseDiagnosticsRerunWithoutInfluentialCases", + # optimizer settings + "optimizerMethod", "optimizerInitialTau2", "optimizerInitialTau2Value", + "optimizerMinimumTau2", "optimizerMinimumTau2Value", "optimizerMaximumTau2", "optimizerMaximumTau2Value", + "optimizerMaximumIterations", "optimizerMaximumIterationsValue", "optimizerConvergenceTolerance", "optimizerConvergenceToleranceValue", + "optimizerConvergenceRelativeTolerance", "optimizerConvergenceRelativeToleranceValue", "optimizerStepAdjustment", "optimizerStepAdjustmentValue", + "optimizerMaximumEvaluations", "optimizerMaximumEvaluationsValue", + "optimizerInitialTrustRegionRadius", "optimizerInitialTrustRegionRadiusValue", "optimizerFinalTrustRegionRadius", "optimizerFinalTrustRegionRadiusValue", + "optimizerMaximumRestarts", "optimizerMaximumRestartsValue", + "advancedExtendMetaforCall", "advancedExtendMetaforCallCode", + # simple ma specific + "heterogeneityModelTerms", "heterogeneityModelIncludeIntercept", "heterogeneityModelLink", + "permutationTest", "permutationTestIteration", "permutationTestType", "setSeed", "seed", + # multilevel/multivariate specific + "randomEffects", "randomEffectsSpecification", + "computeCovarianceMatrix", "computeCovarianceMatrix" +) +.maForestPlotDependencies <- c( + .maDependencies, "transformEffectSize", "confidenceIntervalsLevel", + "forestPlotStudyInformation", + "forestPlotStudyInformationAllVariables", + "forestPlotStudyInformationSelectedVariables", + "forestPlotStudyInformationSelectedVariablesSettings", + "forestPlotStudyInformationPredictedEffects", + "forestPlotStudyInformationStudyWeights", + "forestPlotStudyInformationOrderBy", + "forestPlotStudyInformationOrderAscending", + "forestPlotEstimatedMarginalMeans", + "forestPlotEstimatedMarginalMeansModelVariables", + "forestPlotEstimatedMarginalMeansSelectedVariables", + "forestPlotEstimatedMarginalMeansTermTests", + "forestPlotEstimatedMarginalMeansCoefficientTests", + "forestPlotEstimatedMarginalMeansCoefficientTestsAgainst", + "forestPlotEstimatedMarginalMeansAdjustedEffectSizeEstimate", + "forestPlotModelInformation", + "forestPlotPooledEffectSizeEstimate", + "forestPlotPooledEffectSizeTest", + "forestPlotResidualHeterogeneityTest", + "forestPlotResidualHeterogeneityEstimate", + "forestPlotEffectSizeModerationTest", + "forestPlotHeterogeneityModerationTest", + "forestPlotPredictionIntervals", + "forestPlotEstimatesAndConfidenceIntervals", + "forestPlotTestsInRightPanel", + "forestPlotMappingColor", + "forestPlotMappingShape", + "forestPlotRelativeSizeEstimates", + "forestPlotRelativeSizeText", + "forestPlotRelativeSizeAxisLabels", + "forestPlotRelativeSizeRow", + "forestPlotRelativeSizeLeftPanel", + "forestPlotRelativeSizeMiddlePanel", + "forestPlotRelativeSizeRightPanel", + "forestPlotAuxiliaryAdjustWidthBasedOnText", + "forestPlotAuxiliaryDigits", + "forestPlotAuxiliaryTestsInformation", + "forestPlotAuxiliaryPlotColor", + "forestPlotAuxiliaryAddVerticalLine", + "forestPlotAuxiliaryAddVerticalLineValue", + "forestPlotAuxiliaryAddVerticalLine2", + "forestPlotAuxiliaryAddVerticalLineValue2", + "forestPlotAuxiliaryEffectLabel", + "forestPlotAuxiliarySetXAxisLimit", + "forestPlotAuxiliarySetXAxisLimitLower", + "forestPlotAuxiliarySetXAxisLimitUpper", + "forestPlotStudyInformationSecondaryConfidenceInterval", + "forestPlotStudyInformationSecondaryConfidenceIntervalLevel" +) +.maBubblePlotDependencies <- c( + .maDependencies, "transformEffectSize", "confidenceIntervalsLevel", + "bubblePlotSelectedVariable", + "bubblePlotSeparateLines", + "bubblePlotSeparatePlots", + "bubblePlotSdFactorCovariates", + "bubblePlotBubblesSize", + "bubblePlotBubblesRelativeSize", + "bubblePlotBubblesTransparency", + "bubblePlotBubblesJitter", + "bubblePlotConfidenceIntervals", + "bubblePlotConfidenceIntervalsTransparency", + "bubblePlotPredictionIntervals", + "bubblePlotPredictionIntervalsTransparency", + "colorPalette", + "bubblePlotTheme", + "bubblePlotLegendPosition", + "bubblePlotRelativeSizeText" +) +.maReady <- function(options) { -.metaAnalysisReadData <- function(dataset, options) { - if (!is.null(dataset)) - return(dataset) - else { - effsizeName <- unlist(options$effectSize) - stderrName <- unlist(options$effectSizeSe) - covarNames <- if (length(options$covariates) > 0) unlist(options$covariates) - factNames <- if (length(options$factors) > 0) unlist(options$factors) - - numeric.variables <- Filter(function(s) s != "", c(effsizeName, covarNames, stderrName)) - factor.variables <- Filter(function(s) s != "", c(factNames, options$studyLabel)) - return(.readDataSetToEnd(columns.as.factor = factor.variables, - columns.as.numeric = numeric.variables, - exclude.na.listwise = numeric.variables)) - } + inputReady <- options[["effectSize"]] != "" && options[["effectSizeStandardError"]] != "" + termsEffectSizeReady <- length(options[["effectSizeModelTerms"]]) > 0 || options[["effectSizeModelIncludeIntercept"]] + termsHeterogeneityReady <- length(options[["heterogeneityModelTerms"]]) > 0 || options[["heterogeneityModelIncludeIntercept"]] + + return(inputReady && termsEffectSizeReady && termsHeterogeneityReady) } +.maCheckData <- function(dataset, options) { + + # model data + predictorsNominal <- options[["predictors"]][options[["predictors.types"]] == "nominal"] + predictorsScale <- options[["predictors"]][options[["predictors.types"]] == "scale"] -.metaAnalysisCheckErrors <- function(dataset, options){ - effsizeName <- unlist(options$effectSize) - stderrName <- unlist(options$effectSizeSe) - covarNames <- if (length(options$covariates) > 0) unlist(options$covariates) - numeric.variables <- Filter(function(s) s != "", c(effsizeName, covarNames, stderrName)) - .hasErrors(dataset = dataset, - type = c("infinity", "observations", "variance"), - all.target = numeric.variables, - observations.amount = "< 2", - exitAnalysisIfErrors = TRUE) - .hasErrors(dataset = dataset, - type = c("modelInteractions"), - modelInteractions.modelTerms = options$modelTerms, - exitAnalysisIfErrors = TRUE) - .hasErrors(dataset = dataset, - seCheck.target = options[["effectSizeSe"]], - custom = .metaAnalysisCheckSE, - exitAnalysisIfErrors = TRUE) + # omit NAs + omitOnVariables <- c( + options[["effectSize"]], + options[["effectSizeStandardError"]], + if (options[["clustering"]] != "") options[["clustering"]], + if (length(predictorsNominal) > 0) predictorsNominal, + if (length(predictorsScale) > 0) predictorsScale + ) + anyNaByRows <- apply(dataset[,omitOnVariables], 1, function(x) anyNA(x)) + dataset <- dataset[!anyNaByRows,] + attr(dataset, "NAs") <- sum(anyNaByRows) + + return(dataset) } +.maCheckErrors <- function(dataset, options) { + + .hasErrors( + dataset = dataset, + type = c("infinity", "observations", "variance"), + all.target = c( + options[["effectSize"]], + options[["effectSizeStandardError"]], + options[["predictors"]][options[["predictors.types"]] == "scale"] + ), + observations.amount = "< 2", + exitAnalysisIfErrors = TRUE) + + if (length(options[["effectSizeModelTerms"]]) > 0) + .hasErrors( + dataset = dataset, + type = c("modelInteractions"), + modelInteractions.modelTerms = options[["effectSizeModelTerms"]], + exitAnalysisIfErrors = TRUE) -.metaAnalysisCheckSE <- list( - seCheck = function(dataset, target) { - nonPositive <- !all(na.omit(dataset[,target]) > 0) + if (length(options[["heterogeneityModelTerms"]]) > 0) + .hasErrors( + dataset = dataset, + type = c("modelInteractions"), + modelInteractions.modelTerms = options[["heterogeneityModelTerms"]], + exitAnalysisIfErrors = TRUE) + + .hasErrors( + dataset = dataset, + seCheck.target = options[["effectSizeStandardError"]], + custom = .maCheckStandardErrors, + exitAnalysisIfErrors = TRUE) +} +.maCheckStandardErrors <- list(seCheck = function(dataset, target) { + nonPositive <- !all(dataset[,target] > 0) if (nonPositive) { - return(gettext("All standard errors/sample sizes must be positive.")) + return(gettext("All standard errors must be positive.")) } - } -) \ No newline at end of file + }) diff --git a/R/classicalmetaanalysiscommon.R b/R/classicalmetaanalysiscommon.R index fb553835..de2e9d75 100644 --- a/R/classicalmetaanalysiscommon.R +++ b/R/classicalmetaanalysiscommon.R @@ -15,1407 +15,3378 @@ # along with this program. If not, see . # -.ClassicalMetaAnalysisCommon <- function(container, dataset = NULL, ready, options, ...) { - - # Output tables - .metaAnalysisFixRandTable( container, dataset, options, ready) - .metaAnalysisCoeffTable( container, dataset, options, ready) - .metaAnalysisFitMeasuresTable( container, dataset, options, ready) - .metaAnalysisResidualTable( container, dataset, options, ready) - .metaAnalysisCovMatTable( container, dataset, options, ready) - .metaAnalysisRankTestTable( container, dataset, options, ready) - .metaAnalysisRegTestTable( container, dataset, options, ready) - .metaAnalysisCasewiseTable( container, dataset, options, ready) - .metaAnalysisFailSafeTable( container, dataset, options, ready) - - # Output plots - .metaAnalysisForestPlot( container, dataset, options, ready) - .metaAnalysisFunnelPlot( container, dataset, options, ready) - .metaAnalysisDiagnosticPlot( container, dataset, options, ready) - .metaAnalysisProfilePlot( container, dataset, options, ready) - .metaAnalysisTrimFillPlot( container, dataset, options, ready) +# This analysis runs +# - classical meta-analysis (using rma.uni) +# - classical multilevel/multivariate meta-analysis (using rma.mv; custom function prefix .mamm) +# - classical binimal meta-analysis (using rma.; custom function prefix .mab) + + +# TODO: +# Coefficient tests +# - parwise() from new metafor version +# - add permutation test for omnibus moderation tests if this is implemented: https://github.com/wviechtb/metafor/issues/88 +# Estimated Marginal Means +# - add variable interactions +# - specify and test contrasts +# Forest plot +# - allow aggregation of studies by a factor (then show simple REML aggregation within and overlaying shaded estimates) +# AIC/BIC Model-averaging +# Diagnostics +# - model re-run on presence of influential cases +# - residual +# - vs predicted +# - vs outcome +# - vs covariates +# Generic +# - allow different covariates factoring across all settings +# - confidence interval for heterogeneity in multilevel multivariate + +.ClassicalMetaAnalysisCommon <- function(jaspResults, dataset, options, ...) { + + # fit the model + .maFitModel(jaspResults, dataset, options) + + # # remove influential observations and refit the model if requested + # if (options[["diagnosticsCasewiseDiagnostics"]] && options[["diagnosticsCasewiseDiagnosticsRerunWithoutInfluentialCases"]]) { + # dataset <- .maRemoveInfluentialObservations(jaspResults, dataset, options) + # .maFitModel(jaspResults, dataset, options, objectName = "fitNoInfluence") + # } + + # model summary + .maResidualHeterogeneityTable(jaspResults, dataset, options) + .maModeratorsTable(jaspResults, dataset, options) + .maPooledEstimatesTable(jaspResults, dataset, options) + + # random effects + if (.maIsMultilevelMultivariate(options)) + .mammRandomEstimatesTable(jaspResults, dataset, options) + + if (options[["fitMeasures"]]) + .maFitMeasuresTable(jaspResults, dataset, options) + + # meta-regression tables + if (.maIsMetaregression(options)) { + if (options[["metaregressionTermTests"]]) { + .maTermsTable(jaspResults, dataset, options, "effectSize") + .maTermsTable(jaspResults, dataset, options, "heterogeneity") + } + if (options[["metaregressionCoefficientEstimates"]]) { + .maCoefficientEstimatesTable(jaspResults, dataset, options, "effectSize") + .maCoefficientEstimatesTable(jaspResults, dataset, options, "heterogeneity") + } + if (options[["metaregressionCoefficientCorrelationMatrix"]]) { + .maCoefficientCorrelationMatrixTable(jaspResults, dataset, options, "effectSize") + .maCoefficientCorrelationMatrixTable(jaspResults, dataset, options, "heterogeneity") + } + } + + # estimated marginal means + .maEstimatedMarginalMeansTable(jaspResults, dataset, options, "effectSize") + .maEstimatedMarginalMeansTable(jaspResults, dataset, options, "heterogeneity") + + # plots + .maUltimateForestPlot(jaspResults, dataset, options) + .maBubblePlot(jaspResults, dataset, options) + + # diagnostics + if (.maIsMetaregression(options) && options[["diagnosticsVarianceInflationFactor"]]) { + .maVarianceInflationTable(jaspResults, dataset, options, "effectSize") + .maVarianceInflationTable(jaspResults, dataset, options, "heterogeneity") + } + if (options[["diagnosticsCasewiseDiagnostics"]]) { + .maCasewiseDiagnosticsTable(jaspResults, dataset, options) + .maCasewiseDiagnosticsExportColumns(jaspResults, dataset, options) + } + if (options[["diagnosticsPlotsProfileLikelihood"]]) + .maProfileLikelihoodPlot(jaspResults, dataset, options) + if (options[["diagnosticsPlotsBaujat"]]) + .maBaujatPlot(jaspResults, dataset, options) + if (options[["diagnosticsResidualFunnel"]]) + .maResidualFunnelPlot(jaspResults, dataset, options) + + + # additional + if (options[["showMetaforRCode"]]) + .maShowMetaforRCode(jaspResults, options) return() } -## This file interfaces the metafor::rma function and associated diagnostic functions -### (but it restricts its multipurposeness to one central purpose: fitting a -### meta-regression to effect sizes and their standard errors and providing diagnostics.) +# fitting functions +.maGetFormula <- function(modelTerms, includeIntercept) { -### options contains: -## essentials: -# effectsize: string (maps to 'yi'), name of the variable that contains the effect sizes (ES) -# stderr: string (maps to 'sei'), name of the variable containing the ES standard errors -# intercept: logical (maps to 'intercept'), intercept in the model? -# -## optional: -# covariates: string array (maps to 'mods'), names of continuous predictor variables -# factors: string array (maps to 'mods'), names of nominal/ordinal predictor variables -## plotting: -# studylabels: string (maps to 'slab'), name of variable that contains label for a forrest plot -# forrestPlot: logical, make this plot? -# funnelPlot: logical, -## advanced analysis: -# method: string, one of [`Fixed Effects`, `Maximum Likelihood`, `Restricted ML`, `DerSimonian-Laird`, `Hedges`, `Hunter-Schmidt`, `Sidik-Jonkman`, `Empirical Bayes`, `Paule-Mandel`] (see ?rma) -# - -# test: string, one of ["z", "knha"] -# btt: numeric, vector of indices specifying which coefficients to include in the omnibus test of moderators -# - -# ...: numeric, -3 ??? value ??? 3, distribution used is dt((tStatistic - Tlocation) / Tscale, TDf) - -.metaAnalysisComputeModel <- function(container, dataset, options, ready) { - if (!is.null(container[["Model"]])) - return(container[["Model"]]$object) - rma.fit <- structure(list('b' = numeric(), - 'se' = numeric(), - 'ci.lb' = numeric(), - 'ci.ub' = numeric(), - 'zval' = numeric(), - 'pval' = numeric()), - class = c("dummy", "rma")) - if (ready) { - - argList <- list( - yi = dataset[,options$effectSize], - sei = dataset[,options$effectSizeSe], - slab = if(options$studyLabel != "") dataset[,options$studyLabel], - method = .metaAnalysisGetMethod(options), - mods = .metaAnalysisFormula(options), - data = dataset, - test = options$estimateTest, - # add tiny amount because 1 is treated by rma() as 100% whereas values > 1 as percentages - level = options$coefficientCiLevel * 100, - control = list(maxiter = 500) - ) - argList <- argList[!sapply(argList, is.null)] + predictors <- unlist(lapply(modelTerms, function(x) { + if (length(x[["components"]]) > 1) + return(paste(x[["components"]], collapse = ":")) + else + return(x[["components"]]) + })) + + if (length(predictors) == 0) + return(NULL) + if (includeIntercept) + formula <- paste("~", paste(predictors, collapse = "+")) + else + formula <- paste("~", paste(predictors, collapse = "+"), "-1") + + return(as.formula(formula, env = parent.frame(1))) +} +.maFitModel <- function(jaspResults, dataset, options, objectName = "fit") { + # --------------------------------------------------------------------------- # + # when updating don't forget to update the '.maMakeMetaforCallText' function! # + # --------------------------------------------------------------------------- # + if (!.maReady(options) || !is.null(jaspResults[[objectName]])) + return() - # analysis - rma.fit <- tryCatch( - do.call(metafor::rma, argList), - error = function(e) .quitAnalysis(gettextf("The metafor package crashed with the following error: %s", e$message)) + # create the output container + fitContainer <- createJaspState() + fitContainer$dependOn(.maDependencies) + jaspResults[[objectName]] <- fitContainer + + # specify the effect size and outcome + if (options[["module"]] == "metaAnalysis") { + rmaInput <- list( + yi = as.name(options[["effectSize"]]), + sei = as.name(options[["effectSizeStandardError"]]), + data = dataset ) + } else if (options[["module"]] == "metaAnalysisMultilevelMultivariate") { + # TODO: extend to covariance matrices + rmaInput <- list( + yi = as.name(options[["effectSize"]]), + V = as.name("samplingVariance"), # precomputed on data load + data = dataset + ) + } + + # add formulas if specified + rmaInput$mods <- .maGetFormula(options[["effectSizeModelTerms"]], options[["effectSizeModelIncludeIntercept"]]) + rmaInput$scale <- .maGetFormula(options[["heterogeneityModelTerms"]], options[["heterogeneityModelIncludeIntercept"]]) + + # add random effects + if (.maIsMultilevelMultivariate(options)) { + randomFormulaList <- .mammGetRandomFormulaList(options) + randomFormulaList <- unname(randomFormulaList) # remove names for some metafor post-processing functions + if (length(randomFormulaList) != 0) { + rmaInput$random <- randomFormulaList + rmaInput$struct <- do.call(c, lapply(randomFormulaList, attr, which = "structure")) + + # spatial-specific settings + rmaInput$dist <- unlist(lapply(randomFormulaList, attr, which = "dist"), recursive = FALSE) + addConstant <- do.call(c, lapply(randomFormulaList, attr, which = "addConstant")) + if (length(addConstant) > 0 && any(addConstant)) + rmaInput$data$constant <- 1 + for (i in seq_along(rmaInput$dist)) { + if (is.matrix(rmaInput$dist[[i]]) && !all(unique(rmaInput[["data"]][[names(rmaInput$dist)[i]]]) %in% rownames(rmaInput$dist[[names(rmaInput$dist)[i]]]))) + .quitAnalysis(sprintf(gettext("The loaded distance matrix for '%1$s' does not match the dataset. The following levels are missing: %2$s."), + names(rmaInput$dist)[i], + paste0(unique(rmaInput[["data"]][[names(rmaInput$dist)[i]]])[!unique(rmaInput[["data"]][[names(rmaInput$dist)[i]]]) %in% rownames(rmaInput$dist)], collapse = ", "))) + } + # known correlation-specific settings + rmaInput$R <- unlist(lapply(randomFormulaList, attr, which = "R"), recursive = FALSE) + for (i in seq_along(rmaInput$R)) { + if (!all(unique(rmaInput[["data"]][[names(rmaInput$R)[i]]]) %in% rownames(rmaInput$R[[names(rmaInput$R)[i]]]))) + .quitAnalysis(sprintf(gettext("The loaded correlation matrix for '%1$s' does not match the dataset. The following levels are missing: %2$s."), + names(rmaInput$R)[i], + paste0(unique(rmaInput[["data"]][[names(rmaInput$R)[i]]])[!unique(rmaInput[["data"]][[names(rmaInput$R)[i]]]) %in% rownames(rmaInput$R)], collapse = ", "))) + } + } } - # Save results to state - container[["Model"]] <- createJaspState(rma.fit) + # specify method and fixed effect terms test + rmaInput$method <- .maGetMethodOptions(options) + rmaInput$test <- options[["fixedEffectTest"]] - return(rma.fit) -} + if (!options[["weightedEstimation"]]) + rmaInput$weighted <- FALSE + + # add fixed parameters if needed + if (options[["fixParametersWeights"]] && options[["fixParametersWeightsVariable"]] != "") + rmaInput$weights <- dataset[[options[["fixParametersWeightsVariable"]]]] + if (options[["fixParametersTau2"]]) + rmaInput$tau2 <- .maGetFixedTau2Options(options) # TODO: add multiple possible fixed taus -#Tables -.metaAnalysisFixRandTable <- function(container, dataset, options, ready) { - if (!is.null(container[["fixRandTable"]])) return() + # add link function if needed + if (.maIsMetaregressionHeterogeneity(options)) + rmaInput$link <- options[["heterogeneityModelLink"]] - mainTable <- createJaspTable(gettext("Fixed and Random Effects")) - mainTable$position <- 1 - mainTable$addCitation("Hedges, L. V., & Olkin, I. (1985). Statistical methods for meta-analysis. San Diego, CA: Academic Press.") + if (.maIsMultilevelMultivariate(options)) { + rmaInput$sparse <- if (options[["useSparseMatricies"]]) options[["useSparseMatricies"]] + rmaInput$cvvc <- if (!options[["computeCovarianceMatrix"]]) !options[["computeCovarianceMatrix"]] + } - mainTable$addColumnInfo(name = "name", type = "string", title = "") - mainTable$addColumnInfo(name = "qstat", type = "number", title = gettext("Q")) - mainTable$addColumnInfo(name = "df", type = "integer", title = gettext("df")) - mainTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) + # add control options if needed + control <- .maGetControlOptions(options) + if (length(control) != 0) + rmaInput$control <- control - mainTable$addFootnote(gettext("p-values are approximate.")) + # additional input + rmaInput$level <- 100 * options[["confidenceIntervalsLevel"]] - container[["fixRandTable"]] <- mainTable + # extend the call by custom commands from R if requested + if (options[["advancedExtendMetaforCall"]]) + rmaInput <- c(rmaInput, .maExtendMetaforCallFromOptions(options)) - res <- try(.metaAnalysisFixRandFill(container, dataset, options, ready)) + ### fit the model + if (options[["module"]] == "metaAnalysis") { + fit <- try(do.call(metafor::rma, rmaInput)) + } else if (options[["module"]] == "metaAnalysisMultilevelMultivariate") { + fit <- try(do.call(metafor::rma.mv, rmaInput)) + } - .metaAnalysisSetError(res, mainTable) -} -.metaAnalysisCoeffTable <- function(container, dataset, options, ready) { - if (!options$coefficientEstimate || !is.null(container[["coeffTable"]])) - return() + # add clustering if specified + if (options[["clustering"]] != "") { + fitClustered <- try(metafor::robust( + fit, + cluster = dataset[[options[["clustering"]]]], + clubSandwich = options[["clusteringUseClubSandwich"]], + adjust = options[["clusteringSmallSampleCorrection"]] + )) + } else { + fitClustered <- NULL + } - coeffTable <- createJaspTable(gettext("Coefficients")) - coeffTable$dependOn(c("coefficientEstimate", "coefficientCi")) - coeffTable$position <- 2 - coeffTable$showSpecifiedColumnsOnly <- TRUE - coeffTable$addCitation("Viechtbauer, W. (2010). Conducting meta-analyses in R with the metafor package. Journal of Statistical Software, 36(3), 1-48. URL: http://www.jstatsoft.org/v36/i03/") - coeffTable$addColumnInfo(name = "name", type = "string", title = "") - coeffTable$addColumnInfo(name = "est", type = "number", title = gettext("Estimate")) - coeffTable$addColumnInfo(name = "se", type = "number", title = gettext("Standard Error")) - if (options[["estimateTest"]] == "z") - coeffTable$addColumnInfo(name = "zval", type = "number", title = gettext("z")) - else if (options[["estimateTest"]] == "knha") { - coeffTable$addColumnInfo(name = "tval", type = "number", title = gettext("t")) - coeffTable$addColumnInfo(name = "df", type = "number", title = gettext("df")) + # add permutation test if requested (only available for non-clustered fits) + if (.maIsPermutation(options)) { + .setSeedJASP(options) + fitPermutation <- try(metafor::permutest( + fit, + exact = options[["permutationTestType"]] == "exact", + iter = options[["permutationTestIteration"]] + )) + fit <- .maFitAddPermutationPValues(fit, fitPermutation, options) + } else { + fitPermutation <- NULL } - coeffTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) - .metaAnalysisConfidenceInterval(options, coeffTable) - coeffTable$addFootnote(switch(options$estimateTest, z = gettext("Wald test."), knha = gettext("Knapp and Hartung test adjustment."))) - container[["coeffTable"]] <- coeffTable - if(!ready) - return() + # add information about dropped levels to the fit + if (.maIsMultilevelMultivariate(options)) { + attr(fit, "skipped") <- attr(randomFormulaList, "skipped") + if (options[["clustering"]] != "") { + attr(fitClustered, "skipped") <- attr(randomFormulaList, "skipped") + } + } + + # return the results + jaspResults[[objectName]]$object <- list( + fit = fit, + fitClustered = fitClustered, + fitPermutation = fitPermutation + ) + + return() +} +.maFitAddPermutationPValues <- function(fit, fitPerumation, options) { + + # stores the permutation p-values in the fit object + # this simplifies object dispatching later in the code + # the whole fitPermutation object can be essentially forgotten + + if (.maIsMetaregressionEffectSize(options)) { + attr(fit[["QMp"]], "permutation") <- fitPerumation[["QMp"]] + attr(fit[["pval"]], "permutation") <- fitPerumation[["pval"]] + } - res <- try(.metaAnalysisCoeffFill(container, dataset, options)) + if (.maIsMetaregressionEffectSize(options)) { + attr(fit[["QSp"]], "permutation") <- fitPerumation[["QSp"]] + attr(fit[["pval.alpha"]], "permutation") <- fitPerumation[["pval.alpha"]] + } - .metaAnalysisSetError(res, coeffTable) + return(fit) } +.maRemoveInfluentialObservations <- function(jaspResults, dataset, options) { -.metaAnalysisFitMeasuresTable <- function(container, dataset, options, ready) { - if (!options$fitMeasure || !is.null(container[["fitMeasuresTable"]])) + if (!.maReady(options) || !is.null(jaspResults[["fit"]])) return() - fitMeasuresTable <- createJaspTable(gettext("Fit measures")) - fitMeasuresTable$dependOn("fitMeasure") - fitMeasuresTable$position <- 3 + fit <- .maExtractFit(jaspResults, options) - method <- .metaAnalysisGetTranslatedMethod(options) + if (jaspBase::isTryError(fit)) + return() - fitMeasuresTable$addColumnInfo(name = "name", type = "string", title = "") - fitMeasuresTable$addColumnInfo(name = "method", type = "number", title = method) + # remove influential observations + influenceResults <- influence.rma.uni(fit) + influentialObservation <- influenceResults$inf$inf == "*" - container[["fitMeasuresTable"]] <- fitMeasuresTable + dataset <- dataset[!influentialObservation, ] + attr(dataset, "influentialObservations") <- sum(influentialObservation) - res <- try(.metaAnalysisFitMeasuresFill(container, dataset, options, ready)) + if (nrow(dataset) == 0) + return(.quitAnalysis(gettext("All observations were removed as influential."))) - .metaAnalysisSetError(res, fitMeasuresTable) + return(dataset) } -.metaAnalysisResidualTable <- function(container, dataset, options, ready) { - method <- .metaAnalysisGetMethod(options) +# output tables +.maResidualHeterogeneityTable <- function(jaspResults, dataset, options) { - if (!options$residualParameter || method == "FE" || !is.null(container[["residualTable"]])) + modelSummaryContainer <- .maExtractModelSummaryContainer(jaspResults) + + if (!is.null(modelSummaryContainer[["residualHeterogeneityTable"]])) return() - residualTable <- createJaspTable(gettext("Residual Heterogeneity Estimates")) - residualTable$dependOn(c("residualParameter", "coefficientCi")) - residualTable$position <- 4 - residualTable$showSpecifiedColumnsOnly <- TRUE + fit <- .maExtractFit(jaspResults, options) - residualTable$addColumnInfo(name = "name", type = "string", title = "") - residualTable$addColumnInfo(name = "est", type = "number", title = gettext("Estimate")) - .metaAnalysisConfidenceInterval(options, residualTable) + # residual heterogeneity table + residualHeterogeneityTable <- createJaspTable(gettext("Residual Heterogeneity Test")) + residualHeterogeneityTable$position <- 1 + modelSummaryContainer[["residualHeterogeneityTable"]] <- residualHeterogeneityTable - container[["residualTable"]] <- residualTable + residualHeterogeneityTable$addColumnInfo(name = "qstat", type = "number", title = gettext("Q\U2091")) + residualHeterogeneityTable$addColumnInfo(name = "df", type = "integer", title = gettext("df")) + residualHeterogeneityTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) - res <- try(.metaAnalysisResidualFill(container, dataset, options, ready)) + # stop and display errors + if (is.null(fit)) + return() - .metaAnalysisSetError(res, residualTable) -} + if (!is.null(.maCheckIsPossibleOptions(options))) { + residualHeterogeneityTable$setError(.maCheckIsPossibleOptions(options)) + return() + } -.metaAnalysisCovMatTable <- function(container, dataset, options, ready) { - if (!options$covarianceMatrix || !is.null(container[["covMatTable"]])) + if (jaspBase::isTryError(fit)) { + residualHeterogeneityTable$setError(.maTryCleanErrorMessages(fit)) return() + } - covMatTable <- createJaspTable(gettext("Parameter Covariances")) - covMatTable$dependOn("covarianceMatrix") - covMatTable$position <- 5 - covMatTable$showSpecifiedColumnsOnly <- TRUE + # residual heterogeneity + residualHeterogeneityTable$addRows(list( + qstat = fit[["QE"]], + df = fit[["k"]] - fit[["p"]], + pval = fit[["QEp"]] + )) - covMatTable$addColumnInfo(name = "name", type = "string", title = "") - if(!ready) { - coeffVcov <- NULL - covMatTable$addColumnInfo(name = "intercept", type = "number", title = "...") - } else { - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - coeffVcov <- try(vcov(rma.fit)) - colnames(coeffVcov) <- .metaAnalysisMakePrettyCoeffNames(colnames(coeffVcov), dataset) - for (i in seq_along(colnames(coeffVcov))) - covMatTable$addColumnInfo(name = colnames(coeffVcov)[i], type = "number") - } + return() +} +.maModeratorsTable <- function(jaspResults, dataset, options) { - container[["covMatTable"]] <- covMatTable + modelSummaryContainer <- .maExtractModelSummaryContainer(jaspResults) - res <- try(.metaAnalysisCovMatFill(container, dataset, options, ready, coeffVcov)) + if (!is.null(modelSummaryContainer[["moderatorsTable"]])) + return() - .metaAnalysisSetError(res, covMatTable) -} + if (!.maIsMetaregression(options)) + return() -.metaAnalysisRankTestTable <- function(container, dataset, options, ready) { - if (!options$funnelPlotRankTestAsymmetry || !is.null(container[["rankTestTable"]])) + fit <- .maExtractFit(jaspResults, options) + + # omnibus moderator table + moderatorsTable <- createJaspTable(gettext("Omnibus Moderation Test")) + moderatorsTable$position <- 2 + moderatorsTable$dependOn(c("addOmnibusModeratorTestEffectSizeCoefficients", "addOmnibusModeratorTestEffectSizeCoefficientsValues", + "addOmnibusModeratorTestHeterogeneityCoefficients", "addOmnibusModeratorTestHeterogeneityCoefficientsValues")) + modelSummaryContainer[["moderatorsTable"]] <- moderatorsTable + + moderatorsTable$addColumnInfo(name = "parameter", type = "string", title = gettext("Parameter")) + moderatorsTable$addColumnInfo(name = "stat", type = "number", title = if(.maIsMetaregressionFtest(options)) gettext("F") else gettext("Q\U2098")) + moderatorsTable$addColumnInfo(name = "df1", type = "integer", title = if(.maIsMetaregressionFtest(options)) gettext("df\U2081") else gettext("df")) + if (.maIsMetaregressionFtest(options)) + moderatorsTable$addColumnInfo(name = "df2", type = "number", title = gettext("df\U2082")) + moderatorsTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) + + if (.maIsPermutation(options)) { + moderatorsTable$addColumnInfo(name = "pval2", type = "pvalue", title = gettext("p (permutation)")) + moderatorsTable$addFootnote(.maPermutationMessage(options)) + } + + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) return() - rankTestTable <- createJaspTable(gettext("Rank correlation test for Funnel plot asymmetry")) - rankTestTable$dependOn("funnelPlotRankTestAsymmetry") - rankTestTable$position <- 6 - rankTestTable$showSpecifiedColumnsOnly <- TRUE + # effect size moderation + if (.maIsMetaregressionEffectSize(options)) { + + testEffectSize <- .maOmnibusTest(fit, options, parameter = "effectSize") + moderatorsTable$addRows(testEffectSize) + if (options[["addOmnibusModeratorTestEffectSizeCoefficients"]]) { + testEffectSizeCoefficients <- .maOmnibusTestCoefficients(fit, options, parameter = "effectSize") + if (length(testEffectSizeCoefficients) == 1) { + moderatorsTable$setError(testEffectSizeCoefficients) + return() + } else { + moderatorsTable$addRows(testEffectSizeCoefficients) + moderatorsTable$addFootnote(attr(testEffectSizeCoefficients, "footnote")) + } + } + } - rankTestTable$addColumnInfo(name = "name", type = "string", title = "") - rankTestTable$addColumnInfo(name = "kendall", type = "number", title = gettextf("Kendall's %s", "\u3C4")) - rankTestTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) + # heterogeneity moderation + if (.maIsMetaregressionHeterogeneity(options)) { - container[["rankTestTable"]] <- rankTestTable + testHeterogeneity <- .maOmnibusTest(fit, options, parameter = "heterogeneity") + moderatorsTable$addRows(testHeterogeneity) - res <- try(.metaAnalysisRankTestFill(container, dataset, options, ready)) + if (options[["addOmnibusModeratorTestHeterogeneityCoefficients"]]) { + testHeterogeneityCoefficients <- .maOmnibusTestCoefficients(fit, options, parameter = "heterogeneity") + if (length(testHeterogeneityCoefficients) == 1) { + moderatorsTable$setError(testHeterogeneityCoefficients) + return() + } else { + moderatorsTable$addRows(testHeterogeneityCoefficients) + moderatorsTable$addFootnote(attr(testHeterogeneityCoefficients, "footnote")) + } + } + } - .metaAnalysisSetError(res, rankTestTable) + return() } +.maPooledEstimatesTable <- function(jaspResults, dataset, options) { + + modelSummaryContainer <- .maExtractModelSummaryContainer(jaspResults) -.metaAnalysisRegTestTable <- function(container, dataset, options, ready) { - if (!options$funnelPlotRegressionTestAsymmetry || !is.null(container[["regTestTable"]])) + if (!is.null(modelSummaryContainer[["pooledEstimatesTable"]])) return() - regTestTable <- createJaspTable(gettext("Regression test for Funnel plot asymmetry (\"Egger's test\")")) - regTestTable$dependOn("funnelPlotRegressionTestAsymmetry") - regTestTable$position <- 6 - regTestTable$showSpecifiedColumnsOnly <- TRUE - regTestTable$addCitation("Viechtbauer, W. (2010). Conducting meta-analyses in R with the metafor package. Journal of Statistical Software, 36(3), 1-48.") - - regTestTable$addColumnInfo(name = "name", type = "string", title = "") - if (options$estimateTest == "knha") - title <- gettext("t") - else - title <- gettext("z") - regTestTable$addColumnInfo(name = "test", type = "number", title = title) - regTestTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) - container[["regTestTable"]] <- regTestTable + fit <- .maExtractFit(jaspResults, options) + + # pooled estimates + pooledEstimatesTable <- createJaspTable(gettext("Meta-Analytic Estimates")) + pooledEstimatesTable$position <- 4 + pooledEstimatesTable$dependOn(c("heterogeneityTau", "heterogeneityTau2", "heterogeneityI2", "heterogeneityH2", + "confidenceIntervals", "confidenceIntervalsLevel", "predictionIntervals", "transformEffectSize")) + modelSummaryContainer[["pooledEstimatesTable"]] <- pooledEstimatesTable + + pooledEstimatesTable$addColumnInfo(name = "par", type = "string", title = "") + pooledEstimatesTable$addColumnInfo(name = "est", type = "number", title = gettext("Estimate")) + if (options[["confidenceIntervals"]]) { + overtitleCi <- gettextf("%s%% CI", 100 * options[["confidenceIntervalsLevel"]]) + pooledEstimatesTable$addColumnInfo(name = "lCi", title = gettext("Lower"), type = "number", overtitle = overtitleCi) + pooledEstimatesTable$addColumnInfo(name = "uCi", title = gettext("Upper"), type = "number", overtitle = overtitleCi) + } + if (options[["predictionIntervals"]]) { + overtitleCi <- gettextf("%s%% PI", 100 * options[["confidenceIntervalsLevel"]]) + pooledEstimatesTable$addColumnInfo(name = "lPi", title = gettext("Lower"), type = "number", overtitle = overtitleCi) + pooledEstimatesTable$addColumnInfo(name = "uPi", title = gettext("Upper"), type = "number", overtitle = overtitleCi) + + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE)) { + for (colName in .mammExtractTauLevelNames(fit)) { + pooledEstimatesTable$addColumnInfo(name = colName, title = colName, type = .maGetVariableColumnType(colName, options), overtitle = gettext("Heterogeneity Level")) + } + } + } - if(!ready) + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) return() - res <- try(.metaAnalysisRegTestFill(container, dataset, options)) + # pooled effect size + pooledEffect <- .maComputePooledEffect(fit, options) + pooledEstimatesTable$addRows(pooledEffect) + + # pooled heterogeneity + if (!.maGetMethodOptions(options) %in% c("EE", "FE") && !.maIsMultilevelMultivariate(options)) { + + # requires non-clustered fit + pooledHeterogeneity <- .maComputePooledHeterogeneity(.maExtractFit(jaspResults, options, nonClustered = TRUE), options) + + for (i in seq_len(nrow(pooledHeterogeneity))) + pooledEstimatesTable$addRows(pooledHeterogeneity[i, ]) + } + + # add messages + pooledEstimatesMessages <- .maPooledEstimatesMessages(fit, dataset, options) + for (i in seq_along(pooledEstimatesMessages)) + pooledEstimatesTable$addFootnote(pooledEstimatesMessages[i]) - .metaAnalysisSetError(res, regTestTable) + return() } +.maFitMeasuresTable <- function(jaspResults, dataset, options) { + + modelSummaryContainer <- .maExtractModelSummaryContainer(jaspResults) -.metaAnalysisCasewiseTable <- function(container, dataset, options, ready) { - if (!options$casewiseDiagnostics || !is.null(container[["casewiseTable"]])) + if (!is.null(modelSummaryContainer[["fitMeasuresTable"]])) return() - casewiseTable <- createJaspTable(gettext("Influence Measures")) - casewiseTable$dependOn("casewiseDiagnostics") - casewiseTable$position <- 6 - casewiseTable$showSpecifiedColumnsOnly <- TRUE + fit <- .maExtractFit(jaspResults, options) - casewiseTable$addColumnInfo(name = "name", type = "string", title = "") - casewiseTable$addColumnInfo(name = "sdRes", type = "number", title = gettext("Std. Residual")) - casewiseTable$addColumnInfo(name = "dfFits", type = "number", title = gettext("DFFITS")) - casewiseTable$addColumnInfo(name = "cook", type = "number", title = gettext("Cook's Distance")) - casewiseTable$addColumnInfo(name = "cov", type = "number", title = gettext("Cov. Ratio")) - casewiseTable$addColumnInfo(name = "tau2", type = "number", title = gettextf("%1$s%2$s(-i)", "\u3C4", "\u00B2")) - casewiseTable$addColumnInfo(name = "QE", type = "number", title = gettext("QE(-i)")) - casewiseTable$addColumnInfo(name = "hat", type = "number", title = gettext("Hat")) - casewiseTable$addColumnInfo(name = "weight", type = "number", title = gettext("Weight")) + # fit measures table + fitMeasuresTable <- createJaspTable(gettext("Fit Measures")) + fitMeasuresTable$position <- 4 + fitMeasuresTable$dependOn(c(.maDependencies, "fitMeasures")) + modelSummaryContainer[["fitMeasuresTable"]] <- fitMeasuresTable - container[["casewiseTable"]] <- casewiseTable - if(!ready) + fitMeasuresTable$addColumnInfo(name = "model", title = "", type = "string") + fitMeasuresTable$addColumnInfo(name = "ll", title = gettext("Log Lik."), type = "number") + fitMeasuresTable$addColumnInfo(name = "dev", title = gettext("Deviance"), type = "number") + fitMeasuresTable$addColumnInfo(name = "AIC", title = gettext("AIC"), type = "number") + fitMeasuresTable$addColumnInfo(name = "BIC", title = gettext("BIC"), type = "number") + fitMeasuresTable$addColumnInfo(name = "AICc", title = gettext("AICc"), type = "number") + + if (.maIsMetaregressionEffectSize(options) && !.maIsMultilevelMultivariate(options)) + fitMeasuresTable$addColumnInfo(name = "R2", title = gettext("R\U00B2"), type = "number") + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) return() - res <- try(.metaAnalysisCasewiseFill(container, dataset, options)) + fitSummary <- cbind("model" = colnames(fit[["fit.stats"]]), data.frame(t(fit[["fit.stats"]]))) + + if (.maIsMetaregressionEffectSize(options) && !.maIsMultilevelMultivariate(options)) + fitSummary$R2 <- fit[["R2"]] + + fitMeasuresTable$setData(fitSummary) - .metaAnalysisSetError(res, casewiseTable) + return() } +.maTermsTable <- function(jaspResults, dataset, options, parameter = "effectSize") { + + metaregressionContainer <- .maExtractMetaregressionContainer(jaspResults) -.metaAnalysisFailSafeTable <- function(container, dataset, options, ready) { - if (!options$failSafeN || !is.null(container[["failSafeTable"]]) || !ready) + if (!is.null(metaregressionContainer[[paste0(parameter, "TermsTable")]])) return() - failSafeTable <- createJaspTable(gettext("File Drawer Analysis")) - failSafeTable$dependOn("failSafeN") - failSafeTable$position <- 6 - failSafeTable$showSpecifiedColumnsOnly <- TRUE - - failSafeTable$addColumnInfo(name = "name", type = "string", title = "") - failSafeTable$addColumnInfo(name = "fsnum", type = "number", title = gettext("Fail-safe N")) - failSafeTable$addColumnInfo(name = "alpha", type = "number", title = gettext("Target Significance")) - failSafeTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("Observed Significance")) - - container[["failSafeTable"]] <- failSafeTable - - res <- try(.metaAnalysisFailSafeFill(container, dataset, options)) - - .metaAnalysisSetError(res, failSafeTable) -} - -#Table filling -.metaAnalysisFixRandFill <- function(container, dataset, options, ready) { - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - - row <- list(name = gettext("Omnibus test of Model Coefficients"), - qstat = ".", df = ".", pval = ".") - if(ready) { - row$qstat <- rma.fit$QM - row$df <- rma.fit$m - row$pval <- rma.fit$QMp - } - container[["fixRandTable"]]$addRows(row) - row <- list(name = gettext("Test of Residual Heterogeneity"), - qstat = ".", df = ".", pval = ".") - if(ready) { - row$qstat <- rma.fit$QE - row$df <- rma.fit$k - rma.fit$p - row$pval <- rma.fit$QEp - } - container[["fixRandTable"]]$addRows(row) - - if (ready) - container[["fixRandTable"]]$addFootnote(gettextf("The model was estimated using %1$s method.", options[["method"]])) -} - -.metaAnalysisCoeffFill <- function(container, dataset, options) { - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready = TRUE) - coeff <- coef(summary(rma.fit)) - - if (options[["estimateTest"]] == "z") { - for (i in 1:nrow(coeff)) { - container[["coeffTable"]]$addRows(list( - name = .metaAnalysisMakePrettyCoeffNames(rownames(coeff)[i], dataset), - est = coeff[i,"estimate"], - se = coeff[i,"se"], - zval = coeff[i,"zval"], - pval = coeff[i,"pval"], - lower = coeff[i,"ci.lb"], - upper = coeff[i,"ci.ub"] - )) - } - } else if (options[["estimateTest"]] == "knha") { - for (i in 1:nrow(coeff)) { - container[["coeffTable"]]$addRows(list( - name = .metaAnalysisMakePrettyCoeffNames(rownames(coeff)[i], dataset), - est = coeff[i,"estimate"], - se = coeff[i,"se"], - tval = coeff[i,"tval"], - df = coeff[i,"df"], - pval = coeff[i,"pval"], - lower = coeff[i,"ci.lb"], - upper = coeff[i,"ci.ub"] - )) - } - } -} + if (parameter == "heterogeneity" && !.maIsMetaregressionHeterogeneity(options)) + return() -.metaAnalysisFitMeasuresFill <- function(container, dataset, options, ready) { - stats <- list( - logLik = ".", - deviance = ".", - AIC = ".", - BIC = ".", - AICc = "." - ) - if(ready) { - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - fitStats <- try(metafor:::fitstats(rma.fit)) - stats$logLik <- fitStats[[1]] - stats$deviance <- fitStats[[2]] - stats$AIC <- fitStats[[3]] - stats$BIC <- fitStats[[4]] - stats$AICc <- fitStats[[5]] - } - - # Fill table - container[["fitMeasuresTable"]]$addRows(list(name = gettext("Log-Likelihood"), method = stats$logLik)) - container[["fitMeasuresTable"]]$addRows(list(name = gettext("Deviance"), method = stats$deviance)) - container[["fitMeasuresTable"]]$addRows(list(name = gettext("AIC"), method = stats$AIC)) - container[["fitMeasuresTable"]]$addRows(list(name = gettext("BIC"), method = stats$BIC)) - container[["fitMeasuresTable"]]$addRows(list(name = gettext("AICc"), method = stats$AICc)) -} - -.metaAnalysisResidualFill <- function(container, dataset, options, ready) { - est <- ci.lower <- ci.upper <- list( - tau2 = ".", - tau = ".", - I2 = ".", - H2 = "." - ) + fit <- .maExtractFit(jaspResults, options) - if (ready) { - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - confInt <- options$coefficientCiLevel - residPars <- try(confint(rma.fit, digits = 12, level = confInt)$random) - - est$tau2 <- residPars[1,1] - est$tau <- residPars[2,1] - est$I2 <- residPars[3,1] - est$H2 <- residPars[4,1] - - ci.lower$tau2 <- residPars[1,2] - ci.lower$tau <- residPars[2,2] - ci.lower$I2 <- residPars[3,2] - ci.lower$H2 <- residPars[4,2] - - ci.upper$tau2 <- residPars[1,3] - ci.upper$tau <- residPars[2,3] - ci.upper$I2 <- residPars[3,3] - ci.upper$H2 <- residPars[4,3] - } - - ##TODO: need name column entries in - # Fill table - container[["residualTable"]]$addRows(list( - list(name = "\u3C4\u00B2", est = est$tau2, - lower = ci.lower$tau2, upper = ci.upper$tau2), - list(name = "\u3C4", est = est$tau, - lower = ci.lower$tau, upper = ci.upper$tau), - list(name = gettextf("I%s (%%)", "\u00B2"), est = est$I2, - lower = ci.lower$I2, upper = ci.upper$I2), - list(name = gettextf("H%s", "\u00B2"), est = est$H2, - lower = ci.lower$H2, upper = ci.upper$H2) + termsTable <- createJaspTable(switch( + parameter, + effectSize = gettext("Effect Size Meta-Regression Terms Tests"), + heterogeneity = gettext("Heterogeneity Meta-Regression Terms Tests") )) -} + termsTable$position <- switch( + parameter, + effectSize = 1, + heterogeneity = 2 + ) + termsTable$dependOn("metaregressionTermTests") + metaregressionContainer[[paste0(parameter, "TermsTable")]] <- termsTable + + termsTable$addColumnInfo(name = "term", type = "string", title = "") + termsTable$addColumnInfo(name = "stat", type = "number", title = if(.maIsMetaregressionFtest(options)) gettext("F") else gettext("Q\U2098")) + termsTable$addColumnInfo(name = "df1", type = "integer", title = if(.maIsMetaregressionFtest(options)) gettext("df\U2081") else gettext("df")) + if (.maIsMetaregressionFtest(options)) { + termsTable$addColumnInfo(name = "df2", type = "number", title = gettext("df\U2082")) + } + termsTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) + termsTable$addFootnote(.maFixedEffectTextMessage(options)) -.metaAnalysisCovMatFill <- function(container, dataset, options, ready, coeffVcov) { - if(ready) { - cov <- colnames(coeffVcov) - for(i in 1:length(cov)) { - row <- list(name = cov[[i]]) - for(j in 1:length(cov)) - row[[paste(cov[[j]])]] <- coeffVcov[i,j] - container[["covMatTable"]]$addRows(row) - } - } else - container[["covMatTable"]]$addRows(list(name = "...", intercept = ".")) -} - -.metaAnalysisRankTestFill <- function(container, dataset, options, ready) { - results <- list(name = gettext("Rank test"), kendall = ".", pval = ".") - if(ready) { - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - ranktst <- unlist(metafor::ranktest(rma.fit)) - results$kendall <- ranktst[[1]] - results$pval <- ranktst[[2]] - } - container[["rankTestTable"]]$addRows(results) -} - -.metaAnalysisRegTestFill <- function(container, dataset, options) { - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready = TRUE) - egger <- metafor::regtest(rma.fit) - container[["regTestTable"]]$setData(list(name = egger$predictor, test = egger$zval, pval = egger$pval)) -} - -.metaAnalysisCasewiseFill <- function(container, dataset, options) { - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready = TRUE) - influ <- metafor::influence.rma.uni(rma.fit) - influenceVals <- influ$inf - isInfluential <- influ$is.infl - - if (sum(isInfluential) > 0) - container[["casewiseTable"]]$addFootnote(gettextf("Cases marked with %s are influential.", "\u002A")) - - for (i in 1:length(influenceVals$rstudent)) { - name <- influenceVals$slab[i] - if (!is.na(isInfluential[i]) && isInfluential[i]) - name <- paste0(name, "\u002A") - - container[["casewiseTable"]]$addRows(list( - name = name, - sdRes = influenceVals$rstudent[i], - dfFits = influenceVals$dffits[i], - cook = influenceVals$cook.d[i], - cov = influenceVals$cov.r[i], - tau2 = influenceVals$tau2.del[i], - QE = influenceVals$QE.del[i], - hat = influenceVals$hat[i], - weight = influenceVals$weight[i] + if (is.null(fit) || jaspBase::isTryError(fit)) + return() + + if (parameter == "effectSize") { + + if (!.maIsMetaregressionEffectSize(options)) + return() + + terms <- attr(terms(fit[["formula.mods"]], data = fit[["data"]]),"term.labels") + termsTests <- do.call(rbind.data.frame, lapply(terms, function(term) + .maTermTests(fit, options, term, parameter = "effectSize") + )) + termsTable$setData(termsTests) + + } else if (parameter == "heterogeneity") { + + if (!.maIsMetaregressionHeterogeneity(options)) + return() + + terms <- attr(terms(fit[["formula.scale"]], data = fit[["data"]]),"term.labels") + termsTests <- do.call(rbind.data.frame, lapply(terms, function(term) + .maTermTests(fit, options, term, parameter = "heterogeneity") )) + termsTable$setData(termsTests) + } -} -.metaAnalysisFailSafeFill <- function(container, dataset, options) { - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - fsn.fit <- metafor::fsn(x = get(options$effectSize), - sei = get(options$effectSizeSe), - data = dataset) - container[["failSafeTable"]]$addRows(list("name" = fsn.fit$type, - "fsnum" = fsn.fit$fsnum, - "alpha" = fsn.fit$alpha, - "pval" = fsn.fit$pval)) + return() } +.maCoefficientEstimatesTable <- function(jaspResults, dataset, options, parameter = "effectSize") { -# Plots -.metaAnalysisPlotsContainer <- function(container, options, ready) { - if(!ready) return() - if(!options$forestPlot && !options$funnelPlot && !options$diagnosticPlot && - !options$profilePlot && !options$trimFillAnalysis) + metaregressionContainer <- .maExtractMetaregressionContainer(jaspResults) + + if (!is.null(metaregressionContainer[[paste0(parameter, "CoefficientTable")]])) return() - if (is.null(container[["plots"]])) { - plotContainer <- createJaspContainer(gettext("Plot")) - container[["plots"]] <- plotContainer - } -} -.metaAnalysisForestPlot <- function(container, dataset, options, ready) { - if(!options$forestPlot) + if (parameter == "heterogeneity" && !.maIsMetaregressionHeterogeneity(options)) return() - .metaAnalysisPlotsContainer(container, options, ready) - plotContainer <- container[["plots"]] - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - imgHeight <- 400 - imgWidth <- 520 - if (ready){ - imgHeight <- nobs(rma.fit) * 30 + 100 - if(options[["studyLabel"]] != "") - imgWidth <- max(nchar(as.character(dataset[,options[["studyLabel"]]]))) * 5 + 500 - } - - forestPlot <- createJaspPlot(title = gettext("Forest Plot"), width = imgWidth, height = imgHeight) - forestPlot$position <- 1 - forestPlot$dependOn(c("forestPlot")) - plotContainer[["forest"]] <- forestPlot - if (ready){ - p <- try(.metaAnalysisForestPlotFill(rma.fit, showLabels = if(!is.null(options[["forestPlotLabel"]])) options[["forestPlotLabel"]] else TRUE)) - if(isTryError(p)) - forestPlot$setError(.extractErrorMessage(p)) - else - forestPlot$plotObject <- p + + fit <- .maExtractFit(jaspResults, options) + + coefficientsTable <- createJaspTable(switch( + parameter, + effectSize = gettext("Effect Size Meta-Regression Coefficients"), + heterogeneity = gettext("Heterogeneity Meta-Regression Coefficients") + )) + coefficientsTable$position <- switch( + parameter, + effectSize = 3, + heterogeneity = 4 + ) + coefficientsTable$dependOn(c("metaregressionCoefficientEstimates", "confidenceIntervals")) + metaregressionContainer[[paste0(parameter, "CoefficientTable")]] <- coefficientsTable + + coefficientsTable$addColumnInfo(name = "name", type = "string", title = "") + coefficientsTable$addColumnInfo(name = "est", type = "number", title = gettext("Estimate")) + coefficientsTable$addColumnInfo(name = "se", type = "number", title = gettext("Standard Error")) + coefficientsTable$addColumnInfo(name = "stat", type = "number", title = if(.maIsMetaregressionFtest(options)) gettext("t") else gettext("z")) + if (.maIsMetaregressionFtest(options)) + coefficientsTable$addColumnInfo(name = "df", type = "number", title = gettext("df")) + coefficientsTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) + + if (.maIsPermutation(options)) { + coefficientsTable$addColumnInfo(name = "pval2", type = "pvalue", title = gettext("p (permutation)")) + coefficientsTable$addFootnote(.maPermutationMessage(options)) } - return() -} -.metaAnalysisFunnelPlot <- function(container, dataset, options, ready) { - if(!options$funnelPlot) - return() - .metaAnalysisPlotsContainer(container, options, ready) - plotContainer <- container[["plots"]] - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - - funnelPlot <- createJaspPlot(title = gettext("Funnel Plot"), width = 520, height = 520) - funnelPlot$position <- 2 - funnelPlot$dependOn(c("funnelPlot")) - plotContainer[["funnel"]] <- funnelPlot - - if(ready){ - p <- try(.metaAnalysisFunnelPlotFill(rma.fit)) - if(isTryError(p)) - funnelPlot$setError(.extractErrorMessage(p)) - else - funnelPlot$plotObject <- p + if (options[["confidenceIntervals"]]) { + overtitleCi <- gettextf("%s%% CI", 100 * options[["confidenceIntervalsLevel"]]) + coefficientsTable$addColumnInfo(name = "lCi", title = gettext("Lower"), type = "number", overtitle = overtitleCi) + coefficientsTable$addColumnInfo(name = "uCi", title = gettext("Upper"), type = "number", overtitle = overtitleCi) } - return() -} -.metaAnalysisProfilePlot <- function(container, dataset, options, ready) { - if(!options$profilePlot) + coefficientsTable$addFootnote(.maFixedEffectTextMessage(options)) + + if (is.null(fit) || jaspBase::isTryError(fit)) return() - .metaAnalysisPlotsContainer(container, options, ready) - plotContainer <- container[["plots"]] - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - - profilePlot <- createJaspPlot(title = gettextf("Log-Likelihood for %1$s%2$s", "\u3C4", "\u00B2"), width = 520, height = 520) - profilePlot$position <- 4 - profilePlot$dependOn(c("profilePlot")) - plotContainer[["profile"]] <- profilePlot - if(ready){ - p <- try(.metaAnalysisProfilePlotFill(rma.fit)) - if(isTryError(p)) - profilePlot$setError(.extractErrorMessage(p)) - else - profilePlot$plotObject <- p + + if (parameter == "effectSize") { + + estimates <- data.frame( + name = .maVariableNames(rownames(fit[["beta"]]), options[["predictors"]]), + est = fit[["beta"]][,1], + se = fit[["se"]], + stat = fit[["zval"]], + pval = fit[["pval"]] + ) + + if (.maIsPermutation(options)) + estimates$pval2 <- attr(fit[["pval"]], "permutation") + + if (.maIsMetaregressionFtest(options)) + estimates$df <- fit[["ddf"]] + + if (options[["confidenceIntervals"]]) { + estimates$lCi <- fit[["ci.lb"]] + estimates$uCi <- fit[["ci.ub"]] + } + + coefficientsTable$setData(estimates) + + } else if (parameter == "heterogeneity") { + + estimates <- data.frame( + name = .maVariableNames(rownames(fit[["alpha"]]), options[["predictors"]]), + est = fit[["alpha"]][,1], + se = fit[["se.alpha"]], + stat = fit[["zval.alpha"]], + pval = fit[["pval.alpha"]] + ) + + if (.maIsPermutation(options)) + estimates$pval2 <- attr(fit[["pval.alpha"]], "permutation") + + if (.maIsMetaregressionFtest(options)) + estimates$df <- fit[["ddf.alpha"]] + + if (options[["confidenceIntervals"]]) { + estimates$lCi <- fit[["ci.lb.alpha"]] + estimates$uCi <- fit[["ci.ub.alpha"]] + } + + coefficientsTable$setData(estimates) + } + + if (parameter == "heterogeneity") + coefficientsTable$addFootnote(.meMetaregressionHeterogeneityMessages(options)) + return() } +.maCoefficientCorrelationMatrixTable <- function(jaspResults, dataset, options, parameter = "effectSize") { + + metaregressionContainer <- .maExtractMetaregressionContainer(jaspResults) -.metaAnalysisTrimFillPlot <- function(container, dataset, options, ready) { - if(!options$trimFillAnalysis) + if (!is.null(metaregressionContainer[[paste0(parameter, "CorrelationTable")]])) return() - .metaAnalysisPlotsContainer(container, options, ready) - plotContainer <- container[["plots"]] - # Compute/get model - trimFillPlot <- createJaspPlot(title = gettext("Trim-Fill Analysis"), width = 820, height = 820) - trimFillPlot$position <- 5 - trimFillPlot$dependOn(c("trimFillAnalysis")) - plotContainer[["trimFill"]] <- trimFillPlot - - if (ready) { - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - trimfill.fit <- metafor::trimfill(update(rma.fit, mods = ~1)) - - p <- try(.metaAnalysisTrimFillPlotFill(trimfill.fit)) - if (isTryError(p)) - trimFillPlot$setError(.extractErrorMessage(p)) - else - trimFillPlot$plotObject <- p - } - return() -} -.metaAnalysisDiagnosticPlot <- function(container, dataset, options, ready) { - if(!options$diagnosticPlot) + if (parameter == "heterogeneity" && !.maIsMetaregressionHeterogeneity(options)) return() - .metaAnalysisPlotsContainer(container, options, ready) - plotContainer <- container[["plots"]] - # Compute/get model - rma.fit <- .metaAnalysisComputeModel(container, dataset, options, ready) - diagnosticPlot <- createJaspPlot(title = gettext("Diagnostic Plots"), width = 820, height = 820) - diagnosticPlot$position <- 3 - diagnosticPlot$dependOn(c("diagnosticPlot", "diagnosticQqPlot")) - plotContainer[["diagnosticPlot"]] <- diagnosticPlot - if(ready){ - p <- try(.metaAnalysisDiagnosticPlotFill(plotContainer, rma.fit, - qqplot = options$diagnosticQqPlot, - radial = rma.fit$int.only)) - if(isTryError(p)) - diagnosticPlot$setError(.extractErrorMessage(p)) - else - diagnosticPlot$plotObject <- p - } + + fit <- .maExtractFit(jaspResults, options) + + correlationMatrixTable <- createJaspTable(switch( + parameter, + effectSize = gettext("Effect Size Meta-Regression Correlation Matrix"), + heterogeneity = gettext("Heterogeneity Meta-Regression Correlation Matrix") + )) + correlationMatrixTable$position <- switch( + parameter, + effectSize = 5, + heterogeneity = 6 + ) + correlationMatrixTable$dependOn("metaregressionCoefficientCorrelationMatrix") + metaregressionContainer[[paste0(parameter, "CorrelationTable")]] <- correlationMatrixTable + + + if (is.null(fit) || jaspBase::isTryError(fit)) + return() + + if (parameter == "effectSize") + correlationMatrix <- data.frame(cov2cor(fit[["vb"]])) + else if (parameter == "heterogeneity") + correlationMatrix <- data.frame(cov2cor(fit[["va"]])) + + correlationMatrixNames <- .maVariableNames(colnames(correlationMatrix), options[["predictors"]]) + colnames(correlationMatrix) <- correlationMatrixNames + correlationMatrix$name <- correlationMatrixNames + + correlationMatrixTable$addColumnInfo(name = "name", type = "string", title = "") + for (correlationMatrixName in correlationMatrixNames) + correlationMatrixTable$addColumnInfo(name = correlationMatrixName, type = "number") + + correlationMatrixTable$setData(correlationMatrix) + return() } +.maEstimatedMarginalMeansTable <- function(jaspResults, dataset, options, parameter = "effectSize") { -#Plot filling -.metaAnalysisTrimFillPlotFill <- function(trimfill.fit){ - plotMat <- matrix(list(), 2, 2) - plotMat[[1,1]] <- .metaAnalysisForestPlotFill(trimfill.fit) - plotMat[[1,2]] <- .metaAnalysisFunnelPlotFill(trimfill.fit) - plotMat[[2,1]] <- .metaAnalysisRadialPlotFill(trimfill.fit) - plotMat[[2,2]] <- .metaAnalysisQQPlotFill(trimfill.fit) - p <- jaspGraphs::ggMatrixPlot(plotList = plotMat, scaleXYlabels = NULL) - return(p) -} + estimatedMarginalMeansContainer <- .maExtractEstimatedMarginalMeansContainer(jaspResults) -.metaAnalysisDiagnosticPlotFill <- function(plotContainer, rma.fit, qqplot, radial = TRUE) { - plotMat <- matrix(list(), 2, 2) + if (!is.null(estimatedMarginalMeansContainer[[parameter]])) + return() - if(!is.null(plotContainer[["forest"]])) - plotMat[[1,1]] <- plotContainer[["forest"]][["plotObject"]] - else - plotMat[[1,1]] <- .metaAnalysisForestPlotFill(rma.fit) + if (parameter == "effectSize" && length(options[["estimatedMarginalMeansEffectSizeSelectedVariables"]]) == 0) + return() + if (parameter == "heterogeneity" && length(options[["estimatedMarginalMeansHeterogeneitySelectedVariables"]]) == 0) + return() - if(!is.null(plotContainer[["funnel"]])) - plotMat[[1,2]] <- plotContainer[["funnel"]][["plotObject"]] - else - plotMat[[1,2]] <- .metaAnalysisFunnelPlotFill(rma.fit) + fit <- .maExtractFit(jaspResults, options) - if(radial) - plotMat[[2,1]] <- .metaAnalysisRadialPlotFill(rma.fit) - else - plotMat[[2,1]] <- .metaAnalysisFittedVsStandardPlotFill(rma.fit) + estimatedMarginalMeansTable <- createJaspTable(switch( + parameter, + effectSize = gettext("Estimated Marginal Means: Effect Size"), + heterogeneity = gettext("Estimated Marginal Means: Heterogeneity") + )) + estimatedMarginalMeansTable$position <- switch( + parameter, + effectSize = 1, + heterogeneity = 2 + ) + estimatedMarginalMeansTable$dependOn(switch( + parameter, + effectSize = c("estimatedMarginalMeansEffectSizeSelectedVariables", "transformEffectSize", "estimatedMarginalMeansEffectSizeSdFactorCovariates", + "estimatedMarginalMeansEffectSizeTestAgainst", "estimatedMarginalMeansEffectSizeTestAgainstValue", "predictionIntervals", + "estimatedMarginalMeansEffectSizeAddAdjustedEstimate"), + heterogeneity = c("estimatedMarginalMeansHeterogeneitySelectedVariables", "estimatedMarginalMeansHeterogeneityTransformation", "estimatedMarginalMeansHeterogeneitySdFactorCovariates", + "estimatedMarginalMeansHeterogeneityAddAdjustedEstimate") + )) + estimatedMarginalMeansContainer[[parameter]] <- estimatedMarginalMeansTable - if(qqplot) - plotMat[[2,2]] <- .metaAnalysisQQPlotFill(rma.fit) - else - plotMat[[2,2]] <- .metaAnalysisStandResidPlotFill(rma.fit) - p <- jaspGraphs::ggMatrixPlot(plotList = plotMat, scaleXYlabels = NULL) - return(p) -} + if (is.null(fit) || jaspBase::isTryError(fit)) + return() + -.metaAnalysisForestPlotFill <- function(rma.fit, showLabels = TRUE){ - ci.lb <- rma.fit$yi - qnorm(rma.fit$level/2, lower.tail = FALSE) * sqrt(rma.fit$vi) - ci.ub <- rma.fit$yi + qnorm(rma.fit$level/2, lower.tail = FALSE) * sqrt(rma.fit$vi) - xlims <- c(-1, rma.fit$k+1) - ylims <- c(min(ci.lb), max(ci.ub)) - ci.int <- sprintf("%.2f [%.2f, %.2f]", rma.fit$yi, ci.lb, ci.ub) - b.pred <- predict(rma.fit) - b.ci.lb <- round(b.pred$ci.lb, 2) - b.ci.ub <- round(b.pred$ci.ub, 2) - b.ci.int <- sprintf("%.2f [%.2f, %.2f]", b.pred$pred, b.ci.lb, b.ci.ub) + estimatedMarginalMeansTable$addColumnInfo(name = "variable", type = "string", title = gettext("Variable")) + estimatedMarginalMeansTable$addColumnInfo(name = "value", type = "string", title = gettext("Level")) + estimatedMarginalMeansTable$addColumnInfo(name = "est", type = "number", title = gettext("Estimate")) - cols <- c("black", "grey") + if (options[["confidenceIntervals"]]) { + overtitleCi <- gettextf("%s%% CI", 100 * options[["confidenceIntervalsLevel"]]) + estimatedMarginalMeansTable$addColumnInfo(name = "lCi", title = gettext("Lower"), type = "number", overtitle = overtitleCi) + estimatedMarginalMeansTable$addColumnInfo(name = "uCi", title = gettext("Upper"), type = "number", overtitle = overtitleCi) + } - k <- rma.fit$k - wi <- weights(rma.fit) - psize <- wi/sum(wi, na.rm = TRUE) - rng <- max(psize, na.rm = TRUE) - min(psize, na.rm = TRUE) + if (parameter == "effectSize") { - if (rng <= .Machine$double.eps^0.5) - psize <- rep(1, k) - else - psize <- 0.5 * (psize - min(psize, na.rm = TRUE))/rng - if (all(is.na(psize))) - psize <- rep(1, k) - if(rma.fit$slab.null) - slabs <- gettextf("Study %s", rma.fit$ids[rma.fit$not.na]) - else - slabs <- rma.fit$slab[rma.fit$not.na] - - studyNos <- rma.fit$ids[rma.fit$not.na] - studies.not.na <- sum(rma.fit$not.na) - rma.data <- data.frame(StudyNo = studies.not.na + 1 - 1:studies.not.na, - labs = slabs, - ES = rma.fit$yi, - ci.int = ci.int, - ci.lb = ci.lb, - ci.ub = ci.ub, - shape = rep(15, sum(rma.fit$not.na)), - size = psize) - - #grey polygons when not intercept only - if(!rma.fit$int.only){ - pred <- fitted(rma.fit) - height <- (xlims[2] - xlims[1])/50 - alim <- range(k + 1 - rma.fit$ids[rma.fit$not.na]) - add.data <- data.frame() - for(study in 1:studies.not.na) { - if (is.na(pred[study])) - next - rownum <- studies.not.na + 1 - study - row1 <- data.frame(ES = c(pred[study], b.ci.ub[study], pred[study]), - StudyNo = c(rownum - height, rownum, rownum + height), - group = as.character(rep(study,3))) - row2 <- data.frame(ES = c(pred[study], b.ci.lb[study], pred[study]), - StudyNo = c(rownum - height, rownum, rownum + height), - group = as.character(rep(study+0.5,3))) - add.data <- rbind(add.data, row1, row2) + if (options[["predictionIntervals"]]) { + overtitleCi <- gettextf("%s%% PI", 100 * options[["confidenceIntervalsLevel"]]) + estimatedMarginalMeansTable$addColumnInfo(name = "lPi", title = gettext("Lower"), type = "number", overtitle = overtitleCi) + estimatedMarginalMeansTable$addColumnInfo(name = "uPi", title = gettext("Upper"), type = "number", overtitle = overtitleCi) + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE)) { + for (colName in .mammExtractTauLevelNames(fit)) { + estimatedMarginalMeansTable$addColumnInfo(name = colName, title = colName, type = .maGetVariableColumnType(colName, options), overtitle = gettext("Heterogeneity Level")) + } + } } - } - if(rma.fit$int.only){ - mName <- ifelse(rma.fit$method == "FE", gettext("FE Model"), gettext("RE Model")) - mData <- data.frame(StudyNo = -1, - labs = mName, - ES = b.pred$pred, - ci.int = b.ci.int, - ci.lb = b.ci.lb, - ci.ub = b.ci.ub, - shape = 18, - size = 1) - dat <- rbind(rma.data, mData) - } - else - dat <- rma.data - - # a sneaky way of coloring user-added estimates for Cochrane - dat$color <- ifelse(grepl("_add", dat$labs), "blue", "black") - dat$labs <- gsub("_add", "", dat$labs) - - if (!showLabels) { - dat$labs <- "" - dat$ci.int <- "" - } - - p <- ggplot2::ggplot(data = dat, ggplot2::aes(x = StudyNo, y = ES)) - if(!rma.fit$int.only) - p <- p + ggplot2::geom_polygon(data = add.data, fill = "grey75", ggplot2::aes(group = group)) - - p <- p + ggplot2::geom_point(data = dat, ggplot2::aes(size = size, shape = factor(shape)), colour = dat$color) + - ggplot2::geom_errorbar(ggplot2::aes(x = StudyNo, ymax = ci.ub, ymin = ci.lb), - width = 0.5, colour = dat$color) + - ggplot2::scale_shape_manual(values = c(15, 18)) - - p <- p + - ggplot2::geom_hline(ggplot2::aes(yintercept = 0), lty = "dotted", size = 0.5, colour = cols[1]) + - ggplot2::annotate("segment", x = k + .95, xend = k + .95, y = 10 * ylims[1], yend = 10 * ylims[2]) - if(rma.fit$int.only) - p <- p + ggplot2::annotate("segment", x = 0, xend = 0, y = 10 * ylims[1], yend = 10 * ylims[2]) - - # clip = "off" allows us to draw outside of the margins using the annotate("segment", ...) above. - p <- p + ggplot2::coord_flip(ylim = ylims, clip = "on") + - ggplot2::xlab(NULL) + ggplot2::ylab("Effect Size") + - ggplot2::scale_y_continuous(breaks = jaspGraphs::getPrettyAxisBreaks(ylims), - expand = ggplot2::expand_scale(mult = c(0.3,0.3), add = 0)) - - p <- p + ggplot2::scale_x_continuous(breaks = dat$StudyNo, - limits = xlims, - labels = dat$labs, - sec.axis = ggplot2::dup_axis(trans = ~., labels = dat$ci.int), - expand = ggplot2::expand_scale(mult = c(0.1,0), add = 0)) - - fontsize <- 0.85 * jaspGraphs::getGraphOption("fontsize") - p <- p + jaspGraphs::geom_rangeframe(sides = "b") + jaspGraphs::themeJaspRaw() + - ggplot2::theme(axis.ticks.y = ggplot2::element_blank(), - axis.text.y.left = ggplot2::element_text(hjust = 0, size = fontsize), - axis.text.y.right = ggplot2::element_text(hjust = 1, size = fontsize), - plot.margin = ggplot2::margin(5)) - return(p) -} - -.metaAnalysisProfilePlotFill <- function(rma.fit){ - x <- rma.fit - vc.ci <- try(suppressWarnings(confint(x)), silent = TRUE) - if (isTryError(vc.ci)) { - vc.lb <- NA - vc.ub <- NA - } - else { - vc.lb <- min(x$tau2, vc.ci$random[1, 2]) - vc.ub <- max(0.1, x$tau2, vc.ci$random[1, 3]) - } - if (is.na(vc.lb) || is.na(vc.ub)) { - vc.lb <- max(0, x$tau2 - 1.96 * x$se.tau2) - vc.ub <- max(0.1, x$tau2 + 1.96 * x$se.tau2) - } - if (is.na(vc.lb) || is.na(vc.ub)) { - vc.lb <- max(0, x$tau2/4) - vc.ub <- max(0.1, x$tau2 * 4) - } - if (is.na(vc.lb) || is.na(vc.ub)) - stop("Cannot set 'xlim' automatically. Please set this argument manually.") - xlim <- c(vc.lb, vc.ub) - vcs <- seq(xlim[1], xlim[2], length = 20) - lls <- rep(NA_real_, length(vcs)) - for (i in seq_along(vcs)) { - - argList <- list( - yi = x$yi, - vi = x$vi, - weights = x$weights, - mods = x$X, - intercept = FALSE, - method = x$method, - weighted = x$weighted, - test = x$estimateTest, - level = x$level, - control = x$control, - tau2 = vcs[i] - ) - argList <- argList[!sapply(argList, is.null)] - - res <- try(suppressWarnings(do.call(metafor::rma.uni, argList)), silent = TRUE) - if (isTryError(res)) - next - lls[i] <- c(logLik(res)) - } - - xlab <- bquote(paste(tau^2, .(gettext(" Value")))) - title <- bquote(paste(.(gettext("Profile Plot for ")), tau^2)) - profile.data <- data.frame(tau2 = vcs, ll = lls) - - ylim <- c(min(lls, logLik(x)[1]), max(lls, logLik(x)[1] + 0.001*abs(logLik(x)[1]))) - - p <- ggplot2::ggplot(data = profile.data, ggplot2::aes(x = tau2, y = ll)) + - ggplot2::geom_point(data = profile.data, shape = 19, colour = "black") + - ggplot2::geom_line() + - ggplot2::geom_hline(yintercept = logLik(x), linetype = "dotted", colour = "black") + - ggplot2::geom_vline(xintercept = x$tau2, linetype = "dotted", colour = "black") + - ggplot2::xlab(xlab) + ggplot2::ylab(gettext("Restricted Log-Likelihood")) + - ggplot2::ggtitle(title) + - ggplot2::scale_x_continuous(breaks = jaspGraphs::getPrettyAxisBreaks(xlim), - limits = xlim) + - ggplot2::scale_y_continuous(breaks = jaspGraphs::getPrettyAxisBreaks(ylim), - limits = ylim) - p <- p + ggplot2::theme(axis.line.x = ggplot2::element_line(), - axis.line.y = ggplot2::element_line()) - p <- jaspGraphs::themeJasp(p, legend.position = "none") - return(p) -} - -.metaAnalysisFunnelPlotFill <- function(rma.fit){ - x <- rma.fit - level <- x$level - ci.res <- 1000 - k <- x$k - - if (!inherits(x, "rma.uni.trimfill")) { - col.vec <- FALSE - col <- rep("black", x$k.all) - if (!is.null(x$subset)) - col <- col[x$subset] - bg.vec <- FALSE - bg <- rep("white", x$k.all) - if (!is.null(x$subset)) - bg <- bg[x$subset] - } else { - col <- c("black", "black") - if (length(col) == 1L) - col <- c(col, "black") - col.vec <- FALSE - bg <- c("white", "white") - if (length(bg) == 1L) - bg <- c(bg, "white") - bg.vec <- FALSE - } - if (x$int.only) { - refline <- c(x$beta) - yi <- x$yi - vi <- x$vi - ni <- x$ni - sei <- sqrt(vi) - slab <- x$slab[x$not.na] - xlab <- "Effect Size" - } else { - refline <- 0 - res <- rstandard(x) - not.na <- x$not.na - #not.na <- !is.na(res$resid) - yi <- res$resid[not.na] - sei <- res$se[not.na] - ni <- x$ni.f[not.na] - vi <- sei^2 - slab <- x$slab[not.na] - xlab <- gettext("Residual Value") - } - - ylim <- c(0, max(sei[!is.na(sei)])) - - level <- ifelse(level == 0, 1, - ifelse(level >= 1, (100 - level)/100, - ifelse(level > 0.5, 1 - level, level))) - level.min <- min(level) - lvals <- length(level) - - x.lb.bot <- refline - qnorm(level.min/2, lower.tail = FALSE) * ylim[2] - x.ub.bot <- refline + qnorm(level.min/2, lower.tail = FALSE) * ylim[2] - - xlim <- c(min(x.lb.bot, min(yi[!is.na(yi)])), max(x.ub.bot, max(yi[!is.na(yi)]))) - rxlim <- xlim[2] - xlim[1] - xlim[1] <- xlim[1] - (rxlim * 0.1) - xlim[2] <- xlim[2] + (rxlim * 0.1) - - new_ylim <- c() - rylim <- ylim[1] - ylim[2] - new_ylim[1] <- ylim[1] - #new_ylim[1] <- ylim[1] + (rylim * 0.1) - # new_ylim[2] <- ylim[2] # this is not necessary I believe - new_ylim[2] <- max(0, ylim[2] - (rylim * 0.1)) - - yi.vals <- seq(from = new_ylim[2], to = new_ylim[1], length.out = ci.res) - - xaxis.vals <- yi - yaxis.vals <- sei - - ci.left <- refline - qnorm(level[1]/2, lower.tail = FALSE) * yi.vals - ci.right <- refline + qnorm(level[1]/2, lower.tail = FALSE) * yi.vals - - # I don't know why this was added - # It makes the x-axis symmetric, but this is unusual for a funnel plot.. - # xend <- max(abs(c(ci.left, ci.right, xlim))) - # xlims <- c(-1*xend, xend) - xlims <- xlim - - if(inherits(x, "rma.uni.trimfill")) { - fillcol <- ifelse(x$fill, "white", "black") - shape <- ifelse(x$fill, 1, 19) - } else { - fillcol <- rep("black", sum(x$not.na)) - shape <- 19 - } - - funnel.data <- data.frame(x = xaxis.vals, y = yaxis.vals, slab = slab, fill = fillcol) - triangle.data <- data.frame(x = c(ci.left, ci.right[ci.res:1]), - y = c(yi.vals, yi.vals[ci.res:1])) - hlines <- jaspGraphs::getPrettyAxisBreaks(ylim) - #hlines <- seq(from = ylim[1], to = ylim[2], length.out = 5) - p <- ggplot2::ggplot(data = funnel.data, ggplot2::aes(x = x, y = y)) - p <- p + ggplot2::geom_hline(yintercept = hlines, linetype = "solid", colour = "white") - p <- p + ggplot2::geom_polygon(data = triangle.data, fill = "white") - p <- p + ggplot2::geom_point(data = funnel.data, shape = shape, colour = "black", fill = fillcol) - p <- p + ggplot2::geom_segment(ggplot2::aes(x = refline, y = new_ylim[2], xend = refline, yend = ylim[1]), - linetype = "solid", colour = "black") - p <- p + ggplot2::geom_segment(ggplot2::aes(x = min(ci.left), y = new_ylim[2], xend = refline, yend = new_ylim[1]), - linetype = "dotted", colour = "black") + - ggplot2::geom_segment(ggplot2::aes(x = refline, y = new_ylim[1], xend = max(ci.right), yend = new_ylim[2]), - linetype = "dotted", colour = "black") - p <- p + ggplot2::xlab(xlab) + ggplot2::ylab(gettext("Standard Error")) - #p <- p + ggplot2::ylim(new_ylim[1], new_ylim[2]) - p <- jaspGraphs::themeJasp(p) - p <- p + ggplot2::theme(axis.line.x.bottom= ggplot2::element_line(), - axis.line.x.top = ggplot2::element_blank(), - axis.line.y = ggplot2::element_line(), - panel.background = ggplot2::element_rect(fill = "lightgrey"), - panel.grid.major = ggplot2::element_blank(), - panel.grid.minor = ggplot2::element_blank(), - legend.position = "none") - p <- p + ggplot2::scale_y_reverse(limits = c(new_ylim[2], new_ylim[1]), - breaks = hlines, - labels = round(hlines, 3), - expand = ggplot2::expand_scale(mult = c(0,0.05), add = 0)) + - ggplot2::scale_x_continuous(limits = xlims, - breaks = jaspGraphs::getPrettyAxisBreaks(xlims)) - return(p) -} - -.metaAnalysisRadialPlotFill <- function(rma.fit){ - x <- rma.fit - #new.radial(x) - if (!inherits(x, "rma")) - stop("Argument 'x' must be an object of class \"rma\".") - if (inherits(x, "robust.rma")) - stop("Function not applicable to objects of class \"robust.rma\".") - if (inherits(x, "rma.ls")) - stop("Function not applicable to objects of class \"rma.ls\".") - level <- x$level - yi <- x$yi - vi <- x$vi - beta <- x$beta - ci.lb <- x$ci.lb - ci.ub <- x$ci.ub - tau2 <- 1/mean(1/x$tau2) - atyis <- range(yi) - level <- ifelse(level == 0, 1, - ifelse(level >= 1, (100 - level)/100, - ifelse(level > 0.5, 1 - level, level))) - zcrit <- qnorm(level/2, lower.tail = FALSE) - zi <- yi/sqrt(vi + tau2) - xi <- 1/sqrt(vi + tau2) - if (any(is.infinite(c(xi, zi)))) - stop(mstyle$stop("Setting 'xlim' and 'zlim' automatically not possible (must set axis limits manually).")) - xlims <- c(0, (1.3 * max(xi))) - ci.xpos <- xlims[2] + 0.12 * (xlims[2] - xlims[1]) - ya.xpos <- xlims[2] + 0.14 * (xlims[2] - xlims[1]) - xaxismax <- xlims[2] - zlims <- c(min(-5, 1.1 * min(zi), 1.1 * ci.lb * ci.xpos, - 1.1 * min(atyis) * ya.xpos, 1.1 * min(yi) * ya.xpos, - -1.1 * zcrit + xaxismax * beta), - max(5, 1.1 * max(zi), 1.1 * ci.ub * ci.xpos, - 1.1 * max(atyis) * ya.xpos, 1.1 * max(yi) * ya.xpos, - 1.1 * zcrit + xaxismax * beta)) - - asp.rat <- (zlims[2] - zlims[1])/(xlims[2] - xlims[1]) - - if(x$method == "FE") { - xlabExpression <- bquote(x[i] == frac(1, sqrt(v[i]))) - ylabExpression <- bquote(z[i] == frac(y[i], sqrt(v[i]))) - } else { - xlabExpression <- bquote(x[i] == frac(1, sqrt(v[i]+tau^2))) - ylabExpression <- bquote(z[i] == frac(y[i], sqrt(v[i]+tau^2))) - } - - .arc.line <- function(zlims, yi, ya.xpos, asp.rat, length){ - atyis <- seq(min(yi), max(yi), length = length) - len <- ya.xpos - xis <- sqrt(len^2/(1 + (atyis/asp.rat)^2)) - zis <- xis * atyis - valid <- zis > zlims[1] & zis < zlims[2] - xisv <- xis[valid] - zisv <- zis[valid] - dat <- data.frame() - for(j in 2:length(atyis)) { - row <- data.frame( - x = xisv[j-1], - y = zisv[j-1], - xend = xisv[j], - yend = zisv[j] - ) - dat <- rbind(dat, row) + if (options[["estimatedMarginalMeansEffectSizeTestAgainst"]]) { + estimatedMarginalMeansTable$addColumnInfo(name = "stat", type = "number", title = if(.maIsMetaregressionFtest(options)) gettext("t") else gettext("z")) + if (.maIsMetaregressionFtest(options)) + estimatedMarginalMeansTable$addColumnInfo(name = "df", type = "number", title = gettext("df")) + + estimatedMarginalMeansTable$addColumnInfo(name = "pval", type = "pvalue", title = gettext("p")) } - return(ggplot2::geom_segment(data = dat, - ggplot2::aes(x = x, y = y, - xend = xend, yend = yend))) - } - .arc.ticks <- function(xlims, yi, ya.xpos, asp.rat){ - atyis <- seq(min(yi), max(yi), length = 7) - len.l <- ya.xpos - len.u <- ya.xpos + 0.015 * (xlims[2] - xlims[1]) - xis.l <- sqrt(len.l^2/(1 + (atyis/asp.rat)^2)) - zis.l <- xis.l * atyis - xis.u <- sqrt(len.u^2/(1 + (atyis/asp.rat)^2)) - zis.u <- xis.u * atyis - valid <- zis.l > zlims[1] & zis.u > zlims[1] & zis.l < zlims[2] & zis.u < zlims[2] - dat <- data.frame(x = xis.l[valid], xend = xis.u[valid], - y = zis.l[valid], yend = zis.u[valid]) - return(ggplot2::geom_segment(data = dat, - ggplot2::aes(x = x, y = y, - xend = xend, yend = yend), - colour = "black")) - } - .arc.text <- function(xlims, yi, ya.xpos, asp.rat){ - atyis <- seq(min(yi), max(yi), length = 7) - len <- ya.xpos + 0.02 * (xlims[2] - xlims[1]) - xis <- sqrt(len^2/(1 + (atyis/asp.rat)^2)) - zis <- xis * atyis - valid <- zis > zlims[1] & zis < zlims[2] - dat <- data.frame(x = xis[valid], y = zis[valid], - label = as.character(round(atyis[valid], 2))) - return(ggplot2::geom_text(data = dat, ggplot2::aes(x = x, y = y, label = label), - nudge_x = 0.1 * (xlims[2] - xlims[1]), hjust = 0)) - } - .arc.int <- function(xlims, zlims, ci.xpos, ci.lb, beta, ci.ub, asp.rat){ - atyis <- c(ci.lb, beta, ci.ub) - len.l <- ci.xpos - 0.007 * (xlims[2] - xlims[1]) - len.u <- ci.xpos + 0.007 * (xlims[2] - xlims[1]) - - xis.l <- sqrt(len.l^2/(1 + (atyis/asp.rat)^2)) - zis.l <- xis.l * atyis - xis.u <- sqrt(len.u^2/(1 + (atyis/asp.rat)^2)) - zis.u <- xis.u * atyis - - valid <- zis.l > zlims[1] & zis.u > zlims[1] & zis.l < zlims[2] & zis.u < zlims[2] - dat <- data.frame(xl = xis.l[valid], - zl = zis.l[valid], - xu = xis.u[valid], - zu = (xis.u * atyis)[valid]) - connectingLine <- data.frame(xl = mean(c(dat[1,1], dat[1,3])), - zl = mean(c(dat[1,2], dat[1,4])), - xu = mean(c(dat[3,1], dat[3,3])), - zu = mean(c(dat[3,2], dat[3,4]))) - dat <- rbind(dat, connectingLine) - return(ggplot2::geom_segment(data = dat, ggplot2::aes(x = xl, xend = xu, - y = zl, yend = zu))) - } - arc.line <- .arc.line(zlims, yi, ya.xpos, asp.rat, length = 100) - arc.ticks <- .arc.ticks(xlims, yi, ya.xpos, asp.rat) - arc.text <- .arc.text(xlims, yi, ya.xpos, asp.rat) - arc.int <- .arc.int(xlims, zlims, ci.xpos, ci.lb, beta, ci.ub, asp.rat) - - len <- ya.xpos + 0.02 * (xlims[2] - xlims[1]) - atyis <- seq(min(yi), max(yi), length = 7) - x.margin.right <- 1.2 * max(arc.text$data$x)#max(sqrt(len^2/(1 + (atyis)/asp.rat)^2)) - - radial.data <- data.frame(x = xi, y = zi, slab = x$slab[x$not.na]) - rectangle.data <- data.frame(x = c(0, xaxismax, xaxismax, 0), - y = c(zcrit, zcrit + xaxismax * beta, - -zcrit + xaxismax * beta, -zcrit)) - p <- ggplot2::ggplot(data = radial.data, ggplot2::aes(x = x, y = y)) + - ggplot2::geom_polygon(data = rectangle.data, fill = "lightgrey") + - ggplot2::geom_point(data = radial.data, shape = 19, colour = "black") + - ggplot2::ggtitle(gettext("Radial Plot")) - p <- p + arc.line + arc.ticks + arc.int + arc.text - p <- p + ggplot2::geom_segment(ggplot2::aes(x = xlims[1], y = max(zcrit), xend = xlims[2], - yend = max(zcrit + xaxismax * beta)), - linetype = "dotted", colour = "black") - p <- p + ggplot2::geom_segment(ggplot2::aes(x = xlims[1], y = min(-zcrit), xend = xlims[2], - yend = min(-zcrit +xaxismax * beta)), - linetype = "dotted", colour = "black") - p <- p + ggplot2::geom_segment(ggplot2::aes(x = 0, y = 0, xend = xlims[2], yend = xaxismax * beta), - linetype = "solid", colour = "black") - - valsForBreaks <- c(-zcrit, zcrit, min(-zcrit +xaxismax * beta), max(zcrit + xaxismax * beta)) - yBreaks <- jaspGraphs::getPrettyAxisBreaks(valsForBreaks) - # do it again to get something symmetric around 0 - temp <- max(abs(yBreaks)) - yBreaks <- jaspGraphs::getPrettyAxisBreaks(c(-temp, temp)) - # add the data from the right axis to stop ggplot2 from deleting these values - yLimits <- range(jaspGraphs::getPrettyAxisBreaks(c( - yBreaks, valsForBreaks, arc.text$data$y, arc.line$data$y, arc.line$data$yend) - )) + } - yBreaks <- jaspGraphs::getPrettyAxisBreaks(c(-temp, temp)) - xBreaks <- jaspGraphs::getPrettyAxisBreaks(c(0, radial.data$x)) - xLimits <- c(0, x.margin.right) - p <- p + ggplot2::xlab(xlabExpression) + ggplot2::ylab(ylabExpression) + - ggplot2::scale_x_continuous(breaks = xBreaks, limits = xLimits) + - ggplot2::scale_y_continuous(breaks = yBreaks, limits = yLimits) - - p <- p + jaspGraphs::geom_rangeframe() + jaspGraphs::themeJaspRaw() - - # we want to show the axis titles in the middle of the breaks, not the middle of the limits (the default) - # so we adjust the vjust and hjust accordingly - vjustY <- (mean(yBreaks) - yLimits[1L]) / (yLimits[2L] - yLimits[1L]) - hjustX <- (mean(xBreaks) - xLimits[1L]) / (xLimits[2L] - xLimits[1L]) - - p <- p + ggplot2::theme(axis.line.x = ggplot2::element_blank(), - axis.line.y = ggplot2::element_blank(), - axis.title.y = ggplot2::element_text(size = 12, angle = 0, vjust = vjustY), - axis.title.x = ggplot2::element_text(size = 12, hjust = hjustX), - panel.background = ggplot2::element_blank(), - panel.grid.major = ggplot2::element_blank(), - panel.grid.minor = ggplot2::element_blank(), - legend.position = "none") - return(p) -} - -.metaAnalysisQQPlotFill <- function(rma.fit){ - x <- rma.fit - if (x$k == 1) - stop(gettext("Stopped because k = 1.")) - - res <- rstandard(x) - not.na <- !is.na(res$z) - zi <- res$z[not.na] - slab <- res$slab[not.na] - ord <- order(zi) - slab <- slab[ord] - - sav <- qqnorm(zi, plot.it = FALSE) - pos.x <- sav$x[ord] - pos.y <- sav$y[ord] - - reps <- 1000 - level <- x$level - dat <- matrix(rnorm(x$k * reps), nrow = x$k, ncol = reps) - H <- hatvalues(x, type = "matrix") - ImH <- diag(x$k) - H - ei <- ImH %*% dat - ei <- apply(ei, 2, sort) - lb <- apply(ei, 1, quantile, (level/2)) - ub <- apply(ei, 1, quantile, 1 - (level/2)) - temp.lb <- qqnorm(lb, plot.it = FALSE) - temp.lb <- supsmu(temp.lb$x, temp.lb$y) - temp.ub <- qqnorm(ub, plot.it = FALSE) - temp.ub <- supsmu(temp.ub$x, temp.ub$y) - - xBreaks <- jaspGraphs::getPrettyAxisBreaks(pos.x) - yBreaks <- jaspGraphs::getPrettyAxisBreaks(c(pos.y, temp.lb$y, temp.ub$y)) - xLimits <- range(xBreaks) - yLimits <- range(yBreaks) - - qq.data <- data.frame(x = pos.x, y = pos.y, ci.lb = temp.lb$y, ci.ub = temp.ub$y) - p <- ggplot2::ggplot(data = qq.data) + - ggplot2::ggtitle(gettext("Normal Q-Q Plot")) + - ggplot2::geom_ribbon(data = qq.data, ggplot2::aes(ymin = ci.lb, ymax = ci.ub, x = x), - fill = "gray", alpha = 0.5, stat = "identity") + - ggplot2::geom_point(ggplot2::aes(x = x, y = y), shape = 19, colour = "black") + - ggplot2::geom_abline(slope = 1, intercept = 0) + - ggplot2::scale_x_continuous(name = gettext("Theoretical Quantiles"), limits = xLimits, breaks = xBreaks) + - ggplot2::scale_y_continuous(name = gettext("Sample Quantiles"), limits = yLimits, breaks = yBreaks) - p <- jaspGraphs::themeJasp(p) - return(p) -} - -.metaAnalysisStandResidPlotFill <- function(rma.fit) { - res <- rstandard(rma.fit) - zi <- res$z[!is.na(res$z)] - title <- gettext("Standardized Residuals") - study <- seq_along(zi) - stand.data <- data.frame(study = factor(study, levels = study), resid = zi) - hlines <- qnorm(c(0.025, 0.5, 0.975)) - linetypes <- c("dotted", "dashed", "dotted") - ylims <- range(c(zi, hlines)) - - p <- ggplot2::ggplot(data = stand.data, ggplot2::aes(x = study, y = resid, group = 1)) + - ggplot2::geom_point(shape = 19, colour = "black") + ggplot2::geom_line() + - ggplot2::geom_hline(yintercept = hlines, linetype = linetypes, colour = "black") + - ggplot2::xlab(gettext("Study")) + ggplot2::ylab(" ") + ggplot2::ggtitle(title) - p <- p + ggplot2::scale_y_continuous(breaks = jaspGraphs::getPrettyAxisBreaks(ylims), - limits = ylims) + - ggplot2::theme(axis.line.x = ggplot2::element_line(), - axis.line.y = ggplot2::element_line(), - axis.ticks.x.bottom = ggplot2::element_line()) - p <- jaspGraphs::themeJasp(p, legend.position = "none") - - return(p) -} - -.metaAnalysisFittedVsStandardPlotFill <- function(rma.fit){ - title <- gettext("Fitted vs. Standardized Residuals") - fit.data <- data.frame(x = fitted(rma.fit), y = rstandard(rma.fit)$z) - hlines <- qnorm(c(0.025, 0.5, 0.975)) - lty <- c("dotted", "dashed", "dotted") - xlims <- range(fitted(rma.fit)) - ylims <- range(rstandard(rma.fit)$z) - p <- ggplot2::ggplot(data = fit.data) + - ggplot2::geom_point(ggplot2::aes(x = x, y = y)) + - ggplot2::geom_hline(yintercept = hlines, linetype = lty, colour = "black") + - ggplot2::xlab(gettext("Fitted Value")) + ggplot2::ylab(gettext("Standardized Residual")) + - ggplot2::ggtitle(title) + - ggplot2::scale_x_continuous(limits = xlims, - breaks = jaspGraphs::getPrettyAxisBreaks(xlims)) + - ggplot2::scale_y_continuous(limits = ylims, - breaks = jaspGraphs::getPrettyAxisBreaks(ylims)) - p <- p + ggplot2::theme(axis.line.x = ggplot2::element_line(), - axis.line.y = ggplot2::element_line(), - axis.ticks.x.bottom = ggplot2::element_line() + + selectedVariables <- switch( + parameter, + effectSize = c( + if (options[["estimatedMarginalMeansEffectSizeAddAdjustedEstimate"]]) "", + unlist(options[["estimatedMarginalMeansEffectSizeSelectedVariables"]]) + ), + heterogeneity = c( + if (options[["estimatedMarginalMeansHeterogeneityAddAdjustedEstimate"]]) "", + unlist(options[["estimatedMarginalMeansHeterogeneitySelectedVariables"]]) + ) ) - p <- jaspGraphs::themeJasp(p, legend.position = "none") - return(p) + estimatedMarginalMeans <- do.call(rbind, lapply(selectedVariables, function(selectedVariable) + .maComputeMarginalMeansVariable(fit, options, dataset, selectedVariable, options[["estimatedMarginalMeansEffectSizeTestAgainstValue"]], parameter))) + + # drop non-required columns + if (parameter == "effectSize" && !options[["estimatedMarginalMeansEffectSizeTestAgainst"]]) + estimatedMarginalMeans <- estimatedMarginalMeans[,!colnames(estimatedMarginalMeans) %in% c("df", "stat", "pval")] + else if (parameter == "heterogeneity") + estimatedMarginalMeans <- estimatedMarginalMeans[,!colnames(estimatedMarginalMeans) %in% c("lPi", "uPi")] + + estimatedMarginalMeansTable$setData(estimatedMarginalMeans) + + estimatedMarginalMeansMessages <- .maEstimatedMarginalMeansMessages(options, parameter) + for (i in seq_along(estimatedMarginalMeansMessages)) + estimatedMarginalMeansTable$addFootnote(estimatedMarginalMeansMessages[i]) + + return() } +.maUltimateForestPlot <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["forestPlot"]])) + return() + + if (!any(c( + options[["forestPlotStudyInformation"]], + (options[["forestPlotEstimatedMarginalMeans"]] && ( + length(options[["forestPlotEstimatedMarginalMeansSelectedVariables"]]) > 0 || + options[["forestPlotEstimatedMarginalMeansAdjustedEffectSizeEstimate"]] + )), + options[["forestPlotModelInformation"]] + ))) + return() + + fit <- .maExtractFit(jaspResults, options) + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) + return() + + # try execute! + plotOut <- try(.maMakeTheUltimateForestPlot(fit, dataset, options)) + + if (inherits(plotOut, "try-error")) { + forestPlot <- createJaspPlot(title = gettext("Forest Plot")) + forestPlot$position <- 4 + forestPlot$dependOn(.maForestPlotDependencies) + forestPlot$setError(plotOut) + jaspResults[["forestPlot"]] <- forestPlot + return() + } -# Extra functions -.metaAnalysisFormula <- function(options){ - if (length(options$modelTerms) > 0) - formula.rhs <- formula(as.modelTerms(options$modelTerms)) + # try adjusting height and width + height <- 200 + (attr(plotOut, "rows")) * 10 + if (!attr(plotOut, "isPanel")) + width <- 500 else - formula.rhs <- NULL - - if (is.null(formula.rhs)) - formula.rhs <- ~1 - if (!options$interceptTerm) - formula.rhs <- update(formula.rhs, ~ . + 0) - - if (identical(formula.rhs, ~ 1 - 1)) - .quitAnalysis(gettext("The model should contain at least one predictor or an intercept.")) - - return(formula.rhs) -} - -# we need both of these functions, because these values are shown as columns, but also passed along as arguments to the meta analysis pkg -.metaAnalysisGetTranslatedMethod <- function(options){ - switch(options$method, - "Fixed Effects" = gettext("FE"), - "Maximum Likelihood" = gettext("ML"), - "Restricted ML" = gettext("REML"), - "DerSimonian-Laird" = gettext("DL"), - "Hedges" = gettext("HE"), - "Hunter-Schmidt" = gettext("HS"), - "Sidik-Jonkman" = gettext("SJ"), - "Empirical Bayes" = gettext("EB"), - "Paule-Mandel" = gettext("PM") - ) -} + width <- 500 + 500 * attr(plotOut, "panelRatio") -.metaAnalysisGetMethod <- function(options){ - switch(options$method, - "Fixed Effects" = "FE", - "Maximum Likelihood" = "ML", - "Restricted ML" = "REML", - "DerSimonian-Laird" = "DL", - "Hedges" = "HE", - "Hunter-Schmidt" = "HS", - "Sidik-Jonkman" = "SJ", - "Empirical Bayes" = "EB", - "Paule-Mandel" = "PM" + forestPlot <- createJaspPlot( + title = gettext("Forest Plot"), + width = width, + height = height ) -} + forestPlot$position <- 5 + forestPlot$dependOn(.maForestPlotDependencies) -.metaAnalysisConfidenceInterval <- function(options, table) { - if(options$coefficientCi) { - ci <- gettextf("%g%% Confidence Interval", 100 * options$coefficientCiLevel) - table$addColumnInfo(name = "lower", type = "number", title = "Lower", overtitle = ci) - table$addColumnInfo(name = "upper", type = "number", title = "Upper", overtitle = ci) + if (!attr(plotOut, "isPanel")) { + forestPlot$plotObject <- plotOut + } else { + plotOut <- jaspGraphs:::jaspGraphsPlot$new( + subplots = plotOut, + layout = attr(plotOut, "layout"), + heights = 1, + widths = attr(plotOut, "widths") + ) + forestPlot$plotObject <- plotOut } -} -.metaAnalysisSetError <- function(res, table) { - if(isTryError(res)) - table$setError(.extractErrorMessage(res)) + jaspResults[["forestPlot"]] <- forestPlot + + + return() } +.maBubblePlot <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["bubblePlot"]])) + return() -# Replaces "intrcpt" with "intercept" and concated "factorNamelevelName" with "factorName (levelName)" -.metaAnalysisMakePrettyCoeffNames <- function(coeffNames, dataset, concatFactorNames = NULL) { - newNames <- coeffNames + if (length(options[["bubblePlotSelectedVariable"]]) == 0) + return() - if (is.null(concatFactorNames)) - concatFactorNames <- .metaAnalysisMapConcatFactorNames(dataset) + fit <- .maExtractFit(jaspResults, options) - for (i in seq_along(coeffNames)) { - coeffName <- coeffNames[i] + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) + return() - if (coeffName == "intrcpt") { - newNames[i] <- "intercept" - } else if (!is.null(concatFactorNames)) { - coeffNameEnc <- coeffName - if (grepl(":", coeffNameEnc, fixed = TRUE)) { # it's an interaction term - terms <- unlist(strsplit(coeffNameEnc, ":", fixed = TRUE)) - replaced <- .metaAnalysisMakePrettyCoeffNames(terms, dataset, concatFactorNames) - newNames[i] <- paste(replaced, collapse = "\u2009\u273b\u2009") - } else { # it's a regular term - match <- which(concatFactorNames == coeffName) - if (length(match) == 1) - newNames[i] <- names(concatFactorNames)[match] - } + # set dimensions + width <- if (length(options[["bubblePlotSeparateLines"]]) == 0 || options[["bubblePlotLegendPosition"]] == "none") 450 else 550 + height <- 350 + + # create containers / figure + if (length(options[["bubblePlotSeparatePlots"]]) > 0) { + bubblePlotContainer <- createJaspContainer(title = gettext("Bubble Plots")) + bubblePlotContainer$dependOn(.maBubblePlotDependencies) + bubblePlotContainer$position <- 5 + jaspResults[["bubblePlot"]] <- bubblePlotContainer + } else { + bubblePlot <- createJaspPlot(title = gettext("Bubble Plot"), width = width, height = height) + bubblePlot$dependOn(.maBubblePlotDependencies) + bubblePlot$position <- 6 + jaspResults[["bubblePlot"]] <- bubblePlot + } + + # make bubble plots + dfPlot <- .maMakeBubblePlotDataset(fit, options, dataset) + + if (attr(dfPlot, "separatePlots") == "") { + tempPlots <- list(.maMakeBubblePlot(fit, options, dfPlot)) + } else { + tempPlots <- lapply(unique(dfPlot[["separatePlots"]]), function(lvl) { + .maMakeBubblePlot(fit, options, dfPlot[dfPlot[["separatePlots"]] == lvl,], separatePlotsLvl = lvl) + }) + } + + # modify all generated plots simultaneously + yRange <- do.call(rbind, lapply(tempPlots, attr, which = "yRange")) + yRange <- c(min(yRange[, 1]), max(yRange[, 2])) + yRange <- range(jaspGraphs::getPrettyAxisBreaks(yRange)) + + tempPlots <- lapply(tempPlots, function(plot) { + .maAddBubblePlotTheme(plot, options, dfPlot, yRange) + }) + + if (length(options[["bubblePlotSeparatePlots"]]) > 0) { + for (i in seq_along(tempPlots)) { + bubblePlot <- createJaspPlot(title = gettextf("%1$s (%2$s)", attr(dfPlot, "separatePlots"), unique(dfPlot[["separatePlots"]])[i]), width = width, height = height) + bubblePlot$position <- i + bubblePlot$plotObject <- tempPlots[[i]] + bubblePlotContainer[[paste0("plot", i)]] <- bubblePlot } + } else { + bubblePlot$plotObject <- tempPlots[[1]] } - return(newNames) + return() } +.maShowMetaforRCode <- function(jaspResults, options) { -# Creates a named character vector with values = "factorNameLevelName" and names = "factorName (levelName)" -.metaAnalysisMapConcatFactorNames <- function(dataset) { - factorCols <- unlist(lapply(dataset, is.factor)) - if (length(factorCols) == 0) - return(NULL) + if (!.maReady(options) || !is.null(jaspResults[["metaforRCode"]])) + return() + + metaforRCode <- createJaspHtml(title = gettext("Metafor R Code")) + metaforRCode$dependOn(c(.maDependencies, "showMetaforRCode")) + metaforRCode$position <- 99 + + metaforRCode$text <- .maTransformToHtml(.maMakeMetaforCallText(options)) + + jaspResults[['metaforRCode']] <- metaforRCode + + return() +} +.maVarianceInflationTable <- function(jaspResults, dataset, options, parameter = "effectSize") { + + varianceInflationContainer <- .maExtractVarianceInflationContainer(jaspResults) + + if (!is.null(varianceInflationContainer[[parameter]])) + return() + + if (parameter == "heterogeneity" && !.maIsMetaregressionHeterogeneity(options)) + return() + + fit <- .maExtractFit(jaspResults, options) + + termsTable <- createJaspTable(switch( + parameter, + effectSize = gettext("Effect Size Meta-Regression Variance Inflation"), + heterogeneity = gettext("Heterogeneity Meta-Regression Variance Inflation") + )) + termsTable$position <- switch( + parameter, + effectSize = 1, + heterogeneity = 2 + ) + varianceInflationContainer[[parameter]] <- termsTable + + termsTable$addColumnInfo(name = "term", type = "string", title = "") + if (options[["diagnosticsVarianceInflationFactorAggregate"]]) + termsTable$addColumnInfo(name = "m", type = "integer", title = gettext("Parameters")) + + termsTable$addColumnInfo(name = "vif", type = "number", title = gettext("VIF")) + termsTable$addColumnInfo(name = "sif", type = "number", title = gettext("SIF")) + + if (is.null(fit) || jaspBase::isTryError(fit)) + return() + + termsTable$setData(.maComputeVifSummary(fit, options, parameter)) + + return() +} +.maCasewiseDiagnosticsTable <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["casewiseDiagnosticsTable"]])) + return() + + # diagnostics are unavaible for location-scale models + if (.maIsMetaregressionHeterogeneity(options)) { + # fit measures table + casewiseDiagnosticsTable <- createJaspTable(gettext("Casewise Diagnostics Table")) + casewiseDiagnosticsTable$position <- 7 + casewiseDiagnosticsTable$dependOn(c(.maDependencies, "diagnosticsCasewiseDiagnostics", "diagnosticsCasewiseDiagnosticsShowInfluentialOnly", + "diagnosticsCasewiseDiagnosticsIncludePredictors", "diagnosticsCasewiseDiagnosticsDifferenceInCoefficients", + "studyLabels")) + casewiseDiagnosticsTable$setError(gettext("Casewise diagnostics are not available for models that contain meta-regression on heterogeneity.")) + jaspResults[["casewiseDiagnosticsTable"]] <- casewiseDiagnosticsTable + return() + } + + # the fit diagnostics work only for the non-clustered fit + fit <- .maExtractFit(jaspResults, options, nonClustered = TRUE) + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) + return() + + # extract precomputed diagnostics if done before: + if (!is.null(jaspResults[["diagnosticsResults"]])) { + + diagnosticsResults <- jaspResults[["diagnosticsResults"]]$object + + influenceResultsDfbs <- diagnosticsResults[["influenceResultsDfbs"]] + influenceResultsInf <- diagnosticsResults[["influenceResultsInf"]] + + } else { + + # create the output container + diagnosticsResults <- createJaspState() + diagnosticsResults$dependOn(.maDependencies) + jaspResults[["diagnosticsResults"]] <- diagnosticsResults + + if (.maIsMultilevelMultivariate(options)) { + # only a subset of diagnostics is available for rma.mv + influenceResultsDfbs <- data.frame(dfbetas(fit)) + influenceResultsInf <- data.frame( + rstudent = rstudent(fit)[["resid"]], + cook.d = cooks.distance(fit), + hat = hatvalues(fit) + ) + } else { + # the complete suite of influence diagnostics is only available for rma.uni + influenceResults <- influence(fit) + influenceResultsDfbs <- data.frame(influenceResults$dfbs) + influenceResultsInf <- data.frame(influenceResults$inf) + influenceResultsInf$tau.del <- sqrt(influenceResultsInf$tau2.del) + influenceResultsInf$inf[influenceResultsInf$inf == "*"] <- "Yes" + } + + # store the results + jaspResults[["diagnosticsResults"]]$object <- list( + "influenceResultsDfbs" = influenceResultsDfbs, + "influenceResultsInf" = influenceResultsInf + ) + } + + # extract fit data + fitData <- fit[["data"]] + + # fit measures table + casewiseDiagnosticsTable <- createJaspTable(gettext("Casewise Diagnostics Table")) + casewiseDiagnosticsTable$position <- 7 + casewiseDiagnosticsTable$dependOn(c(.maDependencies, "diagnosticsCasewiseDiagnostics", "diagnosticsCasewiseDiagnosticsShowInfluentialOnly", + "diagnosticsCasewiseDiagnosticsIncludePredictors", "diagnosticsCasewiseDiagnosticsDifferenceInCoefficients", + "studyLabels")) + jaspResults[["casewiseDiagnosticsTable"]] <- casewiseDiagnosticsTable + + if (options[["diagnosticsCasewiseDiagnosticsShowInfluentialOnly"]] && sum(influenceResultsInf$inf != "Yes") == 0) { + casewiseDiagnosticsTable$addFootnote(gettext("No influential cases found.")) + return() + } + + if (options[["studyLabels"]] != "") { + influenceResultsInf$label <- dataset[[options[["studyLabels"]]]] + casewiseDiagnosticsTable$addColumnInfo(name = "label", type = "string", title = gettext("Label")) + } + + if (options[["diagnosticsCasewiseDiagnosticsIncludePredictors"]]) { + for (var in colnames(fitData)) { + casewiseDiagnosticsTable$addColumnInfo(name = paste0("pred_", var), type = .maGetVariableColumnType(var, options), title = var, overtitle = gettext("Predictor")) + } + colnames(fitData) <- paste0("pred_", colnames(fitData)) + influenceResultsInf <- cbind(fitData, influenceResultsInf) + } + + casewiseDiagnosticsTable$addColumnInfo(name = "rstudent", title = gettext("Standardized Residual"), type = "number") + if (!.maIsMultilevelMultivariate(options)) + casewiseDiagnosticsTable$addColumnInfo(name = "dffits", title = gettext("DFFITS"), type = "number") + casewiseDiagnosticsTable$addColumnInfo(name = "cook.d", title = gettext("Cook's Distance"), type = "number") + if (!.maIsMultilevelMultivariate(options)) { + casewiseDiagnosticsTable$addColumnInfo(name = "cov.r", title = gettext("Covariance ratio"), type = "number") + casewiseDiagnosticsTable$addColumnInfo(name = "tau.del", title = gettext("\U1D70F"), type = "number", overtitle = gettext("Leave One Out")) + casewiseDiagnosticsTable$addColumnInfo(name = "tau2.del",title = gettext("\U1D70F\U00B2"), type = "number", overtitle = gettext("Leave One Out")) + casewiseDiagnosticsTable$addColumnInfo(name = "QE.del", title = gettext("Q\U2091"), type = "number", overtitle = gettext("Leave One Out")) + } + casewiseDiagnosticsTable$addColumnInfo(name = "hat", title = gettext("Hat"), type = "number") + if (!.maIsMultilevelMultivariate(options)) + casewiseDiagnosticsTable$addColumnInfo(name = "weight", title = gettext("Weight"), type = "number") + + if (options[["diagnosticsCasewiseDiagnosticsDifferenceInCoefficients"]]) { + for (par in colnames(influenceResultsDfbs)) { + casewiseDiagnosticsTable$addColumnInfo(name = par, title = .maVariableNames(par, options[["predictors"]]), type = "number", overtitle = gettext("Difference in coefficients")) + } + influenceResultsInf <- cbind(influenceResultsInf, influenceResultsDfbs) + } + + if (!.maIsMultilevelMultivariate(options)) + casewiseDiagnosticsTable$addColumnInfo(name = "inf", title = gettext("Influential"), type = "string") + + if (options[["diagnosticsCasewiseDiagnosticsShowInfluentialOnly"]]) + influenceResultsInf <- influenceResultsInf[influenceResultsInf$inf == "Yes",,drop=FALSE] + + casewiseDiagnosticsTable$setData(influenceResultsInf) + + if (.maIsClustered(options)) + casewiseDiagnosticsTable$addFootnote(gettext("Diagnostics are based on the non-clustered model.")) + + return() +} +.maCasewiseDiagnosticsExportColumns <- function(jaspResults, dataset, options) { + + if (!options[["diagnosticsCasewiseDiagnosticsExportToDataset"]]) + return() + + if (.maIsMetaregressionHeterogeneity(options)) + return() + + # extract diagnostics already computed in '.maCasewiseDiagnosticsTable' + diagnosticsResults <- jaspResults[["diagnosticsResults"]]$object + + influenceResultsDfbs <- diagnosticsResults[["influenceResultsDfbs"]] + influenceResultsInf <- diagnosticsResults[["influenceResultsInf"]] + + # export columns: + if (options[["diagnosticsCasewiseDiagnosticsExportToDatasetInfluentialIndicatorOnly"]]) { + + columnName <- "Diagnostics: Influential" + if (jaspBase:::columnExists(columnName) && !jaspBase:::columnIsMine(columnName)) + .quitAnalysis(gettextf("Column name %s already exists in the dataset.", columnName)) + + jaspResults[[columnName]] <- createJaspColumn(columnName = columnName, dependencies = .maDependencies) + jaspResults[[columnName]]$setNominal(influenceResultsInf[["inf"]]) + + } else { + + # export diagnostics + for (diagnosticName in colnames(influenceResultsInf)) { + + columnName <- paste0("Diagnostics: ", .maCasewiseDiagnosticsExportColumnsNames(diagnosticName)) + + if (jaspBase:::columnExists(columnName) && !jaspBase:::columnIsMine(columnName)) + .quitAnalysis(gettextf("Column name %s already exists in the dataset.", columnName)) + + jaspResults[[columnName]] <- createJaspColumn(columnName = columnName, dependencies = .maDependencies) + if (diagnosticName == "inf") { + jaspResults[[columnName]]$setNominal(influenceResultsInf[[diagnosticName]]) + } else { + jaspResults[[columnName]]$setScale(influenceResultsInf[[diagnosticName]]) + } + } + + # export change in coefficients + if (options[["diagnosticsCasewiseDiagnosticsDifferenceInCoefficients"]]) { + + for (diagnosticName in colnames(influenceResultsDfbs)) { + + columnName <- decodeColNames(paste0("Difference in coefficients: ", .maVariableNames(diagnosticName, options[["predictors"]]))) + + if (jaspBase:::columnExists(columnName) && !jaspBase:::columnIsMine(columnName)) + .quitAnalysis(gettextf("Column name %s already exists in the dataset.", columnName)) + + jaspResults[[columnName]] <- createJaspColumn(columnName = columnName, dependencies = .maDependencies) + jaspResults[[columnName]]$setScale(influenceResultsDfbs[[diagnosticName]]) + } + } + + } + + return() +} +.maProfileLikelihoodPlot <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["profileLikelihoodPlot"]])) + return() + + fit <- .maExtractFit(jaspResults, options) + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) + return() + + # extract precomputed profile likelihoods if done before: + if (!is.null(jaspResults[["profileLikelihoodResults"]])) { + + dfProfile <- jaspResults[["profileLikelihoodResults"]]$object + + } else { + + # create the output container + profileLikelihoodResults <- createJaspState() + profileLikelihoodResults$dependOn(.maDependencies) + jaspResults[["profileLikelihoodResults"]] <- profileLikelihoodResults + + if (.maIsMultilevelMultivariate(options)) { + # use the defaults (too many possible parameter combinations to control) + dfProfile <- try(metafor::profile.rma.mv(fit, plot = FALSE, progbar = FALSE)) + + jaspResults[["diagnosticsResults"]]$object <- dfProfile + } else { + # proceed with some nice formatting for rma.uni (too difficult to implement for rma.mv) + xTicks <- jaspGraphs::getPrettyAxisBreaks(c(0, max(0.1, 2*fit[["tau2"]]))) + dfProfile <- try(profile(fit, xlim = range(xTicks), plot = FALSE, progbar = FALSE)) + attr(dfProfile, "xTicks") <- xTicks + + jaspResults[["diagnosticsResults"]]$object <- dfProfile + } + } + + # create profile likelihood plot / container + if (.maIsMultilevelMultivariate(options)) { + # container for multivariate + profileLikelihoodPlot <- createJaspContainer(title = gettext("Profile Likelihood Plots")) + profileLikelihoodPlot$dependOn(c(.maDependencies, "diagnosticsPlotsProfileLikelihood")) + profileLikelihoodPlot$position <- 8 + + jaspResults[["profileLikelihoodPlot"]] <- profileLikelihoodPlot + + if (jaspBase::isTryError(dfProfile)) { + errorPlot <- createJaspPlot(title = gettext("Profile Likelihood Plot")) + errorPlot$setError(dfProfile) + + profileLikelihoodPlot[["errorPlot"]] <- errorPlot + return() + } + + for (i in 1:dfProfile[["comps"]]) { + tempProfilePlot <- createJaspPlot(title = paste0(dfProfile[[i]][["title"]][-1], collapse = " "), width = 400, height = 320) + tempProfilePlot$position <- i + + profileLikelihoodPlot[[paste0("plot", i)]] <- tempProfilePlot + + tempProfilePlot$plotObject <- .maMakeProfileLikelihoodPlot(dfProfile[[i]]) + } + + } else { + # plot for univariate + profileLikelihoodPlot <- createJaspPlot(title = gettext("Profile Likelihood Plot"), width = 400, height = 320) + profileLikelihoodPlot$dependOn(c(.maDependencies, "diagnosticsPlotsProfileLikelihood")) + profileLikelihoodPlot$position <- 8 + + jaspResults[["profileLikelihoodPlot"]] <- profileLikelihoodPlot + + if (.maIsMetaregressionHeterogeneity(options)) { + profileLikelihoodPlot$setError(gettext("Profile likelihood is not available for models that contain meta-regression on heterogeneity.")) + return() + } + + if (jaspBase::isTryError(dfProfile)) { + profileLikelihoodPlot$setError(dfProfile) + return() + } + + profileLikelihoodPlot$plotObject <- .maMakeProfileLikelihoodPlot(dfProfile) + } + + return() +} +.maBaujatPlot <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["baujatPlot"]])) + return() + + fit <- .maExtractFit(jaspResults, options) + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) + return() + + # create plot + baujatPlot <- createJaspPlot(title = gettext("Baujat Plot"), width = 400, height = 320) + baujatPlot$dependOn(c(.maDependencies, "diagnosticsPlotsBaujat", "studyLabels")) + baujatPlot$position <- 9 + jaspResults[["baujatPlot"]] <- baujatPlot + + if (.maIsMetaregressionHeterogeneity(options)) { + baujatPlot$setError(gettext("Baujat plot is not available for models that contain meta-regression on heterogeneity.")) + return() + } + if (.maIsClustered(options)) { + baujatPlot$setError(gettext("Baujat plot is not available for models with clustering.")) + return() + } + + # extract precomputed baujat data if done before: + if (!is.null(jaspResults[["baujatResults"]])) { + + dfBaujat <- jaspResults[["baujatResults"]]$object + + } else { + + # create the output container + baujatResults <- createJaspState() + baujatResults$dependOn(.maDependencies) + jaspResults[["baujatResults"]] <- baujatResults + + # compute the results and save them in the container + dfBaujat <- try(.maSuppressPlot(metafor::baujat(fit))) + + # store in the container + jaspResults[["baujatResults"]]$object <- dfBaujat + } + + if (jaspBase::isTryError(dfBaujat)) { + baujatPlot$setError(dfBaujat) + return() + } + + if (options[["studyLabels"]] != "") + dfBaujat$label <- as.character(dataset[[options[["studyLabels"]]]]) + + xTicks <- jaspGraphs::getPrettyAxisBreaks(range(dfBaujat$x)) + yTicks <- jaspGraphs::getPrettyAxisBreaks(range(dfBaujat$y)) + + + aesCall <- list( + x = as.name("x"), + y = as.name("y"), + label = if (options[["studyLabels"]] != "") as.name("label") + ) + geomCall <- list( + data = dfBaujat, + mapping = do.call(ggplot2::aes, aesCall[!sapply(aesCall, is.null)]) + ) + + # create plot + plotOut <- do.call(ggplot2::ggplot, geomCall) + + jaspGraphs::geom_point( + size = if (options[["studyLabels"]] != "") 2 else 3 + ) + + if (options[["studyLabels"]] != "") + plotOut <- plotOut + ggplot2::geom_text(hjust = 0, vjust = 0) + + plotOut <- plotOut + + ggplot2::labs(x = gettext("Squared Pearson Residual"), y = gettext("Influence on Fitted Value")) + + jaspGraphs::scale_x_continuous(breaks = xTicks, limits = range(xTicks)) + + jaspGraphs::scale_y_continuous(breaks = yTicks, limits = range(yTicks)) + + jaspGraphs::geom_rangeframe() + + jaspGraphs::themeJaspRaw() + + baujatPlot$plotObject <- plotOut + + return() +} +.maResidualFunnelPlot <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["residualFunnelPlot"]])) + return() + + fit <- .maExtractFit(jaspResults, options) + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) + return() + + # create plot + residualFunnelPlot <- createJaspPlot(title = gettext("Residual Funnel Plot"), width = 550, height = 480) + residualFunnelPlot$dependOn(c(.maDependencies, "diagnosticsResidualFunnel", "studyLabels")) + residualFunnelPlot$position <- 10 + jaspResults[["residualFunnelPlot"]] <- residualFunnelPlot + + # obtain residual funnel plot + plotOut <- .maMakeResidualFunnelPlot(fit, options, dataset) + + residualFunnelPlot$plotObject <- plotOut + + return() +} + +# containers/state functions +.maExtractFit <- function(jaspResults, options, nonClustered = FALSE) { + + if (is.null(jaspResults[["fit"]]$object)) + return() + + if (!is.null(jaspResults[["fitNoInfluence"]]$object)) { + # extract clustered model if specified + if (!.maIsClustered(options) || nonClustered) { + return(jaspResults[["fitNoInfluence"]]$object[["fit"]]) + } else { + return(jaspResults[["fitNoInfluence"]]$object[["fitClustered"]]) + } + } else { + # extract clustered model if specified + if (!.maIsClustered(options) || nonClustered) { + return(jaspResults[["fit"]]$object[["fit"]]) + } else { + return(jaspResults[["fit"]]$object[["fitClustered"]]) + } + } +} +.maExtractModelSummaryContainer <- function(jaspResults) { + + if (!is.null(jaspResults[["modelSummaryContainer"]])) + return(jaspResults[["modelSummaryContainer"]]) + + # create the output container + modelSummaryContainer <- createJaspContainer(gettext("Model Summary")) + modelSummaryContainer$dependOn(.maDependencies) + modelSummaryContainer$position <- 1 + jaspResults[["modelSummaryContainer"]] <- modelSummaryContainer + + return(modelSummaryContainer) +} +.maExtractMetaregressionContainer <- function(jaspResults) { + + if (!is.null(jaspResults[["metaregressionContainer"]])) + return(jaspResults[["metaregressionContainer"]]) + + # create the output container + metaregressionContainer <- createJaspContainer(gettext("Meta-Regression Summary")) + metaregressionContainer$dependOn(c(.maDependencies, "confidenceInterval")) + metaregressionContainer$position <- 3 + jaspResults[["metaregressionContainer"]] <- metaregressionContainer + + return(metaregressionContainer) +} +.maExtractEstimatedMarginalMeansContainer <- function(jaspResults) { + + if (!is.null(jaspResults[["estimatedMarginalMeansContainer"]])) + return(jaspResults[["estimatedMarginalMeansContainer"]]) + + # create the output container + estimatedMarginalMeansContainer <- createJaspContainer(gettext("Estimated Marginal Means Summary")) + estimatedMarginalMeansContainer$dependOn(c(.maDependencies, "confidenceIntervals", "confidenceIntervalsLevel")) + estimatedMarginalMeansContainer$position <- 4 + jaspResults[["estimatedMarginalMeansContainer"]] <- estimatedMarginalMeansContainer + + return(estimatedMarginalMeansContainer) +} +.maExtractVarianceInflationContainer <- function(jaspResults) { + + if (!is.null(jaspResults[["varianceInflationContainer"]])) + return(jaspResults[["varianceInflationContainer"]]) + + # create the output container + varianceInflationContainer <- createJaspContainer(gettext("Variance Inflation Summary")) + varianceInflationContainer$dependOn(c(.maDependencies, "diagnosticsVarianceInflationFactor", "diagnosticsVarianceInflationFactorAggregate")) + varianceInflationContainer$position <- 7 + jaspResults[["varianceInflationContainer"]] <- varianceInflationContainer + + return(varianceInflationContainer) +} + +# help compute functions +.maComputePooledEffect <- function(fit, options) { + + # prediction for effect size of a location-scale models without effect size moderator does not work (compute it manually) + if (!.maIsMetaregressionEffectSize(options) && .maIsMetaregressionHeterogeneity(options)) { + + predictedHeterogeneity <- .maComputePooledHeterogeneity(fit, options) + predictedEffect <- data.frame( + pred = fit$beta[1], + se = fit$se[1], + ci.lb = fit$ci.lb[1], + ci.ub = fit$ci.ub[1], + pi.lb = fit$beta[1] - 1.96 * sqrt(fit$se[1]^2 + predictedHeterogeneity[1, 2]^2), + pi.ub = fit$beta[1] + 1.96 * sqrt(fit$se[1]^2 + predictedHeterogeneity[1, 2]^2) + ) + + } else { + + predictInput <- list( + object = fit, + level = 100 * options[["confidenceIntervalsLevel"]] + ) + + if (.maIsMetaregressionHeterogeneity(options)) { + predictInput$newmods <- t(colMeans(model.matrix(fit)$location)) + predictInput$newscale <- t(colMeans(model.matrix(fit)$scale)) + } else if (.maIsMetaregressionEffectSize(options)) { + predictInput$newmods <- t(colMeans(model.matrix(fit))) + } + + if (!is.null(predictInput$newmods) && options[["effectSizeModelIncludeIntercept"]]) + predictInput$newmods <- predictInput$newmods[, -1, drop=FALSE] + + if (!is.null(predictInput$newscale) && options[["heterogeneityModelIncludeIntercept"]]) + predictInput$newscale <- predictInput$newscale[, -1, drop=FALSE] + + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE) && options[["predictionIntervals"]]) { + tauLevelsMatrix <- .mammExtractTauLevels(fit) + predictInput$tau2.levels <- tauLevelsMatrix[["tau2.levels"]] + predictInput$gamma2.levels <- tauLevelsMatrix[["gamma2.levels"]] + + if (.maIsMetaregressionEffectSize(options)) + predictInput$newmods <- do.call(rbind, lapply(1:nrow(tauLevelsMatrix), function(i) predictInput$newmods)) + } + + predictedEffect <- do.call(predict, predictInput) + } + + + # remove the non-requested heterogeneity levels + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE) && !options[["predictionIntervals"]]) + predictedEffect <- predictedEffect[1, , drop = FALSE] + + # keep levels for which the heterogeneity is predicted for complex multivariate models + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE) && options[["predictionIntervals"]]) { + tauLevels <- list( + predictedEffect[["tau2.level"]], + predictedEffect[["gamma2.level"]] + ) + tauLevels <- do.call(cbind.data.frame, tauLevels[!sapply(tauLevels, is.null)]) + colnames(tauLevels) <- .mammExtractTauLevelNames(fit) + } + + # to data.frame + predictedEffect <- .maExtractAndFormatPrediction(predictedEffect) + predictedEffect$par <- "Effect Size" + + # apply effect size transformation + if (options[["transformEffectSize"]] != "none") + predictedEffect[,c("est", "lCi", "uCi", "lPi", "uPi")] <- do.call( + .maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), + list(predictedEffect[,c("est", "lCi", "uCi", "lPi", "uPi")])) + + # remove non-requested columns + predictedEffect <- predictedEffect[,c( + "par", "est", + if (options[["confidenceIntervals"]]) c("lCi", "uCi"), + if (options[["predictionIntervals"]]) c("lPi", "uPi") + )] + + # return the tau levels + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE) && options[["predictionIntervals"]]) + predictedEffect <- cbind(predictedEffect, tauLevels) + + return(predictedEffect <- apply(predictedEffect, 1, as.list)) +} +.maComputePooledEffectPlot <- function(fit, options) { + + if (!.maIsMetaregressionEffectSize(options)) { + predictedEffect <- predict(fit) + } else { + if (.maIsMetaregressionHeterogeneity(options)) { + predictedEffect <- predict( + fit, + newmods = colMeans(model.matrix(fit)$location)[-1], + newscale = colMeans(model.matrix(fit)$scale)[-1] + ) + } else { + predictedEffect <- predict( + fit, + newmods = colMeans(model.matrix(fit))[-1] + ) + } + } + + # compute test against specified value + if (.maIsMetaregressionFtest(options)) { + + # to extract the degrees of freedom + tempDf <- predictedEffect$ddf + predictedEffect <- .maExtractAndFormatPrediction(predictedEffect) + predictedEffect$df <- tempDf + predictedEffect$stat <- (predictedEffect$est - 0) / predictedEffect$se + predictedEffect$pval <- 2 * pt(abs(predictedEffect$stat), predictedEffect$df, lower.tail = FALSE) + + } else { + + predictedEffect <- .maExtractAndFormatPrediction(predictedEffect) + predictedEffect$stat <- (predictedEffect$est - 0) / predictedEffect$se + predictedEffect$pval <- 2 * pnorm(abs(predictedEffect$stat), lower.tail = FALSE) + + } + + # fix column names + predictedEffect$par <- "Effect Size" + + # apply effect size transformation + if (options[["transformEffectSize"]] != "none") + predictedEffect[,c("est", "lCi", "uCi", "lPi", "uPi")] <- do.call( + .maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), + list(predictedEffect[,c("est", "lCi", "uCi", "lPi", "uPi")])) + + + return(as.list(predictedEffect)) +} +.maComputePooledHeterogeneity <- function(fit, options) { + + if (fit[["tau2.fix"]]) { + + confIntHeterogeneity <- data.frame( + par = c("\U1D70F", "\U1D70F\U00B2"), + est = c(sqrt(fit[["tau2"]]), fit[["tau2"]]), + lCi = c(NA, NA), + uCi = c(NA, NA) + ) + + # keep only the requested parameters (other than tau and tau^2 are not possible) + heterogeneityShow <- c( + if (options[["heterogeneityTau"]]) 1, + if (options[["heterogeneityTau2"]]) 2 + ) + + confIntHeterogeneity <- confIntHeterogeneity[heterogeneityShow,,drop = FALSE] + + } else if (.maIsMetaregressionHeterogeneity(options)) { + # no confint support + # predict the scale on the average value + predScale <- predict(fit, newscale = colMeans(model.matrix(fit)$scale)[-1], level = 100 * options[["confidenceIntervalsLevel"]]) + + if (options[["heterogeneityModelLink"]] == "log") { + confIntHeterogeneity <- data.frame( + par = c("\U1D70F", "\U1D70F\U00B2"), + est = exp(c(predScale[["pred"]] / 2, predScale[["pred"]])), + lCi = exp(c(predScale[["ci.lb"]] / 2, predScale[["ci.lb"]])), + uCi = exp(c(predScale[["ci.ub"]] / 2, predScale[["ci.ub"]])) + ) + } else if (options[["heterogeneityModelLink"]] == "identity") { + confIntHeterogeneity <- data.frame( + par = c("\U1D70F", "\U1D70F\U00B2"), + est = c(sqrt(predScale[["pred"]]), predScale[["pred"]]), + lCi = c(sqrt(predScale[["ci.lb"]]), predScale[["ci.lb"]]), + uCi = c(sqrt(predScale[["ci.ub"]]), predScale[["ci.ub"]]) + ) + } + + # keep only the requested parameters (other than tau and tau^2 are not possible) + heterogeneityShow <- c( + if (options[["heterogeneityTau"]]) 1, + if (options[["heterogeneityTau2"]]) 2 + ) + + confIntHeterogeneity <- confIntHeterogeneity[heterogeneityShow,,drop = FALSE] + + } else { + + confIntHeterogeneity <- confint(fit, level = 100 * options[["confidenceIntervalsLevel"]]) + confIntHeterogeneity <- data.frame(confIntHeterogeneity[["random"]])[c(2,1,3,4),] + colnames(confIntHeterogeneity) <- c("est", "lCi", "uCi") + confIntHeterogeneity$par <- c("\U1D70F", "\U1D70F\U00B2", "I\U00B2", "H\U00B2") + + # keep only the requested parameters + heterogeneityShow <- c( + if (options[["heterogeneityTau"]]) 1, + if (options[["heterogeneityTau2"]]) 2, + if (options[["heterogeneityI2"]]) 3, + if (options[["heterogeneityH2"]]) 4 + ) + + confIntHeterogeneity <- confIntHeterogeneity[heterogeneityShow,,drop = FALSE] + + } + + if (!options[["confidenceIntervals"]]) + confIntHeterogeneity <- confIntHeterogeneity[,c("par", "est")] + + return(confIntHeterogeneity) +} +.maComputePooledHeterogeneityPlot <- function(fit, options) { + + # don't use the confint on robust.rma objects (they are not implemented) + # the clustering works only on the fixed effect estimates + # -> we can drop the class and compute confint and get the heterogeneity from the original fit + if (inherits(fit, "robust.rma")) + class(fit) <- class(fit)[!class(fit) %in% "robust.rma"] + + if (fit[["tau2.fix"]]) { + + confIntHeterogeneity <- list( + est = sqrt(.maGetFixedTau2Options(options)), + lCi = NA, + uCi = NA + ) + + } else if (.maIsMetaregressionHeterogeneity(options)) { + + # no confint support + # predict the scale on the average value + predScale <- predict(fit, newscale = colMeans(model.matrix(fit)$scale)[-1], level = 100 * options[["confidenceIntervalsLevel"]]) + + if (options[["heterogeneityModelLink"]] == "log") { + confIntHeterogeneity <- data.frame( + est = exp(predScale[["pred"]] / 2), + lCi = exp(predScale[["ci.lb"]] / 2), + uCi = exp(predScale[["ci.ub"]] / 2) + ) + } else if (options[["heterogeneityModelLink"]] == "identity") { + confIntHeterogeneity <- data.frame( + est = sqrt(predScale[["pred"]]), + lCi = sqrt(predScale[["ci.lb"]]), + uCi = sqrt(predScale[["ci.ub"]]) + ) + } + + } else { + + confIntHeterogeneity <- confint(fit) + confIntHeterogeneity <- data.frame(confIntHeterogeneity[["random"]])[2,] + colnames(confIntHeterogeneity) <- c("est", "lCi", "uCi") + } + + return(confIntHeterogeneity) +} +.maOmnibusTest <- function(fit, options, parameter = "effectSize") { + + if (parameter == "effectSize") { + row <- list( + parameter = gettext("Effect Size"), + stat = fit[["QM"]], + df1 = fit[["QMdf"]][1], + pval = fit[["QMp"]] + ) + } else if (parameter == "heterogeneity") { + row <- list( + parameter = gettext("Heterogeneity"), + stat = fit[["QS"]], + df1 = fit[["QSdf"]][1], + pval = fit[["QSp"]] + ) + } + + if (.maIsMetaregressionFtest(options)) { + if (parameter == "effectSize") + row$df2 <- fit[["QMdf"]][2] + else if (parameter == "heterogeneity") + row$df2 <- fit[["QSdf"]][2] + } + + if (.maIsPermutation(options)) { + if (parameter == "effectSize") + row$pval2 <- attr(fit[["QMp"]], "permutation") + else if (parameter == "heterogeneity") + row$pval2 <- attr(fit[["QSp"]], "permutation") + } + + return(row) +} +.maOmnibusTestCoefficients <- function(fit, options, parameter = "effectSize") { + + if (parameter == "effectSize") { + maxCoef <- nrow(fit$beta) + selCoef <- .robmaCleanOptionsToPriors( + options[["addOmnibusModeratorTestEffectSizeCoefficientsValues"]], + message = gettext("Indexes of effect size moderation coefficients were specified in an incorrect format. Try '(1, 2)' to test the first two coefficients.") + ) + } else if (parameter == "heterogeneity") { + maxCoef <- nrow(fit$alpha) + selCoef <- .robmaCleanOptionsToPriors( + options[["addOmnibusModeratorTestHeterogeneityCoefficientsValues"]], + message = gettext("Indexes of heterogeneity moderation coefficients were specified in an incorrect format. Try '(1, 2)' to test the first two coefficients.") + ) + } + + if (!is.numeric(selCoef) || any(!(abs(selCoef - round(selCoef)) < .Machine$double.eps^0.5))) + return(gettext("The selected coefficients must be an integer vector.")) + if (any(selCoef < 1) || any(selCoef > maxCoef)) + return(gettextf("The selected coefficients must be between 1 and %1$i (i.e., the number of regression parameters).", maxCoef)) + + if (parameter == "effectSize") { + out <- anova(fit, btt = selCoef) + } else if (parameter == "heterogeneity") { + out <- anova(fit, btt = selCoef) + } + + row <- list( + stat = out[["QM"]], + df1 = out[["QMdf"]][1], + pval = out[["QMp"]] + ) + + if (.maIsMetaregressionFtest(options)) + row$df2 <- fit[["QMdf"]][2] + + if (parameter == "effectSize") { + row$parameter <- gettextf("Effect Size (coef: %1$s)", paste(selCoef, collapse = ", ")) + attr(row, "footnote") <- gettextf( + "Effect size coefficients %1$s correspond to %2$s.", + paste(selCoef, collapse = ","), + paste(sapply(rownames(fit$beta)[selCoef], function(coefName) .maVariableNames(coefName, options[["predictors"]])), collapse = ", ")) + } else if (parameter == "heterogeneity") { + row$parameter <- gettextf("Heterogeneity (coef: %1$s)", paste(selCoef, collapse = ", ")) + attr(row, "footnote") <- sapply(rownames(fit$alpha)[selCoef], function(coefName) .maVariableNames(coefName, options[["predictors"]])) + attr(row, "footnote") <- gettextf( + "Heterogeneity coefficients %1$s correspond to %2$s.", + paste(selCoef, collapse = ","), + paste(sapply(rownames(fit$alpha)[selCoef], function(coefName) .maVariableNames(coefName, options[["predictors"]])), collapse = ", ")) + } + + return(row) +} +.maTermTests <- function(fit, options, term, parameter = "effectSize") { + + # obtain terms indicies + if (parameter == "effectSize") { + terms <- attr(terms(fit[["formula.mods"]], data = fit[["data"]]),"term.labels") + termsIndex <- attr(model.matrix(fit[["formula.mods"]], data = fit[["data"]]), "assign") + termsAnova <- anova(fit, btt = seq_along(termsIndex)[termsIndex == which(terms == term)]) + + out <- list( + term = .maVariableNames(term, options[["predictors"]]), + stat = termsAnova[["QM"]], + df1 = termsAnova[["QMdf"]][1], + pval = termsAnova[["QMp"]] + ) + + if (.maIsMetaregressionFtest(options)) + out$df2 <- termsAnova[["QMdf"]][2] + + } else if (parameter == "heterogeneity") { + terms <- attr(terms(fit[["formula.scale"]], data = fit[["data"]]),"term.labels") + termsIndex <- attr(model.matrix(fit[["formula.scale"]], data = fit[["data"]]), "assign") + termsAnova <- anova(fit, att = seq_along(termsIndex)[termsIndex == which(terms == term)]) + + out <- list( + term = .maVariableNames(term, options[["predictors"]]), + stat = termsAnova[["QS"]], + df1 = termsAnova[["QSdf"]][1], + pval = termsAnova[["QSp"]] + ) + + if (.maIsMetaregressionFtest(options)) + out$df2 <- termsAnova[["QSdf"]][2] + + } + + return(out) +} +.maGetMarginalMeansPredictorMatrix <- function(fit, options, dataset, selectedVariables, trendVarible = NULL, trendSequence = NULL, sdFactor, parameter) { + + variablesContinuous <- options[["predictors"]][options[["predictors.types"]] == "scale"] + variablesFactors <- options[["predictors"]][options[["predictors.types"]] == "nominal"] + + # extract the corresponding formula + formula <- switch( + parameter, + effectSize = fit[["formula.mods"]], + heterogeneity = fit[["formula.scale"]] + ) + hasIntercept <- switch( + parameter, + effectSize = options[["effectSizeModelIncludeIntercept"]], + heterogeneity = options[["heterogeneityModelIncludeIntercept"]] + ) + + # extract the used variables + terms <- attr(terms(formula, data = fit[["data"]]), "term.labels") + variables <- terms[!grepl(":", terms)] + + # average across remaining variables + remainingVariables <- setdiff(variables, c(selectedVariables, trendVarible)) + + ### create model matrix for the remaining predictors + # (use all factors for levels to average out the predictor matrix later) + predictorsRemaining <- list() + for (i in seq_along(remainingVariables)) { + if (remainingVariables[[i]] %in% variablesFactors) { + predictorsRemaining[[remainingVariables[i]]] <- factor(levels(dataset[[remainingVariables[[i]]]]), levels = levels(dataset[[remainingVariables[[i]]]])) + contrasts(predictorsRemaining[[remainingVariables[i]]]) <- contrasts(dataset[[remainingVariables[[i]]]]) + } else if (remainingVariables[[i]] %in% variablesContinuous) { + predictorsRemaining[[remainingVariables[i]]] <- mean(dataset[[remainingVariables[[i]]]]) + } + } + + # create complete model matrices including the specified variable + predictorsSelected <- list() + if (length(selectedVariables) > 0) { + for (selectedVariable in selectedVariables) { + if (selectedVariable %in% variablesFactors) { + predictorsSelected[[selectedVariable]] <- factor(levels(dataset[[selectedVariable]]), levels = levels(dataset[[selectedVariable]])) + contrasts(predictorsSelected[[selectedVariable]]) <- contrasts(dataset[[selectedVariable]]) + } else if (selectedVariable %in% variablesContinuous) { + predictorsSelected[[selectedVariable]] <- c( + mean(dataset[[selectedVariable]]) - sdFactor * sd(dataset[[selectedVariable]]), + mean(dataset[[selectedVariable]]), + mean(dataset[[selectedVariable]]) + sdFactor * sd(dataset[[selectedVariable]]) + ) + } + } + } + + + # create model matrix for the trend variable + if (length(trendVarible) != 0) { + predictorsSelected[[trendVarible]] <- trendSequence + } + + # add the specified variable and pool across the combinations of the remaining values + if (length(selectedVariables) == 1 && selectedVariables == "") { + # empty string creates overall adjusted estimate + outMatrix <- t(colMeans(model.matrix(formula, data = expand.grid(predictorsRemaining)))) + } else { + predictorsSelectedGrid <- expand.grid(predictorsSelected) + outMatrix <- do.call(rbind, lapply(1:nrow(predictorsSelectedGrid), function(i) { + colMeans(model.matrix(formula, data = expand.grid(c(predictorsRemaining, predictorsSelectedGrid[i,,drop = FALSE])))) + })) + } + + if (hasIntercept) + outMatrix <- outMatrix[, -1, drop=FALSE] + + # keep information about the variable and levels + if (length(selectedVariables) == 1 && selectedVariables == "") { + + # add intercept + attr(outMatrix, "variable") <- gettext("Adjusted Estimate") + attr(outMatrix, gettext("Adjusted Estimate")) <- "" + + } else { + + # selected variables grid + attr(outMatrix, "selectedGrid") <- predictorsSelectedGrid + + # add remaining variables + attr(outMatrix, "variable") <- c(selectedVariables, trendVarible) + + for (selectedVariable in selectedVariables) { + if (selectedVariable %in% variablesFactors) { + attr(outMatrix, selectedVariable) <- predictorsSelected[[selectedVariable]] + } else if (selectedVariable %in% variablesContinuous) { + attr(outMatrix, selectedVariable) <- c( + gettextf("Mean - %1$sSD", sdFactor), + gettext("Mean"), + gettextf("Mean + %1$sSD", sdFactor)) + } + } + } + + if (length(trendVarible) != 0) { + attr(outMatrix, "trend") <- trendVarible + attr(outMatrix, "trend") <- trendSequence + } + + return(outMatrix) + +} +.maComputeMarginalMeansVariable <- function(fit, options, dataset, selectedVariable, testAgainst = 0, parameter) { + + if (parameter == "effectSize") { + + predictorMatrixEffectSize <- .maGetMarginalMeansPredictorMatrix( + fit = fit, + options = options, + dataset = dataset, + selectedVariables = selectedVariable, + sdFactor = options[["estimatedMarginalMeansEffectSizeSdFactorCovariates"]], + parameter = "effectSize" + ) + + if (.maIsMetaregressionHeterogeneity(options)) { + + predictorMatrixHeterogeneity <- .maGetMarginalMeansPredictorMatrix( + fit = fit, + options = options, + dataset = dataset, + selectedVariables = selectedVariable, + sdFactor = options[["estimatedMarginalMeansEffectSizeSdFactorCovariates"]], + parameter = "heterogeneity" + ) + computedMarginalMeans <- predict( + fit, + newmods = predictorMatrixEffectSize, + newscale = predictorMatrixHeterogeneity, + level = 100 * options[["confidenceIntervalsLevel"]] + ) + } else { + + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE) && options[["predictionIntervals"]]) { + tauLevelsMatrix <- .mammExtractTauLevels(fit) + computedMarginalMeans <- predict( + fit, + newmods = do.call(rbind, lapply(1:nrow(tauLevelsMatrix), function(i) predictorMatrixEffectSize)), + level = 100 * options[["confidenceIntervalsLevel"]], + tau2.levels = if (is.null(dim(predictorMatrixEffectSize))) tauLevelsMatrix[["tau2.levels"]] else do.call(rbind, lapply(1:nrow(predictorMatrixEffectSize), function(i) tauLevelsMatrix))[["tau2.levels"]], + gamma2.levels = if (is.null(dim(predictorMatrixEffectSize))) tauLevelsMatrix[["gamma2.levels"]] else do.call(rbind, lapply(1:nrow(predictorMatrixEffectSize), function(i) tauLevelsMatrix))[["gamma2.levels"]] + ) + } else { + computedMarginalMeans <- predict( + fit, + newmods = predictorMatrixEffectSize, + level = 100 * options[["confidenceIntervalsLevel"]] + ) + } + } + + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE) && options[["predictionIntervals"]]) { + tauLevels <- list( + computedMarginalMeans[["tau2.level"]], + computedMarginalMeans[["gamma2.level"]] + ) + tauLevels <- do.call(cbind.data.frame, tauLevels[!sapply(tauLevels, is.null)]) + colnames(tauLevels) <- .mammExtractTauLevelNames(fit) + } + + + # compute test against specified value + if (.maIsMetaregressionFtest(options)) { + + # extract degrees of freedom + tempDf <- computedMarginalMeans$ddf + computedMarginalMeans <- .maExtractAndFormatPrediction(computedMarginalMeans) + computedMarginalMeans$df <- tempDf + computedMarginalMeans$stat <- (computedMarginalMeans$est - testAgainst) / computedMarginalMeans$se + computedMarginalMeans$pval <- 2 * pt(abs(computedMarginalMeans$stat), computedMarginalMeans$df, lower.tail = FALSE) + + } else { + + computedMarginalMeans <- .maExtractAndFormatPrediction(computedMarginalMeans) + computedMarginalMeans$stat <- (computedMarginalMeans$est - testAgainst) / computedMarginalMeans$se + computedMarginalMeans$pval <- 2 * pnorm(abs(computedMarginalMeans$stat), lower.tail = FALSE) + + } + + # apply effect size transformation + if (options[["transformEffectSize"]] != "none") + computedMarginalMeans[,c("est", "lCi", "uCi", "lPi", "uPi")] <- do.call( + .maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), + list(computedMarginalMeans[,c("est", "lCi", "uCi", "lPi", "uPi")])) + + # create full data frame + computedMarginalMeans <- data.frame( + "variable" = attr(predictorMatrixEffectSize, "variable"), + "value" = attr(predictorMatrixEffectSize, attr(predictorMatrixEffectSize, "variable")), + computedMarginalMeans + ) + + } else if (parameter == "heterogeneity") { + + predictorMatrixHeterogeneity <- .maGetMarginalMeansPredictorMatrix( + fit = fit, + options = options, + dataset = dataset, + selectedVariables = selectedVariable, + sdFactor = options[["estimatedMarginalMeansHeterogeneitySdFactorCovariates"]], + parameter = "heterogeneity" + ) + + computedMarginalMeans <- predict( + fit, + newscale = predictorMatrixHeterogeneity, + level = 100 * options[["confidenceIntervalsLevel"]] + ) + + computedMarginalMeans <- .maExtractAndFormatPrediction(computedMarginalMeans) + + + # apply link transform + if (options[["heterogeneityModelLink"]] == "log") { + computedMarginalMeans <- exp(computedMarginalMeans) + } + + # apply tau / tau2 transform + if (options[["estimatedMarginalMeansHeterogeneityTransformation"]] == "tau") + computedMarginalMeans <- sqrt(computedMarginalMeans) + + # create full data frame + computedMarginalMeans <- data.frame( + "variable" = attr(predictorMatrixHeterogeneity, "variable"), + "value" = attr(predictorMatrixHeterogeneity, attr(predictorMatrixHeterogeneity, "variable")), + computedMarginalMeans + ) + } + + + # remove unnecessary columns + computedMarginalMeans <- computedMarginalMeans[,!colnames(computedMarginalMeans) %in% "se"] + + if (!options[["confidenceIntervals"]]) + computedMarginalMeans <- computedMarginalMeans[,!colnames(computedMarginalMeans) %in% c("lCi", "uCi")] + + if (!options[["predictionIntervals"]]) + computedMarginalMeans <- computedMarginalMeans[,!colnames(computedMarginalMeans) %in% c("lPi", "uPi")] + + # return the tau levels + if (.mammHasMultipleHeterogeneities(options, canAddOutput = TRUE) && options[["predictionIntervals"]]) + computedMarginalMeans <- cbind(computedMarginalMeans, tauLevels) + + return(computedMarginalMeans) +} +.maMakeBubblePlotDataset <- function(fit, options, dataset) { + + # extract options + separateLines <- unlist(options[["bubblePlotSeparateLines"]]) + separatePlots <- unlist(options[["bubblePlotSeparatePlots"]]) + selectedVariable <- options[["bubblePlotSelectedVariable"]][[1]][["variable"]] + selectedVariableType <- options[["predictors.types"]][options[["predictors"]] == selectedVariable] + + # create a range of values for continuous predictors to plot the trend but use lvls for factors + if (selectedVariableType == "scale") { + + xRange <- range(jaspGraphs::getPrettyAxisBreaks(range(dataset[[selectedVariable]]))) + trendSequence <- seq(xRange[1], xRange[2], length.out = 101) + + predictorMatrixEffectSize <- .maGetMarginalMeansPredictorMatrix( + fit = fit, + options = options, + dataset = dataset, + selectedVariables = c(separateLines, separatePlots), + sdFactor = options[["bubblePlotSdFactorCovariates"]], + trendVarible = selectedVariable, + trendSequence = trendSequence, + parameter = "effectSize" + ) + + } else if (selectedVariableType == "nominal") { + + predictorMatrixEffectSize <- .maGetMarginalMeansPredictorMatrix( + fit = fit, + options = options, + dataset = dataset, + selectedVariables = c(selectedVariable, separateLines, separatePlots), + sdFactor = options[["bubblePlotSdFactorCovariates"]], + parameter = "effectSize" + ) + + } + + + if (.maIsMetaregressionHeterogeneity(options)) { + + predictorMatrixHeterogeneity <- .maGetMarginalMeansPredictorMatrix( + fit = fit, + options = options, + dataset = dataset, + selectedVariables = c(separateLines, separatePlots), + sdFactor = options[["bubblePlotSdFactorCovariates"]], + trendVarible = selectedVariable, + trendSequence = trendSequence, + parameter = "heterogeneity" + ) + + computedMarginalMeans <- predict( + fit, + newmods = predictorMatrixEffectSize, + newscale = predictorMatrixHeterogeneity, + level = 100 * options[["confidenceIntervalsLevel"]] + ) + } else { + + computedMarginalMeans <- predict( + fit, + newmods = predictorMatrixEffectSize, + level = 100 * options[["confidenceIntervalsLevel"]] + ) + } + + ### modify and rename selectedGrid + selectedGrid <- attr(predictorMatrixEffectSize, "selectedGrid") + selectedGrid$selectedVariable <- selectedGrid[,selectedVariable] + # deal with continuous variables dichotomization + selectedGrid <- .maDichotomizeVariablesLevels(selectedGrid, c(separateLines, separatePlots), options) + continuousLevels <- attr(selectedGrid, "continuousLevels") + # collapse factor levels if multiple selected + selectedGrid <- .maMergeVariablesLevels(selectedGrid, separateLines, "separateLines") + selectedGrid <- .maMergeVariablesLevels(selectedGrid, separatePlots, "separatePlots") + # remove original names + selectedGrid <- selectedGrid[,setdiff(names(selectedGrid), c(selectedVariable, separateLines, separatePlots)),drop = FALSE] + + ### modify marginal means + computedMarginalMeans <- .maExtractAndFormatPrediction(computedMarginalMeans) + + ### merge and add attributes + dfPlot <- cbind.data.frame(selectedGrid, computedMarginalMeans) + + attr(dfPlot, "selectedVariable") <- selectedVariable + attr(dfPlot, "selectedVariableType") <- selectedVariableType + attr(dfPlot, "separateLines") <- paste(separateLines, collapse = " | ") + attr(dfPlot, "separatePlots") <- paste(separatePlots, collapse = " | ") + attr(dfPlot, "variablesLines") <- separateLines + attr(dfPlot, "variablesPlots") <- separatePlots + attr(dfPlot, "continuousLevels") <- continuousLevels[!sapply(continuousLevels, is.null)] + attr(dfPlot, "xRange") <- if (selectedVariableType == "scale") xRange + + return(dfPlot) +} +.maMakeBubblePlot <- function(fit, options, dfPlot, separatePlotsLvl = NULL) { + + bubblePlot <- ggplot2::ggplot() + yRange <- NULL + + hasSeparateLines <- attr(dfPlot, "separateLines") != "" + hasSeparatePlots <- attr(dfPlot, "separatePlots") != "" + + ### add prediction bads + if (options[["bubblePlotPredictionIntervals"]]) { + + geomPi <- .maBubblePlotMakeCiGeom(dfPlot, options, ci = FALSE) + + if (!is.null(geomPi)) { + bubblePlot <- bubblePlot + do.call(geomPi$what, geomPi$args) + yRange <- attr(geomPi, "yRange") + } else { + yRange <- NA + } + + } + + ### add confidence bands + if (options[["bubblePlotConfidenceIntervals"]]) { + + geomCi <- .maBubblePlotMakeCiGeom(dfPlot, options, ci = TRUE) + + if (!is.null(geomCi)) { + bubblePlot <- bubblePlot + do.call(geomCi$what, geomCi$args) + yRange <- range(c(yRange, attr(geomCi, "yRange")), na.rm = TRUE) + } + + } + + ### add prediction line + if (attr(dfPlot, "selectedVariableType") == "scale") { + aesCall <- list( + x = as.name("selectedVariable"), + y = as.name("est"), + color = if (hasSeparateLines) as.name("separateLines") + ) + dfPlot[["y"]] <- do.call(.maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), list(dfPlot[["y"]])) + geomCall <- list( + data = dfPlot, + mapping = do.call(ggplot2::aes, aesCall[!sapply(aesCall, is.null)]) + ) + bubblePlot <- bubblePlot + do.call(jaspGraphs::geom_line, geomCall) + yRange <- range(c(yRange, dfPlot$pred), na.rm = TRUE) + } + + ### add studies as bubbles + dfStudies <- data.frame( + effectSize = fit[["yi"]], + inverseVariance = 1/fit[["vi"]], + weight = weights(fit), + constant = rep(options[["bubblePlotBubblesRelativeSize"]], nrow(fit[["data"]])), + selectedVariable = fit[["data"]][[attr(dfPlot, "selectedVariable")]] + ) + + # add separate lines and plots + if (hasSeparateLines) + dfStudies[attr(dfPlot, "variablesLines")] <- fit[["data"]][attr(dfPlot, "variablesLines")] + if (hasSeparatePlots) + dfStudies[attr(dfPlot, "variablesPlots")] <- fit[["data"]][attr(dfPlot, "variablesPlots")] + + # make same encoding + dfStudies <- .maDichotomizeVariablesDataset(dfStudies, c(attr(dfPlot, "variablesLines"), attr(dfPlot, "variablesPlots")), attr(dfPlot, "continuousLevels"), options) + dfStudies <- .maMergeVariablesLevels(dfStudies, variablesLines <- attr(dfPlot, "variablesLines"), "separateLines") + dfStudies <- .maMergeVariablesLevels(dfStudies, variablesLines <- attr(dfPlot, "variablesPlots"), "separatePlots") + if (hasSeparateLines) + levels(dfStudies[,"separateLines"]) <- levels(dfPlot[,"separateLines"]) + + # subset original data across plots + if (!is.null(separatePlotsLvl)) + dfStudies <- dfStudies[dfStudies$separatePlots == separatePlotsLvl,] + + aesCall <- list( + x = as.name("selectedVariable"), + y = as.name("effectSize"), + size = switch( + options[["bubblePlotBubblesSize"]], + "weight" = as.name("weight"), + "inverseVariance" = as.name("inverseVariance"), + "equal" = as.name("constant") + ), + color = if (hasSeparateLines) as.name("separateLines"), + fill = if (hasSeparateLines) as.name("separateLines"), + alpha = options[["bubblePlotBubblesTransparency"]] + ) + + dfStudies[["effectSize"]] <- do.call(.maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), list(dfStudies[["effectSize"]])) + + geomCall <- list( + data = dfStudies, + mapping = do.call(ggplot2::aes, aesCall[!sapply(aesCall, is.null)]), + show.legend = FALSE + ) + if (attr(dfPlot, "selectedVariableType") == "nominal" && hasSeparateLines) { + geomCall$position <- ggplot2::position_jitterdodge( + jitter.width = 0.35 * options[["bubblePlotBubblesJitter"]], + jitter.height = 0, + dodge.width = 0.9 + ) + }else if (attr(dfPlot, "selectedVariableType") == "nominal") { + geomCall$position <- ggplot2::position_jitter( + width = 0.35 * options[["bubblePlotBubblesJitter"]], + height = 0 + ) + } + + bubblePlot <- bubblePlot + do.call(jaspGraphs::geom_point, geomCall) + + ggplot2::scale_size(range = c(1.5, 10) * options[["bubblePlotBubblesRelativeSize"]]) + yRange <- range(c(yRange, dfStudies[["effectSize"]])) + + # add color palette + bubblePlot <- bubblePlot + + jaspGraphs::scale_JASPcolor_discrete(options[["colorPalette"]]) + + jaspGraphs::scale_JASPfill_discrete(options[["colorPalette"]]) + + attr(bubblePlot, "yRange") <- yRange + return(bubblePlot) +} +.maAddBubblePlotTheme <- function(plot, options, dfPlot, yRange) { + + + selectedVariableType <- attr(dfPlot, "selectedVariableType") + + if (selectedVariableType == "scale") { + plot <- plot + + jaspGraphs::scale_x_continuous( + name = attr(dfPlot, "selectedVariable"), + breaks = jaspGraphs::getPrettyAxisBreaks(attr(dfPlot, "xRange")), + limits = attr(dfPlot, "xRange") + ) + } else if (selectedVariableType == "nominal") { + plot <- plot + + ggplot2::scale_x_discrete( + name = attr(dfPlot, "selectedVariable") + ) + } + + plot <- plot + + jaspGraphs::scale_y_continuous( + name = if (options[["transformEffectSize"]] == "none") gettext("Effect Size") else .maGetOptionsNameEffectSizeTransformation(options[["transformEffectSize"]]), + breaks = jaspGraphs::getPrettyAxisBreaks(yRange), + limits = yRange + ) + + if (attr(dfPlot, "separateLines") != "") + plot <- plot + ggplot2::labs(fill = attr(dfPlot, "separateLines"), color = attr(dfPlot, "separateLines")) + + if (options[["bubblePlotTheme"]] == "jasp") { + + plot <- plot + + jaspGraphs::geom_rangeframe() + + jaspGraphs::themeJaspRaw(legend.position = if (attr(dfPlot, "separateLines") == "") "none" else options[["bubblePlotLegendPosition"]]) + + } else { + + plot <- plot + + switch( + options[["bubblePlotTheme"]], + "whiteBackground" = ggplot2::theme_bw() + ggplot2::theme(legend.position = "bottom"), + "light" = ggplot2::theme_light() + ggplot2::theme(legend.position = "bottom"), + "minimal" = ggplot2::theme_minimal() + ggplot2::theme(legend.position = "bottom"), + "pubr" = jaspGraphs::themePubrRaw(legend = options[["bubblePlotLegendPosition"]]), + "apa" = jaspGraphs::themeApaRaw(legend.pos = switch( + options[["bubblePlotLegendPosition"]], + "none" = "none", + "bottom" = "bottommiddle", + "right" = "bottomright", + "top" = "topmiddle", + "left" = "bottomleft" + )) + ) + + plot <- plot + ggplot2::theme( + legend.text = ggplot2::element_text(size = ggplot2::rel(options[["bubblePlotRelativeSizeText"]])), + legend.title = ggplot2::element_text(size = ggplot2::rel(options[["bubblePlotRelativeSizeText"]])), + axis.text = ggplot2::element_text(size = ggplot2::rel(options[["bubblePlotRelativeSizeText"]])), + axis.title = ggplot2::element_text(size = ggplot2::rel(options[["bubblePlotRelativeSizeText"]])), + legend.position = if (attr(dfPlot, "separateLines") == "") "none" else options[["bubblePlotLegendPosition"]]) + } + + return(plot) +} +.maMakeMetaforCallText <- function(options) { + + if (options[["module"]] == "metaAnalysis") { + rmaInput <- list( + yi = as.name(options[["effectSize"]]), + sei = as.name(options[["effectSizeStandardError"]]), + data = as.name("dataset") + ) + } else if (options[["module"]] == "metaAnalysisMultilevelMultivariate") { + # TODO: extend to covariance matrices + rmaInput <- list( + yi = as.name(options[["effectSize"]]), + V = paste0(options[["effectSizeStandardError"]], "^2"), # precomputed on data load + data = as.name("dataset") + ) + } + + # add formulas if specified + rmaInput$mods <- .maGetFormula(options[["effectSizeModelTerms"]], options[["effectSizeModelIncludeIntercept"]]) + rmaInput$scale <- .maGetFormula(options[["heterogeneityModelTerms"]], options[["heterogeneityModelIncludeIntercept"]]) + + # add random effects + if (.maIsMultilevelMultivariate(options)) { + randomFormulaList <- .mammGetRandomFormulaList(options) + if (length(randomFormulaList) != 0) { + struct <- do.call(c, lapply(randomFormulaList, attr, "structure")) + dist <- unlist(unname(lapply(randomFormulaList, attr, which = "dist")), recursive = FALSE) + R <- unlist(unname(lapply(randomFormulaList, attr, which = "R")), recursive = FALSE) + # change distance matrix into a variable + for (i in seq_along(dist)) { + if (is.matrix(dist[[i]])) + dist[[i]] <- paste0(names(dist)[i], gettext(" Distance Matrix")) + } + # change correlation matrix into a variable + for (i in seq_along(R)) { + R[[i]] <- paste0(names(R)[i], gettext(" Correlation Matrix")) + } + + if (length(randomFormulaList) > 1) + randomFormulaList <- paste0("list(\n\t\t", paste0("'", names(randomFormulaList), "' = ", randomFormulaList, collapse = "\n\t\t"),")") + rmaInput$random <- randomFormulaList + if (length(struct) != 0) + struct <- paste0("c(", paste0("'", names(struct), "' = '", struct, "'", collapse = ", "),")") + rmaInput$struct <- struct + if (length(dist) > 0) + dist <- paste0("list(", paste0(names(dist), ifelse(names(dist) == "", "'", " = '"), dist, "'", collapse = ", "),")") + rmaInput$dist <- dist + if (length(R) > 0) + R <- paste0("list(", paste0(names(R), " = '", R, "'", collapse = ", "),")") + rmaInput$R <- R + } + } + + # specify method and fixed effect terms test + rmaInput$method <- paste0("'", .maGetMethodOptions(options), "'") + rmaInput$test <- paste0("'", options[["fixedEffectTest"]], "'") + + if (!options[["weightedEstimation"]]) + rmaInput$weighted <- FALSE + + # add fixed parameters if needed + if (options[["fixParametersWeights"]] && options[["fixParametersWeightsVariable"]] != "") + rmaInput$weights <- as.name(options[["fixParametersWeightsVariable"]]) + if (options[["fixParametersTau2"]]) + rmaInput$tau2 <- .maGetFixedTau2Options(options) + + # add link function if needed + if (.maIsMetaregressionHeterogeneity(options)) + rmaInput$link <- paste0("'", options[["heterogeneityModelLink"]], "'") + + if (.maIsMultilevelMultivariate(options)) { + rmaInput$sparse <- if (options[["useSparseMatricies"]]) options[["useSparseMatricies"]] + rmaInput$cvvc <- if (!options[["computeCovarianceMatrix"]]) !options[["computeCovarianceMatrix"]] + } + + # add control options if needed + control <- .maGetControlOptions(options) + if (length(control) != 0) + rmaInput$control <- control + + # additional input + rmaInput$level <- 100 * options[["confidenceIntervalsLevel"]] + + # add additional options + if (options[["advancedExtendMetaforCall"]]) + rmaInput <- c(rmaInput, .maExtendMetaforCallFromOptions(options)) + + ### fit the model + fit <- paste0("fit <- rma(\n\t", paste(names(rmaInput), "=", rmaInput, collapse = ",\n\t"), "\n)\n") + + # add clustering if specified + if (options[["clustering"]] != "") { + + robustInput <- list( + cluster = as.name(options[["clustering"]]), + clubSandwich = options[["clusteringUseClubSandwich"]], + adjust = options[["clusteringSmallSampleCorrection"]] + ) + + fit <- paste0( + fit, "\n", + "fit <- robust(\n", + "\tfit,\n\t", + paste(names(robustInput), "=", robustInput, collapse = ",\n\t"), "\n)\n" + ) + } + + # add permutation if specified + if (.maIsPermutation(options)) { + + if (options[["setSeed"]]) + fit <- paste0(fit, "\nset.seed(", options[["seed"]], ")\n") + + fit <- paste0( + fit, "\n", + "fitPermutation <- permutest(\n", + "\tfit,\n", + "\texact = ", options[["permutationTestType"]] == "exact", ",\n", + "\titer = ", options[["permutationTestIteration"]], "\n", + ")\n" + ) + } + + return(fit) +} +.maComputeVifSummary <- function(fit, options, parameter = "effectSize") { + + if (options[["diagnosticsVarianceInflationFactorAggregate"]]) { + + # obtain terms indicies + if (parameter == "effectSize") { + terms <- attr(terms(fit[["formula.mods"]], data = fit[["data"]]),"term.labels") + termsIndex <- attr(model.matrix(fit[["formula.mods"]], data = fit[["data"]]), "assign") + tableVif <- do.call(rbind, lapply(seq_along(terms), function(i) { + cbind.data.frame( + term = terms[i], + .maExtractVifResults(metafor::vif(fit, btt = seq_along(termsIndex)[termsIndex == i]), options, parameter) + ) + })) + } else if (parameter == "heterogeneity") { + terms <- attr(terms(fit[["formula.scale"]], data = fit[["data"]]),"term.labels") + termsIndex <- attr(model.matrix(fit[["formula.scale"]], data = fit[["data"]]), "assign") + tableVif <- do.call(rbind, lapply(seq_along(terms), function(i) { + cbind.data.frame( + term = terms[i], + .maExtractVifResults(metafor::vif(fit, att = seq_along(termsIndex)[termsIndex == i]), options, parameter) + ) + })) + } + + } else { + + tableVif <- .maExtractVifResults(metafor::vif(fit), options, parameter) + tableVif$term <- .maVariableNames(rownames(tableVif), options[["predictors"]]) + } + + return(tableVif) +} +.maBubblePlotMakeCiGeom <- function(dfPlot, options, ci = TRUE) { + + hasSeparateLines <- attr(dfPlot, "separateLines") != "" + hasSeparatePlots <- attr(dfPlot, "separatePlots") != "" + selectedVariableType <- attr(dfPlot, "selectedVariableType") + + aesCall <- list( + x = as.name("selectedVariable"), + fill = if (hasSeparateLines) as.name("separateLines"), + group = if (hasSeparateLines && selectedVariableType == "scale") as.name("separateLines") + ) + + if (selectedVariableType == "scale") { + aesCall$y <- as.name("y") + } else if (selectedVariableType == "nominal") { + aesCall$lower <- as.name("lower") + aesCall$upper <- as.name("upper") + aesCall$ymin <- as.name("lower") + aesCall$ymax <- as.name("upper") + aesCall$middle <- as.name("middle") + } + + dfBands <- .maBubblePlotMakeConfidenceBands( + dfPlot, + lCi = if (ci) "lCi" else "lPi", + uCi = if (ci) "uCi" else "uPi" + ) + + if (selectedVariableType == "scale") { + dfBands[["y"]] <- do.call(.maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), list(dfBands[["y"]])) + } else if (selectedVariableType == "nominal") { + dfBands[,c("lower","middle","upper")] <- do.call( + .maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), + list(dfBands[,c("lower","middle","upper")])) + } + + geomCall <- list( + data = dfBands, + mapping = do.call(ggplot2::aes, aesCall[!sapply(aesCall, is.null)]), + alpha = options[["bubblePlotPredictionIntervalsTransparency"]] + ) + + if (selectedVariableType == "nominal") { + geomCall$stat <- "identity" + geomCall$position <- ggplot2::position_dodge2(width = 0.9) + if (!hasSeparateLines) + geomCall$fill <- "grey" + } + + + if (selectedVariableType == "scale" && any(!is.na(dfBands[["y"]]))) { + geom <- list( + what = ggplot2::geom_polygon, + args = geomCall + ) + attr(geom, "yRange") <- range(c(dfBands$y)) + } else if (selectedVariableType == "nominal" && any(!is.na(dfBands[["lower"]]))) { + geom <- list( + what = ggplot2::geom_boxplot, + args = geomCall + ) + attr(geom, "yRange") <- range(c(dfBands$lower, dfBands$upper)) + } else { + geom <- NULL + } + + return(geom) +} +.maMakeResidualFunnelPlot <- function(fit, options, dataset) { + + dfPlot <- data.frame( + x = resid(fit), + y = sqrt(fit[["vi"]]) + ) + + yTicks <- jaspGraphs::getPrettyAxisBreaks(range(dfPlot$y)) + + dfFunnel <- data.frame( + x = c(-max(yTicks), 0, max(yTicks)) / 1.96, + y = c(max(yTicks), 0, max(yTicks)) + ) + dfFunnelEdge1 <- dfFunnel[1:2,] + dfFunnelEdge2 <- dfFunnel[2:3,] + + xTicks <- jaspGraphs::getPrettyAxisBreaks(range(c(dfPlot$x, dfFunnel$x))) + + dfBackground <- data.frame( + x = c(min(xTicks), max(xTicks), max(xTicks), min(xTicks)), + y = c(min(yTicks), min(yTicks), max(yTicks), max(yTicks)) + ) + + out <- ggplot2::ggplot() + + ggplot2::geom_polygon( + data = dfBackground, + mapping = ggplot2::aes(x = x, y = y), + fill = "grey", + ) + + ggplot2::geom_polygon( + data = dfFunnel, + mapping = ggplot2::aes(x = x, y = y), + fill = "white", + ) + + ggplot2::geom_line( + mapping = ggplot2::aes( + x = c(0, 0), + y = range(yTicks) + ), linetype = "dotted" + ) + + ggplot2::geom_line( + data = dfFunnelEdge1, + mapping = ggplot2::aes(x = x, y = y), linetype = "dotted" + ) + + ggplot2::geom_line( + data = dfFunnelEdge2, + mapping = ggplot2::aes(x = x, y = y), linetype = "dotted" + ) + + ggplot2::geom_line( + mapping = ggplot2::aes( + x = c(0, 0), + y = range(yTicks) + ), linetype = "dotted" + ) + + jaspGraphs::geom_point( + data = dfPlot, + mapping = ggplot2::aes(x = x, y = y), + fill = "black" + ) + + # add labels if specified + if (options[["studyLabels"]] != "") { + + dfLabels <- cbind( + dfPlot, + label = dataset[[options[["studyLabels"]]]] + ) + dfLabels <- dfLabels[abs(dfLabels$y/1.96) < abs(dfLabels$x),] + dfLabels$position <- ifelse(dfLabels$x < 0, "right", "left") + dfLabels$nudge_x <- ifelse(dfLabels$x < 0, -0.1, 0.1) + + out <- out + + ggplot2::geom_text( + data = dfLabels, + mapping = ggplot2::aes(x = x, y = y, label = label, hjust = position), nudge_x = dfLabels$nudge_x + ) + } + + out <- out + + jaspGraphs::scale_x_continuous(breaks = xTicks, limits = range(xTicks), name = gettext("Residual Value")) + + ggplot2::scale_y_reverse(breaks = rev(yTicks), limits = rev(range(yTicks)), name = gettext("Standard Error")) + + jaspGraphs::geom_rangeframe() + + jaspGraphs::themeJaspRaw() + + return(out) +} +.maMakeProfileLikelihoodPlot <- function(dfPlot) { + + yTicks <- jaspGraphs::getPrettyAxisBreaks(c(min(dfPlot$ll), max(dfPlot$ll))) + + # xTicks and other attributes only passed for rma.uni + # (there are way too many options to deal with for rma.mv --- using the metafor package defaults) + if (!is.null(attr(dfPlot, "xTicks"))) + xTicks <- attr(dfPlot, "xTicks") + else + xTicks <- jaspGraphs::getPrettyAxisBreaks(c(min(dfPlot[[1]]), max(dfPlot[[1]]))) + + # create plot + plotOut <- ggplot2::ggplot( + data = data.frame(x = dfPlot[[1]], y = dfPlot[["ll"]]), + mapping = ggplot2::aes(x = x, y = y) + ) + + jaspGraphs::geom_line() + + jaspGraphs::geom_point() + + plotOut <- plotOut + + ggplot2::geom_line( + data = data.frame( + x = rep(dfPlot[["vc"]], 2), + y = range(yTicks)), + linetype = "dotted") + + ggplot2::geom_line( + data = data.frame( + x = range(xTicks), + y = rep(max(dfPlot[["maxll"]]), 2)), + linetype = "dotted") + + plotOut <- plotOut + + ggplot2::labs(x = dfPlot[["xlab"]], y = gettext("Profile Likelihood")) + + jaspGraphs::scale_x_continuous(breaks = xTicks, limits = range(xTicks)) + + jaspGraphs::scale_y_continuous(breaks = yTicks, limits = range(yTicks)) + + jaspGraphs::geom_rangeframe() + + jaspGraphs::themeJaspRaw() + + return(plotOut) +} + +# check functions +.maIsMetaregression <- function(options) { + return(.maIsMetaregressionEffectSize(options) || .maIsMetaregressionHeterogeneity(options)) +} +.maIsMetaregressionEffectSize <- function(options) { + return(length(options[["effectSizeModelTerms"]]) > 0) +} +.maIsMetaregressionHeterogeneity <- function(options) { + return(length(options[["heterogeneityModelTerms"]]) > 0) +} +.maIsClustered <- function(options) { + return(options[["clustering"]] != "") +} +.maIsMetaregressionFtest <- function(options) { + return(options[["fixedEffectTest"]] %in% c("knha", "t")) +} +.maIsMultilevelMultivariate <- function(options) { + return(options[["module"]] == "metaAnalysisMultilevelMultivariate") +} +.maIsPermutation <- function(options) { + return(!.maIsClustered(options) && options[["permutationTest"]]) +} +.maCheckIsPossibleOptions <- function(options) { + + if (length(options[["heterogeneityModelTerms"]]) > 0 && options[["clustering"]] != "") { + return(gettext("Clustering is not supported when specifying a heterogeneity meta-regression model.")) + } + + return(NULL) +} + +# extract options +.maGetMethodOptions <- function(options) { + + switch( + options[["method"]], + "equalEffects" = "EE", + "fixedEffects" = "FE", + "maximumLikelihood" = "ML", + "restrictedML" = "REML", + "derSimonianLaird" = "DL", + "hedges" = "HE", + "hunterSchmidt" = "HS", + "hunterSchmidtSsc" = "HSk", + "sidikJonkman" = "SJ", + "empiricalBayes" = "EB", + "pauleMandel" = "PM", + "pauleMandelMu" = "PMM", + "qeneralizedQStat" = "GENQ", + "qeneralizedQStatMu" = "GENQM", + NA + ) +} +.maGetFixedTau2Options <- function(options) { + + tau2 <- .parseRCodeInOptions(options[["fixParametersTau2Value"]]) + + if (!is.numeric(tau2) || length(tau2) != 1 || tau2 < 0) + .quitAnalysis(gettext("The fixed value for tau2 must be a positive number.")) + else + return(tau2) +} +.maGetControlOptions <- function(options) { + + if (.maIsMetaregressionHeterogeneity(options)) { + out <- list( + optimizer = options[["optimizerMethod"]], + iter.max = if (options[["optimizerMaximumIterations"]]) options[["optimizerMaximumIterationsValue"]], + rel.tol = if (options[["optimizerConvergenceRelativeTolerance"]]) options[["optimizerConvergenceRelativeToleranceValue"]] + ) + } else { + if (.maIsMultilevelMultivariate(options)) { + if (options[["optimizerMethod"]] == "nlminb") { + out <- list( + optimizer = options[["optimizerMethod"]], + eval.max = if (options[["optimizerMaximumEvaluations"]]) options[["optimizerMaximumEvaluationsValue"]], + iter.max = if (options[["optimizerMaximumIterations"]]) options[["optimizerMaximumIterationsValue"]], + rel.tol = if (options[["optimizerConvergenceRelativeTolerance"]]) options[["optimizerConvergenceRelativeToleranceValue"]] + ) + } else if (options[["optimizerMethod"]] %in% c("Nelder-Mead", "BFGS")){ + out <- list( + optimizer = options[["optimizerMethod"]], + maxit = if (options[["optimizerMaximumIterations"]]) options[["optimizerMaximumIterationsValue"]], + reltol = if (options[["optimizerConvergenceRelativeTolerance"]]) options[["optimizerConvergenceRelativeToleranceValue"]] + ) + } else if (options[["optimizerMethod"]] %in% c("uobyqa", "newuoa", "bobyqa")){ + out <- list( + optimizer = options[["optimizerMethod"]], + maxfun = if (options[["optimizerMaximumEvaluations"]]) options[["optimizerMaximumEvaluationsValue"]], + rhobeg = if (options[["optimizerInitialTrustRegionRadius"]]) options[["optimizerInitialTrustRegionRadiusValue"]], + rhoend = if (options[["optimizerFinalTrustRegionRadius"]]) options[["optimizerFinalTrustRegionRadiusValue"]] + ) + } else if (options[["optimizerMethod"]] %in% c("nloptr", "nlm")){ + # could be much more, "nloptr" probably requires choosing a method too + out <- list( + optimizer = options[["optimizerMethod"]], + iterlim = if (options[["optimizerMaximumIterations"]]) options[["optimizerMaximumIterationsValue"]] + ) + } else if (options[["optimizerMethod"]] %in% c("hjk", "nmk", "mads")){ + out <- list( + optimizer = options[["optimizerMethod"]], + tol = if (options[["optimizerConvergenceTolerance"]]) options[["optimizerConvergenceToleranceValue"]], + maxfeval = if (options[["optimizerMaximumEvaluations"]]) options[["optimizerMaximumEvaluationsValue"]], + restarts.max = if (options[["optimizerMethod"]] == "mmk" && options[["optimizerMaximumRestarts"]]) options[["optimizerMaximumRestartsValue"]] + ) + } + } else { + if (.maGetMethodOptions(options) %in% c("REML", "ML", "EB")) { + out <- list( + tau2.init = if (options[["optimizerInitialTau2"]]) options[["optimizerInitialTau2Value"]], + iter.max = if (options[["optimizerMaximumIterations"]]) options[["optimizerMaximumIterationsValue"]], + threshold = if (options[["optimizerConvergenceTolerance"]]) options[["optimizerConvergenceToleranceValue"]], + stepadj = if (options[["optimizerStepAdjustment"]]) options[["optimizerStepAdjustmentValue"]] + ) + } else if (.maGetMethodOptions(options) %in% c("PM", "PMM", "GENQM")) { + out <- list( + iter.max = if (options[["optimizerMaximumIterations"]]) options[["optimizerMaximumIterationsValue"]], + tol = if (options[["optimizerConvergenceTolerance"]]) options[["optimizerConvergenceToleranceValue"]], + tau2.min = if (options[["optimizerMinimumTau2"]]) options[["optimizerMinimumTau2Value"]], + tau2.max = if (options[["optimizerMaximumTau2"]]) options[["optimizerMaximumTau2Value"]] + ) + } else if (.maGetMethodOptions(options) %in% c("SD")) { + out <- list( + tau2.init = if (options[["optimizerInitialTau2"]]) options[["optimizerInitialTau2Value"]] + ) + } else { + out <- list() + } + } + } + return(out[!sapply(out, is.null)]) +} +.maGetEffectSizeTransformationOptions <- function(effectSizeTransformation) { + + switch( + effectSizeTransformation, + none = function(x) x, + fishersZToCorrelation = metafor::transf.ztor, + exponential = exp, + logOddsToProportions = metafor::transf.logit, + logOddsToSmdNormal = metafor::transf.lnortod.norm, + logOddsToSmdLogistic = metafor::transf.lnortod.logis, + smdToLogOddsNormal = metafor::transf.dtolnor.norm, + smdToLogOddsLogistic = metafor::transf.dtolnor.logis, + hakstianAndWhalenInverseAlpha = metafor::transf.iahw, + bonettInverseAlpha = metafor::transf.iabt, + zToR2 = metafor::transf.ztor2, + smdToCohensU1 = metafor::transf.dtou1, + smdToCohensU2 = metafor::transf.dtou2, + smdToCohensU3 = metafor::transf.dtou3, + smdToCles = metafor::transf.dtocles, + stop(paste0("Unknown effect size transformation: ", effectSizeTransformation)) + ) +} +.maExtendMetaforCallFromOptions <- function(options) { + + optionsCode <- options[["advancedExtendMetaforCallCode"]] + optionsCode <- trimws(optionsCode, which = "both") + if (substr(optionsCode, 1, 4) != "list") + optionsCode <- paste0("list(\n", optionsCode, "\n)") + optionsCode <- try(eval(parse(text = optionsCode))) + + if (jaspBase::isTryError(optionsCode)) + .quitAnalysis(gettextf("The custom R code for extending the metafor call failed with the following message: %1$s", optionsCode)) + + return(optionsCode) +} + +# options names +.maGetOptionsNameEffectSizeTransformation <- function(effectSizeTransformation) { + + return(switch( + effectSizeTransformation, + "none" = NULL, + "fishersZToCorrelation" = gettext("Fisher's z to r"), + "exponential" = gettext("Exponential"), + "logOddsToProportions" = gettext("Log odds to proportions"), + "logOddsToSmdNormal" = gettext("Log odds to SMD (normal)"), + "logOddsToSmdLogistic" = gettext("Log odds to SMD (logistic)"), + "smdToLogOddsNormal" = gettext("SMD to log odds (normal)"), + "smdToLogOddsLogistic" = gettext("SMD to log odds (logistic)"), + "hakstianAndWhalenInverseAlpha" = gettext("Hakstian & Whalen inverse α"), + "bonettInverseAlpha" = gettext("Bonett inverse α"), + "zToR2" = gettext("Z to R²"), + "smdToCohensU1" = gettext("SMD to Cohen's U₁"), + "smdToCohensU2" = gettext("SMD to Cohen's U₂"), + "smdToCohensU3" = gettext("SMD to Cohen's U₃"), + "smdToCles" = gettext("SMD to CLES, Pr(supperiority)") + )) +} +.maCasewiseDiagnosticsExportColumnsNames <- function(columnName) { + + return(switch( + columnName, + "rstudent" = "Standardized Residual", + "dffits" = "DFFITS", + "cook.d" = "Cook's Distance", + "cov.r" = "Covariance Ratio", + "tau.del" = "Tau", + "tau2.del" = "Tau2 LOO", + "QE.del" = "QE LOO", + "hat" = "Hat", + "weight" = "Weight", + "inf" = "Influential" + )) +} + +# misc +.maVariableNames <- function(varNames, variables) { + + return(sapply(varNames, function(varName){ + + if (varName == "intrcpt") + return("Intercept") + + for (vn in variables) { + inf <- regexpr(vn, varName, fixed = TRUE) + + if (inf[1] != -1) { + varName <- paste0( + substr(varName, 0, inf[1] - 1), + substr(varName, inf[1], inf[1] + attr(inf, "match.length") - 1), + " (", + substr(varName, inf[1] + attr(inf, "match.length"), nchar(varName)) + ) + } + + } + + varName <- gsub(":", paste0(")", jaspBase::interactionSymbol), varName, fixed = TRUE) + varName <- paste0(varName, ")") + varName <- gsub(" ()", "", varName, fixed = TRUE) + varName <- gsub(" (/", "/", varName, fixed = TRUE) + + return(varName) + + })) +} +.maPrintQTest <- function(fit) { + + return(sprintf("Heterogeneity: Q(%1$i) = %2$.2f, %3$s", fit[["k"]] - fit[["p"]], fit[["QE"]], .maPrintPValue(fit[["QEp"]]))) +} +.maPrintModerationTest <- function(fit, options, parameter) { + + out <- .maOmnibusTest(fit, options, parameter) + outPrint <- .maPrintTermTest(out, testStatistic = TRUE) + + if (.maIsMetaregressionHeterogeneity(options)) { + if (parameter == "effectSize") + return(gettextf("Moderation (Effect Size): %1$s", outPrint)) + else if (parameter == "heterogeneity") + return(gettextf("Moderation (Heterogeneity): %1$s", outPrint)) + } else { + if (parameter == "effectSize") + return(gettextf("Moderation: %1$s", outPrint)) + } +} +.maPrintHeterogeneityEstimate <- function(fit, options, digits, keepText) { + + out <- .maComputePooledHeterogeneityPlot(fit, options) + + if (keepText) + prefix <- gettext("Heterogeneity: ") + else + prefix <- "" # paste0(rep(" ", nchar(gettext("Heterogeneity: "))), collapse = "") + + return(sprintf(paste0( + "%1$s tau = ", + "%2$.", digits, "f", + " [", + "%3$.", digits, "f", + ", ", + "%4$.", digits, "f", + "]" + ), prefix, out$est, out$lCi, out$uCi)) +} +.maPrintTermTest <- function(out, testStatistic = TRUE) { + + if (testStatistic) { + if (!is.null(out[["df2"]])) { + return(sprintf("F(%1$i, %2$.2f) = %3$.2f, %4$s", out[["df1"]], out[["df2"]], out[["stat"]], .maPrintPValue(out[["pval"]]))) + } else { + return(sprintf("Q\U2098(%1$i) = %2$.2f, %3$s", out[["df1"]], out[["stat"]], .maPrintPValue(out[["pval"]]))) + } + } else { + return(.maPrintPValue(out[["pval"]])) + } +} +.maPrintCoefficientTest <- function(out, testStatistic = TRUE) { + + if (testStatistic) { + if (!is.null(out[["df"]])) { + return(sprintf("t(%1$.2f) = %2$.2f, %3$s", out[["df"]], out[["stat"]], .maPrintPValue(out[["pval"]]))) + } else { + return(sprintf("z = %1$.2f, %2$s", out[["df1"]], out[["stat"]], .maPrintPValue(out[["pval"]]))) + } + } else { + return(.maPrintPValue(out[["pval"]])) + } +} +.maPrintPValue <- function(pValue) { + if (pValue < 0.001) { + return("p < 0.001") + } else { + return(sprintf("p = %.3f", pValue)) + } +} +.maPrintEstimateAndInterval <- function(est, lCi, uCi, digits) { + return(sprintf(paste0( + .maAddSpaceForPositiveValue(est), "%1$.", digits, "f", + " [", + .maAddSpaceForPositiveValue(lCi), "%2$.", digits, "f", + ", ", + .maAddSpaceForPositiveValue(uCi), "%3$.", digits, "f", + "]"), est, lCi, uCi)) +} +.maPrintPredictionInterval <- function(est, lCi, uCi, digits) { + return(sprintf(paste0( + " ", "%1$.", digits, "f", + " [", + .maAddSpaceForPositiveValue(lCi), "%2$.", digits, "f", + ", ", + .maAddSpaceForPositiveValue(uCi), "%3$.", digits, "f", + "]"), est, lCi, uCi)) +} +.maAddSpaceForPositiveValue <- function(value) { + if (value >= 0) + return(" ") + else + return("") +} +.maMakeDiamondDataFrame <- function(est, lCi, uCi, row, id, adj = 1/3) { + return(data.frame( + id = id, + x = c(lCi, est, uCi, est), + y = c(row, row-adj, row, row+adj), + type = "diamond", + mapColor = NA + )) +} +.maMakeRectangleDataFrame <- function(lCi, uCi, row, id, adj = 1/5) { + return(data.frame( + id = id, + x = c(lCi, uCi, uCi, lCi), + y = c(row-adj, row-adj, row+adj, row+adj), + type = "rectangle", + mapColor = NA + )) +} +.maGetDigitsBeforeDecimal <- function(x) { + + dNAs <- is.na(x) + dPos <- floor(log10(x[!dNAs & x >= 0])) + 1 + dNeg <- floor(log10(-x[!dNAs & x < 0])) + 2 + + # account for missing zeros + dPos[dPos <= 1] <- 1 + dNeg[dNeg <= 1] <- 2 # (+2 because of minus sign) + + nDigits <- rep(NA, length(x)) + nDigits[!dNAs & x >= 0] <- dPos + nDigits[!dNAs & x < 0] <- dNeg + + return(nDigits) +} +.maFormatDigits <- function(x, digits) { + + xOut <- rep("", length(x)) + xNa <- is.na(x) + + # compute the character width + nDigits <- .maGetDigitsBeforeDecimal(x[!xNa]) + nDigitsMax <- max(nDigits, na.rm = TRUE) + addDigits <- nDigitsMax - nDigits + + # add the missing widths + xOut[!xNa] <- sprintf(paste0("%1$s%2$.", digits,"f"), sapply(addDigits, function(i) paste(rep(" ", i), collapse = "")), x[!xNa]) + xOut[ xNa] <- paste(rep(" ", nDigitsMax + 1 + digits), collapse = "") + + return(xOut) +} +.maBubblePlotMakeConfidenceBands <- function(dfPlot, lCi = "lCi", uCi = "uCi") { + + if (attr(dfPlot, "selectedVariableType") == "scale") { + + if (!is.null(dfPlot[["separateLines"]])) { + + dfBands <- do.call(rbind, lapply(unique(dfPlot[["separateLines"]]), function(lvl) { + dfSubset <- dfPlot[dfPlot[["separateLines"]] == lvl,] + dfPolygon <- data.frame( + selectedVariable = c(dfSubset$selectedVariable, rev(dfSubset$selectedVariable)), + y = c(dfSubset[[lCi]], rev(dfSubset[[uCi]])) + ) + dfPolygon$separateLines <- lvl + return(dfPolygon) + })) + + } else { + + dfBands <- data.frame( + selectedVariable = c(dfPlot$selectedVariable, rev(dfPlot$selectedVariable)), + y = c(dfPlot[[lCi]], rev(dfPlot[[uCi]])) + ) + + } + + } else { + + dfBands <- data.frame( + lower = dfPlot[[lCi]], + upper = dfPlot[[uCi]], + middle = dfPlot[["est"]], + selectedVariable = dfPlot[["selectedVariable"]] + ) + + if (!is.null(dfPlot[["separateLines"]])) + dfBands$separateLines <- dfPlot[["separateLines"]] + + } + + return(dfBands) +} +.maMergeVariablesLevels <- function(df, variables, mergedName) { + if (length(variables) == 1) { + df[[mergedName]] <- factor( + df[,variables], + levels = unique(df[,variables]) + ) + } else if (length(variables) > 1) { + df[[mergedName]] <- factor( + apply(df[,variables], 1, function(x) paste(x, collapse = " | ")), + levels = unique(apply(df[,variables], 1, function(x) paste(x, collapse = " | "))) + ) + } + return(df) +} +.maTransformToHtml <- function(rCode) { + + # Replace special characters with HTML entities + htmlCode <- gsub("&", "&", rCode) + htmlCode <- gsub("<", "<", htmlCode) + htmlCode <- gsub(">", ">", htmlCode) + + # Wrap the code in
 and  tags
+  htmlCode <- paste0(
+    "
", htmlCode, "\n
" + ) + + return(htmlCode) +} +.maExtractVifResults <- function(vifResults, options, parameter) { + + if (.maIsMetaregressionHeterogeneity(options)) + vifResults <- vifResults[[switch( + parameter, + "effectSize" = "beta", + "heterogeneity" = "alpha" + )]] + + vifResults <- data.frame(vifResults) + + if (options[["diagnosticsVarianceInflationFactorAggregate"]]) + vifResults <- vifResults[,c("m", "vif", "sif"),drop = FALSE] + else + vifResults <- vifResults[,c("vif", "sif"),drop = FALSE] + + return(vifResults) +} +.maGetVariableColumnType <- function(variable, options) { + + if (.maIsMultilevelMultivariate(options)) { + randomVariables <- .mammExtractRandomVariableNames(options) + } else { + randomVariables <- NULL + } + + if (variable %in% c(options[["effectSize"]], options[["effectSizeStandardError"]], "samplingVariance", + options[["predictors"]][options[["predictors.types"]] == "scale"], randomVariables[["scale"]], randomVariables[["ordinal"]])) { + return("number") + } else if (variable %in% c(options[["predictors"]][options[["predictors.types"]] == "nominal"], options[["clustering"]], randomVariables[["nominal"]])) { + return("string") + } else { + return("string") + } +} +.maSuppressPlot <- function(plotExpression) { + temp <- tempfile() + pdf(file = temp) + dfOut <- plotExpression + dev.off() + unlink(temp) + return(dfOut) +} +.maExtractAndFormatPrediction <- function(out) { + + # save as a data.frame + out <- data.frame(out) + + # TODO: decide whether those should be added as NAs or CIs + # - if NAs, need to be adjusted for in the rest of the code / GUI + if (!"pi.lb" %in% colnames(out)) { + out$pi.lb <- NA + out$pi.ub <- NA + #out$pi.lb <- out$ci.lb + #out$pi.ub <- out$ci.ub + } + + # rename into a consistent format + out <- out[,c("pred", "se", "ci.lb", "ci.ub", "pi.lb", "pi.ub")] + colnames(out) <- c("est", "se", "lCi", "uCi", "lPi", "uPi") + + return(out) +} +.maDichotomizeVariablesLevels <- function(df, variables, options) { + + variablesContinuous <- variables[variables %in% options[["predictors"]][options[["predictors.types"]] == "scale"]] + for (i in seq_along(variablesContinuous)){ + tempUnique <- sort(unique(df[[variablesContinuous[i]]])) + df[[variablesContinuous[i]]] <- as.character(factor( + df[[variablesContinuous[i]]], + levels = tempUnique, + labels = c(paste0("Mean - ", options[["bubblePlotSdFactorCovariates"]], "SD"), "Mean", paste0("Mean + ", options[["bubblePlotSdFactorCovariates"]], "SD")) + )) + attr(df, "continuousLevels") <- list( + attr(df, "continuousLevels"), + list( + variable = variablesContinuous[i], + levels = tempUnique + ) + ) + } + return(df) +} +.maDichotomizeVariablesDataset <- function(df, variables, variablesInformation, options) { + + variablesContinuous <- variables[variables %in% options[["predictors"]][options[["predictors.types"]] == "scale"]] + + for (i in seq_along(variablesContinuous)){ + + tempUnique <- variablesInformation[[sapply(variablesInformation, function(x) x[["variable"]]) == variablesContinuous[i]]] + + df[[variablesContinuous[i]]] <- cut( + df[[variablesContinuous[i]]], + breaks = c(-Inf, mean(tempUnique[["levels"]][1:2]), mean(tempUnique[["levels"]][2:3]), Inf), + labels = c(paste0("Mean - ", options[["bubblePlotSdFactorCovariates"]], "SD"), "Mean", paste0("Mean + ", options[["bubblePlotSdFactorCovariates"]], "SD")) + ) + + } + + return(df) +} + +# messages +.maFixedEffectTextMessage <- function(options) { + return(switch( + options[["fixedEffectTest"]], + "z" = gettext("Fixed effect tested using z-distribution."), + "t" = gettext("Fixed effect tested using t-distribution."), + "knha" = gettext("Fixed effect tested using Knapp and Hartung adjustment."), + stop(paste0("Unknown fixed effect test.", options[["fixedEffectTest"]])) + )) +} +.meMetaregressionHeterogeneityMessages <- function(options) { + + if (options[["heterogeneityModelLink"]] == "log") + return(gettext("The heterogeneity model for \U1D70F\U00B2 is specified on the log scale.")) + else if (options[["heterogeneityModelLink"]] == "identity") + return(gettext("The heterogeneity model for \U1D70F\U00B2 is specified on the identity scale.")) +} +.maPooledEstimatesMessages <- function(fit, dataset, options) { + + messages <- NULL + + if (options[["clustering"]] != "") { + if (all(fit[["tcl"]][1] == fit[["tcl"]])) + messages <- c(messages, gettextf("%1$i clusters with %2$i estimates each.", fit[["n"]], fit[["tcl"]][1])) + else + messages <- c(messages, gettextf("%1$i clusters with min/median/max %2$i/%3$i/%4$i estimates.", fit[["n"]], min(fit[["tcl"]]), median(fit[["tcl"]]), max(fit[["tcl"]]))) + } + + if (options[["transformEffectSize"]] != "none") + messages <- c(messages, gettextf("The pooled effect size is transformed using %1$s transformation.", .maGetOptionsNameEffectSizeTransformation(options[["transformEffectSize"]]))) + + if (.maIsMetaregressionEffectSize(options)) + messages <- c(messages, gettext("The pooled effect size corresponds to the weighted average effect across studies.")) + + if (.maIsMetaregressionHeterogeneity(options)) + messages <- c(messages, gettext("The pooled heterogeneity estimate corresponds to the heterogeneity at the average of predictor values.")) + + if (.maIsMetaregressionHeterogeneity(options) && (options[["heterogeneityI2"]] || options[["heterogeneityH2"]])) + messages <- c(messages, gettext("The I² and H² statistics are not available for heterogeneity models.")) + + if (attr(dataset, "NAs") > 0) + messages <- c(messages, gettextf("%1$i observations were ommited due to missing values.", attr(dataset, "NAs"))) + + if (!is.null(attr(dataset, "influentialObservations")) && attr(dataset, "influentialObservations") > 0) + messages <- c(messages, gettextf("%1$i influential observations were detected and removed.", attr(dataset, "influentialObservations"))) + + if (.maIsMultilevelMultivariate(options) && any(attr(fit, "skipped"))) + messages <- c(messages, gettextf("The Model Structure %1$s was not completely specified and was skipped.", paste0(which(attr(fit, "skipped")), collapse = " and "))) + + if (.mammAnyStructureGen(options) && options[["predictionIntervals"]]) + messages <- c(messages, gettext("Prediction interval for the pooled effect size is not available for models with multiple heterogeneity estimates.")) + + return(messages) +} +.maEstimatedMarginalMeansMessages <- function(options, parameter) { + + messages <- gettext("Each marginal mean estimate is averaged across the levels of the remaining predictors.") + + if (parameter == "effectSize" && options[["transformEffectSize"]] != "none") + messages <- c(messages, gettextf("The estimates and intervals are transformed using %1$s transformation.", .maGetOptionsNameEffectSizeTransformation(options[["transformEffectSize"]]))) + + if (parameter == "heterogeneity") + messages <- c(messages, gettextf("The estimates and intervals correspond to %1$s.", switch( + options[["estimatedMarginalMeansHeterogeneityTransformation"]], + "tau" = gettext("\U1D70F"), + "tau2" = gettext("\U1D70F\U00B2") + ))) + + return(messages) +} +.maPermutationMessage <- function(options) { + return(gettextf("Permutation p-value is based on %1$s permutations.", switch( + options[["permutationTestType"]], + "exact" = gettext("exact"), + "approximate" = options[["permutationTestIteration"]] + ))) +} +.maTryCleanErrorMessages <- function(message) { + # probably more messages will be gathered over time + if (grepl("singular matrix", message)) + return(gettextf("The model estimation failed with the following message: %1$s. Please, consider simplifying the model.", message)) - dataset <- dataset[factorCols] - - mapping <- levelsPerFactor <- lapply(dataset, levels) - names(levelsPerFactor) <- names(levelsPerFactor) - names(mapping) <- NULL - - for (i in seq_along(levelsPerFactor)) { - values <- paste0(names(levelsPerFactor)[i], levelsPerFactor[[i]]) - values <- setNames(values, paste0(names(levelsPerFactor)[i], " (", levelsPerFactor[[i]], ")")) - mapping[[i]] <- values - } - - return(unlist(mapping)) -} - -# these functions originally lived in jaspBase/R/common.R, but are only used by this module -as.modelTerms <- function(object, ...) UseMethod("as.modelTerms") -as.modelTerms.list <- function(object) structure(object, class = "modelTerms") -as.modelTerms.formula <- function(formula) structure(sapply(attr(terms(formula), "term.labels"), strsplit, ":"), class="modelTerms") -formula.modelTerms <- function(modelTerms, env = parent.frame()) { - # Converts a modelTerms list into a one-side R formula - # - # Args: - # modelTerms: A list of interaction terms, each term being a list of variable names involved in the interaction - # env: An environement associated with the variables in the formula, see ?as.formula - # - # Value: - # A formula. See ?formula - # - terms = sapply(modelTerms, function(x) paste0(unlist(x), collapse = ":")) - terms = terms[terms != ""] - formula.rhs = paste(terms, collapse = " + ") - if (formula.rhs != "") as.formula(paste(" ~ ", formula.rhs), env = env) + return(message) } diff --git a/R/classicalmetaanalysismultilevelmultivariate.R b/R/classicalmetaanalysismultilevelmultivariate.R new file mode 100644 index 00000000..4d40a18b --- /dev/null +++ b/R/classicalmetaanalysismultilevelmultivariate.R @@ -0,0 +1,941 @@ +# +# Copyright (C) 2013-2018 University of Amsterdam +# +# This program is free software: you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation, either version 2 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with this program. If not, see . +# + + +ClassicalMetaAnalysisMultilevelMultivariate <- function(jaspResults, dataset = NULL, options, ...) { + + options[["module"]] <- "metaAnalysisMultilevelMultivariate" + + if (.maReady(options)) { + dataset <- .mammCheckData(dataset, options) + .mammCheckErrors(dataset, options) + } + + .ClassicalMetaAnalysisCommon(jaspResults, dataset, options) + + return() +} + +.mammCheckData <- function(dataset, options) { + + # model data + predictorsNominal <- options[["predictors"]][options[["predictors.types"]] == "nominal"] + predictorsScale <- options[["predictors"]][options[["predictors.types"]] == "scale"] + + # random effects variables + randomVariables <- .mammExtractRandomVariableNames(options) + + # omit NAs + omitOnVariables <- c( + options[["effectSize"]], + options[["effectSizeStandardError"]], + unlist(randomVariables), + if (options[["clustering"]] != "") options[["clustering"]], + if (length(predictorsNominal) > 0) predictorsNominal, + if (length(predictorsScale) > 0) predictorsScale + ) + anyNaByRows <- apply(dataset[,omitOnVariables], 1, function(x) anyNA(x)) + dataset <- dataset[!anyNaByRows,] + attr(dataset, "NAs") <- sum(anyNaByRows) + + # add se^2 for V^2 input + dataset$samplingVariance <- dataset[[options[["effectSizeStandardError"]]]]^2 + + return(dataset) +} +.mammCheckErrors <- function(dataset, options) { + + randomVariables <- .mammExtractRandomVariableNames(options) + + .hasErrors( + dataset = dataset, + type = c("infinity", "observations", "variance"), + all.target = c( + options[["effectSize"]], + options[["effectSizeStandardError"]], + options[["predictors"]][options[["predictors.types"]] == "scale"], + c(randomVariables$scale, randomVariables$ordinal) + ), + observations.amount = "< 2", + exitAnalysisIfErrors = TRUE) + + .hasErrors( + dataset = dataset, + type = c("modelInteractions"), + modelInteractions.modelTerms = options[["effectSizeModelTerms"]], + exitAnalysisIfErrors = TRUE) + + .hasErrors( + dataset = dataset, + seCheck.target = options[["effectSizeStandardError"]], + custom = .maCheckStandardErrors, + exitAnalysisIfErrors = TRUE) +} +.mammGetRandomFormulaList <- function(options) { + + if (length(options[["randomEffects"]]) == 0) + return(NULL) + + # extract the random effects + randomFormulas <- list() + for (i in seq_along(options[["randomEffects"]])) { + + tempType <- options[["randomEffects"]][[i]][["type"]] + + if (tempType == "simple") { + + tempValue <- options[["randomEffectsSpecification"]][[i]][["groupingFactor"]] + + if (tempValue != "") { + randomFormulas[[i]] <- as.formula(paste0("~ 1 | ", tempValue), env = parent.frame(1)) + } + + } else if (tempType == "nested") { + + tempValues <- c( + options[["randomEffectsSpecification"]][[i]][["level1"]], + options[["randomEffectsSpecification"]][[i]][["level2"]], + options[["randomEffectsSpecification"]][[i]][["level3"]], + options[["randomEffectsSpecification"]][[i]][["level4"]], + options[["randomEffectsSpecification"]][[i]][["level5"]] + ) + tempValues <- tempValues[tempValues != ""] + + if (length(tempValues) > 0) { + randomFormulas[[i]] <- as.formula(paste0("~ 1 | ", paste(tempValues, collapse = "/")), env = parent.frame(1)) + } + + } else if (tempType == "randomSlopes") { + + tempValuesSlopes <- unlist(options[["randomEffectsSpecification"]][[i]][["randomSlopeTerms"]]) + tempValueGrouping <- options[["randomEffectsSpecification"]][[i]][["groupingFactor"]] + + if (length(tempValuesSlopes) > 0 && tempValueGrouping != "") { + randomFormulas[[i]] <- as.formula(paste0("~ ", paste(tempValuesSlopes, collapse = "+")," | ", tempValueGrouping), env = parent.frame(1)) + attr(randomFormulas[[i]], "structure") <- "GEN" + } + + } else if (tempType %in% c("structured", "autoregressive")) { + + tempValueInner <- switch( + tempType, + "structured" = options[["randomEffectsSpecification"]][[i]][["factorLevels"]], + "autoregressive" = options[["randomEffectsSpecification"]][[i]][["time"]] + ) + tempValueOuter <- options[["randomEffectsSpecification"]][[i]][["groupingFactor"]] + + if (tempValueInner != "" && tempValueOuter != "") { + randomFormulas[[i]] <- as.formula(paste0("~ ", tempValueInner, " | ", tempValueOuter), env = parent.frame(1)) + attr(randomFormulas[[i]], "structure") <- .mammGetStructureOptions(options[["randomEffects"]][[i]][["structure"]]) + } + + } else if (tempType == "spatial") { + + tempDistanceMetric <- .mammGetDistanceOptions(options[["randomEffectsSpecification"]][[i]][["distanceMetric"]]) + + if (tempDistanceMetric != "loadFromFile") { + + # dispatch distance type + if (tempDistanceMetric == "gcd") { + tempValueInner <- c( + if (options[["randomEffectsSpecification"]][[i]][["longitude"]] != "") options[["randomEffectsSpecification"]][[i]][["longitude"]], + if (options[["randomEffectsSpecification"]][[i]][["latitude"]] != "") options[["randomEffectsSpecification"]][[i]][["latitude"]] + ) + } else { + tempValueInner <- unlist(options[["randomEffectsSpecification"]][[i]][["spatialCoordinates"]]) + } + + tempValueOuter <- options[["randomEffectsSpecification"]][[i]][["groupingFactor"]] + + # spatial does not require a grouping factor + if (tempValueOuter == "") + tempValueOuter <- "constant" + + if ((tempDistanceMetric == "gcd" && length(tempValueInner) == 2) || (tempDistanceMetric != "gcd" && length(tempValueInner) > 0)) { + randomFormulas[[i]] <- as.formula(paste0("~ ", paste(tempValueInner, collapse = "+")," | ", tempValueOuter), env = parent.frame(1)) + attr(randomFormulas[[i]], "structure") <- .mammGetStructureOptions(options[["randomEffects"]][[i]][["structure"]]) + attr(randomFormulas[[i]], "dist") <- tempDistanceMetric + attr(randomFormulas[[i]], "addConstant") <- tempValueOuter == "constant" + } + + } else { + + # requires the inner term, the matrix needs to be a row & columns named file + tempValueInner <- options[["randomEffectsSpecification"]][[i]][["locationIdentifier"]] + distanceMatrixFileName <- options[["randomEffectsSpecification"]][[i]][["distanceMatrixFile"]] + + if (distanceMatrixFileName != "" && tempValueInner != "") { + + # try regular csv loading + distanceMatrix <- try(as.matrix(read.csv(file = distanceMatrixFileName, row.names = 1))) + + if (inherits(distanceMatrix, "try-error")) + .quitAnalysis(gettextf("Error reading the distance matrix file: %1$s", distanceMatrix)) + + # if there is only one column, try csv2 (indicates different decimals enconding) + if (ncol(distanceMatrix) == 1) + distanceMatrix <- try(as.matrix(read.csv2(file = distanceMatrixFileName, row.names = 1))) + + if (inherits(distanceMatrix, "try-error")) + .quitAnalysis(gettextf("Error reading the distance matrix file: %1$s", distanceMatrix)) + + if (nrow(distanceMatrix) != ncol(distanceMatrix)) + .quitAnalysis(gettext("The distance matrix must be square. The number of rows (%1$i) does not match the number of columns (%2$i).", + nrow(distanceMatrix), ncol(distanceMatrix))) + + # spatial does not require a grouping factor + tempValueOuter <- options[["randomEffectsSpecification"]][[i]][["groupingFactor"]] + if (tempValueOuter == "") + tempValueOuter <- "constant" + + randomFormulas[[i]] <- as.formula(paste0("~ ", tempValueInner, " | ", tempValueOuter), env = parent.frame(1)) + attr(randomFormulas[[i]], "structure") <- .mammGetStructureOptions(options[["randomEffects"]][[i]][["structure"]]) + attr(randomFormulas[[i]], "dist") <- list(distanceMatrix) + names(attr(randomFormulas[[i]], "dist")) <- tempValueInner + attr(randomFormulas[[i]], "addConstant") <- tempValueOuter == "constant" + + } + } + + } else if (tempType == "knownCorrelation") { + + # requires the outer term, the matrix needs to be a row & columns named file + tempValueOuter <- options[["randomEffectsSpecification"]][[i]][["groupingFactor"]] + distanceMatrixFileName <- options[["randomEffectsSpecification"]][[i]][["correlationMatrixFile"]] + if (tempValueOuter != "" && distanceMatrixFileName != "") { + # try regular csv loading + correlationMatrix <- try(as.matrix(read.csv(file = distanceMatrixFileName, row.names = 1))) + + if (inherits(correlationMatrix, "try-error")) + .quitAnalysis(gettextf("Error reading the correlation matrix file: %1$s", correlationMatrix)) + + # if there is only one column, try csv2 (indicates different decimals encoding) + if (ncol(correlationMatrix) == 1) + correlationMatrix <- try(as.matrix(read.csv2(file = distanceMatrixFileName, row.names = 1))) + + if (inherits(correlationMatrix, "try-error")) + .quitAnalysis(gettextf("Error reading the correlation matrix file: %1$s", correlationMatrix)) + + if (nrow(correlationMatrix) != ncol(correlationMatrix)) + .quitAnalysis(gettext("The distance matrix must be square. The number of rows (%1$i) does not match the number of columns (%2$i).", + nrow(correlationMatrix), ncol(correlationMatrix))) + + randomFormulas[[i]] <- as.formula(paste0("~ 1 | ", tempValueOuter), env = parent.frame(1)) + attr(randomFormulas[[i]], "R") <- list(correlationMatrix) + names(attr(randomFormulas[[i]], "R")) <- tempValueOuter + } + } + } + + randomFormulasSkipped <- sapply(randomFormulas, is.null) + + if (all(randomFormulasSkipped)) + return(NULL) + + randomFormulas <- randomFormulas[!randomFormulasSkipped] + # add missing null elements in case the last random effects was skipped + if (length(options[["randomEffectsSpecification"]]) > length(randomFormulasSkipped)) + randomFormulasSkipped[(length(randomFormulasSkipped)+1):length(options[["randomEffectsSpecification"]])] <- TRUE + attr(randomFormulas, "skipped") <- randomFormulasSkipped + names(randomFormulas) <- paste("Component", seq_along(randomFormulas)) + + return(randomFormulas) +} +.mammExtractRandomVariableNames <- function(options) { + + if (length(options[["randomEffects"]]) == 0) + return(NULL) + + # extract the random effects + variablesNominal <- NULL + variablesOrdinal <- NULL + variablesScale <- NULL + + for (i in seq_along(options[["randomEffects"]])) { + + tempType <- options[["randomEffects"]][[i]][["type"]] + + if (tempType == "simple") { + + variablesNominal <- c(variablesNominal, options[["randomEffectsSpecification"]][[i]][["groupingFactor"]]) + + } else if (tempType == "nested") { + + variablesNominal <- c( + variablesNominal, + options[["randomEffectsSpecification"]][[i]][["level1"]], + options[["randomEffectsSpecification"]][[i]][["level2"]], + options[["randomEffectsSpecification"]][[i]][["level3"]], + options[["randomEffectsSpecification"]][[i]][["level4"]], + options[["randomEffectsSpecification"]][[i]][["level5"]] + ) + + } else if (tempType == "randomSlopes") { + + tempValuesSlopes <- unlist(options[["randomEffectsSpecification"]][[i]][["randomSlopeTerms"]]) + tempValuesSlopesTypes <- options[["randomEffectsSpecification"]][[i]][["randomSlopeTerms.types"]] + + variablesNominal <- c(variablesNominal, tempValuesSlopes[tempValuesSlopesTypes == "nominal"]) + variablesScale <- c(variablesScale, tempValuesSlopes[tempValuesSlopesTypes == "scale"]) + variablesNominal <- c(variablesNominal, options[["randomEffectsSpecification"]][[i]][["groupingFactor"]]) + + } else if (tempType == "structured") { + + variablesNominal <- c( + variablesNominal, + options[["randomEffectsSpecification"]][[i]][["factorLevels"]], + options[["randomEffectsSpecification"]][[i]][["groupingFactor"]] + ) + + }else if (tempType == "autoregressive") { + + if (options[["randomEffects"]][[i]][["structure"]] == "continuousTimeAr") { + variablesScale <- c(variablesScale, options[["randomEffectsSpecification"]][[i]][["time"]]) + } else { + variablesOrdinal <- c(variablesOrdinal, options[["randomEffectsSpecification"]][[i]][["time"]]) + } + variablesNominal <- c(variablesNominal, options[["randomEffectsSpecification"]][[i]][["groupingFactor"]]) + + } else if (tempType == "spatial") { + + variablesScale <- c(variablesScale, unlist(options[["randomEffectsSpecification"]][[i]][["spatialCoordinates"]]), + options[["randomEffectsSpecification"]][[i]][["longitude"]], + options[["randomEffectsSpecification"]][[i]][["latitude"]]) + variablesNominal <- c(variablesNominal, options[["randomEffectsSpecification"]][[i]][["groupingFactor"]], + options[["randomEffectsSpecification"]][[i]][["locationIdentifier"]]) + + } else if (tempType == "knownCorrelation") { + + variablesNominal <- c(variablesNominal, options[["randomEffectsSpecification"]][[i]][["groupingFactor"]]) + } + } + + variablesScale <- unique(variablesScale) + variablesNominal <- unique(variablesNominal) + variablesOrdinal <- unique(variablesOrdinal) + + variablesScale <- variablesScale[variablesScale != ""] + variablesNominal <- variablesNominal[variablesNominal != ""] + variablesOrdinal <- variablesOrdinal[variablesOrdinal != ""] + + return(list( + scale = if (length(variablesScale) != 0) variablesScale, + nominal = if (length(variablesNominal) != 0) variablesNominal, + ordinal = if (length(variablesOrdinal) != 0) variablesOrdinal + )) +} +.mammRandomEstimatesTable <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["randomEstimatesContainer"]])) + return() + + randomEstimatesContainer <- createJaspContainer(title = gettext("Random Effects / Model Stucture Summary")) + randomEstimatesContainer$dependOn(.maDependencies) + randomEstimatesContainer$position <- 2 + jaspResults[["randomEstimatesContainer"]] <- randomEstimatesContainer + + fit <- .maExtractFit(jaspResults, options) + + # stop on error + if (is.null(fit) || jaspBase::isTryError(fit) || !is.null(.maCheckIsPossibleOptions(options))) + return() + + ### create table for nested random effects + if (fit[["withS"]]) { + + containerS <- createJaspContainer(title = gettext("Simple / Nested Summary")) + containerS$position <- 1 + randomEstimatesContainer[["containerS"]] <- containerS + + tableS <- createJaspTable(title = gettext("Estimates")) + tableS$position <- 1 + + tableS$addColumnInfo(name = "factor", type = "string", title = "") + tableS$addColumnInfo(name = "sigma2", type = "number", title = gettext("\U03C3\U00B2")) + tableS$addColumnInfo(name = "sigma", type = "number", title = gettext("\U03C3")) + tableS$addColumnInfo(name = "nlvls", type = "integer", title = gettext("Levels")) + if (.mammAddIsFixedRandom(options, 3)) + tableS$addColumnInfo(name = "fixed", type = "string", title = gettext("Fixed")) + + # tableS$addColumnInfo(name = "R", type = "string", title = gettext("R")) # whether supplied via known correlation matrix + containerS[["tableS"]] <- tableS + + resultsS <- data.frame( + factor = .maVariableNames(fit[["s.names"]], unlist(.mammExtractRandomVariableNames(options))), + sigma = sqrt(fit[["sigma2"]]), + sigma2 = fit[["sigma2"]], + nlvls = fit[["s.nlevels"]], + fixed = ifelse(fit[["vc.fix"]]$sigma2, "yes", "no") + # R = ifelse(fit[["Rfix"]] , "yes", "no") + ) + + if (!.mammAddIsFixedRandom(options, indx)) + resultsS <- resultsS[,colnames(resultsS) != "fixed", drop = FALSE] + + tableS$setData(resultsS) + } + + ### create summary for the remaining types + if (fit[["withG"]]) { + + # create jasp containers + containerG <- createJaspContainer(title = .mammGetRandomEstimatesTitle(fit[["struct"]][1])) + containerG$position <- 2 + randomEstimatesContainer[["containerG"]] <- containerG + .mammExtractRandomTables(containerG, options, fit, indx = 1) + + } + + if (fit[["withH"]]) { + + containerH <- createJaspContainer(title = .mammGetRandomEstimatesTitle(fit[["struct"]][2])) + containerH$position <- 3 + randomEstimatesContainer[["containerH"]] <- containerH + .mammExtractRandomTables(containerH, options, fit, indx = 2) + + } + + ### create random structure inclusion summary + if (options[["randomEffectsTestInclusion"]]) { + + tableInclusion <- createJaspTable(title = gettext("Inclusion Test")) + tableInclusion$position <- 4 + tableInclusion$dependOn("randomEffectsTestInclusion") + randomEstimatesContainer[["tableInclusion"]] <- tableInclusion + + tableInclusion$addColumnInfo(name = "model", title = gettext("Removed Component"), type = "string") + tableInclusion$addColumnInfo(name = "logLik", title = gettext("Log Lik."), type = "number") + tableInclusion$addColumnInfo(name = "df", title = gettext("df"), type = "integer") + tableInclusion$addColumnInfo(name = "AIC", title = gettext("AIC"), type = "number") + tableInclusion$addColumnInfo(name = "BIC", title = gettext("BIC"), type = "number") + tableInclusion$addColumnInfo(name = "AICc", title = gettext("AICc"), type = "number") + tableInclusion$addColumnInfo(name = "LRT", title = gettext("LRT"), type = "number") + tableInclusion$addColumnInfo(name = "pval", title = gettext("p"), type = "pvalue") + + dropOneFits <- .mammFitDropOneRandom(jaspResults, options) + + if (length(dropOneFits) == 0) + return() + + fit <- .maExtractFit(jaspResults, options) + fitTests <- lapply(dropOneFits, function(fitB) data.frame(anova(fit, fitB))) + fitTests <- rbind( + cbind(model = "", fitTests[[1]][1,]), + cbind(model = names(fitTests), do.call(rbind, lapply(fitTests, function(fitTest) fitTest[2,]))) + ) + + fitTests <- fitTests[,!colnames(fitTests) %in% "QE"] + tableInclusion$setData(fitTests) + tableInclusion$addFootnote(gettext("Likelihood Ratio Test (LRT) and p-value are based on a comparison with the complete model.")) + } + + return() +} +.mammGetRandomEstimatesTitle <- function(structure) { + + if (structure == "GEN") + return(gettext("Random Slopes Summary")) + else if (structure %in% c("CS", "HCS", "UN", "ID", "DIAG")) + return(paste0(gettext("Structured"), " (", .mammGetOptionsNameStructure(structure), ") ", gettext("Summary"))) + else if (structure %in% c("AR", "HAR", "CAR")) + return(paste0(gettext("Autoregressive"), " (", .mammGetOptionsNameStructure(structure), ") ", gettext("Summary"))) + else if (structure %in% c("SPEXP", "SPGAU", "SPLIN", "SPRAT", "SPSPH")) + return(paste0(gettext("Spatial"), " (", .mammGetOptionsNameStructure(structure), ") ", gettext("Summary"))) + else + return(gettext("Known Correlation Summary")) +} +.mammFitDropOneRandom <- function(jaspResults, options) { + + if (!is.null(jaspResults[["dropOneFits"]])) + return(jaspResults[["dropOneFits"]]$object) + + dropOneFitsContainer <- createJaspState() + dropOneFitsContainer$dependOn(.maDependencies) + jaspResults[["dropOneFits"]] <- dropOneFitsContainer + + fit <- .maExtractFit(jaspResults, options) + + # create list of all structures + randomFormulaLists <- .mammGetRandomFormulaList(options) + dropOneFits <- vector("list", length = length(randomFormulaLists)) + names(dropOneFits) <- names(randomFormulaLists) + + startProgressbar(expectedTicks = length(randomFormulaLists), label = gettext("Testing Inclusion of Random Effects / Model Structure")) + + # perform drop one re-estimation + for (i in seq_along(randomFormulaLists)) { + + randomFormulaList <- randomFormulaLists[-i] + randomFormulaList <- unname(randomFormulaList) + + random <- NULL + struct <- NULL + dist <- NULL + R <- NULL + + if (length(randomFormulaList) != 0) { + random <- randomFormulaList + struct <- do.call(c, lapply(randomFormulaList, attr, which = "structure")) + dist <- unlist(lapply(randomFormulaList, attr, which = "dist"), recursive = FALSE) + R <- unlist(lapply(randomFormulaList, attr, which = "R"), recursive = FALSE) + } + + # set default struct if unspecified + if (is.null(struct)) + struct <- "CS" + + tempFit <- try(update(fit, random = random, struct = struct, dist = dist, R = R)) + + dropOneFits[[i]] <- tempFit + progressbarTick() + } + + dropOneFitsContainer$object <- dropOneFits + return(dropOneFits) +} +.mammGetStructureOptions <- function(structure) { + + return(switch( + structure, + "compoundSymmetry" = "CS", + "heteroscedasticCompoundSymmetry" = "HCS", + "unstructured" = "UN", + "identity" = "ID", + "diagonal" = "DIAG", + "ar1" = "AR", + "heteroskedasticAr1" = "HAR", + "continuousTimeAr" = "CAR", + "exponential" = "SPEXP", + "gaussian" = "SPGAU", + "linear" = "SPLIN", + "rationalQuadratic" = "SPRAT", + "spherical" = "SPSPH", + stop(paste0("Unknown structure: ", structure)) + )) +} +.mammGetOptionsNameStructure <- function(structure) { + + return(switch( + structure, + "GEN" = gettextf("Random Slopes"), + "CS" = gettextf("Compound Symmetry"), + "HCS" = gettextf("Heteroscedastic Compound Symmetry"), + "UN" = gettextf("Unstructured"), + "ID" = gettextf("Identity"), + "DIAG" = gettextf("Diagonal"), + "AR" = gettextf("AR(1)"), + "HAR" = gettextf("Heteroskedastic AR(1)"), + "CAR" = gettextf("Continuous-Time AR"), + "SPEXP" = gettextf("Exponential"), + "SPGAU" = gettextf("Gaussian"), + "SPLIN" = gettextf("Linear"), + "SPRAT" = gettextf("Rational Quadratic"), + "SPSPH" = gettextf("Spherical"), + stop(paste0("Unknown value: ", structure)) + )) +} +.mammGetDistanceOptions <- function(distance) { + + return(switch( + distance, + "euclidean" = "euclidean", + "manhattan" = "manhattan", + "maximum" = "maximum", + "greatCircle" = "gcd", + "loadFromFile" = "loadFromFile", + stop(paste0("Unknown value: ", distance)) + )) +} +.mammAnyStructureGen <- function(options) { + # only relevant for multivariate + if (options[["module"]] != "metaAnalysisMultilevelMultivariate") + return(FALSE) + + # get all the active components types + randomFormulaList <- .mammGetRandomFormulaList(options) + if (length(randomFormulaList) == 0) + return(FALSE) + + structures <- unlist(lapply(randomFormulaList, attr, which = "structure")) + + return(any(structures %in% "GEN")) +} +.mammHasMultipleHeterogeneities <- function(options, canAddOutput = FALSE) { + # only relevant for multivariate + if (options[["module"]] != "metaAnalysisMultilevelMultivariate") + return(FALSE) + + # get all the active components types + randomFormulaList <- .mammGetRandomFormulaList(options) + if (length(randomFormulaList) == 0) + return(FALSE) + + structures <- unlist(lapply(randomFormulaList, attr, which = "structure")) + + if (canAddOutput) + return(any(structures %in% c("HCS", "UN", "DIAG", "HAR")) && !any(structures %in% "GEN")) + else + return(any(structures %in% c("GEN", "HCS", "UN", "DIAG", "HAR"))) +} +.mammExtractTauLevelNames <- function(fit) { + + levelNames <- c() + + if (fit[["withG"]] && fit[["struct"]][1] %in% c("HCS", "UN", "DIAG", "HAR")) + levelNames <- c(levelNames, fit$g.names[[1]]) + + if (fit[["withH"]] && fit[["struct"]][2] %in% c("HCS", "UN", "DIAG", "HAR")) + levelNames <- c(levelNames, fit$h.names[[1]]) + + return(levelNames) +} +.mammExtractTauLevels <- function(fit, expanded = TRUE) { + + levels <- list() + + if (fit[["withG"]] && fit[["struct"]][1] %in% c("HCS", "UN", "DIAG", "HAR")) + levels[["tau2.levels"]] <- fit$g.levels.f[[1]] + + if (fit[["withH"]] && fit[["struct"]][2] %in% c("HCS", "UN", "DIAG", "HAR")) + levels[["gamma2.levels"]] <- fit$h.levels.f[[1]] + + if (expanded) + levels <- expand.grid(levels) + else + levels <- do.call(cbind.data.frame, levels) + + return(levels) +} +.mammExtractRandomTables <- function(tempContainer, options, x, indx = 1) { + + # dispatching + struct <- x$struct[indx] + + tau2 <- if (indx == 1) x[["tau2"]] else x[["gamma2"]] + tau <- sqrt(tau2) + rho <- if (indx == 1) x[["rho"]] else x[["phi"]] + + tau2Name <- if (indx == 1) "tau2" else "gamma2" + rhoName <- if (indx == 1) "rho" else "phi" + + GName <- if (indx == 1) "G" else "H" + g.levels.kName <- if (indx == 1) "g.levels.k" else "h.levels.k" + g.levels.fName <- if (indx == 1) "g.levels.f" else "h.levels.f" + g.nlevels.kName <- if (indx == 1) "g.nlevels.k" else "h.nlevels.k" + g.nlevels.fName <- if (indx == 1) "g.nlevels.f" else "h.nlevels.f" + g.levels.comb.kName <- if (indx == 1) "g.levels.comb.k" else "h.levels.comb.k" + g.nlevelsName <- if (indx == 1) "g.nlevels" else "h.nlevels" + g.namesName <- if (indx == 1) "g.names" else "h.names" + + + # create information messages + if (is.element(struct, c("SPEXP", "SPGAU", "SPLIN", "SPRAT", "SPSPH", "PHYBM", "PHYPL", "PHYPD", "GEN", "GDIAG"))) { + inner <- trimws(paste0(strsplit(paste0(x$formulas[[indx]], collapse = ""), "|", fixed = TRUE)[[1]][1], collapse = "")) + } else { + inner <- x[[g.namesName]][1] + } + outer <- tail(x[[g.namesName]], 1) + innerLvl <- x[[g.nlevels.fName]][1] + outerLvl <- x[[g.nlevelsName]][2] + + message1 <- paste0(x[[g.nlevels.fName]][1], " | ", outerLvl) + message2 <- paste0(inner, " | ", outer) + + if (is.element(struct, c("CS", "AR", "CAR", "ID", "SPEXP", "SPGAU", "SPLIN", "SPRAT", "SPSPH", "PHYBM", "PHYPL", "PHYPD"))) { + + vc <- cbind(tau2, tau, ifelse(x$vc.fix[[tau2Name]], "yes", "no")) + vc <- rbind(vc, c(rho, "", ifelse(x$vc.fix[[rhoName]], "yes", "no"))) + + vc <- data.frame(vc) + colnames(vc) <- c("estimate", "estimateSqrt", "fixed") + vc$parameter <- c("\U1D70F\U00B2", "\U03C1") + for(colName in c("estimate", "estimateSqrt")) { + vc[,colName] <- as.numeric(vc[,colName]) + } + + if (struct == "ID") { + vc <- vc[1, , drop = FALSE] + } + + if (!.mammAddIsFixedRandom(options, indx)) + vc <- vc[,colnames(vc) != "fixed", drop = FALSE] + + tempTable <- createJaspTable(title = gettext("Estimates")) + tempTable$position <- 1 + tempTable$addColumnInfo(name = "parameter", type = "string", title = "") + tempTable$addColumnInfo(name = "estimate", type = "number", title = gettext("Estimate")) + tempTable$addColumnInfo(name = "estimateSqrt", type = "number", title = gettext("Sqrt. Estimate")) + if (.mammAddIsFixedRandom(options, indx)) + tempTable$addColumnInfo(name = "fixed", type = "string", title = gettext("Fixed")) + tempContainer[["table1"]] <- tempTable + + tempTable$setData(vc) + tempTable$addFootnote(message1, symbol = gettext("Levels: ")) + tempTable$addFootnote(message2, symbol = gettext("Component: ")) + + } + + if (is.element(struct, c("HCS", "HAR", "DIAG"))) { + + vc <- cbind(tau2, tau, x[[g.levels.kName]], ifelse(x$vc.fix$tau2, "yes", "no"), x[[g.levels.fName]][[1]]) + vc <- rbind(vc, c(rho, "", "", ifelse(x$vc.fix[[rhoName]], "yes", "no"), "")) + + vc <- data.frame(vc) + colnames(vc) <- c("estimate", "estimateSqrt", "nLevels", "fixed", "level") + for(colName in c("estimate", "estimateSqrt", "nLevels")) { + vc[,colName] <- as.numeric(vc[,colName]) + } + + if (length(x[[tau2Name]]) == 1L) { + vc$parameter <- c("\U1D70F\U00B2", "\U03C1") + } else { + vc$parameter <- c(paste0("\U1D70F\U00B2[",seq_along(x[[tau2Name]]),"]"), "\U03C1") + } + + if (struct == "DIAG") + vc <- vc[seq_along(tau2), , drop = FALSE] + + if (!.mammAddIsFixedRandom(options, indx)) + vc <- vc[,colnames(vc) != "fixed", drop = FALSE] + + tempTable <- createJaspTable(title = gettext("Estimates")) + tempTable$position <- 1 + tempTable$addColumnInfo(name = "parameter", type = "string", title = "") + tempTable$addColumnInfo(name = "level", type = "string", title = gettext("Level")) + tempTable$addColumnInfo(name = "estimate", type = "number", title = gettext("Estimate")) + tempTable$addColumnInfo(name = "estimateSqrt", type = "number", title = gettext("Sqrt. Estimate")) + tempTable$addColumnInfo(name = "nLevels", type = "integer", title = gettext("Levels")) + if (.mammAddIsFixedRandom(options, indx)) + tempTable$addColumnInfo(name = "fixed", type = "string", title = gettext("Fixed")) + + tempTable$setData(vc) + tempTable$addFootnote(message1, symbol = gettext("Levels: ")) + tempTable$addFootnote(message2, symbol = gettext("Component: ")) + tempContainer[["table1"]] <- tempTable + + } + + if (is.element(struct, c("UN", "UNR"))) { + + if (struct == "UN") { + vc <- cbind(tau2, tau, x[[g.levels.kName]], ifelse(x$vc.fix[[tau2Name]], "yes", "no"), x[[g.levels.fName]][[1]]) + } else { + vc <- cbind(rep(tau2, length(x[[g.levels.kName]])), + rep(tau, length(x[[g.levels.kName]])), x[[g.levels.kName]], + ifelse(rep(x$vc.fix[[tau2Name]], length(x[[g.levels.kName]])), "yes", "no"), + x[[g.levels.fName]][[1]]) + } + vc <- data.frame(vc) + colnames(vc) <- c("estimate", "estimateSqrt", "nLevels", "fixed", "level") + for(colName in c("estimate", "estimateSqrt", "nLevels")) { + vc[,colName] <- as.numeric(vc[,colName]) + } + + if (length(x[[g.levels.kName]]) == 1L) { + vc$parameter <- c("\U1D70F\U00B2") + } else { + vc$parameter <-paste0("\U1D70F\U00B2[",seq_along(x[[g.levels.kName]]),"]") + } + + if (!.mammAddIsFixedRandom(options, indx)) + vc <- vc[,colnames(vc) != "fixed", drop = FALSE] + + tempTable <- createJaspTable(title = gettext("Estimates \U1D70F\U00B2")) + tempTable$position <- 1 + tempTable$addColumnInfo(name = "parameter", type = "string", title = "") + tempTable$addColumnInfo(name = "level", type = "string", title = gettext("Level")) + tempTable$addColumnInfo(name = "estimate", type = "number", title = gettext("Estimate")) + tempTable$addColumnInfo(name = "estimateSqrt", type = "number", title = gettext("Sqrt. Estimate")) + tempTable$addColumnInfo(name = "nLevels", type = "string", title = gettext("Levels")) + if (.mammAddIsFixedRandom(options, indx)) + tempTable$addColumnInfo(name = "fixed", type = "string", title = gettext("Fixed")) + + tempTable$setData(vc) + tempTable$addFootnote(message1, symbol = gettext("Levels: ")) + tempTable$addFootnote(message2, symbol = gettext("Component: ")) + tempContainer[["table1"]] <- tempTable + + + if (length(x[[rhoName]]) == 1L) { + G <- matrix(NA_real_, nrow = 2, ncol = 2) + } else { + G <- matrix(NA_real_, nrow = x[[g.nlevels.fName]][1], ncol = x[[g.nlevels.fName]][1]) + } + + G[lower.tri(G)] <- rho + G[upper.tri(G)] <- t(G)[upper.tri(G)] + diag(G) <- 1 + G[upper.tri(G)] <- NA + + G <- data.frame(G) + colnames(G) <- paste0("rho", 1:(ncol(G))) + G$parameter <- sprintf("\U03C1[%1$i,]", 1:nrow(G)) + + + if (length(x$rho) == 1L) { + G.info <- matrix(NA_real_, nrow = 2, ncol = 2) + } else { + G.info <- matrix(NA_real_, nrow = x[[g.nlevels.fName]][1], ncol = x[[g.nlevels.fName]][1]) + } + G.infoLevels <- G.info + G.infoLevels[lower.tri(G.infoLevels)] <- x[[g.levels.comb.kName]] + G.infoLevels[upper.tri(G.infoLevels)] <- t(G.infoLevels)[upper.tri(G.infoLevels)] + G.infoLevels[lower.tri(G.infoLevels)] <- NA + diag(G.infoLevels) <- NA + + G.infoLevels <- data.frame(G.infoLevels) + colnames(G.infoLevels) <- paste0("rhoLevel", 1:ncol(G.infoLevels)) + + G.infoEstimated <- G.info + G.infoEstimated[upper.tri(G.infoEstimated)] <- ifelse(x$vc.fix[[rhoName]], "yes", "no") + + G.infoEstimated <- data.frame(G.infoEstimated) + colnames(G.infoEstimated) <- paste0("rhoEstimated", 1:ncol(G.infoEstimated)) + + if (!.mammAddIsFixedRandom(options, indx)) + Gmat <- cbind(G, G.infoLevels) + else + Gmat <- cbind(G, G.infoLevels, G.infoEstimated) + + tempTable2 <- createJaspTable(title = gettext("Estimates \U03C1")) + tempTable2$position <- 2 + tempTable2$addColumnInfo(name = "parameter", type = "string", title = "") + for(i in 1:ncol(G)){ + tempTable2$addColumnInfo(name = paste0("rho",i), type = "number", title = sprintf("[,%1$i]", i), overtitle = gettext("Estimates")) + } + for(i in 1:ncol(G.infoLevels)){ + tempTable2$addColumnInfo(name = paste0("rhoLevel",i), type = "integer", title = sprintf("[,%1$i]", i), overtitle = gettext("Levels")) + } + if (.mammAddIsFixedRandom(options, indx)) { + for(i in 1:ncol(G.infoEstimated)){ + tempTable2$addColumnInfo(name = paste0("rhoEstimated",i), type = "string", title = sprintf("[,%1$i]", i), overtitle = gettext("Fixed")) + } + } + + tempTable2$setData(Gmat) + tempTable2$addFootnote(message1, symbol = gettext("Levels: ")) + tempTable2$addFootnote(message2, symbol = gettext("Component: ")) + tempContainer[["table2"]] <- tempTable2 + } + + if (is.element(struct, c("GEN"))) { + + vc <- cbind(tau2, tau, ifelse(x$vc.fix[[tau2Name]], "yes", "no")) + + vc <- data.frame(vc) + colnames(vc) <- c("estimate", "estimateSqrt", "fixed") + vc$parameter <- .maVariableNames(x[[g.namesName]][-length(x[[g.namesName]])], unlist(.mammExtractRandomVariableNames(options))) + for(colName in c("estimate", "estimateSqrt")) { + vc[,colName] <- as.numeric(vc[,colName]) + } + + if (!.mammAddIsFixedRandom(options, indx)) + vc <- vc[,colnames(vc) != "fixed", drop = FALSE] + + tempTable <- createJaspTable(title = gettext("Estimates \U1D70F\U00B2")) + tempTable$position <- 1 + tempTable$addColumnInfo(name = "parameter", type = "string", title = "") + tempTable$addColumnInfo(name = "estimate", type = "number", title = gettext("Estimate")) + tempTable$addColumnInfo(name = "estimateSqrt", type = "number", title = gettext("Sqrt. Estimate")) + if (.mammAddIsFixedRandom(options, indx)) + tempTable$addColumnInfo(name = "fixed", type = "string", title = gettext("Fixed")) + + tempTable$setData(vc) + tempTable$addFootnote(message1, symbol = gettext("Levels: ")) + tempTable$addFootnote(message2, symbol = gettext("Component: ")) + tempContainer[["table1"]] <- tempTable + + + G.info <- cov2cor(x[[GName]]) + diag(G.info) <- NA + G.info[upper.tri(G.info)] <- NA + + G.info <- data.frame(G.info) + colnames(G.info) <- paste0("rho", 1:ncol(G.info)) + + + G.infoFixed <- G.info + G.infoFixed[lower.tri(G.infoFixed)] <- NA + G.infoFixed[upper.tri(G.infoFixed)] <- ifelse(x$vc.fix[[rhoName]], "yes", "no") + + G.infoFixed <- data.frame(G.infoFixed) + colnames(G.infoFixed) <- paste0("rhoFixed", 1:ncol(G.infoFixed)) + + if (!.mammAddIsFixedRandom(options, indx)) + Gmat <- G.info + else + Gmat <- cbind(G.info, G.infoFixed) + + Gmat$parameter <- .maVariableNames(x[[g.namesName]][-length(x[[g.namesName]])], unlist(.mammExtractRandomVariableNames(options))) + + + tempTable2 <- createJaspTable(title = gettext("Estimates \U03C1")) + tempTable2$position <- 2 + tempTable2$addColumnInfo(name = "parameter", type = "string", title = "") + for(i in 1:ncol(G.info)){ + tempTable2$addColumnInfo(name = paste0("rho",i), type = "number", title = Gmat$parameter[i], overtitle = gettext("Estimates")) + } + if (.mammAddIsFixedRandom(options, indx)) { + for(i in 1:ncol(G.infoFixed)){ + tempTable2$addColumnInfo(name = paste0("rhoFixed",i), type = "string", title = Gmat$parameter[i], overtitle = gettext("Fixed")) + } + } + + tempTable2$setData(Gmat) + tempTable2$addFootnote(message1, symbol = gettext("Levels: ")) + tempTable2$addFootnote(message2, symbol = gettext("Component: ")) + tempContainer[["table2"]] <- tempTable2 + } + + if (is.element(struct, c("GDIAG"))) { + + vc <- cbind(tau2, tau, ifelse(x$vc.fix[["tau2"]], "yes", "no")) + + vc <- data.frame(vc) + colnames(vc) <- c("estimate", "estimateSqrt", "fixed") + vc$parameter <- .maVariableNames(x[[g.namesName]][-length(x[[g.namesName]])], unlist(.mammExtractRandomVariableNames(options))) + for(colName in c("estimate", "estimateSqrt")) { + vc[,colName] <- as.numeric(vc[,colName]) + } + + if (!.mammAddIsFixedRandom(options, indx)) + vc <- vc[,colnames(vc) != "fixed", drop = FALSE] + + tempTable <- createJaspTable(title = gettext("Estimates \U1D70F\U00B2")) + tempTable$position <- 1 + tempTable$addColumnInfo(name = "parameter", type = "string", title = "") + tempTable$addColumnInfo(name = "estimate", type = "number", title = gettext("Estimate")) + tempTable$addColumnInfo(name = "estimateSqrt", type = "number", title = gettext("Sqrt. Estimate")) + if (.mammAddIsFixedRandom(options, indx)) + tempTable$addColumnInfo(name = "fixed", type = "string", title = gettext("Fixed")) + + + tempTable$setData(vc) + tempTable$addFootnote(message1, symbol = gettext("Levels: ")) + tempTable$addFootnote(message2, symbol = gettext("Component: ")) + tempContainer[["table1"]] <- tempTable + } + + return() +} +.mammAddIsFixedRandom <- function(options, indx) { + + return(FALSE) + + # TODO: show / hide information on whether the random effects are fixed by the user +} + diff --git a/R/effectsizecomputation.R b/R/effectsizecomputation.R new file mode 100644 index 00000000..11add3b4 --- /dev/null +++ b/R/effectsizecomputation.R @@ -0,0 +1,900 @@ +# +# Copyright (C) 2013-2018 University of Amsterdam +# +# This program is free software: you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation, either version 2 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with this program. If not, see . +# + +EffectSizeComputation <- function(jaspResults, dataset, options, state = NULL) { + + # all input checking is done within the escalc function + # - error messages are cleaned and forwarded to the user + dataOutput <- .escComputeEffectSizes(dataset, options) + + .escComputeSummaryTable(jaspResults, dataset, options, dataOutput) + .escExportData(jaspResults, options, dataOutput) + + return() +} + +.escComputeEffectSizes <- function(dataset, options) { + + # proceed with the escal in order + dataOutput <- NULL + errors <- list() + for (i in seq_along(options[["variables"]])) { + + # subset the relevant options (need to be passed separately as there are names overlap in "effectSize") + effectSizeType <- options[["effectSizeType"]][[i]] + variables <- options[["variables"]][[i]] + + # skip on no input to the reported effect sizes (no error added) + if (effectSizeType[["design"]] == "reportedEffectSizes" && !.escReportedEffectSizesReady(variables, all = FALSE)) + next + + # set escalc input (allows to check whether at least something was specified) + tempDataOptions <- .escGetEscalcDataOptions(dataset, effectSizeType, variables) + + # skip on no input and don't set an error message + if (length(tempDataOptions) == 0) + next + + # set error message if reported effect sizes cannot be performed + if (effectSizeType[["design"]] == "reportedEffectSizes" && !.escReportedEffectSizesReady(variables, all = TRUE)) { + newDataOutput <- try(stop(gettext("Cannot compute outcomes. Chech that all of the required information is specified via the appropriate arguments (i.e. an Effect Size and either Standard Error, Sampling Variance, or 95% Confidence Interval)."))) + } else { + # set escalc input + escalcInput <- c( + tempDataOptions, + .escGetEscalcAdjustFrequenciesOptions(effectSizeType, variables), + .escGetEscalcVtypeOption(effectSizeType, variables), + measure = if (effectSizeType[["design"]] == "reportedEffectSizes") "GEN" else effectSizeType[["effectSize"]], + replace = i == 1, + add.measure = TRUE, + data = if (!is.null(dataOutput)) list(dataOutput) + ) + + newDataOutput <- try(do.call(metafor::escalc, escalcInput)) + } + + if (inherits(newDataOutput, "try-error")) { + errors[[paste0("i",i)]] <- list( + step = i, + error = .escCleanErrorMessage(attr(newDataOutput, "condition")$message, effectSizeType) + ) + } else { + + # keep track of computation steps + # (needs to be done manually as the same effect size can be specified multiple times...) + newDataOutput$step <- NA + newDataOutput[["step"]][!is.na(newDataOutput[["yi"]])] <- i + + if (is.null(dataOutput)) { + dataOutput <- newDataOutput + } else { + dataOutput[is.na(dataOutput[["yi"]]),] <- newDataOutput[is.na(dataOutput[["yi"]]),] + } + } + } + + # create an empty list if nothing was computed + if (is.null(dataOutput)) + dataOutput <- list() + + attr(dataOutput, "errors") <- errors + return(dataOutput) +} +.escComputeSummaryTable <- function(jaspResults, dataset, options, dataOutput) { + + # create summary table + computeSummary <- createJaspTable(title = gettext("Summary")) + computeSummary$dependOn(c("effectSizeType", "variables")) + computeSummary$position <- 1 + + jaspResults[["computeSummary"]] <- computeSummary + + computeSummary$addColumnInfo(name = "step", title = gettext("Step"), type = "integer") + computeSummary$addColumnInfo(name = "effectSize", title = gettext("Effect Size"), type = "string") + computeSummary$addColumnInfo(name = "computed", title = gettext("Computed"), type = "integer") + computeSummary$addColumnInfo(name = "totalComputed", title = gettext("Total Computed"), type = "integer") + + # compute summary + if (length(seq_along(options[["effectSizeType"]])) > 0) { + + computeSummaryData <- lapply(seq_along(options[["effectSizeType"]]), function(i) { + list("step" = i, "effectSize" = options[["effectSizeType"]][[i]][["effectSize"]], "computed" = sum(dataOutput[["step"]] == i, na.rm = TRUE)) + }) + computeSummaryData <- do.call(rbind.data.frame, computeSummaryData) + computeSummaryData$totalComputed <- cumsum(computeSummaryData$computed) + + # set the data + computeSummary$setData(computeSummaryData) + + if (nrow(dataset) == sum(computeSummaryData[["computed"]])) + computeSummary$addFootnote(gettext("Effect sizes were successfully computed for each data entry.")) + else + computeSummary$addFootnote(gettextf( + "Effect sizes were successfully computed for %1$i out of %2$i data entries.", + sum(computeSummaryData[["computed"]]), + nrow(dataset))) + } + + computeErrors <- attr(dataOutput, "errors") + for (i in seq_along(computeErrors)) { + computeSummary$addFootnote(computeErrors[[i]]$error, symbol = gettextf("Error in Step %1$i:", computeErrors[[i]]$step)) + } + + return() +} +.escExportData <- function(jaspResults, options, dataOutput) { + + if (length(dataOutput) == 0) + return() + + # columns to add + if (options[["computeSamplingVariance"]]) { + columnOptions <- c("computedColumnsNamesEffectSize", "computedcolumnsNamesSamplingVariance", "computedColumnsNamesEffectSizeType") + } else { + columnOptions <- c("computedColumnsNamesEffectSize", "computedcolumnsNamesStandardError", "computedColumnsNamesEffectSizeType") + } + + for (column in columnOptions) { + + columnName <- options[[column]] + + if (jaspBase:::columnExists(columnName) && !jaspBase:::columnIsMine(columnName)) + .quitAnalysis(gettextf("Column name %s already exists in the dataset.", columnName)) + + jaspResults[[column]] <- createJaspColumn(columnName = columnName, dependencies = c("effectSizeType", "variables", column)) + jaspResults[[column]]$setScale(switch( + column, + "computedColumnsNamesEffectSize" = dataOutput[["yi"]], + "computedcolumnsNamesStandardError" = sqrt(dataOutput[["vi"]]), + "computedcolumnsNamesSamplingVariance" = dataOutput[["vi"]], + "computedColumnsNamesEffectSizeType" = dataOutput[["measure"]] + )) + + } + + return() +} + +# functions for transforming input into metafor::escalc settings +.escGetEscalcDataOptions <- function(dataset, effectSizeType, variables) { + + design <- effectSizeType[["design"]] + measurement <- effectSizeType[["measurement"]] + effectSize <- effectSizeType[["effectSize"]] + + if (design == "independentGroups") { + if (measurement == "quantitative") { + if (effectSize == "SMD") { + inputs <- list( + m1i = dataset[[variables[["meanGroup1"]]]], + m2i = dataset[[variables[["meanGroup2"]]]], + sd1i = dataset[[variables[["sdGroup1"]]]], + sd2i = dataset[[variables[["sdGroup2"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]], + ti = dataset[[variables[["tStatistic"]]]], + pi = dataset[[variables[["pValue"]]]], + di = dataset[[variables[["cohensD"]]]] + ) + } else if (effectSize %in% c("SMD1", "SMDH1")) { + inputs <- list( + m1i = dataset[[variables[["meanGroup1"]]]], + m2i = dataset[[variables[["meanGroup2"]]]], + sd2i = dataset[[variables[["sdGroup2"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]] + ) + } else if (effectSize %in% c("CVR", "VR")) { + inputs <- list( + sd1i = dataset[[variables[["sdGroup1"]]]], + sd2i = dataset[[variables[["sdGroup2"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]] + ) + } else { + inputs <- list( + m1i = dataset[[variables[["meanGroup1"]]]], + m2i = dataset[[variables[["meanGroup2"]]]], + sd1i = dataset[[variables[["sdGroup1"]]]], + sd2i = dataset[[variables[["sdGroup2"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]] + ) + } + } else if (measurement == "binary") { + inputs <- list( + ai = dataset[[variables[["group1OutcomePlus"]]]], + bi = dataset[[variables[["group1OutcomeMinus"]]]], + ci = dataset[[variables[["group2OutcomePlus"]]]], + di = dataset[[variables[["group2OutcomeMinus"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]] + ) + } else if (measurement == "countsPerTime") { + inputs <- list( + t1i = dataset[[variables[["personTimeGroup1"]]]], + t2i = dataset[[variables[["personTimeGroup2"]]]], + x1i = dataset[[variables[["eventsGroup1"]]]], + x2i = dataset[[variables[["eventsGroup2"]]]] + ) + } else if (measurement == "mixed") { + if (effectSize %in% c("D2ORN", "D2ORL")) { + inputs <- list( + m1i = dataset[[variables[["meanGroup1"]]]], + m2i = dataset[[variables[["meanGroup2"]]]], + sd1i = dataset[[variables[["sdGroup1"]]]], + sd2i = dataset[[variables[["sdGroup2"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]], + ti = dataset[[variables[["tStatistic"]]]], + pi = dataset[[variables[["pValue"]]]], + di = dataset[[variables[["cohensD"]]]] + ) + } else if (effectSize %in% c("PBIT", "OR2DN", "OR2DL")) { + inputs <- list( + ai = dataset[[variables[["group1OutcomePlus"]]]], + bi = dataset[[variables[["group1OutcomeMinus"]]]], + ci = dataset[[variables[["group2OutcomePlus"]]]], + di = dataset[[variables[["group2OutcomeMinus"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]] + ) + } + } + } else if (design == "variableAssociation") { + if (measurement == "quantitative") { + inputs <- list( + ri = dataset[[variables[["correlation"]]]], + ni = dataset[[variables[["sampleSize"]]]], + ti = dataset[[variables[["tStatistic"]]]], + pi = dataset[[variables[["pValue"]]]] + ) + } else if (measurement == "binary") { + if (effectSize %in% c("OR", "YUQ", "YUY", "RTET", "ZTET")) { + inputs <- list( + ai = dataset[[variables[["outcomePlusPlus"]]]], + bi = dataset[[variables[["outcomePlusMinus"]]]], + ci = dataset[[variables[["outcomeMinusPlus"]]]], + di = dataset[[variables[["outcomeMinusMinus"]]]], + n1i = dataset[[variables[["outcomePlusPlusAndPlusMinus"]]]], + n2i = dataset[[variables[["outcomeMinusPlusAndMinusMinus"]]]] + ) + } else if (effectSize %in% c("PHI", "ZPHI")) { + inputs <- list( + ai = dataset[[variables[["outcomePlusPlus"]]]], + bi = dataset[[variables[["outcomePlusMinus"]]]], + ci = dataset[[variables[["outcomeMinusPlus"]]]], + di = dataset[[variables[["outcomeMinusMinus"]]]], + n1i = dataset[[variables[["outcomePlusPlusAndPlusMinus"]]]], + n2i = dataset[[variables[["outcomeMinusPlusAndMinusMinus"]]]] + ) + if (variables[["samplingVarianceTypeMixed"]] != "") + inputs$vtype <- dataset[[variables[["samplingVarianceTypeMixed"]]]] + } + } else if (measurement == "mixed") { + if (effectSize %in% c("RBIS", "ZBIS")) { + inputs <- list( + m1i = dataset[[variables[["meanGroup1"]]]], + m2i = dataset[[variables[["meanGroup2"]]]], + sd1i = dataset[[variables[["sdGroup1"]]]], + sd2i = dataset[[variables[["sdGroup2"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]], + ti = dataset[[variables[["tStatistic"]]]], + pi = dataset[[variables[["pValue"]]]], + di = dataset[[variables[["cohensD"]]]] + ) + } else if (effectSize %in% c("RPB", "ZPB")) { + inputs <- list( + m1i = dataset[[variables[["meanGroup1"]]]], + m2i = dataset[[variables[["meanGroup2"]]]], + sd1i = dataset[[variables[["sdGroup1"]]]], + sd2i = dataset[[variables[["sdGroup2"]]]], + n1i = dataset[[variables[["sampleSizeGroup1"]]]], + n2i = dataset[[variables[["sampleSizeGroup2"]]]], + ti = dataset[[variables[["tStatistic"]]]], + pi = dataset[[variables[["pValue"]]]], + di = dataset[[variables[["cohensD"]]]] + ) + if (variables[["samplingVarianceTypeMixed"]] != "") + inputs$vtype <- dataset[[variables[["samplingVarianceTypeMixed"]]]] + } + } + } else if (design == "singleGroup") { + if (measurement == "quantitative") { + if (effectSize %in% c("MN", "SMN", "MNLN", "CVLN")) { + inputs <- list( + mi = dataset[[variables[["mean"]]]], + sdi = dataset[[variables[["sd"]]]], + ni = dataset[[variables[["sampleSize"]]]] + ) + } else if (effectSize == "SDLN") { + inputs <- list( + sdi = dataset[[variables[["sd"]]]], + ni = dataset[[variables[["sampleSize"]]]] + ) + } + } else if (measurement == "binary") { + inputs <- list( + xi = dataset[[variables[["events"]]]], + mi = dataset[[variables[["nonEvents"]]]], + ni = dataset[[variables[["sampleSize"]]]] + ) + } else if (measurement == "countsPerTime") { + inputs <- list( + xi = dataset[[variables[["events"]]]], + ti = dataset[[variables[["personTime"]]]], + ni = dataset[[variables[["sampleSize"]]]] + ) + } + } else if (design == "repeatedMeasures") { + if (measurement == "quantitative") { + if (effectSize %in% c("MC", "SMCR", "SMCRH", "SMCRP", "SMCRPH", "ROMC")) { + inputs <- list( + m1i = dataset[[variables[["meanTime1"]]]], + m2i = dataset[[variables[["meanTime2"]]]], + sd1i = dataset[[variables[["sdTime1"]]]], + sd2i = dataset[[variables[["sdTime2"]]]], + ni = dataset[[variables[["sampleSize"]]]], + ri = dataset[[variables[["correlation"]]]] + ) + } else if (effectSize == "SMCC") { + inputs <- list( + m1i = dataset[[variables[["meanTime1"]]]], + m2i = dataset[[variables[["meanTime2"]]]], + sd1i = dataset[[variables[["sdTime1"]]]], + sd2i = dataset[[variables[["sdTime2"]]]], + ni = dataset[[variables[["sampleSize"]]]], + ri = dataset[[variables[["correlation"]]]], + ti = dataset[[variables[["tStatistic"]]]], + pi = dataset[[variables[["pValue"]]]], + di = dataset[[variables[["cohensD"]]]] + ) + } else if (effectSize %in% c("CVRC", "VRC")) { + inputs <- list( + sd1i = dataset[[variables[["sdTime1"]]]], + sd2i = dataset[[variables[["sdTime2"]]]], + ni = dataset[[variables[["sampleSize"]]]], + ri = dataset[[variables[["correlation"]]]] + ) + } + } else if (measurement == "binary") { + inputs <- list( + ai = dataset[[variables[["outcomePlusPlus"]]]], + bi = dataset[[variables[["outcomePlusMinus"]]]], + ci = dataset[[variables[["outcomeMinusPlus"]]]], + di = dataset[[variables[["outcomeMinusMinus"]]]] + ) + } else if (measurement == "binaryMarginal") { + inputs <- list( + ai = dataset[[variables[["time1OutcomePlus"]]]], + bi = dataset[[variables[["time1OutcomeMinus"]]]], + ci = dataset[[variables[["time2OutcomePlus"]]]], + di = dataset[[variables[["time2OutcomeMinus"]]]], + ri = dataset[[variables[["correlation"]]]], + pi = dataset[[variables[["proportionPlusPlus"]]]] + ) + } + } else if (design == "other") { + if (measurement == "reliability") { + inputs <- list( + ai = dataset[[variables[["coefficientAlpha"]]]], + mi = dataset[[variables[["items"]]]], + ni = dataset[[variables[["sampleSize"]]]] + ) + } else if (measurement == "partialCorrelation") { + if (effectSize %in% c("PCOR", "ZPCOR")) { + inputs <- list( + ti = dataset[[variables[["tStatistic"]]]], + mi = dataset[[variables[["predictors"]]]], + ni = dataset[[variables[["sampleSize"]]]], + ti = dataset[[variables[["tStatistic"]]]], + ri = dataset[[variables[["semipartialCorrelation"]]]], + pi = dataset[[variables[["pValue"]]]] + ) + } else if (effectSize %in% c("SPCOR", "ZSPCOR")) { + inputs <- list( + ti = dataset[[variables[["tStatistic"]]]], + mi = dataset[[variables[["predictors"]]]], + ni = dataset[[variables[["sampleSize"]]]], + r2i = dataset[[variables[["rSquared"]]]], + ti = dataset[[variables[["tStatistic"]]]], + ri = dataset[[variables[["semipartialCorrelation"]]]], + pi = dataset[[variables[["pValue"]]]] + ) + } + } else if (measurement == "modelFit") { + inputs <- list( + mi = dataset[[variables[["predictors"]]]], + ni = dataset[[variables[["sampleSize"]]]], + r2i = dataset[[variables[["rSquared"]]]], + fi = dataset[[variables[["fStatistic"]]]], + pi = dataset[[variables[["pValue"]]]] + ) + } else if (measurement == "heterozygosity") { + inputs <- list( + ai = dataset[[variables[["homozygousDominantAlleles"]]]], + bi = dataset[[variables[["heterozygousAlleles"]]]], + ci = dataset[[variables[["homozygousRecessiveAlleles"]]]] + ) + } + } else if (design == "reportedEffectSizes") { + inputs <- list( + yi = dataset[[variables[["effectSize"]]]], + sei = dataset[[variables[["standardError"]]]], + vi = dataset[[variables[["samplingVariance"]]]], + lci = if (length(variables[["confidenceInterval"]]) != 0) dataset[[variables[["confidenceInterval"]][[1]][1]]], + uci = if (length(variables[["confidenceInterval"]]) != 0) dataset[[variables[["confidenceInterval"]][[1]][2]]] + ) + inputs <- .escReportedEffectSizesInput(inputs) + } + + if (variables[["subset"]] != "") { + # subset should not be added to the dataset - escalc returns only the subset rows + # we need the whole data set to facilitate merging across the steps + # therefore, we set all non-subset columns to NAs + for (i in seq_along(inputs)) { + if (length(inputs[[i]]) != 0) + inputs[[i]][dataset[[variables[["subset"]]]] != variables[["subsetLevel"]]] <- NA + } + } + + inputs <- inputs[!sapply(inputs, is.null)] + + return(inputs) +} +.escGetEscalcAdjustFrequenciesOptions <- function(effectSizeType, variables) { + + design <- effectSizeType[["design"]] + measurement <- effectSizeType[["measurement"]] + effectSize <- effectSizeType[["effectSize"]] + + # Conditions for when add is appropriate + if ((design == "independentGroups" && measurement == "binary") || + (design == "independentGroups" && measurement == "countsPerTime") || + (design == "independentGroups" && measurement == "mixed" && effectSize %in% c("PBIT", "OR2DN", "OR2DL")) || + (design == "variableAssociation" && measurement == "binary") || + (design == "singleGroup" && measurement == "binary") || + (design == "singleGroup" && measurement == "countsPerTime")) { + return(list( + add = variables[["add"]], + to = switch( + variables[["to"]], + "all" = "all", + "onlyZero" = "only0", + "ifAnyZero" = "if0all", + "none" = "none" + ), + drop00 = switch( + variables[["dropStudiesWithNoCasesOrEvents"]], + "yes" = TRUE, + "no" = FALSE + ) + )) + } else { + return(NULL) + } +} +.escGetEscalcVtypeOption <- function(effectSizeType, variables) { + + design <- effectSizeType[["design"]] + measurement <- effectSizeType[["measurement"]] + effectSize <- effectSizeType[["effectSize"]] + + # Conditions for when vtype is appropriate + if ((design == "independentGroups" && measurement == "quantitative" && effectSize %in% c("MD", "SMD", "SMD1", "ROM")) || + (design == "variableAssociation" && measurement == "quantitative") || + (design == "variableAssociation" && measurement == "binary" && effectSize %in% c("PHI", "ZHI")) || + (design == "variableAssociation" && measurement == "mixed" && effectSize %in% c("RPB", "ZPB")) || + (design == "other" && measurement == "modelFit") && + variables[["samplingVarianceType"]] != "mixed") { + return(list(vtype = variables[["samplingVarianceType"]])) + } else { + return(NULL) + } +} +.escMapEscalcInput2Options <- function(effectSizeType) { + + design <- effectSizeType[["design"]] + measurement <- effectSizeType[["measurement"]] + effectSize <- effectSizeType[["effectSize"]] + + if (design == "independentGroups") { + if (measurement == "quantitative") { + if (effectSize == "SMD") { + inputs <- list( + m1i = "Mean Group 1", + m2i = "Mean Group 2", + sd1i = "SD Group 1", + sd2i = "SD Group 2", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2", + ti = "T-Statistic", + pi = "P-Value", + di = "Cohen's d" + ) + } else if (effectSize %in% c("SMD1", "SMDH1")) { + inputs <- list( + m1i = "Mean Group 1", + m2i = "Mean Group 2", + sd2i = "SD Group 2", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2" + ) + } else if (effectSize %in% c("CVR", "VR")) { + inputs <- list( + sd1i = "SD Group 1", + sd2i = "SD Group 2", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2" + ) + } else { + inputs <- list( + m1i = "Mean Group 1", + m2i = "Mean Group 2", + sd1i = "SD Group 1", + sd2i = "SD Group 2", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2" + ) + } + } else if (measurement == "binary") { + inputs <- list( + ai = "Group 1/Outcome +", + bi = "Group 1/Outcome -", + ci = "Group 2/Outcome +", + di = "Group 2/Outcome -", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2" + ) + } else if (measurement == "countsPerTime") { + inputs <- list( + t1i = "Person-Time Group 1", + t2i = "Person-Time Group 2", + x1i = "Events Group 1", + x2i = "Events Group 2" + ) + } else if (measurement == "mixed") { + if (effectSize %in% c("D2ORN", "D2ORL")) { + inputs <- list( + m1i = "Mean Group 1", + m2i = "Mean Group 2", + sd1i = "SD Group 1", + sd2i = "SD Group 2", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2", + ti = "T-Statistic", + pi = "P-Value", + di = "Cohen's d" + ) + } else if (effectSize %in% c("PBIT", "OR2DN", "OR2DL")) { + inputs <- list( + ai = "Group 1/Outcome +", + bi = "Group 1/Outcome -", + ci = "Group 2/Outcome +", + di = "Group 2/Outcome -", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2" + ) + } + } + } else if (design == "variableAssociation") { + if (measurement == "quantitative") { + inputs <- list( + ri = "Correlation", + ni = "Sample Size", + ti = "T-Statistic", + pi = "P-Value" + ) + } else if (measurement == "binary") { + if (effectSize %in% c("OR", "YUQ", "YUY", "RTET", "ZTET")) { + inputs <- list( + ai = "Outcome +/+", + bi = "Outcome +/-", + ci = "Outcome -/+", + di = "Outcome -/-", + n1i = "Outcome +/+ and +/-", + n2i = "Outcome -/+ and -/-" + ) + } else if (effectSize %in% c("PHI", "ZPHI")) { + inputs <- list( + ai = "Outcome +/+", + bi = "Outcome +/-", + ci = "Outcome -/+", + di = "Outcome -/-", + n1i = "Outcome +/+ and +/-", + n2i = "Outcome -/+ and -/-", + vtype = "Sampling Variance Type Mixed" + ) + } + } else if (measurement == "mixed") { + if (effectSize %in% c("RBIS", "ZBIS")) { + inputs <- list( + m1i = "Mean Group 1", + m2i = "Mean Group 2", + sd1i = "SD Group 1", + sd2i = "SD Group 2", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2", + ti = "T-Statistic", + pi = "P-Value", + di = "Cohen's d" + ) + } else if (effectSize %in% c("RPB", "ZPB")) { + inputs <- list( + m1i = "Mean Group 1", + m2i = "Mean Group 2", + sd1i = "SD Group 1", + sd2i = "SD Group 2", + n1i = "Sample Size Group 1", + n2i = "Sample Size Group 2", + ti = "T-Statistic", + pi = "P-Value", + di = "Cohen's d", + vtype = "Sampling Variance Type Mixed" + ) + } + } + } else if (design == "singleGroup") { + if (measurement == "quantitative") { + if (effectSize %in% c("MN", "SMN", "MNLN", "CVLN")) { + inputs <- list( + mi = "Mean", + sdi = "SD", + ni = "Sample Size" + ) + } else if (effectSize == "SDLN") { + inputs <- list( + sdi = "SD", + ni = "Sample Size" + ) + } + } else if (measurement == "binary") { + inputs <- list( + xi = "Events", + mi = "Non-Events", + ni = "Sample Size" + ) + } else if (measurement == "countsPerTime") { + inputs <- list( + xi = "Events", + ti = "Person-Time", + ni = "Sample Size" + ) + } + } else if (design == "repeatedMeasures") { + if (measurement == "quantitative") { + if (effectSize %in% c("MC", "SMCR", "SMCRH", "SMCRP", "SMCRPH", "ROMC")) { + inputs <- list( + m1i = "Mean Time 1 (or Group 1)", + m2i = "Mean Time 2 (or Group 2)", + sd1i = "SD Time 1 (or Group 1)", + sd2i = "SD Time 2 (or Group 2)", + ni = "Sample Size", + ri = "Correlation" + ) + } else if (effectSize == "SMCC") { + inputs <- list( + m1i = "Mean Time 1 (or Group 1)", + m2i = "Mean Time 2 (or Group 2)", + sd1i = "SD Time 1 (or Group 1)", + sd2i = "SD Time 2 (or Group 2)", + ni = "Sample Size", + ri = "Correlation", + ti = "T-Statistic", + pi = "P-Value", + di = "Cohen's d" + ) + } else if (effectSize %in% c("CVRC", "VRC")) { + inputs <- list( + sd1i = "SD Time 1 (or Group 1)", + sd2i = "SD Time 2 (or Group 2)", + ni = "Sample Size", + ri = "Correlation" + ) + } + } else if (measurement == "binary") { + inputs <- list( + ai = "Outcome +/+", + bi = "Outcome +/-", + ci = "Outcome -/+", + di = "Outcome -/-" + ) + } else if (measurement == "binaryMarginal") { + inputs <- list( + ai = "Time 1/Outcome +", + bi = "Time 1/Outcome -", + ci = "Time 2/Outcome +", + di = "Time 2/Outcome -", + ri = "Correlation", + pi = "Proportion +/+" + ) + } + } else if (design == "other") { + if (measurement == "reliability") { + inputs <- list( + ai = "Cronbach's alpha", + mi = "Items", + ni = "Sample Size" + ) + } else if (measurement == "partialCorrelation") { + if (effectSize %in% c("PCOR", "ZPCOR")) { + inputs <- list( + ti = "T-Statistic", + mi = "Predictors", + ni = "Sample Size", + ti = "T-Statistic", + ri = "(Semi)Partial Correlation", + pi = "P-Value" + ) + } else if (effectSize %in% c("SPCOR", "ZSPCOR")) { + inputs <- list( + ti = "T-Statistic", + mi = "Predictors", + ni = "Sample Size", + r2i = "R-Squared", + ti = "T-Statistic", + ri = "(Semi)Partial Correlation", + pi = "P-Value" + ) + } + } else if (measurement == "modelFit") { + inputs <- list( + mi = "Predictors", + ni = "Sample Size", + r2i = "R-Squared", + fi = "F-Statistic", + pi = "P-Value" + ) + } else if (measurement == "heterozygosity") { + inputs <- list( + ai = "Homozygous Dominant Alleles", + bi = "Heterozygous Alleles", + ci = "Homozygous Recessive Alleles" + ) + } + } else if (design == "reportedEffectSizes") { + inputs <- list( + yi = "Effect Size", + sei = "Standard Error", + vi = "Sampling Variance" + ) + } + + return(inputs) +} +.escCleanErrorMessage <- function(errorMessage, effectSizeType) { + + # remove new lines + errorMessage <- gsub("\\n ", "", errorMessage) + + if (grepl("via the appropriate arguments", errorMessage)) { + + # split the message at 'via the appropriate arguments' + errorSplit <- regexpr("via the appropriate arguments", errorMessage) + errorMessageStart <- substr(errorMessage, 1, errorSplit + attr(errorSplit, "match.length") - 1) + errorMessageEnd <- substr(errorMessage, errorSplit + attr(errorSplit, "match.length"), nchar(errorMessage)) + + inputMapping <- .escMapEscalcInput2Options(effectSizeType) + for (input in names(inputMapping)) { + errorMessageEnd <- gsub(input, inputMapping[[input]], errorMessageEnd) + } + + # re-assemble the message + errorMessage <- paste(errorMessageStart, errorMessageEnd, sep = "") + + } else if (grepl("'vtype'", errorMessage)) { + errorMessage <- gsub("'vtype'", "'Sampling variance type'", errorMessage) + } + + return(errorMessage) +} +.escReportedEffectSizesInput <- function(inputs) { + + inputs <- inputs[!sapply(inputs, is.null)] + inputs <- do.call(cbind.data.frame, inputs) + + if (is.null(inputs$sei)) + inputs$sei <- NA + if (is.null(inputs$vi)) + inputs$vi <- NA + if (is.null(inputs$uci)) + inputs$uci <- NA + if (is.null(inputs$lci)) + inputs$lci <- NA + + # add standard error when missing and CI is available + if (length((inputs$uci[is.na(inputs$sei)] - inputs$lci[is.na(inputs$sei)]) ) != 0) + inputs$sei[is.na(inputs$sei)] <- (inputs$uci[is.na(inputs$sei)] - inputs$lci[is.na(inputs$sei)]) / (2 * stats::qnorm(0.975)) + + # add variance when missing and standard error is available + if (length(inputs$sei[is.na(inputs$vi)]) != 0) + inputs$vi[is.na(inputs$vi)] <- inputs$sei[is.na(inputs$vi)]^2 + + # remove sei and cis + inputs$sei <- NULL + inputs$uci <- NULL + inputs$lci <- NULL + + return(inputs) +} +.escReportedEffectSizesReady <- function(variables, all = TRUE){ + + varianceMeasureReady <- !(length(variables[["confidenceInterval"]]) == 0 && variables[["standardError"]] == "" && variables[["samplingVariance"]] == "") + effectSizeReady <- variables[["effectSize"]] != "" + + if (all) { + return(effectSizeReady && varianceMeasureReady) + } else { + return((effectSizeReady + varianceMeasureReady) >= 1) + } +} +.escVariableInputs <- c( + "group1OutcomePlus", + "time1OutcomePlus", + "outcomePlusPlus", + "coefficientAlpha", + "homozygousDominantAlleles", + "group1OutcomeMinus", + "time1OutcomeMinus", + "outcomePlusMinus", + "heterozygousAlleles", + "group2OutcomePlus", + "time2OutcomePlus", + "outcomeMinusPlus", + "homozygousRecessiveAlleles", + "group2OutcomeMinus", + "time2OutcomeMinus", + "outcomeMinusMinus", + "outcomePlusPlusAndPlusMinus", + "outcomeMinusPlusAndMinusMinus", + "eventsGroup1", + "events", + "nonEvents", + "items", + "predictors", + "eventsGroup2", + "personTimeGroup1", + "personTime", + "personTimeGroup2", + "meanGroup1", + "meanTime1", + "meanGroup2", + "meanTime2", + "mean", + "sdGroup1", + "sdTime1", + "sdGroup2", + "sdTime2", + "sd", + "sampleSizeGroup1", + "sampleSizeGroup2", + "correlation", + "proportionPlusPlus", + "sampleSize", + "cohensD", + "rSquared", + "tStatistic", + "fStatistic", + "semipartialCorrelation", + "pValue", + "effectSize", + "standardError", + "samplingVariance", + "samplingVarianceTypeMixed", + "subset", "subsetLevel" +) diff --git a/R/emmeans.rma.R b/R/emmeans.rma.R deleted file mode 100644 index b37718a8..00000000 --- a/R/emmeans.rma.R +++ /dev/null @@ -1,210 +0,0 @@ -emmeans.rma <- function(object, formula, data, conf.level = .95, contrasts = NULL, ...) { - if (is.null(object$call) || is.null(object$call$yi) || !inherits(object$call$yi, "formula")) - stop("Currently this only works with rma and rma.mv objects that have specified 'yi' as a formula.") - - mdlformula = object$call$yi - mdlformula[[2]] = NULL # remove dependent - - # build a new data matrix - used_terms = all.vars(mdlformula) - if(!(all.vars(formula) %in% used_terms)) stop("Formula is refering to factors that are not in the model.") - factor_levels = lapply(data[, used_terms, drop=FALSE], function(x) if (!is.numeric(x)) levels(factor(x)) ) # extract factor levels - .grid = expand.grid(Filter(Negate(is.null), factor_levels)) - if(nrow(.grid) == 0) stop("There are no predictors in the model that correspond to factors in '", deparse(substitute(data)), "'. Factor levels: ", paste(capture.output(str(factor_levels)), collapse = ", "), ". Data names: ", paste(names(data), collapse = ", "), "; Used Terms: ",paste(used_terms, collapse=", "), "; Data set head: ", paste(capture.output(head(data)), collapse="\n")) - covariate_means = colMeans(data[, names(Filter(is.null, factor_levels)), drop = FALSE], na.rm = TRUE) - newdata = do.call(transform, c(list(.grid), as.list(covariate_means))) - - b = coef(object) - Vb = vcov(object) - - # compute transformation matrix: - # - M: design matrix conforming the model for obtain cell means for all factors crossed (fixing covariates to their sample averages; should this be within cell averages?) - # - K: matrix with dummies for picking out the means to combine - # - K.M = (K'K)^-1 K'M is the transformation matrix for the model's regression coefficients to yield the marginal means - M = do.call(model.matrix, list(mdlformula, newdata)) - match.colnames = max.col(-adist(names(b), colnames(M))) - M = M[, match.colnames] - factors = all.vars(formula) - Kmf = model.frame(paste("~ 0 + ", factors, collapse = ":"), unique(.grid[, factors, drop = FALSE])) - K = model.matrix(Kmf, newdata, constrasts = sapply(factors, function(...) 'contr.Treatment',simplify = F)) - K.M = MASS::ginv(K) %*% M - - # if contrast matrix is specified, a hypothesis test on these contrasts are given - if(!missing(contrasts) && is.matrix(contrasts)) { - if (is.null(rownames(contrasts))) rownames(contrasts) = paste(deparse(substitute(contrasts)), "[", 1:nrow(contrasts), ", ]", sep="") - K.M = contrasts %*% K.M - } - - # compute marginal means requested, plus their standard errors - emmeans = K.M %*% b - se = diag(K.M %*% Vb %*% t(K.M))^0.5 - - # build return structure - if (!missing(contrasts)) { - ret = data.frame(Contrast=rownames(K.M), Estimate = emmeans, SE = se, df = df.residual(object)) - t = emmeans / se - pval = pt(-abs(t), ret$df, lower.tail = TRUE) - comparisons = if (is.null(rownames(contrasts))) ret$Contrast else rownames(contrasts) - ret = transform(ret, Contrast = comparisons, `t value` = t, `P(>|t|)` = pval, check.names=FALSE) - } else { - ret = transform(Kmf, emmean = emmeans, SE = se, df = df.residual(object)) - p = (1-conf.level) / 2 - ret = transform(ret, lower.CL = emmean + qt(p, df) * SE, upper.CL = emmean - qt(p, df) * SE) - } - rownames(ret) = NULL - structure(ret, collapsed = setdiff(colnames(.grid), all.vars(formula)), conf.level = conf.level, - covariate_means = covariate_means, class = c("emmeans.rma","data.frame")) -} - -print.emmeans.rma <- function(x, ...) { - print(structure(x, class = "data.frame"), ...) - if (length(attr(x, "collapsed")) > 0 ) { - cat("\n\nMeans are averaged over the levels of: ") - cat(attr(x, "collapsed"), sep = ", ") - } - if (length(attr(x,"covariate_means")) > 0) { - cat("\nThe following means for the covariates were used:\n") - print(attr(x,"covariate_means"), ...) - } - cat("\nConfidence level used:", attr(x,"conf.level"), "\n") - invisible(x) -} - - -emmeans_contrasts.rma <- function(x, ..., contrasts) { - C = contrasts - if (!is.matrix(C)) stop("Argument 'contrasts' should be a matrix.") - if (!all(abs(rowSums(C)) < .Machine$double.eps)^.5) stop("Invalid contrasts: Rows in", deparse(substitute(contrasts)), "do not add to 0.") - emmeans.rma(x, ..., contrasts = C) -} - -contr.all_deviations <- function(n) { - # n is either a factor, or a number (of levels) - # Deviation contrasts for all levels are computed - fact <- NA - if (is.factor(n)) { - fact <- n - n <- nlevels(n) - } - C <- diag(n) - 1/n - rownames(C) = colnames(C) = if (is.factor(fact)) levels(fact) else 1:n - C -} - -contr.all_pairs <- function(n) { - # n is either a factor, or a number of levels - # Contrasts for all possible pairwise comparisons are computed - fact = NA - if (is.factor(n)) { - fact = n - n = nlevels(n) - } - if (length(n) > 1) {n = n[1]; warning("Only using first element of", deparse(substitute(n)),".")} - if (n < 2) stop(deparse(substitute(n)), "is smaller than 2.") - N = n-1 - C = sapply(1:n, function(i) cbind(-1, diag(N))[,(0:N+i) %% n + 1, drop=FALSE]) - C = C[!duplicated(abs(C)),, drop = FALSE] - colnames(C) = if (is.factor(fact)) levels(fact) else 1:n - rownames(C) = apply(C, 1, function(x) {i <- which(x!=0); nms <- colnames(C)[i[order(x[i], decreasing=TRUE)]]; paste(nms, collapse = " - ")}) - C -} - -addSignifStars <- function(x, ..., column = "P(>|t|)", stars = c(' ***'=.001, ' **'=.01, ' *'=.05, ' .'=.1) ) { - X = transform(x, ` ` = c(names(stars),'')[findInterval(get(column), c(0, stars, 1))], check.names = FALSE, stringsAsFactors=FALSE) - attributes(X) <- attributes(x) - names(X) = ifelse(is.na(names(X)), ' ', names(X)) - X -} - -# (function(conf.level = .95){ -# formula = ~ colour -# data = carData::Arrests -# fit = lm(checks ~ colour*sex+employed, data = data) -# mf = if(is.data.frame(model.frame(fit))) model.frame(fit) else data[, all.vars(mdlformula)] -# -# mdlformula = fit$call$formula -# mdlformula[[2]] = NULL # remove response variable -# -# b = coef(fit) -# Vb = vcov(fit) -# -# tmp = expand.grid(Filter(Negate(is.null), lapply(mf, levels))) -# #browser() -# M = do.call(model.matrix, list(mdlformula, tmp)) #, contrasts = list(wool='contr.Treatment', tension='contr.Treatment'))) -# Kmf = model.frame(paste("~ 0 + ",all.vars(formula), collapse = ":"), unique(tmp[, all.vars(formula), drop = FALSE])) -# K = model.matrix(Kmf, tmp, contrasts = as.list(setNames(rep("contr.Treatment", length(all.vars(formula))), all.vars(formula)))) -# K.M = ginv(K) %*% M -# em = K.M %*% b -# se = diag(K.M %*% Vb %*% t(K.M))^.5 -# ret = transform(Kmf, emmean = em, SE = se, df = df.residual(fit)) -# structure(transform(ret, lower.CL = emmean - qt(.025, df)*se, upper.CL = emmean - qt(0.5-conf.level/2, df)*se), -# collapsed = setdiff(all.vars(mdlformula), all.vars(formula)), conf.level = conf.level) -# })() # for testing the correctness - - -### -### NIET AAN BEGINNEN!!!! (gebruik gewoon package emmeans!) -### -# -# emmeans <- function(object, ...) UseMethod("emmeans") -# -# emmeans.default <- function(object, conditioning, contrasts = NULL) { -# require(tidyverse) -# conditioning = if (is_formula(conditioning)) all.vars(conditioning[-2]) else as.character(conditioning) -# -# method = match.arg(method) -# -# mf = model.frame(object) -# used_terms = names(mf) -# -# factor_levels = Filter(Negate(is.null), lapply(mf, levels)) # extract factor levels -# covariate_names = names(Filter(is.null, lapply(mf, levels))) -# .grid = expand.grid(factor_levels) -# covariate_means = colMeans(mf[covariate_names], na.rm = TRUE) -# newdata = do.call(transform, c(list(.grid), as.list(covariate_means))) -# -# piv = object$qr$pivot[1:object$rank] -# b = coef(object)[piv] -# Vb = vcov(object)[piv,piv] -# -# # compute transformation matrix: -# # - M: design matrix conforming the model for obtain cell means for all factors crossed (fixing covariates to their sample averages; should this be within cell averages?) -# # - K: matrix with dummies for picking out the means to combine -# # - K.M = (K'K)^-1 K'M is the transformation matrix for the model's regression coefficients to yield the marginal means -# # M = do.call(model.matrix, list(mdlformula, newdata)) -# M = model.matrix(terms(object), newdata)[, object$qr$pivot[1:object$rank], drop = FALSE] -# match.colnames = max.col(-adist(names(b), colnames(M))) -# M = M[, match.colnames] -# factors = all.vars(formula) -# Kmf = model.frame(paste("~ 0 + ", factors, collapse = ":"), unique(.grid[, factors, drop = FALSE])) -# K = model.matrix(Kmf, newdata, constrasts = sapply(factors, function(...) 'contr.Treatment',simplify = F)) -# K.M = MASS::ginv(K) %*% M -# -# # if contrast matrix is specified, a hypothesis test on these contrasts are given -# if(!missing(contrasts) && is.matrix(contrasts)) { -# K.M = contrasts %*% K.M -# } -# -# # compute marginal means requested, plus their standard errors -# emmeans = K.M %*% b -# se = diag(K.M %*% Vb %*% t(K.M))^0.5 -# -# # build return structure -# if (!missing(contrasts)) { -# ret = data.frame(Contrast=rownames(K.M), Estimate = emmeans, SE = se, df = df.residual(object)) -# t = emmeans / se -# pval = pt(-abs(t), ret$df, lower.tail = TRUE) -# comparisons = if (is.null(rownames(contrasts))) ret$Contrast else rownames(contrasts) -# ret = transform(ret, Contrast = comparisons, `t value` = t, `P(>|t|)` = pval, check.names=FALSE) -# } else { -# ret = transform(Kmf, emmean = emmeans, SE = se, df = df.residual(object)) -# p = (1-conf.level) / 2 -# ret = transform(ret, lower.CL = emmean + qt(p, df) * SE, upper.CL = emmean - qt(p, df) * SE) -# } -# rownames(ret) = NULL -# structure(ret, collapsed = setdiff(colnames(.grid), all.vars(formula)), conf.level = conf.level, -# covariate_means = covariate_means, class = c("emmeans.rma","data.frame")) -# } -# -# -# diff --git a/R/forestplot.R b/R/forestplot.R new file mode 100644 index 00000000..99a7512b --- /dev/null +++ b/R/forestplot.R @@ -0,0 +1,892 @@ +.maMakeTheUltimateForestPlot <- function(fit, dataset, options) { + + # extract common options + relativeRowSize <- options[["forestPlotRelativeSizeRow"]] + + # overwrite basic options used in the pooled effect/marginal means + options[["confidenceIntervals"]] <- TRUE + options[["predictionIntervals"]] <- options[["forestPlotPredictionIntervals"]] + + # keep track of added rows across marginal means and model estimates: + tempRow <- 1 + additionalInformation <- list() + additionalObjects <- list() + + ### Study information panel ---- + if (options[["forestPlotStudyInformation"]]) { + + ### extract effect sizes and variances from the fitted object + dfForrest <- data.frame( + effectSize = fit[["yi"]], + standardError = sqrt(fit[["vi"]]), + weights = weights(fit), + id = seq_along(fit[["yi"]]) + ) + + # add CI using normal approximation + dfForrest$lCi <- dfForrest$effectSize - qnorm((1 - options[["confidenceIntervalsLevel"]]) / 2, lower.tail = F) * dfForrest$standardError + dfForrest$uCi <- dfForrest$effectSize + qnorm((1 - options[["confidenceIntervalsLevel"]]) / 2, lower.tail = F) * dfForrest$standardError + + if (options[["forestPlotStudyInformationSecondaryConfidenceInterval"]]) { + dfForrest$lCi2 <- dfForrest$effectSize - qnorm((1 - options[["forestPlotStudyInformationSecondaryConfidenceIntervalLevel"]]) / 2, lower.tail = F) * dfForrest$standardError + dfForrest$uCi2 <- dfForrest$effectSize + qnorm((1 - options[["forestPlotStudyInformationSecondaryConfidenceIntervalLevel"]]) / 2, lower.tail = F) * dfForrest$standardError + } + + + # transform effect size when requested + if (options[["transformEffectSize"]] != "none") { + + dfForrest[,c( + "effectSize", "lCi", "uCi", + if (options[["forestPlotStudyInformationSecondaryConfidenceInterval"]]) c("lCi2", "uCi2"))] <- do.call( + .maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), + list(dfForrest[,c( + "effectSize", "lCi", "uCi", + if (options[["forestPlotStudyInformationSecondaryConfidenceInterval"]]) c("lCi2", "uCi2"))])) + } + + xRangeStudyInformationPanel <- range(c(dfForrest$lCi, dfForrest$uCi)) + + # add variables used for either color, shape, order or Left panel information + additionalVariables <- c( + if (length(options[["forestPlotStudyInformationSelectedVariables"]]) > 0) unlist(options[["forestPlotStudyInformationSelectedVariables"]]), + if (options[["forestPlotStudyInformationOrderBy"]] != "") options[["forestPlotStudyInformationOrderBy"]], + if (options[["forestPlotMappingColor"]] != "") options[["forestPlotMappingColor"]], + if (options[["forestPlotMappingShape"]] != "") options[["forestPlotMappingShape"]] + ) + if (length(additionalVariables) > 0) + dfForrest <- cbind(dfForrest, dataset[,additionalVariables,drop=FALSE]) + + # TODO: temporal fix for the variable names in the Component list not being properly translated + for (i in seq_along(options[["forestPlotStudyInformationSelectedVariables"]])) { + options[["forestPlotStudyInformationSelectedVariablesSettings"]][[i]][["value"]] <- options[["forestPlotStudyInformationSelectedVariables"]][[i]] + } + + # combine left panel information + leftPanelStudyInformation <- do.call(rbind.data.frame, options[["forestPlotStudyInformationSelectedVariablesSettings"]]) + + # re-order + if (options[["forestPlotStudyInformationOrderBy"]] != "") { + dfForrest <- dfForrest[order( + dfForrest[,options[["forestPlotStudyInformationOrderBy"]]], + decreasing = options[["forestPlotStudyInformationOrderAscending"]]),] + } + + # add y-axis coordinates for plotting + dfForrest$row <- seq(nrow(dfForrest)) + + ### add predicted effects + if (options[["forestPlotStudyInformationPredictedEffects"]]) { + + fitPrediction <- data.frame(predict(fit)) + + # replicate the prediction for each estimate if the predictions are the same (no moderators) + if (nrow(fitPrediction) == 1) + fitPrediction <- do.call(rbind, replicate(nrow(dfForrest), fitPrediction, simplify = FALSE)) + + fitPrediction$id <- dfForrest$id + fitPrediction$row <- dfForrest$row + + # create prediction diamond coordinates for each estimate + fitPrediction <- do.call(rbind, lapply(1:nrow(fitPrediction), function(i) { + with(fitPrediction[i,], .maMakeDiamondDataFrame(est = pred, lCi = pi.lb, uCi = pi.ub, row = row, id = id)) + })) + + fitPrediction <- merge(fitPrediction, dfForrest[,!colnames(dfForrest) %in% c("effectSize", "standardError", "weights", "lCi", "uCi")], by = "id") + + # transform effect size when requested + if (options[["transformEffectSize"]] != "none") + fitPrediction[,"xPrediction"] <- do.call( + .maGetEffectSizeTransformationOptions(options[["transformEffectSize"]]), + list(fitPrediction[,"xPrediction"])) + + xRangeStudyInformationPanel <- range(c(xRangeStudyInformationPanel, range(fitPrediction$x))) + + # adjust y-coordinates + fitPrediction$y <- fitPrediction$y * relativeRowSize + } + + # adjust y-coordinates + dfForrest$y <- dfForrest$row * relativeRowSize + + } else { + dfForrest <- NULL + xRangeStudyInformationPanel <- NA + } + + ### Make sure no multiple prediction intervals are drawn for complex models ---- + if (.mammHasMultipleHeterogeneities(options)) { + options[["predictionIntervals"]] <- FALSE + options[["forestPlotPredictionIntervals"]] <- FALSE + } + + ### Estimated marginal means panel ---- + + ### compute and add marginal estimates + if (options[["forestPlotEstimatedMarginalMeans"]] && ( + length(options[["forestPlotEstimatedMarginalMeansSelectedVariables"]]) > 0 || options[["forestPlotEstimatedMarginalMeansAdjustedEffectSizeEstimate"]] + )) { + + # terms and levels information + estimatedMarginalMeansTestsStaistics <- options[["forestPlotAuxiliaryTestsInformation"]] == "statisticAndPValue" + estimatedMarginalMeansVariables <- unlist(options[["forestPlotEstimatedMarginalMeansSelectedVariables"]]) + + # statistics position adjustment + estimatedMarginalMeansTermsTestsRight <- options[["forestPlotEstimatedMarginalMeansTermTests"]] && options[["forestPlotTestsInRightPanel"]] + estimatedMarginalMeansTermsTestsLeft <- options[["forestPlotEstimatedMarginalMeansTermTests"]] && !options[["forestPlotTestsInRightPanel"]] + + estimatedMarginalMeansCoefficientTestsRight <- options[["forestPlotEstimatedMarginalMeansCoefficientTests"]] && options[["forestPlotTestsInRightPanel"]] + estimatedMarginalMeansCoefficientTestsBelow <- options[["forestPlotEstimatedMarginalMeansCoefficientTests"]] && !options[["forestPlotTestsInRightPanel"]] && options[["forestPlotPredictionIntervals"]] + estimatedMarginalMeansCoefficientTestsLeft <- options[["forestPlotEstimatedMarginalMeansCoefficientTests"]] && !options[["forestPlotTestsInRightPanel"]] && !options[["forestPlotPredictionIntervals"]] + + # add header + additionalInformation[[tempRow]] <- data.frame( + "label" = gettext("Estimated Marginal Means"), + "row" = tempRow, + "est" = NA, + "lCi" = NA, + "uCi" = NA, + "test" = "", + "face" = "bold" + ) + tempRow <- tempRow + 1 + + # add marginal estimates + for (i in seq_along(estimatedMarginalMeansVariables)) { + + tempTermTest <- .maTermTests(fit, options, estimatedMarginalMeansVariables[i]) + tempEstimatedMarginalMeans <- .maComputeMarginalMeansVariable(fit, options, dataset, estimatedMarginalMeansVariables[i], options[["forestPlotEstimatedMarginalMeansCoefficientTestsAgainst"]] , "effectSize") + tempTestText <- .maPrintTermTest(tempTermTest, estimatedMarginalMeansTestsStaistics) + + # add term information + additionalInformation[[tempRow]] <- data.frame( + "label" = if (estimatedMarginalMeansTermsTestsLeft) paste0(estimatedMarginalMeansVariables[i], ": ", tempTestText) else estimatedMarginalMeansVariables[i], + "row" = tempRow, + "est" = NA, + "lCi" = NA, + "uCi" = NA, + "test" = if (estimatedMarginalMeansTermsTestsRight) tempTestText else "", + "face" = NA + ) + tempRow <- tempRow + 1 + + # add levels information + for (j in 1:nrow(tempEstimatedMarginalMeans)) { + + tempCoefficientTest <- .maPrintCoefficientTest(tempEstimatedMarginalMeans[j,], estimatedMarginalMeansTestsStaistics) + + additionalInformation[[tempRow]] <- data.frame( + "label" = if (estimatedMarginalMeansCoefficientTestsLeft) paste0(tempEstimatedMarginalMeans$value[j], ": ", tempCoefficientTest) else tempEstimatedMarginalMeans$value[j], + "row" = tempRow, + "est" = tempEstimatedMarginalMeans$est[j], + "lCi" = tempEstimatedMarginalMeans$lCi[j], + "uCi" = tempEstimatedMarginalMeans$uCi[j], + "test" = if (estimatedMarginalMeansCoefficientTestsRight) tempCoefficientTest else "", + "face" = "italic" + ) + additionalObjects[[tempRow]] <- with(tempEstimatedMarginalMeans[j,], .maMakeDiamondDataFrame(est = est, lCi = lCi, uCi = uCi, row = tempRow, id = tempRow)) + additionalObjects[[tempRow]]$mapColor <- if(options[["forestPlotMappingColor"]] == estimatedMarginalMeansVariables[i]) tempEstimatedMarginalMeans$value[j] else NA + tempRow <- tempRow + 1 + + + if (options[["forestPlotPredictionIntervals"]] || estimatedMarginalMeansCoefficientTestsBelow) { + + additionalInformation[[tempRow]] <- data.frame( + "label" = if (estimatedMarginalMeansCoefficientTestsBelow) tempCoefficientTest else NA, + "row" = tempRow, + "est" = NA, + "lCi" = if (options[["forestPlotPredictionIntervals"]]) tempEstimatedMarginalMeans$lPi[j] else NA, + "uCi" = if (options[["forestPlotPredictionIntervals"]]) tempEstimatedMarginalMeans$uPi[j] else NA, + "test" = "", + "face" = NA + ) + if (options[["forestPlotPredictionIntervals"]]) { + additionalObjects[[tempRow]] <- with(tempEstimatedMarginalMeans[j,], .maMakeRectangleDataFrame(lCi = lPi, uCi = uPi, row = tempRow, id = tempRow)) + additionalObjects[[tempRow]]$mapColor <- if(options[["forestPlotMappingColor"]] == estimatedMarginalMeansVariables[i]) tempEstimatedMarginalMeans$value[j] else NA + } + + + tempRow <- tempRow + 1 + } + } + + # add empty row + tempRow <- tempRow + 1 + } + + # add adjusted effect size estimate + if (options[["forestPlotEstimatedMarginalMeansAdjustedEffectSizeEstimate"]]) { + + tempEstimatedMarginalMeans <- .maComputeMarginalMeansVariable(fit, options, dataset, "", options[["forestPlotEstimatedMarginalMeansCoefficientTestsAgainst"]] , "effectSize") + tempCoefficientTest <- .maPrintCoefficientTest(tempEstimatedMarginalMeans, options[["forestPlotAuxiliaryTestsInformation"]] == "statisticAndPValue") + + additionalInformation[[tempRow]] <- data.frame( + "label" = if (estimatedMarginalMeansCoefficientTestsLeft) paste0(gettext("Adjusted Estimate"), ": ", tempCoefficientTest) else gettext("Adjusted Estimate"), + "row" = tempRow, + "est" = tempEstimatedMarginalMeans$est, + "lCi" = tempEstimatedMarginalMeans$lCi, + "uCi" = tempEstimatedMarginalMeans$uCi, + "test" = if (estimatedMarginalMeansCoefficientTestsRight) tempCoefficientTest else "", + "face" = NA + ) + additionalObjects[[tempRow]] <- with(tempEstimatedMarginalMeans, .maMakeDiamondDataFrame(est = est, lCi = lCi, uCi = uCi, row = tempRow, id = tempRow)) + tempRow <- tempRow + 1 + + if (options[["forestPlotPredictionIntervals"]] || estimatedMarginalMeansCoefficientTestsBelow) { + + additionalInformation[[tempRow]] <- data.frame( + "label" = if(estimatedMarginalMeansCoefficientTestsBelow) tempCoefficientTest else NA, + "row" = tempRow, + "est" = NA, + "lCi" = if (options[["forestPlotPredictionIntervals"]]) tempEstimatedMarginalMeans$lPi else NA, + "uCi" = if (options[["forestPlotPredictionIntervals"]]) tempEstimatedMarginalMeans$uPi else NA, + "test" = "", + "face" = NA + ) + + if (options[["forestPlotPredictionIntervals"]]) + additionalObjects[[tempRow]] <- with(tempEstimatedMarginalMeans, .maMakeRectangleDataFrame(lCi = lPi, uCi = uPi, row = tempRow, id = tempRow)) + + tempRow <- tempRow + 1 + } + } + + tempRow <- tempRow + 1 + } + + + ### Model information panel ---- + # - residual heterogeneity test + # - moderation tests + # - pooled estimate + if (options[["forestPlotModelInformation"]]) { + + if (any(unlist(options[c( + "forestPlotResidualHeterogeneityTest", "forestPlotResidualHeterogeneityEstimate", + "forestPlotEffectSizeModerationTest", + "forestPlotHeterogeneityModerationTest", + "forestPlotPooledEffectSizeEstimate" + )]))) { + # add Header + additionalInformation[[tempRow]] <- data.frame( + "label" = gettext("Model Information"), + "row" = tempRow, + "est" = NA, + "lCi" = NA, + "uCi" = NA, + "test" = "", + "face" = "bold" + ) + tempRow <- tempRow + 1 + } + + if (options[["forestPlotResidualHeterogeneityTest"]]) { + additionalInformation[[tempRow]] <- data.frame( + "label" = .maPrintQTest(fit), + "row" = tempRow, + "est" = NA, + "lCi" = NA, + "uCi" = NA, + "test" = "", + "face" = NA + ) + tempRow <- tempRow + 1 + } + + if (!.maGetMethodOptions(options) %in% c("FE", "EE") && options[["forestPlotResidualHeterogeneityEstimate"]]) { + additionalInformation[[tempRow]] <- data.frame( + "label" = .maPrintHeterogeneityEstimate(fit, options, digits = options[["forestPlotAuxiliaryDigits"]], keepText = !options[["forestPlotResidualHeterogeneityTest"]]), + "row" = tempRow, + "est" = NA, + "lCi" = NA, + "uCi" = NA, + "test" = "", + "face" = NA + ) + tempRow <- tempRow + 1 + } + + if (.maIsMetaregressionEffectSize(options) && options[["forestPlotEffectSizeModerationTest"]]) { + additionalInformation[[tempRow]] <- data.frame( + "label" = .maPrintModerationTest(fit, options, par = "effectSize"), + "row" = tempRow, + "est" = NA, + "lCi" = NA, + "uCi" = NA, + "test" = "", + "face" = NA + ) + tempRow <- tempRow + 1 + } + + if (.maIsMetaregressionHeterogeneity(options) && options[["forestPlotHeterogeneityModerationTest"]]) { + additionalInformation[[tempRow]] <- data.frame( + "label" = .maPrintModerationTest(fit, options, par = "heterogeneity"), + "row" = tempRow, + "est" = NA, + "lCi" = NA, + "uCi" = NA, + "test" = "", + "face" = NA + ) + tempRow <- tempRow + 1 + } + + if (options[["forestPlotPooledEffectSizeEstimate"]]) { + + pooledEffectSizeTestsRight <- options[["forestPlotPooledEffectSizeTest"]] && options[["forestPlotTestsInRightPanel"]] + pooledEffectSizeTestsBelow <- options[["forestPlotPooledEffectSizeTest"]] && !options[["forestPlotTestsInRightPanel"]] && options[["forestPlotPredictionIntervals"]] + pooledEffectSizeTestsLeft <- options[["forestPlotPooledEffectSizeTest"]] && !options[["forestPlotTestsInRightPanel"]] && !options[["forestPlotPredictionIntervals"]] + + tempPooledEstimate <- .maComputePooledEffectPlot(fit, options) + tempTestText <- .maPrintCoefficientTest(tempPooledEstimate, options[["forestPlotAuxiliaryTestsInformation"]] == "statisticAndPValue") + + additionalInformation[[tempRow]] <- data.frame( + "label" = if (pooledEffectSizeTestsLeft) paste0(gettext("Pooled Estimate"), ": ", tempTestText) else gettext("Pooled Estimate"), + "row" = tempRow, + "est" = tempPooledEstimate$est, + "lCi" = tempPooledEstimate$lCi, + "uCi" = tempPooledEstimate$uCi, + "test" = if (pooledEffectSizeTestsRight) tempTestText else "", + "face" = NA + ) + additionalObjects[[tempRow]] <- with(tempPooledEstimate, .maMakeDiamondDataFrame(est = est, lCi = lCi, uCi = uCi, row = tempRow, id = tempRow)) + tempRow <- tempRow + 1 + + if (pooledEffectSizeTestsBelow || options[["forestPlotPredictionIntervals"]]) { + additionalInformation[[tempRow]] <- data.frame( + "label" = if (pooledEffectSizeTestsBelow) tempTestText else NA, + "row" = tempRow, + "est" = NA, + "lCi" = if (options[["forestPlotPredictionIntervals"]]) tempPooledEstimate$lPi else NA, + "uCi" = if (options[["forestPlotPredictionIntervals"]]) tempPooledEstimate$uPi else NA, + "test" = "", + "face" = NA + ) + + if (options[["forestPlotPredictionIntervals"]]) + additionalObjects[[tempRow]] <- with(tempPooledEstimate, .maMakeRectangleDataFrame(lCi = lPi, uCi = uPi, row = tempRow, id = tempRow)) + + tempRow <- tempRow + 1 + } + } + + } + + + ### Merge results from estimated marginal means and information panel ---- + if (length(additionalInformation) > 0) { + + # merge additional information + additionalInformation <- do.call(rbind, additionalInformation) + additionalObjects <- do.call(rbind, additionalObjects[!sapply(additionalObjects, is.null)]) + + # adjust y-coordinates + additionalInformation$y <- -additionalInformation$row * relativeRowSize + additionalObjects$y <- -additionalObjects$y * relativeRowSize + + xRangeAddedPanels <- range(c(additionalInformation$lCi, additionalInformation$uCi, additionalObjects$x), na.rm = TRUE) + } else { + xRangeAddedPanels <- NA + } + + # specify x-axis limits + if (options[["forestPlotAuxiliarySetXAxisLimit"]]) { + xBreaks <- jaspGraphs::getPrettyAxisBreaks(c(options[["forestPlotAuxiliarySetXAxisLimitLower"]], options[["forestPlotAuxiliarySetXAxisLimitUpper"]])) + } else { + xBreaks <- jaspGraphs::getPrettyAxisBreaks(range(c(xRangeStudyInformationPanel, xRangeAddedPanels), na.rm = TRUE)) + } + xRange <- range(xBreaks) + + # specify y-axis limits + if (options[["forestPlotStudyInformation"]]) { + yRange <- c(0, max(dfForrest$y) + relativeRowSize + any(leftPanelStudyInformation$title != "")) + } else { + yRange <- c(0, 0) + } + if (length(additionalInformation) > 0) { + yRange[1] <- min(additionalInformation$y) - relativeRowSize + } + if (length(additionalInformation) > 0) { + yRange[1] <- min(c(additionalObjects$y, yRange)) + } + + ### Make the forest plot ---- + plotForest <- ggplot2::ggplot() + + # study information panel estimates + if (options[["forestPlotStudyInformation"]]) { + + # add prediction intervals + if (options[["forestPlotStudyInformationPredictedEffects"]]) { + # dispatch the aes call based on mapping + aesCall <- list( + x = as.name("x"), + y = as.name("y"), + group = as.name("id"), + fill = if (options[["forestPlotMappingColor"]] != "") as.name(options[["forestPlotMappingColor"]]) + ) + geomCall <- list( + data = fitPrediction, + mapping = do.call(ggplot2::aes, aesCall[!sapply(aesCall, is.null)]), + fill = if (options[["forestPlotMappingColor"]] == "") "grey20", + alpha = 0.8 + ) + plotForest <- plotForest + do.call(ggplot2::geom_polygon, geomCall[!sapply(geomCall, is.null)]) + } + + ### add estimates + # dispatch the aes call based on mapping: + aesCall <- list( + x = as.name("effectSize"), + y = as.name("y"), + color = if (options[["forestPlotMappingColor"]] != "") as.name(options[["forestPlotMappingColor"]]), + shape = if (options[["forestPlotMappingShape"]] != "") as.name(options[["forestPlotMappingShape"]]), + size = as.name("weights") + ) + geomCall <- list( + data = dfForrest, + mapping = do.call(ggplot2::aes, aesCall[!sapply(aesCall, is.null)]), + color = if (options[["forestPlotMappingColor"]] == "") options[["forestPlotAuxiliaryPlotColor"]], + shape = if (options[["forestPlotMappingShape"]] == "") 15 + ) + plotForest <- plotForest + do.call(ggplot2::geom_point, geomCall[!sapply(geomCall, is.null)]) + + ggplot2::scale_size(range = c(1, 6) * options[["forestPlotRelativeSizeEstimates"]]) + + + # change scale for shapes to full shapes if used + if (options[["forestPlotMappingShape"]] != "") + plotForest <- plotForest + ggplot2::scale_shape_manual(values = rep(c(15:18, 21:25), length.out = length(unique(dfForrest[[options[["forestPlotMappingShape"]]]])))) + + + ### add CIs + plotForest <- plotForest + ggplot2::geom_errorbarh( + data = dfForrest, + mapping = ggplot2::aes( + xmin = lCi, + xmax = uCi, + y = y + ), + height = 0 + ) + + if (options[["forestPlotStudyInformationSecondaryConfidenceInterval"]]) { + plotForest <- plotForest + ggplot2::geom_errorbarh( + data = dfForrest, + mapping = ggplot2::aes( + xmin = lCi2, + xmax = uCi2, + y = y + ), + color = "darkblue", + height = 0.3 + ) + } + + } + + # add additional information + if (length(additionalInformation) > 0) { + + # dispatch the aes call based on color mapping + if (any(!is.na(additionalObjects$mapColor))) { + plotForest <- plotForest + ggplot2::geom_polygon( + data = additionalObjects[!is.na(additionalObjects$mapColor),], + mapping = ggplot2::aes( + x = x, + y = y, + group = id, + fill = mapColor + ) + ) + } + + if (any(is.na(additionalObjects$mapColor))) { + plotForest <- plotForest + ggplot2::geom_polygon( + data = additionalObjects[is.na(additionalObjects$mapColor),], + mapping = ggplot2::aes( + x = x, + y = y, + group = id, + ) + ) + } + } + + # add vertical line + if (options[["forestPlotAuxiliaryAddVerticalLine"]]) + plotForest <- plotForest + ggplot2::geom_vline(xintercept = options[["forestPlotAuxiliaryAddVerticalLineValue"]], linetype = "dashed") + if (options[["forestPlotAuxiliaryAddVerticalLine2"]]) + plotForest <- plotForest + ggplot2::geom_vline(xintercept = options[["forestPlotAuxiliaryAddVerticalLineValue2"]], linetype = "dotted") + + + ### Make the left information panel ---- + if (length(options[["forestPlotStudyInformationSelectedVariablesSettings"]]) > 0 || length(additionalInformation) > 0) { + + ### determine number of columns and study information + leftPanelStudyInformation <- do.call(rbind.data.frame, options[["forestPlotStudyInformationSelectedVariablesSettings"]]) + + ### compute the total character width + if (options[["forestPlotStudyInformation"]] && length(leftPanelStudyInformation) != 0) { + leftPanelStudyInformationChars <- rbind( + nchar(leftPanelStudyInformation$title), + apply(dfForrest[,leftPanelStudyInformation$value, drop = FALSE], 2, function(x) max(nchar(x), na.rm = TRUE))) + leftPanelStudyInformationChars <- apply(leftPanelStudyInformationChars, 2, max) + 2 + maxCharsLeft <- sum(leftPanelStudyInformationChars) + } else { + leftPanelStudyInformationChars <- 0 + maxCharsLeft <- 0 + } + if (length(additionalInformation) != 0) { + additionalInformationChars <- max(nchar(additionalInformation$label), na.rm = TRUE) + maxCharsLeft <- max(c(maxCharsLeft, additionalInformationChars)) + } else { + additionalInformationChars <- 0 + } + + ### start plotting + plotLeft <- ggplot2::ggplot() + + ### add the subplots + if (options[["forestPlotStudyInformation"]] && length(leftPanelStudyInformation) > 0) { + + # split the columns + if (options[["forestPlotAuxiliaryAdjustWidthBasedOnText"]]) { + leftPanelRelativeWidths <- c(maxCharsLeft - sum(leftPanelStudyInformationChars), leftPanelStudyInformationChars) + leftPanelRelativeWidths[2:length(leftPanelRelativeWidths)] <- leftPanelRelativeWidths[2:length(leftPanelRelativeWidths)] * leftPanelStudyInformation$width + leftPanelRelativeWidths <- leftPanelRelativeWidths / sum(leftPanelRelativeWidths) + leftPanelStudyInformation$xStart <- cumsum(leftPanelRelativeWidths[-length(leftPanelRelativeWidths)]) + leftPanelStudyInformation$xEnd <- cumsum(leftPanelRelativeWidths)[-1] + } else { + leftPanelRelativeWidths <- leftPanelStudyInformation$width / sum(leftPanelStudyInformation$width) + leftPanelStudyInformation$xStart <- c(0, cumsum(leftPanelRelativeWidths[-length(leftPanelRelativeWidths)])) + leftPanelStudyInformation$xEnd <- cumsum(leftPanelRelativeWidths) + } + + # compute study information coordinates + leftPanelStudyInformation$y <- (max(dfForrest$row) + 1) * relativeRowSize + leftPanelStudyInformation$x <- ifelse( + leftPanelStudyInformation$alignment == "left", leftPanelStudyInformation$xStart, ifelse( + leftPanelStudyInformation$alignment == "middle", (leftPanelStudyInformation$xStart + leftPanelStudyInformation$xEnd) / 2, leftPanelStudyInformation$xEnd + )) + + # add titles + plotLeft <- plotLeft + ggplot2::geom_text( + data = leftPanelStudyInformation, + mapping = ggplot2::aes( + x = x, + y = y, + label = title, + hjust = alignment + ), + size = 4 * options[["forestPlotRelativeSizeText"]], + vjust = "midle", + fontface = "bold" + ) + + # add information + if (any(leftPanelStudyInformation$value == options[["forestPlotMappingColor"]])) { + leftPanelStudyDataColored <- data.frame( + x = leftPanelStudyInformation$x[leftPanelStudyInformation$value == options[["forestPlotMappingColor"]]], + y = dfForrest$y, + label = as.character(dfForrest[[options[["forestPlotMappingColor"]]]]), + alignment = leftPanelStudyInformation$alignment[leftPanelStudyInformation$value == options[["forestPlotMappingColor"]]] + ) + plotLeft <- plotLeft + ggplot2::geom_text( + data = leftPanelStudyDataColored, + mapping = ggplot2::aes( + x = x, + y = y, + label = label, + hjust = alignment, + color = label + ), + size = 4 * options[["forestPlotRelativeSizeText"]], + vjust = "midle", + ) + } + if (any(leftPanelStudyInformation$value != options[["forestPlotMappingColor"]])) { + tempVariables <- leftPanelStudyInformation$value[leftPanelStudyInformation$value != options[["forestPlotMappingColor"]]] + leftPanelStudyData <- do.call(rbind.data.frame, lapply(tempVariables, function(variable) { + data.frame( + x = leftPanelStudyInformation$x[leftPanelStudyInformation$value == variable], + y = dfForrest$y, + label = as.character(dfForrest[[variable]]), + alignment = leftPanelStudyInformation$alignment[leftPanelStudyInformation$value == variable] + ) + })) + plotLeft <- plotLeft + ggplot2::geom_text( + data = leftPanelStudyData, + mapping = ggplot2::aes( + x = x, + y = y, + label = label, + hjust = alignment + ), + size = 4 * options[["forestPlotRelativeSizeText"]], + vjust = "midle", + ) + } + + } + + if (length(additionalInformation) > 0) { + + # subset left panel information only + leftPanelAdditionalInformation <- additionalInformation[!is.na(additionalInformation$label),] + leftPanelAdditionalInformation$x <- 1 + leftPanelAdditionalInformation$face[is.na(leftPanelAdditionalInformation$face)] <- "plain" + + # add titles + plotLeft <- plotLeft + ggplot2::geom_text( + data = leftPanelAdditionalInformation, + mapping = ggplot2::aes( + x = x, + y = y, + label = label, + fontface = face + ), + size = 4 * options[["forestPlotRelativeSizeText"]], + hjust = "right", + vjust = "midle", + ) + } + } else { + plotLeft <- NULL + } + ### Make the right information panel ---- + if (.maForestPlotMakeRightPannel(options, additionalInformation)) { + + # estimates and confidence intervales + if (options[["forestPlotEstimatesAndConfidenceIntervals"]]) { + + ### join the est and Cis for the right panel + rightPanelCis <- rbind( + if (options[["forestPlotStudyInformation"]]) { + tempDf <- dfForrest[,c("y", "effectSize", "lCi", "uCi")] + colnames(tempDf) <- c("y", "est", "lCi", "uCi") + tempDf + }, + if (length(additionalInformation) > 0) additionalInformation[,c("y", "est", "lCi", "uCi")] + ) + + # remove all NAs + rightPanelCis <- rightPanelCis[!apply(rightPanelCis[,2:4], 1, function(x) all(is.na(x))),] + + # adjust the number formatings + for (colName in c("est", "lCi", "uCi")) { + rightPanelCis[!is.na(rightPanelCis[,colName]),colName] <- .maFormatDigits( + rightPanelCis[!is.na(rightPanelCis[,colName]),colName], + options[["forestPlotAuxiliaryDigits"]]) + } + + # deal with PIs and CIs separately + rightPanelCis$label <- NA + rightPanelCis$label[ is.na(rightPanelCis$est)] <- with(rightPanelCis[ is.na(rightPanelCis$est), ], paste0("PI [", lCi, ", ", uCi, "]")) + rightPanelCis$label[!is.na(rightPanelCis$est)] <- with(rightPanelCis[!is.na(rightPanelCis$est), ], paste0(est, " [", lCi, ", ", uCi, "]")) + + } else { + rightPanelCis <- NULL + } + + ### tests and weights right panel + rightPanelTestsAndWeights <- rbind( + if (options[["forestPlotStudyInformation"]] > 0 && options[["forestPlotStudyInformationStudyWeights"]]) { + tempDf <- dfForrest[,c("y", "weights")] + tempDf$label <- paste0(sprintf(paste0("%1$.", options[["forestPlotAuxiliaryDigits"]], "f"), tempDf$weights), " %") + tempDf[,c("y", "label")] + }, + if (length(additionalInformation) > 0) { + tempDf <- additionalInformation[,c("y", "test")] + colnames(tempDf) <- c("y", "label") + tempDf + } + ) + rightPanelTestsAndWeights <- rightPanelTestsAndWeights[rightPanelTestsAndWeights$label != "",] + if (length(rightPanelTestsAndWeights) == 0 || nrow(rightPanelTestsAndWeights) == 0) + rightPanelTestsAndWeights <- NULL + + ### compute the total character width + if (!is.null(rightPanelCis)) { + maxCharsRightCis <- max(nchar(rightPanelCis$label)) + } else { + maxCharsRightCis <- 0 + } + if (length(rightPanelTestsAndWeights) != 0) { + maxCharsRightAdd <- max(nchar(rightPanelTestsAndWeights$label)) + } else { + maxCharsRightAdd <- 0 + } + maxCharsRight <- maxCharsRightCis + maxCharsRightAdd + 2 + + + ### start plotting + plotRight <- ggplot2::ggplot() + + ### add the subplots + if (!is.null(rightPanelCis)) { + + rightPanelCis$x <- maxCharsRightCis / maxCharsRight + + # add titles + plotRight <- plotRight + ggplot2::geom_text( + data = rightPanelCis, + mapping = ggplot2::aes( + x = x, + y = y, + label = label + ), + hjust = "right", + family = "mono", + size = 4 * options[["forestPlotRelativeSizeText"]] + ) + } + + if (length(rightPanelTestsAndWeights) > 0) { + + rightPanelTestsAndWeights$x <- (maxCharsRightCis + 2) / maxCharsRight + + # add titles + plotRight <- plotRight + ggplot2::geom_text( + data = rightPanelTestsAndWeights, + mapping = ggplot2::aes( + x = x, + y = y, + label = label + ), + hjust = "left", + family = "mono", + size = 4 * options[["forestPlotRelativeSizeText"]] + ) + } + } else { + plotRight <- NULL + } + + ### adjust axis, themes, and labels ---- + + # fix plotting range + plotForest <- plotForest + ggplot2::coord_cartesian( + xlim = xRange, + ylim = yRange, + expand = FALSE + ) + ggplot2::xlab( + if (options[["forestPlotAuxiliaryEffectLabel"]] != "Effect Size") options[["forestPlotAuxiliaryEffectLabel"]] + else if (options[["transformEffectSize"]] == "none") gettext("Effect Size") + else .maGetOptionsNameEffectSizeTransformation(options[["transformEffectSize"]]) + ) + ggplot2::theme( + axis.line.y = ggplot2::element_blank(), + axis.line.x = ggplot2::element_line(color = "black"), + axis.text.y = ggplot2::element_blank(), + axis.text.x = ggplot2::element_text(color = "black", size = 12 * options[["forestPlotRelativeSizeAxisLabels"]]), + axis.ticks.y = ggplot2::element_blank(), + axis.title.y = ggplot2::element_blank(), + axis.title.x = ggplot2::element_text(color = "black", size = 12 * options[["forestPlotRelativeSizeAxisLabels"]]), + legend.position = "none", + panel.background = ggplot2::element_blank(), + panel.border = ggplot2::element_blank(), + panel.grid.major = ggplot2::element_blank(), + panel.grid.minor = ggplot2::element_blank(), + plot.background = ggplot2::element_blank() + ) + + if (!is.null(plotLeft)) { + plotLeft <- plotLeft + ggplot2::coord_cartesian( + xlim = c(0,1), + ylim = yRange, + expand = FALSE + ) + ggplot2::xlab("") + ggplot2::theme( + axis.line = ggplot2::element_blank(), + axis.text.y = ggplot2::element_blank(), + axis.text.x = ggplot2::element_text(color = NA, size = 12 * options[["forestPlotRelativeSizeAxisLabels"]]), + axis.ticks = ggplot2::element_blank(), + axis.title.y = ggplot2::element_blank(), + axis.title.x = ggplot2::element_text(color = NA, size = 12 * options[["forestPlotRelativeSizeAxisLabels"]]), + legend.position = "none", + panel.background = ggplot2::element_blank(), + panel.border = ggplot2::element_blank(), + panel.grid.major = ggplot2::element_blank(), + panel.grid.minor = ggplot2::element_blank(), + plot.background = ggplot2::element_blank() + ) + } + + if (!is.null(plotRight)) { + plotRight <- plotRight + ggplot2::coord_cartesian( + xlim = c(0,1), + ylim = yRange, + expand = FALSE + ) + ggplot2::xlab("") + ggplot2::theme( + axis.line = ggplot2::element_blank(), + axis.text.y = ggplot2::element_blank(), + axis.text.x = ggplot2::element_text(color = NA, size = 12 * options[["forestPlotRelativeSizeAxisLabels"]]), + axis.ticks = ggplot2::element_blank(), + axis.title.y = ggplot2::element_blank(), + axis.title.x = ggplot2::element_text(color = NA, size = 12 * options[["forestPlotRelativeSizeAxisLabels"]]), + legend.position = "none", + panel.background = ggplot2::element_blank(), + panel.border = ggplot2::element_blank(), + panel.grid.major = ggplot2::element_blank(), + panel.grid.minor = ggplot2::element_blank(), + plot.background = ggplot2::element_blank() + ) + } + + ### adjust panel plot widths + plotsWidths <- c( + if (!is.null(plotLeft)) options[["forestPlotRelativeSizeLeftPanel"]], + options[["forestPlotRelativeSizeMiddlePanel"]], + if (!is.null(plotRight)) options[["forestPlotRelativeSizeRightPanel"]] + ) + if (options[["forestPlotAuxiliaryAdjustWidthBasedOnText"]] && length(plotsWidths) == 3) { + plotsWidths[1] <- plotsWidths[1] * 2 * maxCharsLeft / (maxCharsRight + maxCharsLeft) + plotsWidths[3] <- plotsWidths[3] * 2 * maxCharsRight / (maxCharsRight + maxCharsLeft) + } + # compute ratio of main panel to side panels + if (length(plotsWidths) != 1) { + panelRatio <- sum(c( + if (!is.null(plotLeft)) options[["forestPlotRelativeSizeLeftPanel"]] else 0, + if (!is.null(plotRight)) options[["forestPlotRelativeSizeRightPanel"]] else 0 + )) / options[["forestPlotRelativeSizeMiddlePanel"]] + } + + if (length(plotsWidths) == 1) { + + plotOut <- plotForest + attr(plotOut, "isPanel") <- FALSE + attr(plotOut, "rows") <- tempRow + max(dfForrest$row) + + } else { + + plotOut <- list() + if (!is.null(plotLeft)) + plotOut <- c(plotOut, list(plotLeft)) + plotOut <- c(plotOut, list(plotForest)) + if (!is.null(plotRight)) + plotOut <- c(plotOut, list(plotRight)) + + attr(plotOut, "isPanel") <- TRUE + attr(plotOut, "panelRatio") <- panelRatio + attr(plotOut, "rows") <- tempRow + if(!is.null(dfForrest)) max(dfForrest$row) else 0 + attr(plotOut, "widths") <- plotsWidths + attr(plotOut, "layout") <- matrix(1:length(plotOut), nrow = 1, ncol = length(plotOut), byrow = TRUE) + + } + + return(plotOut) +} +.maForestPlotMakeRightPannel <- function(options, additionalInformation) { + + if (!options[["forestPlotStudyInformation"]] && length(additionalInformation) == 0) + return(FALSE) + if (options[["forestPlotEstimatesAndConfidenceIntervals"]]) + return(TRUE) + if (options[["forestPlotStudyInformation"]] && options[["forestPlotStudyInformationStudyWeights"]]) + return(TRUE) + if (length(additionalInformation) != 0 && + (options[["forestPlotEstimatedMarginalMeansTermTests"]] || options[["forestPlotEstimatedMarginalMeansCoefficientTests"]]) && + options[["forestPlotTestsInRightPanel"]]) + return(TRUE) + else + return(FALSE) +} diff --git a/R/funnelplot.R b/R/funnelplot.R new file mode 100644 index 00000000..c6214370 --- /dev/null +++ b/R/funnelplot.R @@ -0,0 +1,782 @@ +# +# Copyright (C) 2013-2018 University of Amsterdam +# +# This program is free software: you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation, either version 2 of the License, or +# (at your option) any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with this program. If not, see . +# + +FunnelPlot <- function(jaspResults, dataset = NULL, options, ...) { + + if (.fpReady(options)) { + dataset <- .fpCheckDataset(jaspResults, dataset, options) + .fpH1Fits(jaspResults, dataset, options) + } + + # make the funnel plots + .fpPlot(jaspResults, dataset, options) + if (options[["funnelUnderH1EstimatesTable"]]) + .fpPlotEstimatesTable(jaspResults, dataset, options) + + # add the funnel plot asymmetry table + if (options[["funnelPlotAsymmetryTests"]]) + .fpTestFunnelPlotAsymmetryTests(jaspResults, dataset, options) + + return() +} + +.fpDependencies <- c("effectSize", "effectSizeStandardError", "split") +.fpReady <- function(options) { + return(options[["effectSize"]] != "" && options[["effectSizeStandardError"]] != "") +} +.fpCheckDataset <- function(jaspResults, dataset, options) { + + # omit NAs + dataset <- na.omit(dataset) + + # add a warning message + if (!is.null(attr(dataset, "na.action")) && is.null(jaspResults[["missingDataInformation"]])) { + missingDataInformation <- createJaspHtml(gettext("Missing Data Summary")) + missingDataInformation$position <- 0.1 + missingDataInformation$dependOn(c(.fpDependencies, "estimatesMappingColor", "estimatesMappingShape", "studyLabel")) + missingDataInformation$text <- gettextf("The dataset contains missing values: %1$i missing values were removed from the analysis.", length(attr(dataset, "na.action"))) + jaspResults[["missingDataInformation"]] <- missingDataInformation + } + + .hasErrors( + dataset = dataset, + type = c("infinity", "observations", "variance"), + all.target = c( + options[["effectSize"]], + options[["effectSizeStandardError"]] + ), + observations.amount = "< 2", + exitAnalysisIfErrors = TRUE) + + .hasErrors( + dataset = dataset, + seCheck.target = options[["effectSizeStandardError"]], + custom = .maCheckStandardErrors, + exitAnalysisIfErrors = TRUE) + + return(dataset) +} + +.fpH1Fits <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["fitState"]])) + return() + + fitState <- createJaspState() + fitState$dependOn(c(.fpDependencies, "method")) + jaspResults[["fitState"]] <- fitState + + if (options[["split"]] == "") { + + fitState$object <- try(metafor::rma( + yi = dataset[[options[["effectSize"]]]], + sei = dataset[[options[["effectSizeStandardError"]]]], + method = .maGetMethodOptions(options) + )) + + } else { + + splitLevels <- unique(dataset[[options[["split"]]]]) + fits <- lapply(splitLevels, function(splitLevel) { + try(metafor::rma( + yi = dataset[[options[["effectSize"]]]], + sei = dataset[[options[["effectSizeStandardError"]]]], + subset = dataset[[options[["split"]]]] == splitLevel, + method = .maGetMethodOptions(options) + )) + }) + names(fits) <- splitLevels + fitState$object <- fits + } + + return() +} +.fpPlot <- function(jaspResults, dataset, options) { + + if (is.null(jaspResults[["funnelPlotContainer"]])) { + funnelPlotContainer <- createJaspContainer(title = gettext("Funnel Plot")) + funnelPlotContainer$dependOn(c( + .fpDependencies, "studyLabel", + "funnelUnderH0", "funnelUnderH0ParametersFixedMu", "funnelUnderH0ParametersFixedTau", + "funnelUnderH1", "funnelUnderH1Parameters", "funnelUnderH1ParametersFixedMu", "funnelUnderH1ParametersFixedTau", "funnelUnderH1IncludeHeterogeneity", "method", + "funnelUnderH1PowerEnhancement", "funnelUnderH1PowerEnhancementBreaks", + "funnelPredictionInterval", "funnelUnderH0LineType", "funnelUnderH0FillColors", "funnelUnderH1LineType", "funnelUnderH1FillColors", + "invertColors", + "estimatesMappingLabel", "estimatesMappingColor", "estimatesMappingShape", "estimatesLegendPosition", "estimatesMappingLabelOffset" + )) + funnelPlotContainer$position <- 1 + jaspResults[["funnelPlotContainer"]] <- funnelPlotContainer + } else { + funnelPlotContainer <- jaspResults[["funnelPlotContainer"]] + } + + # create a waitting plot + if (!.fpReady(options)) { + tempPlot <- createJaspPlot(width = 550, height = 480) + funnelPlotContainer[["tempPlot"]] <- tempPlot + return() + } + + # create funnel plots + if (options[["split"]] == "") { + + funnelPlot <- createJaspPlot(width = 550, height = 480) + funnelPlotContainer[["funnelPlot"]] <- funnelPlot + + fit <- jaspResults[["fitState"]]$object + if (options[["funnelUnderH1"]] && options[["funnelUnderH1Parameters"]] == "estimated" && jaspBase::isTryError(fit)) + funnelPlot$setError(.fpMetaforTranslateErrorMessage(fit)) + else + funnelPlot$plotObject <- .fpMakeFunnelPlot(jaspResults, dataset, options) + + } else { + + splitLevels <- unique(dataset[[options[["split"]]]]) + for (splitLevel in splitLevels) { + + funnelPlot <- createJaspPlot(title = paste0(options[["split"]], " = ", splitLevel), width = 550, height = 480) + funnelPlotContainer[[splitLevel]] <- funnelPlot + + fit <- jaspResults[["fitState"]]$object[[splitLevel]] + if (options[["funnelUnderH1"]] && options[["funnelUnderH1Parameters"]] == "estimated" && jaspBase::isTryError(fit)) + funnelPlot$setError(.fpMetaforTranslateErrorMessage(fit)) + else + funnelPlot$plotObject <- .fpMakeFunnelPlot(jaspResults, dataset, options, splitLevel = splitLevel) + + } + + } + + return() +} +.fpMakeFunnelPlot <- function(jaspResults, dataset, options, splitLevel = NULL) { + + # extract the funnel levels + if (options[["funnelUnderH0"]] || options[["funnelUnderH1"]]) { + funnelLevels <- .robmaCleanOptionsToPriors(options[["funnelPredictionInterval"]], message = gettext("Funnel plot prediction interval was specified in an incorrect format. Try '(0.90, 0.95, 0.99)'.")) + if (any(is.na(funnelLevels)) || any(funnelLevels <= 0 | funnelLevels >= 1)) + .quitAnalysis(gettext("Funnel plot prediction intervals must be between 0 and 1.")) + if (length(funnelLevels) < 1) + .quitAnalysis(gettext("Funnel plot prediction intervals must be specified.")) + funnelLevels <- (1 - funnelLevels) / 2 + funnelLevels <- sort(funnelLevels) + + # funnel colors + funnelColorsSteps <- 2 * length(funnelLevels) + 1 + funnelColorsSteps <- seq(0, 1, length.out = funnelColorsSteps) + funnelColorsSteps <- funnelColorsSteps[-c(1, length(funnelColorsSteps))] + funnelColors <- paste0("grey", round(funnelColorsSteps * 100)) + + if (options[["invertColors"]]) + funnelColors <- rev(funnelColors) + } + + # data-points + dfPlot <- data.frame( + x = dataset[[options[["effectSize"]]]], + y = dataset[[options[["effectSizeStandardError"]]]] + ) + if (options[["estimatesMappingShape"]] != "") dfPlot$shape <- dataset[[options[["estimatesMappingShape"]]]] + if (options[["estimatesMappingColor"]] != "") dfPlot$color <- dataset[[options[["estimatesMappingColor"]]]] + if (options[["studyLabel"]] != "") dfPlot$label <- dataset[[options[["studyLabel"]]]] + + if (!is.null(splitLevel)) + dfPlot <- dfPlot[dataset[[options[["split"]]]] == splitLevel,] + + # y-axis plotting range (based on the common data set to make them common across figures) + yTicks <- jaspGraphs::getPrettyAxisBreaks(range(c(0, dataset[[options[["effectSizeStandardError"]]]]))) + # a sequence of points must be used if tau is included in the confidence bands (PI is a nonlinear function of se) + ySeqH0 <- if (options[["funnelUnderH0ParametersFixedTau"]] == 0) range(yTicks) else seq(from = min(yTicks), to = max(yTicks), length.out = 100) + ySeqH1 <- if ((options[["funnelUnderH1Parameters"]] == "estimated" && !options[["funnelUnderH1IncludeHeterogeneity"]]) + || (options[["funnelUnderH1Parameters"]] == "fixed" && options[["funnelUnderH1ParametersFixedTau"]] == 0)) + range(yTicks) else seq(from = min(yTicks), to = max(yTicks), length.out = 100) + + ### specify zero-centered funnels + if (options[["funnelUnderH0"]]) { + adjustFunnel0Mean <- options[["funnelUnderH0ParametersFixedMu"]] + adjustFunnel0Heterogeneity <- options[["funnelUnderH0ParametersFixedTau"]] + dfsFunnel0 <- .fpComputeFunnelDf(ySeqH0, adjustFunnel0Mean, adjustFunnel0Heterogeneity, funnelLevels) + } + + ### specify meta-analysis centered funnels + # allow user imputed vs meta-analytic estimated values + if (options[["funnelUnderH1"]]) { + + if (options[["funnelUnderH1Parameters"]] == "fixed") { + adjustFunnel1Mean <- options[["funnelUnderH1ParametersFixedMu"]] + adjustFunnel1Heterogeneity <- options[["funnelUnderH1ParametersFixedTau"]] + } else if (options[["funnelUnderH1Parameters"]] == "estimated"){ + + if (options[["split"]] == "") { + fit <- jaspResults[["fitState"]]$object + } else { + fit <- jaspResults[["fitState"]]$object[[splitLevel]] + } + + adjustFunnel1Mean <- fit$b[1] + adjustFunnel1Heterogeneity <- if(options[["funnelUnderH1IncludeHeterogeneity"]]) sqrt(fit$tau2) else 0 + } + + dfsFunnel1 <- .fpComputeFunnelDf(ySeqH1, adjustFunnel1Mean, adjustFunnel1Heterogeneity, funnelLevels) + + # get maximum x value across all funnels in case of a split + if (options[["split"]] == "" || options[["funnelUnderH1Parameters"]] == "fixed") { + dfsFunnel1XRange <- range(sapply(dfsFunnel1, function(x) x$x)) + } else { + dfsFunnel1XMax <- list() + for (i in seq_along(jaspResults[["fitState"]]$object)) { + # extract each fit + tempFit <- jaspResults[["fitState"]]$object[[i]] + if (jaspBase::isTryError(tempFit)) + next + tempAdjustFunnel1Mean <- tempFit$b[1] + tempAdjustFunnel1Heterogeneity <- if(options[["funnelUnderH1IncludeHeterogeneity"]]) sqrt(tempFit$tau2) else 0 + + # compute the maximum funnel width + tempFitX <- .fpComputeFunnelDf(max(ySeqH1), tempAdjustFunnel1Mean, tempAdjustFunnel1Heterogeneity, max(funnelLevels)) + dfsFunnel1XMax[[i]] <- range(tempFitX[[1]]) + } + dfsFunnel1XRange <- range(unlist(dfsFunnel1XMax)) + } + } + + + ### get x-axis ticks + xTicks <- jaspGraphs::getPrettyAxisBreaks(range(c( + range(dataset[[options[["effectSize"]]]]), + if (options[["funnelUnderH0"]]) range(sapply(dfsFunnel0, function(x) x$x)), + if (options[["funnelUnderH1"]]) dfsFunnel1XRange + ))) + + + ### compute power enhancement + if (options[["funnelUnderH1"]] && options[["funnelUnderH1PowerEnhancement"]]) { + powerEnhancementBreaks <- .robmaCleanOptionsToPriors(options[["funnelUnderH1PowerEnhancementBreaks"]], message = gettext("Power enhancement breaks were specified in an incorrect format. Try '(0.30, 0.50, 0.80)'.")) + if (any(is.na(powerEnhancementBreaks)) || any(powerEnhancementBreaks <= 0.05 | powerEnhancementBreaks >= 1)) + .quitAnalysis(gettext("Power enhancement breaks must be between 0.05 and 1.")) + powerEnhancementBreaks <- sort(powerEnhancementBreaks) + powerEnhancementBreaksZ <- .power_to_z(powerEnhancementBreaks, two.sided = TRUE) + + # add the first and last breaks + powerEnhancementBreaks <- c(0.05, powerEnhancementBreaks, 1) + powerEnhancementBreaksZ <- c(0, powerEnhancementBreaksZ, Inf) + + # compute the se ranges and restrict to the plotting range + powerEnhancementBreaksSe <- abs(adjustFunnel1Mean) / powerEnhancementBreaksZ + powerEnhancementBreaks <- powerEnhancementBreaks[(which.max(powerEnhancementBreaksSe < max(yTicks)) - 1):length(powerEnhancementBreaksSe)] + powerEnhancementBreaksSe <- powerEnhancementBreaksSe[(which.max(powerEnhancementBreaksSe < max(yTicks)) - 1):length(powerEnhancementBreaksSe)] + powerEnhancementBreaksSe[1] <- max(yTicks) + powerEnhancementBreaksLabels <- paste0(powerEnhancementBreaks[-length(powerEnhancementBreaks)] * 100, "% - ", round(powerEnhancementBreaks[-1] * 100, 2), "%") + + # get the colors + powerEnhancementColors <- .getPowerEnhancementColors(length(powerEnhancementBreaksLabels)) + + # create segments + dfsPowerEnhancement <- lapply(seq_along(powerEnhancementBreaksLabels), function(i) { + data.frame( + x = c(min(xTicks), max(xTicks), max(xTicks), min(xTicks)), + y = c(powerEnhancementBreaksSe[i], powerEnhancementBreaksSe[i], powerEnhancementBreaksSe[i+1], powerEnhancementBreaksSe[i+1]), + label = powerEnhancementBreaksLabels[i], + color = powerEnhancementColors[i] + ) + }) + } + + + ### prepare lables + if (options[["studyLabel"]] != "" && options[["estimatesMappingLabel"]] != "none") { + + dfLabels <- dfPlot + + # exclusion of data points outside the funnel (if requested) and alignment with the appropriate funnel + if (options[["estimatesMappingLabel"]] %in% c("outsideH0", "outsideH1")) { + # get the appropriate funnel parameters + tempAdjustMean <- if (options[["estimatesMappingLabel"]] == "outsideH0") adjustFunnel0Mean else adjustFunnel1Mean + tempAdjustHeterogeneity <- if (options[["estimatesMappingLabel"]] == "outsideH0") adjustFunnel0Heterogeneity else adjustFunnel1Heterogeneity + # exclusion of data points outside the funnel + tempDiff <- abs(dfLabels$x - tempAdjustMean) + tempDiff[tempDiff < 1.96 * tempAdjustHeterogeneity] <- 0 + tempZ <- tempDiff / dfLabels$y + dfLabels <- dfLabels[tempZ > max(qnorm(funnelLevels, lower.tail = FALSE)),] + } else { + # use H1 -> H0 -> mean to align the if the funnels are present + tempAdjustMean <- if (options[["funnelUnderH1"]]) adjustFunnel1Mean else if (options[["funnelUnderH0"]]) adjustFunnel0Mean else 0 + } + # specify the position of the labels + dfLabels$position <- ifelse(dfLabels$x < tempAdjustMean, "right", "left") + dfLabels$nudge_x <- ifelse(dfLabels$x < tempAdjustMean, -1, 1) * options[["estimatesMappingLabelOffset"]] + } + + ### specify "background" for the funnel plot + dfBackground <- data.frame( + x = c(min(xTicks), max(xTicks), max(xTicks), min(xTicks)), + y = c(min(yTicks), min(yTicks), max(yTicks), max(yTicks)) + ) + + ### plot + out <- ggplot2::ggplot() + + if (options[["invertColors"]]) + out <- out + ggplot2::geom_polygon( + data = dfBackground, + mapping = ggplot2::aes(x = x, y = y), + fill = "black" + ) + + if (options[["funnelUnderH1"]] && options[["funnelUnderH1PowerEnhancement"]]) { + for (i in seq_along(dfsPowerEnhancement)) { + out <- out + ggplot2::geom_polygon( + data = dfsPowerEnhancement[[i]], + mapping = ggplot2::aes(x = x, y = y), + fill = dfsPowerEnhancement[[i]]$color[1] + ) + } + } + + # add H0 funnel + if (options[["funnelUnderH0"]]) { + + if (options[["funnelUnderH0FillColors"]]) { + for (i in rev(seq_along(dfsFunnel0))) { + out <- out + ggplot2::geom_polygon( + data = dfsFunnel0[[i]], + mapping = ggplot2::aes(x = x, y = y), + fill = scales::alpha(funnelColors[i], .25) + ) + } + } + + if (options[["funnelUnderH0LineType"]]!= "none") { + for (i in rev(seq_along(dfsFunnel0))) { + out <- out + ggplot2::geom_line( + data = dfsFunnel0[[i]], + mapping = ggplot2::aes(x = x, y = y), + linetype = options[["funnelUnderH0LineType"]] + ) + } + } + } + + # add H1 funnel + if (options[["funnelUnderH1"]]) { + + if (options[["funnelUnderH1FillColors"]]) { + for (i in rev(seq_along(dfsFunnel1))) { + out <- out + ggplot2::geom_polygon( + data = dfsFunnel1[[i]], + mapping = ggplot2::aes(x = x, y = y), + fill = scales::alpha(funnelColors[i], .25) + ) + } + } + + if (options[["funnelUnderH1LineType"]]!= "none") { + for (i in rev(seq_along(dfsFunnel1))) { + out <- out + ggplot2::geom_line( + data = dfsFunnel1[[i]], + mapping = ggplot2::aes(x = x, y = y), + linetype = options[["funnelUnderH1LineType"]] + ) + } + } + } + + # add estimates + pointAes <- list( + x = as.name("x"), + y = as.name("y") + ) + if (options[["estimatesMappingShape"]] != "") pointAes$shape <- as.name("shape") + if (options[["estimatesMappingColor"]] != "") pointAes$color <- as.name("color") + if (options[["estimatesMappingColor"]] != "") pointAes$fill <- as.name("color") + + out <- out + jaspGraphs::geom_point( + data = dfPlot, + mapping = do.call(ggplot2::aes, pointAes) + ) + + if (options[["estimatesMappingShape"]] != "") + out <- out + ggplot2::labs(shape = options[["estimatesMappingShape"]]) + if (options[["estimatesMappingColor"]] != "") + out <- out + ggplot2::labs(color = options[["estimatesMappingColor"]], fill = options[["estimatesMappingColor"]]) + + + # add labels + if (options[["studyLabel"]] != "" && options[["estimatesMappingLabel"]] != "none") { + out <- out + + ggplot2::geom_text( + data = dfLabels, + mapping = ggplot2::aes(x = x, y = y, label = label, hjust = position), + nudge_x = dfLabels$nudge_x, + + ) + } + + out <- out + jaspGraphs::scale_x_continuous(breaks = xTicks, limits = range(xTicks), name = gettext("Effect Size")) + + # add secondary axis whenever needed + if (options[["funnelUnderH1"]] && options[["funnelUnderH1PowerEnhancement"]]) { + out <- out + ggplot2::scale_y_reverse( + breaks = rev(yTicks), limits = rev(range(yTicks)), name = gettext("Standard Error"), + sec.axis = ggplot2::dup_axis( + breaks = rev(powerEnhancementBreaksSe), + labels = rev(paste0(round(c(.z_to_power(abs(adjustFunnel1Mean) / powerEnhancementBreaksSe[1]), powerEnhancementBreaks[-1]) * 100), "% ")), name = gettext("Power")) + ) + } else { + out <- out + ggplot2::scale_y_reverse(breaks = rev(yTicks), limits = rev(range(yTicks)), name = gettext("Standard Error")) + } + + + out <- out + + jaspGraphs::geom_rangeframe(sides = if (options[["funnelUnderH1"]] && options[["funnelUnderH1PowerEnhancement"]]) "blr" else "bl") + + jaspGraphs::themeJaspRaw(legend.position = options[["estimatesLegendPosition"]]) + + return(out) +} +.fpPlotEstimatesTable <- function(jaspResults, dataset, options) { + + if (!is.null(jaspResults[["funnelParametersTable"]]) || options[["funnelUnderH1Parameters"]] != "estimated") + return() + + # estimates table + funnelParametersTable <- createJaspTable(gettext("H₁ Funnel Parameter Estimates")) + funnelParametersTable$position <- 2 + funnelParametersTable$dependOn(c(.fpDependencies, "funnelUnderH1Parameters", "method", "funnelUnderH1EstimatesTable")) + jaspResults[["funnelParametersTable"]] <- funnelParametersTable + + if (options[["split"]] != "") + funnelParametersTable$addColumnInfo(name = "split", title = options[["split"]], type = "string") + funnelParametersTable$addColumnInfo(name = "k", title = gettext("Estimates"), type = "integer") + funnelParametersTable$addColumnInfo(name = "mu", title = gettext("\U03BC"), type = "number") + if (!.maGetMethodOptions(options) %in% c("EE", "FE")) + funnelParametersTable$addColumnInfo(name = "tau", title = gettext("\U1D70F"), type = "number") + + + if (!.fpReady(options)) + return() + + if (options[["split"]] == "") { + + fit <- jaspResults[["fitState"]]$object + if (jaspBase::isTryError(fit)) { + fitSummary <- data.frame(k = NA, mu = NA) + funnelParametersTable$addFootnote(.fpMetaforTranslateErrorMessage(fit), symbol = gettext("The funnel plot parameter estimation failed with the following error: ")) + } else { + fitSummary <- data.frame( + k = fit$k, + mu = fit$b[1] + ) + if (!.maGetMethodOptions(options) %in% c("EE", "FE")) + fitSummary$tau <- sqrt(fit$tau2) + } + + } else { + + fits <- jaspResults[["fitState"]]$object + fitSummary <- do.call(rbind, lapply(fits, function(fit) { + + if (jaspBase::isTryError(fit)) { + funnelParametersTable$addFootnote(.fpMetaforTranslateErrorMessage(fit), symbol = gettext("The funnel plot parameter estimation failed with the following error: ")) + if (.maGetMethodOptions(options) %in% c("EE", "FE")) + return(data.frame(k = NA, mu = NA)) + else + return(data.frame(k = NA, mu = NA, tau = NA)) + } + + tempFitSummary <- data.frame( + k = fit$k, + mu = fit$b[1] + ) + if (!.maGetMethodOptions(options) %in% c("EE", "FE")) + tempFitSummary$tau <- sqrt(fit$tau2) + + return(tempFitSummary) + })) + fitSummary <- data.frame(split = names(fits), fitSummary) + + } + + funnelParametersTable$setData(fitSummary) + + return() +} +.fpTestFunnelPlotAsymmetryTests <- function(jaspResults, dataset, options) { + + if (is.null(jaspResults[["funnelPlotAsymmetryTests"]])) { + funnelAsymetryTests <- createJaspContainer(title = gettext("Funnel Plot Asymmetry Tests")) + funnelAsymetryTests$dependOn(c(.fpDependencies, "funnelPlotAsymmetryTests")) + funnelAsymetryTests$position <- 3 + jaspResults[["funnelAsymetryTests"]] <- funnelAsymetryTests + } else { + funnelAsymetryTests <- jaspResults[["funnelAsymetryTests"]] + } + + ### create table for each test + + # meta-regression + if (options[["funnelPlotAsymmetryTests"]] && is.null(funnelAsymetryTests[["metaRegressionTable"]])) { + + metaRegressionTable <- createJaspTable(gettext("Meta-Regression Test for Funnel Plot Asymmetry")) + metaRegressionTable$position <- 1 + metaRegressionTable$dependOn("funnelPlotAsymmetryTestsMetaRegression") + funnelAsymetryTests[["metaRegressionTable"]] <- metaRegressionTable + + if (options[["split"]] != "") + metaRegressionTable$addColumnInfo(name = "split", title = options[["split"]], type = "string") + metaRegressionTable$addColumnInfo(name = "k", title = gettext("Estimates"), type = "integer") + metaRegressionTable$addColumnInfo(name = "z", title = gettext("z"), type = "number", overtitle = gettext("Asymmetry Test")) + metaRegressionTable$addColumnInfo(name = "p", title = gettext("p"), type = "pvalue", overtitle = gettext("Asymmetry Test")) + metaRegressionTable$addColumnInfo(name = "est", title = gettext("Estimate"), type = "number", overtitle = gettext("Limit Estimate")) + metaRegressionTable$addColumnInfo(name = "lCI", title = gettext("Lower 95% CI"), type = "number", overtitle = gettext("Limit Estimate")) + metaRegressionTable$addColumnInfo(name = "uCI", title = gettext("Upper 95% CI"), type = "number", overtitle = gettext("Limit Estimate")) + + if (.fpReady(options)) { + if (options[["split"]] == "") { + + fit <- jaspResults[["fitState"]]$object + fitTest <- try(metafor::regtest(fit)) + fitSummary <- .dpExtractAsymmetryTest(fitTest, testType = "metaRegression") + + if (jaspBase::isTryError(fit)) + metaRegressionTable$addFootnote(.fpMetaforTranslateErrorMessage(fit), symbol = .fpAsymmetryTestErrorMessage()) + else if (jaspBase::isTryError(fitTest)) + metaRegressionTable$addFootnote(fitTest, symbol = .fpAsymmetryTestErrorMessage()) + + metaRegressionTable$setData(fitSummary) + + } else { + + fits <- jaspResults[["fitState"]]$object + fitSummaries <- do.call(rbind, lapply(seq_along(fits), function(i) { + + fitTest <- try(metafor::regtest(fits[[i]])) + fitSummary <- .dpExtractAsymmetryTest(fitTest, testType = "metaRegression") + fitSummary$split <- names(fits)[i] + + if (jaspBase::isTryError(fits[[i]])) + metaRegressionTable$addFootnote(.fpMetaforTranslateErrorMessage(fits[[i]]), symbol = .fpAsymmetryTestErrorMessage(names(fits)[i])) + else if (jaspBase::isTryError(fitTest)) + metaRegressionTable$addFootnote(fitTest, symbol = .fpAsymmetryTestErrorMessage(names(fits)[i])) + + return(fitSummary) + })) + + metaRegressionTable$setData(fitSummaries) + + } + } + } + + # weighted regression + if (options[["funnelPlotAsymmetryTestsWeightedRegression"]] && is.null(funnelAsymetryTests[["weightedRegressionTable"]])) { + + weightedRegressionTable <- createJaspTable(gettext("Weighted Regression Test for Funnel Plot Asymmetry")) + weightedRegressionTable$position <- 2 + weightedRegressionTable$dependOn("funnelPlotAsymmetryTestsWeightedRegression") + funnelAsymetryTests[["weightedRegressionTable"]] <- weightedRegressionTable + + if (options[["split"]] != "") + weightedRegressionTable$addColumnInfo(name = "split", title = options[["split"]], type = "string") + weightedRegressionTable$addColumnInfo(name = "k", title = gettext("Estimates"), type = "integer") + weightedRegressionTable$addColumnInfo(name = "t", title = gettext("t"), type = "number", overtitle = gettext("Asymmetry Test")) + weightedRegressionTable$addColumnInfo(name = "df", title = gettext("df"), type = "integer", overtitle = gettext("Asymmetry Test")) + weightedRegressionTable$addColumnInfo(name = "p", title = gettext("p"), type = "pvalue", overtitle = gettext("Asymmetry Test")) + weightedRegressionTable$addColumnInfo(name = "est", title = gettext("Estimate"), type = "number", overtitle = gettext("Limit Estimate")) + weightedRegressionTable$addColumnInfo(name = "lCI", title = gettext("Lower 95% CI"), type = "number", overtitle = gettext("Limit Estimate")) + weightedRegressionTable$addColumnInfo(name = "uCI", title = gettext("Upper 95% CI"), type = "number", overtitle = gettext("Limit Estimate")) + + if (.fpReady(options)) { + if (options[["split"]] == "") { + + fit <- jaspResults[["fitState"]]$object + fitTest <- try(metafor::regtest(fit, model = "lm")) + fitSummary <- .dpExtractAsymmetryTest(fitTest, testType = "weightedRegression") + + if (jaspBase::isTryError(fit)) + weightedRegressionTable$addFootnote(.fpMetaforTranslateErrorMessage(fit), symbol = .fpAsymmetryTestErrorMessage()) + else if (jaspBase::isTryError(fitTest)) + weightedRegressionTable$addFootnote(fitTest, symbol = .fpAsymmetryTestErrorMessage()) + + weightedRegressionTable$setData(fitSummary) + + } else { + + fits <- jaspResults[["fitState"]]$object + fitSummaries <- do.call(rbind, lapply(seq_along(fits), function(i) { + + fitTest <- try(metafor::regtest(fits[[i]], model = "lm")) + fitSummary <- .dpExtractAsymmetryTest(fitTest, testType = "weightedRegression") + fitSummary$split <- names(fits)[i] + + if (jaspBase::isTryError(fits[[i]])) + weightedRegressionTable$addFootnote(.fpMetaforTranslateErrorMessage(fits[[i]]), symbol = .fpAsymmetryTestErrorMessage(names(fits)[i])) + else if (jaspBase::isTryError(fitTest)) + weightedRegressionTable$addFootnote(fitTest, symbol = .fpAsymmetryTestErrorMessage(names(fits)[i])) + + return(fitSummary) + })) + + weightedRegressionTable$setData(fitSummaries) + + } + } + } + + # rank correlation + if (options[["funnelPlotAsymmetryTestsRankCorrelation"]] && is.null(funnelAsymetryTests[["rankCorrelationTable"]])) { + + rankCorrelationTable <- createJaspTable(gettext("Rank Correlation Test for Funnel Plot Asymmetry")) + rankCorrelationTable$position <- 3 + rankCorrelationTable$dependOn("funnelPlotAsymmetryTestsRankCorrelation") + funnelAsymetryTests[["rankCorrelationTable"]] <- rankCorrelationTable + + if (options[["split"]] != "") + rankCorrelationTable$addColumnInfo(name = "split", title = options[["split"]], type = "string") + rankCorrelationTable$addColumnInfo(name = "k", title = gettext("Estimates"), type = "integer") + rankCorrelationTable$addColumnInfo(name = "tau", title = gettext("\U1D70F"), type = "number") + rankCorrelationTable$addColumnInfo(name = "p", title = gettext("p"), type = "pvalue") + + if (.fpReady(options)) { + + if (options[["split"]] == "") { + + fit <- jaspResults[["fitState"]]$object + fitTest <- try(metafor::ranktest(fit)) + fitSummary <- .dpExtractAsymmetryTest(fitTest, testType = "rankCorrelation") + + if (jaspBase::isTryError(fit)) + rankCorrelationTable$addFootnote(.fpMetaforTranslateErrorMessage(fit), symbol = .fpAsymmetryTestErrorMessage()) + else if (jaspBase::isTryError(fitTest)) + rankCorrelationTable$addFootnote(fitTest, symbol = .fpAsymmetryTestErrorMessage()) + else + fitSummary$k <- fit$k + + rankCorrelationTable$setData(fitSummary) + + } else { + + fits <- jaspResults[["fitState"]]$object + fitSummaries <- do.call(rbind, lapply(seq_along(fits), function(i) { + + fitTest <- try(metafor::ranktest(fits[[i]])) + fitSummary <- .dpExtractAsymmetryTest(fitTest, testType = "rankCorrelation") + fitSummary$split <- names(fits)[i] + + if (jaspBase::isTryError(fits[[i]])) { + fitSummary$k <- NA + rankCorrelationTable$addFootnote(.fpMetaforTranslateErrorMessage(fits[[i]]), symbol = .fpAsymmetryTestErrorMessage(names(fits)[i])) + } else if (jaspBase::isTryError(fitTest)) { + fitSummary$k <- fits[[i]]$k + rankCorrelationTable$addFootnote(fitTest, symbol = .fpAsymmetryTestErrorMessage(names(fits)[i])) + } else { + fitSummary$k <- fits[[i]]$k + } + + return(fitSummary) + })) + + rankCorrelationTable$setData(fitSummaries) + + } + } + } + + return() +} + +.fpComputeFunnelDf <- function(seSeq, mean, heterogeneity, funnelLevels) { + dfs <- list() + for (i in seq_along(funnelLevels)) { + tempZ <- qnorm(funnelLevels[i], lower.tail = FALSE) + dfs[[i]] <- data.frame( + x = c(rev(mean - tempZ * sqrt(heterogeneity^2 + seSeq^2)), mean + tempZ * sqrt(heterogeneity^2 + seSeq^2)), + y = c(rev(seSeq), seSeq), + p = 2 * funnelLevels[i], + lvl = 1 - 2 * funnelLevels[i] + ) + } + return(dfs) +} +.fpAsymmetryTestErrorMessage <- function(level = NULL) { + if (is.null(level)) + return(gettext("The funnel plot asymmetry test failed with the following error: ")) + else + return(gettextf("The funnel plot asymmetry test at level %1$s failed with the following error: ", level)) +} +.fpMetaforTranslateErrorMessage <- function(fit) { + if (grepl("did not converge", fit)) + return(gettext("The meta-analytic model did not converge. Try modifying the 'Method' option for the 'Funnel under H\U2081' settings.")) + else + return(fit) +} +.dpExtractAsymmetryTest <- function(fitTest, testType) { + if (testType == "metaRegression") { + return(data.frame( + k = if (jaspBase::isTryError(fitTest)) NA else fitTest$fit$k, # nobs will be fixed in the next release + z = if (jaspBase::isTryError(fitTest)) NA else fitTest$zval, + p = if (jaspBase::isTryError(fitTest)) NA else fitTest$pval, + est = if (jaspBase::isTryError(fitTest)) NA else fitTest$est, + lCI = if (jaspBase::isTryError(fitTest)) NA else fitTest$ci.lb, + uCI = if (jaspBase::isTryError(fitTest)) NA else fitTest$ci.ub + )) + } else if (testType == "weightedRegression") { + return(data.frame( + k = if (jaspBase::isTryError(fitTest)) NA else nobs(fitTest$fit), + t = if (jaspBase::isTryError(fitTest)) NA else fitTest$zval, + df = if (jaspBase::isTryError(fitTest)) NA else fitTest$dfs, + p = if (jaspBase::isTryError(fitTest)) NA else fitTest$pval, + est = if (jaspBase::isTryError(fitTest)) NA else fitTest$est, + lCI = if (jaspBase::isTryError(fitTest)) NA else fitTest$ci.lb, + uCI = if (jaspBase::isTryError(fitTest)) NA else fitTest$ci.ub + )) + } else if (testType == "rankCorrelation") { + return(data.frame( + tau = if (jaspBase::isTryError(fitTest)) NA else fitTest$tau, + p = if (jaspBase::isTryError(fitTest)) NA else fitTest$pval + )) + } +} + +# compute power enhancement contours (lifted from zcurve) +.power_to_z <- function(power, alpha = .05, a = stats::qnorm(alpha/2,lower.tail = FALSE), two.sided = TRUE, nleqslv_control = list(xtol = 1e-15, maxit = 300, stepmax = .5)){ + if(a < 0)stop("a must be >= 0") + if(is.null(a) & is.null(alpha))stop("Either 'alpha' or 'a' must be provided") + if(is.null(alpha) & !is.null(a))alpha <- stats::pnorm(a, lower.tail = FALSE)*2 + if(alpha < 0 | alpha > 1)stop("alpha must be >= 0 & <= 1") + if(!all(sapply(power, function(x)x >= alpha & x <= 1)))stop("power must be >= alpha & <= 1") + sapply(power, function(pow)nleqslv::nleqslv(.5, .solve_power_to_z, power = pow, a = a, two.sided = two.sided, control = nleqslv_control)$x) +} +.solve_power_to_z <- function(x, power, a, two.sided){ + y = numeric(1) + y = .z_to_power(z = x, a = a, two.sided = two.sided) - power + y +} +.z_to_power <- function(z, alpha = .05, a = stats::qnorm(alpha/2,lower.tail = FALSE), two.sided = TRUE){ + if(!all(sapply(z, function(x)x >= 0)))stop("z must be >= 0") + if(a < 0)stop("a must be >= 0") + if(is.null(a) & is.null(alpha))stop("Either 'alpha' or 'a' must be provided") + if(is.null(alpha) & !is.null(a))alpha <- stats::pnorm(a, lower.tail = FALSE)*2 + if(alpha < 0 | alpha > 1)stop("alpha must be >= 0 & <= 1") + if(two.sided){ + return(1 - stats::pnorm(a, z, 1) + stats::pnorm(-a, z, 1)) + }else{ + return(1 - stats::pnorm(a, z, 1)) + } +} + +# get the color scale +.getPowerEnhancementColors <- function(n) scales::gradient_n_pal(RColorBrewer::brewer.pal(n = 11, name = "RdYlGn"))(seq(0, 1, length.out = n)) diff --git a/R/multilevelmetaanalysis.R b/R/multilevelmetaanalysis.R deleted file mode 100644 index 928c8c0c..00000000 --- a/R/multilevelmetaanalysis.R +++ /dev/null @@ -1,813 +0,0 @@ -# -# Copyright (C) 2013-2018 University of Amsterdam -# -# This program is free software: you can redistribute it and/or modify -# it under the terms of the GNU General Public License as published by -# the Free Software Foundation, either version 2 of the License, or -# (at your option) any later version. -# -# This program is distributed in the hope that it will be useful, -# but WITHOUT ANY WARRANTY; without even the implied warranty of -# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -# GNU General Public License for more details. -# -# You should have received a copy of the GNU General Public License -# along with this program. If not, see . -# - - - - -MultilevelMetaAnalysis <- function(jaspResults, options, dataset, state=NULL) { - #options(contrasts = list(unordered = "contr.Treatment", ordered = "contr.poly")) - options = Filter(function(x) !all(x=="" | is.na(x)), options) # only keep set components - do.call(multi_meta_analysis, c(list(jaspResults=jaspResults, dataset=dataset, state=state, debug=FALSE), options)) - - return() -} - -multi_meta_analysis <- - function(jaspResults, dataset, state, debug=FALSE, - ES_name, # effect size variable (continuous) - SE_name, # standard error of effect size (continuous, strictly positive) - inner_grouping = "1", # factor that distinguishes outcomes in a multivariate model - outer_grouping = NA, # factors that specify hierarchy of otherwise independent samples - fixed_predictor_terms = "1", # nested list with predictor terms (including potential interaction terms) - labels_variable, - method = c("REML", "ML"), - inner_cov_struct = c("CS", "HCS", "ID", "DIAG", "AR", "HAR"), - anova_table = TRUE, - intercept = TRUE, - coeftest_type = c('z', 't'), - add_robust_qtest = TRUE, - FE_coef_table = TRUE, - fit_measures_table = TRUE, - varComp_params_table = TRUE, - FE_vcov_table = FALSE, - funnelPlotAsymmetry = FALSE, - ranktest_table = FALSE, - regtest_table = FALSE, - diagnostics_table = FALSE, - failsafe_n_table = FALSE, - funnel_plot = FALSE, - forest_plot = TRUE, - residual_dependent_plot = FALSE, - profile_plot = FALSE, - emmeans_table = FALSE, - ... - ) - { - ### Help functions #### - # unfortunately, inside JASP the requirement to use namespaces causes - # dplyr- and other operators not to exist... Hence, it is/they are define here - `%>%` <- dplyr::`%>%` - # `cout` makes html output and debug easier - cout <- function(...) paste(capture.output(...), collapse = "\n") - - ### Restore Previous State? #### - res <- if (!is.null(jaspResults[['res']])) jaspResults[['res']]$object else NULL - #jaspResults[['bla']] <- createJaspHtml(cout(res), "pre", title='Stored object', position=1) - - - ### Default jaspResults #### - - jaspResults$title = "Multivariate/Multilevel Meta-Analysis" - - if (anova_table && is.null(res)) { - jaspResults[['anova_table']] = createJaspTable( title = "Analysis of Variance Table", position = 20, - data.frame(rowname=c("Test of Residual Heterogeneity","Omnibus test of Effects"), - Q=".", df=".", p=".") %>% tibble::column_to_rownames("rowname") - ) - jaspResults[['anova_table']]$dependOnOptions("anova_table") - } - - - ### Verify and standardize input #### - - if (missing(ES_name) || missing(SE_name)) { - return() - } - ES_name = head(ES_name, 1) - SE_name = head(SE_name, 1) - - if (!missing(inner_grouping)) - inner_grouping = as.character(substitute(inner_grouping)) - - if (!missing(labels_variable)) - labels_variable = as.character(substitute(labels_variable)) - - - ### Verify and standardize input #### - - if (missing(ES_name) || missing(SE_name)) { - return() - } - ES_name = head(ES_name, 1) - SE_name = head(SE_name, 1) - - if (!missing(inner_grouping)) - inner_grouping = as.character(substitute(inner_grouping)) - - if (!missing(labels_variable)) - labels_variable = as.character(substitute(labels_variable)) - - - ### Extract data to data frame #### - - if (is.null(dataset)) { - #dataset <- .readDataSetToEnd(columns.as.numeric=variables) - #dataset.factors <- .readDataSetToEnd(columns=variables) - - - dataset_pred = dataset_ESSE = dataset_grouping = dataset_labels = NULL - - if (!missing(fixed_predictor_terms)) - dataset_pred <- .readDataSetToEnd(columns = unique(unlist(fixed_predictor_terms))) - - if (!missing(ES_name) && !missing(SE_name)) - dataset_ESSE = .readDataSetToEnd(columns.as.numeric = c(ES_name, SE_name)) - - if (!missing(outer_grouping)) { - - if (!missing(inner_grouping)) - dataset_grouping = .readDataSetToEnd(columns.as.factor = c(inner_grouping, outer_grouping)) - else - dataset_grouping = .readDataSetToEnd(columns.as.factor = outer_grouping) - - } - - if (!missing(labels_variable)) - dataset_labels = .readDataSetToEnd(columns.as.factor = labels_variable) - - #if (debug) jaspResults[['ES data']] = createJaspTable("Debug: ES/V Data", dataset_ESSE) - #if (debug) jaspResults[['pred data']] = createJaspTable("Debug: Predictors Data", dataset_pred) - #if (debug) jaspResults[['group data']] = createJaspTable("Debug: Grouping Data", dataset_grouping) - #if (debug) jaspResults[['label data']] = createJaspTable("Debug: Label Data", dataset_labels) - - args = c(list(dataset_ESSE), list(dataset_pred), list(dataset_grouping), list(dataset_labels)) - dataset = do.call(cbind, Filter(Negate(is.null), args)) - - } - - if (debug) jaspResults[['raw data']] = createJaspTable("Debug: Raw Data", dataset) - - ### Check data #### - - #.hasErrors(data = dataset, type = c("observations", "infinity")) - dataErrors <- - c( - verify_that(dataset[ES_name], is.numeric, is.finite, not.constant), - verify_that(dataset[SE_name], is.numeric, is.finite, is.positive) - ) - - - - if (length(dataErrors) > 0) { - - message = '

Conditions not met:
  • bla

' - message = gsub("bla", dataErrors %>% paste(names(.), ., collapse="\n
  • "), message) - jaspResults[["error_message"]] <- createJaspHtml(message, - elementType = "div",title = "Data problems", position = 5) - return() - - } - - - ### Build model #### - - if (is.null(res)) { - - # construct model formulas - - fixed_formula = as.formula(paste(ES_name, "~", paste(lapply(lapply(fixed_predictor_terms,unlist), paste, collapse = ":"), collapse = " + "))) # e.g.: ES ~ x1 + x2 + x2:x3 - random_formula = as.formula(paste(" ~ ", inner_grouping, " | ", paste(outer_grouping, collapse = "/"))) # e.g.: ~ test_type | district / school - - if (debug) jaspResults[['predictor_terms']] = createJaspHtml(paste(capture.output(fixed_predictor_terms), collapse="\n"), "pre", title="Predictor terms") - - # construct fitting call - - call = quote(metafor::rma.mv(yi = yi ~ 1, V = vi, data = dataset)) - - call$yi = fixed_formula - call$V = as.name(SE_name) - - if (! missing(outer_grouping)) call$random = random_formula - if (! missing(labels_variable)) call$slab = as.name(labels_variable) - if (! missing(method)) call$method = method[1] - if (! missing(inner_cov_struct)) call$struct = inner_cov_struct[1] - if (! missing(intercept)) call$intercept = intercept - if (! missing(coeftest_type)) call$test = coeftest_type[1] - - # do call fitting call - - res <- try(eval(call)) - - #jaspResults[['output']] = createJaspHtml(paste(c(capture.output(print(call)), capture.output(res)), collapse = "\n"), "pre", title = "Elementary output", position=10) - - if (inherits(res, "try-error")) return() - - # store the result as a state - jaspResults[['res']] <- - createJaspState(object = res, title = "Meta-analysis fit object", dependencies = - c("ES_name","SE_name","fixed_predictor_terms","outer_grouping","inner_cov_struct", "method", - "intercept","coeftest_type","labels_variable") - ) - - - if (debug) jaspResults[['call']] = createJaspHtml(paste(capture.output(call), collapse = "\n"), "pre", title="Debug: Call") - if (debug) jaspResults[['vars']] = createJaspHtml(paste(capture.output({cat("labels: ", labels_variable)}), collapse = "\n"), "pre", title="Debug: Call") - - } - - - - ### Set Output Title #### - jaspResults$title <- capture.output(summary(res))[2] - - - - ### Prepare Q-tests table output #### - - if (anova_table) { - - jaspResults[['anova_table']] <- - createJaspTable( title = "Analysis of Variance Table", position = 20, - (function(object, add_robust = FALSE, ...){ - - # Omnibus - qstat <- unlist(object[c('QE','QM')]) - df <- c(object$k - object$p, object$m) - pval <- unlist(object[c('QEp','QMp')]) - name <- c("Test of Residual Heterogeneity","Omnibus test of Fixed Effects") - qtable <- data.frame(` ` = name, `Q` = qstat, `df` = df, `p`= pval, check.names = FALSE) - rownames(qtable) = name - qtable <- qtable[1, , drop=FALSE] - - if (add_robust && !is.null(object$mf.g)) { - rob = metafor::robust(object, object$mf.g$outer) - - qstat <- unlist(rob[c('QE','QM')]) - df <- c(rob$k - rob$p, rob$m) - pval <- unlist(rob[c('QEp','QMp')]) - name <- c("Robust Test of Residual Heterogeneity","Robust Omnibus test of Fixed Effects") - qtabler <- data.frame(` ` = name, `Q` = qstat, `df` = df, `p`= pval, check.names = FALSE) - rownames(qtabler) = name - qtable <- rbind(qtable, qtabler[-1,, drop = FALSE]) - } - - - cleanUpColNames <- . %>% - stringr::str_replace_all("Pr\\(.+","p") %>% - stringr::str_replace_all("Chisq value", "Q") %>% - stringr::str_replace_all("Df","df") - - anova_df = ANOVA.rma(res, data=dataset) - heading = attr(anova_df,"heading") - anova_df = anova_df %>% tibble::rownames_to_column() %>% dplyr::rename(` `=rowname) - colnames(anova_df) = colnames(anova_df) %>% cleanUpColNames - - structure(rbind(anova_df[,c(1,3,2,4)], qtable), heading = heading) - - })(res, add_robust = FALSE) -> anova_df - ) - - jaspResults[['anova_table']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['anova_table']]$dependOnOptions("anova_table") - - jaspResults[['anova_table']]$setColTypes(list(` ` = "string", `Q` = "number", `df` = "number", `p` = "number")) - jaspResults[['anova_table']]$setColFormats(list(` ` = "", `Q` = "sf:4", `df` = "sf:2", `p` = "dp:4")) - jaspResults[['anova_table']]$addFootnote(message = attr(anova_df,"heading")[2], symbol = "", colNames="Q") - - } - - ### Prepare Coefficients Table Output #### - - if (FE_coef_table && is.null(jaspResults[['coef']])) { - - jaspResults[['coef']] = createJaspTable("Fixed Effects Coefficients", position = 30, - (function(object, ...){ - test = if (exists('test')) test else 'z' - coefdf = coef(summary(object)) - colnames(coefdf) = c('Estimate', 'Standard Error', test, 'p', 'Lower Bound', 'Upper Bound') - rownames(coefdf) = gsub("intrcpt", "(Intercept)", rownames(coefdf)) - coefdf %>% tibble::rownames_to_column() %>% dplyr::rename(` ` = rowname) - })(res)) - - jaspResults[['coef']]$setColFormats(c("", "sf:5", "sf:5", "sf:5", "dp:5","sf:5","sf:5")) - jaspResults[['coef']]$setColTypes(c("string", rep("number", 6))) - - jaspResults[['coef']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['coef']]$dependOnOptions("FE_coef_table") - - # Add footnotes to the analysis result - - jaspResults[['coef']]$addFootnote(message = "Wald test.", colNames=if (exists('test')) test else 'z') - - # Add citation reference list - - jaspResults[['coef']]$addCitation("Viechtbauer, W. (2010). Conducting meta-analyses in R with the metafor package. Journal of - Statistical Software, 36(3), 1-48. URL: http://www.jstatsoft.org/v36/i03/") - - - } - - - - ### Prepare Model fit table output #### - - #jaspResults[['fitmeasures']] <- NULL - if (fit_measures_table && is.null(jaspResults[['fitmeasures']])) { - clearUpNames <- . %>% - gsub("logLik","log Likelihood", .) %>% - gsub(":","", .) - - jaspResults[['fitmeasures']] <- - createJaspTable("Fit measures", position = 40, - (function(object, ...) { - fitdf = metafor::fitstats(res) %>% as.data.frame - rownames(fitdf) = rownames(fitdf) %>% clearUpNames - fitdf %>% tibble::rownames_to_column() %>% dplyr::rename(` `=rowname) - })(res) - ) - - jaspResults[['fitmeasures']]$setColFormats(c("", "sf:5")) - jaspResults[['fitmeasures']]$setColTypes(c("string", "number")) - - jaspResults[['fitmeasures']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['fitmeasures']]$dependOnOptions("fit_measures_table") - - } - - - - ### Prepare Residuals Variance Components Parameters #### - - if (debug) jaspResults[['extract']] <- createJaspHtml(title="myRMAprint(res)", text = paste(capture.output(myRMAprint(res)), collapse="\n"), elementType = "pre") - - #jaspResults[['variance_components']] <- NULL - if (varComp_params_table && is.null(jaspResults[['variance_components']])) { - - jaspResults[['variance_components']] <- - (function(varComp){ - - vcTableNamesCleanUp <- . %>% - gsub("tau", "τ", .) %>% - gsub("sigma", "σ", .) %>% - gsub("rho", "ρ", .) %>% - gsub("phi", "φ", .) %>% - gsub("gamma", "γ", .) %>% - gsub("\\^(\\d+)", "\\1", .) %>% - gsub("estim", "Estimate", .) %>% - gsub("sqrt", "√ Estimate", .) %>% - gsub("k.lvl|nlvls", "Number of levels", .) %>% - gsub("fixed", "Fixed", .) %>% - gsub("level", "Level",.) %>% - gsub("X(.+)", "\\1", .) %>% - gsub("\\.(\\S+)", "\\1", .) %>% - gsub("factor", "Factor", .) - - vctmp = varComp - tmp = createJaspContainer(gettext("Variance Components")) - tmp[['structure']] = createJaspHtml(text = - paste("
      ", - paste("
    • ", - c( - vctmp$structure$grouping, - paste("Inner covariance structure:", paste(vctmp$structure$inner.cov.struct, collapse = ", ")) - ), - collapse = "
    • "), - " -
    "), - title="Covariance Model") - for (nm in names(vctmp)[-1]) { - print(nm) - tmpTable = vctmp[[nm]] %>% dplyr::select(-dplyr::matches("^X$")) - names(tmpTable) = names(tmpTable) %>% vcTableNamesCleanUp - rownames(tmpTable) = rownames(tmpTable) %>% vcTableNamesCleanUp - tmpTable = tmpTable %>% tibble::rownames_to_column() %>% dplyr::rename(` `=rowname) - tmp[[nm]] = createJaspTable(nm, data = tmpTable) - tmp[[nm]]$setColFormats(c("", rep("sf:5", ncol(tmpTable)))) - tmp[[nm]]$setColTypes(c("string", rep("number", ncol(tmpTable)), `Number of Levels`="integer", Level="string")) - } - tmp - })(extractRMAVarComp(res)) - - - jaspResults[['variance_components']]$position = 50 - - jaspResults[['variance_components']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['variance_components']]$dependOnOptions("varComp_params_table") - - - } - - - - ### Prepare Coefficient Covariance Matrix #### - - #jaspResults[['FixedEffectsParameterCovariance']] <- NULL - if (FE_vcov_table && is.null(jaspResults[['FixedEffectsParameterCovariance']])) { - - jaspResults[['FixedEffectsParameterCovariance']] <- - createJaspTable("Fixed Effects Estimates Covariance Matrix", position= 60, - (function(object, ...){ - - vcovTableNamesCleanUp <- . %>% - stringr::str_replace_all("intrcpt", "Intercept") %>% - stringr::str_replace_all("\\[", " [") - - V = vcov(object) - rownames(V) = rownames(V) %>% vcovTableNamesCleanUp - colnames(V) = colnames(V) %>% vcovTableNamesCleanUp - - V %>% as.data.frame() %>% tibble::rownames_to_column() %>% dplyr::rename(` `=rowname) - })(res) -> vcov_df - ) #%>% jasp_as_html() - - jaspResults[['FixedEffectsParameterCovariance']]$setColFormats(c("", rep("sf:5", nrow(vcov_df)))) - jaspResults[['FixedEffectsParameterCovariance']]$setColTypes(c("string", rep("number", nrow(vcov_df)))) - - jaspResults[['FixedEffectsParameterCovariance']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['FixedEffectsParameterCovariance']]$dependOnOptions("FE_vcov_table") - - } - - - ### Prepare Tests for Funnel plot asymmetry #### - - #jaspResults[['funnel_asymmetry_test']] <- NULL - if (funnelPlotAsymmetry && is.null(jaspResults[['funnel_asymmetry_test']])) { - - - jaspResults[['funnel_asymmetry_test']] <- - createJaspTable("Tests for Funnel Plot Asymmetry", position=70, - (function(object, ...) { - - df = data.frame('Statistic' = numeric(), 'p' = numeric()) - - if (ranktest_table) { - # Prepare Kendall's Rank Correlation Test for testing Funnel plot asymmetry - kendall = metafor::ranktest(object) - df = rbind(df, data.frame('Statistic' = kendall$tau, 'p' = kendall$p)) - rownames(df)[1] = "Kendall's tau" - } - - if (regtest_table && FALSE) { - # Prepare Egger's test for Funnel plot asymmetry ('test for publication bias') - egger = purrr::safely(metafor::regtest)(res) - df = rbind(df, data.frame('Statistic' = NA, 'p' = NA)) - rownames(df)[2] = "Egger's regression test (z)" - } - - df %>% tibble::rownames_to_column() %>% dplyr::rename(` `=rowname) - })(res) - ) #%>% jasp_as_html() - - jaspResults[['funnel_asymmetry_test']]$setColFormats(c("", "sf:5", "dp:5")) - jaspResults[['funnel_asymmetry_test']]$setColTypes(c("string", "number", "number")) - - jaspResults[['funnel_asymmetry_test']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['funnel_asymmetry_test']]$dependOnOptions("funnelPlotAsymmetry") - - if (regtest_table) - jaspResults[['funnel_asymmetry_test']]$addFootnote(message = "Egger's test is not yet implemented.", symbol = "(!)", colNames="") - - - } - - - - - ### Prepare Casewise diagnostics table #### - - # jaspResults[['diagnostics']] <- NULL - if (diagnostics_table && is.null(jaspResults[['diagnostics']])) { - - jaspResults[['diagnostics']] <- - createJaspTable("Case Wise Influence Diagnostics", position = 80, - (function(object, ...) { - - #source("~/Desktop/Arnoud Multilevel Meta-analysis/quick.influence.R") - - qiTableNamesCleanUp <- . %>% - stringr::str_to_title() %>% - stringr::str_replace_all(".+pval", "p") %>% - stringr::str_replace("Hatvalues","Hat Values") %>% - paste(., Reduce(paste0, purrr::rep_along(., " "), accumulate = TRUE), sep="") # add increasing number of spaces to fool createJaspTable - - qi = quick.influence(object) - colnames(qi) = colnames(quick.influence(res)) %>% qiTableNamesCleanUp - rownames(qi) = paste(rownames(qi), ifelse(rowSums(qi[,c(2,4,6)] < .05) > 0, "*", "")) - - qi %>% tibble::rownames_to_column() %>% dplyr::rename(` `=rowname) - })(res) - ) #%>% jasp_as_html() - - jaspResults[['diagnostics']]$setColFormats(c("", "sf:5", "dp:5", "sf:5", "dp:5", "sf:5", "dp:5")) - jaspResults[['diagnostics']]$setColTypes(c("string", "number", "number", "number", "number", "number", "number")) - jaspResults[['diagnostics']]$dependOnOptions("diagnostics_table") - - jaspResults[['diagnostics']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['diagnostics']]$dependOnOptions("diagnostics_table") - - # Markup influential cases in a footnote - - jaspResults[['diagnostics']]$addFootnote(message = "Potentially influential.", symbol = "*", colNames="") - - } - - ### Prepare Fail-safe N diagnostics table #### - - #jaspResults[['fsn']] <- NULL - if (failsafe_n_table) { - - jaspResults[['fsn']] <- - createJaspTable("Fail-safe N", position = 90, - (function(object, ...) { - # we want to call fsn(yi = yi, vi = vi, data = data) with the right arguments: - rmacall= object$call - call = quote(metafor::fsn(yi = yi ~ 1, vi = vi, data = dataset)) - call$yi = as.name(all.vars(rmacall$yi)[1]) # deals with both single variable names as well as formulas - call$vi = as.name(all.vars(rmacall$V)[1]) # deals with both single variable names as well as formulas - FSN = eval(call) - df = data.frame(`Fail-safe N` = FSN$fsnum, `Target Significance Level` = FSN$alph, p=FSN$p, check.names = FALSE) - row.names(df) = paste(FSN$type, "method") - df - })(res) - ) #%>% jasp_as_html() - - jaspResults[['fsn']]$setColFormats(c("", "", "sf:2", "sf:5")) - jaspResults[['fsn']]$setColTypes(c("integer", "number", "number")) - - jaspResults[['fsn']]$addFootnote(message = "Fail-safe-N procedures are controversial.") - jaspResults[['fsn']]$addFootnote(message = "Rosenthal's method.") - - jaspResults[['fsn']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['fsn']]$dependOnOptions("failsafe_n_table") - - } - - - - - ### Prepare Plot Output #### - - if (is.null(jaspResults[['plots']])) { - jaspResults[['plots']] <- createJaspContainer(gettext("Plots"), position = 100) - jaspResults[['plots']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['plots']]$dependOnOptions(c("forest_plot","funnel_plot","residual_dependent_plot","profile_plot")) - } - jaspResultsPlots <- jaspResults[['plots']] - - # plot forest plot - - if (forest_plot && is.null(jaspResultsPlots[['forest_plot']])) { - jaspResultsPlots[['forest_plot']] <- - createJaspPlot(function() metafor::forest(res), title = "Forest plot", height=16*nrow(dataset), width=500) - - jaspResultsPlots[['forest_plot']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResultsPlots[['forest_plot']]$dependOnOptions("forest_plot") - } - - # plot funnel plot - - if (funnel_plot && is.null(jaspResultsPlots[['plot_funnel']])) { - jaspResultsPlots[['plot_funnel']] <- - createJaspPlot(function() metafor::funnel(res), title = "Funnel plot", aspectRatio = 1 ) - - jaspResultsPlots[['plot_funnel']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResultsPlots[['plot_funnel']]$dependOnOptions("funnel_plot") - } - - # plot residuals vs dependent diagnostic plot - - #jaspResultsPlots[['plot_residual_dependent']] <- NULL - if (residual_dependent_plot && is.null(jaspResultsPlots[['plot_residual_dependent']] )) { - - jaspResultsPlots[['plot_residual_dependent']] <- - createJaspPlot(title = "Fitted vs Dependent and Residual vs Dependent", plot = - data.frame(Dependent = res$yi, Fitted = fitted(res), Residual = residuals(res)) %>% - tidyr::gather(what, value, -Dependent) %>% - ggplot2::ggplot(ggplot2::aes(x = Dependent, y = value)) + ggplot2::geom_point(alpha=.5) + ggplot2::geom_smooth() + - ggplot2::labs(title = "") + ggplot2::facet_wrap(~what, scales="free") - ) - - jaspResultsPlots[['plot_residual_dependent']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResultsPlots[['plot_residual_dependent']]$dependOnOptions("residual_dependent_plot") - - } - - # profile plot: diagnostic plot for tau parameter - - #jaspResultsPlots[['plot_profile']] <- NULL - if (profile_plot && !is.null(jaspResults[['plots']])) { - jaspResultsPlots[['plot_profile']] <- - createJaspPlot(function() profile(res), title = "Profile plot for Random Effects parameters") - - jaspResultsPlots[['plot_profile']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResultsPlots[['plot_profile']]$dependOnOptions("profile_plot") - - } - - - - ### Prepare Fixed Effects EMMEANS #### - - if (debug) jaspResults[['conditionals']] = createJaspHtml(text = paste("\nfactors in model: ", paste(names(Filter(Negate(is.numeric), dataset)), collapse=", "), "\n\nvariable names: ", paste(colnames(dataset), collapse = ", ")), elementType="pre", title = "Debug: Factors in the model") - - #jaspResults[['emmeans']] = NULL - if (emmeans_table) { - - jaspResults[['emmeans']] = createJaspTable("Estimated Marginal Means", position = 45, - data = (function(object, ...){ - cout <- function(...) paste(capture.output(...), collapse = "\n") - cleanUpNames = . %>% - stringr::str_replace("emmean", "Marginal Mean") %>% - stringr::str_replace("SE", "Standard Error") %>% - stringr::str_replace("lower.CL", "Lower Bound") %>% - stringr::str_replace("upper.CL", "Upper Bound") - - conditionals = intersect(all.vars(object$call$yi), names(Filter(Negate(is.numeric), dataset))) # names(dataset %>% dplyr::select_if(is.factor)) - ret = data.frame(` `=c(), `Marginal Means`=c(), `Standard Error`=c(), `Lower Bound`=c(), `Upper Bound`=c(), check.names = FALSE) - if (!is.null(conditionals) && length(conditionals) > 0) { - myformula = as.formula(paste("~1+",paste(conditionals, collapse="+"))) - #jaspResults[['emmeans_formula']] = createJaspHtml(cout({print(myformula); dataset}),"pre",title="EMMEANS formula") - ret = try(emmeans.rma(object, myformula, dataset)) - if (!inherits(ret, "try-error")) - colnames(ret) = colnames(ret) %>% cleanUpNames - else - jaspResults[['emmeans_results']] = createJaspHtml(cout({ret}),"pre",title="EMMEANS results") - } - ret - })(res) - ) - - jaspResults[['emmeans']]$setColFormats(c("", "sf:5", "sf:5", "sf:5", "sf:5", "sf:5")) - jaspResults[['emmeans']]$setColTypes(c("string", "number", "number", "number", "number")) - jaspResults[['emmeans']]$copyDependenciesFromJaspObject(jaspResults[['res']]) - jaspResults[['emmeans']]$dependOnOptions("emmeans_table") - - } - - ### Prepare Fixed Effects Contrasts #### - } - - - - - - -{ # utility functions - verify_that <- function(x, ...) { - funs = list(...) - if (length(funs) > 0) { - - names(funs) = setdiff(all.vars(match.call()), all.vars(match.call()$x)) - tests = rapply(funs, function(fun) sapply(x, fun), classes = "function", how = 'replace') - Filter(length, lapply(tests, function(x) names(x)[!x])) - } - } - not.constant <- function(x) stats::var(as.numeric(x)) > 0 - all.finite <- function(x) all(base::is.finite(x)) - is.positive <- function(x) all(x > 0) - is.negative <- function(x) all(x < 0) - non.positive <- function(x) all(x <= 0) - non.negative <- function(x) all(x >= 0) -} - -{ # Functions for extracting variance components - reinterpret.data.frame <- function(object) { - zz <- textConnection("foo", "w"); on.exit(close(zz)) - write.table(object, sep=",",file = zz) - close(zz) - zz = textConnection(foo,"r") - bok <- read.csv(zz) - bok - } - - # `%>%` <- magrittr::`%>%` - # myRMAprint <- deparse(metafor::print.rma.mv) %>% - # gsub("\\.print\\.out", "metafor:::.print.out", .) %>% - # gsub("invisible\\(\\)", "invisible(list(fit_stats = if(exists('fs')) fs else NA, variance_components= if(!exists('VC')) list() else VC, res_table=res.table))", .) %>% - # gsub("\\.pval\\(", "format(", .) %>% - # gsub("\\.format\\.btt\\(", "I(", .) %>% - # gsub("print\\(vc", "my_counter <- if(!exists('my_counter')){ 1 }else{ my_counter+1}; if(!exists('VC')) VC = list(); VC[[my_counter]] = print(vc", .) %>% - # parse(text = .) %>% - # eval() - - extractRMAVarComp <- function(object, ...) { - text_output = capture.output(outp <- myRMAprint(object, digits=18)) - varComp <- rapply(outp, reinterpret.data.frame, classes = "matrix", how="replace")$variance_components - - struct = list(inner.cov.struct = object$struct, grouping = Filter(function(x) grepl("inner|outer",x), text_output)) - structure(c(list(structure = struct), `Estimates ` = varComp), text_output= text_output) - } -} - - - -{ ##### Help functions to produce anova tables for 'rma.mv' objects and do automatic model selection ##### - - ## Fix a the metafor limitation that you cannot use step() - RMA.mv = function(formula, ...) { - call = rmacall = match.call(); - rmacall[[1]] = as.name("rma.mv"); - rmacall$mods = formula; - rmacall$formula = NULL; - fit = eval(rmacall); - fit$rmacall = fit$call - fit$call = call; - fit$terms = terms(formula); - fit$formula = formula; - class(fit) = c("RMA_mv", class(fit)) - fit - } - extractAIC.RMA_mv = function(object, scale, k = 2, ...) { - class(object) = class(object)[-1] - c(sum(hatvalues(object)), AIC(object)) - } - update.RMA_mv = function(object, formula., ..., evaluate = TRUE) { - update.default(object, formula., ..., evaluate = evaluate) - } - - ANOVA.rma <- function(object, data = object$model) { - formula <- as.formula(object$call[[2]]) - # in stats:::anova.lm 'asgn' is extracted as: - # p1=1:object$rank; object$assign[qr.lm(object)$pivot][p1] - asgn <- attr(model.matrix(formula, data = data), "assign") # coefficient group indicators - eff <- split(1:sum(!object$coef.na), asgn[!object$coef.na]) - names(eff) <- terms(as.formula(object$call[[2]])) %>% labels %>% c("(Intercept)", .) - as_anova_row = function(x) { - if (x$test == 'z') - data.frame(Df=x$m, `Chisq value` = x$QM, `Pr(>X^2)` = x$QMp, check.names = FALSE) - else - data.frame(Df1 = x$m, Df2 = x$dfs, `F value` = x$QM, `Pr(>F)` = x$QMp, check.names = FALSE) - } - lapply(eff, function(btt) anova(object, btt = btt) %>% as_anova_row) %>% - do.call(rbind, .) %>% - structure(heading = c("Analysis of Variance Table\n", paste("Response:", deparse(formula[[2L]]))), - class = c("anova", "data.frame")) - } - - ANOVA <- function(object, ...) UseMethod("ANOVA") - get_rank <- function(object, ...) UseMethod("get_rank") - get_rank.default <- function(object, ...) object$rank - get_rank.rma <- function(object, ...) sum(!object$coef.na) - get_assign <- function(object, ...) UseMethod("get_assign") - get_assign.default <- function(object, ...) {p1=1:object$rank; object$assign[qr.lm(object)$pivot][p1]} - get_assign.rma <- function(object, ...) { - formula <- formula(object) - asgn <- attr(model.matrix(formula, ...), "assign") # coefficient group indicators - asgn[!object$coef.na] - } - terms.rma <- function(object, ...) terms(formula(object)) - formula.rma <- function(object, ...) as.formula(object$call$yi) - - ANOVA.mipo <- function(object, mids.object, ...) { - # ANOVA tables for mice's mipo object returned by pool() - ffit <- mids.object - object1 = ffit$analyses[[1]] - p1 <- 1:get_rank(object1, ...) - asgn <- get_assign(object1, ...) - eff <- split(p1, asgn) - names(eff) <- terms(ffit$analyses[[1]]) %>% labels %>% c("(Intercept)", .) - as_anova_row <- function(i) { - #Df1 = length(i) - #Df2 = mean(object$df[i]) # does this make sense at all??? - #F_value = drop(b %*% Sigma.b.inv %*% b) * Df1 / Df2 - #data.frame(Df1 = Df1, Df2 = Df2, `F value` = F_value, - # `Pr(>F)` = 1-pf(F_value, Df1, Df2), check.names = FALSE) - res <- wald.test(object, i) - data.frame(Df1 = res$parameter['Df1'], Df2 = res$parameter['Df2'], `F value` = res$statistic, - `Pr(>F)` = res$p.value, check.names = FALSE) - } - lapply(eff, as_anova_row) %>% - do.call(rbind, .) %>% - structure(heading = c("Analysis of Variance Table\n", paste("Response:", deparse(formula(object1)[[2]]))), class = c('anova', 'data.frame')) - } - wald.test <- function(object, ...) UseMethod("wald.test") - wald.test.mipo <- function(object, i, useUbar=FALSE) { - Df1 <- length(i) - k <- Df1 - m <- object$m - Qbar <- object$qbar[i] - Q0 <- structure(rep(0,k), .Names = names(Qbar)) - r1 <- (1 + 1/m) * sum(diag(object$b[i,i] %*% solve(object$ubar[i,i]))) / k - V <- if (useUbar) object$ubar[i,i] else object$t[i,i] - w1 <- (1 + r1)^(-1) * t(Q0 -Qbar) %*% solve(V) %*% (Q0 - Qbar) / k - a <- k * m - v1 <- if (a > 4) 4 + (a-4)*(1 + (1-2/a)/r1)^2 else 0.5*a*(1+a/r1)^2 - Df2 <- v1 - structure(list(statistic = c(`F`=w1), parameter = c(`Df1`=Df1,`Df2`=Df2), p.value = 1-pf(w1,Df1,Df2), - estimate = Qbar, null.value = Q0, alternative = "Not all coefficients equal their null value", - method=sprintf("Wald test on coefficients (using the %s variance)", if (useUbar) - "Within" else "Total"), data.name = deparse(substitute(object))), class="htest") - } - - - contr.simple <- function(n, contrasts = TRUE, sparse = FALSE) - { # define a simple contrasts function (compares each level to the reference level) - t(MASS::ginv(contr.sum(n, contrasts, sparse))) - } - -} diff --git a/R/quick.influence.R b/R/quick.influence.R deleted file mode 100644 index d81f423f..00000000 --- a/R/quick.influence.R +++ /dev/null @@ -1,59 +0,0 @@ -quick.rstudent <- function(x, ...) { # the metafor::rstudent is weirdly slow... - # formula's used from Steven's (1995), which disappeared in the newest edition of the book Stevens (2015) - h = hatvalues(x) - n = length(h) - p = sum(h) - df.resid = n - p - 1 - e = resid(x) - sigma = sqrt(sum(e^2) / df.resid) - rstud = e / sqrt(1-h) / sigma - tval = rstud * sqrt((n-p-1) / (n-p-rstud^2)) - structure(rstud, t.value = tval, p.value = 2*pt(-abs(tval), df.resid), df=df.resid) -} - -hat.significance <- function(x, h = if (inherits(x, "numeric")) x else hatvalues(x)) { - nms = if (!is.null(names(h))) names(h) else seq_along(h) - n = length(h) - p = sum(h) - df = n - p - statistic = (n-p) * (h - 1/n) / ((1-h) * (p-1)) # F-values - structure(h, statistic = statistic, df=c(df1 = p-1, df2 = n-p), p.value = pf(statistic, p-1, n-p, lower.tail = FALSE)) -} - -mahalanobis.significance <- function(x) { - require(MASS) - .X = model.matrix(x) - df = qr(.X)$rank - mahdist = mahalanobis(.X,colMeans(.X), MASS::ginv(cov(.X)), inverted = T) - p.mahdist = pchisq(mahdist, df, lower.tail = FALSE) - structure(mahdist, statistic = mahdist, df=df, p.value = p.mahdist) -} - -quick.influence <- function(x, ...) { - rstud = quick.rstudent(x) - p.rstud = attr(rstud, 'p.value') - hat = hat.significance(x) - p.hat = attr(hat, 'p.value') - mahdist = mahalanobis.significance(x) - p.mahdist = attr(mahdist, 'p.value') - structure( - data.frame(#` ` = "|", - studentized = rstud, stud.pval = p.rstud, #` ` = marks[findInterval(p.rstud, cutof)], - hatvalues = hat, hat.pval=p.hat, #` `= marks[findInterval(p.hat, cutof)], - mahalanobis = mahdist, manh.pval = p.mahdist, #` ` = marks[findInterval(p.mahdist, cutof)], - check.names=FALSE), - class = c("quick.influence", "data.frame")) -} - -print.quick.influence <- function(x, ...) { - marks = c('*** \u23B9 ','** \u23B9 ','* \u23B9 ','. \u23B9 ',' \u23B9 ') - cutof = c(0,.001,.01,.05,.1,1) - M = with(x, data.frame(` ` = "\u23B8", - studentized = studentized, `p-value` = stud.pval, ` ` = marks[findInterval(stud.pval, cutof)], - hatvalues = hatvalues, `p-value` = hat.pval, ` ` = marks[findInterval(hat.pval, cutof)], - mahalanobis = mahalanobis, `p-value` = manh.pval, ` ` = marks[findInterval(manh.pval, cutof)], - check.names = FALSE) - ) - rownames(M) = rownames(x) - print(M, ...) -} diff --git a/R/robustbayesianmetaanalysis.R b/R/robustbayesianmetaanalysis.R index 9b4266df..81485e24 100644 --- a/R/robustbayesianmetaanalysis.R +++ b/R/robustbayesianmetaanalysis.R @@ -120,7 +120,7 @@ RobustBayesianMetaAnalysis <- function(jaspResults, dataset, options, state = NU args = .robmaMapOptionsToPriors(optionsPrior, parameter) )) } -.robmaCleanOptionsToPriors <- function(x) { +.robmaCleanOptionsToPriors <- function(x, message = gettext("The priors for publication bias were set incorrectly.")) { x <- trimws(x, which = "both") x <- trimws(x, which = "both", whitespace = "c") @@ -134,7 +134,7 @@ RobustBayesianMetaAnalysis <- function(jaspResults, dataset, options, state = NU x <- x[x != ""] if (anyNA(as.numeric(x))) - .quitAnalysis(gettext("The priors for publication bias were set incorrectly.")) + .quitAnalysis(message) return(as.numeric(x)) } .robmaEvalOptionsToPriors <- function(x) { diff --git a/inst/Description.qml b/inst/Description.qml index 494f3d71..3fb4cb72 100644 --- a/inst/Description.qml +++ b/inst/Description.qml @@ -7,6 +7,7 @@ Description title : qsTr("Meta-Analysis") description: qsTr("Synthesize evidence across multiple studies") requiresData: false + preloadData: true icon: "meta-analysis.svg" version : "0.19.2" author: "JASP Team" @@ -14,10 +15,33 @@ Description website: "jasp-stats.org" license: "GPL (>= 2)" + + GroupTitle + { + title: qsTr("Miscellaneous") + icon: "meta-analysis.svg" + } + + Analysis + { + menu: qsTr("Effect Size Computation") + title: qsTr("Effect Size Computation") + func: "EffectSizeComputation" + requiresData: true + } + + Analysis + { + menu: qsTr("Funnel Plot") + title: qsTr("Funnel Plot") + func: "FunnelPlot" + requiresData: true + } + GroupTitle { - title: qsTr("Classical") - icon: "meta-analysis.svg" + title: qsTr("Classical") + icon: "meta-analysis.svg" } Analysis @@ -28,6 +52,14 @@ Description requiresData: true } + Analysis + { + menu: qsTr("Meta-Analysis (Multilevel/Multivariate)") + title: qsTr("Classical Meta-Analysis (Multilevel/Multivariate)") + func: "ClassicalMetaAnalysisMultilevelMultivariate" + requiresData: true + } + Analysis { menu: qsTr("Prediction Model Performance") @@ -59,8 +91,8 @@ Description GroupTitle { - title: qsTr("Bayesian") - icon: "meta-analysis-bayesian.svg" + title: qsTr("Bayesian") + icon: "meta-analysis-bayesian.svg" } Analysis diff --git a/inst/Upgrades.qml b/inst/Upgrades.qml index 5446fdb8..8b454072 100644 --- a/inst/Upgrades.qml +++ b/inst/Upgrades.qml @@ -71,33 +71,13 @@ Upgrades Upgrade { functionName: "ClassicalMetaAnalysis" - fromVersion: "0.16.4" - toVersion: "0.17" + fromVersion: "0.19.1" + toVersion: "0.19.2" - // ClassicalMetaAnalysis.qml - ChangeRename { from: "dependent"; to: "effectSize" } - ChangeRename { from: "wlsWeights"; to: "effectSizeSe" } - ChangeRename { from: "studyLabels"; to: "studyLabel" } - ChangeRename { from: "includeConstant"; to: "interceptTerm" } - - // ClassicalMetaAnalysisStatistics.qml - ChangeRename { from: "regressionCoefficientsEstimates"; to: "coefficientEstimate" } - ChangeRename { from: "regressionCoefficientsConfidenceIntervals"; to: "coefficientCi" } - ChangeRename { from: "regressionCoefficientsConfidenceIntervalsInterval"; to: "coefficientCiLevel" } - ChangeRename { from: "test"; to: "estimateTest" } - ChangeRename { from: "regressionCoefficientsCovarianceMatrix"; to: "covarianceMatrix" } - ChangeRename { from: "modelFit"; to: "fitMeasure" } - ChangeRename { from: "rSquaredChange"; to: "funnelPlotRankTestAsymmetry" } - ChangeRename { from: "funnelPlotAsymmetryTest"; to: "funnelPlotRegressionTestAsymmetry" } - ChangeRename { from: "residualsParameters"; to: "residualParameter" } - - // ClassicalMetaAnalysisDiagnostics.qml - ChangeRename { from: "trimFillPlot"; to: "trimFillAnalysis" } - ChangeRename { from: "plotResidualsPredicted"; to: "profilePlot" } - ChangeRename { from: "plotResidualsDependent"; to: "diagnosticPlot" } - ChangeRename { from: "plotResidualsQQ"; to: "diagnosticQqPlot" } - ChangeRename { from: "plotResidualsCovariates"; to: "failSafeN" } - ChangeRename { from: "residualsCasewiseDiagnostics"; to: "casewiseDiagnostics" } + ChangeIncompatible + { + msg: qsTr("Results of this analysis cannot be updated. The analysis was created with an older version of JASP and the analysis options are not longer compatible. Please, redo the analysis with the updated module or download the 0.19.1 version of JASP to rerun or edit the analysis.") + } } Upgrade { diff --git a/inst/help/ClassicalMetaAnalysis.md b/inst/help/ClassicalMetaAnalysis.md deleted file mode 100644 index 9ad5724d..00000000 --- a/inst/help/ClassicalMetaAnalysis.md +++ /dev/null @@ -1,11 +0,0 @@ -Classical Meta-Analysis -========================== - -You can read this blog to have more information about Meta Analysis. - -Additional documentation will be available in future releases of JASP. - -### R Packages ---- -- metafor -- stats diff --git a/inst/help/ClassicalMetaAnalysis_nl.md b/inst/help/ClassicalMetaAnalysis_nl.md deleted file mode 100644 index dce460fd..00000000 --- a/inst/help/ClassicalMetaAnalysis_nl.md +++ /dev/null @@ -1,11 +0,0 @@ -Klassieke Meta-Analyse -========================== - -Om meer informatie te verkrijgen over Meta-Analyses kan dit bestand worden gelezen: blog. - -Aanvullende documentatie zal beschikbaar zijn in toekomstige versies van JASP. - -### R Packages ---- -- metafor -- stats diff --git a/inst/help/EffectSizeComputation.md b/inst/help/EffectSizeComputation.md new file mode 100644 index 00000000..989a59db --- /dev/null +++ b/inst/help/EffectSizeComputation.md @@ -0,0 +1,382 @@ +Effect Size Computation +========================== +-------------------------- +This analysis allows users to compute effect sizes based on the design and measurement of the studies. In case multiple types of designs and measurements are included in the data set, the user can specify the order in which the effect sizes are calculated (the effect size from the following option is filled in only if it was computed in the previous step). + +Already included effect sizes can be passed forward using the Reported effect sizes option. + +The selected effect size can be computed only for a subset of the dataset using the Subset indicator variable.. + +See [metafor's documentation](https://wviechtb.github.io/metafor/reference/escalc.html) for more detail about the effect sizes. + + +#### Design + +The design dropdown allows users to select the type of effect size based on the design of the original studies. + +- Independent groups: This option is for analyzing data comparing two independent groups. The groups may be experimentally defined or naturally occurring. +- Variable association: This option is for examining the direction and strength of the association between two variables measured concurrently and/or without manipulation by experimenters. +- Single group: This option is for summarizing characteristics of individual groups based on either quantitative or dichotomous variables. +- Repeated measures (or matched groups): This option is for assessing change within a single group over time or comparing two matched samples. +- Other: This option includes specific effect sizes that do not fit into the other categories, such as reliability or partial correlations. +- Reported effect sizes: This option allows to directly pass effect sizes and their standard errors or condifidence interval if they were already reported in the original studies. (When condifence interval is passed, normal approximation is used to compute the standard error.) + +#### Measurement + +The measurement dropdown allows users to select the type effect size based on the measurement in the original studies. + +- Quantitative: This option is for analyzing data where the measurement is on a continuous scale (e.g., means and standard deviations). +- Binary: This option is for analyzing data where the measurement is dichotomous (e.g., success/failure, yes/no). +- Counts per time: This option is for analyzing data where the measurement is an event count over a specific time period (e.g., number of incidents per year). +- Mixed: This option is for analyzing data that combines different types of measurements (e.g., a mix of continuous and dichotomous variables). + +The available measurement options depend on the selected design type: +- Independent groups: Quantitative / Binary / Counts per time / Mixed +- Variable association: Quantitative / Binary / Mixed +- Single group: Quantitative / Binary / Counts per time +- Repeated measures/matched groups: Quantitative / Binary + +The measurement dropdown is enabled only when a design type other than "Other" is selected. + + +#### Effect size +The Effect size dropdown allows users to select the specific effect size or outcome measure to be calculated based on the chosen design and measurement type. The available options are dynamically adjusted according to the selected design and measurement type. + +#### Independent groups +- Quantitative: + - MD: Mean Difference + - SMD: Standardized Mean Difference (bias corrected, i.e., Hedges' g) + - SMDH: Standardized Mean Difference with heteroscedastic variances (bias corrected) + - SMD1: Standardized Mean Difference using standard deviation of second group (bias corrected) + - SMD1H: Standardized Mean Difference using standard deviation of second group with heteroscedastic variances (bias corrected) + - ROM: Ratio of Means + - CVR: Coefficient of Variation Ratio + - VR: Variability Ratio +- Binary: + - RR: Log Risk Ratio + - OR: Log Odds Ratio + - RD: Risk Difference + - AS: Arcsine Square Root Transformed Risk Difference + - PETO: Log Odds Ratio estimated with Peto's method +- Counts per time: + - IRR: Log Incidence Rate Ratio + - IRD: Incidence Rate Difference + - IRSD: Square Root Transformed Incidence Rate Difference +- Mixed: + - D2ORN: transformed Standardized Mean Difference to Log Odds Ratio assuming normal distributions + - D2ORL: transformed Standardized Mean Difference to Log Odds Ratio assuming logistic distributions + - PBIT: Probit Transformed Risk Difference + - OR2DN: Transformed Log Odds Ratio to Standardized Mean Difference assuming normal distributions + - OR2DL: Transformed Log Odds Ratio to Standardized Mean Difference assuming logistic distributions + +For SMD (including D2ORN, D2ORL) the Cohen's d, T-Statistics from an independent samples t-test, or (signed) P-Values together with the group sizes are sufficient statistics. + +For Binary designs (and the corresponding Mixed designs) the table frequencies (Group 1/Outcome +, Group 1/Outcome -, Group 2/Outcome +, and Group 2/Outcome -) or the first column (Group 1/Outcome + and Group 2/Outcome +) with sample sizes (Sample Size Group 1 and Sample Size Group 2) are sufficient statistics. + +The Binary design uses the corresponding table: +| | **Outcome +** | **Outcome -** | **Sample Size** | +| :--- | :----: | :----: | ---: | +| **Group 1** | Group 1/Outcome + | Group 1/Outcome - | Sample Size Group 1 | +| **Group 2** | Group 2/Outcome + | Group 2/Outcome - | Sample Size Group 2 | + + +#### Variable association +- Quantitative: + - COR: Raw Correlation Coefficient + - UCOR: Bias-Corrected Correlation Coefficient + - ZCOR: Fisher's r-to-z Transformed Correlation Coefficient +- Binary: + - OR: Log Odds Ratio + - PHI: Phi Coefficient + - YUQ: Yule's Q + - YUY: Yule's Y + - RTET: Tetrachoric Correlation Coefficient + - ZPHI: Fisher's r-to-z Phi Coefficient + - ZTET: Fisher's r-to-z Tetrachoric Correlation Coefficient +- Mixed: + - RPB: Point-Biserial Correlation Coefficient + - RBIS: Biserial Correlation Coefficient + - ZPB: Fisher's r-to-z Transformed Point-Biserial Correlation Coefficient + - ZBIS: Fisher's r-to-z Transformed Biserial Correlation Coefficient + +For PHI, ZPHI, RPB, and ZPB the Sampling Variance Type specifies ST = stratified vs CS = cross-sectional design, the Mixed option allows passing of character vector specifying ST/CS for each study. + +For Binary designs the table frequencies (Outcome +/+, Outcome +/-, Outcome -/+, and Outcome -/-) or the first column (Outcome +/+ and Outcome -/+) with the total +/. and -/. outcomes (Outcome +/+ and Outcome +/-, and Outcome -/+ and Outcome -/-) are sufficient statistics. + +For RPB, RBIS, ZPB, and ZBIS the Cohen's d, T-Statistics from an independent samples t-test, or (signed) P-Values together with the group sizes are sufficient statistics. + +The Binary design uses the corresponding table: +| | **Variable 2, Outcome +** | **Variable 2, Outcome +** | **Sample Size** | +| :--- | :----: | :----: | ---: | +| **Variable 1, Outcome +** | Outcome +/+ | Outcome +/- | Outcome +/+ and +/- | +| **Variable 1, Outcome -** | Outcome -/+ | Outcome -/- | Outcome -/+ and -/- | + + +#### Single group +- Quantitative: + - MN: Raw Mean + - SMN: Single-Group Standardized Mean + - MNLN: Log Transformed Mean + - CVLN: Log Transformed Coefficient of Variation + - SDLN: Log Transformed Standard Deviation +- Binary: + - PR: Raw Proportion + - PLN: Log Transformed Proportion + - PLO: Logit Transformed Proportion + - PAS: Arcsine Square Root Transformed Proportion + - PFT: Freeman-Tukey Double Arcsine Transformed Proportion +- Counts per time: + - IR: Raw Incidence Rate + - IRLN: Log Transformed Incidence Rate + - IRS: Square Root Transformed Incidence Rate + - IRFT: Freeman-Tukey Transformed Incidence Rate + +For Binary designs the Events and Sample Size or the Events and Non-Events are sufficient statistics. + + +#### Repeated measures (matched groups) +- Quantitative: + - MC: Mean Change + - SMCC: Standardized Mean Change using Change Score Standardization + - SMCR: Standardized Mean Change using Raw Score Standardization + - SMCRH: Standardized Mean Change using Raw Score Standardization with heteroscedastic variances + - SMCRP: Standardized Mean Change using Raw Score Standardization with pooled standard deviations + - SMCRPH: Standardized Mean Change using Raw Score Standardization with pooled standard deviations and heteroscedastic variances + - ROMC: Log Transformed Ratio of Means + - CVRC: Log Transformed Coefficient of Variation Ratio + - VRC: Log Transformed Variability Ratio +- Binary: + - MPRR: Matched Pairs Marginal Log Risk Ratio + - MPOR: Matched Pairs Marginal Log Odds Ratio + - MPRD: Matched Pairs Marginal Risk Difference + - MPORC: Conditional Log Odds Ratio + - MPPETO: Conditional Log Odds Ratio estimated with Peto's method + - MPORM: Marginal Log Odds Ratio using known/guestimated correlations +- Binary (marginal): + - MPORM: Matched Pairs Marginal Log Odds Ratio estimated from marginal table + +Correlation refers to between measures or between groups correlation. + +For SMCC the Cohen's d, T-Statistics from paired-samples t-test, or (signed) P-Values together with the group sizes and correlation are sufficient statistics. + +The Binary design uses the corresponding table (Time can reffer to different treatments or matched groups): +| | **Time 2, Outcome +** | **Time 2, Outcome +** | +| :--- | :----: | ---: | +| **Time 1, Outcome +** | Outcome +/+ | Outcome +/- | +| **Time 1, Outcome -** | Outcome -/+ | Outcome -/- | + +The Binary design can be also reported marginally which results in the following table: +| | **Outcome +** | **Outcome -** | +| :--- | :----: | ---: | +| **Time 1** | Time 1/Outcome + | Time 1/Outcome - | +| **Time 2** | Time 2/Outcome + | Time 2/Outcome - | + +In the Binary Marginal design the user also has to supply either the Correlation or Proportion of +/+ outcomes in the binary design. If an impossible value is supplied (the correlation/proportion is restricted by the possible binary tables) the effect size is not calculated. + + +#### Other +- Reliability + - ARAW: Raw Cronbach's Alpha + - AHW: Transformed Cronbach's Alpha (Hakstian & Whalen) + - ABT: Transformed Cronbach's Alpha (Bonett) +- Partial and Semi-Partial Correlations + - PCOR: Partial Correlation Coefficient + - ZPCOR: Fisher's r-to-z Transformed Partial Correlation Coefficient + - SPCOR: Semi-Partial Correlation Coefficient + - ZSPCOR: Fisher's r-to-z Transformed Semi-Partial Correlation Coefficient +- Model fit + - R2: Raw Coefficient of Determination + - ZR2: r-to-z Transformed Coefficient of Determination +- Heterozygosity + - REH: Relative Excess Heterozygosity + +Note that (Semi)Partial Correlation in the input does NOT correspond to the raw correlation between the variables. The input can be used when e.g., the partial eta2 is known. + +For Partial and Semi-Partial Correlations the P-Value can be supplied instead of the T-Statistic. + +For Model fit only one of the R-Squared, F-Statistic, and P-Value is required. + +-------------------------- + +### Variable Inputs +The specific variable inputs are based on selected effect sizes. + +Note that users can supply "signed" P-Value (e.g., p = -0.01, 0.95) where the sign determines the sign of the resulting effect size (p = -0.01 leads to a negative effect size and p = 0.95 leads to a positive effect size). Sign of T-Statistics is used in the same manner. + +#### Independent Groups + +- Quantitative Measurement + - Mean Group 1: Means for group 1. + - Mean Group 2: Means for group 2. + - SD Group 1: Standard deviations for group 1. + - SD Group 2: Standard deviations for group 2. + - Sample Size Group 1: Total sample sizes of group 1. + - Sample Size Group 2: Total sample sizes of group 2. + - T-Statistic: T-test statistics for the variables (for SMD only). + - P-Value: P-values from a t-test (for SMD only). + - Cohen's d: Already reported Cohen's d (for SMD only). + +- Binary Measurement + - Group 1/Outcome +: Number of individuals in Group 1 with Outcome +. + - Group 1/Outcome -: Number of individuals in Group 1 with Outcome -. + - Group 2/Outcome +: Number of individuals in Group 2 with Outcome +. + - Group 2/Outcome -: Number of individuals in Group 2 with Outcome -. + - Sample Size Group 1: Total sample size of Group 1. + - Sample Size Group 2: Total sample size of Group 2. + +- Counts Per Time Measurement + - Person-Time Group 1: Total person-time for Group 1. + - Person-Time Group 2: Total person-time for Group 2. + - Events Group 1: Number of events in Group 1. + - Events Group 2: Number of events in Group 2. + +- Mixed Measurement + - For Effect Sizes PBIT, OR2DN, OR2DL: + - Group 1/Outcome +: Number of individuals in group 1 with outcome +. + - Group 1/Outcome -: Number of individuals in group 1 with outcome -. + - Group 2/Outcome +: Number of individuals in group 2 with outcome +. + - Group 2/Outcome -: Number of individuals in group 2 with outcome -. + - Group 1: Total sample size of group 1. + - Group 2: Total sample size of group 2. + - For Effect Sizes D2ORN, D2ORL: + - Mean Group 1: Means for group 1. + - Mean Group 2: Means for group 2. + - SD Group 1: Standard deviations for group 1. + - SD Group 2: Standard deviations for group 2. + - Sample Size Group 1: Total sample sizes of group 1. + - Sample Size Group 2: Total sample sizes of group 2. + - T-Statistic: T-test statistics for the variables. + - P-Value: P-values from a t-test. + - Cohen's d: Already reported Cohen's d. + +#### Variable Association + +- Quantitative Measurement + - Correlation Coefficient: Correlation coefficients between the two variables. + - Sample Size: Total sample sizes. + - T-Statistic: T-test statistics for the variables. + - P-Value: P-values for the correlation coefficients. + +- Binary Measurement + - Variable 1/Outcome +: Number of individuals with outcome + for variable 1. + - Variable 1/Outcome -: Number of individuals with outcome - for variable 1. + - Variable 2/Outcome +: Number of individuals with outcome + for variable 2. + - Variable 2/Outcome -: Number of individuals with outcome - for variable 2. + +#### Single Group + +- Quantitative Measurement + - Mean: Means. + - Standard Deviation: Standard deviations. + - Sample Size: Total sample sizes. + +- Binary Measurement + - Events: Frequencies of the event of interest. + - Non-Events: Frequencies of the complement event or group means. + - Sample Size: Total sample sizes. + +- Counts Per Time Measurement + - Events: Number of events. + - Person-Time: Total person-times. + +#### Repeated Measures/Matched Groups + +- Quantitative Measurement + - Mean Time 1: Means at time point 1. + - Mean Time 2: Means at time point 2. + - SD Time 1: Standard deviations at time point 1. + - SD Time 2: Standard deviations at time point 2. + - Sample Size: Total sample sizes. + +- Binary Measurement + - Time 1/Outcome +: Number of individuals with outcome + at time point 1. + - Time 1/Outcome -: Number of individuals with outcome - at time point 1. + - Time 2/Outcome +: Number of individuals with outcome + at time point 2. + - Time 2/Outcome -: Number of individuals with outcome - at time point 2. + + +#### Other + +- Reliability + - Cronbach's alpha: Cronbach's alpha. + - Items: Items or replications or parts of the measurement instrument. + - Sample Size: Total sample sizes. + +- Partial and Semi-Partial Correlations + - Predictors: Number of regression predictors. + - Sample Size: Total sample sizes. + - R-Squared: R-squared values (for semi-partial correlation only). + - T-Statistic: T-test statistics for the regression coefficient. + - P-Value: P-values for the regression coefficient. + - (Semi)Partial Correlation: Semi(partial) correlations of the regression coefficient. + +- Model fit + - Predictors: Number of regression predictors. + - Sample Size: Total sample sizes. + - R-Squared: R-squared values. + - F-Statistic: F-test statistics for the regression coefficients. + - P-Value: P-values for the F-test of regression coefficients. + +- Relative Excess Heterozygosity (REH) + - Homozygous Dominant Alleles: Number of individuals with homozygous dominant alleles. + - Heterozygous Alleles: Number of individuals with heterozygous alleles. + - Homozygous Recessive Alleles: Number of individuals with homozygous recessive alleles. + + +#### Reported effect sizes +- Effect size: The reported effect sizes. +- Standard error: Standard errors of the reported effect sizes. +- Sampling Variance: Sampling variances of the reported effect sizes. +- 95% Confidence Interval: Lower and upper bound of the 95% CI of the reported effect sizes. + + +-------------------------- + +#### Frequency/event cell adjustment +Available only for: +- Independent groups design with Binary measurement. +- Independent groups design with Counts per time measurement. +- Independent groups design with Mixed measurement and effect sizes `PBIT`, `OR2DN`, or `OR2DL`. +- Variable association with Binary measurement. +- Single group designs with Binary measurement. +- Single group designs with Counts per time measurement. + +#### Add +The Add input field allows you to specify a small constant to add to zero cells, counts, or frequencies when computing effect sizes, as many effect sizes are undefined when one of the cells, counts or frequencies is equal to zero. + +Default Value: +- 0.5: Default value for most effect sizes. +- 0: Used for AS, PHI, ZPHI, RTET, ZTET, IRSD, PAS, PFT, IRS, IRFT + + +#### To +The To dropdown allows you to specify when the values under the Add option should be added to + +Options +- All: The value of Add is added to each cell/count/frequency of all studies. +- Only zero: The value of Add is added to each cell/count/frequency of a study with at least one cell/count/frequency equal to 0. +- If any zero: The value of Add is added to each cell/count/frequency of all studies, but only when there is at least one study with a zero cell/count/frequency. +- None: No adjustment to the observed table frequencies is made. + + +#### Drop studies with no cases/events +The `Drop Studies with No Cases/Events` radio button group allows you to specify whether studies with no cases or events should be dropped when calculating the effect sizes. + +Options: +- Yes: Drop studies with no cases/events. +- No: Do not drop studies with no cases/events. + +#### Sampling variance type +The Sampling variance type dropdown allows you to specify the type of sampling variances for the effect size. The options available depend on the design, measurement, and effect size values. + +Options: +- LS: Large-sample approximation. +- LS2: Alternative large-sample approximation. +- UB: Unbiased estimates of the sampling variances. +- AV: Sampling variances with the sample-size weighted average. +- HO: Homoscedastic variances assumption. +- AVHO: Homoscedasticity variances assumption for both groups across studies. + +### R Packages +--- +- metafor \ No newline at end of file diff --git a/inst/qml/ClassicalMetaAnalysis.qml b/inst/qml/ClassicalMetaAnalysis.qml index 2925aa1f..7a5a0fcc 100644 --- a/inst/qml/ClassicalMetaAnalysis.qml +++ b/inst/qml/ClassicalMetaAnalysis.qml @@ -26,29 +26,123 @@ Form { VariablesForm { - preferredHeight: 400 * preferencesModel.uiScale - AvailableVariablesList { name: "allVariables" } - AssignedVariablesList { name: "effectSize"; title: qsTr("Effect Size"); singleVariable: true; allowedColumns: ["scale"] } - AssignedVariablesList { name: "effectSizeSe"; title: qsTr("Effect Size Standard Error"); singleVariable: true; allowedColumns: ["scale"] } - MA.ClassicalMetaAnalysisMethod{ visible: true} - AssignedVariablesList { name: "studyLabel"; title: qsTr("Study Labels"); singleVariable: true; allowedColumns: ["nominal"] } - AssignedVariablesList { name: "covariates"; title: qsTr("Covariates"); allowedColumns: ["scale"] } - AssignedVariablesList { name: "factors"; title: qsTr("Factors"); allowedColumns: ["nominal"] } - } + preferredHeight: 450 * preferencesModel.uiScale - Section - { - title: qsTr("Model") - VariablesForm + AvailableVariablesList + { + name: "allVariables" + } + + AssignedVariablesList + { + name: "effectSize" + id: effectSize + title: qsTr("Effect Size") + singleVariable: true + allowedColumns: ["scale"] + info: qsTr("Variable containing the observed effect sizes.") + } + AssignedVariablesList + { + name: "effectSizeStandardError" + id: effectSizeStandardError + title: qsTr("Effect Size Standard Error") + singleVariable: true + allowedColumns: ["scale"] + info: qsTr("Variable containing the standard errors corresponding to the effect sizes.") + } + + DropDown + { + name: "method" + id: method + label: qsTr("Method") + startValue: "restrictedML" + info: qsTr("Method used to estimate heterogeneity (tau-squared) in the meta-analysis. The available methods depend on the inclusion of heterogeneity model terms.") + values: (function() { + if (sectionModel.heterogeneityModelTermsCount == 0) { + return [ + { label: qsTr("Equal Effects") , value: "equalEffects" }, + { label: qsTr("Fixed Effects") , value: "fixedEffects" }, + { label: qsTr("Maximum Likelihood") , value: "maximumLikelihood"}, + { label: qsTr("Restricted ML") , value: "restrictedML" }, + { label: qsTr("DerSimonian-Laird") , value: "derSimonianLaird" }, + { label: qsTr("Hedges") , value: "hedges" }, + { label: qsTr("Hunter-Schmidt") , value: "hunterSchmidt" }, + { label: qsTr("Hunter-Schmidt (SSC)") , value: "hunterSchmidtSsc" }, + { label: qsTr("Sidik-Jonkman") , value: "sidikJonkman" }, + { label: qsTr("Empirical Bayes") , value: "empiricalBayes" }, + { label: qsTr("Paule-Mandel") , value: "pauleMandel" }, + { label: qsTr("Paule-Mandel (MU)") , value: "pauleMandelMu" }, + { label: qsTr("Generalized Q-stat") , value: "qeneralizedQStat" }, + { label: qsTr("Generalized Q-stat (MU)"), value: "qeneralizedQStatMu"} + ]; + } else { + return [ + { label: qsTr("Maximum Likelihood") , value: "maximumLikelihood"}, + { label: qsTr("Restricted ML") , value: "restrictedML" }, + { label: qsTr("Empirical Bayes") , value: "empiricalBayes" } + ]; + }})() + } + + DropDown + { + name: "fixedEffectTest" + label: qsTr("Fixed effect test") + startValue: "knha" + values: [ "z", "t", "knha"] + info: qsTr("Method for testing the model coefficients: 'z' uses standard normal approximation, 't' uses t-distribution, and 'knha' uses the Knapp and Hartung adjustment (default).") + } + + AssignedVariablesList { - preferredHeight: 150 * preferencesModel.uiScale - AvailableVariablesList { name: "modelComponents"; title: qsTr("Components"); source: ["covariates","factors"]} - AssignedVariablesList { name: "modelTerms"; title: qsTr("Model Terms"); listViewType: JASP.Interaction } + name: "predictors" + id: predictors + title: qsTr("Predictors") + allowedColumns: ["nominal", "scale"] + allowTypeChange: true + info: qsTr("Variables to include as predictors (moderators) in the meta-regression model.") + } + + AssignedVariablesList + { + name: "clustering" + id: clustering + title: qsTr("Clustering") + singleVariable: true + enabled: !sectionAdvanced.permutationTestChecked + allowedColumns: ["nominal"] + info: qsTr("Variable indicating clustering of effect sizes. This option is disabled when permutation tests are selected.") + } + + AssignedVariablesList + { + name: "studyLabels" + title: qsTr("Study Labels") + singleVariable: true + allowedColumns: ["nominal"] + info: qsTr("Variable containing labels for the studies. Used for labeling outputs and plots.") } - CheckBox { name: "interceptTerm"; label: qsTr("Include intercept"); checked: true } } - MA.ClassicalMetaAnalysisStatistics{} + MA.ClassicalMetaAnalysisModel + { + id: sectionModel + } - MA.ClassicalMetaAnalysisDiagnostics{} -} \ No newline at end of file + MA.ClassicalMetaAnalysisStatistics {} + + MA.ClassicalMetaAnalysisEstimatedMarginalMeans {} + + MA.ClassicalMetaAnalysisForestPlot {} + + MA.ClassicalMetaAnalysisBubblePlot {} + + MA.ClassicalMetaAnalysisDiagnostics {} + + MA.ClassicalMetaAnalysisAdvanced + { + id: sectionAdvanced + } +} diff --git a/inst/qml/ClassicalMetaAnalysisMultilevelMultivariate.qml b/inst/qml/ClassicalMetaAnalysisMultilevelMultivariate.qml new file mode 100644 index 00000000..7e0df159 --- /dev/null +++ b/inst/qml/ClassicalMetaAnalysisMultilevelMultivariate.qml @@ -0,0 +1,422 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 +import "../qml/qml_components" as MA + +Form +{ + + VariablesForm + { + preferredHeight: 450 * preferencesModel.uiScale + + AvailableVariablesList + { + name: "allVariables" + } + + AssignedVariablesList + { + name: "effectSize" + id: effectSize + title: qsTr("Effect Size") + singleVariable: true + allowedColumns: ["scale"] + info: qsTr("Variable containing the observed effect sizes.") + } + + AssignedVariablesList + { + name: "effectSizeStandardError" + id: effectSizeStandardError + title: qsTr("Effect Size Standard Error") + singleVariable: true + allowedColumns: ["scale"] + info: qsTr("Variable containing the standard errors corresponding to the effect sizes.") + } + + DropDown + { + name: "method" + id: method + label: qsTr("Method") + startValue: "restrictedML" + info: qsTr("Method used to estimate heterogeneity in the meta-analysis.") + values: [ + { label: qsTr("Maximum Likelihood") , value: "maximumLikelihood"}, + { label: qsTr("Restricted ML") , value: "restrictedML" } + ] + } + + DropDown + { + name: "fixedEffectTest" + label: qsTr("Fixed effect test") + startValue: "t" + values: [ "z", "t"] + info: qsTr("Method for testing the model coefficients: 'z' uses standard normal approximation, 't' uses t-distribution.") + } + + AssignedVariablesList + { + name: "predictors" + id: predictors + title: qsTr("Predictors") + allowedColumns: ["nominal", "scale"] + info: qsTr("Variables to include as predictors (moderators) in the meta-regression model.") + } + + AssignedVariablesList + { + name: "clustering" + id: clustering + title: qsTr("Clustering") + singleVariable: true + allowedColumns: ["nominal"] + info: qsTr("Variable indicating clustering of effect sizes. This option is disabled when permutation tests are selected.") + } + + AssignedVariablesList + { + name: "studyLabels" + title: qsTr("Study Labels") + singleVariable: true + allowedColumns: ["nominal"] + info: qsTr("Variable containing labels for the studies. Used for labeling outputs and plots.") + } + } + + + Section + { + title: qsTr("Random Effects / Model Structure") + expanded: true + info: qsTr("Options for specifying the random effects structure for the meta-analysis model, including the types of random effects and their associated variables. Allows modeling of complex data structures such as multilevel, multivariate, autoregressive, spatial, and other forms of dependency.") + + ComponentsList + { + id: randomEffects + name: "randomEffects" + headerLabels: ["Type"] + defaultValues: [{"type": "nested"}] + + rowComponent: RowLayout + { + property string typeValue: type.value + property string structureValue: structure.value + property string spatialInputTypeValue: spatialInputType.value + property string typeLabel: type.currentLabel + property string structureLabel: structure.currentLabel + property string structureCounterValue: structureCounter.text + + Text + { + text: qsTr("Structure %1").arg((rowIndex + 1)) + id: structureCounter + } + + DropDown + { + id: type + name: "type" + info: qsTr("Type of random effect to include in the model.") + values: [ + { label: qsTr("Simple"), value: "simple"}, + { label: qsTr("Nested (multilevel)"), value: "nested"}, + { label: qsTr("Random slopes"), value: "randomSlopes"}, + { label: qsTr("Structured"), value: "structured"}, + { label: qsTr("Autoregressive"), value: "autoregressive"}, + { label: qsTr("Spatial"), value: "spatial"}, + { label: qsTr("Known correlation"), value: "knownCorrelation"} + ] + } + + DropDown + { + id: structure + name: "structure" + label: qsTr("Structure") + visible: type.value == "structured" || type.value == "autoregressive" || type.value == "spatial" + info: qsTr("Structure of the random effect when the type is 'Structured', 'Autoregressive', or 'Spatial'. Available structures depend on the selected type.") + values: (function() { + if (type.value == "structured") { + return [ + { label: qsTr("Compound symmetry"), value: "compoundSymmetry"}, + { label: qsTr("Heteroscedastic compound symmetry"), value: "heteroscedasticCompoundSymmetry"}, + { label: qsTr("Unstructured "), value: "unstructured"}, + { label: qsTr("Identity"), value: "identity"}, + { label: qsTr("Diagonal"), value: "diagonal"} + ]; + } else if (type.value == "autoregressive") { + return [ + { label: qsTr("AR(1)"), value: "ar1"}, + { label: qsTr("Heteroscedastic AR(1)"), value: "heteroskedasticAr1"}, + { label: qsTr("Continuous-time AR"), value: "continuousTimeAr"} + ]; + } else if (type.value == "spatial") { + return [ + { label: qsTr("Exponential"), value: "exponential"}, + { label: qsTr("Gaussian"), value: "gaussian"}, + { label: qsTr("Linear"), value: "linear"}, + { label: qsTr("Rational quadratic"), value: "rationalQuadratic"}, + { label: qsTr("Spherical"), value: "spherical"} + ]; + } else { + return []; + } + })() + } + } + } + + ComponentsList + { + name: "randomEffectsSpecification" + source: "randomEffects" + title: qsTr("Specification") + visible: true + rowSpacing: 20 + + rowComponent: ColumnLayout + { + property var typeValue: randomEffects.rowAt(rowIndex).typeValue + property var structureValue: randomEffects.rowAt(rowIndex).structureValue + property var spatialInputTypeValue: randomEffects.rowAt(rowIndex).spatialInputTypeValue + property var typeLabel: randomEffects.rowAt(rowIndex).typeLabel + property var structureLabel: randomEffects.rowAt(rowIndex).structureLabel + property var structureCounterValue: randomEffects.rowAt(rowIndex).structureCounterValue + + VariablesForm + { + removeInvisibles: true + preferredHeight: (typeValue == "nested" || typeValue == "randomSlopes" || (typeValue == "spatial" && distanceMetric.value != "greatCircle")) ? 250 * preferencesModel.uiScale : 200 * preferencesModel.uiScale + visible: typeValue == "simple" || typeValue == "nested" || typeValue == "randomSlopes" || typeValue == "structured" || typeValue == "autoregressive" || typeValue == "spatial" || typeValue == "knownCorrelation" + + AvailableVariablesList + { + name: "allVars" + title: structureCounterValue + ": " + typeLabel + } + + AssignedVariablesList + { + name: "randomSlopeTerms" + title: qsTr("Random Slope Terms") + visible: typeValue == "randomSlopes" + listViewType: JASP.Interaction + allowedColumns: ["nominal", "scale"] // this should be choose on assignment + info: qsTr("Variables to include as random slope terms in the model. Available when the random effect type is 'Random slopes'.") + addAvailableVariablesToAssigned: false + } + + AssignedVariablesList + { + name: "factorLevels" + title: qsTr("Factor Levels") + visible: typeValue == "structured" + singleVariable: true + info: qsTr("Variable indicating the factor levels ('Inner Term') for the structured random effect. Available when the random effect type is 'Structured'.") + allowedColumns: ["nominal"] + } + + + AssignedVariablesList + { + name: "level1" + title: qsTr("Level 1") + visible: typeValue == "nested" + singleVariable: true + allowedColumns: ["nominal"] + } + + AssignedVariablesList + { + name: "level2" + title: qsTr("Level 2") + visible: typeValue == "nested" + singleVariable: true + allowedColumns: ["nominal"] + } + + AssignedVariablesList + { + name: "level3" + title: qsTr("Level 3") + visible: typeValue == "nested" + singleVariable: true + allowedColumns: ["nominal"] + } + + AssignedVariablesList + { + name: "level4" + title: qsTr("Level 4") + visible: typeValue == "nested" + singleVariable: true + allowedColumns: ["nominal"] + } + + AssignedVariablesList + { + name: "level5" + title: qsTr("Level 5") + visible: typeValue == "nested" + singleVariable: true + allowedColumns: ["nominal"] + } + + AssignedVariablesList + { + name: "time" + title: qsTr("Time") + visible: typeValue == "autoregressive" + singleVariable: true + allowedColumns: ["ordinal", "scale"] // scale for continuous time AR otherwise ordinal + info: qsTr("Variable indicating time points for an autoregressive random effects structure. Available when the random effect type is 'Autoregressive'.") + } + + AssignedVariablesList + { + name: "spatialCoordinates" + title: qsTr("Spatial Coordinates") + visible: typeValue == "spatial" && distanceMetric.value != "greatCircle" && distanceMetric.value != "loadFromFile" + allowedColumns: ["scale"] + info: qsTr("Variables representing spatial coordinates for a spatial random effects structure. Available when the random effect type is 'Spatial' and the distance metric is not 'Great-circle' or prespecified in a file.") + } + + AssignedVariablesList + { + name: "longitude" + title: qsTr("Longitude") + visible: typeValue == "spatial" && distanceMetric.value == "greatCircle" + allowedColumns: ["scale"] + singleVariable: true + info: qsTr("Variable representing longitude (in decimal degrees, with minus signs for West) for a spatial random effects structure using the 'Great-circle' distance metric. Available when the random effect type is 'Spatial' and the distance metric is 'Great-circle'.") + } + + AssignedVariablesList + { + name: "latitude" + title: qsTr("Latitude") + visible: typeValue == "spatial" && distanceMetric.value == "greatCircle" + allowedColumns: ["scale"] + singleVariable: true + info: qsTr("Variable representing latitude (in decimal degrees, with minus signs for South) for a spatial random effects structure using the 'Great-circle' distance metric. Available when the random effect type is 'Spatial' and the distance metric is 'Great-circle'.") + } + + AssignedVariablesList + { + name: "locationIdentifier" + title: qsTr("Location Identifier") + visible: typeValue == "spatial" && distanceMetric.value == "loadFromFile" + allowedColumns: ["nominal"] + singleVariable: true + info: qsTr("Variable identifying locations when loading distances matrix from a file for a spatial random effects structure. The location corresponds to the row and column names of the distance matrix. The names cannot start with a number.") + } + + AssignedVariablesList + { + name: "groupingFactor" + title: qsTr("Grouping Factor") + visible: typeValue != "nested" + singleVariable: true + allowedColumns: ["nominal"] + info: qsTr("Grouping variable specifying which observations share the same random effect ('Outer Term'). Available for random effect types other than 'Nested (Multilevel)'. The 'Grouping Factor' is not required for 'Spatial' Random Effects.") + } + } + + DropDown + { + name: "distanceMetric" + id: distanceMetric + label: qsTr("Distance metric") + visible: typeValue == "spatial" + info: qsTr("Distance metric used to calculate distances in a spatial random effects structure. Available when the random effect type is 'Spatial'.") + values: [ + { label: qsTr("Euclidean"), value: "euclidean" }, + { label: qsTr("Manhattan"), value: "manhattan" }, + { label: qsTr("Maximum"), value: "maximum" }, + { label: qsTr("Great-circle"), value: "greatCircle"}, + { label: qsTr("Load from file"), value: "loadFromFile"} + ] + } + + FileSelector + { + name: "distanceMatrixFile" + label: qsTr("Distance matrix file") + visible: typeValue == "spatial" && distanceMetric.value == "loadFromFile" + filter: "*.csv" + save: false + info: qsTr("CSV file containing the distance matrix for the spatial random effects structure. The first row and the first column of the file must contain names that map the matrix entries to the 'Location Identifier' (the names cannot start with a number). Available when the random effect type is 'Spatial' and the distance metric is loaded from a file.") + + } + + FileSelector + { + name: "correlationMatrixFile" + label: qsTr("Correlation matrix file") + visible: typeValue == "knownCorrelation" + filter: "*.csv" + save: false + info: qsTr("CSV file containing the known correlation matrix for the random effects structure. The first row and the first column of the file must contain names that map the matrix entries to the 'Grouping Factor' (the names cannot start with a number). Available when the random effect type is 'Known correlation'.") + } + + Divider { } + + } + } + } + + MA.ClassicalMetaAnalysisModel + { + id: sectionModel + module: "metaAnalysisMultilevelMultivariate" + } + + MA.ClassicalMetaAnalysisStatistics + { + module: "metaAnalysisMultilevelMultivariate" + } + + MA.ClassicalMetaAnalysisEstimatedMarginalMeans + { + module: "metaAnalysisMultilevelMultivariate" + } + + MA.ClassicalMetaAnalysisForestPlot + { + module: "metaAnalysisMultilevelMultivariate" + } + + MA.ClassicalMetaAnalysisBubblePlot {} + + MA.ClassicalMetaAnalysisDiagnostics + { + module: "metaAnalysisMultilevelMultivariate" + } + + MA.ClassicalMetaAnalysisAdvanced + { + module: "metaAnalysisMultilevelMultivariate" + } +} diff --git a/inst/qml/EffectSizeComputation.qml b/inst/qml/EffectSizeComputation.qml new file mode 100644 index 00000000..8e226726 --- /dev/null +++ b/inst/qml/EffectSizeComputation.qml @@ -0,0 +1,1062 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 +import "../qml/qml_components" as MA + +Form +{ + + ComponentsList + { + id: effectSizeType + name: "effectSizeType" + headerLabels: ["Design", "Measurement", "Effect size"] + defaultValues: [{"design": "independentGroups"}] + + rowComponent: RowLayout + { + + property string designValue: design.value + property string measurementValue: measurement.value + property string effectSizeValue: effectSize.value + property string stepCounterValue: stepCounter.text + property string designLabel: design.currentLabel + property string measurementLabel: measurement.currentLabel + + Text + { + text: qsTr("Step %1").arg((rowIndex + 1)) + id: stepCounter + } + + DropDown + { + id: design + name: "design" + values: [ + { label: qsTr("Independent groups"), value: "independentGroups"}, + { label: qsTr("Variable association"), value: "variableAssociation"}, + { label: qsTr("Single group"), value: "singleGroup"}, + { label: qsTr("Repeated measures"), value: "repeatedMeasures"}, + { label: qsTr("Other"), value: "other"}, + { label: qsTr("Reported effect sizes"), value: "reportedEffectSizes"} + ] + } + + DropDown + { + id: measurement + name: "measurement" + visible: design.value != "reportedEffectSizes" + values: (function() { + if (design.value == "independentGroups") { + return [ + { label: qsTr("Quantitative"), value: "quantitative"}, + { label: qsTr("Binary"), value: "binary"}, + { label: qsTr("Counts per time"), value: "countsPerTime"}, + { label: qsTr("Mixed"), value: "mixed"} + ]; + } else if (design.value == "variableAssociation") { + return [ + { label: qsTr("Quantitative"), value: "quantitative"}, + { label: qsTr("Binary"), value: "binary"}, + { label: qsTr("Mixed"), value: "mixed"} + ]; + } else if (design.value == "singleGroup") { + return [ + { label: qsTr("Quantitative"), value: "quantitative"}, + { label: qsTr("Binary"), value: "binary"}, + { label: qsTr("Counts per time"), value: "countsPerTime"} + ]; + } else if (design.value == "repeatedMeasures") { + return [ + { label: qsTr("Quantitative"), value: "quantitative"}, + { label: qsTr("Binary"), value: "binary"}, + { label: qsTr("Binary (marginal)"), value: "binaryMarginal"} + ]; + } else if (design.value == "other") { + return [ + { label: qsTr("Reliability"), value: "reliability"}, + { label: qsTr("Partial correlation"), value: "partialCorrelation"}, + { label: qsTr("Model fit"), value: "modelFit"}, + { label: qsTr("Heterozygosity"), value: "heterozygosity"} + ]; + } else { + return []; + } + })() + } + + DropDown + { + id: effectSize + name: "effectSize" + visible: design.value != "reportedEffectSizes" + indexDefaultValue: (function() { + if (design.value == "independentGroups" && measurement.value == "quantitative") + return 1; + else if (design.value == "independentGroups" && measurement.value == "binary") + return 1; + else if (design.value == "variableAssociation" && measurement.value == "quantitative") + return 2; + else if (design.value == "variableAssociation" && measurement.value == "mixed") + return 2; + else if (design.value == "singleGroup") + return 1; + else if (design.value == "repeatedMeasures" && measurement.value == "quantitative") + return 1; + else if (design.value == "repeatedMeasures" && measurement.value == "binary") + return 1; + else if (design.value == "other" && measurement.value == "reliability") + return 1; + else if (design.value == "other" && measurement.value == "partialCorrelation") + return 1; + else if (design.value == "other" && measurement.value == "modelFit") + return 1; + else + return 0; + })() + values: (function() { + if (design.value == "independentGroups" && measurement.value == "quantitative") { + return [ + { label: qsTr("MD"), value: "MD"}, + { label: qsTr("SMD"), value: "SMD"}, + { label: qsTr("SMDH"), value: "SMDH"}, + { label: qsTr("SMD1"), value: "SMD1"}, + { label: qsTr("SMD1H"), value: "SMD1H"}, + { label: qsTr("ROM"), value: "ROM"}, + { label: qsTr("CVR"), value: "CVR"}, + { label: qsTr("VR"), value: "VR"} + ]; + } else if (design.value == "independentGroups" && measurement.value == "binary") { + return [ + { label: qsTr("RR"), value: "RR"}, + { label: qsTr("OR"), value: "OR"}, + { label: qsTr("RD"), value: "RD"}, + { label: qsTr("AS"), value: "AS"}, + { label: qsTr("PETO"), value: "PETO"} + ]; + } else if (design.value == "independentGroups" && measurement.value == "countsPerTime") { + return [ + { label: qsTr("IRR"), value: "IRR"}, + { label: qsTr("IRD"), value: "IRD"}, + { label: qsTr("IRSD"), value: "IRSD"} + ]; + } else if (design.value == "independentGroups" && measurement.value == "mixed") { + return [ + { label: qsTr("D2ORN"), value: "D2ORN"}, + { label: qsTr("D2ORL"), value: "D2ORL"}, + { label: qsTr("PBIT"), value: "PBIT"}, + { label: qsTr("OR2DN"), value: "OR2DN"}, + { label: qsTr("OR2DL"), value: "OR2DL"} + ]; + } else if (design.value == "variableAssociation" && measurement.value == "quantitative") { + return [ + { label: qsTr("COR"), value: "COR"}, + { label: qsTr("UCOR"), value: "UCOR"}, + { label: qsTr("ZCOR"), value: "ZCOR"} + ]; + } else if (design.value == "variableAssociation" && measurement.value == "binary") { + return [ + { label: qsTr("OR"), value: "OR"}, + { label: qsTr("PHI"), value: "PHI"}, + { label: qsTr("YUQ"), value: "YUQ"}, + { label: qsTr("YUY"), value: "YUY"}, + { label: qsTr("RTET"), value: "RTET"}, + { label: qsTr("ZPHI"), value: "ZPHI"}, + { label: qsTr("ZTET"), value: "ZTET"} + ]; + } else if (design.value == "variableAssociation" && measurement.value == "mixed") { + return [ + { label: qsTr("RPB"), value: "RPB"}, + { label: qsTr("RBIS"), value: "RBIS"}, + { label: qsTr("ZPB"), value: "ZPB"}, + { label: qsTr("ZBIS"), value: "ZBIS"} + ]; + } else if (design.value == "singleGroup" && measurement.value == "quantitative") { + return [ + { label: qsTr("MN"), value: "MN"}, + { label: qsTr("SMN"), value: "SMN"}, + { label: qsTr("MNLN"), value: "MNLN"}, + { label: qsTr("CVLN"), value: "CVLN"}, + { label: qsTr("SDLN"), value: "SDLN"} + ]; + } else if (design.value == "singleGroup" && measurement.value == "binary") { + return [ + { label: qsTr("PR"), value: "PR"}, + { label: qsTr("PLN"), value: "PLN"}, + { label: qsTr("PLO"), value: "PLO"}, + { label: qsTr("PAS"), value: "PAS"}, + { label: qsTr("PFT"), value: "PFT"} + ]; + } else if (design.value == "singleGroup" && measurement.value == "countsPerTime") { + return [ + { label: qsTr("IR"), value: "IR"}, + { label: qsTr("IRLN"), value: "IRLN"}, + { label: qsTr("IRS"), value: "IRS"}, + { label: qsTr("IRFT"), value: "IRFT"} + ]; + } else if (design.value == "repeatedMeasures" && measurement.value == "quantitative") { + return [ + { label: qsTr("MC"), value: "MC"}, + { label: qsTr("SMCC"), value: "SMCC"}, + { label: qsTr("SMCR"), value: "SMCR"}, + { label: qsTr("SMCRH"), value: "SMCRH"}, + { label: qsTr("SMCRP"), value: "SMCRP"}, + { label: qsTr("SMCRPH"), value: "SMCRPH"}, + { label: qsTr("ROMC"), value: "ROMC"}, + { label: qsTr("CVRC"), value: "CVRC"}, + { label: qsTr("VRC"), value: "VRC"} + ]; + } else if (design.value == "repeatedMeasures" && measurement.value == "binary") { + return [ + { label: qsTr("MPRR"), value: "MPRR"}, + { label: qsTr("MPOR"), value: "MPOR"}, + { label: qsTr("MPRD"), value: "MPRD"}, + { label: qsTr("MPORC"), value: "MPORC"}, + { label: qsTr("MPPETO"), value: "MPPETO"} + ]; + } else if (design.value == "repeatedMeasures" && measurement.value == "binaryMarginal") { + return [ + { label: qsTr("MPORM"), value: "MPORM"} + ]; + }else if (design.value == "other" && measurement.value == "reliability") { + return [ + { label: qsTr("ARAW"), value: "ARAW"}, + { label: qsTr("AHW"), value: "AHW"}, + { label: qsTr("ABT"), value: "ABT"} + ]; + } else if (design.value == "other" && measurement.value == "partialCorrelation") { + return [ + { label: qsTr("PCOR"), value: "PCOR"}, + { label: qsTr("ZPCOR"), value: "ZPCOR"}, + { label: qsTr("SPCOR"), value: "SPCOR"}, + { label: qsTr("ZSPCOR"), value: "ZSPCOR"} + ]; + } else if (design.value == "other" && measurement.value == "modelFit") { + return [ + { label: qsTr("R2"), value: "R2"}, + { label: qsTr("ZR2"), value: "ZR2"} + ]; + } else if (design.value == "other" && measurement.value == "heterozygosity") { + return [ + { label: qsTr("REH"), value: "REH"} + ]; + } else { + return []; + } + })(); + } + + } + } + + + ComponentsList + { + name: "variables" + source: "effectSizeType" + rowSpacing: 20 + + rowComponent: ColumnLayout + { + property var designValue: effectSizeType.rowAt(rowIndex).designValue + property var measurementValue: effectSizeType.rowAt(rowIndex).measurementValue + property var effectSizeValue: effectSizeType.rowAt(rowIndex).effectSizeValue + property var designLabel: effectSizeType.rowAt(rowIndex).designLabel + property var measurementLabel: effectSizeType.rowAt(rowIndex).measurementLabel + property var effectSizeLabel: effectSizeType.rowAt(rowIndex).effectSizeLabel + property var stepCounterValue: effectSizeType.rowAt(rowIndex).stepCounterValue + + VariablesForm + { + // TODO: dynamically set proper height + removeInvisibles: true + preferredWidth: parent.width - 6 * jaspTheme.contentMargin + preferredHeight: (function() { + if ((designValue == "variableAssociation" && measurementValue == "mixed" && samplingVarianceType.value == "mixed")) { + return 12 * 50 * preferencesModel.uiScale + } else if (effectSizeValue == "SMD" || effectSizeValue == "D2ORL" || effectSizeValue == "D2ORN" || effectSizeValue == "SMCC" || + (designValue == "variableAssociation" && measurementValue == "mixed")) { + return 11 * 50 * preferencesModel.uiScale + } else if (effectSizeValue == "CVR" || effectSizeValue == "VR" || effectSizeValue == "CVRC" || effectSizeValue == "VRC" || + (designValue == "independentGroups" && measurementValue == "countsPerTime") || + (designValue == "repeatedMeasures" && measurementValue == "binary") || + (designValue == "variableAssociation" && measurementValue == "quantitative") || + (designValue == "reportedEffectSizes")) { + return 6 * 50 * preferencesModel.uiScale + } else if (effectSizeValue == "SDLN" || (designValue == "singleGroup" && measurementValue == "countsPerTime")) { + return 4 * 50 * preferencesModel.uiScale + } else if (effectSizeValue == "SMD1" || effectSizeValue == "SMCR" || effectSizeValue == "PCOR" || effectSizeValue == "ZPCOR" || + (designValue == "other" && measurementValue == "modelFit")) { + return 7 * 50 * preferencesModel.uiScale + } else if ((designValue == "independentGroups" && measurementValue == "quantitative") || + (designValue == "other" && measurementValue == "partialCorrelation")) { + return 8 * 50 * preferencesModel.uiScale + } else if ((designValue == "singleGroup" && (measurementValue == "quantitative" || measurementValue == "binary")) || + (designValue == "other" && (measurementValue == "reliability" || measurementValue == "heterozygosity"))) { + return 5 * 50 * preferencesModel.uiScale + } else { + return 8 * 50 * preferencesModel.uiScale + } + })() + + AvailableVariablesList + { + name: "allVars" + title: stepCounterValue + ": " + effectSizeValue + " (" + designLabel + "/" + measurementLabel + ")" + } + + AssignedVariablesList + { // metafor: ai + name: "group1OutcomePlus" + title: qsTr("Group 1/Outcome +") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "binary") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "PBIT" || effectSizeValue == "OR2DN" || effectSizeValue == "OR2DL")) + } + + AssignedVariablesList + { // metafor: ai + name: "time1OutcomePlus" + title: qsTr("Time 1/Outcome +") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "binaryMarginal") + } + + AssignedVariablesList + { // metafor: ai + name: "outcomePlusPlus" + title: qsTr("Outcome +/+") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "binary") || + (designValue == "repeatedMeasures" && measurementValue == "binary") + } + + AssignedVariablesList + { // metafor: ai + name: "coefficientAlpha" + title: qsTr("Coefficient α") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "reliability") + } + + AssignedVariablesList + { // metafor: ai + name: "homozygousDominantAlleles" + title: qsTr("Homozygous Dominant Alleles") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "heterozygosity") + } + + AssignedVariablesList + { // metafor: bi + name: "group1OutcomeMinus" + title: qsTr("Group 1/Outcome -") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "binary") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "PBIT" || effectSizeValue == "OR2DN" || effectSizeValue == "OR2DL")) + } + + AssignedVariablesList + { // metafor: bi + name: "time1OutcomeMinus" + title: qsTr("Time 1/Outcome -") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "binaryMarginal") + } + + AssignedVariablesList + { // metafor: bi + name: "outcomePlusMinus" + title: qsTr("Outcome +/-") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "binary") || + (designValue == "repeatedMeasures" && measurementValue == "binary") + } + + AssignedVariablesList + { // metafor: bi + name: "heterozygousAlleles" + title: qsTr("Heterozygous Alleles") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "heterozygosity") + } + + AssignedVariablesList + { // metafor: ci + name: "group2OutcomePlus" + title: qsTr("Group 2/Outcome +") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "binary") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "PBIT" || effectSizeValue == "OR2DN" || effectSizeValue == "OR2DL")) + } + + AssignedVariablesList + { // metafor: ci + name: "time2OutcomePlus" + title: qsTr("Time 2/Outcome +") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "binaryMarginal") + } + + AssignedVariablesList + { // metafor: ci + name: "outcomeMinusPlus" + title: qsTr("Outcome -/+") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "binary") || + (designValue == "repeatedMeasures" && measurementValue == "binary") + } + + AssignedVariablesList + { // metafor: ci + name: "homozygousRecessiveAlleles" + title: qsTr("Homozygous Recessive Alleles") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "heterozygosity") + } + + AssignedVariablesList + { // metafor: di + name: "group2OutcomeMinus" + title: qsTr("Group 2/Outcome Minus") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "binary") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "PBIT" || effectSizeValue == "OR2DN" || effectSizeValue == "OR2DL")) + } + + AssignedVariablesList + { // metafor: di + name: "time2OutcomeMinus" + title: qsTr("Time 2/Outcome -") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "binaryMarginal") + } + + AssignedVariablesList + { // metafor: di + name: "outcomeMinusMinus" + title: qsTr("Outcome -/-") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "binary") || + (designValue == "repeatedMeasures" && measurementValue == "binary") + } + + AssignedVariablesList + { // metafor: n1i + name: "outcomePlusPlusAndPlusMinus" + title: qsTr("Outcome +/+ and +/-") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "binary") + } + + AssignedVariablesList + { // metafor: n2i + name: "outcomeMinusPlusAndMinusMinus" + title: qsTr("Outcome -/+ and -/-") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "binary") + } + + AssignedVariablesList + { // metafor: x1i + name: "eventsGroup1" + title: qsTr("Events Group 1") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "countsPerTime") + } + + AssignedVariablesList + { // metafor: xi + name: "events" + title: qsTr("Events") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "singleGroup" && (measurementValue == "binary" || measurementValue == "countsPerTime")) + } + + AssignedVariablesList + { // metafor: mi + name: "nonEvents" + title: qsTr("Non-Events") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "singleGroup" && measurementValue == "binary") + } + + AssignedVariablesList + { // metafor: mi + name: "items" + title: qsTr("Items") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "reliability") + } + + AssignedVariablesList + { // metafor: mi + name: "predictors" + title: qsTr("Predictors") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "partialCorrelation") || + (designValue == "other" && measurementValue == "modelFit") + } + + AssignedVariablesList + { // metafor: x2i + name: "eventsGroup2" + title: qsTr("Events Group 2") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "countsPerTime") + } + + AssignedVariablesList + { // metafor: t1i + name: "personTimeGroup1" + title: qsTr("Person-Time Group 1") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "countsPerTime") + } + + AssignedVariablesList + { // metafor: ti + name: "personTime" + title: qsTr("Person-Time") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "singleGroup" && measurementValue == "countsPerTime") + } + + AssignedVariablesList + { // metafor: t2i + name: "personTimeGroup2" + title: qsTr("Person-Time Group 2") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "countsPerTime") + } + + AssignedVariablesList + { // metafor: m1i + name: "meanGroup1" + title: qsTr("Mean Group 1") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "quantitative" && (effectSizeValue != "CVR" && effectSizeValue != "VR")) || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "D2ORN" || effectSizeValue == "D2ORL")) || + (designValue == "variableAssociation" && measurementValue == "mixed") + } + + AssignedVariablesList + { // metafor: m1i + name: "meanTime1" + title: qsTr("Mean Time 1 (or Group 1)") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "quantitative" && (effectSizeValue != "CVRC" && effectSizeValue != "VRC")) + } + + AssignedVariablesList + { // metafor: m2i + name: "meanGroup2" + title: qsTr("Mean Group 2") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "quantitative" && (effectSizeValue != "CVR" && effectSizeValue != "VR")) || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "D2ORN" || effectSizeValue == "D2ORL")) || + (designValue == "variableAssociation" && measurementValue == "mixed") + } + + AssignedVariablesList + { // metafor: m2i + name: "meanTime2" + title: qsTr("Mean Time 2 (or Group 2)") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "quantitative" && (effectSizeValue != "CVRC" && effectSizeValue != "VRC")) + } + + AssignedVariablesList + { // metafor: mi + name: "mean" + title: qsTr("Mean") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "singleGroup" && measurementValue == "quantitative" && effectSizeValue != "SDLN") + } + + AssignedVariablesList + { // metafor: sd1i + name: "sdGroup1" + title: qsTr("SD Group 1") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "quantitative" && (effectSizeValue != "SMD1" && effectSizeValue != "SMDH1")) || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "D2ORN" || effectSizeValue == "D2ORL")) || + (designValue == "variableAssociation" && measurementValue == "mixed") + } + + AssignedVariablesList + { // metafor: sd1i + name: "sdTime1" + title: qsTr("SD Time 1 (or Group 1)") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "quantitative") + } + + AssignedVariablesList + { // metafor: sd2i + name: "sdGroup2" + title: qsTr("SD Group 2") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "quantitative") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "D2ORN" || effectSizeValue == "D2ORL")) || + (designValue == "variableAssociation" && measurementValue == "mixed") + } + + AssignedVariablesList + { // metafor: sd2i + name: "sdTime2" + title: qsTr("SD Time 2 (or Group 2)") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "quantitative" && effectSizeValue != "SMCR") + } + + AssignedVariablesList + { // metafor: sdi + name: "sd" + title: qsTr("SD") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "singleGroup" && measurementValue == "quantitative") + } + AssignedVariablesList + { // metafor: n1i + name: "sampleSizeGroup1" + title: qsTr("Sample Size Group 1") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue != "countsPerTime") || + (designValue == "variableAssociation" && measurementValue == "mixed") + } + + AssignedVariablesList + { // metafor: n2i + name: "sampleSizeGroup2" + title: qsTr("Sample Size Group 2") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue != "countsPerTime") || + (designValue == "variableAssociation" && measurementValue == "mixed") + } + + AssignedVariablesList + { // metafor: ri + name: "correlation" + title: qsTr("Correlation") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "quantitative") || + (designValue == "repeatedMeasures" && measurementValue == "quantitative") || + (designValue == "repeatedMeasures" && measurementValue == "binaryMarginal") + } + + AssignedVariablesList + { // metafor: pi + name: "proportionPlusPlus" + title: qsTr("Proportion +/+") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "repeatedMeasures" && measurementValue == "binaryMarginal") + } + + AssignedVariablesList + { // metafor: ni + name: "sampleSize" + title: qsTr("Sample Size") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "quantitative") || + (designValue == "singleGroup" && (measurementValue == "quantitative" || measurementValue == "binary")) || + (designValue == "repeatedMeasures" && measurementValue == "quantitative") || + (designValue == "other" && measurementValue == "reliability") || + (designValue == "other" && measurementValue == "partialCorrelation") || + (designValue == "other" && measurementValue == "modelFit") + + } + + AssignedVariablesList + { // metafor: di + name: "cohensD" + title: qsTr("Cohen's d") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "quantitative" && effectSizeValue == "SMD") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "D2ORN" || effectSizeValue == "D2ORL")) || + (designValue == "variableAssociation" && measurementValue == "mixed") || + (designValue == "repeatedMeasures" && measurementValue == "quantitative" && effectSizeValue == "SMCC") + } + + AssignedVariablesList + { // metafor: r2i + name: "rSquared" + title: qsTr("R-Squared") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "partialCorrelation" && (effectSizeValue == "SPCOR" || effectSizeValue == "ZSPCOR")) || + (designValue == "other" && measurementValue == "modelFit") + } + + AssignedVariablesList + { // metafor: ti + name: "tStatistic" + title: qsTr("T-Statistic") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "quantitative" && effectSizeValue == "SMD") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "D2ORN" || effectSizeValue == "D2ORL")) || + (designValue == "variableAssociation" && measurementValue == "quantitative") || + (designValue == "variableAssociation" && measurementValue == "mixed") || + (designValue == "repeatedMeasures" && measurementValue == "quantitative" && effectSizeValue == "SMCC") || + (designValue == "other" && measurementValue == "partialCorrelation") + } + + AssignedVariablesList + { // metafor: fi + name: "fStatistic" + title: qsTr("F-Statistic") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "modelFit") + } + + AssignedVariablesList + { // metafor: ri + name: "semipartialCorrelation" + title: qsTr("(Semi)Partial Correlation") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "other" && measurementValue == "partialCorrelation") + } + + AssignedVariablesList + { // metafor: pi + name: "pValue" + title: qsTr("P-Value") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "independentGroups" && measurementValue == "quantitative" && effectSizeValue == "SMD") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "D2ORN" || effectSizeValue == "D2ORL")) || + (designValue == "variableAssociation" && measurementValue == "quantitative") || + (designValue == "variableAssociation" && measurementValue == "mixed") || + (designValue == "repeatedMeasures" && measurementValue == "quantitative" && effectSizeValue == "SMCC") || + (designValue == "other" && measurementValue == "partialCorrelation") || + (designValue == "other" && measurementValue == "modelFit") + } + + + AssignedVariablesList + { // metafor: yi + name: "effectSize" + title: qsTr("Effect Size") + singleVariable: true + allowedColumns: ["scale"] + visible: designValue == "reportedEffectSizes" + } + + AssignedVariablesList + { // metafor: sei + name: "standardError" + title: qsTr("Standard Error") + singleVariable: true + allowedColumns: ["scale"] + visible: designValue == "reportedEffectSizes" + } + + AssignedVariablesList + { // metafor: vi + name: "samplingVariance" + title: qsTr("Sampling Variance") + singleVariable: true + allowedColumns: ["scale"] + visible: designValue == "reportedEffectSizes" + } + + AssignedPairsVariablesList + { + name: "confidenceInterval" + title: qsTr("95% Confidence Interval") + singleVariable: true + allowedColumns: ["scale"] + visible: designValue == "reportedEffectSizes" + } + + AssignedVariablesList + { // metafor: vtype for mixed designs with PHI or ZPHI + name: "samplingVarianceTypeMixed" + title: qsTr("Sampling Variance Type Mixed") + singleVariable: true + allowedColumns: ["scale"] + visible: (designValue == "variableAssociation" && measurementValue == "binary" && (effectSizeValue == "PHI" || effectSizeValue == "ZPHI") && samplingVarianceType.value == "mixed") || + (designValue == "variableAssociation" && measurementValue == "mixed" && (effectSizeValue == "RPB" || effectSizeValue == "ZPB") && samplingVarianceType.value == "mixed") + } + + AssignedVariablesList + { + name: "subset" + id: subset + title: qsTr("Subset") + singleVariable: true + allowedColumns: ["nominal"] + } + + DropDown + { + name: "subsetLevel" + label: qsTr("Subset Level") + values: subset.levels + } + } + + Group + { + title: qsTr("Frequency/event cell adjustment") + columns: 3 + visible: (designValue == "independentGroups" && measurementValue == "binary") || + (designValue == "independentGroups" && measurementValue == "countsPerTime") || + (designValue == "independentGroups" && measurementValue == "mixed" && (effectSizeValue == "PBIT" || effectSizeValue == "OR2DN" || effectSizeValue == "OR2DL")) || + (designValue == "variableAssociation" && measurementValue == "binary") || + (designValue == "singleGroup" && measurementValue == "binary") || + (designValue == "singleGroup" && measurementValue == "countsPerTime") + + DoubleField + { + label: qsTr("Add") + name: "add" + enabled: to.value != "none" + defaultValue: (effectSizeValue == "AS" || effectSizeValue == "PHI" || effectSizeValue == "ZPHI" || + effectSizeValue == "RTET" || effectSizeValue == "ZTET" || effectSizeValue == "IRSD" || + effectSizeValue == "PAS" || effectSizeValue == "PFT" || effectSizeValue == "IRS" || effectSizeValue == "IRFT" ) ? 0 : 0.5 + } + + DropDown + { + name: "to" + id: to + label: qsTr("To") + startValue: "onlyZero" + values: [ + { label: qsTr("All"), value: "all" }, + { label: qsTr("Only zero"), value: "onlyZero" }, + { label: qsTr("If any zero"), value: "ifAnyZero" }, + { label: qsTr("None"), value: "none" } + ] + //TODO: defaultValue: "onlyZero" + } + + RadioButtonGroup + { + name: "dropStudiesWithNoCasesOrEvents" + title: qsTr("Drop studies with no cases/events") + columns: 2 + radioButtonsOnSameRow: true + + RadioButton + { + value: "yes" + label: qsTr("Yes") + } + + RadioButton + { + value: "no" + label: qsTr("No") + checked: true + } + } + } + + DropDown + { + name: "samplingVarianceType" + id: samplingVarianceType + label: qsTr("Sampling variance type") + values: (function() { + if (designValue == "independentGroups" && measurementValue == "quantitative") { + if (effectSizeValue == "MD") { + return [ + { label: qsTr("LS"), value: "LS" }, + { label: qsTr("HO"), value: "HO" } + ]; + } else if (effectSizeValue == "SMD" || effectSizeValue == "SMD1") { + return [ + { label: qsTr("LS"), value: "LS" }, + { label: qsTr("LS2"), value: "LS2" }, + { label: qsTr("UB"), value: "UB" }, + { label: qsTr("AV"), value: "AV" } + ]; + } else if (effectSizeValue == "ROM") { + return [ + { label: qsTr("LS"), value: "LS" }, + { label: qsTr("HO"), value: "HO" }, + { label: qsTr("AV"), value: "AV" }, + { label: qsTr("AVHO"), value: "AVHO" } + ]; + } else { + return []; + } + } else if (designValue == "variableAssociation" && measurementValue == "quantitative") { + if (effectSizeValue == "COR" || effectSizeValue == "ZCOR") { + return [ + { label: qsTr("LS"), value: "LS" }, + { label: qsTr("AV"), value: "AV" } + ]; + } else if (effectSizeValue == "UCOR") { + return [ + { label: qsTr("LS"), value: "LS" }, + { label: qsTr("UB"), value: "UB" }, + { label: qsTr("AV"), value: "AV" } + ]; + } else { + return []; + } + } else if (designValue == "variableAssociation" && measurementValue == "binary") { + if (effectSizeValue == "PHI" || effectSizeValue == "ZPHI") { + return [ + { label: qsTr("ST"), value: "ST" }, + { label: qsTr("CS"), value: "CS" }, + { label: qsTr("mixed"), value: "mixed" } + ]; + } else { + return []; + } + } else if (designValue == "variableAssociation" && measurementValue == "mixed") { + if (effectSizeValue == "RPB" || effectSizeValue == "ZPB") { + return [ + { label: qsTr("ST"), value: "ST" }, + { label: qsTr("CS"), value: "CS" }, + { label: qsTr("mixed"), value: "mixed" } + ]; + } else { + return []; + } + } else if (designValue == "other" && measurementValue == "modelFit") { + return [ + { label: qsTr("LS"), value: "LS" }, + { label: qsTr("LS2"), value: "LS2" }, + { label: qsTr("AV"), value: "AV" }, + { label: qsTr("AV2"), value: "AV2" } + ]; + } else { + return []; + } + })() + visible: (designValue == "independentGroups" && measurementValue == "quantitative" && (effectSizeValue == "MD" || effectSizeValue == "SMD" || effectSizeValue == "SMD1" || effectSizeValue == "ROM")) || + (designValue == "variableAssociation" && measurementValue == "quantitative" && (effectSizeValue == "COR" || effectSizeValue == "ZCOR" || effectSizeValue == "UCOR")) || + (designValue == "variableAssociation" && measurementValue == "binary" && (effectSizeValue == "PHI" || effectSizeValue == "ZPHI")) || + (designValue == "variableAssociation" && measurementValue == "mixed" && (effectSizeValue == "RPB" || effectSizeValue == "ZPB")) || + (designValue == "other" && measurementValue == "modelFit") + } + + Divider { } + + } + + } + + Section + { + title: qsTr("Options") + + CheckBox + { + id: computeSamplingVariance + name: "computeSamplingVariance" + text: qsTr("Compute sampling variance") + checked: false + } + + Group + { + title: qsTr("Computed Columns Names") + + TextField + { + name: "computedColumnsNamesEffectSize" + label: qsTr("Effect size") + defaultValue: "computed effect size" + } + + TextField + { + name: "computedcolumnsNamesStandardError" + label: qsTr("Standard error") + defaultValue: "computed standard error" + visible: !computeSamplingVariance.checked + } + + TextField + { + name: "computedcolumnsNamesSamplingVariance" + label: qsTr("Sampling variance") + defaultValue: "computed sampling variance" + visible: computeSamplingVariance.checked + } + + TextField + { + name: "computedColumnsNamesEffectSizeType" + label: qsTr("Effect size type") + defaultValue: "computed effect size type" + } + + } + + } + +} diff --git a/inst/qml/FunnelPlot.qml b/inst/qml/FunnelPlot.qml new file mode 100644 index 00000000..5db34381 --- /dev/null +++ b/inst/qml/FunnelPlot.qml @@ -0,0 +1,404 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 + +Form +{ + + infoBottom: qsTr("Kossmeier, M., Tran, U. S., & Voracek, M. (2020). Power-enhanced funnel plots for meta-analysis. Zeitschrift für Psychologie, 228(1).") + + VariablesForm + { + preferredHeight: 200 * preferencesModel.uiScale + + AvailableVariablesList + { + name: "allVariables" + } + + AssignedVariablesList + { + title: qsTr("Effect Size") + name: "effectSize" + singleVariable: true + allowedColumns: ["scale"] + info: qsTr("Variable containing the observed effect sizes.") + } + + AssignedVariablesList + { + name: "effectSizeStandardError" + title: qsTr("Effect Size Standard Error") + singleVariable: true + allowedColumns: ["scale"] + info: qsTr("Variable containing the standard errors corresponding to the effect sizes.") + } + + AssignedVariablesList + { + name: "studyLabel" + id: studyLabel + title: qsTr("Study Label") + singleVariable: true + allowedColumns: ["nominal"] + info: qsTr("Variable containing labels for the studies. Used for labeling outputs and plots.") + } + + AssignedVariablesList + { + name: "split" + title: qsTr("Split") + singleVariable: true + allowedColumns: ["nominal"] + info: qsTr("Variable used to split the funnel plot into separate groups or categories.") + } + } + + CheckBox + { + name: "funnelUnderH0" + id: funnelUnderH0 + label: qsTr("Funnel under H₀") + checked: true + info: qsTr("Specify the funnel plot under the null hypothesis.") + + Group + { + title: qsTr("Parameters") + + DoubleField + { + text: qsTr("μ") + name: "funnelUnderH0ParametersFixedMu" + defaultValue: 0 + negativeValues: true + info: qsTr("Fixed value for the mean effect size under the null hypothesis.") + } + + DoubleField + { + text: qsTr("𝜏") + name: "funnelUnderH0ParametersFixedTau" + defaultValue: 0 + min: 0 + info: qsTr("Fixed value for 𝜏, representing the heterogeneity under the null hypothesis.") + } + } + + CheckBox + { + name: "funnelUnderH0FillColors" + label: qsTr("Fill colors") + checked: true + info: qsTr("Fill the funnel plot's prediction intervals under the null hypothesis with different colors.") + } + + DropDown + { + name: "funnelUnderH0LineType" + label: qsTr("Line type") + info: qsTr("Set the type of line of the funnel plot's prediction intervals under the null hypothesis.") + values: [ + { label: qsTr("None"), value: "none" }, + { label: qsTr("Solid"), value: "solid" }, + { label: qsTr("Dashed"), value: "dashed" }, + { label: qsTr("Dotted"), value: "dotted" } + ] + } + } + + CheckBox + { + name: "funnelUnderH1" + id: funnelUnderH1 + label: qsTr("Funnel under H₁") + checked: false + info: qsTr("Estimate or specify the funnel plot under the alternative hypothesis.") + + RadioButtonGroup + { + name: "funnelUnderH1Parameters" + title: qsTr("Parameters") + columns: 2 + radioButtonsOnSameRow: true + info: qsTr("Choose whether to estimate or manually fix the parameters for the funnel plot under the alternative hypothesis.") + + RadioButton + { + value: "estimated" + label: qsTr("Estimated") + checked: true + id: estimated + } + + RadioButton + { + value: "fixed" + label: qsTr("Fixed") + id: fixed + } + } + + Group + { + visible: estimated.checked + + DropDown + { + name: "method" + id: method + label: qsTr("Method") + startValue: "restrictedML" + info: qsTr("Select the heterogeneity estimation method for the funnel plot under the alternative hypothesis.") + values: [ + { label: qsTr("Equal Effects") , value: "equalEffects" }, + { label: qsTr("Fixed Effects") , value: "fixedEffects" }, + { label: qsTr("Maximum Likelihood") , value: "maximumLikelihood"}, + { label: qsTr("Restricted ML") , value: "restrictedML" }, + { label: qsTr("DerSimonian-Laird") , value: "derSimonianLaird" }, + { label: qsTr("Hedges") , value: "hedges" }, + { label: qsTr("Hunter-Schmidt") , value: "hunterSchmidt" }, + { label: qsTr("Hunter-Schmidt (SSC)") , value: "hunterSchmidtSsc" }, + { label: qsTr("Sidik-Jonkman") , value: "sidikJonkman" }, + { label: qsTr("Empirical Bayes") , value: "empiricalBayes" }, + { label: qsTr("Paule-Mandel") , value: "pauleMandel" }, + { label: qsTr("Paule-Mandel (MU)") , value: "pauleMandelMu" } + ] + } + + CheckBox + { + name: "funnelUnderH1IncludeHeterogeneity" + label: qsTr("Include heterogeneity") + enabled: method.value != "fixedEffects" && method.value != "equalEffects" + info: qsTr("Include heterogeneity (𝜏) in the funnel plot under the alternative hypothesis. If unselected, the heterogeneity estimate is not used to adjust the prediction intervals.") + } + + CheckBox + { + name: "funnelUnderH1EstimatesTable" + label: qsTr("Estimates table") + info: qsTr("Summarize the effect size and heterogeneity estimates used for the funnel plot under the alternative hypothesis in a table.") + } + } + + Group + { + visible: fixed.checked + + DoubleField + { + text: qsTr("μ") + name: "funnelUnderH1ParametersFixedMu" + defaultValue: 0 + negativeValues: true + info: qsTr("Fixed value for the mean effect size under the alternative hypothesis.") + } + + DoubleField + { + text: qsTr("𝜏") + name: "funnelUnderH1ParametersFixedTau" + defaultValue: 0 + min: 0 + info: qsTr("Fixed value for 𝜏, representing the heterogeneity under the alternative hypothesis.") + } + } + + CheckBox + { + name: "funnelUnderH1FillColors" + label: qsTr("Fill colors") + info: qsTr("Fill the funnel plot's prediction intervals under the alternative hypothesis with different colors.") + } + + DropDown + { + name: "funnelUnderH1LineType" + label: qsTr("Line type") + startValue: "solid" + info: qsTr("Set the type of line of the funnel plot's prediction intervals under the alternative hypothesis.") + values: [ + { label: qsTr("None"), value: "none" }, + { label: qsTr("Solid"), value: "solid" }, + { label: qsTr("Dashed"), value: "dashed" }, + { label: qsTr("Dotted"), value: "dotted" } + ] + } + + CheckBox + { + name: "funnelUnderH1PowerEnhancement" + enabled: funnelUnderH1.checked + label: qsTr("Power enhancement") + info: qsTr("Visualize power levels to detect the effect size under the alternative hypothesis with alpha = 0.05.") + + TextField + { + label: qsTr("Breaks") + name: "funnelUnderH1PowerEnhancementBreaks" + value: "(0.15, 0.30, 0.50, 0.70, 0.90)" + fieldWidth: 200 * preferencesModel.uiScale + info: qsTr("Specify the breakpoints for power enhancement. All levels must be within the 0.05 - 1 range.") + } + } + } + + + Group + { + title: qsTr("Estimates Mapping") + info: qsTr("Set mapping for labels, colors, and shapes of the effect size estimates.") + + DropDown + { + label: qsTr("Label") + name: "estimatesMappingLabel" + info: qsTr("Show all or only a subset of the effect size estimate labels.") + enabled: studyLabel.count > 0 + values: { + if (funnelUnderH0.checked && funnelUnderH1.checked) { + [ + { label: qsTr("All"), value: "all" }, + { label: qsTr("None"), value: "none" }, + { label: qsTr("Outside H₀"), value: "outsideH0" }, + { label: qsTr("Outside H₁"), value: "outsideH1" } + ] + } else if (funnelUnderH0.checked) { + [ + { label: qsTr("All"), value: "all" }, + { label: qsTr("None"), value: "none" }, + { label: qsTr("Outside H₀"), value: "outsideH0" } + ] + } else if (funnelUnderH1.checked) { + [ + { label: qsTr("All"), value: "all" }, + { label: qsTr("None"), value: "none" }, + { label: qsTr("Outside H₁"), value: "outsideH1" } + ] + } else { + [ + { label: qsTr("All"), value: "all" }, + { label: qsTr("None"), value: "none" } + ] + } + } + } + + DropDown + { + name: "estimatesMappingColor" + id: estimatesMappingColor + label: qsTr("Color") + addEmptyValue: true + allowedColumns: ["nominal"] + info: qsTr("Map colors of the effect size estimates in the funnel plot based on the selected variable.") + } + + DropDown + { + name: "estimatesMappingShape" + id: estimatesMappingShape + label: qsTr("Shape") + addEmptyValue: true + allowedColumns: ["nominal"] + info: qsTr("Map shapes of the effect size estimates in the funnel plot based on the selected variable.") + + } + + DropDown + { + name: "estimatesLegendPosition" + enabled: estimatesMappingColor.checked || estimatesMappingShape.checked + label: qsTr("Legend position") + startValue: "right" + info: qsTr("Set the legend position of the funnel plot. Available when color or shape mapping is enabled.") + values: + [ + { label: qsTr("None"), value: "none"}, + { label: qsTr("Bottom"), value: "bottom"}, + { label: qsTr("Right"), value: "right"}, + { label: qsTr("Top"), value: "top"}, + { label: qsTr("Left"), value: "left"} + ] + } + + DoubleField + { + name: "estimatesMappingLabelOffset" + label: qsTr("Label offset") + defaultValue: 0.10 + info: qsTr("Adjust the offset of labels in the funnel plot.") + } + } + + + Group + { + TextField + { + label: qsTr("Funnel prediction interval") + name: "funnelPredictionInterval" + value: "(0.90, 0.95, 0.99)" + fieldWidth: 120 * preferencesModel.uiScale + info: qsTr("Specify the confidence levels for the funnel plot prediction intervals.") + } + + CheckBox + { + name: "invertColors" + label: qsTr("Invert colors") + info: qsTr("Invert the colors used in the funnel plot.") + } + } + + CheckBox + { + name: "funnelPlotAsymmetryTests" + label: qsTr("Funnel plot asymmetry tests") + info: qsTr("Perform tests to detect asymmetry in the funnel plot indicating potential publication bias. The tests are performed with the 'Method' specified in the 'Funnel under H₁' option.") + + + CheckBox + { + name: "funnelPlotAsymmetryTestsMetaRegression" + label: qsTr("Meta-regression") + checked: true + info: qsTr("Include meta-regression tests for funnel plot asymmetry.") + } + + CheckBox + { + name: "funnelPlotAsymmetryTestsWeightedRegression" + label: qsTr("Weighted regression") + info: qsTr("Include weighted regression tests for funnel plot asymmetry.") + + } + + CheckBox + { + name: "funnelPlotAsymmetryTestsRankCorrelation" + label: qsTr("Rank correlation") + info: qsTr("Include rank correlation tests for funnel plot asymmetry.") + } + } +} diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisAdvanced.qml b/inst/qml/qml_components/ClassicalMetaAnalysisAdvanced.qml new file mode 100644 index 00000000..f81116ca --- /dev/null +++ b/inst/qml/qml_components/ClassicalMetaAnalysisAdvanced.qml @@ -0,0 +1,517 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 + +Section +{ + title: qsTr("Advanced") + property string module: "metaAnalysis" + columns: 1 + + info: qsTr("Advanced options for the meta-analysis, including optimization settings, clustering, and permutation tests.") + + property alias permutationTestChecked: permutationTest.checked + + Group + { + columns: 2 + + Group + { + + CheckBox + { + name: "showMetaforRCode" + text: qsTr("Show metafor R code") + Layout.preferredWidth: 300 * jaspTheme.uiScale + info: qsTr("Display the underlying R code used by the metafor package to fit the model.") + } + + CheckBox + { + name: "weightedEstimation" + text: qsTr("Weighted estimation") + checked: true + info: qsTr("Perform weighted estimation using inverse-variance weights. Uncheck for unweighted estimation.") + } + + Group + { + title: qsTr("Clustering") + enabled: clustering.count == 1 + + CheckBox + { + name: "clusteringUseClubSandwich" + text: qsTr("Use clubSandwich") + checked: true + info: qsTr("Use the clubSandwich package for robust variance estimation in clustered data. Enabled when a clustering variable is specified.") + } + + CheckBox + { + name: "clusteringSmallSampleCorrection" + text: qsTr("Small sample correction") + checked: true + info: qsTr("Apply a small-sample correction to the clustered standard errors.") + } + } + + Group + { + visible: module == "metaAnalysisMultilevelMultivariate" + title: qsTr("Random Effects / Modele Structure") + + CheckBox + { + name: "useSparseMatricies" + text: qsTr("Use sparse matricies") + checked: false + info: qsTr("Use sparse matrix representations to speed up computations in models with large datasets or complex random effects structures. Available in multilevel/multivariate meta-analysis.") + } + + CheckBox + { + name: "computeCovarianceMatrix" + text: qsTr("Compute covariance matrix") + checked: true + info: qsTr("Compute the covariance matrix of the parameter estimates. Available in multilevel/multivariate meta-analysis.") + } + } + } + + Group + { + title: qsTr("Fix Parameters") + visible: module == "metaAnalysis" + + CheckBox + { // TODO: allow fixing in multivariate models + name: "fixParametersTau2" + text: qsTr("𝜏²") + enabled: sectionModel.heterogeneityModelTermsCount == 0 + childrenOnSameRow: true + info: qsTr("Fix the value of 𝜏² in the model instead of estimating it. Unavailable in multilevel/multivariate meta-analysis or with meta-regression model for heterogeneity. A more complex heterogeneity terms in the multilevel/multivariate meta-analysis can be fixed via the 'Extend metafor call' option.") + + FormulaField + { + label: "" + name: "fixParametersTau2Value" + value: "1" + min: 0 + inclusive: JASP.None + } + } + + CheckBox + { + name: "fixParametersWeights" + text: qsTr("Weights") + childrenOnSameRow: true + info: qsTr("Use custom weights for the effect sizes instead of inverse-variance weights.") + + DropDown + { + label: "" + name: "fixParametersWeightsVariable" + source: "allVariables" + addEmptyValue: true + allowedColumns: ["scale"] + } + } + } + + Group + { + title: qsTr("Add Omibus Moderator Test") + enabled: sectionModel.effectSizeModelTermsCount > 0 || sectionModel.heterogeneityModelTermsCount > 0 + + CheckBox + { + text: qsTr("Effect size coefficients") + name: "addOmnibusModeratorTestEffectSizeCoefficients" + enabled: sectionModel.effectSizeModelTermsCount > 0 + childrenOnSameRow: false + info: qsTr("Include an omnibus test for the specified effect size regression coefficients. Available when effect size model terms are included. The coefficients should be selected via their comma-separated indicies which correspond to the order presented in the 'Effect Size Meta-Regression Coefficients' Table.") + + TextField + { + label: "" + name: "addOmnibusModeratorTestEffectSizeCoefficientsValues" + value: "(1, 2)" + info: qsTr("Specify the indices of the effect size meta-regression coefficients to include in the omnibus test, e.g. '(1, 2)' for the first and the second coefficient.") + } + } + + CheckBox + { + text: qsTr("Heterogeneity coefficients") + name: "addOmnibusModeratorTestHeterogeneityCoefficients" + enabled: sectionModel.heterogeneityModelTermsCount > 0 + childrenOnSameRow: false + visible: module == "metaAnalysis" + info: qsTr("Include an omnibus test for the specified heterogeneity regression coefficients. Available when heterogeneity model terms are included. The coefficients should be selected via their comma-separated indicies which correspond to the order presented in the 'Heterogeneity Meta-Regression Coefficients' Table.") + + TextField + { + label: "" + name: "addOmnibusModeratorTestHeterogeneityCoefficientsValues" + value: "(1, 2)" + info: qsTr("Specify the indices of the heterogeneity meta-regression coefficients to include in the omnibus test, e.g. '(1, 2)' for the first and the second coefficient.") + } + } + } + + Group + { + title: qsTr("Optimizer") + enabled: method.value == "restrictedML" || method.value == "maximumLikelihood" || method.value == "empiricalBayes" || + method.value == "pauleMandel" || method.value == "pauleMandelMu" || method.value == "qeneralizedQStatMu" || + method.value == "sidikJonkman" + info: qsTr("Optimizer settings for estimating the meta-analytic models. A more complex/unavailbe settings can be specified via the 'Extend metafor call' option.") + + DropDown + { + name: "optimizerMethod" + id: optimizerMethod + label: qsTr("Method") // TODO: switch default value on heterogeneityModelLink change + info: qsTr("Select the optimization method to use for fitting the model. Available in multilevel/multivariate meta-analysis or when heterogeneity model terms are included.") + values: { + if (module == "metaAnalysis") { + if (sectionModel.heterogeneityModelLinkValue == "log") + ["nlminb", "BFGS", "Nelder-Mead", "uobyqa", "newuoa", "bobyqa", "nloptr", "nlm"] + else + ["constrOptim", "nlminb", "BFGS", "Nelder-Mead", "uobyqa", "newuoa", "bobyqa", "nloptr", "nlm"] + } else if (module == "metaAnalysisMultilevelMultivariate") { + ["nlminb", "BFGS", "Nelder-Mead", "uobyqa", "newuoa", "bobyqa", "nloptr", "nlm", "hjk", "nmk", "mads"] // many else could be added "ucminf", "lbfgsb3c", "BBoptim" + } + + } + visible: module == "metaAnalysisMultilevelMultivariate" || sectionModel.heterogeneityModelTermsCount > 0 + } + + CheckBox + { + name: "optimizerInitialTau2" + text: qsTr("Initial 𝜏²") + checked: false + childrenOnSameRow: true + info: qsTr("Specify the initial value of 𝜏² for the optimization algorithm. Available only for specific optimization methods and unavailable in multilevel/multivariate meta-analysis or when heterogeneity model terms are included.") + visible: (method.value == "restrictedML" || method.value == "maximumLikelihood" || method.value == "empiricalBayes" || + method.value == "sidikJonkman") && sectionModel.heterogeneityModelTermsCount == 0 && module == "metaAnalysis" + + DoubleField + { + label: "" + name: "optimizerInitialTau2Value" + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerMinimumTau2" + text: qsTr("Minimum 𝜏²") + checked: false + childrenOnSameRow: true + info: qsTr("Specify the minimum allowable value of 𝜏² during optimization. Available only for specific optimization methods and unavailable in multilevel/multivariate meta-analysis or when heterogeneity model terms are included.") + visible: (method.value == "pauleMandel" || method.value == "pauleMandelMu" || method.value == "qeneralizedQStatMu") && + sectionModel.heterogeneityModelTermsCount == 0 && module == "metaAnalysis" + + DoubleField + { + label: "" + name: "optimizerMinimumTau2Value" + id: optimizerMinimumTau2Value + defaultValue: 1e-6 + min: 0 + max: optimizerMaximumTau2Value.value + } + } + + CheckBox + { + name: "optimizerMaximumTau2" + text: qsTr("Maximum 𝜏²") + checked: false + childrenOnSameRow: true + info: qsTr("Specify the maximim allowable value of 𝜏² during optimization. Available only for specific optimization methods and unavailable in multilevel/multivariate meta-analysis or when heterogeneity model terms are included.") + visible: ((method.value == "pauleMandel" || method.value == "pauleMandelMu" || method.value == "qeneralizedQStatMu") && + sectionModel.heterogeneityModelTermsCount == 0 && module == "metaAnalysis") + + DoubleField + { + label: "" + name: "optimizerMaximumTau2Value" + id: optimizerMaximumTau2Value + defaultValue: 100 + min: optimizerMinimumTau2Value.value + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerMaximumEvaluations" + text: qsTr("Maximum evaluations") + checked: false + childrenOnSameRow: true + info: qsTr("Set the maximum number of function evaluations for the optimizer. Available when using specific optimization methods in multilevel/multivariate meta-analysis.") + visible: (optimizerMethod.value == "nlminb" || optimizerMethod.value == "uobyqa" || optimizerMethod.value == "newuoa" || optimizerMethod.value == "bobyqa" || + optimizerMethod.value == "hjk" || optimizerMethod.value == "nmk" || optimizerMethod.value == "mads") && module == "metaAnalysisMultilevelMultivariate" + + IntegerField + { + label: "" + name: "optimizerMaximumEvaluationsValue" + value: 250 + min: 1 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerMaximumIterations" + text: qsTr("Maximum iterations") + checked: false + childrenOnSameRow: true + info: qsTr("Set the maximum number of iterations for the optimizer. Available when using certain estimation or optimization methods.") + visible: ((method.value == "restrictedML" || method.value == "maximumLikelihood" || method.value == "empiricalBayes" || + method.value == "pauleMandel" || method.value == "pauleMandelMu" || method.value == "qeneralizedQStatMu") && module == "metaAnalysis") || + ((optimizerMethod.value == "nlminb" || optimizerMethod.value == "Nelder-Mead" || optimizerMethod.value == "BFGS" || + optimizerMethod.value == "nloptr" || optimizerMethod.value == "nlm") && module == "metaAnalysisMultilevelMultivariate") + + IntegerField + { + label: "" + name: "optimizerMaximumIterationsValue" + value: { + if (sectionModel.heterogeneityModelTermsCount == 0) + 150 + else + 1000 + } + min: 1 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerConvergenceTolerance" + text: qsTr("Convergence tolerance") + checked: false + childrenOnSameRow: true + info: qsTr("Set the convergence tolerance for the optimizer. Available when using certain methods without heterogeneity model terms or specific optimizers in multilevel/multivariate meta-analysis.") + visible: ((method.value == "restrictedML" || method.value == "maximumLikelihood" || method.value == "empiricalBayes" || + method.value == "pauleMandel" || method.value == "pauleMandelMu" || method.value == "qeneralizedQStatMu") && + sectionModel.heterogeneityModelTermsCount == 0 && module == "metaAnalysis") || + ((optimizerMethod.value == "hjk" || optimizerMethod.value == "nmk" || optimizerMethod.value == "mads") && module == "metaAnalysisMultilevelMultivariate") + + DoubleField + { + label: "" + name: "optimizerConvergenceToleranceValue" + defaultValue: { + if (method.value == "restrictedML" || method.value == "maximumLikelihood" || method.value == "empiricalBayes") + 1e-5 + else if (method.value == "pauleMandel" || method.value == "pauleMandelMu" || method.value == "qeneralizedQStatMu") + 1e-4 + else + 1 + } + min: 0 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerConvergenceRelativeTolerance" + text: qsTr("Convergence relative tolerance") + checked: false + childrenOnSameRow: true + info: qsTr("Set the relative convergence tolerance for the optimizer. Available when heterogeneity model terms are included or using specific optimizers in multilevel/multivariate meta-analysis.") + visible: (sectionModel.heterogeneityModelTermsCount > 0 && module == "metaAnalysis") || + ((optimizerMethod.value == "nlminb" || optimizerMethod.value == "Nelder-Mead" || optimizerMethod.value == "BFGS") && module == "metaAnalysisMultilevelMultivariate") + + DoubleField + { + label: "" + name: "optimizerConvergenceRelativeToleranceValue" + defaultValue: 1e-8 + min: 0 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerStepAdjustment" + text: qsTr("Step adjustment") + checked: false + childrenOnSameRow: true + info: qsTr("Set the step adjustment factor for the optimizer. Available when using certain methods without heterogeneity model terms and unavailable in multilevel/multivariate meta-analysis.") + visible: ((method.value == "restrictedML" || method.value == "maximumLikelihood" || method.value == "empiricalBayes") && + sectionModel.heterogeneityModelTermsCount == 0 && module == "metaAnalysis") + + + DoubleField + { + label: "" + name: "optimizerStepAdjustmentValue" + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerInitialTrustRegionRadius" + text: qsTr("Initial trust region radius") + checked: false + childrenOnSameRow: true + info: qsTr("Set the initial trust region radius for the optimizer. Available when using specific optimization methods in multilevel/multivariate meta-analysis.") + visible: ((optimizerMethod.value == "uobyqa" || optimizerMethod.value == "newuoa" || optimizerMethod.value == "bobyqa") && module == "metaAnalysisMultilevelMultivariate") + + DoubleField + { + label: "" + name: "optimizerInitialTrustRegionRadiusValue" + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerFinalTrustRegionRadius" + text: qsTr("Final trust region radius") + checked: false + childrenOnSameRow: true + info: qsTr("Set the final trust region radius for the optimizer. Available when using specific optimization methods in multilevel/multivariate meta-analysis.") + visible: ((optimizerMethod.value == "uobyqa" || optimizerMethod.value == "newuoa" || optimizerMethod.value == "bobyqa") && module == "metaAnalysisMultilevelMultivariate") + + DoubleField + { + label: "" + name: "optimizerFinalTrustRegionRadiusValue" + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + } + + CheckBox + { + name: "optimizerMaximumRestarts" + text: qsTr("Maximum restarts") + checked: false + childrenOnSameRow: true + info: qsTr("Set the maximum number of restarts for the optimizer. Available when using the Nelder-Mead method ('nmk') in multilevel/multivariate meta-analysis.") + visible: optimizerMethod.value == "mmk" && module == "metaAnalysisMultilevelMultivariate" + + IntegerField + { + label: "" + name: "optimizerMaximumRestartsValue" + defaultValue: 3 + min: 1 + inclusive: JASP.None + } + } + } + + CheckBox + { + text: qsTr("Permutation test") + name: "permutationTest" + id: permutationTest + visible: module == "metaAnalysis" + enabled: clustering.count == 0 + info: qsTr("Perform a permutation test for the model coefficients. Available in the meta-analysis module when clustering is not specified. The resulting permuation p-values are displayed in the 'p (permutation)' column. Note that permutation can be computationally intesive.") + + + RadioButtonGroup + { + name: "permutationTestType" + title: qsTr("Type") + columns: 2 + radioButtonsOnSameRow: true + info: qsTr("Select the type of permutation test.") + + RadioButton + { + value: "approximate" + label: qsTr("Approximate") + checked: true + id: approximate + } + + RadioButton + { + value: "exact" + label: qsTr("Exact") + } + } + + Group + { + visible: approximate.checked + + IntegerField + { + label: qsTr("Iteration") + name: "permutationTestIteration" + value: 1000 + min: 10 + inclusive: JASP.None + info: qsTr("Specify the number of permutations to use in the approximate permutation test.") + } + + SetSeed{} + } + + } + } + + CheckBox + { + name: "advancedExtendMetaforCall" + id: advancedExtendMetaforCall + text: qsTr("Extend metafor call") + checked: false + info: qsTr("Allow adding custom arguments to the metafor function call. Consult the metafor R package documentation for the available commands (https://wviechtb.github.io/metafor/reference/rma.uni.html and https://wviechtb.github.io/metafor/reference/rma.mv.html).") + } + + TextArea + { + name: "advancedExtendMetaforCallCode" + visible: advancedExtendMetaforCall.checked + info: qsTr("The additional arguments to the metafor function call must be specified as a named list (the 'list()' call can be ommited). E.g., 'list(tau2 = 1)' (or 'tau2 = 1') can be used to fix the between-study heterogeneity to a given value. Multiple arguments must be comma-seprated, e.g. 'list(tau2 = 1, gamma2 = 0.5)' (or 'tau2 = 1, gamma2 = 0.5'). New lines are ignored." ) + } +} \ No newline at end of file diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisBubblePlot.qml b/inst/qml/qml_components/ClassicalMetaAnalysisBubblePlot.qml new file mode 100644 index 00000000..89548e70 --- /dev/null +++ b/inst/qml/qml_components/ClassicalMetaAnalysisBubblePlot.qml @@ -0,0 +1,227 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 + +Section +{ + title: qsTr("Bubble Plot") + property string module: "metaAnalysis" + info: qsTr("Options for visualizing the estimated effect sizes at different levels of the predictors with the observed estimates visualized as bubbles. Continuous predictors can be split into three bins with cutoffs at ±x standard deviations from the mean. Predictors that are not specified for either the x-axis, lines, or plots are averaged over.") + + VariablesForm + { + preferredHeight: 200 * preferencesModel.uiScale + + AvailableVariablesList + { + name: "bubblePlotModelVariables" + title: qsTr("Model Variables") + source: [{ name: "effectSizeModelTerms", use: "noInteraction" }] + } + + AssignedVariablesList + { + name: "bubblePlotSelectedVariable" + id: bubblePlotSelectedVariable + title: qsTr("Selected Variable") + singleVariable: true + allowTypeChange:false + info: qsTr("Variable to be visualized on the x-axis.") + } + + AssignedVariablesList + { + name: "bubblePlotSeparateLines" + id: bubblePlotSeparateLines + title: qsTr("Separate Lines") + allowTypeChange:false + info: qsTr("Variable(s) according to which predictions are split across different lines.") + } + + AssignedVariablesList + { + name: "bubblePlotSeparatePlots" + id: bubblePlotSeparatePlots + title: qsTr("Separate Plots") + allowTypeChange:false + info: qsTr("Variable(s) according to which predictions are split across different plots.") + } + } + + Group + { + columns: 2 + + Group + { + DoubleField + { + name: "bubblePlotSdFactorCovariates" + label: qsTr("SD factor covariates") + defaultValue: 1 + min: 0 + enabled: bubblePlotSeparateLines.columnsTypes.includes("scale") || bubblePlotSeparatePlots.columnsTypes.includes("scale") + Layout.preferredWidth: 300 * jaspTheme.uiScale + info: qsTr("Standard deviation cutoff used for binning continuous covariates.") + } + + Group + { + title: qsTr("Bubbles") + + DropDown + { + name: "bubblePlotBubblesSize" + label: qsTr("Size") + info: qsTr("Options for determining the size of the observed estimates.") + values: [ + { label: qsTr("Weight") , value: "weight"}, + { label: qsTr("Inverse variance") , value: "inverseVariance" }, + { label: qsTr("Equal") , value: "equal" } + ] + } + + DoubleField + { + name: "bubblePlotBubblesRelativeSize" + label: qsTr("Relative size") + defaultValue: 1 + min: 0 + inclusive: JASP.None + info: qsTr("Set the relative size of the observed estimates.") + } + + DoubleField + { + name: "bubblePlotBubblesTransparency" + label: qsTr("Transparency") + defaultValue: 0.90 + min: 0 + max: 1 + inclusive: JASP.None + info: qsTr("Set the transparency of the observed estimates.") + } + + DoubleField + { + enabled: bubblePlotSelectedVariable.columnsTypes.includes("nominal") + name: "bubblePlotBubblesJitter" + label: qsTr("Jitter") + defaultValue: 1 + min: 0 + info: qsTr("Set the degree of x-coordinate jitter of the observed estimates. Available when the x-axis variable is nominal.") + } + } + } + + Group + { + CheckBox + { + name: "bubblePlotConfidenceIntervals" + label: qsTr("Condifence intervals") + checked: true + info: qsTr("Include confidence intervals of the estimated effect sizes.") + + DoubleField + { + name: "bubblePlotConfidenceIntervalsTransparency" + label: qsTr("Transparency") + defaultValue: 0.30 + min: 0 + max: 1 + inclusive: JASP.None + } + } + + CheckBox + { + name: "bubblePlotPredictionIntervals" + label: qsTr("Prediction intervals") + checked: true + info: qsTr("Include prediction intervals of the estimated effect sizes.") + + DoubleField + { + name: "bubblePlotPredictionIntervalsTransparency" + label: qsTr("Transparency") + defaultValue: 0.10 + min: 0 + max: 1 + inclusive: JASP.None + } + } + } + + Group + { + + ColorPalette{} + + DropDown + { + name: "bubblePlotTheme" + id: bubblePlotTheme + label: qsTr("Theme") + startValue: "jasp" + info: qsTr("Set the theme of the bubble plot.") + values: + [ + { label: "JASP", value: "jasp"}, + { label: qsTr("White background"), value: "whiteBackground"}, + { label: qsTr("Light"), value: "light"}, + { label: qsTr("Minimal") , value: "minimal"}, + { label: "APA", value: "apa"}, + { label: "pubr", value: "pubr"} + ] + } + + DoubleField + { + enabled: bubblePlotTheme.value != "jasp" + name: "bubblePlotRelativeSizeText" + label: qsTr("Relative text size") + defaultValue: 1.5 + min: 0 + inclusive: JASP.None + info: qsTr("Adjust the text size of the bubble plot.") + } + + DropDown + { + name: "bubblePlotLegendPosition" + label: qsTr("Legend position") + info: qsTr("Set the legend position of the bubble plot.") + startValue: "right" + values: + [ + { label: qsTr("None"), value: "none"}, + { label: qsTr("Bottom"), value: "bottom"}, + { label: qsTr("Right"), value: "right"}, + { label: qsTr("Top"), value: "top"}, + { label: qsTr("Left"), value: "left"} + ] + } + } + } + +} diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisDiagnostics.qml b/inst/qml/qml_components/ClassicalMetaAnalysisDiagnostics.qml index 21cda798..b110c964 100644 --- a/inst/qml/qml_components/ClassicalMetaAnalysisDiagnostics.qml +++ b/inst/qml/qml_components/ClassicalMetaAnalysisDiagnostics.qml @@ -23,22 +23,115 @@ import JASP 1.0 Section { - title: qsTr("Diagnostics") + title: qsTr("Diagnostics") + property string module: "metaAnalysis" + columns: 1 + info: qsTr("Options for evaluating the influence of individual studies and assessing model diagnostics, including variance inflation factors, casewise diagnostics, and diagnostic plots.") + Group { - title: qsTr("Plots") - CheckBox { name: "trimFillAnalysis"; text: qsTr("Trim-fill analysis") } - CheckBox { name: "profilePlot"; text: qsTr("Profile plot") } - CheckBox + columns: 2 + + Group { - name: "diagnosticPlot"; text: qsTr("Diagnostic plots") - CheckBox { name: "diagnosticQqPlot"; text: qsTr("Q-Q plot standardized residuals"); checked: true } + CheckBox + { + name: "diagnosticsVarianceInflationFactor" + text: qsTr("Variace inflation factor") + Layout.preferredWidth: 300 * jaspTheme.uiScale + enabled: predictors.count > 0 + info: qsTr("Include variance inflation factors to assess multicollinearity among predictors. Available when predictors are included in the model.") + + CheckBox + { + name: "diagnosticsVarianceInflationFactorAggregate" + text: qsTr("Aggregate by terms") + checked: true + info: qsTr("Aggregate variance inflation factors by terms instead of individual coefficients.") + } + } + + CheckBox + { + name: "diagnosticsCasewiseDiagnostics" + text: qsTr("Casewise diagnostics") + info: qsTr("Include casewise diagnostics to assess the influence of individual studies on the meta-analysis results.") + + CheckBox + { + name: "diagnosticsCasewiseDiagnosticsShowInfluentialOnly" + text: qsTr("Show influential only") + visible: module == "metaAnalysis" + info: qsTr("Show only the influential studies in the casewise diagnostics. Unvailable when performing multilevel/multivariate meta-analysis.") + } + + CheckBox + { + name: "diagnosticsCasewiseDiagnosticsIncludePredictors" + text: qsTr("Include predictors") + info: qsTr("Include predictor variables in the casewise diagnostics output.") + } + + CheckBox + { + name: "diagnosticsCasewiseDiagnosticsDifferenceInCoefficients" + text: qsTr("Difference in coefficients") + info: qsTr("Include the differences in model coefficients when each study is excluded (DFBETAS).") + } + + CheckBox + { + name: "diagnosticsCasewiseDiagnosticsExportToDataset" + text: qsTr("Export to dataset") + info: qsTr("Export the casewise diagnostics results to the dataset.") + + CheckBox + { + name: "diagnosticsCasewiseDiagnosticsExportToDatasetInfluentialIndicatorOnly" + text: qsTr("Influential indicator only") + checked: true + visible: module == "metaAnalysis" + info: qsTr("Export only the indicator of influential cases to the dataset.") + } + } + + /* + CheckBox + { + name: "diagnosticsCasewiseDiagnosticsRerunWithoutInfluentialCases" + text: qsTr("Rerun without influential cases") + visible: false + info: qsTr("Option to rerun the analysis without influential cases.") + } + */ + } + } + + Group + { + title: qsTr("Plots") + + CheckBox + { + name: "diagnosticsPlotsProfileLikelihood" + text: qsTr("Profile likelihood") + info: qsTr("Include a profile likelihood plot for the heterogeneity parameter (τ²).") + } + + CheckBox + { + name: "diagnosticsPlotsBaujat" + text: qsTr("Baujat") + visible: module == "metaAnalysis" + info: qsTr("Include a Baujat plot to detect studies contributing to heterogeneity and overall effect size. Unvailable when performing multilevel/multivariate meta-analysis.") + } + + CheckBox + { + name: "diagnosticsResidualFunnel" + text: qsTr("Residual funnel") + info: qsTr("Include a residual funnel plot.") + } } - } - Group - { - title: qsTr("Robustness") - CheckBox { name: "failSafeN"; text: qsTr("Fail-safe N") } - CheckBox { name: "casewiseDiagnostics"; text: qsTr("Casewise diagnostics") } } } \ No newline at end of file diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisEstimatedMarginalMeans.qml b/inst/qml/qml_components/ClassicalMetaAnalysisEstimatedMarginalMeans.qml new file mode 100644 index 00000000..85cf9453 --- /dev/null +++ b/inst/qml/qml_components/ClassicalMetaAnalysisEstimatedMarginalMeans.qml @@ -0,0 +1,156 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 + +Section +{ + title: qsTr("Estimated Marginal Means") + columns: 1 + property string module: "metaAnalysis" + info: qsTr("Options to compute estimated marginal means (EMMs) for the effect size and heterogeneity models, allowing examination of predicted values at specific levels of moderators.") + + Group + { + title: qsTr("Effect size") + enabled: sectionModel.effectSizeModelTermsCount > 0 + + VariablesForm + { + preferredHeight: 250 * preferencesModel.uiScale + + AvailableVariablesList + { + name: "estimatedMarginalMeansEffectSizeModelVariables" + title: qsTr("Model variables") + source: [{ name: "effectSizeModelTerms", use: "noInteraction" }] + } + + AssignedVariablesList + { + id: estimatedMarginalMeansEffectSizeSelectedVariables + name: "estimatedMarginalMeansEffectSizeSelectedVariables" + title: qsTr("Selected variables") + allowTypeChange:false + info: qsTr("Variables selected for computing estimated marginal means in the effect size model.") + } + } + + Group + { + columns: 2 + + DoubleField + { + name: "estimatedMarginalMeansEffectSizeSdFactorCovariates" + label: qsTr("SD factor covariates") + defaultValue: 1 + min: 0 + enabled: estimatedMarginalMeansEffectSizeSelectedVariables.columnsTypes.includes("scale") + Layout.preferredWidth: 350 * jaspTheme.uiScale + info: qsTr("Standard deviation factor for covariates when computing estimated marginal means; applies to scale variables.") + } + + CheckBox + { + name: "estimatedMarginalMeansEffectSizeAddAdjustedEstimate" + label: qsTr("Add adjusted estimate") + info: qsTr("Include the adjusted effect estimate, which accounts for the moderators in the meta-regression model. This provides the effect size adjusted for the influence of moderators, as opposed to the pooled effect which combines the estimates across all studies.") + } + + CheckBox + { + name: "estimatedMarginalMeansEffectSizeTestAgainst" + label: qsTr("Test against") + childrenOnSameRow: true + info: qsTr("Option to test the estimated marginal means against a specific value.") + + DoubleField + { + name: "estimatedMarginalMeansEffectSizeTestAgainstValue" + defaultValue: 0 + } + } + } + } + + Group + { + title: qsTr("Heterogeneity") + enabled: sectionModel.heterogeneityModelTerms.count > 0 + visible: module == "metaAnalysis" + + VariablesForm + { + preferredHeight: 250 * preferencesModel.uiScale + + AvailableVariablesList + { + name: "estimatedMarginalHeterogeneityModelVariables" + title: qsTr("Model variables") + source: [{ name: "heterogeneityModelTerms", use: "noInteraction" }] + } + + AssignedVariablesList + { + id: estimatedMarginalMeansHeterogeneitySelectedVariables + name: "estimatedMarginalMeansHeterogeneitySelectedVariables" + title: qsTr("Selected variables") + allowTypeChange:false + info: qsTr("Variables selected for computing estimated marginal means in the heterogeneity model. Unvailable when performing multilevel/multivariate meta-analysis.") + } + } + + Group + { + columns: 2 + + DoubleField + { + name: "estimatedMarginalMeansHeterogeneitySdFactorCovariates" + label: qsTr("SD factor covariates") + defaultValue: 1 + min: 0 + enabled: estimatedMarginalMeansHeterogeneitySelectedVariables.columnsTypes.includes("scale") + Layout.preferredWidth: 350 * jaspTheme.uiScale + info: qsTr("Standard deviation factor for covariates when computing estimated marginal means; applies to scale variables.") + } + + CheckBox + { + name: "estimatedMarginalMeansHeterogeneityAddAdjustedEstimate" + label: qsTr("Add adjusted estimate") + info: qsTr("Include the adjusted heterogeneity estimate, which accounts for the moderators in the heterogeneity meta-regression model. This provides the heterogeneity estimate adjusted for the influence of moderators, as opposed to the pooled heterogeneity estimate which combines the heterogeneity estimates across all studies.") + } + + DropDown + { + name: "estimatedMarginalMeansHeterogeneityTransformation" + label: qsTr("Heterogeneity transformation") + info: qsTr("Transformation to apply to the heterogeneity estimate: tau (𝜏) or tau-squared (𝜏²).") + values: [ + { label: qsTr("𝜏") , value: "tau" }, + { label: qsTr("𝜏²") , value: "tau2" } + ] + } + } + } +} \ No newline at end of file diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisForestPlot.qml b/inst/qml/qml_components/ClassicalMetaAnalysisForestPlot.qml new file mode 100644 index 00000000..58265d08 --- /dev/null +++ b/inst/qml/qml_components/ClassicalMetaAnalysisForestPlot.qml @@ -0,0 +1,582 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 + +Section +{ + title: qsTr("Forest Plot") + property string module: "metaAnalysis" + columns: 1 + info: qsTr("Options for visualizing study-level information, estimated marginal means, and the model information in an all encompassing forest plot. Different sections of the forest plot can be individually enabled/disabled.") + + CheckBox + { + id: forestPlotStudyInformation + name: "forestPlotStudyInformation" + text: qsTr("Study information") + info: qsTr("Add study-level information panel to the forest plot. There are three sections of the study-level information panel: a) the left section with study labels, names, and etc designed via the 'Selected Variables' option, b) the middle section visualizing the estimates and confidence intervals based on the meta-analytic input, c) the right section textually summarizing the estimates and confidence intervals based on the meta-analytic input.") + } + + VariablesForm + { + preferredHeight: 150 * preferencesModel.uiScale + enabled: forestPlotStudyInformation.checked + + AvailableVariablesList + { + name: "forestPlotStudyInformationAllVariables" + } + + AssignedVariablesList + { + name: "forestPlotStudyInformationSelectedVariables" + id: forestPlotStudyInformationSelectedVariables + title: qsTr("Selected Variables") + allowedColumns: ["nominal"] + info: qsTr("Select variables containing study-level information to be printed in the left section of the panel. Each variable creates a new column in the panel.") + } + } + + ComponentsList + { + name: "forestPlotStudyInformationSelectedVariablesSettings" + source: "forestPlotStudyInformationSelectedVariables" + enabled: forestPlotStudyInformation.checked + visible: forestPlotStudyInformationSelectedVariables.count > 0 + headerLabels: [qsTr("Title"), qsTr("Width"), qsTr("Alignment")] + info: qsTr("Adjust the Title, Width, and Alignment of each column in the left section of the study-level information panel.") + + rowComponent: RowLayout + { + Text + { + text: rowValue + Layout.preferredWidth: 100 * preferencesModel.uiScale + elide: Text.ElideRight + } + + TextField + { + label: "" + name: "title" + value: "" + fieldWidth: 120 * preferencesModel.uiScale + useExternalBorder: false + showBorder: true + } + + DoubleField + { + label: "" + name: "width" + value: "1" + min: 0 + inclusive: JASP.None + fieldWidth: 40 * preferencesModel.uiScale + useExternalBorder: false + showBorder: true + } + + DropDown + { + label: "" + name: "alignment" + values: [ + { label: qsTr("Left") , value: "left" }, + { label: qsTr("Middle") , value: "middle" }, + { label: qsTr("Right") , value: "right" } + ] + fieldWidth: 40 * preferencesModel.uiScale + useExternalBorder: false + showBorder: true + } + } + } + + Group + { + enabled: forestPlotStudyInformation.checked + columns: 2 + + Group + { + CheckBox + { + name: "forestPlotStudyInformationPredictedEffects" + text: qsTr("Predicted effects") + enabled: effectSize.count == 1 && effectSizeStandardError.count == 1 + checked: false + Layout.preferredWidth: 300 * jaspTheme.uiScale + info: qsTr("Include predicted effect sizes in the middle section of the study-level information panel.") + } + + CheckBox + { + name: "forestPlotStudyInformationStudyWeights" + text: qsTr("Study weights") + enabled: forestPlotStudyInformation.checked + info: qsTr("Include the study weights in the right section of the study-level information panel.") + } + + CheckBox + { + name: "forestPlotStudyInformationSecondaryConfidenceInterval" + text: qsTr("Secondary confidence interval") + enabled: forestPlotStudyInformation.checked + childrenOnSameRow: true + info: qsTr("Include secondary confidence interval for effect sizes in the middle section of the study-level information panel.") + + CIField + { + name: "forestPlotStudyInformationSecondaryConfidenceIntervalLevel" + text: "" + defaultValue: 89 + } + } + } + + Group + { + title: qsTr("Order") + info: qsTr("Order the study-level information panel by a variable.") + + DropDown + { + name: "forestPlotStudyInformationOrderBy" + label: qsTr("By") + addEmptyValue: true + } + + CheckBox + { + name: "forestPlotStudyInformationOrderAscending" + text: qsTr("Ascending") + } + } + } + + + + Divider { } + + CheckBox + { + name: "forestPlotEstimatedMarginalMeans" + id: forestPlotEstimatedMarginalMeans + text: qsTr("Estimated marginal means") + enabled: sectionModel.effectSizeModelTermsCount > 0 + info: qsTr("Add estimated marginal means information to the forest plot. Available when effect size meta-regression is specified.") + } + + VariablesForm + { + preferredHeight: 250 * preferencesModel.uiScale + enabled: forestPlotEstimatedMarginalMeans.checked + + AvailableVariablesList + { + name: "forestPlotEstimatedMarginalMeansModelVariables" + title: qsTr("Model Variables") + source: [{ name: "effectSizeModelTerms", use: "noInteraction" }] + } + + AssignedVariablesList + { + id: forestPlotEstimatedMarginalMeansSelectedVariables + name: "forestPlotEstimatedMarginalMeansSelectedVariables" + title: qsTr("Selected Variables") + allowTypeChange:false + info: qsTr("Select variables for which the estimated marginal means are visualized.") + } + } + + Group + { + columns: 2 + + Group + { + CheckBox + { + name: "forestPlotEstimatedMarginalMeansTermTests" + id: forestPlotEstimatedMarginalMeansTermTests + enabled: forestPlotEstimatedMarginalMeans.checked + label: qsTr("Term tests") + checked: true + Layout.preferredWidth: 350 * jaspTheme.uiScale + info: qsTr("Include the omnibus term test of variables included in the estimated marginal means. The null hypothesis states that the effect size at all levels of the categorical variable are equal or that there is no linear association between the effect size and the continuous variable.") + } + + CheckBox + { + name: "forestPlotEstimatedMarginalMeansCoefficientTests" + id: forestPlotEstimatedMarginalMeansCoefficientTests + enabled: forestPlotEstimatedMarginalMeans.checked + label: qsTr("Coefficient tests") + checked: true + info: qsTr("Include coefficient tests of variables included in the estimated marginal means. The null hypothesis states that the estimated marginal mean for a given level equals the tested value.") + + DoubleField + { + name: "forestPlotEstimatedMarginalMeansCoefficientTestsAgainst" + text: qsTr("Against") + defaultValue: 0 + info: qsTr("Specify the test value for the coefficient tests.") + } + } + + } + + CheckBox + { + name: "forestPlotEstimatedMarginalMeansAdjustedEffectSizeEstimate" + label: qsTr("Adjusted effect size estimate") + enabled: forestPlotEstimatedMarginalMeans.checked + info: qsTr("Include the adjusted effect size estimate in the estimated marginal means section.") + } + } + + + Divider { } + + CheckBox + { + name: "forestPlotModelInformation" + id: forestPlotModelInformation + enabled: effectSize.count == 1 && effectSizeStandardError.count == 1 + text: qsTr("Model information") + info: qsTr("Add meta-analytic model information to the forest plot.") + } + + Group + { + enabled: forestPlotModelInformation.checked + columns: 2 + + CheckBox + { + name: "forestPlotPooledEffectSizeEstimate" + text: qsTr("Pooled effect size estimate") + checked: true + Layout.preferredWidth: 300 * jaspTheme.uiScale + info: qsTr("Include the overall meta-analytic effect size estimate in the model information section.") + } + + CheckBox + { + name: "forestPlotPooledEffectSizeTest" + text: qsTr("Pooled effect size test") + checked: true + info: qsTr("Include the test of the overall meta-analytic effect size estimate in the model information section.") + } + + CheckBox + { + name: "forestPlotResidualHeterogeneityTest" + text: qsTr("Residual heterogeneity test") + checked: true + info: qsTr("Include the test of the residual heterogeneity in the model information section.") + } + + CheckBox + { + name: "forestPlotResidualHeterogeneityEstimate" + text: qsTr("Residual heterogeneity estimate") + enabled: (method.value != "fixedEffects" || method.value != "equalEffects") + visible: module == "metaAnalysis" + checked: module == "metaAnalysis" + info: qsTr("Include the meta-analytic residual heterogeneity estimate in the model information section. Not available for multilevel/multivariate meta-analysis.") + } + + CheckBox + { + name: "forestPlotEffectSizeModerationTest" + text: qsTr("Effect size moderation test") + enabled: sectionModel.effectSizeModelTermsCount > 0 + checked: true + info: qsTr("Include the omnibus effect size moderation test in the model information section. Available when effect size meta-regression is specified.") + } + + CheckBox + { + name: "forestPlotHeterogeneityModerationTest" + text: qsTr("Heterogeneity moderation test") + enabled: sectionModel.heterogeneityModelTermsCount > 0 + visible: module == "metaAnalysis" + checked: module == "metaAnalysis" + info: qsTr("Include the omnibus heterogeneity moderation test in the model information section. Available when moderation meta-regression is specified.") + } + } + + + Divider {} + + Text + { + text: qsTr("Settings") + } + + Group + { + columns: 2 + + + Group + { + CheckBox + { + name: "forestPlotPredictionIntervals" + text: qsTr("Prediction intervals") + checked: true + Layout.preferredWidth: 300 * jaspTheme.uiScale + info: qsTr("Include prediction intervals of the estimated marginal means and the model information output.") + } + + CheckBox + { + name: "forestPlotEstimatesAndConfidenceIntervals" + text: qsTr("Estimates and confidence intervals") + checked: true + info: qsTr("Include effect size estimates and confidence intervals summary text in the right panel of the forest plot.") + } + + CheckBox + { + name: "forestPlotTestsInRightPanel" + text: qsTr("Tests in right panel") + checked: false + info: qsTr("Move test results text to the right panel.") + } + } + + Group + { + title: qsTr("Mapping") + info: qsTr("Select a variable for encoding the color or shape of the study information and the estimated marginal means output.") + + DropDown + { + name: "forestPlotMappingColor" + id: forestPlotMappingColor + label: qsTr("Color") + addEmptyValue: true + allowedColumns: ["nominal"] + } + + DropDown + { + name: "forestPlotMappingShape" + label: qsTr("Shape") + addEmptyValue: true + allowedColumns: ["nominal"] + } + } + + + + Group + { + title: qsTr("Relative Size") + info: qsTr("Adjust the relative size of the forest plot components.") + + DoubleField + { + name: "forestPlotRelativeSizeEstimates" + text: qsTr("Estimates") + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + + DoubleField + { + name: "forestPlotRelativeSizeText" + text: qsTr("Text") + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + + DoubleField + { + name: "forestPlotRelativeSizeAxisLabels" + text: qsTr("Axis labels") + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + + DoubleField + { + name: "forestPlotRelativeSizeRow" + text: qsTr("Row") + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + + DoubleField + { + name: "forestPlotRelativeSizeLeftPanel" + text: qsTr("Left panel") + defaultValue: 0.5 + min: 0 + inclusive: JASP.None + } + + DoubleField + { + name: "forestPlotRelativeSizeMiddlePanel" + text: qsTr("Middle panel") + defaultValue: 1 + min: 0 + inclusive: JASP.None + } + + DoubleField + { + name: "forestPlotRelativeSizeRightPanel" + text: qsTr("Right panel") + defaultValue: 0.5 + min: 0 + inclusive: JASP.None + } + + CheckBox + { + name: "forestPlotAuxiliaryAdjustWidthBasedOnText" + text: qsTr("Adjust width based on text") + checked: true + info: qsTr("Turn off the automatic width adjustment of the individual components.") + } + } + + Group + { + title: qsTr("Auxiliary") + + IntegerField + { + name: "forestPlotAuxiliaryDigits" + text: qsTr("Digits") + min: 1 + value: 2 + inclusive: JASP.None + info: qsTr("Number of digits printed for the effect size and confidence intervals summary text.") + } + + DropDown + { + label: qsTr("Tests information") + name: "forestPlotAuxiliaryTestsInformation" + values: [ + { label: qsTr("Statistic and p-value") , value: "statisticAndPValue" }, + { label: qsTr("P-value") , value: "pValue" } + ] + } + + DropDown + { + name: "forestPlotAuxiliaryPlotColor" + enabled: forestPlotMappingColor.value == "" + label: qsTr("Color") + info: qsTr("Change color of the plotted objects. Only available if no color mapping is selected.") + values: [ + { label: qsTr("Black") , value: "black"}, + { label: qsTr("Blue") , value: "blue" }, + { label: qsTr("Red") , value: "red" } + ] + } + + CheckBox + { + name: "forestPlotAuxiliaryAddVerticalLine" + text: qsTr("Add vertical line") + childrenOnSameRow: true + info: qsTr("Add a solid vertical line in the forest plot.") + + DoubleField + { + name: "forestPlotAuxiliaryAddVerticalLineValue" + defaultValue: 0 + negativeValues: true + } + } + + CheckBox + { + name: "forestPlotAuxiliaryAddVerticalLine2" + text: qsTr("Add vertical line (2)") + childrenOnSameRow: true + info: qsTr("Add a dotted vertical line in the forest plot.") + + DoubleField + { + name: "forestPlotAuxiliaryAddVerticalLineValue2" + defaultValue: 0 + negativeValues: true + } + } + + TextField + { + name: "forestPlotAuxiliaryEffectLabel" + text: qsTr("X-axis label") + value: "Effect Size" + info: qsTr("Change the x-axis label of the forest plot (the default 'Effect Size' changes in accordance with the selected effect size transformation).") + } + + CheckBox + { + name: "forestPlotAuxiliarySetXAxisLimit" + text: qsTr("X-axis limits") + childrenOnSameRow: true + info: qsTr("Change the default x-axis limits.") + + DoubleField + { + name: "forestPlotAuxiliarySetXAxisLimitLower" + id: forestPlotAuxiliarySetXAxisLimitLower + text: qsTr("Lower") + defaultValue: -1 + negativeValues: true + max: forestPlotAuxiliarySetXAxisLimitUpper + inclusive: JASP.None + } + + DoubleField + { + name: "forestPlotAuxiliarySetXAxisLimitUpper" + id: forestPlotAuxiliarySetXAxisLimitUpper + text: qsTr("Upper") + defaultValue: 1 + min: forestPlotAuxiliarySetXAxisLimitLower + inclusive: JASP.None + } + } + + } + + } + + +} \ No newline at end of file diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisMethod.qml b/inst/qml/qml_components/ClassicalMetaAnalysisMethod.qml deleted file mode 100644 index c37cd5de..00000000 --- a/inst/qml/qml_components/ClassicalMetaAnalysisMethod.qml +++ /dev/null @@ -1,42 +0,0 @@ -// -// Copyright (C) 2013-2018 University of Amsterdam -// -// This program is free software: you can redistribute it and/or modify -// it under the terms of the GNU Affero General Public License as -// published by the Free Software Foundation, either version 3 of the -// License, or (at your option) any later version. -// -// This program is distributed in the hope that it will be useful, -// but WITHOUT ANY WARRANTY; without even the implied warranty of -// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -// GNU Affero General Public License for more details. -// -// You should have received a copy of the GNU Affero General Public -// License along with this program. If not, see -// . -// -import QtQuick 2.8 -import QtQuick.Layouts 1.3 -import JASP.Controls 1.0 -import JASP.Widgets 1.0 -import JASP 1.0 - -DropDown -{ - name: "method" - label: qsTr("Method") - currentIndex: 2 - visible: visible - - values: [ - { label: qsTr("Fixed Effects") , value: "Fixed Effects" }, - { label: qsTr("Maximum Likelihood") , value: "Maximum Likelihood" }, - { label: qsTr("Restricted ML") , value: "Restricted ML" }, - { label: qsTr("DerSimonian-Laird") , value: "DerSimonian-Laird" }, - { label: qsTr("Hedges") , value: "Hedges" }, - { label: qsTr("Hunter-Schmidt") , value: "Hunter-Schmidt" }, - { label: qsTr("Sidik-Jonkman") , value: "Sidik-Jonkman" }, - { label: qsTr("Empirical Bayes") , value: "Empirical Bayes" }, - { label: qsTr("Paule-Mandel") , value: "Paule-Mandel" } - ] -} \ No newline at end of file diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisModel.qml b/inst/qml/qml_components/ClassicalMetaAnalysisModel.qml new file mode 100644 index 00000000..7ce0c8be --- /dev/null +++ b/inst/qml/qml_components/ClassicalMetaAnalysisModel.qml @@ -0,0 +1,120 @@ +// +// Copyright (C) 2013-2018 University of Amsterdam +// +// This program is free software: you can redistribute it and/or modify +// it under the terms of the GNU Affero General Public License as +// published by the Free Software Foundation, either version 3 of the +// License, or (at your option) any later version. +// +// This program is distributed in the hope that it will be useful, +// but WITHOUT ANY WARRANTY; without even the implied warranty of +// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +// GNU Affero General Public License for more details. +// +// You should have received a copy of the GNU Affero General Public +// License along with this program. If not, see +// . +// +import QtQuick 2.8 +import QtQuick.Layouts 1.3 +import JASP.Controls 1.0 +import JASP.Widgets 1.0 +import JASP 1.0 + +Section +{ + title: qsTr("Model") + columns: 2 + property string module: "metaAnalysis" + info: qsTr("Options for specifing the effect size and heterogeneity models based on the included predictors, including model terms, intercepts, and link functions.") + + property alias effectSizeModelTerms: effectSizeModelTerms + property alias effectSizeModelTermsCount: effectSizeModelTerms.count + property alias heterogeneityModelTermsCount: heterogeneityModelTerms.count + property alias heterogeneityModelLinkValue: heterogeneityModelLink.value + + + Group + { + title: qsTr("Effect size model") + info: qsTr("Specify the effect size model.") + + VariablesForm + { + preferredHeight: 150 * preferencesModel.uiScale + + AvailableVariablesList + { + name: "effectSizeModelAvailableComponents" + title: qsTr("Available Components") + source: ["predictors"] + } + + AssignedVariablesList + { + name: "effectSizeModelTerms" + id: effectSizeModelTerms + title: qsTr("Model Terms") + listViewType: JASP.Interaction + allowTypeChange:false + info: qsTr("Variables assigned as model terms in the effect size model.") + } + } + + CheckBox + { + name: "effectSizeModelIncludeIntercept" + label: qsTr("Include intercept") + checked: true + info: qsTr("Include an intercept in the effect size model.") + } + } + + Group + { + title: qsTr("Heterogeneity model") + visible: module =="metaAnalysis" + columns: 2 + info: qsTr("Specify the heterogeneity model. Unvailable when performing multilevel/multivariate meta-analysis.") + + VariablesForm + { + preferredHeight: 150 * preferencesModel.uiScale + + AvailableVariablesList + { + name: "heterogeneityModelAvailableComponents" + title: qsTr("Available Components") + source: ["predictors"] + } + + AssignedVariablesList + { + name: "heterogeneityModelTerms" + id: heterogeneityModelTerms + title: qsTr("Model Terms") + listViewType: JASP.Interaction + allowTypeChange:false + addAvailableVariablesToAssigned: false + info: qsTr("Variables assigned as model terms in the heterogeneity model. Specifying a heterogeneity model results in a 'location-scale' meta-analytic model.") + } + } + + CheckBox + { + name: "heterogeneityModelIncludeIntercept"; + label: qsTr("Include intercept") + checked: true + info: qsTr("Include an intercept in the heterogeneity model.") + } + + DropDown + { + name: "heterogeneityModelLink" + id: heterogeneityModelLink + label: qsTr("Link") + values: ["log", "identity"] + info: qsTr("Link function used in the heterogeneity model: 'log' or 'identity'.") + } + } +} diff --git a/inst/qml/qml_components/ClassicalMetaAnalysisStatistics.qml b/inst/qml/qml_components/ClassicalMetaAnalysisStatistics.qml index 2216daca..0005caf3 100644 --- a/inst/qml/qml_components/ClassicalMetaAnalysisStatistics.qml +++ b/inst/qml/qml_components/ClassicalMetaAnalysisStatistics.qml @@ -23,72 +23,161 @@ import JASP 1.0 Section { - title: qsTr("Statistics") - property string module: "metaAnalysis" + title: qsTr("Statistics") + columns: 2 + property string module: "metaAnalysis" + info: qsTr("Options for summarizing the meta-analytic results.") Group { - title: qsTr("Regression Coefficients") + title: qsTr("Heterogeneity") + columns: 2 + enabled: method.value != "fixedEffects" && method.value != "equalEffects" + visible: module == "metaAnalysis" + info: qsTr("Summarize the meta-analytic between-study heterogeneity. Unvailable when performing multilevel/multivariate meta-analysis.") + CheckBox { - name: "coefficientEstimate"; - text: qsTr("Estimates"); - checked: true - onClicked: { if (!checked && estimatesConfInt.checked) estimatesConfInt.click() } - CheckBox - { - id: estimatesConfInt - name: "coefficientCi"; text: qsTr("Confidence intervals") - CIField { name: "coefficientCiLevel"; label: qsTr("Interval") } - } + text: qsTr("𝜏") + name: "heterogeneityTau" + checked: true + info: qsTr("Include 𝜏, the square root of the estimated between-study variance.") + } + + CheckBox + { + text: qsTr("𝜏²") + name: "heterogeneityTau2" + checked: true + info: qsTr("Include 𝜏², the estimated between-study variance.") + } + + CheckBox + { + text: qsTr("I²") + name: "heterogeneityI2" + checked: false + info: qsTr("Include I², the percentage of total variation across studies due to heterogeneity.") + } + + CheckBox + { + text: qsTr("H²") + name: "heterogeneityH2" + checked: false + info: qsTr("Include H², an index indicating the ratio of total variability to sampling variability.") + } + } + + Group + { + title: qsTr("Random Effects / Model Structure") + visible: module == "metaAnalysisMultilevelMultivariate" + info: qsTr("Available when performing multilevel/multivariate meta-analysis.") + + CheckBox + { + text: qsTr("Test inclusion") + name: "randomEffectsTestInclusion" + checked: false + info: qsTr("Test the inclusion of the individual Random Effects / Model Structure components. The test compares the complete model (i.e., including all components) with a model without one of the specified Random Effects / Model Structure components at a time.") + } + /* TODO: will require a lot of work in sorting out which value belongs where + CheckBox + { + text: qsTr("Confidence intervals") + name: "randomEffectsConfidenceIntervals" + checked: false } - DropDown { name: "estimateTest"; label: qsTr("Test"); values: [ "z", "knha"]; } - CheckBox { name: "covarianceMatrix"; text: qsTr("Covariance matrix") } + */ + } + + Group + { + title: qsTr("Meta-Regression") + enabled: predictors.count > 0 + info: qsTr("Create summaries of the meta-regression. Available when predictors are included.") + CheckBox + { + name: "metaregressionTermTests" + text: qsTr("Term tests") + checked: true + info: qsTr("Include tests for each term in the meta-regression model. The null hypothesis states that the effect size at all levels of the categorical variable are equal or that there is no linear association between the effect size and the continuous variable).") + } + + CheckBox + { + name: "metaregressionCoefficientEstimates" + text: qsTr("Coefficient estimates") + checked: true + info: qsTr("Include estimates of the regression coefficients in the meta-regression model.") + } + + CheckBox + { + name: "metaregressionCoefficientCorrelationMatrix" + text: qsTr("Coefficient correlation matrix") + checked: false + info: qsTr("Include the correlation matrix of the regression coefficients.") + } } + Group { - title: qsTr("Model Fit") - CheckBox { name: "fitMeasure"; text: qsTr("Fit measures") } CheckBox { - id: forestPlot - name: "forestPlot" - text: qsTr("Forest plot") - - CheckBox + name: "confidenceIntervals" + text: qsTr("Confidence intervals") + checked: true + childrenOnSameRow: true + info: qsTr("Include confidence intervals in the tabular output.") + + CIField { - name: "forestPlotLabel" - text: qsTr("Show labels") - checked: true - enabled: forestPlot.checked - visible: module == "cochrane" + name: "confidenceIntervalsLevel" } + } - DropDown - { - name: "forestPlotOrder" - label: qsTr("Ordering") - enabled: forestPlot.checked - visible: module == "cochrane" - currentIndex: 1 - values: [ - { label: qsTr("Year (ascending)") , value: "yearAscending" }, - { label: qsTr("Year (descending)") , value: "yearDescending" }, - { label: qsTr("Effect size (ascending)") , value: "effectSizeAscending" }, - { label: qsTr("Effect size (descending)") , value: "effectSizeDescending" } + CheckBox + { + text: qsTr("Prediction intervals") + name: "predictionIntervals" + checked: true + info: qsTr("Include prediction intervals in the tabular output.") + } + + DropDown + {//TODO: make shorter or across both rows? + name: "transformEffectSize" + label: qsTr("Transform effect size") + setLabelAbove: true + info: qsTr("Select a transformation to apply to the effect size estimates in the output. This transformation applies to the 'Meta-Analytic Estimates Table', 'Estimated Marginal Means Table', 'Forest Plot', and the 'Bubble Plot'. The 'Meta-Regression Coeffient Estimates' are not transformed.") + values: [ + { label: qsTr("None") , value: "none" }, // NULL + { label: qsTr("Fisher's z to r") , value: "fishersZToCorrelation" }, // transf.ztor + { label: qsTr("Exponential") , value: "exponential" }, // exp + { label: qsTr("Log odds to proportions") , value: "logOddsToProportions" }, // transf.logit + { label: qsTr("Log odds to SMD (normal)") , value: "logOddsToSmdNormal" }, // transf.lnortod.norm + { label: qsTr("Log odds to SMD (logistic)") , value: "logOddsToSmdLogistic" }, // transf.lnortod.logis + { label: qsTr("SMD to log odds (normal)") , value: "smdToLogOddsNormal" }, // transf.dtolnor.norm + { label: qsTr("SMD to log odds (logistic)") , value: "smdToLogOddsLogistic" }, // transf.dtolnor.logis + { label: qsTr("Hakstian & Whalen inverse α") , value: "hakstianAndWhalenInverseAlpha"}, // transf.iahw + { label: qsTr("Bonett inverse α") , value: "bonettInverseAlpha" }, // transf.iabt + { label: qsTr("Z to R²") , value: "zToR2" }, // transf.ztor2 + { label: qsTr("SMD to Cohen's U₁") , value: "smdToCohensU1" }, // transf.dtou1 + { label: qsTr("SMD to Cohen's U₂") , value: "smdToCohensU2" }, // transf.dtou2 + { label: qsTr("SMD to Cohen's U₃") , value: "smdToCohensU3" }, // transf.dtou3 + { label: qsTr("SMD to CLES, Pr(supperiority)") , value: "smdToCles" }, // transf.dtocles ] - } - } - CheckBox { name: "funnelPlot"; text: qsTr("Funnel plot") } - CheckBox { name: "funnelPlotRankTestAsymmetry"; text: qsTr("Rank test for funnel plot asymmetry") } - CheckBox { name: "funnelPlotRegressionTestAsymmetry"; text: qsTr("Regression test for funnel plot asymmetry") } } - Group + CheckBox { - title: qsTr("Residuals Model") - CheckBox { name: "residualParameter"; text: qsTr("Residuals parameters"); checked: true;} + name: "fitMeasures" + text: qsTr("Fit measures") + info: qsTr("Include fit statistics for the model, such as AIC and BIC.") } + } \ No newline at end of file diff --git a/jaspMetaAnalysis.Rproj b/jaspMetaAnalysis.Rproj index 497f8bfc..0b4df82b 100644 --- a/jaspMetaAnalysis.Rproj +++ b/jaspMetaAnalysis.Rproj @@ -17,4 +17,5 @@ StripTrailingWhitespace: Yes BuildType: Package PackageUseDevtools: Yes +PackageCleanBeforeInstall: No PackageInstallArgs: --no-multiarch --with-keep.source diff --git a/renv/.gitignore b/renv/.gitignore new file mode 100644 index 00000000..0ec0cbba --- /dev/null +++ b/renv/.gitignore @@ -0,0 +1,7 @@ +library/ +local/ +cellar/ +lock/ +python/ +sandbox/ +staging/ diff --git a/run.R b/run.R new file mode 100644 index 00000000..eb57494e --- /dev/null +++ b/run.R @@ -0,0 +1,3 @@ +renv::activate() +renv::restore() +renv::install('.') diff --git a/tests/dist.csv b/tests/dist.csv new file mode 100644 index 00000000..c4bc2085 --- /dev/null +++ b/tests/dist.csv @@ -0,0 +1,3 @@ +,m,f +m,1,1.2 +f,1.2,1 diff --git a/tests/species.phy-dat.csv b/tests/species.phy-dat.csv new file mode 100644 index 00000000..176d81f6 --- /dev/null +++ b/tests/species.phy-dat.csv @@ -0,0 +1,171 @@ +"","article","author","year","species","amniotes","environment","ri","ni","yi","vi","species.phy","esid" +"1",1,"Abell, A.J.","1999","Sceloporus_virgatus","yes","wild",0.1,21,0.100335347731076,0.0555555555555556,"Sceloporus_virgatus",1 +"2",1,"Abell, A.J.","1999","Sceloporus_virgatus","yes","wild",-0.17,14,-0.171666663500579,0.0909090909090909,"Sceloporus_virgatus",2 +"3",1,"Abell, A.J.","1999","Sceloporus_virgatus","yes","wild",-0.07,21,-0.0701146706543251,0.0555555555555556,"Sceloporus_virgatus",3 +"4",1,"Abell, A.J.","1999","Sceloporus_virgatus","yes","wild",-0.14,14,-0.140925576070494,0.0909090909090909,"Sceloporus_virgatus",4 +"5",2,"Allaine, D., Graziani, L. & Coulon, J.","1998","Marmota_marmota","yes","wild",-0.54,74,-0.604155602962267,0.0140845070422535,"Marmota_marmota",5 +"6",3,"Baron, J.P., Tully, T. & Le Galliard, J.F.","2010","Vipera_ursinii","yes","wild",0.487,105,0.532120050644693,0.00980392156862745,"Vipera_ursinii",6 +"7",4,"Blouin-Demers, G. & Weatherhead, P.J.","2007","Pantherophis_obsoletus","yes","wild",-0.29,104,-0.298566263660178,0.0099009900990099,"Pantherophis_obsoletus",7 +"8",5,"Bluhm, C.K. & Gowaty, P.A.","2004","Anas_platyrhynchos","yes","captive",0.395,49,0.417710618112312,0.0217391304347826,"Anas_platyrhynchos",8 +"9",6,"Brown, G.P. & Shine, R.","2005","Tropidonophis_mairii","yes","wild",-0.13,318,-0.130739850028878,0.00317460317460317,"Tropidonophis_mairii",9 +"10",10,"Dobson, F.S. & Michener, G.R.","1995","Urocitellus_richardsonii","yes","wild",-0.67,51,-0.810743125475137,0.0208333333333333,"Urocitellus_richardsonii",10 +"11",10,"Dobson, F.S. & Michener, G.R.","1995","Urocitellus_richardsonii","yes","wild",-0.4,38,-0.423648930193602,0.0285714285714286,"Urocitellus_richardsonii",11 +"12",11,"Dobson, F.S., Risch, T.S. & Murie, J.O.","1999","Urocitellus_richardsonii","yes","wild",-0.53,134,-0.590145159841189,0.00763358778625954,"Urocitellus_richardsonii",12 +"13",11,"Dobson, F.S., Risch, T.S. & Murie, J.O.","1999","Urocitellus_richardsonii","yes","wild",-0.5,43,-0.549306144334055,0.025,"Urocitellus_richardsonii",13 +"14",15,"Ebert, D.","1993","Daphnia_magna","no","captive",0.03,215,0.0300090048631265,0.00471698113207547,"Daphnia_magna",14 +"15",16,"Edwards, T.M., Miller, H.D. & Guillette Jr., L.J.","2006","Gambusia_holbrooki","no","wild",-0.32,240,-0.331647108705132,0.00421940928270042,"Gambusia_holbrooki",15 +"16",17,"Ferreiro, R. & Galan, P.","2004","Anguis_fragilis","yes","captive",0.898,68,1.4617915829428,0.0153846153846154,"Anguis_fragilis",16 +"17",20,"Galeotti, P., Rubolini, D., Fea, G., Ghia, D., Nardi, P.A., Gherardi, F. & Fasola, M.","2006","Austropotamobius_italicus","no","wild",-0.17,68,-0.171666663500579,0.0153846153846154,"Austropotamobius_italicus",17 +"18",21,"Genoud, M. & Perrin, N.","1994","Crocidura_russula","yes","captive",-0.64,62,-0.758173744684044,0.0169491525423729,"Crocidura_russula",18 +"19",22,"Gignac, A. & Gregory, P.T.","2005","Thamnophis_ordinoides","yes","captive",-0.22,24,-0.223656109021832,0.0476190476190476,"Thamnophis_ordinoides",19 +"20",23,"Glazier, D.S.","1992","Daphnia_magna","no","captive",0.752,43,0.977542262665677,0.025,"Daphnia_magna",20 +"21",23,"Glazier, D.S.","1992","Daphnia_magna","no","captive",0.168,43,0.169607861283482,0.025,"Daphnia_magna",21 +"22",27,"Hassal, M., Walters, R.J., Telfer, M. & Hassall, M.R.J.","2006","Chorthippus_brunneus","no","wild",-0.406,27,-0.430812376503983,0.0416666666666667,"Chorthippus_brunneus",22 +"23",27,"Hassal, M., Walters, R.J., Telfer, M. & Hassall, M.R.J.","2006","Chorthippus_brunneus","no","captive",-0.433,131,-0.46358306205021,0.0078125,"Chorthippus_brunneus",23 +"24",30,"Huber, S., Hoffmann, E., Millesi, E., Dittami, J. & Arnold, W.","2001","Urocitellus_richardsonii","yes","wild",-0.86,27,-1.29334467204897,0.0416666666666667,"Urocitellus_richardsonii",24 +"25",32,"Kasparian, K., Gei_ler, E. & Trillmich, F.","2005","Cavia_aperea","yes","captive",-0.53,249,-0.590145159841189,0.0040650406504065,"Cavia_aperea",25 +"26",36,"Luiselli, L., Capula, M. & Shine, R.","1996","Coronella_austriaca","yes","wild",0.4,28,0.423648930193602,0.04,"Coronella_austriaca",26 +"27",39,"Marsh-Matthews, E., Brooks, M., Deaton, R. & Tan, H.","2005","Gambusia_affinis","no","captive",-0.393,23,-0.415343091360154,0.05,"Gambusia_affinis",27 +"28",39,"Marsh-Matthews, E., Brooks, M., Deaton, R. & Tan, H.","2005","Gambusia_geiseri","no","captive",0.088,26,0.0882282186707783,0.0434782608695652,"Gambusia_geiseri",28 +"29",40,"Michel, C.L. & Bonnet, X.","2012","Cavia_aperea","yes","captive",-0.78,22,-1.04537054846688,0.0526315789473684,"Cavia_aperea",29 +"30",41,"Michimae, H.","2007","Hynobius_retardatus","no","captive",-0.658,154,-0.789278299316318,0.00662251655629139,"Hynobius_retardatus",30 +"31",42,"Radder, R.S. & Shanbhag, B.A.","2004","Calotes_versicolor","yes","wild",-0.57,25,-0.647522844827373,0.0454545454545455,"Calotes_versicolor",31 +"32",46,"Scantlebury, M., Butterwick, R. & Speakman, J.R.","2001","Canis_lupus","yes","captive",-0.319,12,-0.330533423283901,0.111111111111111,"Canis_lupus",32 +"33",46,"Scantlebury, M., Butterwick, R. & Speakman, J.R.","2001","Canis_lupus","yes","captive",-0.418,7,-0.445266129680317,0.25,"Canis_lupus",33 +"34",49,"Sikes, R.S.","1995","Onychomys_leucogaster","yes","captive",0.282,42,0.289853534216196,0.0256410256410256,"Onychomys_leucogaster",34 +"35",51,"Skibiel, A.L., Dobson, F.S. & Murie, J.O.","2009","Urocitellus_columbianus","yes","wild",-0.28,90,-0.287682072451781,0.0114942528735632,"Urocitellus_columbianus",35 +"36",53,"Stuart-Smith, J., Swain, R., Stuart-Smith, R.D. & Wapstra, E.","2007","Rankinia_diemensis","yes","captive",0.05,90,0.0500417292784913,0.0114942528735632,"Rankinia_diemensis",36 +"37",54,"Taborsky, B., Skubic, E. & Bruintjes, R.","2007","Neolamprologus_pulcher","no","captive",0.26,10,0.266108406873654,0.142857142857143,"Neolamprologus_pulcher",37 +"38",56,"Wagner, E.C. & Williams, T.D.","2007","Taeniopygia_guttata","yes","captive",0.56,52,0.632833186665638,0.0204081632653061,"Taeniopygia_guttata",38 +"39",56,"Wagner, E.C. & Williams, T.D.","2007","Taeniopygia_guttata","yes","captive",0.39,22,0.41180003447869,0.0526315789473684,"Taeniopygia_guttata",39 +"40",57,"Walker, S.E., Rypstra, A.L. & Marshall, S.D.","2003","Hogna_helluo","no","wild",-0.118,17,-0.118552298854127,0.0714285714285714,"Hogna_helluo",40 +"41",58,"Wilkinson, L.R. & Gibbons, J.W.","2005","Kinosternon_subrubrum","yes","wild",0.083,635,0.0831913873722629,0.00158227848101266,"Kinosternon_subrubrum",41 +"42",58,"Wilkinson, L.R. & Gibbons, J.W.","2005","Pseudemys_floridana","yes","wild",0.158,79,0.159334821945307,0.0131578947368421,"Pseudemys_floridana",42 +"43",58,"Wilkinson, L.R. & Gibbons, J.W.","2005","Sternotherus_odoratus","yes","wild",0.193,46,0.195451376913984,0.0232558139534884,"Sternotherus_odoratus",43 +"44",59,"Bonnet, X., Naulleau, G., Shine, R. & Lourdais, O.","2001","Vipera_aspis","yes","wild",-0.14,132,-0.140925576070494,0.00775193798449612,"Vipera_aspis",44 +"45",60,"Oksanen, T.A., Koskela,E. & Mappes, T.","2002","Myodes_glareolus","yes","captive",-0.894,38,-1.44150358981698,0.0285714285714286,"Myodes_glareolus",45 +"46",61,"Rasanen, K., Fredrik, S., Laurila, A. & Merila, J.","2008","Rana_arvalis","no","wild",-0.474,233,-0.515216930005786,0.00434782608695652,"Rana_arvalis",46 +"47",62,"Rollison, N., Brooks, R.J.","2008","Chrysemys_picta","yes","wild",-0.141,130,-0.14194571393891,0.0078740157480315,"Chrysemys_picta",47 +"48",63,"Weatherhead, P.J., Brown, G.P., Prosser, M.R. & Kissner, K.J.","1999","Nerodia_sipedon","yes","wild",-0.22,75,-0.223656109021832,0.0138888888888889,"Nerodia_sipedon",48 +"49",64,"Lim, J.N.",NA,"Gambusia_affinis","no","captive",0.208,23,0.211079993340167,0.05,"Gambusia_affinis",49 +"50",65,"Arcos-Garcia, J. L., Martinez, G. D. M., Gama, R. B., Barros, O. V. E. & Morales, G. E. L.","2010","Iguana_iguana","yes","captive",0.26,137,0.266108406873654,0.00746268656716418,"Iguana_iguana",50 +"51",66,"Bauerfeind, S. S. & Fischer, K.","2007","Bicyclus_anynana","no","captive",-0.27,86,-0.2768638226551,0.0120481927710843,"Bicyclus_anynana",51 +"52",67,"Bauerfeind, S. S. & Fischer, K.","2008","Araschnia_levana","no","captive",0.37,142,0.388423099718296,0.00719424460431655,"Araschnia_levana",52 +"53",68,"Bradshaw, W. E., Holzapfel, C. M. & Oneill, T.","1993","Wyeomyia_smithii","no","captive",-0.026,41,-0.0260058610440899,0.0263157894736842,"Wyeomyia_smithii",53 +"54",69,"Brana, F., Bea, A. & Arrayago, M. J.","1991","Zootoca_vivipara","yes","captive",0.819,14,1.15377257362615,0.0909090909090909,"Zootoca_vivipara",54 +"55",70,"Brooks, R. J., Shilton, C. M., Brown, G. P. & Quinn, N. W. S.","1992","Clemmys_insculpta","yes","wild",0.5,21,0.549306144334055,0.0555555555555556,"Clemmys_insculpta",55 +"56",73,"Cabezas-Diaz, S., Virgos, E. & Villafuerte, R.","2005","Alectoris_rufa","yes","captive",0.54,23,0.604155602962267,0.05,"Alectoris_rufa",56 +"57",75,"Castilla, A. M. & Bauwens, D.","2000a","Podarcis_atrata","yes","captive",-0.552,152,-0.62125323416409,0.00671140939597315,"Podarcis_atrata",57 +"58",76,"Castilla, A. M. & Bauwens, D.","2000b","Podarcis_lilfordi","yes","captive",-0.476,27,-0.517799660419688,0.0416666666666667,"Podarcis_lilfordi",58 +"59",77,"Castro-Franco, R., Bustos-Zagal, M. G. & Mendez-De la Cruz, F. R.","2011","Ctenosaura_pectinata","yes","captive",0.408,25,0.433209450916991,0.0454545454545455,"Ctenosaura_pectinata",59 +"60",78,"Christians, J. K. & Williams, T. D.","2002","Taeniopygia_guttata","yes","captive",0.1,42,0.100335347731076,0.0256410256410256,"Taeniopygia_guttata",60 +"61",79,"Clark, D. R., Bunck, C. M. & Hall, R. J.","1997","Diadophis_punctatus","yes","captive",-0.23,47,-0.234189466759367,0.0227272727272727,"Diadophis_punctatus",61 +"62",80,"Clark, P. J., Ewert, M. A. & Nelson, C. E.","2001","Sternotherus_odoratus","yes","wild",-0.36,70,-0.37688590118819,0.0149253731343284,"Sternotherus_odoratus",62 +"63",81,"Congdon, J. D. & Sels, R. C. V.","1991","Emydoidea_blandingii","yes","wild",0.439,219,0.470991400682336,0.00462962962962963,"Emydoidea_blandingii",63 +"64",82,"Conrad, K. F. & Robertson, R. J.","1992","Sayornis_phoebe","yes","wild",-0.37,32,-0.388423099718296,0.0344827586206897,"Sayornis_phoebe",64 +"65",83,"Costantini, D., Carello, L. & Dell'Omo, G.","2010","Falco_tinnunculus","yes","wild",0.128,1368,0.128706004074512,0.000732600732600733,"Falco_tinnunculus",65 +"66",85,"Doody, J. S., Georges, A. & Young, J. E.","2003","Carettochelys_insculpta","yes","wild",-0.32,44,-0.331647108705132,0.024390243902439,"Carettochelys_insculpta",66 +"67",85,"Doody, J. S., Georges, A. & Young, J. E.","2003","Carettochelys_insculpta","yes","wild",-0.254,44,-0.259684060494553,0.024390243902439,"Carettochelys_insculpta",67 +"68",85,"Doody, J. S., Georges, A. & Young, J. E.","2003","Carettochelys_insculpta","yes","wild",0.098,69,0.0983155510034261,0.0151515151515152,"Carettochelys_insculpta",68 +"69",86,"Du, Y., Lin, C. X., Lin, L. H., Qiu, Q. B. & Ji, X.","2011","Leiolepis_reevesii","yes","captive",-0.26,200,-0.266108406873654,0.0050761421319797,"Leiolepis_reevesii",69 +"70",87,"Dufva, R.","1996","Parus_major","yes","wild",0.086,73,0.0862129645198654,0.0142857142857143,"Parus_major",70 +"71",88,"Formanowicz, D. R. & Shaffer, L. R.","1993","Centruroides_vittatus","no","captive",0.156,34,0.157284277318183,0.032258064516129,"Centruroides_vittatus",71 +"72",92,"Galdino, C. A. B. & Van Sluys, M.","2011","Eurolophosaurus_nanuzae","yes","wild",0.19,12,0.192337169219545,0.111111111111111,"Eurolophosaurus_nanuzae",72 +"73",93,"Guntrip, J., Sibly, R. M. & Smith, R. H.","1997","Prostephanus_truncatus","no","captive",-0.417,54,-0.444055026670094,0.0196078431372549,"Prostephanus_truncatus",73 +"74",96,"Herrmann, P. A. & Herrmann, H. W.","2005","Chamaeleo_montium","yes","captive",0.31,49,0.320545409301946,0.0217391304347826,"Chamaeleo_montium",74 +"75",97,"Horak, D., Klvana, P. & Albrecht, T.","2008","Aythya_ferina","yes","wild",0.01,25,0.0100003333533348,0.0454545454545455,"Aythya_ferina",75 +"76",98,"Isaksson, C., Johansson, A. & Andersson, S.","2008","Parus_major","yes","wild",0.021,66,0.0210030878170776,0.0158730158730159,"Parus_major",76 +"77",99,"Iverson, J. B., Barthelmess, E. L., Smith, G. R. & Derivera, C. E.","1991","Kinosternon_hirtipes","yes","wild",-0.36,11,-0.37688590118819,0.125,"Kinosternon_hirtipes",77 +"78",100,"Iverson, J. B. & Smith, G. R.","1993","Chrysemys_picta","yes","wild",0.03,202,0.0300090048631265,0.0050251256281407,"Chrysemys_picta",78 +"79",101,"Iverson, J. B. & Moler, P. E.","1997","Apalone_ferox","yes","wild",-0.015,41,-0.0150011251518994,0.0263157894736842,"Apalone_ferox",79 +"80",103,"Iverson, J. B., Hines, K. N. & Valiulis, J. M.","2004","Cyclura_cychlura","yes","wild",0.06,78,0.0600721559210316,0.0133333333333333,"Cyclura_cychlura",80 +"81",104,"Iverson, J. B., Young, C. A., Akre, T. S. B. & Griffiths, C. M.","2012","Pituophis_catenifer","yes","wild",-0.34,39,-0.354092528962243,0.0277777777777778,"Pituophis_catenifer",81 +"82",105,"Janzen, F. J.","1993","Apalone_mutica","yes","wild",0.365,6,0.382642354363184,0.333333333333333,"Apalone_mutica",82 +"83",105,"Janzen, F. J.","1993","Apalone_mutica","yes","wild",-0.141,14,-0.14194571393891,0.0909090909090909,"Apalone_mutica",83 +"84",106,"Jarvinen, A.","1996","Ficedula_hypoleuca","yes","wild",-0.033,567,-0.0330119868331721,0.00177304964539007,"Ficedula_hypoleuca",84 +"85",107,"Ji, X., Qiu, Q. B. & Diong, C. H.","2002","Calotes_versicolor","yes","captive",-0.12,20,-0.120581028408444,0.0588235294117647,"Calotes_versicolor",85 +"86",110,"Kamosawa, M. & Ota, H.","1996","Ramphotyphlops_braminus","yes","captive",-0.238,19,-0.242652948778948,0.0625,"Ramphotyphlops_braminus",86 +"87",111,"King, R. B.","1993","Storeria_dekayi","yes","captive",-0.83,25,-1.1881364043926,0.0454545454545455,"Storeria_dekayi",87 +"88",115,"Luddecke, H.","2002","Hyla_labialis","no","captive",-0.425,85,-0.4537785259527,0.0121951219512195,"Hyla_labialis",88 +"89",115,"Luddecke, H.","2002","Hyla_labialis","no","captive",-0.497,25,-0.545314107159945,0.0454545454545455,"Hyla_labialis",89 +"90",115,"Luddecke, H.","2002","Hyla_labialis","no","captive",-0.337,15,-0.35070429345804,0.0833333333333333,"Hyla_labialis",90 +"91",116,"Luiselli, L., Capula, M. & Shine, R.","1997","Natrix_natrix","yes","captive",-0.02,18,-0.0200026673068496,0.0666666666666667,"Natrix_natrix",91 +"92",119,"Czapulak, A.","2002","Cygnus_olor","yes","wild",0.108,390,0.10842286736361,0.00258397932816537,"Cygnus_olor",92 +"93",120,"Diaz, J. A., Perez-Tris, Bauwens, D., Perez-Aranda, D. Carbonell, R., Santos, T & Telleria, J.","2007","Psammodromus_algirus","yes","wild",-0.439,54,-0.470991400682336,0.0196078431372549,"Psammodromus_algirus",93 +"94",120,"Diaz, J. A., Perez-Tris, Bauwens, D., Perez-Aranda, D. Carbonell, R., Santos, T & Telleria, J.","2007","Psammodromus_algirus","yes","wild",-0.411,22,-0.436813884100614,0.0526315789473684,"Psammodromus_algirus",94 +"95",122,"Ji, X. & Brana, F.","2000","Podarcis_muralis","yes","wild",0.44,44,0.472230804420426,0.024390243902439,"Podarcis_muralis",95 +"96",123,"Macip-Ri_os, R. Cisneros, M., Aguilar-Miguel X., & Casas-Andreu, G.","2009","Kinosternon_integrum","yes","wild",-0.787,20,-1.063500674725,0.0588235294117647,"Kinosternon_integrum",96 +"97",124,"Maddox, J. D. & Weatherhead, P. J.","2012","Quiscalus_quiscula","yes","wild",0.154,161,0.155235043730911,0.00632911392405063,"Quiscalus_quiscula",97 +"98",125,"Mallory, M., McNicol, D. & Weatherhead, P.","1994","Bucephala_clangula","yes","wild",-0.19,31,-0.192337169219545,0.0357142857142857,"Bucephala_clangula",98 +"99",126,"Marquez, R.","1996","Alytes_obstetricans","no","wild",-0.04,67,-0.0400213538367682,0.015625,"Alytes_obstetricans",99 +"100",127,"Moreno, J., Merino, S., Vasquez, R. and Armesto, J.","2005","Aphrastura_spinicauda","yes","wild",0.414,30,0.440429028439753,0.037037037037037,"Aphrastura_spinicauda",100 +"101",128,"Nelson, N., Thompson, M. Pledger, S. Keall, S. & Daugherty, C.","2004","Sphenodon_punctatus","yes","wild",0.102,50,0.10235596070533,0.0212765957446809,"Sphenodon_punctatus",101 +"102",129,"Nieuwolt-Dacanay, P. M.","1997","Terrapene_ornata","yes","wild",0.107,203,0.107411175916069,0.005,"Terrapene_ornata",102 +"103",130,"Nilsson, J. & Svensson, E.","1993","Parus_caeruleus","yes","wild",-0.034,108,-0.0340131104279282,0.00952380952380952,"Parus_caeruleus",103 +"104",132,"Podlesak, D. & Blem, C.","2001","Protonotaria_citrea","yes","wild",-0.575,211,-0.654960691167658,0.00480769230769231,"Protonotaria_citrea",104 +"105",133,"Potti, J.","1993","Ficedula_hypoleuca","yes","wild",-0.06,103,-0.0600721559210316,0.01,"Ficedula_hypoleuca",105 +"106",134,"Radder, R. & Shanbhag, B.","2003","Sitana_ponticeriana","yes","wild",0.175,29,0.176820020121789,0.0384615384615385,"Sitana_ponticeriana",106 +"107",135,"Randriamahazo, H & Mori, A","2001","Oplurus_cuvieri","yes","wild",-0.22,19,-0.223656109021832,0.0625,"Oplurus_cuvieri",107 +"108",136,"Roosenburg, W. & Dunham, A.","1997","Malaclemys_terrapin","yes","wild",0.045,92,0.0450304119590906,0.0112359550561798,"Malaclemys_terrapin",108 +"109",136,"Roosenburg, W. & Dunham, A.","1997","Malaclemys_terrapin","yes","wild",0.198,95,0.20065008540444,0.0108695652173913,"Malaclemys_terrapin",109 +"110",137,"Rowe, J.","1992","Emydoidea_blandingii","yes","wild",-0.6,17,-0.693147180559945,0.0714285714285714,"Emydoidea_blandingii",110 +"111",138,"Samraoui, F., Menai, R. & Samraoui, B.","2007","Bubulcus_ibis","yes","wild",0.24,61,0.244774112659353,0.0172413793103448,"Bubulcus_ibis",111 +"112",139,"Schwarzkopf, L.","1992","Eulamprus_tympanum","yes","captive",-0.055,45,-0.0550555592082121,0.0238095238095238,"Eulamprus_tympanum",112 +"113",139,"Schwarzkopf, L.","1992","Eulamprus_tympanum","yes","captive",-0.302,48,-0.311718860003071,0.0222222222222222,"Eulamprus_tympanum",113 +"114",141,"Shanbhag, B. A.,Radder, R. S. & Saidapur, S. K.","2000","Calotes_versicolor","yes","wild",-0.236,131,-0.240533924425558,0.0078125,"Calotes_versicolor",114 +"115",143,"Sinervo, B. & Licht, P.","1991","Uta_stansburiana","yes","captive",-0.67,13,-0.810743125475137,0.1,"Uta_stansburiana",115 +"116",143,"Sinervo, B. & Licht, P.","1991","Uta_stansburiana","yes","captive",-0.59,34,-0.677666067757962,0.032258064516129,"Uta_stansburiana",116 +"117",143,"Sinervo, B. & Licht, P.","1991","Uta_stansburiana","yes","captive",-0.7,37,-0.867300527694053,0.0294117647058824,"Uta_stansburiana",117 +"118",144,"Smith, G. R., Ballinger, R. E. & Rose, B. R.","1995","Sceloporus_virgatus","yes","wild",0.141,28,0.14194571393891,0.04,"Sceloporus_virgatus",118 +"119",145,"Smith, H. G., Ottosson, U. & Ohlsson, T.","1993","Sturnus_vulgaris","yes","wild",0.27,33,0.2768638226551,0.0333333333333333,"Sturnus_vulgaris",119 +"120",145,"Smith, H. G., Ottosson, U. & Ohlsson, T.","1993","Sturnus_vulgaris","yes","wild",0.18,125,0.181982688600706,0.00819672131147541,"Sturnus_vulgaris",120 +"121",145,"Smith, H. G., Ottosson, U. & Ohlsson, T.","1993","Sturnus_vulgaris","yes","wild",0.07,187,0.0701146706543251,0.00543478260869565,"Sturnus_vulgaris",121 +"122",146,"Tanaka, K. & Mori, A.","2011","Elaphe_quadrivirgata","yes","captive",-0.69,43,-0.847955755218963,0.025,"Elaphe_quadrivirgata",122 +"123",146,"Tanaka, K. & Mori, A.","2011","Elaphe_quadrivirgata","yes","captive",-0.8,12,-1.09861228866811,0.111111111111111,"Elaphe_quadrivirgata",123 +"124",147,"Tejedo, M.","1992","Epidalea_calamita","no","captive",0.409,94,0.434409747246291,0.010989010989011,"Epidalea_calamita",124 +"125",148,"Thorbjarnarson, J. B.","1994","Caiman_crocodilus","yes","wild",0.28,152,0.287682072451781,0.00671140939597315,"Caiman_crocodilus",125 +"126",150,"Timi, J. T., Lanfranchi, A. L. & Poulin, R.","2005","Lernanthropus_cynoscicola","no","wild",0.541,54,0.605568312629785,0.0196078431372549,"Lernanthropus_cynoscicola",126 +"127",153,"Uzun, A., Uzun, B. & Kopij, G.","2010","Fulica_atra","yes","wild",-0.54,9,-0.604155602962267,0.166666666666667,"Fulica_atra",127 +"128",154,"Wallace, B. P., Sotherland, P. R., Tomillo, P. S., Reina, R. D., Spotila, J. R. & Paladino, F. V.","2007","Dermochelys_coriacea","yes","wild",0.036,137,0.0360155641044414,0.00746268656716418,"Dermochelys_coriacea",128 +"129",155,"Wheelwright, N. T., Leary, J. & Fitzgerald, C.","1991","Tachycineta_bicolor","yes","wild",-0.26,12,-0.266108406873654,0.111111111111111,"Tachycineta_bicolor",129 +"130",155,"Wheelwright, N. T., Leary, J. & Fitzgerald, C.","1991","Tachycineta_bicolor","yes","wild",-0.29,55,-0.298566263660178,0.0192307692307692,"Tachycineta_bicolor",130 +"131",155,"Wheelwright, N. T., Leary, J. & Fitzgerald, C.","1991","Tachycineta_bicolor","yes","wild",-0.21,52,-0.21317134656486,0.0204081632653061,"Tachycineta_bicolor",131 +"132",155,"Wheelwright, N. T., Leary, J. & Fitzgerald, C.","1991","Tachycineta_bicolor","yes","wild",0.12,21,0.120581028408444,0.0555555555555556,"Tachycineta_bicolor",132 +"133",156,"You, Y. Y., Feng, J., Wang, H. T., Wang, J. L., Dong, C., Su, X. R., Sun, H. M. & Gao, W.","2009","Parus_major","yes","wild",-0.204,818,-0.206902720012192,0.00122699386503067,"Parus_major",133 +"134",157,"Van-Damme, R., Bauwens, D., Brana, F. & Verheyen, R.","1992","Podarcis_muralis","yes","captive",-0.207,14,-0.210034999731342,0.0909090909090909,"Podarcis_muralis",134 +"135",158,"Murphy, M., Armbrecth, B., Vlamis, E. & Pierce, A.","2000","Tachycineta_bicolor","yes","wild",-0.178,52,-0.179916484577676,0.0204081632653061,"Tachycineta_bicolor",135 +"136",159,"Naef-Daenzer, L., Nager, R., Keller, L. & Naef-Daenzer, B.","2004","Parus_major","yes","wild",-0.685,57,-0.838474101980415,0.0185185185185185,"Parus_major",136 +"137",160,"Pettifor, R., Perrins, C. & McCleery","2001","Parus_major","yes","wild",0.14,525,0.140925576070494,0.00191570881226054,"Parus_major",137 +"138",161,"Rauter, C., Mcguire, M., Gwartney, M. & Space, J.","2010","Nicrophorus_pustulatus","no","captive",-0.558,120,-0.629924172176498,0.00854700854700855,"Nicrophorus_pustulatus",138 +"139",162,"Saeki, Y., Crowley, P., Fox, C. & Potter, D.","2009","Copidosoma_bakeri","no","captive",-0.758,25,-0.991497176044218,0.0454545454545455,"Copidosoma_bakeri",139 +"140",163,"Saino, N., Incagli, M., Martinelli, R., Ambrosini, R & Moller, A.","2001","Hirundo_rustica","yes","wild",-0.47,32,-0.510070336613307,0.0344827586206897,"Hirundo_rustica",140 +"141",164,"Sanchez-Lafuente, A.","2004","Porphyrio_porphyrio","yes","wild",0.498,19,0.546643022192718,0.0625,"Porphyrio_porphyrio",141 +"142",164,"Sanchez-Lafuente, A.","2004","Porphyrio_porphyrio","yes","wild",0.7,16,0.867300527694053,0.0769230769230769,"Porphyrio_porphyrio",142 +"143",165,"Jarvinen, A.","1991","Ficedula_hypoleuca","yes","wild",0.32,262,0.331647108705132,0.00386100386100386,"Ficedula_hypoleuca",143 +"144",165,"Jarvinen, A.","1991","Phoenicurus_phoenicurus","yes","wild",0.32,94,0.331647108705132,0.010989010989011,"Phoenicurus_phoenicurus",144 +"145",167,"Rua, M. & P., Galan","2002","Iberolacerta_monticola","yes","captive",-0.36,54,-0.37688590118819,0.0196078431372549,"Iberolacerta_monticola",145 +"146",168,"Bejakovic, D., Kalezic, M. Aleksic, I., Dzukic, G. & Crnobrnja-Isalovic, J.","1995","Podarcis_melisellensis","yes","wild",-0.81,6,-1.12702902604969,0.333333333333333,"Podarcis_melisellensis",146 +"147",168,"Bejakovic, D., Kalezic, M. Aleksic, I., Dzukic, G. & Crnobrnja-Isalovic, J.","1995","Podarcis_melisellensis","yes","captive",-0.06,38,-0.0600721559210316,0.0285714285714286,"Podarcis_melisellensis",147 +"148",169,"Adamopoulou, C. & Valakos, E.","2000","Podarcis_milensis","yes","wild",-0.475,126,-0.516507503091148,0.00813008130081301,"Podarcis_milensis",148 +"149",173,"Sasvari, L., Hegyi, Z. & Hahn, I.","1999","Ciconia_ciconia","yes","wild",0.098,96,0.0983155510034261,0.010752688172043,"Ciconia_ciconia",149 +"150",173,"Sasvari, L., Hegyi, Z. & Hahn, I.","1999","Ciconia_ciconia","yes","wild",0.12,109,0.120581028408444,0.00943396226415094,"Ciconia_ciconia",150 +"151",174,"Ramirez-Bautista, A., Stephenson, B. P., Hernandez-Ibarra, X., Hernandez-Salinas, U., Cruz-Elizalde, R., Lozano, A. & Geoffrey, R.S.","2012","Sceloporus_spinosus","yes","wild",0.424,10,0.452558715638015,0.142857142857143,"Sceloporus_spinosus",151 +"152",175,"Rohwer, F. C. & Eisenhaur, D. I.","1989","Chen_canagica","yes","wild",-0.036,277,-0.0360155641044414,0.00364963503649635,"Chen_canagica",152 +"153",175,"Rohwer, F. C. & Eisenhaur, D. I.","1989","Branta_canadensis","yes","wild",-0.056,82,-0.0560586490603531,0.0126582278481013,"Branta_canadensis",153 +"154",175,"Rohwer, F. C. & Eisenhaur, D. I.","1989","Branta_bernicla","yes","wild",-0.028,25,-0.0280073207773357,0.0454545454545455,"Branta_bernicla",154 +"155",175,"Rohwer, F. C. & Eisenhaur, D. I.","1989","Branta_bernicla","yes","wild",0.314,57,0.324976785659335,0.0185185185185185,"Branta_bernicla",155 +"156",175,"Rohwer, F. C. & Eisenhaur, D. I.","1989","Cygnus_buccinator","yes","wild",-0.226,21,-0.229970121453215,0.0555555555555556,"Cygnus_buccinator",156 +"157",175,"Rohwer, F. C. & Eisenhaur, D. I.","1989","Cygnus_buccinator","yes","wild",0.334,29,0.34732377796759,0.0384615384615385,"Cygnus_buccinator",157 +"158",175,"Rohwer, F. C. & Eisenhaur, D. I.","1989","Somateria_fischeri","yes","wild",-0.157,30,-0.158309384595911,0.037037037037037,"Somateria_fischeri",158 +"159",177,"Milanovich, J. R., Trauth, S. E., Saugey, D. A. & Jordan, R. R.","2006","Plethodon_albagula","no","wild",-0.609,91,-0.707330293503509,0.0113636363636364,"Plethodon_albagula",159 +"160",178,"Jones","unpub","Galaxias_anomalus","no","wild",-0.166,25,-0.167550482275845,0.0454545454545455,"Galaxias_anomalus",160 +"161",178,"Jones","unpub","Galaxias_depressiceps","no","wild",0.237,19,0.241593170554015,0.0625,"Galaxias_depressiceps",161 +"162",178,"Jones","unpub","Galaxias_eldoni","no","wild",0.395,22,0.417710618112312,0.0526315789473684,"Galaxias_eldoni",162 +"163",178,"Jones","unpub","Galaxias_pullus","no","wild",0.284,17,0.29202765864463,0.0714285714285714,"Galaxias_pullus",163 +"164",178,"Jones","unpub","Galaxias_gollumoides","no","wild",0.096,18,0.0962965535578922,0.0666666666666667,"Galaxias_gollumoides",164 +"165",178,"Jones","unpub","Galaxias_southern","no","wild",0.541,20,0.605568312629785,0.0588235294117647,"Galaxias_southern",165 +"166",178,"Jones","unpub","Galaxias_D.","no","wild",0.214,8,0.217359589595119,0.2,"Galaxias_D.",166 +"167",178,"Jones","unpub","Galaxias_vulgaris","no","wild",-0.387,15,-0.40826674218931,0.0833333333333333,"Galaxias_vulgaris",167 +"168",179,"Ford, N. B. & Seigel, R. A.","2010","Spalerosophis_diadema","yes","captive",-0.265,30,-0.271478450974392,0.037037037037037,"Spalerosophis_diadema",168 +"169",180,"Uller, T. & Olsson, M.","2011","Ctenophorus_fordi","yes","captive",0.123,178,0.12362598118313,0.00571428571428571,"Ctenophorus_fordi",169 +"170",181,"Boulton, R. L. Powlesland, R. G.","2008","Petroica_australis","yes","wild",-0.104,133,-0.104377406931055,0.00769230769230769,"Petroica_australis",170 diff --git a/tests/species.phy-rmatrix.csv b/tests/species.phy-rmatrix.csv new file mode 100644 index 00000000..34ca3034 --- /dev/null +++ b/tests/species.phy-rmatrix.csv @@ -0,0 +1,121 @@ +"","Hogna_helluo","Centruroides_vittatus","Chorthippus_brunneus","Prostephanus_truncatus","Nicrophorus_pustulatus","Copidosoma_bakeri","Wyeomyia_smithii","Araschnia_levana","Bicyclus_anynana","Lernanthropus_cynoscicola","Daphnia_magna","Austropotamobius_italicus","Galaxias_pullus","Galaxias_eldoni","Galaxias_gollumoides","Galaxias_anomalus","Galaxias_depressiceps","Galaxias_southern","Galaxias_D.","Galaxias_vulgaris","Gambusia_geiseri","Gambusia_affinis","Gambusia_holbrooki","Neolamprologus_pulcher","Plethodon_albagula","Hynobius_retardatus","Alytes_obstetricans","Rana_arvalis","Epidalea_calamita","Hyla_labialis","Cavia_aperea","Marmota_marmota","Urocitellus_columbianus","Urocitellus_richardsonii","Onychomys_leucogaster","Myodes_glareolus","Crocidura_russula","Canis_lupus","Carettochelys_insculpta","Apalone_ferox","Apalone_mutica","Dermochelys_coriacea","Sternotherus_odoratus","Kinosternon_subrubrum","Kinosternon_integrum","Kinosternon_hirtipes","Emydoidea_blandingii","Terrapene_ornata","Clemmys_insculpta","Chrysemys_picta","Pseudemys_floridana","Malaclemys_terrapin","Caiman_crocodilus","Alectoris_rufa","Cygnus_olor","Cygnus_buccinator","Branta_bernicla","Branta_canadensis","Chen_canagica","Somateria_fischeri","Bucephala_clangula","Anas_platyrhynchos","Aythya_ferina","Fulica_atra","Porphyrio_porphyrio","Bubulcus_ibis","Ciconia_ciconia","Falco_tinnunculus","Aphrastura_spinicauda","Sayornis_phoebe","Petroica_australis","Parus_caeruleus","Parus_major","Hirundo_rustica","Tachycineta_bicolor","Sturnus_vulgaris","Phoenicurus_phoenicurus","Ficedula_hypoleuca","Taeniopygia_guttata","Protonotaria_citrea","Quiscalus_quiscula","Sphenodon_punctatus","Eulamprus_tympanum","Psammodromus_algirus","Zootoca_vivipara","Podarcis_atrata","Podarcis_melisellensis","Podarcis_milensis","Podarcis_muralis","Podarcis_lilfordi","Iberolacerta_monticola","Anguis_fragilis","Chamaeleo_montium","Leiolepis_reevesii","Rankinia_diemensis","Ctenophorus_fordi","Sitana_ponticeriana","Calotes_versicolor","Cyclura_cychlura","Ctenosaura_pectinata","Iguana_iguana","Uta_stansburiana","Sceloporus_spinosus","Sceloporus_virgatus","Oplurus_cuvieri","Eurolophosaurus_nanuzae","Ramphotyphlops_braminus","Vipera_aspis","Vipera_ursinii","Diadophis_punctatus","Natrix_natrix","Tropidonophis_mairii","Storeria_dekayi","Thamnophis_ordinoides","Nerodia_sipedon","Spalerosophis_diadema","Elaphe_quadrivirgata","Coronella_austriaca","Pituophis_catenifer","Pantherophis_obsoletus" +"Hogna_helluo",1,0.991596638655462,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Centruroides_vittatus",0.991596638655462,1,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Chorthippus_brunneus",0.907563025210084,0.907563025210084,1,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Prostephanus_truncatus",0.907563025210084,0.907563025210084,0.92436974789916,1,0.991596638655462,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.932773109243697,0.932773109243697,0.932773109243697,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Nicrophorus_pustulatus",0.907563025210084,0.907563025210084,0.92436974789916,0.991596638655462,1,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.932773109243697,0.932773109243697,0.932773109243697,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Copidosoma_bakeri",0.907563025210084,0.907563025210084,0.92436974789916,0.957983193277311,0.957983193277311,1,0.974789915966387,0.974789915966387,0.974789915966387,0.932773109243697,0.932773109243697,0.932773109243697,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Wyeomyia_smithii",0.907563025210084,0.907563025210084,0.92436974789916,0.957983193277311,0.957983193277311,0.974789915966387,1,0.983193277310924,0.983193277310924,0.932773109243697,0.932773109243697,0.932773109243697,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Araschnia_levana",0.907563025210084,0.907563025210084,0.92436974789916,0.957983193277311,0.957983193277311,0.974789915966387,0.983193277310924,1,0.991596638655462,0.932773109243697,0.932773109243697,0.932773109243697,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Bicyclus_anynana",0.907563025210084,0.907563025210084,0.92436974789916,0.957983193277311,0.957983193277311,0.974789915966387,0.983193277310924,0.991596638655462,1,0.932773109243697,0.932773109243697,0.932773109243697,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Lernanthropus_cynoscicola",0.907563025210084,0.907563025210084,0.92436974789916,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,1,0.991596638655462,0.983193277310924,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Daphnia_magna",0.907563025210084,0.907563025210084,0.92436974789916,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.991596638655462,1,0.983193277310924,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Austropotamobius_italicus",0.907563025210084,0.907563025210084,0.92436974789916,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.983193277310924,0.983193277310924,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 +"Galaxias_pullus",0,0,0,0,0,0,0,0,0,0,0,0,1,0.991596638655462,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Galaxias_eldoni",0,0,0,0,0,0,0,0,0,0,0,0,0.991596638655462,1,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Galaxias_gollumoides",0,0,0,0,0,0,0,0,0,0,0,0,0.941176470588235,0.941176470588235,1,0.991596638655462,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Galaxias_anomalus",0,0,0,0,0,0,0,0,0,0,0,0,0.941176470588235,0.941176470588235,0.991596638655462,1,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Galaxias_depressiceps",0,0,0,0,0,0,0,0,0,0,0,0,0.941176470588235,0.941176470588235,0.957983193277311,0.957983193277311,1,0.974789915966387,0.974789915966387,0.974789915966387,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Galaxias_southern",0,0,0,0,0,0,0,0,0,0,0,0,0.941176470588235,0.941176470588235,0.957983193277311,0.957983193277311,0.974789915966387,1,0.983193277310924,0.983193277310924,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Galaxias_D.",0,0,0,0,0,0,0,0,0,0,0,0,0.941176470588235,0.941176470588235,0.957983193277311,0.957983193277311,0.974789915966387,0.983193277310924,1,0.991596638655462,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Galaxias_vulgaris",0,0,0,0,0,0,0,0,0,0,0,0,0.941176470588235,0.941176470588235,0.957983193277311,0.957983193277311,0.974789915966387,0.983193277310924,0.991596638655462,1,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Gambusia_geiseri",0,0,0,0,0,0,0,0,0,0,0,0,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,1,0.983193277310924,0.983193277310924,0.974789915966387,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Gambusia_affinis",0,0,0,0,0,0,0,0,0,0,0,0,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.983193277310924,1,0.991596638655462,0.974789915966387,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Gambusia_holbrooki",0,0,0,0,0,0,0,0,0,0,0,0,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.983193277310924,0.991596638655462,1,0.974789915966387,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Neolamprologus_pulcher",0,0,0,0,0,0,0,0,0,0,0,0,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.907563025210084,0.974789915966387,0.974789915966387,0.974789915966387,1,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454 +"Plethodon_albagula",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,1,0.991596638655462,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908 +"Hynobius_retardatus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.991596638655462,1,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908 +"Alytes_obstetricans",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.957983193277311,0.957983193277311,1,0.974789915966387,0.974789915966387,0.974789915966387,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908 +"Rana_arvalis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.957983193277311,0.957983193277311,0.974789915966387,1,0.983193277310924,0.983193277310924,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908 +"Epidalea_calamita",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.957983193277311,0.957983193277311,0.974789915966387,0.983193277310924,1,0.991596638655462,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908 +"Hyla_labialis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.957983193277311,0.957983193277311,0.974789915966387,0.983193277310924,0.991596638655462,1,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908 +"Cavia_aperea",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,1,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.941176470588235,0.941176470588235,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Marmota_marmota",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.957983193277311,1,0.983193277310924,0.983193277310924,0.966386554621849,0.966386554621849,0.941176470588235,0.941176470588235,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Urocitellus_columbianus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.957983193277311,0.983193277310924,1,0.991596638655462,0.966386554621849,0.966386554621849,0.941176470588235,0.941176470588235,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Urocitellus_richardsonii",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.957983193277311,0.983193277310924,0.991596638655462,1,0.966386554621849,0.966386554621849,0.941176470588235,0.941176470588235,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Onychomys_leucogaster",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.957983193277311,0.966386554621849,0.966386554621849,0.966386554621849,1,0.991596638655462,0.941176470588235,0.941176470588235,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Myodes_glareolus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.957983193277311,0.966386554621849,0.966386554621849,0.966386554621849,0.991596638655462,1,0.941176470588235,0.941176470588235,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Crocidura_russula",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,1,0.991596638655462,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Canis_lupus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.991596638655462,1,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336135,0.252100840336135 +"Carettochelys_insculpta",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,1,0.983193277310924,0.983193277310924,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Apalone_ferox",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.983193277310924,1,0.991596638655462,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Apalone_mutica",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.983193277310924,0.991596638655462,1,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Dermochelys_coriacea",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,1,0.966386554621849,0.966386554621849,0.966386554621849,0.966386554621849,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Sternotherus_odoratus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.966386554621849,1,0.974789915966387,0.974789915966387,0.974789915966387,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Kinosternon_subrubrum",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.966386554621849,0.974789915966387,1,0.983193277310924,0.983193277310924,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Kinosternon_integrum",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.966386554621849,0.974789915966387,0.983193277310924,1,0.991596638655462,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Kinosternon_hirtipes",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.966386554621849,0.974789915966387,0.983193277310924,0.991596638655462,1,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Emydoidea_blandingii",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,1,0.983193277310924,0.983193277310924,0.957983193277311,0.957983193277311,0.957983193277311,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Terrapene_ornata",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.983193277310924,1,0.991596638655462,0.957983193277311,0.957983193277311,0.957983193277311,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Clemmys_insculpta",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.983193277310924,0.991596638655462,1,0.957983193277311,0.957983193277311,0.957983193277311,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Chrysemys_picta",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.957983193277311,0.957983193277311,0.957983193277311,1,0.991596638655462,0.983193277310924,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Pseudemys_floridana",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.957983193277311,0.957983193277311,0.957983193277311,0.991596638655462,1,0.983193277310924,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Malaclemys_terrapin",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.890756302521008,0.890756302521008,0.890756302521008,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.957983193277311,0.957983193277311,0.957983193277311,0.983193277310924,0.983193277310924,1,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Caiman_crocodilus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,1,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Alectoris_rufa",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,1,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Cygnus_olor",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,1,0.991596638655462,0.966386554621849,0.966386554621849,0.966386554621849,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Cygnus_buccinator",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.991596638655462,1,0.966386554621849,0.966386554621849,0.966386554621849,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Branta_bernicla",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.966386554621849,0.966386554621849,1,0.991596638655462,0.983193277310924,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Branta_canadensis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.966386554621849,0.966386554621849,0.991596638655462,1,0.983193277310924,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Chen_canagica",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.966386554621849,0.966386554621849,0.983193277310924,0.983193277310924,1,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Somateria_fischeri",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,1,0.991596638655462,0.974789915966386,0.974789915966386,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Bucephala_clangula",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.991596638655462,1,0.974789915966386,0.974789915966386,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Anas_platyrhynchos",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.974789915966386,0.974789915966386,1,0.991596638655462,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Aythya_ferina",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.92436974789916,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.932773109243697,0.974789915966386,0.974789915966386,0.991596638655462,1,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Fulica_atra",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,1,0.991596638655462,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Porphyrio_porphyrio",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.991596638655462,1,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.857142857142857,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Bubulcus_ibis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,1,0.991596638655462,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Ciconia_ciconia",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.991596638655462,1,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.873949579831933,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Falco_tinnunculus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,1,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Aphrastura_spinicauda",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,1,0.991596638655462,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Sayornis_phoebe",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.991596638655462,1,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Petroica_australis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,1,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Parus_caeruleus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,1,0.991596638655462,0.974789915966386,0.974789915966386,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Parus_major",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.991596638655462,1,0.974789915966386,0.974789915966386,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Hirundo_rustica",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.974789915966386,0.974789915966386,1,0.991596638655462,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Tachycineta_bicolor",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.974789915966386,0.974789915966386,0.991596638655462,1,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Sturnus_vulgaris",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,1,0.983193277310924,0.983193277310924,0.957983193277311,0.957983193277311,0.957983193277311,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Phoenicurus_phoenicurus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.983193277310924,1,0.991596638655462,0.957983193277311,0.957983193277311,0.957983193277311,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Ficedula_hypoleuca",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.983193277310924,0.991596638655462,1,0.957983193277311,0.957983193277311,0.957983193277311,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Taeniopygia_guttata",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.957983193277311,0.957983193277311,0.957983193277311,1,0.983193277310924,0.983193277310924,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Protonotaria_citrea",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.957983193277311,0.957983193277311,0.957983193277311,0.983193277310924,1,0.991596638655462,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Quiscalus_quiscula",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.647058823529412,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.857142857142857,0.857142857142857,0.873949579831933,0.873949579831933,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.924369747899159,0.957983193277311,0.957983193277311,0.957983193277311,0.983193277310924,0.991596638655462,1,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437 +"Sphenodon_punctatus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,1,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563,0.680672268907563 +"Eulamprus_tympanum",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,1,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101,0.689075630252101 +"Psammodromus_algirus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,1,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Zootoca_vivipara",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.941176470588235,1,0.949579831932773,0.949579831932773,0.949579831932773,0.949579831932773,0.949579831932773,0.949579831932773,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Podarcis_atrata",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.941176470588235,0.949579831932773,1,0.966386554621849,0.966386554621849,0.966386554621849,0.966386554621849,0.957983193277311,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Podarcis_melisellensis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.941176470588235,0.949579831932773,0.966386554621849,1,0.991596638655462,0.974789915966386,0.974789915966386,0.957983193277311,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Podarcis_milensis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.941176470588235,0.949579831932773,0.966386554621849,0.991596638655462,1,0.974789915966386,0.974789915966386,0.957983193277311,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Podarcis_muralis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.941176470588235,0.949579831932773,0.966386554621849,0.974789915966386,0.974789915966386,1,0.991596638655462,0.957983193277311,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Podarcis_lilfordi",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.941176470588235,0.949579831932773,0.966386554621849,0.974789915966386,0.974789915966386,0.991596638655462,1,0.957983193277311,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Iberolacerta_monticola",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.941176470588235,0.949579831932773,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,1,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639 +"Anguis_fragilis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,1,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941,0.764705882352941 +"Chamaeleo_montium",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,1,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.957983193277311,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Leiolepis_reevesii",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.957983193277311,1,0.966386554621849,0.966386554621849,0.966386554621849,0.966386554621849,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Rankinia_diemensis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.957983193277311,0.966386554621849,1,0.991596638655462,0.974789915966386,0.974789915966386,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Ctenophorus_fordi",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.957983193277311,0.966386554621849,0.991596638655462,1,0.974789915966386,0.974789915966386,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Sitana_ponticeriana",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.957983193277311,0.966386554621849,0.974789915966386,0.974789915966386,1,0.991596638655462,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Calotes_versicolor",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.957983193277311,0.966386554621849,0.974789915966386,0.974789915966386,0.991596638655462,1,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Cyclura_cychlura",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,1,0.983193277310924,0.983193277310924,0.957983193277311,0.957983193277311,0.957983193277311,0.941176470588235,0.941176470588235,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Ctenosaura_pectinata",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.983193277310924,1,0.991596638655462,0.957983193277311,0.957983193277311,0.957983193277311,0.941176470588235,0.941176470588235,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Iguana_iguana",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.983193277310924,0.991596638655462,1,0.957983193277311,0.957983193277311,0.957983193277311,0.941176470588235,0.941176470588235,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Uta_stansburiana",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.957983193277311,0.957983193277311,0.957983193277311,1,0.983193277310924,0.983193277310924,0.941176470588235,0.941176470588235,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Sceloporus_spinosus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.957983193277311,0.957983193277311,0.957983193277311,0.983193277310924,1,0.991596638655462,0.941176470588235,0.941176470588235,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Sceloporus_virgatus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.957983193277311,0.957983193277311,0.957983193277311,0.983193277310924,0.991596638655462,1,0.941176470588235,0.941176470588235,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Oplurus_cuvieri",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,1,0.991596638655462,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Eurolophosaurus_nanuzae",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.941176470588235,0.991596638655462,1,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479 +"Ramphotyphlops_braminus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,1,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521009,0.890756302521009,0.890756302521008,0.890756302521008,0.890756302521008,0.890756302521009,0.890756302521009 +"Vipera_aspis",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,1,0.991596638655462,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546 +"Vipera_ursinii",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.991596638655462,1,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546,0.899159663865546 +"Diadophis_punctatus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.899159663865546,0.899159663865546,1,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622,0.915966386554622 +"Natrix_natrix",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,1,0.966386554621849,0.966386554621849,0.966386554621849,0.966386554621849,0.924369747899159,0.924369747899159,0.924369747899159,0.92436974789916,0.92436974789916 +"Tropidonophis_mairii",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.966386554621849,1,0.974789915966386,0.974789915966387,0.974789915966387,0.924369747899159,0.924369747899159,0.924369747899159,0.92436974789916,0.92436974789916 +"Storeria_dekayi",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.966386554621849,0.974789915966386,1,0.983193277310924,0.983193277310924,0.924369747899159,0.924369747899159,0.924369747899159,0.92436974789916,0.92436974789916 +"Thamnophis_ordinoides",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521009,0.899159663865546,0.899159663865546,0.915966386554622,0.966386554621849,0.974789915966387,0.983193277310924,1,0.991596638655462,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916 +"Nerodia_sipedon",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521009,0.899159663865546,0.899159663865546,0.915966386554622,0.966386554621849,0.974789915966387,0.983193277310924,0.991596638655462,1,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916 +"Spalerosophis_diadema",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.92436974789916,0.92436974789916,1,0.966386554621849,0.966386554621849,0.966386554621849,0.966386554621849 +"Elaphe_quadrivirgata",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.92436974789916,0.92436974789916,0.966386554621849,1,0.974789915966386,0.974789915966387,0.974789915966387 +"Coronella_austriaca",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.252100840336134,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521008,0.899159663865546,0.899159663865546,0.915966386554622,0.924369747899159,0.924369747899159,0.924369747899159,0.92436974789916,0.92436974789916,0.966386554621849,0.974789915966386,1,0.983193277310924,0.983193277310924 +"Pituophis_catenifer",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521009,0.899159663865546,0.899159663865546,0.915966386554622,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.966386554621849,0.974789915966387,0.983193277310924,1,0.991596638655462 +"Pantherophis_obsoletus",0,0,0,0,0,0,0,0,0,0,0,0,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.100840336134454,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.201680672268908,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.252100840336135,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.319327731092437,0.680672268907563,0.689075630252101,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.697478991596639,0.764705882352941,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.773109243697479,0.890756302521009,0.899159663865546,0.899159663865546,0.915966386554622,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.92436974789916,0.966386554621849,0.974789915966387,0.983193277310924,0.991596638655462,1