source: trunk/LMDZ.GENERIC/libf/phystd/dyn1d/initracer_1D.F90 @ 3753

Last change on this file since 3753 was 3753, checked in by afalco, 2 months ago

Generic PCM

Tracers in 1D can now be initialized with VMR set in traceur.def
(homogeneous value or profile) with or without chemistry. Inichim_1D
is still called after. Initialization of co2_ice, h2o_vap and h2o_ice
can still be initialized with profile_co2_ice etc. the old way.

MM

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