@@ -54,6 +54,7 @@ module quickbeam
5454 pClass_Snow1, pClass_Snow2, pClass_Mixed1, pClass_Mixed2, &
5555 pClass_Rain4, pClass_default, Zenonbinval, Zbinvallnd, &
5656 N_HYDRO,nCloudsatPrecipClass,cloudsat_preclvl
57+
5758 USE MOD_COSP_STATS, ONLY: COSP_LIDAR_ONLY_CLOUD,hist1D,COSP_CHANGE_VERTICAL_GRID
5859 implicit none
5960
@@ -232,7 +233,7 @@ end subroutine quickbeam_subcolumn
232233 ! SUBROUTINE quickbeam_column
233234 ! ######################################################################################
234235 subroutine quickbeam_column (npoints , ncolumns , nlevels , llm , DBZE_BINS , platform , &
235- Ze_tot , Ze_tot_non , land , t2m , fracPrecipIce , zlev , zlev_half , cfad_ze , &
236+ Ze_tot , Ze_tot_non , land , surfelev , t2m , fracPrecipIce , zlev , zlev_half , cfad_ze , &
236237 cloudsat_precip_cover , cloudsat_pia )
237238 ! Inputs
238239 integer ,intent (in ) :: &
@@ -245,6 +246,7 @@ subroutine quickbeam_column(npoints, ncolumns, nlevels, llm, DBZE_BINS, platform
245246 platform ! Name of platform (e.g. cloudsat)
246247 real (wp),dimension (Npoints),intent (in ) :: &
247248 land, & ! Land/Sea mask. (1/0)
249+ surfelev, & ! Surface Elevation (m)
248250 t2m ! Near-surface temperature
249251 real (wp),dimension (Npoints,Ncolumns),intent (in ) :: &
250252 fracPrecipIce ! Fraction of precipitation which is frozen. (1)
@@ -266,6 +268,7 @@ subroutine quickbeam_column(npoints, ncolumns, nlevels, llm, DBZE_BINS, platform
266268
267269 ! Local variables
268270 integer :: i,j
271+ real (wp) :: zstep
269272 real (wp),dimension (npoints,ncolumns,llm) :: ze_toti,ze_noni
270273 logical :: lcloudsat = .false.
271274
@@ -294,9 +297,11 @@ subroutine quickbeam_column(npoints, ncolumns, nlevels, llm, DBZE_BINS, platform
294297 call cosp_change_vertical_grid(Npoints,Ncolumns,Nlevels,zlev(:,nlevels:1 :- 1 ),&
295298 zlev_half(:,nlevels:1 :- 1 ),Ze_tot_non(:,:,nlevels:1 :- 1 ),llm,vgrid_zl(llm:1 :- 1 ),&
296299 vgrid_zu(llm:1 :- 1 ),Ze_noni(:,:,llm:1 :- 1 ),log_units= .true. )
297- ! Not call routine to generate diagnostics.
300+ ! Compute the zstep distance between two atmopsheric layers
301+ zstep = vgrid_zl(1 )- vgrid_zl(2 )
302+ ! Now call routine to generate diagnostics.
298303 call cloudsat_precipOccurence(Npoints, Ncolumns, llm, N_HYDRO, Ze_toti, Ze_noni, &
299- land, t2m, fracPrecipIce, cloudsat_precip_cover, cloudsat_pia)
304+ land, surfelev, t2m, fracPrecipIce, cloudsat_precip_cover, cloudsat_pia, zstep )
300305 else
301306 ! Effective reflectivity histogram
302307 do i= 1 ,Npoints
@@ -345,7 +350,7 @@ end subroutine quickbeam_column
345350 ! parameter cloudsat_preclvl, defined in src/cosp_config.F90
346351 ! ######################################################################################
347352 subroutine cloudsat_precipOccurence (Npoints , Ncolumns , llm , Nhydro , Ze_out , Ze_non_out , &
348- land , t2m , fracPrecipIce , cloudsat_precip_cover , cloudsat_pia )
353+ land , surfelev , t2m , fracPrecipIce , cloudsat_precip_cover , cloudsat_pia , zstep )
349354
350355 ! Inputs
351356 integer ,intent (in ) :: &
@@ -355,23 +360,29 @@ subroutine cloudsat_precipOccurence(Npoints, Ncolumns, llm, Nhydro, Ze_out, Ze_n
355360 llm ! Number of levels
356361 real (wp),dimension (Npoints),intent (in ) :: &
357362 land, & ! Land/Sea mask. (1/0)
363+ surfelev, & ! Surface Elevation (m)
358364 t2m ! Near-surface temperature
359365 real (wp),dimension (Npoints,Ncolumns,llm),intent (in ) :: &
360366 Ze_out, & ! Effective reflectivity factor (dBZ)
361367 Ze_non_out ! Effective reflectivity factor, w/o attenuation (dBZ)
362368 real (wp),dimension (Npoints,Ncolumns),intent (in ) :: &
363369 fracPrecipIce ! Fraction of precipitation which is frozen. (1)
370+ real (wp),intent (in ) :: &
371+ zstep ! Distance between two atmopsheric layers (m)
364372
365373 ! Outputs
366374 real (wp),dimension (Npoints,nCloudsatPrecipClass),intent (out ) :: &
367375 cloudsat_precip_cover ! Model precip rate in by CloudSat precip flag
368376 real (wp),dimension (Npoints),intent (out ) :: &
369- cloudsat_pia ! Cloudsat path integrated attenuation
370-
377+ cloudsat_pia ! Cloudsat path integrated attenuation
378+
371379 ! Local variables
372380 integer ,dimension (Npoints,Ncolumns) :: &
373381 cloudsat_pflag, & ! Subcolumn precipitation flag
374382 cloudsat_precip_pia ! Subcolumn path integrated attenutation.
383+ integer ,dimension (Npoints) :: &
384+ cloudsat_preclvl_index ! Altitude index for precip flags calculation
385+ ! in 40-level grid (one layer above surfelev)
375386 integer :: pr,i,k,m,j
376387 real (wp) :: Zmax
377388
@@ -380,57 +391,62 @@ subroutine cloudsat_precipOccurence(Npoints, Ncolumns, llm, Nhydro, Ze_out, Ze_n
380391 cloudsat_precip_pia(:,:) = 0._wp
381392 cloudsat_precip_cover(:,:) = 0._wp
382393 cloudsat_pia(:) = 0._wp
394+ cloudsat_preclvl_index(:) = 0._wp
395+
396+ ! Computing altitude index for precip flags calculation
397+ cloudsat_preclvl_index(:) = cloudsat_preclvl - floor ( surfelev(:)/ zstep )
383398
384399 ! ######################################################################################
385400 ! SUBCOLUMN processing
386401 ! ######################################################################################
387402 do i= 1 , Npoints
388403 do pr= 1 ,Ncolumns
389- ! 1) Compute the PIA in all profiles containing hydrometeors
390- if ( (Ze_non_out(i,pr,cloudsat_preclvl).gt. - 100 ) .and. (Ze_out(i,pr,cloudsat_preclvl).gt. - 100 ) ) then
391- if ( (Ze_non_out(i,pr,cloudsat_preclvl).lt. 100 ) .and. (Ze_out(i,pr,cloudsat_preclvl).lt. 100 ) ) then
392- cloudsat_precip_pia(i,pr) = Ze_non_out(i,pr,cloudsat_preclvl) - Ze_out(i,pr,cloudsat_preclvl)
393- endif
394- endif
395-
396- ! 2) Compute precipitation flag
404+ ! Compute precipitation flag
397405 ! ################################################################################
398- ! 2a ) Oceanic points.
406+ ! 1 ) Oceanic points.
399407 ! ################################################################################
400408 if (land(i) .eq. 0 ) then
409+
410+ ! 1a) Compute the PIA in all profiles containing hydrometeors
411+ if ( (Ze_non_out(i,pr,cloudsat_preclvl_index(i)).gt. - 100 ) .and. (Ze_out(i,pr,cloudsat_preclvl_index(i)).gt. - 100 ) ) then
412+ if ( (Ze_non_out(i,pr,cloudsat_preclvl_index(i)).lt. 100 ) .and. (Ze_out(i,pr,cloudsat_preclvl_index(i)).lt. 100 ) ) then
413+ cloudsat_precip_pia(i,pr) = Ze_non_out(i,pr,cloudsat_preclvl_index(i)) - Ze_out(i,pr,cloudsat_preclvl_index(i))
414+ endif
415+ endif
416+
401417 ! Snow
402418 if (fracPrecipIce(i,pr).gt. 0.9 ) then
403- if (Ze_non_out(i,pr,cloudsat_preclvl ).gt. Zenonbinval(2 )) then
419+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).gt. Zenonbinval(2 )) then
404420 cloudsat_pflag(i,pr) = pClass_Snow2 ! TSL: Snow certain
405421 endif
406- if (Ze_non_out(i,pr,cloudsat_preclvl ).gt. Zenonbinval(4 ).and. &
407- Ze_non_out(i,pr,cloudsat_preclvl ).le. Zenonbinval(2 )) then
422+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).gt. Zenonbinval(4 ).and. &
423+ Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).le. Zenonbinval(2 )) then
408424 cloudsat_pflag(i,pr) = pClass_Snow1 ! TSL: Snow possible
409425 endif
410426 endif
411427
412428 ! Mixed
413429 if (fracPrecipIce(i,pr).gt. 0.1 .and. fracPrecipIce(i,pr).le. 0.9 ) then
414- if (Ze_non_out(i,pr,cloudsat_preclvl ).gt. Zenonbinval(2 )) then
430+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).gt. Zenonbinval(2 )) then
415431 cloudsat_pflag(i,pr) = pClass_Mixed2 ! TSL: Mixed certain
416432 endif
417- if (Ze_non_out(i,pr,cloudsat_preclvl ).gt. Zenonbinval(4 ).and. &
418- Ze_non_out(i,pr,cloudsat_preclvl ).le. Zenonbinval(2 )) then
433+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).gt. Zenonbinval(4 ).and. &
434+ Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).le. Zenonbinval(2 )) then
419435 cloudsat_pflag(i,pr) = pClass_Mixed1 ! TSL: Mixed possible
420436 endif
421437 endif
422438
423439 ! Rain
424440 if (fracPrecipIce(i,pr).le. 0.1 ) then
425- if (Ze_non_out(i,pr,cloudsat_preclvl ).gt. Zenonbinval(1 )) then
441+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).gt. Zenonbinval(1 )) then
426442 cloudsat_pflag(i,pr) = pClass_Rain3 ! TSL: Rain certain
427443 endif
428- if (Ze_non_out(i,pr,cloudsat_preclvl ).gt. Zenonbinval(3 ).and. &
429- Ze_non_out(i,pr,cloudsat_preclvl ).le. Zenonbinval(1 )) then
444+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).gt. Zenonbinval(3 ).and. &
445+ Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).le. Zenonbinval(1 )) then
430446 cloudsat_pflag(i,pr) = pClass_Rain2 ! TSL: Rain probable
431447 endif
432- if (Ze_non_out(i,pr,cloudsat_preclvl ).gt. Zenonbinval(4 ).and. &
433- Ze_non_out(i,pr,cloudsat_preclvl ).le. Zenonbinval(3 )) then
448+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).gt. Zenonbinval(4 ).and. &
449+ Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).le. Zenonbinval(3 )) then
434450 cloudsat_pflag(i,pr) = pClass_Rain1 ! TSL: Rain possible
435451 endif
436452 if (cloudsat_precip_pia(i,pr).gt. 40 ) then
@@ -439,37 +455,46 @@ subroutine cloudsat_precipOccurence(Npoints, Ncolumns, llm, Nhydro, Ze_out, Ze_n
439455 endif
440456
441457 ! No precipitation
442- if (Ze_non_out(i,pr,cloudsat_preclvl ).le. - 15 ) then
458+ if (Ze_non_out(i,pr,cloudsat_preclvl_index(i) ).le. - 15 ) then
443459 cloudsat_pflag(i,pr) = pClass_noPrecip ! TSL: Not Raining
444460 endif
445461 endif ! Ocean points
446462
447463 ! ################################################################################
448- ! 2b) Land points.
464+ ! 2) Land points.
465+ ! *NOTE* For land points we go up a layer higher, so cloudsat_preclvl_index(i)-1
466+ !
449467 ! ################################################################################
450- if (land(i) .eq. 1 ) then
468+ if (land(i) .eq. 1 ) then
469+ ! 2a) Compute the PIA in all profiles containing hydrometeors
470+ if ( (Ze_non_out(i,pr,cloudsat_preclvl_index(i)- 1 ).gt. - 100 ) .and. (Ze_out(i,pr,cloudsat_preclvl_index(i)- 1 ).gt. - 100 ) ) then
471+ if ( (Ze_non_out(i,pr,cloudsat_preclvl_index(i)- 1 ).lt. 100 ) .and. (Ze_out(i,pr,cloudsat_preclvl_index(i)- 1 ).lt. 100 ) ) then
472+ cloudsat_precip_pia(i,pr) = Ze_non_out(i,pr,cloudsat_preclvl_index(i)- 1 ) - Ze_out(i,pr,cloudsat_preclvl_index(i)- 1 )
473+ endif
474+ endif
475+
451476 ! Find Zmax, the maximum reflectivity value in the attenuated profile (Ze_out);
452477 Zmax= maxval (Ze_out(i,pr,:))
453478
454479 ! Snow (T<273)
455480 if (t2m(i) .lt. 273._wp ) then
456- if (Ze_out(i,pr,cloudsat_preclvl ) .gt. Zbinvallnd(5 )) then
481+ if (Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .gt. Zbinvallnd(5 )) then
457482 cloudsat_pflag(i,pr) = pClass_Snow2 ! JEK: Snow certain
458483 endif
459- if (Ze_out(i,pr,cloudsat_preclvl ) .gt. Zbinvallnd(6 ) .and. &
460- Ze_out(i,pr,cloudsat_preclvl ).le. Zbinvallnd(5 )) then
484+ if (Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .gt. Zbinvallnd(6 ) .and. &
485+ Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ).le. Zbinvallnd(5 )) then
461486 cloudsat_pflag(i,pr) = pClass_Snow1 ! JEK: Snow possible
462487 endif
463488 endif
464489
465490 ! Mized phase (273<T<275)
466491 if (t2m(i) .ge. 273._wp .and. t2m(i) .le. 275._wp ) then
467492 if ((Zmax .gt. Zbinvallnd(1 ) .and. cloudsat_precip_pia(i,pr).gt. 30 ) .or. &
468- (Ze_out(i,pr,cloudsat_preclvl ) .gt. Zbinvallnd(4 ))) then
493+ (Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .gt. Zbinvallnd(4 ))) then
469494 cloudsat_pflag(i,pr) = pClass_Mixed2 ! JEK: Mixed certain
470495 endif
471- if ((Ze_out(i,pr,cloudsat_preclvl ) .gt. Zbinvallnd(6 ) .and. &
472- Ze_out(i,pr,cloudsat_preclvl ) .le. Zbinvallnd(4 )) .and. &
496+ if ((Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .gt. Zbinvallnd(6 ) .and. &
497+ Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .le. Zbinvallnd(4 )) .and. &
473498 (Zmax .gt. Zbinvallnd(5 )) ) then
474499 cloudsat_pflag(i,pr) = pClass_Mixed1 ! JEK: Mixed possible
475500 endif
@@ -478,14 +503,14 @@ subroutine cloudsat_precipOccurence(Npoints, Ncolumns, llm, Nhydro, Ze_out, Ze_n
478503 ! Rain (T>275)
479504 if (t2m(i) .gt. 275 ) then
480505 if ((Zmax .gt. Zbinvallnd(1 ) .and. cloudsat_precip_pia(i,pr).gt. 30 ) .or. &
481- (Ze_out(i,pr,cloudsat_preclvl ) .gt. Zbinvallnd(2 ))) then
506+ (Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .gt. Zbinvallnd(2 ))) then
482507 cloudsat_pflag(i,pr) = pClass_Rain3 ! JEK: Rain certain
483508 endif
484- if ((Ze_out(i,pr,cloudsat_preclvl ) .gt. Zbinvallnd(6 )) .and. &
509+ if ((Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .gt. Zbinvallnd(6 )) .and. &
485510 (Zmax .gt. Zbinvallnd(3 ))) then
486511 cloudsat_pflag(i,pr) = pClass_Rain2 ! JEK: Rain probable
487512 endif
488- if ((Ze_out(i,pr,cloudsat_preclvl ) .gt. Zbinvallnd(6 )) .and. &
513+ if ((Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .gt. Zbinvallnd(6 )) .and. &
489514 (Zmax.lt. Zbinvallnd(3 ))) then
490515 cloudsat_pflag(i,pr) = pClass_Rain1 ! JEK: Rain possible
491516 endif
@@ -495,7 +520,7 @@ subroutine cloudsat_precipOccurence(Npoints, Ncolumns, llm, Nhydro, Ze_out, Ze_n
495520 endif
496521
497522 ! No precipitation
498- if (Ze_out(i,pr,cloudsat_preclvl) .le. - 15 ) then
523+ if (Ze_out(i,pr,cloudsat_preclvl_index(i) - 1 ) .le. - 15 ) then
499524 cloudsat_pflag(i,pr) = pClass_noPrecip ! JEK: Not Precipitating
500525 endif
501526 endif ! Land points
@@ -514,7 +539,7 @@ subroutine cloudsat_precipOccurence(Npoints, Ncolumns, llm, Nhydro, Ze_out, Ze_n
514539 cloudsat_precip_cover(i,k) = count (cloudsat_pflag(i,:) .eq. k-1 )
515540 endif
516541 enddo
517-
542+
518543 ! Gridmean path integrated attenuation (pia)
519544 cloudsat_pia(i)= sum (cloudsat_precip_pia(i,:))
520545 enddo
0 commit comments