Project

General

Profile

« Previous | Next » 

Revision 5f212fe8

Added by Adam Wilson over 11 years ago

Added script to test functionality of HEG tool which reveals that v2.12 segfaults when multiple bands are selected for processing. Also updated MOD35_ExtractProcessPath to process one-band-at-a-time instead of in batches.

View differences:

climate/procedures/MOD35C5_Evaluation.r
25 25
  system("align.sh data/MOD35C6.vrt data/MOD09_2009.tif data/MOD35C6_2009.tif")
26 26
}
27 27
mod35c6=raster("data/MOD35C6_2009.tif")
28
mod35c6=crop(mod35c6,mod09)
29 28
names(mod35c6)="C6MOD35CF"
30 29
NAvalue(mod35c6)=255
31 30

  
32 31

  
33 32
## landcover
34
if(!file.exists("data/MCD12Q1_IGBP_2009_v5_wgs84_1km.tif")){
33
if(!file.exists("data/MCD12Q1_IGBP_2009_051_wgs84_1km.tif")){
35 34
  system(paste("/usr/local/gdal-1.10.0/bin/gdalwarp -tr 0.008983153 0.008983153 -r mode -ot Byte -co \"COMPRESS=LZW\"",
36
               " ~/acrobatesroot/jetzlab/Data/environ/global/landcover/MODIS/MCD12Q1_IGBP_2009_v5_wgs84.tif ",
35
               " /mnt/data/jetzlab/Data/environ/global/MODIS/MCD12Q1/051/MCD12Q1_051_2009.tif ",
37 36
               " -t_srs \"+proj=longlat +ellps=WGS84 +datum=WGS84 +no_defs\" ",
38
               "data/MCD12Q1_IGBP_2009_v5_wgs84_1km.tif -overwrite ",sep=""))}
39
  lulc=raster("data/MCD12Q1_IGBP_2009_v5_wgs84_1km.tif")
37
               " -te -180.0044166 -60.0074610 180.0044166 90.0022083 ",
38
               "data/MCD12Q1_IGBP_2009_051_wgs84_1km.tif -overwrite ",sep=""))}
39
lulc=raster("data/MCD12Q1_IGBP_2009_051_wgs84_1km.tif")
40 40

  
41
  ## read it in
42
lulc=raster("data/MCD12Q1_IGBP_2005_v51_1km_wgs84.tif")
43 41
#  lulc=ratify(lulc)
44 42
  data(worldgrids_pal)  #load palette
45 43
  IGBP=data.frame(ID=0:16,col=worldgrids_pal$IGBP[-c(18,19)],
46 44
    lulc_levels2=c("Water","Forest","Forest","Forest","Forest","Forest","Shrublands","Shrublands","Savannas","Savannas","Grasslands","Permanent wetlands","Croplands","Urban and built-up","Cropland/Natural vegetation mosaic","Snow and ice","Barren or sparsely vegetated"),stringsAsFactors=F)
47 45
  IGBP$class=rownames(IGBP);rownames(IGBP)=1:nrow(IGBP)
48 46
  levels(lulc)=list(IGBP)
49
lulc=crop(lulc,mod09)
47
#lulc=crop(lulc,mod09)
50 48
names(lulc)="MCD12Q1"
51 49

  
52 50
## make land mask
......
54 52
  land=calc(lulc,function(x) ifelse(x==0,NA,1),file="data/land.tif",options=c("COMPRESS=LZW","ZLEVEL=9","PREDICTOR=2"),datatype="INT1U",overwrite=T)
55 53
land=raster("data/land.tif")
56 54

  
57

  
58 55
## mask cloud masks to land pixels
59 56
#mod09l=mask(mod09,land)
60 57
#mod35l=mask(mod35,land)
......
68 65
system("align.sh ~/acrobates/adamw/projects/interp/data/modis/MOD17/MOD17A3_Science_NPP_mean_00_12.tif data/MOD09_2009.tif data/MOD17.tif")
69 66
mod17=raster("data/MOD17.tif",format="GTiff")
70 67
NAvalue(mod17)=65535
71
mod17=crop(mod17,mod09)
72 68
names(mod17)="MOD17"
73 69

  
74 70
if(!file.exists("data/MOD17qc.tif"))
75 71
  system("align.sh ~/acrobates/adamw/projects/interp/data/modis/MOD17/MOD17A3_Science_NPP_Qc_mean_00_12.tif data/MOD09_2009.tif data/MOD17qc.tif")
76 72
mod17qc=raster("data/MOD17qc.tif",format="GTiff")
77 73
NAvalue(mod17qc)=255
78
mod17qc=crop(mod17qc,mod09)
79 74
names(mod17qc)="MOD17CF"
80 75

  
81 76
## MOD11 via earth engine
......
87 82
if(!file.exists("data/MOD11qc_2009.tif"))
88 83
  system("align.sh ~/acrobates/adamw/projects/interp/data/modis/mod11/2009/MOD11_Pmiss_2009.tif data/MOD09_2009.tif data/MOD11qc_2009.tif")
89 84
mod11qc=raster("data/MOD11qc_2009.tif",format="GTiff")
90
mod11qc=crop(mod11qc,mod09)
91 85
names(mod11qc)="MOD11CF"
92 86

  
93 87

  
......
102 96
pp=raster("data/MOD35pp.tif")
103 97
NAvalue(pp)=255
104 98
names(pp)="MOD35pp"
105
pp=crop(pp,mod09)
106 99

  
107
## comparison of % cloudy days
108
dif_c5_09=mod35c5-mod09
109
dif_c6_09=mod35c6-mod09
110
dif_c5_c6=mod35c5-mod35c6
111 100

  
112 101
#hist(dif,maxsamp=1000000)
113 102
## draw lulc-stratified random sample of mod35-mod09 differences 
......
194 183
  ## normalize MOD11 and MOD17
195 184
  for(j in which(do.call(c,lapply(tdd,function(i) names(i)))%in%c("MOD11","MOD17"))){
196 185
    trange=cellStats(tdd[[j]],range)
197
    tdd[[j]]=100*(tdd[[j]]-trange[1])/(trange[2]-trange[1])
198
    tdd[[j]]@history=list(range=trange)
186
    tscaled=100*(tdd[[j]]-trange[1])/(trange[2]-trange[1])
187
    tscaled@history=list(range=trange)
188
    names(tscaled)=paste(names(tdd[[j]]),"scaled",collapse="_",sep="_")
189
    tdd=c(tdd,tscaled)
199 190
  }
200 191
  return(brick(tdd))
201 192
})
......
227 218

  
228 219
transd$type=ifelse(grepl("MOD35|MOD09|CF",transd$variable),"CF","Data")
229 220

  
221

  
222

  
223
## comparison of % cloudy days
224
dif_c5_09=mod35c5-mod09
225
dif_c6_09=mod35c6-mod09
226
dif_c5_c6=mod35c5-mod35c6
227

  
228
t1=trd1[[1]]
229
dif_p=calc(trd1[[1]], function(x) (x[1]-x[3])/(1-x[1]))
230
edge=edge(subset(t1,"MCD12Q1"),classes=T,type="inner")
231
names(edge)="edge"
232
td1=as.data.frame(stack(t1,edge))
233

  
234

  
235
cor(td1$MOD17,td1$C5MOD35,use="complete",method="spearman")
236
cor(td1$MOD17[td1$edge==1],td1$C5MOD35[td1$edge==1],use="complete",method="spearman")
237

  
238
cor(td1,use="complete",method="spearman")
239

  
240
splom(t1)
241

  
242
plot(mod17,mod17qc)
243

  
244
xyplot(MOD17~C5MOD35CF|edge,data=td1)
245

  
246
     , function(x) (x[1]-x[3])/(1-x[1]))
247

  
248
plot(dif_p)
249

  
230 250
#rondonia=trd[trd$trans=="Brazil",]
231 251
#trd=trd[trd$trans!="Brazil",]
232 252

  
......
239 259
library(maptools)
240 260
coast=map2SpatialLines(map("world", interior=FALSE, plot=FALSE),proj4string=CRS("+proj=longlat +ellps=WGS84 +datum=WGS84 +no_defs"))
241 261

  
242
g1=levelplot(stack(mod35c5,mod35c6,mod09),xlab=" ",scales=list(x=list(draw=F),y=list(alternating=1)),col.regions=cols,at=at)+layer(sp.polygons(bbs[1:4],lwd=2))+layer(sp.lines(coast,lwd=.5))
243
#g2=levelplot(dif,col.regions=bgrayr(100),at=seq(-70,70,len=100),margin=F,ylab=" ",colorkey=list("right"))+layer(sp.polygons(bbs[1:4],lwd=2))+layer(sp.lines(coast,lwd=.5))
244
#trellis.par.set(background=list(fill="white"),panel.background=list(fill="white"))
262
g1=levelplot(stack(mod35c5,mod09),xlab=" ",scales=list(x=list(draw=F),y=list(alternating=1)),col.regions=cols,at=at)+layer(sp.polygons(bbs[1:4],lwd=2))+layer(sp.lines(coast,lwd=.5))
263
g2=levelplot(dif,col.regions=bgrayr(100),at=seq(-70,70,len=100),margin=F,ylab=" ",colorkey=list("right"))+layer(sp.polygons(bbs[1:4],lwd=2))+layer(sp.lines(coast,lwd=.5))
264
trellis.par.set(background=list(fill="white"),panel.background=list(fill="white"))
245 265
#g3=histogram(dif,bg="white",col="black",border=NA,scales=list(x=list(at=c(-50,0,50)),y=list(draw=F),cex=1))+layer(panel.abline(v=0,col="red",lwd=2))
246 266

  
247 267
### regional plots
......
309 329
       legend=list(
310 330
         bottom=list(fun=draw.key(list( rep=FALSE,columns=1,title=" ",
311 331
                      ##                   text=list(c("MOD09 % Cloudy","C5 MOD35 % Cloudy","C6 MOD35 % Cloudy","MOD17 % Missing","MOD17 (scaled)","MOD11 % Missing","MOD11 (scaled)")),
312
                      lines=list(type=c("b","b","b","b","l","b","l"),pch=16,cex=.5,lty=c(1,1,1,1,5,1,5),col=c("red","blue","black","darkgreen","darkgreen","orange","orange")),
313
                       text=list(c("MOD09 % Cloudy","C5 MOD35 % Cloudy","C6 MOD35 % Cloudy","MOD17 % Missing","MOD17 (scaled)","MOD11 % Missing","MOD11 (scaled)")),
332
                      lines=list(type=c("b","b","b","b","b","l","b","l"),pch=16,cex=.5,lty=c(0,1,1,1,1,5,1,5),col=c("transparent","red","blue","black","darkgreen","darkgreen","orange","orange")),
333
                       text=list(c("MODIS Products","MOD09 % Cloudy","C5 MOD35 % Cloudy","C6 MOD35 % Cloudy","MOD17 % Missing","MOD17 (scaled)","MOD11 % Missing","MOD11 (scaled)")),
314 334
                       rectangles=list(border=NA,col=c(NA,"tan","darkgreen")),
315 335
                       text=list(c("C5 MOD35 Processing Path","Desert","Land")),
316
                       rectangles=list(border=NA,col=c(NA,IGBP$col[sort(unique(transd$value[transd$variable=="MCD12Q1"]+1))])),
336
                      rectangles=list(border=NA,col=c(NA,IGBP$col[sort(unique(transd$value[transd$variable=="MCD12Q1"]+1))])),
317 337
                      text=list(c("MCD12Q1 IGBP Land Cover",IGBP$class[sort(unique(transd$value[transd$variable=="MCD12Q1"]+1))])))))),
318 338
 strip = strip.custom(par.strip.text=list(cex=.75)))
319 339
print(p4)
climate/procedures/MOD35_ExtractProcessPath.r
39 39

  
40 40
#### Grid and mosaic the swath data
41 41

  
42
stitch="sudo MRTDATADIR=\"/usr/local/heg/data\" PGSHOME=/usr/local/heg/TOOLKIT_MTD PWD=/home/adamw /usr/local/heg/bin/swtif"
42
stitch="sudo MRTDATADIR=\"/usr/local/heg/2.12/data\" PGSHOME=/usr/local/heg/2.12/TOOLKIT_MTD PWD=/home/adamw /usr/local/heg/2.12/bin/swtif"
43
stitch="/usr/local/heg/2.12/bin/swtif"
43 44

  
45
stitch="sudo MRTDATADIR=\"/usr/local/heg/2.11/data\" PGSHOME=/usr/local/heg/2.11/TOOLKIT_MTD PWD=/home/adamw /usr/local/heg/2.11/bin/swtif"
44 46
files=paste(getwd(),"/",list.files("swath",pattern="hdf$",full=T),sep="")
45 47

  
46 48
## vars to process
47 49
vars=as.data.frame(matrix(c(
48
  "Cloud_Mask",              "CM",
49
  "Sensor_Azimuth",       "ZA",
50
  "Sensor_Zenith",        "SZ"),
51
  byrow=T,ncol=2,dimnames=list(1:3,c("variable","varid"))),stringsAsFactors=F)
50
  "Cloud_Mask",           "CM",   "NN",    1,
51
#  "Sensor_Azimuth",       "ZA",   "CUBIC", 1,
52
  "Sensor_Zenith",        "SZ",   "CUBIC", 1),
53
  byrow=T,ncol=4,dimnames=list(1:2,c("variable","varid","method","band"))),stringsAsFactors=F)
52 54

  
53 55
## global bounding box
54
   gbb=cbind(c(-180,-180,180,180,-180),c(-85,85,85,-85,-85))
56
   gbb=cbind(c(-180,-180,180,180,-180),c(-90,90,90,-90,-90))
55 57
   gpp = SpatialPolygons(list(Polygons(list(Polygon(gbb)),1)))
56 58
   proj4string(gpp)=projection(glb)
57 59

  
60
outdir="~/acrobates/adamw/projects/interp/data/modis/mod35/gridded/"
58 61

  
59
getpath<- function(file){  
60
   setwd(tempdir())
61
   bfile=sub(".hdf","",basename(file))
62
   tempfile_path=paste(tempdir(),"/path_",basename(file),sep="")  #gridded path
63
   tempfile_sz=paste(tempdir(),"/sz_",basename(file),sep="")  # gridded sensor zenith
64
   tempfile2_path=paste(tempdir(),"/",bfile,".tif",sep="")  #gridded/masked/processed path
65
   outfile=paste("~/acrobates/adamw/projects/interp/data/modis/mod35/gridded/",bfile,".tif",sep="")  #final file
66
   if(file.exists(outfile)) return(c(file,0))
67
   ## get bounding coordinates
68
#   glat=as.numeric(do.call(c,strsplit(sub("GRINGPOINTLATITUDE=","",system(paste("gdalinfo ",file," | grep GRINGPOINTLATITUDE"),intern=T)),split=",")))
69
#   glon=as.numeric(do.call(c,strsplit(sub("GRINGPOINTLONGITUDE=","",system(paste("gdalinfo ",file," | grep GRINGPOINTLONGITUDE"),intern=T)),split=",")))
70
#   bb=cbind(c(glon,glon[1]),c(glat,glat[1]))
71
#   pp = SpatialPolygons(list(Polygons(list(Polygon(bb)),1)))
72
#   proj4string(pp)=projection(glb)
73
#   ppc=gIntersection(pp,gpp)
74
#   ppc=gBuffer(ppc,width=0.3)  #buffer a little to remove gaps between images
75
ppc=gpp
62
swtif<-function(file,var){
63
  outfile=paste(tempdir(),"/",var$varid,"_",basename(file),sep="")  #gridded path
76 64
   ## First write the parameter file (careful, heg is very finicky!)
77
   hdr=paste("NUM_RUNS = ",length(vars$varid),"|MULTI_BAND_HDFEOS:",length(vars$varid),sep="")
65
   hdr=paste("NUM_RUNS = 1")
78 66
   grp=paste("
79 67
BEGIN
80 68
INPUT_FILENAME=",file,"
81 69
OBJECT_NAME=mod35
82
FIELD_NAME=",vars$variable,"|
83
BAND_NUMBER = ",1:length(vars$varid),"
70
FIELD_NAME=",var$variable,"|
71
BAND_NUMBER = ",var$band,"
84 72
OUTPUT_PIXEL_SIZE_X=0.008333333
85 73
OUTPUT_PIXEL_SIZE_Y=0.008333333
86
SPATIAL_SUBSET_UL_CORNER = ( ",bbox(ppc)[2,2]," ",bbox(ppc)[1,1]," )
87
SPATIAL_SUBSET_LR_CORNER = ( ",bbox(ppc)[2,1]," ",bbox(ppc)[1,2]," )
88
OUTPUT_OBJECT_NAME = mod35|
89
RESAMPLING_TYPE =NN
74
SPATIAL_SUBSET_UL_CORNER = ( ",bbox(gpp)[2,2]," ",bbox(gpp)[1,1]," )
75
SPATIAL_SUBSET_LR_CORNER = ( ",bbox(gpp)[2,1]," ",bbox(gpp)[1,2]," )
76
RESAMPLING_TYPE =",var$method,"
90 77
OUTPUT_PROJECTION_TYPE = GEO
91 78
OUTPUT_PROJECTION_PARAMETERS = ( 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 )
92 79
# OUTPUT_PROJECTION_PARAMETERS = ( 6371007.181 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 )
93 80
# projection parameters from http://landweb.nascom.nasa.gov/cgi-bin/QA_WWW/newPage.cgi?fileName=sn_gctp
94 81
ELLIPSOID_CODE = WGS84
95 82
OUTPUT_TYPE = HDFEOS
96
OUTPUT_FILENAME= ",tempfile_path,"
83
OUTPUT_FILENAME= ",outfile,"
97 84
END
98 85

  
99 86
",sep="")
100

  
101
   ## if any remnants from previous runs remain, delete them
102
   if(length(list.files(tempdir(),pattern=bfile)>0))
103
     file.remove(list.files(tempdir(),pattern=bfile,full=T))
104 87
   ## write it to a file
105 88
   cat( c(hdr,grp)   , file=paste(tempdir(),"/",basename(file),"_MODparms.txt",sep=""))
106 89
   ## now run the swath2grid tool
107 90
   ## write the gridded file
108 91
   print(paste("Starting",file))
109
   system(paste("(",stitch," -p ",tempdir(),"/",basename(file),"_MODparms.txt -d)",sep=""),intern=F)#,ignore.stderr=F)
110
##############  Now run the 5km summary
111
   ## First write the parameter file (careful, heg is very finicky!)
112
   hdr=paste("NUM_RUNS = ",nrow(vars[-1,]),"|MULTI_BAND_HDFEOS:",nrow(vars[-1,]),sep="")
113
   grp=paste("
114
BEGIN
115
INPUT_FILENAME=",file,"
116
OBJECT_NAME=mod35
117
FIELD_NAME=",vars$variable[-1],"|
118
BAND_NUMBER = ",1,"
119
OUTPUT_PIXEL_SIZE_X=0.008333333
120
#0.0416666
121
OUTPUT_PIXEL_SIZE_Y=0.008333333
122
#0.0416666
123
SPATIAL_SUBSET_UL_CORNER = ( ",bbox(ppc)[2,2]," ",bbox(ppc)[1,1]," )
124
SPATIAL_SUBSET_LR_CORNER = ( ",bbox(ppc)[2,1]," ",bbox(ppc)[1,2]," )
125
#OUTPUT_OBJECT_NAME = mod35|
126
RESAMPLING_TYPE =NN
127
OUTPUT_PROJECTION_TYPE = GEO
128
OUTPUT_PROJECTION_PARAMETERS = ( 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 )
129
#OUTPUT_PROJECTION_PARAMETERS = ( 6371007.181 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 )
130
# projection parameters from http://landweb.nascom.nasa.gov/cgi-bin/QA_WWW/newPage.cgi?fileName=sn_gctp
131
ELLIPSOID_CODE = WGS84
132
OUTPUT_TYPE = HDFEOS
133
OUTPUT_FILENAME= ",tempfile_sz,"
134
END
92
   system(paste("",stitch," -p ",tempdir(),"/",basename(file),"_MODparms.txt -d -log /dev/null ",sep=""),intern=F)#,ignore.stderr=F)
93
   print(paste("Finished processing variable",var$variable,"from ",basename(file),"to",outfile))
94
}  
135 95

  
136
",sep="")
137

  
138
   ## write it to a file
139
   cat( c(hdr,grp)   , file=paste(tempdir(),"/",basename(file),"_MODparms_angle.txt",sep=""))
140
   
141
   ## now run the swath2grid tool
142
   ## write the gridded file
143
   print(paste("Starting",file))
144
   system(paste("(",stitch," -p ",tempdir(),"/",basename(file),"_MODparms_angle.txt -d)",sep=""),intern=F,ignore.stderr=F)
96
getpath<- function(file){  
97
   setwd(tempdir())
98
   bfile=sub(".hdf","",basename(file))
99
   tempfile2_path=paste(tempdir(),"/",bfile,".tif",sep="")  #gridded/masked/processed path
100
   outfile=paste(outdir,"/",bfile,".tif",sep="")  #final file
101
   if(file.exists(outfile)) return(c(file,0))
102
   ppc=gpp
103
#######
104
## run swtif for each band
105
   lapply(1:nrow(vars),function(i) swtif(file,vars[i,]))
145 106
####### import to R for processing
146
   if(!file.exists(tempfile_path)) {
107
  
108
   if(!file.exists(paste(tempdir(),"/CM_",basename(file),sep=""))) {
147 109
     file.remove(list.files(tempdir(),pattern=bfile,full=T))
148 110
     return(c(file,0))
149 111
   }
150 112
   ## convert to land path
151
   d=raster(paste("HDF4_EOS:EOS_GRID:\"",tempfile_path,"\":mod35:Cloud_Mask_0",sep=""))
152
   sz=raster(paste("HDF4_EOS:EOS_GRID:\"",tempfile_sz,"\":mod35:Sensor_Zenith",sep=""))
153
   NAvalue(sz)=0
154
   ## resample sensor angles to 1km grid and mask paths with angles >=30
155
#   sz2=resample(sz,d,method="ngb",file=sub("hdf","tif",tempfile_sz),overwrite=T)
156
   getlc=function(x,y) {ifelse(y==0|y>40,NA,((x%/%2^6) %% 2^2))}
113
   d=raster(paste(tempdir(),"/CM_",basename(file),sep=""))
114
   sz=raster(paste(tempdir(),"/SZ_",basename(file),sep=""))
115
   NAvalue(sz)=-9999
116
   getlc=function(x,y) {ifelse(y==0|y>6000,NA,((x%/%2^6) %% 2^2))}
157 117
   path=  overlay(d,sz,fun=getlc,filename=tempfile2_path,options=c("COMPRESS=LZW", "LEVEL=9","PREDICTOR=2"),datatype="INT1U",overwrite=T)
158 118
### warp them to align all pixels
159 119
   system(paste("gdalwarp -overwrite -srcnodata 255 -dstnodata 255 -tap -tr 0.008333333 0.008333333 -co COMPRESS=LZW -co ZLEVEL=9 -co PREDICTOR=2 -s_srs \"",projection(t),"\" ",tempfile2_path," ",outfile,sep=""))
......
163 123
 }
164 124

  
165 125

  
166
## establish sudo priveleges to run swtif
167
system("sudo ls"); mclapply(files,getpath,mc.cores=10)
126
### run it
127
mclapply(files[1:200],getpath,mc.cores=10)
168 128

  
169 129
## check gdal can read all of them
170
gfiles=list.files("gridded",pattern="tif$",full=T)
130
gfiles=list.files(outdir,pattern="tif$",full=T)
171 131
length(gfiles)
172 132

  
173 133
check=do.call(rbind,mclapply(gfiles,function(file){
......
181 141
file.remove(gfiles[check==0])
182 142

  
183 143
## use new gdal
184
system(paste("/usr/local/gdal-1.10.0/bin/gdalwarp -wm 900 -overwrite -co COMPRESS=LZW -co PREDICTOR=2 -multi -r mode gridded/*.tif MOD35_path_gdalwarp.tif"))
144
system(paste("/usr/local/gdal-1.10.0/bin/gdalwarp -wm 900 -overwrite -co COMPRESS=LZW -co PREDICTOR=2 -multi -r mode ",outdir,"/*.tif MOD35_path_gdalwarp.tif",sep=""))
185 145

  
186 146

  
187 147
###  Merge them into a geotiff
climate/tests/HEG_test.sh
1
#! /bin/bash
2

  
3
mkdir /tmp/tmp1
4
cd /tmp/tmp1
5

  
6
## get swath data
7
wget ftp://ladsweb.nascom.nasa.gov/allData/6/MOD35_L2/2009/029/MOD35_L2.A2009029.0005.006.2012245113426.hdf
8

  
9
## build parameter file
10
echo "
11
NUM_RUNS = 1
12

  
13
BEGIN
14
INPUT_FILENAME = /tmp/tmp1/MOD35_L2.A2009029.0005.006.2012245113426.hdf
15
OBJECT_NAME = mod35
16
FIELD_NAME = Cloud_Mask|
17
BAND_NUMBER = 1
18
OUTPUT_PIXEL_SIZE_X = 1013.0
19
OUTPUT_PIXEL_SIZE_Y = 1013.0
20
SPATIAL_SUBSET_UL_CORNER = ( 89.929451 -179.998932 )
21
SPATIAL_SUBSET_LR_CORNER = ( 64.8638 179.998108 )
22
RESAMPLING_TYPE = NN
23
OUTPUT_PROJECTION_TYPE = SIN
24
ELLIPSOID_CODE = WGS84
25
OUTPUT_PROJECTION_PARAMETERS = ( 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0  )
26
OUTPUT_FILENAME = /tmp/tmp1/MOD35_L2.A2009029.0005.006.2012245113426_mod35.hdf
27
OUTPUT_TYPE = HDFEOS
28
END
29
" > params.txt
30

  
31
### run it
32
swtif -p params.txt -d  -tmpLatLondir /tmp/tmp1/
33

  
34
## now view the output file in 

Also available in: Unified diff