Project

General

Profile

Download (33 KB) Statistics
| Branch: | Revision:
1
runGAMCAI <- function(i) {            # loop over dates
2
  
3
  #ith upates from 10/26/2012
4
  #date<-strptime(dates[i], "%Y%m%d")   # interpolation date being processed
5
  date<-strptime(sampling_dat$date[i], "%Y%m%d")   # interpolation date being processed, converting the string using specific format
6
  month<-strftime(date, "%m")          # current month of the date being processed
7
  LST_month<-paste("mm_",month,sep="") # name of LST month to be matched in the raster stack of covariates and data.frame
8
  
9
  #Adding layer LST to the raster stack
10
  
11
  pos<-match("LST",layerNames(s_raster)) #Find the position of the layer with name "LST", if not present pos=NA
12
  s_raster<-dropLayer(s_raster,pos)      # If it exists drop layer
13
  pos<-match(LST_month,layerNames(s_raster)) #Find column with the current month for instance mm12
14
  r1<-raster(s_raster,layer=pos)             #Select layer from stack
15
  layerNames(r1)<-"LST"
16
  #Screen for extreme values" 10/30
17
  min_val<-(-15+273.16) #if values less than -15C then screen out (note the Kelvin units that will need to be changed later in all datasets)
18
  r1[r1 < (min_val)]<-NA
19
  s_raster<-addLayer(s_raster,r1)            #Adding current month
20
  
21
  ###Regression part 1: Creating a validation dataset by creating training and testing datasets
22
  
23
  mod_LST <-ghcn.subsets[[i]][,match(LST_month, names(ghcn.subsets[[i]]))]  #Match interpolation date and monthly LST average
24
  ghcn.subsets[[i]] <- transform(ghcn.subsets[[i]],LST = mod_LST)            #Add the variable LST to the subset dataset
25
  dst$LST<-dst[[LST_month]] #Add also to monthly dataset
26
  
27
  #n<-nrow(ghcn.subsets[[i]])
28
  #ns<-n-round(n*prop)   #Create a sample from the data frame with 70% of the rows
29
  #nv<-n-ns              #create a sample for validation with prop of the rows
30
  #ind.training <- sample(nrow(ghcn.subsets[[i]]), size=ns, replace=FALSE) #This selects the index position for 70% of the rows taken randomly
31
  ind.training<-sampling[[i]]
32
  ind.testing <- setdiff(1:nrow(ghcn.subsets[[i]]), ind.training)
33
  data_s <- ghcn.subsets[[i]][ind.training, ]   #Training dataset currently used in the modeling
34
  data_v <- ghcn.subsets[[i]][ind.testing, ]    #Testing/validation dataset using input sampling
35
  
36
  ns<-nrow(data_s)
37
  nv<-nrow(data_v)
38
  #i=1
39
  date_proc<-sampling_dat$date[i]
40
  date_proc<-strptime(sampling_dat$date[i], "%Y%m%d")   # interpolation date being processed
41
  mo<-as.integer(strftime(date_proc, "%m"))          # current month of the date being processed
42
  day<-as.integer(strftime(date_proc, "%d"))
43
  year<-as.integer(strftime(date_proc, "%Y"))
44

    
45
  datelabel=format(ISOdate(year,mo,day),"%b %d, %Y")
46
  
47
  ###########
48
  #  STEP 1 - LST 10 year monthly averages: THIS IS NOT USED IN CAI method
49
  ###########
50

    
51
  themolst<-raster(molst,mo) #current month being processed saved in a raster image
52
  min_val<-(-15)     #Screening for extreme values
53
  themolst[themolst < (min_val)]<-NA
54
  
55
  plot(themolst)
56
  
57
  ###########
58
  # STEP 2 - Weather station means across same days: Monthly mean calculation
59
  ###########
60
  
61
  modst=dst[dst$month==mo,] #Subsetting dataset for the relevant month of the date being processed
62
  
63
  ##########
64
  # STEP 3 - get LST at stations
65
  ##########
66
  
67
  sta_lola=modst[,c("lon","lat")] #Extracting locations of stations for the current month..
68
  
69
  proj_str="+proj=lcc +lat_1=43 +lat_2=45.5 +lat_0=41.75 +lon_0=-120.5 +x_0=400000 +y_0=0 +ellps=GRS80 +units=m +no_defs";
70
  lookup<-function(r,lat,lon) {
71
    xy<-project(cbind(lon,lat),proj_str);
72
    cidx<-cellFromXY(r,xy);
73
    return(r[cidx])
74
  }
75
  sta_tmax_from_lst=lookup(themolst,sta_lola$lat,sta_lola$lon) #Extracted values of LST for the stations
76
  
77
  #########
78
  # STEP 4 - bias at stations     
79
  #########
80
  
81
  sta_bias=sta_tmax_from_lst-modst$TMax; #That is the difference between the monthly LST mean and monthly station mean
82
  #Added by Benoit
83
  modst$LSTD_bias<-sta_bias  #Adding bias to data frame modst containning the monthly average for 10 years
84
  
85
  bias_xy=project(as.matrix(sta_lola),proj_str)
86
#   png(paste("LST_TMax_scatterplot_",dates[i],out_prefix,".png", sep=""))
87
#   plot(modst$TMax,sta_tmax_from_lst,xlab="Station mo Tmax",ylab="LST mo Tmax",main=paste("LST vs TMax for",datelabel,sep=" "))
88
#   abline(0,1)
89
#   dev.off()
90
  
91
  #added by Benoit 
92
  #x<-ghcn.subsets[[i]]  #Holds both training and testing for instance 161 rows for Jan 1
93
  x<-data_v
94
  d<-data_s
95
  
96
  pos<-match("value",names(d)) #Find column with name "value"
97
  #names(d)[pos]<-c("dailyTmax")
98
  names(d)[pos]<-y_var_name
99
  names(x)[pos]<-y_var_name
100
  #names(x)[pos]<-c("dailyTmax")
101
  d$dailyTmax=(as.numeric(d$dailyTmax))/10 #stored as 1/10 degree C to allow integer storage
102
  x$dailyTmax=(as.numeric(x$dailyTmax))/10 #stored as 1/10 degree C to allow integer storage
103
  pos<-match("station",names(d)) #Find column with name "value"
104
  names(d)[pos]<-c("id")
105
  names(x)[pos]<-c("id")
106
  names(modst)[1]<-c("id")       #modst contains the average tmax per month for every stations...it has 193 rows
107
  
108
  dmoday=merge(modst,d,by="id",suffixes=c("",".y2"))  #LOOSING DATA HERE!!! from 113 t0 103
109
  xmoday=merge(modst,x,by="id",suffixes=c("",".y2"))  #LOOSING DATA HERE!!! from 48 t0 43
110
  mod_pat<-glob2rx("*.y2")   
111
  var_pat<-grep(mod_pat,names(dmoday),value=FALSE) # using grep with "value" extracts the matching names
112
  dmoday<-dmoday[,-var_pat]
113
  mod_pat<-glob2rx("*.y2")   
114
  var_pat<-grep(mod_pat,names(xmoday),value=FALSE) # using grep with "value" extracts the matching names
115
  xmoday<-xmoday[,-var_pat] #Removing duplicate columns
116
  
117
  #dmoday=merge(modst,d,by="id")  #LOOSING DATA HERE!!! from 113 t0 103
118
  #xmoday=merge(modst,x,by="id")  #LOOSING DATA HERE!!! from 48 t0 43
119
  #names(dmoday)[4]<-c("lat")
120
  #names(dmoday)[5]<-c("lon")     #dmoday contains all the the information: BIAS, monn
121
  #names(xmoday)[4]<-c("lat")
122
  #names(xmoday)[5]<-c("lon")     #dmoday contains all the the information: BIAS, monn
123
  
124
  data_v<-xmoday
125
  ###
126
  
127
  #dmoday contains the daily tmax values for training with TMax being the monthly station tmax mean
128
  #xmoday contains the daily tmax values for validation with TMax being the monthly station tmax mean
129
  
130
  # windows()
131
  #png(paste("LST_TMax_scatterplot_",dates[i],out_prefix,".png", sep=""))
132
  png(paste("Daily_tmax_monthly_TMax_scatterplot_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],
133
            out_prefix,".png", sep=""))
134
  plot(dailyTmax~TMax,data=dmoday,xlab="Mo Tmax",ylab=paste("Daily for",datelabel),main="across stations in OR")
135
  #savePlot(paste("Daily_tmax_monthly_TMax_scatterplot_",dates[i],out_prefix,".png", sep=""), type="png")
136
  #png(paste("LST_TMax_scatterplot_",dates[i],out_prefix,".png", sep=""))
137
  dev.off()
138
  
139
  ########
140
  # STEP 5 - interpolate bias/climatology
141
  ########
142
  
143
  # ?? include covariates like elev, distance to coast, cloud frequency, tree height
144
  #library(fields)
145
  #windows()
146
  #quilt.plot(sta_lola,sta_bias,main="Bias at stations",asp=1)
147
  #US(add=T,col="magenta",lwd=2)
148
  #fitbias<-Tps(bias_xy,sta_bias) #use TPS or krige
149
  
150
  #Adding options to use only training stations: 07/11/2012
151
  bias_xy<-project(as.matrix(sta_lola),proj_str)
152
  clim_xy<-project(as.matrix(sta_lola),proj_str)     #This is the coordinates of monthly station location (193)
153
  #bias_xy2=project(as.matrix(c(dmoday$lon,dmoday$lat),proj_str)
154
  if(bias_val==1){
155
    sta_bias<-dmoday$LSTD_bias         
156
    bias_xy<-cbind(dmoday$x_OR83M,dmoday$y_OR83M) #This will use only stations from training daily samples for climatology step if bias_val=1
157
  }
158
  
159
  sta_clim<-modst$TMax #This contains the monthly climatology...used in the prediction of the monthly surface
160
  clim_covar<-data_month$ELEV_SRTM
161
  #fitbias<-Krig(bias_xy,sta_bias,theta=1e5) #use TPS or krige 
162
  fitclim<-Krig(clim_xy,sta_clim,theta=1e5)
163
  
164
  theta_val<-100000
165
  kf<-exp(-rdist(clim_xy/theta_val))
166
  image(kf)
167
  kf_fun<-function(dist,theta=1,C=NA){
168
    exp(-rdist(dist/theta))
169
  }
170
  plot(sort(kf[1,],decreasing=T),type="l")
171
  
172
  fitclim2<-Krig(x=clim_xy,Y=sta_clim,Z=clim_covar,theta=1e5)
173
  fitclim2<-Krig(clim_xy,sta_clim,theta=theta_val)
174
  fitclim2<-Krig(clim_xy,sta_clim,cov.function="kf_fun",theta=1e5)      
175
            
176
  #The output is a krig object using fields: modif 10/30
177
  #mod9a<-fitbias
178
  mod_krtmp1<-fitclim
179
  model_name<-paste("mod_kr","month",sep="_")
180
  assign(model_name,mod_krtmp1)
181
  
182
  # Creating plot of bias surface and saving it
183
  #X11()
184
  png(paste("Climtology_surface_LST_TMax_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],
185
            out_prefix,".png", sep="")) #Create file to write a plot
186
  datelabel2=format(ISOdate(year,mo,day),"%B ") #added by Benoit, label
187
  surface(fitclim,col=rev(terrain.colors(100)),asp=1,main=paste("Interpolated clim for",datelabel2,sep=" ")) #Plot to file
188
  #savePlot(paste("Bias_surface_LST_TMax_",dates[i],out_prefix,".png", sep=""), type="png")
189
  dev.off()  #Release the hold to the file
190
  
191
  #US(add=T,col="magenta",lwd=2)
192
  
193
  ##########
194
  # STEP 7 - interpolate delta across space: this is the daily deviation from the monthly average
195
  ##########
196
  
197
  daily_sta_lola=dmoday[,c("lon","lat")] #could be same as before but why assume merge does this - assume not
198
  daily_sta_xy=project(as.matrix(daily_sta_lola),proj_str)
199
  daily_delta=dmoday$dailyTmax-dmoday$TMax
200
  
201
  daily_deltaclim<-dmoday$dailyTmax-dmoday$TMax    #For daily surface interpolation...
202
  daily_deltaclim_v<-data_v$dailyTmax-data_v$TMax  #For validation...
203
  #dmoday$daily_deltaclim <-daily_deltaclim
204
  #fitdelta<-Tps(daily_sta_xy,daily_delta) #use TPS or krige
205
  fitdelta<-Krig(daily_sta_xy,daily_delta,theta=1e5) #use TPS or krige
206
  fitdeltaclim<-Krig(daily_sta_xy,daily_deltaclim,theta=1e5) #use TPS or krige
207
  
208
  #Kriging using fields package: modif 10/30
209
  #mod9b<-fitdelta
210
  mod_krtmp2<-fitdeltaclim
211
  model_name<-paste("mod_kr","day",sep="_")
212
  assign(model_name,mod_krtmp2)
213
  
214
  # Creating plot of bias surface and saving it
215
  #X11()
216
  png(paste("Deltaclim_surface_TMax_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],
217
            out_prefix,".png", sep=""))
218
  surface(fitdeltaclim,col=rev(terrain.colors(100)),asp=1,main=paste("Interpolated deltaclim for",datelabel,sep=" "))
219
  #savePlot(paste("Delta_surface_LST_TMax_",dates[i],out_prefix,".png", sep=""), type="png")
220
  dev.off()
221
  #US(add=T,col="magenta",lwd=2)
222
  #
223
  
224
  #### Added by Benoit on 06/19
225
  data_s<-dmoday #put the 
226
  #data_s$daily_delta<-daily_delta
227
  data_s$daily_deltaclim<-daily_deltaclim
228
  data_v$daily_deltaclim<-daily_deltaclim_v
229
  #data_s$y_var<-daily_delta  #y_var is the variable currently being modeled, may be better with BIAS!!
230
  #data_s$y_var<-data_s$LSTD_bias
231
  #### Added by Benoit ends
232
  
233
  #########
234
  # STEP 8 - assemble final answer - T= LST-Bias(interpolated)+delta(interpolated)    (This is for fusion not implemented in this script...)
235
  #                                  T= clim(interpolated) + deltaclim(interpolated)  (This is for CAI)
236
  #########
237

    
238
  #bias_rast=interpolate(themolst,fitbias) #interpolation using function from raster package
239
  clim_rast=interpolate(themolst,fitclim) #interpolation using function from raster package
240
  #themolst is raster layer, fitbias is "Krig" object from bias surface
241
  clim_rast2=interpolate(themolst,fitclim2) #interpolation using function from raster package
242
          
243
  clim_rast2=interpolate(ELEV_SRTM,fitclim2,xyOnly=FALSE) #interpolation using function from raster package
244
  
245
  #Saving kriged surface in raster images
246
  data_name<-paste("clim_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],sep="")
247
  raster_name<-paste("CAI_",data_name,out_prefix,".rst", sep="")
248
  writeRaster(clim_rast, filename=raster_name,overwrite=TRUE)  #Writing the data in a raster file format...(IDRISI)
249
  
250
  #daily_delta_rast=interpolate(themolst,fitdelta) #Interpolation of the bias surface...
251
  daily_deltaclim_rast=interpolate(themolst,fitdeltaclim) #Interpolation of the bias surface...
252
  
253
  #plot(daily_delta_rast,main="Raster Daily Delta")
254
  
255
  #Saving kriged surface in raster images
256
  data_name<-paste("deltaclim_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],sep="")
257
  raster_name<-paste("CAI_",data_name,out_prefix,".rst", sep="")
258
  writeRaster(daily_deltaclim_rast, filename=raster_name,overwrite=TRUE)  #Writing the data in a raster file format...(IDRISI)
259
  
260
  #tmax_predicted=themolst+daily_delta_rast-bias_rast #Final surface  as a raster layer...eqt ok
261
  tmax_predicted<-daily_deltaclim_rast + clim_rast #Final surface  as a raster layer...
262
  #tmp6<-data_s$daily_deltaclim +data_s$TMax
263
  #tmp7<-extract(tmax_predicted,data_s)
264
  #plot(tmax_predicted,main="Predicted daily")
265
  
266
  #Saving kriged surface in raster images
267
  data_name<-paste("tmax_predicted_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],sep="")
268
  raster_name<-paste("CAI_",data_name,out_prefix,".rst", sep="")
269
  writeRaster(tmax_predicted, filename=raster_name,overwrite=TRUE)  #Writing the data in a raster file format...(IDRISI)
270
  
271
  ########
272
  # check: assessment of results: validation
273
  ########
274
  RMSE<-function(x,y) {return(mean((x-y)^2)^0.5)}
275
  MAE_fun<-function(x,y) {return(mean(abs(x-y)))}
276
  #ME_fun<-function(x,y){return(mean(abs(y)))}
277
  #FIT ASSESSMENT
278
  sta_pred_data_s=lookup(tmax_predicted,data_s$lat,data_s$lon)
279
  rmse_fit=RMSE(sta_pred_data_s,data_s$dailyTmax)
280
  mae_fit=MAE_fun(sta_pred_data_s,data_s$dailyTmax)
281
    
282
  sta_pred=lookup(tmax_predicted,data_v$lat,data_v$lon)
283
  #sta_pred=lookup(tmax_predicted,daily_sta_lola$lat,daily_sta_lola$lon)
284
  #rmse=RMSE(sta_pred,dmoday$dailyTmax)
285
  #pos<-match("value",names(data_v)) #Find column with name "value"
286
  #names(data_v)[pos]<-c("dailyTmax")
287
  tmax<-data_v$dailyTmax
288
  #data_v$dailyTmax<-tmax
289
  rmse=RMSE(sta_pred,tmax)
290
  mae<-MAE_fun(sta_pred,tmax)
291
  r2<-cor(sta_pred,tmax)^2              #R2, coef. of var
292
  me<-mean(sta_pred-tmax)
293
 
294
  #plot(sta_pred~dmoday$dailyTmax,xlab=paste("Actual daily for",datelabel),ylab="Pred daily",main=paste("RMSE=",rmse))
295
  
296
  png(paste("Predicted_tmax_versus_observed_scatterplot_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",
297
            sampling_dat$run_samp[i],out_prefix,".png", sep=""))
298
  plot(sta_pred~tmax,xlab=paste("Actual daily for",datelabel),ylab="Pred daily",main=paste("RMSE=",rmse))
299
  abline(0,1)
300
  #savePlot(paste("Predicted_tmax_versus_observed_scatterplot_",dates[i],out_prefix,".png", sep=""), type="png")
301
  dev.off()
302
  #resid=sta_pred-dmoday$dailyTmax
303
  resid=sta_pred-tmax
304
  #quilt.plot(daily_sta_lola,resid)
305
  
306

    
307
  ###BEFORE GAM prediction the data object must be transformed to SDF
308
  
309
  coords<- data_v[,c('x_OR83M','y_OR83M')]
310
  coordinates(data_v)<-coords
311
  proj4string(data_v)<-CRS  #Need to assign coordinates...
312
  coords<- data_s[,c('x_OR83M','y_OR83M')]
313
  coordinates(data_s)<-coords
314
  proj4string(data_s)<-CRS  #Need to assign coordinates..
315
  coords<- modst[,c('x_OR83M','y_OR83M')]
316
  coordinates(modst)<-coords
317
  proj4string(modst)<-CRS  #Need to assign coordinates..
318
  
319
  ns<-nrow(data_s) #This is added to because some loss of data might have happened because of the averaging...
320
  nv<-nrow(data_v)
321
  
322
  ###GAM PREDICTION
323
  
324
  #data_s$y_var<-data_s$dailyTmax  #This shoudl be changed for any variable!!!
325
  #data_v$y_var<-data_v$dailyTmax
326
  #data_v$y_var<-data_v$daily_deltaclim
327
  data_s$y_var<-data_s$daily_deltaclim
328
  data_v$y_var<-data_v$daily_deltaclim
329
  
330
  if (climgam==1){          #This is an option to use covariates in the daily surface...
331
    data_s$y_var<-data_s$TMax
332
    data_v$y_var<-data_v$TMax
333
    data_month<-modst
334
    data_month$y_var<-modst$TMax
335
  }
336
  
337
  #Model and response variable can be changed without affecting the script
338
  #list_formulas<-vector("list",nmodels)
339
  
340
  #list_formulas[[1]] <- as.formula("y_var ~ s(lat) + s(lon) + s(ELEV_SRTM)", env=.GlobalEnv)
341
  #list_formulas[[2]] <- as.formula("y_var~ s(lat,lon)+ s(ELEV_SRTM)", env=.GlobalEnv)
342
  #list_formulas[[3]] <- as.formula("y_var~ s(lat) + s (lon) + s (ELEV_SRTM) +  s (Northness)+ s (Eastness) + s(DISTOC)", env=.GlobalEnv)
343
  #list_formulas[[4]] <- as.formula("y_var~ s(lat) + s (lon) + s(ELEV_SRTM) + s(Northness) + s (Eastness) + s(DISTOC) + s(LST)", env=.GlobalEnv)
344
  #list_formulas[[5]] <- as.formula("y_var~ s(lat,lon) +s(ELEV_SRTM) + s(Northness,Eastness) + s(DISTOC) + s(LST)", env=.GlobalEnv)
345
  #list_formulas[[6]] <- as.formula("y_var~ s(lat,lon) +s(ELEV_SRTM) + s(Northness,Eastness) + s(DISTOC) + s(LST)+s(LC1)", env=.GlobalEnv)
346
  #list_formulas[[7]] <- as.formula("y_var~ s(lat,lon) +s(ELEV_SRTM) + s(Northness,Eastness) + s(DISTOC) + s(LST)+s(LC3)", env=.GlobalEnv)
347
  #list_formulas[[8]] <- as.formula("y_var~ s(lat,lon) +s(ELEV_SRTM) + s(Northness,Eastness) + s(DISTOC) + s(LST) + s(LC1,LC3)", env=.GlobalEnv)
348
  
349
  
350
  #This can be entered as textfile or option later...ok for running now on 10/30/2012
351
  #list_formulas[[1]] <- as.formula("y_var~ s(ELEV_SRTM)", env=.GlobalEnv)
352
  #list_formulas[[2]] <- as.formula("y_var~ s(LST)", env=.GlobalEnv)
353
  #list_formulas[[3]] <- as.formula("y_var~ s(LST) + s(ELEV_SRTM)", env=.GlobalEnv)
354
  #list_formulas[[4]] <- as.formula("y_var~ s(LST,ELEV_SRTM)", env=.GlobalEnv)
355
  #list_formulas[[5]] <- as.formula("y_var~ s(lat,lon,ELEV_SRTM)", env=.GlobalEnv)
356
  
357
  if (climgam==1){          #This will automatically use monthly station data in the second step
358
    
359
    for (j in 1:nmodels){
360
      formula<-list_formulas[[j]]
361
      mod<- try(gam(formula, data=data_month))
362
      model_name<-paste("mod",j,sep="")
363
      assign(model_name,mod) 
364
    }
365
    
366
  } else if (climgam==0){ #This will use daily delta in the second step
367
    
368
    for (j in 1:nmodels){
369
      formula<-list_formulas[[j]]
370
      mod<- try(gam(formula, data=data_s))
371
      model_name<-paste("mod",j,sep="")
372
      assign(model_name,mod) 
373
    }
374
    
375
  }
376
  
377
  ### Added by benoit
378
  #Store results using TPS
379
  j=nmodels+1
380
  results_RMSE[1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
381
  results_RMSE[2]<- ns          #number of stations used in the training stage
382
  results_RMSE[3]<- "RMSE"
383

    
384
  results_RMSE[j+3]<- rmse  #Storing RMSE for the model j
385
  
386
  results_RMSE_f[1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
387
  results_RMSE_f[2]<- ns          #number of stations used in the training stage
388
  results_RMSE_f[3]<- "RMSE_f"
389
  results_RMSE_f[j+3]<- rmse_fit  #Storing RMSE for the model j
390
  
391
  results_MAE_f[1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
392
  results_MAE_f[2]<- ns          #number of stations used in the training stage
393
  results_MAE_f[3]<- "RMSE_f"
394
  results_MAE_f[j+3]<- mae_fit  #Storing RMSE for the model j
395

    
396
  results_MAE[1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
397
  results_MAE[2]<- ns          #number of stations used in the training stage
398
  results_MAE[3]<- "MAE"
399
  results_MAE[j+3]<- mae  #Storing RMSE for the model j
400

    
401
  results_ME[1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
402
  results_ME[2]<- ns          #number of stations used in the training stage
403
  results_ME[3]<- "ME"
404
  results_ME[j+3]<- me  #Storing RMSE for the model j
405
  
406
  results_R2[1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
407
  results_R2[2]<- ns          #number of stations used in the training stage
408
  results_R2[3]<- "R2"
409
  results_R2[j+3]<- r2  #Storing RMSE for the model j
410
  
411
  pred_mod<-paste("pred_mod",j,sep="")
412
  #Adding the results back into the original dataframes.
413
  data_s[[pred_mod]]<-sta_pred_data_s
414
  data_v[[pred_mod]]<-sta_pred 
415
  
416
  #Model assessment: RMSE and then krig the residuals....!
417
  
418
  res_mod_s<- data_s$dailyTmax - data_s[[pred_mod]]           #Residuals from kriging training
419
  res_mod_v<- data_v$dailyTmax - data_v[[pred_mod]]           #Residuals from kriging validation
420
  
421
  name2<-paste("res_mod",j,sep="")
422
  data_v[[name2]]<-as.numeric(res_mod_v)
423
  data_s[[name2]]<-as.numeric(res_mod_s)
424
  
425
  #ns<-nrow(data_s) #This is added to because some loss of data might have happened because of the averaging...
426
  #nv<-nrow(data_v)
427
  #browser()
428
  
429
  mod_obj<-vector("list",nmodels+2)  #This will contain the model objects fitting: 10/30
430
  mod_obj[[nmodels+1]]<-mod_kr_month  #Storing climatology object
431
  mod_obj[[nmodels+2]]<-mod_kr_day  #Storing delta object
432

    
433
  for (j in 1:nmodels){
434
    
435
    ##Model assessment: specific diagnostic/metrics for GAM
436
    
437
    name<-paste("mod",j,sep="")  #modj is the name of The "j" model (mod1 if j=1) 
438
    mod<-get(name)               #accessing GAM model ojbect "j"
439
    mod_obj[[j]]<-mod  #storing current model object
440
      
441
    #If mod "j" is not a model object
442
    if (inherits(mod,"try-error")) {
443
      results_m1[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
444
      results_m1[1,2]<- ns        #number of stations used in the training stage
445
      results_m1[1,3]<- "AIC"
446
      results_m1[1,j+3]<- NA
447
      
448
      results_m2[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
449
      results_m2[1,2]<- ns        #number of stations used in the training 
450
      results_m2[1,3]<- "GCV"
451
      results_m2[1,j+3]<- NA
452
      
453
      results_m3[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
454
      results_m3[1,2]<- ns        #number of stations used in the training stage
455
      results_m3[1,3]<- "DEV"
456
      results_m3[1,j+3]<- NA
457
      
458
      results_RMSE_f[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
459
      results_RMSE_f[1,2]<- ns        #number of stations used in the training stage
460
      results_RMSE_f[1,3]<- "RSME_f"
461
      results_RMSE_f[1,j+3]<- NA
462
      
463
      results_MAE_f[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
464
      results_MAE_f[1,2]<- ns        #number of stations used in the training stage
465
      results_MAE_f[1,3]<- "MAE_f"
466
      results_MAE_f[1,j+3]<-NA
467
      
468
      results_R2_f[1,1]<- sampling_dat$date[i]      #storing the interpolation dates in the first column
469
      results_R2_f[1,2]<- ns            #number of stations used in the training stage
470
      results_R2_f[1,3]<- "R2_f"
471
      results_R2_f[1,j+3]<- NA     #Storing R2 for the model j
472
      
473
      
474
      results_RMSE[1,1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
475
      results_RMSE[1,2]<- ns          #number of stations used in the training stage
476
      results_RMSE[1,3]<- "RMSE"
477
      results_RMSE[1,j+3]<- NA  #Storing RMSE for the model j
478
      results_MAE[1,1]<- sampling_dat$date[i]     #storing the interpolation dates in the first column
479
      results_MAE[1,2]<- ns           #number of stations used in the training stage
480
      results_MAE[1,3]<- "MAE"
481
      results_MAE[1,j+3]<- NA    #Storing MAE for the model j
482
      results_ME[1,1]<- sampling_dat$date[i]      #storing the interpolation dates in the first column
483
      results_ME[1,2]<- ns            #number of stations used in the training stage
484
      results_ME[1,3]<- "ME"
485
      results_ME[1,j+3]<- NA      #Storing ME for the model j
486
      results_R2[1,1]<- sampling_dat$date[i]      #storing the interpolation dates in the first column
487
      results_R2[1,2]<- ns            #number of stations used in the training stage
488
      results_R2[1,3]<- "R2"
489
      results_R2[1,j+3]<- NA      #Storing R2 for the model j
490
      
491
    }
492
    
493
    #If mod is a modelobject
494
    
495
    #If mod "j" is not a model object
496
    if (inherits(mod,"gam")) {
497
      
498
      # model specific metrics
499
      results_m1[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
500
      results_m1[1,2]<- ns        #number of stations used in the training stage
501
      results_m1[1,3]<- "AIC"
502
      results_m1[1,j+3]<- AIC (mod)
503
      
504
      results_m2[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
505
      results_m2[1,2]<- ns        #number of stations used in the training 
506
      results_m2[1,3]<- "GCV"
507
      results_m2[1,j+3]<- mod$gcv.ubre
508
      
509
      results_m3[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
510
      results_m3[1,2]<- ns        #number of stations used in the training stage
511
      results_m3[1,3]<- "DEV"
512
      results_m3[1,j+3]<- mod$deviance
513
      
514
      ##Model assessment: general diagnostic/metrics
515
      ##validation: using the testing data
516
      if (predval==1) {
517
      
518
        ##Model assessment: specific diagnostic/metrics for GAM
519
        
520
        name<-paste("mod",j,sep="")  #modj is the name of The "j" model (mod1 if j=1) 
521
        mod<-get(name)               #accessing GAM model ojbect "j"
522
        
523
        s_sgdf<-as(s_raster,"SpatialGridDataFrame") #Conversion to spatial grid data frame
524
        
525
        rpred<- predict(mod, newdata=s_sgdf, se.fit = TRUE) #Using the coeff to predict new values.
526
        y_pred<-rpred$fit
527
        raster_pred<-r1
528
        layerNames(raster_pred)<-"y_pred"
529
        values(raster_pred)<-as.numeric(y_pred)
530
        data_name<-paste("predicted_mod",j,"_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],sep="")
531
        raster_name<-paste("GAMCAI_",data_name,out_prefix,".rst", sep="")
532
        writeRaster(raster_pred, filename=raster_name,overwrite=TRUE)  #Writing the data in a raster file format...(IDRISI)
533
        #writeRaster(r2, filename=raster_name,overwrite=TRUE)  #Writing the data in a raster file format...(IDRISI)
534
        
535
        tmax_predicted_CAI<-raster_pred + clim_rast #Final surface  as a raster layer...taht is if daily prediction with GAM
536
        if (climgam==1){
537
          tmax_predicted_CAI<-raster_pred + daily_deltaclim_rast #Final surface  as a raster layer...
538
        }
539
          
540
        layerNames(tmax_predicted_CAI)<-"y_pred"
541
        data_name<-paste("predicted_mod",j,"_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],sep="")
542
        raster_name<-paste("GAMCAI_tmax_predicted_",data_name,out_prefix,".rst", sep="")
543
        writeRaster(tmax_predicted_CAI, filename=raster_name,overwrite=TRUE)  #Writing the data in a raster file format...(IDRISI)
544
        #writeRaster(r2, filename=raster_name,overwrite=TRUE)  #Writing the data in a raster file format...(IDRISI)
545
        
546
        pred_sgdf<-as(tmax_predicted_CAI,"SpatialGridDataFrame") #Conversion to spatial grid data frame
547
        #rpred_val_s <- overlay(raster_pred,data_s)             #This overlays the kriged surface tmax and the location of weather stations
548
                
549
        rpred_val_s <- overlay(pred_sgdf,data_s)             #This overlays the kriged surface tmax and the location of weather stations
550
        rpred_val_v <- overlay(pred_sgdf,data_v)             #This overlays the kriged surface tmax and the location of weather stations
551
        
552
        pred_mod<-paste("pred_mod",j,sep="")
553
        #Adding the results back into the original dataframes.
554
        data_s[[pred_mod]]<-rpred_val_s$y_pred
555
        data_v[[pred_mod]]<-rpred_val_v$y_pred  
556
        
557
        #Model assessment: RMSE and then krig the residuals....!
558
        
559
        res_mod_s<- data_s$dailyTmax - data_s[[pred_mod]]           #Residuals from kriging training
560
        res_mod_v<- data_v$dailyTmax - data_v[[pred_mod]]           #Residuals from kriging validation
561
        
562
      }
563
      
564
      if (predval==0) {
565
        
566
        y_mod<- predict(mod, newdata=data_v, se.fit = TRUE) #Using the coeff to predict new values.
567
        
568
        pred_mod<-paste("pred_mod",j,sep="")
569
        #Adding the results back into the original dataframes.
570
        data_s[[pred_mod]]<-as.numeric(mod$fit)
571
        data_v[[pred_mod]]<-as.numeric(y_mod$fit)
572
        
573
        #Model assessment: RMSE and then krig the residuals....!
574
        #y_var_name<-"dailyTmax"
575
        res_mod_s<- data_s$dailyTmax - data_s[[pred_mod]]           #Residuals from kriging training
576
        res_mod_v<- data_v$dailyTmax - data_v[[pred_mod]]           #Residuals from kriging validation
577
      }
578

    
579
      #y_var_fit= mod$fit #move it
580
      #Use res_mod_s so the R2 is based on daily station training
581
      R2_mod_f<- cor(data_s$dailyTmax,res_mod_s, use="complete")^2
582
      RMSE_mod_f<- sqrt(mean(res_mod_s^2,na.rm=TRUE))
583
      
584
      results_RMSE_f[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
585
      results_RMSE_f[1,2]<- ns        #number of stations used in the training stage
586
      results_RMSE_f[1,3]<- "RSME_f"
587
      #results_RMSE_f[1,j+3]<-sqrt(mean(mod$residuals^2,na.rm=TRUE))
588
      results_RMSE_f[1,j+3]<-sqrt(mean(res_mod_s^2,na.rm=TRUE))
589
      
590
      results_MAE_f[1,1]<- sampling_dat$date[i]  #storing the interpolation dates in the first column
591
      results_MAE_f[1,2]<- ns        #number of stations used in the training stage
592
      results_MAE_f[1,3]<- "MAE_f"
593
      #results_MAE_f[j+3]<-sum(abs(y_var_fit-data_s$y_var))/ns
594
      results_MAE_f[1,j+3]<-mean(abs(res_mod_s),na.rm=TRUE)
595
      
596
      results_R2_f[1,1]<- sampling_dat$date[i]      #storing the interpolation dates in the first column
597
      results_R2_f[1,2]<- ns            #number of stations used in the training stage
598
      results_R2_f[1,3]<- "R2_f"
599
      results_R2_f[1,j+3]<- R2_mod_f      #Storing R2 for the model j
600
      
601
      #### Now calculate validation metrics
602
      res_mod<-res_mod_v
603
      
604
      #RMSE_mod <- sqrt(sum(res_mod^2)/nv)                 #RMSE FOR REGRESSION STEP 1: GAM  
605
      RMSE_mod<- sqrt(mean(res_mod^2,na.rm=TRUE))
606
      #MAE_mod<- sum(abs(res_mod),na.rm=TRUE)/(nv-sum(is.na(res_mod)))        #MAE from kriged surface validation
607
      MAE_mod<- mean(abs(res_mod), na.rm=TRUE)
608
      #ME_mod<- sum(res_mod,na.rm=TRUE)/(nv-sum(is.na(res_mod)))                    #ME, Mean Error or bias FOR REGRESSION STEP 1: GAM
609
      ME_mod<- mean(res_mod,na.rm=TRUE)                            #ME, Mean Error or bias FOR REGRESSION STEP 1: GAM
610
      #R2_mod<- cor(data_v$y_var,data_v[[pred_mod]])^2              #R2, coef. of var FOR REGRESSION STEP 1: GAM
611
      pred_mod<-paste("pred_mod",j,sep="")
612
      R2_mod<- cor(data_v$dailyTmax,data_v[[pred_mod]], use="complete")^2
613
      results_RMSE[1]<- sampling_dat$date[i]    #storing the interpolation dates in the first column
614
      results_RMSE[2]<- ns          #number of stations used in the training stage
615
      results_RMSE[3]<- "RMSE"
616
      results_RMSE[j+3]<- RMSE_mod  #Storing RMSE for the model j
617
      results_MAE[1]<- sampling_dat$date[i]     #storing the interpolation dates in the first column
618
      results_MAE[2]<- ns           #number of stations used in the training stage
619
      results_MAE[3]<- "MAE"
620
      results_MAE[j+3]<- MAE_mod    #Storing MAE for the model j
621
      results_ME[1]<- sampling_dat$date[i]      #storing the interpolation dates in the first column
622
      results_ME[2]<- ns            #number of stations used in the training stage
623
      results_ME[3]<- "ME"
624
      results_ME[j+3]<- ME_mod      #Storing ME for the model j
625
      results_R2[1]<- sampling_dat$date[i]      #storing the interpolation dates in the first column
626
      results_R2[2]<- ns            #number of stations used in the training stage
627
      results_R2[3]<- "R2"
628
      results_R2[j+3]<- R2_mod      #Storing R2 for the model j
629
      
630
      #Saving residuals and prediction in the dataframes: tmax predicted from GAM
631

    
632
      name2<-paste("res_mod",j,sep="")
633
      data_v[[name2]]<-as.numeric(res_mod_v)
634
      data_s[[name2]]<-as.numeric(res_mod_s)
635
      #end of loop calculating RMSE
636
    }
637
  }
638
  
639
  #if (i==length(dates)){
640
  
641
  
642
  #Specific diagnostic measures related to the testing datasets
643
  
644
  results_table_RMSE<-as.data.frame(results_RMSE)
645
  results_table_MAE<-as.data.frame(results_MAE)
646
  results_table_ME<-as.data.frame(results_ME)
647
  results_table_R2<-as.data.frame(results_R2)
648
  results_table_RMSE_f<-as.data.frame(results_RMSE_f)
649
  results_table_MAE_f<-as.data.frame(results_MAE_f)
650
  results_table_R2_f<-as.data.frame(results_R2_f)
651
  
652
  results_table_m1<-as.data.frame(results_m1)
653
  results_table_m2<-as.data.frame(results_m2)
654
  results_table_m3<-as.data.frame(results_m3)
655
  
656
  tb_metrics1<-rbind(results_table_RMSE,results_table_MAE, results_table_ME, 
657
                     results_table_R2,results_table_RMSE_f,results_table_MAE_f,results_table_R2_f)   #
658
  tb_metrics2<-rbind(results_table_m1,results_table_m2, results_table_m3)
659
  
660
  #Preparing labels
661
  mod_labels<-rep("mod",nmodels+1)
662
  index<-as.character(1:(nmodels+1))
663
  mod_labels<-paste(mod_labels,index,sep="")
664
  cname<-c("dates","ns","metric", mod_labels)
665
  #cname<-c("dates","ns","metric","mod1", "mod2","mod3", "mod4", "mod5", "mod6", "mod7","mod8","mod9")
666
  colnames(tb_metrics1)<-cname
667
  #cname<-c("dates","ns","metric","mod1", "mod2","mod3", "mod4", "mod5", "mod6", "mod7","mod8")
668
  colnames(tb_metrics2)<-cname[1:(nmodels+3)]
669

    
670
  print(paste(sampling_dat$date[i],"processed"))
671
  # Kriging object may need to be modified...because it contains the full image of prediction!!
672
  ##loop through model objects data frame and set field to zero...
673

    
674
  #mod_obj<-list(mod1,mod2,mod3,mod4,mod5,mod6,mod7,mod8,mod9a,mod9b)
675
  #names(mod_obj)<-c("mod1","mod2","mod3","mod4","mod5","mod6","mod7","mod8","mod9a","mod9b") #generate names automatically??
676
  mod_labels_kr<-c("mod_kr_month", "mod_kr_day")
677
  names(mod_obj)<-c(mod_labels[1:nmodels],mod_labels_kr)
678
  results_list<-list(data_s,data_v,tb_metrics1,tb_metrics2,mod_obj,data_month,list_formulas)
679
  names(results_list)<-c("data_s","data_v","tb_metrics1","tb_metrics2","mod_obj","data_month","formulas")
680
  save(results_list,file= paste(path,"/","results_list_metrics_objects_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i],
681
                                out_prefix,".RData",sep=""))
682
  return(results_list)
683
  #return(tb_diagnostic1)
684
}
(3-3/33)