Project

General

Profile

« Previous | Next » 

Revision 20a4e4bb

Added by Benoit Parmentier over 12 years ago

OR, Kriging using automated fitting of variograms TASK#364

View differences:

climate/research/oregon/interpolation/kriging_reg.R
1
####################GWR of Tmax for one Date#####################
2
#This script generates predicted values from station values for the Oregon case study. This program loads the station data from a shp file 
3
#and performs Kriging and co-kriging on tmax regression.
4
#Script created by Benoit Parmentier on April 17, 2012. 
5

  
6
###Loading r library and packages
7
library(sp)
8
library(spdep)
9
library(rgdal)
1
##################    Interpolation of Tmax Using Kriging  #######################################
2
########################### Kriging and Cokriging   ###############################################
3
#This script interpolates station values for the Oregon case study using Kriging and Cokring.    #
4
#The script uses LST monthly averages as input variables and  loads the station data             # 
5
#from a shape file with projection information.                                                  #
6
#Note that this program:                                                                         #
7
#1)assumes that the shape file is in the current working.                                        # 
8
#2)relevant variables were extracted from raster images before performing the regressions        #
9
#  and stored shapefile                                                                          #
10
#This scripts predicts tmax using autokrige, gstat and LST derived from MOD11A1.                 #
11
#also included and assessed using the RMSE,MAE,ME and R2 from validation dataset.                #
12
#TThe dates must be provided as a textfile.                                                      #
13
#AUTHOR: Benoit Parmentier                                                                       #
14
#DATE: 07/07/2012                                                                                #
15
#PROJECT: NCEAS INPLANT: Environment and Organisms --TASK#364--                                  #
16
##################################################################################################
17

  
18
###Loading R library and packages                                                      
19
#library(gtools)                                         # loading some useful tools 
20
library(mgcv)                                           # GAM package by Wood 2006 (version 2012)
21
library(sp)                                             # Spatial pacakge with class definition by Bivand et al. 2008
22
library(spdep)                                          # Spatial pacakge with methods and spatial stat. by Bivand et al. 2012
23
library(rgdal)                                          # GDAL wrapper for R, spatial utilities (Keitt et al. 2012)
24
library(gstat)                                          # Kriging and co-kriging by Pebesma et al. 2004
25
library(automap)                                        # Automated Kriging based on gstat module by Hiemstra et al. 2008
10 26
library(spgwr)
11 27
library(gpclib)
12 28
library(maptools)
13
library(gstat)
14 29
library(graphics)
30

  
15 31
###Parameters and arguments
16 32

  
17
path<- "/data/computer/parmentier/Data/IPLANT_project/data_Oregon_stations/"         #Path to all datasets
18
setwd(path)
19
infile1<-"ghcn_or_tmax_b_04142012_OR83M.shp" #Weather station location in Oregon with input variables
20
infile2<-"dates_interpolation_03052012.txt"  # list of 10 dates for the regression, more thatn 10 dates may be used
21
infile3<-"mean_day244_rescaled.rst"          #This image serves as the reference grid for kriging
22
infile4<- "orcnty24_OR83M.shp"               #Vector file defining the study area: Oregon state and its counties.
23
prop<-0.3                                    #Propotion of weather stations retained for validation/testing
24
out_prefix<-"_LST_04172012_RMSE"                 #output name used in the text file result
33
infile1<- "ghcn_or_tmax_covariates_06262012_OR83M.shp"             #GHCN shapefile containing variables for modeling 2010                 
34
infile2<-"list_10_dates_04212012.txt"                     #List of 10 dates for the regression
35
#infile2<-"list_365_dates_04212012.txt"
36
infile3<-"LST_dates_var_names.txt"                        #LST dates name
37
infile4<-"models_interpolation_05142012.txt"              #Interpolation model names
38
infile5<-"mean_day244_rescaled.rst"
39

  
40
# infile1<- "ghcn_or_tmax_b_04142012_OR83M.shp"             #GHCN shapefile containing variables                  
41
# infile2<-"list_10_dates_04212012.txt"                      #List of 10 dates for the regression
42
# #infile2<-"list_365_dates_04212012.txt"
43
# infile3<-"mean_day244_rescaled.rst"          #This image serves as the reference grid for kriging
44
# infile4<- "orcnty24_OR83M.shp"               #Vector file defining the study area: Oregon state and its counties.
45

  
46
path<-"/data/computer/parmentier/Data/IPLANT_project/data_Oregon_stations_07152012"         #Jupiter LOCATION on EOS
47
#path<-"/home/parmentier/Data/IPLANT_project/data_Oregon_stations"                 #Jupiter LOCATION on EOS/Atlas
48
#path<-"H:/Data/IPLANT_project/data_Oregon_stations"                                 #Jupiter Location on XANDERS
49
setwd(path) 
50
prop<-0.3                                                                       #Proportion of testing retained for validation   
51
seed_number<- 100                                                               #Seed number for random sampling
52
models<-5                                                                       #Number of kriging model
53
out_prefix<-"_07132012_auto_krig_"                                              #User defined output prefix
25 54

  
26 55
###STEP 1 DATA PREPARATION AND PROCESSING#####
27 56

  
57
###Reading the station data and setting up for models' comparison
58
filename<-sub(".shp","",infile1)             #Removing the extension from file.
59
ghcn<-readOGR(".", filename)                 #reading shapefile 
60

  
61
CRS<-proj4string(ghcn)                       #Storing projection information (ellipsoid, datum,etc.)
62

  
63
mean_LST<- readGDAL(infile5)                 #Reading the whole raster in memory. This provides a grid for kriging
64
proj4string(mean_LST)<-CRS                   #Assigning coordinate information to prediction grid.
65

  
66
ghcn = transform(ghcn,Northness = cos(ASPECT*pi/180)) #Adding a variable to the dataframe
67
ghcn = transform(ghcn,Eastness = sin(ASPECT*pi/180))  #adding variable to the dataframe.
68
ghcn = transform(ghcn,Northness_w = sin(slope*pi/180)*cos(ASPECT*pi/180)) #Adding a variable to the dataframe
69
ghcn = transform(ghcn,Eastness_w = sin(slope*pi/180)*sin(ASPECT*pi/180))  #adding variable to the dataframe.
70

  
71
#Remove NA for LC and CANHEIGHT
72
ghcn$LC1[is.na(ghcn$LC1)]<-0
73
ghcn$LC3[is.na(ghcn$LC3)]<-0
74
ghcn$CANHEIGHT[is.na(ghcn$CANHEIGHT)]<-0
75

  
76
set.seed(seed_number)                        #Using a seed number allow results based on random number to be compared...
77

  
78
dates <-readLines(paste(path,"/",infile2, sep=""))
79
LST_dates <-readLines(paste(path,"/",infile3, sep=""))
80
models <-readLines(paste(path,"/",infile4, sep=""))
81
#Model assessment: specific diagnostic/metrics for GAM
82
results_AIC<- matrix(1,length(dates),models+3)  
83
results_GCV<- matrix(1,length(dates),models+3)
84

  
85
#Model assessment: general diagnostic/metrics 
86
results_RMSE <- matrix(1,length(dates),models+3)
87
results_MAE <- matrix(1,length(dates),models+3)
88
results_ME <- matrix(1,length(dates),models+3)
89
results_R2 <- matrix(1,length(dates),models+3)       #Coef. of determination for the validation dataset
90
results_RMSE_f<- matrix(1,length(dates),models+3)
91

  
28 92
###Reading the shapefile and raster image from the local directory
29 93

  
30 94
mean_LST<- readGDAL(infile3)                  #This reads the whole raster in memory and provide a grid for kriging in a SpatialGridDataFrame object
......
33 97
CRS_ghcn<-proj4string(ghcn)                   #This retrieves the coordinate system information for the SDF object (PROJ4 format)
34 98
proj4string(mean_LST)<-CRS_ghcn               #Assigning coordinates information to SpatialGridDataFrame object
35 99

  
36
# Creating state outline from county
37

  
38
orcnty<-readOGR(".", "orcnty24_OR83M")
39
proj4string(orcnty)                           #This retrieves the coordinate system for the SDF
40
lps <-getSpPPolygonsLabptSlots(orcnty)        #Getting centroids county labels
41
IDOneBin <- cut(lps[,1], range(lps[,1]), include.lowest=TRUE)  #Creating one bin var
42
gpclibPermit()                                #Set the gpclib to True to allow union
43
OR_state <- unionSpatialPolygons(orcnty ,IDOneBin) #Dissolve based on bin var
44

  
45 100
# Adding variables for the regressions
46 101

  
47
ghcn$Northness<- cos(ghcn$ASPECT)             #Adding a variable to the dataframe by calculating the cosine of Aspect
48
ghcn$Eastness <- sin(ghcn$ASPECT)             #Adding variable to the dataframe.
49
ghcn$Northness_w <- sin(ghcn$slope)*cos(ghcn$ASPECT)  #Adding a variable to the dataframe
50
ghcn$Eastness_w  <- sin(ghcn$slope)*sin(ghcn$ASPECT)  #Adding variable to the dataframe.
102
ghcn$Northness<- cos(ghcn$ASPECT*pi/180)             #Adding a variable to the dataframe by calculating the cosine of Aspect
103
ghcn$Eastness <- sin(ghcn$ASPECT*pi/180)             #Adding variable to the dataframe.
104
ghcn$Northness_w <- sin(ghcn$slope*pi/180)*cos(ghcn$ASPECT*pi/180)  #Adding a variable to the dataframe
105
ghcn$Eastness_w  <- sin(ghcn$slope*pi/180)*sin(ghcn$ASPECT*pi/180)  #Adding variable to the dataframe.
51 106

  
52
set.seed(100)                                 #This set a seed number for the random sampling to make results reproducible.
107
set.seed(seed_number)                                 #This set a seed number for the random sampling to make results reproducible.
53 108

  
54 109
dates <-readLines(paste(path,"/",infile2, sep=""))  #Reading dates in a list from the textile.
55
results <- matrix(1,length(dates),4)            #This is a matrix containing the diagnostic measures from the GAM models.
56
results_mod_n<-matrix(1,length(dates),3)
110

  
57 111

  
58 112
#Screening for bad values and setting the valid range
59 113

  
......
84 138
  
85 139
  #Kriging tmax
86 140
  
87
  hscat(tmax~1,data_s,(0:9)*20000)                       # 9 lag classes with 20,000m width
88
  v<-variogram(tmax~1, data_s)                           # This plots a sample varigram for date 10 fir the testing dataset
89
  plot(v)
90
  v.fit<-fit.variogram(v,vgm(2000,"Sph", 150000,1000))   #Model variogram: sill is 2000, spherical, range 15000 and nugget 1000
91
  plot(v, v.fit)                                         #Compare model and sample variogram via a graphical plot
92
  tmax_krige<-krige(tmax~1, data_s,mean_LST, v.fit)      #mean_LST provides the data grid/raster image for the kriging locations to be predicted.
93
  
94
  #Cokriging tmax
95
  g<-gstat(NULL,"tmax", tmax~1, data_s)                   #This creates a gstat object "g" that acts as container for kriging specifications.
96
  g<-gstat(g, "SRTM_elev",ELEV_SRTM~1,data_s)            #Adding variables to gstat object g
97
  g<-gstat(g, "LST", LST~1,data_s)
141
#   hscat(tmax~1,data_s,(0:9)*20000)                       # 9 lag classes with 20,000m width
142
#   v<-variogram(tmax~1, data_s)                           # This plots a sample varigram for date 10 fir the testing dataset
143
#   plot(v)
144
#   v.fit<-fit.variogram(v,vgm(2000,"Sph", 150000,1000))   #Model variogram: sill is 2000, spherical, range 15000 and nugget 1000
145
#   plot(v, v.fit)                                         #Compare model and sample variogram via a graphical plot
146
#   tmax_krige<-krige(tmax~1, data_s,mean_LST, v.fit)      #mean_LST provides the data grid/raster image for the kriging locations to be predicted.
98 147
  
99
  vm_g<-variogram(g)                                     #Visualizing multivariate sample variogram.
100
  vm_g.fit<-fit.lmc(vm_g,g,vgm(2000,"Sph", 100000,1000)) #Fitting variogram for all variables at once.
101
  plot(vm_g,vm_g.fit)                                    #Visualizing variogram fit and sample
102
  vm_g.fit$set <-list(nocheck=1)                         #Avoid checking and allow for different range in variogram
103
  co_kriged_surf<-predict(vm_g.fit,mean_LST) #Prediction using co-kriging with grid location defined from input raster image.
104
  #co_kriged_surf$tmax.pred                              #Results stored in SpatialGridDataFrame with tmax prediction accessible in dataframe.
148
  krmod1<-autoKrige(tmax~1, data_s,mean_LST,data_s) #Use autoKrige instead of krige: with data_s for fitting on a grid
149
  krmod2<-autoKrige(tmax~lat+lon,input_data=data_s,new_data=mean_LST,data_variogram=data_s)
150
  krmod2<-autoKrige(tmax~lat+lon,data_s,mean_LST, verbose=TRUE)
105 151
  
152
  krmod3<-autoKrige(tmax~LST, data_s,mean_LST,data_s)
153
  krmod4<-autoKrige(tmax~LST+ELEV_SRTM, data_s,mean_LST,data_s)
154
  krmod5<-autoKrige(tmax~LST+ELEV_SRTM+DISTOC, data_s,mean_LST,data_s)
106 155
  
107
  #spplot.vcov(co_kriged_surf)                           #Visualizing the covariance structure
108
  
109
  tmax_krig1_s <- overlay(tmax_krige,data_s)             #This overlays the kriged surface tmax and the location of weather stations
110
  tmax_cokrig1_s<- overlay(co_kriged_surf,data_s)        #This overalys the cokriged surface tmax and the location of weather stations
111
  tmax_krig1_v <- overlay(tmax_krige,data_v)             #This overlays the kriged surface tmax and the location of weather stations
112
  tmax_cokrig1_v<- overlay(co_kriged_surf,data_v)
156
  krig1<-krmod1$krige_output                   #Extracting Spatial Grid Data frame                    
157
  krig2<-krmod2$krige_output
158
  krig3<-krmod3$krige_outpu
159
  krig4<-krmod4$krige_output
160
  krig5<-krmod5$krige_output
161
  #tmax_krig1_s <- overlay(krige,data_s)             #This overlays the kriged surface tmax and the location of weather stations
162
  #tmax_krig1_v <- overlay(krige,data_v)
163
#   
164
#   #Cokriging tmax
165
#   g<-gstat(NULL,"tmax", tmax~1, data_s)                   #This creates a gstat object "g" that acts as container for kriging specifications.
166
#   g<-gstat(g, "SRTM_elev",ELEV_SRTM~1,data_s)            #Adding variables to gstat object g
167
#   g<-gstat(g, "LST", LST~1,data_s)
113 168
  
114
  data_s$tmax_kr<-tmax_krig1_s$var1.pred                 #Adding the results back into the original dataframes.
115
  data_v$tmax_kr<-tmax_krig1_v$var1.pred  
116
  data_s$tmax_cokr<-tmax_cokrig1_s$tmax.pred    
117
  data_v$tmax_cokr<-tmax_cokrig1_v$tmax.pred
169
#   vm_g<-variogram(g)                                     #Visualizing multivariate sample variogram.
170
#   vm_g.fit<-fit.lmc(vm_g,g,vgm(2000,"Sph", 100000,1000)) #Fitting variogram for all variables at once.
171
#   plot(vm_g,vm_g.fit)                                    #Visualizing variogram fit and sample
172
#   vm_g.fit$set <-list(nocheck=1)                         #Avoid checking and allow for different range in variogram
173
#   co_kriged_surf<-predict(vm_g.fit,mean_LST) #Prediction using co-kriging with grid location defined from input raster image.
174
#   #co_kriged_surf$tmax.pred                              #Results stored in SpatialGridDataFrame with tmax prediction accessible in dataframe.
118 175
  
119
  #Co-kriging only on the validation sites for faster computing
120
  
121
  cokrig1_dv<-predict(vm_g.fit,data_v)
122
  cokrig1_ds<-predict(vm_g.fit,data_s)
123
  data_s$tmax_cokr<-cokrig1_ds$tmax.pred    
124
  data_v$tmax_cokr<-cokrig1_dv$tmax.pred
125
  
126
  #Calculate RMSE and then krig the residuals....!
176
  #spplot.vcov(co_kriged_surf)                           #Visualizing the covariance structure
177
    
178
#   tmax_cokrig1_s<- overlay(co_kriged_surf,data_s)        #This overalys the cokriged surface tmax and the location of weather stations
179
#   tmax_cokrig1_v<- overlay(co_kriged_surf,data_v)
127 180
  
128
  res_mod1<- data_v$tmax - data_v$tmax_kr              #Residuals from kriging.
129
  res_mod2<- data_v$tmax - data_v$tmax_cokr                #Residuals from cokriging.
181
  for (j in 1:models){
182
    
183
    krmod<-paste("krig",j,sep="")
184
    
185
    krig_val_s <- overlay(krmod,data_s)             #This overlays the kriged surface tmax and the location of weather stations
186
    krig_val_v <- overlay(krmod,data_v)             #This overlays the kriged surface tmax and the location of weather stations
187
    
188
    pred_krmod<-paste("pred_krmod",j,sep="")
189
    #Adding the results back into the original dataframes.
190
    data_s[[pred_krmod]]<-krig_val_s$var1.pred
191
    data_v[[pred_krmod]]<-krig_val_v$var1.pred  
192
    
193
    #Model assessment: RMSE and then krig the residuals....!
194
    
195
    res_mod_kr_s<- data_s$tmax - data_s[[pred_krmod]]           #Residuals from kriging training
196
    res_mod_kr_v<- data_v$tmax - data_v[[pred_krmod]]           #Residuals from kriging validation
197
    
198
    RMSE_mod_kr_s <- sqrt(sum(res_mod_kr_s^2,na.rm=TRUE)/(nv-sum(is.na(res_mod_kr_s))))         #RMSE from kriged surface training
199
    RMSE_mod_kr_v <- sqrt(sum(res_mod_kr_v^2,na.rm=TRUE)/(nv-sum(is.na(res_mod_kr_v))))         #RMSE from kriged surface validation
200
    MAE_mod_kr_s<- sum(abs(res_mod_kr_s),na.rm=TRUE)/(nv-sum(is.na(res_mod_kr_s)))        #MAE from kriged surface training                    #MAE, Mean abs. Error FOR REGRESSION STEP 1: GAM   
201
    MAE_mod_kr_v<- sum(abs(res_mod_kr_v),na.rm=TRUE)/(nv-sum(is.na(res_mod_kr_v)))        #MAE from kriged surface validation
202
    ME_mod_kr_s<- sum(res_mod_kr_s,na.rm=TRUE)/(nv-sum(is.na(res_mod_kr_s)))                    #ME, Mean Error or bias FOR REGRESSION STEP 1: GAM
203
    ME_mod_kr_v<- sum(res_mod_kr_v,na.rm=TRUE)/(nv-sum(is.na(res_mod_kr_v)))                    #ME, Mean Error or bias FOR REGRESSION STEP 1: GAM
204
    R2_mod_kr_s<- cor(data_s$tmax,data_s[[gam_kr]],use="complete.obs")^2                  #R2, coef. of determination FOR REGRESSION STEP 1: GAM
205
    R2_mod_kr_v<- cor(data_v$tmax,data_v[[gam_kr]],use="complete.obs")^2                  #R2, coef. of determinationFOR REGRESSION STEP 1: GAM
206
    #(nv-sum(is.na(res_mod2)))
207
    #Writing out results
208
    
209
    results_RMSE[i,1]<- dates[i]  #storing the interpolation dates in the first column
210
    results_RMSE[i,2]<- ns        #number of stations used in the training stage
211
    results_RMSE[i,3]<- "RMSE"
212
    results_RMSE[i,j+3]<- RMSE_mod_kr_v
213
    #results_RMSE_kr[i,3]<- res_mod_kr_v
214
    
215
    results_MAE[i,1]<- dates[i]  #storing the interpolation dates in the first column
216
    results_MAE[i,2]<- ns        #number of stations used in the training stage
217
    results_MAE[i,3]<- "MAE"
218
    results_MAE[i,j+3]<- MAE_mod_kr_v
219
    #results_RMSE_kr[i,3]<- res_mod_kr_v
220
    
221
    results_ME[i,1]<- dates[i]  #storing the interpolation dates in the first column
222
    results_ME[i,2]<- ns        #number of stations used in the training stage
223
    results_ME[i,3]<- "ME"
224
    results_ME[i,j+3]<- ME_mod_kr_v
225
    #results_RMSE_kr[i,3]<- res_mod_kr_v
226
    
227
    results_R2[i,1]<- dates[i]  #storing the interpolation dates in the first column
228
    results_R2[i,2]<- ns        #number of stations used in the training stage
229
    results_R2[i,3]<- "R2"
230
    results_R2[i,j+3]<- R2_mod_kr_v
231
    #results_RMSE_kr[i,3]<- res_mod_kr_v
232
    
233
    name3<-paste("res_kr_mod",j,sep="")
234
    #as.numeric(res_mod)
235
    #data_s[[name3]]<-res_mod_kr_s
236
    data_s[[name3]]<-as.numeric(res_mod_kr_s)
237
    #data_v[[name3]]<-res_mod_kr_v 
238
    data_v[[name3]]<-as.numeric(res_mod_kr_v)
239
    #Writing residuals from kriging
240
    
241
  }
130 242
  
131
  RMSE_mod1 <- sqrt(sum(res_mod1^2,na.rm=TRUE)/(nv-sum(is.na(res_mod1))))                  #RMSE from kriged surface.
132
  RMSE_mod2 <- sqrt(sum(res_mod2^2,na.rm=TRUE)/(nv-sum(is.na(res_mod2))))                  #RMSE from co-kriged surface.
133
  #(nv-sum(is.na(res_mod2)))       
243
#   #Co-kriging only on the validation sites for faster computing
244
#   
245
#   cokrig1_dv<-predict(vm_g.fit,data_v)
246
#   cokrig1_ds<-predict(vm_g.fit,data_s)
247
# #   data_s$tmax_cokr<-cokrig1_ds$tmax.pred    
248
# #   data_v$tmax_cokr<-cokrig1_dv$tmax.pred
249
#   
250
#   #Calculate RMSE and then krig the residuals....!
251
#   
252
#   res_mod1<- data_v$tmax - data_v$tmax_kr              #Residuals from kriging.
253
#   res_mod2<- data_v$tmax - data_v$tmax_cokr            #Residuals from cokriging.
254
#   
255
#   RMSE_mod1 <- sqrt(sum(res_mod1^2,na.rm=TRUE)/(nv-sum(is.na(res_mod1))))                  #RMSE from kriged surface.
256
#   RMSE_mod2 <- sqrt(sum(res_mod2^2,na.rm=TRUE)/(nv-sum(is.na(res_mod2))))                  #RMSE from co-kriged surface.
257
#   #(nv-sum(is.na(res_mod2)))       
134 258

  
135 259
  #Saving the subset in a dataframe
136 260
  data_name<-paste("ghcn_v_",dates[[i]],sep="")
......
138 262
  data_name<-paste("ghcn_s_",dates[[i]],sep="")
139 263
  assign(data_name,data_s)
140 264
  
141
  krig_raster_name<-paste("coKriged_tmax_",data_name,out_prefix,".tif", sep="")
142
  writeGDAL(co_kriged_surf,fname=krig_raster_name, driver="GTiff", type="Float32",options ="INTERLEAVE=PIXEL")
143
  krig_raster_name<-paste("Kriged_tmax_",data_name,out_prefix,".tif", sep="")
144
  writeGDAL(tmax_krige,fname=krig_raster_name, driver="GTiff", type="Float32",options ="INTERLEAVE=PIXEL")
145
  X11()
146
  plot(raster(co_kriged_surf))
147
  title(paste("Tmax cokriging for date ",dates[[i]],sep=""))
148
  savePlot(paste("Cokriged_tmax",data_name,out_prefix,".png", sep=""), type="png")
149
  dev.off()
150
  X11()
151
  plot(raster(tmax_krige))
152
  title(paste("Tmax Kriging for date ",dates[[i]],sep=""))
153
  savePlot(paste("Kriged_res_",data_name,out_prefix,".png", sep=""), type="png")
154
  dev.off()
155
  
156
  results[i,1]<- dates[i]  #storing the interpolation dates in the first column
157
  results[i,2]<- ns     #number of stations in training
158
  results[i,3]<- RMSE_mod1
159
  results[i,4]<- RMSE_mod2  
265
  #Saving kriged surface in raster images
160 266
  
161
  results_mod_n[i,1]<-dates[i]
162
  results_mod_n[i,2]<-(nv-sum(is.na(res_mod1)))
163
  results_mod_n[i,3]<-(nv-sum(is.na(res_mod2)))
267
  #krig_raster_name<-paste("coKriged_tmax_",data_name,out_prefix,".tif", sep="")
268
  #writeGDAL(co_kriged_surf,fname=krig_raster_name, driver="GTiff", type="Float32",options ="INTERLEAVE=PIXEL")
269
  #krig_raster_name<-paste("Kriged_tmax_",data_name,out_prefix,".tif", sep="")
270
  #writeGDAL(tmax_krige,fname=krig_raster_name, driver="GTiff", type="Float32",options ="INTERLEAVE=PIXEL")
271
  #X11()
272
  #plot(raster(co_kriged_surf))
273
  #title(paste("Tmax cokriging for date ",dates[[i]],sep=""))
274
  #savePlot(paste("Cokriged_tmax",data_name,out_prefix,".png", sep=""), type="png")
275
  #dev.off()
276
  #X11()
277
  #plot(raster(tmax_krige))
278
  #title(paste("Tmax Kriging for date ",dates[[i]],sep=""))
279
  #savePlot(paste("Kriged_res_",data_name,out_prefix,".png", sep=""), type="png")
280
  #dev.off()
281
#   
282
#   results[i,1]<- dates[i]  #storing the interpolation dates in the first column
283
#   results[i,2]<- ns     #number of stations in training
284
#   results[i,3]<- RMSE_mod1
285
#   results[i,4]<- RMSE_mod2  
286
#   
287
#   results_mod_n[i,1]<-dates[i]
288
#   results_mod_n[i,2]<-(nv-sum(is.na(res_mod1)))
289
#   results_mod_n[i,3]<-(nv-sum(is.na(res_mod2)))
164 290
  }
165 291

  
166 292
## Plotting and saving diagnostic measures
167
results_num <-results
168
mode(results_num)<- "numeric"
169
# Make it numeric first
170
# Now turn it into a data.frame...
293
results_table_RMSE<-as.data.frame(results_RMSE)
294
results_table_MAE<-as.data.frame(results_MAE)
295
results_table_ME<-as.data.frame(results_ME)
296
results_table_R2<-as.data.frame(results_R2)
297

  
298
cname<-c("dates","ns","metric","krmod1", "krmod2","krmod3", "krmod4", "mkrod5")
299
colnames(results_table_RMSE)<-cname
300
colnames(results_table_MAE)<-cname
301
colnames(results_table_ME)<-cname
302
colnames(results_table_R2)<-cname
303

  
304

  
305
#Summary of diagnostic measures are stored in a data frame
306
tb_diagnostic1<-rbind(results_table_RMSE,results_table_MAE, results_table_ME, results_table_R2)   #
307
#tb_diagnostic1_kr<-rbind(results_table_RMSE_kr,results_table_MAE_kr, results_table_ME_kr, results_table_R2_kr)
308
#tb_diagnostic2<-rbind(results_table_AIC,results_table_GCV, results_table_DEV,results_table_RMSE_f)
309

  
310
write.table(tb_diagnostic1, file= paste(path,"/","results_GAM_Assessment_measure1",out_prefix,".txt",sep=""), sep=",")
311
#write.table(tb_diagnostic1_kr, file= paste(path,"/","results_GAM_Assessment_measure1_kr_",out_prefix,".txt",sep=""), sep=",")
312
#write.table(tb_diagnostic2, file= paste(path,"/","results_GAM_Assessment_measure2_",out_prefix,".txt",sep=""), sep=",")
171 313

  
172
results_table<-as.data.frame(results_num)
173
colnames(results_table)<-c("dates","ns","RMSE")
174 314

  
175
write.csv(results_table, file= paste(path,"/","results_Kriging_Assessment",out_prefix,".txt",sep=""))
315
#### END OF SCRIPT #####

Also available in: Unified diff