source: trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/inichim_newstart.F90 @ 3893

Last change on this file since 3893 was 3893, checked in by gmilcareck, 4 months ago

Remove all "call abort" and "stop" statement in LMDZ.GENERIC and replacing them by call abort_physic().

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