source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/diverg_p.f90 @ 5133

Last change on this file since 5133 was 5123, checked in by abarral, 5 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
File size: 2.6 KB
RevLine 
[5105]1SUBROUTINE diverg_p(klevel,x,y,div)
2  !
3  ! P. Le Van
4  !
5  !  *********************************************************************
6  !  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
7  ! x et y...
8  !          x et y  etant des composantes covariantes   ...
9  !  *********************************************************************
10  USE parallel_lmdz
[5123]11  USE lmdz_ssum_scopy, ONLY: ssum
12
[5105]13  IMPLICIT NONE
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  !
21  !    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
22  !
23  !   ---------------------------------------------------------------------
24  INCLUDE "dimensions.h"
25  INCLUDE "paramet.h"
26  INCLUDE "comgeom.h"
27  !
28  !    ..........          variables en arguments    ...................
29  !
30  INTEGER :: klevel
31  REAL :: x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
32  INTEGER :: l,ij
33  !
34  !    ...............     variables  locales   .........................
[1632]35
[5105]36  REAL :: aiy1( iip1 ) , aiy2( iip1 )
37  REAL :: sumypn,sumyps
38  INTEGER :: ijb,ije
39  !    ...................................................................
40  !
41  !
42  ijb=ij_begin
43  ije=ij_end
[5117]44  IF (pole_nord) ijb=ij_begin+iip1
[5116]45  IF(pole_sud)  ije=ij_end-iip1
[1632]46
[5105]47!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
48  DO l = 1,klevel
49  !
50    DO  ij = ijb, ije - 1
51     div( ij + 1, l )     = &
52           cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) + &
53           cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
54    ENDDO
55  !
56  ! ....  correction pour  div( 1,j,l)  ......
57  ! ....   div(1,j,l)= div(iip1,j,l) ....
58  !
59  !DIR$ IVDEP
60    DO  ij = ijb,ije,iip1
61     div( ij,l ) = div( ij + iim,l )
62    ENDDO
63  !
64  ! ....  calcul  aux poles  .....
65  !
[5117]66    IF (pole_nord) THEN
[5105]67      DO  ij  = 1,iim
68       aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
69      ENDDO
70      sumypn = SSUM ( iim,aiy1,1 ) / apoln
71  !
72      DO  ij = 1,iip1
73       div(     ij    , l ) = - sumypn
74      ENDDO
75    endif
[1632]76
[5117]77   IF (pole_sud) THEN
[5105]78      DO  ij  = 1,iim
79       aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
80      ENDDO
81      sumyps = SSUM ( iim,aiy2,1 ) / apols
82  !
83      DO  ij = 1,iip1
84       div( ij + ip1jm, l ) =   sumyps
85      ENDDO
86    endif
[1632]87
[5105]88
89  END DO
90!$OMP END DO NOWAIT
91  !
92
93  !cc        CALL filtreg( div, jjp1, klevel, 2, 2, .TRUE., 1 )
94
95  !
96!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
97    DO l = 1, klevel
98       DO ij = ijb,ije
99        div(ij,l) = div(ij,l) * unsaire(ij)
100      ENDDO
101    ENDDO
102!$OMP END DO NOWAIT
103  !
104
105END SUBROUTINE diverg_p
Note: See TracBrowser for help on using the repository browser.