[Stacomir-commits] r198 - in pkg/stacomir: R examples examples/03_BilanFonctionnementDF inst/config man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Thu Sep 8 21:19:35 CEST 2016


Author: briand
Date: 2016-09-08 21:19:34 +0200 (Thu, 08 Sep 2016)
New Revision: 198

Added:
   pkg/stacomir/examples/03_BilanFonctionnementDF/
   pkg/stacomir/examples/03_BilanFonctionnementDF/bilanFonctionnementDF_example.R
   pkg/stacomir/man/choice_c-RefDF-method.Rd
   pkg/stacomir/man/choice_c-RefHorodate-method.Rd
Modified:
   pkg/stacomir/R/BilanFonctionnementDF.r
   pkg/stacomir/R/RefDC.r
   pkg/stacomir/R/RefDF.r
   pkg/stacomir/R/RefHorodate.r
   pkg/stacomir/R/interface_BilanFonctionnementDF.r
   pkg/stacomir/inst/config/generate_data.R
   pkg/stacomir/man/charge-BilanFonctionnementDF-method.Rd
   pkg/stacomir/man/choice-RefDC-method.Rd
   pkg/stacomir/man/choice-RefDF-method.Rd
   pkg/stacomir/man/choice-RefHorodate-method.Rd
   pkg/stacomir/man/choice_c-RefDC-method.Rd
   pkg/stacomir/man/connect-BilanFonctionnementDF-method.Rd
Log:
Developping RefDF

Modified: pkg/stacomir/R/BilanFonctionnementDF.r
===================================================================
--- pkg/stacomir/R/BilanFonctionnementDF.r	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/R/BilanFonctionnementDF.r	2016-09-08 19:19:34 UTC (rev 198)
@@ -25,21 +25,24 @@
 setClass(Class="BilanFonctionnementDF",
 		representation= representation(data="data.frame",
 				df="RefDF",
-				horodate="RefHorodate",
+				horodatedebut="RefHorodate",
+				horodatefin="RefHorodate",
 				requete="RequeteODBCwheredate"),
 		prototype=prototype(data=data.frame(),df=new("RefDF"),
-				horodate=new("RefHorodate"),
+				horodatedebut=new("RefHorodate"),
+				horodatefin=new("RefHorodate"),
 				requete=new("RequeteODBCwheredate"))
 )
 
 
 #' connect method for BilanFonctionnementDF
 #' 
+#' @param object An object of class \link{BilanFonctionnementDF-class}
 #' loads the working periods and type of arrest or disfunction of the DF
 #' @return  An object of class \code{BilanFonctionnementDF}
 #' 
 #' @author cedric.briand
-setMethod("connect",signature=signature("BilanFonctionnementDF"),definition=function(object,h) {
+setMethod("connect",signature=signature("BilanFonctionnementDF"),definition=function(object) {
 #  construit une requete ODBCwheredate
 			object at requete@baseODBC<-get("baseODBC",envir=envir_stacomi)
 			object at requete@select= paste("SELECT",
@@ -65,12 +68,22 @@
 
 #' charge method for BilanFonctionnementDF
 #' 
-#' used by the graphical interface to retreive the objects of Referential classes
+#' 
+#' used by the graphical interface to retrieve the objects of Referential classes
 #' assigned to envir_stacomi
-#' @return  An object of class \code{BilanFonctionnementDF}
+#' @note Fishways (DF) are of various nature, from very simple eel ladders fed by water discharged from the river,
+#' to more complex fishways with levels adjusted by the opening of various gates and regulators. 
+#' The objective of this class is to provide an assessment of the working status of a fishway throughout the year.
+#' A number of fishes ascending a fishway has meaning only if we know that the fishway is operational, and that the counting 
+#' orerated on the fishway has remained operational.
+#' In the database the operation of the fishway (DF) and counting device (DC) is agregated in one table (t_periodefonctdispositif_per).
+#' The column  per_etat_fonctionnement indicates whether the fishway is operational (with a boolean) and the column per_tar_code indicates
+#' the status of either the fishway or DC. 
+#' @param object An object of class \link{BilanFonctionnementDF-class}
+#' @return  An object of class \link{BilanFonctionnementDF-class}
 #' 
 #' @author cedric.briand
-setMethod("charge",signature=signature("BilanFonctionnementDF"),definition=function(object,h) {
+setMethod("charge",signature=signature("BilanFonctionnementDF"),definition=function(object) {
 #  construit une requete ODBCwheredate
 			# chargement des donnees dans l'environnement de la fonction
 			if (exists("refDF",envir=envir_stacomi)) {
@@ -80,13 +93,13 @@
 			}     
 			
 			if (exists("fonctionnementDF_date_debut",envir=envir_stacomi)) {
-				object at requete@datedebut<-get("fonctionnementDF_date_debut",envir=envir_stacomi)@horodate
+				object at horodatedebut<-get("fonctionnementDF_date_debut",envir=envir_stacomi)@horodate
 			} else {
 				funout(get("msg",envir=envir_stacomi)$ref.5,arret=TRUE)
 			}
 			
 			if (exists("fonctionnementDF_date_fin",envir=envir_stacomi)) {
-				object at requete@datefin<-get("fonctionnementDF_date_fin",envir=envir_stacomi)@horodate
+				object at horodatefin<-get("fonctionnementDF_date_fin",envir=envir_stacomi)@horodate
 			} else {
 				funout(get("msg",envir=envir_stacomi)$ref.6,arret=TRUE)
 			}			
@@ -95,6 +108,40 @@
 			return(object)
 		})
 
+#' command line interface for BilanFonctionnementDF class
+#' 
+#' The choice_c method fills in the data slot for RefDC, and then 
+#' uses the choice_c methods of these object to "select" the data.
+#' @param object An object of class \link{RefDC-class}
+#' @param horodatedebut A POSIXt or Date or character to fix the date of beginning of the Bilan
+#' @param horodatefin A POSIXt or Date or character to fix the last date of the Bilan
+#' @return An object of class \link{RefDC-class} with slots filled
+#' @author Cedric Briand \email{cedric.briand"at"eptb-vilaine.fr}
+#' @export
+setMethod("choice_c",signature=signature("BilanFonctionnementDF"),definition=function(object,horodatedebut,horodatefin,...){
+		
+			# only taxa present in the bilanMigration are used
+			fonctionnementDF<-new("BilanFonctionnementDF")
+			assign("fonctionnementDF",fonctionnementDF,envir=envir_stacomi)    
+			funout(get("msg",envir=envir_stacomi)$interface_BilanFonctionnementDC.1)
+			fonctionnementDF at df<-charge(fonctionnementDF at df)    
+			fonctionnementDF at df<-choice_c(fonctionnementDF at df)
+			# assigns the parameter (horodatedebut) of the method to the object using choice_c method for RefDF
+			fonctionnementDF at horodatedebut<-choice_c(fonctionnementDF at horodatedebut,
+					nomassign="fonctionnementDF_date_debut",
+					funoutlabel=get("msg",envir=envir_stacomi)$interface_Bilan_lot.5,
+					decal=-2,
+					horodate=horodatedebut)
+			fonctionnementDF at horodatefin<-choice_c(fonctionnementDF at horodate,
+					nomassign="fonctionnementDF_date_fin",
+					funoutlabel=get("msg",envir=envir_stacomi)$interface_Bilan_lot.6,
+					decal=-1,
+					horodate=horodatefin)
+			return(fonctionnementDF)
+		})
+
+
+
 #' funbarchartDF creates a barchart for BilanFonctionnementDF class
 #' 
 #' @note The program cuts periods which overlap between two month

Modified: pkg/stacomir/R/RefDC.r
===================================================================
--- pkg/stacomir/R/RefDC.r	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/R/RefDC.r	2016-09-08 19:19:34 UTC (rev 198)
@@ -48,6 +48,8 @@
 			
 		}   
 )
+
+
 #' Method to load the counting devices of the control station
 #' @return Object of class RefDC
 #' @author Cedric Briand \email{cedric.briand"at"eptb-vilaine.fr}
@@ -82,7 +84,10 @@
 			object at data<-requete at query
 			return(object)
 		})
-#' choice method for RefDC
+
+
+
+#' Graphical method to choose a fishway through the interface
 #' 
 #' @note   The choice method has for arguments a report (bilan) object
 #'  (e.g) is called from a report Bilan(e.g Bilan_carlot).
@@ -269,12 +274,12 @@
 		})
 
 
-#' choice_c method for RefDC
+#' Command line interface to select a counting device
 #' 
 #' the choice_c method is intented to have the same behaviour as choice (which creates a
 #' widget in the graphical interface) but from the command line.  The parameters for dc are transformed to integer as the RefDC only 
 #' takes integer in the dc slots. The method also loads the stations and ouvrages (dams) associated with the counting device (dc).
-#' The values passed to thchoice_cchargec method are then checked with the setValidty method.
+#' The values passed to the choice_c method are then checked with the setValidty method.
 #' Finally, if an objectBilan is passed as a parameter, the method will do a charge_avec_filtre to select only the taxa present in the counting devices
 #' @param object an object of class RefDC
 #' @param dc a character vector of dc chosen
@@ -301,9 +306,8 @@
 			validObject(object) 		
 # the method validObject verifies that the dc is in the data slot of RefDC			
 			
-			object at ouvrage= object at data$dif_ouv_identifiant[ object at data$dc%in% object at dc_selectionne]
-			object at station= as.character(object at data$sta_code[ object at data$dc%in% object at dc_selectionne])
-			object at ouvrage=object at data$dif_ouv_identifiant[object at data$dc%in%object at dc_selectionne]
+			object at station<- as.character(object at data$sta_code[ object at data$dc%in% object at dc_selectionne])
+			object at ouvrage<-object at data$dif_ouv_identifiant[object at data$dc%in%object at dc_selectionne]
 			assign("refDC",object,envir=envir_stacomi)
 			return(object)
 		})
\ No newline at end of file

Modified: pkg/stacomir/R/RefDF.r
===================================================================
--- pkg/stacomir/R/RefDF.r	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/R/RefDF.r	2016-09-08 19:19:34 UTC (rev 198)
@@ -8,6 +8,7 @@
 #' \code{new("RefDF", df_selectionne=integer(), ouvrage=integer(),
 #' data=data.frame())}.  
 #' 
+#' 
 #' @slot df_selectionne Object of class \code{"integer"} The identifier of the fishway
 #' @slot ouvrage Object of class \code{"integer"} The attached dam
 #' @slot data Object of class \code{"data.frame"} Data concerning the fishway
@@ -30,7 +31,24 @@
 #' @family Referential objects
 setClass(Class="RefDF",representation=
 				representation(df_selectionne="integer",ouvrage="integer",data="data.frame") )
-                               
+
+setValidity("RefDF",method=function(object){
+			if (length(object at df_selectionne)!=0){		
+				if (nrow(object at data)>0) {
+					concord<-object at df_selectionne%in%object at data$df					
+					if (any(!concord)){
+						return(paste("No data for DF",object at df_selectionne[!concord]))
+						
+					} else {
+						return(TRUE)
+					}
+				} else {
+					return("You tried to set a value for df_selectionne without initializing the data slot")
+				}
+			}  else return(TRUE)
+			
+		}   
+)
 #' Loading method for DF referential objects
 #' 
 #' @return An object of class RefDF
@@ -64,8 +82,8 @@
 			return(object)
 		})
 
-#' Choice method for DF referential objects
-#' 
+#' Graphical method to choose a fishway through the interface
+#' @param object An object of class \link{RefDF-class}
 #' @note the choice method assigns an object of class refDF in the environment envir_stacomi
 #' @author Cedric Briand \email{cedric.briand"at"eptb-vilaine.fr}
 #' @examples  
@@ -103,4 +121,41 @@
 			} else {
 				funout(get("msg",envir=envir_stacomi)$RefDF.4,arret=TRUE)
 			}
+		})
+
+
+#' Command line interface to choose a fishway
+#' 
+#' the choice_c method is intented to have the same behaviour as choice (which creates a
+#' widget in the graphical interface) but from the command line.  The parameters for dF are transformed to integer as the RefDF only 
+#' takes integer in the df slots. 
+#' DF are third in hierarchy in the stacomi database Station>ouvrage>DF>DC>operation. This class is only used in the
+#' BilanFonctionnementDF class.
+#' @param object an object of class \link{RefDF-class}
+#' @param df a character vector of df chosen
+#' @author Cedric Briand \email{cedric.briand"at"eptb-vilaine.fr}
+#' @examples
+#' \dontrun{
+#' win=gwindow()
+#' group=ggroup(container=win,horizontal=FALSE)
+#' object=new("RefDC")
+#' object<-charge(object)
+#' objectBilan=new("BilanMigrationMult")
+#' choice_c(object=object,objectBilan=objectBilan,dc=1)
+#' }
+setMethod("choice_c",signature=signature("RefDF"),definition=function(object,df) {
+			if (class(df)=="numeric") {
+				df<-as.integer(df) 
+			} else if (class(df)=="character"){
+				df=as.integer(as.numeric(df))
+			}
+			if (any(is.na(df))) stop ("NA values df")
+			
+			
+			object at df_selectionne<-df
+			validObject(object) 		
+# the method validObject verifies that the df is in the data slot of RefDF			
+			
+				assign("refDF",object,envir=envir_stacomi)
+			return(object)
 		})
\ No newline at end of file

Modified: pkg/stacomir/R/RefHorodate.r
===================================================================
--- pkg/stacomir/R/RefHorodate.r	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/R/RefHorodate.r	2016-09-08 19:19:34 UTC (rev 198)
@@ -4,7 +4,7 @@
 #' @author Cedric Briand \email{cedric.briand"at"eptb-vilaine.fr}
 validite_RefHorodate=function(object)
 {
-	rep1= class(object at dateDebut)[1]=="POSIXt"
+	rep1= class(object at horodate)[2]=="POSIXt"
 	
 	return(ifelse(rep1,TRUE,FALSE))
 }
@@ -54,50 +54,113 @@
 			return(object) 
 		})
 # retourne l'annee d'avant l'annee en cours
-setGeneric("getanneeprec",def=function(object,...) standardGeneric("getanneeprec"))
-setMethod("getanneeprec",signature=signature("RefHorodate"),definition=function(object,decal){
-			anneeprec=as.numeric(strftime(object at horodate,"%Y"))+decal
-			object at horodate<-strptime(paste(anneeprec,"-01-01",sep=""),format="%Y-%m-%d")
-			return (object)
-		})
 
 
-#' choice method for RefHorodate
-#' 
+
+
+
+
+#' Graphical interface
+#' @param object An object of class \link{RefHorodate-class}
+#' @param label Label for the gframe
+#' @param nomassing The name assigned in environment envir_stacomi
+#' @param funoutlabel, text displayed by the interface
+#' @param decale Default 0, number of years to shift forward or backward 
 #' @return Selects the date in the graphical interface
-#' 
-#' @author cedric.briand
-#' @docType methods
-setMethod("choice",signature=signature("RefHorodate"),definition=function(object,label="date",nomassign="horodate",funoutlabel="nous avons le choice dans la date\n",decal=0,affichecal=TRUE) {
+setMethod("choice",signature=signature("RefHorodate"),definition=function(object,label="date",
+				nomassign="horodate",
+				funoutlabel="nous avons le choix dans la date\n",
+				decal=0) {
 			hwinhor=function(h,...){
 				object=setRefHorodate(object,svalue(horodate))
-				if (affichecal){
-			    # bug dans horocal
-				#	svalue(horocal)<-as.character(strftime(object at horodate,"%Y-%m-%d"))
-				}
 				assign(nomassign,object,envir_stacomi)
 				funout(funoutlabel)
 				#print(object)
 				#dispose(winpa)
 			}
 			if (decal!=0){
-				object<-getanneeprec(object,decal)
+				# Returns the first horodate of a year shifted by decal
+				# @param horodate The horodate to shift (class POSIXt)
+				# @param decal number of year to shift
+				# @return A POSIXt
+				shiftyear<-function(horodate,decal){
+					anneeprec=as.numeric(strftime(horodate,"%Y"))+decal
+					return(strptime(paste(anneeprec,"-01-01",sep=""),format="%Y-%m-%d"))
+				}
+				object at horodate<-shiftyear(object at horodate,decal)
 			}
 			winhor=gframe(label,container=group,horizontal=!affichecal)
 			pg<-ggroup(horizontal=FALSE,container=winhor)
 			horodate<-gedit(getRefHorodate(object),container=pg,handler=hwinhor,width=20)
 			horodate2=as.character(strftime(object at horodate,"%Y-%m-%d"))
-			if (affichecal) {
-#				horocal<-gcalendar(horodate2,container=pg,handler=function(h,...){
-#							svalue(horodate)<-as.character(strftime(
-#											strptime(svalue(horocal),"%Y-%m-%d"),
-#											"%Y-%m-%d %H:%M:%S"))
-#						} ) 
-			}
 			gbutton("OK", container=winhor,handler=hwinhor,icon="execute")
 		})
 
-# showClass("PasDeTemps")
-# validObject( pasDeTemps)
-# showMethods("suivant")
 
+
+#' Command line
+#' @param object An object of class \link{RefHorodate-class}
+#' @param label Label for the gframe
+#' @param nomassing The name assigned in environment envir_stacomi
+#' @param funoutlabel, text displayed by the interface
+#' @param decale Default 0, number of years to shift forward or backward, the date will be set to the first day of the year
+#' @param affichecal Default TRUE, should the calendar be displayed
+#' @param horodate The horodate to set, formats "%d/%m/%Y %H:%M:%s", "%d/%m/%y %H:%M:%s", "%Y-%m-%d  %H:%M:%s"
+#' \dots are accepted
+#' @return An object of class \link{RefHorodate-class} with slot \emph{horodate} set
+setMethod("choice_c",signature=signature("RefHorodate"),definition=function(object,
+				nomassign="horodate",
+				funoutlabel="nous avons le choix dans la date\n",
+				decal=0,
+				horodate
+		) {
+			# parse the horohorodate
+			if (length(horodate)>1) stop("horodate should be a vector of length 1")
+			if (is.null(horodate)) stop("horodate should not be null")
+			if (class(horodate)=="character") {
+				if (grepl("/",horodate)){
+					.horodate=strptime(horodate, format="%d/%m/%Y %H:%M:%s")
+					if (is.na(.horodate)){
+						.horodate=strptime(horodate, format="%d/%m/%y %H:%M:%s")				
+					}
+					if (is.na(.horodate)){
+						.horodate=strptime(horodate, format="%d/%m/%y %H:%M")				
+					}
+					if (is.na(.horodate)){
+						.horodate=strptime(horodate, format="%d/%m/%Y %H:%M")				
+					}
+				} else if (grepl("-",horodate)){
+					.horodate=strptime(horodate, format="%Y-%m-%d  %H:%M:%s")
+					if (is.na(.horodate)){
+						.horodate=strptime(horodate, format="%d-%m-%Y  %H:%M:%s")				
+					}
+					if (is.na(.horodate)){
+						.horodate=strptime(horodate, format="%Y-%m-%d  %H:%M")				
+					}
+					if (is.na(.horodate)){
+						.horodate=strptime(horodate, format="%d-%m-%Y  %H:%M")				
+					}
+				}
+		
+			} else if (class(horodate)=="Date"){
+				.horodate<-as.POSIXlt(horodate)
+			} else if (class(horodate)[2]=="POSIXt"){
+				.horodate=horodate
+			}
+			object at horodate=.horodate	
+			if (decal!=0){
+				# Returns the first horodate of a year shifted by decal
+				# @param horodate The horodate to shift (class POSIXt)
+				# @param decal number of year to shift
+				# @return A POSIXt
+				shiftyear<-function(horodate,decal){
+					anneeprec=as.numeric(strftime(horodate,"%Y"))+decal
+					return(strptime(paste(anneeprec,"-01-01",sep=""),format="%Y-%m-%d"))
+				}
+				object at horodate<-shiftyear(object at horodate,decal)
+			}
+			validObject(object)				
+			assign(nomassign,object,envir_stacomi)
+			funout(funoutlabel)	
+		})
+

Modified: pkg/stacomir/R/interface_BilanFonctionnementDF.r
===================================================================
--- pkg/stacomir/R/interface_BilanFonctionnementDF.r	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/R/interface_BilanFonctionnementDF.r	2016-09-08 19:19:34 UTC (rev 198)
@@ -1,4 +1,3 @@
-# Nom fichier :        interface_BilanFonctionnementDF.R    (classe)
 #' interface for BilanFonctionnementDF class
 #' @author Cedric Briand \email{cedric.briand"at"eptb-vilaine.fr}
 interface_BilanFonctionnementDF = function()
@@ -14,12 +13,12 @@
    gWidgets::add(ggroupboutons,group)
     
     choice(fonctionnementDF at df)
-	choice(fonctionnementDF at horodate,
+	choice(fonctionnementDF at horodatedebut,
 			label=get("msg",envir=envir_stacomi)$interface_Bilan_lot.3,
 			nomassign="fonctionnementDF_date_debut",
 			funoutlabel=get("msg",envir=envir_stacomi)$interface_Bilan_lot.5,
 			decal=-2)
-	choice(fonctionnementDF at horodate,
+	choice(fonctionnementDF at horodatefin,
 			label=get("msg",envir=envir_stacomi)$interface_Bilan_lot.4,
 			nomassign="fonctionnementDF_date_fin",
 			funoutlabel=get("msg",envir=envir_stacomi)$interface_Bilan_lot.6,
@@ -39,9 +38,5 @@
     add(group, gmenu(toolbarlist))
     add(group,gbutton(text = "graph", handler = function(h,...){X11()})) 
     gWidgets::addSpring(group)
-    #graphes=ggraphics(width=600,height=400)
-    #add(ggrouptotal1,graphes )  # on ajoute au groupe horizontal
-    # A cet endroit sinon ouvre plusieurs fenetres pour plusieurs choses
-    #assign("graphes",graphes,envir=envir_stacomi)
 	grDevices::X11()
 }
\ No newline at end of file

Added: pkg/stacomir/examples/03_BilanFonctionnementDF/bilanFonctionnementDF_example.R
===================================================================
--- pkg/stacomir/examples/03_BilanFonctionnementDF/bilanFonctionnementDF_example.R	                        (rev 0)
+++ pkg/stacomir/examples/03_BilanFonctionnementDF/bilanFonctionnementDF_example.R	2016-09-08 19:19:34 UTC (rev 198)
@@ -0,0 +1,15 @@
+stacomi(gr_interface=FALSE,
+		login_window=FALSE,
+		database_expected=FALSE)
+bDF=new("BilanFonctionnementDF")
+choice_c(fonctionnementDF at df,df=2)
+choice(fonctionnementDF at horodate,
+		label=get("msg",envir=envir_stacomi)$interface_Bilan_lot.3,
+		nomassign="fonctionnementDF_date_debut",
+		funoutlabel=get("msg",envir=envir_stacomi)$interface_Bilan_lot.5,
+		decal=-2)
+choice(fonctionnementDF at horodate,
+		label=get("msg",envir=envir_stacomi)$interface_Bilan_lot.4,
+		nomassign="fonctionnementDF_date_fin",
+		funoutlabel=get("msg",envir=envir_stacomi)$interface_Bilan_lot.6,
+		decal=-1)

Modified: pkg/stacomir/inst/config/generate_data.R
===================================================================
--- pkg/stacomir/inst/config/generate_data.R	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/inst/config/generate_data.R	2016-09-08 19:19:34 UTC (rev 198)
@@ -58,4 +58,15 @@
 bM_Arzal at taxons@data[,"tax_nom_commun"]<-iconv(bM_Arzal at taxons@data[,"tax_nom_commun"],from="latin1",to="UTF8")
 bM_Arzal at stades@data[,"std_libelle"]<-iconv(bM_Arzal at stades@data[,"std_libelle"],from="latin1",to="UTF8")
 setwd("F:/workspace/stacomir/pkg/stacomir")
-devtools::use_data(bM_Arzal,internal=FALSE,overwrite=TRUE)
\ No newline at end of file
+devtools::use_data(bM_Arzal,internal=FALSE,overwrite=TRUE)
+
+
+
+#################################
+# generates dataset for BilanFonctionnementDF
+##################################
+stacomi(gr_interface=FALSE,
+		login_window=FALSE,
+		database_expected=FALSE)
+bDF=new("BilanFonctionnementDF")
+bDF

Modified: pkg/stacomir/man/charge-BilanFonctionnementDF-method.Rd
===================================================================
--- pkg/stacomir/man/charge-BilanFonctionnementDF-method.Rd	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/man/charge-BilanFonctionnementDF-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -5,15 +5,28 @@
 \alias{charge,BilanFonctionnementDF-method}
 \title{charge method for BilanFonctionnementDF}
 \usage{
-\S4method{charge}{BilanFonctionnementDF}(object, h)
+\S4method{charge}{BilanFonctionnementDF}(object)
 }
+\arguments{
+\item{object}{An object of class \link{BilanFonctionnementDF-class}}
+}
 \value{
-An object of class \code{BilanFonctionnementDF}
+An object of class \link{BilanFonctionnementDF-class}
 }
 \description{
-used by the graphical interface to retreive the objects of Referential classes
+used by the graphical interface to retrieve the objects of Referential classes
 assigned to envir_stacomi
 }
+\note{
+Fishways (DF) are of various nature, from very simple eel ladders fed by water discharged from the river,
+to more complex fishways with levels adjusted by the opening of various gates and regulators. 
+The objective of this class is to provide an assessment of the working status of a fishway throughout the year.
+A number of fishes ascending a fishway has meaning only if we know that the fishway is operational, and that the counting 
+orerated on the fishway has remained operational.
+In the database the operation of the fishway (DF) and counting device (DC) is agregated in one table (t_periodefonctdispositif_per).
+The column  per_etat_fonctionnement indicates whether the fishway is operational (with a boolean) and the column per_tar_code indicates
+the status of either the fishway or DC.
+}
 \author{
 cedric.briand
 }

Modified: pkg/stacomir/man/choice-RefDC-method.Rd
===================================================================
--- pkg/stacomir/man/choice-RefDC-method.Rd	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/man/choice-RefDC-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -3,7 +3,7 @@
 \docType{methods}
 \name{choice,RefDC-method}
 \alias{choice,RefDC-method}
-\title{choice method for RefDC}
+\title{Graphical method to choose a fishway through the interface}
 \usage{
 \S4method{choice}{RefDC}(object, objectBilan = NULL, is.enabled = TRUE)
 }
@@ -14,7 +14,7 @@
 frame may cause some frame to be disabled. When created the frame is enabled.}
 }
 \description{
-choice method for RefDC
+Graphical method to choose a fishway through the interface
 }
 \note{
 The choice method has for arguments a report (bilan) object

Modified: pkg/stacomir/man/choice-RefDF-method.Rd
===================================================================
--- pkg/stacomir/man/choice-RefDF-method.Rd	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/man/choice-RefDF-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -3,12 +3,15 @@
 \docType{methods}
 \name{choice,RefDF-method}
 \alias{choice,RefDF-method}
-\title{Choice method for DF referential objects}
+\title{Graphical method to choose a fishway through the interface}
 \usage{
 \S4method{choice}{RefDF}(object)
 }
+\arguments{
+\item{object}{An object of class \link{RefDF-class}}
+}
 \description{
-Choice method for DF referential objects
+Graphical method to choose a fishway through the interface
 }
 \note{
 the choice method assigns an object of class refDF in the environment envir_stacomi

Modified: pkg/stacomir/man/choice-RefHorodate-method.Rd
===================================================================
--- pkg/stacomir/man/choice-RefHorodate-method.Rd	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/man/choice-RefHorodate-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -3,20 +3,27 @@
 \docType{methods}
 \name{choice,RefHorodate-method}
 \alias{choice,RefHorodate-method}
-\title{choice method for RefHorodate}
+\title{Graphical interface}
 \usage{
 \S4method{choice}{RefHorodate}(object, label = "date",
   nomassign = "horodate",
-  funoutlabel = "nous avons le choice dans la date\\n", decal = 0,
-  affichecal = TRUE)
+  funoutlabel = "nous avons le choix dans la date\\n", decal = 0)
 }
+\arguments{
+\item{object}{An object of class \link{RefHorodate-class}}
+
+\item{label}{Label for the gframe}
+
+\item{funoutlabel, }{text displayed by the interface}
+
+\item{nomassing}{The name assigned in environment envir_stacomi}
+
+\item{decale}{Default 0, number of years to shift forward or backward}
+}
 \value{
 Selects the date in the graphical interface
 }
 \description{
-choice method for RefHorodate
+Graphical interface
 }
-\author{
-cedric.briand
-}
 

Modified: pkg/stacomir/man/choice_c-RefDC-method.Rd
===================================================================
--- pkg/stacomir/man/choice_c-RefDC-method.Rd	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/man/choice_c-RefDC-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -3,7 +3,7 @@
 \docType{methods}
 \name{choice_c,RefDC-method}
 \alias{choice_c,RefDC-method}
-\title{choice_c method for RefDC}
+\title{Command line interface to select a counting device}
 \usage{
 \S4method{choice_c}{RefDC}(object, dc)
 }
@@ -16,7 +16,7 @@
 the choice_c method is intented to have the same behaviour as choice (which creates a
 widget in the graphical interface) but from the command line.  The parameters for dc are transformed to integer as the RefDC only 
 takes integer in the dc slots. The method also loads the stations and ouvrages (dams) associated with the counting device (dc).
-The values passed to thchoice_cchargec method are then checked with the setValidty method.
+The values passed to the choice_c method are then checked with the setValidty method.
 Finally, if an objectBilan is passed as a parameter, the method will do a charge_avec_filtre to select only the taxa present in the counting devices
 }
 \examples{

Added: pkg/stacomir/man/choice_c-RefDF-method.Rd
===================================================================
--- pkg/stacomir/man/choice_c-RefDF-method.Rd	                        (rev 0)
+++ pkg/stacomir/man/choice_c-RefDF-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -0,0 +1,35 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/RefDF.r
+\docType{methods}
+\name{choice_c,RefDF-method}
+\alias{choice_c,RefDF-method}
+\title{Command line interface to choose a fishway}
+\usage{
+\S4method{choice_c}{RefDF}(object, df)
+}
+\arguments{
+\item{object}{an object of class \link{RefDF-class}}
+
+\item{df}{a character vector of df chosen}
+}
+\description{
+the choice_c method is intented to have the same behaviour as choice (which creates a
+widget in the graphical interface) but from the command line.  The parameters for dF are transformed to integer as the RefDF only 
+takes integer in the df slots. 
+DF are third in hierarchy in the stacomi database Station>ouvrage>DF>DC>operation. This class is only used in the
+BilanFonctionnementDF class.
+}
+\examples{
+\dontrun{
+win=gwindow()
+group=ggroup(container=win,horizontal=FALSE)
+object=new("RefDC")
+object<-charge(object)
+objectBilan=new("BilanMigrationMult")
+choice_c(object=object,objectBilan=objectBilan,dc=1)
+}
+}
+\author{
+Cedric Briand \email{cedric.briand"at"eptb-vilaine.fr}
+}
+

Added: pkg/stacomir/man/choice_c-RefHorodate-method.Rd
===================================================================
--- pkg/stacomir/man/choice_c-RefHorodate-method.Rd	                        (rev 0)
+++ pkg/stacomir/man/choice_c-RefHorodate-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -0,0 +1,33 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/RefHorodate.r
+\docType{methods}
+\name{choice_c,RefHorodate-method}
+\alias{choice_c,RefHorodate-method}
+\title{Command line}
+\usage{
+\S4method{choice_c}{RefHorodate}(object, nomassign = "horodate",
+  funoutlabel = "nous avons le choix dans la date\\n", decal = 0, horodate)
+}
+\arguments{
+\item{object}{An object of class \link{RefHorodate-class}}
+
+\item{funoutlabel, }{text displayed by the interface}
+
+\item{horodate}{The horodate to set, formats "%d/%m/%Y %H:%M:%s", "%d/%m/%y %H:%M:%s", "%Y-%m-%d  %H:%M:%s"
+\dots are accepted}
+
+\item{label}{Label for the gframe}
+
+\item{nomassing}{The name assigned in environment envir_stacomi}
+
+\item{decale}{Default 0, number of years to shift forward or backward, the date will be set to the first day of the year}
+
+\item{affichecal}{Default TRUE, should the calendar be displayed}
+}
+\value{
+An object of class \link{RefHorodate-class} with slot \emph{horodate} set
+}
+\description{
+Command line
+}
+

Modified: pkg/stacomir/man/connect-BilanFonctionnementDF-method.Rd
===================================================================
--- pkg/stacomir/man/connect-BilanFonctionnementDF-method.Rd	2016-09-08 14:15:52 UTC (rev 197)
+++ pkg/stacomir/man/connect-BilanFonctionnementDF-method.Rd	2016-09-08 19:19:34 UTC (rev 198)
@@ -5,13 +5,17 @@
 \alias{connect,BilanFonctionnementDF-method}
 \title{connect method for BilanFonctionnementDF}
 \usage{
-\S4method{connect}{BilanFonctionnementDF}(object, h)
+\S4method{connect}{BilanFonctionnementDF}(object)
 }
+\arguments{
+\item{object}{An object of class \link{BilanFonctionnementDF-class}
+loads the working periods and type of arrest or disfunction of the DF}
+}
 \value{
 An object of class \code{BilanFonctionnementDF}
 }
 \description{
-loads the working periods and type of arrest or disfunction of the DF
+connect method for BilanFonctionnementDF
 }
 \author{
 cedric.briand



More information about the Stacomir-commits mailing list