source: LMDZ6/trunk/libf/dyn3d_common/diverg.f90 @ 5310

Last change on this file since 5310 was 5298, checked in by abarral, 9 days ago

Turn planete.h comsoil.h into module
Remove obsolete message related to /scratch/ common

  • 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.0 KB
Line 
1!
2! $Header$
3!
4SUBROUTINE diverg(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  !  *********************************************************************
13  USE comgeom_mod_h
14  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
15USE paramet_mod_h
16IMPLICIT 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  !    ..........          variables en arguments    ...................
25  !
26  INTEGER :: klevel
27  REAL :: x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
28  INTEGER :: l,ij
29  !
30  !    ...............     variables  locales   .........................
31
32  REAL :: aiy1( iip1 ) , aiy2( iip1 )
33  REAL :: sumypn,sumyps
34  !    ...................................................................
35  !
36  REAL :: SSUM
37  !
38  !
39  DO l = 1,klevel
40  !
41    DO  ij = iip2, ip1jm - 1
42     div( ij + 1, l )     = &
43           cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) + &
44           cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
45    ENDDO
46  !
47  ! ....  correction pour  div( 1,j,l)  ......
48  ! ....   div(1,j,l)= div(iip1,j,l) ....
49  !
50  !DIR$ IVDEP
51    DO  ij = iip2,ip1jm,iip1
52     div( ij,l ) = div( ij + iim,l )
53    ENDDO
54  !
55  ! ....  calcul  aux poles  .....
56  !
57    DO  ij  = 1,iim
58     aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
59     aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
60    ENDDO
61    sumypn = SSUM ( iim,aiy1,1 ) / apoln
62    sumyps = SSUM ( iim,aiy2,1 ) / apols
63  !
64    DO  ij = 1,iip1
65     div(     ij    , l ) = - sumypn
66     div( ij + ip1jm, l ) =   sumyps
67    ENDDO
68  END DO
69  !
70
71  !cc        CALL filtreg( div, jjp1, klevel, 2, 2, .TRUE., 1 )
72
73  !
74    DO l = 1, klevel
75       DO ij = iip2,ip1jm
76        div(ij,l) = div(ij,l) * unsaire(ij)
77      ENDDO
78    ENDDO
79  !
80   RETURN
81END SUBROUTINE diverg
Note: See TracBrowser for help on using the repository browser.