[Rsiena-commits] r134 - in pkg: RSiena RSiena/R RSiena/inst/doc RSiena/man RSiena/src/model/ml RSiena/src/model/variables RSiena/tests RSienaTest RSienaTest/R RSienaTest/doc RSienaTest/man RSienaTest/src/model/ml RSienaTest/src/model/variables RSienaTest/tests

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sat Feb 5 19:59:23 CET 2011


Author: ripleyrm
Date: 2011-02-05 19:59:22 +0100 (Sat, 05 Feb 2011)
New Revision: 134

Modified:
   pkg/RSiena/DESCRIPTION
   pkg/RSiena/R/iwlsm.R
   pkg/RSiena/R/phase2.r
   pkg/RSiena/R/siena08.r
   pkg/RSiena/R/sienaDataCreate.r
   pkg/RSiena/R/sienaDataCreateFromSession.r
   pkg/RSiena/R/sienaTimeTest.r
   pkg/RSiena/changeLog
   pkg/RSiena/inst/doc/s_man400.pdf
   pkg/RSiena/man/RSiena-package.Rd
   pkg/RSiena/man/iwlsm.Rd
   pkg/RSiena/man/print.sienaMeta.Rd
   pkg/RSiena/man/siena08.Rd
   pkg/RSiena/src/model/ml/MLSimulation.cpp
   pkg/RSiena/src/model/ml/NetworkChange.cpp
   pkg/RSiena/src/model/variables/DependentVariable.cpp
   pkg/RSiena/src/model/variables/NetworkVariable.cpp
   pkg/RSiena/tests/parallel.R
   pkg/RSiena/tests/parallel.Rout.save
   pkg/RSienaTest/DESCRIPTION
   pkg/RSienaTest/NAMESPACE
   pkg/RSienaTest/R/iwlsm.R
   pkg/RSienaTest/R/siena08.r
   pkg/RSienaTest/R/sienaDataCreate.r
   pkg/RSienaTest/R/sienaDataCreateFromSession.r
   pkg/RSienaTest/R/sienaTimeTest.r
   pkg/RSienaTest/changeLog
   pkg/RSienaTest/doc/s_man400.tex
   pkg/RSienaTest/man/RSiena-package.Rd
   pkg/RSienaTest/man/iwlsm.Rd
   pkg/RSienaTest/man/print.sienaMeta.Rd
   pkg/RSienaTest/man/siena08.Rd
   pkg/RSienaTest/src/model/ml/MLSimulation.cpp
   pkg/RSienaTest/src/model/ml/NetworkChange.cpp
   pkg/RSienaTest/src/model/variables/DependentVariable.cpp
   pkg/RSienaTest/src/model/variables/NetworkVariable.cpp
   pkg/RSienaTest/tests/parallel.R
   pkg/RSienaTest/tests/parallel.Rout.save
Log:
Enhancements to siena08, ML for bipartite networks. 

Modified: pkg/RSiena/DESCRIPTION
===================================================================
--- pkg/RSiena/DESCRIPTION	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/DESCRIPTION	2011-02-05 18:59:22 UTC (rev 134)
@@ -1,8 +1,8 @@
 Package: RSiena
 Type: Package
 Title: Siena - Simulation Investigation for Empirical Network Analysis
-Version: 1.0.12.133
-Date: 2011-01-25
+Version: 1.0.12.134
+Date: 2011-02-05
 Author: Various
 Depends: R (>= 2.9.0), xtable
 Imports: Matrix

Modified: pkg/RSiena/R/iwlsm.R
===================================================================
--- pkg/RSiena/R/iwlsm.R	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/R/iwlsm.R	2011-02-05 18:59:22 UTC (rev 134)
@@ -73,7 +73,7 @@
 }
 ##@iwlsm.default iwlsm
 iwlsm.default <-
-  function(x, y, weights, ses, ..., w = rep(1, nrow(x)),
+  function(x, y, weights, ses, ..., w = rep(1/nrow(x), nrow(x)),
            init = "ls", psi = psi.iwlsm,
            scale.est = c("MAD", "Huber", "proposal 2"), k2 = 1.345,
            method = c("M", "MM"), wt.method = c("inv.var", "case"),
@@ -146,6 +146,7 @@
             } else stop("'init' method is unknown")
             coef <- temp$coefficient
             resid <- temp$residuals
+            hh <- hatvalues(lm(y ~ -1 + x, weights=w))
         } else {
             if(is.list(init)) coef <- init$coef
             else coef <- init
@@ -193,11 +194,12 @@
             }
         }
        ## w <- psi(resid/scale)###
-        w <- psi(resid, w=w, sj2=ses)
+        w <- psi(resid, w=w, sj2=ses, hh=hh)
         if(!is.null(wt)) w <- w * weights
         temp <- lm.wfit(x, y, w, method="qr")
         coef <- temp$coefficients
         resid <- temp$residuals ##  w * res* res
+        hh <- hatvalues(lm(y ~ -1 + x, weights=w))
         if(!is.null(test.vec)) convi <- irls.delta(testpv, get(test.vec))
         else convi <- irls.rrxwr(x, w, resid)
         conv <- c(conv, convi)
@@ -428,15 +430,15 @@
     so$stddev^2 * so$cov.unscaled
 }
 ##@psi.iwlsm iwlsm
-psi.iwlsm <- function(u, k, deriv=0, w, sj2)
+psi.iwlsm <- function(u, k, deriv=0, w, sj2, hh)
 {
     if (!deriv)
     {
-        v <- sum(w * u^2) / (1 - sum(w * w))
+        v <- sum(w * u^2) / (1 - sum(w * hh))
         v1 <- max(0, v - weighted.mean(sj2, w))
         ww <- 1 /(v1 + sj2)
         ww / sum(ww)
-    }
+   }
     else ## dummy: I have removed the call with deriv = 1
     {
         rep(1, length(u))

Modified: pkg/RSiena/R/phase2.r
===================================================================
--- pkg/RSiena/R/phase2.r	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/R/phase2.r	2011-02-05 18:59:22 UTC (rev 134)
@@ -285,7 +285,7 @@
         }
         if (x$maxlike)
         {
-            z$phase2fras[subphase, ,z$nit] <- fra
+         #   z$phase2fras[subphase, ,z$nit] <- fra
          #   z$rejectprops[subphase, , z$nit] <- zz$rejectprop
         }
         if (z$nit %% 2 == 1)
@@ -464,7 +464,7 @@
         }
         if (x$maxlike)
         {
-            z$phase2fras[subphase, ,z$nit] <- fra
+            # z$phase2fras[subphase, ,z$nit] <- fra
             ##   z$rejectprops[subphase, , z$nit] <- zz$rejectprop
         }
         if (z$nit %% 2 == 1)

Modified: pkg/RSiena/R/siena08.r
===================================================================
--- pkg/RSiena/R/siena08.r	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/R/siena08.r	2011-02-05 18:59:22 UTC (rev 134)
@@ -90,6 +90,14 @@
         x1 <- x[!is.na(x$theta) & !is.na(x$se) & x$se < bound,]
         if (any(x1$theta != 0))
         {
+            if (sum((x1$se < bound)) >= 3)
+            {
+                check.correl <- cor.test(x1$theta, x1$se)
+            }
+            else
+            {
+                check.correl <- data.frame(estimate=NA, p.value=NA)
+            }
             regfit <- iwlsm(theta ~ 1, psi=psi.iwlsm, data=x1,
                             ses=x1$se^2)
             regfit$terms <- NA
@@ -105,7 +113,9 @@
             cjminus <- -2 * sum(pnorm(x1$theta / x1$se, log=TRUE))
             cjplusp <- 1 - pchisq(cjplus, 2 * nrow(x1))
             cjminusp <- 1 - pchisq(cjminus, 2 * nrow(x1))
-            ret1 <- list(regfit=regfit, regsummary=regsummary,
+            ret1 <- list(cor.est=check.correl$estimate,
+                         cor.pval=check.correl$p.value,
+                         regfit=regfit, regsummary=regsummary,
                          Tsq=Tsq, pTsq=1 - pchisq(Tsq, nrow(x1) - 1),
                          tratio=tratio,
                          ptratio=2 * pnorm(abs(tratio), lower.tail=FALSE),
@@ -145,7 +155,7 @@
     meta$thetadf <- mydf
     class(meta) <- "sienaMeta"
     meta$projname <- projname
-    meta$bound <- 5
+    meta$bound <- bound
     ## count the score tests
     meta$scores <- by(mydf, mydf$effects, function(x)
                       any(!is.na(x$scoretests)))
@@ -181,7 +191,7 @@
     nProjects <- length(projnames)
     effects <- unique(x$thetadf$effects)
     nEffects <- length(effects)
-## results
+    ## results
 
     ## estimates
 
@@ -208,16 +218,39 @@
        Report(c(" ", y$n1, " datasets used.\n\n"), sep="", outf)
        if (y$n1 > 0)
        {
-           Report(c("\nTest that all parameters are 0 : \n"), outf)
+           Report("Test that estimates and standard errors are uncorrelated",
+                  outf)
+           if (is.na(y$cor.est))
+           {
+               Report("\ncannot be performed.\n\n", outf)
+           }
+           else
+           {
+               Report(c(": \nPearson correlation =", format(round(y$cor.est, 4),
+                                                            width=9),
+                        ", two-sided ",reportp(y$cor.pval,3), "\n\n"), sep="",
+                      outf)
+           }
+           Report(c("Test that all parameters are 0 : \n"), outf)
            Report(c("chi-squared =", format(round(y$Tsq, 4), width=9),
                     ", d.f. = ", y$n1, ", ",
                     reportp(y$pTsq, 3), "\n\n"), sep="", outf)
            Report(c("Estimated mean parameter",
-                    format(round(y[[2]]$coefficients[1, 1], 4), width=9),
-                    " (s.e.", format(round(y[[2]]$coefficients[1, 2], 4),
+                    format(round(y$regsummary$coefficients[1, 1], 4), width=9),
+                    " (s.e.", format(round(y$regsummary$coefficients[1, 2], 4),
                                      width=9), "), two-sided ",
-                    reportp(2 * pt(-abs(y[[2]]$coefficients[1, 3]),
-                               y$n1 - 1), 3), "\n\n"), sep="", outf)
+                    reportp(2 * pt(-abs(y$regsummary$coefficients[1, 3]),
+                                   y$n1 - 1), 3), "\n"), sep="", outf)
+           Report(c("based on IWLS modification of Snijders & Baerveldt (2003). ",
+                  "\n\n"), sep="", outf)
+           Report(c("Residual standard error",
+                    format(round(y$regsummary$stddev, 4), width=9)), outf)
+           Report("\nTest that variance of parameter is 0 :\n", outf)
+           Report(c("Chi-squared = ", format(round(y$Qstat, 4), width=9),
+                    " (d.f. = ", y$n1-1, "), ", reportp(y$pttilde, 3),
+                    "\n"), sep="", outf)
+           Report(c("based on IWLS modification of Snijders & Baerveldt (2003). ",
+                    "\n\n"), sep="", outf)
            Report("Fisher's combination of one-sided tests\n", outf)
            Report("----------------------------------------\n", outf)
            Report("Combination of right one-sided p-values:\n", outf)
@@ -232,8 +265,8 @@
        else
        {
            Report(c("There were no data sets satisfying the bounds for",
-                   "this parameter.\n No combined output is given.\n"), outf)
-        }
+                    "this parameter.\n No combined output is given.\n"), outf)
+       }
    }, y=x)
     ##score tests
     if (any(x$scores))
@@ -252,8 +285,9 @@
                         as.character(x$effects[1]), "\n"), sep="", outf)
                tmp <- paste("Data set ", 1:nrow(x), ", ", format(x$projname),
                             " : z = ", ifelse(is.na(x$scoretests), "NA",
-                        format(round(x$scoretests, 4), width=12)),
-                        "\n", sep="")
+                                              format(round(x$scoretests, 4),
+                                                     width=12)),
+                            "\n", sep="")
                Report(c(tmp, "\n"), sep="", outf)
                Report("Combination of right one-sided p-values:\n", outf)
                Report(c("Chi-squared = ", format(round(y$scoreplus, 4),
@@ -296,14 +330,14 @@
 plot.sienaMeta <- function(x, ...)
 {
     library(lattice)
-    tmp <- xyplot(se ~ theta|effects, data=x$thetadf, xlab="estimates",
-           ylab="standard errors", layout=c(4,4),
-           panel=function(x, y)
-       {
-           panel.xyplot(x, y)
-           panel.abline(0, 2)
-           panel.abline(0, -2)
-       }, scales="free")
+    tmp <- xyplot(theta ~ se|effects, data=x$thetadf, ylab="estimates",
+                  xlab="standard errors", layout=c(4,4),
+                  panel=function(x, y)
+              {
+                  panel.xyplot(x, y)
+                  panel.abline(0, qnorm(0.025))
+                  panel.abline(0, qnorm(0.975))
+              }, scales="free")
     tmp[!sapply(tmp$y.limits, function(x)all(is.na(x)))]
 }
 
@@ -397,7 +431,7 @@
     }
     Report(c("================================= SIENA08 ",
              "================================================\n",
-             "Multilevel use of Siena algorithms according to",
+             "Multilevel use of Siena algorithms according to ",
              "Snijders & Baerveldt (2003) with extension\n",
              "=================================================",
              "=========================================\n\n"), sep="", outf)
@@ -423,9 +457,9 @@
     {
         Report("-> No extra output requested\n", outf)
     }
-    ### RSiena version
+    ## RSiena version
     Report(c("\nThe RSiena Version of the first fit object is ",
-           x$thetadf$version[1], ".\n\n"), sep="", outf)
+             x$thetadf$version[1], ".\n\n"), sep="", outf)
     ## project names
     by(x$thetadf, x$thetadf$projname, function(x)
    {
@@ -433,20 +467,23 @@
                 nrow(x), " parameters.\n"), sep="", outf)
        Report(c("The number of valid score tests found was ",
                 sum(is.na(x$scoretests)), ".\n"),
-                sep="",outf);
+              sep="", outf);
    })
     ##parameters:
     Report(c("\nA total of", nEffects, "parameters in", nProjects,
              "projects :\n"),   outf)
     Report(paste(format(1:length(effects)), ". " , effects, "\n", sep=""),
-             sep="", outf)
+           sep="", outf)
     Report(c("\nThe projects contain the parameters as follows",
-           "(1=present, 0=absent):\n\n"), outf)
+             "(1=present, 0=absent):\n\n"), outf)
     row1 <- c(1:nEffects)
     rows <- do.call(rbind, tapply(x$thetadf$effects,
-                                      x$thetadf$projname, function(x){
-                                          as.numeric(effects %in% x)
-                                      }))
+                                  x$thetadf$projname, function(x)
+                              {
+                                  as.numeric(effects %in% x)
+                              }
+                                  )
+                    )
     rows <- format(rbind(row1, rows), width=3)
     row2 <- rep(paste(rep("-", nchar(rows[1, 1])), collapse=""), nEffects)
     rows <- rbind(rows[1,], row2, rows[-1, ])
@@ -469,7 +506,7 @@
                 format(round(max(abs(x$tconv)), 4), width=9), "\n"), outf)
        ## score tests
    })
-## results
+    ## results
 
     ## estimates
     Report(c("\n\n", paste(rep("=", 29), collapse=""),
@@ -501,25 +538,48 @@
        {
            if (extra)
            {
-               Report(c("Snijders-Baerveldt (2003) method of combining",
-                        "estimates"), outf)
-               Report(c("\n---------------------------------------",
-                        "----------------\n"), sep="", outf)
+               Report(c("IWLS modification of Snijders-Baerveldt (2003) method ",
+                        "of combining estimates"), outf)
+               Report(c("\n--------------------------------------------",
+                        "---------------------------------\n"), sep="", outf)
                Report(c("This method assumes that true parameters and",
                         " standard errors are uncorrelated.\n",
-                        "This can be checked from the plots.\n"), sep="",
-                      outf)
+                        "This can be checked by the plot method ",
+                        "and the test below.\n\n"), sep="", outf)
            }
-           Report(c("\nTest that all parameters are 0 : \n"), outf)
+           Report("Test that estimates and standard errors are uncorrelated",
+                  outf)
+           if (is.na(y$cor.est))
+           {
+               Report("\ncannot be performed.\n\n", outf)
+           }
+           else
+           {
+               Report(c(": \nPearson correlation =", format(round(y$cor.est, 4),
+                                                            width=9),
+                        ", two-sided ",reportp(y$cor.pval,3), "\n\n"),
+                      sep="", outf)
+           }
+           Report(c("Test that all parameters are 0 : \n"), outf)
            Report(c("chi-squared =", format(round(y$Tsq, 4), width=9),
                     ", d.f. = ", y$n1, ", ",
                     reportp(y$pTsq, 3), "\n\n"), sep="", outf)
            Report(c("Estimated mean parameter",
-                    format(round(y[[2]]$coefficients[1, 1], 4), width=9),
-                    " (s.e.", format(round(y[[2]]$coefficients[1, 2], 4),
+                    format(round(y$regsummary$coefficients[1, 1], 4), width=9),
+                    " (s.e.", format(round(y$regsummary$coefficients[1, 2], 4),
                                      width=9), "), two-sided ",
-                    reportp(pt(y[[2]]$coefficients[1, 3],
-                               y$n1 - 1), 3), "\n\n"), sep="", outf)
+                    reportp(pt(y$regsummary$coefficients[1, 3],
+                               y$n1 - 1), 3), "\n"), sep="", outf)
+           Report(c("based on IWLS modification of Snijders & Baerveldt (2003). ",
+                  "\n\n"), sep="", outf)
+           Report(c("Residual standard error",
+                    format(round(y$regsummary$stddev, 4), width=9)), outf)
+           Report("\nTest that variance of parameter is 0 :\n",outf)
+           Report(c("Chi-squared = ", format(round(y$Qstat, 4), width=9),
+	            " (d.f. = ", y$n1-1, "), ", reportp(y$pttilde, 3),
+	            "\n"), sep="", outf)
+           Report("based on IWLS modification of Snijders & Baerveldt (2003).",
+                  "\n\n", sep="", outf)
            Report("Fisher's combination of one-sided tests\n", outf)
            Report("----------------------------------------\n", outf)
            Report("Combination of right one-sided p-values:\n", outf)
@@ -534,8 +594,8 @@
        else
        {
            Report(c("There were no data sets satisfying the bounds for",
-                   "this parameter.\n No combined output is given.\n"), outf)
-        }
+                    "this parameter.\n No combined output is given.\n"), outf)
+       }
    }, y=x)
     ##score tests
     if (any(x$scores))
@@ -553,9 +613,10 @@
                Report(c("\n", "(", i, ")   ",
                         as.character(x$effects[1]), "\n"), sep="", outf)
                tmp <- paste("Data set ", 1:nrow(x), ", ", format(x$projname),
-                            " : z = ", ifelse(is.na(x$scoretests), "NA",
-                        format(round(x$scoretests, 4), width=12)),
-                        "\n", sep="")
+                            " : z = ",
+                            ifelse(is.na(x$scoretests), "NA",
+                                   format(round(x$scoretests, 4), width=12)),
+                            "\n", sep="")
                Report(c(tmp, "\n"), sep="", outf)
                Report("Combination of right one-sided p-values:\n", outf)
                Report(c("Chi-squared = ", format(round(y$scoreplus, 4),
@@ -570,6 +631,5 @@
            }
        }, y=x)
     }
-
 }
 

Modified: pkg/RSiena/R/sienaDataCreate.r
===================================================================
--- pkg/RSiena/R/sienaDataCreate.r	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/R/sienaDataCreate.r	2011-02-05 18:59:22 UTC (rev 134)
@@ -753,13 +753,13 @@
                    vals <- lapply(depvars[[i]], function(x)
                                    c(x at x[!(is.na(x at x) |
                                            x at x %in% c(10, 11))] , 0))
-                    attr(depvars[[i]], "range") <-
+                    attr(depvars[[i]], "range2") <-
                         do.call(range, vals)
                }
                 else
                 {
                     tmp <- depvars[[i]]
-                    attr(depvars[[i]], "range") <-
+                    attr(depvars[[i]], "range2") <-
                         range(tmp[!(is.na(tmp) | tmp %in% c(10, 11))])
                 }
                 ## average degree
@@ -903,7 +903,7 @@
     disjoint <- namedVector(FALSE, pairsNames )
 
     ## identify any nets which may relate. These are those that
-    ## share a node set and type.
+    ## share both node sets and type.
     relates <- data.frame(name=names(z$depvars), type=types,
                           nodeSets=sapply(nodeSets, paste, collapse=","),
                           tn=paste(types, sapply(nodeSets, paste,
@@ -2077,16 +2077,17 @@
     netNames <- names(z$depvars)
     netTypes <- sapply(z$depvars, function(x)attr(x, "type"))
     netActorSet <- sapply(z$depvars, function(x)
+                      {
                           if (attr(x, "type") == "bipartite")
-                      {
-                          attr(x, "nodeSet")[2]
-                      }
+                          {
+                              attr(x, "nodeSet")[2]
+                          }
                           else
-                      {
-                          attr(x, "nodeSet")
+                          {
+                              attr(x, "nodeSet")
+                          }
                       }
                           )
-    ## find the constant covariates
     for (i in seq(along=z$cCovars))
     {
         nodeSet <- attr(z$cCovars[[i]], "nodeSet")
@@ -2160,7 +2161,7 @@
         }
         else
         {
-            dep <- depvar[, , i]
+            dep <- depvar[, , i, drop=FALSE]
             dep[dep %in% c(10, 11)] <- dep[dep %in% c(10, 11)] - 10
         }
         vi <- apply(dep, 1, function(x)

Modified: pkg/RSiena/R/sienaDataCreateFromSession.r
===================================================================
--- pkg/RSiena/R/sienaDataCreateFromSession.r	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/R/sienaDataCreateFromSession.r	2011-02-05 18:59:22 UTC (rev 134)
@@ -569,6 +569,11 @@
                                                         "ActorSet"], " ")[[1]]
                        miss <- namesession$MissingValues
                        miss <- strsplit(miss, " ")
+                       if (observations - 1 != nrow(namesession))
+                       {
+                           stop("observations and periods don't match ",
+                                "for dyadic covariate")
+                       }
                        if (namesession$Format[1] == "matrix")
                        {
                            myarray <- array(NA, dim=c(dim(namefiles[[1]]),
@@ -587,11 +592,6 @@
                        {
                            if (nrow(namesession) > 1)
                            {
-                               if (observations - 1 != nrow(namesession))
-                               {
-                                   stop("observations and periods don't match",
-                                        "for dyadic covariate")
-                               }
                                mylist <- vector("list", observations - 1)
                                nActors <-
                                    as.numeric(strsplit(namesession$

Modified: pkg/RSiena/R/sienaTimeTest.r
===================================================================
--- pkg/RSiena/R/sienaTimeTest.r	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/R/sienaTimeTest.r	2011-02-05 18:59:22 UTC (rev 134)
@@ -555,6 +555,13 @@
 #                " for network effects of type eval or for RateX.")
 #        effects$timeDummy[!implemented] <- ","
 #	}
+    structuralRate <- effects$type == "rate" & effects$rateType %in% "structural"
+    if (any(effects$timeDummy[structuralRate] != ","))
+    {
+		warning("Time dummy effects are not implemented",
+                " for structural rate effects.")
+        effects$timeDummy[structuralRate] <- ","
+    }
     behaviorNonRateX <- effects$netType =="behavior" & effects$type != "rate"
     if (any(effects$timeDummy[behaviorNonRateX] != ","))
     {

Modified: pkg/RSiena/changeLog
===================================================================
--- pkg/RSiena/changeLog	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/changeLog	2011-02-05 18:59:22 UTC (rev 134)
@@ -1,5 +1,23 @@
-2011-01-25 R-forge revision 133
-        * changes to RSienaTest only
+2011-02-05 R-forge revision 134
+
+	* R/phase2.r, R/siena08.r, man/siena08.Rd, man/print.sienaMeta.Rd:
+	changes as in revision 133 copied to RSiena.
+	* R/siena08.r, man/siena08.Rd, man/print.sienaMeta.Rd: changes to
+	format of new code, reinstate object in summary method  help page.
+	* R/iwlsm.r, man/iwlsm.Rd: correct calculation of variance estimate
+	* R/sienaDataCreate.r: minor amendments
+	* R/sienaDataCreateFromSession.r: message from siena01Gui if
+	changing dyadic covariates do not match number of observations.
+	* R/sienaTimeTest.r: message that timedummies are not implemented
+	for structural rate effects.
+	* src/model/ml/MLSimulation.cpp, src/model/ml/NetworkChange.cpp,
+	src/model/variables/NetworkVariable.cpp: changes for ML, should now run OK
+	for bipartite networks.
+	* src/model/variables/DependentVariable.cpp: added some error trapping.
+	* tests/parallel.R, tests/parallel.Rout.save: removed multiple
+	processes from tests as they were failing on R-forge.
+
+2011-01-25 R-forge revision 133 (RSienaTest only)
         * R/phase2.r: comment out two test lines causing a crash of the ML
         estimation when model specifications get so large that subphases
         exceed 1000 iterations.
@@ -7,7 +25,7 @@
         analysis.
         * man/siena08.Rd: explain new features in help function
         * man/print.sienaMeta.Rd: explain new features in help function
-        
+
 2011-01-17 R-forge revision 132
 	* Changing revision 131 to conform with coding standards
 2011-01-17 R-forge revision 131

Modified: pkg/RSiena/inst/doc/s_man400.pdf
===================================================================
--- pkg/RSiena/inst/doc/s_man400.pdf	2011-01-24 23:35:15 UTC (rev 133)
+++ pkg/RSiena/inst/doc/s_man400.pdf	2011-02-05 18:59:22 UTC (rev 134)
@@ -505,19 +505,21 @@
 (References)
 endobj
 348 0 obj <<
-/Length 1102      
+/Length 1106      
 /Filter /FlateDecode
 >>
 stream
-xÚ}VKsÛ6¾ëWà͘0@x´''±ÛdÆîÔVOI0EK¬ùP)*Žþ}Xкã\ì~ûú°'ÂÉoþÎúaµ¸¼Š¤ÓF²z"B¦LÚŒhaY*Y­ÉWzëÚeªèÁÕËDò”>uýòïÕ°Õ[¡˜ ƒÕÃç뻫¨7ñ¡S¦Ô«Úw]öûªk=cÜ[½Fyy#“™J½y¢S9IrÎŒ@Œûðc ºe~Õô¾ÚÕåq‚3®$1,O5IRÎd*aµ4)í4¾bÂ=´Õ?knÌæ9&8@
-’HaŽÈµ¤¨CŠƒßº{ÂõPÎõ/Ë$“9ýTî\?4eë‡SEM7TKA÷ËDÀ™ U±ÿî߸Pe½F‹]]—›r4.7µa™Âо¸àçàú“P¸I¹³9_¯6œ"tÎ×DrͤѤhÿ.d8ÄÿA0jGÁåM#ȧnñ'ücªÉˆœœ@®JC³Je¾Ü©L
-I€¦llãÕã~è]1¼×/{bŸèJ"ÀPùœµRO¼1¥³‘´ßxÎ_oÁUøˆó×;P5‡چܶôsû½ÜÕæDôÔ-SC{ü¸nvU_xÑ,½+1–¾xÎïúg<¸j]}ÜWû¹@EʲÓ@š€rX,‚Ó¢kv ÑPö(Øõݦw
-*
-[jtɁ/ÖzrÑã@(\ßW¥T‚vOT•‚Q‰’½g*¤‰y€ÀçÜŒ9{“'´hº%ð‘®Ë:bùšN±Êï!ùú Ön‹Ç ž<€¥E5zjO+Ö?GXWpǪvrâ1‹É€‘Yƒ.ýf}l]SþÊU]Ÿtn끇rJ
-z†Ðñ"š\·¯A:;?â™çЙî粋Ÿ­WÌÏ}¯RÎ¥~‹"ø…
-…ÕÕlù° özÞ!¸ °v===+ò[R©‚_gBðâùŸóƒ:‡µÚV{\#ƒm\è¾^ðýν5Šñ,Ÿy¼¦·Ë2a²“·Ë¾½]€ùù©SHÌ3ÓKàÔåzÆ¡ÑŒ§¯¯àýÌÍ9T,×rT‹ð/[ '¸ÞNSvxe%Ì*㟡Óò·¯Ä©ÍèÎþ¢</sM<A8tqÝBÏ£lr£ƒà¸Êf¶Žà”¿å5“RάÏ­¶ÑÑi³ü·Oͯn?íkñE›ÒõuåÇØÀ|·ßn£íIÿ§é\Í7=7T^Ä)Óú÷×—»»Pu-®j÷'’± Å/}5eÄ)Ò0†Ã.¤e"‰áûуQýÖ…g¤¿ª=h^ÄэaOR¼Äq~nÉLÒ‡H$ 	‰UÁÑcÌe¿)ûTÄì²”~Üöž
-® C¹©#*;ûáfˆ…"¦
-‰‘3¸Ä$±93&Åp¦Ã~\üêÄ¡„
+xÚ}VÉrã6½ë+p„ªL ˆ…ÉÉ3c'“*;K9Íä Q°Ä˜‹BRvô÷i,´E
+r•6º_o
+Q´Cý² ¬ŸÖ‹ë;&Qš¥Cë'ÄxJxž!År’2Ö[ô
+ß›f™J|4Õ2á4ÅOm·ükýت‰-“D² ½ÕêëíÃMÔ›øP)‘òMíÅAÛ®/Û& g„:«·(¯ï¸D,#<“©3O¤&R DP¢YÀx<{0 {âV…ËCeOœqE‰&"U(I)á)ë¥Nq[ãò‰¸USþ½…àfB`ŒäB„À…p†î"ùϦ„•Oqp›S€nŸÂúû¿PÎíOË$ã±Ó
+µmœâp®¨ðj0C¹d¸_&Î.‹þçpôpüN™´Õ6X|n«Êîì$hÄ ]!5¤
+éç1í;—¶ÝtGӝ”¸
+)el6ëÛõ‚Á†"†˜DR…8U$ÍsTԋ܆ÿ^0jGÁõ]ÍЗvñü]bªÉˆœœA{¶r4É¥Ì\ÁSÍgQ	Ó2¤t³é‡ÎÃG-ËÏ &ЊÂÀ°ù’¸\MÜ©²‘·ß© oa‚Ê S‹·kPÖÇ
+:èã¯Í‹í‡rw&zj—©Æ]ø¸­eWá®åøÁirüê4Z·ëžÃÁMcªS_ös²”d灲`Ê~5°0Š‹¶>Gƒí‚àе»ÎÔAiØ_C ŒÐ$ƒ ¿ëy at -LוÖJ†Û£ãªLÁÈIïÈ
+i†<@àr®ÇœÉS°¨Û%0om±\M§XöÅ'_ÁÂmÂq  O ÇE9zjÎ+Ö=GXSpÍÊfçs¢ÓdÀÈr\ºÍöÔ˜º,Ü”«Ú.i!ÝÆv”êàBßÑäÆ}óÒÙχ.äpñ(»”]ýhœ;Eq©èzýƒ²àê=
+ï*äWS‘9ä‚ګy‡àÀšíôô¢Èï!p)}n	Á‰çC`tÎ?Ìjk½/#ö¸FI\ß¹ð€Á÷÷VKB31ó~MoWÃ&;{¾ò÷ç°37 at U
+‰9f:	܁ÊngjEhúö>®€`fΡ$BñQ-¿àz?MÙ„+ËaVi÷ùÄg¼h»rsô$NóLá.ÊóR(làÍð¡ëze“í§~°õlÁ)}Ïk&%Ar5ž“ ·ÞGGçÍrß.5·nL?íjâ‹6ÖtUéÆØÀ|·×n­.ÆÚÿ5Êù¦ùUœ2{‚])C÷a竣ŔM&û QüÚ•Ã`#`˜‚ õcØï|Z:’¾7äÔï@úë±ìAó*Žîö$ÅûHãæÏ8^E"ø«O¬ôŽ6~0Ûng»« ²ËRüyß9*˜&vWETrñÛM£Š˜Ê@Aà£$ÀÎÈÊé°ƒ_ÿG¢k
 endstream
 endobj
 347 0 obj <<
@@ -662,49 +664,49 @@
 /Type /Annot
 /Subtype /Link
 /Border[0 0 0]/H/I/C[0 1 0]
-/Rect [282.619 177.458 316.685 188.417]
+/Rect [282.619 177.414 316.685 188.372]
 /A << /S /GoTo /D (cite.Snijders01) >>
 >> endobj
 340 0 obj <<
 /Type /Annot
 /Subtype /Link
 /Border[0 0 0]/H/I/C[0 1 0]
-/Rect [322.744 177.458 343.167 188.417]
+/Rect [322.744 177.414 343.167 188.372]
 /A << /S /GoTo /D (cite.Snijders01) >>
 >> endobj
 341 0 obj <<
 /Type /Annot
 /Subtype /Link
 /Border[0 0 0]/H/I/C[0 1 0]
-/Rect [348.202 177.458 368.625 188.417]
+/Rect [348.202 177.414 368.625 188.372]
 /A << /S /GoTo /D (cite.Snijders05) >>
 >> endobj
 342 0 obj <<
 /Type /Annot
 /Subtype /Link
 /Border[0 0 0]/H/I/C[0 1 0]
-/Rect [377.593 177.458 438.005 188.417]
+/Rect [377.593 177.414 438.005 188.372]
 /A << /S /GoTo /D (cite.SnijdersEA07) >>
 >> endobj
 343 0 obj <<
 /Type /Annot
 /Subtype /Link
 /Border[0 0 0]/H/I/C[0 1 0]
-/Rect [444.064 177.458 464.487 188.417]
+/Rect [444.064 177.414 464.487 188.372]
 /A << /S /GoTo /D (cite.SnijdersEA07) >>
 >> endobj
 344 0 obj <<
 /Type /Annot
 /Subtype /Link
 /Border[0 0 0]/H/I/C[0 1 0]
-/Rect [112.918 166.499 170.956 177.458]
+/Rect [112.918 166.455 170.956 177.414]
 /A << /S /GoTo /D (cite.SnijdersEA10a) >>
 >> endobj
 345 0 obj <<
 /Type /Annot
 /Subtype /Link
 /Border[0 0 0]/H/I/C[0 1 0]
-/Rect [175.828 166.499 196.252 177.458]
+/Rect [175.828 166.455 196.252 177.414]
 /A << /S /GoTo /D (cite.SnijdersEA10a) >>
 >> endobj
 349 0 obj <<
@@ -3415,35 +3417,37 @@
 /ProcSet [ /PDF /Text ]
 >> endobj
 759 0 obj <<
-/Length 3172      
+/Length 3182      
 /Filter /FlateDecode
 >>
 stream
-xÚµÛŽÛÆõ=_¡æ‰X³rxKP´¶Nk§XoIQp¥Y‰1Eª¼x½ßsŠ¤(Û¤Oš9ž9÷å¯v+õÃW¾ü¾¸ýêú•ñWZ«,Š‚Õíý*͔匿$Öʏõêv»úÅ”¯ÖZ‘÷Cñ¡¨vWë0‰¼ÆÞÛÆVÛ^ýûöÇëWé*SYĈÆ_­uªÂ4c?ïm/e‰×·ø>üÑQ¬Œoà=:ÿîõ÷oŸŸc
- S»CÏcÑáoê-ïóã±±›"ïì–tû¼ãGWAêÕ=ƒ‰|†wµ;éò
-ÏöyÉOòj;=ZW–uÀCݤ±¥ýpEã萏Õ:5*Œ"Ê:fF\Dz¿Ðap°Ý.,[9RŽ¥=€4 9$`Å¿ò^毴×Ô»&?¨«uf|ïÖa®”›j÷f!ç	snD¬72â³p_—el>€^Õp¨Ì>qS ŏWiˆ
-’Ô»é»=¬bã½Q"ñ"ä]Uü¶µM+ð[|­>ð³çê…âUàk–&¼7#Eá£{Ôa"¢åduÅ £|^üêGþ|üôG'æ‘:~¶Ä:P¡FJüÄûé#ܽýl ͼVÅ€·Clˆ
-ÈE
-ã/F.ñ¾³Ç¼éH©h.p ¾ëò®h»bÓ~€(óÞö¿ú:¶å–Ÿ¿ù۝U.šHùiìÜeßuÇo®¯TH[Ejû¨òêß_·…­òës—[‡¡¯´	¦:Á†&ðîò¶ØðrdW¸%5à‚L24¡WIÂRƒh-ä‰Í{>´}¬ò°È»ƒX¼-y_P|‚Öê‚:KYz†jÁA[¾žÃP{|ûÇÜ-݁’h¢sbOãhı3åˆeˆ±dð	À+;êúŽŽÙ}Ž€㉽M½¶d•uÙwbî¥;çO<1;´»¨‡·÷§…£ÀÕ
-²d¤"a7 ü¬&wÍ\ê‚P“eÅ™!"æÔxFnèc†pËÔÃѐŸæM9Ã] Iû—ôjôD,ށˑwà–5Ö,Üò‚TEùɶE^ñcŽÈEU°Ÿ{ÂLz«Û÷EE™VIY:ºlÅÚ<QàˆMÐ
-aÈ!ÿX(tP²,&öËOGܝQMԥӁ7ÙŠÚ	HBý„%b,ÞÙs7Ã'ª¯]rß7\ €c´G¾oS@¨6 “tâÝxhÁíü;8 äOုgí%Rk ŽvChoMÁäñèÜOí&ú«l+\`b´é!èÕñ8wΟ÷,Cª—"ÁÙEƒÆCO3hÄF’ÀWO€c“—›¾¿Ã'T—Á/äÍj›7[>f›¦nÚñ	WàÍ©rã'Ç›z½TL¸ì’´ó
-À1ÅhïÕUj¸Ö„§yÛ‚¸Ç-¹$,@ƒPúvÃÀayµ·…‚ÐV¶`í":ô¥Àœ^´5)ªg4zàO32l¡ÂÝ8ǝs²©«¶ õüÈ}ÁÅ\±,9|ðïu{,ªº­å…Á(NkçFáŽâl™¸FÊÎ/w÷ÅêàÛOÒzþÐüAÁä9sÓõ`5!¡Y*„Îà:Úl-ÿ¾èÙºž1"R8I“Hdœ·“ƒÃCë–ºnúIãúIÛuCC¹·å‘W¶¸:6õ4<Ÿo1_£ÉC‡›=Ô9ÚãÌñ'p˜ÖôUµÜ˜j£UšéÍ;,”ZÓT%:µ¦&J<°À¼•[›oyÕ훺ßí™
- 4RB}1Äz¯æWZ+¯Â2·@¼8Ãf⫪ÿ‰YÁmÈ°fYCh‰¡W!ɨªÑ>LèÖ1ÜFa—
+xÚµZYÛÈ~÷¯Pö‰¬6Ù¼v$>Nbo0ž`ìGꑸ¦H-ëߧ.R$E=çIÝÅfuW×õUQîb»p?>så÷åͳ«·Æ]h­’ ð7w‹8Q®/¢P+7Ô‹›ÍâÇSÚ_®´öçÇì>+¶Ë•Neïle‹µ­—ÿ¹ùÛÕÛx‘¨$ôBdã.V:V~œ0‡Ÿw¶€—’Èik|ŸÖîà… TÆ5ð­ÿøî͇ç\½Ω»EÏ™cÖàoìd5ÏÓá²ë,mì†4»´áGÇ¥;eËd:>Ó›²[Ù1Ù§®mÓœŸ¤Åf¼´,,ÊŠ	û²Jes{¿‡y4(Çbå\ÞuÈnpeéþ&pË„½mv°!pÙÈ’lÈínÓƒ³ „D,øWÞKœÃR;U¹­Ò½Z®ã:7Ç~KÙ©ìÞÌd’<bɍ\kÇqE„€E¸+ó¼D1@¯ª_aTb¯¸ÎàÄÇeì£Â¼Øs®Ûf£ÈuÞ+"ù|½HùXd¿mlUýf§Üã3í¼P/¯ò\íÂÐx¾ó~ (|t‡ú NdB4¼G€iVL0ÊåÁ¯nàÞãûçoñ¬ö¶jÓêÈ”àùœèp
+
+4žÄœŸ>ÃÞ›ïÁâÄùW‘õ|Ü9yiy1JiŒóÚÒª!¥¢¹À¿_ø±I›¬n²uý‚ÄùÐþêêÐæ~þ
+îßn­šq)ßʍÃÎ]vMsøþêêááAÕÀ´V¤¶Ï*]«öÓUÙ"½:w¹•ï»Jo¬S¸XßxÎmZgkì
+§¤IúÆw
+0Ij­…<±úÄ‹6Ç"݃ˆ<Û‹ÅÛœçÅ—>h-~!jg)sÏP­:hËÕSj÷€ã~›=‚¹=ÐBÀ€_ÒuQ4ËÙÓ0xa(¦|‡HÞ> #zaG—ºº¥ev—"á>c>¡³.W–¬²Ìۆ͘¤•Ê‡‹‡ž%`‡v›Ãéá흐Øiq)“åàjY2ž"bW ü­ŒF{M\êÂ¥FóŠóC‡˜žÈ“ãú®7§|zXúOòÓ´ªáBÎ8Ž¤ÝKzö5z2ïÀáÀ;pÊš…kvyIª¢üdë,-ø±Çߧ¢*˜O=ar{/ëOYA™VIY:¸lÅ°èiŽÜ„­vq ìÓÏÙž’Çž	yö‰$Ê3Ébb¿üt ÝÙÉ‚‘ºtÜË&SQ{’P±DŒÅ[{îæ¾ÿDã¶sîûž 8F}àýÖ„jƒ2ŠGލ‹fÜÉ@`þ	x{Ö^$XyÔk@;+
+&ÇC羸j;Ò_ak‘#@›F‚^;§Î9÷¾BdHõ‚ÁŒ—\4h\ô4ƒFnt8`ô<Öi¾nsñ;|B¸~!o›´Úð2[UeUWtïOȍŸt<Þ—«90Ñe¼9Ow¾ü1¦ Ä0Ö„§i]ƒˆã”\ A€¾Mÿ xXílcÚÂf¬]d‡¾ä™ÓëÀ¶$¥zFS î8#ÃÂîºsÜ©$벨3Pݹ/¸X¶}ƒsÆÿQÖ‡¬(ëR^è"â´vnÝÂAœðIâ6;¿ÞÝgÑÁžõü¡ùFÁäKÓ´`!¾™BçÐU4ÙXþ}Ù²u=gFrIþ(M~“È8-'{‡‡Ò-îªA¨'MWOÚ¦éʝÍ<zÈ°DÀÑ¡*o¡àùr‰ùýŽÜ×x8ÙîHцŒ31ůãÌ´ª-ŠùÂT­â¨¯L¯?"Pž)McioPšš rÀÓZv­lºáQ³«Êv»ãSpÀ ꨐ’Óg}L ÷J~¥¶òJ&"s	tä	ÄF˜‘«@ÿ#³‚ÝP`Íw
+¡%„Z…nHE‰öaüàtnÂnv	Pð:»O³œ‡t$ø­¨|X!Ó¿æP®ÔªZA\…º¤ZÁ=/WAèü!CMö ¨¯r®,놧™l2-7%Á‹‰€å {‚åsÅ…
+OÕÏ%½ùȼ×.îŽÌ¯WýîÀzPKþ7Ö†ÔA€U…=I¾ü•ÅGK™VÙ-Ü
+äÿ
+“÷ †A4ãE”Káá5_Ñ%@‡ý]ÕÙm~ì_:}•D*œD”¯3\°‹9H?8e²Éµ{J% PÛÈã‚‹^¯ë” mMQ	ÈlRH"SªyL’Ê.‡ÊÖ’ÿÔk¨¹Þ¼ôˆÌ˶ê.³®Ó­•#t¶K2Ø<go)G7ÒÖv#gÇÓRÐ&0ŠL@« ½=%†ò[q÷Ö¨‹€Ïg£8Go’çÊ•ñÍ°¿5ÌhhÇ$Q:ø²xÊõýnÕ©M†ÛªöԹ㌅ @Àß'õM¢¸±ó{k«Œ°.LR6t`‰å?lq? Ç{F /r¾q|¥э0™¿Ð8Rn?¹oˆüä¤dmF×h¡Ã?Y,PC7^Ü
+•œ~Ûn™D­©;zL{›Ÿ^}xss~Z¨ÄOºÓ^Í0„´çzOÓ):Zo΢Õ(‡_½
+õðÄq¨¼Ó6XÇÌâÕή—°ic¢…1;!`É{œõÖûÔ¥}åç'œc$(W÷þðÔÃÑ"`	Y…Ë  ^·¤€8v £6B–8ÊòÒ>“9"Ø`fiÉåpu39¸ÒÀ¬|P„§'
+6ñÐWaO:<VêQRf¤	¤Ç.3^]_ýeØàðßlógêGnF'Fº7…¬¤ËëÞô<nŽãï¦kñÕS…JY)ÐpܨÄq:dÔµpjOáÐRÁ/­žJ ‡c²@­\•H²9Å8¿®§HÐé>ëÂœÚö”?)=˜Ar†eëŽJر—8ÔHeã™ç)Ɂìì++aÞB¡5èîOPJV@¥˜çt¯‘žh#¢‹&¼†ã.Ý\‚Ÿäã?’3´«´ƒ[Ô•„‘t[‡ó¡‘
+¢>9Òõ'È£¯m½®²BÔÙwì¥ß‘²Î77p¼`h† {Ù'‚³W ¥I4¶þæ‚]Ì´âëåá¢Ö'ÒÀðsÅ]d¨/Ä©—l@K+IC8Îë’G›¬>ä]Gìz#è3RpâZ®Ά»Ie|!;õ¢^eÛEQ-©MNIT
+KL4çÛD¾ŠL&xî*+W_[AŒDjfð†¹7.Jg°ÓÖÊþâæü“Ž³£JzÇ¿aN8ÊŒ 8mÄ¡P{äã{Û¶™êÌïbÆò ÐtѲ€æÿ¯ŒõXHÖ
 
->gyQò’H‚߆ڇ5"ýk	íJ«š5ÄUèKš5ÈùjÅÞo2À䊺ð*çʺíx[È%óvS¼˜X §2#àBù\qq¤âS÷sIo!"´‹·#ò›5F¿{°d׆ÿE
-iϧ*{
-’,ü•Ťåkì¤ùËà¨aÍøåRxxâc z èxU[Ü•ÃK笯³Dųˆòe†+ÜÅì$—¤Ü2XKDDýR	0Ôwò¸â¦7p“€m(*˜M
-AdJ-¯‰S¹åØØVâŸ\a
-=×늏>"òºoœ0Û6ßY!ÁÙ.ñ`Ë’½A¸œH¤o9>ì1&Þž·µTo˜À(2¬}íx-1”ßJÝ[“)>_TŒÎ€ŽÁ$Ï•+šñ|kœÑ~׍Y¦tôy/”†îÔiL†×SUèirÇ‹ ÞTž¯È7P)~êý··MAµ.lr6t@‰í?€°Øây ®\u at yQ²Äñ•¡ˆîɲ@ÓDùQúä¹!âJ%ÈÚŒ®£¢…zŒðdIpŠš¸ñá^ äðÛ»cµæî°‰ÂYÙÛýôòí÷·çÔšHea樽^@iÏž¦St´Áœ1D«I¿~ë1Åi¬‚Ó6¬SFñro7Wph“b¢…5;aŠ36Ø
-Ö˜†Ô¥CD甏蘰 ÊÕƒ?|êáhI°„¬Âí  ^·¤ 8u£B®pU”9¤}sDŠÆ1;ÂÌÒ“ËáénF¸ÒȬBPD g6ñ8Tq’Î&<V"ßs™‘6]f¼¾¹þËjƒãŠíŸM¬?!éÁH¢’)os<Çß­ñÕS‡JY)Ò Tâ:#r#œ‚S0ôÔð˨§‘ÒCˆ;íX„,P+_e’lN1.
-×S¤ÒéCáÂ\xºö”?)=˜Qr†c‡
-9tè%uBÙx–qJr ;;•• ï¡ÑM÷gUJQA§X–$×DÏ´‘ ©^õK7—ÊÏ r‚	?‘3´¯tŽƒ[âZÂD¦­Çò±G‰Š’!9óÍ{È£ßÙvÓG„¨³¯ÙK¿&e_n€¼hl†Pö²Îg¯0P”fÉÔ2ø›N1ó†W¬\ÔG,µ>FÆ€ïœ+î"2¨:°â…8õ‚- `y#i×e[ój[´ÇÒMäÀ®·r€>#E'Œ å¦ãåb¸›uƲ” A2(°î»#UQÔKjSR•ÆÍù5I¨3„É#ÒÝUçë+#º…zÇy0.JgpÓÎÊýâæü“g¤JŸzÏ¿£:Âœêh3FÅé"Pµ'~4•Û®/”3¿‹+€FÓGËXý¿2Ö§B²Vи¸“üÅÓ¤T ë&Mø[€rþ©ìÃ'¨@ÍQšŽŒ KB;®Lœ|¶ÁÕ‡6§côEY
-ê
-
-„¹TÈþ•d³¯–.™F£dKÿ¿Rœó&ï»g¼‡"ë8;×׈Ã&>‰ô탲;±ùþÉûCÎý%t°Ÿ†ÛøB8A_ñ—ãŠQ¡º4ÃJ•Îì•ROÐW0ù'ç@’ÜP!WØiÒ²²4†DËß“SNÆǘ»kšˆUeoILx†¿"ÀGw9ª7ô~ïŠJ°¹'2÷M}Xæá·séC¸·Ã±C7Œ£FIÕv•ìèâHϽ㖆‰£€°Ô­kEÁkã³á@gÀ€>î°K”j Å wd@[àÔͶŸrv7‘?”~?£I“‘'_ݤpBÈèã—‡›LÓøåv"Œ.6 ŸS:ŽŸ6‘úK¤Ô{yóü-ã–’+r¥ÕPån阍2ɬeŠìtÞ ¢	hÉ›¼$†iøöˆü¥Á¨ÊÆ%9€Ééôtƒ¥EÆI…7:Ì!
-ÀñžEŠÆÖÊ
-Sà¤ó
-XÔ6[‰ôÕRÕ†²[oÅ‚ïúÝ3ÛGÛNºá?mAЦ¨6Ø|ˆÿ>a.óæT~6­Ë˜Óòö÷eµ×ãrÙDc`md¡üœXi7ö%¿ljü”Êx(Ä>SLƦ˜hféi|†”¦Ð–êœð4ŠMá=™ÂΔcÚä5Ä Š):éx`¡èd$„TA³†ë–¹ÆŠ&<V®šVÿ“ô;iGƝ‡Yì¦môJ§xN¦#¥M‡SûÕÿ ÌÓ†®
+—n%ñ41aÝÄKRÊ?…}`úè¨8Šã±uî€PŽ+F_D>¸z_æ4Ìþ!Ësa]`A´.²¿úFEÉä«e—LƒA2
+¥þ_ç<IÛ¦ÄïÂá‘Idgë*áÒâ0	O ‘¾}PvÇ%v-ß?y¾O¹¾$@óq¸
+/ÔHÀô~-WÌ
[TRUNCATED]

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


More information about the Rsiena-commits mailing list