Project

General

Profile

« Previous | Next » 

Revision 8a7857ec

Added by Benoit Parmentier over 9 years ago

mosaicing test script splitting function from script and clean up

View differences:

climate/research/oregon/interpolation/global_run_scalingup_mosaicing.R
5 5
#Analyses, figures, tables and data are also produced in the script.
6 6
#AUTHOR: Benoit Parmentier 
7 7
#CREATED ON: 04/14/2015  
8
#MODIFIED ON: 06/15/2015            
8
#MODIFIED ON: 06/16/2015            
9 9
#Version: 4
10 10
#PROJECT: Environmental Layers project     
11 11
#COMMENTS: analyses run for reg5 for test of mosaicing using 1500x4500km and other tiles
......
48 48

  
49 49
#### FUNCTION USED IN SCRIPT
50 50

  
51
function_analyses_paper1 <-"contribution_of_covariates_paper_interpolation_functions_07182014.R" #first interp paper
52
function_analyses_paper2 <-"multi_timescales_paper_interpolation_functions_08132014.R"
53

  
54
load_obj <- function(f)
55
{
56
  env <- new.env()
57
  nm <- load(f, env)[1]
58
  env[[nm]]
59
}
60

  
61
create_dir_fun <- function(out_dir,out_suffix){
62
  if(!is.null(out_suffix)){
63
    out_name <- paste("output_",out_suffix,sep="")
64
    out_dir <- file.path(out_dir,out_name)
65
  }
66
  #create if does not exists
67
  if(!file.exists(out_dir)){
68
    dir.create(out_dir)
69
  }
70
  return(out_dir)
71
}
72

  
73
sine_structure_fun <-function(x,T,phase,a,b,use_cos=FALSE){
74
  
75
  #Create sine for a one dimensional series
76
  #Note that sine function uses radian unit.
77
  #a=amplitude
78
  #b=mean or amplitude 0 of the series
79
  #T= stands for period definition
80
  #phase=phase angle (in radian!!)
81
  #cos: use cosine instead of sine if TRUE
82
  
83
  if(use_cos==FALSE){
84
    y <- a*sin((x*pi/T)+ phase) + b
85
  }else{
86
    y <- a*cos((x*pi/T)+ phase) + b
87
  }
88
  return(y)
89
}
90

  
91
create_weights_fun <- function(i, list_param){
92
  #This function generates weights from a point location on a raster layer.
93
  #Note that the weights are normatlized on 0-1 scale using max and min values.
94
  #Inputs:
95
  #lf: list of raster files
96
  #df_points: reference points from which to compute distance
97
  #r_feature: reference features as raster image from which to compute distance from
98
  #methods: options available: use_sine_weights,use_edge,use_linear_weights
99
  #Outputs:
100
  #raster list of weights and product of wegihts and inuts
101
  #TODO: 
102
  # -use gdal proximity for large files and use_edge option
103
  # - add raster options
104
  # - improve efficiency
105
  # - change name options
106
  #
107
  ############
108
  
109
  lf <- list_param$lf
110
  df_points <- list_param$df_points
111
  r_feature <- list_param$r_feature #this should be change to a list
112
  padding <- TRUE #if padding true then make buffer around edges??
113
  method <- list_param$method #differnt methods available to create weights
114
  #NAflag,file_format,out_suffix etc...
115
  out_dir_str <- list_param$out_dir_str
116
    
117
  ####### START SCRIPT #####
118
  
119
  r_in <- raster(lf[i]) #input image
120
  tile_no <- i
121
  
122
  set1f <- function(x){rep(NA, x)}
123
  r_init <- init(r_in, fun=set1f)
124

  
125
  if(!is.null(r_feature)){
126
    r_init <- r_feature
127
  }
128

  
129
  if(!is.null(df_points)){ #reference points as SPDF object
130
    cell_ID <- cellFromXY(r_init,xy=df_points[i,])
131
    r_init[cell_ID] <- df_points$ID[i]
132
  }
133

  
134
  if(method=="use_sine_weights"){
135
    #Generate spatial pattern 5:     
136
    n_col <- ncol(r_init)
137
    n_row <- nrow(r_init)
138

  
139
    #u <- xFromCol(r_init,col=1:n_col)
140
    #add padding option later...buffer from a specific distance and tailling of at 0.1
141
    u <- 1:n_col
142
    a<- 1 #amplitude in this case
143
    b<- 0
144
    T<- n_col
145
    phase <- 0
146
    use_cos <- FALSE
147
    ux <- sine_structure_fun(u,T,phase,a,b,use_cos)
148
    ux_rep <-rep(ux,time=n_row)  
149
    r1 <-setValues(r_init,ux_rep)  #note efficient in memory might need to revise this
150
    #plot(r)
151
  
152
    v <- 1:n_row
153
    a<- 1 #amplitude in this case
154
    b<- 0
155
    T<- n_row
156
    phase <- 0
157
    use_cos <- FALSE
158
    vx <- sine_structure_fun(v,T,phase,a,b,use_cos)
159
    vx_rep <- unlist((lapply(1:n_row,FUN=function(j){rep(vx[j],time=n_col)})))  
160
  
161
    r2 <-setValues(r_init,vx_rep)  
162
    #plot(r2)
163
 
164
    r <- (r1+r2)*0.5  #combine patterns to make a elliptic surface, -0.5 could be modified
165
    #plot(r)
166
  }
167

  
168
  #change here to distance from edges..
169
  if(method=="use_edge"){ #does not work with large images
170
      #change...use gdal
171
      n_col <- ncol(r_init)
172
      n_row <- nrow(r_init)
173
    
174
      #xfrom
175
      r_init[1,1:n_col] <- 1
176
      r_init[n_row,1:n_col] <- 1
177
      r_init[1:n_row,1] <- 1
178
      r_init[1:n_row,n_col] <- 1
179
      #r_dist <- distance(r_init)
180
      srcfile <- file.path(out_dir,paste("feature_target_",tile_no,".tif",sep=""))
181

  
182
      writeRaster(r_init,filename=srcfile,overwrite=T)
183
      dstfile <- file.path(out_dir,paste("feature_target_edge_distance",tile_no,".tif",sep=""))
184
      n_values <- "1"
185
        
186
      cmd_str <- paste("gdal_proximity.py", srcfile, dstfile,"-values",n_values,sep=" ")
187
      system(cmd_str)
188
      r_dist<- raster(dstfile)
189
      min_val <- cellStats(r_dist,min) 
190
      max_val <- cellStats(r_dist,max)
191
      r <- abs(r_dist - min_val)/ (max_val - min_val) #no need to inverse...
192
  } #too slow with R so used http://www.gdal.org/gdal_proximity.html
193
  
194
  if(method=="use_linear_weights"){
195
    #
196
    r_dist <- distance(r_init)
197
    min_val <- cellStats(r_dist,min) 
198
    max_val <- cellStats(r_dist,max)
199
    r <- abs(r_dist - max_val)/ (max_val - min_val)
200
  }
201
  
202
  extension_str <- extension(lf[i])
203
  raster_name_tmp <- gsub(extension_str,"",basename(lf[i]))
204
  raster_name <- file.path(out_dir_str,paste(raster_name_tmp,"_",method,"_weights.tif",sep=""))
205
  writeRaster(r, NAflag=NA_flag_val,filename=raster_name,overwrite=TRUE)  
206
  
207
  r_var_prod <- r_in*r
208
  raster_name_prod <- file.path(out_dir_str, paste(raster_name_tmp,"_",method,"_prod_weights.tif",sep=""))
209
  writeRaster(r_var_prod, NAflag=NA_flag_val,filename=raster_name_prod,overwrite=TRUE)  
210
    
211
  weights_obj <- list(raster_name,raster_name_prod)
212
  names(weights_obj) <- c("r_weights","r_weights_prod")
213
  return(weights_obj)
214
}
215

  
216
mosaic_m_raster_list<-function(j,list_param){
217
  #This functions returns a subset of tiles from the modis grid.
218
  #Arguments: modies grid tile,list of tiles
219
  #Output: spatial grid data frame of the subset of tiles
220
  #Note that rasters are assumed to be in the same projection system!!
221
  #modified for global mosaic...still not working right now...
222
  
223
  #rast_list<-vector("list",length(mosaic_list))
224
  #for (i in 1:length(mosaic_list)){  
225
  # read the individual rasters into a list of RasterLayer objects
226
  # this may be changed so that it is not read in the memory!!!
227
  
228
  #parse output...
229
  
230
  #j<-list_param$j
231
  mosaic_list<-list_param$mosaic_list
232
  out_path<-list_param$out_path
233
  out_names<-list_param$out_rastnames
234
  file_format <- list_param$file_format
235
  NA_flag_val <- list_param$NA_flag_val
236
  out_suffix <- list_param$out_suffix
237
  ## Start
238
  
239
  if(class(mosaic_list[[j]])=="list"){
240
    m_list <- unlist(mosaic_list[[j]])
241
  }else{
242
    m_list <- mosaic_list[[j]]
243
  }
244
  input.rasters <- lapply(m_list, raster) #create raster image for each element of the list
245
  #inMemory(input.rasters[[1]])
246
  #note that input.rasters are not stored in memory!!
247
  mosaiced_rast<-input.rasters[[1]]
248
  
249
  for (k in 2:length(input.rasters)){
250
    mosaiced_rast<-mosaic(mosaiced_rast,input.rasters[[k]], tolerance=1,fun=mean)
251
    #mosaiced_rast<-mosaic(mosaiced_rast,raster(input.rasters[[k]]), fun=mean)
252
  }
253
  
254
  data_name<-paste("mosaiced_",sep="") #can add more later...
255
  #raster_name<-paste(data_name,out_names[j],".tif", sep="")
256
  raster_name<-paste(data_name,out_names[j],file_format, sep="")
257
  
258
  writeRaster(mosaiced_rast, NAflag=NA_flag_val,filename=file.path(out_path,raster_name),overwrite=TRUE)  
259
  #Writing the data in a raster file format...  
260
  rast_list<-file.path(out_path,raster_name)
261
  
262
  ## The Raster and rgdal packages write temporary files on the disk when memory is an issue. This can potential build up
263
  ## in long  loops and can fill up hard drives resulting in errors. The following  sections removes these files 
264
  ## as they are created in the loop. This code section  can be transformed into a "clean-up function later on
265
  ## Start remove
266
  #tempfiles<-list.files(tempdir(),full.names=T) #GDAL transient files are not removed
267
  #files_to_remove<-grep(out_suffix,tempfiles,value=T) #list files to remove
268
  #if(length(files_to_remove)>0){
269
  #  file.remove(files_to_remove)
270
  #}
271
  #now remove temp files from raster package located in rasterTmpDir
272
  removeTmpFiles(h=0) #did not work if h is not set to 0
273
  ## end of remove section
274
  
275
  return(rast_list)
276
}
277

  
278
raster_match <- function(i,list_param){
279
  ### Read in parameters/arguments
280
  lf_files <- list_param$lf_files
281
  rast_ref <- list_param$rast_ref #name of reference file
282
  file_format <- list_param$file_format #".tif",".rst" or others
283
  out_suffix <- list_param$out_suffix
284
  out_dir_str <- list_param$out_dir_str
285
    
286
  ### START SCRIPT ##
287
  
288
  r_m <- raster(rast_ref) #ref image with resolution and extent to match
289

  
290
  set1f <- function(x){rep(NA, x)}
291
  
292
  inFilename <- lf_files[i]
293
  
294
  extension_str <- extension(inFilename)
295
  raster_name_tmp <- gsub(extension_str,"",basename(inFilename))
296
  #outFilename <- file.path(out_dir,paste(raster_name_tmp,"_","m_",out_suffix,file_format,sep="")) #for use in function later...
297
  
298
  raster_name <- file.path(out_dir_str,paste(raster_name_tmp,"_","m_",out_suffix,file_format,sep=""))#output file
299
  r_ref <- init(r_m, fun=set1f, filename=raster_name, overwrite=TRUE)
300
  #NAvalue(r_ref) <- -9999
301

  
302
  cmd_str <- paste("/usr/bin/gdalwarp",inFilename,raster_name,sep=" ") 
303
  #gdalwarp -t_srs '+proj=utm +zone=11 +datum=WGS84' raw_spot.tif utm11.tif
304

  
305
  system(cmd_str)
306
  
307
  ##return name of file created
308
  return(raster_name)
309
}
310

  
311
mosaicFiles <- function(lf_mosaic,mosaic_method,num_cores,python_bin=NULL,df_points=NULL,NA_flag_val=-9999,file_format=".tif",out_suffix=NULL,out_dir=NULL){
312
  
313
  out_dir_str <- out_dir
314

  
315
  lf_r_weights <- vector("list",length=length(lf_mosaic))
316
  
317
  ###############
318
  ### PART 2: prepare weights using tile rasters ############
319
  #methods availbable:use_sine_weights,use_edge,use_linear_weights
320

  
321
  if(mosaic_method=="use_linear_weights"){
322
    method <- "use_linear_weights"
323
    df_points <- df_centroids
324
    #df_points <- NULL
325
    r_feature <- NULL
326

  
327
    list_param_create_weights <- list(lf_mosaic,df_points,r_feature,method,out_dir_str) 
328
    names(list_param_create_weights) <- c("lf","df_points","r_feature","method","out_dir_str") 
329
    #num_cores <- 11
330

  
331
    #debug(create_weights_fun)
332
    weights_obj <- create_weights_fun(1,list_param=list_param_create_weights)
333

  
334
    #This is the function creating the weights by tile. Distance from the centroids needs to be change from distance to
335
    #the edges...can use rows and columsn to set edges to 1 and 0 for the others.
336
    linear_weights_obj_list <- mclapply(1:length(lf_mosaic),FUN=create_weights_fun,list_param=list_param_create_weights,mc.preschedule=FALSE,mc.cores = num_cores)                           
337

  
338
    list_linear_r_weights <- lapply(1:length(linear_weights_obj_list), FUN=function(i,x){x[[i]]$r_weights},x=linear_weights_obj_list)
339
    list_linear_r_weights_prod <- lapply(1:length(linear_weights_obj_list), FUN=function(i,x){x[[i]]$r_weights_prod},x=linear_weights_obj_list)
340

  
341
    list_weights <- list_linear_r_weights
342
    list_weights_prod <- list_linear_r_weights_prod 
343

  
344
  }
345
  if(mosaic_method=="use_sine_weights"){
346
    
347
    ### Third use sine weights
348
    method <- "use_sine_weights"
349
    #df_points <- df_centroids
350
    df_points <- NULL
351
    r_feature <- NULL
352

  
353
    list_param_create_weights <- list(lf_mosaic,df_points,r_feature,method,out_dir_str) 
354
    names(list_param_create_weights) <- c("lf","df_points","r_feature","method","out_dir_str") 
355
    #num_cores <- 11
356

  
357
    #debug(create_weights_fun)
358
    weights_obj <- create_weights_fun(1,list_param=list_param_create_weights)
359

  
360
    #This is the function creating the weights by tile. Distance from the centroids needs to be change from distance to
361
    #the edges...can use rows and columsn to set edges to 1 and 0 for the others.
362
    sine_weights_obj_list <- mclapply(1:length(lf_mosaic),FUN=create_weights_fun,list_param=list_param_create_weights,mc.preschedule=FALSE,mc.cores = num_cores)                           
363

  
364
    list_sine_r_weights <- lapply(1:length(sine_weights_obj_list), FUN=function(i,x){x[[i]]$r_weights},x=sine_weights_obj_list)
365
    list_sine_r_weights_prod <- lapply(1:length(sine_weights_obj_list), FUN=function(i,x){x[[i]]$r_weights_prod},x=sine_weights_obj_list)
366

  
367
    list_weights <- list_sine_r_weights
368
    list_weights_prod <- list_sine_r_weights_prod 
369

  
370
  }
371
  
372
  if(mosaic_method=="use_edge_weights"){
373
    
374
    method <- "use_edge"
375
    df_points <- NULL
376
    r_feature <- NULL
377
    list_param_create_weights <- list(lf_mosaic,df_points,r_feature,method,out_dir_str) 
378
    names(list_param_create_weights) <- c("lf","df_points","r_feature","method","out_dir_str") 
379
    #num_cores <- 11
380

  
381
    weights_obj <- create_weights_fun(1,list_param=list_param_create_weights)
382

  
383
    #This is the function creating the weights by tile. Distance from the centroids needs to be change from distance to
384
    #the edges...can use rows and columsn to set edges to 1 and 0 for the others.
385
    use_edge_weights_obj_list <- mclapply(1:length(lf_mosaic),FUN=create_weights_fun,list_param=list_param_create_weights,mc.preschedule=FALSE,mc.cores = num_cores)                           
386

  
387
    list_edge_r_weights <- lapply(1:length(use_edge_weights_obj_list), FUN=function(i,x){x[[i]]$r_weights},x=use_edge_weights_obj_list)
388
    list_edge_r_weights_prod <- lapply(1:length(use_edge_weights_obj_list), FUN=function(i,x){x[[i]]$r_weights_prod},x=use_edge_weights_obj_list)
389
    
390
    #simplifly later...
391
    list_weights <- list_edge_r_weights
392
    list_weights_prod <- list_edge_r_weights_prod 
393
    #r_test <- raster(list_edge_r_weights[[1]])
394

  
395
  }
396
  
397
  ###############
398
  ### PART 3: prepare weightsfor mosaicing by matching extent ############
399

  
400
  ## Rasters tiles vary slightly in resolution, they need to be matched for the mosaic. Resolve issue in the 
401
  #mosaic funciton using gdal_merge to compute a reference image to mach.
402

  
403
  rast_ref <- file.path(out_dir,paste("avg_",out_suffix,file_format,sep="")) #this is a the ref
404

  
405
  cmd_str <- paste("python","/usr/bin/gdal_merge.py","-o ",rast_ref,paste(lf_mosaic,collapse=" ")) 
406
  system(cmd_str)
407

  
408
  ## Create raster image for original predicted images with matching resolution and extent to the mosaic (reference image)
409

  
410
  #rast_ref <- file.path(out_dir,"avg.tif")
411
  r_ref <- raster(rast_ref)
412
  #plot(r_ref)
413
  
414
  if(mosaic_method%in%c("use_linear_weights","use_sine_weights","use_edge_weights")){
415
    
416
    lf_files <- unlist(list_weights)
417

  
418
    list_param_raster_match <- list(lf_files,rast_ref,file_format,out_suffix,out_dir)
419
    names(list_param_raster_match) <- c("lf_files","rast_ref","file_format","out_suffix","out_dir_str")
420

  
421
    #debug(raster_match)
422
    #r_test <- raster(raster_match(1,list_param_raster_match))
423

  
424
    list_weights_m <- mclapply(1:length(lf_files),FUN=raster_match,list_param=list_param_raster_match,mc.preschedule=FALSE,mc.cores = num_cores)                           
425

  
426
    lf_files <- unlist(list_weights_prod)
427
    list_param_raster_match <- list(lf_files,rast_ref,file_format,out_suffix,out_dir)
428
    names(list_param_raster_match) <- c("lf_files","rast_ref","file_format","out_suffix","out_dir_str")
429

  
430
    #num_cores <-11
431
    list_weights_prod_m <- mclapply(1:length(lf_files),FUN=raster_match,list_param=list_param_raster_match,mc.preschedule=FALSE,mc.cores = num_cores)                           
432

  
433
    #####################
434
    ###### PART 4: compute the weighted mean with the mosaic function #####
435

  
436
    ##Make this a function later
437
    #list_weights_m <- list(list_linear_weights_m,list_edge_weights_m,list_sine_weights_m)
438
    #list_weights_prod_m <- list(list_linear_weights_prod_m,list_edge_weights_prod_m,list_sine_weights_prod_m)
439
    #list_methods <- c("linear","edge","sine")
440
    list_mosaiced_files <- vector("list",length=1)
441

  
442
    list_args_weights <- list_weights_m
443
    list_args_weights_prod <- list_weights_prod_m
444
    method_str <- method
445
  
446
    #list_args_weights <- (mixedsort(list.files(pattern="r_weights_m_.*.tif")))
447
    list_args_weights <- lapply(1:length(list_args_weights), FUN=function(i,x){raster(x[[i]])},x=list_args_weights)
448

  
449
    #get the list of weights product into raster objects
450
    #list_args_weights_prod <- list_weights_prod_m
451
    #list_args_weights_prod <- (mixedsort(list.files(pattern="r_weights_prod_m_.*.tif")))
452
    list_args_weights_prod <- lapply(1:length(list_args_weights_prod), FUN=function(i,x){raster(x[[i]])},x=list_args_weights_prod)
453

  
454
    list_args_weights_prod$fun <- "sum"
455
    list_args_weights_prod$na.rm <- TRUE
456
    
457
    list_args_weights$fun <- "sum" #we want the sum to compute the weighted mean
458
    list_args_weights$na.rm <- TRUE
459

  
460
    #Mosaic files
461
    r_weights_sum <- do.call(mosaic,list_args_weights) #weights sum image mosaiced
462
    r_prod_sum <- do.call(mosaic,list_args_weights_prod) #weights sum product image mosacied
463

  
464
    r_m_weighted_mean <- r_prod_sum/r_weights_sum #this is the mosaic using weighted mean...
465
    raster_name <- file.path(out_dir,paste("r_m_",method_str,"_weighted_mean_",out_suffix,".tif",sep=""))
466
    writeRaster(r_m_weighted_mean, NAflag=NA_flag_val,filename=raster_name,overwrite=TRUE)  
467
    
468
  }
469

  
470
  if(mosaic_method=="unweighted"){
471
    #### Fourth use original images
472
    #macth file to mosaic extent using the original predictions
473
    lf_files <- lf_mosaic
474
    list_param_raster_match <- list(lf_files,rast_ref,file_format,out_suffix,out_dir)
475
    names(list_param_raster_match) <- c("lf_files","rast_ref","file_format","out_suffix","out_dir_str")
476

  
477
    list_pred_m <- mclapply(1:length(lf_files),FUN=raster_match,list_param=list_param_raster_match,mc.preschedule=FALSE,mc.cores = num_cores)                           
478

  
479
    #list_mosaiced_files <- list.files(pattern="r_m.*._weighted_mean_.*.tif")
480

  
481
    #names(list_mosaiced_files) <- c("edge","linear","sine")
482
  
483
    #### NOW unweighted mean mosaic
484

  
485
    #get the original predicted image to raster (matched previously to the mosaic extent)
486
    list_args_pred_m <- list_pred_m
487
    #list_args_pred_m <- (mixedsort(list.files(pattern="^gam_CAI.*.m_mosaic_run10_1500x4500_global_analyses_03252015.tif")))
488
    list_args_pred_m <- lapply(1:length(list_args_pred_m), FUN=function(i,x){raster(x[[i]])},x=list_args_pred_m)
489

  
490
    list_args_pred_m$fun <- "mean"
491
    list_args_pred_m$na.rm <- TRUE
492

  
493
    #Mosaic files
494
    r_m_mean <- do.call(mosaic,list_args_pred_m) #this is unweighted mean from the predicted raster
495

  
496
    raster_name <- file.path(out_dir,paste("r_m_mean_",out_suffix,".tif",sep=""))
497
    writeRaster(r_m_mean, NAflag=NA_flag_val,filename=raster_name,overwrite=TRUE)  #unweighted mean
498

  
499
    #r_m_mean_unweighted <- paste("r_m_mean_",out_suffix,".tif",sep="")
500
    list_weights <- NULL
501
    list_weights_prod <- NULL
502

  
503
  }
504
  
505
  #Create return object
506
  mosaic_obj <- list(raster_name,list_weights,list_weights_prod,mosaic_method)
507
  names(mosaic_obj) <- c("mean_mosaic","r_weights","r_weigths_prod","method")
508
  return(mosaic_obj)
509
}
51
#function_analyses_paper1 <-"contribution_of_covariates_paper_interpolation_functions_07182014.R" #first interp paper
52
#function_analyses_paper2 <-"multi_timescales_paper_interpolation_functions_08132014.R"
510 53

  
54
function_mosaicing <-"multi_timescales_paper_interpolation_functions_08132014.R"
511 55

  
56
in_dir_script <-"/home/parmentier/Data/IPLANT_project/env_layers_scripts"
57
source(file.path(in_dir_script,function_mosaicing))
512 58

  
513 59
############################################
514 60
#### Parameters and constants  
......
606 152
                                        file_format=file_format,out_suffix=out_suffix_str,
607 153
                                        out_dir=out_dir)
608 154
#debug(mosaicFiles)
155
save(mosaic_unweighted_20100901_obj,file=file.path(out_dir,
156
                                                   paste(mosaic_method,"_","mosaic_obj_","20100901_",out_suffix,".RData",sep="")))
609 157

  
610 158
mosaic_unweighted_20100901_obj <- mosaicFiles(lf_mosaic2,mosaic_method="unweighted",
611 159
                                        num_cores=num_cores,
......
613 161
                                        df_points=NULL,NA_flag=NA_flag_val,
614 162
                                        file_format=file_format,out_suffix=out_suffix_str,
615 163
                                        out_dir=out_dir)
616

  
617
r2_unweighted <-raster(mosaic_unweighted_20100901_obj$mean_mosaic)
618
r2_edge <-raster(mosaic_edge_20100901_obj$mean_mosaic)
619

  
620
#plot(r2_edge)
164
mosaic_method <- "unweighted"
165
save(mosaic_edge_20100901_obj,file=file.path(out_dir,paste(mosaic_method,"_","mosaic_obj_","20100901",out_suffix,".RData")))
621 166

  
622 167
mosaic_edge_20100831_obj <- mosaicFiles(lf_mosaic1,mosaic_method="use_edge_weights",
623 168
                                        num_cores=num_cores,
......
626 171
                                        file_format=file_format,out_suffix=out_suffix_str,
627 172
                                        out_dir=out_dir)
628 173

  
629
mosaic_edge_20100831_obj <- mosaicFiles(lf_mosaic1,mosaic_method="unweighted",
174
mosaic_unweighted_20100831_obj <- mosaicFiles(lf_mosaic1,mosaic_method="unweighted",
630 175
                                        num_cores=num_cores,
631 176
                                        python_bin=NULL,
632 177
                                        df_points=NULL,NA_flag=NA_flag_val,
633 178
                                        file_format=file_format,out_suffix=out_suffix_str,
634 179
                                        out_dir=out_dir)
635 180

  
181
r2_unweighted <-raster(mosaic_unweighted_20100901_obj$mean_mosaic)
182
r2_edge <-raster(mosaic_edge_20100901_obj$mean_mosaic)
636 183

  
637
##
638

  
639
#Then scale on 1 to zero? or 0 to 1000
640
#e.g. for a specific pixel
641
#weight_sum=0.2 +0.4 +0.4+0.2=1.2
642
#val_w_sum= (0.2*val1+0.4*val2+0.4*val3+0.2*val4)
643
#no_valid = number of valid observation, needs to be added in the function
644
#m_val= sum_val/weight_sum #mean value
645
#
646

  
184
r1_unweighted <-raster(mosaic_unweighted_20100831_obj$mean_mosaic)
185
r1_edge <-raster(mosaic_edge_20100831_obj$mean_mosaic)
186
plot(r1_edge)
647 187

  
648 188
#####################
649 189
###### PART 2: Analysis and figures for the outputs of mosaic function #####
650 190

  
651 191
#### compute and aspect and slope with figures
192
list_mosaic_unweighted <- list(mosaic_unweighted_20100831_obj,mosaic_edge_20100831_obj)
193
list_mosaic_edge <- list(mosaic_unweighted_20100901_obj,mosaic_edge_20100901_obj)
652 194

  
653
list_mosaiced_files2 <- c(list_mosaiced_files,r_m_mean_unweighted)
195
list_mosaiced_files <- c(list_mosaiced_files,r_m_mean_unweighted)
654 196
names(list_mosaiced_files2) <- c(names(list_mosaiced_files),"unweighted")
655 197

  
656
for(k in 1:length(list_mosaiced_files)){
657
  
658
  method_str <- names(list_mosaiced_files)[k]
659
  r_mosaic <- raster(list_mosaiced_files[k])
198
plot_mosaic <- function(f_mosaic,method,out_dir,out_stuffix){
199

  
200
  method_str <- method
201
  r_mosaic <- raster(f_mosaiced)
660 202

  
661 203
  r_mosaic_terrain <- terrain(r_mosaic,opt=c("slope","aspect"),unit="degrees")
662 204

  
......
664 206
  col_mfrow <- 1 
665 207
  row_mfrow <- 0.8
666 208

  
667
  png(filename=paste("Figure2_mosaic_mean_",method_str,region_name,"_",out_suffix,".png",sep=""),
209
  png(filename=paste("Figure2_mosaic_mean_",method_str,"_",out_suffix,".png",sep=""),
668 210
    width=col_mfrow*res_pix,height=row_mfrow*res_pix)
669 211

  
670 212
  plot(r_mosaic,main=paste("mosaic mean ",method_str,sep=""))
......
676 218
  col_mfrow <- 1 
677 219
  row_mfrow <- 0.8
678 220

  
679
  png(filename=paste("Figure2_slope_mean_",method_str,region_name,"_",out_suffix,".png",sep=""),
221
  png(filename=paste("Figure2_slope_mean_",method_str,"_",out_suffix,".png",sep=""),
680 222
    width=col_mfrow*res_pix,height=row_mfrow*res_pix)
681 223

  
682 224
  plot(r_mosaic_terrain,y=1,main=paste("slope mosaic mean ",method_str,sep=""))
683 225

  
684 226
  dev.off()
685 227

  
686
  png(filename=paste("Figure2_aspect_mean_",method_str,region_name,"_",out_suffix,".png",sep=""),
228
  png(filename=paste("Figure2_aspect_mean_",method_str,"_",out_suffix,".png",sep=""),
687 229
    width=col_mfrow*res_pix,height=row_mfrow*res_pix)
688 230

  
689 231
  plot(r_mosaic_terrain,y=2,main=paste("aspect mean ",method_str,sep=""))

Also available in: Unified diff