Skip to content

Commit

Permalink
Clean up some formatting, and rewrite parts of the README and methods…
Browse files Browse the repository at this point in the history
… vignette
  • Loading branch information
Kss2k committed Oct 24, 2024
1 parent 11c786c commit b88a0ad
Show file tree
Hide file tree
Showing 3 changed files with 53 additions and 42 deletions.
46 changes: 21 additions & 25 deletions R/constraints_pi_ca.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
# Functitions for specifying constraints in the constrained approach
# modsem(method = "ca"). Last updated: 29.05.2024


labelFactorLoadings <- function(parTable) {
Expand All @@ -14,14 +13,17 @@ labelFactorLoadings <- function(parTable) {

specifyFactorLoadingsSingle <- function(parTable, relDf) {
latentProdName <- stringr::str_c(rownames(relDf), collapse = "")

for (indProd in colnames(relDf)) {
indProdLabel <- createLabelLambda(indProd, latentProdName)
indProdLabel <- createLabelLambda(indProd, latentProdName)
indsInProdLabels <- createLabelLambda(relDf[[indProd]], rownames(relDf))
vecLhsRhs <- c(indProdLabel, stringr::str_c(indsInProdLabels,
collapse = " * "))
newRow <- createParTableRow(vecLhsRhs, op = "==")
vecLhsRhs <- c(indProdLabel, stringr::str_c(indsInProdLabels,
collapse = " * "))

newRow <- createParTableRow(vecLhsRhs, op = "==")
parTable <- rbind(parTable, newRow)
}

parTable
}

Expand Down Expand Up @@ -129,10 +131,9 @@ specifyVarCovSingle <- function(parTable, relDf) {
# This function specifies variances for latents, indicators,
# and indicator products. It will also specifies covariances for latent
# products, and elements int those products.
if (nrow(relDf) > 2) {
stop2("Constraints for products with more than two ",
stopif(nrow(relDf) > 2, "Constraints for products with more than two ",
" elements are not supported for this method")
}

# General info
elemsInProdTerm <- rownames(relDf)
latentProd <- stringr::str_c(rownames(relDf), collapse = "")
Expand All @@ -144,12 +145,11 @@ specifyVarCovSingle <- function(parTable, relDf) {
FUN = function(x) trace_path(parTable, x, x))

labelCovElems <- trace_path(parTable, elemsInProdTerm[[1]],
elemsInProdTerm[[2]]) |> paste0(" ^ 2")
elemsInProdTerm[[2]]) |> paste0(" ^ 2")

lhs <- labelLatentProd
rhs <- paste(stringr::str_c(labelsElemsInProd, collapse = " * "),
labelCovElems,
sep = " + ")
labelCovElems, sep = " + ")
varLatentProd <- createParTableRow(c(lhs, rhs), op = "==")

# covariances between elems and latents
Expand All @@ -170,30 +170,26 @@ specifyVarCovSingle <- function(parTable, relDf) {
labelVarIndProd <- createLabelVar(indProd)

labelsFactorLoadings <- vector("character", length = nrow(relDf))
labelsVarLatents <- vector("character", length = nrow(relDf))
labelsVarInds <- vector("character", length = nrow(relDf))
labelsVarLatents <- vector("character", length = nrow(relDf))
labelsVarInds <- vector("character", length = nrow(relDf))

for (latent in 1:nrow(relDf)) {
for (latent in seq_len(nrow(relDf))) {
labelsFactorLoadings[[latent]] <-
createLabelLambdaSquared(relDf[latent, indProd],
rownames(relDf)[[latent]])
labelsVarLatents[[latent]] <-
trace_path(parTable, rownames(relDf)[[latent]],
rownames(relDf)[[latent]])
rownames(relDf)[[latent]])
labelsVarInds[[latent]] <- createLabelVar(relDf[latent, indProd])
}

lhs <- labelVarIndProd
rhs1 <- paste(labelsFactorLoadings[[1]],
labelsVarLatents[[1]],
labelsVarInds[[2]],
sep = " * ")
rhs2 <- paste(labelsFactorLoadings[[2]],
labelsVarLatents[[2]],
labelsVarInds[[1]],
sep = " * ")
lhs <- labelVarIndProd
rhs1 <- paste(labelsFactorLoadings[[1]], labelsVarLatents[[1]],
labelsVarInds[[2]], sep = " * ")
rhs2 <- paste(labelsFactorLoadings[[2]], labelsVarLatents[[2]],
labelsVarInds[[1]], sep = " * ")
rhs3 <- paste(labelsVarInds[[1]], labelsVarInds[[2]], sep = " * ")
rhs <- paste(rhs1, rhs2, rhs3, sep = " + ")
rhs <- paste(rhs1, rhs2, rhs3, sep = " + ")

constrained.varProdInds[[indProd]] <- createParTableRow(c(lhs, rhs), op = "==")
}
Expand Down
12 changes: 9 additions & 3 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@
[![CRAN](https://www.r-pkg.org/badges/version/modsem)](https://cran.r-project.org/package=modsem)
[![PKGDOWN-Build](https://github.com/kss2k/modsem/actions/workflows/pkgdown.yml/badge.svg)](https://github.com/kss2k/modsem/actions/workflows/pkgdown.yml)
<!-- badges: end -->
This is a package which allows you to perform interactions between latent variables (i.e., moderation) in CB-SEM.
See https://www.modsem.org for a tutorial.
`modsem` is an `R`-package for estimating interaction (i.e., moderation) effects between latent variables
in structural equation models (SEMs). See https://www.modsem.org for a tutorial.

# To Install
```
Expand All @@ -20,8 +20,12 @@ devtools::install_github("kss2k/modsem", build_vignettes = TRUE)

# Methods/Approaches

There are a number of approaches for estimating interaction effects in SEM. In `modsem()`, the `method = "method"` argument allows you to choose which to use.
There are a number of approaches for estimating interaction effects in SEM.
In `modsem()`, the `method = "method"` argument allows you to choose which to use.
Different approaches can be categorized into two groups:
Product Indicator (PI) and Distribution Analytic (DA) approaches.

## Product Indicator (PI) Approaches:
- `"ca"` = constrained approach (Algina & Moulder, 2001)
- Note that constraints can become quite complicated for complex models,
particularly when there is an interaction including enodgenous variables.
Expand All @@ -31,6 +35,8 @@ There are a number of approaches for estimating interaction effects in SEM. In `
- `"dblcent"` = double centering approach (Marsh., 2013)
- default
- `"pind"` = basic product indicator approach (not recommended)

## Distribution Analytic (DA) Approaches
- `"lms"` = The Latent Moderated Structural equations (LMS) approach, see the [vignette](https://kss2k.github.io/modsem/articles/lms_qml.html)
- `"qml"` = The Quasi Maximum Likelihood (QML) approach, see the [vignette](https://kss2k.github.io/modsem/articles/lms_qml.html)
- `"mplus"`
Expand Down
37 changes: 23 additions & 14 deletions vignettes/methods.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -19,21 +19,27 @@ knitr::opts_chunk$set(
```{r setup}
library(modsem)
```
There are a number of approaches for estimating interaction effects in SEM.
In `modsem()`, the `method = "method"` argument allows you to choose which to use.
Different approaches can be categorized into two groups:
Product Indicator (PI) and Distribution Analytic (DA) approaches.

There are a number of approaches for estimating interaction effects in SEM. In `modsem()`, the `method = "method"` argument allows you to choose which to use.

- `"ca"` = constrained approach (Algina & Moulder, 2001)
- `"uca"` = unconstrained approach (Marsh, 2004)
- `"rca"` = residual centering approach (Little et al., 2006)
- default
- `"dblcent"`= double centering approach (Marsh., 2013)
- `"pind"` = basic product indicator approach (not recommended)
- `"lms"` = The Latent Moderated Structural equations approach
- note: there can not be an interaction between two endogenous variables.
- `"qml"` = The Quasi Maximum Likelihood approach.
- note: can only be done if you have a single endogenous (dependent) variable.
- `"mplus"`
- estimates model through Mplus, if it is installed
## Product Indicator (PI) Approaches:
- `"ca"` = constrained approach (Algina & Moulder, 2001)
- Note that constraints can become quite complicated for complex models,
particularly when there is an interaction including enodgenous variables.
The method can therefore be quite slow.
- `"uca"` = unconstrained approach (Marsh, 2004)
- `"rca"` = residual centering approach (Little et al., 2006)
- `"dblcent"` = double centering approach (Marsh., 2013)
- default
- `"pind"` = basic product indicator approach (not recommended)

## Distribution Analytic (DA) Approaches
- `"lms"` = The Latent Moderated Structural equations (LMS) approach, see the [vignette](https://kss2k.github.io/modsem/articles/lms_qml.html)
- `"qml"` = The Quasi Maximum Likelihood (QML) approach, see the [vignette](https://kss2k.github.io/modsem/articles/lms_qml.html)
- `"mplus"`
- estimates model through Mplus, if it is installed

```{r, eval = FALSE}
Expand All @@ -47,10 +53,13 @@ Z =~ z1 + z2 + z3
Y ~ X + Z + X:Z
'
# Product Indicator Approaches
modsem(m1, data = oneInt, method = "ca")
modsem(m1, data = oneInt, method = "uca")
modsem(m1, data = oneInt, method = "rca")
modsem(m1, data = oneInt, method = "dblcent")
# Distribution Analytic Approaches
modsem(m1, data = oneInt, method = "mplus")
modsem(m1, data = oneInt, method = "lms")
modsem(m1, data = oneInt, method = "qml")
Expand Down

0 comments on commit b88a0ad

Please sign in to comment.