Changeset 2822 for LMDZ5/trunk/libf
- Timestamp:
- Mar 14, 2017, 10:58:56 AM (8 years ago)
- Location:
- LMDZ5/trunk/libf/phylmd/cosp
- Files:
-
- 4 edited
Legend:
- Unmodified
- Added
- Removed
-
TabularUnified LMDZ5/trunk/libf/phylmd/cosp/cosp_output_mod.F90 ¶
r2713 r2822 20 20 INTEGER, DIMENSION(3), SAVE :: nhoricosp,nvert,nvertmcosp,nvertcol,nvertbze, & 21 21 nvertsratio,nvertisccp,nvertp,nverttemp,nvertmisr, & 22 nvertReffIce,nvertReffLiq 22 nvertReffIce,nvertReffLiq,nverttau 23 23 REAL, DIMENSION(3), SAVE :: zoutm_cosp 24 24 !$OMP THREADPRIVATE(nhoricosp, nvert,nvertmcosp,nvertcol,nvertsratio,nvertbze,nvertisccp,nvertp,zoutm_cosp,nverttemp,nvertmisr) 25 !$OMP THREADPRIVATE(nvertReffIce,nvertReffLiq )25 !$OMP THREADPRIVATE(nvertReffIce,nvertReffLiq,nverttau) 26 26 REAL, SAVE :: zdtimemoy_cosp 27 27 !$OMP THREADPRIVATE(zdtimemoy_cosp) … … 207 207 SUBROUTINE cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, & 208 208 ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml, & 209 ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid) 210 209 ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid, stlidar) 211 210 212 211 USE iophy … … 229 228 logical :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, use_vgrid, ok_all_xml 230 229 type(cosp_vgrid) :: vgrid ! Information on vertical grid of stats 230 type(cosp_lidarstats) :: stlidar ! Summary statistics from lidar simulator 231 231 232 232 !!! Variables locales … … 236 236 real,dimension(2,SR_BINS) :: sratio_bounds 237 237 real,dimension(SR_BINS) :: sratio_ax 238 real,dimension(DBZE_BINS) :: dbze_ax 238 239 CHARACTER(LEN=20), DIMENSION(3) :: chfreq = (/ '1day', '1d ', '3h ' /) 239 240 … … 257 258 enddo 258 259 259 ! do ii=1,DBZE_BINS 260 ! dbze_ax(i) = CFAD_ZE_MIN + CFAD_ZE_WIDTH*(ii - 0.5) 261 ! enddo 262 263 ! sratio_bounds(2,:)=stlidar%srbval(:) ! srbval contains the upper 260 do i=1,DBZE_BINS 261 dbze_ax(i) = CFAD_ZE_MIN + CFAD_ZE_WIDTH*(i - 0.5) 262 enddo 263 264 265 sratio_bounds(2,:)=stlidar%srbval(:) ! srbval contains the upper 264 266 ! limits from lmd_ipsl_stats.f90 265 !sratio_bounds(1,2:SR_BINS) = stlidar%srbval(1:SR_BINS-1)266 !sratio_bounds(1,1) = 0.0267 !sratio_bounds(2,SR_BINS) = 1.e5 ! This matches with Chepfer et al., JGR,267 sratio_bounds(1,2:SR_BINS) = stlidar%srbval(1:SR_BINS-1) 268 sratio_bounds(1,1) = 0.0 269 sratio_bounds(2,SR_BINS) = 1.e5 ! This matches with Chepfer et al., JGR, 268 270 ! ! 2009. However, it is not consistent 269 271 ! with the upper limit in 270 272 ! lmd_ipsl_stats.f90, which is 271 273 ! LIDAR_UNDEF-1=998.999 272 !sratio_ax(:) = (sratio_bounds(1,:)+sratio_bounds(2,:))/2.0274 sratio_ax(:) = (sratio_bounds(1,:)+sratio_bounds(2,:))/2.0 273 275 274 276 cosp_outfilenames(1) = 'histmthCOSP' … … 331 333 CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP) 332 334 CALL wxios_add_vaxis("cth16", MISR_N_CTH, MISR_CTH) 333 !CALL wxios_add_vaxis("dbze", DBZE_BINS, dbze_ax)334 !CALL wxios_add_vaxis("scatratio", SR_BINS, sratio_ax)335 CALL wxios_add_vaxis("dbze", DBZE_BINS, dbze_ax) 336 CALL wxios_add_vaxis("scatratio", SR_BINS, sratio_ax) 335 337 CALL wxios_add_vaxis("ReffIce", numMODISReffIceBins, reffICE_binCenters) 336 338 CALL wxios_add_vaxis("ReffLiq", numMODISReffLiqBins, reffLIQ_binCenters) 339 print*,'reffICE_binCenters=',reffICE_binCenters 340 CALL wxios_add_vaxis("tau", 7, ISCCP_TAU) 337 341 338 342 #endif … … 384 388 nvertReffLiq(iff)) 385 389 386 !CALL histvert(cosp_nidfiles(iff),"dbze","equivalent_reflectivity_factor","dBZ",DBZE_BINS,dbze_ax,nvertbze(iff))390 CALL histvert(cosp_nidfiles(iff),"dbze","equivalent_reflectivity_factor","dBZ",DBZE_BINS,dbze_ax,nvertbze(iff)) 387 391 388 ! CALL histvert(cosp_nidfiles(iff),"scatratio","backscattering_ratio","1",SR_BINS,sratio_ax,nvertsratio(iff)) 392 CALL histvert(cosp_nidfiles(iff),"scatratio","backscattering_ratio","1",SR_BINS,sratio_ax,nvertsratio(iff)) 393 394 CALL histvert(cosp_nidfiles(iff),"tau","cloud optical depth","1",7,ISCCP_TAU,nverttau(iff)) 389 395 390 396 !!! Valeur indefinie en cas IOIPSL -
TabularUnified LMDZ5/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90 ¶
r2794 r2822 17 17 CONTAINS 18 18 19 SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, missing_ val, &19 SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, missing_cosp, & 20 20 cfg, gbx, vgrid, sglidar, sgradar, stlidar, stradar, & 21 21 isccp, misr, modis) … … 32 32 !!! Variables d'entree 33 33 integer :: itap, Nlevlmdz, Ncolumns, Npoints 34 real :: freq_COSP, dtime, missing_val 34 real :: freq_COSP, dtime, missing_val, missing_cosp 35 35 type(cosp_config) :: cfg ! Control outputs 36 36 type(cosp_gridbox) :: gbx ! Gridbox information. Input for COSP … … 49 49 integer :: itau_wcosp 50 50 real, dimension(Npoints,PARASOL_NREFL) :: parasolcrefl, Ncref 51 52 53 #ifdef CPP_XIOS 54 missing_val=missing_cosp 55 #else 56 missing_val=0. 57 #endif 51 58 52 59 Nlevout = vgrid%Nlvgrid … … 169 176 CALL histwrite3d_cosp(o_clcalipsotmpun,stlidar%lidarcldtmp(:,:,4),nverttemp) 170 177 178 #ifdef CPP_XIOS 179 CALL histwrite4d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr) 180 #else 171 181 do icl=1,SR_BINS 172 182 CALL histwrite3d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr(:,icl,:),nvert,icl) 173 183 enddo 174 175 CALL histwrite3d_cosp(o_parasol_refl,stlidar%parasolrefl,nvertp) 184 CALL histwrite3d_cosp(o_parasol_refl,stlidar%parasolrefl,nvertp) 185 #endif 176 186 177 187 do k=1,PARASOL_NREFL … … 182 192 Ncref(ip,k) = 1. 183 193 else 184 parasolcrefl(ip,k)= 0.194 parasolcrefl(ip,k)=missing_val 185 195 Ncref(ip,k) = 0. 186 196 endif … … 190 200 CALL histwrite3d_cosp(o_parasol_crefl,parasolcrefl,nvertp) 191 201 202 #ifdef CPP_XIOS 203 CALL histwrite4d_cosp(o_atb532,sglidar%beta_tot) 204 #else 192 205 do icl=1,Ncolumns 193 206 CALL histwrite3d_cosp(o_atb532,sglidar%beta_tot(:,icl,:),nvertmcosp,icl) 194 207 enddo 208 #endif 209 195 210 CALL histwrite3d_cosp(o_beta_mol532,sglidar%beta_mol,nvertmcosp) 196 211 endif !Lidar 197 212 198 213 if (cfg%Lradar_sim) then 214 215 #ifdef CPP_XIOS 216 CALL histwrite4d_cosp(o_dbze94,sgradar%Ze_tot) 217 CALL histwrite4d_cosp(o_cfadDbze94,stradar%cfad_ze) 218 #else 199 219 do icl=1,Ncolumns 200 220 CALL histwrite3d_cosp(o_dbze94,sgradar%Ze_tot(:,icl,:),nvertmcosp,icl) … … 203 223 CALL histwrite3d_cosp(o_cfadDbze94,stradar%cfad_ze(:,icl,:),nvert,icl) 204 224 enddo 225 #endif 205 226 endif 206 227 … … 259 280 260 281 CALL histwrite2d_cosp(o_sunlit,gbx%sunlit) 282 #ifdef CPP_XIOS 283 CALL histwrite4d_cosp(o_clisccp2,isccp%fq_isccp) 284 #else 261 285 do icl=1,7 262 286 CALL histwrite3d_cosp(o_clisccp2,isccp%fq_isccp(:,icl,:),nvertisccp,icl) 263 287 enddo 288 #endif 264 289 CALL histwrite3d_cosp(o_boxtauisccp,isccp%boxtau,nvertcol) 265 290 CALL histwrite3d_cosp(o_boxptopisccp,isccp%boxptop,nvertcol) … … 284 309 enddo 285 310 311 #ifdef CPP_XIOS 312 CALL histwrite4d_cosp(o_clMISR,misr%fq_MISR) 313 #else 286 314 do icl=1,7 287 315 CALL histwrite3d_cosp(o_clMISR,misr%fq_MISR(:,icl,:),nvertmisr,icl) 288 316 enddo 317 #endif 289 318 endif 290 319 … … 376 405 enddo 377 406 407 #ifdef CPP_XIOS 408 CALL histwrite4d_cosp(o_clmodis,modis%Optical_Thickness_vs_Cloud_Top_Pressure) 409 #else 378 410 do icl=1,7 379 411 CALL histwrite3d_cosp(o_clmodis, & 380 412 modis%Optical_Thickness_vs_Cloud_Top_Pressure(:,icl,:),nvertisccp,icl) 381 413 enddo 414 #endif 382 415 383 416 where(modis%Optical_Thickness_vs_ReffIce == R_UNDEF) & … … 387 420 modis%Optical_Thickness_vs_ReffLiq = missing_val 388 421 422 #ifdef CPP_XIOS 423 ! print*,'dimension de crimodis=',size(modis%Optical_Thickness_vs_ReffIce,2),& 424 ! size(modis%Optical_Thickness_vs_ReffIce,3) 425 CALL histwrite4d_cosp(o_crimodis,modis%Optical_Thickness_vs_ReffIce) 426 CALL histwrite4d_cosp(o_crlmodis,modis%Optical_Thickness_vs_ReffLiq) 427 #else 389 428 do icl=1,7 390 429 CALL histwrite3d_cosp(o_crimodis, & … … 393 432 modis%Optical_Thickness_vs_ReffLiq(:,icl,:),nvertReffLiq,icl) 394 433 enddo 434 #endif 395 435 endif 396 436 … … 794 834 END SUBROUTINE histwrite3d_cosp 795 835 836 ! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE 837 ! AI sept 2013 838 SUBROUTINE histwrite4d_cosp(var, field) 839 USE dimphy 840 USE mod_phys_lmdz_para 841 USE ioipsl 842 use iophy 843 USE mod_grid_phy_lmdz, ONLY: nbp_lon 844 USE print_control_mod, ONLY: lunout,prt_level 845 846 #ifdef CPP_XIOS 847 USE xios, only: xios_send_field 848 #endif 849 850 851 IMPLICIT NONE 852 INCLUDE 'clesphys.h' 853 854 TYPE(ctrl_outcosp), INTENT(IN) :: var 855 REAL, DIMENSION(:,:,:), INTENT(IN) :: field ! --> field(klon,:) 856 857 INTEGER :: iff, k 858 859 REAL,DIMENSION(klon_mpi,SIZE(field,2),SIZE(field,3)) :: buffer_omp 860 REAL :: field4d(nbp_lon,jj_nb,SIZE(field,2),SIZE(field,3)) 861 INTEGER :: ip, n, nlev, nlev2 862 INTEGER, ALLOCATABLE, DIMENSION(:) :: index4d 863 CHARACTER(LEN=20) :: nomi, nom 864 865 IF (prt_level >= 9) write(lunout,*)'Begin histrwrite4d ',var%name 866 867 IF(cosp_varsdefined) THEN 868 !Et sinon on.... écrit 869 IF (SIZE(field,1)/=klon) & 870 CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1) 871 872 nlev=SIZE(field,2) 873 nlev2=SIZE(field,3) 874 CALL Gather_omp(field,buffer_omp) 875 !$OMP MASTER 876 CALL grid1Dto2D_mpi(buffer_omp,field4d) 877 878 #ifdef CPP_XIOS 879 IF (ok_all_xml) THEN 880 CALL xios_send_field(var%name, Field4d(:,:,1:nlev,1:nlev2)) 881 IF (prt_level >= 1) WRITE(lunout,*)'xios_send_field ',var%name 882 ENDIF 883 #endif 884 885 !$OMP END MASTER 886 ENDIF ! vars_defined 887 IF (prt_level >= 9) write(lunout,*)'End histrwrite4d_cosp ',nom 888 END SUBROUTINE histwrite4d_cosp 889 796 890 SUBROUTINE conf_cospoutputs(nam_var,cles_var) 797 891 !!! Lecture des noms et cles de sortie des variables dans config.def -
TabularUnified LMDZ5/trunk/libf/phylmd/cosp/modis_simulator.F90 ¶
r2794 r2822 532 532 533 533 ! ######################################################################################## 534 ! Normalize pixel counts to fraction. The first three cloud fractions have been set to -1 535 ! in cloud-free areas, so set those places to 0. 536 ! ######################################################################################## 537 Cloud_Fraction_High_Mean(1:nPoints) = Cloud_Fraction_High_Mean(1:nPoints) /nSubcols 538 Cloud_Fraction_Mid_Mean(1:nPoints) = Cloud_Fraction_Mid_Mean(1:nPoints) /nSubcols 539 Cloud_Fraction_Low_Mean(1:nPoints) = Cloud_Fraction_Low_Mean(1:nPoints) /nSubcols 540 Cloud_Fraction_Total_Mean(1:nPoints) = Cloud_Fraction_Total_Mean(1:nPoints) /nSubcols 541 534 ! Normalize pixel counts to fraction. 535 ! ######################################################################################## 536 Cloud_Fraction_High_Mean(1:nPoints) = Cloud_Fraction_High_Mean(1:nPoints) /nSubcols 537 Cloud_Fraction_Mid_Mean(1:nPoints) = Cloud_Fraction_Mid_Mean(1:nPoints) /nSubcols 538 Cloud_Fraction_Low_Mean(1:nPoints) = Cloud_Fraction_Low_Mean(1:nPoints) /nSubcols 539 Cloud_Fraction_Total_Mean(1:nPoints) = Cloud_Fraction_Total_Mean(1:nPoints) /nSubcols 540 Cloud_Fraction_Ice_Mean(1:nPoints) = Cloud_Fraction_Ice_Mean(1:nPoints) /nSubcols 541 Cloud_Fraction_Water_Mean(1:nPoints) = Cloud_Fraction_Water_Mean(1:nPoints) /nSubcols 542 542 543 ! ######################################################################################## 543 544 ! Set clear-scenes to undefined -
TabularUnified LMDZ5/trunk/libf/phylmd/cosp/phys_cosp.F90 ¶
r2794 r2822 325 325 call cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, & 326 326 ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml, & 327 ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid )327 ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid, stlidar) 328 328 !$OMP END MASTER 329 329 !$OMP BARRIER
Note: See TracChangeset
for help on using the changeset viewer.