R/gprogressbar.R

##' @include GWidget.R
NULL

##' Toolkit  constructor
##'
##' @export
##' @rdname gWidgets2RGtk2-undocumented
##' @method .gprogressbar guiWidgetsToolkitRGtk2
## @export .gprogressbar guiWidgetsToolkitRGtk2
.gprogressbar.guiWidgetsToolkitRGtk2 <- function(toolkit, value, container, ...) {
  GProgressBar$new(toolkit, value, container, ...)
}

##' For RGtk2, the Gprogressbar class has the extra reference method
##' \code{set_border}. The \code{border} argument has been deprecated.
##' @rdname gWidgets2RGtk2-package
GProgressBar <- setRefClass("GProgressBar",
                            contains="GWidget",
                            methods=list(
                              initialize=function(toolkit=NULL, value, container, ...) {
                                
                                widget <<- gtkProgressBar()

                                if(!missing(value))
                                  set_value(value)
                                
                                initFields(block=widget)
                                
                                add_to_parent(container, .self, ...)

                                callSuper(toolkit)
                              },
                              set_value=function(value, index=TRUE, drop=TRUE, ...) {
                                if(is.null(value)) {
                                  widget$pulse()
                                } else {
                                  value <- as.numeric(value)
                                  frac <- (value/100) %% 1
                                  widget$setFraction(frac)
                                }
                              },
                              get_value=function(index=TRUE, drop=TRUE, ...) {
                                as.integer(widget$getFraction() * 100)
                              }
                              ))

Try the gWidgets2RGtk2 package in your browser

Any scripts or data that you put into this service are public.

gWidgets2RGtk2 documentation built on May 2, 2019, 2:44 a.m.