diff --git a/DESCRIPTION b/DESCRIPTION
index 083153476d297efeab577f0c0bc08d54286dfbd1..2f170c60921f0152128071b3119b9e67cc90eb80 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -14,14 +14,13 @@ Imports:
     evd,
     formula.tools,
     ggplot2,
+    kableExtra,
     magrittr,
     mixl,
     psych,
     purrr,
     readr,
-    reshape,
     rmarkdown,
-    stats,
     stringr,
     tibble,
     tictoc,
diff --git a/R/globals.R b/R/globals.R
index 94a876df8de89bdf81829990f246d824a2a98f53..7acdf7a92b5cd721b7d60c1abccc42a7539a7ad8 100644
--- a/R/globals.R
+++ b/R/globals.R
@@ -1 +1 @@
-utils::globalVariables(c("designfile", "destype", "Choice.situation", "Design"))
+utils::globalVariables(c("designfile", "destype", "Choice.situation", "Design", "." ,"ID", ":=", "..density.."))
diff --git a/R/readdesign.R b/R/readdesign.R
index 1a38b6c571774758b8ab5488727748b8a856d441..b0ec78fe2708ad32f283624bb14069f837cdeee6 100644
--- a/R/readdesign.R
+++ b/R/readdesign.R
@@ -28,11 +28,12 @@ readdesign <- function(design = designfile, designtype = destype) {
       trim_ws = TRUE,
       col_select = c(-Design, -tidyr::starts_with("...")),
       name_repair = "universal", show_col_types = FALSE
-    ) |>
+    ) %>%
       dplyr::filter(!is.na(Choice.situation)),
-    "spdesign" = as.data.frame(readRDS(design)) |>
-      dplyr::mutate(Choice.situation = 1:dplyr::n()) |>
-      dplyr::rename_with(~ stringr::str_replace(., pattern = "_", "\\."), tidyr::everything()),
+    "spdesign" = as.data.frame(readRDS(design)) %>%
+      dplyr::mutate(Choice.situation = 1:dplyr::n()) %>%
+      dplyr::rename_with(~ stringr::str_replace(., pattern = "_", "\\."), tidyr::everything()) %>%
+      dplyr::rename(Block=block),
     stop("Invalid value for design. Please provide either 'ngene' or 'spdesign'.")
   )
 }
diff --git a/R/sim_choice.R b/R/sim_choice.R
index 9fdf8b5bbadb205e620c1ed33f2d7b22187c9303..de9f9613fe2384b837d4c1fb1c5aaa13105fa73d 100644
--- a/R/sim_choice.R
+++ b/R/sim_choice.R
@@ -1,3 +1,11 @@
+
+
+
+
+
+
+
+
 #' Title
 #'
 #' @param designfile path to a file containing a design.
@@ -10,16 +18,20 @@
 #' @return a list with all information on the run
 #' @export
 #'
-#' @examples
+#' @examples \dontrun{  simchoice(designfile="somefile", no_sim=10, respondents=330,
+#'  mnl_U,utils=u[[1]] ,destype="ngene")}
 #'
 sim_choice <- function(designfile, no_sim=10, respondents=330, mnl_U,utils=u[[1]] ,destype) {
 
-  require("gridExtra")
-
-  require("ggplot2")
 
   require("rlang")
 
+## Function that transforms user written utiliy for simulation into utility function for mixl.
+  transform_util <- function() {
+    mnl_U <-paste(purrr::map_chr(utils,as.character,keep.source.attr = TRUE),collapse = "",";") %>%
+      stringr::str_replace_all( c( "priors\\[\"" = "" , "\"\\]" = "" ,  "~" = "=", "\\." = "_" , " b" = " @b"  , "V_"="U_", " alt"="$alt"))
+
+  }
 
   estimate_sim <- function(run=1) {         #start loop
 
@@ -36,23 +48,27 @@ sim_choice <- function(designfile, no_sim=10, respondents=330, mnl_U,utils=u[[1]
 
   }
 
-  mnl_U <-paste(map_chr(utils,as.character,keep.source.attr = TRUE),collapse = "",";") %>%
-    stringr::str_replace_all( c( "priors\\[\"" = "" , "\"\\]" = "" ,  "~" = "=", "\\." = "_" , " b" = " @b"  , "V_"="U_", " alt"="$alt"))
 
-  cat("mixl \n")
-  cat(mnl_U)
 
-  cat("\n Simulation \n")
+mnl_U <- transform_util()
+
+
+ cat("Utility function used in simulation, ie the true utility: \n\n")
+
+     print(u)
 
-  print(u)
 
+  cat("Utility function used for Logit estimation with mixl: \n\n")
+  print(mnl_U)
 
-  designs_all <- list()
 
 
-  design<- readdesign(design = designfile)
+  designs_all <- list()   ## Empty list where to store all designs later on
 
-  if (!exists("design$Block")) design$Block=1
+
+  design<- readdesign(design = designfile)    # Read in the design file
+
+  if (!("Block" %in% colnames(design))) design$Block=1  # If no Blocks exist, create a variable Blocks to indicate it is only one block
 
   nsets<-nrow(design)
   nblocks<-max(design$Block)
@@ -69,6 +85,9 @@ sim_choice <- function(designfile, no_sim=10, respondents=330, mnl_U,utils=u[[1]
 
   database <- simulate_choices(data=datadet, utility = utils, setspp = setpp)
 
+
+# specify model for mixl estimation
+
   model_spec <- mixl::specify_model(mnl_U, database, disable_multicore=F)
 
   est=setNames(rep(0,length(model_spec$beta_names)), model_spec$beta_names)
@@ -78,7 +97,7 @@ sim_choice <- function(designfile, no_sim=10, respondents=330, mnl_U,utils=u[[1]
     database, model_spec$num_utility_functions)
 
 
-  output<- 1:no_sim %>% map(estimate_sim)
+  output<- 1:no_sim %>% purrr::map(estimate_sim)
 
 
 
diff --git a/R/utils.R b/R/utils.R
index d2a978472b6ee6ee4682a9b6a0ccf13c7bdccaa2..957d27bc78499efc4cae75daa4cfa7ff2a816b70 100644
--- a/R/utils.R
+++ b/R/utils.R
@@ -3,7 +3,8 @@ plot_multi_histogram <- function(df, feature, label_column, hist=FALSE) { #funct
     ggplot2::geom_density(alpha=0.5) +
     ggplot2::geom_vline(ggplot2::aes(xintercept=mean(eval(parse(text=feature)))), color="black", linetype="dashed", linewidth=1) +  ## this makes a vertical line of the mean
     ggplot2::labs(x=feature, y = "Density") +
-    ggplot2::guides(fill=guide_legend(title=label_column))
+    ggplot2::guides(fill=ggplot2::guide_legend(title=label_column))
+
   if (hist==TRUE) plt + ggplot2::geom_histogram(alpha=0.7, position="identity", ggplot2::aes(y = ..density..), color="black")
 
   return(plt)
@@ -21,7 +22,7 @@ plot_multi_histogram <- function(df, feature, label_column, hist=FALSE) { #funct
 #' @return nothing, stores the data on the local system
 #' @export
 #'
-#' @examples
+#' @examples \dontrun{ download_and_extract_zip(url="www.nextcloud.de/mysuperfile")}
 download_and_extract_zip <- function(url, dest_folder = ".", zip_name = NULL) {
   # If zip_name is not provided, extract it from the URL
   if (is.null(zip_name)) {
@@ -38,10 +39,10 @@ download_and_extract_zip <- function(url, dest_folder = ".", zip_name = NULL) {
 
 
   # Download the zip file
-  download.file(url, zip_name, method = "auto", quiet = FALSE, mode = "w", cacheOK = TRUE)
+  utils::download.file(url, zip_name, method = "auto", quiet = FALSE, mode = "w", cacheOK = TRUE)
 
   # Extract the contents
-  unzip(zip_name, exdir = dest_folder)
+  utils::unzip(zip_name, exdir = dest_folder)
 
 
   # Return the path to the extracted folder
diff --git a/inst/extdata/CSA/design1.RDS b/inst/extdata/CSA/design1.RDS
new file mode 100644
index 0000000000000000000000000000000000000000..c3ad4809b9dd93b05f8d6993d4eda66be33480b2
Binary files /dev/null and b/inst/extdata/CSA/design1.RDS differ
diff --git a/inst/extdata/SE_AGRI/bayeff3_newpriors_dummy.ngd b/inst/extdata/SE_AGRI/bayeff3_newpriors_dummy.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..c232f8f660117e9b9180e6b668cc0389b1510137
--- /dev/null
+++ b/inst/extdata/SE_AGRI/bayeff3_newpriors_dummy.ngd
@@ -0,0 +1,113 @@
+Design	Choice situation	alt1.initiator	alt1.funding	alt1.damage	alt1.compensation	alt2.initiator	alt2.funding	alt2.damage	alt2.compensation	Block	
+1	1	2	1	0	2	1	0	1	30	1	
+1	2	2	1	0	5	1	2	1	10	4	
+1	3	1	0	0	10	0	1	1	20	3	
+1	4	1	1	0	20	0	2	1	30	4	
+1	5	0	1	1	30	1	2	0	5	3	
+1	6	1	0	0	5	0	2	1	15	2	
+1	7	1	1	0	2	0	2	1	5	4	
+1	8	0	1	0	15	1	0	1	2	2	
+1	9	0	2	1	30	1	0	0	2	2	
+1	10	1	2	1	30	2	0	0	20	4	
+1	11	2	2	0	10	1	1	1	5	3	
+1	12	2	2	0	30	0	1	1	10	1	
+1	13	0	1	0	2	2	0	1	5	2	
+1	14	2	0	1	10	0	2	0	30	2	
+1	15	1	0	0	20	2	1	1	30	4	
+1	16	1	1	1	10	2	2	0	2	2	
+1	17	0	2	0	5	1	0	1	20	2	
+1	18	0	0	1	30	1	2	0	15	3	
+1	19	0	0	1	2	2	1	0	15	4	
+1	20	0	1	1	20	2	2	0	10	1	
+1	21	1	2	1	10	2	0	0	5	2	
+1	22	0	0	1	15	2	1	1	30	2	
+1	23	2	2	1	2	0	0	1	10	1	
+1	24	1	2	0	5	2	1	1	2	3	
+1	25	2	0	0	30	0	2	0	20	1	
+1	26	1	2	1	20	2	1	0	10	1	
+1	27	2	2	1	20	1	1	0	15	3	
+1	28	1	1	1	5	2	0	0	15	4	
+1	29	0	0	0	2	2	1	1	20	1	
+1	30	0	0	0	15	1	1	0	30	1	
+1	31	2	0	1	5	1	2	0	2	1	
+1	32	2	2	0	20	0	0	1	2	3	
+1	33	2	2	1	15	0	0	0	10	3	
+1	34	1	1	1	15	0	2	0	20	3	
+1	35	0	1	0	10	1	0	1	15	4	
+1	36	2	0	1	15	0	1	0	5	4	
+||||||||||
+design
+;alts = alt1, alt2, alt3
+;rows = 36
+;block = 4
+
+;eff = (mnl,d,mean)
+;rep = 1000
+;bdraws = halton(1000)
+;bseed = 2333344
+;rseed = 2333344
+
+;con
+;model:
+
+
+
+U(alt1) = b0[(n,-1.3,0.5)] + b1.dummy[(n,-0.14,0.2)|(n,-0.18,0.2)] * Initiator[1,2,0] + b2.dummy[(n,0.4,0.4)|(n,0.5,0.5)]  * Funding[1,2,0]  + b3[(n,0.5,0.3)] * Damage [0,1]  + 
+ b4.dummy[(n,1.26,0.3)|(n,1.125,0.3)|(n,0.9,0.3)|(n,0.67,0.3)|(n,0.45,0.3)] * Compensation[2,5,10,15,20,30] / 
+U(alt2) =  b0 + b1 * Initiator + b2 * Funding + b3 * Damage   + b4 * Compensation
+
+;formatTitle = 'Scenario <scenarionumber>'
+;formatTableDimensions = 3, 6
+;formatTable:
+1,1 = '' /
+1,2 = 'Initiative to join the scheme' /
+1,3 = 'Source of funding for the compensation' /
+1,4 = 'Impact of forest damage on the carbon amount' /
+1,5 = 'Amount of carbon compensation ' /
+1,6 = 'Choice question&:' /
+2,1 = 'alt1' /
+2,2 = '<alt1.initiator>' /
+2,3 = '<alt1.funding>' /
+2,4 = '<alt1.damage>' /
+2,5 = '<alt1.compensation>' /
+2,6 = '' /
+3,1 = 'alt2' /
+3,2 = '<alt2.initiator>' /
+3,3 = '<alt2.funding>' /
+3,4 = '<alt2.damage>' /
+3,5 = '<alt2.compensation>' /
+3,6 = ''
+;formatTableStyle:
+1,1 = 'default' /
+1,2 = 'headingattribute' /
+1,3 = 'headingattribute' /
+1,4 = 'headingattribute' /
+1,5 = 'headingattribute' /
+1,6 = 'headingattribute' /
+2,1 = 'heading1' /
+2,2 = 'body1' /
+2,3 = 'body1' /
+2,4 = 'body1' /
+2,5 = 'body1' /
+2,6 = 'choice1' /
+3,1 = 'heading2' /
+3,2 = 'body2' /
+3,3 = 'body2' /
+3,4 = 'body2' /
+3,5 = 'body2' /
+3,6 = 'choice2'
+;formatStyleSheet = Default.css
+;formatAttributes:
+alt1.initiator(1='A familiar forestry professional ', 2='A forestry expert ', 0='My initiative') /
+alt1.funding(1='Emission offset payments paid by domestic companies', 2='Emission offset payments paid by foreign companies', 0='State tax resources') /
+alt1.damage(0='not taken into account' , 1= 'taken into account') /
+alt1.compensation(2=# EUR, 5=# EUR, 10=# EUR, 15=# EUR, 20=# EUR, 30=# EUR) /
+alt2.initiator(1='A familiar forestry professional ', 2='A forestry expert ', 0='My initiative')  /
+alt2.funding(1='Emission offset payments paid by domestic companies', 2='Emission offset payments paid by foreign companies', 0='State tax resources')  /
+alt2.damage(0='not taken into account' , 1= 'taken into account') /
+alt2.compensation(2=# EUR, 5=# EUR, 10=# EUR, 15=# EUR, 20=# EUR, 30=# EUR)
+
+
+
+
+$
\ No newline at end of file
diff --git a/inst/extdata/SE_AGRI/bayeff_newpriors1.ngd b/inst/extdata/SE_AGRI/bayeff_newpriors1.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..36a3e0f5e78c14c3a3514c36adc46ac443d370d4
--- /dev/null
+++ b/inst/extdata/SE_AGRI/bayeff_newpriors1.ngd
@@ -0,0 +1,112 @@
+Design	Choice situation	alt1.initiator	alt1.funding	alt1.damage	alt1.compensation	alt2.initiator	alt2.funding	alt2.damage	alt2.compensation	Block	
+1	1	1	0	0	30	0	1	1	30	4	
+1	2	2	1	0	10	0	2	1	10	3	
+1	3	1	2	1	10	0	0	0	10	3	
+1	4	0	0	1	10	2	2	0	10	4	
+1	5	1	1	1	2	2	0	0	2	4	
+1	6	1	0	1	2	2	2	0	2	1	
+1	7	2	1	1	20	0	0	0	20	2	
+1	8	0	1	1	5	1	2	0	5	1	
+1	9	2	1	0	15	1	2	1	15	1	
+1	10	1	1	1	30	2	2	0	30	2	
+1	11	0	2	1	5	1	1	0	10	2	
+1	12	0	0	1	20	2	1	0	20	3	
+1	13	2	2	1	2	1	0	0	5	1	
+1	14	0	2	0	30	1	0	1	30	4	
+1	15	1	1	1	20	0	2	0	20	3	
+1	16	1	2	0	30	0	1	1	30	2	
+1	17	0	1	0	2	2	0	1	2	4	
+1	18	0	2	0	5	2	1	1	5	3	
+1	19	0	0	0	30	2	2	1	30	2	
+1	20	0	0	1	2	1	2	0	2	2	
+1	21	1	1	0	5	0	2	1	5	4	
+1	22	2	1	0	5	1	2	1	2	4	
+1	23	2	2	1	10	1	1	0	10	4	
+1	24	0	2	1	15	2	0	0	20	3	
+1	25	1	2	0	15	0	0	1	15	1	
+1	26	2	0	1	15	0	1	0	15	4	
+1	27	2	2	1	20	1	1	0	20	2	
+1	28	0	1	0	15	2	0	1	15	1	
+1	29	1	2	0	30	2	0	1	30	3	
+1	30	1	0	0	20	0	1	1	15	2	
+1	31	2	1	1	2	0	0	0	5	3	
+1	32	0	2	0	20	1	0	1	20	1	
+1	33	2	0	0	5	0	1	1	2	1	
+1	34	1	0	1	15	2	1	0	15	1	
+1	35	2	0	0	10	1	1	1	5	3	
+1	36	2	0	0	10	1	2	1	10	2	
+||||||||||
+design
+;alts = alt1, alt2, alt3
+;rows = 36
+;block = 4
+
+;eff = (mnl,d,mean)
+;rep = 1000
+;bdraws = halton(1000)
+;bseed = 2333344
+;rseed = 2333344
+
+;con
+;model:
+
+
+
+U(alt1) = b0[(n,-1.3,0.5)] + b1.dummy[(n,-0.14,0.2)|(n,-0.18,0.2)] * Initiator[1,2,0] + b2.dummy[(n,0.4,0.4)|(n,0.5,0.5)]  * Funding[1,2,0]  + b3[(n,0.5,0.3)] * Damage [0,1]  + b4[(n,0.45,0.3)] * Compensation[2,5,10,15,20,30] / 
+U(alt2) =  b0 + b1 * Initiator + b2 * Funding + b3 * Damage   + b4 * Compensation
+
+;formatTitle = 'Scenario <scenarionumber>'
+;formatTableDimensions = 3, 6
+;formatTable:
+1,1 = '' /
+1,2 = 'Initiative to join the scheme' /
+1,3 = 'Source of funding for the compensation' /
+1,4 = 'Impact of forest damage on the carbon amount' /
+1,5 = 'Amount of carbon compensation ' /
+1,6 = 'Choice question&:' /
+2,1 = 'alt1' /
+2,2 = '<alt1.initiator>' /
+2,3 = '<alt1.funding>' /
+2,4 = '<alt1.damage>' /
+2,5 = '<alt1.compensation>' /
+2,6 = '' /
+3,1 = 'alt2' /
+3,2 = '<alt2.initiator>' /
+3,3 = '<alt2.funding>' /
+3,4 = '<alt2.damage>' /
+3,5 = '<alt2.compensation>' /
+3,6 = ''
+;formatTableStyle:
+1,1 = 'default' /
+1,2 = 'headingattribute' /
+1,3 = 'headingattribute' /
+1,4 = 'headingattribute' /
+1,5 = 'headingattribute' /
+1,6 = 'headingattribute' /
+2,1 = 'heading1' /
+2,2 = 'body1' /
+2,3 = 'body1' /
+2,4 = 'body1' /
+2,5 = 'body1' /
+2,6 = 'choice1' /
+3,1 = 'heading2' /
+3,2 = 'body2' /
+3,3 = 'body2' /
+3,4 = 'body2' /
+3,5 = 'body2' /
+3,6 = 'choice2'
+;formatStyleSheet = Default.css
+;formatAttributes:
+alt1.initiator(1='A familiar forestry professional ', 2='A forestry expert ', 0='My initiative') /
+alt1.funding(1='Emission offset payments paid by domestic companies', 2='Emission offset payments paid by foreign companies', 0='State tax resources') /
+alt1.damage(0='not taken into account' , 1= 'taken into account') /
+alt1.compensation(2=# EUR, 5=# EUR, 10=# EUR, 15=# EUR, 20=# EUR, 30=# EUR) /
+alt2.initiator(1='A familiar forestry professional ', 2='A forestry expert ', 0='My initiative')  /
+alt2.funding(1='Emission offset payments paid by domestic companies', 2='Emission offset payments paid by foreign companies', 0='State tax resources')  /
+alt2.damage(0='not taken into account' , 1= 'taken into account') /
+alt2.compensation(2=# EUR, 5=# EUR, 10=# EUR, 15=# EUR, 20=# EUR, 30=# EUR)
+
+
+
+
+$
\ No newline at end of file
diff --git a/inst/extdata/SE_AGRI/bayrevised_newpriors1.ngd b/inst/extdata/SE_AGRI/bayrevised_newpriors1.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..fb784a6900a2f13f166ca103ac634461b75537c6
--- /dev/null
+++ b/inst/extdata/SE_AGRI/bayrevised_newpriors1.ngd
@@ -0,0 +1,112 @@
+Design	Choice situation	alt1.initiator	alt1.funding	alt1.damage	alt1.compensation	alt2.initiator	alt2.funding	alt2.damage	alt2.compensation	Block	
+1	1	0	0	0	15	1	1	1	10	2	
+1	2	2	2	0	20	0	0	1	20	4	
+1	3	0	1	0	5	2	0	1	2	3	
+1	4	2	1	1	15	1	2	0	15	1	
+1	5	2	2	1	10	0	1	0	10	1	
+1	6	1	2	1	10	0	1	0	15	2	
+1	7	1	0	0	10	2	2	1	5	2	
+1	8	1	0	0	30	0	2	1	5	4	
+1	9	0	1	0	30	2	0	1	30	3	
+1	10	2	2	1	15	1	0	0	15	1	
+1	11	1	1	1	20	2	0	0	20	2	
+1	12	2	0	1	30	1	2	0	30	3	
+1	13	0	2	0	30	1	0	1	30	1	
+1	14	2	2	0	2	1	0	1	5	1	
+1	15	1	0	1	2	0	1	0	2	1	
+1	16	1	1	1	2	2	0	0	2	4	
+1	17	1	2	0	20	0	1	1	20	4	
+1	18	0	0	1	5	1	1	0	5	1	
+1	19	2	0	0	20	0	1	1	15	4	
+1	20	2	1	1	5	0	2	0	5	4	
+1	21	0	2	1	15	2	0	0	20	4	
+1	22	1	1	0	5	0	0	1	2	3	
+1	23	0	2	1	10	2	1	0	10	4	
+1	24	0	2	1	2	2	0	0	15	3	
+1	25	0	2	0	10	1	1	1	10	3	
+1	26	2	1	1	5	1	2	0	2	4	
+1	27	2	0	0	15	1	2	1	15	2	
+1	28	1	0	0	15	0	2	1	10	3	
+1	29	0	0	1	20	2	1	0	20	2	
+1	30	1	2	0	10	0	1	1	10	1	
+1	31	1	0	1	30	2	1	0	30	3	
+1	32	2	1	0	30	0	0	0	30	2	
+1	33	1	1	0	20	2	2	1	20	1	
+1	34	0	1	1	2	2	2	1	5	2	
+1	35	0	0	0	5	1	2	1	2	2	
+1	36	2	1	1	2	1	2	0	30	3	
+||||||||||
+design
+;alts = alt1, alt2, alt3
+;rows = 36
+;block = 4
+
+;eff = (mnl,d,mean)
+;rep = 1000
+;bdraws = halton(1000)
+;bseed = 2333344
+;rseed = 2333344
+
+;con
+;model:
+
+
+
+U(alt1) = b0[(n,-1.3,0.5)] + b1.dummy[(n,-0.14,0.2)|(n,-0.18,0.2)] * Initiator[1,2,0] + b2.dummy[(n,0.4,0.4)|(n,0.5,0.5)]  * Funding[1,2,0]  + b3[(n,0.5,0.3)] * Damage [0,1]  + b4[(n,0.045,0.3)] * Compensation[2,5,10,15,20,30] / 
+U(alt2) =  b0 + b1 * Initiator + b2 * Funding + b3 * Damage   + b4 * Compensation
+
+;formatTitle = 'Scenario <scenarionumber>'
+;formatTableDimensions = 3, 6
+;formatTable:
+1,1 = '' /
+1,2 = 'Initiative to join the scheme' /
+1,3 = 'Source of funding for the compensation' /
+1,4 = 'Impact of forest damage on the carbon amount' /
+1,5 = 'Amount of carbon compensation ' /
+1,6 = 'Choice question&:' /
+2,1 = 'alt1' /
+2,2 = '<alt1.initiator>' /
+2,3 = '<alt1.funding>' /
+2,4 = '<alt1.damage>' /
+2,5 = '<alt1.compensation>' /
+2,6 = '' /
+3,1 = 'alt2' /
+3,2 = '<alt2.initiator>' /
+3,3 = '<alt2.funding>' /
+3,4 = '<alt2.damage>' /
+3,5 = '<alt2.compensation>' /
+3,6 = ''
+;formatTableStyle:
+1,1 = 'default' /
+1,2 = 'headingattribute' /
+1,3 = 'headingattribute' /
+1,4 = 'headingattribute' /
+1,5 = 'headingattribute' /
+1,6 = 'headingattribute' /
+2,1 = 'heading1' /
+2,2 = 'body1' /
+2,3 = 'body1' /
+2,4 = 'body1' /
+2,5 = 'body1' /
+2,6 = 'choice1' /
+3,1 = 'heading2' /
+3,2 = 'body2' /
+3,3 = 'body2' /
+3,4 = 'body2' /
+3,5 = 'body2' /
+3,6 = 'choice2'
+;formatStyleSheet = Default.css
+;formatAttributes:
+alt1.initiator(1='A familiar forestry professional ', 2='A forestry expert ', 0='My initiative') /
+alt1.funding(1='Emission offset payments paid by domestic companies', 2='Emission offset payments paid by foreign companies', 0='State tax resources') /
+alt1.damage(0='not taken into account' , 1= 'taken into account') /
+alt1.compensation(2=# EUR, 5=# EUR, 10=# EUR, 15=# EUR, 20=# EUR, 30=# EUR) /
+alt2.initiator(1='A familiar forestry professional ', 2='A forestry expert ', 0='My initiative')  /
+alt2.funding(1='Emission offset payments paid by domestic companies', 2='Emission offset payments paid by foreign companies', 0='State tax resources')  /
+alt2.damage(0='not taken into account' , 1= 'taken into account') /
+alt2.compensation(2=# EUR, 5=# EUR, 10=# EUR, 15=# EUR, 20=# EUR, 30=# EUR)
+
+
+
+
+$
\ No newline at end of file
diff --git a/inst/extdata/SE_DRIVE/bayeffdesignconstr.ngd b/inst/extdata/SE_DRIVE/bayeffdesignconstr.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..f862f4f231bd73085cbe82ff0159bab4d771dcad
--- /dev/null
+++ b/inst/extdata/SE_DRIVE/bayeffdesignconstr.ngd
@@ -0,0 +1,150 @@
+Design	Choice situation	alt1.x1	alt1.x2	alt1.x3	alt2.x1	alt2.x2	alt2.x3	Block	
+1	1	20	200	0	40	25	0	7	
+1	2	40	100	0	80	50	25	7	
+1	3	80	100	50	40	100	100	10	
+1	4	20	25	50	40	50	25	6	
+1	5	60	50	50	20	100	50	8	
+1	6	60	25	25	40	200	0	7	
+1	7	80	25	100	60	200	100	1	
+1	8	80	50	0	20	25	100	3	
+1	9	60	100	0	80	25	50	5	
+1	10	60	100	50	20	50	100	9	
+1	11	60	200	50	80	50	25	3	
+1	12	80	50	25	20	50	50	2	
+1	13	20	200	25	60	25	0	8	
+1	14	20	100	50	80	25	100	10	
+1	15	40	25	100	60	100	0	3	
+1	16	80	25	25	40	25	50	2	
+1	17	20	100	50	40	25	0	4	
+1	18	20	100	100	60	50	25	4	
+1	19	20	25	50	60	25	0	1	
+1	20	80	50	50	80	100	0	4	
+1	21	80	25	0	40	200	100	8	
+1	22	40	200	0	20	100	100	7	
+1	23	40	100	50	20	50	100	2	
+1	24	20	200	50	80	50	25	7	
+1	25	80	100	0	40	200	100	7	
+1	26	20	50	25	40	50	0	6	
+1	27	40	50	50	20	100	25	4	
+1	28	40	50	25	60	25	0	5	
+1	29	80	50	0	20	200	0	10	
+1	30	20	100	50	80	50	100	1	
+1	31	60	25	50	20	200	50	8	
+1	32	40	200	25	80	25	0	1	
+1	33	40	200	0	60	100	0	5	
+1	34	80	50	0	60	25	100	8	
+1	35	60	25	0	20	100	25	3	
+1	36	20	100	100	40	25	25	6	
+1	37	60	200	100	80	25	100	3	
+1	38	40	25	25	20	100	25	2	
+1	39	40	200	0	80	100	100	1	
+1	40	20	100	50	80	25	50	2	
+1	41	40	100	25	80	25	50	10	
+1	42	60	100	0	20	200	50	10	
+1	43	60	200	0	80	100	25	9	
+1	44	80	50	0	40	25	25	8	
+1	45	20	100	100	80	100	50	4	
+1	46	60	200	50	80	50	100	5	
+1	47	60	50	0	60	25	25	5	
+1	48	60	50	25	20	50	100	1	
+1	49	60	100	50	20	200	25	8	
+1	50	60	200	100	80	200	25	4	
+1	51	40	50	0	20	200	100	2	
+1	52	60	25	100	80	50	0	3	
+1	53	40	25	50	60	50	25	9	
+1	54	40	200	50	60	25	0	10	
+1	55	40	50	100	80	25	100	5	
+1	56	40	100	50	60	25	50	9	
+1	57	80	50	25	40	50	50	2	
+1	58	80	200	0	60	200	100	5	
+1	59	80	50	0	20	100	50	1	
+1	60	20	100	100	60	25	100	10	
+1	61	60	25	25	20	100	0	2	
+1	62	80	25	0	20	25	25	6	
+1	63	60	50	100	20	200	0	2	
+1	64	20	200	0	60	25	50	7	
+1	65	20	200	50	80	100	100	5	
+1	66	80	25	25	60	25	100	9	
+1	67	60	50	25	20	200	50	8	
+1	68	20	100	100	40	25	0	7	
+1	69	40	25	100	80	100	0	9	
+1	70	20	25	100	40	25	25	6	
+1	71	80	25	50	40	200	25	6	
+1	72	40	50	50	20	100	50	1	
+1	73	80	50	0	40	200	50	5	
+1	74	20	100	25	40	50	0	6	
+1	75	80	25	25	40	200	50	9	
+1	76	80	50	25	20	200	25	10	
+1	77	40	200	0	60	50	100	4	
+1	78	80	25	25	20	100	0	10	
+1	79	20	200	100	80	200	50	7	
+1	80	60	50	100	40	200	0	1	
+1	81	40	100	50	80	50	25	9	
+1	82	40	100	50	60	50	50	9	
+1	83	20	100	50	80	50	25	4	
+1	84	60	25	0	20	200	100	3	
+1	85	20	25	100	80	25	0	4	
+1	86	60	200	25	80	100	100	3	
+1	87	60	100	50	80	25	100	7	
+1	88	60	25	100	40	200	100	8	
+1	89	60	200	100	80	200	50	6	
+1	90	40	50	25	20	100	50	1	
+1	91	80	200	0	60	100	100	6	
+1	92	80	50	50	40	100	25	6	
+1	93	80	25	25	60	200	25	4	
+1	94	60	200	0	80	50	50	6	
+1	95	20	50	25	60	50	0	3	
+1	96	40	25	25	80	25	0	10	
+1	97	40	100	0	20	100	25	10	
+1	98	80	100	0	40	200	25	1	
+1	99	60	100	100	80	25	25	5	
+1	100	40	25	100	20	200	50	3	
+1	101	20	200	50	60	50	50	8	
+1	102	40	200	100	60	50	0	3	
+1	103	40	50	25	20	100	0	2	
+1	104	20	200	25	40	50	0	7	
+1	105	80	25	25	60	100	0	2	
+1	106	40	50	100	40	100	50	9	
+1	107	20	200	50	60	50	0	4	
+1	108	40	100	25	20	200	100	7	
+1	109	80	25	0	60	200	50	6	
+1	110	20	200	0	80	25	0	3	
+1	111	80	50	0	60	50	25	8	
+1	112	60	100	25	40	200	0	4	
+1	113	80	25	100	20	50	100	5	
+1	114	40	200	0	60	50	50	5	
+1	115	40	200	100	80	100	25	2	
+1	116	20	50	100	40	100	25	8	
+1	117	60	100	25	20	200	50	1	
+1	118	20	100	100	40	100	0	9	
+1	119	40	200	100	60	100	50	9	
+1	120	80	25	100	40	200	0	10	
+||||||||||
+design
+;alts = alt1, alt2
+;block = 10
+
+;eff = (mnl,d,mean)
+;rep = 1000
+;bdraws = halton(1000)
+;bseed = 2333344
+;rseed = 2333344
+;alg = swap
+;rows = 120
+
+
+
+;cond:
+if(alt1.x2+alt1.x3 >alt2.x2+alt2.x3   , alt1.x1<alt2.x1),
+if(alt1.x2+alt1.x3 <alt2.x2+alt2.x3   , alt1.x1>alt2.x1),
+if(alt1.x2=alt2.x2  , alt1.x3<>alt2.x3 )
+
+;model:
+U(alt1) = b1[(n,-0.036,0.02)]   * x1[20,40,60,80]
+        + b2[(n,-0.0034,0.002)] * x2[25,50,100,200]
+        + b3[(n,-0.0049,0.003)] * x3[0,25,50,100]
+/
+U(alt2) = b1 * x1
+        + b2 * x2
+        + b3 * x3
+$
\ No newline at end of file
diff --git a/inst/extdata/SE_DRIVE/effconstrsmall.ngd b/inst/extdata/SE_DRIVE/effconstrsmall.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..bea6f37342d60f7bb2b8623e04ee4c4fbfb711b8
--- /dev/null
+++ b/inst/extdata/SE_DRIVE/effconstrsmall.ngd
@@ -0,0 +1,85 @@
+Design	Choice situation	alt1.x1	alt1.x2	alt1.x3	alt2.x1	alt2.x2	alt2.x3	Block	
+1	1	20	100	25	60	100	0	3	
+1	2	80	25	25	40	200	100	5	
+1	3	60	200	50	80	50	25	2	
+1	4	60	25	25	40	50	50	3	
+1	5	20	25	25	40	25	0	2	
+1	6	40	100	100	80	100	25	5	
+1	7	40	200	50	80	200	25	3	
+1	8	60	25	50	20	200	50	3	
+1	9	80	25	100	40	200	50	3	
+1	10	20	50	50	80	50	0	5	
+1	11	60	50	0	20	200	100	2	
+1	12	60	25	0	20	200	100	1	
+1	13	80	100	50	60	200	0	5	
+1	14	40	50	100	60	100	0	3	
+1	15	80	100	100	60	200	0	5	
+1	16	20	100	50	40	50	0	1	
+1	17	20	200	0	80	100	100	1	
+1	18	60	200	25	80	25	50	5	
+1	19	20	200	50	80	50	100	3	
+1	20	40	100	0	20	100	50	2	
+1	21	60	100	25	80	50	25	4	
+1	22	60	100	50	80	50	25	2	
+1	23	80	100	0	40	100	100	2	
+1	24	80	50	50	60	200	100	5	
+1	25	60	50	100	20	200	50	1	
+1	26	80	50	25	40	100	0	4	
+1	27	80	50	100	40	100	50	2	
+1	28	20	25	100	80	25	50	5	
+1	29	20	50	100	80	50	0	1	
+1	30	20	200	50	60	100	50	4	
+1	31	20	200	50	40	100	50	3	
+1	32	40	100	25	80	25	50	1	
+1	33	80	50	100	60	200	25	1	
+1	34	40	50	100	80	25	50	4	
+1	35	40	25	100	20	200	25	3	
+1	36	20	200	25	60	100	0	2	
+1	37	60	50	50	20	200	100	4	
+1	38	80	50	25	60	25	50	5	
+1	39	60	100	0	20	200	0	5	
+1	40	40	200	100	80	25	25	2	
+1	41	20	200	0	60	25	100	5	
+1	42	40	200	50	20	200	100	4	
+1	43	20	50	0	60	25	0	4	
+1	44	20	25	50	80	25	25	4	
+1	45	60	25	25	20	100	100	2	
+1	46	80	25	25	40	200	25	1	
+1	47	60	50	0	40	100	100	1	
+1	48	80	25	25	40	50	25	2	
+1	49	60	25	25	20	50	25	3	
+1	50	40	200	0	60	50	25	4	
+1	51	40	100	0	20	25	100	4	
+1	52	80	50	100	40	100	100	2	
+1	53	20	100	50	40	100	0	5	
+1	54	40	100	0	20	50	50	4	
+1	55	20	50	100	80	100	0	1	
+1	56	40	200	100	60	25	0	3	
+1	57	60	200	25	80	25	0	1	
+1	58	60	25	0	20	50	100	3	
+1	59	60	200	0	80	25	50	1	
+1	60	80	50	50	20	25	100	4	
+||||||||||
+design
+;alts = alt1, alt2
+;block = 5
+;eff = (mnl, d)
+;alg = swap
+;rows = 60
+
+
+
+;cond:
+if(alt1.x2+alt1.x3 >alt2.x2+alt2.x3   , alt1.x1<alt2.x1),
+if(alt1.x2+alt1.x3 <alt2.x2+alt2.x3   , alt1.x1>alt2.x1),
+if(alt1.x2=alt2.x2  , alt1.x3<>alt2.x3 )
+
+;model:
+U(alt1) = b1[-0.036]  * x1[20,40,60,80]
+        + b2[-0.0034] * x2[25,50,100,200]
+        + b3[-0.0049] * x3[0,25,50,100]
+/
+U(alt2) = b1 * x1
+        + b2 * x2
+        + b3 * x3
+$
\ No newline at end of file
diff --git a/inst/extdata/SE_DRIVE/effdesignconstr.ngd b/inst/extdata/SE_DRIVE/effdesignconstr.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..47e6025142d82f07b0751ea92b1d7e5435d81886
--- /dev/null
+++ b/inst/extdata/SE_DRIVE/effdesignconstr.ngd
@@ -0,0 +1,145 @@
+Design	Choice situation	alt1.x1	alt1.x2	alt1.x3	alt2.x1	alt2.x2	alt2.x3	Block	
+1	1	40	50	50	80	25	50	5	
+1	2	20	200	25	40	50	100	6	
+1	3	80	50	0	20	50	100	1	
+1	4	40	50	100	60	100	0	3	
+1	5	60	25	50	20	200	50	1	
+1	6	40	200	100	60	25	100	2	
+1	7	60	100	0	40	200	100	8	
+1	8	60	50	50	40	200	25	10	
+1	9	60	100	100	80	50	0	5	
+1	10	80	25	25	20	200	0	1	
+1	11	20	200	100	60	200	50	7	
+1	12	60	100	100	80	100	50	4	
+1	13	40	50	50	80	25	25	3	
+1	14	80	25	0	40	200	0	2	
+1	15	20	25	50	80	25	25	8	
+1	16	80	25	25	40	50	100	4	
+1	17	40	100	50	60	25	0	2	
+1	18	60	50	25	40	25	50	3	
+1	19	60	50	0	20	200	0	8	
+1	20	60	25	100	80	25	0	6	
+1	21	80	25	50	20	200	25	2	
+1	22	80	25	50	60	100	100	8	
+1	23	40	25	100	60	50	25	7	
+1	24	40	100	100	80	100	50	9	
+1	25	60	25	25	20	200	0	3	
+1	26	80	50	25	20	50	100	10	
+1	27	60	100	0	20	25	100	7	
+1	28	40	50	100	20	200	50	7	
+1	29	20	200	25	80	25	50	8	
+1	30	20	50	100	80	25	0	8	
+1	31	60	50	100	20	100	50	4	
+1	32	40	25	50	60	50	0	2	
+1	33	80	100	0	40	100	25	8	
+1	34	80	25	50	60	50	50	1	
+1	35	60	200	100	80	25	50	10	
+1	36	80	25	0	20	200	25	10	
+1	37	40	50	100	60	50	25	1	
+1	38	60	200	100	80	25	25	7	
+1	39	20	200	25	60	25	25	1	
+1	40	20	200	0	40	50	50	6	
+1	41	20	100	50	60	25	100	7	
+1	42	80	25	25	60	200	50	7	
+1	43	20	50	50	60	50	0	2	
+1	44	20	100	50	40	50	0	5	
+1	45	40	100	0	80	50	50	3	
+1	46	40	200	100	60	25	0	10	
+1	47	40	25	25	20	200	100	1	
+1	48	20	200	100	60	25	100	4	
+1	49	20	100	50	60	50	50	8	
+1	50	60	100	50	40	200	25	7	
+1	51	80	50	0	40	50	100	3	
+1	52	20	100	25	80	25	100	5	
+1	53	40	200	0	60	50	25	1	
+1	54	40	50	50	80	50	25	9	
+1	55	80	100	50	20	200	50	1	
+1	56	60	200	0	80	50	100	3	
+1	57	20	200	0	20	100	100	3	
+1	58	40	25	0	20	100	100	2	
+1	59	20	200	100	40	200	25	8	
+1	60	40	50	25	20	100	0	7	
+1	61	60	25	100	20	100	25	9	
+1	62	40	200	0	80	100	100	5	
+1	63	80	50	25	40	100	100	6	
+1	64	60	50	25	80	50	0	1	
+1	65	80	50	25	40	25	50	10	
+1	66	60	25	25	40	200	50	6	
+1	67	60	25	25	20	25	50	5	
+1	68	20	25	100	60	100	25	4	
+1	69	20	200	25	60	50	0	6	
+1	70	60	100	50	20	100	100	2	
+1	71	40	200	100	80	200	25	4	
+1	72	80	25	100	20	200	100	2	
+1	73	20	25	25	80	25	0	5	
+1	74	60	25	0	40	100	50	9	
+1	75	40	50	50	20	200	100	4	
+1	76	60	25	100	60	100	25	7	
+1	77	80	50	50	20	25	100	9	
+1	78	60	100	50	20	200	50	6	
+1	79	80	25	100	40	100	25	9	
+1	80	40	50	50	20	200	25	8	
+1	81	40	200	0	60	25	100	10	
+1	82	60	25	50	80	50	0	4	
+1	83	20	100	25	80	100	0	2	
+1	84	60	50	0	20	25	100	9	
+1	85	80	50	100	60	100	50	3	
+1	86	80	25	50	20	50	100	4	
+1	87	40	25	100	20	50	100	6	
+1	88	20	100	25	80	50	0	4	
+1	89	40	50	0	60	25	0	5	
+1	90	60	25	50	40	100	50	7	
+1	91	20	25	100	60	50	25	3	
+1	92	80	25	0	60	200	50	2	
+1	93	80	100	0	40	200	25	5	
+1	94	20	100	25	40	50	50	10	
+1	95	20	200	100	80	25	0	5	
+1	96	20	200	100	80	50	0	5	
+1	97	80	200	0	20	100	100	3	
+1	98	60	100	25	40	200	0	1	
+1	99	20	25	100	60	50	50	10	
+1	100	40	200	50	60	200	0	9	
+1	101	60	50	0	20	50	100	8	
+1	102	60	200	50	40	200	100	8	
+1	103	20	200	25	40	25	0	4	
+1	104	40	100	0	20	100	50	6	
+1	105	40	50	0	20	100	25	9	
+1	106	60	100	50	80	100	0	6	
+1	107	60	25	25	20	200	25	10	
+1	108	60	100	50	40	50	100	2	
+1	109	80	100	0	20	100	50	9	
+1	110	20	100	0	80	25	50	10	
+1	111	80	50	0	60	200	25	9	
+1	112	60	200	100	80	50	25	6	
+1	113	20	200	0	40	25	100	1	
+1	114	20	200	0	80	100	50	9	
+1	115	20	200	50	40	50	100	4	
+1	116	80	100	25	20	100	100	7	
+1	117	40	200	25	80	25	25	3	
+1	118	80	50	25	40	200	50	5	
+1	119	20	100	100	80	50	0	6	
+1	120	80	25	25	40	100	25	10	
+||||||||||
+design
+;alts = alt1, alt2
+;block = 10
+;eff = (mnl, d)
+;alg = swap
+;rows = 120
+
+
+
+;cond:
+if(alt1.x2+alt1.x3 >alt2.x2+alt2.x3   , alt1.x1<alt2.x1),
+if(alt1.x2+alt1.x3 <alt2.x2+alt2.x3   , alt1.x1>alt2.x1),
+if(alt1.x2=alt2.x2  , alt1.x3<>alt2.x3 )
+
+;model:
+U(alt1) = b1[-0.036]  * x1[20,40,60,80]
+        + b2[-0.0034] * x2[25,50,100,200]
+        + b3[-0.0049] * x3[0,25,50,100]
+/
+U(alt2) = b1 * x1
+        + b2 * x2
+        + b3 * x3
+$
\ No newline at end of file
diff --git a/inst/extdata/SE_DRIVE/effdesignnorestr.ngd b/inst/extdata/SE_DRIVE/effdesignnorestr.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..77658242e2eb0f8ef3d66d88d0755956148ce458
--- /dev/null
+++ b/inst/extdata/SE_DRIVE/effdesignnorestr.ngd
@@ -0,0 +1,138 @@
+Design	Choice situation	alt1.x1	alt1.x2	alt1.x3	alt2.x1	alt2.x2	alt2.x3	Block	
+1	1	60	200	100	80	25	0	10	
+1	2	40	25	0	20	200	100	8	
+1	3	40	200	100	60	25	0	9	
+1	4	60	25	0	20	200	100	9	
+1	5	80	25	0	40	200	100	4	
+1	6	80	25	100	40	200	0	7	
+1	7	40	200	100	60	50	0	6	
+1	8	20	200	0	60	25	100	6	
+1	9	80	50	0	60	200	100	1	
+1	10	20	200	100	40	50	0	5	
+1	11	40	25	100	20	200	0	2	
+1	12	60	25	100	40	200	0	1	
+1	13	20	200	100	80	25	0	1	
+1	14	40	25	100	80	200	0	9	
+1	15	80	25	100	20	200	0	5	
+1	16	20	25	100	60	200	0	3	
+1	17	40	200	0	80	50	100	8	
+1	18	80	50	0	40	200	100	5	
+1	19	60	25	100	80	200	0	6	
+1	20	20	200	0	60	50	100	4	
+1	21	60	50	0	20	200	100	5	
+1	22	60	200	0	40	25	100	2	
+1	23	20	25	100	40	200	0	3	
+1	24	60	25	25	40	200	100	7	
+1	25	80	50	0	20	200	100	10	
+1	26	80	50	100	20	200	0	9	
+1	27	40	25	25	20	200	100	5	
+1	28	60	200	0	60	25	100	7	
+1	29	60	200	100	80	25	25	8	
+1	30	20	200	25	80	25	100	8	
+1	31	80	200	0	20	25	100	3	
+1	32	60	200	0	20	50	100	6	
+1	33	20	200	100	80	25	25	7	
+1	34	60	100	100	20	200	0	6	
+1	35	40	50	100	80	200	0	10	
+1	36	80	100	100	40	200	0	9	
+1	37	40	200	25	80	25	100	4	
+1	38	80	25	25	40	200	100	5	
+1	39	20	25	100	60	200	25	9	
+1	40	60	25	100	20	200	25	8	
+1	41	60	25	25	20	200	100	6	
+1	42	20	200	0	20	25	100	4	
+1	43	80	25	100	80	200	0	2	
+1	44	60	25	100	20	50	0	7	
+1	45	40	50	0	80	25	100	7	
+1	46	20	50	100	80	200	0	4	
+1	47	20	100	0	60	25	100	5	
+1	48	40	25	50	80	200	0	10	
+1	49	40	25	100	40	200	0	6	
+1	50	40	100	0	80	25	100	6	
+1	51	60	50	100	20	100	0	2	
+1	52	20	200	100	80	50	25	2	
+1	53	60	200	0	20	25	50	10	
+1	54	60	200	0	80	50	100	5	
+1	55	40	25	100	80	200	50	7	
+1	56	20	200	100	80	100	0	3	
+1	57	40	200	0	60	50	100	3	
+1	58	60	200	50	20	25	100	4	
+1	59	20	25	50	60	200	25	10	
+1	60	80	25	0	20	200	50	6	
+1	61	40	25	50	80	200	25	9	
+1	62	20	200	100	80	25	50	3	
+1	63	40	50	100	60	200	0	8	
+1	64	20	200	0	80	100	100	6	
+1	65	40	200	0	20	50	100	3	
+1	66	80	50	25	60	200	100	6	
+1	67	80	200	0	60	50	100	3	
+1	68	60	200	0	20	25	25	10	
+1	69	40	50	25	20	200	100	7	
+1	70	80	50	100	20	200	25	1	
+1	71	60	200	100	80	100	0	1	
+1	72	40	25	25	80	200	0	2	
+1	73	60	100	0	40	200	100	1	
+1	74	80	25	100	60	200	0	5	
+1	75	20	200	50	80	25	100	10	
+1	76	60	200	25	40	25	100	10	
+1	77	40	100	0	20	200	100	9	
+1	78	20	200	0	80	25	50	3	
+1	79	20	100	100	80	25	0	2	
+1	80	40	200	25	20	25	100	7	
+1	81	60	25	100	80	200	25	1	
+1	82	40	200	100	60	50	25	2	
+1	83	40	200	100	80	50	25	3	
+1	84	80	25	100	20	100	0	4	
+1	85	40	25	100	80	200	25	7	
+1	86	60	100	0	20	200	100	5	
+1	87	40	200	25	80	50	100	7	
+1	88	80	200	25	20	25	100	8	
+1	89	80	100	0	40	200	100	2	
+1	90	60	50	100	20	200	25	4	
+1	91	40	50	100	80	200	25	3	
+1	92	60	50	25	20	200	100	8	
+1	93	60	200	25	20	50	100	1	
+1	94	80	200	0	80	50	100	10	
+1	95	80	200	0	20	100	100	10	
+1	96	40	100	0	80	50	100	1	
+1	97	40	200	0	40	50	100	1	
+1	98	80	25	0	60	200	50	2	
+1	99	20	100	0	80	50	100	8	
+1	100	60	25	0	20	200	50	1	
+1	101	20	200	0	20	50	100	6	
+1	102	20	200	0	40	50	100	4	
+1	103	20	200	50	80	25	25	2	
+1	104	80	200	25	20	50	100	2	
+1	105	60	200	0	60	50	100	9	
+1	106	40	25	50	20	200	100	1	
+1	107	20	50	0	80	25	100	4	
+1	108	20	25	100	80	100	0	3	
+1	109	20	200	100	60	25	50	10	
+1	110	40	25	0	20	200	50	4	
+1	111	60	200	0	20	100	100	5	
+1	112	80	25	25	20	200	0	8	
+1	113	40	100	100	80	200	0	9	
+1	114	40	200	100	60	25	50	7	
+1	115	80	25	50	20	200	25	9	
+1	116	20	25	100	80	200	50	8	
+1	117	60	100	100	40	200	0	5	
+1	118	20	100	100	80	50	0	8	
+1	119	40	200	50	60	25	0	9	
+1	120	20	25	50	80	200	0	4	
+||||||||||
+design
+;alts = alt1*, alt2*
+;block = 10
+;eff = (mnl, d)
+;alg = mfederov
+;rows = 120
+
+;model:
+U(alt1) = b1[-0.036]  * x1[20,40,60,80]
+        + b2[-0.0034] * x2[25,50,100,200]
+        + b3[-0.0049] * x3[0,25,50,100]
+/
+U(alt2) = b1 * x1
+        + b2 * x2
+        + b3 * x3
+$
\ No newline at end of file
diff --git a/inst/extdata/SE_DRIVE/olddesign.ngd b/inst/extdata/SE_DRIVE/olddesign.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..ae5072f1abdc9bc1443026b8f13792bdae01fd6a
--- /dev/null
+++ b/inst/extdata/SE_DRIVE/olddesign.ngd
@@ -0,0 +1,121 @@
+"Choice situation"	"Block"	"alt1.x1"	"alt2.x1"	"alt1.x2"	"alt2.x2"	"alt1.x3"	"alt2.x3"	"Design"
+97	9	20	40	200	25	100	0	1
+98	9	40	60	200	25	100	0	1
+99	9	20	80	200	25	100	25	1
+100	9	20	40	200	50	25	50	1
+101	9	80	60	25	100	25	50	1
+102	9	40	80	100	25	100	0	1
+106	9	60	20	25	100	100	50	1
+105	9	20	40	100	100	100	50	1
+104	9	20	40	50	25	100	100	1
+103	9	80	20	25	200	100	100	1
+108	9	80	40	50	200	50	25	1
+107	9	40	20	50	25	25	100	1
+49	5	80	40	50	25	50	100	1
+50	5	60	40	50	100	50	25	1
+51	5	60	20	50	100	25	50	1
+52	5	60	40	100	100	0	50	1
+53	5	20	80	100	50	50	50	1
+54	5	60	20	50	100	0	50	1
+58	5	40	80	25	100	100	0	1
+57	5	60	20	25	50	0	25	1
+56	5	80	20	100	200	0	25	1
+55	5	40	60	200	50	50	0	1
+60	5	40	20	25	200	50	25	1
+59	5	80	60	25	200	0	0	1
+37	4	20	60	200	100	100	100	1
+38	4	60	80	200	100	0	50	1
+39	4	40	80	200	25	25	0	1
+40	4	80	20	25	100	50	0	1
+41	4	80	40	25	50	100	100	1
+42	4	60	20	50	25	0	100	1
+46	4	60	20	100	200	25	0	1
+45	4	80	60	25	200	0	50	1
+44	4	20	80	50	25	25	25	1
+43	4	40	60	100	100	50	25	1
+48	4	80	20	50	200	25	0	1
+47	4	40	60	50	100	100	25	1
+109	10	80	40	25	200	100	0	1
+110	10	60	20	25	200	50	50	1
+111	10	60	40	25	200	100	25	1
+112	10	40	80	200	100	50	0	1
+113	10	40	60	200	25	100	50	1
+114	10	40	80	100	25	50	50	1
+118	10	40	20	200	200	25	50	1
+117	10	60	80	50	50	100	50	1
+116	10	80	60	25	50	50	50	1
+115	10	80	40	50	100	25	25	1
+120	10	20	80	50	50	50	0	1
+119	10	20	60	25	25	100	50	1
+85	8	20	40	100	50	25	25	1
+86	8	20	60	200	50	25	50	1
+87	8	80	20	50	200	50	25	1
+88	8	60	80	50	25	50	0	1
+89	8	40	20	25	200	50	100	1
+90	8	40	60	100	25	25	25	1
+94	8	40	80	200	25	0	0	1
+93	8	80	40	25	25	0	25	1
+92	8	20	60	200	100	0	50	1
+91	8	60	80	200	100	50	0	1
+96	8	40	20	50	200	0	100	1
+95	8	40	20	50	100	50	50	1
+61	6	40	20	25	100	0	100	1
+62	6	80	60	25	100	50	25	1
+63	6	20	40	50	50	50	25	1
+64	6	80	60	50	100	50	50	1
+65	6	60	40	25	25	0	100	1
+66	6	80	60	50	200	50	0	1
+70	6	60	20	25	50	0	0	1
+69	6	80	40	25	200	25	0	1
+68	6	60	20	25	50	0	50	1
+67	6	80	20	50	200	50	0	1
+72	6	40	60	100	50	50	0	1
+71	6	20	60	200	200	50	0	1
+73	7	80	20	25	200	50	50	1
+74	7	40	60	200	25	50	100	1
+75	7	40	60	50	50	25	0	1
+76	7	40	60	200	25	25	25	1
+77	7	20	80	100	100	50	0	1
+78	7	20	80	25	50	100	0	1
+82	7	20	80	200	25	25	0	1
+81	7	80	40	25	200	25	100	1
+80	7	20	40	50	100	100	0	1
+79	7	40	80	200	100	50	100	1
+84	7	60	20	25	50	0	100	1
+83	7	40	60	200	100	25	25	1
+25	3	20	80	200	25	50	25	1
+26	3	80	60	50	100	25	25	1
+27	3	20	40	100	25	0	50	1
+28	3	60	80	25	25	100	0	1
+29	3	80	60	25	25	0	25	1
+30	3	40	60	200	25	0	100	1
+34	3	60	20	200	200	0	25	1
+33	3	40	20	200	200	0	50	1
+32	3	80	60	25	200	25	25	1
+31	3	40	80	100	50	100	25	1
+36	3	60	80	200	200	100	50	1
+35	3	20	40	100	50	100	0	1
+13	2	40	80	200	50	25	0	1
+14	2	40	60	100	25	100	50	1
+15	2	80	40	100	100	0	25	1
+16	2	60	20	25	50	25	25	1
+17	2	20	40	200	25	50	50	1
+18	2	60	40	50	100	25	100	1
+22	2	20	80	25	25	100	50	1
+21	2	20	80	200	100	100	50	1
+20	2	20	40	50	50	100	25	1
+19	2	80	40	25	25	25	100	1
+24	2	40	20	100	200	50	50	1
+23	2	40	20	50	200	100	0	1
+1	1	80	20	25	200	100	50	1
+2	1	60	40	50	100	50	100	1
+3	1	60	20	200	200	0	100	1
+4	1	20	80	200	25	0	100	1
+5	1	40	80	100	50	100	50	1
+6	1	60	80	50	25	0	0	1
+10	1	40	60	50	25	100	0	1
+9	1	80	40	100	200	100	25	1
+8	1	40	20	25	25	25	100	1
+7	1	20	60	25	25	100	0	1
+12	1	20	60	200	25	50	100	1
+11	1	20	60	200	25	50	0	1
diff --git a/inst/extdata/SVAB/SVAB_simulation_DesignType1_test.ngd b/inst/extdata/SVAB/SVAB_simulation_DesignType1_test.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..cb3e2e6f9cfddb0359630566c9b6820e4d491965
--- /dev/null
+++ b/inst/extdata/SVAB/SVAB_simulation_DesignType1_test.ngd
@@ -0,0 +1,76 @@
+Design	Choice situation	alt1.distance	alt1.subssite	alt1.biotopearea	alt1.biotopequality	alt1.acreageexisting	alt1.acreagenew	alt1.quality	alt1.cost	alt2.distance	alt2.subssite	alt2.biotopearea	alt2.biotopequality	alt2.acreageexisting	alt2.acreagenew	alt2.quality	alt2.cost	alt3.distance	alt3.subssite	alt3.biotopearea	alt3.biotopequality	alt3.acreageexisting	alt3.acreagenew	alt3.quality	alt3.cost	Block	
+1	1	0.2	0.875	0.375	0.125	0.625	0.125	0.125	0.125	0.06	0.125	0.625	0.375	0.375	0.625	0.625	0.625	0.2	0.875	0.625	0.375	0	0	0.875	0.875	1	
+1	2	0.02	0.375	0.625	0.625	0.625	0.625	0.875	0.875	0.2	0.375	0.625	0.375	0.375	0.375	0.125	0.125	0.66	0.625	0.375	0.125	0.375	0.375	0.375	0.625	3	
+1	3	0.02	0.625	0.875	0.375	0.875	0.375	0.625	0.875	0.06	0.125	0.625	0.125	0	0.625	0.875	0.375	0.02	0.875	0.125	0.875	0.625	0	0.125	0.125	4	
+1	4	0.2	0.625	0.125	0.375	0	0.875	0.125	0.125	0.06	0.125	0.875	0.375	0.125	0.125	0.875	0.375	0.2	0.375	0.375	0.625	0.375	0.375	0.125	0.875	3	
+1	5	0.06	0.625	0.875	0.375	0.625	0.625	0.875	0.625	0.02	0.625	0.375	0.125	0.375	0.625	0.625	0.625	0.66	0.375	0.125	0.875	0	0	0.125	0.875	1	
+1	6	0.02	0.125	0.125	0.125	0.125	0	0.125	0.625	0.66	0.875	0.875	0.625	0.625	0	0.125	0.375	0.06	0.625	0.625	0.625	0	0.625	0.875	0.875	4	
+1	7	0.2	0.875	0.125	0.625	0	0.625	0.125	0.625	0.2	0.375	0.125	0.875	0.125	0.125	0.625	0.375	0.06	0.625	0.625	0.125	0.875	0.625	0.375	0.375	2	
+1	8	0.06	0.375	0.625	0.375	0.375	0.625	0.625	0.625	0.66	0.375	0.375	0.875	0.875	0.875	0.625	0.125	0.2	0.625	0.625	0.375	0.375	0.125	0.625	0.625	2	
+1	9	0.66	0.625	0.875	0.125	0.375	0.125	0.375	0.625	0.2	0.125	0.125	0.625	0	0.125	0.125	0.375	0.06	0.875	0.125	0.875	0.625	0.875	0.875	0.375	4	
+1	10	0.06	0.625	0.625	0.375	0.625	0.125	0.375	0.875	0.66	0.375	0.125	0.125	0.625	0	0.375	0.125	0.02	0.125	0.875	0.875	0.125	0.875	0.625	0.125	3	
+1	11	0.06	0.375	0.875	0.125	0.125	0.125	0.125	0.875	0.66	0.125	0.625	0.875	0.875	0.125	0.625	0.875	0.02	0.875	0.125	0.625	0.625	0.125	0.875	0.125	1	
+1	12	0.66	0.625	0.125	0.875	0.125	0.375	0.375	0.875	0.06	0.875	0.875	0.125	0.375	0	0.125	0.375	0.02	0.125	0.875	0.375	0.875	0.875	0.625	0.125	1	
+1	13	0.06	0.875	0.375	0.875	0.875	0.875	0.375	0.375	0.66	0.875	0.125	0.875	0.125	0	0.875	0.125	0.2	0.375	0.875	0.125	0	0.375	0.125	0.875	2	
+1	14	0.06	0.875	0.125	0.125	0.875	0.875	0.625	0.375	0.2	0.625	0.875	0.375	0	0.375	0.625	0.625	0.06	0.125	0.375	0.875	0.125	0	0.125	0.375	4	
+1	15	0.02	0.375	0.625	0.875	0.125	0	0.375	0.125	0.66	0.875	0.125	0.125	0.625	0.375	0.375	0.875	0.02	0.125	0.625	0.625	0.625	0.625	0.875	0.375	4	
+1	16	0.66	0.125	0.875	0.875	0.375	0.875	0.125	0.375	0.02	0.625	0.375	0.125	0	0.125	0.875	0.625	0.02	0.375	0.375	0.375	0.875	0.375	0.375	0.375	1	
+1	17	0.66	0.125	0.375	0.625	0	0.875	0.625	0.125	0.02	0.875	0.625	0.375	0.875	0.125	0.625	0.125	0.2	0.625	0.875	0.375	0	0.125	0.125	0.875	4	
+1	18	0.66	0.125	0.625	0.875	0	0.375	0.625	0.125	0.2	0.375	0.125	0.375	0.875	0.375	0.375	0.875	0.06	0.875	0.625	0.375	0.375	0.125	0.375	0.625	3	
+1	19	0.02	0.375	0.625	0.125	0.125	0.375	0.875	0.375	0.02	0.625	0.375	0.875	0.625	0	0.375	0.875	0.06	0.375	0.125	0.875	0.125	0.125	0.375	0.625	1	
+1	20	0.02	0.875	0.375	0.625	0	0.375	0.375	0.125	0.02	0.125	0.125	0.375	0	0.375	0.375	0.375	0.66	0.375	0.875	0.625	0.875	0.625	0.375	0.875	1	
+1	21	0.66	0.375	0.625	0.375	0.875	0.125	0.375	0.375	0.02	0.875	0.875	0.625	0.125	0.875	0.875	0.875	0.2	0.375	0.375	0.375	0.125	0	0.125	0.125	2	
+1	22	0.06	0.625	0.875	0.625	0.125	0.125	0.875	0.125	0.2	0.625	0.375	0.375	0.375	0.875	0.375	0.125	0.02	0.125	0.375	0.625	0.625	0.375	0.375	0.875	2	
+1	23	0.02	0.125	0.125	0.625	0.625	0.625	0.625	0.875	0.66	0.125	0.875	0.125	0.125	0.375	0.625	0.125	0.06	0.875	0.875	0.625	0.125	0.125	0.875	0.375	1	
+1	24	0.2	0.875	0.375	0.875	0.875	0	0.875	0.375	0.02	0.375	0.625	0.625	0	0.625	0.375	0.625	0.2	0.125	0.125	0.125	0.625	0.875	0.625	0.625	3	
+1	25	0.06	0.625	0.375	0.875	0	0	0.375	0.625	0.06	0.625	0.375	0.625	0.625	0.875	0.875	0.625	0.66	0.625	0.875	0.375	0.375	0.625	0.625	0.625	2	
+1	26	0.02	0.125	0.625	0.375	0.375	0.625	0.125	0.875	0.2	0.625	0.625	0.875	0.875	0	0.875	0.375	0.66	0.125	0.125	0.625	0	0.875	0.875	0.625	3	
+1	27	0.2	0.125	0.375	0.625	0.625	0	0.875	0.875	0.06	0.375	0.375	0.125	0.625	0.625	0.125	0.625	0.02	0.875	0.625	0.875	0	0.875	0.625	0.125	2	
+1	28	0.66	0.125	0.375	0.125	0.875	0.125	0.625	0.125	0.66	0.875	0.875	0.875	0.375	0.875	0.125	0.875	0.06	0.625	0.125	0.125	0.125	0.125	0.625	0.625	2	
+1	29	0.66	0.875	0.125	0.625	0.375	0.875	0.625	0.625	0.06	0.625	0.875	0.625	0.125	0.125	0.125	0.125	0.66	0.125	0.375	0.125	0.875	0	0.625	0.375	3	
+1	30	0.2	0.375	0.875	0.875	0.125	0	0.125	0.625	0.06	0.875	0.125	0.625	0.125	0.875	0.375	0.875	0.66	0.375	0.625	0.125	0.375	0	0.875	0.125	4	
+1	31	0.2	0.875	0.875	0.375	0	0.375	0.875	0.375	0.2	0.125	0.375	0.875	0.875	0	0.875	0.875	0.2	0.625	0.375	0.125	0.125	0.625	0.375	0.375	3	
+1	32	0.2	0.375	0.125	0.125	0.375	0	0.875	0.375	0.02	0.375	0.625	0.625	0	0.625	0.125	0.625	0.66	0.875	0.875	0.875	0.875	0.375	0.125	0.125	4	
+||||||||||
+Design
+
+;bseed=12345
+;rseed=12345
+
+
+;alts  = Alt1, Alt2, Alt3, sq
+;rows = 32
+;block = 4
+;eff= (mnl,d) 
+
+;model:
+U(Alt1)= basc[0.5]                                                                          +
+         bdist[-0.01]            *DISTANCE[0.02,0.06,0.2,0.66]                              + 
+         bsubssite[-0.1]        *SUBSSITE[0.125 , 0.375 , 0.625 , 0.875]                  +
+         bbiotopearea[0.1]      *BIOTOPEAREA [0.125 , 0.375 , 0.625 , 0.875]              + 
+         bbiotopequality[0.1]   *BIOTOPEQUALITY [0.125 , 0.375 , 0.625 , 0.875]           + 
+         bacreexist[0.04]       *ACREAGEEXISTING [0, 0.125 , 0.375 , 0.625 , 0.875]       + 
+         bacrenew[0.08]         *ACREAGENEW [0, 0.125 , 0.375 , 0.625 , 0.875]            +         
+         bquality[0.1]           *QUALITY[0.125 , 0.375 , 0.625 , 0.875]                    + 
+         bcost[-0.01]            *COST[0.125 , 0.375 , 0.625 , 0.875]                       /
+
+U(Alt2)= basc                                                                +
+         bdist                   *DISTANCE                                   + 
+         bsubssite              *SUBSSITE                                  +
+         bbiotopearea           *BIOTOPEAREA                               +
+         bbiotopequality        *BIOTOPEQUALITY                            + 
+         bacreexist             *ACREAGEEXISTING                           +
+         bacrenew               *ACREAGENEW                                +
+         bquality                *QUALITY                                    +
+         bcost                   *COST                                       /
+
+
+U(Alt3)= basc                                                                +
+         bdist                   *DISTANCE                                   + 
+         bsubssite              *SUBSSITE                                  +
+         bbiotopearea           *BIOTOPEAREA                               +
+         bbiotopequality        *BIOTOPEQUALITY                            + 
+         bacreexist             *ACREAGEEXISTING                           +
+         bacrenew               *ACREAGENEW                                +
+         bquality                *QUALITY                                    +
+         bcost                   *COST                                       $
\ No newline at end of file
diff --git a/inst/extdata/feedadditives/effcont.ngd b/inst/extdata/feedadditives/effcont.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..af8ddbf77ecc8fd7542e0a507cd9dfb828589bac
--- /dev/null
+++ b/inst/extdata/feedadditives/effcont.ngd
@@ -0,0 +1,44 @@
+Design	Choice situation	alt1.cow	alt1.adv	alt1.vet	alt1.far	alt1.met	alt1.bon	alt2.cow	alt2.adv	alt2.vet	alt2.far	alt2.met	alt2.bon	Block	
+1	1	1	1	1	1	1	1	1	0	0	0	3	7	2	
+1	2	1	1	1	0	2	6	0	0	1	1	2	1	2	
+1	3	0	1	0	1	3	0	0	0	1	0	0	4	2	
+1	4	1	0	1	0	1	2	1	1	0	1	2	7	1	
+1	5	0	0	0	0	1	3	1	1	0	1	3	2	2	
+1	6	1	1	1	1	0	5	0	0	1	0	4	3	1	
+1	7	0	1	0	1	4	2	1	0	1	0	0	6	1	
+1	8	0	0	0	0	2	7	0	1	1	1	2	0	2	
+1	9	0	0	1	1	3	6	1	1	0	0	1	2	2	
+1	10	1	0	0	0	4	3	0	1	1	1	0	6	1	
+1	11	1	0	0	1	0	4	0	1	0	0	4	5	1	
+1	12	1	1	0	0	0	4	1	0	1	1	4	4	2	
+1	13	0	1	1	0	3	5	1	0	0	1	1	3	1	
+1	14	0	1	1	0	2	0	0	0	0	1	1	0	1	
+1	15	0	0	0	1	0	7	1	1	1	0	3	1	1	
+1	16	1	0	1	1	4	1	0	1	0	0	0	5	2	
+||||||||||
+design  
+ ;alts = alt1*, alt2*, alt3  
+ ;eff = (mnl, d)  
+ ;alg = swap  
+ ;rows = 16  
+ ;block = 2  
+ ;model:  
+ U(alt1) = b1[0.2] * COW[0,1]    
+         + b2[0.2] * ADV[0,1]    
+         + b3[0.2] * VET[0,1]    
+         + b4[0.2] * FAR[0,1]    
+         + b5[0.1] * MET[0,1,2,3,4]      
+         + b6[0.2] * BON[0,1,2,3,4,5,6,7]           
+         + i1[0] * COW.dummy[0] * VET.dummy[1]  
+ /  
+ U(alt2) = b1 * COW  
+         + b2 * ADV  
+         + b3 * VET  
+         + b4 * FAR  
+         + b5 * MET      
+         + b6 * BON     
+         + i1 * COW.dummy[0] * VET.dummy[1]  
+/  
+U(alt3) = asc3[0.2]  
+;
+$
\ No newline at end of file
diff --git a/inst/extdata/feedadditives/effdummynew.ngd b/inst/extdata/feedadditives/effdummynew.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..54f9add5215e934e31b4409d10d16ab7a6d4ae48
--- /dev/null
+++ b/inst/extdata/feedadditives/effdummynew.ngd
@@ -0,0 +1,44 @@
+Design	Choice situation	alt1.cow	alt1.adv	alt1.vet	alt1.far	alt1.met	alt1.bon	alt2.cow	alt2.adv	alt2.vet	alt2.far	alt2.met	alt2.bon	Block	
+1	1	1	0	1	0	1	5	0	1	1	1	3	3	2	
+1	2	1	1	1	1	0	2	1	0	0	0	3	7	2	
+1	3	0	1	0	1	2	7	1	0	0	0	0	6	1	
+1	4	0	1	0	0	1	4	0	0	1	1	2	5	1	
+1	5	1	1	1	0	0	4	0	0	0	1	1	2	2	
+1	6	0	0	1	1	2	6	1	1	0	0	0	5	2	
+1	7	0	0	0	0	2	3	1	1	1	1	1	0	2	
+1	8	0	0	1	0	0	7	1	1	0	1	2	4	1	
+1	9	1	1	1	0	3	6	0	0	1	1	1	4	1	
+1	10	0	1	0	1	0	0	1	0	1	0	3	1	1	
+1	11	1	0	1	0	2	0	0	1	0	1	0	6	1	
+1	12	1	0	1	1	1	3	0	1	1	0	2	1	1	
+1	13	0	0	0	1	3	1	1	1	0	0	2	2	1	
+1	14	1	1	0	1	1	1	0	0	1	0	3	0	2	
+1	15	0	1	0	0	3	5	1	0	0	1	0	7	2	
+1	16	1	0	0	1	3	2	0	1	1	0	1	3	2	
+||||||||||
+design  
+ ;alts = alt1*, alt2*, alt3  
+ ;eff = (mnl, d)  
+ ;alg = swap  
+ ;rows = 16  
+ ;block = 2  
+ ;model:  
+ U(alt1) = b1[0.2] * COW[0,1]    
+         + b2[0.2] * ADV[0,1]    
+         + b3[0.2] * VET[0,1]    
+         + b4[0.2] * FAR[0,1]    
+         + b5.dummy[0.1|0.2|0.3] * MET[1,2,3,0]      
+         + b6.dummy[0.3|0.5|0.65|0.75|0.8|0.83|0.85] * BON[1,2,3,4,5,6,7,0]           
+         + i1[0] * COW.dummy[0] * VET.dummy[1]  
+ /  
+ U(alt2) = b1 * COW  
+         + b2 * ADV  
+         + b3 * VET  
+         + b4 * FAR  
+         + b5 * MET      
+         + b6 * BON     
+         + i1 * COW.dummy[0] * VET.dummy[1]  
+/  
+ U(alt3) = asc3[0.2]  
+;
+$
\ No newline at end of file
diff --git a/inst/extdata/feedadditives/effdummyold.ngd b/inst/extdata/feedadditives/effdummyold.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..d60e4d6a9352c77c04a02ff6b280fa7c45fdc585
--- /dev/null
+++ b/inst/extdata/feedadditives/effdummyold.ngd
@@ -0,0 +1,44 @@
+Design	Choice situation	alt1.cow	alt1.adv	alt1.vet	alt1.far	alt1.met	alt1.bon	alt2.cow	alt2.adv	alt2.vet	alt2.far	alt2.met	alt2.bon	Block	
+1	1	0	1	1	1	3	6	1	0	1	0	1	0	2	
+1	2	1	0	0	1	0	7	0	1	0	0	1	2	2	
+1	3	1	0	0	1	1	1	1	1	1	0	3	5	2	
+1	4	0	0	1	1	3	0	0	1	0	0	2	3	1	
+1	5	0	0	1	0	2	4	0	1	0	1	1	7	2	
+1	6	1	1	0	1	2	0	0	0	1	0	1	5	2	
+1	7	1	0	1	0	2	3	0	1	0	1	0	4	1	
+1	8	0	0	0	1	0	5	0	1	1	0	2	7	1	
+1	9	1	1	0	0	0	2	0	0	0	1	2	0	1	
+1	10	1	1	1	0	1	4	0	0	0	1	0	2	2	
+1	11	0	1	1	0	0	1	1	0	0	1	3	4	2	
+1	12	1	1	0	0	1	6	1	0	1	1	3	1	1	
+1	13	0	0	1	1	1	2	1	1	0	0	3	1	1	
+1	14	1	1	0	1	2	5	1	0	1	0	0	6	1	
+1	15	0	0	0	0	3	7	1	1	1	1	0	3	2	
+1	16	0	1	1	0	3	3	1	0	1	1	2	6	1	
+||||||||||
+design  
+ ;alts = alt1*, alt2*, alt3  
+ ;eff = (mnl, d)  
+ ;alg = swap  
+ ;rows = 16  
+ ;block = 2  
+ ;model:  
+ U(alt1) = b1[0.3] * COW[0,1]    
+         + b2[0.3] * ADV[0,1]    
+         + b3[0.3] * VET[0,1]    
+         + b4[0.3] * FAR[0,1]    
+         + b5.dummy[0.3|0.3|0.3] * MET[1,2,3,0]      
+         + b6.dummy[0.6|0.3|0.3|0.3|0.3|0.3|0.3] * BON[1,2,3,4,5,6,7,0]           
+         + i1[0] * COW.dummy[0] * VET.dummy[1]  
+ /  
+ U(alt2) = b1 * COW  
+         + b2 * ADV  
+         + b3 * VET  
+         + b4 * FAR  
+         + b5 * MET      
+         + b6 * BON     
+         + i1 * COW.dummy[0] * VET.dummy[1]  
+/  
+ U(alt3) = asc3[0]  
+;
+$
\ No newline at end of file
diff --git a/inst/extdata/feedadditives/orth.ngd b/inst/extdata/feedadditives/orth.ngd
new file mode 100644
index 0000000000000000000000000000000000000000..ca0d0aa4e1fc6a468c96165c77525759eab5e786
--- /dev/null
+++ b/inst/extdata/feedadditives/orth.ngd
@@ -0,0 +1,91 @@
+Design	Choice situation	alt1.cow	alt1.adv	alt1.vet	alt1.far	alt1.met	alt1.bon	alt2.cow	alt2.adv	alt2.vet	alt2.far	alt2.met	alt2.bon	Block	
+1	1	0	0	0	0	0	1	1	0	1	0	3	0	8	
+1	2	0	0	0	0	1	6	0	1	1	1	0	5	1	
+1	3	0	0	0	0	2	1	0	1	0	0	0	0	4	
+1	4	0	0	0	0	3	6	0	0	0	0	2	1	5	
+1	5	0	1	0	0	3	3	0	1	1	1	1	2	5	
+1	6	0	1	0	0	2	0	0	1	1	1	2	5	3	
+1	7	0	1	0	0	1	3	1	0	0	0	2	4	1	
+1	8	0	1	0	0	0	0	0	0	0	0	1	6	6	
+1	9	1	0	0	0	3	7	0	0	0	1	2	3	2	
+1	10	1	0	0	0	2	4	0	0	1	1	3	7	8	
+1	11	1	0	0	0	1	7	0	0	0	1	1	0	4	
+1	12	1	0	0	0	0	4	0	1	1	0	3	4	4	
+1	13	1	1	0	0	0	5	0	0	1	0	2	2	3	
+1	14	1	1	0	0	1	2	1	0	1	1	3	6	2	
+1	15	1	1	0	0	2	5	1	0	1	1	0	1	5	
+1	16	1	1	0	0	3	2	1	0	0	1	2	2	7	
+1	17	0	0	1	0	0	2	1	0	1	1	1	6	4	
+1	18	0	0	1	0	1	5	0	1	1	0	0	7	1	
+1	19	0	0	1	0	2	2	0	1	0	0	3	3	7	
+1	20	0	0	1	0	3	5	1	0	0	1	3	5	2	
+1	21	0	1	1	0	3	4	1	1	1	0	3	1	5	
+1	22	0	1	1	0	2	7	1	0	1	0	0	3	1	
+1	23	0	1	1	0	1	4	0	0	0	0	0	1	5	
+1	24	0	1	1	0	0	7	0	1	1	1	3	2	8	
+1	25	1	0	1	0	3	0	1	0	1	0	2	3	4	
+1	26	1	0	1	0	2	3	1	0	0	1	1	5	6	
+1	27	1	0	1	0	1	0	1	0	0	0	0	4	4	
+1	28	1	0	1	0	0	3	0	1	0	0	1	3	6	
+1	29	1	1	1	0	0	6	1	1	0	0	3	2	6	
+1	30	1	1	1	0	1	1	0	0	1	0	3	5	7	
+1	31	1	1	1	0	2	6	1	0	0	0	1	7	3	
+1	32	1	1	1	0	3	1	1	1	1	1	2	0	7	
+1	33	0	0	0	1	3	0	1	1	1	1	3	3	8	
+1	34	0	0	0	1	2	3	0	0	1	1	1	7	5	
+1	35	0	0	0	1	1	0	0	0	1	1	2	4	3	
+1	36	0	0	0	1	0	3	1	1	0	1	3	4	2	
+1	37	0	1	0	1	0	6	0	0	0	0	3	6	8	
+1	38	0	1	0	1	1	1	0	0	1	0	1	5	6	
+1	39	0	1	0	1	2	6	1	0	1	1	2	1	2	
+1	40	0	1	0	1	3	1	1	1	1	0	0	6	8	
+1	41	1	0	0	1	0	2	0	1	0	1	2	6	5	
+1	42	1	0	0	1	1	5	1	1	0	1	0	7	7	
+1	43	1	0	0	1	2	2	0	1	1	0	2	7	1	
+1	44	1	0	0	1	3	5	1	1	1	0	1	1	8	
+1	45	1	1	0	1	3	4	0	1	1	0	1	4	3	
+1	46	1	1	0	1	2	7	0	0	0	1	3	0	4	
+1	47	1	1	0	1	1	4	1	0	1	0	1	0	7	
+1	48	1	1	0	1	0	7	0	0	1	0	0	2	3	
+1	49	0	0	1	1	3	7	1	1	1	0	2	6	3	
+1	50	0	0	1	1	2	4	1	0	0	0	3	7	1	
+1	51	0	0	1	1	1	7	0	1	0	1	0	6	7	
+1	52	0	0	1	1	0	4	1	1	0	0	1	2	4	
+1	53	0	1	1	1	0	5	1	1	0	0	2	5	5	
+1	54	0	1	1	1	1	2	0	1	0	1	1	1	2	
+1	55	0	1	1	1	2	5	0	0	1	1	0	4	8	
+1	56	0	1	1	1	3	2	1	1	0	1	1	4	6	
+1	57	1	0	1	1	0	1	1	0	0	1	0	2	3	
+1	58	1	0	1	1	1	6	1	1	0	0	0	5	6	
+1	59	1	0	1	1	2	1	1	1	1	1	1	3	1	
+1	60	1	0	1	1	3	6	0	0	0	1	0	3	6	
+1	61	1	1	1	1	3	3	1	1	1	1	0	0	2	
+1	62	1	1	1	1	2	0	0	1	0	0	2	0	1	
+1	63	1	1	1	1	1	3	0	1	0	1	3	1	2	
+1	64	1	1	1	1	0	0	1	1	0	1	2	7	7	
+||||||||||
+design  
+ ;alts = alt1*, alt2*, alt3  
+ ;orth = seq    
+ ;rows = 64  
+ ;block = 8  
+ ;model:  
+ U(alt1) = b1[0.2] * COW[0,1]    
+         + b2[0.2] * ADV[0,1]    
+         + b3[0.2] * VET[0,1]    
+         + b4[0.2] * FAR[0,1]    
+         + b5.dummy[0.1|0.2|0.3] * MET[1,2,3,0]      
+         + b6.dummy[0.3|0.5|0.65|0.75|0.8|0.83|0.85] * BON[1,2,3,4,5,6,7,0]           
+         + i1[0] * COW.dummy[0] * VET.dummy[1]  
+ /  
+ U(alt2) = b1 * COW  
+         + b2 * ADV  
+         + b3 * VET  
+         + b4 * FAR  
+         + b5 * MET      
+         + b6 * BON     
+         + i1 * COW.dummy[0] * VET.dummy[1]  
+/  
+ U(alt3) = asc3[0.2]  
+;
+$
\ No newline at end of file
diff --git a/man/download_and_extract_zip.Rd b/man/download_and_extract_zip.Rd
index e4cbbe96a3593a93f67b8974263a2d3069f1e6af..27c2c7d18e479383be04aa88762ca7b69cd749e9 100644
--- a/man/download_and_extract_zip.Rd
+++ b/man/download_and_extract_zip.Rd
@@ -19,3 +19,6 @@ nothing, stores the data on the local system
 \description{
 Title Downloads and extracts external data to be used in the simulation
 }
+\examples{
+\dontrun{ download_and_extract_zip(url="www.nextcloud.de/mysuperfile")}
+}
diff --git a/man/sim_choice.Rd b/man/sim_choice.Rd
index 02ac2709b54a2665242c04883ab03eb8ad383940..7ec225d724cd7e72cb16732459749598f8a809cc 100644
--- a/man/sim_choice.Rd
+++ b/man/sim_choice.Rd
@@ -32,3 +32,8 @@ a list with all information on the run
 \description{
 Title
 }
+\examples{
+\dontrun{  simchoice(designfile="somefile", no_sim=10, respondents=330,
+ mnl_U,utils=u[[1]] ,destype="ngene")}
+
+}
diff --git a/tests/testthat/test-readdesign.R b/tests/testthat/test-readdesign.R
index 1e08d8a59c46b14c4b8677c93eee84920822e281..a240071ed95873bc6cc60ad14a0b6bf195556bc9 100644
--- a/tests/testthat/test-readdesign.R
+++ b/tests/testthat/test-readdesign.R
@@ -16,4 +16,4 @@ test_that("all is correct, but gives a warning", {
                  "One or more parsing issues, call ")
 })
 
-de
+