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

Diff of /trunk/dyn3d/dudv1.f

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

revision 76 by guez, Fri Nov 15 18:45:49 2013 UTC revision 91 by guez, Wed Mar 26 17:18:58 2014 UTC
# Line 1  Line 1 
1  !  module dudv1_m
2  ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/dudv1.F,v 1.1.1.1 2004/05/19 12:53:06 lmdzadmin Exp $  
3  !    IMPLICIT NONE
4        SUBROUTINE dudv1 ( vorpot, pbaru, pbarv, du, dv )  
5        use dimens_m  contains
6        use paramet_m  
7        IMPLICIT NONE    SUBROUTINE dudv1(vorpot, pbaru, pbarv, du, dv)
8  c  
9  c-----------------------------------------------------------------------      ! From LMDZ4/libf/dyn3d/dudv1.F, version 1.1.1.1, 2004/05/19 12:53:06
10  c  
11  c   Auteur:   P. Le Van      ! Author: P. Le Van
12  c   -------  
13  c      ! Objet: calcul du terme de rotation. Ce terme est ajouté à
14  c   Objet:      ! d(ucov)/dt et à d(vcov)/dt.
15  c   ------  
16  c   calcul du terme de  rotation      USE dimens_m, ONLY: iim, jjm, llm
17  c   ce terme est ajoute a  d(ucov)/dt et a d(vcov)/dt  ..      USE paramet_m, ONLY: iip1, iip2, ip1jm, ip1jmp1
18  c   vorpot, pbaru et pbarv sont des arguments d'entree  pour le s-pg ..  
19  c   du  et dv              sont des arguments de sortie pour le s-pg ..      REAL, intent(in):: vorpot(ip1jm, llm)
20  c      REAL, intent(in):: pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
21  c-----------------------------------------------------------------------      real, intent(out):: du(iim + 2: (iim + 1) * jjm, llm), dv(ip1jm, llm)
22    
23        ! Local:
24        REAL vorpot( ip1jm,llm ) ,pbaru( ip1jmp1,llm ) ,      INTEGER l, ij
25       *     pbarv( ip1jm,llm ) ,du( ip1jmp1,llm ) ,dv( ip1jm,llm )  
26        INTEGER  l,ij      !----------------------------------------------------------------------
27  c  
28  c      DO l = 1, llm
29        DO 10 l = 1,llm         DO ij = iip2, ip1jm - 1
30  c            du(ij, l) = 0.125 * (vorpot(ij - iip1, l) + vorpot(ij, l)) &
31        DO 2  ij = iip2, ip1jm - 1                 * (pbarv(ij - iip1, l) + pbarv(ij - iim, l) + pbarv(ij, l) &
32        du( ij,l ) = 0.125 *(  vorpot(ij-iip1, l) + vorpot( ij, l)  ) *                 + pbarv(ij + 1, l))
33       *                    (   pbarv(ij-iip1, l) + pbarv(ij-iim,  l) +         END DO
34       *                        pbarv(   ij  , l) + pbarv(ij+ 1 ,  l)   )  
35     2  CONTINUE         DO ij = 1, ip1jm - 1
36  c            dv(ij + 1, l) = - 0.125 * (vorpot(ij, l) + vorpot(ij + 1, l)) &
37        DO 3 ij = 1, ip1jm - 1                 * (pbaru(ij, l) + pbaru(ij + 1, l) + pbaru(ij + iip1, l) &
38        dv( ij+1,l ) = - 0.125 *(  vorpot(ij, l)  + vorpot(ij+1, l)  ) *                 + pbaru(ij + iip2, l))
39       *                        (   pbaru(ij, l)  +  pbaru(ij+1   , l) +         END DO
40       *                       pbaru(ij+iip1, l)  +  pbaru(ij+iip2, l)  )  
41     3  CONTINUE         ! correction pour dv(1, j, l)
42  c         ! dv(1, j, l) = dv(iip1, j, l)
43  c    .... correction  pour  dv( 1,j,l )  .....         DO ij = 1, ip1jm, iip1
44  c    ....   dv(1,j,l)= dv(iip1,j,l) ....            dv(ij, l) = dv(ij + iim, l)
45  c         END DO
46  CDIR$ IVDEP      END DO
47        DO 4 ij = 1, ip1jm, iip1  
48        dv( ij,l ) = dv( ij + iim, l )    END SUBROUTINE dudv1
49     4  CONTINUE  
50  c  end module dudv1_m
   10  CONTINUE  
       RETURN  
       END  

Legend:
Removed from v.76  
changed lines
  Added in v.91

  ViewVC Help
Powered by ViewVC 1.1.21