Skip to content

Commit

Permalink
Fixed further bugs related to #277 to streamline data.frame & matrix …
Browse files Browse the repository at this point in the history
…classes
  • Loading branch information
aiorazabala committed Mar 2, 2021
1 parent d8035df commit 03647f4
Show file tree
Hide file tree
Showing 6 changed files with 10 additions and 8 deletions.
4 changes: 2 additions & 2 deletions R/plot.QmethodRes.R
Expand Up @@ -46,8 +46,8 @@ Only a subset of all the factors is plotted (argument 'factors'), and filled mar
pts <- pts[sta.order, ]
}
if (is.null(colours)) colours <- rainbow(length(dfr))
if (is.null(fnames) & names(x$zsc)[1] == "zsc_f1") fnames <- paste0("Factor ", factors)
if (is.null(fnames) & names(x$zsc)[1] != "zsc_f1") fnames <- names(x$zsc)
if (is.null(fnames) & colnames(x$zsc)[1] == "zsc_f1") fnames <- paste0("Factor ", factors)
if (is.null(fnames) & colnames(x$zsc)[1] != "zsc_f1") fnames <- colnames(x$zsc)
dotchart(dfr[[factors[1]]], lcolor=grey(0.4),
xlim=xlimits,
ylab=ylab, xlab=xlab, axis=NULL,
Expand Down
2 changes: 2 additions & 0 deletions R/qdc.R
@@ -1,4 +1,6 @@
qdc <- function(dataset, nfactors, zsc, sed) {
zsc <- as.data.frame(zsc)
sed <- as.data.frame(sed)
if (nfactors==1) {
qdc.res <- "Warning: Only one factor selected. No distinguishing and consensus statements will be calculated."
warning(qdc.res)
Expand Down
2 changes: 1 addition & 1 deletion R/qfcharact.R
Expand Up @@ -10,7 +10,7 @@ qfcharact <- function(loa, flagged, zsc, nfactors, floa, av_rel_coef=0.8) {
#Reliability
reliability <- av_rel_coef*nload/(1+(nload-1)*av_rel_coef)
#Standard Error of Factor Scores
se_fscores <- sapply(zsc, sd)*sqrt(1-reliability)
se_fscores <- sapply(as.data.frame(zsc), sd)*sqrt(1-reliability)
#FACTOR MATRIXES
#correlation among factors
f_cor <- cor(zsc)
Expand Down
4 changes: 2 additions & 2 deletions R/qzscores.R
Expand Up @@ -35,7 +35,7 @@ qzscores <- function(dataset, nfactors, loa, flagged, forced = TRUE, distributio
colnames(zsc_mea) <- paste("z_mea_",c(1:ncol(floa)),sep="")
colnames(zsc_std) <- paste("z_std_",c(1:ncol(floa)),sep="")
#-- z-scores for each statement
zsc <- data.frame(cbind(1:nstat))
zsc <- matrix(NA, ncol=nfactors, nrow=nstat)
row.names(zsc) <- row.names(dataset)
n <- 1
while (n <= ncol(floa)) {
Expand All @@ -55,7 +55,7 @@ qzscores <- function(dataset, nfactors, loa, flagged, forced = TRUE, distributio
if (!is.numeric(distribution) & !is.integer(distribution)) stop("Q method input: The distribution provided contains non-numerical values.")
qscores <- sort(distribution, decreasing=FALSE)
}
zsc_n <- as.data.frame(zsc)
zsc_n <- as.matrix(zsc)
f <- 1
while (f <= ncol(floa)) {
if (length(unique(zsc[,f])) == length(zsc[,f])) {
Expand Down
2 changes: 1 addition & 1 deletion man/centroid.Rd
Expand Up @@ -56,7 +56,7 @@ results <- qzscores(lip, 3, loa=vmax$loadings, flagged=flags)
summary(results)

# Consensus and distinguishing statements
results$qdc <- qdc(lip, 3, zsc=results$zsc, sed=as.data.frame(results$f_char$sd_dif))
results$qdc <- qdc(lip, 3, zsc=results$zsc, sed=results$f_char$sd_dif)

plot(results)

Expand Down
4 changes: 2 additions & 2 deletions man/qdc.Rd
Expand Up @@ -7,8 +7,8 @@
\arguments{
\item{dataset}{a matrix or a dataframe containing original data, with statements as rows, Q sorts as columns, and grid column values in each cell.}
\item{nfactors}{number of factors extracted.}
\item{zsc}{a matrix with the factor z-scores for statements resulting from \code{\link{qzscores}}.}
\item{sed}{a matrix with the standard error of differences resulting from \code{\link{qfcharact}}.}
\item{zsc}{a matrix or a dataframe with the factor z-scores for statements resulting from \code{\link{qzscores}}.}
\item{sed}{a matrix or a dataframe with the standard error of differences resulting from \code{\link{qfcharact}}.}
}

\details{
Expand Down

0 comments on commit 03647f4

Please sign in to comment.