diff --git a/DESCRIPTION b/DESCRIPTION index f4548ca..5ecc33d 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@ Package: gosset Type: Package Title: Tools for Data Analysis in Experimental Agriculture -Version: 1.4 +Version: 1.4.1 Authors@R: c(person("Kauê", "de Sousa", email = "desousa.kaue@gmail.com", role = c("aut", "cre"), comment = c(ORCID = "0000-0002-7571-7845")), diff --git a/R/worth_map.R b/R/worth_map.R index 4dd3e6b..688284b 100755 --- a/R/worth_map.R +++ b/R/worth_map.R @@ -8,6 +8,8 @@ #' an object of class \code{PlackettLuce} or #' a list objects of class \code{PlackettLuce} #' @param labels a vector with the name of models in \var{object} +#' @param labels.order optional, a vector to determine the order of labels +#' @param items.order optional, a vector to determine the order of items #' @param ... additional arguments passed to methods #' @examples #' library("psychotree") @@ -106,20 +108,41 @@ worth_map.default = function(object, ...) { #' @method worth_map list #' @rdname worth_map #' @export -worth_map.list = function(object, labels, ...) { +worth_map.list = function(object, + labels, + labels.order = NULL, + items.order = NULL, ...) { + + if (is.null(labels.order)) { + lvls = labels + } else { + lvls = labels.order + } - winprobs = .combine_coeffs(object, log = TRUE, vcov = FALSE, ...) + winprobs = .combine_coeffs(object, log = TRUE, ...) # add name of features names(winprobs) = labels + if (is.null(items.order)) { + order_items = order(exp(winprobs[,lvls[[1]]])) + order_items = rownames(winprobs)[order_items] + } else { + order_items = items.order + } + + + winprobs = data.frame(items = rep(dimnames(winprobs)[[1]], times = ncol(winprobs)), labels = rep(dimnames(winprobs)[[2]], each = nrow(winprobs)), winprob = as.numeric(unlist(winprobs))) - winprobs$labels = factor(winprobs$labels, levels = labels) + winprobs$labels = factor(winprobs$labels, levels = rev(lvls)) + + winprobs$items = factor(winprobs$items, + levels = rev(order_items)) items = winprobs$items winprob = winprobs$winprob @@ -142,16 +165,13 @@ worth_map.list = function(object, labels, ...) { direction = 1, na.value = "white", name = "") + - ggplot2::theme_bw() + - theme(axis.text = ggplot2::element_text(color = "grey20"), - strip.text.x = ggplot2::element_text(color = "grey20"), - axis.text.x = ggplot2::element_text(angle = 40, vjust = 1, hjust = 1), - axis.text.y = ggplot2::element_text(angle = angle, vjust = 1, hjust = 1), - panel.grid = ggplot2::element_blank()) - ggplot2::labs(x = "", - y = "", - fill = "") - + ggplot2::theme_minimal() + + ggplot2::theme(axis.text = ggplot2::element_text(color = "grey20"), + strip.text.x = ggplot2::element_text(color = "grey20"), + axis.text.x = ggplot2::element_text(angle = 40, vjust = 1, hjust = 1), + axis.text.y = ggplot2::element_text(angle = angle, vjust = 1, hjust = 1), + panel.grid = ggplot2::element_blank()) + + ggplot2::labs(x = "", y = "") return(p) @@ -162,11 +182,14 @@ worth_map.list = function(object, labels, ...) { #'Combine coefficients from PlackettLuce models #' @param x a list with PlackettLuce models #' @param na.replace logical, to replace or keep NAs -#' @param ... further arguments passed to methods +#' @param ... additional arguments passed to methods #' @noRd .combine_coeffs = function(x, na.replace = TRUE, rescale = TRUE, ...) { - coeffs = lapply(x, function(y) {psychotools::itempar(y, ...)}) + coeffs = lapply(x, function(y) { + #psychotools::itempar(y, ...) + stats::coefficients(y, ...) + }) items = unique(unlist(lapply(coeffs, names))) diff --git a/dev/dominance-analysis.R b/dev/dominance-analysis.R new file mode 100644 index 0000000..4d4db89 --- /dev/null +++ b/dev/dominance-analysis.R @@ -0,0 +1,82 @@ +library(dominanceanalysis) +library(caTools) +library("gosset") +library("ClimMobTools") +library("PlackettLuce") +library("ggplot2") +library("patchwork") + +data("cassava", package = "gosset") + +dat = cassava + +head(dat[, 1:11]) + +keep = unlist(lapply(dat[1:ncol(dat)], function(x) sum(is.na(x)))) + +keep = keep == 0 + +dat = dat[, keep] + +names(dat) + +# extract list of traits from the data +trait_list = getTraitList(dat, pattern = c("_pos", "_neg")) + +# trait names extracted from the function +traits = unlist(lapply(trait_list, function(x) x$trait_label)) + +# clean trait names and put them title case +traits = gsub("(^|[[:space:]])([[:alpha:]])", "\\1\\U\\2", traits, perl = TRUE) + +traits + +pack = c("option_a", "option_b", "option_c") + +items = sort(unique(unlist(dat[pack]))) + +check = "Obasanjo-2" + +ov = which(traits %in% "Overall") + +R = lapply(trait_list, function(x) { + rank_tricot(dat, + items = pack, + input = x$string, + validate.rankings = TRUE) +}) + +mod = lapply(R, PlackettLuce) + +worth = lapply(mod, function(x){ + z = resample(x, log = TRUE, bootstrap = TRUE, n1 = 10, seed = 1432)$estimate + #log(z) +}) + +worth = as.data.frame(do.call("cbind", worth)) + +names(worth) = traits + +head(worth) + +plot(worth$Colour, worth$Overall) +plot(worth$Stretchability, worth$Overall) +plot(worth$Taste, worth$Overall) + +modpres = lm(Overall ~ Taste + Stretchability + Colour, data = worth) + +summary(modpres) + +dapres = dominanceAnalysis(modpres) + +getFits(dapres,"r2") + +dominanceMatrix(dapres, type="complete",fit.functions = "r2", ordered=TRUE) + +contributionByLevel(dapres,fit.functions="r2") + +plot(dapres, which.graph ="conditional",fit.function = "r2") + theme_minimal() + +dom = averageContribution(dapres,fit.functions = "r2") + + diff --git a/docs/404.html b/docs/404.html index 06c5031..3909c2a 100644 --- a/docs/404.html +++ b/docs/404.html @@ -39,7 +39,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/CODE_OF_CONDUCT.html b/docs/CODE_OF_CONDUCT.html index b9333a1..cd00044 100644 --- a/docs/CODE_OF_CONDUCT.html +++ b/docs/CODE_OF_CONDUCT.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/CONTRIBUTING.html b/docs/CONTRIBUTING.html index 8d6dd41..5082ed5 100644 --- a/docs/CONTRIBUTING.html +++ b/docs/CONTRIBUTING.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index e4496f9..543274a 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/LICENSE.html b/docs/LICENSE.html index d1244e6..caf96e2 100644 --- a/docs/LICENSE.html +++ b/docs/LICENSE.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/articles/index.html b/docs/articles/index.html index 2e0a65e..e06575a 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/articles/vignette-1-trait-prioritization-and-crop-performance.html b/docs/articles/vignette-1-trait-prioritization-and-crop-performance.html index ef1937b..82096bc 100644 --- a/docs/articles/vignette-1-trait-prioritization-and-crop-performance.html +++ b/docs/articles/vignette-1-trait-prioritization-and-crop-performance.html @@ -38,7 +38,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/articles/vignette-1-trait-prioritization-and-crop-performance_files/figure-html/worthmap-1.png b/docs/articles/vignette-1-trait-prioritization-and-crop-performance_files/figure-html/worthmap-1.png index 60424d9..eb67f1b 100644 Binary files a/docs/articles/vignette-1-trait-prioritization-and-crop-performance_files/figure-html/worthmap-1.png and b/docs/articles/vignette-1-trait-prioritization-and-crop-performance_files/figure-html/worthmap-1.png differ diff --git a/docs/articles/vignette-2-gari-eba-consumer-testing.html b/docs/articles/vignette-2-gari-eba-consumer-testing.html index 5ac53d3..0301bf4 100644 --- a/docs/articles/vignette-2-gari-eba-consumer-testing.html +++ b/docs/articles/vignette-2-gari-eba-consumer-testing.html @@ -38,7 +38,7 @@ gosset - 1.4 + 1.4.1 @@ -103,37 +103,38 @@

Kauê de

Introduction

-

Here, I present a workflow to analyze data from a consumer preference -trial executed in Nigeria and Cameroon by the International Institute of -Tropical Agriculture (IITA) under the RTBFoods project (https://rtbfoods.cirad.fr). Consumer testing was carried -out with 1,000 participants in 2022 in Cameroon and Nigeria using the -tricot approach [1]. Diverse consumers in -villages, towns, and cities evaluated the overall acceptability of -gari-eba made from 13 cassava (Manihot esculenta Crantz) -genotypes. Apart from the overall preference of the samples, the -following traits were evaluated for eba based on triangulated insights -obtained through earlier surveys and participatory work in the three -areas: Nigeria (Osun and Benue States): color, smoothness, moldability, -stretchability, and taste. Cameroon (Littoral zone): color, odor, taste, -firmness, and stretchability.

-

Traits in common are color, taste, and stretchability. The results of -this study were published by Olaosebikan et al. (2023)[2], and a deeper analysis for the Nigerian -subset, linking the consumer data to laboratory instrumental metrics, -was published by Alamu et al. (2023)[3]. -The present vignette does not intend to replicate the results of these -studies. Instead, it presents an alternative workflow to what was -developed in the study. For the replication data on Olaosebikan et -al. (2023), please visit https://github.com/AgrDataSci/rtbfoods-consumer-testing. -For the replication data on Alamu et al. (2023), please visit https://github.com/AgrDataSci/cassava-consumer-iita/.

+

This vignette demonstrates a workflow for analyzing consumer +preference data from decentralized trials of cassava (Manihot +esculenta Crantz) varieties in Nigeria and Cameroon. Using the +tricot approach [1], 1,000 participants +evaluated gari-eba made from 13 cassava genotypes in 2022. The trial was +implemented by the International Institute of Tropical Agriculture +(IITA) under the RTBFoods project (https://rtbfoods.cirad.fr). Participants assessed +overall preference and traits such as color, stretchability, and taste, +reflecting diverse consumer priorities.

+

Building on studies by Olaosebikan et al. (2023) [2] and Alamu et al. (2023) [3], this vignette introduces an alternative +workflow. It leverages statistical models, such as the Plackett-Luce +model, to analyze overall preference, explore trait-specific +performance, and account for consumer heterogeneity. By segmenting the +data by groups like country, the analysis uncovers context-specific +varietal performance and identifies the best varieties for specific +groups.

+

Additionally, a weighted selection index is proposed to integrate +multiple traits, enabling a data-driven approach to ranking varieties. +This workflow emphasizes a consumer- and market-oriented approach, +offering insights into plant breeding and selection strategies that +align with local preferences and environmental contexts. The +selection index approach is under development and open for improvements, +suggestions and comments.

+
+
+

Read the data and select traits +

The cassava data is a data frame with 1,000 observations and 27 variables, which are described in the data documentation with ?cassava. This vignette will require the packages PlackettLuce [4], ClimMobTools [5], ggplot2 [6], and patchwork [7].

-
-
-

Read the data and select traits -

 library("gosset")
 library("ClimMobTools")
@@ -285,12 +286,9 @@ 

Assess the full data
-worth_map(mod, labels = traits) +
-  labs(x = "", y = "") +
-  scale_fill_distiller(palette = "BrBG", 
-                       direction = 1, 
-                       na.value = "white", 
-                       name = "")

+worth_map(mod, + labels = traits, + labels.order = c("Overall", "Taste", "Stretchability", "Colour"))

The worth map confirms the superiority of TMS6, Sape and TMEB1 across the traits, but also presents Madame among the top varieties for color. @@ -359,9 +357,11 @@

Participants’ heterogeneity# and get the unique values slice_lvs = unique(slice) - trait_plot = list() +# order of varieties from best to worst in the full dataset +items_lvls = rev(names(sort(rank(coef(mod[[ov]], log = FALSE) * -1)))) + for (i in seq_along(slice_lvs)) { # fit the model also applying the slice @@ -370,35 +370,29 @@

Participants’ heterogeneity}) # plot the worth map - trait_plot[[i]] = worth_map(mod_i, - labels = traits) + - labs(x = "", - y = "", - title = slice_lvs[i]) + - scale_fill_distiller(palette = "BrBG", - direction = 1, - na.value = "white", - name = "") + trait_plot[[i]] = worth_map(mod_i, + labels = traits, + labels.order = c("Overall", "Taste", "Stretchability", "Colour"), + items.order = items_lvls) - } # plot the two maps using patchwork trait_plot[[1]] + trait_plot[[2]] + plot_layout(ncol = 1)

- -
-

Selection index -

The segmented analysis reveals contrasting results compared to the previous analysis using the full dataset. It highlights the superiority of TMS6 and TMEB1 in Nigeria, and Game Changer and Sape in Cameroon. This approach provides a visual method to select the best variety -overall for each group. To account for all traits in a data-driven -manner when selecting varieties, I propose a selection index approach. -This method calculates weighted estimates and derives a selection score -that represents the overall performance of the varieties across all -traits.

+overall for each group.

+
+
+

Selection index +

+

To account for all traits in a data-driven manner when selecting +varieties, I propose a selection index approach. This method calculates +weighted estimates and derives a selection score that represents the +overall performance of the varieties across all traits.

Suppose we have three varieties with standardized probabilities for each trait:

diff --git a/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth-1.png b/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth-1.png index edb99ee..9072a9f 100644 Binary files a/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth-1.png and b/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth-1.png differ diff --git a/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth2-1.png b/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth2-1.png index dd9aec8..a34a51c 100644 Binary files a/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth2-1.png and b/docs/articles/vignette-2-gari-eba-consumer-testing_files/figure-html/worth2-1.png differ diff --git a/docs/authors.html b/docs/authors.html index 88eb7e7..e7e2429 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/index.html b/docs/index.html index 70dc1eb..bb638f0 100644 --- a/docs/index.html +++ b/docs/index.html @@ -40,7 +40,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/news/index.html b/docs/news/index.html index eb50f89..1100cb4 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 9a4c0dd..a4c349c 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -4,4 +4,4 @@ pkgdown_sha: ~ articles: vignette-1-trait-prioritization-and-crop-performance: vignette-1-trait-prioritization-and-crop-performance.html vignette-2-gari-eba-consumer-testing: vignette-2-gari-eba-consumer-testing.html -last_built: 2024-11-28T12:43Z +last_built: 2024-11-30T12:37Z diff --git a/docs/reference/akaike_weights.html b/docs/reference/akaike_weights.html index 83f3310..ef1586b 100644 --- a/docs/reference/akaike_weights.html +++ b/docs/reference/akaike_weights.html @@ -18,7 +18,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/breadwheat.html b/docs/reference/breadwheat.html index 0d0aa9c..961af62 100644 --- a/docs/reference/breadwheat.html +++ b/docs/reference/breadwheat.html @@ -23,7 +23,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/btpermute.html b/docs/reference/btpermute.html index da1c612..362c138 100644 --- a/docs/reference/btpermute.html +++ b/docs/reference/btpermute.html @@ -21,7 +21,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/cassava.html b/docs/reference/cassava.html index a639e45..4da2650 100644 --- a/docs/reference/cassava.html +++ b/docs/reference/cassava.html @@ -27,7 +27,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/compare.html b/docs/reference/compare.html index e2ec732..c5ce049 100644 --- a/docs/reference/compare.html +++ b/docs/reference/compare.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/crossvalidation.html b/docs/reference/crossvalidation.html index a50a983..b3572a5 100644 --- a/docs/reference/crossvalidation.html +++ b/docs/reference/crossvalidation.html @@ -20,7 +20,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/gosset.html b/docs/reference/gosset.html index 37a3eeb..dfde5bb 100644 --- a/docs/reference/gosset.html +++ b/docs/reference/gosset.html @@ -1,5 +1,6 @@ -Tools for Data Analysis in Experimental Agriculture — gosset • gossetTools for Data Analysis in Experimental Agriculture — gosset • gosset @@ -17,7 +18,7 @@ gosset - 1.4 + 1.4.1 @@ -62,7 +63,8 @@

Tools for Data Analysis in Experimental Agriculture

-

Methods to analyse experimental agriculture data, from data synthesis to model selection and visualisation. The package is named after W.S. Gosset aka ‘Student’, a pioneer of modern statistics in small sample experimental design and analysis.

+

+

Methods to analyse experimental agriculture data, from data synthesis to model selection and visualisation. The package is named after W.S. Gosset aka ‘Student’, a pioneer of modern statistics in small sample experimental design and analysis.

diff --git a/docs/reference/index.html b/docs/reference/index.html index 1551115..ccf297f 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 @@ -99,6 +99,10 @@

All functions kendallW()

+ + diff --git a/docs/reference/kendallTau.html b/docs/reference/kendallTau.html index c234a9e..7337029 100644 --- a/docs/reference/kendallTau.html +++ b/docs/reference/kendallTau.html @@ -24,7 +24,7 @@ gosset - 1.4 + 1.4.1 @@ -130,7 +130,7 @@

Arguments

Value

The Kendall correlation coefficient and the Effective N, which is the equivalent N needed if all items were compared to all items. -Can be used for significance testing.

+Used for significance testing.

References

diff --git a/docs/reference/kendallW.html b/docs/reference/kendallW.html index 31461c3..71e146a 100644 --- a/docs/reference/kendallW.html +++ b/docs/reference/kendallW.html @@ -18,7 +18,7 @@ gosset - 1.4 + 1.4.1
diff --git a/docs/reference/kendall_permute.html b/docs/reference/kendall_permute.html new file mode 100644 index 0000000..09a158f --- /dev/null +++ b/docs/reference/kendall_permute.html @@ -0,0 +1,163 @@ + +Kendall's tau permutation test — kendall_permute • gosset + + +
+
+ + + +
+
+ + +
+

Perform a pairwise permutation test to assess statistical differences +in Kendall's Tau correlation between two or more groups.

+
+ +
+
kendall_permute(x, y, split, n.permutations = 500)
+
+ +
+

Arguments

+ + +
x
+

a numeric vector, matrix or data frame

+ + +
y
+

a vector, matrix or data frame with compatible dimensions to x

+ + +
split
+

a vector indicating the splitting rule for the test

+ + +
n.permutations
+

an integer, the number of permutations to perform

+ +
+
+

Value

+

A data.frame containing:

+
observed_diff
+

observed absolute differences in Kendall's tau for all group pairs.

+ +
p_values
+

p-values from the permutation test for all group pairs.

+ +
+
+

See also

+ +
+
+

Author

+

Kauê de Sousa

+
+ +
+

Examples

+
if (FALSE) { # interactive()
+set.seed(42)
+x = rnorm(100)
+y = rnorm(100)
+split = rep(c("Group1", "Group2", "Group3"), length.out = 100)
+kendall_permute(x, y, split)
+
+data("breadwheat", package = "gosset")
+
+x = rank_tricot(breadwheat, 
+                items = paste0("variety_", letters[1:3]),
+                input = c("yield_best", "yield_worst"),
+                validate.rankings = TRUE)
+
+y = rank_tricot(breadwheat, 
+                items = paste0("variety_", letters[1:3]),
+                input = c("overall_best", "overall_worst"),
+                validate.rankings = TRUE)
+                
+kendall_permute(x, y, 
+                split = rep(c("Group1", "Group2", "Group3"), length.out = nrow(breadwheat)), 
+                n.permutations = 100)
+                
+}
+
+
+ +
+ + +
+ +
+

Site built with pkgdown 2.1.1.

+
+ +
+ + + + + + + + diff --git a/docs/reference/kenyachoice.html b/docs/reference/kenyachoice.html index 52c723b..39a6ceb 100644 --- a/docs/reference/kenyachoice.html +++ b/docs/reference/kenyachoice.html @@ -22,7 +22,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/likelihood_ratio.html b/docs/reference/likelihood_ratio.html index 41a8673..ed958c3 100644 --- a/docs/reference/likelihood_ratio.html +++ b/docs/reference/likelihood_ratio.html @@ -18,7 +18,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/nicabean.html b/docs/reference/nicabean.html index 9d309bb..d580ad5 100644 --- a/docs/reference/nicabean.html +++ b/docs/reference/nicabean.html @@ -25,7 +25,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/node_labels.html b/docs/reference/node_labels.html index 8b34925..7500bd7 100644 --- a/docs/reference/node_labels.html +++ b/docs/reference/node_labels.html @@ -19,7 +19,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/pairwise_probs.html b/docs/reference/pairwise_probs.html index 9358778..d936a6d 100644 --- a/docs/reference/pairwise_probs.html +++ b/docs/reference/pairwise_probs.html @@ -21,7 +21,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/pseudoR2.html b/docs/reference/pseudoR2.html index dfeee2d..985e8cd 100644 --- a/docs/reference/pseudoR2.html +++ b/docs/reference/pseudoR2.html @@ -21,7 +21,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/pseudo_rank.html b/docs/reference/pseudo_rank.html index 9ab79ff..23ca838 100644 --- a/docs/reference/pseudo_rank.html +++ b/docs/reference/pseudo_rank.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/rank_numeric.html b/docs/reference/rank_numeric.html index 2795129..beca8b8 100644 --- a/docs/reference/rank_numeric.html +++ b/docs/reference/rank_numeric.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/rank_tricot.html b/docs/reference/rank_tricot.html index f910e8e..58073c6 100644 --- a/docs/reference/rank_tricot.html +++ b/docs/reference/rank_tricot.html @@ -21,7 +21,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/regret.html b/docs/reference/regret.html index 50790ed..f7ed11b 100644 --- a/docs/reference/regret.html +++ b/docs/reference/regret.html @@ -20,7 +20,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/reliability.html b/docs/reference/reliability.html index 2aa9505..112652c 100644 --- a/docs/reference/reliability.html +++ b/docs/reference/reliability.html @@ -19,7 +19,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/resample.html b/docs/reference/resample.html index 0913dcb..14962d4 100644 --- a/docs/reference/resample.html +++ b/docs/reference/resample.html @@ -22,7 +22,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/rowbind.html b/docs/reference/rowbind.html index 3bcc266..defae4d 100644 --- a/docs/reference/rowbind.html +++ b/docs/reference/rowbind.html @@ -17,7 +17,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/set_binomialfreq.html b/docs/reference/set_binomialfreq.html index 0ae71cf..e7c7dbf 100644 --- a/docs/reference/set_binomialfreq.html +++ b/docs/reference/set_binomialfreq.html @@ -18,7 +18,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/set_paircomp.html b/docs/reference/set_paircomp.html index c766a4b..09c27df 100644 --- a/docs/reference/set_paircomp.html +++ b/docs/reference/set_paircomp.html @@ -18,7 +18,7 @@ gosset - 1.4 + 1.4.1 diff --git a/docs/reference/worth_map.html b/docs/reference/worth_map.html index 435db7e..0e5dc22 100644 --- a/docs/reference/worth_map.html +++ b/docs/reference/worth_map.html @@ -19,7 +19,7 @@ gosset - 1.4 + 1.4.1 @@ -76,7 +76,7 @@

Plot worth parameters

worth_map(object, ...)# S3 method for class 'list' -worth_map(object, labels, ...) +worth_map(object, labels, labels.order = NULL, items.order = NULL, ...)worth_bar(object, ...) @@ -98,6 +98,14 @@

Arguments

labels

a vector with the name of models in object

+ +
labels.order
+

optional, a vector to determine the order of labels

+ + +
items.order
+

optional, a vector to determine the order of items

+
diff --git a/docs/sitemap.xml b/docs/sitemap.xml index 2d2fcc8..d6f5eb8 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -20,6 +20,7 @@ /reference/index.html /reference/kendallTau.html /reference/kendallW.html +/reference/kendall_permute.html /reference/kenyachoice.html /reference/likelihood_ratio.html /reference/nicabean.html diff --git a/man/worth_map.Rd b/man/worth_map.Rd index c9cd9e6..515e9da 100644 --- a/man/worth_map.Rd +++ b/man/worth_map.Rd @@ -11,7 +11,7 @@ worth_map(object, ...) \method{worth_map}{default}(object, ...) -\method{worth_map}{list}(object, labels, ...) +\method{worth_map}{list}(object, labels, labels.order = NULL, items.order = NULL, ...) worth_bar(object, ...) } @@ -23,6 +23,10 @@ a list objects of class \code{PlackettLuce}} \item{...}{additional arguments passed to methods} \item{labels}{a vector with the name of models in \var{object}} + +\item{labels.order}{optional, a vector to determine the order of labels} + +\item{items.order}{optional, a vector to determine the order of items} } \description{ Produces plots to highlight worth diff --git a/vignettes/vignette-2-gari-eba-consumer-testing.R b/vignettes/vignette-2-gari-eba-consumer-testing.R index e530735..0d3afce 100644 --- a/vignettes/vignette-2-gari-eba-consumer-testing.R +++ b/vignettes/vignette-2-gari-eba-consumer-testing.R @@ -91,12 +91,9 @@ ggplot(data = rel, ## ----worth, message = FALSE, eval = TRUE, echo = TRUE------------------------- -worth_map(mod, labels = traits) + - labs(x = "", y = "") + - scale_fill_distiller(palette = "BrBG", - direction = 1, - na.value = "white", - name = "") +worth_map(mod, + labels = traits, + labels.order = c("Overall", "Taste", "Stretchability", "Colour")) ## ----llr, message = FALSE, eval = TRUE, echo = TRUE--------------------------- # by gender @@ -130,9 +127,11 @@ slice = dat$country # and get the unique values slice_lvs = unique(slice) - trait_plot = list() +# order of varieties from best to worst in the full dataset +items_lvls = names(sort(rank(coef(mod[[ov]], log = FALSE) * -1))) + for (i in seq_along(slice_lvs)) { # fit the model also applying the slice @@ -141,17 +140,11 @@ for (i in seq_along(slice_lvs)) { }) # plot the worth map - trait_plot[[i]] = worth_map(mod_i, - labels = traits) + - labs(x = "", - y = "", - title = slice_lvs[i]) + - scale_fill_distiller(palette = "BrBG", - direction = 1, - na.value = "white", - name = "") + trait_plot[[i]] = worth_map(mod_i, + labels = traits, + labels.order = c("Overall", "Taste", "Stretchability", "Colour"), + items.order = items_lvls) - } # plot the two maps using patchwork diff --git a/vignettes/vignette-2-gari-eba-consumer-testing.Rmd b/vignettes/vignette-2-gari-eba-consumer-testing.Rmd index 235d8c5..5d500b8 100755 --- a/vignettes/vignette-2-gari-eba-consumer-testing.Rmd +++ b/vignettes/vignette-2-gari-eba-consumer-testing.Rmd @@ -152,12 +152,9 @@ The reliability estimates show an improvement in overall preference of 32% for T So far, we have focused solely on the overall preference. However, there are other traits to assess. The function `worth_plot()` can be used to visually analyze and compare variety performance across different traits. The values represented in a worth map are *log-worth* estimates. The function can be used with `ggplot2` functions to improve the plot. ``` {r worth, message = FALSE, eval = TRUE, echo = TRUE} -worth_map(mod, labels = traits) + - labs(x = "", y = "") + - scale_fill_distiller(palette = "BrBG", - direction = 1, - na.value = "white", - name = "") +worth_map(mod, + labels = traits, + labels.order = c("Overall", "Taste", "Stretchability", "Colour")) ``` The worth map confirms the superiority of TMS6, Sape and TMEB1 across the traits, but also presents Madame among the top varieties for color. We will return to this analysis later, but for now, let us examine the data from the perspective of different groups to consider heterogeneity in the participants' evaluations, as proposed by van Etten et al. (2023) [@vanEtten2023]. @@ -204,9 +201,11 @@ slice = dat$country # and get the unique values slice_lvs = unique(slice) - trait_plot = list() +# order of varieties from best to worst in the full dataset +items_lvls = rev(names(sort(rank(coef(mod[[ov]], log = FALSE) * -1)))) + for (i in seq_along(slice_lvs)) { # fit the model also applying the slice @@ -215,17 +214,11 @@ for (i in seq_along(slice_lvs)) { }) # plot the worth map - trait_plot[[i]] = worth_map(mod_i, - labels = traits) + - labs(x = "", - y = "", - title = slice_lvs[i]) + - scale_fill_distiller(palette = "BrBG", - direction = 1, - na.value = "white", - name = "") + trait_plot[[i]] = worth_map(mod_i, + labels = traits, + labels.order = c("Overall", "Taste", "Stretchability", "Colour"), + items.order = items_lvls) - } # plot the two maps using patchwork

Kendall's W (coefficient of concordance)

+

kendall_permute()

+

Kendall's tau permutation test

kenyachoice