source: trunk/LMDZ.MARS/libf/aeronomars/chemistrydata.F90

Last change on this file was 3012, checked in by emillour, 17 months ago

Mars PCM:
Code cleanup concerning chemistry. Turn chimiedata.h into module
chemistrydata.F90 and integrate read_phototable.F in it.
Also fix an OpenMP issue with read_phototable; different OpenMP threads
should not simultaneously open/read a file. Let the master do the job
and then broadcast the result to all cores.
While at it, also turned nltecool.F and nlte_tcool.F into modules.
EM

File size: 4.2 KB
Line 
1MODULE chemistrydata_mod
2!--------------------------------------------
3!     data for photochemistry
4!--------------------------------------------
5IMPLICIT NONE
6!--------------------------------------------
7!     dimensions of photolysis lookup table
8!--------------------------------------------
9
10integer, parameter :: nd    = 13  ! species
11integer, parameter :: nz    = 143 ! altitude
12integer, parameter :: nozo  = 7   ! ozone
13integer, parameter :: nsza  = 27  ! solar zenith angle
14integer, parameter :: ntemp = 4   ! temperature
15integer, parameter :: ntau  = 8   ! dust
16
17!--------------------------------------------
18
19! tabulated solar zenith angles
20real,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. ]
25
26! tabulated opacities
27real,parameter :: tautab(ntau)=[0., 0.2, 0.4, 0.6, 0.8, 1., 2., 4.]
28
29
30real,save,protected :: jphot(ntemp,nsza,nz,nozo,ntau,nd)
31!$OMP THREADPRIVATE(jphot)
32real,save,protected :: colairtab(nz)
33!$OMP THREADPRIVATE(colairtab)
34real,save,protected :: table_ozo(nozo)
35!$OMP THREADPRIVATE(table_ozo)
36
37CONTAINS
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
136end subroutine read_phototable
137
138END MODULE chemistrydata_mod
Note: See TracBrowser for help on using the repository browser.