Changeset 3012
- Timestamp:
- Jul 24, 2023, 9:31:31 AM (16 months ago)
- Location:
- trunk/LMDZ.MARS
- Files:
-
- 1 deleted
- 7 edited
- 1 moved
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/changelog.txt
r3008 r3012 4124 4124 microphys_h.F90, and while at it also turn nuclea.F, growthrate.F90 and 4125 4125 massflowrateco2.F90 into modules. 4126 4127 == 24/07/2023 == EM 4128 Code cleanup concerning chemistry. Turn chimiedata.h into module 4129 chemistrydata.F90 and integrate read_phototable.F in it. 4130 Also fix an OpenMP issue with read_phototable; different OpenMP threads 4131 should not simultaneously open/read a file. Let the master do the job 4132 and then broadcast the result to all cores. 4133 While at it, also turned nltecool.F and nlte_tcool.F into modules. -
trunk/LMDZ.MARS/libf/aeronomars/calchim_mod.F90
r2613 r3012 31 31 use conc_mod, only: mmean ! mean molecular mass of the atmosphere 32 32 use comcstfi_h, only: pi 33 use chemistrydata_mod, only: read_phototable 33 34 use photolysis_mod, only: init_photolysis, nphot 34 35 use iono_h, only: temp_elect -
trunk/LMDZ.MARS/libf/aeronomars/chemistrydata.F90
r3011 r3012 1 MODULE chemistrydata_mod 1 2 !-------------------------------------------- 2 3 ! data for photochemistry 3 4 !-------------------------------------------- 4 5 IMPLICIT NONE 5 6 !-------------------------------------------- 6 7 ! dimensions of photolysis lookup table 7 8 !-------------------------------------------- 8 9 9 10 11 12 13 14 10 integer, parameter :: nd = 13 ! species 11 integer, parameter :: nz = 143 ! altitude 12 integer, parameter :: nozo = 7 ! ozone 13 integer, parameter :: nsza = 27 ! solar zenith angle 14 integer, parameter :: ntemp = 4 ! temperature 15 integer, parameter :: ntau = 8 ! dust 15 16 16 17 !-------------------------------------------- 17 18 18 common/chimiedata/jphot,colairtab,table_ozo 19 ! tabulated solar zenith angles 20 real,parameter :: szatab(nsza) = [ 0., 5., 10., 15., 20., 25., & 21 30., 35., 40., 45., 50., 55., & 22 60., 65., 70., 75., 80., 82., & 23 84., 86., 88., 90., 91., 92., & 24 93., 94., 95. ] 19 25 20 !$OMP THREADPRIVATE(/chimiedata/) 26 ! tabulated opacities 27 real,parameter :: tautab(ntau)=[0., 0.2, 0.4, 0.6, 0.8, 1., 2., 4.] 21 28 22 real jphot(ntemp,nsza,nz,nozo,ntau,nd)23 real colairtab(nz)24 real szatab(nsza)25 real table_ozo(nozo)26 real tautab(ntau)27 29 28 data szatab/0., 5., 10., 15., 20., 25., & 29 & 30., 35., 40., 45., 50., 55., & 30 & 60., 65., 70., 75., 80., 82., & 31 & 84., 86., 88., 90., 91., 92., & 32 & 93., 94., 95./ 30 real,save,protected :: jphot(ntemp,nsza,nz,nozo,ntau,nd) 31 !$OMP THREADPRIVATE(jphot) 32 real,save,protected :: colairtab(nz) 33 !$OMP THREADPRIVATE(colairtab) 34 real,save,protected :: table_ozo(nozo) 35 !$OMP THREADPRIVATE(table_ozo) 33 36 34 data tautab/0., 0.2, 0.4, 0.6, 0.8, 1., 2., 4./ 37 CONTAINS 38 39 subroutine read_phototable 40 41 !*********************************************************************** 42 ! 43 ! subject: 44 ! -------- 45 ! 46 ! read photolysis lookup table 47 ! 48 ! VERSION: 8/10/2014 49 ! 50 ! Author: Franck Lefevre 51 ! 52 ! Arguments: 53 ! ---------- 54 ! 55 !*********************************************************************** 56 57 use ioipsl_getin_p_mod, only: getin_p 58 use datafile_mod, only: datadir 59 use mod_phys_lmdz_para, only: is_master 60 use mod_phys_lmdz_transfert_para, only: bcast 61 62 implicit none 63 64 !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc 65 ! local: 66 !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc 67 68 integer :: fic, ij, iozo, isza, itemp, iz, itau, ierr 69 real :: xsza 70 71 character(len = 128) :: phototable ! photolysis table file name 72 73 !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc 74 ! set photolysis table input file name 75 !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc 76 77 phototable = "jmars.20140930" ! default 78 79 ! look for a " phototable= ..." option in def files 80 81 call getin_p("phototable",phototable) 82 83 fic = 81 84 85 if (is_master) then ! only the master needs to open file and read data 86 87 open(fic, form = 'formatted', status = 'old', & 88 file =trim(datadir)//"/"//trim(phototable),iostat=ierr) 89 90 if (ierr /= 0) THEN 91 write(*,*)'Error : cannot open photolysis lookup table ', trim(phototable) 92 write(*,*)'It should be in :',trim(datadir),'/' 93 write(*,*)'1) You can change this directory in callphys.def' 94 write(*,*)' with:' 95 write(*,*)' datadir=/path/to/the/directory' 96 write(*,*)'2) You can change the input phototable file name in' 97 write(*,*)' callphys.def with:' 98 write(*,*)' phototable=filename' 99 call abort_physic("read_phototable","missing "//trim(phototable)//"file",1) 100 end if 101 102 !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc 103 ! read photolys table 104 !ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc 105 106 print*, 'read photolysis lookup table ',trim(phototable) 107 108 do itau = 1,ntau 109 do itemp = 1,ntemp 110 do iozo = 1,nozo 111 do isza = 1,nsza 112 do iz = nz,1,-1 113 read(fic,*) colairtab(iz), xsza, table_ozo(iozo) 114 read(fic,'(7e11.4)') (jphot(itemp,isza,iz,iozo,itau,ij), ij= 1,nd) 115 do ij = 1,nd 116 if (jphot(itemp,isza,iz,iozo,itau,ij) == 1.e-30) then 117 jphot(itemp,isza,iz,iozo,itau,ij) = 0. 118 end if 119 end do 120 end do 121 end do 122 end do 123 end do 124 end do 125 126 print*, 'lookup table...ok' 127 close(fic) 128 129 endif ! of if (is_master) 130 131 ! broadcast the information to all cores 132 call bcast(colairtab) 133 call bcast(table_ozo) 134 call bcast(jphot) 135 136 end subroutine read_phototable 137 138 END MODULE chemistrydata_mod -
trunk/LMDZ.MARS/libf/aeronomars/photolysis.F90
r2170 r3012 7 7 !========================================================================== 8 8 9 use comcstfi_h 9 use comcstfi_h, only: g 10 use chemistrydata_mod, only: nd, nz, nozo, nsza, ntemp, ntau 11 use chemistrydata_mod, only: szatab, tautab, colairtab, table_ozo, jphot 10 12 11 13 implicit none 12 13 #include "chimiedata.h"14 14 15 15 !========================================================================== … … 19 19 integer, intent(in) :: nlayer ! number of atmospheric layers 20 20 integer, intent(in) :: nb_phot_max ! number of processes treated numerically as photodissociations 21 integer :: lswitch! interface level between chemistries22 real :: press(nlayer)! pressure (hPa)23 real :: temp(nlayer)! temperature (K)24 real :: sza! solar zenith angle (deg)25 real :: tauref! optical depth at 7 hpa26 real :: zmmean(nlayer)! mean molecular mass (g)27 real :: dist_sol! sun distance (AU)28 real :: rmco2(nlayer)! co2 mixing ratio29 real :: rmo3(nlayer)! ozone mixing ratio21 integer,intent(in) :: lswitch ! interface level between chemistries 22 real,intent(in) :: press(nlayer) ! pressure (hPa) 23 real,intent(in) :: temp(nlayer) ! temperature (K) 24 real,intent(in) :: sza ! solar zenith angle (deg) 25 real,intent(in) :: tauref ! optical depth at 7 hpa 26 real,intent(in) :: zmmean(nlayer) ! mean molecular mass (g) 27 real,intent(in) :: dist_sol ! sun distance (AU) 28 real,intent(in) :: rmco2(nlayer) ! co2 mixing ratio 29 real,intent(in) :: rmo3(nlayer) ! ozone mixing ratio 30 30 31 31 !========================================================================== … … 33 33 !========================================================================== 34 34 35 real (kind = 8), 35 real (kind = 8),intent(out),dimension(nlayer,nb_phot_max) :: v_phot 36 36 37 37 !========================================================================== -
trunk/LMDZ.MARS/libf/phymars/nlte_calc.F
r2616 r3012 28 28 subroutine MZESC110 (ig,nl_cts_real, nzy_cts_real,ierr,varerr) 29 29 c*********************************************************************** 30 use nlte_tcool_mod, only: errors 30 31 implicit none 31 32 … … 710 711 711 712 c*********************************************************************** 712 713 use nlte_tcool_mod, only: errors 713 714 implicit none 714 715 … … 1257 1258 subroutine MZESC121 1258 1259 c*********************************************************************** 1259 1260 use nlte_tcool_mod, only: errors 1260 1261 implicit none 1261 1262 -
trunk/LMDZ.MARS/libf/phymars/nlte_tcool.F
r2398 r3012 1 MODULE nlte_tcool_mod 2 3 IMPLICIT NONE 4 5 CONTAINS 1 6 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 2 7 ! Fast scheme for NLTE cooling rates at 15um by CO2 in a Martian GCM ! … … 35 40 include 'nlte_paramdef.h' 36 41 include 'nlte_commons.h' 37 include "chimiedata.h"38 42 39 43 … … 195 199 enddo 196 200 c end subroutine 197 return 198 end 201 202 end subroutine nlte_tcool 199 203 200 204 … … 232 236 233 237 c functions 234 external hrkday_convert235 real hrkday_convert238 ! external hrkday_convert 239 ! real hrkday_convert 236 240 237 241 c*********************************************************************** … … 472 476 473 477 c end 474 return 475 end 478 479 end subroutine NLTEdlvr11_ZGRID 476 480 477 481 … … 1253 1257 1254 1258 c final 1255 return 1259 1256 1260 c 1257 end 1261 end subroutine NLTEdlvr11_CZALU 1258 1262 1259 1263 … … 1340 1344 1341 1345 c 1342 return 1343 end 1346 end subroutine NLTEdlvr11_FB626CTS 1344 1347 1345 1348 … … 1372 1375 1373 1376 c end 1374 return 1375 end 1377 1378 end function hrkday_convert 1376 1379 1377 1380 … … 1635 1638 call abort_physic("nlte_tcool", 1636 1639 & 'Stopped in NLTE scheme due to severe error.',1) 1637 end 1640 1641 end subroutine ERRORS 1642 1643 END MODULE nlte_tcool_mod -
trunk/LMDZ.MARS/libf/phymars/nltecool.F
r2586 r3012 1 MODULE nltecool_mod 2 3 IMPLICIT NONE 4 5 CONTAINS 1 6 c************************************************************************** 2 7 c … … 34 39 implicit none 35 40 36 #include "nltedata.h" ! (Equivalent to the reading of the "nlte_escape.dat" file) 37 #include "chimiedata.h" 38 #include "callkeys.h" 41 include "nltedata.h" 42 include "callkeys.h" 39 43 40 44 c Input and output variables 41 45 c 42 integer ngrid! no. of horiz. gridpoints43 integer nlayer! no. of atmospheric layers44 integer nq! no. of tracers45 real pplay(ngrid,nlayer) ! input pressure grid46 real pt(ngrid,nlayer) ! input temperatures47 real pq(ngrid,nlayer,nq) ! input mmrs48 real dtnlte(ngrid,nlayer) ! output temp. tendencies46 integer,intent(in) :: ngrid ! no. of horiz. gridpoints 47 integer,intent(in) :: nlayer ! no. of atmospheric layers 48 integer,intent(in) :: nq ! no. of tracers 49 real,intent(in) :: pplay(ngrid,nlayer) ! input pressure grid (Pa) 50 real,intent(in) :: pt(ngrid,nlayer) ! input temperatures (K) 51 real,intent(in) :: pq(ngrid,nlayer,nq) ! input mmrs (kg/kg_air) 52 real,intent(out) :: dtnlte(ngrid,nlayer) ! output temp. tendencies (K/s) 49 53 50 54 c … … 261 265 c close(7) 262 266 c 263 return 264 end267 268 end subroutine nltecool 265 269 266 270 c*********************************************************************** … … 290 294 endif 291 295 enddo 292 return 293 end 296 297 end subroutine interp1 294 298 295 299 c*********************************************************************** … … 324 328 endif 325 329 enddo 326 return 327 end 330 331 end subroutine interp3 332 333 END MODULE nltecool_mod -
trunk/LMDZ.MARS/libf/phymars/physiq_mod.F
r3006 r3012 24 24 use calcstormfract_mod, only: calcstormfract 25 25 use topmons_mod, only: topmons,topmons_setup 26 use nltecool_mod, only: nltecool 27 use nlte_tcool_mod, only: nlte_tcool 26 28 use tracer_mod, only: noms, mmol, igcm_co2, igcm_n2, igcm_co2_ice, 27 29 & igcm_co, igcm_o, igcm_h2o_vap, igcm_h2o_ice,
Note: See TracChangeset
for help on using the changeset viewer.