source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/divergf.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: 2.3 KB
RevLine 
[5099]1
[524]2! $Header$
[5099]3
[5105]4SUBROUTINE divergf(klevel,x,y,div)
5  !
6  ! P. Le Van
7  !
8  !  *********************************************************************
9  !  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
10  ! x et y...
11  !          x et y  etant des composantes covariantes   ...
12  !  *********************************************************************
[5106]13  USE lmdz_filtreg, ONLY: filtreg
[5123]14  USE lmdz_ssum_scopy, ONLY: ssum
[5136]15  USE lmdz_comgeom
[5123]16
[5105]17  IMPLICIT NONE
18  !
19  !  x  et  y  sont des arguments  d'entree pour le s-prog
20  !    div      est  un argument  de sortie pour le s-prog
21  !
22  !
23  !   ---------------------------------------------------------------------
24  !
25  !    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
26  !
27  !   ---------------------------------------------------------------------
28  INCLUDE "dimensions.h"
29  INCLUDE "paramet.h"
30  !
31  !    ..........          variables en arguments    ...................
32  !
33  INTEGER :: klevel
34  REAL :: x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
35  INTEGER :: l,ij
36  !
37  !    ...............     variables  locales   .........................
[524]38
[5105]39  REAL :: aiy1( iip1 ) , aiy2( iip1 )
40  REAL :: sumypn,sumyps
41  !    ...................................................................
[5123]42
[5105]43  !
44  DO l = 1,klevel
45  !
46    DO  ij = iip2, ip1jm - 1
47     div( ij + 1, l )     = &
48           cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) + &
49           cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
50    ENDDO
51  !
52  ! ....  correction pour  div( 1,j,l)  ......
53  ! ....   div(1,j,l)= div(iip1,j,l) ....
54  !
55  !DIR$ IVDEP
56    DO  ij = iip2,ip1jm,iip1
57     div( ij,l ) = div( ij + iim,l )
58    ENDDO
59  !
60  ! ....  calcul  aux poles  .....
61  !
62    DO  ij  = 1,iim
63     aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
64     aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
65    ENDDO
66    sumypn = SSUM ( iim,aiy1,1 ) / apoln
67    sumyps = SSUM ( iim,aiy2,1 ) / apols
68  !
69    DO  ij = 1,iip1
70     div(     ij    , l ) = - sumypn
71     div( ij + ip1jm, l ) =   sumyps
72    ENDDO
73  END DO
74  !
[524]75
[5105]76    CALL filtreg( div, jjp1, klevel, 2, 2, .TRUE., 1 )
77
78  !
79    DO l = 1, klevel
80       DO ij = iip2,ip1jm
81        div(ij,l) = div(ij,l) * unsaire(ij)
82      ENDDO
83    ENDDO
84  !
85   RETURN
86END SUBROUTINE divergf
Note: See TracBrowser for help on using the repository browser.