[R-sig-ME] Collinearity diagnostics for (mixed) multinomial models

John Fox j|ox @end|ng |rom mcm@@ter@c@
Wed Feb 1 17:19:24 CET 2023


Dear Phillip (and Juho),

You raise a reasonable point but, unfortunately, one that isn't really 
relevant to the problem at hand.

Applied to a linear model, which is the context in which generalized 
variance inflation was originally defined in the paper by me and Georges 
Monette cited in ?car::vif, the GVIF *is* invariant with respect to 
inessential changes to the model such as centering regressors or any 
change in the bases for the regressor subspaces of terms in the model. 
The GVIF compares the size of the joint confidence region for the set of 
coefficients for a term in the model to its size in a utopian situation 
in which the subspace for the term is orthogonal to the subspaces of the 
other terms, and reduces to the usual VIF when the term in one-dimensional.

Generalized variance inflation has subsequently been extended to some 
other regression models, such as generalized linear models, and it 
retains these essential invariances (although interpretation isn't as 
straightforward).

In response to Juho's original question, I conjectured an extension to 
multinomial logit models, tested some of its invariance properties, but 
unfortunately didn't test sufficiently extensively. (I did suggest 
additional tests that I didn't perform.) It's clear from Juho's example 
that my conjecture was wrong.

The reason that I hadn't yet responded to Juho's recent question is that 
Georges and I are still trying to understand why my proposed definition 
fails for multinomial logit models. It appears to work, for example, for 
multivariate linear models. Neither of us, at this point, has a solution 
to Juho's problem, and it's possible that there isn't one. We're 
continuing to discuss the problem, and one of us will post an update to 
the list if we come up with either a solution or a clear explanation of 
why my proposal failed.

Thank you for prompting me to reply, if only in a preliminary manner.

Best,
  John

-- 
John Fox, Professor Emeritus
McMaster University
Hamilton, Ontario, Canada
web: https://socialsciences.mcmaster.ca/jfox/

On 2023-02-01 12:19 a.m., Phillip Alday wrote:
> I haven't seen an answer go by yet, but here's a breadcrumb:
> 
> Iacobucci, D., Schneider, M.J., Popovich, D.L. et al. Mean centering
> helps alleviate “micro” but not “macro” multicollinearity. Behav Res 48,
> 1308–1317 (2016). https://doi.org/10.3758/s13428-015-0624-x
> 
> 
> 
> On 26/1/23 8:56 am, Juho Kristian Ruohonen wrote:
>> Dear all,
>>
>> I'm resurrecting this thread because a problem has come up which might need
>> fixing once someone gets around to writing a relevant R package.
>>
>> In this same thread last March, John Fox showed me how to compute GVIFs for
>> a *nnet* multinomial model. I then wrote a simple function that loops
>> through all predictors in such a model and applies John's code to them,
>> returning the GVIF, DF, and GVIF^(1/(2*Df)) statistic for each predictor.
>> Available here
>> <https://github.com/jkruohon/StatsMisc/blob/main/gvif_multinom.R>, the
>> function seems to work just fine, reproducing John's results exactly on the
>> carData examples. Likewise, applying this function to my own research data
>> yielded entirely plausible results.
>>
>> But to my horror, I now discover that *when I refit my multinomial model
>> with two quantitative predictors centered, the GVIF statistics change
>> considerably** -- *even though the model has the same fit and virtually
>> identical coefficients (except for the intercepts) as the original one. How
>> can this be? The only thing that changes between the two models is the set
>> of intercepts which, moreover, are specifically excluded from the GVIF
>> calculations.
>>
>> Below is a minimal example. The anonymized datafile is downloadable here
>> <https://github.com/jkruohon/StatsMisc/raw/main/d_anon.RData>.
>>
>>> mod1 <- multinom(y ~., data = d.anon, maxit = 999)
>>> gvif.multinom(mod1) # x6 and x26 top the collinearity list
>>              GVIF DF GVIF^(1/(2df))
>> x6  3.463522e+03  3       3.889732
>> x26 2.988396e+03  3       3.795244
>> x27 1.390830e+03  3       3.341019
>> x2  3.889656e+02  3       2.701792
>> x13 2.930026e+02  3       2.577183
>> x19 2.051250e+04  6       2.287362
>> x25 7.043339e+03  6       2.092417
>> x24 1.078212e+07 12       1.963493
>> x9  2.357662e+01  3       1.693351
>> x17 1.991744e+01  3       1.646413
>> x5  3.869759e+02  6       1.643010
>> x12 1.787075e+01  3       1.616927
>> x18 2.943991e+02  6       1.605997
>> x1  2.700175e+03  9       1.551075
>> x16 2.576739e+04 12       1.526844
>> x7  1.483341e+02  6       1.516829
>> x20 1.159374e+01  3       1.504425
>> x3  1.612637e+04 12       1.497318
>> x28 1.081693e+01  3       1.487136
>> x10 9.706880e+00  3       1.460539
>> x22 9.459035e+00  3       1.454257
>> x15 9.124519e+00  3       1.445556
>> x14 7.017242e+00  3       1.383655
>> x21 6.404687e+00  3       1.362750
>> x8  6.072614e+00  3       1.350712
>> x11 4.797251e+00  3       1.298670
>> x4  3.665742e+03 18       1.256043
>> x23 3.557201e+00  3       1.235525
>>
>> Now we refit the model with the quantitative predictors x6 and x26 centered:
>>
>>> d.anon$x6 <- d.anon$x6 - mean(d.anon$x6)
>>> d.anon$x26 <- d.anon$x26 - mean(d.anon$x26)
>>> mod2 <- update(mod1, data = d.anon, maxit = 999)
>>> c(logLik(mod1), logLik(mod2))  # same fit to the data
>> [1] -2074.133 -2074.134
>>
>>> gvif.multinom(mod2)
>>              GVIF DF GVIF^(1/(2df))
>> x2  6.196959e+04  3       6.290663
>> x13 3.031115e+04  3       5.583850
>> x27 2.552811e+04  3       5.426291
>> x14 1.642231e+04  3       5.041646
>> x6  1.573721e+04  3       5.005967
>> x26 1.464437e+04  3       4.946277
>> x9  1.262667e+04  3       4.825564
>> x10 5.714321e+03  3       4.228251
>> x19 2.255013e+07  6       4.099798
>> x25 1.227033e+07  6       3.897068
>> x12 3.394139e+03  3       3.876635
>> x15 1.938364e+03  3       3.531067
>> x11 1.685265e+03  3       3.449674
>> x21 8.429450e+02  3       3.073500
>> x23 7.639755e+02  3       3.023523
>> x22 6.887451e+02  3       2.971733
>> x17 5.640312e+02  3       2.874422
>> x20 3.855848e+02  3       2.697864
>> x24 1.444083e+10 12       2.650430
>> x7  7.148911e+04  6       2.538166
>> x18 1.674603e+04  6       2.249017
>> x5  9.662266e+03  6       2.148275
>> x16 6.264044e+07 12       2.112851
>> x1  6.634544e+05  9       2.105882
>> x3  1.558132e+07 12       1.993847
>> x8  6.168472e+01  3       1.987755
>> x4  4.256459e+06 18       1.528059
>> x28 9.783234e+00  3       1.462448
>>
>> And so I'm at my wits' end. The models are virtually identical, yet the
>> GVIF statistics are very different. I don't know which ones to trust.
>> Worse, the discrepancy makes me disinclined to trust either of them --
>> which is a return to Square One, i.e. the situation where GVIF statistics
>> for multinomial models did not exist. And I don't know which
>> multicollinearity metric I can present in my thesis, if any.
>>
>> I hope someone can help.
>>
>> Best,
>>
>> Juho
>>
>>
>>
>>
>>
>> ke 2. maalisk. 2022 klo 16.35 John Fox (jfox using mcmaster.ca) kirjoitti:
>>
>>> Dear Juho,
>>>
>>> On 2022-03-02 6:23 a.m., Juho Kristian Ruohonen wrote:
>>>> One last comment, John: Sorry if I seemed to be implying that you (or
>>>> anyone else) should debug my code for me. That wasn't the idea. I do
>>>> believe that the function locates the intended rows/columns
>>>> successfully. I just wasn't entirely positive what those intended
>>>> rows/columns should be when dealing with a multicategory factor.
>>>> Presently, it locates every row/column involving the multicategory
>>>> factor in question, so the number of rows/columns identified is the
>>>> number of factor levels minus one, times the number of response
>>>> categories minus one. I hope that's correct.
>>>
>>> OK, that's a fair remark. Yes, what you describe is correct.
>>>
>>> You can also reassure yourself that your function is working properly by:
>>>
>>> (1) If you haven't already done so, show that you get the same GVIFs
>>> from your function as from the one I sent you used directly.
>>>
>>> (2) Vary the baseline level of the response variable and confirm that
>>> you get the same GVIFs.
>>>
>>> (3) Vary the basis for the regressor subspace for a factor, e.g., either
>>> by using contr.sum() in place of the default contr.treatment() or by
>>> changing the baseline level of the factor for contr.treatment(), and
>>> again confirm that the GVIFs are unchanged.
>>>
>>> Best,
>>>    John
>>>
>>>>
>>>> My current plan is to present the output of the new function in my
>>>> thesis and credit you for the math. But if *vif()* gets a relevant
>>>> update before my project is finished, then I'll use that and cite the
>>>> /car /package instead.
>>>>
>>>> Thanks again for your help.
>>>>
>>>> Best,
>>>>
>>>> Juho
>>>>
>>>> ti 1. maalisk. 2022 klo 23.54 John Fox (jfox using mcmaster.ca
>>>> <mailto:jfox using mcmaster.ca>) kirjoitti:
>>>>
>>>>      Dear Juho,
>>>>
>>>>      On 2022-03-01 3:13 p.m., Juho Kristian Ruohonen wrote:
>>>>       > Dear John,
>>>>       >
>>>>       > Yes, my function uses your code for the math. I was just hoping to
>>>>       > verify that it is handling multicategory factors correctly (your
>>>>       > examples didn't involve any).
>>>>
>>>>      That's not really my point. Your code sets up computations for the
>>>>      various terms in the model automatically, while the function I sent
>>>>      requires that you locate the rows/columns for the intercepts and each
>>>>      focal term manually. If you haven't already done so, you could check
>>>>      that your function is identifying the correct columns and getting the
>>>>      corresponding GVIFs.
>>>>
>>>>       >
>>>>       > I guess interactions aren't that important after all, given that
>>> the
>>>>       > chief concern is usually collinearity among main effects.
>>>>
>>>>      I wouldn't say that, but it's not clear what collinearity means in
>>>>      models with interactions, and if you compute VIFs or GVIFs for "main
>>>>      effects" in models with interactions, you'll probably get nonsense.
>>>>
>>>>      As I said, I think that this might be a solvable problem, but one
>>> that
>>>>      requires thought about what needs to remain invariant.
>>>>
>>>>      I think that we've probably come to end for now.
>>>>
>>>>      John
>>>>
>>>>       >
>>>>       > Many thanks for all your help.
>>>>       >
>>>>       > Best,
>>>>       >
>>>>       > Juho
>>>>       >
>>>>       > ti 1. maalisk. 2022 klo 18.01 John Fox (jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca>
>>>>       > <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>) kirjoitti:
>>>>       >
>>>>       >     Dear Juho,
>>>>       >
>>>>       >     On 2022-03-01 8:24 a.m., Juho Kristian Ruohonen wrote:
>>>>       >      > Dear John (Fox, as well as other list members),
>>>>       >      >
>>>>       >      > I've now written a simple function to try and calculate
>>>>      GVIFS for
>>>>       >     all
>>>>       >      > predictors in a nnet::multinom() object based on John's
>>>>      example
>>>>       >     code. If
>>>>       >      > its results are correct (see below), I will proceed to
>>> write a
>>>>       >     version
>>>>       >      > that also works with mixed-effects multinomial models fit
>>> by
>>>>       >      > brms::brm(). Here's the code:
>>>>       >      >
>>>>       >      >     gvif.multinom <- function(model){
>>>>       >      >        (classes <- model$lev)
>>>>       >      >        (V.all <- vcov(model))
>>>>       >      >        (V.noIntercepts <- V.all[!grepl("\\(Intercept\\)$",
>>>>       >      >     rownames(V.all), perl = T),
>>>>       >      >                                 !grepl("\\(Intercept\\)$",
>>>>       >      >     colnames(V.all), perl = T)])
>>>>       >      >        (R <- cov2cor(V.noIntercepts))
>>>>       >      >        (terms <- attr(model$terms, "term.labels"))
>>>>       >      >        (gvif <- numeric(length = length(terms)))
>>>>       >      >        (names(gvif) <- terms)
>>>>       >      >        (SE.multiplier <- numeric(length = length(terms)))
>>>>       >      >        (names(SE.multiplier) <- terms)
>>>>       >      >        #The line below tries to capture all factor levels
>>>>      into a
>>>>       >     regex
>>>>       >      >     for coef name matching.
>>>>       >      >        (LevelsRegex <- paste0("(",
>>>>      paste(unlist(model$xlevels),
>>>>       >     collapse
>>>>       >      >     = "|"),")?"))
>>>>       >      >
>>>>       >      >        for(i in terms){
>>>>       >      >          #The regex stuff below tries to ensure all
>>>>      interaction
>>>>       >      >     coefficients are matched, including those involving
>>>>      factors.
>>>>       >      >          if(grepl(":", i)){
>>>>       >      >            (termname <- gsub(":", paste0(LevelsRegex,
>>> ":"), i,
>>>>       >     perl = T))
>>>>       >      >          }else{termname <- i}
>>>>       >      >          (RegexToMatch <- paste0("^(",
>>>>       >     paste(classes[2:length(classes)],
>>>>       >      >     collapse = "|") ,"):", termname, LevelsRegex, "$"))
>>>>       >      >
>>>>       >      >          #Now the actual calculation:
>>>>       >      >          (indices <- grep(RegexToMatch, rownames(R), perl
>>>>      = T))
>>>>       >      >          (gvif[i] <- det(R[indices, indices]) *
>>>>      det(R[-indices,
>>>>       >      >     -indices]) / det(R))
>>>>       >      >          (SE.multiplier[i] <-
>>> gvif[i]^(1/(2*length(indices))))
>>>>       >      >        }
>>>>       >      >        #Put the results together and order them by degree
>>>>      of SE
>>>>       >     inflation:
>>>>       >      >        (result <- cbind(GVIF = gvif, `GVIF^(1/(2df))` =
>>>>       >     SE.multiplier))
>>>>       >      >        return(result[order(result[,"GVIF^(1/(2df))"],
>>>>      decreasing
>>>>       >     = T),])}
>>>>       >      >
>>>>       >      >
>>>>       >      > The results seem correct to me when applied to John's
>>> example
>>>>       >     model fit
>>>>       >      > to the BEPS data. However, that dataset contains no
>>> multi-df
>>>>       >     factors, of
>>>>       >      > which my own models have many. Below is a maximally simple
>>>>       >     example with
>>>>       >      > one multi-df factor (/region/):
>>>>       >      >
>>>>       >      >     mod1 <- multinom(partic ~., data = carData::Womenlf)
>>>>       >      >     gvif.multinom(mod1)
>>>>       >      >
>>>>       >      >     GVIF GVIF^(1/(2df))
>>>>       >      >     children 1.298794       1.067542
>>>>       >      >     hincome  1.184215       1.043176
>>>>       >      >     region   1.381480       1.020403
>>>>       >      >
>>>>       >      >
>>>>       >      > These results look plausible to me. Finally, below is an
>>>>      example
>>>>       >      > involving both a multi-df factor and an interaction:
>>>>       >      >
>>>>       >      >     mod2 <- update(mod1, ~. +children:region)
>>>>       >      >     gvif.multinom(mod2)
>>>>       >      >
>>>>       >      >                              GVIF GVIF^(1/(2df))
>>>>       >      >     children:region 4.965762e+16      11.053482
>>>>       >      >     region          1.420418e+16      10.221768
>>>>       >      >     children        1.471412e+03       6.193463
>>>>       >      >     hincome         6.462161e+00       1.594390
>>>>       >      >
>>>>       >      >
>>>>       >      > These results look a bit more dubious. To be sure, it is
>>> to be
>>>>       >     expected
>>>>       >      > that interaction terms will introduce a lot of
>>>>      collinearity. But an
>>>>       >      > 11-fold increase in SE? I hope someone can tell me whether
>>>>      this is
>>>>       >      > correct or not!
>>>>       >
>>>>       >     You don't need someone else to check your work because you
>>>>      could just
>>>>       >     apply the simple function that I sent you yesterday, which,
>>>>      though not
>>>>       >     automatic, computes the GVIFs in a transparent manner.
>>>>       >
>>>>       >     A brief comment on GVIFs for models with interactions (this
>>>>      isn't the
>>>>       >     place to discuss the question in detail): The Fox and Monette
>>>>      JASA
>>>>       >     paper
>>>>       >     addresses the question briefly in the context of a two-way
>>>>      ANOVA, but I
>>>>       >     don't think that the approach suggested there is easily
>>>>      generalized.
>>>>       >
>>>>       >     The following simple approach pays attention to what's
>>>>      invariant under
>>>>       >     different parametrizations of the RHS side of the model:
>>>>      Simultaneously
>>>>       >     check the collinearity of all of the coefficients of an
>>>>      interaction
>>>>       >     together with the main effects and, potentially, lower-order
>>>>       >     interactions that are marginal to it. So, e.g., in the model
>>>>      y ~ a +
>>>>       >     b +
>>>>       >     a:b + c, you'd check all of the coefficients for a, b, and
>>>>      a:b together.
>>>>       >
>>>>       >     Alternatively, one could focus in turn on each explanatory
>>>>      variable and
>>>>       >     check the collinearity of all coefficients to which it is
>>>>      marginal. So
>>>>       >     in y ~ a + b + c + a:b + a:c + d, when you focus on a, you'd
>>>>      look at
>>>>       >     all
>>>>       >     of the coefficients for a, b, c, a:b, and a:c.
>>>>       >
>>>>       >     John
>>>>       >
>>>>       >      >
>>>>       >      > Best,
>>>>       >      >
>>>>       >      > Juho
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      >
>>>>       >      > ti 1. maalisk. 2022 klo 0.05 John Fox (jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >      > <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>) kirjoitti:
>>>>       >      >
>>>>       >      >     Dear Juha,
>>>>       >      >
>>>>       >      >     On 2022-02-28 5:00 p.m., Juho Kristian Ruohonen wrote:
>>>>       >      >      > Apologies for my misreading, John, and many thanks
>>>>      for showing
>>>>       >      >     how the
>>>>       >      >      > calculation is done for a single term.
>>>>       >      >      >
>>>>       >      >      > Do you think *vif()* might be updated in the near
>>>>      future
>>>>       >     with the
>>>>       >      >      > capability of auto-detecting a multinomial model
>>>>      and returning
>>>>       >      >      > mathematically correct GVIF statistics?
>>>>       >      >
>>>>       >      >     The thought crossed my mind, but I'd want to do it in a
>>>>       >     general way,
>>>>       >      >     not
>>>>       >      >     just for the multinom() function, and in a way that
>>> avoids
>>>>       >     incorrect
>>>>       >      >     results such as those currently produced for "multinom"
>>>>       >     models, albeit
>>>>       >      >     with a warning. I can't guarantee whether or when I'll
>>> be
>>>>       >     able to do
>>>>       >      >     that.
>>>>       >      >
>>>>       >      >     John
>>>>       >      >
>>>>       >      >      >
>>>>       >      >      > If not, I'll proceed to writing my own function
>>>>      based on your
>>>>       >      >     example.
>>>>       >      >      > However, /car/ is such an excellent and widely used
>>>>       >     package that the
>>>>       >      >      > greatest benefit to mankind would probably accrue
>>>>      if /car /was
>>>>       >      >     upgraded
>>>>       >      >      > with this feature sooner rather than later.
>>>>       >      >      >
>>>>       >      >      > Best,
>>>>       >      >      >
>>>>       >      >      > Juho
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      > ma 28. helmik. 2022 klo 17.08 John Fox
>>>>      (jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >      >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>
>>>>       >      >      > <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>>) kirjoitti:
>>>>       >      >      >
>>>>       >      >      >     Dear Juho,
>>>>       >      >      >
>>>>       >      >      >     On 2022-02-28 2:06 a.m., Juho Kristian Ruohonen
>>>>      wrote:
>>>>       >      >      >      > Dear Professor Fox and other list members,
>>>>       >      >      >      >
>>>>       >      >      >      > Profuse thanks for doing that detective work
>>> for
>>>>       >     me! I myself
>>>>       >      >      >     thought
>>>>       >      >      >      > the inflation factors reported by
>>>>       >     check_collinearity() were
>>>>       >      >      >     suspiciously
>>>>       >      >      >      > high, but unlike you I lacked the expertise
>>>>      to identify
>>>>       >      >     what was
>>>>       >      >      >     going on.
>>>>       >      >      >      >
>>>>       >      >      >      > As for your suggested approach, have I
>>>>      understood this
>>>>       >      >     correctly:
>>>>       >      >      >      >
>>>>       >      >      >      > Since there doesn't yet exist an R function
>>>>      that will
>>>>       >      >     calculate the
>>>>       >      >      >      > (G)VIFS of multinomial models correctly, my
>>> best
>>>>       >     bet for
>>>>       >      >     now is
>>>>       >      >      >     just to
>>>>       >      >      >      > ignore the fact that such models partition
>>>>      the data
>>>>       >     into C-1
>>>>       >      >      >     subsets,
>>>>       >      >      >      > and to calculate approximate GVIFs from the
>>>>      entire
>>>>       >     dataset at
>>>>       >      >      >     once as if
>>>>       >      >      >      > the response were continuous? And a simple
>>>>      way to
>>>>       >     do this
>>>>       >      >     is to
>>>>       >      >      >      > construct a fake continuous response, call
>>>>       >      >     *lm(fakeresponse ~.)*,
>>>>       >      >      >     and
>>>>       >      >      >      > apply *car::vif()* on the result?
>>>>       >      >      >
>>>>       >      >      >     No, you misunderstand my suggestion, which
>>>>      perhaps isn't
>>>>       >      >     surprising
>>>>       >      >      >     given the length of my message. What you
>>>>      propose is what I
>>>>       >      >     suggested as
>>>>       >      >      >     a rough approximation *before* I confirmed that
>>> my
>>>>       >     guess of the
>>>>       >      >      >     solution
>>>>       >      >      >     was correct.
>>>>       >      >      >
>>>>       >      >      >     The R code that I sent yesterday showed how to
>>>>      compute the
>>>>       >      >     GVIF for a
>>>>       >      >      >     multinomial regression model, and I suggested
>>>>      that you
>>>>       >     write
>>>>       >      >     either a
>>>>       >      >      >     script or a simple function to do that. Here's
>>>>      a function
>>>>       >      >     that will
>>>>       >      >      >     work
>>>>       >      >      >     for a model object that responds to vcov():
>>>>       >      >      >
>>>>       >      >      >     GVIF <- function(model, intercepts, term){
>>>>       >      >      >         # model: regression model object
>>>>       >      >      >         # intercepts: row/column positions of
>>>>      intercepts
>>>>       >     in the
>>>>       >      >     coefficient
>>>>       >      >      >     covariance matrix
>>>>       >      >      >         # term: row/column positions of the
>>>>      coefficients
>>>>       >     for the
>>>>       >      >     focal term
>>>>       >      >      >         V <- vcov(model)
>>>>       >      >      >         term <- colnames(V)[term]
>>>>       >      >      >         V <- V[-intercepts, -intercepts]
>>>>       >      >      >         V <- cov2cor(V)
>>>>       >      >      >         term <- which(colnames(V) %in% term)
>>>>       >      >      >         gvif <- det(V[term, term])*det(V[-term,
>>>>      -term])/det(V)
>>>>       >      >      >         c(GVIF=gvif,
>>>>       >     "GVIF^(1/(2*p))"=gvif^(1/(2*length(term))))
>>>>       >      >      >     }
>>>>       >      >      >
>>>>       >      >      >     and here's an application to the multinom()
>>>>      example that I
>>>>       >      >     showed you
>>>>       >      >      >     yesterday:
>>>>       >      >      >
>>>>       >      >      >       > colnames(vcov(m)) # to get coefficient
>>>>      positions
>>>>       >      >      >        [1] "Labour:(Intercept)"
>>>>       >       "Labour:age"
>>>>       >      >      >
>>>>       >      >      >        [3] "Labour:economic.cond.national"
>>>>       >      >      >     "Labour:economic.cond.household"
>>>>       >      >      >        [5] "Labour:Blair"
>>>>       >       "Labour:Hague"
>>>>       >      >      >
>>>>       >      >      >        [7] "Labour:Kennedy"
>>>>       >       "Labour:Europe"
>>>>       >      >      >
>>>>       >      >      >        [9] "Labour:political.knowledge"
>>>>       >      >       "Labour:gendermale"
>>>>       >      >      >
>>>>       >      >      >     [11] "Liberal Democrat:(Intercept)"
>>>>        "Liberal
>>>>       >      >     Democrat:age"
>>>>       >      >      >
>>>>       >      >      >     [13] "Liberal Democrat:economic.cond.national"
>>>>      "Liberal
>>>>       >      >      >     Democrat:economic.cond.household"
>>>>       >      >      >     [15] "Liberal Democrat:Blair"
>>>>        "Liberal
>>>>       >      >      >     Democrat:Hague"
>>>>       >      >      >
>>>>       >      >      >     [17] "Liberal Democrat:Kennedy"
>>>>        "Liberal
>>>>       >      >      >     Democrat:Europe"
>>>>       >      >      >     [19] "Liberal Democrat:political.knowledge"
>>>>        "Liberal
>>>>       >      >      >     Democrat:gendermale"
>>>>       >      >      >
>>>>       >      >      >       > GVIF(m, intercepts=c(1, 11), term=c(2, 12))
>>>>      # GVIF
>>>>       >     for age
>>>>       >      >      >                 GVIF GVIF^(1/(2*p))
>>>>       >      >      >             1.046232       1.011363
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >     Finally, here's what you get for a linear model
>>>>      with
>>>>       >     the same RHS
>>>>       >      >      >     (where
>>>>       >      >      >     the sqrt(VIF) should be a rough approximation to
>>>>       >     GVIF^(1/4)
>>>>       >      >     reported by
>>>>       >      >      >     my GVIF() function):
>>>>       >      >      >
>>>>       >      >      >       > m.lm <- lm(as.numeric(vote) ~ . - vote1,
>>>>      data=BEPS)
>>>>       >      >      >       > sqrt(car::vif(m.lm))
>>>>       >      >      >                           age
>>> economic.cond.national
>>>>       >      >      >     economic.cond.household
>>>>       >      >      >                         Blair
>>>>       >      >      >                      1.006508
>>> 1.124132
>>>>       >      >      >     1.075656
>>>>       >      >      >                      1.118441
>>>>       >      >      >                         Hague
>>>   Kennedy
>>>>       >      >      >     Europe
>>>>       >      >      >           political.knowledge
>>>>       >      >      >                      1.066799
>>> 1.015532
>>>>       >      >      >     1.101741
>>>>       >      >      >                      1.028546
>>>>       >      >      >                        gender
>>>>       >      >      >                      1.017386
>>>>       >      >      >
>>>>       >      >      >
>>>>       >      >      >     John
>>>>       >      >      >
>>>>       >      >      >      >
>>>>       >      >      >      > Best,
>>>>       >      >      >      >
>>>>       >      >      >      > Juho
>>>>       >      >      >      >
>>>>       >      >      >      > ma 28. helmik. 2022 klo 2.23 John Fox
>>>>       >     (jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >      >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>
>>>>       >      >      >     <mailto:jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca> <mailto:jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca>>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>>
>>>>       >      >      >      > <mailto:jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca> <mailto:jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca>>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>
>>>>       >      >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>>>) kirjoitti:
>>>>       >      >      >      >
>>>>       >      >      >      >     Dear Juho,
>>>>       >      >      >      >
>>>>       >      >      >      >     I've now had a chance to think about this
>>>>       >     problem some
>>>>       >      >     more,
>>>>       >      >      >     and I
>>>>       >      >      >      >     believe that the approach I suggested is
>>>>      correct. I
>>>>       >      >     also had an
>>>>       >      >      >      >     opportunity to talk the problem over a
>>>>      bit with
>>>>       >     Georges
>>>>       >      >      >     Monette, who
>>>>       >      >      >      >     coauthored the paper that introduced
>>>>       >     generalized variance
>>>>       >      >      >     inflation
>>>>       >      >      >      >     factors (GVIFs). On the other hand, the
>>>>      results
>>>>       >      >     produced by
>>>>       >      >      >      >     performance::check_collinearity() for
>>>>       >     multinomial logit
>>>>       >      >      >     models don't
>>>>       >      >      >      >     seem to be correct (see below).
>>>>       >      >      >      >
>>>>       >      >      >      >     Here's an example, using the
>>>>      nnet::multinom()
>>>>       >     function
>>>>       >      >     to fit a
>>>>       >      >      >      >     multinomial logit model, with alternative
>>>>       >      >     parametrizations of the
>>>>       >      >      >      >     LHS of
>>>>       >      >      >      >     the model:
>>>>       >      >      >      >
>>>>       >      >      >      >     --------- snip -----------
>>>>       >      >      >      >
>>>>       >      >      >      >       > library(nnet) # for multinom()
>>>>       >      >      >      >       > library(carData) # for BEPS data set
>>>>       >      >      >      >
>>>>       >      >      >      >       > # alternative ordering of the
>>>>      response levels:
>>>>       >      >      >      >       > BEPS$vote1 <- factor(BEPS$vote,
>>>>       >     levels=c("Labour",
>>>>       >      >     "Liberal
>>>>       >      >      >      >     Democrat", "Conservative"))
>>>>       >      >      >      >       > levels(BEPS$vote)
>>>>       >      >      >      >     [1] "Conservative"     "Labour"
>>>>        "Liberal
>>>>       >      >     Democrat"
>>>>       >      >      >      >       > levels(BEPS$vote1)
>>>>       >      >      >      >     [1] "Labour"           "Liberal Democrat"
>>>>       >     "Conservative"
>>>>       >      >      >      >
>>>>       >      >      >      >       > m <- multinom(vote ~ . - vote1,
>>>>      data=BEPS)
>>>>       >      >      >      >     # weights:  33 (20 variable)
>>>>       >      >      >      >     initial  value 1675.383740
>>>>       >      >      >      >     iter  10 value 1345.935273
>>>>       >      >      >      >     iter  20 value 1150.956807
>>>>       >      >      >      >     iter  30 value 1141.921662
>>>>       >      >      >      >     iter  30 value 1141.921661
>>>>       >      >      >      >     iter  30 value 1141.921661
>>>>       >      >      >      >     final  value 1141.921661
>>>>       >      >      >      >     converged
>>>>       >      >      >      >       > m1 <- multinom(vote1 ~ . - vote,
>>>>      data=BEPS)
>>>>       >      >      >      >     # weights:  33 (20 variable)
>>>>       >      >      >      >     initial  value 1675.383740
>>>>       >      >      >      >     iter  10 value 1280.439304
>>>>       >      >      >      >     iter  20 value 1165.513772
>>>>       >      >      >      >     final  value 1141.921662
>>>>       >      >      >      >     converged
>>>>       >      >      >      >
>>>>       >      >      >      >       > rbind(coef(m), coef(m1)) # compare
>>>>      coefficients
>>>>       >      >      >      >                        (Intercept)
>>> age
>>>>       >      >      >     economic.cond.national
>>>>       >      >      >      >     economic.cond.household
>>>>       >      >      >      >     Labour             0.9515214 -0.021913989
>>>>       >      >     0.5575707
>>>>       >      >      >      >            0.15839096
>>>>       >      >      >      >     Liberal Democrat   1.4119306 -0.016810735
>>>>       >      >     0.1810761
>>>>       >      >      >      >           -0.01196664
>>>>       >      >      >      >     Liberal Democrat   0.4604567  0.005102666
>>>>       >      >       -0.3764928
>>>>       >      >      >      >           -0.17036682
>>>>       >      >      >      >     Conservative      -0.9514466  0.021912305
>>>>       >      >       -0.5575644
>>>>       >      >      >      >           -0.15838744
>>>>       >      >      >      >                             Blair       Hague
>>>>       >     Kennedy
>>>>       >      >          Europe
>>>>       >      >      >      >     political.knowledge
>>>>       >      >      >      >     Labour            0.8371764 -0.90775585
>>>>      0.2513436
>>>>       >      >     -0.22781308
>>>>       >      >      >      >     -0.5370612
>>>>       >      >      >      >     Liberal Democrat  0.2937331 -0.82217625
>>>>      0.6710567
>>>>       >      >     -0.20004624
>>>>       >      >      >      >     -0.2034605
>>>>       >      >      >      >     Liberal Democrat -0.5434408  0.08559455
>>>>      0.4197027
>>>>       >      >     0.02776465
>>>>       >      >      >      >     0.3336068
>>>>       >      >      >      >     Conservative     -0.8371670  0.90778068
>>>>      -0.2513735
>>>>       >      >     0.22781092
>>>>       >      >      >      >     0.5370545
>>>>       >      >      >      >                         gendermale
>>>>       >      >      >      >     Labour            0.13765774
>>>>       >      >      >      >     Liberal Democrat  0.12640823
>>>>       >      >      >      >     Liberal Democrat -0.01125898
>>>>       >      >      >      >     Conservative     -0.13764849
>>>>       >      >      >      >
>>>>       >      >      >      >       > c(logLik(m), logLik(m1)) # same fit
>>>>      to the data
>>>>       >      >      >      >     [1] -1141.922 -1141.922
>>>>       >      >      >      >
>>>>       >      >      >      >       > # covariance matrices for
>>> coefficients:
>>>>       >      >      >      >       > V <- vcov(m)
>>>>       >      >      >      >       > V1 <- vcov(m1)
>>>>       >      >      >      >       > cbind(colnames(V), colnames(V1)) #
>>>>      compare
>>>>       >      >      >      >             [,1]
>>>>       >         [,2]
>>>>       >      >      >      >
>>>>       >      >      >      >        [1,] "Labour:(Intercept)"
>>>>       >      >       "Liberal
>>>>       >      >      >      >     Democrat:(Intercept)"
>>>>       >      >      >      >        [2,] "Labour:age"
>>>>       >      >       "Liberal
>>>>       >      >      >      >     Democrat:age"
>>>>       >      >      >      >
>>>>       >      >      >      >        [3,] "Labour:economic.cond.national"
>>>>       >      >     "Liberal
>>>>       >      >      >      >     Democrat:economic.cond.national"
>>>>       >      >      >      >        [4,] "Labour:economic.cond.household"
>>>>       >      >       "Liberal
>>>>       >      >      >      >     Democrat:economic.cond.household"
>>>>       >      >      >      >        [5,] "Labour:Blair"
>>>>       >      >       "Liberal
>>>>       >      >      >      >     Democrat:Blair"
>>>>       >      >      >      >        [6,] "Labour:Hague"
>>>>       >      >       "Liberal
>>>>       >      >      >      >     Democrat:Hague"
>>>>       >      >      >      >        [7,] "Labour:Kennedy"
>>>>       >      >       "Liberal
>>>>       >      >      >      >     Democrat:Kennedy"
>>>>       >      >      >      >        [8,] "Labour:Europe"
>>>>       >      >     "Liberal
>>>>       >      >      >      >     Democrat:Europe"
>>>>       >      >      >      >        [9,] "Labour:political.knowledge"
>>>>       >      >       "Liberal
>>>>       >      >      >      >     Democrat:political.knowledge"
>>>>       >      >      >      >     [10,] "Labour:gendermale"
>>>>       >        "Liberal
>>>>       >      >      >      >     Democrat:gendermale"
>>>>       >      >      >      >     [11,] "Liberal Democrat:(Intercept)"
>>>>       >      >      >      >     "Conservative:(Intercept)"
>>>>       >      >      >      >     [12,] "Liberal Democrat:age"
>>>>       >      >      >       "Conservative:age"
>>>>       >      >      >      >
>>>>       >      >      >      >     [13,] "Liberal
>>>>      Democrat:economic.cond.national"
>>>>       >      >      >      >     "Conservative:economic.cond.national"
>>>>       >      >      >      >     [14,] "Liberal
>>>>      Democrat:economic.cond.household"
>>>>       >      >      >      >     "Conservative:economic.cond.household"
>>>>       >      >      >      >     [15,] "Liberal Democrat:Blair"
>>>>       >      >      >       "Conservative:Blair"
>>>>       >      >      >      >
>>>>       >      >      >      >     [16,] "Liberal Democrat:Hague"
>>>>       >      >      >       "Conservative:Hague"
>>>>       >      >      >      >
>>>>       >      >      >      >     [17,] "Liberal Democrat:Kennedy"
>>>>       >      >      >       "Conservative:Kennedy"
>>>>       >      >      >      >
>>>>       >      >      >      >     [18,] "Liberal Democrat:Europe"
>>>>       >      >      >     "Conservative:Europe"
>>>>       >      >      >      >
>>>>       >      >      >      >     [19,] "Liberal
>>> Democrat:political.knowledge"
>>>>       >      >      >      >     "Conservative:political.knowledge"
>>>>       >      >      >      >     [20,] "Liberal Democrat:gendermale"
>>>>       >      >      >      >     "Conservative:gendermale"
>>>>       >      >      >      >
>>>>       >      >      >      >       > int <- c(1, 11) # remove intercepts
>>>>       >      >      >      >       > colnames(V)[int]
>>>>       >      >      >      >     [1] "Labour:(Intercept)"
>>>   "Liberal
>>>>       >      >     Democrat:(Intercept)"
>>>>       >      >      >      >
>>>>       >      >      >      >       > colnames(V1)[int]
>>>>       >      >      >      >     [1] "Liberal Democrat:(Intercept)"
>>>>       >      >     "Conservative:(Intercept)"
>>>>       >      >      >      >       > V <- V[-int, -int]
>>>>       >      >      >      >       > V1 <- V1[-int, -int]
>>>>       >      >      >      >
>>>>       >      >      >      >       > age <- c(1, 10) # locate age
>>>>      coefficients
>>>>       >      >      >      >       > colnames(V)[age]
>>>>       >      >      >      >     [1] "Labour:age"           "Liberal
>>>>      Democrat:age"
>>>>       >      >      >      >       > colnames(V1)[age]
>>>>       >      >      >      >     [1] "Liberal Democrat:age"
>>>>      "Conservative:age"
>>>>       >      >      >      >
>>>>       >      >      >      >       > V <- cov2cor(V) # compute coefficient
>>>>       >     correlations
>>>>       >      >      >      >       > V1 <- cov2cor(V1)
>>>>       >      >      >      >
>>>>       >      >      >      >       > # compare GVIFs:
>>>>       >      >      >      >       > c(det(V[age, age])*det(V[-age,
>>>>      -age])/det(V),
>>>>       >      >      >      >     +   det(V1[age, age])*det(V1[-age,
>>>>      -age])/det(V1))
>>>>       >      >      >      >     [1] 1.046232 1.046229
>>>>       >      >      >      >
>>>>       >      >      >      >     --------- snip -----------
>>>>       >      >      >      >
>>>>       >      >      >      >     For curiosity, I applied car::vif() and
>>>>       >      >      >      >     performance::check_collinearity() to
>>> these
>>>>       >     models to
>>>>       >      >     see what
>>>>       >      >      >     they
>>>>       >      >      >      >     would
>>>>       >      >      >      >     do. Both returned the wrong answer. vif()
>>>>       >     produced a
>>>>       >      >     warning, but
>>>>       >      >      >      >     check_collinearity() didn't:
>>>>       >      >      >      >
>>>>       >      >      >      >     --------- snip -----------
>>>>       >      >      >      >
>>>>       >      >      >      >       > car::vif(m1)
>>>>       >      >      >      >                           age
>>>>      economic.cond.national
>>>>       >      >      >      >     economic.cond.household
>>>>       >      >      >      >                     15.461045
>>>>        22.137772
>>>>       >      >      >      >       16.693877
>>>>       >      >      >      >                         Blair
>>>>          Hague
>>>>       >      >      >      >       Kennedy
>>>>       >      >      >      >                     14.681562
>>>>      7.483039
>>>>       >      >      >      >       15.812067
>>>>       >      >      >      >                        Europe
>>>>        political.knowledge
>>>>       >      >      >      >     gender
>>>>       >      >      >      >                      6.502119
>>>>      4.219507
>>>>       >      >      >      >     2.313885
>>>>       >      >      >      >     Warning message:
>>>>       >      >      >      >     In vif.default(m1) : No intercept: vifs
>>>>      may not be
>>>>       >      >     sensible.
>>>>       >      >      >      >
>>>>       >      >      >      >       > performance::check_collinearity(m)
>>>>       >      >      >      >     # Check for Multicollinearity
>>>>       >      >      >      >
>>>>       >      >      >      >     Low Correlation
>>>>       >      >      >      >
>>>>       >      >      >      >                           Term  VIF
>>> Increased SE
>>>>       >     Tolerance
>>>>       >      >      >      >                            age 1.72
>>>>        1.31
>>>>       >        0.58
>>>>       >      >      >      >         economic.cond.national 1.85
>>>>        1.36
>>>>       >        0.54
>>>>       >      >      >      >        economic.cond.household 1.86
>>>>        1.37
>>>>       >        0.54
>>>>       >      >      >      >                          Blair 1.63
>>>>        1.28
>>>>       >        0.61
>>>>       >      >      >      >                          Hague 1.94
>>>>        1.39
>>>>       >        0.52
>>>>       >      >      >      >                        Kennedy 1.70
>>>>        1.30
>>>>       >        0.59
>>>>       >      >      >      >                         Europe 2.01
>>>>        1.42
>>>>       >        0.50
>>>>       >      >      >      >            political.knowledge 1.94
>>>>        1.39
>>>>       >        0.52
>>>>       >      >      >      >                         gender 1.78
>>>>        1.33
>>>>       >        0.56
>>>>       >      >      >      >       > performance::check_collinearity(m1)
>>>>       >      >      >      >     # Check for Multicollinearity
>>>>       >      >      >      >
>>>>       >      >      >      >     Low Correlation
>>>>       >      >      >      >
>>>>       >      >      >      >                           Term  VIF
>>> Increased SE
>>>>       >     Tolerance
>>>>       >      >      >      >                            age 1.19
>>>>        1.09
>>>>       >        0.84
>>>>       >      >      >      >         economic.cond.national 1.42
>>>>        1.19
>>>>       >        0.70
>>>>       >      >      >      >        economic.cond.household 1.32
>>>>        1.15
>>>>       >        0.76
>>>>       >      >      >      >                          Blair 1.50
>>>>        1.22
>>>>       >        0.67
>>>>       >      >      >      >                          Hague 1.30
>>>>        1.14
>>>>       >        0.77
>>>>       >      >      >      >                        Kennedy 1.19
>>>>        1.09
>>>>       >        0.84
>>>>       >      >      >      >                         Europe 1.34
>>>>        1.16
>>>>       >        0.75
>>>>       >      >      >      >            political.knowledge 1.30
>>>>        1.14
>>>>       >        0.77
>>>>       >      >      >      >                         gender 1.23
>>>>        1.11
>>>>       >        0.81
>>>>       >      >      >      >
>>>>       >      >      >      >     --------- snip -----------
>>>>       >      >      >      >
>>>>       >      >      >      >     I looked at the code for vif() and
>>>>       >     check_collinearity() to
>>>>       >      >      >     see where
>>>>       >      >      >      >     they went wrong. Both failed to handle
>>>>      the two
>>>>       >      >     intercepts in
>>>>       >      >      >     the model
>>>>       >      >      >      >     correctly -- vif() thought there was no
>>>>       >     intercept and
>>>>       >      >      >      >     check_collinearity() just removed the
>>> first
>>>>       >     intercept
>>>>       >      >     but not the
>>>>       >      >      >      >     second.
>>>>       >      >      >      >
>>>>       >      >      >      >     In examining the code for
>>>>      check_collinearity(), I
>>>>       >      >     discovered a
>>>>       >      >      >      >     couple of
>>>>       >      >      >      >     additional disconcerting facts. First,
>>>>      part of the
>>>>       >      >     code seems
>>>>       >      >      >     to be
>>>>       >      >      >      >     copied from vif.default(). Second, as a
>>>>       >     consequence,
>>>>       >      >      >      >     check_collinearity() actually computes
>>>>      GVIFs rather
>>>>       >      >     than VIFs
>>>>       >      >      >     (and
>>>>       >      >      >      >     doesn't reference either the Fox and
>>>>      Monette paper
>>>>       >      >      >     introducing GVIFs or
>>>>       >      >      >      >     the car package) but doesn't seem to
>>>>      understand
>>>>       >     that, and,
>>>>       >      >      >     for example,
>>>>       >      >      >      >     takes the squareroot of the GVIF
>>>>      (reported in the
>>>>       >      >     column marked
>>>>       >      >      >      >     "Increased SE") rather than the 2p root
>>>>      (when there
>>>>       >      >     are p > 1
>>>>       >      >      >      >     coefficients in a term).
>>>>       >      >      >      >
>>>>       >      >      >      >     Here's the relevant code from the two
>>>>      functions
>>>>       >     (where
>>>>       >      >     . . .
>>>>       >      >      >     denotes
>>>>       >      >      >      >     elided lines) -- the default method for
>>>>      vif() and
>>>>       >      >      >      >     .check_collinearity(),
>>>>       >      >      >      >     which is called by
>>>>      check_collinearity.default():
>>>>       >      >      >      >
>>>>       >      >      >      >     --------- snip -----------
>>>>       >      >      >      >
>>>>       >      >      >      >       > car:::vif.default
>>>>       >      >      >      >     function (mod, ...)
>>>>       >      >      >      >     {
>>>>       >      >      >      >           . . .
>>>>       >      >      >      >           v <- vcov(mod)
>>>>       >      >      >      >           assign <- attr(model.matrix(mod),
>>>>      "assign")
>>>>       >      >      >      >           if (names(coefficients(mod)[1]) ==
>>>>       >     "(Intercept)") {
>>>>       >      >      >      >               v <- v[-1, -1]
>>>>       >      >      >      >               assign <- assign[-1]
>>>>       >      >      >      >           }
>>>>       >      >      >      >           else warning("No intercept: vifs
>>>>      may not be
>>>>       >      >     sensible.")
>>>>       >      >      >      >           terms <- labels(terms(mod))
>>>>       >      >      >      >           n.terms <- length(terms)
>>>>       >      >      >      >           if (n.terms < 2)
>>>>       >      >      >      >               stop("model contains fewer
>>>>      than 2 terms")
>>>>       >      >      >      >           R <- cov2cor(v)
>>>>       >      >      >      >           detR <- det(R)
>>>>       >      >      >      >           . . .
>>>>       >      >      >      >           for (term in 1:n.terms) {
>>>>       >      >      >      >               subs <- which(assign == term)
>>>>       >      >      >      >               result[term, 1] <-
>>>>      det(as.matrix(R[subs,
>>>>       >      >     subs])) *
>>>>       >      >      >      >     det(as.matrix(R[-subs,
>>>>       >      >      >      >                   -subs]))/detR
>>>>       >      >      >      >               result[term, 2] <- length(subs)
>>>>       >      >      >      >           }
>>>>       >      >      >      >           . . .
>>>>       >      >      >      >     }
>>>>       >      >      >      >
>>>>       >      >      >      >       > performance:::.check_collinearity
>>>>       >      >      >      >     function (x, component, verbose = TRUE)
>>>>       >      >      >      >     {
>>>>       >      >      >      >           v <- insight::get_varcov(x,
>>>>      component =
>>>>       >     component,
>>>>       >      >      >     verbose =
>>>>       >      >      >      >     FALSE)
>>>>       >      >      >      >           assign <- .term_assignments(x,
>>>>      component,
>>>>       >     verbose =
>>>>       >      >      >     verbose)
>>>>       >      >      >      >           . . .
>>>>       >      >      >      >           if (insight::has_intercept(x)) {
>>>>       >      >      >      >               v <- v[-1, -1]
>>>>       >      >      >      >               assign <- assign[-1]
>>>>       >      >      >      >           }
>>>>       >      >      >      >           else {
>>>>       >      >      >      >               if (isTRUE(verbose)) {
>>>>       >      >      >      >                   warning("Model has no
>>>>      intercept. VIFs
>>>>       >      >     may not be
>>>>       >      >      >      >     sensible.",
>>>>       >      >      >      >                       call. = FALSE)
>>>>       >      >      >      >               }
>>>>       >      >      >      >           }
>>>>       >      >      >      >               . . .
>>>>       >      >      >      >               terms <-
>>>>       >     labels(stats::terms(f[[component]]))
>>>>       >      >      >      >               . . .
>>>>       >      >      >      >           n.terms <- length(terms)
>>>>       >      >      >      >           if (n.terms < 2) {
>>>>       >      >      >      >               if (isTRUE(verbose)) {
>>>>       >      >      >      >
>>>>       >       warning(insight::format_message(sprintf("Not
>>>>       >      >      >     enough model
>>>>       >      >      >      >     terms in the %s part of the model to
>>>>      check for
>>>>       >      >      >     multicollinearity.",
>>>>       >      >      >      >                       component)), call. =
>>>>      FALSE)
>>>>       >      >      >      >               }
>>>>       >      >      >      >               return(NULL)
>>>>       >      >      >      >           }
>>>>       >      >      >      >           R <- stats::cov2cor(v)
>>>>       >      >      >      >           detR <- det(R)
>>>>       >      >      >      >           . . .
>>>>       >      >      >      >           for (term in 1:n.terms) {
>>>>       >      >      >      >               subs <- which(assign == term)
>>>>       >      >      >      >                   . . .
>>>>       >      >      >      >                   result <- c(result,
>>>>       >      >     det(as.matrix(R[subs, subs])) *
>>>>       >      >      >      >                       det(as.matrix(R[-subs,
>>>>       >     -subs]))/detR)
>>>>       >      >      >      >                   . . .
>>>>       >      >      >      >           }
>>>>       >      >      >      >           . . .
>>>>       >      >      >      >     }
>>>>       >      >      >      >
>>>>       >      >      >      >     --------- snip -----------
>>>>       >      >      >      >
>>>>       >      >      >      >     So, the upshot of all this is that you
>>>>      should
>>>>       >     be able
>>>>       >      >     to do
>>>>       >      >      >     what you
>>>>       >      >      >      >     want, but not with either car::vif() or
>>>>       >      >      >      >     performance::check_collinearity().
>>>>      Instead, either
>>>>       >      >     write your own
>>>>       >      >      >      >     function or do the computations in a
>>> script.
>>>>       >      >      >      >
>>>>       >      >      >      >     There's also a lesson here about S3
>>> default
>>>>       >     methods:
>>>>       >      >     The fact
>>>>       >      >      >     that a
>>>>       >      >      >      >     default method returns a result rather
>>> than
>>>>       >     throwing
>>>>       >      >     an error
>>>>       >      >      >     or a
>>>>       >      >      >      >     warning doesn't mean that the result is
>>> the
>>>>       >     right answer.
>>>>       >      >      >      >
>>>>       >      >      >      >     I hope this helps,
>>>>       >      >      >      >        John
>>>>       >      >      >      >
>>>>       >      >      >      >
>>>>       >      >      >      >     On 2022-02-26 3:45 p.m., Juho Kristian
>>>>      Ruohonen
>>>>       >     wrote:
>>>>       >      >      >      >      > Dear John W,
>>>>       >      >      >      >      >
>>>>       >      >      >      >      > Thank you very much for the tip-off!
>>>>       >     Apologies for not
>>>>       >      >      >     responding
>>>>       >      >      >      >     earlier
>>>>       >      >      >      >      > (gmail apparently decided to direct
>>>>      your email
>>>>       >      >     right into the
>>>>       >      >      >      >     junk folder).
>>>>       >      >      >      >      > I am very pleased to note that the
>>>>      package you
>>>>       >      >     mention does
>>>>       >      >      >      >     indeed work
>>>>       >      >      >      >      > with *brms* multinomial models!
>>>>      Thanks again!
>>>>       >      >      >      >      >
>>>>       >      >      >      >      > Best,
>>>>       >      >      >      >      >
>>>>       >      >      >      >      > Juho
>>>>       >      >      >      >      >
>>>>       >      >      >      >      > pe 25. helmik. 2022 klo 19.23 John
>>>>      Willoughby
>>>>       >      >      >      >     (johnwillec using gmail.com
>>>>      <mailto:johnwillec using gmail.com>
>>>>       >     <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>>
>>>>      <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>
>>>>       >     <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>>>
>>>>       >      >     <mailto:johnwillec using gmail.com
>>>>      <mailto:johnwillec using gmail.com> <mailto:johnwillec using gmail.com
>>>>      <mailto:johnwillec using gmail.com>>
>>>>       >     <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>
>>>>      <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>>>>
>>>>       >      >      >     <mailto:johnwillec using gmail.com
>>>>      <mailto:johnwillec using gmail.com>
>>>>       >     <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>>
>>>>      <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>
>>>>       >     <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>>>
>>>>       >      >     <mailto:johnwillec using gmail.com
>>>>      <mailto:johnwillec using gmail.com> <mailto:johnwillec using gmail.com
>>>>      <mailto:johnwillec using gmail.com>>
>>>>       >     <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>
>>>>      <mailto:johnwillec using gmail.com <mailto:johnwillec using gmail.com>>>>>)
>>>>       >      >      >      >      > kirjoitti:
>>>>       >      >      >      >      >
>>>>       >      >      >      >      >> Have you tried the
>>> check_collinearity()
>>>>       >     function
>>>>       >      >     in the
>>>>       >      >      >     performance
>>>>       >      >      >      >      >> package? It's supposed to work on
>>> brms
>>>>       >     models, but
>>>>       >      >     whether it
>>>>       >      >      >      >     will work on
>>>>       >      >      >      >      >> a multinomial model I don't know.
>>>>      It works
>>>>       >     well
>>>>       >      >     on mixed
>>>>       >      >      >     models
>>>>       >      >      >      >     generated
>>>>       >      >      >      >      >> by glmmTMB().
>>>>       >      >      >      >      >>
>>>>       >      >      >      >      >> John Willoughby
>>>>       >      >      >      >      >>
>>>>       >      >      >      >      >>
>>>>       >      >      >      >      >> On Fri, Feb 25, 2022 at 3:01 AM
>>>>       >      >      >      >
>>>>        <r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>
>>>>       >      >      >
>>>>        <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>>
>>>>       >      >      >      >
>>>>       >       <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>
>>>>       >      >      >
>>>>        <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>>>>
>>>>       >      >      >      >      >> wrote:
>>>>       >      >      >      >      >>
>>>>       >      >      >      >      >>> Send R-sig-mixed-models mailing list
>>>>       >     submissions to
>>>>       >      >      >      >      >>> r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>>
>>>>       >      >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>>>
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> To subscribe or unsubscribe via the
>>>>      World Wide
>>>>       >      >     Web, visit
>>>>       >      >      >      >      >>>
>>>>       >      > https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>
>>>>       >      >      >
>>>>       >       <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>>
>>>>       >      >      >      >
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>
>>>>       >      >      >
>>>>       >       <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>>>
>>>>       >      >      >      >      >>> or, via email, send a message with
>>>>      subject or
>>>>       >      >     body 'help' to
>>>>       >      >      >      >      >>>
>>>>      r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>
>>>>       >      >      >
>>>>        <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>>
>>>>       >      >      >      >
>>>>       >       <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>
>>>>       >      >      >
>>>>        <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-request using r-project.org
>>>>      <mailto:r-sig-mixed-models-request using r-project.org>>>>>
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> You can reach the person managing
>>>>      the list at
>>>>       >      >      >      >      >>>
>>>>      r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>>>
>>>>       >      >      >      >
>>>>        <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models-owner using r-project.org
>>>>      <mailto:r-sig-mixed-models-owner using r-project.org>>>>>
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> When replying, please edit your
>>> Subject
>>>>       >     line so it is
>>>>       >      >      >     more specific
>>>>       >      >      >      >      >>> than "Re: Contents of
>>>>      R-sig-mixed-models
>>>>       >     digest..."
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> Today's Topics:
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>>     1. Collinearity diagnostics for
>>>>      (mixed)
>>>>       >      >     multinomial
>>>>       >      >      >     models
>>>>       >      >      >      >      >>>        (Juho Kristian Ruohonen)
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >
>>>>       >      >      >
>>>>       >      >
>>>>       >
>>>>
>>>   ----------------------------------------------------------------------
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> Message: 1
>>>>       >      >      >      >      >>> Date: Fri, 25 Feb 2022 10:23:25
>>> +0200
>>>>       >      >      >      >      >>> From: Juho Kristian Ruohonen
>>>>       >      >      >     <juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>
>>>>       >      >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>>
>>>>       >      >      >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>
>>>>       >      >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>>>
>>>>       >      >      >      >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>
>>>>       >      >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>>
>>>>       >      >      >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>
>>>>       >      >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>
>>>>       >     <mailto:juho.kristian.ruohonen using gmail.com
>>>>      <mailto:juho.kristian.ruohonen using gmail.com>>>>>>
>>>>       >      >      >      >      >>> To: John Fox <jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >      >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >      >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>>
>>>>       >      >      >     <mailto:jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca> <mailto:jfox using mcmaster.ca
>>>>      <mailto:jfox using mcmaster.ca>>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>
>>>>       >      >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>
>>>>       >     <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>
>>>>      <mailto:jfox using mcmaster.ca <mailto:jfox using mcmaster.ca>>>>>>
>>>>       >      >      >      >      >>> Cc:
>>>>      "r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>>
>>>>       >      >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>>>"
>>>>       >      >      >      >      >>>
>>>>      <r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>>
>>>>       >      >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>
>>>>       >     <mailto:r-sig-mixed-models using r-project.org
>>>>      <mailto:r-sig-mixed-models using r-project.org>>>>>>
>>>>       >      >      >      >      >>> Subject: [R-sig-ME] Collinearity
>>>>       >     diagnostics for
>>>>       >      >     (mixed)
>>>>       >      >      >      >     multinomial
>>>>       >      >      >      >      >>>          models
>>>>       >      >      >      >      >>> Message-ID:
>>>>       >      >      >      >      >>>          <
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >
>>>>       >      >      >
>>>>       >      >
>>>>       >
>>>>      CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>>>      <mailto:
>>> CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>>>       >
>>>>        <mailto:
>>> CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>>>>
>>>>       >      >
>>>>       >
>>>>        <mailto:
>>> CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>>>>>
>>>>       >      >      >
>>>>       >      >
>>>>       >
>>>>        <mailto:
>>> CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>>>>>>
>>>>       >      >      >      >
>>>>       >      >      >
>>>>       >      >
>>>>       >
>>>>        <mailto:
>>> CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>>>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com>
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>> <mailto:CAG_dBVfZr1-P7Q3kbE8TGPm-_2sJixdGCHCtWM9Q9PEnd8ftZw using mail.gmail.com
>>>>>>>>>
>>>>       >      >      >      >      >>> Content-Type: text/plain;
>>>>      charset="utf-8"
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> Dear John (and anyone else
>>> qualified to
>>>>       >     comment),
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> I fit lots of mixed-effects
>>> multinomial
>>>>       >     models in my
>>>>       >      >      >     research,
>>>>       >      >      >      >     and I
>>>>       >      >      >      >      >> would
>>>>       >      >      >      >      >>> like to see some (multi)collinearity
>>>>       >     diagnostics
>>>>       >      >     on the
>>>>       >      >      >     fixed
>>>>       >      >      >      >     effects, of
>>>>       >      >      >      >      >>> which there are over 30. My models
>>>>      are fit
>>>>       >     using the
>>>>       >      >      >     Bayesian
>>>>       >      >      >      >     *brms*
>>>>       >      >      >      >      >>> package because I know of no
>>>>      frequentist
>>>>       >     packages
>>>>       >      >     with
>>>>       >      >      >      >     multinomial GLMM
>>>>       >      >      >      >      >>> compatibility.
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> With continuous or dichotomous
>>>>      outcomes,
>>>>       >     my go-to
>>>>       >      >      >     function for
>>>>       >      >      >      >      >> calculating
>>>>       >      >      >      >      >>> multicollinearity diagnostics is of
>>>>      course
>>>>       >      >     *vif()* from
>>>>       >      >      >     the *car*
>>>>       >      >      >      >      >> package.
>>>>       >      >      >      >      >>> As expected, however, this function
>>>>      does not
>>>>       >      >     report sensible
>>>>       >      >      >      >     diagnostics
>>>>       >      >      >      >      >>> for multinomial models -- not even
>>> for
>>>>       >     standard
>>>>       >      >     ones fit
>>>>       >      >      >     by the
>>>>       >      >      >      >     *nnet*
>>>>       >      >      >      >      >>> package's *multinom()* function.
>>>>      The reason, I
>>>>       >      >     presume, is
>>>>       >      >      >      >     because a
>>>>       >      >      >      >      >>> multinomial model is not really one
>>>>      but C-1
>>>>       >      >     regression
>>>>       >      >      >     models
>>>>       >      >      >      >     (where C
>>>>       >      >      >      >      >> is
>>>>       >      >      >      >      >>> the number of response categories)
>>>>      and the
>>>>       >     *vif()*
>>>>       >      >      >     function is not
>>>>       >      >      >      >      >> designed
>>>>       >      >      >      >      >>> to deal with this scenario.
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> Therefore, in order to obtain
>>>>      meaningful
>>>>       >     collinearity
>>>>       >      >      >     metrics,
>>>>       >      >      >      >     my present
>>>>       >      >      >      >      >>> plan is to write a simple helper
>>>>      function
>>>>       >     that uses
>>>>       >      >      >     *vif() *to
>>>>       >      >      >      >     calculate
>>>>       >      >      >      >      >>> and present (generalized) variance
>>>>      inflation
>>>>       >      >     metrics for
>>>>       >      >      >     the C-1
>>>>       >      >      >      >      >>> sub-datasets to which the C-1
>>> component
>>>>       >     binomial
>>>>       >      >     models
>>>>       >      >      >     of the
>>>>       >      >      >      >     overall
>>>>       >      >      >      >      >>> multinomial model are fit. In other
>>>>      words, it
>>>>       >      >     will partition
>>>>       >      >      >      >     the data
>>>>       >      >      >      >      >> into
>>>>       >      >      >      >      >>> those C-1 subsets, and then apply
>>>>      *vif()*
>>>>       >     to as
>>>>       >      >     many linear
>>>>       >      >      >      >     regressions
>>>>       >      >      >      >      >>> using a made-up continuous response
>>> and
>>>>       >     the fixed
>>>>       >      >     effects of
>>>>       >      >      >      >     interest.
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> Does this seem like a sensible
>>>>      approach?
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> Best,
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>> Juho
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>>
>>>>       >      >      >      >      >>
>>>>       >      >      >      >      >>          [[alternative HTML version
>>>>      deleted]]
>>>>       >      >      >      >      >>
>>>>       >      >      >      >      >>
>>>>      _______________________________________________
>>>>       >      >      >      >      >> R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>>
>>>>       >      >      >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>>> mailing list
>>>>       >      >      >      >      >>
>>>>       >      > https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>
>>>>       >      >      >
>>>>       >       <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>>
>>>>       >      >      >      >
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>
>>>>       >      >      >
>>>>       >       <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>>>
>>>>       >      >      >      >      >>
>>>>       >      >      >      >      >
>>>>       >      >      >      >      >       [[alternative HTML version
>>>>      deleted]]
>>>>       >      >      >      >      >
>>>>       >      >      >      >      >
>>>>      _______________________________________________
>>>>       >      >      >      >      > R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>>
>>>>       >      >      >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>
>>>>       >      >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>
>>>>       >      >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>
>>>>       >     <mailto:R-sig-mixed-models using r-project.org
>>>>      <mailto:R-sig-mixed-models using r-project.org>>>>> mailing list
>>>>       >      >      >      >      >
>>>>       >      > https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>
>>>>       >      >      >
>>>>       >       <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>>
>>>>       >      >      >      >
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>
>>>>       >      >      >
>>>>       >       <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>
>>>>       >      >
>>>>        <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>
>>>>       >     <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>>>      <https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models>>>>>
>>>>       >      >      >      >     --
>>>>       >      >      >      >     John Fox, Professor Emeritus
>>>>       >      >      >      >     McMaster University
>>>>       >      >      >      >     Hamilton, Ontario, Canada
>>>>       >      >      >      >     web:
>>>>      https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>>
>>>>       >      >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>>>
>>>>       >      >      >      >
>>>>        <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>>
>>>>       >      >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>>>>
>>>>       >      >      >      >
>>>>       >      >      >     --
>>>>       >      >      >     John Fox, Professor Emeritus
>>>>       >      >      >     McMaster University
>>>>       >      >      >     Hamilton, Ontario, Canada
>>>>       >      >      >     web: https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>>
>>>>       >      >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>>>
>>>>       >      >      >
>>>>       >      >     --
>>>>       >      >     John Fox, Professor Emeritus
>>>>       >      >     McMaster University
>>>>       >      >     Hamilton, Ontario, Canada
>>>>       >      >     web: https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >      >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>>
>>>>       >      >
>>>>       >
>>>>
>>>   ------------------------------------------------------------------------
>>>>       >     --
>>>>       >     John Fox, Professor Emeritus
>>>>       >     McMaster University
>>>>       >     Hamilton, Ontario, Canada
>>>>       >     web: https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>       >     <https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>>
>>>>       >
>>>>      --
>>>>      John Fox, Professor Emeritus
>>>>      McMaster University
>>>>      Hamilton, Ontario, Canada
>>>>      web: https://socialsciences.mcmaster.ca/jfox/
>>>>      <https://socialsciences.mcmaster.ca/jfox/>
>>>>
>>> --
>>> John Fox, Professor Emeritus
>>> McMaster University
>>> Hamilton, Ontario, Canada
>>> web: https://socialsciences.mcmaster.ca/jfox/
>>>
>>>
>>
>> 	[[alternative HTML version deleted]]
>>
>> _______________________________________________
>> R-sig-mixed-models using r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-sig-mixed-models
>>



More information about the R-sig-mixed-models mailing list