source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/diverg_gam.f90 @ 5123

Last change on this file since 5123 was 5123, checked in by abarral, 2 months ago

Correct various minor mistakes from previous commits

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.3 KB
Line 
1
2! $Header$
3
4SUBROUTINE diverg_gam(klevel,cuvscvgam,cvuscugam,unsairegam , &
5        unsapolnga,unsapolsga,  x, y,  div )
6  !
7  ! P. Le Van
8  !
9  !  *********************************************************************
10  !  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
11  ! x et y...
12  !          x et y  etant des composantes covariantes   ...
13  !  *********************************************************************
14  USE lmdz_ssum_scopy, ONLY: ssum
15
16  IMPLICIT NONE
17  !
18  !  x  et  y  sont des arguments  d'entree pour le s-prog
19  !    div      est  un argument  de sortie pour le s-prog
20  !
21  !
22  !   ---------------------------------------------------------------------
23  !
24  !    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
25  !
26  !   ---------------------------------------------------------------------
27  INCLUDE "dimensions.h"
28  INCLUDE "paramet.h"
29  INCLUDE "comgeom.h"
30  !
31  !    ..........          variables en arguments    ...................
32  !
33  INTEGER :: klevel
34  REAL :: x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
35  REAL :: cuvscvgam(ip1jm),cvuscugam(ip1jmp1),unsairegam(ip1jmp1)
36  REAL :: unsapolnga,unsapolsga
37  !
38  !    ...............     variables  locales   .........................
39
40  REAL :: aiy1( iip1 ) , aiy2( iip1 )
41  REAL :: sumypn,sumyps
42  INTEGER :: l,ij
43  !    ...................................................................
44
45  !
46  DO l = 1,klevel
47  !
48    DO  ij = iip2, ip1jm - 1
49     div( ij + 1, l )     = ( &
50           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    ENDDO
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    ENDDO
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    ENDDO
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    ENDDO
76  END DO
77  !
78
79   RETURN
80END SUBROUTINE diverg_gam
Note: See TracBrowser for help on using the repository browser.