source: trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/vert_regrid_kim.F90 @ 3026

Last change on this file since 3026 was 1904, checked in by jvatant, 7 years ago

Fixed 2 critical bugs.
+ One about rat_mmol (* instead of /)
+ One about zonal means (or not) arrays sent in chemistry and mufi
In any case zonal means seems to be responsible for crashes of chem and mufi !
Stop using them until further informations (for mufi, no problem, full 3D is quick)
--JVO

File size: 6.0 KB
Line 
1SUBROUTINE vert_regrid_kim(nq,q)
2
3  ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4  !
5  ! Purpose : * Calculates the zonally averaged upper chemistry fields according
6  !           to the new pressure grid - based on interp_vert.
7  !           * In case the GCM top is lowered we interpolate upper fields
8  !           between the former ones and the GCM top layer zonally averaged.
9  !           * In case the GCM top is highered we interpolate tracers on the
10  !           GCM grid uppermost layers between the upper chemsitry fields and
11  !           the chem. tracers below.
12  !
13  ! Author : Jan Vatant d'Ollone (2018)
14  ! ------
15  !
16  ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
17
18  USE comchem_h, ONLY: nkim, nlaykim_up, preskim, ykim_up
19  USE comchem_newstart_h
20  USE tracer_h
21  USE comvert_mod, ONLY: aps
22 
23  IMPLICIT NONE
24 
25  INCLUDE "netcdf.inc"
26
27  INCLUDE "dimensions.h"
28 
29  ! -----------------
30  ! Declarations
31  ! -----------------
32  INTEGER, INTENT(IN) :: nq ! Total number of advected fields (tracers)
33 
34  REAL,DIMENSION(iim+1,jjm+1,llm,nq), INTENT(INOUT) :: q   ! Advected fields (kg/kg) on 3D dyn. grid
35
36  REAL, DIMENSION(:,:), ALLOCATABLE   :: avg_qtop  ! Zonally averaged q (mol/mol) on top layer
37
38  REAL :: coef, ykimlon
39
40  INTEGER :: ngridmx
41 
42  INTEGER :: ng0, isup
43
44  INTEGER :: ln, lo, ilay, ichem, ilon, ilat
45
46  LOGICAL :: lowered
47
48  ! -----------------------------
49  ! 0. Get useful size of arrays
50  ! -----------------------------
51
52  ngridmx = size(ykim_up,DIM=2)
53
54  ! ------------------------------------------------------------
55  ! 1. Compute zonal mean of last layer for every chem and lat
56  ! and convert it to molar mixing fraction and to physics grid
57  ! Preliminary, only in case ceiling has been lowered
58  ! ------------------------------------------------------------
59
60  lowered = .FALSE.
61
62  IF ( preskim(1) .GT. preskimold(1) ) THEN
63
64    lowered = .TRUE.
65
66    ALLOCATE(avg_qtop(nkim,ngridmx))
67
68    DO ichem=1,nkim
69      avg_qtop(ichem,:)=0.0
70      DO ilon=1,iim
71        avg_qtop(ichem,1)=avg_qtop(ichem,1)+q(ilon,1,llm,chimi_indx(ichem))
72        avg_qtop(ichem,ngridmx)=avg_qtop(ichem,ngridmx)+q(ilon,jjm+1,llm,chimi_indx(ichem))
73        DO ilat=2,jjm
74          ng0 = iim*(ilat-2)+1
75          avg_qtop(ichem,ng0+1:ng0+iim)=avg_qtop(ichem,ng0+1:ng0+iim)+q(ilon,ilat,llm,chimi_indx(ichem))
76        ENDDO
77      ENDDO
78      ! mass -> molar mixing ratio to be comparable to ykim_up later
79      avg_qtop(ichem,:)=avg_qtop(ichem,:)/rat_mmol(chimi_indx(ichem))
80    ENDDO
81
82  avg_qtop(:,:) = avg_qtop(:,:) / real(iim)
83
84  ENDIF
85
86  ! ------------------------------
87  ! 2. Process upper chem. fields
88  ! ------------------------------
89
90  DO ln=1,nlaykim_up
91
92    ! Standard case between 2 old upper pressure grid points
93
94    DO lo=1,nlaykimold-1
95
96      IF ( ( preskim(ln) .LE. preskimold(lo)   ) .AND. &
97           ( preskim(ln) .GT. preskimold(lo+1) ) ) THEN
98
99        coef = (preskim(ln)-preskimold(lo)) / (preskimold(lo+1)-preskimold(lo))
100        ykim_up(:,:,ln) = (1.0-coef)*ykim_up_oldv(:,:,lo) + coef*ykim_up_oldv(:,:,lo+1)
101
102      ENDIF
103
104    ENDDO
105
106    ! Special cases
107
108    IF ( lowered )  THEN
109
110    ! If the ceiling of GCM has been lowered we interpolate a zonal mean between new GCM top and former upper fields
111    ! NB : We could have kept in memory the former tracers at this altitude and zonally averaged them
112    ! but it's certainly useless as we're in newstart and the fields will re-equilibrate
113
114      IF ( preskim(ln) .GT. preskimold(1) ) THEN
115          DO ichem=1,nkim
116            coef = ( preskim(ln)-aps(llm) ) / ( preskimold(1)-aps(llm) )
117            ykim_up(ichem,:,ln) = (1.0-coef)*avg_qtop(ichem,:) + coef*ykim_up_oldv(ichem,:,1)
118          ENDDO
119      ENDIF
120
121    ENDIF
122
123    IF ( preskim(ln) .LE. preskimold(nlaykimold) ) THEN ! upper ceiling at 1300km can have slight variations
124      ykim_up(:,:,ln) = ykim_up_oldv(:,:,lo)
125    ENDIF 
126 
127  ENDDO ! do ln=1,nlaykim_up
128
129  ! ----------------------------------------------------------------------------
130  ! 3. Correct the 3D advected chem. tracer fields if model ceiling is highered
131  ! In this case we interpolate between tracers below and upper_chemistry values
132  ! Doing this we convert via rat_mmol ykim_up from molar to mass mixing ratio
133  ! ----------------------------------------------------------------------------
134 
135  IF ( preskim(1) .LT. preskimold(1) ) THEN
136 
137    ! We just want to process the concerned upper layers of the GCM
138    DO ilay=1,llm
139      IF ( aps(ilay) .LT. preskimold(1) ) THEN
140        isup = ilay-1
141        EXIT
142      ENDIF
143    ENDDO
144
145    DO ilay=isup+1,llm
146 
147      coef = ( aps(ilay) - preskim(1) ) / ( aps(isup) - preskim(1) )
148
149      DO ichem=1,nkim
150
151        ! We need to convert ykim_up on phys grid to q on dyn grid
152        ! so we deal with mono-gridpoints for North and South Poles   
153
154        q(:,1,ilay,chimi_indx(ichem)) = (1.0-coef)*ykim_up(ichem,1,1)*rat_mmol(chimi_indx(ichem)) &
155                                      + coef*q(:,1,isup,chimi_indx(ichem))
156        q(:,jjm+1,ilay,chimi_indx(ichem)) = (1.0-coef)*ykim_up(ichem,ngridmx,1)*rat_mmol(chimi_indx(ichem)) &
157                                          + coef*q(:,jjm+1,isup,chimi_indx(ichem))
158
159          DO ilat=2,jjm
160
161            ng0 = iim*(ilat-2)+1
162           
163            DO ilon=2,iim
164              ! ykim_up and q are shifted one to the other on longitudinal grid
165              ykimlon = 0.5*(ykim_up(ichem,ng0+ilon-1,1)+ykim_up(ichem,ng0+ilon,1)) * rat_mmol(chimi_indx(ichem))
166
167              q(ilon,ilat,ilay,chimi_indx(ichem)) = (1.0-coef)*ykimlon + coef*q(ilon,ilat,isup,chimi_indx(ichem))
168            ENDDO
169
170            ! Periodicity on longitude at 180 and -180
171
172            ykimlon = 0.5*(ykim_up(ichem,ng0+1,1)+ykim_up(ichem,ng0+iim,1)) * rat_mmol(chimi_indx(ichem))
173
174            q(1,ilat,ilay,chimi_indx(ichem)) = (1.0-coef)*ykimlon + coef*q(1,ilat,isup,chimi_indx(ichem))
175            q(iim+1,ilat,ilay,chimi_indx(ichem)) = q(1,ilat,ilay,chimi_indx(ichem))
176
177          ENDDO ! do ilat=2,jjm
178      ENDDO ! do ichem=1,nkim
179    ENDDO ! do ilay=1,llm
180
181  ENDIF
182 
183END SUBROUTINE vert_regrid_kim
Note: See TracBrowser for help on using the repository browser.