- Timestamp:
- Jun 6, 2019, 5:08:45 PM (5 years ago)
- Location:
- LMDZ6/trunk/libf/phylmd
- Files:
-
- 17 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/acama_gwd_rando_m.F90
-
Property
svn:keywords
set to
Id
r3198 r3531 1 ! 2 ! $Id$ 3 ! 1 4 module ACAMA_GWD_rando_m 2 5 … … 120 123 !$OMP THREADPRIVATE(firstcall,gwd_reproductibilite_mpiomp) 121 124 122 CHARACTER (LEN=20) :: modname=' flott_gwd_rando'125 CHARACTER (LEN=20) :: modname='acama_gwd_rando_m' 123 126 CHARACTER (LEN=80) :: abort_message 124 127 … … 208 211 209 212 IF(DELTAT < DTIME)THEN 210 PRINT *, 'flott_gwd_rando: deltat < dtime!' 211 STOP 1 213 ! PRINT *, 'flott_gwd_rando: deltat < dtime!' 214 ! STOP 1 215 abort_message=' deltat < dtime! ' 216 CALL abort_physic(modname,abort_message,1) 212 217 ENDIF 213 218 214 219 IF (KLEV < NW) THEN 215 PRINT *, 'flott_gwd_rando: you will have problem with random numbers' 216 STOP 1 220 ! PRINT *, 'flott_gwd_rando: you will have problem with random numbers' 221 ! STOP 1 222 abort_message=' you will have problem with random numbers' 223 CALL abort_physic(modname,abort_message,1) 217 224 ENDIF 218 225 -
Property
svn:keywords
set to
-
LMDZ6/trunk/libf/phylmd/alpale_th.F90
-
Property
svn:keywords
set to
Id
r3209 r3531 1 ! 2 ! $Id$ 3 ! 1 4 SUBROUTINE alpale_th ( dtime, lmax_th, t_seri, cell_area, & 2 5 cin, s2, n2, & … … 62 65 REAL umexp ! expression of (1.-exp(-x))/x valid for all x, especially when x->0 63 66 REAL x 67 CHARACTER (LEN=20) :: modname='alpale_th' 68 CHARACTER (LEN=80) :: abort_message 69 64 70 umexp(x) = max(sign(1.,x-1.e-3),0.)*(1.-exp(-x))/max(x,1.e-3) + & 65 71 (1.-max(sign(1.,x-1.e-3),0.))*(1.-0.5*x*(1.-x/3.*(1.-0.25*x))) !!! correct formula (jyg) … … 104 110 ! 105 111 IF (prt_level .GE. 10) THEN 106 print *,'cin, ale_bl_stat, alp_bl, alp_bl_stat ', &112 WRITE(lunout,*)'cin, ale_bl_stat, alp_bl, alp_bl_stat ', & 107 113 cin, ale_bl_stat, alp_bl, alp_bl_stat 108 114 ENDIF … … 122 128 ! 123 129 IF (prt_level .GE. 10) THEN 124 print *,'random_notrig, tau_trig ', &130 WRITE(lunout,*)'random_notrig, tau_trig ', & 125 131 random_notrig, tau_trig 126 print *,'s_trig,s2,n2 ', &132 WRITE(lunout,*)'s_trig,s2,n2 ', & 127 133 s_trig,s2,n2 128 134 ENDIF … … 178 184 ! 179 185 IF (prt_level .GE. 10) THEN 180 print *,'proba_notrig, ale_bl_trig ', &186 WRITE(lunout,*)'proba_notrig, ale_bl_trig ', & 181 187 proba_notrig, ale_bl_trig 182 188 ENDIF … … 224 230 ! 225 231 IF (prt_level .GE. 10) THEN 226 print *,'cin, ale_bl_stat, alp_bl_stat ', &232 WRITE(lunout,*)'cin, ale_bl_stat, alp_bl_stat ', & 227 233 cin, ale_bl_stat, alp_bl_stat 228 234 ENDIF … … 253 259 ! 254 260 IF (prt_level .GE. 10) THEN 255 print *,'random_notrig, tau_trig ', &261 WRITE(lunout,*)'random_notrig, tau_trig ', & 256 262 random_notrig, tau_trig 257 print *,'s_trig,s2,n2 ', &263 WRITE(lunout,*)'s_trig,s2,n2 ', & 258 264 s_trig,s2,n2 259 265 ENDIF … … 289 295 ! 290 296 IF (prt_level .GE. 10) THEN 291 print *,'proba_notrig, ale_bl_trig ', &297 WRITE(lunout,*)'proba_notrig, ale_bl_trig ', & 292 298 proba_notrig, ale_bl_trig 293 299 ENDIF … … 300 306 301 307 IF (prt_level .GE. 10) THEN 302 print *,'alpale_th: ale_bl_trig, alp_bl_stat, birth_rate ', &308 WRITE(lunout,*)'alpale_th: ale_bl_trig, alp_bl_stat, birth_rate ', & 303 309 ale_bl_trig(1), alp_bl_stat(1), birth_rate(1) 304 310 ENDIF … … 310 316 if (iflag_coupl==2) then 311 317 IF (prt_level .GE. 10) THEN 312 print*,'Couplage Thermiques/Emanuel seulement si T<0'318 WRITE(lunout,*)'Couplage Thermiques/Emanuel seulement si T<0' 313 319 ENDIF 314 320 do i=1,klon … … 317 323 endif 318 324 enddo 319 print *,'In order to run with iflag_coupl=2, you have to comment out the following stop' 320 STOP 325 ! print *,'In order to run with iflag_coupl=2, you have to comment out the following stop' 326 ! STOP 327 abort_message='In order to run with iflag_coupl=2, you have to comment out the following abort' 328 CALL abort_physic(modname,abort_message,1) 321 329 endif 322 330 RETURN -
Property
svn:keywords
set to
-
LMDZ6/trunk/libf/phylmd/create_etat0_limit_unstruct.F90
r3470 r3531 65 65 IMPLICIT NONE 66 66 INTEGER :: iflag_phys 67 INTEGER :: ierr 67 INTEGER :: ierr 68 CHARACTER (LEN=20) :: modname='create_etat0_limit_unstruct' 69 CHARACTER (LEN=80) :: abort_message 70 68 71 IF (grid_type==unstructured) THEN 69 72 … … 83 86 CALL MPI_Finalize(ierr) 84 87 #endif 85 WRITE(lunout,*)'create_etat0_limit_unstruct, Initial state file are created, all is fine'86 STOP 088 abort_message='create_etat0_limit_unstruct, Initial state file are created, all is fine' 89 CALL abort_physic(modname,abort_message,0) 87 90 ENDIF 88 91 !$OMP BARRIER 89 STOP 'create_etat0_limit_unstruct, Initial state file are created, all is fine'92 abort_message='create_etat0_limit_unstruct, Initial state file are created, all is fine' CALL abort_physic(modname,abort_message,0) 90 93 ENDIF 91 94 ELSE … … 102 105 ENDIF 103 106 !$OMP BARRIER 104 WRITE(lunout,*)'create_etat0_limit_unstruct, Initial state file are created, all is fine'105 STOP 0107 abort_message='create_etat0_limit_unstruct, Initial state file are created, all is fine' 108 CALL abort_physic(modname,abort_message,0) 106 109 ENDIF 107 110 ENDIF -
LMDZ6/trunk/libf/phylmd/create_limit_unstruct.F90
r3471 r3531 200 200 INTEGER :: ij,ierr, n_extrap 201 201 LOGICAL :: skip 202 202 203 CHARACTER (len = 50) :: modname = 'create_limit_unstruct.time_interpolation' 204 CHARACTER (len = 80) :: abort_message 205 203 206 204 207 IF (is_omp_master) ndays_in=year_len(annee_ref, calendar) … … 212 215 yder = pchsp_95(timeyear, field_in(ij, :), ibeg=2, iend=2, vc_beg=0., vc_end=0.) 213 216 CALL pchfe_95(timeyear, field_in(ij, :), yder, skip, arth(0., real(ndays_in) / ndays, ndays), field_out(ij, :), ierr) 214 if (ierr < 0) stop 1 217 if (ierr < 0) then 218 abort_message='error in pchfe_95' 219 CALL abort_physic(modname,abort_message,1) 220 endif 215 221 n_extrap = n_extrap + ierr 216 222 END DO -
LMDZ6/trunk/libf/phylmd/cv30_routines.F90
r2520 r3531 3298 3298 integer i,k 3299 3299 real hp_bak(nloc,nd) 3300 CHARACTER (LEN=20) :: modname='cv30_epmax_fn_cape' 3301 CHARACTER (LEN=80) :: abort_message 3300 3302 3301 3303 ! on recalcule ep et hp … … 3346 3348 write(*,*) 'clw(i,k)=',clw(i,k) 3347 3349 write(*,*) 'cpd,cpv=',cpd,cpv 3348 stop3350 CALL abort_physic(modname,abort_message,0) 3349 3351 endif 3350 3352 enddo !do k=1,nl -
LMDZ6/trunk/libf/phylmd/flott_gwd_rando_m.F90
-
Property
svn:keywords
set to
Id
r3198 r3531 1 ! 2 ! $Id$ 3 ! 1 4 module FLOTT_GWD_rando_m 2 5 … … 20 23 USE ioipsl_getin_p_mod, ONLY : getin_p 21 24 USE vertical_layers_mod, ONLY : presnivs 25 CHARACTER (LEN=20) :: modname='flott_gwd_rando' 26 CHARACTER (LEN=80) :: abort_message 22 27 23 28 include "YOMCST.h" … … 115 120 LOGICAL, SAVE :: firstcall = .TRUE. 116 121 !$OMP THREADPRIVATE(firstcall,gwd_reproductibilite_mpiomp) 117 118 CHARACTER (LEN=20) :: modname='flott_gwd_rando'119 CHARACTER (LEN=80) :: abort_message120 121 122 122 123 … … 198 199 199 200 IF(DELTAT < DTIME)THEN 200 PRINT *,'flott_gwd_rando: deltat < dtime!'201 STOP 1201 abort_message='flott_gwd_rando: deltat < dtime!' 202 CALL abort_physic(modname,abort_message,1) 202 203 ENDIF 203 204 204 205 IF (KLEV < NW) THEN 205 PRINT *,'flott_gwd_rando: you will have problem with random numbers'206 STOP 1206 abort_message='flott_gwd_rando: you will have problem with random numbers' 207 CALL abort_physic(modname,abort_message,1) 207 208 ENDIF 208 209 -
Property
svn:keywords
set to
-
LMDZ6/trunk/libf/phylmd/mo_simple_plumes.F90
r3297 r3531 78 78 ! 79 79 INTEGER :: iret, ncid, DimID, VarID, xdmy 80 CHARACTER (len = 50) :: modname = 'mo_simple_plumes.sp_setup' 81 CHARACTER (len = 80) :: abort_message 82 80 83 ! 81 84 ! ---------- … … 84 87 ! 85 88 iret = nf90_open("MACv2.0-SP_v1.nc", NF90_NOWRITE, ncid) 86 IF (iret /= NF90_NOERR) STOP 'NetCDF File not opened' 89 IF (iret /= NF90_NOERR) THEN 90 abort_message='NetCDF File not opened' 91 CALL abort_physic(modname,abort_message,1) 92 ENDIF 87 93 ! 88 94 ! read dimensions and make sure file conforms to expected size … … 90 96 iret = nf90_inq_dimid(ncid, "plume_number" , DimId) 91 97 iret = nf90_inquire_dimension(ncid, DimId, len = xdmy) 92 IF (xdmy /= nplumes) STOP 'NetCDF improperly dimensioned -- plume_number' 98 IF (xdmy /= nplumes) THEN 99 abort_message='NetCDF improperly dimensioned -- plume_number' 100 CALL abort_physic(modname,abort_message,1) 101 ENDIF 93 102 ! 94 103 iret = nf90_inq_dimid(ncid, "plume_feature", DimId) 95 104 iret = nf90_inquire_dimension(ncid, DimId, len = xdmy) 96 IF (xdmy /= nfeatures) STOP 'NetCDF improperly dimensioned -- plume_feature' 105 IF (xdmy /= nfeatures) THEN 106 abort_message='NetCDF improperly dimensioned -- plume_feature' 107 CALL abort_physic(modname,abort_message,1) 108 ENDIF 97 109 ! 98 110 iret = nf90_inq_dimid(ncid, "year_fr" , DimId) 99 111 iret = nf90_inquire_dimension(ncid, DimID, len = xdmy) 100 IF (xdmy /= ntimes) STOP 'NetCDF improperly dimensioned -- year_fr' 112 IF (xdmy /= ntimes) THEN 113 abort_message='NetCDF improperly dimensioned -- year_fr' 114 CALL abort_physic(modname,abort_message,1) 115 ENDIF 101 116 ! 102 117 iret = nf90_inq_dimid(ncid, "years" , DimId) 103 118 iret = nf90_inquire_dimension(ncid, DimID, len = xdmy) 104 IF (xdmy /= nyears) STOP 'NetCDF improperly dimensioned -- years' 119 IF (xdmy /= nyears) THEN 120 abort_message='NetCDF improperly dimensioned -- years' 121 CALL abort_physic(modname,abort_message,1) 122 ENDIF 105 123 ! 106 124 ! read variables that define the simple plume climatology … … 108 126 iret = nf90_inq_varid(ncid, "plume_lat", VarId) 109 127 iret = nf90_get_var(ncid, VarID, plume_lat(:), start=(/1/),count=(/nplumes/)) 110 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading plume_lat' 128 IF (iret /= NF90_NOERR) THEN 129 abort_message='NetCDF Error reading plume_lat' 130 CALL abort_physic(modname,abort_message,1) 131 ENDIF 111 132 iret = nf90_inq_varid(ncid, "plume_lon", VarId) 112 133 iret = nf90_get_var(ncid, VarID, plume_lon(:), start=(/1/),count=(/nplumes/)) 113 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading plume_lon' 134 IF (iret /= NF90_NOERR) THEN 135 abort_message='NetCDF Error reading plume_lon' 136 CALL abort_physic(modname,abort_message,1) 137 ENDIF 114 138 iret = nf90_inq_varid(ncid, "beta_a" , VarId) 115 139 iret = nf90_get_var(ncid, VarID, beta_a(:) , start=(/1/),count=(/nplumes/)) 116 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading beta_a' 140 IF (iret /= NF90_NOERR) THEN 141 abort_message='NetCDF Error reading beta_a' 142 CALL abort_physic(modname,abort_message,1) 143 ENDIF 117 144 iret = nf90_inq_varid(ncid, "beta_b" , VarId) 118 145 iret = nf90_get_var(ncid, VarID, beta_b(:) , start=(/1/),count=(/nplumes/)) 119 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading beta_b' 146 IF (iret /= NF90_NOERR) THEN 147 abort_message='NetCDF Error reading beta_b' 148 CALL abort_physic(modname,abort_message,1) 149 ENDIF 120 150 iret = nf90_inq_varid(ncid, "aod_spmx" , VarId) 121 151 iret = nf90_get_var(ncid, VarID, aod_spmx(:) , start=(/1/),count=(/nplumes/)) 122 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading aod_spmx' 152 IF (iret /= NF90_NOERR) THEN 153 abort_message='NetCDF Error reading aod_spmx' 154 CALL abort_physic(modname,abort_message,1) 155 ENDIF 123 156 iret = nf90_inq_varid(ncid, "aod_fmbg" , VarId) 124 157 iret = nf90_get_var(ncid, VarID, aod_fmbg(:) , start=(/1/),count=(/nplumes/)) 125 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading aod_fmbg' 158 IF (iret /= NF90_NOERR) THEN 159 abort_message='NetCDF Error reading aod_fmbg' 160 CALL abort_physic(modname,abort_message,1) 161 ENDIF 126 162 iret = nf90_inq_varid(ncid, "ssa550" , VarId) 127 163 iret = nf90_get_var(ncid, VarID, ssa550(:) , start=(/1/),count=(/nplumes/)) 128 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading ssa550' 164 IF (iret /= NF90_NOERR) THEN 165 abort_message='NetCDF Error reading ssa550' 166 CALL abort_physic(modname,abort_message,1) 167 ENDIF 129 168 iret = nf90_inq_varid(ncid, "asy550" , VarId) 130 169 iret = nf90_get_var(ncid, VarID, asy550(:) , start=(/1/),count=(/nplumes/)) 131 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading asy550' 170 IF (iret /= NF90_NOERR) THEN 171 abort_message='NetCDF Error reading asy550' 172 CALL abort_physic(modname,abort_message,1) 173 ENDIF 132 174 iret = nf90_inq_varid(ncid, "angstrom" , VarId) 133 175 iret = nf90_get_var(ncid, VarID, angstrom(:), start=(/1/),count=(/nplumes/)) 134 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading angstrom' 176 IF (iret /= NF90_NOERR) THEN 177 abort_message='NetCDF Error reading angstrom' 178 CALL abort_physic(modname,abort_message,1) 179 ENDIF 135 180 ! 136 181 iret = nf90_inq_varid(ncid, "sig_lat_W" , VarId) 137 182 iret = nf90_get_var(ncid, VarID, sig_lat_W(:,:) , start=(/1,1/),count=(/nfeatures,nplumes/)) 138 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lat_W' 183 IF (iret /= NF90_NOERR) THEN 184 abort_message='NetCDF Error reading sig_lat_W' 185 CALL abort_physic(modname,abort_message,1) 186 ENDIF 139 187 iret = nf90_inq_varid(ncid, "sig_lat_E" , VarId) 140 188 iret = nf90_get_var(ncid, VarID, sig_lat_E(:,:) , start=(/1,1/),count=(/nfeatures,nplumes/)) 141 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lat_E' 189 IF (iret /= NF90_NOERR) THEN 190 abort_message='NetCDF Error reading sig_lat_E' 191 CALL abort_physic(modname,abort_message,1) 192 ENDIF 142 193 iret = nf90_inq_varid(ncid, "sig_lon_E" , VarId) 143 194 iret = nf90_get_var(ncid, VarID, sig_lon_E(:,:) , start=(/1,1/),count=(/nfeatures,nplumes/)) 144 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lon_E' 195 IF (iret /= NF90_NOERR) THEN 196 abort_message='NetCDF Error reading sig_lon_E' 197 CALL abort_physic(modname,abort_message,1) 198 ENDIF 145 199 iret = nf90_inq_varid(ncid, "sig_lon_W" , VarId) 146 200 iret = nf90_get_var(ncid, VarID, sig_lon_W(:,:) , start=(/1,1/),count=(/nfeatures,nplumes/)) 147 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading sig_lon_W' 201 IF (iret /= NF90_NOERR) THEN 202 abort_message='NetCDF Error reading sig_lon_W' 203 CALL abort_physic(modname,abort_message,1) 204 ENDIF 148 205 iret = nf90_inq_varid(ncid, "theta" , VarId) 149 206 iret = nf90_get_var(ncid, VarID, theta(:,:) , start=(/1,1/),count=(/nfeatures,nplumes/)) 150 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading theta' 207 IF (iret /= NF90_NOERR) THEN 208 abort_message='NetCDF Error reading theta' 209 CALL abort_physic(modname,abort_message,1) 210 ENDIF 151 211 iret = nf90_inq_varid(ncid, "ftr_weight" , VarId) 152 212 iret = nf90_get_var(ncid, VarID, ftr_weight(:,:) , start=(/1,1/),count=(/nfeatures,nplumes/)) 153 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading plume_lat' 213 IF (iret /= NF90_NOERR) THEN 214 abort_message='NetCDF Error reading plume_lat' 215 CALL abort_physic(modname,abort_message,1) 216 ENDIF 154 217 iret = nf90_inq_varid(ncid, "year_weight" , VarId) 155 218 iret = nf90_get_var(ncid, VarID, year_weight(:,:) , start=(/1,1/),count=(/nyears,nplumes /)) 156 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading year_weight' 219 IF (iret /= NF90_NOERR) THEN 220 abort_message='NetCDF Error reading year_weight' 221 CALL abort_physic(modname,abort_message,1) 222 ENDIF 157 223 iret = nf90_inq_varid(ncid, "ann_cycle" , VarId) 158 224 iret = nf90_get_var(ncid, VarID, ann_cycle(:,:,:) , start=(/1,1,1/),count=(/nfeatures,ntimes,nplumes/)) 159 IF (iret /= NF90_NOERR) STOP 'NetCDF Error reading ann_cycle' 225 IF (iret /= NF90_NOERR) THEN 226 abort_message='NetCDF Error reading ann_cycle' 227 CALL abort_physic(modname,abort_message,1) 228 ENDIF 160 229 ! 161 230 iret = nf90_close(ncid) -
LMDZ6/trunk/libf/phylmd/mod_synchro_omp.F90
-
Property
svn:keywords
changed from
Author Date Id Revision
toId
r1907 r3531 1 ! 2 ! $Id$ 3 ! 1 4 MODULE mod_synchro_omp 2 5 … … 21 24 IMPLICIT NONE 22 25 LOGICAL :: out 26 CHARACTER (LEN=20) :: modname='synchro_omp' 27 CHARACTER (LEN=80) :: abort_message 23 28 24 29 out=.FALSE. … … 46 51 47 52 IF (exit_omp/=0) THEN 48 STOP 'synchro_omp' 53 abort_message='synchro_omp' 54 CALL abort_physic(modname,abort_message,1) 49 55 ENDIF 50 56 -
Property
svn:keywords
changed from
-
LMDZ6/trunk/libf/phylmd/phyaqua_mod.F90
r3435 r3531 112 112 REAL paire 113 113 114 ! Local 115 CHARACTER (LEN=20) :: modname='phyaqua' 116 CHARACTER (LEN=80) :: abort_message 117 114 118 115 119 ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 128 132 IF (klon/=nlon) THEN 129 133 WRITE (*, *) 'iniaqua: klon=', klon, ' nlon=', nlon 130 STOP 'probleme de dimensions dans iniaqua' 134 abort_message= 'probleme de dimensions dans iniaqua' 135 CALL abort_physic(modname,abort_message,1) 131 136 END IF 132 137 CALL phys_state_var_init(read_climoz) … … 812 817 PARAMETER (nlat_max=72) 813 818 REAL x_anom_sst(nlat_max) 814 815 IF (klon/=nlon) STOP 'probleme de dimensions dans iniaqua' 819 CHARACTER (LEN=20) :: modname='profil_sst' 820 CHARACTER (LEN=80) :: abort_message 821 822 IF (klon/=nlon) THEN 823 abort_message='probleme de dimensions dans profil_sst' 824 CALL abort_physic(modname,abort_message,1) 825 ENDIF 816 826 WRITE (*, *) ' profil_sst: type_profil=', type_profil 817 827 DO i = 1, 360 -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r3522 r3531 1270 1270 WRITE (lunout, *) ' iflag_ice_thermo==1 requires 3 H2O tracers ', & 1271 1271 '(H2Ov, H2Ol, H2Oi) but nqo=', nqo, '. Might as well stop here.' 1272 STOP 1272 abort_message='see above' 1273 CALL abort_physic(modname,abort_message,1) 1273 1274 ENDIF 1274 1275 -
LMDZ6/trunk/libf/phylmd/phytrac_mod.F90
-
Property
svn:keywords
set to
Id
r3467 r3531 602 602 IF (lessivage .AND. type_trac .EQ. 'inca') THEN 603 603 CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1) 604 STOP604 ! STOP 605 605 ENDIF 606 606 ! -
Property
svn:keywords
set to
-
LMDZ6/trunk/libf/phylmd/readaerosolstrato.F90
r3436 r3531 15 15 USE aero_mod 16 16 USE dimphy 17 USE print_control_mod, ONLY: prt_level,lunout 17 18 #ifdef CPP_XIOS 18 19 USE xios … … 61 62 data alpha_strat_wave/3.36780953,3.34667683,3.20444202,3.0293026,2.82108808/ 62 63 64 CHARACTER (len = 20) :: modname = 'readaerosolstrato' 65 CHARACTER (len = 80) :: abort_message 66 63 67 !-------------------------------------------------------- 64 68 … … 72 76 73 77 IF (nbands.NE.2) THEN 74 print *,'nbands doit etre egal a 2 dans readaerosolstrat'75 STOP78 abort_message='nbands doit etre egal a 2 dans readaerosolstrat' 79 CALL abort_physic(modname,abort_message,1) 76 80 ENDIF 77 81 … … 82 86 n_lev = size(lev) 83 87 IF (n_lev.NE.klev) THEN 84 print *,'Le nombre de niveaux n est pas egal a klev'85 STOP88 abort_message='Le nombre de niveaux n est pas egal a klev' 89 CALL abort_physic(modname,abort_message,1) 86 90 ENDIF 87 91 … … 89 93 CALL nf95_gw_var(ncid_in, varid, latitude) 90 94 n_lat = size(latitude) 91 print *,'LAT aerosol strato=', n_lat, latitude95 WRITE(lunout,*) 'LAT aerosol strato=', n_lat, latitude 92 96 IF (grid_type/=unstructured) THEN 93 97 IF (n_lat.NE.nbp_lat) THEN 94 print *,'Le nombre de lat n est pas egal a nbp_lat'95 STOP98 abort_message='Le nombre de lat n est pas egal a nbp_lat' 99 CALL abort_physic(modname,abort_message,1) 96 100 ENDIF 97 101 ENDIF … … 101 105 n_lon = size(longitude) 102 106 IF (grid_type/=unstructured) THEN 103 print *,'LON aerosol strato=', n_lon, longitude107 WRITE(lunout,*) 'LON aerosol strato=', n_lon, longitude 104 108 IF (n_lon.NE.nbp_lon) THEN 105 print *,'Le nombre de lon n est pas egal a nbp_lon'106 STOP109 abort_message='Le nombre de lon n est pas egal a nbp_lon' 110 CALL abort_physic(modname,abort_message,1) 107 111 ENDIF 108 112 ENDIF … … 111 115 CALL nf95_gw_var(ncid_in, varid, time) 112 116 n_month = size(time) 113 print *,'TIME aerosol strato=', n_month, time117 WRITE(lunout,*) 'TIME aerosol strato=', n_month, time 114 118 IF (n_month.NE.12) THEN 115 print *,'Le nombre de month n est pas egal a 12'116 STOP119 abort_message='Le nombre de month n est pas egal a 12' 120 CALL abort_physic(modname,abort_message,1) 117 121 ENDIF 118 122 … … 124 128 CALL nf95_inq_varid(ncid_in, "TAUSTRAT", varid) 125 129 ncerr = nf90_get_var(ncid_in, varid, tauaerstrat) 126 print *,'code erreur readaerosolstrato=', ncerr, varid130 WRITE(lunout,*) 'code erreur readaerosolstrato=', ncerr, varid 127 131 128 132 CALL nf95_close(ncid_in) … … 130 134 !---select the correct month 131 135 IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN 132 print *,'probleme avec le mois dans readaerosolstrat =', mth_cur136 WRITE(lunout,*) 'probleme avec le mois dans readaerosolstrat =', mth_cur 133 137 ENDIF 134 138 tauaerstrat_mois(:,:,:) = tauaerstrat(:,:,:,mth_cur) -
LMDZ6/trunk/libf/phylmd/readchlorophyll.F90
r3298 r3531 15 15 USE mod_phys_lmdz_para, ONLY: scatter 16 16 USE phys_state_var_mod, ONLY: chl_con 17 USE print_control_mod, ONLY: prt_level,lunout 17 18 18 19 IMPLICIT NONE … … 45 46 46 47 !-------------------------------------------------------- 48 CHARACTER (len = 20) :: modname = 'readchlorophyll' 49 CHARACTER (len = 80) :: abort_message 47 50 48 51 !--only read file if beginning of run or start of new month … … 56 59 CALL nf95_gw_var(ncid_in, varid, longitude) 57 60 n_lon = size(longitude) 58 ! print *, 'LON chlorophyll=', n_lon, longitude59 61 IF (n_lon.NE.nbp_lon) THEN 60 print *,'Le nombre de lon n est pas egal a nbp_lon'61 STOP62 abort_message='Le nombre de lon n est pas egal a nbp_lon' 63 CALL abort_physic(modname,abort_message,1) 62 64 ENDIF 63 65 … … 65 67 CALL nf95_gw_var(ncid_in, varid, latitude) 66 68 n_lat = size(latitude) 67 ! print *, 'LAT chlorophyll=', n_lat, latitude68 69 IF (n_lat.NE.nbp_lat) THEN 69 print *,'Le nombre de lat n est pas egal a jnbp_lat'70 STOP70 abort_message='Le nombre de lat n est pas egal a jnbp_lat' 71 CALL abort_physic(modname,abort_message,1) 71 72 ENDIF 72 73 … … 74 75 CALL nf95_gw_var(ncid_in, varid, time) 75 76 n_month = size(time) 76 ! print *, 'TIME aerosol strato=', n_month, time77 77 IF (n_month.NE.12) THEN 78 print *,'Le nombre de month n est pas egal a 12'79 STOP78 abort_message='Le nombre de month n est pas egal a 12' 79 CALL abort_physic(modname,abort_message,1) 80 80 ENDIF 81 81 … … 87 87 CALL nf95_inq_varid(ncid_in, "CHL", varid) 88 88 ncerr = nf90_get_var(ncid_in, varid, chlorocon) 89 print *,'code erreur readchlorophyll=', ncerr, varid89 WRITE(lunout,*)'code erreur readchlorophyll=', ncerr, varid 90 90 91 91 CALL nf95_close(ncid_in) … … 93 93 !---select the correct month 94 94 IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN 95 print *,'probleme avec le mois dans readchlorophyll =', mth_cur95 WRITE(lunout,*)'probleme avec le mois dans readchlorophyll =', mth_cur 96 96 ENDIF 97 97 chlorocon_mois(:,:) = chlorocon(:,:,mth_cur) … … 100 100 CALL grid2dTo1d_glo(chlorocon_mois,chlorocon_mois_glo) 101 101 102 print *,"chrolophyll current month",mth_cur102 WRITE(lunout,*)"chrolophyll current month",mth_cur 103 103 DO i=1,klon_glo 104 104 ! if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard... -
LMDZ6/trunk/libf/phylmd/simu_airs.F90
r2585 r3531 2 2 module m_simu_airs 3 3 4 USE print_control_mod, ONLY: prt_level,lunout 5 4 6 implicit none 5 7 6 real, parameter:: tau_thresh = 0.05 ! seuil nuages detectables7 real, parameter:: p_thresh = 445. ! seuil nuages hauts8 real, parameter:: em_min = 0.2 ! seuils nuages semi-transp9 real, parameter:: em_max = 0.8510 real, parameter:: undef = 999.8 REAL, PARAMETER :: tau_thresh = 0.05 ! seuil nuages detectables 9 REAL, PARAMETER :: p_thresh = 445. ! seuil nuages hauts 10 REAL, PARAMETER :: em_min = 0.2 ! seuils nuages semi-transp 11 REAL, PARAMETER :: em_max = 0.85 12 REAL, PARAMETER :: undef = 999. 11 13 12 14 contains 13 15 14 realfunction search_tropopause(P,T,alt,N) result(P_tropo)16 REAL function search_tropopause(P,T,alt,N) result(P_tropo) 15 17 ! this function searches for the tropopause pressure in [hPa]. 16 18 ! The search is based on ideology described in … … 18 20 ! GRL, 30(20) 2042, doi:10.1029/2003GL018240, 2003 19 21 20 integerN,i,i_lev,first_point,exit_flag,i_dir21 realP(N),T(N),alt(N),slope(N)22 realP_min, P_max, slope_limit,slope_2km, &22 INTEGER N,i,i_lev,first_point,exit_flag,i_dir 23 REAL P(N),T(N),alt(N),slope(N) 24 REAL P_min, P_max, slope_limit,slope_2km, & 23 25 & delta_alt_limit,tmp,delta_alt 24 parameter(P_min=75.0, P_max=470.0) ! hPa25 parameter(slope_limit=0.002) ! 2 K/km converted to K/m26 parameter(delta_alt_limit=2000.0) ! 2000 meters26 PARAMETER(P_min=75.0, P_max=470.0) ! hPa 27 PARAMETER(slope_limit=0.002) ! 2 K/km converted to K/m 28 PARAMETER(delta_alt_limit=2000.0) ! 2000 meters 27 29 28 30 do i=1,N-1 … … 93 95 94 96 95 integer:: i, n, nss96 97 integer, intent(in) :: len_cs98 real, dimension(:), intent(in) :: rneb_cs, temp_cs99 real, dimension(:), intent(in) :: emis_cs, iwco_cs, rad_cs100 real, dimension(:), intent(in) :: pres_cs, dz_cs, rhodz_cs101 102 real, intent(out) :: cc_tot_cs, cc_hc_cs, cc_hist_cs, &97 INTEGER :: i, n, nss 98 99 INTEGER, intent(in) :: len_cs 100 REAL, DIMENSION(:), intent(in) :: rneb_cs, temp_cs 101 REAL, DIMENSION(:), intent(in) :: emis_cs, iwco_cs, rad_cs 102 REAL, DIMENSION(:), intent(in) :: pres_cs, dz_cs, rhodz_cs 103 104 REAL, intent(out) :: cc_tot_cs, cc_hc_cs, cc_hist_cs, & 103 105 & cc_Cb_cs, cc_ThCi_cs, cc_Anv_cs, & 104 106 & pcld_hc_cs, tcld_hc_cs, em_hc_cs, iwp_hc_cs, & … … 109 111 & deltaz_hc_cs, deltaz_hist_cs, rad_hist_cs 110 112 111 real, dimension(len_cs) :: rneb_ord112 real:: rneb_min113 114 real, dimension(:), allocatable :: s, s_hc, s_hist, rneb_max115 real, dimension(:), allocatable :: sCb, sThCi, sAnv116 real, dimension(:), allocatable :: iwp_ss, pcld_ss, tcld_ss,&113 REAL, DIMENSION(len_cs) :: rneb_ord 114 REAL :: rneb_min 115 116 REAL, DIMENSION(:), allocatable :: s, s_hc, s_hist, rneb_max 117 REAL, DIMENSION(:), allocatable :: sCb, sThCi, sAnv 118 REAL, DIMENSION(:), allocatable :: iwp_ss, pcld_ss, tcld_ss,& 117 119 & emis_ss 118 real, dimension(:), allocatable :: deltaz_ss, rad_ss 119 120 121 write(*,*) 'dans cloud_structure' 120 REAL, DIMENSION(:), allocatable :: deltaz_ss, rad_ss 121 122 CHARACTER (len = 50) :: modname = 'simu_airs.cloud_structure' 123 CHARACTER (len = 160) :: abort_message 124 125 126 write(lunout,*) 'dans cloud_structure' 122 127 123 128 call ordonne(len_cs, rneb_cs, rneb_ord) … … 300 305 if (cc_tot_cs .gt. maxval(rneb_cs) .and. & 301 306 & abs(cc_tot_cs-maxval(rneb_cs)) .gt. 1.e-4 ) then 302 write(*,*) 'cc_tot_cs > max rneb_cs' 303 write(*,*) cc_tot_cs, maxval(rneb_cs) 304 STOP 307 WRITE(abort_message,*) 'cc_tot_cs > max rneb_cs', cc_tot_cs, maxval(rneb_cs) 308 CALL abort_physic(modname,abort_message,1) 305 309 endif 306 310 307 311 if (iwp_hc_cs .lt. 0.) then 308 write(*,*) 'cloud_structure:' 309 write(*,*) 'iwp_hc_cs < 0' 310 STOP 312 abort_message= 'cloud_structure: iwp_hc_cs < 0' 313 CALL abort_physic(modname,abort_message,1) 311 314 endif 312 315 … … 316 319 subroutine normal_undef(num, den) 317 320 318 real, intent(in) :: den319 real, intent(inout) :: num321 REAL, intent(in) :: den 322 REAL, intent(inout) :: num 320 323 321 324 if (den .ne. 0) then … … 330 333 subroutine normal2_undef(res,num,den) 331 334 332 real, intent(in) :: den333 real, intent(in) :: num334 real, intent(out) :: res335 REAL, intent(in) :: den 336 REAL, intent(in) :: num 337 REAL, intent(out) :: res 335 338 336 339 if (den .ne. 0.) then … … 350 353 & emis, pcld, tcld, iwp, deltaz, rad) 351 354 352 integer, intent(in) :: len_cs353 real, dimension(len_cs), intent(in) :: rneb_cs, temp_cs354 real, dimension(len_cs), intent(in) :: emis_cs, iwco_cs, &355 INTEGER, intent(in) :: len_cs 356 REAL, DIMENSION(len_cs), intent(in) :: rneb_cs, temp_cs 357 REAL, DIMENSION(len_cs), intent(in) :: emis_cs, iwco_cs, & 355 358 & rneb_ord 356 real, dimension(len_cs), intent(in) :: pres_cs, dz_cs, rad_cs 357 real, dimension(len_cs), intent(in) :: rhodz_cs 358 real, dimension(len_cs) :: tau_cs, w 359 real, intent(in) :: rnebmax 360 real, intent(inout) :: stot, shc, shist 361 real, intent(inout) :: sCb, sThCi, sAnv 362 real, intent(out) :: emis, pcld, tcld, iwp, deltaz, rad 363 364 integer :: i, ideb, ibeg, iend, nuage, visible 365 real :: som, som_tau, som_iwc, som_dz, som_rad, tau 359 REAL, DIMENSION(len_cs), intent(in) :: pres_cs, dz_cs, rad_cs 360 REAL, DIMENSION(len_cs), intent(in) :: rhodz_cs 361 REAL, DIMENSION(len_cs) :: tau_cs, w 362 REAL, intent(in) :: rnebmax 363 REAL, intent(inout) :: stot, shc, shist 364 REAL, intent(inout) :: sCb, sThCi, sAnv 365 REAL, intent(out) :: emis, pcld, tcld, iwp, deltaz, rad 366 367 INTEGER :: i, ideb, ibeg, iend, nuage, visible 368 REAL :: som, som_tau, som_iwc, som_dz, som_rad, tau 369 370 CHARACTER (len = 50) :: modname = 'simu_airs.sous_section' 371 CHARACTER (len = 160) :: abort_message 366 372 367 373 … … 491 497 492 498 if (iwp .lt. 0.) then 493 write(*,*) 'ideb iwp =', ideb, iwp494 STOP499 WRITE(abort_message,*) 'ideb iwp =', ideb, iwp 500 CALL abort_physic(modname,abort_message,1) 495 501 endif 496 502 497 503 if (deltaz .lt. 0.) then 498 write(*,*)'ideb deltaz =', ideb, deltaz499 STOP504 WRITE(abort_message,*)'ideb deltaz =', ideb, deltaz 505 CALL abort_physic(modname,abort_message,1) 500 506 endif 501 507 502 508 if (emis .lt. 0.048 .and. emis .ne. 0.) then 503 write(*,*) 'ideb emis =', ideb, emis504 STOP509 WRITE(abort_message,*) 'ideb emis =', ideb, emis 510 CALL abort_physic(modname,abort_message,1) 505 511 endif 506 512 … … 511 517 & visible, w) 512 518 513 integer, intent(in) :: ibeg, iend514 real, intent(in) :: som_tau515 516 integer, intent(inout) :: visible517 real, dimension(:), intent(inout) :: w518 519 integer:: i519 INTEGER, intent(in) :: ibeg, iend 520 REAL, intent(in) :: som_tau 521 522 INTEGER, intent(inout) :: visible 523 REAL, DIMENSION(:), intent(inout) :: w 524 525 INTEGER :: i 520 526 521 527 … … 553 559 & som_tau, som_iwc, som_dz, som_rad) 554 560 555 integer, intent(in) :: ibeg, iend 556 real, dimension(:), intent(in) :: tau_cs, iwco_cs, temp_cs 557 real, dimension(:), intent(in) :: pres_cs, dz_cs, rad_cs 558 real, dimension(:), intent(in) :: rhodz_cs 559 real, intent(out) :: som_tau, som_iwc, som_dz, som_rad 560 real , intent(out) :: pcld, tcld 561 562 integer :: i, ibase, imid 561 INTEGER, intent(in) :: ibeg, iend 562 REAL, DIMENSION(:), intent(in) :: tau_cs, iwco_cs, temp_cs 563 REAL, DIMENSION(:), intent(in) :: pres_cs, dz_cs, rad_cs 564 REAL, DIMENSION(:), intent(in) :: rhodz_cs 565 REAL, intent(out) :: som_tau, som_iwc, som_dz, som_rad 566 REAL , intent(out) :: pcld, tcld 567 568 INTEGER :: i, ibase, imid 569 570 CHARACTER (len = 50) :: modname = 'simu_airs.caract' 571 CHARACTER (len = 160) :: abort_message 563 572 564 573 ! Somme des epaisseurs optiques et des contenus en glace sur le nuage … … 585 594 586 595 if (som_dz .ne. 0.) then 587 som_rad = som_rad/som_dz596 som_rad = som_rad/som_dz 588 597 else 589 write(*,*) 'som_dez = 0 STOP' 590 write(*,*) 'ibeg, iend =', ibeg, iend 591 do i = ibeg, iend 592 write(*,*) dz_cs(i), rhodz_cs(i) 593 enddo 594 STOP 598 write(*,*) 'som_dez = 0 STOP' 599 write(*,*) 'ibeg, iend =', ibeg, iend 600 do i = ibeg, iend 601 write(*,*) dz_cs(i), rhodz_cs(i) 602 enddo 603 abort_message='see above' 604 CALL abort_physic(modname,abort_message,1) 595 605 endif 596 606 … … 611 621 subroutine topbot(ideb,w,ibeg,iend) 612 622 613 integer, intent(in) :: ideb614 real, dimension(:), intent(in) :: w615 integer, intent(out) :: ibeg, iend616 617 integer:: i, itest623 INTEGER, intent(in) :: ideb 624 REAL, DIMENSION(:), intent(in) :: w 625 INTEGER, intent(out) :: ibeg, iend 626 627 INTEGER :: i, itest 618 628 619 629 itest = 0 … … 642 652 subroutine ordonne(len_cs, rneb_cs, rneb_ord) 643 653 644 integer, intent(in) :: len_cs645 real, dimension(:), intent(in) :: rneb_cs646 real, dimension(:), intent(out) :: rneb_ord647 648 integer:: i, j, ind_min649 650 real, dimension(len_cs) :: rneb651 real:: rneb_max654 INTEGER, intent(in) :: len_cs 655 REAL, DIMENSION(:), intent(in) :: rneb_cs 656 REAL, DIMENSION(:), intent(out) :: rneb_ord 657 658 INTEGER :: i, j, ind_min 659 660 REAL, DIMENSION(len_cs) :: rneb 661 REAL :: rneb_max 652 662 653 663 … … 689 699 USE dimphy 690 700 691 real, dimension(klev), intent(in) :: rneb_1D, temp_1D, emis_1D, &701 REAL, DIMENSION(klev), intent(in) :: rneb_1D, temp_1D, emis_1D, & 692 702 & iwcon_1D, rad_1D 693 real, dimension(klev), intent(in) :: pres, dz, rhodz_1D694 real, intent(out) :: cc_tot_mesh, cc_hc_mesh, cc_hist_mesh695 real, intent(out) :: cc_Cb_mesh, cc_ThCi_mesh, cc_Anv_mesh696 real, intent(out) :: em_hc_mesh, pcld_hc_mesh, tcld_hc_mesh, &703 REAL, DIMENSION(klev), intent(in) :: pres, dz, rhodz_1D 704 REAL, intent(out) :: cc_tot_mesh, cc_hc_mesh, cc_hist_mesh 705 REAL, intent(out) :: cc_Cb_mesh, cc_ThCi_mesh, cc_Anv_mesh 706 REAL, intent(out) :: em_hc_mesh, pcld_hc_mesh, tcld_hc_mesh, & 697 707 & iwp_hc_mesh 698 708 699 real, intent(out) :: pcld_Cb_mesh, tcld_Cb_mesh, em_Cb_mesh700 real, intent(out) :: pcld_ThCi_mesh, tcld_ThCi_mesh, &709 REAL, intent(out) :: pcld_Cb_mesh, tcld_Cb_mesh, em_Cb_mesh 710 REAL, intent(out) :: pcld_ThCi_mesh, tcld_ThCi_mesh, & 701 711 & em_ThCi_mesh 702 real, intent(out) :: pcld_Anv_mesh, tcld_Anv_mesh, em_Anv_mesh703 704 real, intent(out) :: em_hist_mesh, iwp_hist_mesh, rad_hist_mesh705 real, intent(out) :: deltaz_hc_mesh, deltaz_hist_mesh706 707 real, dimension(:), allocatable :: rneb_cs, temp_cs, emis_cs, &712 REAL, intent(out) :: pcld_Anv_mesh, tcld_Anv_mesh, em_Anv_mesh 713 714 REAL, intent(out) :: em_hist_mesh, iwp_hist_mesh, rad_hist_mesh 715 REAL, intent(out) :: deltaz_hc_mesh, deltaz_hist_mesh 716 717 REAL, DIMENSION(:), allocatable :: rneb_cs, temp_cs, emis_cs, & 708 718 & iwco_cs 709 real, dimension(:), allocatable :: pres_cs, dz_cs, rad_cs, &719 REAL, DIMENSION(:), allocatable :: pres_cs, dz_cs, rad_cs, & 710 720 & rhodz_cs 711 721 712 integer:: i,j,l713 integer:: ltop, itop, ibot, num_cs, N_cs, len_cs, ics714 715 real:: som_emi_hc,som_pcl_hc,som_tcl_hc,som_iwp_hc,som_hc,&722 INTEGER :: i,j,l 723 INTEGER :: ltop, itop, ibot, num_cs, N_cs, len_cs, ics 724 725 REAL :: som_emi_hc,som_pcl_hc,som_tcl_hc,som_iwp_hc,som_hc,& 716 726 & som_hist 717 real:: som_emi_hist, som_iwp_hist, som_deltaz_hc, &727 REAL :: som_emi_hist, som_iwp_hist, som_deltaz_hc, & 718 728 & som_deltaz_hist 719 real :: som_rad_hist 720 real :: som_Cb, som_ThCi, som_Anv 721 real :: som_emi_Cb, som_tcld_Cb, som_pcld_Cb 722 real :: som_emi_Anv, som_tcld_Anv, som_pcld_Anv 723 real :: som_emi_ThCi, som_tcld_ThCi, som_pcld_ThCi 724 real :: tsom_tot, tsom_hc, tsom_hist 725 real :: prod, prod_hh 726 727 real :: cc_tot_cs, cc_hc_cs, cc_hist_cs 728 real :: cc_Cb_cs, cc_ThCi_cs, cc_Anv_cs 729 real :: pcld_hc_cs, tcld_hc_cs 730 real :: em_hc_cs, iwp_hc_cs, deltaz_hc_cs 731 real :: pcld_Cb_cs, tcld_Cb_cs, em_Cb_cs 732 real :: pcld_ThCi_cs, tcld_ThCi_cs, em_ThCi_cs 733 real :: pcld_Anv_cs, tcld_Anv_cs, em_Anv_cs 734 real :: em_hist_cs, iwp_hist_cs, deltaz_hist_cs, rad_hist_cs 735 736 real, dimension(klev) :: test_tot, test_hc, test_hist 737 real, dimension(klev) :: test_pcld, test_tcld, test_em, test_iwp 738 729 REAL :: som_rad_hist 730 REAL :: som_Cb, som_ThCi, som_Anv 731 REAL :: som_emi_Cb, som_tcld_Cb, som_pcld_Cb 732 REAL :: som_emi_Anv, som_tcld_Anv, som_pcld_Anv 733 REAL :: som_emi_ThCi, som_tcld_ThCi, som_pcld_ThCi 734 REAL :: tsom_tot, tsom_hc, tsom_hist 735 REAL :: prod, prod_hh 736 737 REAL :: cc_tot_cs, cc_hc_cs, cc_hist_cs 738 REAL :: cc_Cb_cs, cc_ThCi_cs, cc_Anv_cs 739 REAL :: pcld_hc_cs, tcld_hc_cs 740 REAL :: em_hc_cs, iwp_hc_cs, deltaz_hc_cs 741 REAL :: pcld_Cb_cs, tcld_Cb_cs, em_Cb_cs 742 REAL :: pcld_ThCi_cs, tcld_ThCi_cs, em_ThCi_cs 743 REAL :: pcld_Anv_cs, tcld_Anv_cs, em_Anv_cs 744 REAL :: em_hist_cs, iwp_hist_cs, deltaz_hist_cs, rad_hist_cs 745 746 REAL, DIMENSION(klev) :: test_tot, test_hc, test_hist 747 REAL, DIMENSION(klev) :: test_pcld, test_tcld, test_em, test_iwp 748 749 CHARACTER (len = 50) :: modname = 'simu_airs.sim_mesh' 750 CHARACTER (len = 160) :: abort_message 751 739 752 740 753 do j = 1, klev 741 write(*,*) 'simu_airs, j, rneb_1D =', rneb_1D(j)754 WRITE(lunout,*) 'simu_airs, j, rneb_1D =', rneb_1D(j) 742 755 enddo 743 756 … … 991 1004 if (cc_tot_mesh .gt. tsom_tot .and. & 992 1005 & abs(cc_tot_mesh-tsom_tot) .gt. 1.e-4) then 993 write(*,*) 'cc_tot_mesh > tsom_tot' 994 write(*,*) cc_tot_mesh, tsom_tot 995 STOP 1006 WRITE(abort_message,*)'cc_tot_mesh > tsom_tot', cc_tot_mesh, tsom_tot 1007 CALL abort_physic(modname,abort_message,1) 996 1008 endif 997 1009 998 1010 if (cc_tot_mesh .lt. maxval(test_tot(1:N_CS)) .and. & 999 1011 & abs(cc_tot_mesh-maxval(test_tot(1:N_CS))) .gt. 1.e-4) then 1000 write(*,*) 'cc_tot_mesh < max' 1001 write(*,*) cc_tot_mesh, maxval(test_tot(1:N_CS)) 1002 STOP 1012 WRITE(abort_message,*) 'cc_tot_mesh < max', cc_tot_mesh, maxval(test_tot(1:N_CS)) 1013 CALL abort_physic(modname,abort_message,1) 1003 1014 endif 1004 1015 1005 1016 if (cc_hc_mesh .gt. tsom_hc .and. & 1006 1017 & abs(cc_hc_mesh-tsom_hc) .gt. 1.e-4) then 1007 write(*,*) 'cc_hc_mesh > tsom_hc' 1008 write(*,*) cc_hc_mesh, tsom_hc 1009 STOP 1018 WRITE(abort_message,*) 'cc_hc_mesh > tsom_hc', cc_hc_mesh, tsom_hc 1019 CALL abort_physic(modname,abort_message,1) 1010 1020 endif 1011 1021 1012 1022 if (cc_hc_mesh .lt. maxval(test_hc(1:N_CS)) .and. & 1013 1023 & abs(cc_hc_mesh-maxval(test_hc(1:N_CS))) .gt. 1.e-4) then 1014 write(*,*) 'cc_hc_mesh < max' 1015 write(*,*) cc_hc_mesh, maxval(test_hc(1:N_CS)) 1016 STOP 1024 WRITE(abort_message,*) 'cc_hc_mesh < max', cc_hc_mesh, maxval(test_hc(1:N_CS)) 1025 CALL abort_physic(modname,abort_message,1) 1017 1026 endif 1018 1027 1019 1028 if (cc_hist_mesh .gt. tsom_hist .and. & 1020 1029 & abs(cc_hist_mesh-tsom_hist) .gt. 1.e-4) then 1021 write(*,*) 'cc_hist_mesh > tsom_hist' 1022 write(*,*) cc_hist_mesh, tsom_hist 1023 STOP 1030 WRITE(abort_message,*) 'cc_hist_mesh > tsom_hist', cc_hist_mesh, tsom_hist 1031 CALL abort_physic(modname,abort_message,1) 1024 1032 endif 1025 1033 1026 1034 if (cc_hist_mesh .lt. 0.) then 1027 write(*,*) 'cc_hist_mesh < 0' 1028 write(*,*) cc_hist_mesh 1029 STOP 1035 WRITE(abort_message,*) 'cc_hist_mesh < 0', cc_hist_mesh 1036 CALL abort_physic(modname,abort_message,1) 1030 1037 endif 1031 1038 … … 1035 1042 & maxval(test_pcld(1:N_CS)) .ne. 999. & 1036 1043 & .and. minval(test_pcld(1:N_CS)) .ne. 999.) then 1037 write(*,*) 'pcld_hc_mesh est faux' 1038 write(*,*) pcld_hc_mesh, maxval(test_pcld(1:N_CS)), & 1044 WRITE(abort_message,*) 'pcld_hc_mesh est faux', pcld_hc_mesh, maxval(test_pcld(1:N_CS)), & 1039 1045 & minval(test_pcld(1:N_CS)) 1040 STOP1046 CALL abort_physic(modname,abort_message,1) 1041 1047 endif 1042 1048 … … 1046 1052 & maxval(test_tcld(1:N_CS)) .ne. 999. & 1047 1053 & .and. minval(test_tcld(1:N_CS)) .ne. 999.) then 1048 write(*,*) 'tcld_hc_mesh est faux'1049 write(*,*) tcld_hc_mesh, maxval(test_tcld(1:N_CS)), &1050 & minval(test_tcld(1:N_CS))1054 WRITE(abort_message,*) 'tcld_hc_mesh est faux', tcld_hc_mesh, maxval(test_tcld(1:N_CS)), & 1055 & minval(test_tcld(1:N_CS)) 1056 CALL abort_physic(modname,abort_message,1) 1051 1057 endif 1052 1058 … … 1056 1062 & minval(test_em(1:N_CS)) .ne. 999. .and. & 1057 1063 & maxval(test_em(1:N_CS)) .ne. 999. ) then 1058 write(*,*) 'em_hc_mesh est faux' 1059 write(*,*) em_hc_mesh, maxval(test_em(1:N_CS)), & 1064 WRITE(abort_message,*) 'em_hc_mesh est faux', em_hc_mesh, maxval(test_em(1:N_CS)), & 1060 1065 & minval(test_em(1:N_CS)) 1061 STOP1066 CALL abort_physic(modname,abort_message,1) 1062 1067 endif 1063 1068 … … 1101 1106 subroutine test_bornes(sx,x,bsup,binf) 1102 1107 1103 real, intent(in) :: x, bsup, binf1108 REAL, intent(in) :: x, bsup, binf 1104 1109 character*14, intent(in) :: sx 1110 CHARACTER (len = 50) :: modname = 'simu_airs.test_bornes' 1111 CHARACTER (len = 160) :: abort_message 1105 1112 1106 1113 if (x .gt. bsup .or. x .lt. binf) then 1107 write(*,*) sx, 'est faux' 1108 write(*,*) sx, x 1109 STOP 1114 WRITE(abort_message,*) sx, 'est faux', sx, x 1115 CALL abort_physic(modname,abort_message,1) 1110 1116 endif 1111 1117 … … 1134 1140 include "YOMCST.h" 1135 1141 1136 integer,intent(in) :: itap1137 1138 real, dimension(klon,klev), intent(in) :: &1142 INTEGER,intent(in) :: itap 1143 1144 REAL, DIMENSION(klon,klev), intent(in) :: & 1139 1145 & rneb_airs, temp_airs, cldemi_airs, iwcon0_airs, & 1140 1146 & rad_airs, geop_airs, pplay_airs, paprs_airs 1141 1147 1142 real, dimension(klon,klev) :: &1148 REAL, DIMENSION(klon,klev) :: & 1143 1149 & rhodz_airs, rho_airs, iwcon_airs 1144 1150 1145 real, dimension(klon),intent(out) :: alt_tropo1146 1147 real, dimension(klev) :: rneb_1D, temp_1D, &1151 REAL, DIMENSION(klon),intent(out) :: alt_tropo 1152 1153 REAL, DIMENSION(klev) :: rneb_1D, temp_1D, & 1148 1154 & emis_1D, rad_1D, pres_1D, alt_1D, & 1149 1155 & rhodz_1D, dz_1D, iwcon_1D 1150 1156 1151 integer:: i, j1152 1153 real:: cc_tot_mesh, cc_hc_mesh, cc_hist_mesh1154 real:: cc_Cb_mesh, cc_ThCi_mesh, cc_Anv_mesh1155 real:: pcld_hc_mesh, tcld_hc_mesh, em_hc_mesh, iwp_hc_mesh1156 real:: em_hist_mesh, iwp_hist_mesh1157 real:: deltaz_hc_mesh, deltaz_hist_mesh, rad_hist_mesh1158 real:: pcld_Cb_mesh, tcld_Cb_mesh, em_Cb_mesh1159 real:: pcld_ThCi_mesh, tcld_ThCi_mesh, em_ThCi_mesh1160 real:: pcld_Anv_mesh, tcld_Anv_mesh, em_Anv_mesh1161 1162 real, dimension(klon),intent(out) :: map_prop_hc, map_prop_hist1163 real, dimension(klon),intent(out) :: map_emis_hc, map_iwp_hc1164 real, dimension(klon),intent(out) :: map_deltaz_hc, map_pcld_hc1165 real, dimension(klon),intent(out) :: map_tcld_hc1166 real, dimension(klon),intent(out) :: map_emis_Cb,map_pcld_Cb,map_tcld_Cb1167 real, dimension(klon),intent(out) :: &1157 INTEGER :: i, j 1158 1159 REAL :: cc_tot_mesh, cc_hc_mesh, cc_hist_mesh 1160 REAL :: cc_Cb_mesh, cc_ThCi_mesh, cc_Anv_mesh 1161 REAL :: pcld_hc_mesh, tcld_hc_mesh, em_hc_mesh, iwp_hc_mesh 1162 REAL :: em_hist_mesh, iwp_hist_mesh 1163 REAL :: deltaz_hc_mesh, deltaz_hist_mesh, rad_hist_mesh 1164 REAL :: pcld_Cb_mesh, tcld_Cb_mesh, em_Cb_mesh 1165 REAL :: pcld_ThCi_mesh, tcld_ThCi_mesh, em_ThCi_mesh 1166 REAL :: pcld_Anv_mesh, tcld_Anv_mesh, em_Anv_mesh 1167 1168 REAL, DIMENSION(klon),intent(out) :: map_prop_hc, map_prop_hist 1169 REAL, DIMENSION(klon),intent(out) :: map_emis_hc, map_iwp_hc 1170 REAL, DIMENSION(klon),intent(out) :: map_deltaz_hc, map_pcld_hc 1171 REAL, DIMENSION(klon),intent(out) :: map_tcld_hc 1172 REAL, DIMENSION(klon),intent(out) :: map_emis_Cb,map_pcld_Cb,map_tcld_Cb 1173 REAL, DIMENSION(klon),intent(out) :: & 1168 1174 & map_emis_ThCi,map_pcld_ThCi,map_tcld_ThCi 1169 real, dimension(klon),intent(out) :: &1175 REAL, DIMENSION(klon),intent(out) :: & 1170 1176 & map_emis_Anv,map_pcld_Anv,map_tcld_Anv 1171 real, dimension(klon),intent(out) :: &1177 REAL, DIMENSION(klon),intent(out) :: & 1172 1178 & map_emis_hist,map_iwp_hist,map_deltaz_hist,& 1173 1179 & map_rad_hist 1174 real, dimension(klon),intent(out) :: map_ntot,map_hc,map_hist1175 real, dimension(klon),intent(out) :: map_Cb,map_ThCi,map_Anv1180 REAL, DIMENSION(klon),intent(out) :: map_ntot,map_hc,map_hist 1181 REAL, DIMENSION(klon),intent(out) :: map_Cb,map_ThCi,map_Anv 1176 1182 1177 1183 -
LMDZ6/trunk/libf/phylmd/slab_heat_transp_mod.F90
r3435 r3531 106 106 REAL,INTENT(IN) :: omeg 107 107 108 CHARACTER (len = 20) :: modname = 'slab_heat_transp' 109 CHARACTER (len = 80) :: abort_message 110 108 111 ! Sanity check on dimensions 109 112 if ((ip1jm.ne.((nbp_lon+1)*(nbp_lat-1))).or. & 110 113 (ip1jmp1.ne.((nbp_lon+1)*nbp_lat))) then 111 write(*,*)"ini_slab_transp_geom Error: wrong array sizes"112 stop114 abort_message="ini_slab_transp_geom Error: wrong array sizes" 115 CALL abort_physic(modname,abort_message,1) 113 116 endif 114 117 ! Allocations could be done only on master process/thread... … … 925 928 INTEGER j,ifield,ig 926 929 930 CHARACTER (len = 20) :: modname = 'slab_heat_transp' 931 CHARACTER (len = 80) :: abort_message 932 927 933 ! Sanity check: 928 934 IF(klon_glo.NE.2+(jm-2)*(im-1)) THEN 929 WRITE(*,*)"gr_dyn_fi error, wrong sizes"930 STOP935 abort_message="gr_dyn_fi error, wrong sizes" 936 CALL abort_physic(modname,abort_message,1) 931 937 ENDIF 932 938 -
LMDZ6/trunk/libf/phylmd/tracco2i_mod.F90
r3453 r3531 161 161 LOGICAL, PARAMETER :: readco2ff=.TRUE., readco2bb=.FALSE. 162 162 163 CHARACTER (len = 20) :: modname = 'tracco2i.co2_emissions' 164 CHARACTER (len = 80) :: abort_message 165 163 166 IF (debutphy) THEN 164 167 … … 182 185 n_glo = size(vector) 183 186 IF (n_glo.NE.klon_glo) THEN 184 PRINT *,'sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo'185 STOP187 abort_message='sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo' 188 CALL abort_physic(modname,abort_message,1) 186 189 ENDIF 187 190 … … 190 193 n_month = size(time) 191 194 IF (n_month.NE.12) THEN 192 PRINT *,'sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12'193 STOP195 abort_message='sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12' 196 CALL abort_physic(modname,abort_message,1) 194 197 ENDIF 195 198 … … 214 217 n_glo = size(vector) 215 218 IF (n_glo.NE.klon_glo) THEN 216 PRINT *,'sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo'217 STOP219 abort_message='sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo' 220 CALL abort_physic(modname,abort_message,1) 218 221 ENDIF 219 222 … … 222 225 n_month = size(time) 223 226 IF (n_month.NE.12) THEN 224 PRINT *,'sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12'225 STOP227 abort_message='sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12' 228 CALL abort_physic(modname,abort_message,1) 226 229 ENDIF 227 230 -
LMDZ6/trunk/libf/phylmd/yamada4.F90
r3435 r3531 152 152 !$OMP THREADPRIVATE(firstcall) 153 153 154 CHARACTER (len = 20) :: modname = 'yamada4' 155 CHARACTER (len = 80) :: abort_message 156 154 157 155 158 … … 199 202 ENDIF 200 203 201 PRINT*,'YAMADA4 RIc, RIfc, Sm_min, Alpha_min',ric,rifc,seuilsm,seuilalpha204 WRITE(lunout,*)'YAMADA4 RIc, RIfc, Sm_min, Alpha_min',ric,rifc,seuilsm,seuilalpha 202 205 firstcall = .FALSE. 203 206 CALL getin_p('lmixmin',lmixmin) … … 216 219 217 220 IF (.NOT. (iflag_pbl>=6 .AND. iflag_pbl<=12)) THEN 218 STOP 'probleme de coherence dans appel a MY' 221 abort_message='probleme de coherence dans appel a MY' 222 CALL abort_physic(modname,abort_message,1) 219 223 END IF 220 224 … … 537 541 538 542 ELSE 539 STOP 'Cas nom prevu dans yamada4' 543 abort_message='Cas nom prevu dans yamada4' 544 CALL abort_physic(modname,abort_message,1) 540 545 541 546 END IF ! Fin du cas 8 … … 590 595 591 596 IF (prt_level>1) THEN 592 PRINT *,'YAMADA4 0'597 WRITE(lunout,*) 'YAMADA4 0' 593 598 END IF 594 599 … … 660 665 661 666 IF (prt_level>1) THEN 662 PRINT *,'YAMADA4 1'667 WRITE(lunout,*)'YAMADA4 1' 663 668 END IF !(prt_level>1) THEN 664 669
Note: See TracChangeset
for help on using the changeset viewer.