[Robast-commits] r628 - in branches/robast-0.9/pkg: ROptEst/R RobAStRDA/R RobAStRDA/inst/AddMaterial/interpolation RobExtremes/R RobExtremes/inst/AddMaterial/interpolation RobExtremesBuffer

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Mar 12 23:27:29 CET 2013


Author: ruckdeschel
Date: 2013-03-12 23:27:29 +0100 (Tue, 12 Mar 2013)
New Revision: 628

Added:
   branches/robast-0.9/pkg/RobExtremesBuffer/interpolMBREGEVFamily.csv
   branches/robast-0.9/pkg/RobExtremesBuffer/interpolMBREGEVFamily.txt
Modified:
   branches/robast-0.9/pkg/ROptEst/R/interpolLM.R
   branches/robast-0.9/pkg/RobAStRDA/R/interpolAux.R
   branches/robast-0.9/pkg/RobAStRDA/R/sysdata.rda
   branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt
   branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/interpolationscripts.R
   branches/robast-0.9/pkg/RobExtremes/R/SnQn.R
   branches/robast-0.9/pkg/RobExtremes/R/getStartIC.R
   branches/robast-0.9/pkg/RobExtremes/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt
Log:
fixed a bug in readGridFromCSV (did not read the right file)
and the name of the interpolators' items is fun not fct ...

Modified: branches/robast-0.9/pkg/ROptEst/R/interpolLM.R
===================================================================
--- branches/robast-0.9/pkg/ROptEst/R/interpolLM.R	2013-03-12 21:21:35 UTC (rev 627)
+++ branches/robast-0.9/pkg/ROptEst/R/interpolLM.R	2013-03-12 22:27:29 UTC (rev 628)
@@ -80,7 +80,7 @@
 }
 
 .readGridFromCSV <- function(fromFileCSV){
-  rg <- read.table(CSVFiles[1], colClasses=rep("character",2), sep=" ", header=FALSE)
+  rg <- read.table(fromFileCSV, colClasses=rep("character",2), sep=" ", header=FALSE)
   nrg <- nrow(rg)
   Grid <- matrix(as.numeric(as.matrix(rg)),nrow=nrg)
 

Modified: branches/robast-0.9/pkg/RobAStRDA/R/interpolAux.R
===================================================================
--- branches/robast-0.9/pkg/RobAStRDA/R/interpolAux.R	2013-03-12 21:21:35 UTC (rev 627)
+++ branches/robast-0.9/pkg/RobAStRDA/R/interpolAux.R	2013-03-12 22:27:29 UTC (rev 628)
@@ -21,7 +21,7 @@
 }
 
 .readGridFromCSV <- function(fromFileCSV){
-  rg <- read.table(CSVFiles[1], colClasses=rep("character",2), sep=" ", header=FALSE)
+  rg <- read.table(fromFileCSV, colClasses=rep("character",2), sep=" ", header=FALSE)
   nrg <- nrow(rg)
   Grid <- matrix(as.numeric(as.matrix(rg)),nrow=nrg)
 
@@ -106,7 +106,6 @@
       nameInSysdata <- CSVlist[[i]]$namInSysdata
       namPFam <- CSVlist[[i]]$namPFam
       Grid <- CSVlist[[i]]$Grid
-
       ### check whether object nameInSysdata already exists (ie. some
       ##   grids for this family already exist) or not
       if(!exists(nameInSysdata,envir=newEnv,inherits=FALSE)){

Modified: branches/robast-0.9/pkg/RobAStRDA/R/sysdata.rda
===================================================================
(Binary files differ)

Modified: branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt
===================================================================
--- branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt	2013-03-12 21:21:35 UTC (rev 627)
+++ branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt	2013-03-12 22:27:29 UTC (rev 628)
@@ -64,7 +64,7 @@
 Each layer in the hierarchie gives one ">" and an item is inserted
 below the item next left to it with number of ">" by 1 smaller than
 its own. I-fct denotes the interpolating function to the grid left
-to it. {} denote optional entries and capture that one may want
+to it (named "fun"). {} denote optional entries and capture that one may want
 to smooth out the original interpolation grids in entries 'grid', 
 giving smoothed grids written into entries 'gridS'. 
 OptCrit for the time being is either in ".OMSE", ".MBRE", ".RMXE" or ".Sn".
@@ -73,6 +73,11 @@
 [OptCrit], >[model1], >>[grid], {>>[gridS],} >>[I-fct.O], >>[I-Fct.N],
 >[model2], >>[grid], {>>[gridS],} >>[I-fct.O], >>[I-Fct.N], ...
 
+For instance, to get the clipping height "b" in OMSE for "GEV" at 
+theta = (xi=0.3) for >R-2.16, we may write 
+      .OMSE[["GEVFamily"]][["fun.N"]][[1]](0.3)
+
+
 6. Namespace issue
 
 It is absolutely necessary that functions I-fct (or I-fct.O, I-fct.N)

Modified: branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/interpolationscripts.R
===================================================================
--- branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/interpolationscripts.R	2013-03-12 21:21:35 UTC (rev 627)
+++ branches/robast-0.9/pkg/RobAStRDA/inst/AddMaterial/interpolation/interpolationscripts.R	2013-03-12 22:27:29 UTC (rev 628)
@@ -15,10 +15,10 @@
 oldwd <- getwd()
 .basepath <- "C:/rtest/RobASt/branches/robast-0.9/pkg"
 .myFolderFrom <- file.path(.basepath,"RobExtremesBuffer")
-#myRDA0 <- file.path(.basepath,"RobAStRDA/R/sysdata0.rda")
-#myRDA <- file.path(.basepath,"RobAStRDA/R/sysdata.rda")
 myRDA0 <- file.path(.basepath,"RobExtremesBuffer/sysdata0.rda")
 myRDA <- file.path(.basepath,"RobExtremesBuffer/sysdata.rda")
+#myRDA0 <- file.path(.basepath,"RobAStRDA/R/sysdata0.rda")
+myRDA <- file.path(.basepath,"RobAStRDA/R/sysdata.rda")
 CSVFiles <- grep("\\.csv$", dir(.myFolderFrom), value=TRUE)
 CSVFiles <- paste(.myFolderFrom, CSVFiles, sep="/")
 

Modified: branches/robast-0.9/pkg/RobExtremes/R/SnQn.R
===================================================================
--- branches/robast-0.9/pkg/RobExtremes/R/SnQn.R	2013-03-12 21:21:35 UTC (rev 627)
+++ branches/robast-0.9/pkg/RobExtremes/R/SnQn.R	2013-03-12 22:27:29 UTC (rev 628)
@@ -109,7 +109,7 @@
        sng <- try(getFromNamespace(".Sn", ns = "RobAStRDA"), silent =TRUE)
        if(is(sng,"try-error")) return(Sn(as(x,"AbscontDistribution")))
        if(!nam %in% names(sng)) return(Sn(as(x,"AbscontDistribution")))
-       snf <- sng[[nam]][[.versionSuff("fct")]]
+       snf <- sng[[nam]][[.versionSuff("fun")]]
        ret <- snf(shape(x))
     }else ret <- scale(x)*Sn(x=x/scale(x))
     return(ret)
@@ -122,7 +122,7 @@
     function(x, ...).Sn.intp(x,"GEVFamily") )
 
 setMethod("Sn", signature(x = "Gammad"),
-    function(x, ...).Sn.intp(x,"GammaFamily") )
+    function(x, ...).Sn.intp(x,"Gammafamily") )
 
 setMethod("Sn", signature(x = "Weibull"),
     function(x, ...).Sn.intp(x,"WeibullFamily") )

Modified: branches/robast-0.9/pkg/RobExtremes/R/getStartIC.R
===================================================================
--- branches/robast-0.9/pkg/RobExtremes/R/getStartIC.R	2013-03-12 21:21:35 UTC (rev 627)
+++ branches/robast-0.9/pkg/RobExtremes/R/getStartIC.R	2013-03-12 22:27:29 UTC (rev 628)
@@ -11,7 +11,7 @@
     if(!is(sng,"try-error")) nsng <- names(sng)
     if(length(nsng)){
        if(nam %in% nsng){
-          fctN <- .versionSuff("fct")
+          fctN <- .versionSuff("fun")
           interpolfct <- sng[[nam]][[fctN]]
           .modifyIC <- function(L2Fam, IC){
                    para <- param(L2Fam)

Modified: branches/robast-0.9/pkg/RobExtremes/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt
===================================================================
--- branches/robast-0.9/pkg/RobExtremes/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt	2013-03-12 21:21:35 UTC (rev 627)
+++ branches/robast-0.9/pkg/RobExtremes/inst/AddMaterial/interpolation/WriteUp-Interpolators.txt	2013-03-12 22:27:29 UTC (rev 628)
@@ -64,7 +64,7 @@
 Each layer in the hierarchie gives one ">" and an item is inserted
 below the item next left to it with number of ">" by 1 smaller than
 its own. I-fct denotes the interpolating function to the grid left
-to it. {} denote optional entries and capture that one may want
+to it (named "fun"). {} denote optional entries and capture that one may want
 to smooth out the original interpolation grids in entries 'grid', 
 giving smoothed grids written into entries 'gridS'. 
 OptCrit for the time being is either in ".OMSE", ".MBRE", ".RMXE" or ".Sn".
@@ -73,6 +73,10 @@
 [OptCrit], >[model1], >>[grid], {>>[gridS],} >>[I-fct.O], >>[I-Fct.N],
 >[model2], >>[grid], {>>[gridS],} >>[I-fct.O], >>[I-Fct.N], ...
 
+For instance, to get the clipping height "b" in OMSE for "GEV" at 
+theta = (xi=0.3) for >R-2.16, we may write 
+      .OMSE[["GEVFamily"]][["fun.N"]][[1]](0.3)
+
 6. Namespace issue
 
 It is absolutely necessary that functions I-fct (or I-fct.O, I-fct.N)

Added: branches/robast-0.9/pkg/RobExtremesBuffer/interpolMBREGEVFamily.csv
===================================================================
--- branches/robast-0.9/pkg/RobExtremesBuffer/interpolMBREGEVFamily.csv	                        (rev 0)
+++ branches/robast-0.9/pkg/RobExtremesBuffer/interpolMBREGEVFamily.csv	2013-03-12 22:27:29 UTC (rev 628)
@@ -0,0 +1,492 @@
+" 5.00000000000000010408e-03" " 1.81357633287360164864e+00" "-2.24449754695824399420e-01" "-1.47885705270914519227e-01" "-4.58921540973249220130e-01" "-1.81549049260172734588e-01" " 5.18224508955159923751e-01" "-7.33531573128324149158e-02" "-7.36695431812270096206e-02" " 1.00000000000000000000e+00" " 5.18224508955159923751e-01" "-7.33531573128324149158e-02" "-7.36695431812270096206e-02" " 1.00000000000000000000e+00"
+" 2.14517304631997030029e-02" " 1.82170362017730180781e+00" "-2.21448911244242041541e-01" "-1.50355403686426691845e-01" "-4.55269605129110077613e-01" "-1.76720769852665327004e-01" " 5.08063065632790911152e-01" "-5.82186275198257746633e-02" "-5.77077143417919283253e-02" " 1.00000000000000000000e+00" " 5.08143619270839841384e-01" "-5.80051768448633583986e-02" "-5.81911274646265477828e-02" " 1.00000000000000000000e+00"
+" 3.98406374501992024961e-02" " 1.83083370984061777342e+00" "-2.17035963582212471090e-01" "-1.51512983390812039364e-01" "-4.54345392222172295149e-01" "-1.72894960142815801163e-01" " 4.96136067101396682766e-01" "-4.74932769628111234317e-02" "-4.86195811306312300482e-02" " 1.00000000000000000000e+00" " 4.95936248408226754147e-01" "-4.77016787664086075460e-02" "-4.85995950036596374710e-02" " 1.00000000000000000000e+00"
+" 4.27829746040001568375e-02" " 1.83229759826328653105e+00" "-2.16118212042312296539e-01" "-1.52374008396431198653e-01" "-4.52639888751594832161e-01" "-1.72932720214651891588e-01" " 4.94720174340536444912e-01" "-4.54195759788707867366e-02" "-4.51729009100261397203e-02" " 1.00000000000000000000e+00" " 4.94720174340536444912e-01" "-4.54195759788707867366e-02" "-4.51729009100261397203e-02" " 1.00000000000000000000e+00"
+" 6.40397156295258174197e-02" " 1.84287543551152532828e+00" "-2.09674326233737051695e-01" "-1.54762162850679618753e-01" "-4.48045578614404638174e-01" "-1.66938935089539775003e-01" " 4.81144590091446000546e-01" "-2.80584353688964997786e-02" "-3.19411963298408749234e-02" " 1.00000000000000000000e+00" " 4.80470980864551755474e-01" "-2.87525051330816128203e-02" "-3.19533813366238497733e-02" " 1.00000000000000000000e+00"
+" 7.96812749003984049923e-02" " 1.85070371763565866274e+00" "-2.08536238317104577478e-01" "-1.56919373979981485734e-01" "-4.45272376876807263191e-01" "-1.65208357534006367029e-01" " 4.76384421706800675889e-01" "-1.95038700097885028817e-02" "-2.00647499048494833140e-02" " 1.00000000000000000000e+00" " 4.75947149369317923373e-01" "-1.97086007479972957768e-02" "-2.02230671057971982119e-02" " 1.00000000000000000000e+00"
+" 8.52248570399394278496e-02" " 1.85347985392406511274e+00" "-2.07900841379440981527e-01" "-1.57705602351155882435e-01" "-4.45456845353655817021e-01" "-1.64450967560591382322e-01" " 4.73547754619834226908e-01" "-1.47010272358679451588e-02" "-1.46008738936339865777e-02" " 1.00000000000000000000e+00" " 4.73190003587921015349e-01" "-1.54744589399295820464e-02" "-1.47551495011547725844e-02" " 1.00000000000000000000e+00"
+" 1.06341241002067987687e-01" " 1.86407717660864613585e+00" "-2.04038293795141795206e-01" "-1.60749650474153876756e-01" "-4.40849240782102969050e-01" "-1.60979520513820612004e-01" " 4.62876655217478893967e-01" " 9.72114778390573863092e-05" "-8.42891877730452790569e-04" " 1.00000000000000000000e+00" " 4.62173942462537512554e-01" "-7.70146016848490032672e-05" "-1.28603273751948785943e-03" " 1.00000000000000000000e+00"
+" 1.19521912350597614427e-01" " 1.87071107891449406324e+00" "-2.01555709907786650970e-01" "-1.61798168032950273609e-01" "-4.39355126712112520337e-01" "-1.58267308423409414075e-01" " 4.56173937376610993955e-01" " 7.99529334775864186646e-03" " 7.98285749610598907577e-03" " 1.00000000000000000000e+00" " 4.56243546526286347653e-01" " 8.08383164904142269280e-03" " 7.97491549049226915169e-03" " 1.00000000000000000000e+00"
+" 1.27391651478953704668e-01" " 1.87467845381020259410e+00" "-1.99887198519305114841e-01" "-1.62214108649143956553e-01" "-4.35652477622920419886e-01" "-1.56162774606530135868e-01" " 4.53276494006642161061e-01" " 1.32964504467802183130e-02" " 1.30645222855357446418e-02" " 1.00000000000000000000e+00" " 4.53783095362249866422e-01" " 1.29589301251803803994e-02" " 1.19070988677393678479e-02" " 1.00000000000000000000e+00"
+" 1.48378817222630354777e-01" " 1.88528306742171802846e+00" "-1.96857494101617430671e-01" "-1.64894436497434737632e-01" "-4.33483972627471070282e-01" "-1.53146635514376988629e-01" " 4.44055568874093808951e-01" " 2.76925977606299264511e-02" " 2.76782765166379354782e-02" " 1.00000000000000000000e+00" " 4.43582440347021933480e-01" " 2.65155609011622182825e-02" " 2.73437746621024158067e-02" " 1.00000000000000000000e+00"
+" 1.59362549800796809985e-01" " 1.89084580370348631639e+00" "-1.94459975649268451692e-01" "-1.65167490222664581356e-01" "-4.31789965496753858076e-01" "-1.50578102907902772190e-01" " 4.38181637859916706113e-01" " 3.32399220716845036905e-02" " 3.37822257687323684872e-02" " 1.00000000000000000000e+00" " 4.38045516927180411670e-01" " 3.33810518567187394789e-02" " 3.35127512956347253792e-02" " 1.00000000000000000000e+00"
+" 1.69305414639138729349e-01" " 1.89588500206250176738e+00" "-1.92237411020182491495e-01" "-1.66712756361419578433e-01" "-4.28597609342009910893e-01" "-1.48468578659457506319e-01" " 4.33485765860617155987e-01" " 4.21763540139890938385e-02" " 4.31078513011782862852e-02" " 1.00000000000000000000e+00" " 4.34135195703849285920e-01" " 4.24271326560168374198e-02" " 4.29721595962449867678e-02" " 1.00000000000000000000e+00"
+" 1.90174070534208650152e-01" " 1.90650237952790413409e+00" "-1.90446388794238752329e-01" "-1.68062321880127041318e-01" "-4.28633064041238465158e-01" "-1.45075414580951467247e-01" " 4.26066359533377736479e-01" " 5.36284044036416385204e-02" " 5.39047890722203978942e-02" " 1.00000000000000000000e+00" " 4.26066359533377736479e-01" " 5.36284044036416385204e-02" " 5.39047890722203978942e-02" " 1.00000000000000000000e+00"
+" 1.99203187250996005542e-01" " 1.91110176606159587465e+00" "-1.88579437506588371010e-01" "-1.70162076561279212994e-01" "-4.25592052015728139480e-01" "-1.45216175407850839330e-01" " 4.23417579929574350306e-01" " 5.86145841664037423047e-02" " 5.76814585654925882086e-02" " 1.00000000000000000000e+00" " 4.23417579929574350306e-01" " 5.86145841664037423047e-02" " 5.76814585654925882086e-02" " 1.00000000000000000000e+00"
+" 2.10987364747485084404e-01" " 1.91711834734776820355e+00" "-1.86679259952975490355e-01" "-1.70757163695493652256e-01" "-4.24386593128949107800e-01" "-1.42636944401326126730e-01" " 4.17790926687134411832e-01" " 6.62608568447949491942e-02" " 6.57220468047886308138e-02" " 1.00000000000000000000e+00" " 4.17790926687134411832e-01" " 6.62608568447949491942e-02" " 6.57220468047886308138e-02" " 1.00000000000000000000e+00"
+" 2.31747832682678900351e-01" " 1.92773776737950242044e+00" "-1.83940932931882183965e-01" "-1.72109598457032775265e-01" "-4.22266145537809611810e-01" "-1.38694450737669700002e-01" " 4.09502187334504830218e-01" " 7.91329072256186927259e-02" " 7.94698175609502288630e-02" " 1.00000000000000000000e+00" " 4.09502187334504830218e-01" " 7.91329072256186927259e-02" " 7.94698175609502288630e-02" " 1.00000000000000000000e+00"
+" 2.39043824701195228855e-01" " 1.93147517605161533893e+00" "-1.81763340762608666124e-01" "-1.72681402409168516243e-01" "-4.21329960451714891079e-01" "-1.37452475630147369356e-01" " 4.05966050944434997394e-01" " 8.29164515404993973657e-02" " 8.11334542709693240514e-02" " 1.00000000000000000000e+00" " 4.05831068620737756003e-01" " 8.28745767717891240745e-02" " 8.05291380045802113186e-02" " 1.00000000000000000000e+00"
+" 2.52457967740567557069e-01" " 1.93836271992803976794e+00" "-1.81193463000845739197e-01" "-1.73696000746715789598e-01" "-4.21566265058053224468e-01" "-1.35232767124049885199e-01" " 4.01626384085670862234e-01" " 9.07734428262826908984e-02" " 9.09128963056798911069e-02" " 1.00000000000000000000e+00" " 4.01202888644781818783e-01" " 9.05245364891092141324e-02" " 9.08481781051470455024e-02" " 1.00000000000000000000e+00"
+" 2.73120223661343919375e-01" " 1.94897581408296471928e+00" "-1.80642441275651322030e-01" "-1.74982015704197968464e-01" "-4.18442575258591964449e-01" "-1.31988728559020607189e-01" " 3.98561451113740139451e-01" " 1.02662100775652923024e-01" " 1.06098594111868102519e-01" " 1.00000000000000000000e+00" " 3.98533328094621885906e-01" " 1.03058527463250615419e-01" " 1.06139878813551385983e-01" " 1.00000000000000000000e+00"
+" 2.78884462151394396656e-01" " 1.95194394392986336761e+00" "-1.78187632330723821905e-01" "-1.76234227016729749771e-01" "-4.15002474446507063632e-01" "-1.30785600600483303824e-01" " 3.94567167725847323112e-01" " 1.08643377250491196540e-01" " 1.09935595401980640284e-01" " 1.00000000000000000000e+00" " 3.94371237747624170389e-01" " 1.08692728041646993753e-01" " 1.09787604138102262707e-01" " 1.00000000000000000000e+00"
+" 2.93737016782436521911e-01" " 1.95962867002094442981e+00" "-1.76006233890053570557e-01" "-1.76017903375845441438e-01" "-4.16800091535223737882e-01" "-1.28693807115416308795e-01" " 3.87804254369114642653e-01" " 1.13410200785950654456e-01" " 1.13426633450955605120e-01" " 1.00000000000000000000e+00" " 3.87939814110230318800e-01" " 1.14074870338533571057e-01" " 1.13688684562727390648e-01" " 1.00000000000000000000e+00"
+" 3.14310728217555401809e-01" " 1.97026989402602570323e+00" "-1.73962045758433991871e-01" "-1.77481607760214848968e-01" "-4.14027685138004641896e-01" "-1.25963102842284985217e-01" " 3.82104927124610749267e-01" " 1.24625951561890491170e-01" " 1.25527481256040573943e-01" " 1.00000000000000000000e+00" " 3.81778214194348819444e-01" " 1.25144095510945130290e-01" " 1.25607978091816896438e-01" " 1.00000000000000000000e+00"
+" 3.18725099601593619969e-01" " 1.97255818998371390549e+00" "-1.72930735663139184544e-01" "-1.77396585573541570868e-01" "-4.14617703253063241142e-01" "-1.25023321084555105731e-01" " 3.79822070451222959520e-01" " 1.26714900424334059315e-01" " 1.26567392892025870621e-01" " 1.00000000000000000000e+00" " 3.79874906239952569997e-01" " 1.26520740164107220460e-01" " 1.26105531774140161572e-01" " 1.00000000000000000000e+00"
+" 3.34843705962408810795e-01" " 1.98092047684842320621e+00" "-1.70274678679581847884e-01" "-1.78653429787690998243e-01" "-4.11405942071117913805e-01" "-1.22559331200983445687e-01" " 3.74273701693347726760e-01" " 1.35105329417008812598e-01" " 1.34639811515937790620e-01" " 1.00000000000000000000e+00" " 3.75023191821807655444e-01" " 1.34899359350960618142e-01" " 1.34486391473781496941e-01" " 1.00000000000000000000e+00"
+" 3.55338266932213375782e-01" " 1.99157793193281995592e+00" "-1.68861891788168239081e-01" "-1.79639101585473831557e-01" "-4.11150470518950039711e-01" "-1.19540594776575456737e-01" " 3.68169473181114925708e-01" " 1.45289041499842536131e-01" " 1.45421399548979396465e-01" " 1.00000000000000000000e+00" " 3.68064423103658278080e-01" " 1.45792833916735392608e-01" " 1.45316827492299294189e-01" " 1.00000000000000000000e+00"
+" 3.58565737051792843282e-01" " 1.99325928201677005092e+00" "-1.68088152730626105846e-01" "-1.79452621871856787816e-01" "-4.09589497898819043797e-01" "-1.19673053303831891658e-01" " 3.67480477614653910923e-01" " 1.47206845764279753430e-01" " 1.46780561910211160281e-01" " 1.00000000000000000000e+00" " 3.67474659119407243146e-01" " 1.47459142783165964019e-01" " 1.47962385967833898182e-01" " 1.00000000000000000000e+00"
+" 3.75796698935874085024e-01" " 2.00224356895539079559e+00" "-1.66005387539434834387e-01" "-1.81003722800379907021e-01" "-4.06967311905129858207e-01" "-1.17838238962381824937e-01" " 3.62328485487730389547e-01" " 1.56820365956303525712e-01" " 1.56022823204245209006e-01" " 1.00000000000000000000e+00" " 3.61635512408597481482e-01" " 1.56070359999738145218e-01" " 1.55466379955065903129e-01" " 1.00000000000000000000e+00"
+" 3.96221262591437028977e-01" " 2.01292114203179650644e+00" "-1.64134541183186599689e-01" "-1.81573549339193895946e-01" "-4.06599260011305418949e-01" "-1.14112339796905826184e-01" " 3.57268523744273480691e-01" " 1.65915721392144999147e-01" " 1.65358311266045665544e-01" " 1.00000000000000000000e+00" " 3.57268523744273480691e-01" " 1.65915721392144999147e-01" " 1.65358311266045665544e-01" " 1.00000000000000000000e+00"
+" 3.98406374501992011083e-01" " 2.01406465801608414168e+00" "-1.63359347492141315783e-01" "-1.81938559261247578824e-01" "-4.05678540777555496355e-01" "-1.14427869102482024366e-01" " 3.56033522051043826995e-01" " 1.66452880346637521747e-01" " 1.65506458432017722338e-01" " 1.00000000000000000000e+00" " 3.56557012749407875596e-01" " 1.66351599423153695412e-01" " 1.65339643993273971434e-01" " 1.00000000000000000000e+00"
+" 4.16614193187194392642e-01" " 2.02360826783990788158e+00" "-1.61392940998634243366e-01" "-1.82197107971740934751e-01" "-4.05639702646240607464e-01" "-1.11070945291743189420e-01" " 3.50654327495739881471e-01" " 1.75118142318103936494e-01" " 1.74769579041459566238e-01" " 1.00000000000000000000e+00" " 3.50599447604181935212e-01" " 1.75348510505069499210e-01" " 1.74970046192169104149e-01" " 1.00000000000000000000e+00"
+" 4.36977702492617525731e-01" " 2.03428881590178090022e+00" "-1.59825364420835946966e-01" "-1.83414104447304965317e-01" "-4.04327742817793267527e-01" "-1.09131151937912437844e-01" " 3.45995951816330360451e-01" " 1.84186595150317961034e-01" " 1.83698505075733431458e-01" " 1.00000000000000000000e+00" " 3.45735671727974147593e-01" " 1.84351934846023718384e-01" " 1.84531191536261823805e-01" " 1.00000000000000000000e+00"
+" 4.38247011952191289907e-01" " 2.03493201787984778761e+00" "-1.61778956011384394964e-01" "-1.84741390458027010535e-01" "-4.05503606289195905887e-01" "-1.08596093193116055575e-01" " 3.47437982832751679485e-01" " 1.87795107561500446147e-01" " 1.90948175287012411605e-01" " 1.00000000000000000000e+00" " 3.47611900608600532525e-01" " 1.87625603312824018598e-01" " 1.91117931239299876367e-01" " 1.00000000000000000000e+00"
+" 4.57313980523084140373e-01" " 2.04499990318908952958e+00" "-1.57632954978096817555e-01" "-1.83818106139373937946e-01" "-4.03785849182797584866e-01" "-1.05458860259442885332e-01" " 3.40610817976483515324e-01" " 1.93784740638320546191e-01" " 1.93531549138136999000e-01" " 1.00000000000000000000e+00" " 3.40956238550359558293e-01" " 1.93176064914911044257e-01" " 1.93865537514476327097e-01" " 1.00000000000000000000e+00"
+" 4.77625197262214196137e-01" " 2.05576215076779522661e+00" "-1.55471040919639896805e-01" "-1.84436652285859509215e-01" "-4.00166527997676102490e-01" "-1.03568764489028797282e-01" " 3.36072910549359005206e-01" " 2.01980837800672108351e-01" " 2.01543799544738971852e-01" " 1.00000000000000000000e+00" " 3.36376975414062917569e-01" " 2.02163343849419724352e-01" " 2.01950788170536438271e-01" " 1.00000000000000000000e+00"
+" 4.78087649402390457709e-01" " 2.05600560617205774250e+00" "-1.56107974585544484469e-01" "-1.83829363744616058884e-01" "-4.01820120271884184682e-01" "-1.02412901287741969769e-01" " 3.36824825766857349763e-01" " 2.02619177958996060651e-01" " 2.02757487818918391564e-01" " 1.00000000000000000000e+00" " 3.36824825766857349763e-01" " 2.02619177958996060651e-01" " 2.02757487818918391564e-01" " 1.00000000000000000000e+00"
+" 4.97913504345446511490e-01" " 2.06649991357224971367e+00" "-1.53375495014640150782e-01" "-1.84672353507325415212e-01" "-3.98578030814480621657e-01" "-1.00919636345967039803e-01" " 3.31055955619719899374e-01" " 2.10177295430298449741e-01" " 2.09665955518348795517e-01" " 1.00000000000000000000e+00" " 3.31250290827163951235e-01" " 2.10233737334792170071e-01" " 2.10218765523974088216e-01" " 1.00000000000000000000e+00"
+" 5.17928286852589625511e-01" " 2.07712002659803962601e+00" "-1.52188717197021733396e-01" "-1.85410022930300483202e-01" "-4.00011876814143574332e-01" "-9.75715648594477069633e-02" " 3.26699782728258558695e-01" " 2.18769030765916139281e-01" " 2.18133228310998295019e-01" " 1.00000000000000000000e+00" " 3.27020815986229951289e-01" " 2.18809493222891421338e-01" " 2.18093207167096181376e-01" " 1.00000000000000000000e+00"
+" 5.18181036708362463550e-01" " 2.07725414951462417079e+00" "-1.51725629172057868699e-01" "-1.85653754335790788232e-01" "-3.98443657668464401578e-01" "-9.85084915665803972917e-02" " 3.26759814463525921635e-01" " 2.18714142117734267057e-01" " 2.18562411988511895444e-01" " 1.00000000000000000000e+00" " 3.26759814463525921635e-01" " 2.18714142117734267057e-01" " 2.18562411988511895444e-01" " 1.00000000000000000000e+00"
+" 5.38429914203115922433e-01" " 2.08802504087222873252e+00" "-1.50315020115600356254e-01" "-1.85892372542195621898e-01" "-3.99524971498401881842e-01" "-9.54384768632954155754e-02" " 3.22770748594162937284e-01" " 2.26842039711022375181e-01" " 2.26475744217558727645e-01" " 1.00000000000000000000e+00" " 3.22386583949304361685e-01" " 2.26623553343529543502e-01" " 2.26010129676513321639e-01" " 1.00000000000000000000e+00"
+" 5.57768924302788793312e-01" " 2.09833608902422996678e+00" "-1.48986610696685062294e-01" "-1.86461890233307503451e-01" "-4.00347210070397696580e-01" "-9.21448773459214581782e-02" " 3.18829855791091021366e-01" " 2.35291368840107317784e-01" " 2.34779255156126548387e-01" " 1.00000000000000000000e+00" " 3.19134398178654188349e-01" " 2.35191832026296343550e-01" " 2.35175297787566239816e-01" " 1.00000000000000000000e+00"
+" 5.58662243186231033398e-01" " 2.09881292961108156803e+00" "-1.48732967824660333722e-01" "-1.86388357872649818026e-01" "-3.98054311726238174707e-01" "-9.23470698149933821863e-02" " 3.18130774344331790360e-01" " 2.35617029537986827359e-01" " 2.35564278656810205392e-01" " 1.00000000000000000000e+00" " 3.18232667448426875811e-01" " 2.35697724563712213142e-01" " 2.35960829634340951699e-01" " 1.00000000000000000000e+00"
+" 5.78880118080907335454e-01" " 2.10958827069622945061e+00" "-1.45517075703337384063e-01" "-1.87619332923932347068e-01" "-3.93759901818246327299e-01" "-9.25428835502136171165e-02" " 3.13810940695913420662e-01" " 2.41900056778995536932e-01" " 2.42445752728476793258e-01" " 1.00000000000000000000e+00" " 3.14443162564996325781e-01" " 2.41261417956367518745e-01" " 2.43102923882014654300e-01" " 1.00000000000000000000e+00"
+" 5.97609561752988072136e-01" " 2.11963448996904224586e+00" "-1.45031114595783383603e-01" "-1.87205794188415763912e-01" "-3.94881995005456065684e-01" "-8.86263596631296779460e-02" " 3.10774119082820043936e-01" " 2.49034608074087504548e-01" " 2.49866199366384905689e-01" " 1.00000000000000000000e+00" " 3.11060216594360450237e-01" " 2.49062419964777598258e-01" " 2.49646736663867746531e-01" " 1.00000000000000000000e+00"
+" 5.99085622916895488288e-01" " 2.12042335300555562227e+00" "-1.46234370009478864549e-01" "-1.87433673503737574517e-01" "-3.98897483543813990980e-01" "-8.78030266493344119239e-02" " 3.11926093355595845935e-01" " 2.50466702249947603676e-01" " 2.49703243194474455713e-01" " 1.00000000000000000000e+00" " 3.11679096477434691703e-01" " 2.50718526077582770650e-01" " 2.49627695026237328424e-01" " 1.00000000000000000000e+00"
+" 6.19280832850907736464e-01" " 2.13128017203372088773e+00" "-1.43479487002560690545e-01" "-1.87093698547644349262e-01" "-3.94519776879344918896e-01" "-8.53431610232009141281e-02" " 3.07345695680125985394e-01" " 2.58029092220712907846e-01" " 2.57726857394332764528e-01" " 1.00000000000000000000e+00" " 3.07352157299550066138e-01" " 2.57865253749803069461e-01" " 2.58647121121913348141e-01" " 1.00000000000000000000e+00"
+" 6.37450199203187239938e-01" " 2.14107236318766336325e+00" "-1.42284579615875261815e-01" "-1.88552201130566088327e-01" "-3.96472719776797488667e-01" "-8.40119348903621276925e-02" " 3.03822808634674423889e-01" " 2.63949199153532987339e-01" " 2.64101889023115043997e-01" " 1.00000000000000000000e+00" " 3.03950755933268257358e-01" " 2.63879217052623626927e-01" " 2.64621757216518316280e-01" " 1.00000000000000000000e+00"
+" 6.39467815670481498636e-01" " 2.14216236411993898869e+00" "-1.42078608483172719179e-01" "-1.88161068194381053686e-01" "-3.95942426437073557999e-01" "-8.29085376020118891560e-02" " 3.03247481826876497113e-01" " 2.64426362878928955524e-01" " 2.63971212284766443279e-01" " 1.00000000000000000000e+00" " 3.03872911464449446672e-01" " 2.64129171956780761654e-01" " 2.64462958249511936870e-01" " 1.00000000000000000000e+00"
+" 6.59648633284134366939e-01" " 2.15306911929802691219e+00" "-1.40817815964762116376e-01" "-1.87994674374339532097e-01" "-3.97440525350125917203e-01" "-8.00049170657205627188e-02" " 2.99875446983518978428e-01" " 2.71497139105559615047e-01" " 2.71514348289811247028e-01" " 1.00000000000000000000e+00" " 2.99305537599990512110e-01" " 2.71917720866866385876e-01" " 2.71826816678953808726e-01" " 1.00000000000000000000e+00"
+" 6.77290836653386407740e-01" " 2.16262758933532683869e+00" "-1.39944188220387233379e-01" "-1.87705038133060192473e-01" "-3.98745397420011638001e-01" "-7.79918396707458688732e-02" " 2.97499038930981674067e-01" " 2.76194314907891147470e-01" " 2.76244997319441798478e-01" " 1.00000000000000000000e+00" " 2.97363042218355133617e-01" " 2.75675960158224986341e-01" " 2.75690815206009076643e-01" " 1.00000000000000000000e+00"
+" 6.79825343200614606864e-01" " 2.16398723606551524057e+00" "-1.39004047425796500859e-01" "-1.87504644012200571979e-01" "-3.91366966762861756557e-01" "-7.85486564170837786580e-02" " 2.98331680074675420489e-01" " 2.79115226766198099018e-01" " 2.80736280587756292793e-01" " 1.00000000000000000000e+00" " 2.98214442391661727072e-01" " 2.79170180724318151011e-01" " 2.80699804226712590349e-01" " 1.00000000000000000000e+00"
+" 6.99999999999999955591e-01" " 2.17492582805589984574e+00" "-1.36588405418039071648e-01" "-1.87831693297507290596e-01" "-3.93443823370816958551e-01" "-7.59743719371416825759e-02" " 2.92706490685071152313e-01" " 2.84206871258673887670e-01" " 2.83329876780357869936e-01" " 1.00000000000000000000e+00" " 2.92548580766212540372e-01" " 2.83727427603582216253e-01" " 2.82332644857856362997e-01" " 1.00000000000000000000e+00"
+" 7.17131474103585686564e-01" " 2.18421983239494243989e+00" "-1.36956831114032950847e-01" "-1.92167796883910391159e-01" "-3.93766068731723262175e-01" "-7.93627751999058661525e-02" " 2.90896799466161370962e-01" " 2.86609162506012482563e-01" " 2.83784961406913893711e-01" " 1.00000000000000000000e+00" " 2.91111938998073804807e-01" " 2.86437163168717978667e-01" " 2.84173975316562410498e-01" " 1.00000000000000000000e+00"
+" 7.20174656799385304318e-01" " 2.18594568310359971264e+00" "-1.35534717691423944874e-01" "-1.86919872920234125813e-01" "-3.94224675182199557621e-01" "-7.32759882868472267603e-02" " 2.90457500990027650545e-01" " 2.88296455862945222304e-01" " 2.87130396337602011858e-01" " 1.00000000000000000000e+00" " 2.90447360366767715067e-01" " 2.88228028857387352790e-01" " 2.87145096339809891006e-01" " 1.00000000000000000000e+00"
+" 7.40351366715865544244e-01" " 2.19698681420482699878e+00" "-1.34443674218011816057e-01" "-1.89169236473724244885e-01" "-3.93173013855508957093e-01" "-7.26251167799430441541e-02" " 2.87265517909787049255e-01" " 2.95897838488713538219e-01" " 2.95181163032294802129e-01" " 1.00000000000000000000e+00" " 2.87633174215253861750e-01" " 2.95375966485877217149e-01" " 2.95531903234045323359e-01" " 1.00000000000000000000e+00"
+" 7.56972111553784854365e-01" " 2.20612580888753218034e+00" "-1.33605219725195373259e-01" "-1.88390908776961130133e-01" "-3.95828887908877269375e-01" "-6.95111713481792736768e-02" " 2.85115029882219928048e-01" " 3.01109605508568745069e-01" " 3.00291061930157754389e-01" " 1.00000000000000000000e+00" " 2.85046272297347524916e-01" " 3.00781225538233276673e-01" " 2.99602218509216144948e-01" " 1.00000000000000000000e+00"
+" 7.60532184329518412547e-01" " 2.20805878538101341135e+00" "-1.34054533824664146024e-01" "-1.88894991786114879728e-01" "-3.97612855971857692694e-01" "-6.88792882941900164173e-02" " 2.84917901078804436388e-01" " 3.01840601201333769144e-01" " 3.01505923965321109836e-01" " 1.00000000000000000000e+00" " 2.84917901078804436388e-01" " 3.01840601201333769144e-01" " 3.01505923965321109836e-01" " 1.00000000000000000000e+00"
+" 7.80719167149092174718e-01" " 2.21919001376595659281e+00" "-1.32293935532865392091e-01" "-1.88942521166470728256e-01" "-3.99904986068700285529e-01" "-6.58816047066926313569e-02" " 2.80673617977418354830e-01" " 3.08061771476256629487e-01" " 3.06773690570651347276e-01" " 1.00000000000000000000e+00" " 2.80795372781097951620e-01" " 3.08030448257264000134e-01" " 3.06631535222501028226e-01" " 1.00000000000000000000e+00"
+" 7.96812749003984022167e-01" " 2.22807390005073324701e+00" "-1.30957039955297754874e-01" "-1.88772417984381324363e-01" "-3.96926918010010176818e-01" "-6.50209880749370999764e-02" " 2.78882402083083402733e-01" " 3.11773841214576685754e-01" " 3.11608731412693462648e-01" " 1.00000000000000000000e+00" " 2.78882402083083402733e-01" " 3.11773841214576685754e-01" " 3.11608731412693462648e-01" " 1.00000000000000000000e+00"
+" 8.00914377083104422894e-01" " 2.23034902334584606010e+00" "-1.30993989172689173639e-01" "-1.88955425984223879254e-01" "-3.99259513784885500254e-01" "-6.38864237957462721695e-02" " 2.78482771238290849336e-01" " 3.12924306563041931817e-01" " 3.12620292795022292065e-01" " 1.00000000000000000000e+00" " 2.78605925218550043443e-01" " 3.12784523296142202842e-01" " 3.12029397713817491233e-01" " 1.00000000000000000000e+00"
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/robast -r 628


More information about the Robast-commits mailing list