[Soiltexture-commits] r36 - in pkg: . soiltexture soiltexture/R soiltexture/inst/doc soiltexture/inst/doc2 soiltexture/man
noreply at r-forge.r-project.org
noreply at r-forge.r-project.org
Thu Aug 19 11:36:44 CEST 2010
Author: jmoeys
Date: 2010-08-19 11:36:43 +0200 (Thu, 19 Aug 2010)
New Revision: 36
Modified:
pkg/soiltexture/DESCRIPTION
pkg/soiltexture/R/soiltexture.R
pkg/soiltexture/inst/doc/soiltexture_vignette.pdf
pkg/soiltexture/inst/doc2/soiltexture_vignette.R
pkg/soiltexture/inst/doc2/soiltexture_vignette.Rnw
pkg/soiltexture/inst/doc2/soiltexture_vignette.tex
pkg/soiltexture/man/TT.text.transf.Xm.Rd
pkg/soiltexture/man/soiltexture-package.Rd
pkg/soiltexture_1.0.tar.gz
pkg/soiltexture_1.0.zip
Log:
Commit latest changes by Wei. Compiled package.
Modified: pkg/soiltexture/DESCRIPTION
===================================================================
--- pkg/soiltexture/DESCRIPTION 2010-08-16 16:08:15 UTC (rev 35)
+++ pkg/soiltexture/DESCRIPTION 2010-08-19 09:36:43 UTC (rev 36)
@@ -1,8 +1,8 @@
Package: soiltexture
Version: 1.0
-Date: 2010-08-16
+Date: 2010-08-19
Title: Functions for soil texture plot, classification and transformation
-Author: Julien MOEYS <jules_m78-soiltexture at yahoo.fr>
+Author: Julien MOEYS <jules_m78-soiltexture at yahoo.fr>, contributions from Wei Shangguan.
Maintainer: Julien MOEYS <jules_m78-soiltexture at yahoo.fr>
Depends: R (>= 2.11.1), sp, MASS, drc
Suggests: plotrix
Modified: pkg/soiltexture/R/soiltexture.R
===================================================================
--- pkg/soiltexture/R/soiltexture.R 2010-08-16 16:08:15 UTC (rev 35)
+++ pkg/soiltexture/R/soiltexture.R 2010-08-19 09:36:43 UTC (rev 36)
@@ -2617,21 +2617,21 @@
TT.text.transf.Xm <- function(# Transformations of a soil texture data table between 2 particle size systems (X classes), various methods.
### using various Particle Size Distribution (PSD) models including Anderson (AD), Fredlund4P (F4P), Fredlund3P (F3P),
### modified logistic growth (ML), Offset-Nonrenormalized Lognormal (ONL), Offset-Renormalized Lognormal (ORL),
-### Skaggs (S), van Genuchten type(VG),van Genuchten modified, Weibull (W), Logarithm(L),
-### Logistic growth (LG), Simple Lognormal (SL),Shiozawa and Compbell (SC).
+### Skaggs (S), van Genuchten type(VG),van Genuchten modified(VGM), Weibull (W), Logarithm(L),
+### Logistic growth (LG), Simple Lognormal (SL),Shiozawa and Compbell (SC).
### The performance of PSD models is influenced by many aspects like soil texture class,
### number and position (or closeness) of observation points, clay content etc.
-### The latter four PSD models perform worse than the former ten.
-### The AD, F4P, S, and W model is recommended for most of texture classes.
+### The latter four PSD models perform worse than the former ten.
+### The AD, F4P, S, and W model is recommended for most of texture classes.
### And it will be even better to compare several different PSD models and using the results of the model
### with the minimum residual sum of squares (or other measures).
### Sometimes, the fitting will failed for the iteration is not converged or some errors happened.
-### Transformation of a soil texture data table
-### ('tri.data') from one
-### particle size system ('dat.ps.lim') into another
-### ('base.ps.lim'). No limit in the number of texture classes
-### in the input and output texture tables. See TT.text.transf
-### for transformation involving only 3 particle classes. 'tri.data'
+### Transformation of a soil texture data table
+### ('tri.data') from one
+### particle size system ('dat.ps.lim') into another
+### ('base.ps.lim'). No limit in the number of texture classes
+### in the input and output texture tables. See TT.text.transf
+### for transformation involving only 3 particle classes. 'tri.data'
### can only contain texture data.
##author<<Wei Shangguan
@@ -2645,7 +2645,7 @@
psdmodel = "AD",
omethod = "all",#see optim for available methods, the default "all" is to run all methods and
# choose the best results with minimum residual sum of squares (RSS).
- tri.sum.norm = FALSE #Weather the sum of is
+ tri.sum.norm = FALSE #Weather the sum of is
){#
TT.auto.set( set.par = FALSE )
#
@@ -2691,7 +2691,7 @@
# dat.ps.lim2 <- TT.dia2phi(dat.ps.lim)
#
# old.col.nm <- colnames( tri.data )
-
+
#
fitpsd <- function(
y,
@@ -2699,7 +2699,7 @@
xout,
psdmodel,
method)
- {
+ {
require( "drc" ) # Added 2010/08/11 by JM
#
#default max and min of initial parameters
@@ -2803,6 +2803,8 @@
logi <- S
pn <- 2
pname <- c("u","c")
+ #S model can not deal with first texture data with zero value
+ if(y[1] == 0) y[1] <- 0.0001
}
else if ( psdmodel == "VG" )
{
@@ -2852,7 +2854,7 @@
pn <- 2
pname <- c("u","o")
}
- #default lower and upper limit for drc::drm, these values should not set
+ #default lower and upper limit for drc::drm, these values should not set
#at the beginning of the function for pn is set later
lowerl <- rep(10e-9,times=pn)
upperl <- rep(10e+5,times=pn)
@@ -2860,12 +2862,12 @@
spa <- c(1,1,1,1)
#methods used in optim() of drc::drm
meth <- c("Nelder-Mead", "BFGS", "CG", "L-BFGS-B", "SANN")
-
+
mdev <- 100
for( i in 1:5 ) # The nonlinear optimization runs were carried out using at least
- # five random initial parameter estimates for all soils.
+ # five random initial parameter estimates for all soils.
#When the final solution for each soil converged to different parameter values,
- #the parameter values with the best fitting statistics (RSS) were kept.
+ #the parameter values with the best fitting statistics (RSS) were kept.
{
if( method == "all" )# using all optim methods
{
@@ -2937,18 +2939,19 @@
#when the residual sum of error (deviance) is very small, the iteration is stopped to save time
if(mdev < 0.0001) break
}
- if( psdmodel == "AD" ) #predict() has some bug for AD model
+ #predict() has some bug for PSD model to predict the target values
+ if( psdmodel == "AD" )
{
pre <- coef(ttbest)[1] + coef(ttbest)[2]*atan(coef(ttbest)[3]*log10(xout/coef(ttbest)[4]))
- }
- else if( psdmodel == "F4P" ) #predict() has some bug for F4P model
+ }
+ else if( psdmodel == "F4P" )
{
pre <- (1-(log(1+coef(ttbest)[1]/xout)/log(1+coef(ttbest)[1]/0.0001))^7)/(log(exp(1)+(coef(ttbest)[2]/xout)^coef(ttbest)[3]))^coef(ttbest)[4]
}
else if( psdmodel == "F3P" )
{
pre <- (1-(log(1+0.001/xout)/log(1+0.001/0.0001))^7)/(log(exp(1)+(coef(ttbest)[1]/xout)^coef(ttbest)[2]))^coef(ttbest)[3]
- }
+ }
else if( psdmodel == "ML" )
{
pre <- 1/(1+coef(ttbest)[1]*exp(-coef(ttbest)[2]*xout^(coef(ttbest)[3])))
@@ -2956,46 +2959,46 @@
else if( psdmodel == "ONL" )
{
t <- (-1)^(log(xout) >= coef(ttbest)[1]+1)
- pre <- (1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2+(coef(ttbest)[3])
+ pre <- (1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2+(coef(ttbest)[3])
}
- else if( psdmodel == "ORL" ) #predict() has some bug for F4P model
+ else if( psdmodel == "ORL" )
{
t <- (-1)^(log(xout) >= coef(ttbest)[1]+1)
- pre <- (1-coef(ttbest)[3])*(1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2+coef(ttbest)[3]
+ pre <- (1-coef(ttbest)[3])*(1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2+coef(ttbest)[3]
}
- else if( psdmodel == "S" ) #predict() has some bug for F4P model
+ else if( psdmodel == "S" )
{
- pre <- 1/(1+(1/y[1]-1)*exp(-coef(ttbest)[1]*((xout-r0)/r0)^coef(ttbest)[2]))
+ pre <- 1/(1+(1/y[1]-1)*exp(-coef(ttbest)[1]*((xout-r0)/r0)^coef(ttbest)[2]))
}
- else if( psdmodel == "VG" ) #predict() has some bug for F4P model
+ else if( psdmodel == "VG" )
{
- pre <- 1(1+(coef(ttbest)[1]/xout)^coef(ttbest)[2])^(1/coef(ttbest)[2]-1)
+ pre <- (1+(coef(ttbest)[1]/xout)^coef(ttbest)[2])^(1/coef(ttbest)[2]-1)
}
- else if( psdmodel == "VGM" ) #predict() has some bug for F4P model
+ else if( psdmodel == "VGM" )
{
- pre <- y[1]+(1-y[1])*(1+(coef(ttbest)[1]*xout)^(-coef(ttbest)[2]))^(1/coef(ttbest)[2]-1)
+ pre <- y[1]+(1-y[1])*(1+(coef(ttbest)[1]*xout)^(-coef(ttbest)[2]))^(1/coef(ttbest)[2]-1)
}
- else if( psdmodel == "W" ) #predict() has some bug for F4P model
+ else if( psdmodel == "W" )
{
- pre <- coef(ttbest)[3]+(1-coef(ttbest)[3])*(1-exp(-coef(ttbest)[1]*((xout-dmin)/(dmax-dmin))^coef(ttbest)[2]))
+ pre <- coef(ttbest)[3]+(1-coef(ttbest)[3])*(1-exp(-coef(ttbest)[1]*((xout-dmin)/(dmax-dmin))^coef(ttbest)[2]))
}
- else if( psdmodel == "L" ) #predict() has some bug for F4P model
+ else if( psdmodel == "L" )
{
- pre <- coef(ttbest)[1]*log(xout)+coef(ttbest)[2]
+ pre <- coef(ttbest)[1]*log(xout)+coef(ttbest)[2]
}
- else if( psdmodel == "LG" ) #predict() has some bug for F4P model
+ else if( psdmodel == "LG" )
{
- pre <- 1/(1+coef(ttbest)[1]*exp(-coef(ttbest)[2]*xout))
+ pre <- 1/(1+coef(ttbest)[1]*exp(-coef(ttbest)[2]*xout))
}
- else if( psdmodel == "SC" ) #predict() has some bug for F4P model
+ else if( psdmodel == "SC" )
{
t <- (-1)^(log(xout) >= coef(ttbest)[1]+1)
- pre <- (1-coef(ttbest)[3])*(1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2+coef(ttbest)[3]*(1+t*erf((log(xout)+1.96)/1*2^0.5))/2
+ pre <- (1-coef(ttbest)[3])*(1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2+coef(ttbest)[3]*(1+t*erf((log(xout)+1.96)/1*2^0.5))/2
}
- else if( psdmodel == "SL" ) #predict() has some bug for F4P model
+ else if( psdmodel == "SL" )
{
t <- (-1)^(log(xout) >= coef(ttbest)[1]+1)
- pre <- (1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2
+ pre <- (1+t*erf((log(xout)+coef(ttbest)[1])/coef(ttbest)[2]*2^0.5))/2
}
#pre are the predicted values, coef(ttbest) are the model paremeters,
out <- c(pre[1],pre[2:length(pre)]-pre[1:length(pre)-1])*100
@@ -3003,17 +3006,22 @@
c(out,coef(ttbest),dev=mdev*10000)
}
- results <- t(apply(tri.data[1:dim(tri.data)[1],],
- 1,
- fitpsd,
+ results <- t(apply(
+ X = tri.data[1:dim(tri.data)[1],],
+
+ MARGIN = 1,
+ FUN = fitpsd,
xin = dat.ps.lim[ ps.start:ps.end ],
xout = base.ps.lim[ ps.start:length(base.ps.lim) ],
psdmodel= psdmodel,
method = omethod)
)
-# results <- t(apply(tri.data[1:5,],
-# 1,
-# fitpsd,
+
+
+# results <- t(apply(
+# X = tri.data[1:5,],
+# MARGIN = 1,
+# FUN = fitpsd,
# xin = dat.ps.lim[ ps.start:ps.end ],
# xout = base.ps.lim[ ps.start:length(base.ps.lim) ],
# psdmodel= psdmodel,
@@ -3024,28 +3032,31 @@
results
}
-# my.text4 <- data.frame(
-# "CLAY" = c(05,60,15,05,25,05,25,45,65,75,13,47),
-# "FSILT" = c(02,04,10,15,25,40,35,20,10,05,10,20),
-# "CSILT" = c(03,04,05,10,30,45,30,25,05,10,07,23),
-# "SAND" = c(90,32,70,70,20,10,10,10,20,10,70,10)
+# my.text4 <- data.frame(
+# "CLAY" = c(05,60,15,05,25,05,25,45,65,75,13,47),
+# "FSILT" = c(02,04,10,15,25,40,35,20,10,05,10,20),
+# "CSILT" = c(03,04,05,10,30,45,30,25,05,10,07,23),
+# "SAND" = c(90,32,70,70,20,10,10,10,20,10,70,10)
# ) #
-# TT.text.transf.Xm(
-# tri.data = my.text4,
-# base.ps.lim = c(0,2,20,50,2000),
-# dat.ps.lim = c(0,2,20,63,2000),
+# TT.text.transf.Xm(
+# tri.data = my.text4,
+# base.ps.lim = c(0,2,20,50,2000),
+# dat.ps.lim = c(0,2,20,63,2000),
# psdmodel = "S"
# ) #
# TT.text.transf.Xm( # JM: does not work on my PC
-# tri.data = my.text4,
-# base.ps.lim = c(0,1,50,2000),
+# tri.data = my.text4,
+# base.ps.lim = c(0,1,50,2000),
# dat.ps.lim = c(0,2,30,60,2000),
# psdmodel = "AD",
-# omethod = "Nelder-Mead"
-# )
+# omethod = "Nelder-Mead"
+# )
+
+
+
TT.deg2rad <- function(# Function to convert angle in degree to angle in radian.
### Function to convert angle in degree to angle in radian.
Modified: pkg/soiltexture/inst/doc/soiltexture_vignette.pdf
===================================================================
--- pkg/soiltexture/inst/doc/soiltexture_vignette.pdf 2010-08-16 16:08:15 UTC (rev 35)
+++ pkg/soiltexture/inst/doc/soiltexture_vignette.pdf 2010-08-19 09:36:43 UTC (rev 36)
@@ -387,8 +387,7 @@
>>
stream
xÚuSËNÃ0¼ç+öHdëµãG¸ J@¹!¥>HSAùzÖvÚ"T³kï̬G®7p¾×U2+dQ. Z¤`LÒ¨æðV¥ï,WÒÝó£u·àü«ÛóÚ~úo^¦í×Ëì¥@î,sC. Krú)ö/=xÍ1ãèêM_í¢ÀS¿ÕÆrë¥}Ýuußøvyf×Üy¨?òÀÃyO×Nú_âU:ÂF¡vÅéb'æØ6AѦWûkwdÚM½ØhL%iöí·UaXÛ¡+)jOöÁêhùbÍR§,&]KÁ]¡
-ÕzµSQê¿».BÉpqs)8'á9þ<~J,4~:äÊ 32*¼öäuÓ»£mºö+×LËàU¬Â¥Û*!Nø
-éÉ* )P±îl|$¥Ö
ã<È~ct¿"¸Ù$ü;¿ÉÐ*ùLø¸£Ê²@2|u
ê ÏýÜÀ²
+ÕzµSQê¿».B©äâ"æRpNÂsüy ü:,Xiüt)ÈAgdTxíÉë¦wGÛtí7V¯Á«6X/'J·UBðÒ%U at R bÝÙ*ùHJ+-Çy8ýÆè~Ep³Iùw~¡5Tò#ð?pGedøêÕ?:ûà¢À¶
endstream
endobj
257 0 obj <<
@@ -410,7 +409,6 @@
/ProcSet [ /PDF /Text ]
/Font << /F1 270 0 R/F3 271 0 R/F6 272 0 R>>
/ExtGState <<
-/GSais 273 0 R
>>>>
/Length 10830
>>
@@ -960,8 +958,8 @@
endobj
269 0 obj
<<
-/CreationDate (D:20100816175416)
-/ModDate (D:20100816175416)
+/CreationDate (D:20100819113017)
+/ModDate (D:20100819113017)
/Title (R Graphics Output)
/Producer (R 2.11.1)
/Creator (R)
@@ -981,7 +979,7 @@
/Subtype /Type1
/Name /F3
/BaseFont /Helvetica-Bold
-/Encoding 274 0 R
+/Encoding 273 0 R
>>
endobj
272 0 obj
@@ -994,12 +992,6 @@
endobj
273 0 obj
<<
-/Type /ExtGState
-/AIS false
->>
-endobj
-274 0 obj
-<<
/Type /Encoding
/BaseEncoding /WinAnsiEncoding
/Differences [ 45/minus]
@@ -1019,7 +1011,7 @@
/XObject << /Im1 258 0 R >>
/ProcSet [ /PDF /Text ]
>> endobj
-315 0 obj <<
+314 0 obj <<
/Length 2146
/Filter /FlateDecode
>>
@@ -1038,333 +1030,333 @@
Lu{¸CO@ÚÝ8 Ú[ývèèÈ3^»£0MâzVî´1¿WµA'^Í»Ü('ië<°[KçÕ&R0´X:Dk{V|hÍL«IÍãc»nùÌîSÕexSæÃ'&ë÷oÔéà +m8=wk¼w¢#M¯apWØÆõ¨EðßRÚdHpÿ2dkg{
ñ0v²NïêiÈk*d.
Àõ?pzÕkdâ8·nZÔÜ:xoÜ`0ÞÐójùl½Ìq¼/¦-ѹnÊM8édPº¦Èpú̪J¢¹²·i(Q%É0c»OÛí»´õ?"4
endstream
endobj
-314 0 obj <<
+313 0 obj <<
/Type /Page
-/Contents 315 0 R
-/Resources 313 0 R
+/Contents 314 0 R
+/Resources 312 0 R
/MediaBox [0 0 595.276 841.89]
/Parent 268 0 R
-/Annots [ 275 0 R 276 0 R 277 0 R 278 0 R 279 0 R 280 0 R 320 0 R 281 0 R 282 0 R 283 0 R 284 0 R 285 0 R 286 0 R 287 0 R 288 0 R 289 0 R 290 0 R 321 0 R 291 0 R 292 0 R 293 0 R 322 0 R 294 0 R 295 0 R 296 0 R 297 0 R 298 0 R 299 0 R 300 0 R 301 0 R 302 0 R 303 0 R 323 0 R 304 0 R 324 0 R 305 0 R 306 0 R 307 0 R 308 0 R 325 0 R 309 0 R 326 0 R 310 0 R 311 0 R ]
+/Annots [ 274 0 R 275 0 R 276 0 R 277 0 R 278 0 R 279 0 R 319 0 R 280 0 R 281 0 R 282 0 R 283 0 R 284 0 R 285 0 R 286 0 R 287 0 R 288 0 R 289 0 R 320 0 R 290 0 R 291 0 R 292 0 R 321 0 R 293 0 R 294 0 R 295 0 R 296 0 R 297 0 R 298 0 R 299 0 R 300 0 R 301 0 R 302 0 R 322 0 R 303 0 R 323 0 R 304 0 R 305 0 R 306 0 R 307 0 R 324 0 R 308 0 R 325 0 R 309 0 R 310 0 R ]
>> endobj
-275 0 obj <<
+274 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 683.215 247.849 692.082]
/A << /S /GoTo /D (section.1) >>
>> endobj
-276 0 obj <<
+275 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 669.327 338.777 680.166]
/A << /S /GoTo /D (subsection.1.1) >>
>> endobj
-277 0 obj <<
+276 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 659.304 201.952 668.211]
/A << /S /GoTo /D (subsection.1.2) >>
>> endobj
-278 0 obj <<
+277 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 647.349 240.537 656.256]
/A << /S /GoTo /D (subsection.1.3) >>
>> endobj
-279 0 obj <<
+278 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 635.394 249.633 644.301]
/A << /S /GoTo /D (subsection.1.4) >>
>> endobj
-280 0 obj <<
+279 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 611.544 469.509 622.343]
/A << /S /GoTo /D (section.2) >>
>> endobj
-320 0 obj <<
+319 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 601.521 208.019 610.388]
/A << /S /GoTo /D (section.2) >>
>> endobj
-281 0 obj <<
+280 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 587.075 372.092 598.936]
/A << /S /GoTo /D (subsection.2.1) >>
>> endobj
-282 0 obj <<
+281 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 575.678 344.745 586.517]
/A << /S /GoTo /D (subsection.2.2) >>
>> endobj
-283 0 obj <<
+282 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 553.76 249.932 564.56]
/A << /S /GoTo /D (section.3) >>
>> endobj
-284 0 obj <<
+283 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 541.805 313.931 552.644]
/A << /S /GoTo /D (subsection.3.1) >>
>> endobj
-285 0 obj <<
+284 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 529.292 388.919 541.152]
/A << /S /GoTo /D (subsection.3.2) >>
>> endobj
-286 0 obj <<
+285 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 517.895 301.139 528.734]
/A << /S /GoTo /D (subsection.3.3) >>
>> endobj
-287 0 obj <<
+286 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 495.977 420.42 506.776]
/A << /S /GoTo /D (section.4) >>
>> endobj
-288 0 obj <<
+287 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 484.022 295.898 494.861]
/A << /S /GoTo /D (subsection.4.1) >>
>> endobj
-289 0 obj <<
+288 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 473.999 322.399 482.906]
/A << /S /GoTo /D (subsection.4.2) >>
>> endobj
-290 0 obj <<
+289 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 459.554 469.509 471.414]
/A << /S /GoTo /D (subsection.4.3) >>
>> endobj
-321 0 obj <<
+320 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 447.598 254.236 459.459]
/A << /S /GoTo /D (subsection.4.3) >>
>> endobj
-291 0 obj <<
+290 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 438.134 356.739 447.04]
/A << /S /GoTo /D (subsection.4.4) >>
>> endobj
-292 0 obj <<
+291 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 426.179 367.409 435.085]
/A << /S /GoTo /D (subsection.4.5) >>
>> endobj
-293 0 obj <<
+292 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 411.733 469.509 423.593]
/A << /S /GoTo /D (subsection.4.6) >>
>> endobj
-322 0 obj <<
+321 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 402.268 202.41 411.175]
/A << /S /GoTo /D (subsection.4.6) >>
>> endobj
-294 0 obj <<
+293 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 388.38 422.781 399.22]
/A << /S /GoTo /D (subsection.4.7) >>
>> endobj
-295 0 obj <<
+294 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 378.358 340.291 387.265]
/A << /S /GoTo /D (subsection.4.8) >>
>> endobj
-296 0 obj <<
+295 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 364.47 327.081 375.309]
/A << /S /GoTo /D (subsection.4.9) >>
>> endobj
-297 0 obj <<
+296 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 354.448 336.077 363.354]
/A << /S /GoTo /D (subsection.4.10) >>
>> endobj
-298 0 obj <<
+297 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 342.493 314.777 351.399]
/A << /S /GoTo /D (subsection.4.11) >>
>> endobj
-299 0 obj <<
+298 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 330.537 338.986 339.444]
/A << /S /GoTo /D (subsection.4.12) >>
>> endobj
-300 0 obj <<
+299 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 316.649 411.354 327.489]
/A << /S /GoTo /D (subsection.4.13) >>
>> endobj
-301 0 obj <<
+300 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 304.694 405.067 318.109]
/A << /S /GoTo /D (subsection.4.14) >>
>> endobj
-302 0 obj <<
+301 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 282.777 396.032 293.576]
/A << /S /GoTo /D (section.5) >>
>> endobj
-303 0 obj <<
+302 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 270.821 469.509 281.661]
/A << /S /GoTo /D (subsection.5.1) >>
>> endobj
-323 0 obj <<
+322 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 258.866 245.857 269.705]
/A << /S /GoTo /D (subsection.5.1) >>
>> endobj
-304 0 obj <<
+303 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 246.911 469.509 257.75]
/A << /S /GoTo /D (subsection.5.2) >>
>> endobj
-324 0 obj <<
+323 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 234.956 248.915 245.795]
/A << /S /GoTo /D (subsection.5.2) >>
>> endobj
-305 0 obj <<
+304 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 213.038 268.123 223.837]
/A << /S /GoTo /D (section.6) >>
>> endobj
-306 0 obj <<
+305 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 201.083 299.734 211.922]
/A << /S /GoTo /D (subsection.6.1) >>
>> endobj
-307 0 obj <<
+306 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 189.128 383.987 199.967]
/A << /S /GoTo /D (subsection.6.2) >>
>> endobj
-308 0 obj <<
+307 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 176.615 469.509 188.475]
/A << /S /GoTo /D (subsection.6.3) >>
>> endobj
-325 0 obj <<
+324 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 167.15 197.688 176.057]
/A << /S /GoTo /D (subsection.6.3) >>
>> endobj
-309 0 obj <<
+308 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 152.704 469.509 164.565]
/A << /S /GoTo /D (subsection.6.4) >>
>> endobj
-326 0 obj <<
+325 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 143.24 204.044 152.146]
/A << /S /GoTo /D (subsection.6.4) >>
>> endobj
-310 0 obj <<
+309 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 129.352 385.551 140.191]
/A << /S /GoTo /D (subsection.6.5) >>
>> endobj
-311 0 obj <<
+310 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 117.397 310.882 128.236]
/A << /S /GoTo /D (subsection.6.6) >>
>> endobj
-316 0 obj <<
-/D [314 0 R /XYZ 124.798 753.953 null]
+315 0 obj <<
+/D [313 0 R /XYZ 124.798 753.953 null]
>> endobj
-318 0 obj <<
-/D [314 0 R /XYZ 124.802 696.276 null]
+317 0 obj <<
+/D [313 0 R /XYZ 124.802 696.276 null]
>> endobj
-313 0 obj <<
-/Font << /F44 317 0 R /F49 319 0 R /F8 267 0 R >>
+312 0 obj <<
+/Font << /F44 316 0 R /F49 318 0 R /F8 267 0 R >>
/ProcSet [ /PDF /Text ]
>> endobj
-354 0 obj <<
+353 0 obj <<
/Length 2383
/Filter /FlateDecode
>>
@@ -1389,259 +1381,259 @@
£Öý¤å§éÿÇFeÈ
endstream
endobj
-353 0 obj <<
+352 0 obj <<
/Type /Page
-/Contents 354 0 R
-/Resources 352 0 R
+/Contents 353 0 R
+/Resources 351 0 R
/MediaBox [0 0 595.276 841.89]
/Parent 268 0 R
-/Annots [ 312 0 R 327 0 R 328 0 R 329 0 R 330 0 R 356 0 R 331 0 R 332 0 R 333 0 R 334 0 R 357 0 R 335 0 R 336 0 R 358 0 R 337 0 R 338 0 R 339 0 R 340 0 R 341 0 R 359 0 R 342 0 R 360 0 R 343 0 R 361 0 R 344 0 R 345 0 R 346 0 R 347 0 R 362 0 R 348 0 R 349 0 R 350 0 R 351 0 R ]
+/Annots [ 311 0 R 326 0 R 327 0 R 328 0 R 329 0 R 355 0 R 330 0 R 331 0 R 332 0 R 333 0 R 356 0 R 334 0 R 335 0 R 357 0 R 336 0 R 337 0 R 338 0 R 339 0 R 340 0 R 358 0 R 341 0 R 359 0 R 342 0 R 360 0 R 343 0 R 344 0 R 345 0 R 346 0 R 361 0 R 347 0 R 348 0 R 349 0 R 350 0 R ]
>> endobj
-312 0 obj <<
+311 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 705.133 420.789 713.999]
/A << /S /GoTo /D (section.7) >>
>> endobj
-327 0 obj <<
+326 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 690.687 423.309 702.547]
/A << /S /GoTo /D (subsection.7.1) >>
>> endobj
-328 0 obj <<
+327 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 678.732 408.664 690.592]
/A << /S /GoTo /D (subsection.7.2) >>
>> endobj
-329 0 obj <<
+328 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 656.814 381.346 668.769]
/A << /S /GoTo /D (section.8) >>
>> endobj
-330 0 obj <<
+329 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 635.454 469.509 646.253]
/A << /S /GoTo /D (section.9) >>
>> endobj
-356 0 obj <<
+355 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 623.499 254.335 634.298]
/A << /S /GoTo /D (section.9) >>
>> endobj
-331 0 obj <<
+330 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 610.986 422.87 622.846]
/A << /S /GoTo /D (subsection.9.1) >>
>> endobj
-332 0 obj <<
+331 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 599.03 454.067 610.891]
/A << /S /GoTo /D (subsection.9.2) >>
>> endobj
-333 0 obj <<
+332 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 587.633 403.095 598.473]
/A << /S /GoTo /D (subsection.9.3) >>
>> endobj
-334 0 obj <<
+333 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 575.12 469.509 586.981]
/A << /S /GoTo /D (subsection.9.4) >>
>> endobj
-357 0 obj <<
+356 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 565.656 202.41 574.562]
/A << /S /GoTo /D (subsection.9.4) >>
>> endobj
-335 0 obj <<
+334 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 551.768 414.681 562.607]
/A << /S /GoTo /D (subsection.9.5) >>
>> endobj
-336 0 obj <<
+335 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 539.813 469.509 550.652]
/A << /S /GoTo /D (subsection.9.6) >>
>> endobj
-358 0 obj <<
+357 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 527.857 282.977 538.697]
/A << /S /GoTo /D (subsection.9.6) >>
>> endobj
-337 0 obj <<
+336 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 505.94 354.269 516.739]
/A << /S /GoTo /D (section.10) >>
>> endobj
-338 0 obj <<
+337 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 493.984 238.475 504.824]
/A << /S /GoTo /D (subsection.10.1) >>
>> endobj
-339 0 obj <<
+338 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 483.962 287.191 492.869]
/A << /S /GoTo /D (subsection.10.2) >>
>> endobj
-340 0 obj <<
+339 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 472.007 270.275 480.913]
/A << /S /GoTo /D (subsection.10.3) >>
>> endobj
-341 0 obj <<
+340 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 458.119 469.509 468.958]
/A << /S /GoTo /D (subsection.10.4) >>
>> endobj
-359 0 obj <<
+358 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 446.164 273.931 457.003]
/A << /S /GoTo /D (subsection.10.4) >>
>> endobj
-342 0 obj <<
+341 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 434.209 469.509 445.048]
/A << /S /GoTo /D (subsection.10.5) >>
>> endobj
-360 0 obj <<
+359 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 424.186 192.02 433.093]
/A << /S /GoTo /D (subsection.10.5) >>
>> endobj
-343 0 obj <<
+342 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 400.336 469.509 411.135]
/A << /S /GoTo /D (section.11) >>
>> endobj
-361 0 obj <<
+360 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 388.38 188.971 399.18]
/A << /S /GoTo /D (section.11) >>
>> endobj
-344 0 obj <<
+343 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 376.425 396.579 387.265]
/A << /S /GoTo /D (subsection.11.1) >>
>> endobj
-345 0 obj <<
+344 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 363.912 381.008 375.773]
/A << /S /GoTo /D (subsection.11.2) >>
>> endobj
-346 0 obj <<
+345 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 354.448 294.384 363.354]
/A << /S /GoTo /D (subsection.11.3) >>
>> endobj
-347 0 obj <<
+346 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 330.597 469.509 341.397]
/A << /S /GoTo /D (section.12) >>
>> endobj
-362 0 obj <<
+361 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 320.575 208.019 329.441]
/A << /S /GoTo /D (section.12) >>
>> endobj
-348 0 obj <<
+347 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 306.687 389.785 317.526]
/A << /S /GoTo /D (subsection.12.1) >>
>> endobj
-349 0 obj <<
+348 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [138.75 294.732 454.067 305.571]
/A << /S /GoTo /D (subsection.12.2) >>
>> endobj
-350 0 obj <<
+349 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 272.256 369.372 284.211]
/A << /S /GoTo /D (section.13) >>
>> endobj
-351 0 obj <<
+350 0 obj <<
/Type /Annot
/Subtype /Link
/Border[0 0 0]/H/I/C[1 0 0]
/Rect [123.806 250.896 224.308 261.695]
/A << /S /GoTo /D (section.14) >>
>> endobj
-355 0 obj <<
-/D [353 0 R /XYZ 123.802 753.953 null]
+354 0 obj <<
+/D [352 0 R /XYZ 123.802 753.953 null]
>> endobj
5 0 obj <<
-/D [353 0 R /XYZ 124.802 236.899 null]
+/D [352 0 R /XYZ 124.802 236.899 null]
>> endobj
9 0 obj <<
-/D [353 0 R /XYZ 124.802 211.046 null]
+/D [352 0 R /XYZ 124.802 211.046 null]
>> endobj
-352 0 obj <<
-/Font << /F49 319 0 R /F8 267 0 R /F44 317 0 R /F37 265 0 R >>
+351 0 obj <<
+/Font << /F49 318 0 R /F8 267 0 R /F44 316 0 R /F37 265 0 R >>
/ProcSet [ /PDF /Text ]
>> endobj
-377 0 obj <<
+376 0 obj <<
/Length 2528
/Filter /FlateDecode
>>
@@ -1670,23 +1662,23 @@
@/_ÑMÝÀ< D×Ñp?ò,g>Ê<×J!FÁ¿jʲl*g¢&ËèdSôפ°^+pæ7i@ .)Enù{µÞbÆI=×åÐCkÆD3^ÉK½.u%ñèØÉÊ5P»WûáùLú!à@áÐ LP
endstream
endobj
-376 0 obj <<
+375 0 obj <<
/Type /Page
-/Contents 377 0 R
-/Resources 375 0 R
+/Contents 376 0 R
+/Resources 374 0 R
/MediaBox [0 0 595.276 841.89]
/Parent 268 0 R
-/Group 369 0 R
-/Annots [ 363 0 R 364 0 R 380 0 R 365 0 R 366 0 R 367 0 R 370 0 R 371 0 R 372 0 R 373 0 R ]
+/Group 368 0 R
+/Annots [ 362 0 R 363 0 R 379 0 R 364 0 R 365 0 R 366 0 R 369 0 R 370 0 R 371 0 R 372 0 R ]
>> endobj
-368 0 obj <<
+367 0 obj <<
/Type /XObject
/Subtype /Image
/Width 382
/Height 25
/BitsPerComponent 8
/ColorSpace /DeviceRGB
-/SMask 389 0 R
+/SMask 388 0 R
/Length 1926
/Filter /FlateDecode
>>
@@ -1708,7 +1700,7 @@
O7ÈT-ø¢yºIü/Û2HÁ¤³Bb!Ù®ÿm#þÔ&à
endstream
endobj
-389 0 obj <<
+388 0 obj <<
/Type /XObject
/Subtype /Image
/Width 382
@@ -1722,17 +1714,17 @@
xÚíÁ à û u Ìí*Þ
endstream
endobj
-369 0 obj
+368 0 obj
<</Type/Group /S/Transparency /CS/DeviceRGB /I true>>
endobj
-374 0 obj <<
+373 0 obj <<
/Type /XObject
/Subtype /Image
/Width 88
/Height 31
/BitsPerComponent 8
/ColorSpace /DeviceRGB
-/SMask 390 0 R
+/SMask 389 0 R
/Length 1454
/Filter /FlateDecode
>>
@@ -1756,117 +1748,110 @@
åï8.õ;ÎÇ}íúµ¿¦µÂJím8xÿçûÁH°ü]¯ÔLr«iÚµt¦øÿ§Ûó5á%[ÚNl
endstream
endobj
-390 0 obj <<
+389 0 obj <<
/Type /XObject
/Subtype /Image
/Width 88
/Height 31
/BitsPerComponent 8
/ColorSpace /DeviceGray
-/Length 1934
+/Length 39
/Filter /FlateDecode
>>
stream
-xÚíViTY}A¤U¢fJ$ÐÂÅ -Y ÓdI$h !DvE¡\XEYNå4-§¡Y"*ÛT¤íù9ÎþÑ3ܪ¯^}·î÷U½{Þy§¶¬ü% +kXÃÖ°5¬a
-kø¿Ü_ô?ùry H #Ê-õÆsi,C¦r©\$Ì_ã HåJ4qõç¸"î¹pÔÒjÝx$Æq%Ü8?w,{îàGáç$"§u ÀÍÐ+ B¾¤¬ÃîgÍ*²Èæ`ûÑÜÊ+Ò ÖIô аVGøxC]ýF[`ú¥° @À è(à8À¹x!Ö#à"ÃLw§xT}£ïO¢2 }} ¬ö-] pü/zaEúÃ<ÅêĤ±Âд ?4Îb1üÃ(ß³zP Å"8Éh,Æ© ´Eûb¡Þ?>[·ê¼;9 öñÃÀáN"d¾\á xs,8ÐS)\_Ø+GTxT1uç|ñßç>ûD"°± srÕ»/£ænb=ËVó} f]îæéÝe¸¤6æ°ÞD?û[çF´Õ|ûÔj;rLmÂ:¿ÖûSùoú+¬ù»yAqýO^X0h×0zè×Lÿï½.Nºýé
ÙÑÑD!ÚÚÝÿÝÉ!ý¯ö¸¡ BV3øÚüYyfß
[TRUNCATED]
To get the complete diff run:
svnlook diff /svnroot/soiltexture -r 36
More information about the Soiltexture-commits
mailing list