NASA Logo
Ocean Color Science Software

ocssw V2022
general_science_module.f90
Go to the documentation of this file.
2 
3  implicit none
4 
5 contains
6 
7  subroutine set_drel(threshold_relative_azimuth, drel)
8 
11 
12  real, intent(in) :: threshold_relative_azimuth
13  real, intent(inout) :: drel
14 
15 
16  if (min_solar_zenith > 0.98 .or. min_sensor_zenith > 0.98) then
17  drel = 30.
18  else if (min_solar_zenith > 0.85 .or. min_sensor_zenith > 0.85) then
19  drel = 10.
20  else
21  drel = threshold_relative_azimuth
22  endif
23 
24  end subroutine set_drel
25 
26  subroutine set_interp_controls(i,j, scattering_angle, cur_wind_speed, drel, &
27  threshold_solar_zenith, &
28  threshold_sensor_zenith, &
29  wind_speed_only, interp_SS, interp_MS )
30 
33  use core_arrays
34 
35  real, intent(in) :: scattering_angle, cur_wind_speed, drel,threshold_solar_zenith, &
36  threshold_sensor_zenith
37 
38  integer, intent(in) :: i, j
39 
40  logical, intent(inout) :: wind_speed_only, interp_SS, interp_MS
41 
42  real :: dsol, dsen, dscat
43  real :: diff_scat_angle, diff_scat_angle_ss, diff_solar_zenith, &
44  diff_sensor_zenith, diff_relative_azimuth, diff_wind_speed
45 
46 
47 
48  dsol = threshold_solar_zenith
49  dsen = threshold_sensor_zenith
50 
51  diff_scat_angle = abs(scattering_angle - lastinterp_scat_angle)
52  diff_scat_angle_ss = abs(scattering_angle - lastinterp_scat_angle_ss)
53 
54  if (scattering_angle < 60. .or. (scattering_angle > 120. .and. scattering_angle <= 160.)) then
55  dscat = 2.0
56  dsen = 1.0
57  else if (scattering_angle >= 60 .and. scattering_angle <= 120.) then
58  dscat = dscat3
59  else ! more than 160 degrees
60  dscat = 1.0
61  dsen = 0.5
62  endif
63 
64 
65  diff_solar_zenith = abs(solar_zenith_angle(i,j) - lastinterp_solar_zenith)
66  diff_sensor_zenith= abs(sensor_zenith_angle(i,j)- lastinterp_sensor_zenith)
67  diff_relative_azimuth= abs(relative_azimuth_angle(i,j)-lastinterp_relative_azimuth)
68 
69 
70  diff_wind_speed = abs(cur_wind_speed - lastinterp_wind_speed)
71 
72 
73  if (cox_munk .and. diff_wind_speed > threshold_wind_speed .and. &
74  .not. (diff_solar_zenith > dsol) .and. &
75  .not. (diff_sensor_zenith > dsen) .and. &
76  .not. (diff_relative_azimuth > drel) .and. &
77  .not. (diff_scat_angle > dscat) .and. &
78  .not. (cox_munk .neqv. last_cox_munk)) then
79  wind_speed_only = .true.
80  else
81  ! WDR temp change set .true. to do every pt
82  wind_speed_only = .false.
83  !wind_speed_only = .true.
84  endif
85 
86 ! interpolate the libraries
87  ! WDR temp change set .true. to do every pt
88  interp_ms = .false.
89  !interp_MS = .true.
90 
91  if ( diff_solar_zenith > dsol .or. &
92  diff_sensor_zenith > dsen .or. &
93  diff_relative_azimuth > drel .or. &
94  diff_scat_angle > dscat .or. &
95  (cox_munk .neqv. last_cox_munk) .or. &
96  (cox_munk .and. diff_wind_speed > threshold_wind_speed)) then
97 
98  interp_ms = .true.
99 
100  if (diff_scat_angle > dscat) &
101  lastinterp_scat_angle = scattering_angle
102 
103  if (diff_solar_zenith > dsol) &
105  if (diff_sensor_zenith > dsen) &
107  if (diff_relative_azimuth > drel) &
109 
110  if (cox_munk .and. diff_wind_speed > threshold_wind_speed) &
111  lastinterp_wind_speed = cur_wind_speed
112 
113  if (cox_munk .neqv. last_cox_munk) &
115 
116 
117  endif
118 
119  ! WDR temp change set .true. to do every pt
120  interp_ss = .false.
121  !interp_SS = .true.
122 
123  if ((diff_scat_angle_ss > 0.1) .or. (cox_munk .neqv. last_cox_munk) .or. &
124  (cox_munk .and. diff_wind_speed > threshold_wind_speed)) then
125  interp_ss = .true.
126  lastinterp_scat_angle_ss = scattering_angle
127  end if
128 
129 
130  end subroutine set_interp_controls
131 
132 
133  subroutine set_water_path_answers(i,j, finalize_liq, finalize_ice)
134 
135  use libraryarrays
137  use core_arrays
140  use ch_xfr, only: c2_sensor_id, oci_id, ocis_id
141 
142  integer, intent(in) :: i, j
143  logical, dimension(:), intent(in) :: finalize_liq, finalize_ice
144 
145  if (allocated(liquid_water_path)) &
147  if (allocated(liquid_water_path_1621)) &
149 
150  if (allocated(liquid_water_path_16)) &
152  if (allocated(liquid_water_path_37)) &
154 
155  if (allocated(liquid_water_path_22)) &
157 
158  if (finalize_liq(1)) then
161  liquid_water_density, &
162  water_radii, &
163  extinction_water(1, :), &
165  endif
166  if (finalize_liq(2)) then
169  liquid_water_density, &
170  water_radii, &
171  extinction_water(1, :), &
172  liquid_water_path(i,j))
173  endif
174 
175  if( ( c2_sensor_id == oci_id ) .OR. ( c2_sensor_id == ocis_id ) )then
176  if (finalize_liq(3)) then
179  liquid_water_density, &
180  water_radii, &
181  extinction_water(1, :), &
183  endif
184  else
185  if (finalize_liq(3)) then
188  liquid_water_density, &
189  water_radii, &
190  extinction_water(1, :), &
192  endif
193  endif
194 
195  if (finalize_liq(4)) then
198  liquid_water_density, &
199  water_radii, &
200  extinction_water(1, :), &
202  endif
203 
204  if (finalize_ice(1)) then
207  ice_water_density, &
208  ice_radii, &
209  extinction_ice(1, :), &
210  liquid_water_path_16(i,j))
211  endif
212 
213  if (finalize_ice(2)) then
216  ice_water_density, &
217  ice_radii, &
218  extinction_ice(1, :), &
219  liquid_water_path(i,j))
220 
221  endif
222 
223  if( ( c2_sensor_id == oci_id ) .OR. ( c2_sensor_id == ocis_id ) )then
224  if (finalize_ice(3)) then
227  ice_water_density, &
228  ice_radii, &
229  extinction_ice(1, :), &
231  endif
232  else
233  if (finalize_ice(3)) then
236  ice_water_density, &
237  ice_radii, &
238  extinction_ice(1, :), &
240  endif
241  endif
242 
243  if (finalize_ice(4)) then
246  ice_water_density, &
247  ice_radii, &
248  extinction_ice(1, :), &
250  endif
251 
252  end subroutine set_water_path_answers
253 
254 
255  subroutine set_failure_answers(i,j, RSS_final, set_near)
256 
257  use core_arrays
260  use ch_xfr, only: c2_sensor_id, oci_id, ocis_id
261 
262  integer, intent(in) :: i,j
263  real, dimension(:), intent(in) :: RSS_final
264  logical, intent(in), dimension(:) :: set_near
265 
266 
267  if (set_near(1)) then
268  failure_metric_16(i,j)%tau = nint(optical_thickness_16_final(i,j)/retr_scale_factor)
270  failure_metric_16(i,j)%re = nint(effective_radius_16_final(i,j)/retr_scale_factor)
272  failure_metric_16(i,j)%RSS = nint(rss_final(re16)*100./retr_scale_factor)
276  endif
277 
278  if (set_near(2)) then
279  failure_metric(i,j)%tau = nint(optical_thickness_final(i,j)/retr_scale_factor)
280  if (optical_thickness_final(i,j) < 0) failure_metric(i,j)%tau = fillvalue_int2
281  failure_metric(i,j)%re = nint(effective_radius_21_final(i,j)/retr_scale_factor)
283  failure_metric(i,j)%RSS = nint(rss_final(re21)*100./retr_scale_factor)
287  endif
288  if( ( c2_sensor_id == oci_id ) .OR. ( c2_sensor_id == ocis_id ) ) then
289  if (set_near(3)) then
290  failure_metric_22(i,j)%tau = nint(optical_thickness_22_final(i,j)/retr_scale_factor)
292  failure_metric_22(i,j)%re = nint(effective_radius_22_final(i,j)/retr_scale_factor)
294  failure_metric_22(i,j)%RSS = nint(rss_final(re22)*100./retr_scale_factor)
298  endif
299  else
300  if (set_near(3)) then
301  failure_metric_37(i,j)%tau = nint(optical_thickness_37_final(i,j)/retr_scale_factor)
303  failure_metric_37(i,j)%re = nint(effective_radius_37_final(i,j)/retr_scale_factor)
305  failure_metric_37(i,j)%RSS = nint(rss_final(re37)*100./retr_scale_factor)
309  endif
310  endif
311 
312  if (set_near(4)) then
313  failure_metric_1621(i,j)%tau = nint(optical_thickness_1621_final(i,j)/retr_scale_factor)
315  failure_metric_1621(i,j)%re = nint(effective_radius_1621_final(i,j)/retr_scale_factor)
317  failure_metric_1621(i,j)%RSS = nint(rss_final(re1621)*100./retr_scale_factor)
321  endif
322 
323  end subroutine set_failure_answers
324 
325  subroutine init_science_arrays
326  ! W. Robinson, 1 may 2019 - set this to preserve lines processed
327  ! from a previous call and place them in the proper location
328  ! for the current scan
329  use generalauxtype
331  use core_arrays
332  use ch_xfr
333 
334  integer :: scan_sav = -999 ! saved scan from previous call
335  integer :: iln
336 
337  ! WDR OK, this sets up the lines to just transfer array values
338  ! to their new location relative to the new scan which points to
339  ! the center of the 3 line array (c2_scan). The transfer is done
340  ! from xfr_from to xfr_to for a total of xfr_num lines.
341  ! Otherwise, initialize here for lines scn_loop_st to scn_loop_en
342  ! and process in modis_science_module.f90
343  if( ( ( c2_scan - scan_sav ) .ge. 3 ) .or. &
344  ( ( c2_scan - scan_sav ) .le. -3 ) ) then
345  scn_loop_st = 1
346  scn_loop_en = 3 ! for the 3-line standard
347  !scn_loop_en = 5 ! for the 5-line test
348  xfr_num = 0
349  else if( ( c2_scan - scan_sav ) .eq. 2 ) then ! cur scan is 2 ahead
350  scn_loop_st = 2
351  scn_loop_en = 3
352  xfr_num = 1
353  xfr_from = (/ 3, 0 /)
354  xfr_to = (/ 1, 0 /)
355  else if( ( c2_scan - scan_sav ) .eq. 1 ) then ! cur scan is 1 ahead
356  ! for no mandatory re-compute of center line (fastest)
357  scn_loop_st = 3
358  scn_loop_en = 3
359  xfr_num = 2
360  xfr_from = (/ 2, 3 /)
361  xfr_to = (/ 1, 2 /)
362  ! for mandatory re-compute of center line (does a re-compute of
363  ! output line)
364  !scn_loop_st = 2
365  !scn_loop_en = 3
366  !xfr_num = 1
367  !xfr_from = (/ 2, 0 /)
368  !xfr_to = (/ 1, 0 /)
369  ! for no efficiency at all (Do all 3 lines again)
370  !scn_loop_st = 1
371  !scn_loop_en = 3
372  !xfr_num = 0
373  ! test to go back to 3-lin use - well, it works
374  !scn_loop_st = 1
375  ! WDR for 5-lin test scn_loop_en = 3
376  !scn_loop_en = 3
377  !scn_loop_en = 5
378  !xfr_num = 0
379  else if( ( c2_scan - scan_sav ) .eq. 0 ) then ! cur scan is unchanged
380  scn_loop_st = 0
381  scn_loop_en = 0
382  xfr_num = 0
383  else if( ( c2_scan - scan_sav ) .eq. -1 ) then ! cur scan is 1 behind
384  ! for no mandatory re-compute of center line
385  scn_loop_st = 1
386  scn_loop_en = 1
387  xfr_num = 2
388  xfr_from = (/ 2, 1 /)
389  xfr_to = (/ 3, 2 /)
390  !for mandatory re-compute of center line
391  !scn_loop_st = 1
392  !scn_loop_en = 2
393  !xfr_num = 1
394  !xfr_from = (/ 2, 0 /)
395  !xfr_to = (/ 3, 0 /)
396  else if( ( c2_scan - scan_sav ) .eq. -2 ) then ! cur scan is 2 behind
397  scn_loop_st = 1
398  scn_loop_en = 2
399  xfr_num = 1
400  xfr_from = (/ 1, 0 /)
401  xfr_to = (/ 3, 0 /)
402  endif
403 !print*, __FILE__, __LINE__
404 !print*, "scan_sav, c2_scan, scn_loop_st, scn_loop_en ", scan_sav, c2_scan, scn_loop_st, scn_loop_en
405 !print*, "xfr_num, xfr_from, xfr_to ", xfr_num, xfr_from, xfr_to
406  scan_sav = c2_scan
407  ! WDR We'll have a transfer phase (to put the lines in the right place)
408  ! and a init phase to put fill in the open lines of the array
409  !
410  ! Transfer phase
411  if( xfr_num > 0 ) then
412  do iln = 1, xfr_num
413  if (allocated(optical_thickness_final)) then
423 
433 
434  failure_metric(:,xfr_to(iln))%tau = failure_metric_sav(:,xfr_from(iln))%tau
435  failure_metric(:,xfr_to(iln))%re = failure_metric_sav(:,xfr_from(iln))%re
436  failure_metric(:,xfr_to(iln))%RSS = failure_metric_sav(:,xfr_from(iln))%RSS
437 
441 
442  atm_corr_refl(:,:, xfr_to(iln)) = atm_corr_refl_sav(:,:, xfr_from(iln))
444  endif
445 
446  if (allocated(optical_thickness_22_final)) then
456  failure_metric_22(:,xfr_to(iln))%tau = failure_metric_22_sav(:,xfr_from(iln))%tau
458  failure_metric_22(:,xfr_to(iln))%RSS = failure_metric_22_sav(:,xfr_from(iln))%RSS
459  endif
460  if (allocated(seviri_cloudphase)) seviri_cloudphase(:, xfr_to(iln)) = seviri_cloudphase(:, xfr_from(iln))
461 
468 
475 
483  ml_test_flag(:, xfr_to(iln)) = ml_test_flag_sav(:, xfr_from(iln))
486 
487 
488  failure_metric_16(:,xfr_to(iln))%tau = failure_metric_16_sav(:,xfr_from(iln))%tau
490  failure_metric_16(:,xfr_to(iln))%RSS = failure_metric_16_sav(:,xfr_from(iln))%RSS
491 
492  failure_metric_37(:,xfr_to(iln))%tau = failure_metric_37_sav(:,xfr_from(iln))%tau
494  failure_metric_37(:,xfr_to(iln))%RSS = failure_metric_37_sav(:,xfr_from(iln))%RSS
495 
496  if (allocated(tau_liquid)) then
497  tau_liquid(:, xfr_to(iln)) = tau_liquid_sav(:, xfr_from(iln))
498  tau_ice(:, xfr_to(iln)) = tau_ice_sav(:, xfr_from(iln))
499  re21_liquid(:, xfr_to(iln)) = re21_liquid_sav(:, xfr_from(iln))
500  re21_ice(:, xfr_to(iln)) = re21_ice_sav(:, xfr_from(iln))
501  endif
502  ! WDR this may at least need transfer and was not in the orig code:
503  cloudsummary(:, xfr_to(iln)) = cloudsummary_sav(:, xfr_from(iln))
504  ! WDR 31jul19 add in transfer of processing_information
505  processing_information(:, xfr_to(iln)) = &
507  !
508  ! WDR The point, table reflectance diagnostic arrays
509  prd_out_refl_loc_2100( :, xfr_to(iln), : ) = &
510  prd_out_refl_loc_2100_sav( :, xfr_from(iln), : )
511  prd_out_refl_loc_1600( :, xfr_to(iln), : ) = &
512  prd_out_refl_loc_1600_sav( :, xfr_from(iln), : )
513  prd_out_refl_loc_2200( :, xfr_to(iln), : ) = &
514  prd_out_refl_loc_2200_sav( :, xfr_from(iln), : )
515  prd_out_refl_loc_1621( :, xfr_to(iln), : ) = &
516  prd_out_refl_loc_1621_sav( :, xfr_from(iln), : )
517  enddo
518  endif ! Transfer phase
519  !
520  ! Init phase
521  if( scn_loop_st .ne. 0 ) then
522  if (allocated(optical_thickness_final)) then
523 
536 
543 
547 
551 
554 
555  endif
556 
557  if( allocated( optical_thickness_22_final ) ) then
571  endif
572 
574 
581 
588 
599 
600 
604 
608 
609  if (allocated(tau_liquid)) then
614  endif
615  ! also the refl_loc initialize
619  endif ! Init phase
620  end subroutine init_science_arrays
621 
622  subroutine capture_arrays
623  ! W. Robinson, 3 May 2019 new routine to save the states of the 3
624  ! line science arrays after their derivation in modis_science_module.f90
625  ! for use in the next line (really 3 lines) of data processing
626  use generalauxtype
628  use core_arrays
629  use ch_xfr
630 
631  integer :: adims(3), np, nl, nb
632  integer :: checkvariable, sav_alloc = 0
633  !
634  ! if required, allocate the save arrays
635  if( sav_alloc .eq. 0 ) then
636  sav_alloc = 1
637  adims = shape( atm_corr_refl )
638  nb = adims(1)
639  np = adims(2)
640  nl = adims(3)
641 
642  allocate(optical_thickness_final_sav(np,nl), stat = checkvariable)
643  allocate(optical_thickness_1621_final_sav(np,nl), stat = checkvariable)
644  allocate(effective_radius_21_final_sav(np,nl), stat = checkvariable)
645  allocate(effective_radius_1621_final_sav(np,nl), stat = checkvariable)
646  allocate(liquid_water_path_sav(np,nl), stat = checkvariable)
647  allocate(liquid_water_path_1621_sav(np,nl), stat = checkvariable)
648  allocate(optical_thickness_final_pcl_sav(np,nl), stat = checkvariable)
649  allocate(optical_thickness_1621_final_pcl_sav(np,nl), stat = checkvariable)
650  allocate(effective_radius_21_final_pcl_sav(np,nl), stat = checkvariable)
651  allocate(effective_radius_1621_final_pcl_sav(np,nl), stat = checkvariable)
652  allocate(liquid_water_path_pcl_sav(np,nl), stat = checkvariable)
653  allocate(liquid_water_path_1621_pcl_sav(np,nl), stat = checkvariable)
654  allocate(optical_thickness_error_sav(np,nl), stat = checkvariable)
655  allocate(effective_radius_21_error_sav(np,nl), stat = checkvariable)
656  allocate(liquid_water_path_error_sav(np,nl), stat = checkvariable)
657  allocate(optical_thickness_1621_error_sav(np,nl), stat = checkvariable)
658  allocate(effective_radius_1621_error_sav(np,nl), stat = checkvariable)
659  allocate(liquid_water_path_1621_error_sav(np,nl), stat = checkvariable)
660  allocate(failure_metric_sav(np,nl), stat = checkvariable)
661  allocate(failure_metric_1621_sav(np,nl), stat = checkvariable)
662  allocate(atm_corr_refl_sav(nb,np,nl), stat = checkvariable)
663  allocate(precip_water_094_sav(np,nl), stat = checkvariable)
664  allocate(optical_thickness_16_final_sav(np,nl), stat = checkvariable)
665  allocate(optical_thickness_37_final_sav(np,nl), stat = checkvariable)
666  allocate(effective_radius_16_final_sav(np,nl), stat = checkvariable)
667  allocate(effective_radius_37_final_sav(np,nl), stat = checkvariable)
668  allocate(liquid_water_path_16_sav(np,nl), stat = checkvariable)
669  allocate(liquid_water_path_37_sav(np,nl), stat = checkvariable)
670  allocate(optical_thickness_16_final_pcl_sav(np,nl), stat = checkvariable)
671  allocate(optical_thickness_37_final_pcl_sav(np,nl), stat = checkvariable)
672  allocate(effective_radius_16_final_pcl_sav(np,nl), stat = checkvariable)
673  allocate(effective_radius_37_final_pcl_sav(np,nl), stat = checkvariable)
674  allocate(liquid_water_path_16_pcl_sav(np,nl), stat = checkvariable)
675  allocate(liquid_water_path_37_pcl_sav(np,nl), stat = checkvariable)
676  allocate(optical_thickness_16_error_sav(np,nl), stat = checkvariable)
677  allocate(optical_thickness_37_error_sav(np,nl), stat = checkvariable)
678  allocate(effective_radius_16_error_sav(np,nl), stat = checkvariable)
679  allocate(effective_radius_37_error_sav(np,nl), stat = checkvariable)
680  allocate(liquid_water_path_16_error_sav(np,nl), stat = checkvariable)
681  allocate(liquid_water_path_37_error_sav(np,nl), stat = checkvariable)
682  allocate(cloud_layer_flag_sav(np,nl), stat = checkvariable)
683  allocate(ml_test_flag_sav(np,nl), stat = checkvariable)
684  allocate(csr_flag_array_sav(np,nl), stat = checkvariable)
685  allocate(irw_temperature_sav(np,nl), stat = checkvariable)
686  allocate(failure_metric_16_sav(np,nl), stat = checkvariable)
687  allocate(failure_metric_37_sav(np,nl), stat = checkvariable)
688  if (allocated(tau_liquid)) then
689  allocate(tau_liquid_sav(np,nl), stat = checkvariable)
690  allocate(tau_ice_sav(np,nl), stat = checkvariable)
691  allocate(re21_liquid_sav(np,nl), stat = checkvariable)
692  allocate(re21_ice_sav(np,nl), stat = checkvariable)
693  endif
694  allocate(cloudsummary_sav(np,nl), stat = checkvariable)
695  allocate(processing_information_sav(np,nl), stat = checkvariable)
696  ! WDR add the point / table diagnostics
697  allocate( prd_out_refl_loc_2100_sav(np,nl,10), stat = checkvariable)
698  allocate( prd_out_refl_loc_1600_sav(np,nl,10), stat = checkvariable)
699  allocate( prd_out_refl_loc_1621_sav(np,nl,10), stat = checkvariable)
700  if( ( c2_sensor_id == oci_id ) .OR. ( c2_sensor_id == ocis_id ) ) then
701  allocate(optical_thickness_22_final_sav(np,nl), stat = checkvariable)
702  allocate(effective_radius_22_final_sav(np,nl), stat = checkvariable)
703  allocate(liquid_water_path_22_sav(np,nl), stat = checkvariable)
704  allocate(optical_thickness_22_final_pcl_sav(np,nl), &
705  stat = checkvariable)
706  allocate(effective_radius_22_final_pcl_sav(np,nl), stat = checkvariable)
707  allocate(liquid_water_path_22_pcl_sav(np,nl), stat = checkvariable)
708  allocate(optical_thickness_22_error_sav(np,nl), stat = checkvariable)
709  allocate(effective_radius_22_error_sav(np,nl), stat = checkvariable)
710  allocate(liquid_water_path_22_error_sav(np,nl), stat = checkvariable)
711  allocate(failure_metric_22_sav(np,nl), stat = checkvariable)
712  allocate( prd_out_refl_loc_2200_sav(np,nl,10), stat = checkvariable)
713  endif
714  endif
715  ! and copy the data to the save arrays
763 
764  if( allocated( effective_radius_22_final ) ) then
775  endif
776 
777  if (allocated(tau_liquid)) then
782  endif
785  ! table point refl diagnostic
789 
790  end subroutine capture_arrays
791 
792  subroutine assign_retrieval_error(xpoint, ypoint)
795  use core_arrays
796  integer, intent(in) :: xpoint,ypoint
797 
798 
799  if (allocated(optical_thickness_final)) then
800 
801  optical_thickness_final(xpoint, ypoint) = fillvalue_real
803  effective_radius_21_final(xpoint, ypoint) = fillvalue_real
805  liquid_water_path(xpoint, ypoint) = fillvalue_real
806  liquid_water_path_1621(xpoint, ypoint) = fillvalue_real
807  optical_thickness_error(xpoint, ypoint) = fillvalue_int2
808  effective_radius_21_error(xpoint, ypoint) = fillvalue_int2
809  liquid_water_path_error(xpoint, ypoint) = fillvalue_int2
813 
814  endif
815 
818  effective_radius_16_final(xpoint, ypoint) = fillvalue_real
819  effective_radius_37_final(xpoint, ypoint) = fillvalue_real
820  liquid_water_path_16(xpoint, ypoint) = fillvalue_real
821  liquid_water_path_37(xpoint, ypoint) = fillvalue_real
824  effective_radius_16_error(xpoint, ypoint) = fillvalue_int2
825  effective_radius_37_error(xpoint, ypoint) = fillvalue_int2
828  cloud_layer_flag(xpoint, ypoint) = 0
829  ml_test_flag(xpoint, ypoint) = 0
830  csr_flag_array(xpoint, ypoint) = 0
831 
832  if( allocated( effective_radius_22_final ) ) then
833  effective_radius_22_final(xpoint, ypoint) = fillvalue_real
835  liquid_water_path_22(xpoint, ypoint) = fillvalue_real
836  effective_radius_22_final(xpoint, ypoint) = fillvalue_real
837  effective_radius_22_error(xpoint, ypoint) = fillvalue_int2
840  endif
841 
842  if (allocated(tau_liquid)) then
843  tau_liquid(xpoint, ypoint) = fillvalue_int2
844  tau_ice(xpoint, ypoint) = fillvalue_int2
845  re21_liquid(xpoint, ypoint) = fillvalue_int2
846  re21_ice(xpoint, ypoint) = fillvalue_int2
847  endif
848 
849 
850  end subroutine assign_retrieval_error
851 
852  subroutine split_pcl(xdim, ydim)
853 
854  use core_arrays
856 
857  integer, intent(in) :: xdim, ydim
858 
859  integer :: i,j
860 
861  do j=1, ydim
862  do i=1, xdim
863 
864  if (csr_flag_array(i,j) == 1 .or. csr_flag_array(i,j) == 3) then
865 
866 
867  if (allocated(optical_thickness_final)) then
868  if (optical_thickness_final(i,j) > 0.) &
869  optical_thickness_final_pcl(i,j) = nint(optical_thickness_final(i,j) / retr_scale_factor)
871 
872  if (optical_thickness_1621_final(i,j) > 0.) &
873  optical_thickness_1621_final_pcl(i,j) = nint(optical_thickness_1621_final(i,j) / retr_scale_factor)
875 
876  if (effective_radius_21_final(i,j) > 0.) &
877  effective_radius_21_final_pcl(i,j) = nint(effective_radius_21_final(i,j) / retr_scale_factor)
879 
880  if (effective_radius_1621_final(i,j) > 0.) &
881  effective_radius_1621_final_pcl(i,j) = nint(effective_radius_1621_final(i,j) / retr_scale_factor)
883 
884  if (liquid_water_path(i,j) > 0.) &
885  liquid_water_path_pcl(i,j) = nint(liquid_water_path(i,j))
887 
888  if (liquid_water_path_1621(i,j) > 0.) &
891  endif
892 
893  if (allocated(optical_thickness_22_final)) then
894  if( optical_thickness_22_final(i,j) > 0.) &
895  optical_thickness_22_final_pcl(i,j) = nint(optical_thickness_22_final(i,j) / retr_scale_factor)
897 
898  if( effective_radius_22_final(i,j) > 0.) &
899  effective_radius_22_final_pcl(i,j) = nint(effective_radius_22_final(i,j) / retr_scale_factor)
901 
902  if( liquid_water_path_22(i,j) > 0.) &
905 
906  endif
907 
908  if (optical_thickness_37_final(i,j) > 0.) &
909  optical_thickness_37_final_pcl(i,j) = nint(optical_thickness_37_final(i,j) / retr_scale_factor)
911 
912 
913  if (optical_thickness_16_final(i,j) > 0.) &
914  optical_thickness_16_final_pcl(i,j) = nint(optical_thickness_16_final(i,j) / retr_scale_factor)
916 
917  if (effective_radius_16_final(i,j) > 0.) &
918  effective_radius_16_final_pcl(i,j) = nint(effective_radius_16_final(i,j) / retr_scale_factor)
920 
921 
922  if (effective_radius_37_final(i,j) > 0.) &
923  effective_radius_37_final_pcl(i,j) = nint(effective_radius_37_final(i,j) / retr_scale_factor)
925 
926 
927  if (liquid_water_path_16(i,j) > 0.) &
930 
931  if (liquid_water_path_37(i,j) > 0.) &
934 
935 
936  endif
937 
938  end do
939  end do
940 
941 
942 
943  end subroutine split_pcl
944 
945 
946 
947 
948 end module general_science_module
949 
integer *2, dimension(:,:), allocatable optical_thickness_37_error
Definition: core_arrays.f90:76
Definition: ch_xfr.f90:1
integer *2, dimension(:,:), allocatable effective_radius_16_final_pcl
Definition: core_arrays.f90:54
type(failed_type), dimension(:,:), allocatable failure_metric_22
integer *2, dimension(:,:), allocatable optical_thickness_22_final_pcl
Definition: core_arrays.f90:50
integer, parameter re21
subroutine compute_water_path(tau, re, density, library_re, extinction_efficiency, water_path)
real(single), dimension(:,:), allocatable liquid_water_path
Definition: core_arrays.f90:65
integer *2, dimension(:,:), allocatable liquid_water_path_1621_pcl_sav
real(single), dimension(:,:), allocatable effective_radius_22_final_sav
real(single), dimension(:,:), allocatable liquid_water_path_16_sav
integer *2, dimension(:,:), allocatable effective_radius_1621_final_pcl
Definition: core_arrays.f90:58
integer *2, dimension(:,:), allocatable liquid_water_path_37_pcl_sav
integer *2, dimension(:,:), allocatable liquid_water_path_16_pcl
Definition: core_arrays.f90:61
integer *2, dimension(:,:), allocatable optical_thickness_16_error_sav
integer(integer_onebyte), dimension(:,:), allocatable cloud_layer_flag
Definition: core_arrays.f90:92
integer *2, dimension(:,:), allocatable optical_thickness_16_final_pcl_sav
integer *2, dimension(:,:), allocatable effective_radius_16_error
Definition: core_arrays.f90:80
integer *2, dimension(:,:), allocatable tau_liquid_sav
real(single), dimension(:,:), allocatable optical_thickness_22_final_sav
integer *2, dimension(:,:), allocatable liquid_water_path_22_pcl_sav
integer ocis_id
Definition: ch_xfr.f90:51
integer *2, dimension(:,:), allocatable optical_thickness_22_error
Definition: core_arrays.f90:74
integer *2, dimension(:,:), allocatable effective_radius_37_error_sav
integer *2, dimension(:,:), allocatable liquid_water_path_16_error
Definition: core_arrays.f90:85
subroutine set_interp_controls(i, j, scattering_angle, cur_wind_speed, drel, threshold_solar_zenith, threshold_sensor_zenith, wind_speed_only, interp_SS, interp_MS)
real, dimension(:,:,:), allocatable prd_out_refl_loc_2100_sav
Definition: ch_xfr.f90:71
integer *2, dimension(:,:), allocatable effective_radius_1621_error_sav
real(single), dimension(:,:), allocatable optical_thickness_37_final
Definition: core_arrays.f90:41
real(single), dimension(:,:), allocatable liquid_water_path_22_sav
integer *2, dimension(:,:), allocatable optical_thickness_37_final_pcl
Definition: core_arrays.f90:52
real(single), dimension(:,:), allocatable effective_radius_37_final
Definition: core_arrays.f90:46
real(single), dimension(:,:), allocatable optical_thickness_1621_final_sav
real(single), dimension(:,:), allocatable liquid_water_path_37_sav
integer *2, dimension(:,:), allocatable effective_radius_21_final_pcl
Definition: core_arrays.f90:55
integer, parameter re37
subroutine assign_retrieval_error(xpoint, ypoint)
integer *2, dimension(:,:), allocatable optical_thickness_1621_error
Definition: core_arrays.f90:88
integer *2, dimension(:,:), allocatable liquid_water_path_pcl
Definition: core_arrays.f90:59
integer *2, dimension(:,:), allocatable tau_liquid
Definition: core_arrays.f90:34
real(single), dimension(:,:), allocatable effective_radius_16_final_sav
integer *2, dimension(:,:), allocatable effective_radius_22_error
Definition: core_arrays.f90:79
real, dimension(:,:), allocatable irw_temperature
integer *2, dimension(:,:), allocatable optical_thickness_error
Definition: core_arrays.f90:73
real(single), dimension(:,:), allocatable optical_thickness_16_final_sav
real, dimension(:,:,:), allocatable prd_out_refl_loc_1621_sav
Definition: ch_xfr.f90:74
real(single), dimension(:,:), allocatable liquid_water_path_1621_sav
real, dimension(:,:,:), allocatable atm_corr_refl_sav
real, dimension(:,:,:), allocatable prd_out_refl_loc_1600
Definition: ch_xfr.f90:63
integer *2, dimension(:,:), allocatable effective_radius_21_final_pcl_sav
integer *2, parameter fillvalue_int2
real, dimension(:,:,:), allocatable atm_corr_refl
type(failed_type), dimension(:,:), allocatable failure_metric_1621
integer *2, dimension(:,:), allocatable liquid_water_path_error
Definition: core_arrays.f90:83
subroutine split_pcl(xdim, ydim)
type(failed_type), dimension(:,:), allocatable failure_metric_sav
type(failed_type), dimension(:,:), allocatable failure_metric_37_sav
type(failed_type), dimension(:,:), allocatable failure_metric_1621_sav
type(processflag), dimension(:,:), allocatable cloudsummary
real(single), dimension(:), allocatable water_radii
integer *2, dimension(:,:), allocatable liquid_water_path_37_error
Definition: core_arrays.f90:86
integer *2, dimension(:,:), allocatable liquid_water_path_22_error_sav
integer *2, dimension(:,:), allocatable liquid_water_path_16_error_sav
integer *2, dimension(:,:), allocatable liquid_water_path_error_sav
integer *2, dimension(:,:), allocatable effective_radius_16_final_pcl_sav
integer *2, dimension(:,:), allocatable optical_thickness_16_final_pcl
Definition: core_arrays.f90:51
integer *2, dimension(:,:), allocatable liquid_water_path_16_pcl_sav
type(failed_type), dimension(:,:), allocatable failure_metric_16
integer *2, dimension(:,:), allocatable effective_radius_22_error_sav
subroutine set_water_path_answers(i, j, finalize_liq, finalize_ice)
real, dimension(:,:,:), allocatable prd_out_refl_loc_2200
Definition: ch_xfr.f90:65
real, dimension(:,:,:), allocatable prd_out_refl_loc_1600_sav
Definition: ch_xfr.f90:72
integer(integer_onebyte), dimension(:,:), allocatable csr_flag_array
Definition: core_arrays.f90:93
real, dimension(:,:), allocatable solar_zenith_angle
Definition: core_arrays.f90:6
integer *2, dimension(:,:), allocatable optical_thickness_final_pcl_sav
real(single), dimension(:,:), allocatable effective_radius_37_final_sav
real(single), dimension(:,:), allocatable effective_radius_21_final_sav
integer *2, dimension(:,:), allocatable effective_radius_16_error_sav
real(single), dimension(:,:), allocatable liquid_water_path_37
Definition: core_arrays.f90:68
integer *2, dimension(:,:), allocatable effective_radius_21_error_sav
real(single), dimension(:,:), allocatable extinction_ice
real(single), dimension(:,:), allocatable optical_thickness_final
Definition: core_arrays.f90:38
integer scn_loop_en
integer *2, dimension(:,:), allocatable liquid_water_path_37_error_sav
real(single), dimension(:,:), allocatable extinction_water
integer *2, dimension(:,:), allocatable optical_thickness_final_pcl
Definition: core_arrays.f90:49
type(failed_type), dimension(:,:), allocatable failure_metric
real(single), dimension(:,:), allocatable optical_thickness_final_sav
real(single), dimension(:,:), allocatable optical_thickness_22_final
Definition: core_arrays.f90:39
real(single), dimension(:,:), allocatable liquid_water_path_1621
Definition: core_arrays.f90:69
integer, parameter re22
subroutine set_failure_answers(i, j, RSS_final, set_near)
real(single), dimension(:), allocatable ice_radii
type(failed_type), dimension(:,:), allocatable failure_metric_22_sav
integer *2, dimension(:,:), allocatable liquid_water_path_1621_error
Definition: core_arrays.f90:90
integer scn_loop_st
integer *2, dimension(:,:), allocatable effective_radius_37_final_pcl
Definition: core_arrays.f90:57
integer *2, dimension(:,:), allocatable optical_thickness_1621_final_pcl
Definition: core_arrays.f90:53
integer c2_sensor_id
Definition: ch_xfr.f90:50
integer *2, dimension(:,:), allocatable re21_liquid
Definition: core_arrays.f90:34
real, dimension(:,:), allocatable precip_water_094
integer, dimension(2) xfr_to
real(single), dimension(:,:), allocatable liquid_water_path_sav
integer *2, dimension(:,:), allocatable optical_thickness_22_final_pcl_sav
integer, dimension(2) xfr_from
subroutine set_drel(threshold_relative_azimuth, drel)
real, parameter dscat3
real, dimension(:,:,:), allocatable prd_out_refl_loc_1621
Definition: ch_xfr.f90:64
integer *2, dimension(:,:), allocatable optical_thickness_1621_error_sav
real, dimension(:,:), allocatable sensor_zenith_angle
integer *2, dimension(:,:), allocatable effective_radius_22_final_pcl_sav
integer *2, dimension(:,:), allocatable optical_thickness_22_error_sav
integer(integer_onebyte), dimension(:,:), allocatable ml_test_flag
Definition: core_arrays.f90:92
real(single), dimension(:,:), allocatable relative_azimuth_angle
integer *2, dimension(:,:), allocatable effective_radius_22_final_pcl
Definition: core_arrays.f90:56
real(single), dimension(:,:), allocatable optical_thickness_1621_final
Definition: core_arrays.f90:42
integer(integer_onebyte), dimension(:,:), allocatable csr_flag_array_sav
integer *2, dimension(:,:), allocatable effective_radius_37_final_pcl_sav
integer *2, dimension(:,:), allocatable re21_ice
Definition: core_arrays.f90:35
integer *2, dimension(:,:), allocatable optical_thickness_37_error_sav
integer *2, dimension(:,:), allocatable optical_thickness_error_sav
integer *2, dimension(:,:), allocatable effective_radius_1621_error
Definition: core_arrays.f90:89
integer c2_scan
Definition: ch_xfr.f90:46
type(qualityanalysis), dimension(:,:), allocatable processing_information
integer *2, dimension(:,:), allocatable tau_ice_sav
integer *2, dimension(:,:), allocatable effective_radius_21_error
Definition: core_arrays.f90:78
real(single), dimension(:,:), allocatable liquid_water_path_16
Definition: core_arrays.f90:67
integer *2, dimension(:,:), allocatable optical_thickness_1621_final_pcl_sav
integer *1, dimension(:,:), allocatable seviri_cloudphase
real(single), dimension(:,:), allocatable effective_radius_1621_final_sav
type(failed_type), dimension(:,:), allocatable failure_metric_37
real(single), dimension(:,:), allocatable effective_radius_22_final
Definition: core_arrays.f90:45
integer *2, dimension(:,:), allocatable liquid_water_path_22_pcl
Definition: core_arrays.f90:60
real(single), dimension(:,:), allocatable liquid_water_path_22
Definition: core_arrays.f90:66
integer oci_id
Definition: ch_xfr.f90:52
real, dimension(:,:), allocatable precip_water_094_sav
integer *2, dimension(:,:), allocatable liquid_water_path_pcl_sav
real(single), dimension(:,:), allocatable optical_thickness_16_final
Definition: core_arrays.f90:40
real(single), dimension(:,:), allocatable optical_thickness_37_final_sav
integer *2, dimension(:,:), allocatable re21_ice_sav
real(single), dimension(:,:), allocatable effective_radius_16_final
Definition: core_arrays.f90:43
real, dimension(:,:,:), allocatable prd_out_refl_loc_2200_sav
Definition: ch_xfr.f90:73
integer *2, dimension(:,:), allocatable optical_thickness_37_final_pcl_sav
integer(integer_onebyte), dimension(:,:), allocatable ml_test_flag_sav
integer xfr_num
real, dimension(:,:), allocatable irw_temperature_sav
integer *2, dimension(:,:), allocatable optical_thickness_16_error
Definition: core_arrays.f90:75
integer(integer_onebyte), dimension(:,:), allocatable cloud_layer_flag_sav
integer *2, dimension(:,:), allocatable liquid_water_path_1621_error_sav
type(processflag), dimension(:,:), allocatable cloudsummary_sav
real, dimension(:,:,:), allocatable prd_out_refl_loc_2100
Definition: ch_xfr.f90:62
integer *2, dimension(:,:), allocatable tau_ice
Definition: core_arrays.f90:34
type(qualityanalysis), dimension(:,:), allocatable processing_information_sav
integer *2, dimension(:,:), allocatable effective_radius_37_error
Definition: core_arrays.f90:81
#define abs(a)
Definition: misc.h:90
real(single), dimension(:,:), allocatable effective_radius_1621_final
Definition: core_arrays.f90:47
integer *2, dimension(:,:), allocatable liquid_water_path_37_pcl
Definition: core_arrays.f90:62
integer *2, dimension(:,:), allocatable re21_liquid_sav
real, parameter threshold_wind_speed
integer *2, dimension(:,:), allocatable liquid_water_path_1621_pcl
Definition: core_arrays.f90:63
integer *2, dimension(:,:), allocatable liquid_water_path_22_error
Definition: core_arrays.f90:84
integer, parameter re1621
type(failed_type), dimension(:,:), allocatable failure_metric_16_sav
integer *2, dimension(:,:), allocatable effective_radius_1621_final_pcl_sav
integer, parameter re16
real(single), dimension(:,:), allocatable effective_radius_21_final
Definition: core_arrays.f90:44