source: LMDZ6/trunk/libf/dyn3d/integrd.f90 @ 5281

Last change on this file since 5281 was 5281, checked in by abarral, 8 hours ago

Turn comgeom.h comgeom2.h into modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.8 KB
Line 
1!
2! $Id: integrd.f90 5281 2024-10-28 10:17:48Z abarral $
3!
4SUBROUTINE integrd &
5        (  nq,vcovm1,ucovm1,tetam1,psm1,massem1, &
6        dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis & !,finvmaold
7        )
8
9  USE comgeom_mod_h
10  use control_mod, only : planet_type
11  use comconst_mod, only: pi
12  USE logic_mod, ONLY: leapf
13  use comvert_mod, only: ap, bp
14  USE temps_mod, ONLY: dt
15
16  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
17USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
18          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
19IMPLICIT NONE
20
21
22  !=======================================================================
23  !
24  !   Auteur:  P. Le Van
25  !   -------
26  !
27  !   objet:
28  !   ------
29  !
30  !   Incrementation des tendances dynamiques
31  !
32  !=======================================================================
33  !-----------------------------------------------------------------------
34  !   Declarations:
35  !   -------------
36
37
38
39  include "iniprint.h"
40
41  !   Arguments:
42  !   ----------
43
44  integer,intent(in) :: nq ! number of tracers to handle in this routine
45  real,intent(inout) :: vcov(ip1jm,llm) ! covariant meridional wind
46  real,intent(inout) :: ucov(ip1jmp1,llm) ! covariant zonal wind
47  real,intent(inout) :: teta(ip1jmp1,llm) ! potential temperature
48  real,intent(inout) :: q(ip1jmp1,llm,nq) ! advected tracers
49  real,intent(inout) :: ps(ip1jmp1) ! surface pressure
50  real,intent(inout) :: masse(ip1jmp1,llm) ! atmospheric mass
51  real,intent(in) :: phis(ip1jmp1) ! ground geopotential !!! unused
52  ! ! values at previous time step
53  real,intent(inout) :: vcovm1(ip1jm,llm)
54  real,intent(inout) :: ucovm1(ip1jmp1,llm)
55  real,intent(inout) :: tetam1(ip1jmp1,llm)
56  real,intent(inout) :: psm1(ip1jmp1)
57  real,intent(inout) :: massem1(ip1jmp1,llm)
58  ! ! the tendencies to add
59  real,intent(in) :: dv(ip1jm,llm)
60  real,intent(in) :: du(ip1jmp1,llm)
61  real,intent(in) :: dteta(ip1jmp1,llm)
62  real,intent(in) :: dp(ip1jmp1)
63  real,intent(in) :: dq(ip1jmp1,llm,nq) !!! unused
64   ! real,intent(out) :: finvmaold(ip1jmp1,llm) !!! unused
65
66  !   Local:
67  !   ------
68
69  REAL :: vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1)
70  REAL :: massescr( ip1jmp1,llm )
71   ! REAL finvmasse(ip1jmp1,llm)
72  REAL :: p(ip1jmp1,llmp1)
73  REAL :: tpn,tps,tppn(iim),tpps(iim)
74  REAL :: qpn,qps,qppn(iim),qpps(iim)
75  REAL :: deltap( ip1jmp1,llm )
76
77  INTEGER :: l,ij,iq,i,j
78
79  REAL :: SSUM
80
81  !-----------------------------------------------------------------------
82
83  DO  l = 1,llm
84    DO  ij = 1,iip1
85     ucov(    ij    , l) = 0.
86     ucov( ij +ip1jm, l) = 0.
87     uscr(     ij      ) = 0.
88     uscr( ij +ip1jm   ) = 0.
89    ENDDO
90  ENDDO
91
92
93  !    ............    integration  de       ps         ..............
94
95  CALL SCOPY(ip1jmp1*llm, masse, 1, massescr, 1)
96
97  DO ij = 1,ip1jmp1
98   pscr (ij)    = ps(ij)
99   ps (ij)      = psm1(ij) + dt * dp(ij)
100  ENDDO
101  !
102  DO ij = 1,ip1jmp1
103    IF( ps(ij).LT.0. ) THEN
104     write(lunout,*) "integrd: negative surface pressure ",ps(ij)
105     write(lunout,*) " at node ij =", ij
106     ! ! since ij=j+(i-1)*jjp1 , we have
107     j=modulo(ij,jjp1)
108     i=1+(ij-j)/jjp1
109     write(lunout,*) " lon = ",rlonv(i)*180./pi, " deg", &
110           " lat = ",rlatu(j)*180./pi, " deg"
111     call abort_gcm("integrd", "", 1)
112    ENDIF
113  ENDDO
114  !
115  DO  ij    = 1, iim
116   tppn(ij) = aire(   ij   ) * ps(  ij    )
117   tpps(ij) = aire(ij+ip1jm) * ps(ij+ip1jm)
118  ENDDO
119   tpn      = SSUM(iim,tppn,1)/apoln
120   tps      = SSUM(iim,tpps,1)/apols
121  DO ij   = 1, iip1
122   ps(   ij   )  = tpn
123   ps(ij+ip1jm)  = tps
124  ENDDO
125  !
126  !  ... Calcul  de la nouvelle masse d'air au dernier temps integre t+1 ...
127  !
128  CALL pression ( ip1jmp1, ap, bp, ps, p )
129  CALL massdair (     p  , masse         )
130
131  ! Ehouarn : we don't use/need finvmaold and finvmasse,
132        ! so might as well not compute them
133   ! CALL   SCOPY( ijp1llm  , masse, 1, finvmasse,  1      )
134   ! CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1  )
135  !
136
137  !    ............   integration  de  ucov, vcov,  h     ..............
138
139  DO l = 1,llm
140
141   DO ij = iip2,ip1jm
142    uscr( ij )   =  ucov( ij,l )
143    ucov( ij,l ) = ucovm1( ij,l ) + dt * du( ij,l )
144   ENDDO
145
146   DO ij = 1,ip1jm
147    vscr( ij )   =  vcov( ij,l )
148    vcov( ij,l ) = vcovm1( ij,l ) + dt * dv( ij,l )
149   ENDDO
150
151   DO ij = 1,ip1jmp1
152    hscr( ij )    =  teta(ij,l)
153    teta ( ij,l ) = tetam1(ij,l) *  massem1(ij,l) / masse(ij,l) &
154          + dt * dteta(ij,l) / masse(ij,l)
155   ENDDO
156
157  !   ....  Calcul de la valeur moyenne, unique  aux poles pour  teta    ......
158  !
159  !
160   DO  ij   = 1, iim
161    tppn(ij) = aire(   ij   ) * teta(  ij    ,l)
162    tpps(ij) = aire(ij+ip1jm) * teta(ij+ip1jm,l)
163   ENDDO
164    tpn      = SSUM(iim,tppn,1)/apoln
165    tps      = SSUM(iim,tpps,1)/apols
166
167   DO ij   = 1, iip1
168    teta(   ij   ,l)  = tpn
169    teta(ij+ip1jm,l)  = tps
170   ENDDO
171  !
172
173   IF(leapf)  THEN
174     CALL SCOPY ( ip1jmp1, uscr(1), 1, ucovm1(1, l), 1 )
175     CALL SCOPY (   ip1jm, vscr(1), 1, vcovm1(1, l), 1 )
176     CALL SCOPY ( ip1jmp1, hscr(1), 1, tetam1(1, l), 1 )
177   END IF
178
179  ENDDO ! of DO l = 1,llm
180
181
182  !
183  !   .......  integration de   q   ......
184  !
185  !$$$      IF( iadv(1).NE.3.AND.iadv(2).NE.3 )    THEN
186  !$$$c
187  !$$$       IF( forward.OR. leapf )  THEN
188  !$$$        DO iq = 1,2
189  !$$$        DO  l = 1,llm
190  !$$$        DO ij = 1,ip1jmp1
191  !$$$        q(ij,l,iq) = ( q(ij,l,iq)*finvmaold(ij,l) + dtvr *dq(ij,l,iq) )/
192  !$$$     $                            finvmasse(ij,l)
193  !$$$        ENDDO
194  !$$$        ENDDO
195  !$$$        ENDDO
196  !$$$       ELSE
197  !$$$         DO iq = 1,2
198  !$$$         DO  l = 1,llm
199  !$$$         DO ij = 1,ip1jmp1
200  !$$$         q( ij,l,iq ) = q( ij,l,iq ) * finvmaold(ij,l) / finvmasse(ij,l)
201  !$$$         ENDDO
202  !$$$         ENDDO
203  !$$$         ENDDO
204  !$$$
205  !$$$       END IF
206  !$$$c
207  !$$$      ENDIF
208
209  if (planet_type.eq."earth") then
210  ! Earth-specific treatment of first 2 tracers (water)
211    DO l = 1, llm
212      DO ij = 1, ip1jmp1
213        deltap(ij,l) =  p(ij,l) - p(ij,l+1)
214      ENDDO
215    ENDDO
216
217    CALL qminimum( q, nq, deltap )
218
219  !
220  !    .....  Calcul de la valeur moyenne, unique  aux poles pour  q .....
221  !
222
223   DO iq = 1, nq
224    DO l = 1, llm
225
226       DO ij = 1, iim
227         qppn(ij) = aire(   ij   ) * q(   ij   ,l,iq)
228         qpps(ij) = aire(ij+ip1jm) * q(ij+ip1jm,l,iq)
229       ENDDO
230         qpn  =  SSUM(iim,qppn,1)/apoln
231         qps  =  SSUM(iim,qpps,1)/apols
232
233       DO ij = 1, iip1
234         q(   ij   ,l,iq)  = qpn
235         q(ij+ip1jm,l,iq)  = qps
236       ENDDO
237
238    ENDDO
239   ENDDO
240
241  ! Ehouarn: forget about finvmaold
242   ! CALL  SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 )
243
244  endif ! of if (planet_type.eq."earth")
245  !
246  !
247  ! .....   FIN  de l'integration  de   q    .......
248
249  !    .................................................................
250
251
252  IF( leapf )  THEN
253     CALL SCOPY (    ip1jmp1 ,  pscr   , 1,   psm1  , 1 )
254     CALL SCOPY ( ip1jmp1*llm, massescr, 1,  massem1, 1 )
255  END IF
256
257  RETURN
258END SUBROUTINE integrd
Note: See TracBrowser for help on using the repository browser.