Changeset 4103 for LMDZ6/trunk/libf/phylmd
- Timestamp:
- Mar 17, 2022, 11:51:36 AM (3 years ago)
- Location:
- LMDZ6/trunk/libf/phylmd
- Files:
-
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/cosp/dsd.F90
r2428 r4103 57 57 integer, intent(in) :: nsizes 58 58 integer, intent(in) :: dtype 59 real*8, intent(in) :: Q,Re ,Np,D(nsizes)59 real*8, intent(in) :: Q,Re_,Np,D(nsizes) 60 60 real*8, intent(in) :: rho_a,tk,dmin,dmax,rho_c,p1,p2,p3 61 61 … … 78 78 real*8 :: tmp1, tmp2 79 79 real*8 :: pi,rc,tc 80 real*8 :: Re 80 81 81 82 integer k,lidx,uidx 83 84 Re = Re_ 82 85 83 86 tc = tk - 273.15 -
LMDZ6/trunk/libf/phylmd/cosp/radar_simulator.F90
r2428 r4103 96 96 real*8, dimension(hp%nhclass,nprof,ngate), intent(in) :: hm_matrix 97 97 real*8, dimension(hp%nhclass,nprof,ngate), intent(inout) :: re_matrix 98 real*8, dimension(hp%nhclass,nprof,ngate), intent(in ) :: Np_matrix98 real*8, dimension(hp%nhclass,nprof,ngate), intent(inout) :: Np_matrix 99 99 100 100 ! ----- OUTPUTS ----- -
LMDZ6/trunk/libf/phylmd/iophy.F90
r4046 r4103 975 975 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured, regular_lonlat 976 976 #ifdef CPP_XIOS 977 USE xios, ONLY: xios_send_field 977 USE xios, ONLY: xios_send_field, xios_field_is_active 978 978 #endif 979 979 USE print_control_mod, ONLY: lunout, prt_level … … 996 996 INTEGER :: ip 997 997 REAL, ALLOCATABLE, DIMENSION(:) :: fieldok 998 logical, save :: is_active = .true. 998 999 999 1000 IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_phy for ',trim(var%name) … … 1035 1036 1036 1037 ELSE 1038 #ifdef CPP_XIOS 1039 IF (ok_all_xml) THEN 1040 !$omp barrier 1041 !$omp master 1042 is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.) 1043 !$omp end master 1044 !$omp barrier 1045 IF(.not. is_active) RETURN 1046 ENDIF 1047 #endif 1037 1048 1038 1049 !Et sinon on.... écrit … … 1176 1187 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, regular_lonlat, unstructured 1177 1188 #ifdef CPP_XIOS 1178 USE xios, ONLY: xios_send_field 1189 USE xios, ONLY: xios_send_field, xios_field_is_active 1179 1190 #endif 1180 1191 USE print_control_mod, ONLY: prt_level,lunout … … 1195 1206 INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d 1196 1207 REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok 1208 logical, save :: is_active = .true. 1197 1209 1198 1210 IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy for ', trim(var%name) … … 1222 1234 CALL bcast_omp(swaerofree_diag) 1223 1235 ELSE 1236 #ifdef CPP_XIOS 1237 IF (ok_all_xml) THEN 1238 !$omp barrier 1239 !$omp master 1240 is_active = xios_field_is_active(var%name, at_current_timestep_arg=.false.) 1241 !$omp end master 1242 !$omp barrier 1243 IF(.not. is_active) RETURN 1244 ENDIF 1245 #endif 1246 1224 1247 !Et sinon on.... écrit 1225 1226 1248 IF (SIZE(field,1)/=klon .AND. SIZE(field,1)/=klev .AND. SIZE(field,1)/=klev+1) CALL abort_physic('iophy::histwrite3d_phy','Field first DIMENSION not equal to klon/klev',1) 1227 1249 -
LMDZ6/trunk/libf/phylmd/mo_simple_plumes.F90
r3531 r4103 280 280 281 281 IF ((iweek > ntimes) .OR. (iweek < 1) .OR. (iyear > nyears) .OR. (iyear < 1)) THEN 282 CALL abort_physic('set_time_weight','Time out of bounds' )282 CALL abort_physic('set_time_weight','Time out of bounds',1) 283 283 ENDIF 284 284 -
LMDZ6/trunk/libf/phylmd/o3_chem_m.F90
r2346 r4103 85 85 ! Heterogeneous chemistry is only during daytime: 86 86 call orbite(real(julien), earth_long, trash1) 87 call zenang(earth_long, gmtime, pdtphys, rlat, rlon, pmu0, trash2)87 call zenang(earth_long, gmtime, 0., pdtphys, rlat, rlon, pmu0, trash2) 88 88 forall (k = 1: nbp_lev) 89 89 where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0. -
LMDZ6/trunk/libf/phylmd/readaerosol_mod.F90
r3440 r4103 10 10 !$OMP THREADPRIVATE(nbp_lat_src) 11 11 REAL, ALLOCATABLE, SAVE :: psurf_interp(:,:) 12 !$OMP THREADPRIVATE(psurf_interp)13 12 14 13 CONTAINS … … 692 691 CALL xios_send_field("load_"//TRIM(varname)//"_in",load_glo2D) 693 692 CALL xios_recv_field("load_"//TRIM(varname)//"_out",load_out_mpi) 694 IF (first) THEN 693 IF (.not. allocated(psurf_interp)) THEN 694 ! psurf_interp is a shared array 695 695 ALLOCATE(psurf_interp(klon_mpi,12)) 696 696 CALL xios_send_field("psurf_aerosol_in",psurf_glo2D) -
LMDZ6/trunk/libf/phylmd/rrtm/abor1.intfb.h
r1990 r4103 1 1 INTERFACE 2 2 SUBROUTINE ABOR1(CDTEXT) 3 CHARACTER(LEN=*) :: CDTEXT3 CHARACTER(LEN=*), INTENT(IN) :: CDTEXT 4 4 END SUBROUTINE ABOR1 5 5 END INTERFACE -
LMDZ6/trunk/libf/phylmd/rrtm/tpm_fft.F90
r2010 r4103 7 7 8 8 TYPE FFT_TYPE 9 REAL(KIND=JPRB) , POINTER:: TRIGS(:,:)10 INTEGER(KIND=JPIM), POINTER:: NFAX(:,:)9 REAL(KIND=JPRB) ,ALLOCATABLE :: TRIGS(:,:) 10 INTEGER(KIND=JPIM),ALLOCATABLE :: NFAX(:,:) 11 11 END TYPE FFT_TYPE 12 12
Note: See TracChangeset
for help on using the changeset viewer.