/*Program to estimate power for interaction effects by simulation*/ /*v1.0.0 05 Apr 2014*/ /*v1.0.1 14 Apr 2014: add missing data mechanisms*/ /*v1.0.2 16 Apr 2014: add mi impute and mi estimate approaches*/ /*v1.0.3 17 Apr 2014: make continuous exposure acceptable*/ /*v1.0.4 20 Apr 2014: allow random-effects covariance matrix*/ /*v1.0.5 25 Apr 2014: changed distribution of higher unit size from uniform to Poisson added option for cluster randomisation added option for higher level units to be as close as possible as an alternative to Poisson distribution*/ /*v1.0.6 30 Apr 2014: added expanded outputs for the outcome, as feedbacks to help users adjust input betas if needed*/ /*v1.1.0 25 Feb 2015: debugged covariance matrix issue beautified outputs*/ /*v1.1.1 27 May 2016: seed number is not set automatically any more*/ /*v1.2.0 02 Aug 2017: added high-level variability in distribution of binary covariate*/ program define ipdpower, rclass /*stata version define*/ version 12.1 /*command syntax*/ syntax, sn(integer) ssl(integer) ssh(integer) b0(real) b1(real) b2(real) b3(real) [minsh(integer 50) hpoisson icluster outc(string) cb(real 0.5) cexp cexpd(string) errsd(real 1) /* */ sderrsd(real 0) derr(string) bcov bcb(real 0.5) bsd(real 0) ccovd(string) slcov model(integer 1) tsq0(real 0) tsq1(real 0) tsq2(real 0) tsq3(real 0) dtp0(string) /* */ dtp1(string) dtp2(string) dtp3(string) covmat(name) missp(real -127.77) mar(real -127.77) mnar(real -127.77) minum(integer -127) mipmm(integer -127) /* */ clvl(real 95) seed(integer -127) nskip dnorm xnodts NODIsplay moreon] /*INPUTS-model*/ /*mandatory*/ /*number of simulations*/ scalar simnum=`sn' /*total size of cases (patients)*/ scalar totalsize=`ssl' /*number of studies*/ scalar studynum=`ssh' /*minimum size of study*/ scalar minsize=`minsh' scalar meansize=totalsize/studynum /*issue errors*/ if "`hpoisson'"=="" { if meansize=1 { di as error "Probability for cases must be in the (0,1) range" error 197 } scalar caseprob=`cb' /*continuous exposure*/ scalar binexp=1 if "`cexp'"!="" { if `cb'!=0.5 { di as error "Option cb(#), probability for exposure, cannot be used when exposure is defined as continuous" error 197 } scalar binexp=0 /*exposure mean and sd - fixed to standardised*/ scalar expmn=0 scalar expsd=1 } else { /*distribution for covariate*/ if "`cexpd'"!="" { di as error "Option cexpd(), distribution for exposure, cannot be used when exposure is defined as dichotomous" error 197 } } /*distribution for exposure*/ if "`cexpd'"=="" { scalar distexp=0 } else { if inlist("`cexpd'","norm","sknorm","xsknorm")==0 { di as error "Distribution of exposure:" di as error _col(2) "'cexpd(norm)': default, normal distribution" di as error _col(2) "'cexpd(sknorm)': moderate skew (sk=1, ku=4)" di as error _col(2) "'cexpd(xsknorm)': extreme skew (sk=2, ku=9)" error 197 } if "`cexpd'"=="norm" { scalar distexp=0 } else if "`cexpd'"=="sknorm" { scalar distexp=1 } else if "`cexpd'"=="xsknorm" { scalar distexp=2 } } /*type of outcome: default "cont"(linear)=0, "binr"(logit)=1, "count"(poisson)=2*/ if "`outc'"=="" { scalar outtp=0 } else { if inlist("`outc'","cont","binr","count")==0 { di as error "Outcome can be continuous (outc(cont) - default), binary (outc(binr)) or count data (outc(count))" error 197 } else { if "`outc'"=="cont" { scalar outtp=0 } else if "`outc'"=="binr" { scalar outtp=1 } else if "`outc'"=="count" { scalar outtp=2 } } } /*error variance - only for continuous outcome*/ if ((`errsd'!=1 | `sderrsd'!=0) & outtp!=0) | `errsd'<=0 | `sderrsd'<0 { di as error "Error SD can only be set when the outcome is continuous and errsd>0, sderrsd>=0" error 197 } if outtp==0 { /*Variance of the error terms - affects model fit (R^2) and potentially outcome distribution (i.e. very high outcome skew needs large skewed errors)*/ scalar mnsd=`errsd' scalar cdsd=`sderrsd' /*cannot be zero in the code but user might want a zero value*/ if cdsd==0 scalar cdsd=10^-20 } else { scalar mnsd=. scalar cdsd=. } /*model type 1=regress/logit 2=xtreg/xtlogit 3+=xtmixed/xtmelogit*/ if inlist(`model',1,2,3,4,5,6,7)==0 { di as error "Model choice needs to be an integer in the 1-7 range:" di as error _col(2) "1: standard regression (regress/logit/poisson)" di as error _col(2) "2: random effects regression, for study i.e. intercept (xtreg/xtlogit/xtpoisson)" di as error _col(2) "3: fixed common intercept; random treatment effect; fixed effect for baseline (xtmixed/xtmelogit/xtmepoisson)" di as error _col(2) "4: fixed study specific intercepts; random treatment effect; fixed study specific effect for baseline" di as error _col(2) "5: random study intercept; random treatment effect; fixed study specific effect for baseline" di as error _col(2) "6: random study intercept; random treatment effect; random effect for baseline" di as error _col(2) "7: random study intercept; random treatment effect; random effect for baseline; random effect for interaction" error 197 } scalar modtp=`model' /*if outcome binary/count and xtlogit/xtpoisson allow noskip option for returning pseudo-R^2 although computationally heavier*/ if "`nskip'"!="" & (outtp==0 | modtp!=2){ di as error "Option 'nskip' can only be used with a binary/count outcome and xtlogit/xtpoisson (model=2):" di as error _col(2) "allows the 'noskip' option in regression for returning pseudo-R^2 but is computationally heavier" error 197 } if "`nskip'"=="" { scalar nskip=0 } else { scalar nskip=1 } /*if outcome count and xtpoisson allow estimation to vary assumption about random effect (gamma=default - normal)*/ /*if gamma options chosen then better use skewed distributions that are similar to gamma*/ if "`dnorm'"!="" & (outtp!=2 | modtp!=2){ di as error "Option 'dnorm' can only be used with a count outcome and xtpoisson (model=2):" di as error _col(2) "allows estimation to assume random-effects normally distributed (gamma=default)" error 197 } if "`dnorm'"=="" { scalar redist=0 } else { scalar redist=1 } /*INPUT-parameters*/ /*betas*/ scalar b0=`b0' scalar b1=`b1' scalar b2=`b2' scalar b3=`b3' /*heterogeneity*/ forvalues i=0(1)3 { if `tsq`i''<0 { di as error "Between-study variance cannot be negative (tsq`i')" error 197 } } scalar tausq0=`tsq0' /*intercept*/ scalar tausq1=`tsq1' /*grp*/ scalar tausq2=`tsq2' /*covariate*/ scalar tausq3=`tsq3' /*grp*covariate*/ /*distribution of random effects info: normal ("norm" - default), moderate skew ("sknorm"), extreme skew ("xsknorm")*/ forvalues i=0(1)3 { //distribution of RE if "`dtp`i''"=="" { scalar dtype`i'=0 } else { if inlist("`dtp`i''","norm","sknorm","xsknorm")==0 { di as error "Distribution for random effects can be:" di as error _col(2) "'dtp`i'(norm)': default, normal distribution" di as error _col(2) "'dtp`i'(sknorm)': moderate skew (sk=1, ku=4)" di as error _col(2) "'dtp`i'(xsknorm)': extreme skew (sk=2, ku=9)" error 197 } if "`dtp`i''"=="norm" { scalar dtype`i'=0 } else if "`dtp`i''"=="sknorm" { scalar dtype`i'=1 } else if "`dtp`i''"=="xsknorm" { scalar dtype`i'=2 } } //heterogeneity if tausq`i'==0 & dtype`i'>0 { di as error "Distribution for random-effects can only be defined if random-effects assumed, with tausq`i'>0" error 197 } } /*distribution for errors (and hence outcome) - continuous only*/ if "`derr'"=="" { scalar dtype4=0 } else { if inlist("`derr'","norm","sknorm","xsknorm")==0 { di as error "Distribution for errors:" di as error _col(2) "'derr(norm)': default, normal distribution" di as error _col(2) "'derr(sknorm)': moderate skew (sk=1, ku=4)" di as error _col(2) "'derr(xsknorm)': extreme skew (sk=2, ku=9)" error 197 } if outtp!=0 & inlist("`derr'","sknorm","xsknorm")>0 { di as error "Distribution of the errors (and hence outcome) can only be managed if the outcome is continuous" error 197 } if "`derr'"=="norm" { scalar dtype4=0 } else if "`derr'"=="sknorm" { scalar dtype4=1 } else if "`derr'"=="xsknorm" { scalar dtype4=2 } } /*allow covariance matrix for random effects as an alternative - can't have both*/ scalar xcovmt=0 if "`covmat'"!="" { scalar xcovmt=1 foreach x in tausq0 tausq1 tausq2 tausq3 { if `x'>0 { di as error "Either a random-effects covariance matrix can be provided or random-effects using" di as error "tausq0-tausq3 (their distributions using dtp0-dtp3) - not both." error 197 } } /*make sure input is matrix*/ capture confirm matrix `covmat' if _rc!=0 { di as error "Covariance matrix `covmat' not defined" error 197 } /*make sure it is 4x4*/ scalar terr2=0 if rowsof(`covmat')!=4 | colsof(`covmat')!=4 { scalar terr2=1 } /*make sure no negatives*/ scalar terr3=0 scalar mincell=0 forvalues i=1(1)4 { forvalues j=1(1)4 { if `covmat'[`i',`j']1 then power calculations return very high power*/ scalar covmn=0 scalar covsd=1 /*not needed*/ scalar covprob=. scalar sdcovpb=. } /*binary covariate*/ else { scalar cncov=0 /*probability for the covariate*/ if `bcb'<=0 | `bcb'>=1 { di as error "Probability for the binary covariate needs to be in the (0,1) range" error 197 } scalar covprob=`bcb' /*varying probability across higher units*/ if `bsd'<0 { di as error "SD for probability for the binary covariate needs to be positive" error 197 } scalar sdcovpb=`bsd' /*not needed*/ scalar dtype5=. scalar covmn=. scalar covsd=. } /*study-level covariate (yes=1)*/ if "`slcov'"=="" { scalar slcov=0 } else { scalar slcov=1 } /*missing data assumptions*/ /*make sure percentage of missing given, if mechanism is defined*/ if `missp'==-127.77 & (`mar'!=-127.77 | `mnar'!=-127.77) { di as error "You need to define percentage of missing values with option missp() if you are to have a missing-data mechanism" error 197 } /*can't have both mar and mnar*/ if `mar'!=-127.77 & `mnar'!=-127.77 { di as error "You can define either MAR or NMAR, not both" error 197 } scalar usemiss=0 if `missp'!=-127.77 { /*assume MCAR*/ scalar usemiss=1 if `missp'<=0 | `missp'>=1 { di as error "Percentage of missing values needs to be in the (0,1) range. e.g. missp(0.2)" error 197 } /*assume MAR*/ if `mar'!=-127.77 { if `mar'<=0 { di as error "Odds ratio for MAR mechanism for covariate (1 implies MCAR and should be avoided)" error 197 } scalar usemiss=2 } /*assume NMAR*/ if `mnar'!=-127.77 { if `mnar'<=0 { di as error "Odds ratio for NMAR mechanism for covariate (1 implies MCAR and should be avoided)" error 197 } scalar usemiss=3 } } /*multiple imputation analyses - set number of imputations within each dataset*/ scalar numimp=0 if `minum'!=-127 { /*need missing data to run mi analyses*/ if usemiss==0 { di as error "Analyses using mi commands cannot be run without a missing data mechanism" error 197 } if `minum'<2 { di as error "Number of imputed datasets needs to be at least two: minum(k) needs k>=2" error 197 } scalar numimp=`minum' } /*pmm option for multiple imputation - only for continuous outcome*/ scalar pmm=0 if `mipmm'!=-127 { /*choice only for continuous outcome*/ if `outc'>0 { di as error "Option mipmm() can only be used for a continuous outcome" error 197 } /*need missing data to run mi analyses*/ if usemiss==0 | numimp==0 { di as error "Analyses using mi commands cannot be run without a missing data mechanism" di as error "minum(#) needs to also be used, to define a mi analysis" error 197 } if `mipmm'<1 { di as error "# of closest observations (nearest neighbors) to draw from in predictive mean matching imputation" di as error "mipmm(k) needs k>=1" error 197 } scalar pmm=`mipmm' } /*HETEROGENEITY*/ scalar poolwithinvar = . /*pooled within study variance calculations*/ /*continuous outcome*/ if outtp==0 { /*pool within variance across studies - using the true mean value rather than an estimate i.e. modelling using how much heterogeneity there should be not how much you measure in your dataset*/ scalar poolwithinvar = mnsd^2 } /*MAIN BIT*/ /*not using matrices for results to avoid the IC limit of 400*/ forvalues i=1(1)18 { scalar c`i'=0 } forvalues i=0(1)3 { scalar powb`i'=0 scalar covb`i'=0 } forvalues i=0(1)1 { scalar perc`i'=0 scalar mean`i'=0 scalar sd`i'=0 } /*loop number of simulations*/ timer on 99 scalar cntr=0 forvalues i=1(1)`=simnum' { /*get basics*/ if binexp==1 { /*binary exposure*/ studybasics1 `=totalsize' `=studynum' `=minsize' `=caseprob' `=hlpos' `=iclus' } else { /*continuous exposure*/ studybasics2 `=totalsize' `=studynum' `=minsize' `=distexp' `=expmn' `=expsd' `=hlpos' } /*call data generation*/ modout1 `=b0' `=b1' `=b2' `=b3' `=poolwithinvar' `=cdsd' `=tausq0' `=tausq1' `=tausq2' `=tausq3' /* */ `=dtype0' `=dtype1' `=dtype2' `=dtype3' `=slcov' `=totalsize' `=dtype4' /* */ `=dtype5' `=covmn' `=covsd' `=covprob' `=outtp' `=xcovmt' `=binexp' `=sdcovpb' /*get some characteristics for the outcome*/ if binexp==1 { /*binary exposure and binary outcome*/ if outtp==1 { scalar perc0=perc0+r(perc0)/simnum scalar perc1=perc1+r(perc1)/simnum } /*binary exposure and continuous or count outcome*/ else { scalar mean0=mean0+r(mean0)/simnum scalar sd0=sd0+r(sd0)/simnum scalar mean1=mean1+r(mean1)/simnum scalar sd1=sd1+r(sd1)/simnum } } else { /*continuous exposure and binary outcome*/ if outtp==1 { scalar perc0=perc0+r(perc0)/simnum } /*continuous exposure and continuous or count outcome*/ else { scalar mean0=mean0+r(mean0)/simnum scalar sd0=sd0+r(sd0)/simnum } } /*call missing data mechanisms*/ /*MCAR*/ if usemiss==1 { mcarprg `missp' } else if usemiss==2 { marprg `missp' `mar' } else if usemiss==3 { mnarprg `missp' `mnar' } /*call modelling*/ //nobreak { /*if no multiple imputation*/ if numimp==0 { model`=modtp' `=outtp' `=cncov' `=nskip' `=redist' `=binexp' } /*mi*/ else { model`=modtp'mi `=outtp' `=cncov' `=nskip' `=redist' `=numimp' `=pmm' `=binexp' } //} /*if successful convergence - for basic models there's no question*/ if r(conv)==1 { /*mean coefficients*/ foreach x of numlist 1 4 7 10 13/18 { scalar c`x' = c`x'+r(tc`x') } /*POWER - but only when the observed effect has the same direction as the in model*/ /*intervention effect (main)*/ if r(tc3)<=(100-clvl)/100 & r(tc1)*b1>0 { scalar powb1=powb1+1 } /*covariate effect (main)*/ if r(tc6)<=(100-clvl)/100 & r(tc4)*b2>0 { scalar powb2=powb2+1 } /*interaction effect*/ if r(tc9)<=(100-clvl)/100 & r(tc7)*b3>0 { scalar powb3=powb3+1 } /*intercept*/ if r(tc12)<=(100-clvl)/100 & r(tc10)*b0>0 { scalar powb0=powb0+1 } /*COVERAGE*/ /*intervention effect (main)*/ if (r(tc1)-invnormal(`=1-(1-clvl/100)/2')*r(tc2))<=b1 & b1<=(r(tc1)+invnormal(`=1-(1-clvl/100)/2')*r(tc2)){ scalar covb1=covb1+1 } /*covariate effect (main)*/ if (r(tc4)-invnormal(`=1-(1-clvl/100)/2')*r(tc5))<=b2 & b2<=(r(tc4)+invnormal(`=1-(1-clvl/100)/2')*r(tc5)){ scalar covb2=covb2+1 } /*interaction effect*/ if (r(tc7)-invnormal(`=1-(1-clvl/100)/2')*r(tc8))<=b3 & b3<=(r(tc7)+invnormal(`=1-(1-clvl/100)/2')*r(tc8)){ scalar covb3=covb3+1 } /*intercept*/ if (r(tc10)-invnormal(`=1-(1-clvl/100)/2')*r(tc11))<=b0 & b0<=(r(tc10)+invnormal(`=1-(1-clvl/100)/2')*r(tc11)){ scalar covb0=covb0+1 } /*overall counter*/ scalar cntr=cntr+1 } /*display progress*/ if didots==1 { if r(conv)==1 { di "." _continue } else { di "x" _continue } if mod(`i',50)==0 { di "`i'" } else if `i'==simnum { di "`i'" } } } timer off 99 qui timer list 99 scalar tmin = r(t1)/60 /*calculations*/ forvalues i=0(1)3 { /*power*/ qui cii cntr powb`i' scalar lpowb`i'=100*r(lb) scalar upowb`i'=100*r(ub) scalar powb`i'= 100*powb`i'/cntr /*coverage*/ qui cii cntr covb`i' scalar lcovb`i'=100*r(lb) scalar ucovb`i'=100*r(ub) scalar covb`i'= 100*covb`i'/cntr } /*if covariate not calculated set everything to missing*/ if c4==. { foreach x in lpowb2 upowb2 powb2 lcovb2 ucovb2 covb2 { scalar `x'=. } } if c10==. { foreach x in lpowb0 upowb0 powb0 lcovb0 ucovb0 covb0 { scalar `x'=. } } /*display outputs*/ if dioutp==1 { scalar maxstr1=10 scalar maxstr2=25 scalar maxstr3=15 //model information local mdlstr1 "1: standard regression" local mdlstr2 "2: random effects regression, for study i.e. intercept" local mdlstr3 "3: fixed common intercept; random treatment effect; fixed effect for baseline" local mdlstr4 "4: fixed study specific intercepts; random treatment effect; fixed study specific effect for baseline" local mdlstr5 "5: random study intercept; random treatment effect; fixed study specific effect for baseline" local mdlstr6 "6: random study intercept; random treatment effect; random effect for baseline" local mdlstr7 "7: random study intercept; random treatment effect; random effect for baseline; random effect for interaction" di _newline(2) as text "model " "`mdlstr`=modtp''" local outstr0 "continuous" local outstr1 "binary" local outstr2 "count" di as text "outcome type:" _col(17) as result "`outstr`=outtp''" local expstr0 "continuous" local expstr1 "binary" di as text "exposure type:" _col(17) as result "`expstr`=binexp''" local covstr0 "binary" local covstr1 "continuous" di as text "covariate type:" _col(17) as result "`covstr`=cncov''" di as text "random seed number:" _col(27) as result %6.0f `seed' di as text "number of converging runs:" _col(27) as result %6.0f `=cntr' di as text "computational time (min):" _col(28) as result %5.1f `=tmin' //characteristics for the outcome di _newline as text "Characteristics for the outcome" if binexp==1 { /*binary exposure and binary outcome*/ if outtp==1 { //di as result _col(3) "%(grp=0):" _col(25) %5.2f `=perc0*100' //di as result _col(3) "%(grp=1):" _col(25) %5.2f `=perc1*100' di as text "{hline `=maxstr1+1'}{c TT}{hline `=maxstr1+15'}" di as text "{col `=maxstr1+2'}{c |}{col `=maxstr1+6'}group0{col `=maxstr1+17'}group1 di as text "{hline `=maxstr1+1'}{c +}{hline `=maxstr1+15'}" di as text "perc(%)" "{col `=maxstr1+2'}{c |}" as result _col(`=maxstr1+5') %7.3f `=perc0*100' _col(`=maxstr1+16') %7.3f `=perc1*100' di as text "{hline `=maxstr1+1'}{c BT}{hline `=maxstr1+15'}" } /*binary exposure and continuous or count outcome*/ else { //di as result _col(3) "mean(grp=0):" _col(25) %5.3f `=mean0' //di as result _col(3) "sd(grp=0):" _col(25) %5.3f `=sd0' //di as result _col(3) "mean(grp=1):" _col(25) %5.3f `=mean1' //di as result _col(3) "sd(grp=1):" _col(25) %5.3f `=sd1' di as text "{hline `=maxstr1+1'}{c TT}{hline `=maxstr1+15'}" di as text "{col `=maxstr1+2'}{c |}{col `=maxstr1+6'}group0{col `=maxstr1+17'}group1 di as text "{hline `=maxstr1+1'}{c +}{hline `=maxstr1+15'}" di as text "mean" "{col `=maxstr1+2'}{c |}" as result _col(`=maxstr1+5') %7.3f `=mean0' _col(`=maxstr1+16') %7.3f `=mean1' di as text "sd" "{col `=maxstr1+2'}{c |}" as result _col(`=maxstr1+5') %7.3f `=sd0' _col(`=maxstr1+16') %7.3f `=sd1' di as text "{hline `=maxstr1+1'}{c BT}{hline `=maxstr1+15'}" } } else { /*continuous exposure and binary outcome*/ if outtp==1 { //di as result _col(3) "%(overall):" _col(25) %5.1f `=perc0*100' di as text "{hline `=maxstr1+1'}{c TT}{hline `=maxstr1+5'}" di as text "{col `=maxstr1+2'}{c |}{col `=maxstr1+6'}overall di as text "{hline `=maxstr1+1'}{c +}{hline `=maxstr1+5'}" di as text "perc(%)" "{col `=maxstr1+2'}{c |}" as result _col(`=maxstr1+5') %7.3f `=perc0*100' di as text "{hline `=maxstr1+1'}{c BT}{hline `=maxstr1+5'}" } /*continuous exposure and continuous or count outcome*/ else { //di as result _col(3) "mean(overall):" _col(25) %5.3f `=mean0' //di as result _col(3) "sd(overall):" _col(25) %5.3f `=sd0' di as text "{hline `=maxstr1+1'}{c TT}{hline `=maxstr1+5'}" di as text "{col `=maxstr1+2'}{c |}{col `=maxstr1+6'}overall di as text "{hline `=maxstr1+1'}{c +}{hline `=maxstr1+5'}" di as text "mean" "{col `=maxstr1+2'}{c |}" as result _col(`=maxstr1+5') %7.3f `=mean0' di as text "sd" "{col `=maxstr1+2'}{c |}" as result _col(`=maxstr1+5') %7.3f `=sd0' di as text "{hline `=maxstr1+1'}{c BT}{hline `=maxstr1+5'}" } } /*continuous outcome only*/ if outtp==0 { di _newline as text "Modelled variance and heterogeneity measures" //di as text "modelled between-study variance (tau^2)" //di as result _col(3) "exposure:" _col(25) %5.3f `=tausq1' //di as result _col(3) "covariate:" _col(25) %5.3f `=tausq2' //di as result _col(3) "interaction:" _col(25) %5.3f `=tausq3' //di as result _col(3) "intercept:" _col(25) %5.3f `=tausq0' //di as text "modelled heterogeneity, I^2 (range: 0 to 100%)" //di as result _col(3) "exposure:" _col(25) %5.2f `=100*tausq1/(tausq1+poolwithinvar)' //di as result _col(3) "covariate:" _col(25) %5.2f `=100*tausq2/(tausq2+poolwithinvar)' //di as result _col(3) "interaction:" _col(25) %5.2f `=100*tausq3/(tausq3+poolwithinvar)' //di as result _col(3) "intercept:" _col(25) %5.2f `=100*tausq0/(tausq0+poolwithinvar)' //di as text "modelled heterogeneity, H^2 (range: 1 to +inf)" //di as result _col(3) "exposure:" _col(25) %5.2f `=1/(1-tausq1/(tausq1+poolwithinvar))' //di as result _col(3) "covariate:" _col(25) %5.2f `=1/(1-tausq2/(tausq2+poolwithinvar))' //di as result _col(3) "interaction:" _col(25) %5.2f `=1/(1-tausq3/(tausq3+poolwithinvar))' //di as result _col(3) "intercept:" _col(25) %5.2f `=1/(1-tausq0/(tausq0+poolwithinvar))' //di as text "modelled within-study variance" //di as result _col(3) "pooled:" _col(25) %5.3f `=poolwithinvar' di as text "{hline `=maxstr2+1'}{c TT}{hline `=maxstr2+25'}" di as text "{col `=maxstr2+2'}{c |}{col `=maxstr2+6'}exposure{col `=maxstr2+18'}covariate{col `=maxstr2+30'}interaction{col `=maxstr2+42'}intercept di as text "{hline `=maxstr2+1'}{c +}{hline `=maxstr2+25'}" di as text "between variance (tau^2)" "{col `=maxstr2+2'}{c |}" as result _col(`=maxstr2+5') %7.3f `=tausq1' _col(`=maxstr2+17') %7.3f `=tausq2' /* */ _col(`=maxstr2+29') %7.3f `=tausq3' _col(`=maxstr2+41') %7.3f `=tausq0' di as text "I^2 (range: 0 to 100%)" "{col `=maxstr2+2'}{c |}" as result _col(`=maxstr2+5') %7.3f `=100*tausq1/(tausq1+poolwithinvar)' _col(`=maxstr2+17') %7.3f `=100*tausq2/(tausq2+poolwithinvar)' /* */ _col(`=maxstr2+29') %7.3f `=100*tausq3/(tausq3+poolwithinvar)' _col(`=maxstr2+41') %7.3f `=100*tausq0/(tausq0+poolwithinvar)' di as text "H^2 (range: 1 to +inf)" "{col `=maxstr2+2'}{c |}" as result _col(`=maxstr2+5') %7.3f `=1/(1-tausq1/(tausq1+poolwithinvar))' _col(`=maxstr2+17') %7.3f `=1/(1-tausq2/(tausq2+poolwithinvar))' /* */ _col(`=maxstr2+29') %7.3f `=1/(1-tausq3/(tausq3+poolwithinvar))' _col(`=maxstr2+41') %7.3f `=1/(1-tausq0/(tausq0+poolwithinvar))' di as text "{hline `=maxstr2+1'}{c BT}{hline `=maxstr2+25'}" di as text "modelled within-study variance (pooled):" _col(25) as result %7.3f `=poolwithinvar' } //di as text "mean estimates" //di as result _col(3) "b1 (exposure):" _col(25) %5.3f `=c1/cntr' //di as result _col(3) "b2 (covariate):" _col(25) %5.3f `=c4/cntr' //di as result _col(3) "b3 (interaction):" _col(25) %5.3f `=c7/cntr' //di as result _col(3) "b0 (intercept):" _col(25) %5.3f `=c10/cntr' /*R^2: adjusted for regress / overall for xtreg / pseudo for logit and xtlogit*/ //di as result _col(3) "R^2(%):" _col(25) %5.2f `=100*c18/cntr' //di as result _col(3) "within-sd(error):" _col(25) %5.3f `=c13/cntr' /*e(sigma_u) in all cases except for poisson with gamma distributed RE: e(alpha)*/ //di as result _col(3) "betw-sd(_cons):" _col(25) %5.3f `=c14/cntr' //di as result _col(3) "betw-sd(grp):" _col(25) %5.3f `=c15/cntr' //di as result _col(3) "betw-sd(covar):" _col(25) %5.3f `=c16/cntr' //di as result _col(3) "betw-sd(grpXcovar):" _col(25) %5.3f `=c17/cntr' //di as text "power to detect effects" //di as result _col(3) "exposure:" _col(20) %3.1f powb1 "(" %3.1f lpowb1 "-" %3.1f upowb1 ")" //di as result _col(3) "covariate:" _col(20) %3.1f powb2 "(" %3.1f lpowb2 "-" %3.1f upowb2 ")" //di as result _col(3) "interaction:" _col(20) %3.1f powb3 "(" %3.1f lpowb3 "-" %3.1f upowb3 ")" //di as result _col(3) "intercept:" _col(20) %3.1f powb0 "(" %3.1f lpowb0 "-" %3.1f upowb0 ")" //di as text "coverage for effects (reported CI includes model beta)" //di as result _col(3) "exposure:" _col(20) %3.1f covb1 "(" %3.1f lcovb1 "-" %3.1f ucovb1 ")" //di as result _col(3) "covariate:" _col(20) %3.1f covb2 "(" %3.1f lcovb2 "-" %3.1f ucovb2 ")" //di as result _col(3) "interaction:" _col(20) %3.1f covb3 "(" %3.1f lcovb3 "-" %3.1f ucovb3 ")" //di as result _col(3) "intercept:" _col(20) %3.1f covb0 "(" %3.1f lcovb0 "-" %3.1f ucovb0 ")" //model estimates di _newline as text "Results: model estimates" di as text "{hline `=maxstr2+1'}{c TT}{hline `=maxstr2+25'}" di as text "{col `=maxstr2+2'}{c |}{col `=maxstr2+6'}exposure{col `=maxstr2+18'}covariate{col `=maxstr2+30'}interaction{col `=maxstr2+42'}intercept di as text "{hline `=maxstr2+1'}{c +}{hline `=maxstr2+25'}" di as text "coefficient mean" "{col `=maxstr2+2'}{c |}" as result _col(`=maxstr2+5') %7.3f `=c1/cntr' _col(`=maxstr2+17') %7.3f `=c4/cntr' /* */ _col(`=maxstr2+29') %7.3f `=c7/cntr' _col(`=maxstr2+41') %7.3f `=c10/cntr' di as text "between-sd" "{col `=maxstr2+2'}{c |}" as result _col(`=maxstr2+5') %7.3f `=c15/cntr' _col(`=maxstr2+17') %7.3f `=c16/cntr' /* */ _col(`=maxstr2+29') %7.3f `=c17/cntr' _col(`=maxstr2+41') %7.3f `=c14/cntr' di as text "{hline `=maxstr2+1'}{c BT}{hline `=maxstr2+25'}" di as text "within-sd(error):" _col(20) as result %7.3f `=c13/cntr' di as text "R^2(%):" _col(20) as result %7.3f `=100*c18/cntr' //coverage di _newline as text "Results: coverage" di as text "{hline `=maxstr3+1'}{c TT}{hline `=maxstr3+25'}" di as text "{col `=maxstr3+2'}{c |}{col `=maxstr3+6'}estimate{col `=maxstr3+18'}[95% Conf. Interval]" di as text "{hline `=maxstr3+1'}{c +}{hline `=maxstr3+25'}" di as text "exposure" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f covb1 _col(`=maxstr3+18') %7.1f lcovb1 _col(`=maxstr3+29') %7.1f ucovb1 di as text "covariate" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f covb2 _col(`=maxstr3+18') %7.1f lcovb2 _col(`=maxstr3+29') %7.1f ucovb2 di as text "interaction" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f covb3 _col(`=maxstr3+18') %7.1f lcovb3 _col(`=maxstr3+29') %7.1f ucovb3 di as text "intercept" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f covb0 _col(`=maxstr3+18') %7.1f lcovb0 _col(`=maxstr3+29') %7.1f ucovb0 di as text "{hline `=maxstr3+1'}{c BT}{hline `=maxstr3+25'}" //power di _newline as text "Results: power" di as text "{hline `=maxstr3+1'}{c TT}{hline `=maxstr3+25'}" di as text "{col `=maxstr3+2'}{c |}{col `=maxstr3+6'}estimate{col `=maxstr3+18'}[95% Conf. Interval]" di as text "{hline `=maxstr3+1'}{c +}{hline `=maxstr3+25'}" di as text "exposure" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f powb1 _col(`=maxstr3+18') %7.1f lpowb1 _col(`=maxstr3+29') %7.1f upowb1 di as text "covariate" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f powb2 _col(`=maxstr3+18') %7.1f lpowb2 _col(`=maxstr3+29') %7.1f upowb2 di as text "interaction" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f powb3 _col(`=maxstr3+18') %7.1f lpowb3 _col(`=maxstr3+29') %7.1f upowb3 di as text "intercept" "{col `=maxstr3+2'}{c |}" as result _col(`=maxstr3+5') %7.1f powb0 _col(`=maxstr3+18') %7.1f lpowb0 _col(`=maxstr3+29') %7.1f upowb0 di as text "{hline `=maxstr3+1'}{c BT}{hline `=maxstr3+25'}" } /*RETURN SCALARS*/ /*mean coefficients*/ return scalar b0 = c10/cntr return scalar b1 = c1/cntr return scalar b2 = c4/cntr return scalar b3 = c7/cntr /*characteristics of simulations*/ return scalar nsim = simnum /*number of simulations*/ return scalar nrun = cntr /*number of successful runs*/ return scalar ctime = tmin /*computational time in minutes*/ /*model fit*/ return scalar rsq = c18/cntr /*Adjusted or pseudo R^2*/ /*error*/ return scalar errsd = c13/cntr /*within-sd (error)*/ /*RE estimates*/ return scalar consd = c14/cntr /*betw-sd(_cons)*/ return scalar grpsd = c15/cntr /*betw-sd(grp)*/ return scalar covsd = c16/cntr /*betw-sd(covar)*/ return scalar intsd = c17/cntr /*betw-sd(grpXcovar)*/ /*Power to detect effects (of same direction)*/ forvalues i=0(1)3 { return scalar pow`i' = powb`i' return scalar lpow`i' = lpowb`i' return scalar upow`i' = upowb`i' } /*Coverage for effects (true value within CI of the estimate)*/ forvalues i=0(1)3 { return scalar cov`i' = covb`i' return scalar lcov`i' = lcovb`i' return scalar ucov`i' = ucovb`i' } end /*get the study basics - exposure binary*/ program studybasics1 /*inputs: totalsize studynum minsize caseprob*/ /*SET SIZE*/ /*total size*/ scalar totalsize=`1' /*number of studies*/ scalar studynum=`2' /*variability in study size (meansize automatically computed and from that the maximum - only minimum needs to be inputted - uniform distribution)*/ scalar minsize=`3' scalar meansize=totalsize/studynum scalar maxsize=2*meansize-minsize /*poisson distribution chosen? hlpos=1*/ scalar hlpos=`5' if hlpos==0 { /*generate uniformly distributed study sizes [minsize-maxsize] - repeat until the last study (not random) is within the desired range*/ scalar bool1=0 while bool1==0 { scalar tsize=0 forvalues i=1(1)`=studynum-1'{ scalar stsize`i' = minsize+int((maxsize-minsize+1)*runiform()) scalar tsize = tsize + stsize`i' } scalar stsize`=studynum'=totalsize-tsize if stsize`=studynum'>=minsize & stsize`=studynum'<=maxsize { scalar bool1 = 1 } } } else { /*generate Poisson distributed study sizes*/ scalar tsize=0 forvalues i=1(1)`=studynum-1'{ scalar stsize`i' = rpoisson(meansize) scalar tsize = tsize + stsize`i' } scalar stsize`=studynum'=totalsize-tsize } /*start generating the dataset - groups*/ qui clear qui set obs `=totalsize' /*generate overall identifier*/ qui egen id = seq() /*study identifier*/ qui gen studyid=. qui gen grp=0 scalar tsize=0 forvalues i=1(1)`=studynum'{ qui replace studyid=`i' if id>tsize scalar tsize=tsize+stsize`i' } /*clustered design or not*/ scalar iclus=`6' if iclus==0 { /*not clustered: set balanced-unbalanced design - proportion of intervention group*/ scalar caseprob=`4' forvalues i=1(1)`=studynum'{ scalar stisize`i'=int(caseprob*stsize`i') scalar stcsize`i'=int((1-caseprob)*stsize`i') /*add the potential extra randomly if needed*/ if stisize`i'+stcsize`i'=minsize & stsize`=studynum'<=maxsize { scalar bool1 = 1 } } } else { /*generate Poisson distributed study sizes*/ scalar tsize=0 forvalues i=1(1)`=studynum-1'{ scalar stsize`i' = rpoisson(meansize) scalar tsize = tsize + stsize`i' } scalar stsize`=studynum'=totalsize-tsize } /*start generating the dataset - groups*/ qui clear qui set obs `=totalsize' /*generate overall identifier*/ qui egen id = seq() /*study identifier*/ qui gen studyid=. scalar tsize=0 forvalues i=1(1)`=studynum'{ qui replace studyid=`i' if id>tsize scalar tsize=tsize+stsize`i' } /*exposure*/ scalar distexp=`4' scalar expmn=`5' scalar expsd=`6' /*if normally distributed*/ if distexp==0 { qui gen grp = rnormal(`=expmn',`=expsd') } else { rambergvar distexp Rb2 qui gen grp = expmn + Rb2*expsd qui drop Rb2 } end /*data generation*/ program modout1, rclass /*inputs*/ scalar b0=`1' scalar b1=`2' scalar b2=`3' scalar b3=`4' scalar poolwithinvar=`5' scalar cdsd=`6' scalar tausq0=`7' scalar tausq1=`8' scalar tausq2=`9' scalar tausq3=`10' scalar dtype0=`11' scalar dtype1=`12' scalar dtype2=`13' scalar dtype3=`14' scalar slcov=`15' scalar totnum=`16' scalar dtype4=`17' scalar dtype5=`18' scalar covmn=`19' scalar covsd=`20' scalar covprob=`21' scalar outtp=`22' scalar xcovmt=`23' scalar binexp=`24' scalar sdcovpb=`25' /*if covariate is continuous*/ if covprob==. { /*study level covariate*/ if slcov==1 { qui gen xcovar=. forvalues i=1(1)`=studynum' { /*if normally distributed*/ if dtype5==0 { scalar temp = rnormal(`=covmn',`=covsd') qui replace xcovar = temp if studyid==`i' } else { ramberg dtype5 qui replace xcovar = covmn + r(rb)*covsd if studyid==`i' } } } /*patient-level covariate*/ else { /*if normally distributed*/ if dtype5==0 { qui gen xcovar = rnormal(`=covmn',`=covsd') } else { rambergvar dtype5 Rb2 qui gen xcovar = covmn + Rb2*covsd qui drop Rb2 } } } /*if covariate is binary*/ else { /*study level covariate*/ if slcov==1 { qui gen xcovar=. forvalues i=1(1)`=studynum' { /*draw for study*/ scalar temp=0 if runiform()<=covprob { scalar temp=1 } qui replace xcovar=temp if studyid==`i' } } /*patient-level covariate*/ else { tempvar truni qui gen `truni'=runiform() qui gen xcovar=0 if sdcovpb==0 { qui replace xcovar=1 if `truni'<=covprob } else { forvalues i=1(1)`=studynum' { scalar temp = rnormal(`=covprob',`=sdcovpb') qui replace xcovar=1 if studyid==`i' & `truni'<=temp } } } } /*random effects*/ /*if no covariance matrix*/ if xcovmt==0 { /*distribution intercept(0), main(1), baseline(2) and interaction(3) effect*/ forvalues x=0(1)3 { /*random-effects*/ if tausq`x'==0 { qui gen u`x'=0 } else { qui gen u`x'=. /*draw for each study*/ forvalues i=1(1)`=studynum'{ /*call Ramberg method*/ ramberg dtype`x' scalar Rb`x'=r(rb) /*rescale and add*/ qui replace u`x' = Rb`x'*sqrt(tausq`x') if studyid==`i' } } } } /*if covariance matrix*/ else { qui preserve /*draw the study effects*/ qui clear qui set obs `=studynum' qui drawnorm re0 re1 re2 re3, cov(test1test2test3) cstorage(full) /*get the generated values into scalars*/ forvalues x=0(1)3 { forvalues i=1(1)`=studynum'{ local tmp`x'`i'=re`x' in `i' } } /*add to main dataset*/ qui restore forvalues x=0(1)3 { qui gen u`x'=. /*add for each study*/ forvalues i=1(1)`=studynum'{ qui replace u`x' = `tmp`x'`i'' if studyid==`i' } } } /*errors: only relevant for continuous outcome*/ if outtp==0 { /*calculate observation error using study SD*/ qui gen errx=. /*if normally distributed*/ if dtype4==0 { qui gen Rb2=rnormal(0,1) } else { rambergvar dtype4 Rb2 } /*rescale error according to study variance*/ forvalues i=1(1)`=studynum'{ /*within study variance*/ scalar withinsd`i' = rnormal(`=sqrt(poolwithinvar)',cdsd) /*limit to positive by resampling - which will affect the mean if part of the tail is negative*/ while withinsd`i'<=0 { scalar withinsd`i' = rnormal(`=sqrt(poolwithinvar)',cdsd) } /*rescaled error - e taken from N(0,s^2)*/ qui replace errx = Rb2*withinsd`i' if studyid==`i' } qui drop Rb2 } /*generate outcome for each study*/ if outtp==0 { qui gen outcome= b0 + b1*grp + b2*xcovar + b3*xcovar*grp + u0 + u1*grp + u2*xcovar + u3*xcovar*grp + errx } else if outtp==1 { /*no need to add errors - within errors are fixed for logistic regressions and adding errx has no effect at all besides destabilising the estimates*/ qui gen outcome = uniform() < invlogit(b0 + b1*grp + b2*xcovar + b3*xcovar*grp + u0 + u1*grp + u2*xcovar + u3*xcovar*grp) } else if outtp==2 { /*no need to add errors - within errors are fixed for logistic regressions and adding errx has no effect at all besides destabilising the estimates*/ qui gen outcome =rpoisson(exp(b0 + b1*grp + b2*xcovar + b3*xcovar*grp + u0 + u1*grp + u2*xcovar + u3*xcovar*grp)) } /*also return mean(s)/sd(s) for continuous/counts, percentage(s) for binary*/ if outtp==1 { if binexp==1 { forvalues i=0(1)1 { qui count if grp==`i' scalar den`i'=r(N) qui count if outcome==1 & grp==`i' scalar perc`i'=r(N)/den`i' return scalar perc`i'=perc`i' } } else { qui count scalar den0=r(N) qui count if outcome==1 scalar perc0=r(N)/den0 return scalar perc0=perc0 } } else { if binexp==1 { forvalues i=0(1)1 { qui sum outcome if grp==`i' scalar mean`i'=r(mean) scalar sd`i'=r(sd) return scalar mean`i'=mean`i' return scalar sd`i'=sd`i' } } else { qui sum outcome scalar mean0=r(mean) scalar sd0=r(sd) return scalar mean0=mean0 return scalar sd0=sd0 } } qui compress end /*missing data mechanisms section*/ /*MCAR mechanism*/ program mcarprg scalar missrate=`1' /*missing outcome %*/ tempvar tempx qui gen `tempx' = uniform() qui replace outcome=. if `tempx'