Repository 'stoc_mainglm'
hg clone https://toolshed.g2.bx.psu.edu/repos/ecology/stoc_mainglm

Changeset 0:df3ce23d0d23 (2020-04-02)
Next changeset 1:a961be0a964f (2020-05-11)
Commit message:
"planemo upload for repository https://github.com/Alanamosse/Galaxy-E/tree/stoctool/tools/stoc commit f82f897ab22464de40c878e17616333855814e25"
added:
ExeMainGlmGalaxy.r
FunctTrendSTOCGalaxy.r
mainglm.xml
stoceps_macros.xml
tabSpecies.csv
b
diff -r 000000000000 -r df3ce23d0d23 ExeMainGlmGalaxy.r
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/ExeMainGlmGalaxy.r Thu Apr 02 03:32:56 2020 -0400
[
@@ -0,0 +1,90 @@
+#!/usr/bin/env Rscript
+
+######################################################################################################################################
+############## COMMAND LINE TO CALCULATE AND PLOT EVOLUTION OF SPECIES POPULATION  function:main.glm    ##############################
+######################################################################################################################################
+
+#### Based on Romain Lorrillière R script
+#### Modified by Alan Amosse and Benjamin Yguel for integrating within Galaxy-E
+
+#suppressMessages(library(lme4))
+suppressMessages(library(ggplot2))
+suppressMessages(library(speedglm))
+suppressMessages(library(arm))
+#suppressMessages(library(reshape))
+suppressMessages(library(data.table))
+suppressMessages(library(reshape2))
+
+
+###########
+#delcaration des arguments et variables/ declaring some variables and load arguments
+
+args = commandArgs(trailingOnly=TRUE)
+options(encoding = "UTF-8")
+source(args[6],encoding="UTF-8")### chargement des fonctions / load the functions
+
+if ( (length(args)<8) || (length(args)>9)) {
+    stop("At least 5 arguments must be supplied :\n- An input dataset filtered (.tabular). May come from the filter rare species tool.\n- A species detail table (.tabular)\n- An id to fix output repository name.\n- A list of species to exclude, can be empty.\n- TRUE/FALSE to perform the glm with confidence intervals calculations.\n\n", call.=FALSE) #si pas d'arguments -> affiche erreur et quitte / if no args -> error and exit1
+} else {
+    Datafilteredfortrendanalysis<-args[1] ###### Nom du fichier avec extension ".typedefichier", peut provenir de la fonction "FiltreEspeceRare" / file name without the file type ".filetype", may result from the function "FiltreEspeceRare"    
+    tabSpecies<-args[2] ###### Nom du fichier avec extension ".typedefichier", fichier mis à disposition dans Galaxy-E avec specialisation à l'habitat des especes et si espece considérée comme indicatrice / file name without the file type ".filetype", file available in Galaxy-E containing habitat specialization for each species and whether or not they are considered as indicator  
+    id<-args[3]  ##### nom du dossier de sortie des resultats / name of the output folder
+    spExclude <- strsplit(args [4],",")[[1]] ##### liste d'espece qu on veut exclure de l analyse  / list of species that will be excluded
+    AssessIC <-args [5] ##########  TRUE ou FALSE réalise glm "standard" avec calcul d'intervalle de confiance ou speedglm sans IC bien plus rapide / TRUE or FALSE perform a "standard" glm with confidance interval or speedglm without CI much more fast
+}
+
+## creation d'un dossier pour y mettre les resultats / create folder for the output of the analyses
+
+dir.create(paste("Output/",id,sep=""),recursive=TRUE,showWarnings=FALSE)
+#cat(paste("Create Output/",id,"\n",sep=""))
+dir.create(paste("Output/",id,"/Incertain/",sep=""),recursive=TRUE,showWarnings=FALSE)
+#cat(paste("Create Output/",id,"Incertain/\n",sep=""))
+
+
+#Import des données / Import data 
+tabCLEAN <- fread(Datafilteredfortrendanalysis,sep="\t",dec=".",header=TRUE,encoding="UTF-8") #### charge le fichier de données d abondance / load abundance of species
+tabsp <- fread(tabSpecies,sep="\t",dec=".",header=TRUE,encoding="UTF-8")   #### charge le fichier de donnees sur nom latin, vernaculaire et abbreviation, espece indicatrice ou non / load the file with information on species specialization and if species are indicators
+
+vars_tabCLEAN<-c("carre","annee","espece","abond")
+err_msg_tabCLEAN<-"The input dataset filtered doesn't have the right format. It need to have the following 4 variables :\n- carre\n- annee\n- espece\n- abond\n"
+
+vars_tabsp<-c("espece","nom","nomscientific","indicateur","specialisation")
+err_msg_tabsp<-"\nThe species dataset filtered doesn't have the right format. It need to have the following 4 variables :\n- espece\n- nom\n- nomscientific\n- indicateur\n- specialisation\n"
+
+check_file(tabCLEAN,err_msg_tabCLEAN,vars_tabCLEAN,4)
+check_file(tabsp,err_msg_tabsp,vars_tabsp,5)
+
+
+
+firstYear <- min(tabCLEAN$annee) #### Recupère 1ere annee des donnees / retrieve the first year of the dataset
+lastYear <- max(tabCLEAN$annee)  #### Récupère la dernière annee des donnees / retrieve the last year of the dataset
+annees <- firstYear:lastYear  ##### !!!! une autre variable s'appelle annee donc peut être à modif en "periode" ? ### argument de la fonction mais  DECLARER DANS LA FONCTION AUSSI donc un des 2 à supprimer
+spsFiltre=unique(tabCLEAN$espece) #### Recupère la liste des especes du tabCLEAN qui ont été sélectionnée et qui ont passé le filtre / retrieve species name that were selected and then filtered before
+#cat("\n\nspsFiltre\n")
+tabsp=subset (tabsp, (espece %in% spsFiltre)) #### liste des espèces exclu par le filtre ou manuellement / List of species excluded manually or by the filter from the analyses 
+#cat("\n\ntabsp\n")
+sp=as.character(tabsp$espece)  ##### liste des espece en code ou abbreviation gardées pour les analyses ### arg de la fonction  DECLARE AUSSI APRES DS FONCTION  / list of the code or abbreviation of the species kept for the analyses
+#cat("\n\nsp\n")
+if(length(spExclude)!=0) {
+    tabCLEAN <- subset(tabCLEAN,!(espece %in% spExclude))
+    tabsp <- subset(tabsp, !(espece %in% spExclude))
+
+    cat("\n\nEspèces exclues de l'analyse :\n")
+    cat(spExclude)
+    cat("\n")
+}
+if(length(tabCLEAN$espece)==0){
+    stop("There is no species left for the analyse.", call.=FALSE) #si pas plus d'espèce après filtre / if no more species after filter
+}
+#cat("\n\ntabsp\n")
+
+
+################## 
+###  Do your analysis
+
+main.glm(donneesAll=tabCLEAN,tabsp=tabsp,id=id,assessIC=AssessIC)
+
+
+
+
+
b
diff -r 000000000000 -r df3ce23d0d23 FunctTrendSTOCGalaxy.r
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/FunctTrendSTOCGalaxy.r Thu Apr 02 03:32:56 2020 -0400
[
b'@@ -0,0 +1,776 @@\n+#!/usr/bin/env Rscript\n+\n+\n+##################################################################################################################################\n+############## FUNCTION TO CALCULATE AND PLOT EVOLUTION OF SPECIES POPULATION  function:main.glm    ##############################\n+##################################################################################################################################\n+\n+#### Based on Romain Lorrilli\xc3\xa8re R script\n+#### Modified by Alan Amosse and Benjamin Yguel for integrating within Galaxy-E\n+\n+##### workes with the R version 3.5.1 (2018-07-02)\n+##### Package used with the version:\n+#suppressMessages(library(lme4))  version 1.1.18.1\n+#suppressMessages(library(ggplot2))  version 3.0.0\n+#suppressMessages(library(speedglm))  version 0.3.2\n+#suppressMessages(library(arm))  version 1.10.1\n+#suppressMessages(library(reshape))  version 0.8.8\n+#suppressMessages(library(data.table))  version 1.12.0\n+#suppressMessages(library(reshape2))   version 1.4.3\n+\n+\n+\n+######################################### debut de la fonction makeTableAnalyse / stard of the function makeTableAnalyse\n+## mise en colonne des especes  et rajout de zero mais sur la base des carr\xc3\xa9s selectionn\xc3\xa9 sans l\'import  /  Species are placed in separated columns and addition of zero on plots where at least one selected species is present \n+\n+makeTableAnalyse <- function(data) {\n+    tab <- reshape(data\n+                  ,v.names="abond"\n+                  ,idvar=c("carre","annee")      \n+                  ,timevar="espece"\n+                  ,direction="wide")\n+    tab[is.na(tab)] <- 0               ###### remplace les na par des 0 / replace NAs by 0 \n+\n+    colnames(tab) <- sub("abond.","",colnames(tab))### remplace le premier pattern "abond." par le second "" / replace the column names "abond." by ""\n+    return(tab)\n+}\n+\n+######################################### fin de la fonction makeTableAnalyse / end of the function makeTableAnalyse\n+\n+\n+\n+\n+\n+############################################# les fonctions qui filtrent les donn\xc3\xa9es pas suffisantes pour analyses fiables / The filtering functions removing species with not enough data to perform accurate analyses\n+\n+filter_absent_species<-function(tab){\n+##################### Filtre les esp\xc3\xa8ces jamais pr\xc3\xa9sentes (abondance=0) / Filter of species with 0 abundance\n+#################################################################################  PARTIE POTENTIELLEMENT ISOLABLE ET INSERABLE AVANT LA BOUCLE = permet de gagner du temps sur la boucle car supprime sps pas vu, donc pas repris par la boucle\n+    \n+    ## Fait la somme des abondances totales par esp\xc3\xa8ce / calculate the sum of all abundance per species\n+    if(ncol(tab)==3) {\n+\ttabSum <- sum(tab[,3])## cas d\'une seule especes (probl\xc3\xa8me de format et manip un peu differente)  / when selecting only one species, use a different method\n+\tnames(tabSum) <- colnames(tab)[3]\n+    } else {  ## cas de plusieurs esp\xc3\xa8ce/ when selecting more than one species\n+        tabSum <- colSums(tab[,-(1:2)])\n+    }\n+    ## colNull= espece(s) toujours absente /species with 0 total abundance\n+    colNull <- names(which(tabSum==0))\n+    ## colconserve= espece(s) au moins presente 1 fois/ species at least with 1 presence\n+    colConserve <- names(which(tabSum>0))\n+    ## Affichage des esp\xc3\xa8ces rejetees  / show species eliminated for the analyses\n+    if(length(colNull)>0){\n+        cat("\\n",length(colNull)," Species removed from the analysis, abundance is always 0.\\n\\n",sep="")  #Esp\xc3\xa8ces enlev\xc3\xa9es de l\'analyse car abondance toujours \xc3\xa9gale a 0\\n\\n",sep="")\n+        #tabNull <- data.frame(Code_espece = colNull, nom_espece = tabsp[colNull,"nom"])\n+        #cat("\\n\\n",sep="")\n+        tab <- tab[,c("carre","annee",colConserve)]\n+    }\n+################################################################################ FIN DE LA PARTIE ISOLABLE\n+    return(tab)  \n+}\n+\n+\n+\n+\n+###################### Filtre les especes trop ra'..b' ggplot2  / plots with ggplot2\n+    titre <- paste("Variation de l\'indicateur groupe de specialisation",sep="")\n+\n+    vecCouleur <- setNames(groupeCouleur,groupeNom)\n+                                        #browser()\n+    p <- ggplot(data = da, mapping = aes(x = annee, y = abondance_relative, colour=groupe,fill=groupe))\n+    p <- p + geom_hline(aes(yintercept = 1), colour="white", alpha=1,size=1.2) \n+    if(ICfigureGroupeSp)\n+        p <- p + geom_ribbon(mapping=aes(ymin=IC_inferieur,ymax=IC_superieur),linetype=2,alpha=.1,size=0.1) \n+    p <- p + geom_line(size=1.5)\n+    p <- p +  ylab("") + xlab("Annee")+ ggtitle(titre) \n+    if(!is.null(groupeNom)) p <- p + scale_colour_manual(values=vecCouleur, name = "" )+\n+                                scale_x_continuous(breaks=unique(da$annee))\n+    if(!is.null(groupeNom)) p <- p +  scale_fill_manual(values=vecCouleur, name="")\n+    p <- p +  theme(panel.grid.minor=element_blank(), panel.grid.major.y=element_blank()) \n+    ggsave(nameFileSpepng, p,width=17,height=10,units="cm")\n+\n+                                        #   cat(" <==",nameFileSpepng,"\\n")\n+    \n+    ## calul pour chaque groupe une pente de regression d\'evolution des abondances sur la periode \xc3\xa9tudi\xc3\xa9e / calculating for each group the regression slope for the abundance evolution on the studied period\n+    vecSpe <- unique(da$groupe)\n+    datasum <- data.frame(groupe=NULL,tendance=NULL,pourcentage_variation=NULL)\n+    for(spe in 1:4){\n+        # print(spe)\n+        subtab <- subset(da,groupe==vecSpe[spe])\n+        if(nrow(subtab)>1) {\n+            sumlm <- summary(lm(abondance_relative~annee,data=subtab)) ##### recup\xc3\xa8re les resultats du mod\xc3\xa8le lin\xc3\xa9aire / retrieve the results of the linear model\n+            subdatasum <- data.frame(groupe=vecSpe[spe],\n+                                     tendance=round(sumlm$coefficients[2,1],3),\n+                                     pourcentage_variation=round(sumlm$coefficients[2,1]*(nrow(subtab)-1)*100,3)) #### assemble les resultats pour en faire une sortie  /  bring together the results for an output file\n+            datasum <- rbind(datasum,subdatasum)\n+            \n+        }\n+        \n+    }\n+    datasum <- merge(datasum,tIncert,by="groupe") #### \n+    datasum <- data.frame(id,datasum)\n+                                        #datasum$cat_tendance_EBCC <- affectCatEBCC(trend,pVal,ICinf,ICsup\n+    namefilesum <- paste("Output/",id,"/tendancesGlobalesGroupes_",id,\n+                         ".tabular",sep="" )\n+    write.table(datasum,file=namefilesum,row.names=FALSE,quote=FALSE,sep="\\t",dec=".",fileEncoding="UTF-8")\n+    cat("-->",namefilesum,"\\n")\n+}\n+\n+################################################################################################################## fin de la fonction analyseGroupe / end of the function analyseGroupe\n+\n+\n+\n+\n+\n+\n+\n+################################################################################################################### debut de la fonction check_file / start of the function check_file\n+# Fonction pour verifier les donn\xc3\xa9es d\'entr\xc3\xa9e / General function to check integrity of input file. Will check numbers and contents of variables(colnames). \n+#return an error message and exit if mismatch detected\n+#Faut rentrer le nom du jeu de donn\xc3\xa9es, le nbre et le nom des variables / Enter dataset name,  expected number and names of variables. + an exit error message to guide user.\n+\n+check_file<-function(dataset,err_msg,vars,nb_vars){\n+    if(ncol(dataset)!=nb_vars){ #Verifiction de la pr\xc3\xa9sence du bon nb de colonnes, si c\'est pas le cas= message d\'erreur / checking for right number of columns in the file if not = error message\n+        cat("\\nerr nb var\\n") \n+        stop(err_msg, call.=FALSE)\n+    }\n+\n+    for(i in vars){\n+        if(!(i %in% names(dataset))){\n+            stop(err_msg,call.=FALSE)\n+        }\n+    }\n+}\n+\n+#####################################################################################################################\n+\n'
b
diff -r 000000000000 -r df3ce23d0d23 mainglm.xml
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/mainglm.xml Thu Apr 02 03:32:56 2020 -0400
[
b'@@ -0,0 +1,185 @@\n+<tool id="stoceps_glm" name="Estimate temporal population evolution" version="@VERSION@">\n+    <description>by species</description>\n+    <macros>\n+        <import>stoceps_macros.xml</import>\n+    </macros>\n+    <expand macro="mainglm_requirements"/>\n+    <command detect_errors="exit_code"><![CDATA[\n+        Rscript\n+         \'$__tool_directory__/ExeMainGlmGalaxy.r\'\n+         \'$input\'\n+         \'$inputtabSpecies\'\n+         #if $settings.advanced==\'advanced\'\n+             \'mainglm\'\n+             $settings.sp_code\n+             $settings.compute_ic\n+         #else\n+             \'mainglm\'\n+             \'\'\n+             \'TRUE\'\n+         #end if\n+         \'$__tool_directory__/FunctTrendSTOCGalaxy.r\'\n+\n+\n+        \'$yearly_variations\'\n+        \'$global_tendencies\'\n+        #if $settings.advanced==\'advanced\'\n+            #if $settings.return_plot==\'plot\'\n+                \'$plots\'\n+            #end if\n+        #end if\n+    ]]>\n+    </command>\n+    <inputs>\n+        <expand macro="stoceps_input_filtered"/>\n+        <param name="inputtabSpecies" type="data" format="tabular" label="Species file" help="Input species tabular file, with 5 columns (species ID, species name, species scientific name, specialization status)." />\n+        <conditional name="settings">\n+            <expand macro="stoceps_advanced_params_select"/>\n+            <when value="advanced">\n+                <param name="sp_code" type="select" label="Filter species to exclude" help="Create a subsample by selecting species codes you don\'t want to use." multiple="true" optional="true">\n+                    <options from_dataset="input">\n+                        <column name="value" index="2"/>\n+                        <filter type="unique_value" name="espece" column="2"/>\n+                    </options>\n+                    <sanitizer>\n+                        <valid initial="string.printable">\n+                            <remove value="&quot;"/>\n+                        </valid>\n+                    </sanitizer>\n+                </param>\n+                <param name="return_plot" type="boolean" truevalue="plot" falsevalue="noplot" checked="yes" help="All the figures will be stocked in a datacollection" label="Return visualizations."/>\n+                <expand macro="stoceps_compute_ic"/>\n+            </when>\n+        </conditional>\n+    </inputs>\n+    <outputs>\n+        <data name="yearly_variations" from_work_dir="Output/mainglm/variationsAnnuellesEspece_mainglm.tabular" format="tabular" label="GLM - Yearly variations on ${on_string}"/>\n+        <data name="global_tendencies" from_work_dir="Output/mainglm/tendanceGlobalEspece_mainglm.tabular" format="tabular" label="GLM - Global species tendencies on ${on_string}"/>\n+        <collection type="list" name="plots">\n+            <filter>return_plot == \'plot\'</filter>\n+            <discover_datasets pattern="(?P&lt;designation&gt;.+)\\.png" visible="false" format="png" directory="Output/mainglm/"/>\n+        </collection>\n+    </outputs>\n+    <tests>\n+        <test>\n+            <param name="inputtabSpecies" value="tabSpecies.csv"/>\n+            <param name="input" value="Datafilteredfortrendanalysis.tabular"/>\n+            <param name="advanced" value="simple"/>\n+            <output name="yearly_variations">\n+                <assert_contents>\n+                    <has_n_lines n="37"/>\n+                    <has_n_columns n="14"/>\n+                    <has_size value="3247" delta="100"/>\n+                </assert_contents>\n+            </output> \n+            <output name="global_tendencies">\n+                <assert_contents>\n+                    <has_n_lines n="3"/>\n+                    <has_size value="468" delta="50"/>\n+                </assert_contents>\n+            </output>\n+            <output_collection name="plots"  type="list" count="2">\n+                <element name="ALAARV_mainglm">\n+                    <assert_contents>\n+                        <has_text text="PNG"/>\n+                    </asser'..b'species count shaped and filtered with the STOCs \'Preprocess population data\' ans \'Filter species\' tools.\n+\n+A second optional "species details file" containing indicator status of species (Column with TRUE or FALSE), including the species name or ID (one used in the species count data). If you are not analyzing the default STOC data, you need one file of this kind.\n+\n+Example dataset ::\n+\n+"espece"  "nom"                       "nomscientific"               "indicateur"     "specialisation"\n+"ACCGEN"  "Autour des palombes"       "Accipiter gentilis"          FALSE            ""\n+"ACCNIS"  "Epervier d\'Europe"         "Accipiter nisus"             FALSE            ""\n+"ACRARU"  "Rousserolle turdo\xc3\xafde"      "Acrocephalus arundinaceus"   FALSE            ""\n+"ACRMEL"  "Lusciniole \xc3\xa0 moustaches"   "Acrocephalus melanopogon"    FALSE            ""\n+"ACRPAL"  "Phragmite aquatique"       "Acrocephalus paludicola"     FALSE            ""\n+"ACRRIS"  "Rousserolle verderolle"    "Acrocephalus palustris"      FALSE            ""\n+"ACRSCH"  "Phragmite des joncs"       "Acrocephalus schoenobaenus"  FALSE            ""\n+"ACRSCI"  "Rousserolle effarvatte"    "Acrocephalus scirpaceus"     FALSE            ""\n+"ACTHYP"  "Chevalier guignette"       "Actitis hypoleucos"          FALSE            ""\n+"AEGCAU"  "M\xc3\xa9sange \xc3\xa0 longue queue"    "Aegithalos caudatus"         FALSE            ""\n+"AEGFUN"  "Chouette de Tengmalm"      "Aegolius funereus"           FALSE            ""\n+"AIXGAL"  "Canard mandarin"           "Aix galericulata"            FALSE            ""\n+"AIXSPO"  "Canard carolin"            "Aix sponsa"                  FALSE            ""\n+"ALAARV"  "Alouette des champs"       "Alauda arvensis"             TRUE             "milieux agricoles"\n+\n+|\n+\n+**Output**\n+\n+For each species present in the data, a plot of populations trend is created and stocked in a common data collection.\n+\n+Two tabular files are created, they describe global tendencies and yearly variations.\n+\n+|\n+\n+**Source**\n+\n+UnPublished script available at http://www.vigienature.fr/sites/vigienature/files/atoms/files/analysestoceps_0.zip\n+the first version written by Romain Lorrilliere\n+\n+Original script information:\n+\n+Estimate temporal evolution of population per species - ExeMainGlmGalaxy.r\n+This script analyse the temporal evolution of species population and create graphical vizualisation.\n+\n+Script needs the followings inputs :\n+ - stoc or community data filtered with at least 4 columns: year, site, species, and abundance with 0. Corresponding to "observed" or predicted 0 abundance. May come from the tools "Preprocess population data for evolution trend analyzes" (ExemakeTableAnalyseGalaxy.r) followed by "Filter species with rare and low abundances" (ExeFilteringRareLowabundSPGalaxy.r).\n+ - species details file with name and indicator status file with at least 2 columns: the species name or species ID (found in the community data or in stoc data) and his status as indicator species\n+ - file that stocks functions : "FunctTrendSTOCGalaxy.r"\n+\n+\n+Arguments are :\n+ - spExclude: list of species (using the the species name or ID) that you want to exclude\n+ - assessIC : compute and show confidence interval in plots (TRUE / FALSE)\n+ - analysis custom id\n+\n+\n+How to execute, eg :\n+ # all files are available in github repo\n+ #Exec id=mainglm, return IC on plot, no species excluded\n+ $ Rscript ExeMainGlmGalaxy.r\' Datafilteredfortrendanalysis.tabular tabSpecies.csv \'mainglm\' \'\' \'TRUE\' FunctTrendSTOCGalaxy.r\n+\n+\n+Outputs are created in an Output repo :\n+GLM gives 1 graph per species and 2 tables:\n+- nameofspecies_id.png (one plot per species)\n+- tendanceGlobalEspece_id.tabular\n+- variationsAnnuellesEspece_id.tabular\n+\n+\n+R library needed\n+r-lme4  version 1.1.18.1\n+r-ggplot2  version 3.0.0\n+r-speedglm  version 0.3.2\n+r-arm  version 1.10.1\n+r-reshape  version 0.8.8\n+r-data.table  version 1.12.0\n+r-reshape2   version 1.4.3\n+  ]]></help>\n+  <expand macro="stoceps_bibref" />\n+</tool>\n'
b
diff -r 000000000000 -r df3ce23d0d23 stoceps_macros.xml
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/stoceps_macros.xml Thu Apr 02 03:32:56 2020 -0400
[
@@ -0,0 +1,73 @@
+<macros>
+    <token name="@VERSION@">0.0.1</token>
+    <xml name="reshape_requirements">
+        <requirements>
+            <requirement type="package" version="0.8.8">r-reshape</requirement>
+            <requirement type="package" version="1.12.0">r-data.table</requirement>
+        </requirements>    
+    </xml>
+    <xml name="reshape2_requirements">
+        <requirements>
+            <requirement type="package" version="1.4.3">r-reshape2</requirement>
+        </requirements>    
+    </xml>
+    <xml name="mainglm_requirements">
+        <requirements>
+            <requirement type="package" version="3.0.0">r-ggplot2</requirement>
+            <requirement type="package" version="0.3_2">r-speedglm</requirement>
+            <requirement type="package" version="1.10_1">r-arm</requirement>
+            <requirement type="package" version="1.12.0">r-data.table</requirement>
+            <requirement type="package" version="1.4.3">r-reshape2</requirement>
+        </requirements>
+    </xml>
+    <xml name="temp_indic_requirements">
+        <requirements>
+            <requirement type="package" version="1.3_15">r-rodbc</requirement>
+            <requirement type="package" version="0.8.8">r-reshape</requirement>
+            <requirement type="package" version="1.12.0">r-data.table</requirement>
+            <requirement type="package" version="1.4_3">r-rgdal</requirement>
+            <requirement type="package" version="1.7.4">r-lubridate</requirement>
+            <requirement type="package" version="4.6_2">r-doby</requirement>
+            <requirement type="package" version="1.10_1">r-arm</requirement>
+            <requirement type="package" version="3.1.0">r-ggplot2</requirement>
+            <requirement type="package" version="1.0.0">r-scales</requirement>
+            <requirement type="package" version="1.8_24">r-mgcv</requirement>
+            <requirement type="package" version="1.8.4">r-plyr</requirement>
+            <requirement type="package" version="0.3_2">r-speedglm</requirement>
+            <requirement type="package" version="3.1_0">r-lmertest</requirement>
+            <requirement type="package" version="0.2.3">r-glmmtmb</requirement>
+        </requirements>
+    </xml>
+    <xml name="stoceps_input_filtered">
+        <param name="input" type="data" format="tabular" label="Stoc filtered input" help="Input Stoc count file, shaped and filtered with the 'preprocess population data' and 'filter species' tools." />
+    </xml>
+    <xml name="stoceps_advanced_params_select">
+        <param name="advanced" type="select" label="Specify advanced parameters">
+            <option value="simple" selected="true">No, use program defaults.</option>
+            <option value="advanced">Yes, see full parameter list.</option>
+        </param>        
+        <when value="simple">
+        </when>        
+    </xml>
+    <xml name="stoceps_compute_ic">
+        <param name="compute_ic" type="boolean" truevalue="TRUE" falsevalue="FALSE" checked="yes" label="Compute confidence intervals"/>
+    </xml>
+    <xml name="stoceps_filter_glmmtmb">
+        <filter> settings['advanced'] == 'advanced'</filter>
+        <filter> settings['method'] == 'glmmtmb'</filter>
+    </xml>
+    <xml name="stoceps_filter_gam">
+        <filter> settings['method'] == 'gam'</filter>
+    </xml>
+    <xml name="stoceps_bibref">
+        <citations>
+            <citation type="bibtex">
+     @unpublished{stocepsromain,
+     title={Vigie-Nature STOC unpublished scripts},
+            author={Lorrilliere, R},
+            url={http://www.vigienature.fr/sites/vigienature/files/atoms/files/analysestoceps_0.zip}
+            }
+            </citation>
+        </citations>
+    </xml>
+</macros>
b
diff -r 000000000000 -r df3ce23d0d23 tabSpecies.csv
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/tabSpecies.csv Thu Apr 02 03:32:56 2020 -0400
b
b'@@ -0,0 +1,325 @@\n+"espece"\t"nom"\t"nomscientific"\t"indicateur"\t"specialisation"\n+"ACCGEN"\t"Autour des palombes"\t"Accipiter gentilis"\tFALSE\t""\n+"ACCNIS"\t"Epervier d\'Europe"\t"Accipiter nisus"\tFALSE\t""\n+"ACRARU"\t"Rousserolle turdo\xc3\xafde"\t"Acrocephalus arundinaceus"\tFALSE\t""\n+"ACRMEL"\t"Lusciniole \xc3\xa0 moustaches"\t"Acrocephalus melanopogon"\tFALSE\t""\n+"ACRPAL"\t"Phragmite aquatique"\t"Acrocephalus paludicola"\tFALSE\t""\n+"ACRRIS"\t"Rousserolle verderolle"\t"Acrocephalus palustris"\tFALSE\t""\n+"ACRSCH"\t"Phragmite des joncs"\t"Acrocephalus schoenobaenus"\tFALSE\t""\n+"ACRSCI"\t"Rousserolle effarvatte"\t"Acrocephalus scirpaceus"\tFALSE\t""\n+"ACTHYP"\t"Chevalier guignette"\t"Actitis hypoleucos"\tFALSE\t""\n+"AEGCAU"\t"M\xc3\xa9sange \xc3\xa0 longue queue"\t"Aegithalos caudatus"\tFALSE\t""\n+"AEGFUN"\t"Chouette de Tengmalm"\t"Aegolius funereus"\tFALSE\t""\n+"AIXGAL"\t"Canard mandarin"\t"Aix galericulata"\tFALSE\t""\n+"AIXSPO"\t"Canard carolin"\t"Aix sponsa"\tFALSE\t""\n+"ALAARV"\t"Alouette des champs"\t"Alauda arvensis"\tTRUE\t"milieux agricoles"\n+"ALCATT"\t"Martin-p\xc3\xaacheur d\'Europe"\t"Alcedo atthis"\tFALSE\t""\n+"ALCTOR"\t"Pingouin torda"\t"Alca torda"\tFALSE\t""\n+"ALEGRA"\t"Perdrix bartavelle"\t"Alectoris graeca"\tFALSE\t""\n+"ALERUF"\t"Perdrix rouge"\t"Alectoris rufa"\tTRUE\t"milieux agricoles"\n+"ALLALL"\t"Mergule nain"\t"Alle alle"\tFALSE\t""\n+"ALOAEG"\t"Ouette d\'Egypte"\t"Alopochen aegyptiaca"\tFALSE\t""\n+"ANAACU"\t"Canard pilet"\t"Anas acuta"\tFALSE\t""\n+"ANACLY"\t"Canard souchet"\t"Anas clypeata"\tFALSE\t""\n+"ANACRE"\t"Sarcelle d\'hiver"\t"Anas crecca"\tFALSE\t""\n+"ANAPEN"\t"Canard siffleur"\t"Anas penelope"\tFALSE\t""\n+"ANAPLA"\t"Canard colvert"\t"Anas platyrhynchos"\tFALSE\t""\n+"ANAQUE"\t"Sarcelle d\'\xc3\xa9t\xc3\xa9"\t"Anas querquedula"\tFALSE\t""\n+"ANASTR"\t"Canard chipeau"\t"Anas strepera"\tFALSE\t""\n+"ANSANS"\t"Oie cendr\xc3\xa9e"\t"Anser anser"\tFALSE\t""\n+"ANSIND"\t"Oie \xc3\xa0 t\xc3\xaate barr\xc3\xa9e"\t"Anser indicus"\tFALSE\t""\n+"ANTCAM"\t"Pipit rousseline"\t"Anthus campestris"\tTRUE\t"milieux agricoles"\n+"ANTCER"\t"Pipit \xc3\xa0 gorge rousse"\t"Anthus cervinus"\tFALSE\t""\n+"ANTPET"\t"Pipit maritime"\t"Anthus petrosus"\tFALSE\t""\n+"ANTPRA"\t"Pipit farlouse"\t"Anthus pratensis"\tTRUE\t"milieux agricoles"\n+"ANTRIC"\t"Pipit de Richard"\t"Anthus richardi"\tFALSE\t""\n+"ANTSPI"\t"Pipit spioncelle"\t"Anthus spinoletta"\tFALSE\t""\n+"ANTTRI"\t"Pipit des arbres"\t"Anthus trivialis"\tFALSE\t""\n+"APUAPU"\t"Martinet noir"\t"Apus apus"\tTRUE\t"milieux b\xc3\xa2tis"\n+"APUMEL"\t"Martinet \xc3\xa0 ventre blanc"\t"Apus melba"\tFALSE\t""\n+"APUPAL"\t"Martinet p\xc3\xa2le"\t"Apus pallidus"\tFALSE\t""\n+"AQUCHR"\t"Aigle royal"\t"Aquila chrysaetos"\tFALSE\t""\n+"ARDCIN"\t"H\xc3\xa9ron cendr\xc3\xa9"\t"Ardea cinerea"\tFALSE\t""\n+"ARDPUR"\t"H\xc3\xa9ron pourpr\xc3\xa9"\t"Ardea purpurea"\tFALSE\t""\n+"ARDRAL"\t"Crabier chevelu"\t"Ardeola ralloides"\tFALSE\t""\n+"AREINT"\t"Tournepierre \xc3\xa0 collier"\t"Arenaria interpres"\tFALSE\t""\n+"ASIFLA"\t"Hibou des marais"\t"Asio flammeus"\tFALSE\t""\n+"ASIOTU"\t"Hibou moyen-duc"\t"Asio otus"\tFALSE\t""\n+"ATHNOC"\t"Chev\xc3\xaache d\'Ath\xc3\xa9na"\t"Athene noctua"\tFALSE\t""\n+"AYTAFF"\t"Fuligule \xc3\xa0 t\xc3\xaate noire"\t"Aythya affinis"\tFALSE\t""\n+"AYTFER"\t"Fuligule milouin"\t"Aythya ferina"\tFALSE\t""\n+"AYTFUL"\t"Fuligule morillon"\t"Aythya fuligula"\tFALSE\t""\n+"AYTMAR"\t"Fuligule milouinan"\t"Aythya marila"\tFALSE\t""\n+"BOMGAR"\t"Jaseur bor\xc3\xa9al"\t"Bombycilla garrulus"\tFALSE\t""\n+"BONBON"\t"G\xc3\xa9linotte des bois"\t"Bonasa bonasia"\tFALSE\t""\n+"BOTSTE"\t"Butor \xc3\xa9toil\xc3\xa9"\t"Botaurus stellaris"\tFALSE\t""\n+"BRABER"\t"Bernache cravant"\t"Branta bernicla"\tFALSE\t""\n+"BRACAN"\t"Bernache du Canada"\t"Branta canadensis"\tFALSE\t""\n+"BRALEU"\t"Bernache nonnette"\t"Branta leucopsis"\tFALSE\t""\n+"BUBBUB"\t"Grand-duc d\'Europe"\t"Bubo bubo"\tFALSE\t""\n+"BUBIBI"\t"H\xc3\xa9ron garde-boeufs"\t"Bubulcus ibis"\tFALSE\t""\n+"BUROED"\t"Oedicn\xc3\xa8me criard"\t"Burhinus oedicnemus"\tFALSE\t""\n+"BUTBUT"\t"Buse variable"\t"Buteo buteo"\tTRUE\t"milieux agricoles"\n+"CALACU"\t"B\xc3\xa9casseau \xc3\xa0 queue pointue"\t"Calidris acuminata"\tFALSE\t""\n+"CALALB"\t"B\xc3\xa9casseau sanderling"\t"Calidris alba"\tFALSE\t""\n+"CALALP"\t"B\xc3\xa9casseau variable"\t"Calidris alpina"\tFALSE\t""\n+"CALBRA"\t"Alouette calandrelle"\t"Calandrella brachydactyla"\tFALSE\t""\n+"CALCAN"\t"B\xc3\xa9casseau maub\xc3\xa8che"\t"Calidris canutus"\tFALSE\t""\n+"CALMIN"\t"B\xc3\xa9'..b'Bouvreuil pivoine"\t"Pyrrhula pyrrhula"\tTRUE\t"milieux forestiers"\n+"PYRRAX"\t"Crave \xc3\xa0 bec rouge"\t"Pyrrhocorax pyrrhocorax"\tFALSE\t""\n+"RALAQU"\t"R\xc3\xa2le d\'eau"\t"Rallus aquaticus"\tFALSE\t""\n+"RECAVO"\t"Avocette \xc3\xa9l\xc3\xa9gante"\t"Recurvirostra avosetta"\tFALSE\t""\n+"REGIGN"\t"Roitelet \xc3\xa0 triple bandeau"\t"Regulus ignicapilla"\tTRUE\t"milieux forestiers"\n+"REGREG"\t"Roitelet hupp\xc3\xa9"\t"Regulus regulus"\tTRUE\t"milieux forestiers"\n+"RIPRIP"\t"Hirondelle de rivage"\t"Riparia riparia"\tFALSE\t""\n+"SAXRUB"\t"Tarier des pr\xc3\xa9s"\t"Saxicola rubetra"\tTRUE\t"milieux agricoles"\n+"SAXTOR"\t"Tarier p\xc3\xa2tre"\t"Saxicola rubicola"\tTRUE\t"milieux agricoles"\n+"SCORUS"\t"B\xc3\xa9casse des bois"\t"Scolopax rusticola"\tFALSE\t""\n+"SERCIT"\t"Venturon montagnard"\t"Serinus citrinella"\tFALSE\t""\n+"SERCOR"\t"Venturon corse"\t"Serinus corsicanus"\tFALSE\t""\n+"SERSER"\t"Serin cini"\t"Serinus serinus"\tTRUE\t"milieux b\xc3\xa2tis"\n+"SITEUR"\t"Sittelle torchepot"\t"Sitta europaea"\tTRUE\t"milieux forestiers"\n+"SITWHI"\t"Sittelle corse"\t"Sitta whiteheadi"\tFALSE\t""\n+"STEALB"\t"Sterne naine"\t"Sternula albifrons"\tFALSE\t""\n+"STEHIR"\t"Sterne pierregarin"\t"Sterna hirundo"\tFALSE\t""\n+"STESAN"\t"Sterne caugek"\t"Thalasseus sandvicensis"\tFALSE\t""\n+"STRALU"\t"Chouette hulotte"\t"Strix aluco"\tFALSE\t""\n+"STRDEC"\t"Tourterelle turque"\t"Streptopelia decaocto"\tTRUE\t"milieux b\xc3\xa2tis"\n+"STRORI"\t"Tourterelle orientale"\t"Streptopelia orientalis"\tFALSE\t""\n+"STRSEN"\t"Tourterelle maill\xc3\xa9e"\t"Streptopelia senegalensis"\tFALSE\t""\n+"STRTUR"\t"Tourterelle des bois"\t"Streptopelia turtur"\tFALSE\t""\n+"STUROS"\t"\xc3\x89tourneau roselin"\t"Sturnus roseus"\tFALSE\t""\n+"STUUNI"\t"\xc3\x89tourneau unicolore"\t"Sturnus unicolor"\tFALSE\t""\n+"STUVUL"\t"\xc3\x89tourneau sansonnet"\t"Sturnus vulgaris"\tFALSE\t""\n+"SURULU"\t"Chouette \xc3\xa9pervi\xc3\xa8re"\t"Surnia ulula"\tFALSE\t""\n+"SYLATR"\t"Fauvette \xc3\xa0 t\xc3\xaate noire"\t"Sylvia atricapilla"\tTRUE\t"generaliste"\n+"SYLBOR"\t"Fauvette des jardins"\t"Sylvia borin"\tFALSE\t""\n+"SYLCAN"\t"Fauvette passerinette"\t"Sylvia cantillans"\tFALSE\t""\n+"SYLCOM"\t"Fauvette grisette"\t"Sylvia communis"\tTRUE\t"milieux agricoles"\n+"SYLCON"\t"Fauvette \xc3\xa0 lunettes"\t"Sylvia conspicillata"\tFALSE\t""\n+"SYLCUR"\t"Fauvette babillarde"\t"Sylvia curruca"\tFALSE\t""\n+"SYLHOR"\t"Fauvette orph\xc3\xa9e"\t"Sylvia hortensis"\tFALSE\t""\n+"SYLMEL"\t"Fauvette m\xc3\xa9lanoc\xc3\xa9phale"\t"Sylvia melanocephala"\tTRUE\t"milieux forestiers"\n+"SYLNIS"\t"Fauvette \xc3\xa9pervi\xc3\xa8re"\t"Sylvia nisoria"\tFALSE\t""\n+"SYLSAR"\t"Fauvette sarde"\t"Sylvia sarda"\tFALSE\t""\n+"SYLUND"\t"Fauvette pitchou"\t"Sylvia undata"\tFALSE\t""\n+"SYRREE"\t"Faisan v\xc3\xa9n\xc3\xa9r\xc3\xa9"\t"Syrmaticus reevesii"\tFALSE\t""\n+"TACRUF"\t"Gr\xc3\xa8be castagneux"\t"Tachybaptus ruficollis"\tFALSE\t""\n+"TADFER"\t"Tadorne casarca"\t"Tadorna ferruginea"\tFALSE\t""\n+"TADTAD"\t"Tadorne de Belon"\t"Tadorna tadorna"\tFALSE\t""\n+"TETRAX"\t"Outarde canepeti\xc3\xa8re"\t"Tetrax tetrax"\tFALSE\t""\n+"TETRIX"\t"T\xc3\xa9tras lyre"\t"Tetrao tetrix"\tFALSE\t""\n+"TETURO"\t"Grand T\xc3\xa9tras"\t"Tetrao urogallus"\tFALSE\t""\n+"THRAET"\t"Ibis sacr\xc3\xa9"\t"Threskiornis aethiopicus"\tFALSE\t""\n+"TICMUR"\t"Tichodrome \xc3\xa9chelette"\t"Tichodroma muraria"\tFALSE\t""\n+"TRIERY"\t"Chevalier arlequin"\t"Tringa erythropus"\tFALSE\t""\n+"TRIGLA"\t"Chevalier sylvain"\t"Tringa glareola"\tFALSE\t""\n+"TRINEB"\t"Chevalier aboyeur"\t"Tringa nebularia"\tFALSE\t""\n+"TRIOCH"\t"Chevalier culblanc"\t"Tringa ochropus"\tFALSE\t""\n+"TRITOT"\t"Chevalier gambette"\t"Tringa totanus"\tFALSE\t""\n+"TROTRO"\t"Troglodyte mignon"\t"Troglodytes troglodytes"\tTRUE\t"milieux forestiers"\n+"TURILI"\t"Grive mauvis"\t"Turdus iliacus"\tFALSE\t""\n+"TURMER"\t"Merle noir"\t"Turdus merula"\tTRUE\t"generaliste"\n+"TURPHI"\t"Grive musicienne"\t"Turdus philomelos"\tTRUE\t"milieux forestiers"\n+"TURPIL"\t"Grive litorne"\t"Turdus pilaris"\tFALSE\t""\n+"TURRUF"\t"Grive \xc3\xa0 gorge noire ou rousse"\t"Turdus ruficollis"\tFALSE\t""\n+"TURTOR"\t"Merle \xc3\xa0 plastron"\t"Turdus torquatus"\tFALSE\t""\n+"TURVIS"\t"Grive draine"\t"Turdus viscivorus"\tTRUE\t"milieux forestiers"\n+"TYTALB"\t"Effraie des clochers"\t"Tyto alba"\tFALSE\t""\n+"UPUEPO"\t"Huppe fasci\xc3\xa9e"\t"Upupa epops"\tTRUE\t"milieux agricoles"\n+"VANVAN"\t"Vanneau hupp\xc3\xa9"\t"Vanellus vanellus"\tTRUE\t"milieux agricoles"\n+"ZOODAU"\t"Grive dor\xc3\xa9e"\t"Zoothera dauma"\tFALSE\t""\n'