Changeset 3012 for trunk/LMDZ.MARS/libf/aeronomars
- Timestamp:
- Jul 24, 2023, 9:31:31 AM (2 years ago)
- Location:
- trunk/LMDZ.MARS/libf/aeronomars
- Files:
-
- 1 deleted
- 2 edited
- 1 moved
-
calchim_mod.F90 (modified) (1 diff)
-
chemistrydata.F90 (moved) (moved from trunk/LMDZ.MARS/libf/aeronomars/chimiedata.h) (1 diff)
-
photolysis.F90 (modified) (3 diffs)
-
read_phototable.F90 (deleted)
Legend:
- Unmodified
- Added
- Removed
-
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 integer, parameter :: nd = 13 ! species10 integer, parameter :: nz = 143 ! altitude11 integer, parameter :: nozo = 7 ! ozone12 integer, parameter :: nsza = 27 ! solar zenith angle13 integer, parameter :: ntemp = 4 ! temperature14 integer, parameter :: ntau = 8 ! dust10 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), dimension(nlayer,nb_phot_max) :: v_phot35 real (kind = 8),intent(out),dimension(nlayer,nb_phot_max) :: v_phot 36 36 37 37 !==========================================================================
Note: See TracChangeset
for help on using the changeset viewer.
