source: LMDZ.3.3/branches/rel-LF/libf/dyn3d/adv_h2o.F @ 546

Last change on this file since 546 was 2, checked in by lmdz, 25 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 3.5 KB
Line 
1      SUBROUTINE adv_h2o (nq,iq,q,w, pbaru, pbarv,dq)
2      IMPLICIT NONE
3
4c=======================================================================
5c
6c   Auteur:  P. Le Van / F.Forget
7c   -------
8c
9c   ********************************************************************
10c   Transport d'un traceur q par shema amont (horiz), moy arithmetique (vert)
11c   (Shema classique pour l'humidite specifique LMD)
12c   ********************************************************************
13c     nq,iq,q,pbaru,pbarv,w sont des arguments d'entree  pour le s-pg ....
14c     dq               sont des arguments de sortie pour le s-pg ....
15c
16c=======================================================================
17
18
19#include "dimensions.h"
20#include "paramet.h"
21#include "logic.h"
22#include "comvert.h"
23
24c   Arguments:
25c   ----------
26      INTEGER nq,iq
27      REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm)
28      REAL q(ip1jmp1,llm,nq), dq( ip1jmp1,llm,nq )
29      REAL w(ip1jmp1,llm)
30
31c   Local:
32c   ------
33
34      INTEGER   l,ij
35
36      REAL qbyv( ip1jm,llm ), qbxu( ip1jmp1,llm )
37      REAL wsur2(ip1jmp1),ww
38      REAL dqh( ip1jmp1,llm)
39
40      EXTERNAL     convflu
41
42c     ----------------------------------------------------------------
43c     --        calcul transport horiz. pour  dq                    --
44c     -                                                              -
45c     -         shema ' amont '  pour l'humidite specifique  q       -
46c     ----------------------------------------------------------------
47c
48      IF( iq.GT.2 )   THEN
49        DO   l = 1, llm
50         DO ij = 1, ip1jmp1
51          dq(ij,l,iq) = 0.
52         ENDDO
53        ENDDO
54            RETURN
55      ENDIF
56
57 
58      IF( forward.OR.leapf )   THEN
59 
60        DO 10 l = 1, llm
61 
62        DO 6  ij     = iip2, ip1jm - 1
63 
64          IF( pbaru(ij,l).GT.0.  )   THEN
65            qbxu( ij,l ) =  pbaru( ij,l )  * q(  ij  ,l,iq)
66          ELSE
67            qbxu( ij,l ) =  pbaru( ij,l )  * q(ij +1 ,l,iq)
68          ENDIF
69
70   6    CONTINUE
71 
72c     ..... correction  pour  qbxu(iip1,j,l)   .....
73c     ...   qbxu(iip1,j,l)= qbxu(1,j,l)  ...
74 
75CDIR$ IVDEP
76        DO  7   ij   = iip1 +iip1, ip1jm, iip1
77        qbxu( ij,l ) = qbxu( ij - iim, l )
78   7    CONTINUE
79 
80        DO  8  ij     = 1, ip1jm
81         IF( pbarv(ij,l).GT.0.  )   THEN
82           qbyv( ij,l ) =  pbarv( ij,l )  * q(ij+iip1, l,iq)
83         ELSE
84           qbyv( ij,l ) =  pbarv( ij,l )  * q(   ij  , l,iq)
85         ENDIF
86   8    CONTINUE
87c
88  10    CONTINUE
89c
90 
91c     stockage dans  dqh de la convergence horiz.du flux d'humidite  .
92c     -------------------------------------------------------------
93c
94                  CALL  convflu(qbxu, qbyv, llm, dqh )
95
96c
97c ---------------------------------------------------------------
98c   .... calcul des termes d'advection vertic.pour q ....
99c              (moyenne arithmetique)
100c ---------------------------------------------------------------
101
102c calcul de  - d( q   * w )/ d(sigma)    qu'on ajoute a  dqh pour calculer dq
103c
104
105      DO 20 l = 1,llmm1
106
107c       preliminaires:
108c
109        DO 11 ij = 1,ip1jmp1
110         wsur2( ij ) = - 0.5 * w( ij,l+1 )
111  11    CONTINUE
112
113
114        DO 12 ij = 1,ip1jmp1
115          ww             = wsur2(ij)   * ( q(ij,l,iq) + q(ij,l+1,iq) )
116          dq (ij, l ,iq) = dqh(ij, l ) -  ww
117          dqh(ij,l+1   ) = dqh(ij,l+1) +  ww
118  12    CONTINUE
119c
120  20  CONTINUE
121c
122c       special dq (ij,llm) (qui n'a pas ete rempli ! )
123c
124        DO  ij = 1,ip1jmp1
125          dq( ij,llm,iq ) = dqh( ij,llm )
126        END DO
127           
128      END IF
129
130      RETURN
131      END
Note: See TracBrowser for help on using the repository browser.