source: trunk/LMDZ.GENERIC/libf/phystd/dyn1d/inichim_1D.F90 @ 3801

Last change on this file since 3801 was 3801, checked in by mmaurice, 5 weeks ago

Generic PCM:

Add qsurf flag in modern traceur.def (used in 1D)

MM

  • Property svn:executable set to *
File size: 7.2 KB
RevLine 
[3753]1!module inichim_1D_mod
2
3!implicit none
4
[2542]5      subroutine inichim_1D(nlayer, nq, pq, qsurf, play, &
[1796]6                                  flagh2o,flagthermo)
7
[2542]8      use tracer_h, only: noms, mmol
9      use datafile_mod, only: datadir
[1796]10
11      implicit none
12
13!=======================================================================
14!
15!  Purpose:
16!  --------
17!
18!  Initialization of the chemistry for use in the building of a new start file
19!  used by program newstart.F
20!  also used by program testphys1d.F
21!
22!  Authors:
23!  -------
24!  Initial version 11/2002 by Sebastien Lebonnois
25!  Revised 07/2003 by Monica Angelats-i-Coll to use input files
26!  Modified 10/2008 Identify tracers by their names Ehouarn Millour
27!  Modified 11/2011 Addition of methane Franck Lefevre
28!  Rewritten 04/2012 Franck Lefevre
[2542]29!  Rewritten 03/2021 Yassin Jaziri (Use of #Moderntrac-v1 to init thanks traceur.def)
[1796]30!
31!  Arguments:
32!  ----------
33!
[2542]34!  nlayer          Number of atmospheric layers
35!  pq(nlayer,nq)   Advected fields, ie chemical species here
36!  qsurf(nq)       Amount of tracer on the surface (kg/m2)
37!  play(nlayer)    Pressure (Pa)
38!  flagh2o         flag for initialisation of h2o (1: yes / 0: no)
39!  flagthermo      flag for initialisation of thermosphere only (1: yes / 0: no)
[1796]40!
41!=======================================================================
42
43
44! inputs :
45
[2542]46      integer,intent(in) :: nlayer         ! Number of atmospheric layers.
47      integer,intent(in) :: nq             ! number of tracers
48      real   ,intent(in) :: play(nlayer)   ! Mid-layer pressure (Pa). 
49      integer,intent(in) :: flagh2o        ! flag for h2o initialisation
50      integer,intent(in) :: flagthermo     ! flag for thermosphere initialisation only
[1796]51
52! outputs :
53
[2542]54      real,intent(out)   :: pq(nlayer,nq)  ! tracers (kg/kg_of_air)
55      real,intent(out)   :: qsurf(nq)      ! surface values (kg/m2) of tracers
[1796]56
57! local :
58
[2542]59      real, allocatable  :: pf(:)          ! pressure in vmr profile files set in traceur.def
60      real, allocatable  :: qf(:)          ! vmr      in vmr profile files set in traceur.def
[1796]61
[2542]62      real    :: mmean(nlayer)             ! mean molecular mass (g)
63      real    :: pqx(nlayer,nq)            ! tracers (vmr)
64      real    :: qx(nq)                    ! constant vmr set in traceur.def
65      integer :: iq, ilay, iline, nlines, ierr
[1796]66
[2542]67      CHARACTER(len=100) :: qxf(nq)        ! vmr profile files set in traceur.def
68      CHARACTER(len=100) :: fil            ! path files
69      character(len=500) :: tracline       ! to store a line of text
[1796]70
[2542]71      logical :: foundback = .false.
[1796]72
[2542]73! 1. initialization
[1796]74
[2542]75      pq(:,:)  = 0.
76      qsurf(:) = 0.
77      pqx(:,:) = 0.
78      qx(:)    = 0.
79      qxf(:)   = 'None'
[3073]80      nlines   = 0
[1796]81
[2542]82! 2. load in traceur.def chemistry data for initialization:
[1796]83
[2542]84      ! Skip nq
85      open(90,file='traceur.def',status='old',form='formatted',iostat=ierr)
86      if (ierr.eq.0) then
87        READ(90,'(A)') tracline
88        IF (trim(tracline).eq.'#ModernTrac-v1') THEN ! Test modern traceur.def
89           DO
90             READ(90,'(A)',iostat=ierr) tracline
91             IF (ierr.eq.0) THEN
92               IF (index(tracline,'#').ne.1) THEN ! Allows arbitary number of comments lines in the header
93                 EXIT
94               ENDIF
95             ELSE ! If pb, or if reached EOF without having found number of tracer
96                write(*,*) "calchim: error reading line of tracers"
97                write(*,*) "   (first lines of traceur.def) "
98                stop
99             ENDIF
100           ENDDO
101        ENDIF ! if modern or standard traceur.def
102      else
103         write(*,*) "calchim: error opening traceur.def in inichim_1D"
[1796]104         stop
105      endif
106
[2542]107      ! Get data of tracers
108      do iq=1,nq
109         read(90,'(A)') tracline
110         write(*,*)"inichim_1D: iq=",iq,"noms(iq)=",trim(noms(iq))
111         if (index(tracline,'qx='    ) /= 0) then
112            read(tracline(index(tracline,'qx=')+len('qx='):),*) qx(iq)
113            write(*,*) ' Parameter value (traceur.def) : qx=', qx(iq)
114         else
115            write(*,*) ' Parameter value (default)     : qx=', qx(iq)
116         end if
117         if (index(tracline,'qxf='    ) /= 0) then
118            read(tracline(index(tracline,'qxf=')+len('qxf='):),*) qxf(iq)
119            write(*,*) ' Parameter value (traceur.def) : qxf=', qxf(iq)
120         else
121            write(*,*) ' Parameter value (default)     : qxf=', qxf(iq)
122         end if
[3801]123         if (index(tracline,'qsurf='    ) /= 0) then
124             read(tracline(index(tracline,'qsurf=')+len('qsurf='):),*) qsurf(iq)
125             write(*,*) ' Parameter value (traceur.def) : qsurf=', qsurf(iq)
126         else
127             write(*,*) ' Parameter value (default)     : qsurf=', qsurf(iq)
128         end if
[1796]129      end do
130
[2542]131      close(90)
[1796]132
133! 3. initialization of tracers
134
[2542]135! 3.1 vertical interpolation
[1796]136
[2542]137      do iq=1,nq
138         if (qx(iq) /= 0.) then
139            pqx(:,iq) = qx(iq)
140         else if (qxf(iq) /= 'None') then
141            ! Opening file
[3753]142            fil = qxf(iq)
143            print*, 'chemical profile '//trim(noms(iq))//': ', fil
[2542]144            open(UNIT=90,FILE=fil,STATUS='old',iostat=ierr)
145            if (ierr.eq.0) then
146               read(90,*) ! read one header line
147               do         ! get number of lines
148                   read(90,*,iostat=ierr)
149                   if (ierr<0) exit
150                   nlines = nlines + 1
[1796]151               end do
[2542]152               ! allocate reading variable
153               allocate(pf(nlines))
154               allocate(qf(nlines))
155               ! read file
156               rewind(90) ! restart from the beggining of the file
157               read(90,*) ! read one header line
158               do iline=1,nlines
159                  read(90,*) pf(iline), qf(iline) ! pf [Pa], qf [vmr]
160               end do
161               ! interp in gcm grid
162               do ilay=1,nlayer
163                  call intrplf(log(play(ilay)),pqx(ilay,iq),log(pf),qf,nlines)
164               end do
165               ! deallocate for next tracer
166               deallocate(pf)
167               deallocate(qf)
168            else
169               write(*,*) 'inichim_1D: error opening ', fil
170               stop
171            endif
172            close(90)
173         end if
174      end do
[1796]175
[2542]176! 3.2 background gas
[1796]177
[2542]178      do iq=1,nq
179         if (all(pqx(:,iq)==1.)) then
180            pqx(:,iq) = 0.
181            do ilay=1,nlayer
182               pqx(ilay,iq) = 1-sum(pqx(ilay,:))
183               if (pqx(ilay,iq)<=0.) then
184                  write(*,*) 'inichim_1D: vmr tot > 1 not possible'
185                  stop
[1796]186               end if
187            end do
[2542]188            foundback = .true.
189            exit ! you found the background gas you can skip others
190         end if
191      end do
192      if (.not.foundback) then
193         write(*,*) 'inichim_1D: you need to set a background gas'
194         write(*,*) '            by qx=1. in traceur.def'
195         stop
196      end if
[1796]197
[2542]198! 3.3 mmean
199      mmean(:) = 0.
200      do ilay=1,nlayer
201         do iq=1,nq
202            mmean(ilay) = mmean(ilay) + pqx(ilay,iq)*mmol(iq)
203         end do
204      end do
[1796]205
[2542]206! 3.4 convert vmr to mmr
[1796]207
[2542]208      do ilay=1,nlayer
209         do iq=1,nq
210            pq(ilay,iq) = pqx(ilay,iq)*mmol(iq)/mmean(ilay)
[1796]211         end do
[2542]212      end do
[1796]213
[2542]214! 4. Hard coding
215! Do whatever you want here to specify pq and qsurf
216! Or use #ModernTrac-v1 and add another option section 2.
[1796]217
[3753]218   end subroutine inichim_1D
219
220!end module inichim_1D_mod
Note: See TracBrowser for help on using the repository browser.