source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/divergst.f90 @ 5136

Last change on this file since 5136 was 5136, checked in by abarral, 8 weeks ago

Put comgeom.h, comgeom2.h into modules

  • 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: 1.5 KB
RevLine 
[524]1! $Header$
[5099]2
[5123]3SUBROUTINE divergst(klevel, x, y, div)
4  USE lmdz_ssum_scopy, ONLY: ssum
[5136]5  USE lmdz_comgeom
[5123]6
[5105]7  IMPLICIT NONE
8  !
9  ! P. Le Van
10  !
11  !  ******************************************************************
12  !  ... calcule la divergence a tous les niveaux d'1 vecteur de compos. x et y...
13  !       x et y  etant des composantes contravariantes   ...
14  !  ****************************************************************
15  !  x  et  y  sont des arguments  d'entree pour le s-prog
16  !    div      est  un argument  de sortie pour le s-prog
17  !
18  !
19  !   -------------------------------------------------------------------
20  !
[5123]21
[5105]22  INCLUDE "dimensions.h"
23  INCLUDE "paramet.h"
[524]24
[5105]25  INTEGER :: klevel
[5123]26  REAL :: x(ip1jmp1, klevel), y(ip1jm, klevel), div(ip1jmp1, klevel)
27  INTEGER :: ij, l, i
28  REAL :: aiy1(iip1), aiy2(iip1)
29  REAL :: sumypn, sumyps
[5105]30  !
31  !
[5123]32  DO l = 1, klevel
33    !
34    DO ij = iip2, ip1jm - 1
35      div(ij + 1, l) = x(ij + 1, l) - x(ij, l) + y(ij - iim, l) - y(ij + 1, l)
36    END DO
37    !
38    ! ....  correction pour  div( 1,j,l)  ......
39    ! ....   div(1,j,l)= div(iip1,j,l) ....
40    !
41    !DIR$ IVDEP
42    DO ij = iip2, ip1jm, iip1
43      div(ij, l) = div(ij + iim, l)
44    END DO
45    !
46    ! ....  calcul  aux poles  .....
47    !
48    !
49    DO i = 1, iim
50      aiy1(i) = y(i, l)
51      aiy2(i) = y(i + ip1jmi1, l)
52    END DO
53    sumypn = SSUM (iim, aiy1, 1)
54    sumyps = SSUM (iim, aiy2, 1)
55    DO i = 1, iip1
56      div(i, l) = - sumypn / iim
57      div(i + ip1jm, l) = sumyps / iim
58    END DO
59    !
[5105]60  END DO
61  RETURN
62END SUBROUTINE divergst
Note: See TracBrowser for help on using the repository browser.