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

Diff of /trunk/Sources/dyn3d/diverg_gam.f

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

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

Legend:
Removed from v.55  
changed lines
  Added in v.207

  ViewVC Help
Powered by ViewVC 1.1.21