46 SUBROUTINE cosp_stats(gbx,sgx,cfg,sgradar,sglidar,vgrid,stradar,stlidar)
65 logical :: ok_lidar_cfad = .
false.
66 real,
dimension(:,:,:),
allocatable :: Ze_out,betatot_out,betamol_in,betamol_out,ph_in,ph_out
67 real,
dimension(:,:),
allocatable :: ph_c,betamol_c
72 ncolumns = gbx%Ncolumns
75 if (cfg%Lcfad_Lidarsr532) ok_lidar_cfad=.
true.
77 if (vgrid%use_vgrid)
then
78 allocate(ze_out(npoints,ncolumns,nlr),betatot_out(npoints,ncolumns,nlr), &
79 betamol_in(npoints,1,nlevels),betamol_out(npoints,1,nlr),betamol_c(npoints,nlr), &
80 ph_in(npoints,1,nlevels),ph_out(npoints,1,nlr),ph_c(npoints,nlr))
85 ph_in(:,1,:) = gbx%ph(:,:)
89 if (cfg%Lradar_sim)
then
91 nlr,vgrid%zl,vgrid%zu,ze_out,log_units=.
true.)
96 if (cfg%Llidar_sim)
then
97 betamol_in(:,1,:) = sglidar%beta_mol(:,:)
99 nlr,vgrid%zl,vgrid%zu,betamol_out)
101 nlr,vgrid%zl,vgrid%zu,betatot_out)
103 nlr,vgrid%zl,vgrid%zu,ph_out)
104 ph_c(:,:) = ph_out(:,1,:)
105 betamol_c(:,:) = betamol_out(:,1,:)
108 ,betatot_out,betamol_c,sglidar%refl,gbx%land,ph_c &
110 ,stlidar%cfad_sr,stlidar%srbval &
111 ,
lidar_ncat,stlidar%lidarcld,stlidar%cldlayer,stlidar%parasolrefl)
115 betatot_out,betamol_c,ze_out, &
116 stradar%lidar_only_freq_cloud,stradar%radar_lidar_tcc)
118 deallocate(ze_out,betatot_out,betamol_in,betamol_out,betamol_c,ph_in,ph_out,ph_c)
121 if (cfg%Lradar_sim) stradar%cfad_ze =
cosp_cfad(npoints,ncolumns,nlr,
dbze_bins,sgradar%Ze_tot, &
126 ,sglidar%beta_tot,sglidar%beta_mol,sglidar%refl,gbx%land,gbx%ph &
128 ,stlidar%cfad_sr,stlidar%srbval &
129 ,
lidar_ncat,stlidar%lidarcld,stlidar%cldlayer,stlidar%parasolrefl)
132 sglidar%beta_tot,sglidar%beta_mol,sgradar%Ze_tot, &
133 stradar%lidar_only_freq_cloud,stradar%radar_lidar_tcc)
147 SUBROUTINE cosp_change_vertical_grid(Npoints,Ncolumns,Nlevels,zfull,zhalf,y,M,zl,zu,r,log_units)
150 integer,
intent(in) :: Npoints
151 integer,
intent(in) :: Nlevels
152 integer,
intent(in) :: Ncolumns
153 real,
dimension(Npoints,Nlevels),
intent(in) :: zfull
154 real,
dimension(Npoints,Nlevels),
intent(in) :: zhalf
155 real,
dimension(Npoints,Ncolumns,Nlevels),
intent(in) :: y
156 integer,
intent(in) :: M
157 real,
dimension(M),
intent(in) :: zl
158 real,
dimension(M),
intent(in) :: zu
159 logical,
optional,
intent(in) :: log_units
161 real,
dimension(Npoints,Ncolumns,M),
intent(out) :: r
168 real,
dimension(Npoints) :: ws,sumwyp
169 real,
dimension(Npoints,Nlevels) :: xl,xu
170 real,
dimension(Npoints,Nlevels) :: w
171 real,
dimension(Npoints,Ncolumns,Nlevels) :: yp
174 if (
present(log_units)) lunits=log_units
179 xu(:,1:nlevels-1) = xl(:,2:nlevels)
180 xu(:,nlevels) = zfull(:,nlevels) + zfull(:,nlevels) - zhalf(:,nlevels)
195 if ((xl(i,j) < zl(k)).and.(xu(i,j) > zl(k)).and.(xu(i,j) <= zu(k)))
then
198 w(i,j) = xu(i,j) - zl(k)
199 else if ((xl(i,j) >= zl(k)).and.(xu(i,j) <= zu(k)))
then
202 w(i,j) = xu(i,j) - xl(i,j)
203 else if ((xl(i,j) >= zl(k)).and.(xl(i,j) < zu(k)).and.(xu(i,j) >= zu(k)))
then
206 w(i,j) = zu(k) - xl(i,j)
207 else if ((xl(i,j) <= zl(k)).and.(xu(i,j) >= zu(k)))
then
210 w(i,j) = zu(k) - zl(k)
220 if (zu(k) > zhalf(i,1))
then
221 ws(i) = ws(i) + w(i,l)
222 sumwyp(i) = sumwyp(i) + w(i,l)*yp(i,j,l)
227 if (zu(k) > zhalf(i,1))
then
228 if (ws(i) > 0.0) r(i,j,k) = sumwyp(i)/ws(i)
238 if (zu(k) > zhalf(i,1))
then
239 if (r(i,j,k) <= 0.0)
then
242 r(i,j,k) = 10.0*log10(r(i,j,k))
real function, dimension(npoints, nbins, nlevels) cosp_cfad(Npoints, Ncolumns, Nlevels, Nbins, x, xmin, xmax, bmin, bwidth)
integer, parameter parasol_nrefl
real, parameter cfad_ze_width
integer, parameter sr_bins
subroutine cosp_lidar_only_cloud(Npoints, Ncolumns, Nlevels, beta_tot, beta_mol, Ze_tot, lidar_only_freq_cloud, tcc)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
integer, parameter dbze_bins
integer, parameter lidar_ncat
real, parameter lidar_undef
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
subroutine diag_lidar(npoints, ncol, llm, max_bin, nrefl, pnorm, pmol, refl, land, pplay, undef, ok_lidar_cfad, cfad2, srbval, ncat, lidarcld, cldlayer, parasolrefl)
subroutine cosp_stats(gbx, sgx, cfg, sgradar, sglidar, vgrid, stradar, stlidar)
subroutine cosp_change_vertical_grid(Npoints, Ncolumns, Nlevels, zfull, zhalf, y, M, zl, zu, r, log_units)
real, parameter cfad_ze_min