@@ -25,166 +25,203 @@ source_dir(file.path(app_dir, "R"))
2525source_dir(file.path(app_dir , " modules" ))
2626
2727
28- # ---- small helper: get Pr(NI) across B trials for plotting ------------------
29- prNI_draws_conj <- function (B , p_c , p_t , n_c , n_t , M ,
30- prior = c(" flat" ," power" ), prior_args = list (),
31- n_draws = 2000 , seed = NULL ) {
32- prior <- match.arg(prior )
33- if (! is.null(seed )) set.seed(seed )
34- pr <- numeric (B )
35- for (b in seq_len(B )) {
36- res <- bayesNI_trial_betaBinom_conj(
37- p_c = p_c , p_t = p_t , n_c = n_c , n_t = n_t , M = M ,
38- prior = prior , prior_args = prior_args ,
39- n_draws = n_draws
40- )
41- pr [b ] <- unname(res $ summary [" post_prob_NI" ])
42- }
43- pr
44- }
45-
46-
4728# If your functions live in a package, uncomment:
4829# library(bcts)
4930
50- ui <- fluidPage(
51- withMathJax(), # enable LaTeX rendering for the whole page
52- titlePanel(" Bayesian Trial Simulation (Beta–Binomial, conjugate)" ),
53- sidebarLayout(
54- sidebarPanel(
55-
56- # --- Assumptions (truth used for simulation / planning) ---
57- wellPanel(
58- h4(" Treatment Arm Assumptions" ),
59- sliderInput(" pt" , HTML(" True response rate (\\ (\\ theta_t\\ ))" ),
60- min = 0 , max = 100 , value = 85 , step = 1 ,
61- post = " %" ),
62- numericInput(" nt" , HTML(" Number of randomized patients (\\ (n_t \\ ))" ), value = 29 , min = 1 , step = 1 ),
31+ ui <- navbarPage(
32+ title = " Bayesian Trial Simulation (Beta–Binomial, conjugate)" ,
33+ tabPanel(
34+ title = " Randomized trial" ,
35+ fluidPage(
36+ withMathJax(), # enable LaTeX rendering for the whole page
37+
38+ # --- Description row at top (full width) ---
39+ fluidRow(
40+ column(
41+ width = 12 ,
42+ div(
43+ style = " margin-bottom: 20px;" ,
44+ h4(" Simulate binary responder outcomes from a randomized trial with a treatment and control arm." ),
45+ p(" Use the controls in the left panel to define the data-generating assumptions, prior distributions, and decision criteria.
46+ The design summary and operating characteristics will be shown on the right." )
47+ )
48+ )
6349 ),
6450
65- # --- Assumptions (truth used for simulation / planning) ---
66- tagList (
67- # Panel 1: Control arm (always shown)
51+
52+ sidebarPanel (
53+
6854 wellPanel(
69- h4(" Control Arm Assumptions" ),
70- sliderInput(" pc" , HTML(" True response rate (\\ (\\ theta_c\\ ))" ),
71- min = 0 , max = 100 , value = 85 , step = 1 , post = " %" ),
72- numericInput(" nc" , HTML(" Number of randomized patients (\\ (n_c\\ ))" ),
73- value = 29 , min = 1 , step = 1 ),
74-
75- selectInput(
76- " prior" ,
77- " Prior distribution" ,
78- choices = c(" Flat (no external evidence)" = " flat" ,
79- " Power prior (with historical data)" = " power" ),
80- selected = " flat"
55+ h4(" Summary Output Type" ),
56+ radioButtons(
57+ inputId = " summary_type" ,
58+ label = " Choose summary format:" ,
59+ choices = c(" Narrative" = " narrative" , " Technical" = " technical" ),
60+ selected = " narrative"
8161 )
8262 ),
8363
84- # Panel 2: External data config (only when prior == power)
85- conditionalPanel(
86- condition = " input.prior == 'power'" ,
87- wellPanel(
88- h4(" External Data (Power Prior)" ),
89- sliderInput(" a0" , " Discount factor a₀ (0 = ignore history, 1 = full borrow)" ,
90- min = 0 , max = 100 , value = 50 , step = 1 , post = " %" ),
91- numericInput(" y0" , " Historical responders (y₀)" , value = 64 , min = 0 , step = 1 ),
92- numericInput(" n0" , " Historical sample size (n₀)" , value = 75 , min = 1 , step = 1 ),
93- numericInput(" abase" , " Baseline Beta a_base" , value = 1 , min = 0.001 , step = 0.1 ),
94- numericInput(" bbase" , " Baseline Beta b_base" , value = 1 , min = 0.001 , step = 0.1 )
95- )
96- )
97- ),
64+ # --- Assumptions (truth used for simulation / planning) ---
65+ wellPanel(
66+ h4(" Treatment Arm Assumptions" ),
67+ sliderInput(" pt" , HTML(" True response rate (\\ (\\ theta_t\\ ))" ),
68+ min = 0 , max = 100 , value = 85 , step = 1 ,
69+ post = " %" ),
70+ numericInput(" nt" , HTML(" Number of randomized patients (\\ (n_t \\ ))" ), value = 29 , min = 1 , step = 1 ),
71+ ),
9872
73+ # --- Assumptions (truth used for simulation / planning) ---
74+ tagList(
75+ # Panel 1: Control arm (always shown)
76+ wellPanel(
77+ h4(" Control Arm Assumptions" ),
78+ sliderInput(" pc" , HTML(" True response rate (\\ (\\ theta_c\\ ))" ),
79+ min = 0 , max = 100 , value = 85 , step = 1 , post = " %" ),
80+ numericInput(" nc" , HTML(" Number of randomized patients (\\ (n_c\\ ))" ),
81+ value = 29 , min = 1 , step = 1 ),
82+
83+ selectInput(
84+ " prior" ,
85+ " Prior distribution" ,
86+ choices = c(" Flat (no external evidence)" = " flat" ,
87+ " Power prior (with historical data)" = " power" ),
88+ selected = " flat"
89+ )
90+ ),
9991
100- wellPanel(
101- h4(" Decision criteria" ),
102- sliderInput(
103- " M" ,
104- label = HTML(" Decision Margin (\\ ( \\ Delta \\ ))" ),
105- min = - 100 , max = 100 , value = - 20 , step = 1 , post = " %"
106- ),
107- helpText(
108- " Δ < 0: non-inferiority (treatment may be up to |Δ| worse)." ,
109- " Δ ≥ 0: superiority (treatment must be at least Δ better)." ,
110- " Assumes higher response rates are better (responder events)."
92+ # Panel 2: External data config (only when prior == power)
93+ conditionalPanel(
94+ condition = " input.prior == 'power'" ,
95+ wellPanel(
96+ h4(" External Data (Power Prior)" ),
97+ sliderInput(" a0" , " Discount factor a₀ (0 = ignore history, 1 = full borrow)" ,
98+ min = 0 , max = 100 , value = 50 , step = 1 , post = " %" ),
99+ numericInput(" y0" , " Historical responders (y₀)" , value = 64 , min = 0 , step = 1 ),
100+ numericInput(" n0" , " Historical sample size (n₀)" , value = 75 , min = 1 , step = 1 ),
101+ numericInput(" abase" , " Baseline Beta a_base" , value = 1 , min = 0.001 , step = 0.1 ),
102+ numericInput(" bbase" , " Baseline Beta b_base" , value = 1 , min = 0.001 , step = 0.1 )
103+ )
104+ )
111105 ),
112106
113- # Choice: set gamma directly OR set alpha and calibrate gamma
114- radioButtons(" decision_mode" , " Threshold specification:" ,
115- choices = c(" Specify posterior probability threshold γ" = " gamma" ,
116- " Specify target Type-I error α" = " alpha" ),
117- selected = " gamma" ),
118107
119- conditionalPanel (
120- condition = " input.decision_mode == 'gamma' " ,
108+ wellPanel (
109+ h4( " Decision criteria " ) ,
121110 sliderInput(
122- " gamma " ,
123- label = HTML(" Posterior probability threshold (\\ ( \\ gamma \\ ))" ),
124- min = 80 , max = 99 , value = 90 , step = 1 , post = " %"
111+ " M " ,
112+ label = HTML(" Decision Margin (\\ ( \\ Delta \\ ))" ),
113+ min = - 100 , max = 100 , value = - 20 , step = 1 , post = " %"
125114 ),
126- uiOutput(" decision_rule" ) # placeholder for dynamic help text
127- ),
128-
129- conditionalPanel(
130- condition = " input.decision_mode == 'alpha'" ,
131- sliderInput(
132- " alpha" ,
133- label = HTML(" Target Type-I error (\\ ( \\ alpha \\ ))" ),
134- value = 10 , min = 1 , max = 20 , step = 1 , post = " %"
115+ helpText(
116+ " Δ < 0: non-inferiority (treatment may be up to |Δ| worse)." ,
117+ " Δ ≥ 0: superiority (treatment must be at least Δ better)." ,
118+ " Assumes higher response rates are better (responder events)."
135119 ),
136- selectInput(
137- " calibrate_on" ,
138- " Calibrate Type-I on:" ,
139- choices = c(
140- " Point estimate Pr(reject | H₀)" = " point" ,
141- " Upper 95% MC CI (conservative)" = " upper" ,
142- " Lower 95% MC CI (liberal)" = " lower"
120+
121+ # Choice: set gamma directly OR set alpha and calibrate gamma
122+ radioButtons(" decision_mode" , " Threshold specification:" ,
123+ choices = c(" Specify posterior probability threshold γ" = " gamma" ,
124+ " Specify target Type-I error α" = " alpha" ),
125+ selected = " gamma" ),
126+
127+ conditionalPanel(
128+ condition = " input.decision_mode == 'gamma'" ,
129+ sliderInput(
130+ " gamma" ,
131+ label = HTML(" Posterior probability threshold (\\ ( \\ gamma \\ ))" ),
132+ min = 80 , max = 99 , value = 90 , step = 1 , post = " %"
143133 ),
144- selected = " upper "
134+ uiOutput( " decision_rule " ) # placeholder for dynamic help text
145135 ),
146- helpText(" γ will be calibrated so that the chosen Type-I metric ≈ α (within tolerance) at the least-favourable null." )
147- )
148- ),
136+
137+ conditionalPanel(
138+ condition = " input.decision_mode == 'alpha'" ,
139+ sliderInput(
140+ " alpha" ,
141+ label = HTML(" Target Type-I error (\\ ( \\ alpha \\ ))" ),
142+ value = 10 , min = 1 , max = 20 , step = 1 , post = " %"
143+ ),
144+ selectInput(
145+ " calibrate_on" ,
146+ " Calibrate Type-I on:" ,
147+ choices = c(
148+ " Point estimate Pr(reject | H₀)" = " point" ,
149+ " Upper 95% MC CI (conservative)" = " upper" ,
150+ " Lower 95% MC CI (liberal)" = " lower"
151+ ),
152+ selected = " upper"
153+ ),
154+ helpText(" γ will be calibrated so that the chosen Type-I metric ≈ α (within tolerance) at the least-favourable null." )
155+ )
156+ ),
149157
150158
151159
152- # --- Posterior Evaluation ---
153- wellPanel(
154- h4(" Simulation settings" ),
155- numericInput(" B" ,
156- " Number of simulated trials (for Type-I & Power)" ,
157- value = 2500 , min = 100 , step = 100 ),
158- helpText(textOutput(" design_mc_precision_text" )),
160+ # --- Posterior Evaluation ---
161+ wellPanel(
162+ h4(" Simulation settings" ),
163+ numericInput(" B" ,
164+ " Number of simulated trials (for Type-I & Power)" ,
165+ value = 2500 , min = 100 , step = 100 ),
166+ helpText(textOutput(" design_mc_precision_text" )),
159167
160- numericInput(" ndraws" , " Posterior draws per trial (for Pr(NI))" , value = 2000 , min = 200 , step = 100 ),
161- helpText(textOutput(" post_mc_precision_text" )),
168+ numericInput(" ndraws" , " Posterior draws per trial (for Pr(NI))" , value = 2000 , min = 200 , step = 100 ),
169+ helpText(textOutput(" post_mc_precision_text" )),
162170
163- numericInput(" seed" , " Seed (optional)" , value = 123 , min = 1 , step = 1 ),
164- # helpText(HTML("Larger values give more precise results but increase runtime.")),
165- ),
171+ numericInput(" seed" , " Seed (optional)" , value = 123 , min = 1 , step = 1 ),
172+ # helpText(HTML("Larger values give more precise results but increase runtime.")),
173+ ),
166174
167175
168176
169- actionButton(" run" , " Run simulation" , class = " btn-primary" ),
177+ actionButton(" run" , " Run simulation" , class = " btn-primary" ),
170178
171- hr(),
172- tags $ small(
173- paste(" bcts version:" , utils :: packageVersion(" bcts" ))
174- )
175- ),
176- mainPanel(
177- mod_designsummary_ui(" dsum" ),
178- mod_armpriors_ui(" armpriors" , height = 320 ),
179- mod_oc_ui(" oc" ),
179+ hr(),
180+ tags $ small(
181+ paste(" bcts version:" , utils :: packageVersion(" bcts" ))
182+ )
183+ ),
184+ mainPanel(
185+ conditionalPanel(
186+ condition = " input.summary_type == 'technical'" ,
187+ mod_designsummary_ui(" dsum" )
188+ ),
189+ conditionalPanel(
190+ condition = " input.summary_type == 'narrative'" ,
191+ mod_narrative_ui(" narrative" )
192+ ),
193+ mod_armpriors_ui(" armpriors" , height = 320 ),
194+ mod_oc_ui(" oc" ),
180195
181- # --- Sensitivity analysis ---
182- # Sidebar
183- mod_sensitivity_sidebar_ui(" sens" ),
196+ # --- Sensitivity analysis ---
197+ # Sidebar
198+ mod_sensitivity_sidebar_ui(" sens" ),
184199
185- # Main panel (where you want outputs)
186- mod_sensitivity_main_ui(" sens" , plot_height = 300 )
200+ # Main panel (where you want outputs)
201+ mod_sensitivity_main_ui(" sens" , plot_height = 300 )
187202
203+
204+ )
205+ )
206+ ),
207+
208+ tabPanel(
209+ title = " Single-arm trial" ,
210+ fluidPage(
211+ h4(" Single-arm trial dashboard (under construction)" ),
212+ p(" This section will allow evaluation of single-arm designs using Beta–Binomial conjugate models." ),
213+ p(" You can simulate a posterior for a single group, compare against a threshold, or incorporate external data via power priors." ),
214+ br(),
215+ wellPanel(
216+ p(" Include UI elements here for:" ),
217+ tags $ ul(
218+ tags $ li(" True response rate (θ)" ),
219+ tags $ li(" Sample size (n)" ),
220+ tags $ li(" Prior type: Flat vs Power prior" ),
221+ tags $ li(" External data if using power prior" ),
222+ tags $ li(" Decision margin (Δ) and threshold (γ or α)" )
223+ )
224+ )
188225 )
189226 )
190227)
@@ -279,6 +316,21 @@ server <- function(input, output, session) {
279316 decision_mode = reactive(input $ decision_mode )
280317 )
281318
319+ mod_narrative_server(
320+ " narrative" ,
321+ pt = reactive(input $ pt / 100 ), nt = reactive(input $ nt ),
322+ pc = reactive(input $ pc / 100 ), nc = reactive(input $ nc ),
323+ M = reactive(input $ M / 100 ),
324+ prior = reactive(input $ prior ),
325+ prior_args = prior_args ,
326+ decision_mode = reactive(input $ decision_mode ),
327+ gamma = reactive(input $ gamma / 100 ),
328+ alpha = reactive(input $ alpha / 100 ),
329+ B = reactive(input $ B ),
330+ ndraws = reactive(input $ ndraws ),
331+ seed = reactive(input $ seed )
332+ )
333+
282334
283335 mod_designsummary_server(
284336 " dsum" ,
0 commit comments