OB.DAAC Logo
NASA Logo
Ocean Color Science Software

ocssw V2022
modis_io_module.f90
Go to the documentation of this file.
2 
3  ! WDR use shared_io_module
4  ! WDR no need use general_array_io
5 
6  implicit none
7 
8 
9 
10  private
11 
12  ! WDR public :: output_retrieval, get_modis_data_cube, write_statistics
13  public :: get_modis_data_cube
14 
15 
16  contains
17 
18 ! subroutine write_statistics(filename)
19 !
20 ! use core_arrays
21 !
22 ! include "hdf.f90"
23 ! include "dffunc.f90"
24 !
25 !
26 ! character(*), intent(in) :: filename
27 !
28 ! real :: data_to_write(17)
29 ! integer :: file_id, err_code, vref, vid
30 ! real, parameter :: fill_val = -999.
31 ! character(len=100) :: ln, un
32 ! character(len=85) :: desc(19)
33 !
34 ! data_to_write(1) = Statistics_1km%retrieval_fraction
35 ! data_to_write(2) = Statistics_1km%land_fraction
36 ! data_to_write(3) = Statistics_1km%water_fraction
37 ! data_to_write(4) = Statistics_1km%snow_fraction
38 ! data_to_write(5) = Statistics_1km%cloud_fraction
39 ! data_to_write(6) = Statistics_1km%water_cloud_fraction
40 ! data_to_write(7) = Statistics_1km%ice_cloud_fraction
41 ! data_to_write(8) = Statistics_1km%mean_liquid_tau
42 ! data_to_write(9) = Statistics_1km%mean_ice_tau
43 ! data_to_write(10) = Statistics_1km%mean_liquid_re21
44 ! data_to_write(11) = Statistics_1km%mean_ice_re21
45 ! data_to_write(12) = Statistics_1km%ctp_liquid
46 ! data_to_write(13) = Statistics_1km%ctp_ice
47 ! data_to_write(14) = Statistics_1km%ctp_undetermined
48 ! data_to_write(15) = Statistics_1km%ctt_liquid
49 ! data_to_write(16) = Statistics_1km%ctt_ice
50 ! data_to_write(17) = Statistics_1km%ctt_undetermined
51 !
52 ! file_id = hopen(filename, DFACC_WRITE, 0)
53 !
54 ! err_code = vfstart(file_id)
55 !
56 ! vref = vsffnd(file_id, "Statistics_1km")
57 ! vid = vsfatch(file_id, vref, "w")
58 !
59 ! err_code = vsfwrt(vid, data_to_write, 17, 0)
60 !
61 ! err_code = vsfdtch(vid)
62 ! err_code = vfend(file_id)
63 ! err_code = hclose(file_id)
64 !
65 !! duplicate same information as an SDS
66 !! we can't use MOD_PR06CR because CR automatically turns any 1D SDS into VData
67 !! VData makes it difficult to see SDS attributes in common display tools
68 !! without the attributes the data is useless
69 ! file_id = sfstart(filename, DFACC_WRITE)
70 ! vid = sfselect(file_id, sfn2index(file_id, "Statistics_1km_sds"))
71 ! if (vid == -1) vid = sfcreate(file_id, "Statistics_1km_sds", DFNT_FLOAT, 1, (/ 17 /))
72 ! err_code = sfwdata(vid, (/ 0 /), (/ 1 /), (/ 17 /), data_to_write)
73 !
74 ! ln = "Granule Statistics for parameters at 1x1 resolution"
75 ! un = "see description attribute"
76 ! err_code = sfsattr(vid, "long_name", DFNT_CHAR, len(trim(ln)), ln )
77 ! err_code = sfsattr(vid, "units", DFNT_CHAR, len(trim(un)), un )
78 ! err_code = sfsattr(vid, "_FillValue", DFNT_FLOAT, 1, fill_val)
79 !
80 ! desc(1:19)(1:85) = ' '
81 !
82 ! desc(1) = " "
83 ! desc(2) = "Statistics_1km:"
84 ! desc(3) = " 1. Successful Retrieval Rate (%)"
85 ! desc(4) = " 2. Land Cover Fraction (%)"
86 ! desc(5) = " 3. Water Cover Fraction (%)"
87 ! desc(6) = " 4. Snow Cover Fraction (%)"
88 ! desc(7) = " 5. Cloud Cover Fraction (%)"
89 ! desc(8) = " 6. Water Cloud Detected (%)"
90 ! desc(9) = " 7. Ice Cloud Detected (%)"
91 ! desc(10) = " 8. Mean of Water Cloud Optical Thickness"
92 ! desc(11) = " 9. Mean of Ice Cloud Optical Thickness "
93 ! desc(12) = " 10. Mean of Water Cloud Effective Particle Radius (microns)"
94 ! desc(13) = " 11. Mean of Ice Cloud Effective Diameter (microns)"
95 ! desc(14) = " 12. Mean Liquid Water Cloud Top Pressure (mb)"
96 ! desc(15) = " 13. Mean Ice Cloud Top Pressure (mb)"
97 ! desc(16) = " 14. Mean Undetermined Cloud Top Pressure (mb)"
98 ! desc(17) = " 15. Mean Liquid Water Cloud Top Temperature (K)"
99 ! desc(18) = " 16. Mean Ice Cloud Top Temperature (K) "
100 ! desc(19) = " 17. Mean Undetermined Cloud Top Temperature (K)"
101 !
102 ! desc(1:19)(85:85) = char(10)
103 !
104 ! err_code = sfsattr(vid, "description", DFNT_CHAR, 19*85, desc)
105 !
106 ! err_code = sfendacc(vid)
107 ! err_code = sfend(file_id)
108 !
109 !
110 !
111 ! end subroutine write_statistics
112 
113 
114 
115 ! subroutine output_retrieval(mapi_filedata, &
116 ! filename, &
117 ! currentscanX, currentscanY, nscansX, nscansY, &
118 ! start, edge, stride, &
119 ! status)
120 ! use GeneralAuxType
121 ! use core_arrays
122 ! use nonscience_parameters
123 ! use mod06_run_settings
124 ! use libraryarrays
125 ! use specific_other
126 ! implicit none
127 !
128 ! integer, intent(in) :: mapi_filedata(:), currentscanX, currentscanY, nscansX, nscansY
129 ! integer, intent(in) :: start(:), edge(:), stride(:)
130 ! character(*), intent (in) :: filename
131 !
132 ! integer, intent (out) :: status
133 !
134 ! integer :: buffer_xsize, buffer_ysize, i,j, count
135 ! integer(integer_twobyte) :: fillint_twobyte
136 ! integer(integer_twobyte),allocatable :: outputbuffer(:)
137 ! real(double) :: scale, add_offset
138 ! integer :: localstart(3), localedge(3), localstride(3), xsize, ysize
139 ! integer(integer_onebyte),allocatable :: quality_assurance_1km(:,:,:)
140 ! real, allocatable :: retrieval_diff(:,:,:)
141 ! logical, parameter :: HDF4_OUTPUT = .true.
142 !
143 ! integer*1, allocatable, dimension(:,:) :: cloud_phase_COP
144 !
145 ! status = success
146 ! xsize = size(optical_thickness_final,1)
147 ! ysize = size(optical_thickness_final,2)
148 !
149 ! out_xsize = xsize
150 ! out_ysize = ysize
151 !
152 ! allocate(quality_assurance_1km(9, xsize,ysize ))
153 !
154 ! call set_quality_data(xsize, ysize)
155 !
156 ! call convert_binary_qa(quality_assurance_1km, status)
157 ! call writeqaarray_toolkit(mapi_filedata, start, stride, edge, quality_assurance_1km,'Quality_Assurance_1km', status , HDF4_OUTPUT)
158 !
159 ! deallocate(quality_assurance_1km)
160 !
161 !
162 ! allocate(outputbuffer_twobyte(xsize,ysize))
163 !
164 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, optical_thickness_final, 'Cloud_Optical_Thickness', status, HDF4_OUTPUT)
165 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_final_PCL, 'Cloud_Optical_Thickness_PCL', status, HDF4_OUTPUT)
166 !
167 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, optical_thickness_1621_final, 'Cloud_Optical_Thickness_1621', status, HDF4_OUTPUT)
168 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_1621_final_PCL, 'Cloud_Optical_Thickness_1621_PCL', status, HDF4_OUTPUT)
169 !
170 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, optical_thickness_16_final, 'Cloud_Optical_Thickness_16', status, HDF4_OUTPUT)
171 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_16_final_PCL, 'Cloud_Optical_Thickness_16_PCL', status, HDF4_OUTPUT)
172 !
173 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, optical_thickness_37_final, 'Cloud_Optical_Thickness_37', status, HDF4_OUTPUT)
174 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_37_final_PCL, 'Cloud_Optical_Thickness_37_PCL', status, HDF4_OUTPUT)
175 !
176 !
177 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, effective_radius_21_final, 'Cloud_Effective_Radius', status, HDF4_OUTPUT)
178 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_21_final_PCL, 'Cloud_Effective_Radius_PCL', status, HDF4_OUTPUT)
179 !
180 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, effective_radius_16_final, 'Cloud_Effective_Radius_16', status, HDF4_OUTPUT)
181 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_16_final_PCL, 'Cloud_Effective_Radius_16_PCL', status, HDF4_OUTPUT)
182 !
183 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, effective_radius_37_final, 'Cloud_Effective_Radius_37', status, HDF4_OUTPUT)
184 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_37_final_PCL, 'Cloud_Effective_Radius_37_PCL', status, HDF4_OUTPUT)
185 !
186 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, effective_radius_1621_final, 'Cloud_Effective_Radius_1621', status, HDF4_OUTPUT)
187 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_1621_final_PCL, 'Cloud_Effective_Radius_1621_PCL', status, HDF4_OUTPUT)
188 !
189 !
190 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, liquid_water_path, 'Cloud_Water_Path', status, HDF4_OUTPUT)
191 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_PCL, 'Cloud_Water_Path_PCL', status, HDF4_OUTPUT)
192 !
193 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_16, 'Cloud_Water_Path_16', status, HDF4_OUTPUT)
194 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_16_PCL, 'Cloud_Water_Path_16_PCL', status, HDF4_OUTPUT)
195 !
196 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_37, 'Cloud_Water_Path_37', status, HDF4_OUTPUT)
197 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_37_PCL, 'Cloud_Water_Path_37_PCL', status, HDF4_OUTPUT)
198 !
199 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_1621, 'Cloud_Water_Path_1621', status, HDF4_OUTPUT)
200 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_1621_PCL, 'Cloud_Water_Path_1621_PCL', status, HDF4_OUTPUT)
201 !
202 !
203 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_error, 'Cloud_Optical_Thickness_Uncertainty', status, HDF4_OUTPUT)
204 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_16_error, 'Cloud_Optical_Thickness_Uncertainty_16', status, HDF4_OUTPUT)
205 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_37_error, 'Cloud_Optical_Thickness_Uncertainty_37', status, HDF4_OUTPUT)
206 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, optical_thickness_1621_error, 'Cloud_Optical_Thickness_Uncertainty_1621', status, HDF4_OUTPUT)
207 !
208 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_21_error, 'Cloud_Effective_Radius_Uncertainty', status, HDF4_OUTPUT)
209 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_16_error, 'Cloud_Effective_Radius_Uncertainty_16', status, HDF4_OUTPUT)
210 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_37_error, 'Cloud_Effective_Radius_Uncertainty_37', status, HDF4_OUTPUT)
211 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, effective_radius_1621_error, 'Cloud_Effective_Radius_Uncertainty_1621', status, HDF4_OUTPUT)
212 !
213 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_error, 'Cloud_Water_Path_Uncertainty', status, HDF4_OUTPUT)
214 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_16_error, 'Cloud_Water_Path_Uncertainty_16', status, HDF4_OUTPUT)
215 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_37_error, 'Cloud_Water_Path_Uncertainty_37', status, HDF4_OUTPUT)
216 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, liquid_water_path_1621_error, 'Cloud_Water_Path_Uncertainty_1621', status, HDF4_OUTPUT)
217 !
218 !
219 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, precip_water_094, 'Above_Cloud_Water_Vapor_094', status, HDF4_OUTPUT)
220 !
221 ! call writefloatarray_toolkit(mapi_filedata, start, stride, edge, irw_temperature, 'IRW_Low_Cloud_Temperature_From_COP', status, HDF4_OUTPUT)
222 !
223 !
224 ! if (allocated(tau_liquid)) then
225 !
226 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, tau_liquid, 'Cloud_Optical_Thickness_All_Liquid', status, HDF4_OUTPUT)
227 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, tau_ice, 'Cloud_Optical_Thickness_All_Ice', status, HDF4_OUTPUT)
228 !
229 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, re21_liquid, 'Cloud_Effective_Radius_All_Liquid', status, HDF4_OUTPUT)
230 ! call writeint2array_toolkit(mapi_filedata, start, stride, edge, re21_ice, 'Cloud_Effective_Radius_All_Ice', status, HDF4_OUTPUT)
231 !
232 ! endif
233 !
234 ! deallocate(outputbuffer_twobyte)
235 !
236 !
237 ! call write_failed_array(mapi_filedata, start, stride, edge, failure_metric, 'Retrieval_Failure_Metric', status, HDF4_OUTPUT)
238 ! call write_failed_array(mapi_filedata, start, stride, edge, failure_metric_16, 'Retrieval_Failure_Metric_16', status, HDF4_OUTPUT)
239 ! call write_failed_array(mapi_filedata, start, stride, edge, failure_metric_37, 'Retrieval_Failure_Metric_37', status, HDF4_OUTPUT)
240 ! call write_failed_array(mapi_filedata, start, stride, edge, failure_metric_1621, 'Retrieval_Failure_Metric_1621', status, HDF4_OUTPUT)
241 !
242 ! call writebytearray_toolkit(mapi_filedata, start, stride, edge, cloud_layer_flag, 'Cloud_Multi_Layer_Flag', status, HDF4_OUTPUT)
243 !
244 !
245 ! allocate(cloud_phase_COP(xsize,ysize))
246 ! cloud_phase_COP = processing_information%path_and_outcome
247 ! where(cloud_phase_COP > 4)
248 ! cloud_phase_COP = cloud_phase_COP - 8
249 ! end where
250 !
251 ! call writebytearray_toolkit(mapi_filedata, start, stride, edge, cloud_phase_COP, 'Cloud_Phase_Optical_Properties', status, HDF4_OUTPUT)
252 !
253 !
254 !
255 ! deallocate(cloud_phase_COP)
256 !
257 ! call write3Dfloatarray(mapi_filedata, start, stride, edge, atm_corr_refl, 'Atm_Corr_Refl', status, HDF4_OUTPUT)
258 !
259 !
260 ! if (currentscanX == nscansX .and. currentscanY == nscansY) then
261 !
262 ! localstart = 0
263 ! localstride = 1
264 ! localedge(1) = number_wavelengths
265 ! localedge(2) = number_iceradii
266 !
267 ! call write_float_array(mapi_filedata, "Extinction_Efficiency_Ice", &
268 ! localstart(1:2), localstride(1:2), localedge(1:2), extinction_ice, status)
269 ! call write_float_array(mapi_filedata, "Single_Scatter_Albedo_Ice", &
270 ! localstart(1:2), localstride(1:2), localedge(1:2), singlescattering_ice, status)
271 ! call write_float_array(mapi_filedata, "Asymmetry_Parameter_Ice", &
272 ! localstart(1:2), localstride(1:2), localedge(1:2), asymmetry_ice, status)
273 !
274 ! localedge(2) = number_waterradii
275 !
276 ! call write_float_array(mapi_filedata, "Extinction_Efficiency_Liq", &
277 ! localstart(1:2), localstride(1:2), localedge(1:2), extinction_water, status)
278 ! call write_float_array(mapi_filedata, "Single_Scatter_Albedo_Liq", &
279 ! localstart(1:2), localstride(1:2), localedge(1:2), singlescattering_water, status)
280 ! call write_float_array(mapi_filedata, "Asymmetry_Parameter_Liq", &
281 ! localstart(1:2), localstride(1:2), localedge(1:2), asymmetry_water, status)
282 !
283 !
284 ! endif
285 !
286 ! end subroutine output_retrieval
287 
288 
289 
290  subroutine get_modis_data_cube ( level1b_filedata, &
291  geolocation_filedata, &
292  start, edge, stride, meas_start, meas_edge, scan_number, debug, status)
293 
294 ! Core sds of interest in the MODIS level 1B file read to fill the following:
295 ! latitude (MOD03)
296 ! longitude (MOD03)
297 ! band_measurements
298 ! solar_zenith_angle (MOD03)
299 ! sensor_zenith_angle (MOD03)
300 ! solar_azimuth_angle (MOD03)
301 ! sensor_azimuth_angle (MOD03)
302 
303 
304  use generalauxtype
305  use core_arrays
306 ! WDR out use general_array_io
310 !WDR use modis_reader
311 !WDR new use
312  use ch_xfr
313 
314  implicit none
315 
316 
317  integer, dimension (2), intent (in) :: start, edge, stride, meas_start, meas_edge
318  integer, dimension(:), intent(in) :: level1b_filedata, geolocation_filedata
319  integer, intent(in) :: scan_number
320 
321  logical, intent (in) :: debug
322  integer, intent (out) :: status
323 
324  integer :: numberofbands ,checkvariable, i, j, k
325 
326  integer :: xdimension, meas_xdimension, ydimension
327  real,dimension(:,:),allocatable :: level1b_buffer, sza_temp
328  integer(integer_onebyte),dimension(:,:), allocatable :: uncertainty_buffer
329  logical :: errorflag, useoffset
330  real :: unc_spec, unc_scale
331  integer :: unc_idx
332 
333  logical :: cal_type_is_refl
334 
335 
336  status = success
337  numberofbands = size(bands)
338 
339 ! get level 1b data
340 
341  meas_xdimension = meas_edge(1)
342  xdimension = edge(1)
343  ydimension = edge(2)
344 
345 ! allocate(level1b_buffer(meas_xdimension, ydimension))
346 ! allocate(uncertainty_buffer(meas_xdimension, ydimension))
347 ! allocate(sza_temp(meas_xdimension, ydimension))
348 
349 
350  solar_constant_37 = 10.9295 ! average of Terra and Aqua values from table in Platnick and Fontenla (2008)
351 
352 !WDR out with the reads
353 ! do i = 1, numberofbands
354 ! if(bands(i) < 20 .or. bands(i) == 26) then
355 ! Cal_type_is_refl = .true.
356 ! else
357 ! Cal_type_is_refl = .false.
358 ! endif
359 !
360 ! call read_L1B(level1b_filedata, &
361 ! bands(i), Cal_type_is_refl, &
362 ! meas_xdimension,ydimension,&
363 ! meas_start(1), &
364 ! level1b_buffer, &
365 ! uncertainty_buffer, unc_spec, unc_scale )
366 ! band_measurements(:,i,:) = level1b_buffer(:,:)
367 !
368 ! unc_idx = 0
369 !
370 ! if (bands(i) == 1) unc_idx = band_0065
371 ! if (bands(i) == 2) unc_idx = band_0086
372 ! if (bands(i) == 5) unc_idx = band_0124
373 ! if (bands(i) == 6) unc_idx = band_0163
374 ! if (bands(i) == 7) unc_idx = band_0213
375 ! if (bands(i) == channel_37um) unc_idx = band_0370 - 1
376 !
377 ! if (unc_idx /= 0) then
378 !
379 ! band_uncertainty(:,unc_idx,:) = uncertainty_buffer(:,:)
380 ! spec_uncertain(unc_idx) = unc_spec
381 ! uncertain_sf(unc_idx) = unc_scale
382 !
383 ! endif
384 !
385 ! enddo
386 
387 !WDR fill the arrays with the l2gen values
388 !print*, "WDR check shape of band_measurements ", shape(band_measurements)
389 !print*, "WDR check shape of c2_refl ", shape(c2_refl)
390 !print*, "WDR check shape of band_uncertainty ", shape(band_uncertainty)
391 !print*, "WDR check shape of c2_bnd_unc ", shape(c2_bnd_unc)
396 
397 ! deallocate(level1b_buffer, uncertainty_buffer)
398 
399  no_valid_data = 0
400 
401 ! get full resolution Latitude and Longitude arrays
402 !WDR out again
403 ! call read_float_array(geolocation_filedata, "Latitude", start, stride, edge, latitude, status)
404 ! call read_float_array(geolocation_filedata, "Longitude", start, stride, edge, longitude, status)
405 !
406 ! useoffset = .false.
407 ! call read_int_array(geolocation_filedata, "SensorZenith", start, stride, edge, useoffset, sensor_zenith_angle, status)
408 !
409 ! call read_int_array(geolocation_filedata, "SensorAzimuth", start, stride, edge, useoffset, sensor_azimuth_angle, status)
410 !
411 !
412 ! call read_int_array(geolocation_filedata, "SolarZenith", meas_start, stride, meas_edge, useoffset, sza_temp, status)
413 !
414 ! call read_int_array(geolocation_filedata, "SolarAzimuth", start, stride, edge, useoffset, solar_azimuth_angle, status)
415 
416 
417 !WDR not needed here
418 ! do i = 1, numberofbands
419 ! if(bands(i) < 20 .or. bands(i) == 26) then
420 ! where (band_measurements(:,i,:) > 0.)
421 ! band_measurements(:,i,:) = band_measurements(:,i,:) / cos(d2r*sza_temp)
422 ! end where
423 ! endif
424 ! enddo
425 
426 ! WDR insert angles`
427 ! if (scan_number == 1) then
428 ! solar_zenith_angle(:,:) = sza_temp(1:edge(1), :)
429 ! else
430 ! solar_zenith_angle(:,:) = sza_temp(2:edge(1)+1, :)
431 ! endif
432  latitude = c2_lat
433  longitude = c2_lon
438 
439 ! deallocate(sza_temp)
440 
441 
442 ! calculate the relative azimuth
443 ! WDR we already compute this and send it in so...
444 ! relative_azimuth_angle = solar_azimuth_angle + 180. - sensor_azimuth_angle
445 
446 ! do j = 1, ydimension
447 ! do i = 1, xdimension
448 
449 ! if (relative_azimuth_angle(i,j) <= 0.) relative_azimuth_angle(i,j) = -relative_azimuth_angle(i,j)
450 ! if (relative_azimuth_angle(i,j) > 180.) relative_azimuth_angle(i,j) = 360. - relative_azimuth_angle(i,j)
451 ! enddo
452 ! enddo
453 
454 ! relative_azimuth_angle = abs(relative_azimuth_angle)
455 ! where(relative_azimuth_angle > 180.) relative_azimuth_angle =360. - relative_azimuth_angle
456 
457 ! WDR already prepared
459 ! WDR I believe that just a (+) relaz is needed
461 
462  max_rel_azimuth = 0.
463  min_rel_azimuth = 999999.
464 
465 
466  max_sensor_zenith = 0.
467  min_sensor_zenith = 99999.
468 
469  max_solar_zenith = 0.
470  min_solar_zenith = 99999.
471 
472  do j=1, ydimension
473  do i=1, xdimension
474 
475  if (relative_azimuth_angle(i,j) < min_rel_azimuth .and. relative_azimuth_angle(i,j) >= 0.) &
477  if (relative_azimuth_angle(i,j) > max_rel_azimuth .and. relative_azimuth_angle(i,j) >= 0.) &
479 
480  if (solar_zenith_angle(i,j) < min_solar_zenith .and. solar_zenith_angle(i,j) >= 0. ) &
482  if (solar_zenith_angle(i,j) > max_solar_zenith .and. solar_zenith_angle(i,j) >= 0.) &
484 
485 
486 
487  end do
488  end do
489 
490 
491 ! the sensor zenith is constant along a column
492  do j=1, ydimension
493 
494  do i=1, xdimension
495  if (sensor_zenith_angle(i,j) < 0.) exit ! bad data, get a different line
496  if (sensor_zenith_angle(i,j) < min_sensor_zenith .and. sensor_zenith_angle(i,j) >= 0.) &
498  if (sensor_zenith_angle(i,j) > max_sensor_zenith .and. sensor_zenith_angle(i,j) >= 0.) &
500  end do
501 
502 ! if (i >= xdimension) then
503 ! exit ! we are done, a good line of data
504 ! endif
505 
506  end do
507 
508  end subroutine get_modis_data_cube
509 
510 
511  end module modis_io_module
Definition: ch_xfr.f90:1
real, dimension(:,:,:), allocatable c2_bnd_unc
Definition: ch_xfr.f90:10
real, dimension(:,:), allocatable c2_lon
Definition: ch_xfr.f90:12
real(single), dimension(:,:), allocatable longitude
real, dimension(:,:), allocatable c2_sena
Definition: ch_xfr.f90:13
real, dimension(:), allocatable c2_unc_sf
Definition: ch_xfr.f90:11
real(single), dimension(:,:), allocatable latitude
real, dimension(:,:), allocatable c2_solz
Definition: ch_xfr.f90:13
real, dimension(:,:), allocatable sensor_azimuth_angle
real, dimension(:,:), allocatable c2_lat
Definition: ch_xfr.f90:12
real, dimension(:,:), allocatable solar_zenith_angle
Definition: core_arrays.f90:6
real, dimension(:,:), allocatable c2_relaz
Definition: ch_xfr.f90:13
real, dimension(6) uncertain_sf
real(single), dimension(:,:,:), allocatable band_measurements
real, dimension(:,:), allocatable sensor_zenith_angle
real(single), dimension(:,:), allocatable relative_azimuth_angle
real, dimension(:,:,:), allocatable band_uncertainty
real, dimension(:,:), allocatable solar_azimuth_angle
real, dimension(:,:), allocatable c2_senz
Definition: ch_xfr.f90:12
real, dimension(6) spec_uncertain
#define abs(a)
Definition: misc.h:90
real, dimension(:,:), allocatable c2_sola
Definition: ch_xfr.f90:13
subroutine, public get_modis_data_cube(level1b_filedata, geolocation_filedata, start, edge, stride, meas_start, meas_edge, scan_number, debug, status)
real, dimension(:), allocatable c2_spec_unc
Definition: ch_xfr.f90:11
real, dimension(:,:,:), allocatable c2_refl
Definition: ch_xfr.f90:10