Project

General

Profile

Download (17.8 KB) Statistics
| Branch: | Revision:
1
##################    Validation and analyses of results  #######################################
2
############################ Covariate production for a given tile/region ##########################################
3
#This script examines inputs and outputs from the interpolation step.                             
4
#Part 1: Script produces plots for every selected date
5
#Part 2: Examine 
6
#AUTHOR: Benoit Parmentier                                                                       
7
#DATE: 03/18/2013                                                                                 
8

    
9
#PROJECT: NCEAS INPLANT: Environment and Organisms --TASK#???--   
10

    
11
##Comments and TODO:
12
#Separate inteprolation results analyses from covariates analyses 
13

    
14
##################################################################################################
15

    
16
###Loading R library and packages   
17
library(RPostgreSQL)
18
library(sp)                                             # Spatial pacakge with class definition by Bivand et al.
19
library(spdep)                                          # Spatial pacakge with methods and spatial stat. by Bivand et al.
20
library(rgdal)                                          # GDAL wrapper for R, spatial utilities
21
library(raster)
22
library(gtools)
23
library(rasterVis)
24
library(graphics)
25
library(grid)
26
library(lattice)
27

    
28
### Parameters and arguments
29

    
30
##Paths to inputs and output
31
#Select relevant dates and load R objects created during the interpolation step
32

    
33
##Paths to inputs and output
34
script_path<-"/home/parmentier/Data/IPLANT_project/Venezuela_interpolation/Venezuela_01142013/"
35
in_path <- "/home/parmentier/Data/IPLANT_project/Venezuela_interpolation/Venezuela_01142013/input_data/"
36
out_path<- "/home/parmentier/Data/IPLANT_project/Venezuela_interpolation/Venezuela_01142013/output_data/"
37
infile_covar<-"covariates__venezuela_region__VE_01292013.tif" #this is an output from covariate script
38
date_selected<-c("20000101") ##This is for year 2000!!!
39
raster_prediction_obj<-"raster_prediction_obj__365d_GAM_fus5_all_lstd_03132013.RData"
40
#out_prefix<-"_365d_GAM_fus5_all_lstd_03132013"
41
#out_prefix<-"_365d_GAM_fus5_all_lstd_03142013"                #User defined output prefix
42
out_prefix<-"_365d_GAM_fus5_all_lstd_03132013"                #User defined output prefix
43
var<-"TMAX"
44
#gam_fus_mod<-load_obj("gam_fus_mod_365d_GAM_fus5_all_lstd_02202013.RData")
45
#validation_obj<-load_obj("gam_fus_validation_mod_365d_GAM_fus5_all_lstd_02202013.RData")
46
#clim_obj<-load_obj("gamclim_fus_mod_365d_GAM_fus5_all_lstd_02202013.RData")
47

    
48
rnames<-c("x","y","lon","lat","N","E","N_w","E_w","elev","slope","aspect","CANHEIGHT","DISTOC")
49
lc_names<-c("LC1","LC2","LC3","LC4","LC5","LC6","LC7","LC8","LC9","LC10","LC11","LC12")
50
lst_names<-c("mm_01","mm_02","mm_03","mm_04","mm_05","mm_06","mm_07","mm_08","mm_09","mm_10","mm_11","mm_12",
51
             "nobs_01","nobs_02","nobs_03","nobs_04","nobs_05","nobs_06","nobs_07","nobs_08",
52
             "nobs_09","nobs_10","nobs_11","nobs_12")
53
covar_names<-c(rnames,lc_names,lst_names)
54

    
55
list_param<-list(in_path,out_path,script_path,raster_prediction_obj,infile_covar,covar_names,date_selected,var,out_prefix)
56
names(list_param)<-c("in_path","out_path","script_path","raster_prediction_obj",
57
                     "infile_covar","covar_names","date_selected","var","out_prefix")
58

    
59
setwd(in_path)
60

    
61
## make this a script that calls several function:
62
#1) covariate script
63
#2) plots by dates
64
#3) number of data points monthly and daily
65

    
66
### Functions used in the script
67

    
68
load_obj <- function(f) 
69
{
70
  env <- new.env()
71
  nm <- load(f, env)[1]	
72
  env[[nm]]
73
}
74

    
75
extract_number_obs<-function(list_param){
76
  
77
  method_mod_obj<-list_param$method_mod_obj
78
  #Change to results_mod_obj[[i]]$data_s to make it less specific
79
  lapply(1:length(method_obj),function(k) nrow(method_mod_obj[[k]]$data_s))
80
  lapply(1:length(method_obj),function(k) nrow(method_mod_obj[[k]]$data_v))
81
  lapply(1:length(clim_obj),function(k) nrow(method_mod_obj[[k]]$data_v))
82
  return()
83
}
84

    
85
### PLOTTING RESULTS FROM VENEZUELA INTERPOLATION FOR ANALYSIS
86
#source(file.path(script_path,"results_interpolation_date_output_analyses_03182013.R"))
87
#j=1
88
#plots_assessment_by_date(1,list_param)
89
plots_assessment_by_date<-function(j,list_param){
90
  
91
  date_selected<-list_param$date_selected
92
  var<-list_param$var
93
  #gam_fus_mod<-load_obj("gam_fus_mod_365d_GAM_fus5_all_lstd_02202013.RData")
94
  #validation_obj<-load_obj("gam_fus_validation_mod_365d_GAM_fus5_all_lstd_02202013.RData")
95
  #clim_obj<-load_obj("gamclim_fus_mod_365d_GAM_fus5_all_lstd_02202013.RData")
96
  
97
  raster_prediction_obj<-load_obj(list_param$raster_prediction_obj)
98
  #method_mod_obj<-raster_prediction_obj$method_mod_obj
99
  method_mod_obj<-raster_prediction_obj$gam_fus_mod #change later for any model type
100
  #validation_obj<-raster_prediction_obj$validation_obj
101
  validation_obj<-raster_prediction_obj$gam_fus_validation_mod #change later for any model type
102
  #clim_obj<-raster_prediction_obj$clim_obj
103
  clim_obj<-raster_prediction_obj$gamclim_fus_mod #change later for any model type
104
  
105
  if (var=="TMAX"){
106
    y_var_name<-"dailyTmax"                                       
107
  }
108
  if (var=="TMIN"){
109
    y_var_name<-"dailyTmin"                                       
110
  }
111
  
112
  ## Read covariate stack...
113
  covar_names<-list_param$covar_names
114
  s_raster<-brick(infile_covar)                   #read in the data stack
115
  names(s_raster)<-covar_names               #Assigning names to the raster layers: making sure it is included in the extraction
116
  
117
  ## Figure 0: study area based on LC12 (water) mask
118
  
119
  LC_mask<-subset(s_raster,"LC12")
120
  LC_mask[LC_mask==100]<-NA
121
  LC_mask <- LC_mask < 100
122
  LC_mask_rec<-LC_mask
123
  LC_mask_rec[is.na(LC_mask_rec)]<-0
124
  
125
  #Add proportion covered by study area+ total of image pixels
126
  tmp_tb<-freq(LC_mask_rec)
127
  tmp_tb[2,2]/sum(tmp_tb[,2])*100
128
  png(paste("Study_area_",
129
            out_prefix,".png", sep=""))
130
  plot(LC_mask_rec,legend=FALSE,col=c("black","red"))
131
  legend("topright",legend=c("Outside","Inside"),title="Study area",
132
         pt.cex=0.9,fill=c("black","red"),bty="n")
133
  title("Study area")
134
  dev.off()
135
  
136
  #determine index position matching date selected
137
  
138
  for (j in 1:length(date_selected)){
139
    for (i in 1:length(method_mod_obj)){
140
      if(method_mod_obj[[i]]$sampling_dat$date==date_selected[j]){  
141
        i_dates[[j]]<-i
142
      }
143
    }
144
  }
145
  #Examine the first select date add loop or function later
146
  #j=1
147
  date<-strptime(date_selected[j], "%Y%m%d")   # interpolation date being processed
148
  month<-strftime(date, "%m")          # current month of the date being processed
149
  
150
  #Get raster stack of interpolated surfaces
151
  index<-i_dates[[j]]
152
  pred_temp<-as.character(method_mod_obj[[index]]$dailyTmax) #list of files
153
  rast_pred_temp<-stack(pred_temp) #stack of temperature predictions from models 
154
  
155
  #Get validation metrics, daily spdf training and testing stations, monthly spdf station input
156
  sampling_dat<-method_mod_obj[[index]]$sampling_dat
157
  metrics_v<-validation_obj[[index]]$metrics_v
158
  metrics_s<-validation_obj[[index]]$metrics_s
159
  data_v<-validation_obj[[index]]$data_v
160
  data_s<-validation_obj[[index]]$data_s
161
  data_month<-clim_obj[[index]]$data_month
162
  formulas<-clim_obj[[index]]$formulas
163
  
164
  #Adding layer LST to the raster stack of covariates
165
  #The names of covariates can be changed...
166
  
167
  LST_month<-paste("mm_",month,sep="") # name of LST month to be matched
168
  pos<-match("LST",layerNames(s_raster)) #Find the position of the layer with name "LST", if not present pos=NA
169
  s_raster<-dropLayer(s_raster,pos)      # If it exists drop layer
170
  pos<-match(LST_month,layerNames(s_raster)) #Find column with the current month for instance mm12
171
  r1<-raster(s_raster,layer=pos)             #Select layer from stack
172
  layerNames(r1)<-"LST"
173
  #Get mask image!!
174
  
175
  date_proc<-strptime(sampling_dat$date, "%Y%m%d")   # interpolation date being processed
176
  mo<-as.integer(strftime(date_proc, "%m"))          # current month of the date being processed
177
  day<-as.integer(strftime(date_proc, "%d"))
178
  year<-as.integer(strftime(date_proc, "%Y"))
179
  datelabel=format(ISOdate(year,mo,day),"%b %d, %Y")
180
  
181
  ## Figure 1: LST_TMax_scatterplot 
182
  
183
  rmse<-metrics_v$rmse[nrow(metrics_v)]
184
  rmse_f<-metrics_s$rmse[nrow(metrics_s)]  
185
  
186
  png(paste("LST_TMax_scatterplot_",sampling_dat$date,"_",sampling_dat$prop,"_",sampling_dat$run_samp,
187
            out_prefix,".png", sep=""))
188
  plot(data_month$TMax,data_month$LST,xlab="Station mo Tmax",ylab="LST mo Tmax")
189
  title(paste("LST vs TMax for",datelabel,sep=" "))
190
  abline(0,1)
191
  nb_point<-paste("n=",length(data_month$TMax),sep="")
192
  mean_bias<-paste("Mean LST bias= ",format(mean(data_month$LSTD_bias,na.rm=TRUE),digits=3),sep="")
193
  #Add the number of data points on the plot
194
  legend("topleft",legend=c(mean_bias,nb_point),bty="n")
195
  dev.off()
196
  
197
  ## Figure 2: Daily_tmax_monthly_TMax_scatterplot, modify for TMin!!
198
  
199
  png(paste("Daily_tmax_monthly_TMax_scatterplot_",sampling_dat$date,"_",sampling_dat$prop,"_",sampling_dat$run_samp,
200
            out_prefix,".png", sep=""))
201
  plot(dailyTmax~TMax,data=data_s,xlab="Mo Tmax",ylab=paste("Daily for",datelabel),main="across stations in VE")
202
  nb_point<-paste("ns=",length(data_s$TMax),sep="")
203
  nb_point2<-paste("ns_obs=",length(data_s$TMax)-sum(is.na(data_s[[y_var_name]])),sep="")
204
  nb_point3<-paste("n_month=",length(data_month$TMax),sep="")
205
  #Add the number of data points on the plot
206
  legend("topleft",legend=c(nb_point,nb_point2,nb_point3),bty="n",cex=0.8)
207
  dev.off()
208
  
209
  ## Figure 3: Predicted_tmax_versus_observed_scatterplot 
210
  
211
  #This is for mod_kr!! add other models later...
212
  png(paste("Predicted_tmax_versus_observed_scatterplot_",sampling_dat$date,"_",sampling_dat$prop,"_",sampling_dat$run_samp,
213
            out_prefix,".png", sep=""))
214
  #plot(data_s$mod_kr~data_s[[y_var_name]],xlab=paste("Actual daily for",datelabel),ylab="Pred daily")
215
  
216
  y_range<-range(c(data_s$mod_kr,data_v$mod_kr),na.rm=T)
217
  x_range<-range(c(data_s[[y_var_name]],data_v[[y_var_name]]),na.rm=T)
218
  col_t<- c("black","red")
219
  pch_t<- c(1,2)
220
  plot(data_s$mod_kr,data_s[[y_var_name]], 
221
       xlab=paste("Actual daily for",datelabel),ylab="Pred daily", 
222
       ylim=y_range,xlim=x_range,col=col_t[1],pch=pch_t[1])
223
  points(data_v$mod_kr,data_v[[y_var_name]],col=col_t[2],pch=pch_t[2])
224
  grid(lwd=0.5, col="black")
225
  #plot(data_v$mod_kr~data_v[[y_var_name]],xlab=paste("Actual daily for",datelabel),ylab="Pred daily")
226
  abline(0,1)
227
  legend("topleft",legend=c("training","testing"),pch=pch_t,col=col_t,bty="n",cex=0.8)
228
  title(paste("Predicted_tmax_versus_observed_scatterplot for",datelabel,sep=" "))
229
  nb_point1<-paste("ns_obs=",length(data_s$TMax)-sum(is.na(data_s[[y_var_name]])),sep="")
230
  rmse_str1<-paste("RMSE= ",format(rmse,digits=3),sep="")
231
  rmse_str2<-paste("RMSE_f= ",format(rmse_f,digits=3),sep="")
232
  
233
  #Add the number of data points on the plot
234
  legend("bottomright",legend=c(nb_point1,rmse_str1,rmse_str2),bty="n",cex=0.8)
235
  dev.off()
236
  
237
  ## Figure 5: prediction raster images
238
  png(paste("Raster_prediction_",sampling_dat$date,"_",sampling_dat$prop,"_",sampling_dat$run_samp,
239
            out_prefix,".png", sep=""))
240
  #paste(metrics_v$pred_mod,format(metrics_v$rmse,digits=3),sep=":")
241
  names(rast_pred_temp)<-paste(metrics_v$pred_mod,format(metrics_v$rmse,digits=3),sep=":")
242
  #plot(rast_pred_temp)
243
  levelplot(rast_pred_temp)
244
  dev.off()
245
  
246
  ## Figure 5b: prediction raster images
247
  png(paste("Raster_prediction_plot",sampling_dat$date,"_",sampling_dat$prop,"_",sampling_dat$run_samp,
248
            out_prefix,".png", sep=""))
249
  #paste(metrics_v$pred_mod,format(metrics_v$rmse,digits=3),sep=":")
250
  names(rast_pred_temp)<-paste(metrics_v$pred_mod,format(metrics_v$rmse,digits=3),sep=":")
251
  #plot(rast_pred_temp)
252
  plot(rast_pred_temp)
253
  dev.off()
254
  
255
  ## Figure 6: training and testing stations used
256
  png(paste("Training_testing_stations_map_",sampling_dat$date,"_",sampling_dat$prop,"_",sampling_dat$run_samp,
257
            out_prefix,".png", sep=""))
258
  plot(raster(rast_pred_temp,layer=5))
259
  plot(data_s,col="black",cex=1.2,pch=2,add=TRUE)
260
  plot(data_v,col="red",cex=1.2,pch=1,add=TRUE)
261
  legend("topleft",legend=c("training stations", "testing stations"), 
262
         cex=1, col=c("black","red"),
263
         pch=c(2,1),bty="n")
264
  dev.off()
265
  
266
  ## Figure 7: monthly stations used
267
  
268
  png(paste("Monthly_data_study_area",
269
            out_prefix,".png", sep=""))
270
  plot(raster(rast_pred_temp,layer=5))
271
  plot(data_month,col="black",cex=1.2,pch=4,add=TRUE)
272
  title("Monthly ghcn station in Venezuela for January")
273
  dev.off()
274
  
275
  ## Figure 8: delta surface and bias
276
  
277
  png(paste("Bias_delta_surface_",sampling_dat$date[i],"_",sampling_dat$prop[i],
278
            "_",sampling_dat$run_samp[i],out_prefix,".png", sep=""))
279
  
280
  bias_rast<-stack(clim_obj[[index]]$bias)
281
  delta_rast<-raster(method_mod_obj[[index]]$delta) #only one delta image!!!
282
  names(delta_rast)<-"delta"
283
  rast_temp_date<-stack(bias_rast,delta_rast)
284
  rast_temp_date<-mask(rast_temp_date,LC_mask,file="test.tif",overwrite=TRUE)
285
  #bias_d_rast<-raster("fusion_bias_LST_20100103_30_1_10d_GAM_fus5_all_lstd_02082013.rst")
286
  plot(rast_temp_date)
287
  
288
  dev.off()
289
  
290
  #Figure 9: histogram for all images...
291
  
292
  #histogram(rast_pred_temp)
293
  list_output_analyses<-list(metrics_s,metrics_v)
294
  return(list_output_analyses)
295
  
296
}
297

    
298

    
299

    
300
## Summarize information for the day: write out textfile...
301

    
302
#Number of station per month
303
#Number of station per day (training, testing,NA)
304
#metrics_v,metrics_s
305
#
306

    
307
# ################
308
# #PART 2: Region Covariate analyses ###
309
# ################
310
# 
311
# # This should be in a separate script to analyze covariates from region.
312
# 
313
# #MAP1:Study area with LC mask and tiles/polygon outline
314
# 
315
# 
316
# #MAP 2: plotting land cover in the study region:
317
# 
318
# l1<-"LC1,Evergreen/deciduous needleleaf trees"
319
# l2<-"LC2,Evergreen broadleaf trees"
320
# l3<-"LC3,Deciduous broadleaf trees"
321
# l4<-"LC4,Mixed/other trees"
322
# l5<-"LC5,Shrubs"
323
# l6<-"LC6,Herbaceous vegetation"
324
# l7<-"LC7,Cultivated and managed vegetation"
325
# l8<-"LC8,Regularly flooded shrub/herbaceous vegetation"
326
# l9<-"LC9,Urban/built-up"
327
# l10<-"LC10,Snow/ice"
328
# l11<-"LC11,Barren lands/sparse vegetation"
329
# l12<-"LC12,Open water"
330
# lc_names_str<-c(l1,l2,l3,l4,l5,l6,l7,l8,l9,l10,l11,l12)
331
# 
332
# names(lc_reg_s)<-lc_names_str
333
# 
334
# png(paste("LST_TMax_scatterplot_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i], out_prefix,".png", sep=""))
335
# plot(modst$TMax,sta_tmax_from_lst,xlab="Station mo Tmax",ylab="LST mo Tmax",main=paste("LST vs TMax for",datelabel,sep=" "))
336
# abline(0,1)
337
# nb_point<-paste("n=",length(modst$TMax),sep="")
338
# mean_bias<-paste("LST bigrasas= ",format(mean(modst$LSTD_bias,na.rm=TRUE),digits=3),sep="")
339
# #Add the number of data points on the plot
340
# legend("topleft",legend=c(mean_bias,nb_point),bty="n")
341
# dev.off()
342
# 
343
# #Map 3: Elevation and LST in January
344
# tmp_s<-stack(LST,elev_1)
345
# png(paste("LST_elev_",sampling_dat$date[i],"_",sampling_dat$prop[i],"_",sampling_dat$run_samp[i], out_prefix,".png", sep=""))
346
# plot(tmp_s)
347
# 
348
# #Map 4: LST climatology per month
349
#         
350
# names_tmp<-c("mm_01","mm_02","mm_03","mm_04","mm_05","mm_06","mm_07","mm_08","mm_09","mm_10","mm_11","mm_12")
351
# LST_s<-subset(s_raster,names_tmp)
352
# names_tmp<-c("nobs_01","nobs_02","nobs_03","nobs_04","nobs_05","nobs_06","nobs_07","nobs_08",
353
#              "nobs_09","nobs_10","nobs_11","nobs_12")
354
# LST_nobs<-subset(s_raster,names_tmp)
355
# 
356
# LST_nobs<-mask(LST_nobs,LC_mask,filename="test2.tif")
357
# LST_s<-mask(LST_s,LC_mask,filename="test3.tif")
358
# c("Jan","Feb")
359
# plot(LST_s)
360
# plot(LST_nobs)
361
# 
362
# #Map 5: LST and TMax
363
# 
364
# #note differnces in patternin agricultural areas and 
365
# min_values<-cellStats(LST_s,"min")
366
# max_values<-cellStats(LST_s,"max")
367
# mean_values<-cellStats(LST_s,"mean")
368
# sd_values<-cellStats(LST_s,"sd")
369
# #median_values<-cellStats(molst,"median") Does not extist
370
# statistics_LST_s<-cbind(min_values,max_values,mean_values,sd_values) #This shows that some values are extremes...especially in October
371
# LST_stat_data<-as.data.frame(statistics_LST_s)
372
# names(LST_stat_data)<-c("min","max","mean","sd")
373
# # Statistics for number of valid observation stack
374
# min_values<-cellStats(nobslst,"min")
375
# max_values<-cellStats(nobslst,"max")
376
# mean_values<-cellStats(nobslst,"mean")
377
# sd_values<-cellStats(nobslst,"sd")
378
# statistics_LSTnobs_s<-cbind(min_values,max_values,mean_values,sd_values) #This shows that some values are extremes...especially in October
379
# LSTnobs_stat_data<-as.data.frame(statistics_LSTnobs_s)
380
# 
381
# X11(width=12,height=12)
382
# #Plot statiscs (mean,min,max) for monthly LST images
383
# plot(1:12,LST_stat_data$mean,type="b",ylim=c(-15,60),col="black",xlab="month",ylab="tmax (degree C)")
384
# lines(1:12,LST_stat_data$min,type="b",col="blue")
385
# lines(1:12,LST_stat_data$max,type="b",col="red")
386
# text(1:12,LST_stat_data$mean,rownames(LST_stat_data),cex=1,pos=2)
387
# 
388
# legend("topleft",legend=c("min","mean","max"), cex=1.5, col=c("blue","black","red"),
389
#        lty=1)
390
# title(paste("LST statistics for Oregon", "2010",sep=" "))
391
# savePlot("lst_statistics_OR.png",type="png")
392
# 
393
# #Plot number of valid observations for LST
394
# plot(1:12,LSTnobs_stat_data$mean,type="b",ylim=c(0,280),col="black",xlab="month",ylab="tmax (degree C)")
395
# lines(1:12,LSTnobs_stat_data$min,type="b",col="blue")
396
# lines(1:12,LSTnobs_stat_data$max,type="b",col="red")
397
# text(1:12,LSTnobs_stat_data$mean,rownames(LSTnobs_stat_data),cex=1,pos=2)
398
# 
399
# legend("topleft",legend=c("min","mean","max"), cex=1.5, col=c("blue","black","red"),
400
#        lty=1)
401
# title(paste("LST number of valid observations for Oregon", "2010",sep=" "))
402
# savePlot("lst_nobs_OR.png",type="png")
403
# 
404
# plot(data_month$TMax,add=TRUE)
405
# 
406
# ### Map 6: station in the region
407
# 
408
# plot(tmax_predicted)
409
# plot(data_s,col="black",cex=1.2,pch=4,add=TRUE)
410
# plot(data_v,col="blue",cex=1.2,pch=2,add=TRUE)
411
# 
412
# plot(tmax_predicted)
413
# plot(data_month,col="black",cex=1.2,pch=4,add=TRUE)
414
# title("Monthly ghcn station in Venezuela for 2000-2010")
415
# 
416
#png...output?
417
# plot(interp_area, axes =TRUE)
418
# plot(stat_reg, pch=1, col="red", cex= 0.7, add=TRUE)
419
# plot(data_reg,pch=2,col="blue",cex=2,add=TRUE)
420

    
421
#### End of script ####
(39-39/40)