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

Diff of /trunk/dyn3d/diverg_gam.f

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

trunk/dyn3d/diverg_gam.f revision 76 by guez, Fri Nov 15 18:45:49 2013 UTC trunk/dyn3d/diverg_gam.f90 revision 81 by guez, Wed Mar 5 14:38:41 2014 UTC
# Line 1  Line 1 
 !  
 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/diverg_gam.F,v 1.1.1.1 2004/05/19 12:53:05 lmdzadmin Exp $  
 !  
       SUBROUTINE diverg_gam(klevel,cuvscvgam,cvuscugam,unsairegam ,  
      *                       unsapolnga,unsapolsga,  x, y,  div )  
 c  
 c     P. Le Van  
 c  
 c  *********************************************************************  
 c  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.  
 c     x et y...  
 c              x et y  etant des composantes covariantes   ...  
 c  *********************************************************************  
       use dimens_m  
       use paramet_m  
       use comgeom  
       IMPLICIT NONE  
 c  
 c      x  et  y  sont des arguments  d'entree pour le s-prog  
 c        div      est  un argument  de sortie pour le s-prog  
 c  
 c  
 c   ---------------------------------------------------------------------  
 c  
 c    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .  
 c  
 c   ---------------------------------------------------------------------  
 c  
 c    ..........          variables en arguments    ...................  
 c  
       INTEGER, intent(in):: klevel  
       REAL x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )  
       REAL cuvscvgam(ip1jm),cvuscugam(ip1jmp1),unsairegam(ip1jmp1)  
       REAL unsapolnga,unsapolsga  
 c  
 c    ...............     variables  locales   .........................  
   
       REAL aiy1( iip1 ) , aiy2( iip1 )  
       REAL sumypn,sumyps  
       INTEGER   l,ij  
 c    ...................................................................  
 c  
       REAL      SSUM  
 c  
 c  
       DO 10 l = 1,klevel  
 c  
         DO  ij = iip2, ip1jm - 1  
          div( ij + 1, l )     = (    
      *  cvuscugam( ij+1 ) * x( ij+1,l ) - cvuscugam( ij ) * x( ij , l) +  
      *  cuvscvgam(ij-iim) * y(ij-iim,l) - cuvscvgam(ij+1) * y(ij+1,l) )*  
      *         unsairegam( ij+1 )  
         ENDDO  
 c  
 c     ....  correction pour  div( 1,j,l)  ......  
 c     ....   div(1,j,l)= div(iip1,j,l) ....  
 c  
 CDIR$ IVDEP  
         DO  ij = iip2,ip1jm,iip1  
          div( ij,l ) = div( ij + iim,l )  
         ENDDO  
 c  
 c     ....  calcul  aux poles  .....  
 c  
         DO  ij  = 1,iim  
          aiy1(ij) =    cuvscvgam(    ij       ) * y(     ij     , l )  
          aiy2(ij) =    cuvscvgam( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )  
         ENDDO  
         sumypn = SSUM ( iim,aiy1,1 ) * unsapolnga  
         sumyps = SSUM ( iim,aiy2,1 ) * unsapolsga  
 c  
         DO  ij = 1,iip1  
          div(     ij    , l ) = - sumypn  
          div( ij + ip1jm, l ) =   sumyps  
         ENDDO  
   10  CONTINUE  
 c  
1    
2         RETURN  ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/diverg_gam.F,v 1.1.1.1 2004/05/19
3         END  ! 12:53:05 lmdzadmin Exp $
4    
5    SUBROUTINE diverg_gam(klevel, cuvscvgam, cvuscugam, unsairegam, unsapolnga, &
6        unsapolsga, x, y, div)
7    
8      ! P. Le Van
9    
10      ! *********************************************************************
11      ! ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
12      ! x et y...
13      ! x et y  etant des composantes covariantes   ...
14      ! *********************************************************************
15      USE dimens_m
16      USE paramet_m
17      USE comgeom
18      IMPLICIT NONE
19    
20      ! x  et  y  sont des arguments  d'entree pour le s-prog
21      ! div      est  un argument  de sortie pour le s-prog
22    
23    
24      ! ---------------------------------------------------------------------
25    
26      ! ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
27    
28      ! ---------------------------------------------------------------------
29    
30      ! ..........          variables en arguments    ...................
31    
32      INTEGER, INTENT (IN) :: klevel
33      REAL x(ip1jmp1, klevel), y(ip1jm, klevel), div(ip1jmp1, klevel)
34      REAL cuvscvgam(ip1jm), cvuscugam(ip1jmp1), unsairegam(ip1jmp1)
35      REAL unsapolnga, unsapolsga
36    
37      ! ...............     variables  locales   .........................
38    
39      REAL aiy1(iip1), aiy2(iip1)
40      REAL sumypn, sumyps
41      INTEGER l, ij
42      ! ...................................................................
43    
44      REAL ssum
45    
46    
47      DO l = 1, klevel
48    
49        DO ij = iip2, ip1jm - 1
50          div(ij+1, l) = (cvuscugam(ij+1)*x(ij+1,l)-cvuscugam(ij)*x(ij,l)+ &
51            cuvscvgam(ij-iim)*y(ij-iim,l)-cuvscvgam(ij+1)*y(ij+1,l))* &
52            unsairegam(ij+1)
53        END DO
54    
55        ! ....  correction pour  div( 1,j,l)  ......
56        ! ....   div(1,j,l)= div(iip1,j,l) ....
57    
58        ! DIR$ IVDEP
59        DO ij = iip2, ip1jm, iip1
60          div(ij, l) = div(ij+iim, l)
61        END DO
62    
63        ! ....  calcul  aux poles  .....
64    
65        DO ij = 1, iim
66          aiy1(ij) = cuvscvgam(ij)*y(ij, l)
67          aiy2(ij) = cuvscvgam(ij+ip1jmi1)*y(ij+ip1jmi1, l)
68        END DO
69        sumypn = ssum(iim, aiy1, 1)*unsapolnga
70        sumyps = ssum(iim, aiy2, 1)*unsapolsga
71    
72        DO ij = 1, iip1
73          div(ij, l) = -sumypn
74          div(ij+ip1jm, l) = sumyps
75        END DO
76      END DO
77    
78    
79      RETURN
80    END SUBROUTINE diverg_gam

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

  ViewVC Help
Powered by ViewVC 1.1.21