[Rsiena-commits] r177 - in pkg/RSienaTest: . R doc inst/examples inst/scripts man src/model/variables tests

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Thu Oct 27 15:28:49 CEST 2011


Author: ripleyrm
Date: 2011-10-27 15:28:48 +0200 (Thu, 27 Oct 2011)
New Revision: 177

Added:
   pkg/RSienaTest/inst/examples/s50e.dat
Modified:
   pkg/RSienaTest/DESCRIPTION
   pkg/RSienaTest/R/phase3.r
   pkg/RSienaTest/R/robmon.r
   pkg/RSienaTest/R/siena07.r
   pkg/RSienaTest/R/sienaDataCreate.r
   pkg/RSienaTest/R/sienaGOF.r
   pkg/RSienaTest/R/sienaTimeTest.r
   pkg/RSienaTest/R/simstatsc.r
   pkg/RSienaTest/changeLog
   pkg/RSienaTest/doc/RSienaDeveloper.tex
   pkg/RSienaTest/inst/scripts/Rscript01DataFormat.R
   pkg/RSienaTest/man/RSiena-package.Rd
   pkg/RSienaTest/man/siena07.Rd
   pkg/RSienaTest/src/model/variables/DependentVariable.cpp
   pkg/RSienaTest/tests/parallel.Rout.save
   pkg/RSienaTest/tests/scriptfile.Rout.save
   pkg/RSienaTest/tests/scripts.R
Log:


Modified: pkg/RSienaTest/DESCRIPTION
===================================================================
--- pkg/RSienaTest/DESCRIPTION	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/DESCRIPTION	2011-10-27 13:28:48 UTC (rev 177)
@@ -1,12 +1,12 @@
 Package: RSienaTest
 Type: Package
 Title: Siena - Simulation Investigation for Empirical Network Analysis
-Version: 1.0.12.176
-Date: 2011-10-14
+Version: 1.0.12.177
+Date: 2011-10-27
 Author: Various
 Depends: R (>= 2.10.0)
 Imports: Matrix
-Suggests: tcltk, snow, rlecuyer, network, codetools, lattice, MASS,
+Suggests: tcltk, snow, rlecuyer, network, codetools, lattice, MASS, parallel,
 		  sna, igraph, xtable, tools
 SystemRequirements: GNU make, tcl/tk 8.5, Tktable
 Maintainer: Ruth Ripley <ruth at stats.ox.ac.uk>

Modified: pkg/RSienaTest/R/phase3.r
===================================================================
--- pkg/RSienaTest/R/phase3.r	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/R/phase3.r	2011-10-27 13:28:48 UTC (rev 177)
@@ -351,32 +351,42 @@
         }
     }
     else
+	{
         cov <- z$dinv %*% z$msfc %*% t(z$dinv)
+	}
     error <- FALSE
     if (inherits(try(msfinv <- solve(z$msfc)), "try-error"))
     {
         Report('Covariance matrix not positive definite: \n', outf)
         if (any(z$fixed || any(z$newfixed)))
+		{
             Report(c('(This may be unimportant, and related to the fact\n',
                    'that some parameters are fixed.)\n'), outf)
+		}
         else
+		{
             Report(c('This may mean that the reported standard errors ',
                      'are invalid.\n'), outf)
+		}
         z$msfinv <- NULL
     }
     else
+	{
         z$msfinv <- msfinv
+	}
     if (!is.null(cov))
     {
-        z$diver <- (z$fixed | z$diver | diag(cov) <1e-9) & (!z$AllUserFixed)
-        cov[z$diver,] <- Root(diag(cov))* 33
-        ##not sure this does not use very small vals
-        cov[,z$diver] <- Root(diag(cov))* 33
-        diag(cov)[z$diver]<- 999
+        z$diver <- (z$fixed | z$diver | diag(cov) < 1e-9) & (!z$AllUserFixed)
+		## beware: recycling works for one direction but not the other
+        diag(cov)[z$diver] <- 99 * 99
+        cov[z$diver, ] <- rep(Root(diag(cov)), each=3) * 33
+		diag(cov)[z$diver] <- 99 * 99
+		cov[, z$diver] <- rep(Root(diag(cov)), 3) * 33
+        diag(cov)[z$diver] <- 99 * 99
     }
     z$covtheta <- cov
-   # ans<-InstabilityAnalysis(z)
-   z
+	## ans<-InstabilityAnalysis(z)
+	z
 }
 
 ##@CalulateDerivative3 siena07 Calculates derivative at end of phase 3

Modified: pkg/RSienaTest/R/robmon.r
===================================================================
--- pkg/RSienaTest/R/robmon.r	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/R/robmon.r	2011-10-27 13:28:48 UTC (rev 177)
@@ -13,7 +13,7 @@
 ## returns updated z
 ##@robmon siena07 Controls MOM process
 robmon <- function(z, x, useCluster, nbrNodes, initC, clusterString,
-                   clusterIter, ...)
+                   clusterIter, clusterType, ...)
 {
     z$FinDiff.method<- x$FinDiff.method
     z$n <- 0
@@ -57,11 +57,20 @@
         {
             stop("Not enough observations to use the nodes")
         }
-        cl <- makeCluster(clusterString, type = "SOCK",
+        cl <- makeCluster(clusterString, type = clusterType,
                           outfile = "cluster.out")
         clusterCall(cl, library, pkgname, character.only = TRUE)
-        clusterSetupRNG(cl, seed = as.integer(runif(6,
-                            max=.Machine$integer.max)))
+		if (R.version$minor < 14.0) ## fake this to recreate old results
+	##	if (TRUE)
+		{
+			clusterSetupRNG(cl, seed = as.integer(runif(6,
+								max=.Machine$integer.max)))
+		}
+		else
+		{
+			clusterSetRNGStream(cl, iseed = as.integer(runif(1,
+								max=.Machine$integer.max)))
+		}
         clusterCall(cl, storeinFRANstore,  FRANstore())
         if (initC)
         {

Modified: pkg/RSienaTest/R/siena07.r
===================================================================
--- pkg/RSienaTest/R/siena07.r	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/R/siena07.r	2011-10-27 13:28:48 UTC (rev 177)
@@ -12,9 +12,10 @@
 
 ##@siena07 siena07
 siena07 <- function(x, batch = FALSE, verbose = FALSE, silent=FALSE,
-                   useCluster = FALSE, nbrNodes = 2, initC=TRUE,
-                   clusterString=rep("localhost", nbrNodes), tt=NULL,
-                   parallelTesting=FALSE, clusterIter=!x$maxlike, ...)
+					useCluster = FALSE, nbrNodes = 2, initC=TRUE,
+					clusterString=rep("localhost", nbrNodes), tt=NULL,
+					parallelTesting=FALSE, clusterIter=!x$maxlike,
+					clusterType=c("PSOCK", "FORK"), ...)
 {
     exitfn <- function()
     {
@@ -39,8 +40,22 @@
         {
             stop("cannot parallel test with multiple processes")
         }
-        require(snow, warn.conflicts=FALSE)
-        require(rlecuyer)
+		clusterType <- match.arg(clusterType)
+		if (.Platform$OS.type == "windows" && clusterType != "PSOCK")
+		{
+			stop("cannot use forking processes on Windows")
+		}
+		if (R.version$minor < 14.0) ## fake this to recreate old results
+	##	if (TRUE)
+		{
+			require(snow, warn.conflicts=FALSE)
+			require(rlecuyer)
+			clusterType <- "SOCK"
+		}
+		else
+		{
+			require(parallel)
+		}
         if (clusterIter)
         {
             x$firstg <- x$firstg * sqrt(nbrNodes)
@@ -139,7 +154,7 @@
     }
 
     z <- robmon(z, x, useCluster, nbrNodes, initC, clusterString,
-                clusterIter, ...)
+                clusterIter, clusterType, ...)
 
     time1 <-  proc.time()['elapsed']
     Report(c("Total computation time", round(time1 - time0, digits=2),

Modified: pkg/RSienaTest/R/sienaDataCreate.r
===================================================================
--- pkg/RSienaTest/R/sienaDataCreate.r	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/R/sienaDataCreate.r	2011-10-27 13:28:48 UTC (rev 177)
@@ -563,8 +563,8 @@
         attr(depvars[[i]], 'vals') <- vector("list", observations)
         attr(depvars[[i]], 'nval') <- rep(NA, observations)
         attr(depvars[[i]], 'noMissing') <- rep(0, observations)
-        attr(depvars[[i]], 'noMissingEither') <- rep(0, observations -1)
-        attr(depvars[[i]], 'nonMissingEither') <- rep(0, observations -1)
+        attr(depvars[[i]], 'noMissingEither') <- rep(0, observations - 1)
+        attr(depvars[[i]], 'nonMissingEither') <- rep(0, observations - 1)
         if (type == 'behavior')
         {
             attr(depvars[[i]], 'noMissing') <- FALSE

Modified: pkg/RSienaTest/R/sienaGOF.r
===================================================================
--- pkg/RSienaTest/R/sienaGOF.r	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/R/sienaGOF.r	2011-10-27 13:28:48 UTC (rev 177)
@@ -68,7 +68,7 @@
 	}
 	if (is.null(wave) )
 	{
-		wave <- 1:(attr(sienaFitObject$f[[groupName]]$depvars[[varName]], 
+		wave <- 1:(attr(sienaFitObject$f[[groupName]]$depvars[[varName]],
 						"netdims")[3] - 1)
 	}
 	if (varNumber < 1 || varNumber >
@@ -77,7 +77,7 @@
 		stop("Invalid variable number -- out of bounds.")
 	}
 	if (min(wave) < 1 || max(wave) >
-			attr(sienaFitObject$f[[groupName]]$depvars[[varName]], 
+			attr(sienaFitObject$f[[groupName]]$depvars[[varName]],
 							"netdims")[3] - 1)
 	{
 		stop("Invalid wave index -- out of bounds")
@@ -88,7 +88,7 @@
 						auxiliaryFunction(NULL,
 								sienaFitObject$f, sienaFitObject$sims,
 								groupName, varName, j)
-						, nrow=1) 
+						, nrow=1)
 				})
 	if (join)
 	{
@@ -221,7 +221,6 @@
 			p <- sapply(1:observations, function (i)
 				sum(obsTestStat[i] <= simTestStat) /length(simTestStat))
 		}
-
 		ret <- list( p = p,
 				SimulatedTestStat=simTestStat,
 				ObservedTestStat=obsTestStat,
@@ -235,7 +234,6 @@
 				attr(obsStats,"auxiliaryStatisticName")
 		ret
 	}
-
 	res <- lapply(1:length(simStats),
 					function (i) {
 				 applyTest(obsStats[[i]], simStats[[i]]) })
@@ -346,7 +344,7 @@
 			mmPartialThetaDelta <- rep(0,length(theta0))
 			mmPartialThetaDelta[length(theta0)] <- mmThetaDelta[length(theta0)]
 			JacobianExpStat <- lapply(wave, function (i) {
-				t(SF[,i,]) %*% simStatsByWave[[i]]/ nSims  }) 
+				t(SF[,i,]) %*% simStatsByWave[[i]]/ nSims  })
 			Gradient <- lapply(wave, function(i) {
 						-2  * JacobianExpStat[[i]] %*%
 								covInvByWave[[i]] %*%
@@ -670,7 +668,7 @@
 
 sparseMatrixExtraction <- function (i, data, sims, groupName, varName, wave) {
 	#require(Matrix)
-	dimsOfDepVar<- 
+	dimsOfDepVar<-
 			attr(data[[groupName]]$depvars[[varName]],
 					"netdims")
 	missing <- Matrix(is.na(data[[groupName]]$depvars[[varName]][,,wave+1])*1)
@@ -703,10 +701,11 @@
 	require(sna)
 	actors <- attr(data[[groupName]]$nets[[varName]][[wave+1]]$mat1,
 			"nActors")
-	missing <- t(data[[groupName]]$nets[[varName]][[wave+1]]$mat1)
+	missing <- t(data[[groupName]]$nets[[varName]][[wave+1]]$mat2)
 	attr(missing, "n") <- actors
-	missing <- 1*is.na( as.sociomatrix.sna( missing ) )
-	
+	#missing <- 1*is.na( as.sociomatrix.sna( missing ) )
+	missing <- as.sociomatrix.sna( missing )
+
 	if (is.null(i)) {
 		# sienaGOF wants the observation:
 		returnValue <- t(data[[groupName]]$nets[[varName]][[wave+1]]$mat1)

Modified: pkg/RSienaTest/R/sienaTimeTest.r
===================================================================
--- pkg/RSienaTest/R/sienaTimeTest.r	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/R/sienaTimeTest.r	2011-10-27 13:28:48 UTC (rev 177)
@@ -40,7 +40,7 @@
 	## the optional objects sdf2
 	if (sienaFit$maxlike || sienaFit$FinDiff.method)
 	{
-		if (is.null(sienaFit$sdf2[[1]]))
+		if (is.null(sienaFit$sdf2[[1]][[1]]))
 		{
 			stop("rerun Siena07 with the byWave option TRUE")
 		}

Modified: pkg/RSienaTest/R/simstatsc.r
===================================================================
--- pkg/RSienaTest/R/simstatsc.r	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/R/simstatsc.r	2011-10-27 13:28:48 UTC (rev 177)
@@ -88,6 +88,15 @@
     callGrid <- cbind(rep(1:f$nGroup, groupPeriods - 1),
                       as.vector(unlist(sapply(groupPeriods - 1,
                                               function(x) 1:x))))
+	if (R.version$minor < 14.0) ##fake this to repeat old results
+##	if (TRUE)
+	{
+		useStreams <- TRUE
+	}
+	else
+	{
+		useStreams <- FALSE
+	}
     ## z$int2 is the number of processors if iterating by period, so 1 means
     ## we are not
     if (z$int2==1 || nrow(callGrid) == 1)
@@ -96,7 +105,7 @@
         ans <- .Call('model', PACKAGE=pkgname, z$Deriv, f$pData, seeds,
                      fromFiniteDiff, f$pModel, f$myeffects, z$theta,
                      randomseed2, returnDeps, z$FinDiff.method,
-                     !is.null(z$cl), z$addChainToStore,
+                     !is.null(z$cl) && useStreams, z$addChainToStore,
                      z$needChangeContributions, returnChains)
     }
     else
@@ -104,7 +113,7 @@
         use <- 1:(min(nrow(callGrid), z$int2))
         anss <- parRapply(z$cl[use], callGrid, doModel,
                           z$Deriv, seeds, fromFiniteDiff, z$theta,
-                          randomseed2, returnDeps, z$FinDiff.method, TRUE,
+                          randomseed2, returnDeps, z$FinDiff.method, useStreams,
                           returnChains)
         ## reorganize the anss so it looks like the normal one
         ## browser()

Modified: pkg/RSienaTest/changeLog
===================================================================
--- pkg/RSienaTest/changeLog	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/changeLog	2011-10-27 13:28:48 UTC (rev 177)
@@ -1,5 +1,22 @@
-2011-10-14 r-forge revision 176 RSienaTest only
+2011-10-27 R-forge revision 177
 
+	* inst/scripts/Rscript01DataFormat.R, tests/scripts.R,
+	tests/scriptfile.Rout.save, tests/parallel.Rout.save: minor
+	textual changes. Removed library commands for snow and rlecuyer as
+	will not be necessary in 2.14.0.
+	* src/model/variables/DependentVariable.cpp, R/sienaDataCreate.r:
+	formatting changes
+	* R/simstatsc.r, R/siena07.R, R/robmon.R, man.siena07.Rd: snow/rlecuyer or
+	parallel used depending on R version. New argument for siena07 to
+	allow option FORK as well as PSOCK.
+	* R/phase3.r: correct covariance matrix for effects that have been fixed.
+	* R/sienaTimeTest.r: fix bug since replaced arrays for derivatives
+	by wave by lists of sparse matrices: the error trap failed.
+	* doc/RSienaDeveloper.tex, doc/_emacs, doc/.emacs: added comments
+	about emacs, debugging R, new parallel package, etc.
+
+2011-10-14 R-forge revision 176 RSienaTest only
+
 	* inst/scripts/RScriptDataFormat.R,
 	inst/scripts/RScriptSienaVariable.R,
 	inst/scripts/RScriptSienaRunModel.R,

Modified: pkg/RSienaTest/doc/RSienaDeveloper.tex
===================================================================
--- pkg/RSienaTest/doc/RSienaDeveloper.tex	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/doc/RSienaDeveloper.tex	2011-10-27 13:28:48 UTC (rev 177)
@@ -191,9 +191,12 @@
 \subsection{Files which always need updating}
  Before you commit an update to R-forge please do the following:
 \begin{enumerate}
-\item Record details of the files you have changed in the Changelog for each of
-  RSiena and RSienaTest. The two changelogs are kept identical, otherwise it
-  gets very confusing.
+\item Record details of the files you have changed in the Changelog for
+  RSienaTest. If you have \emph{only} changed documentation files in
+  \textsf{RSienaTest/doc} directory, you may ignore what follows.
+\item Record details of the files you have changed in the Changelog for Riena.
+  The two changelogs are kept identical, apart from changes which only affect
+  the documentation source, otherwise it gets very confusing.
 \item Update the version number and date in the \textsf{DESCRIPTION} file for
   each package.
 \item Update the version number and date in \textsf{man/RSiena-package.Rd} in
@@ -203,7 +206,25 @@
   directory of each package.
 \end{enumerate}
 \section{Coding standards etc}
-I describe the main details of our current practice:
+
+I describe below the main details of our current practice: for other points
+please copy what you see!
+
+For the convenience of any emacs users, I have added my emacs initialization
+files \sfn{\_emacs} and \sfn{.emacs} to the doc directory of RSienaTest. They
+will format R and C++ more or less to standards. If you want to use the package
+on Mac or Windows, I recommend the versions on Vincent Goulet's Site
+\url{http://vgoulet.act.ulaval.ca/en/emacs/} which come packaged with ess (for
+R) and auctex (for \LaTeX). For Windows use \sfn{\_emacs} and put it in
+``c:\textbackslash documents and settings\textbackslash user name\textbackslash
+AppData\textbackslash roaming'' (Windows Vista or 7) or ``c:\textbackslash
+documents and settings\textbackslash user name\textbackslash Application Data''
+(Windows XP). On Mac use \sfn{.emacs} and put it in your home directory. Emacs
+has a nice habit of copying text as soon as you highlight it and then you can
+paste it with a right (Windows with my initialization file) or middle button
+(Linux/Mac) click. There are very few Mac specific commands (to make the copy
+behave as on other platforms), so most of \sfn{.emacs} should also give you a
+guide on Linux.
 \subsection{General}
 \begin{enumerate}
 \item Use spaces: particularly around operators and after commas. (But
@@ -306,8 +327,8 @@
 \verb|R CMD INSTALL RSiena_1.0.n.tar.gz|\\
 (where \verb|n| is adjusted to match the file you have just created.)
 \item You now should have a new version of the package ready for use. (If on 64
-  bit Windows or Mac, you will have two versions, and you will two copies of the
-  course directories.)
+  bit Windows or Mac, you will have two versions, and you will have two copies
+  of the source directories.)
 \item Alternatively, instead of the build and INSTALL, just type
 \verb|R CMD INSTALL RSiena|\\
 If you have a 64-bit Windows and R 2.12.0, or a 64-bit Mac, use
@@ -364,9 +385,10 @@
 \begin{description}
 \item[.R directory] Create, in your home directory, a directory called .R (on
   Windows you will have to use mkdir in a command prompt window to do this). You
-  can use this directory to provide your own version of \verb|Makevars| (useful
+  can use this directory to provide your own version of \verb|Makevars|
+(useful
   for \textsf{valgrind} users on linux where you need to turn off optimisation).
-\item[.check.Renviron] This file is used in the check procedure. It should
+\item[check.Renviron] This file is used in the check procedure. It should
  contain at least the following:
 {\small
 \begin{verbatim}
@@ -390,11 +412,11 @@
 installed.
 \item[build.Renviron] This is the file used for the build procedure.  I suggest
   you set \verb|CYGWIN=nodosfilewarning| here. (Only necessary in Windows but
-  will do no harm on Mac or Linux.). We also need
+  will do no harm on Mac or Linux.). We also used to need
 \begin{verbatim}
 _R_BUILD_RESAVE_DATE=no
 \end{verbatim}
-but I have added this to the DESCRIPTION file.
+but I have added this to the DESCRIPTION file so it is always set.
 \end{description}
 \paragraph{Alternative methods for small changes}
 Good news: from R 2.12.0 it is often possible to update the R functions in
@@ -468,7 +490,33 @@
 \item An hour later, try it out by doing another secure checkout. You should not
   be asked for your password this time.
 \end{enumerate}
+\section{Testing}
+Some testing is done automatically  by the \sfn{R CMD check} procedure. This
+includes all examples on help pages except parts marked \sfn{\textbackslash
+  dontrun} or \sfn{\textbackslash donttest}.
 
+Since the checking is done every day by other people, we are limited as to the
+amount of their time we are allowed to use up. There are now extra testing
+facilities in \sfn{RSienaTest} designed to be run by ourselves only. They should
+be run every time a significant change is made.  Testing is via the check
+procedure after setting the environment variable \sfn{RSIENA\_TESTING} to any
+non-null value.
+\begin{description}
+\item[scripts] There is a file \sfn{scripts.R} in the \sfn{tests} directory
+  which is designed to test the scripts in the manual. Since I got different
+  final \sfn{.Random.Seed} on different platforms when running
+  \sfn{plot.network} I have removed the \sfn{sna}, \sfn{network} etc code to a
+  separate script file with ``SNA'' in its name.  The
+  scripts are concatenated (I added numbers to the names to make this happen in
+  the correct order) and run, after copying all the files from the examples
+  directory to the testing one. Any scripts which contain the text ``SNA'' in the
+  name are ignored. Some difference output will typically be produced: check
+  manually that it does not look important.
+\item[other tests]
+I have begun to create test files for testing the package itself. More will
+follow. But I must ask that for any new features added by others, test data and
+results are added to the testing system somehow.
+\end{description}
 \section{Parallel runs}
 Most of RSiena is set up to produce the same results as Siena3, but some effects
 have been redefined and maximum likelihood uses a different algorithm.
@@ -615,7 +663,11 @@
 In any of these cases, you may find results vary due to garbage
 collection in R. Also changes which spped up the Mac may not speed up Windows,
 particularly changing memory allocation.
-\section{Debugging C++}
+\section{Debugging}
+
+\subsection{Debugging R}
+Refer to session 7 of my R programming slides.
+\subsection{Debugging C++}
 You may find that R tends to crash when you change the C++. You can try to trap
 the error using \sfn{Rprintf} statements to print out details at intervals. The
 syntax for \sfn{Rprintf} is the same as the C function \sfn{printf}, but output
@@ -629,7 +681,7 @@
 which create a data frame from a ministep or a chain. Within C++, you can use
 \textsf{PrintValue(getChainDF(...));} to produce a readable output of the
 chain. There is an option to sort if you want to check how many of a particular
-link occur. For initial and end states there is a more sophosticated version
+link occur. For initial and end states there is a more sophisticated version
 which adds these as attributes and a corresponding R print method to display
 them. As always, you can use sink() to get console output to a file.
 
@@ -648,7 +700,8 @@
 
 If \sfn{valgrind} reports use of uninitialised variables, use the option
 \sfn{--track-origins=yes} to find out where the problem started. It can be
-surprisingly difficult to track these down!
+surprisingly difficult to track these down! But it usually reports some from R,
+which you can ignore.
 \section{The R C++ interface}
 This is not easy to understand from the documentation (Writing R Extensions
 manual), but there should be examples of most functions in the code
@@ -671,10 +724,18 @@
 the beginning of each real iteration and reset to this point at the beginning of
 each finite difference one. The jump to the new substream ignores the current
 state so it does not matter if the streams get muddled up during the finite
-differencing stage.
+differencing stage. As from R version 2.14.0 this package can be removed as
+there will be a new type of random number within R itself, to be used with the
+new \sfn{parallel} package. For the time being the original code can be run if
+desired by replacing the 3 checks for R.version less than 14.0 by TRUE, but I
+intend to remove \sfn{rlecuyer} altogether in due course.
 \item[errors]
 Error messages can use the function \sfn{error} which is similar to
 \sfn{Rprintf} in syntax, and needs the header file \sfn{R\_ext/error.h}.
+\item[Interrupt processing] There is a function provided to make C++ interrupts
+  return to R rather than die completely. It needs to be called at the start:
+  generally one sets up data first, so it is called in the function
+  \sfn{setUpData}.
 \end{description}
 \section{C++ platform independence}
 A few notes of problems we have had:

Added: pkg/RSienaTest/inst/examples/s50e.dat
===================================================================
--- pkg/RSienaTest/inst/examples/s50e.dat	                        (rev 0)
+++ pkg/RSienaTest/inst/examples/s50e.dat	2011-10-27 13:28:48 UTC (rev 177)
@@ -0,0 +1,359 @@
+1 3 9 1
+1 4 9 1
+2 5 10 1
+2 6 10 1
+2 7 11 1
+1 2 9 2
+4 2 9 2
+5 2 10 2
+6 2 11 2
+1 11 1 1
+1 14 1 1
+2 11 1 1
+3 4 1 1
+3 9 1 1
+4 3 1 1
+4 9 1 1
+5 32 1 1
+6 8 1 1
+7 2 1 1
+7 42 1 1
+7 44 1 1
+8 6 1 1
+9 3 1 1
+9 4 1 1
+10 11 1 1
+10 15 1 1
+10 33 1 1
+11 2 1 1
+11 15 1 1
+11 16 1 1
+12 7 1 1
+12 42 1 1
+12 44 1 1
+14 1 1 1
+14 10 1 1
+14 11 1 1
+15 10 1 1
+15 11 1 1
+15 16 1 1
+16 11 1 1
+16 15 1 1
+17 18 1 1
+17 19 1 1
+17 21 1 1
+17 22 1 1
+17 24 1 1
+18 19 1 1
+18 35 1 1
+19 11 1 1
+19 24 1 1
+19 26 1 1
+19 30 1 1
+21 22 1 1
+22 17 1 1
+22 21 1 1
+22 31 1 1
+22 34 1 1
+23 24 1 1
+24 17 1 1
+24 19 1 1
+24 21 1 1
+24 22 1 1
+24 23 1 1
+25 22 1 1
+25 31 1 1
+25 32 1 1
+26 7 1 1
+26 29 1 1
+26 44 1 1
+27 28 1 1
+27 29 1 1
+27 30 1 1
+28 27 1 1
+29 26 1 1
+29 30 1 1
+29 33 1 1
+30 11 1 1
+30 26 1 1
+30 29 1 1
+30 33 1 1
+31 21 1 1
+31 25 1 1
+31 32 1 1
+32 5 1 1
+32 21 1 1
+32 31 1 1
+32 37 1 1
+33 10 1 1
+33 30 1 1
+34 31 1 1
+34 37 1 1
+35 18 1 1
+36 38 1 1
+36 41 1 1
+37 31 1 1
+37 32 1 1
+37 34 1 1
+38 36 1 1
+38 41 1 1
+39 43 1 1
+40 45 1 1
+40 46 1 1
+40 47 1 1
+41 36 1 1
+41 38 1 1
+42 7 1 1
+42 44 1 1
+43 22 1 1
+43 39 1 1
+44 7 1 1
+44 42 1 1
+45 40 1 1
+45 46 1 1
+45 47 1 1
+46 40 1 1
+46 45 1 1
+46 49 1 1
+48 46 1 1
+48 49 1 1
+49 46 1 1
+49 48 1 1
+1 10 1 2
+1 14 1 2
+1 33 1 2
+2 26 1 2
+3 4 1 2
+3 9 1 2
+4 3 1 2
+5 4 1 2
+5 17 1 2
+6 8 1 2
+8 6 1 2
+9 3 1 2
+10 1 1 2
+10 11 1 2
+10 14 1 2
+10 33 1 2
+11 1 1 2
+11 10 1 2
+11 19 1 2
+11 26 1 2
+11 30 1 2
+12 15 1 2
+12 26 1 2
+12 42 1 2
+12 44 1 2
+14 1 1 2
+14 10 1 2
+14 11 1 2
+15 36 1 2
+16 15 1 2
+16 26 1 2
+16 42 1 2
+17 4 1 2
+17 5 1 2
+17 22 1 2
+17 24 1 2
+17 32 1 2
+18 35 1 2
+19 30 1 2
+19 36 1 2
+19 41 1 2
+21 19 1 2
+21 31 1 2
+21 40 1 2
+22 17 1 2
+23 19 1 2
+24 17 1 2
+24 22 1 2
+24 28 1 2
+25 24 1 2
+25 27 1 2
+25 28 1 2
+25 32 1 2
+26 7 1 2
+26 16 1 2
+26 42 1 2
+27 17 1 2
+27 28 1 2
+28 24 1 2
+28 27 1 2
+29 30 1 2
+29 33 1 2
+29 42 1 2
+30 19 1 2
+30 29 1 2
+30 41 1 2
+31 32 1 2
+31 37 1 2
+32 31 1 2
+32 37 1 2
+33 10 1 2
+33 29 1 2
+33 30 1 2
+34 4 1 2
+34 39 1 2
+34 43 1 2
+35 6 1 2
+35 28 1 2
+36 15 1 2
+36 30 1 2
+36 38 1 2
+36 41 1 2
+37 21 1 2
+37 31 1 2
+37 32 1 2
+37 34 1 2
+37 35 1 2
+38 41 1 2
+39 34 1 2
+39 43 1 2
+40 45 1 2
+40 46 1 2
+40 47 1 2
+41 19 1 2
+41 30 1 2
+41 36 1 2
+42 15 1 2
+42 26 1 2
+43 39 1 2
+44 7 1 2
+44 16 1 2
+45 40 1 2
+45 46 1 2
+45 47 1 2
+46 40 1 2
+46 45 1 2
+46 47 1 2
+46 49 1 2
+47 40 1 2
+47 45 1 2
+47 46 1 2
+48 46 1 2
+48 49 1 2
+49 46 1 2
+49 48 1 2
+50 23 1 2
+1 10 1 3
+1 11 1 3
+1 14 1 3
+1 41 1 3
+2 7 1 3
+2 23 1 3
+2 26 1 3
+3 4 1 3
+4 32 1 3
+5 17 1 3
+5 32 1 3
+6 24 1 3
+6 27 1 3
+6 28 1 3
+7 16 1 3
+7 26 1 3
+7 42 1 3
+7 44 1 3
+8 25 1 3
+9 3 1 3
+10 1 1 3
+10 11 1 3
+10 12 1 3
+10 14 1 3
+10 33 1 3
+11 1 1 3
+11 10 1 3
+11 14 1 3
+11 15 1 3
+11 33 1 3
+12 15 1 3
+12 33 1 3
+14 1 1 3
+14 10 1 3
+14 11 1 3
+14 33 1 3
+15 12 1 3
+15 29 1 3
+15 33 1 3
+15 36 1 3
+16 26 1 3
+16 42 1 3
+16 44 1 3
+17 5 1 3
+17 22 1 3
+17 27 1 3
+19 30 1 3
+19 36 1 3
+21 31 1 3
+21 37 1 3
+21 40 1 3
+21 45 1 3
+23 2 1 3
+24 6 1 3
+24 27 1 3
+24 28 1 3
+25 8 1 3
+25 50 1 3
+26 7 1 3
+26 16 1 3
+27 24 1 3
+27 28 1 3
+28 27 1 3
+29 15 1 3
+29 19 1 3
+29 30 1 3
+29 33 1 3
+30 19 1 3
+30 29 1 3
+30 33 1 3
+30 36 1 3
+31 21 1 3
+31 37 1 3
+32 4 1 3
+32 5 1 3
+33 10 1 3
+33 11 1 3
+33 15 1 3
+33 29 1 3
+33 30 1 3
+34 3 1 3
+34 4 1 3
+35 50 1 3
+36 15 1 3
+36 19 1 3
+36 30 1 3
+36 38 1 3
+36 41 1 3
+37 21 1 3
+37 31 1 3
+37 35 1 3
+37 47 1 3
+38 36 1 3
+38 41 1 3
+39 43 1 3
+40 45 1 3
+40 46 1 3
+40 47 1 3
+40 48 1 3
+41 38 1 3
+42 7 1 3
+42 44 1 3
+43 39 1 3
+44 7 1 3
+44 16 1 3
+44 26 1 3
+44 42 1 3
+45 39 1 3
+45 40 1 3
+45 46 1 3
+45 47 1 3
+46 40 1 3
+46 47 1 3
+46 48 1 3
+46 49 1 3
+47 40 1 3
+47 46 1 3
+48 46 1 3
+48 49 1 3
+49 40 1 3
+49 46 1 3
+49 48 1 3

Modified: pkg/RSienaTest/inst/scripts/Rscript01DataFormat.R
===================================================================
--- pkg/RSienaTest/inst/scripts/Rscript01DataFormat.R	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/inst/scripts/Rscript01DataFormat.R	2011-10-27 13:28:48 UTC (rev 177)
@@ -52,15 +52,14 @@
 # The library command loads the packages needed during the session.
 
         library(RSiena)
-        library(snow) # (these four additional libraries will be loaded
-        library(network)# automatically if required)
-        library(rlecuyer)
 
-# You need to have INSTALLED all of them
+# You need to have INSTALLED the packages xtable and network,
+# and for R versions older than 2.14.0 you need snow and rlecuyer
+# if you want to use multiple processes.
 
 	?install.packages
 
-# Or click on the tab "Packages", "Instal package(s)", then select a CRAN mirror
+# Or click on the tab "Packages", "Install package(s)", then select a CRAN mirror
 # (e.g. Bristol if you are in the UK) and finally select from the list
 # the package you wish to install.
 

Modified: pkg/RSienaTest/man/RSiena-package.Rd
===================================================================
--- pkg/RSienaTest/man/RSiena-package.Rd	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/man/RSiena-package.Rd	2011-10-27 13:28:48 UTC (rev 177)
@@ -30,8 +30,8 @@
 \tabular{ll}{
 Package: \tab RSiena\cr
 Type: \tab Package\cr
-Version: \tab 1.0.12.176\cr
-Date: \tab 2011-10-14\cr
+Version: \tab 1.0.12.177\cr
+Date: \tab 2011-10-27\cr
 License: \tab GPL-2 \cr
 LazyLoad: \tab yes\cr
 }

Modified: pkg/RSienaTest/man/siena07.Rd
===================================================================
--- pkg/RSienaTest/man/siena07.Rd	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/man/siena07.Rd	2011-10-27 13:28:48 UTC (rev 177)
@@ -13,7 +13,8 @@
 siena07(x, batch=FALSE, verbose=FALSE, silent=FALSE,
         useCluster=FALSE, nbrNodes=2, initC=TRUE,
         clusterString=rep("localhost", nbrNodes), tt=NULL,
-        parallelTesting=FALSE, clusterIter=!x$maxlike, ...)
+        parallelTesting=FALSE, clusterIter=!x$maxlike,
+        clusterType=c("PSOCK", "FORK"), ...)
       }
 \arguments{
   \item{x}{A control object, of class \code{\link{sienaModel} }}
@@ -38,6 +39,11 @@
   \item{clusterIter}{Boolean. If TRUE, multiple processes execute
    complete iterations at each call.
    If FALSE, multiple processes execute a single wave at each call.}
+  \item{clusterType}{Either "PSOCK" or "FORK". On Windows, must be
+  "PSOCK". On a single non-Windows machine may be "FORK", and
+  subprocesses will be formed by forking. If "PSOCK" subprocesses are
+  formed using \R scripts. If FALSE, multiple processes execute a
+  single wave at each call.}
   \item{\dots}{Arguments for the simulation function, see
     \code{\link{simstats0c}}:
 	usually, \code{data} and \code{effects}; possibly also

Modified: pkg/RSienaTest/src/model/variables/DependentVariable.cpp
===================================================================
--- pkg/RSienaTest/src/model/variables/DependentVariable.cpp	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/src/model/variables/DependentVariable.cpp	2011-10-27 13:28:48 UTC (rev 177)
@@ -537,8 +537,8 @@
 bool DependentVariable::constantRates() const
 {
 	return this->lstructuralRateEffects.empty() &&
-	  this->ldiffusionRateEffects.empty() &&
-	  this->lbehaviorVariableParameters.empty();
+		this->ldiffusionRateEffects.empty() &&
+		this->lbehaviorVariableParameters.empty();
 }
 
 
@@ -553,10 +553,10 @@
 	// later two components are precomputed for efficiency.
 
 	return this->basicRate() *
-	  this->lcovariateRates[i] *
-	  this->behaviorVariableRate(i) *
-	  this->structuralRate(i) *
-	  this->diffusionRate(i);
+		this->lcovariateRates[i] *
+		this->behaviorVariableRate(i) *
+		this->structuralRate(i) *
+		this->diffusionRate(i);
 }
 
 

Modified: pkg/RSienaTest/tests/parallel.Rout.save
===================================================================
--- pkg/RSienaTest/tests/parallel.Rout.save	2011-10-14 13:28:28 UTC (rev 176)
+++ pkg/RSienaTest/tests/parallel.Rout.save	2011-10-27 13:28:48 UTC (rev 177)
@@ -19,7 +19,7 @@
 > library(RSienaTest)
 > print(packageDescription("RSienaTest",fields="Repository/R-Forge/Revision"))
 [1] NA
->
+> 
 > ##test3
 > mynet1 <- sienaNet(array(c(tmp3, tmp4),dim=c(32, 32, 2)))
 > mydata <- sienaDataCreate(mynet1)
@@ -32,11 +32,11 @@
 > ans
 Estimates, standard errors and convergence t-ratios
 
-                                      Estimate   Standard   Convergence
-                                                   Error      t-ratio
-  1. rate basic rate parameter mynet1  3.0264  ( 0.5202   )   -0.0780
-  2. eval outdegree (density)         -1.1343  ( 0.1653   )    0.1078
-  3. eval reciprocity                  1.7921  ( 0.2370   )   -0.0392
+                                      Estimate   Standard   Convergence 
+                                                   Error      t-ratio   
+  1. rate basic rate parameter mynet1  3.0264  ( 0.5202   )   -0.0780   
+  2. eval outdegree (density)         -1.1343  ( 0.1653   )    0.1078   
+  3. eval reciprocity                  1.7921  ( 0.2370   )   -0.0392   
 
 Total of 604 iteration steps.
 
@@ -52,13 +52,13 @@
 > ans
 Estimates, standard errors and convergence t-ratios
 
-                              Estimate   Standard   Convergence
-                                           Error      t-ratio
+                              Estimate   Standard   Convergence 
+                                           Error      t-ratio   
 
-Rate parameters:
-  0       Rate parameter       3.0428  ( 0.5235   )
-  1. eval outdegree (density) -1.0952  ( 0.1923   )    0.2216
-  2. eval reciprocity          1.7007  ( 0.3089   )   -0.0419
+Rate parameters: 
+  0       Rate parameter       3.0428  ( 0.5235   )             
+  1. eval outdegree (density) -1.0952  ( 0.1923   )    0.2216   
+  2. eval reciprocity          1.7007  ( 0.3089   )   -0.0419   
 
 Total of 390 iteration steps.
 
@@ -76,11 +76,11 @@
 > ans
 Estimates, standard errors and convergence t-ratios
 
-                                      Estimate   Standard   Convergence
-                                                   Error      t-ratio
-  1. rate basic rate parameter mynet1  3.1122  ( 0.4077   )   0.1685
-  2. eval outdegree (density)         -1.1288  ( 0.2181   )   0.1968
-  3. eval reciprocity                  1.7487  ( 0.4069   )   0.1410
+                                      Estimate   Standard   Convergence 
+                                                   Error      t-ratio   
+  1. rate basic rate parameter mynet1  3.1122  ( 0.4077   )   0.1685    
+  2. eval outdegree (density)         -1.1288  ( 0.2181   )   0.1968    
+  3. eval reciprocity                  1.7487  ( 0.4069   )   0.1410    
 
 Total of 404 iteration steps.
 
@@ -96,18 +96,18 @@
 > ans
 Estimates, standard errors and convergence t-ratios
 
-                              Estimate   Standard   Convergence
-                                           Error      t-ratio
+                              Estimate   Standard   Convergence 
+                                           Error      t-ratio   
 
-Rate parameters:
-  0       Rate parameter       3.1368  ( 0.4867   )
-  1. eval outdegree (density) -1.1224  ( 0.2040   )    0.0346
-  2. eval reciprocity          1.7395  ( 0.2947   )   -0.0548
+Rate parameters: 
+  0       Rate parameter       3.1368  ( 0.4867   )             
+  1. eval outdegree (density) -1.1224  ( 0.2040   )    0.0346   
+  2. eval reciprocity          1.7395  ( 0.2947   )   -0.0548   
 
 Total of 269 iteration steps.
 
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/rsiena -r 177


More information about the Rsiena-commits mailing list