[Raster-commits] r366 - in pkg/raster: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Mar 17 08:02:01 CET 2009


Author: rhijmans
Date: 2009-03-17 08:02:01 +0100 (Tue, 17 Mar 2009)
New Revision: 366

Added:
   pkg/raster/R/closeHandle.R
   pkg/raster/R/rasterFromFileGDAL.R
   pkg/raster/R/writeRasterAssign.R
Modified:
   pkg/raster/DESCRIPTION
   pkg/raster/R/aaaClasses.R
   pkg/raster/R/properties.R
   pkg/raster/R/rasterFromFile.R
   pkg/raster/R/readRaster.R
   pkg/raster/R/readSurfer.R
   pkg/raster/R/setBbox.R
   pkg/raster/R/setDatatype.R
   pkg/raster/R/setFilename.R
   pkg/raster/R/setRowCol.R
   pkg/raster/R/writeGDAL.R
   pkg/raster/R/writeRaster.R
   pkg/raster/R/writeRasterRow.R
   pkg/raster/R/writeRasterSparse.R
   pkg/raster/R/xyValues.R
   pkg/raster/man/Summary-methods.Rd
   pkg/raster/man/setDatatype.Rd
   pkg/raster/man/setExtent.Rd
   pkg/raster/man/setNAvalue.Rd
   pkg/raster/man/writeRaster.Rd
   pkg/raster/man/xyValues.Rd
Log:


Modified: pkg/raster/DESCRIPTION
===================================================================
--- pkg/raster/DESCRIPTION	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/DESCRIPTION	2009-03-17 07:02:01 UTC (rev 366)
@@ -1,7 +1,7 @@
 Package: raster
 Type: Package
 Title: Raster data handling for geographic data analysis and modeling
-Version: 0.8.9-6
+Version: 0.8.9-7
 Date: 14-March-2009
 Depends: methods, sp, rgdal (>= 0.5-33), R (>= 2.8.0)
 Author: Robert J. Hijmans & Jacob van Etten

Modified: pkg/raster/R/aaaClasses.R
===================================================================
--- pkg/raster/R/aaaClasses.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/aaaClasses.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -62,8 +62,7 @@
 	representation (
 		name ='character',
 		shortname ='character', # short name
-		driver ='character', #gdal, raster
-		gdalhandle='list',
+#		driver ='character', #gdal, raster
 #		datatype ='character', #'numeric' or 'integer'
 #		datasize ='integer',
 #		datasigned='logical',
@@ -77,8 +76,7 @@
 	prototype (	
 	    name = '',
 		shortname ='',
-		driver = 'raster',
-		gdalhandle= list(),
+#		driver = 'raster',
 #		datatype = 'numeric',
 #		datasize = as.integer(4),
 #		datasigned= TRUE,

Added: pkg/raster/R/closeHandle.R
===================================================================
--- pkg/raster/R/closeHandle.R	                        (rev 0)
+++ pkg/raster/R/closeHandle.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -0,0 +1,20 @@
+# Author: Robert J. Hijmans, r.hijmans at gmail.com
+# International Rice Research Institute
+# Date : June 2008
+# Version 0.8
+# Licence GPL v3
+
+
+closeHandle <- function(raster) {
+#	if handle = gdal then gdalclose the handle
+	if (class(raster) != 'RasterLayer') {
+		stop('closeHandle is only for RasterLayer objects')
+	}
+	if (.driver(raster) == "gdal") {
+		try(closeDataset(raster at file@con), silent = T)
+	} else {
+		cr <- try(close(raster at file@con), silent = T)
+	}
+	attr(raster at file, "con" <- "")
+	return(raster)
+}

Modified: pkg/raster/R/properties.R
===================================================================
--- pkg/raster/R/properties.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/properties.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -67,7 +67,11 @@
 
 
 .driver <- function(object) {
-	return(object at file@driver)
+	if (class(object at file@con)[1] == 'file') {
+		return('raster')
+	} else { #  if (class(object at file@con)[1] == "GDALReadOnlyDataset")
+		return('gdal')
+	}
 }	
 
 .nodatavalue <- function(object) {

Modified: pkg/raster/R/rasterFromFile.R
===================================================================
--- pkg/raster/R/rasterFromFile.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/rasterFromFile.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -5,77 +5,12 @@
 # Licence GPL v3
 
 
-closeHandle <- function(raster) {
-#	if handle = gdal then gdalclose the handle
-	if (.driver(raster) == "gdal") {
-		closeDataset(raster at file@gdalhandle[[1]])
-		raster at file@gdalhandle[[1]]	 <- list()
-	} else {
-		cr <- try(close(raster at filecon), silent = T)
-	}
-	return(raster)
-}
 
 
-.rasterFromGDAL <- function(filename, band) {	
-	gdalinfo <- GDALinfo(filename)
-	nc <- as.integer(gdalinfo[["columns"]])
-	nr <- as.integer(gdalinfo[["rows"]])
-	xn <- gdalinfo[["ll.x"]]
-	if (xn < 0) { ndecs <- 9 } else  { ndecs <- 8 }
-	xn <- as.numeric( substr( as.character(xn), 1, ndecs) )
-
-	xx <- xn + gdalinfo[["res.x"]] * nc
-	if (xx < 0) { ndecs <- 9 } else  { ndecs <- 8 }
-	xx <- as.numeric( substr( as.character(xx), 1, ndecs) )
-		
-#	gdalv <- (packageDescription(pkg = "rgdal")$Version)
-#	dif <- compareVersion(gdalv, "0.5-32")
-#	if (dif < 0) {
-#		yx <- gdalinfo[["ll.y"]]
-#		yn <- yx - gdalinfo[["res.y"]] * nr
-#	} else {
-		yn <- gdalinfo[["ll.y"]]
-		yx <- yn + gdalinfo[["res.y"]] * nr
-#	}
-		
-	if (yn < 0) { ndecs <- 9 } else { ndecs <- 8 }
-	yn <- as.numeric( substr( as.character(yn), 1, ndecs) )
-	if (yx < 0) { ndecs <- 9 } else  { ndecs <- 8 }
-	yx <- as.numeric( substr( as.character(yx), 1, ndecs) )
-
-	raster <- raster(ncols=nc, nrows=nr, xmn=xn, ymn=yn, xmx=xx, ymx=yx, projs="")
-	raster <- setFilename(raster, filename)
-	raster <- setDatatype(raster, "FLT4S")
-	
-
-	raster at file@driver <- 'gdal' 
-		#attr(gdalinfo, "driver")
-
-	raster at file@nbands <- as.integer(gdalinfo[["bands"]])
-	band <- as.integer(band)
-	if (band > nbands(raster) ) {
-		warning("band too high. Set to nbands")
-		band <- nbands(raster) }
-	if ( band < 1) { 
-		warning("band too low. Set to 1")
-		band <- 1 }
-	raster at file@band <- as.integer(band)
-
-	raster <- setProjection(raster, attr(gdalinfo, "projection"))
-	
-	raster at file@gdalhandle[1] <- GDAL.open(filename)
-#oblique.x   0  #oblique.y   0 
-	raster at data@source <- 'disk'
-	return(raster)
-}
-
-
-
 .rasterFromRasterFile <- function(filename, band=1) {
-	if (!file.exists( .setFileExtensionValues(filename)) ){
-		warning("no '.gri' file. Assuming this is a Surfer file")
-		return(.readSurfer6(filename))
+	grifile <- .setFileExtensionValues(filename)
+	if (!file.exists( grifile )){
+		stop("no '.gri' file")
 	}	
 	ini <- readIniFile(filename)
 	ini[,2] = toupper(ini[,2]) 
@@ -115,7 +50,7 @@
 
     raster <- raster(ncols=nc, nrows=nr, xmn=xn, ymn=yn, xmx=xx, ymx=yx, projs=projstring)
 	raster <- setFilename(raster, filename)
-	raster at file@driver <- "raster"
+#	raster at file@driver <- "raster"
 
 	raster at data@min <- minval
 	raster at data@max <- maxval
@@ -133,6 +68,9 @@
 #	raster at data@ncellvals <- as.integer(ncellvals)
 
 	raster at data@source <- 'disk'
+
+	attr(raster at file, "con") <- file(grifile, "rb")
+
     return(raster)
 }
 

Added: pkg/raster/R/rasterFromFileGDAL.R
===================================================================
--- pkg/raster/R/rasterFromFileGDAL.R	                        (rev 0)
+++ pkg/raster/R/rasterFromFileGDAL.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -0,0 +1,61 @@
+# Author: Robert J. Hijmans, r.hijmans at gmail.com
+# International Rice Research Institute
+# Date : June 2008
+# Version 0.8
+# Licence GPL v3
+
+
+.rasterFromGDAL <- function(filename, band) {	
+	gdalinfo <- GDALinfo(filename)
+	nc <- as.integer(gdalinfo[["columns"]])
+	nr <- as.integer(gdalinfo[["rows"]])
+	xn <- gdalinfo[["ll.x"]]
+	if (xn < 0) { ndecs <- 9 } else  { ndecs <- 8 }
+	xn <- as.numeric( substr( as.character(xn), 1, ndecs) )
+
+	xx <- xn + gdalinfo[["res.x"]] * nc
+	if (xx < 0) { ndecs <- 9 } else  { ndecs <- 8 }
+	xx <- as.numeric( substr( as.character(xx), 1, ndecs) )
+		
+#	gdalv <- (packageDescription(pkg = "rgdal")$Version)
+#	dif <- compareVersion(gdalv, "0.5-32")
+#	if (dif < 0) {
+#		yx <- gdalinfo[["ll.y"]]
+#		yn <- yx - gdalinfo[["res.y"]] * nr
+#	} else {
+		yn <- gdalinfo[["ll.y"]]
+		yx <- yn + gdalinfo[["res.y"]] * nr
+#	}
+		
+	if (yn < 0) { ndecs <- 9 } else { ndecs <- 8 }
+	yn <- as.numeric( substr( as.character(yn), 1, ndecs) )
+	if (yx < 0) { ndecs <- 9 } else  { ndecs <- 8 }
+	yx <- as.numeric( substr( as.character(yx), 1, ndecs) )
+
+	raster <- raster(ncols=nc, nrows=nr, xmn=xn, ymn=yn, xmx=xx, ymx=yx, projs="")
+	raster <- setFilename(raster, filename)
+	raster <- setDatatype(raster, "FLT4S")
+	
+
+#	raster at file@driver <- 'gdal' 
+		#attr(gdalinfo, "driver")
+
+	raster at file@nbands <- as.integer(gdalinfo[["bands"]])
+	band <- as.integer(band)
+	if (band > nbands(raster) ) {
+		warning("band too high. Set to nbands")
+		band <- nbands(raster) }
+	if ( band < 1) { 
+		warning("band too low. Set to 1")
+		band <- 1 }
+	raster at file@band <- as.integer(band)
+
+	raster <- setProjection(raster, attr(gdalinfo, "projection"))
+	
+	attr(raster at file, "con") <- GDAL.open(filename)
+	
+#oblique.x   0  #oblique.y   0 
+	raster at data@source <- 'disk'
+	return(raster)
+}
+

Modified: pkg/raster/R/readRaster.R
===================================================================
--- pkg/raster/R/readRaster.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/readRaster.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -24,14 +24,14 @@
 	
 	if (dataSource(raster)=='ram') {
 		result <- valuesRow(raster, rownr)[startcol:endcol]
-	} else 	if (.driver(raster) == 'raster') {
-#		if dataContent(raster=='all')
 		
+	} else if (.driver(raster) == 'raster') {
+		
 		rastergri <- .setFileExtensionValues(filename(raster))
 		if (!file.exists( filename(raster))) { 
 			stop(paste(filename(raster)," does not exist"))
 		}
-		con <- file(rastergri, "rb")
+		#con <- file(rastergri, "rb")
 		
 		dtype <- .shortDataType(raster at file@datanotation)
 		if (dtype == "INT" | dtype == "LOG" ) { 
@@ -43,12 +43,12 @@
 		dsign <- dataSigned(raster at file@datanotation)
 		
 		if (rownr > 0) {
-			seek(con, ((rownr-1) * ncol(raster) + (startcol-1)) * dsize)
-			result <- readBin(con, what=dtype, n=ncolumns, dsize, dsign, endian=raster at file@byteorder) }	
+			seek(raster at file@con, ((rownr-1) * ncol(raster) + (startcol-1)) * dsize)
+			result <- readBin(raster at file@con, what=dtype, n=ncolumns, dsize, dsign, endian=raster at file@byteorder) }	
 		else {	
-			result <- readBin(con, what=dtype, n=ncell(raster), dsize, dsign, endian=raster at file@byteorder) 
+			result <- readBin(raster at file@con, what=dtype, n=ncell(raster), dsize, dsign, endian=raster at file@byteorder) 
 		}
-		close(con)
+#		close(con)
 #		result[is.nan(result)] <- NA
 		if (dtype == 'numeric') {
 			result[result <=  (0.999 * .nodatavalue(raster)) ] <- NA 	
@@ -64,24 +64,22 @@
 		else {
 			if (rownr <= 0) {
 				offs <- c(0, 0) 
-				reg <- c(nrow(raster), ncol(raster)) #	reg <- dim(raster at file@gdalhandle[[1]])
+				reg <- c(nrow(raster), ncol(raster)) 
 			}
 			else {
 				offs= c((rownr-1), (startcol-1)) 
 				reg <- c(1, ncolumns)
 			}
 		}
-		result <- getRasterData(raster at file@gdalhandle[[1]], offset=offs, region.dim=reg, band = raster at file@band)
+		result <- getRasterData(raster at file@con, offset=offs, region.dim=reg, band = raster at file@band)
 		
-#		if (!is.vector(result)) {  result <- as.vector(result) 	}
-		
+	
 		# if  setNAvalue() has been used.....
 		if (raster at file@nodatavalue < 0) {
 			result[result <= raster at file@nodatavalue ] <- NA 			
 		} else {
 			result[result == raster at file@nodatavalue ] <- NA 					
-		}
-	
+		}	
 	} 
 	
 	raster at data@values <- as.vector(result)

Modified: pkg/raster/R/readSurfer.R
===================================================================
--- pkg/raster/R/readSurfer.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/readSurfer.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -1,5 +1,5 @@
 
-.readSurfer6 <- function(filename) {
+..readSurfer6 <- function(filename) {
 	con <- file(filename, "rb")
 	id <- readBin(con, "characater", n=1, size=4)
 	r <- raster()
@@ -18,7 +18,7 @@
 	m <- m[nrow(m):1, ] 
 	r at data@values <- as.vector(t(m))
 	r at data@source <- 'disk'
-	r at file@driver <- "surfer"
+#	r at file@driver <- "surfer"
 	return(r)
 }
 

Modified: pkg/raster/R/setBbox.R
===================================================================
--- pkg/raster/R/setBbox.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/setBbox.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -32,11 +32,16 @@
 		newobj at bbox@ymax <- newobj at bbox@ymin + nrow(newobj) * yrs
 		
 		if (dataContent(x) == 'all') {
-			indices <- cellsFromBbox(x, bb, expand=TRUE)
-			v <- vector(length=length(indices))
-			v[] <- NA
-			v[!is.na(indices)] <- values(x)[!is.na(indices)]
-			newobj <- setValues(newobj, v)
+			if (ncol(x) == ncol(newobj) & nrow(x) == nrow(newobj)) {
+				newobj <- setValues(newobj, values(x))
+			} else {
+				newobj at data@source <- 'ram'
+				indices <- cellsFromBbox(x, bb, expand=TRUE)
+				v <- vector(length=length(indices))
+				v[] <- NA
+				v[!is.na(indices)] <- values(x)[!is.na(indices)]
+				newobj <- setValues(newobj, v)
+			}
 		}
 		
 	} else if (class(x) != "BasicRaster") {

Modified: pkg/raster/R/setDatatype.R
===================================================================
--- pkg/raster/R/setDatatype.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/setDatatype.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -4,9 +4,9 @@
 # Version 0.8
 # Licence GPL v3
 
-setDatatype <- function(raster, datatype) {
+setDatatype <- function(x, value) {
 # for backward compatibility issues and non fatal mistakes.
-	datatype <- substr( toupper( trim(datatype) ), 1, 5)
+	datatype <- substr( toupper( trim(value) ), 1, 5)
 	if (datatype=='LOGIC') {datatype <- 'LOG1S'}
 	if (datatype == 'INTEG') {datatype <- 'INT4S'}
 	if (datatype == 'NUMER') {datatype <- 'FLT4S'}
@@ -41,66 +41,66 @@
 	signed <- substr(datatype,1,3) != 'U'
 	
 	if (type == "FLT") {
-		if (dataContent(raster) != 'nodata') { 
-			raster at data@values <- as.numeric(values(raster))
+		if (dataContent(x) != 'nodata') { 
+			x at data@values <- as.numeric(values(x))
 		}
 		if (size == '4') {
-			raster at file@datanotation <- 'FLT4S'
-			raster at file@nodatavalue <- -3.4E38
+			x at file@datanotation <- 'FLT4S'
+			x at file@nodatavalue <- -3.4E38
 		} else if (size == '8') {
-			raster at file@datanotation <- 'FLT8S'
-			raster at file@nodatavalue <-  -1.7E308
+			x at file@datanotation <- 'FLT8S'
+			x at file@nodatavalue <-  -1.7E308
 		} else { 
 			stop("invalid datasize for a FLT (should be 4 or 8)") 
 		}
 	} else if (type == "INT") {
-		raster at data@min <- round(minValue(raster))
-		raster at data@max <- round(maxValue(raster))
-		if (dataContent(raster) != 'nodata') { 
-			raster at data@values <- as.integer(round(values(raster)))
+		x at data@min <- round(minValue(x))
+		x at data@max <- round(maxValue(x))
+		if (dataContent(x) != 'nodata') { 
+			x at data@values <- as.integer(round(values(x)))
 		}
 		if (size == '4') {
 			if (signed) {
-				raster at file@datanotation <- 'INT4S'
-				raster at file@nodatavalue <- -2147483647
+				x at file@datanotation <- 'INT4S'
+				x at file@nodatavalue <- -2147483647
 			} else {
-				raster at file@datanotation <- 'INT4U'
-				raster at file@nodatavalue <- 4294967295
+				x at file@datanotation <- 'INT4U'
+				x at file@nodatavalue <- 4294967295
 			}
 		} else if (size == '2') {
 			if (signed) {
-				raster at file@datanotation <- 'INT2S'
-				raster at file@nodatavalue <- -32768
+				x at file@datanotation <- 'INT2S'
+				x at file@nodatavalue <- -32768
 			} else {
-				raster at file@datanotation <- 'INT2U'
-				raster at file@nodatavalue <- 65535
+				x at file@datanotation <- 'INT2U'
+				x at file@nodatavalue <- 65535
 			}
 		} else if (size == '1') {
 			# there is no nodata value for byte
-			raster at file@nodatavalue <- -9999
+			x at file@nodatavalue <- -9999
 			if (signed) {
-				raster at file@datanotation <- 'INT1S'
+				x at file@datanotation <- 'INT1S'
 			} else {
-				raster at file@datanotation <- 'INT1U'
+				x at file@datanotation <- 'INT1U'
 			}
 			warning("binary files of a single byte do not have NA values on disk")
 		} else if (size == '8') {
 			if (signed) {
-				raster at file@nodatavalue <- -9223372036854775808
-				raster at file@datanotation <- 'INT8S'							
+				x at file@nodatavalue <- -9223372036854775808
+				x at file@datanotation <- 'INT8S'							
 			} else {
-				raster at file@nodatavalue <- 18446744073709551615
-				raster at file@datanotation <- 'INT8U'			
+				x at file@nodatavalue <- 18446744073709551615
+				x at file@datanotation <- 'INT8U'			
 			}
 		} else {
 			stop("invalid datasize for this datatype") 
 		}
 	} else if ( type == 'LOG' ) {
-		raster at file@nodatavalue <- -127
-		raster at file@datanotation <- 'LOG1S'
+		x at file@nodatavalue <- -127
+		x at file@datanotation <- 'LOG1S'
 	} else {
 		stop("unknown datatype")
 	} 
-	return(raster)
+	return(x)
 }
 

Modified: pkg/raster/R/setFilename.R
===================================================================
--- pkg/raster/R/setFilename.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/setFilename.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -7,9 +7,10 @@
 
 
 setFilename <- function(x, value) {
-	filename <- value
-	if (is.na(filename)) {filename <- ""}
-	filename <- trim(filename)
+	filename <- trim(value)
+	if (is.na(filename) || is.null(filename)) {
+		filename <- ""
+	}
 	if (class(x)=='RasterStack') {
 		x at filename <- setFileExtension(filename, ".stk")
 	} else {
@@ -19,9 +20,10 @@
 		shortname <- shortFileName(filename)
 		shortname <- setFileExtension(shortname, "")
 		shortname <- gsub(" ", "_", shortname)
-		if (nbands(x) > 1) { shortname <- paste(shortname, "_", band(x)) } 
+		if (nbands(x) > 1) { 
+			shortname <- paste(shortname, "_", band(x)) 
+		} 
 		x at file@shortname <- shortname
-		x at file@gdalhandle <- list()
 	}	
 	return(x)	
 }

Modified: pkg/raster/R/setRowCol.R
===================================================================
--- pkg/raster/R/setRowCol.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/setRowCol.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -4,10 +4,12 @@
 # Version 0.8
 # Licence GPL v3
 
+
+
 setRowCol <- function(object, nrows=nrow(object), ncols=ncol(object)) {
-# to do: also remove file connection ! 	
 	if (extends(class(object), "Raster")) {
 		object <- clearValues(object)
+		#object at data@source <- 'ram'
 	}
 	object at ncols <- as.integer(ncols)
 	object at nrows <- as.integer(nrows)
@@ -17,6 +19,7 @@
 setRes <- function(object, xres, yres=xres) {
 	if (extends(class(object), "Raster")) {
 		object <- clearValues(object)
+		#object at data@source <- 'ram'
 	}
 	bb <- getBbox(object)
 	nc <- round( (bb at xmax - bb at xmin) / xres )

Modified: pkg/raster/R/writeGDAL.R
===================================================================
--- pkg/raster/R/writeGDAL.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/writeGDAL.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -94,8 +94,7 @@
 		transient <- .getGDALtransient(raster, gdalfiletype, overwrite, mvFlag, options)
 		attr(raster at file, "transient") <- transient
 		
-		raster at file@driver <- 'gdal'
-		raster at file@gdalhandle <- list()
+#		raster at file@driver <- 'gdal'
 		raster at data@source <- 'disk'		
 	}	
     for (band in 1:nlayers(raster)) {
@@ -139,8 +138,8 @@
 	.writeStx(raster) 
 
 	tempras <- raster(filename(raster) )
-	raster at file@driver <- 'gdal'
-	raster at file@gdalhandle <- tempras at file@gdalhandle
+#	raster at file@driver <- 'gdal'
+	attr(raster at file, "con") <- tempras at file@con
 	raster at data@source <- 'disk'
 	return(raster)
 }

Modified: pkg/raster/R/writeRaster.R
===================================================================
--- pkg/raster/R/writeRaster.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/writeRaster.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -17,17 +17,17 @@
  
 
 .writeRasterAll <- function(raster, overwrite=FALSE) {
-	filename(raster) <- trim(filename(raster))
-	if (filename(raster) == "") {
+	filename <- trim(raster at file@name)
+	if (filename == "") {
 		stop('first provide a filename. E.g.: raster <- setFilename(raster, "c:/myfile")')
 	}
-	raster <- setFilename(raster, .setFileExtensionHeader(filename(raster)))
+	filename <- .setFileExtensionHeader(filename)
+	raster <- setFilename(raster, filename)
 
-	if (!overwrite & file.exists(filename(raster))) {
-		stop(paste(filename(raster),"exists.","use 'overwrite=TRUE' if you want to overwrite it")) 
+	if (!overwrite & file.exists(filename)) {
+		stop(paste(filename, "exists. Use 'overwrite=TRUE' if you want to overwrite it")) 
 	}
-	raster at file@driver <- 'raster'
-	raster at file@gdalhandle <- list()
+#	raster at file@driver <- 'raster'
 	raster at data@values[is.nan(raster at data@values)] <- NA
 	raster at data@values[is.infinite(raster at data@values)] <- NA
 	raster <- setMinMax(raster)
@@ -62,14 +62,14 @@
 		}	
 	}
 
+	attr(raster at file, "con") <- file(filename, "wb")
+	
 	if (raster at data@content == 'sparse') { 
 		raster <- .writeSparse(raster, overwrite=overwrite) 
 	} else {
 		binraster <- .setFileExtensionValues(filename(raster))
-		con <- file(binraster, "wb")
 		dsize <- dataSize(raster at file@datanotation)
-		writeBin( values(raster), con, size = dsize ) 
-		close(con)
+		writeBin( values(raster), raster at file@con, size = dsize ) 
 		.writeRasterHdr(raster) 
 	}	
 	

Added: pkg/raster/R/writeRasterAssign.R
===================================================================
--- pkg/raster/R/writeRasterAssign.R	                        (rev 0)
+++ pkg/raster/R/writeRasterAssign.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -0,0 +1,7 @@
+
+.writeRasterAssign <- function(raster, filetype='raster', overwrite=FALSE) {
+	name <- deparse(substitute(raster))
+	raster <- writeRaster(raster, filetype=filetype, overwrite=overwrite)
+	assign(name, raster, envir=parent.frame())
+	return(invisible())
+}

Modified: pkg/raster/R/writeRasterRow.R
===================================================================
--- pkg/raster/R/writeRasterRow.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/writeRasterRow.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -26,8 +26,7 @@
 	raster at data@min <- Inf
 	raster at data@max <- -Inf
 	raster at data@haveminmax <- FALSE
-	raster at file@driver <- 'raster'
-	raster at file@gdalhandle <- list()
+#	raster at file@driver <- 'raster'
 	return(raster)
 }
 

Modified: pkg/raster/R/writeRasterSparse.R
===================================================================
--- pkg/raster/R/writeRasterSparse.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/writeRasterSparse.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -6,8 +6,7 @@
 
 .writeSparse <- function(raster, overwrite=FALSE) {
 
-	raster at file@driver <- 'raster'
-    raster at file@gdalhandle <- list()
+#	raster at file@driver <- 'raster'
 	raster <- setFilename(raster, .setFileExtensionHeader(filename(raster)))
 	if (!overwrite & file.exists(filename(raster))) {
 		stop(paste(filename(raster), "exists. Use 'overwrite=TRUE' if you want to overwrite it")) 
@@ -25,10 +24,8 @@
 	raster <- setMinMax(raster)
 
 	binraster <- .setFileExtensionValues(filename(raster))
-	con <- file(binraster, "wb")
-	writeBin( as.vector(dataIndices(raster)), con, size = as.integer(4)) 
-	writeBin( as.vector(values(raster)), con, size = dataSize(raster at file@datanotation) ) 
-	close(con)
+	writeBin( as.vector(dataIndices(raster)), raster at file@con, size = as.integer(4)) 
+	writeBin( as.vector(values(raster)), raster at file@con, size = dataSize(raster at file@datanotation) ) 
 
 	# add the 'sparse' key word to the hdr file!!!
 	.writeRasterHdr(raster) 

Modified: pkg/raster/R/xyValues.R
===================================================================
--- pkg/raster/R/xyValues.R	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/R/xyValues.R	2009-03-17 07:02:01 UTC (rev 366)
@@ -6,6 +6,7 @@
 # Licence GPL v3
 
 
+
 if (!isGeneric("xyValues")) {
 	setGeneric("xyValues", function(object, xyCoords, ...)
 		standardGeneric("xyValues"))
@@ -14,21 +15,27 @@
 
 setMethod("xyValues", signature(object='Raster', xyCoords='SpatialPoints'), 
 	function(object, xyCoords, method='simple') { 
-		xyCoords <- coordinates(xyCoords)
-		callNextMethod(object, xyCoords, method=method)
+		callGeneric(object, coordinates(xyCoords), method=method)
 	}	
 )
 
 
+setMethod("xyValues", signature(object='Raster', xyCoords='data.frame'), 
+	function(object, xyCoords, method='simple') { 
+		callGeneric(object, as.matrix(xyCoords), method=method)
+	}	
+)
+
+
 setMethod("xyValues", signature(object='Raster', xyCoords='vector'), 
 	function(object, xyCoords, method='simple') { 
 		if (length(xyCoords) != 2) {
 			stop('xyCoords should be a two column matrix or a vector of length 2')
 		}
-		xyCoords <- matrix(xyCoords, ncol=2)
-		callNextMethod(object, xyCoords, method=method)
+		callGeneric(object, matrix(xyCoords, ncol=2), method=method)
 	}
 )
+
 	
 setMethod("xyValues", signature(object='RasterLayer', xyCoords='matrix'), 
 	function(object, xyCoords, method='simple') { 

Modified: pkg/raster/man/Summary-methods.Rd
===================================================================
--- pkg/raster/man/Summary-methods.Rd	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/man/Summary-methods.Rd	2009-03-17 07:02:01 UTC (rev 366)
@@ -18,7 +18,7 @@
 
 
 \note{
- All methods take code{na.rm} as an additional logical argument. Default is \code{FALSE}. 
+ All methods take \code{na.rm} as an additional logical argument. Default is \code{FALSE}. 
  If \code{TRUE}, NA values are removed from calculations
  These methods compare layers and the result of these methods is always a single RasterLayer. 
  
@@ -26,7 +26,8 @@
  However, because generic functions are used, the appropriate method is chosen based on the first argument: '\code{x}'. 
  This means that if \code{r} is a RasterLayer object, \code{mean(r, 5)} will work, but \code{mean(5, r)} will not work.
  
- The generic function \code{range} returns 2 values (the minimum and maximum value of a vector). The Raster* implementations returns a single values (the range)
+ The generic function \code{range} returns 2 values (the minimum and maximum value of a vector). The Raster* implementations returns
+ a single values (the range)
  
  For the extreme values within in a layer use \code{maxValue} and \code{minValue}
 }

Modified: pkg/raster/man/setDatatype.Rd
===================================================================
--- pkg/raster/man/setDatatype.Rd	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/man/setDatatype.Rd	2009-03-17 07:02:01 UTC (rev 366)
@@ -11,13 +11,11 @@
 }
 
 \usage{
-setDatatype(raster, datatype)
+setDatatype(x, value)
 dataType(x) <- value
 }
 
 \arguments{
-  \item{raster}{ A \code{RasterLayer} object }
-  \item{datatype}{ the type of data for writing values to disk. See below }
   \item{x}{ A \code{RasterLayer} object }
   \item{value}{ the type of data for writing values to disk. See below }
 }

Modified: pkg/raster/man/setExtent.Rd
===================================================================
--- pkg/raster/man/setExtent.Rd	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/man/setExtent.Rd	2009-03-17 07:02:01 UTC (rev 366)
@@ -9,22 +9,35 @@
 \title{Set the extent of a RasteLayer}
 
 \description{
-
-setExtent sets the extent (bounding box) of a RasterLayer
+setExtent sets the extent of a Raster* object. Either by providing a new BoundingBox object or by setting the extreme
+coordinates one by one.
 }
 
 \usage{
 setExtent(x, bndbox, keepres=FALSE, snap=FALSE)
+xmin(x) <- value
+xmax(x) <- value
+ymin(x) <- value
+ymax(x) <- value
 }
 
 \arguments{
   \item{x}{A Raster* object}
   \item{bndbox}{An object of class BoundingBox (which you can create with newBbox() )}  
-  \item{keepres}{logical. If \code{TRUE}, the resolution of the cells will stay the same after adjusting the bounding box (by adjusting the number of rows and columns). if \code{FALSE}, the number of rows and columns will stay the same, and the resolution will be adjusted}
-  \item{snap}{logical. If \code{TRUE}, the object's BoundingBox is adjusted so that the cells of the output RasterLayer are aligned with those of the input RasterLayer }
-  
+  \item{keepres}{logical. If \code{TRUE}, the resolution of the cells will stay the same after adjusting the bounding box (see Details)}
+  \item{snap}{logical. If \code{TRUE}, the extent is adjusted so that the cells of the input and output RasterLayer are aligned}
+  \item{value}{an extreme x or y coordinate}  
 }
- 
+
+\details{
+
+If keepres is \code{FALSE}, 
+(by adjusting the number of rows and columns). if \code{FALSE}, the number of rows and columns will stay the same, and the resolution will be adjusted
+
+(the RasterLayers get the same origin)
+
+}
+
 \value{
 a Raster* object
 }

Modified: pkg/raster/man/setNAvalue.Rd
===================================================================
--- pkg/raster/man/setNAvalue.Rd	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/man/setNAvalue.Rd	2009-03-17 07:02:01 UTC (rev 366)
@@ -7,6 +7,8 @@
 \description{
 If you set the NA value of a RasterLayer, this value will be interpreted as NA when reading the values from a file. 
 Values already in memory will not be affected. 
+
+If the NA value is smaller than zero, all values smaller or equal to that number will be set to NA.
 }
 
 \usage{
@@ -14,8 +16,8 @@
 }
 
 \arguments{
-  \item{raster}{ A \code{RasterLayer} object }
-  \item{value}{the value to be interpreted as NA; set this before reading the values from the file. Integer values are matched exactely; for decimal values files any value <= the value will be interpreted as NA}  
+ \item{raster}{A \code{RasterLayer} object}
+ \item{value}{the value to be interpreted as NA; set this before reading the values from the file. Integer values are matched exactely; for decimal values files any value <= the value will be interpreted as NA}  
 }
 
 

Modified: pkg/raster/man/writeRaster.Rd
===================================================================
--- pkg/raster/man/writeRaster.Rd	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/man/writeRaster.Rd	2009-03-17 07:02:01 UTC (rev 366)
@@ -50,7 +50,7 @@
 \examples{ 
 rs <- raster(system.file("external/test.ag", package="sp"))
  
-#read all data
+# read all data
 rs <- readAll(rs)
 
 # write all to a new binary file
@@ -62,9 +62,9 @@
 rs <- writeRaster(rs, filetype="HFA", overwrite=TRUE)
 
  
-# write all to integer binary file
+# write all to an integer binary file
 filename(rs) <- "binallint.grd"
-rs <- setDatatype(rs, "INT4S")
+dataType(rs) <- "INT4S"
 rs <- writeRaster(rs, overwrite=TRUE)
  
 # write all to ascii file
@@ -90,7 +90,7 @@
 }
 
 # read and write row by row; write to GeoTiff binary file
-binras <- raster(rs, "binbyrow")
+binras <- raster(rs, "binbyrow2")
 for (r in 1:nrow(rs)) {
 	rs <- readRow(rs, r)
 	binras <- setValues(binras, values(rs), r)

Modified: pkg/raster/man/xyValues.Rd
===================================================================
--- pkg/raster/man/xyValues.Rd	2009-03-17 02:50:02 UTC (rev 365)
+++ pkg/raster/man/xyValues.Rd	2009-03-17 07:02:01 UTC (rev 366)
@@ -4,6 +4,7 @@
 \alias{xyValues}
 \alias{xyValues,Raster,vector-method}
 \alias{xyValues,Raster,SpatialPoints-method}
+\alias{xyValues,Raster,data.frame-method}
 \alias{xyValues,RasterLayer,matrix-method}
 \alias{xyValues,RasterStack,matrix-method}
 
@@ -12,7 +13,11 @@
 \title{ values at xy coordinates }
 
 \description{
- These methods return values of a RasterLayer or RasterStack for the cells that correspond to the provided xy coordinates (n*2 matrix or SpatialPoints object)
+ These methods return the values of a RasterLayer or RasterStack for a set of xy coordinates (points).
+ The xy coordinates can be passed as a vector of length 2; a n*2 matrix or data.frame; or a SpatialPoints object.
+ 
+ Values can be extracted using bilnear interpolation of values of the four cells nearest to a point.
+ 
 }
 
 \usage{
@@ -23,7 +28,6 @@
 \item{object}{RasterLayer or RasterStack object}
 \item{xyCoords}{xy coordinates (see below, under Methods}
 \item{...}{additional arguments. See below}
-
 }
 
 \section{Methods}{
@@ -33,13 +37,12 @@
 
 if \code{raster} is a \code{RasterLayer} object, the additional argument \code{method='bilinear'} can be used. In the case, the returned values
 are interpolated from the (centers of the) four nearest raster cells.
-
 }
 }
 
 
 \value{
-a vector of cell values for a RasterLayer or or a matrix of values for a RasterStack
+a vector (object is a RasterLayer) or a matrix (object is a RasterStack)
 }
 
 \seealso{ \code{\link[raster]{cellValues}}, \code{\link[raster]{readRow}}, \code{\link[raster]{readAll}}, \code{\link[sp]{SpatialPoints}}  }



More information about the Raster-commits mailing list