/[lmdze]/trunk/dyn3d/integrd.f
ViewVC logotype

Diff of /trunk/dyn3d/integrd.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/dyn3d/integrd.f revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC trunk/dyn3d/integrd.f revision 260 by guez, Tue Mar 6 17:18:33 2018 UTC
# Line 1  Line 1 
1  !  module integrd_m
2  ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/integrd.F,v 1.1.1.1 2004/05/19 12:53:05 lmdzadmin Exp $  
3  !    IMPLICIT NONE
4        SUBROUTINE integrd  
5       $  (  nq,vcovm1,ucovm1,tetam1,psm1,massem1,  contains
6       $     dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis,finvmaold )  
7      SUBROUTINE integrd(vcovm1, ucovm1, tetam1, psm1, massem1, dv, du, dteta, &
8        use dimens_m         dp, vcov, ucov, teta, q, ps, masse, dt, leapf)
9        use paramet_m  
10        use comconst      ! From dyn3d/integrd.F, version 1.1.1.1, 2004/05/19 12:53:05
11        use comvert      ! Author: P. Le Van
12        use logic      ! Objet: incrémentation des tendances dynamiques
13        use comgeom  
14        use serre      USE comgeom, ONLY : aire, aire_2d, apoln, apols
15        use temps      USE dimens_m, ONLY : iim, jjm, llm
16        use advtrac_m      USE disvert_m, ONLY : ap, bp
17        use pression_m, only: pression      use massdair_m, only: massdair
18        use nr_util, only: assert
19        IMPLICIT NONE      USE paramet_m, ONLY : iip1, iip2, ip1jm, llmp1
20        use qminimum_m, only: qminimum
21    
22  c=======================================================================      REAL vcovm1(ip1jm, llm), ucovm1((iim + 1) * (jjm + 1), llm)
23  c      REAL, intent(inout):: tetam1(iim + 1, jjm + 1, llm)
24  c   Auteur:  P. Le Van      REAL, intent(inout):: psm1((iim + 1) * (jjm + 1))
25  c   -------      real, intent(inout):: massem1(iim + 1, jjm + 1, llm)
26  c      REAL, intent(in):: dv(ip1jm, llm), du((iim + 1) * (jjm + 1), llm)
27  c   objet:      REAL, intent(in):: dteta(iim + 1, jjm + 1, llm), dp((iim + 1) * (jjm + 1))
28  c   ------      REAL, intent(inout):: vcov(ip1jm, llm), ucov((iim + 1) * (jjm + 1), llm)
29  c      real, intent(inout):: teta(iim + 1, jjm + 1, llm)
30  c   Incrementation des tendances dynamiques      REAL q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nq)
31  c      REAL, intent(inout):: ps((iim + 1) * (jjm + 1))
32  c=======================================================================      REAL, intent(inout):: masse(iim + 1, jjm + 1, llm)
33  c-----------------------------------------------------------------------      real, intent(in):: dt ! time step, in s
34  c   Declarations:      LOGICAL, INTENT (IN) :: leapf
35  c   -------------  
36        ! Local:
37        REAL finvmaold(iim + 1, jjm + 1, llm)
38  c   Arguments:      INTEGER nq
39  c   ----------      REAL vscr(ip1jm), uscr((iim + 1) * (jjm + 1)), hscr(iim + 1, jjm + 1)
40        real pscr((iim + 1) * (jjm + 1))
41        INTEGER nq      REAL p((iim + 1) * (jjm + 1), llmp1)
42        REAL tpn, tps, tppn(iim), tpps(iim)
43        REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)      REAL deltap((iim + 1) * (jjm + 1), llm)
44        REAL q(ip1jmp1,llm,nq)      INTEGER l, ij, iq
45        REAL ps(ip1jmp1),masse(ip1jmp1,llm),phis(ip1jmp1)  
46        !-----------------------------------------------------------------------
47        REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)  
48        REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1),massem1(ip1jmp1,llm)      call assert(size(q, 1) == iim + 1, size(q, 2) == jjm + 1, &
49             size(q, 3) == llm, "integrd")
50        REAL dv(ip1jm,llm),du(ip1jmp1,llm)      nq = size(q, 4)
51        REAL dteta(ip1jmp1,llm),dp(ip1jmp1)  
52        REAL dq(ip1jmp1,llm,nq), finvmaold(ip1jmp1,llm)      DO l = 1, llm
53           DO ij = 1, iip1
54  c   Local:            ucov(ij, l) = 0.
55  c   ------            ucov(ij+ip1jm, l) = 0.
56              uscr(ij) = 0.
57        REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1)            uscr(ij+ip1jm) = 0.
58        REAL massescr( ip1jmp1,llm ), finvmasse(ip1jmp1,llm)         END DO
59        REAL p(ip1jmp1,llmp1)      END DO
60        REAL tpn,tps,tppn(iim),tpps(iim)  
61        REAL qpn,qps,qppn(iim),qpps(iim)      ! Integration de ps :
62        REAL deltap( ip1jmp1,llm )  
63        pscr = ps
64        INTEGER  l,ij,iq      ps = psm1 + dt * dp
65    
66        REAL SSUM      DO ij = 1, (iim + 1) * (jjm + 1)
67           IF (ps(ij) < 0.) THEN
68  c-----------------------------------------------------------------------            PRINT *, 'integrd: au point ij = ', ij, &
69                   ', negative surface pressure ', ps(ij)
70        DO  l = 1,llm            STOP 1
71          DO  ij = 1,iip1         END IF
72           ucov(    ij    , l) = 0.      END DO
73           ucov( ij +ip1jm, l) = 0.  
74           uscr(     ij      ) = 0.      DO ij = 1, iim
75           uscr( ij +ip1jm   ) = 0.         tppn(ij) = aire(ij) * ps(ij)
         ENDDO  
       ENDDO  
   
   
 c    ............    integration  de       ps         ..............  
   
       CALL SCOPY(ip1jmp1*llm, masse, 1, massescr, 1)  
   
       DO 2 ij = 1,ip1jmp1  
        pscr (ij)    = ps(ij)  
        ps (ij)      = psm1(ij) + dt * dp(ij)  
    2  CONTINUE  
 c  
       DO ij = 1,ip1jmp1  
         IF( ps(ij).LT.0. ) THEN  
          PRINT *,' Au point ij = ',ij, ' , pression sol neg. ', ps(ij)  
          STOP 'integrd'  
         ENDIF  
       ENDDO  
 c  
       DO  ij    = 1, iim  
        tppn(ij) = aire(   ij   ) * ps(  ij    )  
76         tpps(ij) = aire(ij+ip1jm) * ps(ij+ip1jm)         tpps(ij) = aire(ij+ip1jm) * ps(ij+ip1jm)
77        ENDDO      END DO
78         tpn      = SSUM(iim,tppn,1)/apoln      tpn = sum(tppn)/apoln
79         tps      = SSUM(iim,tpps,1)/apols      tps = sum(tpps)/apols
80        DO ij   = 1, iip1      DO ij = 1, iip1
81         ps(   ij   )  = tpn         ps(ij) = tpn
82         ps(ij+ip1jm)  = tps         ps(ij+ip1jm) = tps
83        ENDDO      END DO
84  c  
85  c  ... Calcul  de la nouvelle masse d'air au dernier temps integre t+1 ...      ! Calcul de la nouvelle masse d'air au dernier temps integre t+1
86  c  
87        CALL pression ( ip1jmp1, ap, bp, ps, p )      forall (l = 1: llm + 1) p(:, l) = ap(l) + bp(l) * ps
88        CALL massdair (     p  , masse         )      CALL massdair(p, finvmaold)
89    
90        CALL   SCOPY( ijp1llm  , masse, 1, finvmasse,  1      )      ! integration de ucov, vcov, h
91        CALL filtreg( finvmasse, jjp1, llm, -2, 2, .TRUE., 1  )  
92  c      DO l = 1, llm
93           DO ij = iip2, ip1jm
94  c    ............   integration  de  ucov, vcov,  h     ..............            uscr(ij) = ucov(ij, l)
95              ucov(ij, l) = ucovm1(ij, l) + dt * du(ij, l)
96        DO 10 l = 1,llm         END DO
97    
98        DO 4 ij = iip2,ip1jm         DO ij = 1, ip1jm
99        uscr( ij )   =  ucov( ij,l )            vscr(ij) = vcov(ij, l)
100        ucov( ij,l ) = ucovm1( ij,l ) + dt * du( ij,l )            vcov(ij, l) = vcovm1(ij, l) + dt * dv(ij, l)
101     4  CONTINUE         END DO
102    
103        DO 5 ij = 1,ip1jm         hscr = teta(:, :, l)
104        vscr( ij )   =  vcov( ij,l )         teta(:, :, l) = tetam1(:, :, l) * massem1(:, :, l) / finvmaold(:, :, l) &
105        vcov( ij,l ) = vcovm1( ij,l ) + dt * dv( ij,l )              + dt * dteta(:, :, l) / finvmaold(:, :, l)
106     5  CONTINUE  
107           ! Calcul de la valeur moyenne, unique aux poles pour teta
108        DO 6 ij = 1,ip1jmp1         teta(:, 1, l) = sum(aire_2d(:iim, 1) * teta(:iim, 1, l)) / apoln
109        hscr( ij )    =  teta(ij,l)         teta(:, jjm + 1, l) = sum(aire_2d(:iim, jjm + 1) &
110        teta ( ij,l ) = tetam1(ij,l) *  massem1(ij,l) / masse(ij,l)              * teta(:iim, jjm + 1, l)) / apols
111       $                + dt * dteta(ij,l) / masse(ij,l)  
112     6  CONTINUE         IF (leapf) THEN
113              ucovm1(:, l)  =uscr
114  c   ....  Calcul de la valeur moyenne, unique  aux poles pour  teta    ......            vcovm1(:, l) = vscr
115  c            tetam1(:, :, l) = hscr
116  c         END IF
117        DO  ij   = 1, iim      END DO
118          tppn(ij) = aire(   ij   ) * teta(  ij    ,l)  
119          tpps(ij) = aire(ij+ip1jm) * teta(ij+ip1jm,l)      DO l = 1, llm
120        ENDDO         DO ij = 1, (iim + 1) * (jjm + 1)
121          tpn      = SSUM(iim,tppn,1)/apoln            deltap(ij, l) = p(ij, l) - p(ij, l+1)
122          tps      = SSUM(iim,tpps,1)/apols         END DO
123        END DO
124        DO ij   = 1, iip1  
125          teta(   ij   ,l)  = tpn      CALL qminimum(q, nq, deltap)
126          teta(ij+ip1jm,l)  = tps  
127        ENDDO      ! Calcul de la valeur moyenne, unique aux poles pour q
128  c      DO iq = 1, nq
129           DO l = 1, llm
130        IF(leapf)  THEN            q(:, 1, l, iq) = sum(aire_2d(:iim, 1) * q(:iim, 1, l, iq)) / apoln
131           CALL SCOPY ( ip1jmp1, uscr(1), 1, ucovm1(1, l), 1 )            q(:, jjm + 1, l, iq) = sum(aire_2d(:iim, jjm + 1) &
132           CALL SCOPY (   ip1jm, vscr(1), 1, vcovm1(1, l), 1 )                 * q(:iim, jjm + 1, l, iq)) / apols
133           CALL SCOPY ( ip1jmp1, hscr(1), 1, tetam1(1, l), 1 )         END DO
134        END IF      END DO
135    
136    10  CONTINUE      ! Fin de l'integration de q
137    
138        IF (leapf) THEN
139  c         psm1 = pscr
140  c   .......  integration de   q   ......         massem1 = masse
141  c      END IF
142  c$$$      IF( iadv(1).NE.3.AND.iadv(2).NE.3 )    THEN  
143  c$$$c      masse = finvmaold
144  c$$$       IF( forward. OR . leapf )  THEN  
145  c$$$        DO iq = 1,2    END SUBROUTINE integrd
 c$$$        DO  l = 1,llm  
 c$$$        DO ij = 1,ip1jmp1  
 c$$$        q(ij,l,iq) = ( q(ij,l,iq)*finvmaold(ij,l) + dtvr *dq(ij,l,iq) )/  
 c$$$     $                            finvmasse(ij,l)  
 c$$$        ENDDO  
 c$$$        ENDDO  
 c$$$        ENDDO  
 c$$$       ELSE  
 c$$$         DO iq = 1,2  
 c$$$         DO  l = 1,llm  
 c$$$         DO ij = 1,ip1jmp1  
 c$$$         q( ij,l,iq ) = q( ij,l,iq ) * finvmaold(ij,l) / finvmasse(ij,l)  
 c$$$         ENDDO  
 c$$$         ENDDO  
 c$$$         ENDDO  
 c$$$  
 c$$$       END IF  
 c$$$c  
 c$$$      ENDIF  
   
          DO l = 1, llm  
           DO ij = 1, ip1jmp1  
            deltap(ij,l) =  p(ij,l) - p(ij,l+1)  
           ENDDO  
          ENDDO  
   
          CALL qminimum( q, nq, deltap )  
 c  
 c    .....  Calcul de la valeur moyenne, unique  aux poles pour  q .....  
 c  
   
       DO iq = 1, nq  
         DO l = 1, llm  
   
            DO ij = 1, iim  
              qppn(ij) = aire(   ij   ) * q(   ij   ,l,iq)  
              qpps(ij) = aire(ij+ip1jm) * q(ij+ip1jm,l,iq)  
            ENDDO  
              qpn  =  SSUM(iim,qppn,1)/apoln  
              qps  =  SSUM(iim,qpps,1)/apols  
   
            DO ij = 1, iip1  
              q(   ij   ,l,iq)  = qpn  
              q(ij+ip1jm,l,iq)  = qps  
            ENDDO  
   
         ENDDO  
       ENDDO  
   
   
          CALL  SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 )  
 c  
 c  
 c     .....   FIN  de l'integration  de   q    .......  
   
 15    continue  
   
 c    .................................................................  
   
   
       IF( leapf )  THEN  
          CALL SCOPY (    ip1jmp1 ,  pscr   , 1,   psm1  , 1 )  
          CALL SCOPY ( ip1jmp1*llm, massescr, 1,  massem1, 1 )  
       END IF  
146    
147        RETURN  end module integrd_m
       END  

Legend:
Removed from v.3  
changed lines
  Added in v.260

  ViewVC Help
Powered by ViewVC 1.1.21