troubleshooting and fixing

This commit is contained in:
agdamsbo 2019-11-08 12:22:49 +01:00
parent 7902654ed7
commit 8326ed2cc0
50 changed files with 88 additions and 262 deletions

BIN
.DS_Store vendored

Binary file not shown.

View File

@ -2,16 +2,12 @@ Package: daDoctoR
Type: Package
Title: FUNCTIONS FOR HEALTH RESEARCH
Version: 0.1.0.9023
Author@R: c(person("Andreas", "Gammelgaard Damsbo", email = "agdamsbo@pm.me", role = c("cre", "aut")))
Author: c(person("Andreas", "Gammelgaard Damsbo", email = "agdamsbo@pm.me", role = c("cre", "aut")))
Maintainer: Andreas Gammelgaard Damsbo <agdamsbo@pm.me>
Description: I am a Danish medical doctor involved in neuropsychiatric research.
Here I have collected functions I use for my data analysis. You are very
welcome to get inspired or to use my work.
Imports: broom,
dplyr,
epiR,
ggplot2,
MASS
Imports: broom, dplyr, epiR, ggplot2, MASS
Suggest: shiny
License: GPL (>= 2)
Encoding: UTF-8

View File

@ -7,9 +7,6 @@
#' @param labels labels for all selected columns
#' @keywords factor
#' @export
#' @examples
#' col_fact()
col_fact<-function(string,data,levels=NULL,labels=NULL){
## Defining factors for columns containing string (can be vector of multiple strings), based on dplyr.

View File

@ -5,8 +5,6 @@
#' @param data Dataframe
#' @keywords numeric
#' @export
#' @examples
#' col_num()
col_num<-function(string,data){
## Defining factors for columns containing string (can be vector of multiple strings), based on dplyr

View File

@ -3,12 +3,9 @@
#' Should be combined with "rep_olr()". The confint() function is rather slow, causing the whole function to hang when including many predictors and calculating the ORs with CI.
#' @param meas primary outcome (factor with >2 levels).
#' @param vars variables in model. Input as c() of columnnames, use dput().
#' @param dta data frame to pull variables from.
#' @param data data frame to pull variables from.
#' @keywords olr
#' @export
#' @examples
#' comb_olr()
comb_olr<-function(meas,vars,data){
require(MASS)

View File

@ -4,8 +4,6 @@
#' @param x data as as dd/mm/yyyy.
#' @keywords date
#' @export
#' @examples
#' date_convert()
date_convert<-function(x)
## Input format as dd/mm/yyyy, output is standard yyyy-mm-dd

View File

@ -5,13 +5,11 @@
#' @param y Allele 2.
#' @keywords hardy-weinberg-equllibrium
#' @export
#' @examples
#' hwe_allele()
hwe_allele<-function(x,y)
{
## Witten by Andreas Gammelgaard Damsbo, agdamsbo@pm.me, based on a non-working
## applet at from http://www.husdyr.kvl.dk/htm/kc/popgen/genetik/applets/kitest.htm
## applet at http://www.husdyr.kvl.dk/htm/kc/popgen/genetik/applets/kitest.htm
all<-pmax(length(levels(factor(x))),length(levels(factor(y))))

View File

@ -3,6 +3,7 @@
#' App to easily calculate and visualize the HWE.
#'
#' @export
hwe_app <- function() {
appDir <- system.file("shiny-examples", "hwe_calc", package = "daDoctoR")
if (appDir == "") {

View File

@ -4,8 +4,6 @@
#' @param mm First count of genotype.
#' @keywords hardy-weinberg-equllibrium
#' @export
#' @examples
#' hwe_geno()
hwe_geno<-function(mm,mn,nn,mo,no,oo,alleles=2)
{

View File

@ -6,8 +6,6 @@
#' @param f factor for grouping.
#' @keywords hardy-weinberg-equllibrium
#' @export
#' @examples
#' hwe_sum()
hwe_sum<-function (a1, a2, f) {
require(daDoctoR)

View File

@ -11,8 +11,6 @@
#' @param input can be either "model", which is a olr model (polr()), or "df", which is a dataframe whith three columns for OR, lower CI and upper CI-
#' @keywords forestplot
#' @export
#' @examples
#' plot_ord_odds()
plot_ord_odds<-function(x, title = NULL,dec=3,lbls=NULL,hori="OR (95 % CI)",vert="Variables",short=FALSE,input="model"){

View File

@ -9,8 +9,6 @@
#' @param logistic flag for logistic binomial regression or not (linear is then selected).
#' @keywords logistic regression
#' @export
#' @examples
#' rep_biv()
rep_biv<-function(y,v1,string,data,method="pval",logistic=FALSE,ci=FALSE,cut=0.1,v2=NULL,v3=NULL){

View File

@ -7,9 +7,6 @@
#' @param data dataframe to draw variables from.
#' @keywords ppv npv sensitivity specificity
#' @export
#' @examples
#' rep_epi_tests()
rep_epi_tests<-function(gold,test,data){
require(epiR)

View File

@ -5,20 +5,19 @@
#' @param vars variables in model. Input as c() of columnnames, use dput().
#' @param string variables to test. Input as c() of columnnames, use dput().
#' @param ci flag to get results as OR with 95% confidence interval.
#' @param data data frame to pull variables from.
#' @param data dataframe to pull variables from.
#' @param fixed.var flag to set "vars" as fixed in the model. When FALSE, then true bivariate logistic regression is performed.
#' @keywords logistic
#' @export
#' @examples
#' rep_glm()
rep_glm<-function(meas,vars=NULL,string,ci=FALSE,data,fixed.var=FALSE){
rep_glm<-function(meas,vars=NULL,string,ci=FALSE,data,fixed.var=FALSE)
{
## Intro and definitions
require(broom)
y<-data[,c(meas)]
## Factor check
if(!is.factor(y)){stop("y is not a factor")}
## Running "true" bivariate analysis
if (fixed.var==FALSE){
d<-data
x<-data.frame(d[,c(vars,string)])
@ -85,7 +84,7 @@ rep_glm<-function(meas,vars=NULL,string,ci=FALSE,data,fixed.var=FALSE){
r<-data.frame(df[,1:2],pa,t)[-1,]
}
## Running multivariate analyses (eg "bivariate" analyses with fixed variables)
if (fixed.var==TRUE){
d<-data
x<-data.frame(d[,c(string)])

View File

@ -5,12 +5,10 @@
#' @param vars variables in model. Input as c() of columnnames, use dput().
#' @param string variables to test. Input as c() of columnnames, use dput().
#' @param ci flag to get results as OR with 95% confidence interval.
#' @param fixed.var flag to set "vars" as fixed in the model. When FALSE, then true bivariate linear regression is performed.
#' @param data data frame to pull variables from.
#' @keywords linear
#' @param fixed.var flag to set "vars" as fixed in the model. When FALSE, then true bivariate linear regression is performed.
#' @keywords linear regression
#' @export
#' @examples
#' rep_lm()
rep_lm<-function(meas,vars=NULL,string,ci=FALSE,data,fixed.var=FALSE){

View File

@ -5,12 +5,9 @@
#' @param vars variables in model. Input as c() of columnnames, use dput().
#' @param string variables to test. Input as c() of columnnames, use dput().
#' @param ci flag to get results as OR with 95% confidence interval.
#' @param dta data frame to pull variables from.
#' @param data data frame to pull variables from.
#' @keywords olr
#' @export
#' @examples
#' rep_olr()
rep_olr<-function(meas,vars,string,ci=FALSE,data){

View File

@ -6,9 +6,6 @@
#' @param dta data frame to pull variables from.
#' @keywords olr
#' @export
#' @examples
#' rep_olr_sngl()
rep_olr_sngl<-function(meas,vars,data){
require(MASS)

View File

@ -9,8 +9,6 @@
#' @param cut cut value for gating if including or dropping the tested variable. As suggested bu S. Greenland (1989).
#' @keywords estimate-in-estimate
#' @export
#' @examples
#' rep_reg_cie()
rep_reg_cie<-function(meas,vars,string,data,cut=0.1){

View File

@ -9,8 +9,6 @@
#' @param dec decimals for results, standard is set to 2. Mean and sd is dec-1. pval has 3 decimals.
#' @keywords strobe
#' @export
#' @examples
#' strobe_diff_bygroup()
strobe_diff_bygroup<-function(meas,var,group,adj,data,dec=2){

View File

@ -9,8 +9,6 @@
#' @param dec decimals for results, standard is set to 2. Mean and sd is dec-1.
#' @keywords strobe
#' @export
#' @examples
#' strobe_diff_byvar()
strobe_diff_byvar<-function(meas,var,group,adj,data,dec=2){

View File

@ -8,8 +8,6 @@
#' @param dec decimals for results, standard is set to 2. Mean and sd is dec-1.
#' @keywords strobe
#' @export
#' @examples
#' strobe_diff_twodim()
strobe_diff_twodim<-function(meas,group,adj,data,dec=2){
## meas: sdmt

View File

@ -8,8 +8,6 @@
#' @param dec decimals for results, standard is set to 2. Mean and sd is dec-1.
#' @keywords logistic
#' @export
#' @examples
#' strobe_log()
strobe_log<-function(meas,var,adj,data,dec=2){
## Ønskeliste:

View File

@ -7,8 +7,6 @@
#' @param dec decimals for results, standard is set to 2. Mean and sd is dec-1.
#' @keywords olr
#' @export
#' @examples
#' strobe_olr()
strobe_olr<-function(meas,vars,data,dec=2){

View File

@ -8,8 +8,6 @@
#' @param n.by.adj flag to indicate wether to count number of patients in adjusted model or overall for outcome meassure not NA.
#' @keywords logistic
#' @export
#' @examples
#' strobe_pred()
strobe_pred<-function(meas,adj,data,dec=2,n.by.adj=FALSE){
## Ønskeliste:

View File

@ -19,3 +19,4 @@ BuildType: Package
PackageUseDevtools: Yes
PackageInstallArgs: --no-multiarch --with-keep.source
PackageCheckArgs: --as-cran
PackageRoxygenize: rd,collate,namespace,vignette

View File

@ -18,7 +18,4 @@ col_fact(string, data, levels = NULL, labels = NULL)
\description{
Depending on dply's contains()-function.
}
\examples{
col_fact()
}
\keyword{factor}

View File

@ -14,7 +14,4 @@ col_num(string, data)
\description{
Depending on dply's contains()-function.
}
\examples{
col_num()
}
\keyword{numeric}

View File

@ -11,12 +11,9 @@ comb_olr(meas, vars, data)
\item{vars}{variables in model. Input as c() of columnnames, use dput().}
\item{dta}{data frame to pull variables from.}
\item{data}{data frame to pull variables from.}
}
\description{
Should be combined with "rep_olr()". The confint() function is rather slow, causing the whole function to hang when including many predictors and calculating the ORs with CI.
}
\examples{
comb_olr()
}
\keyword{olr}

View File

@ -12,7 +12,4 @@ date_convert(x)
\description{
Input format as dd/mm/yyyy, output is standard yyyy-mm-dd
}
\examples{
date_convert()
}
\keyword{date}

View File

@ -14,7 +14,4 @@ hwe_allele(x, y)
\description{
For easy calculation.
}
\examples{
hwe_allele()
}
\keyword{hardy-weinberg-equllibrium}

View File

@ -12,7 +12,4 @@ hwe_geno(mm, mn, nn, mo, no, oo, alleles = 2)
\description{
For easy calculation.
}
\examples{
hwe_geno()
}
\keyword{hardy-weinberg-equllibrium}

View File

@ -16,7 +16,4 @@ hwe_sum(a1, a2, f)
\description{
For easy printing.
}
\examples{
hwe_sum()
}
\keyword{hardy-weinberg-equllibrium}

View File

@ -28,7 +28,4 @@ plot_ord_odds(x, title = NULL, dec = 3, lbls = NULL,
\description{
Heavily inspired by https://www.r-bloggers.com/plotting-odds-ratios-aka-a-forrestplot-with-ggplot2/
}
\examples{
plot_ord_odds()
}
\keyword{forestplot}

View File

@ -23,8 +23,5 @@ rep_biv(y, v1, string, data, method = "pval", logistic = FALSE,
\description{
For bivariate analyses, for gating by p-value or change-in-estimate.
}
\examples{
rep_biv()
}
\keyword{logistic}
\keyword{regression}

View File

@ -19,9 +19,6 @@ For bivariate analyses. The confint() function is rather slow, causing the whole
\details{
Repeats the epi.tests from the epiR package. Either gs or test should be of length 1.
}
\examples{
rep_epi_tests()
}
\keyword{npv}
\keyword{ppv}
\keyword{sensitivity}

View File

@ -16,14 +16,11 @@ rep_glm(meas, vars = NULL, string, ci = FALSE, data,
\item{ci}{flag to get results as OR with 95% confidence interval.}
\item{data}{data frame to pull variables from.}
\item{data}{dataframe to pull variables from.}
\item{fixed.var}{flag to set "vars" as fixed in the model. When FALSE, then true bivariate logistic regression is performed.}
}
\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.
}
\examples{
rep_glm()
}
\keyword{logistic}

View File

@ -23,7 +23,5 @@ rep_lm(meas, vars = NULL, string, ci = FALSE, data,
\description{
For bivariate analyses, to determine which variables to include in adjusted model.
}
\examples{
rep_lm()
}
\keyword{linear}
\keyword{regression}

View File

@ -15,12 +15,9 @@ rep_olr(meas, vars, string, ci = FALSE, data)
\item{ci}{flag to get results as OR with 95% confidence interval.}
\item{dta}{data frame to pull variables from.}
\item{data}{data frame to pull variables from.}
}
\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.
}
\examples{
rep_olr()
}
\keyword{olr}

View File

@ -16,7 +16,4 @@ rep_olr_sngl(meas, vars, data)
\description{
Should be combined with "rep_olr()". 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_olr_sngl()
}
\keyword{olr}

View File

@ -22,7 +22,4 @@ rep_reg_cie(meas, vars, string, data, cut = 0.1)
\description{
For bivariate analyses, binary logistic or linear regression. From "Modeling and variable selection in epidemiologic analysis." - S. Greenland, 1989.
}
\examples{
rep_reg_cie()
}
\keyword{estimate-in-estimate}

View File

@ -22,7 +22,4 @@ strobe_diff_bygroup(meas, var, group, adj, data, dec = 2)
\description{
Printable table of three dimensional regression analysis of group vs var for meas. By group.
}
\examples{
strobe_diff_bygroup()
}
\keyword{strobe}

View File

@ -22,7 +22,4 @@ strobe_diff_byvar(meas, var, group, adj, data, dec = 2)
\description{
Printable table of three dimensional regression analysis of group vs var for meas. By var. Includes p-values.
}
\examples{
strobe_diff_byvar()
}
\keyword{strobe}

View File

@ -20,7 +20,4 @@ strobe_diff_twodim(meas, group, adj, data, dec = 2)
\description{
Printable table of regression analysis by group for meas. Detects wether to perform logistic or linear regression.
}
\examples{
strobe_diff_twodim()
}
\keyword{strobe}

View File

@ -20,7 +20,4 @@ strobe_log(meas, var, adj, data, dec = 2)
\description{
Printable table of logistic regression analysis according to STROBE.
}
\examples{
strobe_log()
}
\keyword{logistic}

View File

@ -18,7 +18,4 @@ strobe_olr(meas, vars, data, dec = 2)
\description{
Printable table of logistic regression analysis oaccording to STROBE.
}
\examples{
strobe_olr()
}
\keyword{olr}

View File

@ -20,7 +20,4 @@ strobe_pred(meas, adj, data, dec = 2, n.by.adj = FALSE)
\description{
Printable table of logistic regression analysis according to STROBE.
}
\examples{
strobe_pred()
}
\keyword{logistic}

View File

@ -1,13 +0,0 @@
library(roxygen2)
library(devtools)
source("/Users/andreas/Documents/GitHub/daDoctoR/updatePackageVersion.R")
setwd("/Users/andreas/Documents/GitHub/daDoctoR")
updatePackageVersion()
document()
# Inspiration: "https://hilaryparker.com/2014/04/29/writing-an-r-package-from-scratch/"

View File

@ -1,3 +0,0 @@
## Looking for errors in code
for (f in list.files("/Users/andreas/Documents/GitHub/daDoctoR/R", full.names=TRUE)) parse(f)

View File

@ -1,13 +0,0 @@
# Install new version
# Remove
remove.packages("daDoctoR")
.rs.restartR()
setwd("/")
devtools::install_github('agdamsbo/daDoctoR')
library(daDoctoR)

View File

@ -1,35 +0,0 @@
updatePackageVersion <- function(packageLocation ="."){
## Seen at: https://www.mango-solutions.com/blog/how-to-auto-update-a-package-version-number
## Read DESCRIPTION file
desc <- readLines(file.path(packageLocation, "DESCRIPTION"))
## Find the line where the version is defined
vLine <- grep("^Version\\:", desc)
## Extract version number
vNumber <- gsub("^Version\\:\\s*", "", desc[vLine])
## Split the version number into two; a piece to keep, a piece to increment
versionNumber <- strsplit(vNumber, "\\.")[[1]]
versionParts <- length(versionNumber)
vNumberKeep <- paste(versionNumber[1:(versionParts-1)], sep= "", collapse= ".")
vNumberUpdate <- versionNumber[versionParts]
## Replace old version number with new one (increment by 1)
oldVersion <- as.numeric(vNumberUpdate)
newVersion <- oldVersion + 1
## Build final version number
vFinal <- paste(vNumberKeep, newVersion, sep = ".")
## Update DESCRIPTION file (in R)
desc[vLine] <- paste0("Version: ", vFinal )
## Update the actual DESCRIPTION file
writeLines(desc, file.path(packageLocation, "DESCRIPTION"))
## Return the updated version number to screen
return(vFinal)
}