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

Diff of /trunk/dyn3d/diverg_gam.f90

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

revision 335 by guez, Thu Jun 13 14:40:06 2019 UTC revision 336 by guez, Thu Sep 12 21:34:37 2019 UTC
# Line 7  contains Line 7  contains
7    SUBROUTINE diverg_gam(klevel, cuvscvgam, cvuscugam, unsairegam, unsapolnga, &    SUBROUTINE diverg_gam(klevel, cuvscvgam, cvuscugam, unsairegam, unsapolnga, &
8         unsapolsga, x, y, div)         unsapolsga, x, y, div)
9    
10      ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/diverg_gam.F,v 1.1.1.1 2004/05/19      ! From LMDZ4/libf/dyn3d/diverg_gam.F, version 1.1.1.1 2004/05/19
11      ! 12:53:05 lmdzadmin Exp $      ! 12:53:05
12    
13      ! P. Le Van      ! Author: P. Le Van
14    
15      ! *********************************************************************      ! Calcule la divergence \`a tous les niveaux d'un vecteur de
16      ! ... calcule la divergence a tous les niveaux d'1 vecteur de compos.      ! composantes covariantes x et y.
     ! x et y...  
     ! x et y  etant des composantes covariantes   ...  
     ! *********************************************************************  
     USE dimensions  
     USE paramet_m  
     USE comgeom  
   
     ! x  et  y  sont des arguments  d'entree pour le s-prog  
     ! div      est  un argument  de sortie pour le s-prog  
17    
18        USE dimensions, only: iim
19        USE paramet_m, only: ip1jmp1, ip1jm, iip1, iip2, ip1jmi1
20    
21      ! ---------------------------------------------------------------------      ! div      est  un argument  de sortie pour le s-prog
22    
23      ! ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .      ! ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
24    
# Line 34  contains Line 27  contains
27      ! ..........          variables en arguments    ...................      ! ..........          variables en arguments    ...................
28    
29      INTEGER, INTENT (IN) :: klevel      INTEGER, INTENT (IN) :: klevel
     REAL x(ip1jmp1, klevel), y(ip1jm, klevel), div(ip1jmp1, klevel)  
30      REAL cuvscvgam(ip1jm), cvuscugam(ip1jmp1), unsairegam(ip1jmp1)      REAL cuvscvgam(ip1jm), cvuscugam(ip1jmp1), unsairegam(ip1jmp1)
31      REAL unsapolnga, unsapolsga      REAL unsapolnga, unsapolsga
32        REAL, intent(in):: x(ip1jmp1, klevel), y(ip1jm, klevel)
33        real div(ip1jmp1, klevel)
34    
35      ! ...............     variables  locales   .........................      ! ...............     variables  locales   .........................
36    
37      REAL aiy1(iip1), aiy2(iip1)      REAL aiy1(iip1), aiy2(iip1)
38      REAL sumypn, sumyps      REAL sumypn, sumyps
39      INTEGER l, ij      INTEGER l, ij
     ! ...................................................................  
   
     REAL ssum  
40    
41        ! ...................................................................
42    
43      DO l = 1, klevel      DO l = 1, klevel
44    
# Line 70  contains Line 62  contains
62            aiy1(ij) = cuvscvgam(ij)*y(ij, l)            aiy1(ij) = cuvscvgam(ij)*y(ij, l)
63            aiy2(ij) = cuvscvgam(ij+ip1jmi1)*y(ij+ip1jmi1, l)            aiy2(ij) = cuvscvgam(ij+ip1jmi1)*y(ij+ip1jmi1, l)
64         END DO         END DO
65         sumypn = ssum(iim, aiy1, 1)*unsapolnga         sumypn = sum(aiy1(:iim)) * unsapolnga
66         sumyps = ssum(iim, aiy2, 1)*unsapolsga         sumyps = sum(aiy2(:iim)) * unsapolsga
67    
68         DO ij = 1, iip1         DO ij = 1, iip1
69            div(ij, l) = -sumypn            div(ij, l) = -sumypn

Legend:
Removed from v.335  
changed lines
  Added in v.336

  ViewVC Help
Powered by ViewVC 1.1.21