34 FUNCTION cosp_cfad(Npoints,Ncolumns,Nlevels,Nbins,x,xmin,xmax,bmin,bwidth)
36 integer,
intent(in) :: Npoints,Ncolumns,Nlevels,Nbins
37 real,
dimension(Npoints,Ncolumns,Nlevels),
intent(in) :: x
38 real,
intent(in) :: xmin,xmax
39 real,
intent(in) :: bmin,bwidth
41 real,
dimension(Npoints,Nbins,Nlevels) :: cosp_cfad
68 elseif ((x(i,k,j) >= xmin) .and. (x(i,k,j) <= xmax))
then
69 ibin = ceiling((x(i,k,j) - bmin)/bwidth)
70 if (ibin > nbins) ibin = nbins
71 if (ibin < 1) ibin = 1
72 cosp_cfad(i,ibin,j) = cosp_cfad(i,ibin,j) + 1.0
77 where ((cosp_cfad /=
r_undef).and.(cosp_cfad /= 0.0)) cosp_cfad = cosp_cfad / ncolumns
83 SUBROUTINE cosp_lidar_only_cloud(Npoints,Ncolumns,Nlevels,beta_tot,beta_mol,Ze_tot,lidar_only_freq_cloud,tcc)
85 integer,
intent(in) :: Npoints,Ncolumns,Nlevels
86 real,
dimension(Npoints,Nlevels),
intent(in) :: beta_mol
87 real,
dimension(Npoints,Ncolumns,Nlevels),
intent(in) :: beta_tot
88 real,
dimension(Npoints,Ncolumns,Nlevels),
intent(in) :: Ze_tot
90 real,
dimension(Npoints,Nlevels),
intent(out) :: lidar_only_freq_cloud
91 real,
dimension(Npoints),
intent(out) :: tcc
103 lidar_only_freq_cloud = 0.0
110 sc_ratio = beta_tot(pr,i,j)/beta_mol(pr,j)
112 if ((sc_ratio .le. s_att) .and. (flag_sat .eq. 0)) flag_sat = j
113 if (ze_tot(pr,i,j) .lt. -30.)
then
114 if ( (sc_ratio .gt. s_cld) .or. (flag_sat .eq. j) )
then
116 lidar_only_freq_cloud(pr,j)=lidar_only_freq_cloud(pr,j)+1.
124 if (flag_cld .eq. 1) tcc(pr)=tcc(pr)+1.
131 lidar_only_freq_cloud=lidar_only_freq_cloud/ncolumns
135 END MODULE MOD_LLNL_STATS
real function, dimension(npoints, nbins, nlevels) cosp_cfad(Npoints, Ncolumns, Nlevels, Nbins, x, xmin, xmax, bmin, bwidth)
subroutine cosp_lidar_only_cloud(Npoints, Ncolumns, Nlevels, beta_tot, beta_mol, Ze_tot, lidar_only_freq_cloud, tcc)
!$Header!integer nvarmx parameter(nfmx=10, imx=200, jmx=150, lmx=200, nvarmx=1000) real xd(imx