[Georob-commits] r10 - in pkg: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Thu Jul 4 14:40:02 CEST 2013


Author: papritz
Date: 2013-07-04 14:40:02 +0200 (Thu, 04 Jul 2013)
New Revision: 10

Modified:
   pkg/ChangeLog
   pkg/DESCRIPTION
   pkg/NAMESPACE
   pkg/R/georob.S3methods.R
   pkg/R/georob.cv.R
   pkg/R/georob.exported.functions.R
   pkg/R/georob.private.functions.R
   pkg/man/cv.georob.Rd
   pkg/man/georob.Rd
   pkg/man/georob.control.Rd
   pkg/man/plot.georob.Rd
Log:
changes in transformations of rotation angles of anisotropic variograms


Modified: pkg/ChangeLog
===================================================================
--- pkg/ChangeLog	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/ChangeLog	2013-07-04 12:40:02 UTC (rev 10)
@@ -106,3 +106,11 @@
 * georob.private.functions.R (all functions): substituting [["x"]] for $x in all lists
 * georob.S3methods.R (all functions): substituting [["x"]] for $x in all lists
 * variogram.R (all functions): substituting [["x"]] for $x in all lists
+
+
+2013-07-02  Andreas Papritz  <papritz at env.ethz.ch>
+
+* georob.exported.functions.R (georob, param.transf, fwd.transf, dfwd.transf, bwd.transf): new transformation of rotation angles
+* georob.private.functions.R (georob.fit, prepare.likelihood.calculations): new transformation of rotation angles
+* georob.S3methods.R (print.georob, summary.georob): new transformation of rotation angles
+* georob.cv.R (cv.georob): passing initial values of aniso and fit.aniso to georob via update

Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/DESCRIPTION	2013-07-04 12:40:02 UTC (rev 10)
@@ -1,8 +1,8 @@
 Package: georob
 Type: Package
 Title: Robust Geostatistical Analysis of Spatial Data
-Version: 0.1-0
-Date: 2012-12-14
+Version: 0.1-1
+Date: 2013-06-20
 Authors at R: c(
   person( "Andreas", "Papritz", role = c( "cre", "aut" ), 
           email =  "andreas.papritz at env.ethz.ch" ),
@@ -17,4 +17,4 @@
          and block kriging predictions, along with utility functions for 
          cross-validation and for unbiased back-transformation of kriging 
          predictions of log-transformed data.
-License: GPL
+License: GPL (>= 2)

Modified: pkg/NAMESPACE
===================================================================
--- pkg/NAMESPACE	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/NAMESPACE	2013-07-04 12:40:02 UTC (rev 10)
@@ -31,7 +31,7 @@
   validate.predictions              # ok
 )
 
-# documented but unexported functions
+# documented but not exported functions
 #
 #   deviance.georob,                # ok
 #   fixed.effects.georob,           # ok

Modified: pkg/R/georob.S3methods.R
===================================================================
--- pkg/R/georob.S3methods.R	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/R/georob.S3methods.R	2013-07-04 12:40:02 UTC (rev 10)
@@ -90,6 +90,7 @@
   ## 2012-02-07 AP change for anisotropic variograms 
   ## 2012-12-18 AP invisible(x)
   ## 2013-06-12 AP substituting [["x"]] for $x in all lists
+  ## 2013-07-02 AP new transformation of rotation angles
   
   ## code borrowed from print.lmrob for printing fixed effects coeffcients
   
@@ -123,7 +124,7 @@
     
     cat("\n")
     cat( "Anisotropy parameters: ", "\n" )
-    aniso <- x[["aniso"]][["aniso"]] * c( rep(1, 2), rep( 180/pi, 3 ) )
+    aniso <- x[["aniso"]][["aniso"]]
     names( aniso ) <- ifelse(
       x[["initial.objects"]][["fit.aniso"]],
       names( aniso ),
@@ -484,6 +485,7 @@
   ## 2013-04-23 AP new names for robustness weights
   ## 2013-05-31 AP revised expansion of covariance matrices
   ## 2013-06-12 AP substituting [["x"]] for $x in all lists
+  ## 2013-07-03 AP new transformation of rotation angles
   
   covmat       <- expand( object[["cov"]] )
   
@@ -521,7 +523,7 @@
   
   if( !object[["aniso"]][["isotropic"]] ) ans[["param"]] <- rbind( 
     ans[["param"]],
-    as.matrix( object[["aniso"]][["aniso"]], ncol = 1 ) * c( rep( 1, 2 ), rep( 180/pi, 3 ) )
+    as.matrix( object[["aniso"]][["aniso"]], ncol = 1 )
   )
   
   colnames( ans[["param"]] ) <- "Estimate"
@@ -579,29 +581,47 @@
         )
         sel.names <- sel.names[sr]
         
-        ff <- c( rep( 1, length( object[["param"]] ) + 2 ), rep( 180/pi, 3 ) )
-        names( ff ) <- names( c( object[["param"]], object[["aniso"]][["aniso"]] ) )
-        
         ci[sel.names, ] <- t( 
           sapply(
             sel.names,
-            function( x, param, f, se, param.tf, trafo.fct, inv.trafo.fct ){
+            function( x, param, se, param.tf, trafo.fct, inv.trafo.fct ){
               inv.trafo.fct[[param.tf[x]]]( 
                 trafo.fct[[param.tf[x]]]( param[x] ) + 
                 c(-1, 1) * se[x] * qnorm( (1-signif)/2, lower.tail = FALSE ) 
               )
             },
             param         = c( object[["param"]], object[["aniso"]][["aniso"]] ),
-            f             = ff,
             se            = se,
             param.tf      = object[["param.tf"]],
             trafo.fct     = object[["fwd.tf"]],
             inv.trafo.fct = object[["bwd.tf"]]
           )
         )
-        is.angle <- rownames( ci ) %in% c( "omega", "phi", "zeta" )
-        if( sum(is.angle) > 0 ) ci[is.angle, ] <- ci[is.angle, ] * 180/pi
         
+        if( !object[["aniso"]][["isotropic"]] ){
+        
+          ## map angles to halfcircle
+          
+          if( !object[["aniso"]][["isotropic"]] ){
+            sel <- match( "omega", rownames(ci) )
+            if( !is.na( sel ) ){
+              ci[sel, ] <- ifelse( ci[sel, ] <   0., ci[sel, ] + 180., ci[sel, ] )
+              ci[sel, ] <- ifelse( ci[sel, ] > 180., ci[sel, ] - 180., ci[sel, ] )
+            }
+            sel <- match( "phi", rownames(ci) )
+            if( !is.na( sel ) ){
+              ci[sel, ] <- ifelse( ci[sel, ] <   0., ci[sel, ] + 180., ci[sel, ] )
+              ci[sel, ] <- ifelse( ci[sel, ] > 180., ci[sel, ] - 180., ci[sel, ] )
+            }
+            sel <- match( "zeta", rownames(ci) )
+            if( !is.na( sel ) ){
+              ci[sel, ] <- ifelse( ci[sel, ] < -90., ci[sel, ] + 180., ci[sel, ] )
+              ci[sel, ] <- ifelse( ci[sel, ] >  90., ci[sel, ] - 180., ci[sel, ] )
+            }
+          }
+          
+        }
+        
         ans[["param"]] <- cbind( ans[["param"]], ci )
         if( correlation ) ans[["cor.tf.param"]] <- cor.tf.param
         

Modified: pkg/R/georob.cv.R
===================================================================
--- pkg/R/georob.cv.R	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/R/georob.cv.R	2013-07-04 12:40:02 UTC (rev 10)
@@ -12,6 +12,8 @@
     duplicates.in.same.set = TRUE,
     re.estimate = TRUE, param = object[["param"]], 
     fit.param = object[["initial.objects"]][["fit.param"]],
+    aniso = object[["aniso"]][["aniso"]], 
+    fit.aniso = object[["initial.objects"]][["fit.aniso"]],
     return.fit = FALSE, reduced.output = TRUE,
     lgn = FALSE,
     ncores = min( nset, detectCores() ),
@@ -74,12 +76,14 @@
   ## 2013-05-23 AP correct handling of missing observations
   ## 2013-05-24 AP separate initial variogram parameters for each cross-validation set
   ## 2013-06-12 AP substituting [["x"]] for $x in all lists
+  ## 2013-07-02 AP passing initial values of aniso and fit.aniso to georob via update
     
   ## auxiliary function that fits the model and computes the predictions of
   ## a cross-validation set
   
   f.aux <- function( 
-    ..i.., object, formula, data, sets, re.estimate, param, fit.param, lgn, verbose, ...
+    ..i.., object, formula, data, sets, re.estimate, 
+    param, fit.param, aniso, fit.aniso, lgn, verbose, ...
   ){  ## cv function
     
     if (verbose) cat( "\n\n  processing cross-validation set", ..i.., "\n" ) 
@@ -93,6 +97,7 @@
         gamma = FALSE, lambda = FALSE, n = FALSE, nu = FALSE,
         f1 = FALSE, f2  =FALSE, omega = FALSE, phi = FALSE, zeta = FALSE      
       )[names( param )]
+      fit.aniso <- c( f1 = FALSE, f2 = FALSE, omega = FALSE, phi = FALSE, zeta = FALSE )
     }
     
     ## change environment of terms and formula so that subset selection works for update            
@@ -104,14 +109,16 @@
     
     if( ( is.matrix( param ) || is.data.frame( param ) ) )  param <- param[..i..,]
     if( ( is.matrix( fit.param ) || is.data.frame( fit.param ) ) )  fit.param <- fit.param[..i..,]
+    if( ( is.matrix( aniso ) || is.data.frame( param ) ) )  aniso <- aniso[..i..,]
+    if( ( is.matrix( fit.aniso ) || is.data.frame( fit.aniso ) ) )  fit.aniso <- fit.aniso[..i..,]
 
     t.georob <- update( 
       object, 
       formula = formula,
       data = data,
       subset = -sets[[..i..]] ,
-      param = param,
-      fit.param = fit.param,
+      param = param, fit.param = fit.param,
+      aniso = aniso, fit.aniso = fit.aniso,
       verbose = verbose,
       ...
     )
@@ -242,13 +249,21 @@
   ## check dimension of param and fit.param
   
   if( ( is.matrix( param ) || is.data.frame( param ) ) && nrow( param )!= nset ) stop(
-    "param must have 'nset' rows if it is a matrix or data frame"  
+    "'param' must have 'nset' rows if it is a matrix or data frame"  
   )
     
   if( ( is.matrix( fit.param ) || is.data.frame( fit.param ) ) && nrow( param )!= nset ) stop(
-    "fit.param must have 'nset' rows if it is a matrix or data frame"  
+    "'fit.param' must have 'nset' rows if it is a matrix or data frame"  
   )
     
+  if( ( is.matrix( aniso ) || is.data.frame( aniso ) ) && nrow( aniso )!= nset ) stop(
+    "'aniso' must have 'nset' rows if it is a matrix or data frame"  
+  )
+    
+  if( ( is.matrix( fit.aniso ) || is.data.frame( fit.aniso ) ) && nrow( aniso )!= nset ) stop(
+    "'fit.aniso' must have 'nset' rows if it is a matrix or data frame"  
+  )
+    
   ## loop over all cross-validation sets
   
   if( .Platform[["OS.type"]] == "windows" ){
@@ -270,8 +285,8 @@
       data = data,
       sets = sets,
       re.estimate = re.estimate,
-      param = param,
-      fit.param = fit.param,
+      param = param, fit.param = fit.param,
+      aniso = aniso, fit.aniso = fit.aniso,
       lgn = lgn,
       verbose = verbose,
       ...
@@ -291,8 +306,8 @@
       data = data,
       sets = sets,
       re.estimate = re.estimate,
-      param = param,
-      fit.param = fit.param,
+      param = param, fit.param = fit.param,
+      aniso = aniso, fit.aniso = fit.aniso,
       lgn = lgn,
       verbose = verbose,
       mc.cores = ncores,

Modified: pkg/R/georob.exported.functions.R
===================================================================
--- pkg/R/georob.exported.functions.R	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/R/georob.exported.functions.R	2013-07-04 12:40:02 UTC (rev 10)
@@ -77,6 +77,7 @@
   ## 2013-05-23 AP correct handling of missing observations and to construct model.frame
   ## 2013-06-03 AP handling design matrices with rank < ncol(x)
   ## 2013-06-12 AP substituting [["x"]] for $x in all lists
+  ## 2013-07-02 AP new transformation of rotation angles
   
   ## check whether input is complete
   
@@ -395,7 +396,7 @@
     )
     
     param = t.georob[["param"]][names(fit.param)]
-    aniso = t.georob[["aniso"]][["aniso"]][names(fit.aniso)] * c( 1, 1, rep( 180/pi, 3 ) )
+    aniso = t.georob[["aniso"]][["aniso"]][names(fit.aniso)]
     
   }
   
@@ -644,14 +645,14 @@
     variance = "log", snugget = "log", nugget = "log", scale = "log", 
     a = "identity", alpha = "identity", beta = "identity", delta = "identity", 
     gamma = "identity", lambda = "identity", n = "identity", nu = "identity",
-    f1 = "log", f2  ="log", omega = "identity", phi = "identity", zeta = "identity"
+    f1 = "log", f2  ="log", omega = "rad", phi = "rad", zeta = "rad"
   )
 {
   
   ## function sets meaningful defaults for transformation of variogram
   ## parameters
   
-  ## 2012-11-27 A. Papritz
+  ## 2013-07-02 A. Papritz
   
   c( 
     variance = variance, snugget = snugget, nugget = nugget, scale = scale,
@@ -671,9 +672,9 @@
   
   ## definition of forward transformation of variogram parameters
   
-  ## 2012-11-27 A. Papritz
+  ## 2013-07-02 A. Papritz
   
-  list( log = function(x) log(x),  identity = function(x) x, ... )
+  list( log = function(x) log(x),  identity = function(x) x, rad = function(x) x/180*pi, ... )
 }
 
 ## ======================================================================
@@ -685,10 +686,15 @@
   
   ## definition of first derivative of forward transformation of variogram
   ## parameters
+  ## NOTE: dfwd.transf[["rad"]] must be equal to one since sine and cosine 
+  ## are evaluated for transformed angles
   
-  ## 2012-11-27 A. Papritz
+  ## 2013-07-02 A. Papritz
   
-  list( log = function(x) 1/x, identity = function(x) rep(1, length(x)), ... )  
+  list( 
+    log = function(x) 1/x, identity = function(x) rep(1, length(x)), 
+    rad = function(x) rep(1., length(x)), ... 
+  )  
   
 }
 
@@ -701,9 +707,9 @@
   
   ## definition of backward transformation of variogram parameters
   
-  ## 2012-11-27 A. Papritz
+  ## 2013-07-02 A. Papritz
   
-  list( log = function(x) exp(x), identity = function(x) x, ... )
+  list( log = function(x) exp(x), identity = function(x) x, rad = function(x) x/pi*180, ... )
   
 }
 

Modified: pkg/R/georob.private.functions.R
===================================================================
--- pkg/R/georob.private.functions.R	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/R/georob.private.functions.R	2013-07-04 12:40:02 UTC (rev 10)
@@ -1083,6 +1083,7 @@
   ## 2012-11-27 AP changes in check allowed parameter range
   ## 2013-02-04 AP solving estimating equations for xi
   ## 2013-06-12 AP substituting [["x"]] for $x in all lists
+  ## 2013-07-02 AP new transformation of rotation angles
   
   ##  function transforms (1) the variogram parameters back to their
   ##  original scale; computes (2) the correlation matrix, its inverse
@@ -1102,7 +1103,7 @@
   )
   names( param ) <- param.name
   
-  aniso <- c( adjustable.param, fixed.param )[aniso.name]
+  fwd.tf.aniso <- aniso<- c( adjustable.param, fixed.param )[aniso.name]
   
   aniso <- sapply(
     aniso.name,
@@ -1180,12 +1181,12 @@
     
     lik.item[["aniso"]][["aniso"]] <- aniso
     lik.item[["aniso"]][["sincos"]] <- list(
-      co = unname( cos( aniso["omega"] ) ),
-      so = unname( sin( aniso["omega"] ) ),
-      cp = unname( cos( aniso["phi"] ) ),
-      sp = unname( sin( aniso["phi"] ) ),
-      cz = unname( cos( aniso["zeta"] ) ),
-      sz = unname( sin( aniso["zeta"] ) )
+      co = unname( cos( fwd.tf.aniso["omega"] ) ),
+      so = unname( sin( fwd.tf.aniso["omega"] ) ),
+      cp = unname( cos( fwd.tf.aniso["phi"] ) ),
+      sp = unname( sin( fwd.tf.aniso["phi"] ) ),
+      cz = unname( cos( fwd.tf.aniso["zeta"] ) ),
+      sz = unname( sin( fwd.tf.aniso["zeta"] ) )
     )
     
     n <- NCOL( lag.vectors)
@@ -1435,48 +1436,6 @@
         ( c( 0., 0., -1. / aniso[["aniso"]]["f2"]^2 )[1:n] * aniso[["sclmat"]] ) * aux^2 
       )
     },
-    
-#     omega = {
-#       drotmat <- with(
-#         aniso[["sincos"]],
-#         rbind(
-#           c(             cp*co,            -cp*so, 0. ),
-#           c(  co*sz*sp + cz*so,  cz*co - sz*sp*so, 0. ),
-#           c( -cz*co*sp + sz*so,  co*sz + cz*sp*so, 0. )
-#         )[ 1:n, 1:n, drop = FALSE ]
-#       )
-#       colSums( 
-#         ( aniso[["sclmat"]] * drotmat %*% t(x) ) * ( aniso[["sclmat"]] * aux ) 
-#       )
-#     },
-#     
-#     phi = {
-#       drotmat <- with(
-#         aniso[["sincos"]],
-#         rbind(
-#           c(    -sp*so,    -co*sp,     cp ),
-#           c(  cp*sz*so,  cp*co*sz,  sz*sp ),
-#           c( -cz*cp*so, -cz*cp*co, -cz*sp )
-#         )[ 1:n, 1:n, drop = FALSE ]
-#       )
-#       colSums( 
-#         ( aniso[["sclmat"]] * drotmat %*% t(x) ) * ( aniso[["sclmat"]] * aux ) 
-#       )
-#     },
-#     
-#     zeta = {
-#       drotmat <- with(
-#         aniso[["sincos"]],
-#         rbind(
-#           c(                0.,               0.,     0. ),
-#           c(  co*sz + cz*sp*so, cz*co*sp - sz*so, -cz*cp ),
-#           c( -cz*co + sz*sp*so, co*sz*sp + cz*so, -cp*sz )
-#         )[ 1:n, 1:n, drop = FALSE ]
-#       )
-#       colSums( 
-#         ( aniso[["sclmat"]] * drotmat %*% t(x) ) * ( aniso[["sclmat"]] * aux ) 
-#       )
-#     },
     omega = {
       drotmat <- with(
         aniso[["sincos"]],
@@ -3260,6 +3219,7 @@
   ## 2013-05-06 AP changes for solving estimating equations for xi
   ## 2013-06-12 AP changes in stored items of Valpha object
   ## 2013-06-12 AP substituting [["x"]] for $x in all lists
+  ## 2013-07-03 AP new transformation of rotation angles
   
   ##  ToDos:
   
@@ -3586,10 +3546,6 @@
 #     "undefined transformation of anisotropy parameter"
 #   )
   
-  ##  convert angles to radian
-  
-  aniso[c("omega", "phi", "zeta" )] <- aniso[c("omega", "phi", "zeta" )] / 180 * pi
-  
   ##  transform initial anisotropy parameters
   
   transformed.aniso <- sapply(
@@ -4009,6 +3965,37 @@
     
   }
   
+  ## map angles to halfcircle
+  
+  if( !result.list[["aniso"]][["isotropic"]] ){
+    
+    if( result.list[["aniso"]][["aniso"]]["omega"] < 0. ){
+      result.list[["aniso"]][["aniso"]]["omega"] <- 
+      result.list[["aniso"]][["aniso"]]["omega"] + 180.
+    }
+    if( result.list[["aniso"]][["aniso"]]["omega"] > 180. ){
+      result.list[["aniso"]][["aniso"]]["omega"] <- 
+      result.list[["aniso"]][["aniso"]]["omega"] - 180.
+    }
+    if( result.list[["aniso"]][["aniso"]]["phi"] < 0. ){
+      result.list[["aniso"]][["aniso"]]["phi"] <- 
+      result.list[["aniso"]][["aniso"]]["phi"] + 180.
+    }
+    if( result.list[["aniso"]][["aniso"]]["phi"] > 180. ){
+      result.list[["aniso"]][["aniso"]]["phi"] <- 
+      result.list[["aniso"]][["aniso"]]["phi"] - 180.
+    }
+    if( result.list[["aniso"]][["aniso"]]["zeta"] < 90. ){
+      result.list[["aniso"]][["aniso"]]["zeta"] <- 
+      result.list[["aniso"]][["aniso"]]["zeta"] + 180.
+    }
+    if( result.list[["aniso"]][["aniso"]]["zeta"] > 90. ){
+      result.list[["aniso"]][["aniso"]]["zeta"] <- 
+      result.list[["aniso"]][["aniso"]]["zeta"] - 180.
+    }
+  
+  }
+  
   ##      result.list[["df.model"]] <- r.df
   
   if( full.output ){

Modified: pkg/man/cv.georob.Rd
===================================================================
--- pkg/man/cv.georob.Rd	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/man/cv.georob.Rd	2013-07-04 12:40:02 UTC (rev 10)
@@ -1,4 +1,4 @@
-% 2013-06-12 A. Papritz
+% 2013-07-02 A. Papritz
 % R CMD Rdconv -t html -o bla.html cv.georob.Rd ; open bla.html; R CMD Rd2pdf --force cv.georob.Rd; 
 
 \encoding{macintosh}
@@ -24,7 +24,9 @@
 \method{cv}{georob}(object, formula = NULL, subset = NULL, nset = 10, 
     seed = NULL, sets = NULL, duplicates.in.same.set = TRUE, 
     re.estimate = TRUE, param = object[["param"]], 
-    fit.param = object[["initial.objects"]][["fit.param"]], 
+    fit.param = object[["initial.objects"]][["fit.param"]],
+    aniso = object[["aniso"]][["aniso"]], 
+    fit.aniso = object[["initial.objects"]][["fit.aniso"]],
     return.fit = FALSE, reduced.output = TRUE, lgn = FALSE, 
     ncores = min(nset, detectCores()), verbose = 0, ...)
 }
@@ -82,6 +84,25 @@
   cross-validation sets and \code{colnames(param)} must match
   \code{names(object[["param"]])}.}
   
+  \item{aniso}{an optional named numeric vector or a matrix or data frame
+  with anisotropy parameters passed by \code{\link[stats]{update}} to
+  \code{\link{georob}}, see \emph{Details}.  If \code{aniso} is a matrix
+  (or a data frame) then it must have \code{nset} rows and
+  \code{length(object[["aniso"]][["aniso"]])} columns with initial values
+  of anisotropy parameters for the \code{nset} cross-validation sets and
+  \code{colnames(aniso)} must match
+  \code{names(object[["aniso"]][["aniso"]])}.}
+  
+  \item{fit.aniso}{an optional named logical vector or a matrix or data
+  frame defining which anisotropy parameters should be adjusted when passed
+  by \code{\link[stats]{update}} to \code{\link{georob}}, see
+  \emph{Details}.  If \code{fit.aniso} is a matrix (or a data frame) then
+  it must have \code{nset} rows and
+  \code{length(object[["aniso"]][["aniso"]])} columns with anisotropy
+  parameter fitting flags for the \code{nset} cross-validation sets and
+  \code{colnames(aniso)} must match
+  \code{names(object[["aniso"]][["aniso"]])}.}
+  
   \item{return.fit}{logical controlling whether information about the fit
   should be returned for when re-estimating the model with the reduced data
   sets (default \code{TRUE}).}

Modified: pkg/man/georob.Rd
===================================================================
--- pkg/man/georob.Rd	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/man/georob.Rd	2013-07-04 12:40:02 UTC (rev 10)
@@ -117,7 +117,7 @@
     \itemize{
     
       \item{\code{f1}: ratio \eqn{f_1} of lengths of second and first
-        second semi-principal axes of an ellipsoidal surface with constant
+        semi-principal axes of an ellipsoidal surface with constant
         semivariance in \eqn{\mathrm{I}\!\mathrm{R}^3}{R^3} (default \code{f1 = 1}).}
       
       \item{\code{f2}: ratio \eqn{f_2} of lengths of third and first

Modified: pkg/man/georob.control.Rd
===================================================================
--- pkg/man/georob.control.Rd	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/man/georob.control.Rd	2013-07-04 12:40:02 UTC (rev 10)
@@ -1,4 +1,4 @@
-% 2013-06-12 A. Papritz
+% 2013-07-02 A. Papritz
 % R CMD Rdconv -t html -o bla.html georob.control.Rd ; open bla.html; R CMD Rd2pdf --force georob.control.Rd; 
 \encoding{macintosh}
 \name{georob.control}
@@ -44,8 +44,8 @@
 param.transf(variance = "log", snugget = "log", nugget = "log", scale = "log", 
     a = "identity", alpha = "identity", beta = "identity", delta = "identity", 
     gamma = "identity", lambda = "identity", n = "identity", nu = "identity",
-    f1 = "log", f2  ="log", omega = "identity", phi = "identity",
-    zeta = "identity")
+    f1 = "log", f2  ="log", omega = "rad", phi = "rad",
+    zeta = "rad")
   
 fwd.transf(...)
 
@@ -282,12 +282,13 @@
 
   The arguments \code{param.tf}, \code{fwd.tf}, \code{deriv.fwd.tf},
   \code{bwd.tf} define the transformations of the variogram parameters for
-  robust REML estimation.  Implemented are currently \code{"log"} and
-  \code{"identity"} (= no) transformations.  These are the possible values
-  that the many arguments of the function \code{param.transf} accept (as
-  quoted character strings) and these are the names of the list
-  components returned by \code{fwd.transf}, \code{dfwd.transf} and 
-  \code{bwd.transf}.  Additional transformations can be implemented by:
+  robust REML estimation.  Implemented are currently \code{"log"},
+  \code{"rad"} (conversion from degree to radian) and \code{"identity"} (= no)
+  transformations.  These are the possible values that the many arguments
+  of the function \code{param.transf} accept (as quoted character strings)
+  and these are the names of the list components returned by
+  \code{fwd.transf}, \code{dfwd.transf} and \code{bwd.transf}.  Additional
+  transformations can be implemented by:
   
   \enumerate{
   

Modified: pkg/man/plot.georob.Rd
===================================================================
--- pkg/man/plot.georob.Rd	2013-06-12 13:24:39 UTC (rev 9)
+++ pkg/man/plot.georob.Rd	2013-07-04 12:40:02 UTC (rev 10)
@@ -1,4 +1,4 @@
-% 2012-12-14 A. Papritz
+% 2013-07-01 A. Papritz
 % R CMD Rdconv -t html -o bla.html plot.georob.Rd ; open bla.html; R CMD Rd2pdf --force plot.georob.Rd; 
 
 \encoding{macintosh}
@@ -46,19 +46,19 @@
   grouping the lag distances or a numeric vector with the upper bounds of a
   set of contiguous bins.}
   
-  \item{xy.angle.def}{an numeric vector defining angular classes
-  in the horizontal plane for computing directional variograms.
+  \item{xy.angle.def}{an numeric vector defining angular classes in the
+  horizontal plane for computing directional variograms.
   \code{xy.angle.def} must contain an ascending sequence of azimuth angles
-  in degrees from north (positive clockwise to south), see \emph{Details}.
-  Omnidirectional variograms are computed with the default 
-  \code{c(0,180)}.}
+  in degrees from north (positive clockwise to south), see
+  \code{\link{sample.variogram}}.  Omnidirectional variograms are computed
+  with the default \code{c(0,180)}.}
   
-  \item{xz.angle.def}{an numeric vector defining angular classes
-  in the \eqn{x}-\eqn{z}-plane for computing directional variograms.
+  \item{xz.angle.def}{an numeric vector defining angular classes in the
+  \eqn{x}-\eqn{z}-plane for computing directional variograms.
   \code{xz.angle.def} must contain an ascending sequence of angles in
   degrees from zenith (positive clockwise to nadir), see
-  \emph{Details}.  Omnidirectional variograms are computed with the default
-  \code{c(0,180)}.}
+  \code{\link{sample.variogram}}.  Omnidirectional variograms are computed
+  with the default \code{c(0,180)}.}
   
   \item{max.lag}{positive numeric defining the largest lag distance for
   which semivariances should be computed (default no restriction).}



More information about the Georob-commits mailing list