source: trunk/LMDZ.MARS/libf/dyn3d/adv_h2o.F @ 1766

Last change on this file since 1766 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

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