Next changeset 1:e3e173ae01b0 (2020-04-07) |
Commit message:
"planemo upload for repository https://github.com/Alanamosse/Galaxy-E/tree/stoctool/tools/stoc commit f82f897ab22464de40c878e17616333855814e25" |
added:
ExeMainglmParGroupGalaxy.r FunctTrendSTOCGalaxy.r biais.tabular mainglm_group.xml stoceps_macros.xml tabSpecies.csv |
b |
diff -r 000000000000 -r 06a11044e089 ExeMainglmParGroupGalaxy.r --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/ExeMainglmParGroupGalaxy.r Thu Apr 02 03:34:07 2020 -0400 |
[ |
b'@@ -0,0 +1,105 @@\n+#!/usr/bin/env Rscript\n+\n+##################################################################################################################################################\n+############## CALCULATE AND PLOT EVOLUTION OF SPECIES POPULATION BY SPECIALIZATION GROUP function:analyse.Groupe ##############################\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+suppressMessages(library(lme4))\n+suppressMessages(library(ggplot2))\n+suppressMessages(library(speedglm))\n+suppressMessages(library(arm))\n+suppressMessages(library(ggplot2))\n+#suppressMessages(library(reshape))\n+suppressMessages(library(data.table))\n+suppressMessages(library(reshape2))\n+\n+\n+\n+\n+###########\n+#delcaration des arguments et variables/ declaring some variables and load arguments\n+\n+args = commandArgs(trailingOnly=TRUE)\n+\n+print(args[7])\n+\n+if ((length(args)<7) || (length(args)>11)) {\n+ stop("The tool need the following inputs :\\n\\n- A yearly species variations data set (.tabular). It may come from the main glm tool.\\n- A species global tendencies dataset (.tabular). It may come from the main glm tool.\\n- A species table filtered (.tabular). It may come from the Filter rare species tool.\\n- An id to fix output repository name.\\n- A list of species to exclude, can be empty.\\n- A bias file.\\n\\n", call.=FALSE) #si pas d\'arguments -> affiche erreur et quitte / if no args -> error and exit1\n+} else {\n+ donnees<-args[1] ###### Nom du fichier avec extension "***variationsAnnuellesEspece***.tabular", peut provenir de la fonction "mainglm" / file name without the file type "***variationsAnnuellesEspece***.tabular", may result from the function "mainglm" \n+ donneesTrend <- args[2] ####### Nom du fichier avec extension "***tendanceGlobalEspece***.tabular", peut provenir de la fonction "mainglm" / / file name without the file type "***tendanceGlobalEspece***.tabular", may result from the function "mainglm" \n+ tabSpecies<-args[3] ###### 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" \n+ id<-args[4] ##### nom du dossier de sortie des resultats / name of the output folder\n+ spExclude <- strsplit(args [5],",")[[1]] ##### liste d\'espece qu on veut exclure de l analyse / list of species that will be excluded\n+ tBiais <-args [7] ########## fichier contenant le biais de d\xc3\xa9t\xc3\xa9ction en fonction des occurances, obtenu \xc3\xa0 partir d\'un mod\xc3\xa9le th\xc3\xa9orique de dynamique de pop et de survey / the file containing the detection bias depending on occurance data obtained with theoretical model of population dynamic and survey\n+ source(args[6])### chargement des fonctions analyseGroupe, geometriqueWeighted et checkfile / load the functions analyseGroupe, geometriqueWeighted and checkfile\n+}\n+\n+\n+\n+#Import des donn\xc3\xa9es / Import data \n+tBiais=read.table(tBiais,sep="\\t",dec=".",header=TRUE) ###### charge le fichier contenant le biais de d\xc3\xa9t\xc3\xa9ction en fonction des occurances, obtenu \xc3\xa0 partir d\'un mod\xc3\xa9le th\xc3\xa9orique de dynamique de pop et de survey / load the file containing the detection bias obtained with theoretical model of population dynamic and survey\n+donnees <- read.table(donnees,sep="\\t",dec=".",header=TRUE) #### charge le fichier de resultat sur les tendances annuelles par esp\xc3\xa8ce / load annual population evolution trend for each species obtained with the function mainglm\n+donneesTrend <- read.table(donneesTrend,sep="\\t",dec=".",header=TRUE)#### charge le fichier de resultat sur les tendances sur la periode etudi\xc3\xa9e par esp\xc3\xa8ce / load population evolution trend on the studied period for each species obtained with the function mainglm\n+tabsp <- read.table(tabSpe'..b'e indicators\n+\n+\n+groupeNom = c("generaliste","milieux batis","milieux forestiers","milieux agricoles")\n+groupeCouleur = c("black","firebrick3","chartreuse4","orange")\n+\n+vars_donnees<-c("id","code_espece","nom_espece","indicateur","annee","abondance_relative","IC_inferieur","IC_superieur","erreur_standard","p_value","significatif","nb_carre","nb_carre_presence","abondance")\n+err_msg_donnees<-"\\nThe yearly species variation dataset doesn\'t have the right format. It need to have following 14 variables :\\n- id\\n- code_espece\\n- nom_espece\\n- indicateur\\n- annee\\n- abondance_relative\\n- IC_inferieur\\n- IC_superieur\\n- erreur_standard\\n- p_value\\n- significatif\\n- nb_carre\\n- nb_carre_presence\\n- abondance\\n"\n+\n+vars_donneesTrend<-c("id","code_espece","nom_espece","indicateur","nombre_annees","premiere_annee","derniere_annee","tendance","IC_inferieur","IC_superieur","pourcentage_variation","erreur_standard","p_value","significatif","categorie_tendance_EBCC","mediane_occurrence","valide","raison_incertitude")\n+err_msg_donneesTrend<-"\\nThe species global tendances dataset doesn\'t have the right format. It need to have following 18 variables :\\n- id\\n- code_espece\\n- nom_espece\\n- indicateur\\n- nombre_annees\\n- premiere_annee\\n- derniere_annee\\n- tendance\\n- IC_inferieur\\n- IC_superieur\\n- pourcentage_variation\\n- erreur_standard\\n- p_value\\n- significatif\\n- categorie_tendance_EBCC\\n mediane_occurrence\\n valide\\n raison_incertitude\\n"\n+\n+vars_tabsp<-c("espece","nom","nomscientific","indicateur","specialisation")\n+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"\n+\n+vars_tBiais<-c("occurrenceMed","biais")\n+err_msg_tBiais<-"\\nThe bias dataset doesn\'t have the right format. It need to have the following 2 variables :\\n- occurenceMed\\n- biais\\n"\n+\n+check_file(donnees,err_msg_donnees,vars_donnees,14)\n+check_file(donneesTrend,err_msg_donneesTrend,vars_donneesTrend,18)\n+check_file(tabsp,err_msg_tabsp,vars_tabsp,5)\n+check_file(tBiais,err_msg_tBiais,vars_tBiais,2)\n+\n+\n+spsFiltre=unique(levels(donnees$code_espece)) #### Recup\xc3\xa8re la liste des especes du tabCLEAN qui ont \xc3\xa9t\xc3\xa9 s\xc3\xa9lectionn\xc3\xa9e et qui ont pass\xc3\xa9 le filtre / retrieve species name that were selected and then filtered before\n+\n+tabsp=subset (tabsp, (espece %in% spsFiltre)) #### Enl\xc3\xa8ve les esp\xc3\xa8ces qui n\'ont pas pass\xc3\xa9 le filtre ou exclu manuellement pour les analyses / keep only selected species and species with enough data\n+sp=as.character(tabsp$espece) ##### liste des espece en code ou abbreviation gard\xc3\xa9es 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\n+tabsp=data.frame(tabsp,sp)### rajoute une colonne identique appel\xc3\xa9 sp / add new column called sp\n+\n+if(length(spExclude)!=0) {\n+ donnees <- subset(donnees,!(code_espece %in% spExclude))\n+ tabsp <- subset(tabsp, !(espece %in% spExclude))\n+\n+ cat("\\n\\nEsp\xc3\xa8ces exclues de l\'analyse :\\n")\n+ cat(spExclude)\n+ cat("\\n")\n+}\n+if(length(donnees$code_espece)==0){\n+ stop("There is no species left for the analyse.", call.=FALSE) #si pas plus d\'esp\xc3\xa8ce apr\xc3\xa8s filtre / if no more species after filter\n+}\n+\n+\n+\n+\n+## creation d\'un dossier pour y mettre les resultats / create folder for the output of the analyses ###### NORMALEMENT DOIT \xc3\x8bTRE DEJ2 CREER POUR LES SORTIES TENDANCES PAR SPS DONC PAS SUR QU IL FAUT REFAIRE CETTE ETAPE\n+\n+dir.create(paste("Output/",id,sep=""),recursive=TRUE,showWarnings=FALSE)\n+cat(paste("Create Output/",id,"\\n",sep=""))\n+dir.create(paste("Output/",id,"/Incertain/",sep=""),recursive=TRUE,showWarnings=FALSE)\n+cat(paste("Create Output/",id,"Incertain/\\n",sep=""))\n+\n+\n+\n+\n+\n+################## \n+### Do your analysis\n+analyseGroupe(id=id,tabsp=tabsp,donnees=donnees,donneesTrend=donneesTrend,ICfigureGroupeSp=TRUE,groupeNom = groupeNom,groupeCouleur=groupeCouleur)\n' |
b |
diff -r 000000000000 -r 06a11044e089 FunctTrendSTOCGalaxy.r --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/FunctTrendSTOCGalaxy.r Thu Apr 02 03:34:07 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 06a11044e089 biais.tabular --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/biais.tabular Thu Apr 02 03:34:07 2020 -0400 |
b |
@@ -0,0 +1,8 @@ +"occurrenceMed" "biais" +0 0.5 +2 0.61 +4 0.7 +6 0.76 +8 0.84 +10 0.88 +12 0.9 \ No newline at end of file |
b |
diff -r 000000000000 -r 06a11044e089 mainglm_group.xml --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/mainglm_group.xml Thu Apr 02 03:34:07 2020 -0400 |
[ |
@@ -0,0 +1,121 @@ +<tool id="stoceps_glm_group" name="Estimate temporal population evolution" version="@VERSION@"> + <description>by specialization group</description> + <macros> + <import>stoceps_macros.xml</import> + </macros> + <expand macro="mainglm_requirements"/> + <command detect_errors="exit_code"><![CDATA[ + Rscript + '$__tool_directory__/ExeMainglmParGroupGalaxy.r' + '$input_y_var' + '$input_glob_tendencies' + '$inputtabSpecies' + 'mainglm_group' + #if $settings.advanced=='advanced' + $settings.sp_code + #else + '' + #end if + '$__tool_directory__/FunctTrendSTOCGalaxy.r' + '$__tool_directory__/biais.tabular' + + '$data_group' + '$year_var_group' + '$glob_tend_group' + ]]> + </command> + <inputs> + <param name="input_y_var" type="data" format="tabular" label="Yearly variation dataset" help="Output from the 'Estimate temporal population evoution by species' tool."/> + <param name="input_glob_tendencies" type="data" format="tabular" label="Global tendencies dataset" help="Output from the 'Estimate temporal population evoution by species' tool."/> + <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)." /> + <conditional name="settings"> + <expand macro="stoceps_advanced_params_select"/> + <when value="advanced"> + <param name="sp_code" type="select" label="Filter species to exclude" help="Create a subsample by selecting the species codes you don't want to use." multiple="true" optional="true"> + <options from_dataset="input_glob_tendencies"> + <column name="value" index="1"/> + <filter type="unique_value" name="espece" column="1"/> + </options> + <sanitizer> + <valid initial="string.printable"> + <remove value="""/> + </valid> + </sanitizer> + </param> + </when> + </conditional> + </inputs> + <outputs> + <data name="data_group" from_work_dir="Output/mainglm_group/donneesGroupes_mainglm_group.tabular" format="tabular" label="Glm - Group data on ${on_string}"/> + <data name="year_var_group" from_work_dir="Output/mainglm_group/variationsAnnuellesGroupes_mainglm_group.tabular" format="tabular" label="Glm - Group yearly variations data on ${on_string}"/> + <data name="glob_tend_group" from_work_dir="Output/mainglm_group/tendancesGlobalesGroupes_mainglm_group.tabular" format="tabular" label="Glm - Group tendencies on ${on_string}"/> + <data name="plot_year_var_group" from_work_dir="Output/mainglm_group/variationsAnnuellesGroupes_mainglm_group.png" format="png" label="Glm - Group yearly variations plot on ${on_string}"/> + </outputs> + <tests> + <test> + <param name="inputtabSpecies" value="tabSpecies.csv"/> + <param name="input_y_var" value="mainglm_tab_years.tabular"/> + <param name="input_glob_tendencies" value ="mainglm_tab_global.tabular"/> + <param name="advanced" value="simple"/> + <output name="data_group"> + <assert_contents> + <has_n_lines n="37"/> + <has_size value="3277" delta="100"/> + </assert_contents> + </output> + <output name="year_var_group"> + <assert_contents> + <has_n_lines n="37"/> + <has_size value="1623" delta="100"/> + </assert_contents> + </output> + <output name="glob_tend_group"> + <assert_contents> + <has_n_lines n="3"/> + <has_size value="154" delta="20"/> + </assert_contents> + </output> + <output name="plot_year_var_group"> + <assert_contents> + <has_text text="PNG"/> + </assert_contents> + </output> + </test> + </tests> + <help><![CDATA[ +================================================= +STOC Estimate species population evolution +================================================= + +**What it does** + + + +Compute and plot evolution of species population by specialization group, using a glm model. + + +| + +**Input description** + +Two tabular files processed with the STOCs 'Preprocess population data' 'Filter species' on one hand and 'mainglm' tools on the other hand. + +One tabular species file, with a `species ID` column and species names. + +| + +**Output** + + +Two tabular files are created, they describe global tendencies and yearly variations per groups. One plot of yearly variations per group. +One tabular file describing species with several columns as species ID, species name, species scientific name and specialization status. +| + +**Source** + +UnPublished script available at http://www.vigienature.fr/sites/vigienature/files/atoms/files/analysestoceps_0.zip +the first version written by Romain Lorrilliere. + + ]]></help> + <expand macro="stoceps_bibref" /> +</tool> |
b |
diff -r 000000000000 -r 06a11044e089 stoceps_macros.xml --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/stoceps_macros.xml Thu Apr 02 03:34:07 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 06a11044e089 tabSpecies.csv --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/tabSpecies.csv Thu Apr 02 03:34:07 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' |