diff --git a/R/rep_glm.R b/R/rep_glm.R index 21304cc..f2f18fc 100644 --- a/R/rep_glm.R +++ b/R/rep_glm.R @@ -1,91 +1,95 @@ #' A repeated logistic regression function #' -#' For bivariate analyses. +#' @description For bivariate analyses. The confint() function is rather slow, causing the whole function to hang when including many predictors and calculating the ORs with CI. #' @param y Effect meassure. -#' @param v1 Main variable in model +#' @param vars variables in model. Input as c() of columnnames, use dput(). +#' @param string variables to test. Input as c() of columnnames, use dput(). #' @keywords logistic regression #' @export #' @examples #' rep_glm() -rep_glm<-function(y,v1,string,ci=FALSE,data,v2=NULL,v3=NULL){ -## x is data.frame of predictors, y is vector of an aoutcome as a factor -## output is returned as coefficient, or if or=TRUE as OR with 95 % CI. -## The confint() function is rather slow, causing the whole function to hang when including many predictors and calculating the ORs with CI. +rep_glm<-function(y,vars,string,ci=FALSE,data){ + ## x is data.frame of predictors, y is vector of an aoutcome as a factor + ## output is returned as coefficient, or if or=TRUE as OR with 95 % CI. + ## - require(broom) + require(dplyr) d<-data x<-select(d,one_of(c(string))) - m1<-length(coef(glm(y~v1,family = binomial()))) + v<-select(d,one_of(c(vars))) + dt<-cbind(y,v) + m1<-length(coef(glm(y~.,family = binomial(),data = dt))) -if (!is.factor(y)){stop("Some kind of error message would be nice, but y should be a factor!")} + if (!is.factor(y)){stop("Some kind of error message would be nice, but y should be a factor!")} - if (ci==TRUE){ + if (ci==TRUE){ - df<-data.frame(matrix(ncol = 4)) - names(df)<-c("pred","or_ci","pv","t") + df<-data.frame(matrix(ncol = 3)) + names(df)<-c("pred","or_ci","pv") - for(i in 1:ncol(x)){ - m<-glm(y~v1+x[,i],family = binomial()) + for(i in 1:ncol(x)){ - l<-suppressMessages(round(exp(confint(m))[-c(1:m1),1],2)) - u<-suppressMessages(round(exp(confint(m))[-c(1:m1),2],2)) - or<-round(exp(coef(m))[-c(1:m1)],2) + dat<-cbind(dt,x[,i]) - or_ci<-paste0(or," (",l," to ",u,")") + m<-glm(y~.,family = binomial(),data=dat) - pv<-round(tidy(m)$p.value[-c(1:m1)],3) - pv<-ifelse(pv<0.001,"<0.001",pv) + l<-suppressMessages(round(exp(confint(m))[-c(1:m1),1],2)) + u<-suppressMessages(round(exp(confint(m))[-c(1:m1),2],2)) + or<-round(exp(coef(m))[-c(1:m1)],2) - t <- ifelse(pv<=0.1|pv=="<0.001","include","drop") + or_ci<-paste0(or," (",l," to ",u,")") - pv <- ifelse(pv<=0.05|pv=="<0.001",paste0("*",pv), - ifelse(pv>0.05&pv<=0.1,paste0(".",pv),pv)) + pv<-round(tidy(m)$p.value[-c(1:m1)],3) + x1<-x[,i] - v<-x[,i] + if (is.factor(x1)){ + pred<-paste(names(x)[i],levels(x1)[-1],sep = "_") + } - if (is.factor(v)){ - pred<-paste(names(x)[i],levels(v)[-1],sep = "_") - } + else {pred<-names(x)[i]} - else {pred<-names(x)[i]} - - df<-rbind(df,cbind(pred,or_ci,pv,t)) + df<-rbind(df,cbind(pred,or_ci,pv)) }} if (ci==FALSE){ - df<-data.frame(matrix(ncol = 4)) - names(df)<-c("pred","b","pv","t") + df<-data.frame(matrix(ncol = 3)) + names(df)<-c("pred","b","pv") - for(i in 1:ncol(x)){ - m<-glm(y~v1+x[,i],family = binomial()) + for(i in 1:ncol(x)){ + dat<-cbind(dt,x[,i]) - b<-round(coef(m)[-c(1:m1)],3) + m<-glm(y~.,family = binomial(),data=dat) - pv<-round(tidy(m)$p.value[-c(1:m1)],3) - pv<-ifelse(pv<0.001,"<0.001",pv) + b<-round(coef(m)[-c(1:m1)],3) - t <- ifelse(pv<=0.1|pv=="<0.001","include","drop") + pv<-round(tidy(m)$p.value[-c(1:m1)],3) - pv <- ifelse(pv<=0.05|pv=="<0.001",paste0("*",pv), - ifelse(pv>0.05&pv<=0.1,paste0(".",pv),pv)) + x1<-x[,i] + if (is.factor(x1)){ + pred<-paste(names(x1)[i],levels(x1)[-1],sep = "_") + } - v<-x[,i] + else {pred<-names(x)[i]} - if (is.factor(v)){ - pred<-paste(names(x)[i],levels(v)[-1],sep = "_") - } + df<-rbind(df,cbind(pred,b,pv)) - else {pred<-names(x)[i]} + }} - df<-rbind(df,cbind(pred,b,pv,t)) + pa<-as.numeric(df[,3]) + pa<-ifelse(pa<0.001,"<0.001",pa) - }} - result<-df - return(df) + t <- ifelse(pa<=0.1|pa=="<0.001","include","drop") + + pa <- ifelse(pa<=0.05|pa=="<0.001",paste0("*",pa), + ifelse(pa>0.05&pa<=0.1,paste0(".",pa),pa)) + + r<-data.frame(df[,1:2],pa,t)[-1,] + + return(r) } diff --git a/man/rep_glm.Rd b/man/rep_glm.Rd index 2f5b786..291c196 100644 --- a/man/rep_glm.Rd +++ b/man/rep_glm.Rd @@ -4,15 +4,17 @@ \alias{rep_glm} \title{A repeated logistic regression function} \usage{ -rep_glm(y, v1, string, ci = FALSE, data, v2 = NULL, v3 = NULL) +rep_glm(y, vars, string, ci = FALSE, data) } \arguments{ \item{y}{Effect meassure.} -\item{v1}{Main variable in model} +\item{vars}{variables in model. Input as c() of columnnames, use dput().} + +\item{string}{variables to test. Input as c() of columnnames, use dput().} } \description{ -For bivariate analyses. +For bivariate analyses. The confint() function is rather slow, causing the whole function to hang when including many predictors and calculating the ORs with CI. } \examples{ rep_glm()