source: LMDZ6/trunk/libf/dyn3dmem/diverg_p.f90 @ 5280

Last change on this file since 5280 was 5272, checked in by abarral, 7 weeks ago

Turn paramet.h into a module

  • 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.8 KB
Line 
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
11  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
12USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
13          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
14IMPLICIT NONE
15  !
16  !  x  et  y  sont des arguments  d'entree pour le s-prog
17  !    div      est  un argument  de sortie pour le s-prog
18  !
19  !
20  !   ---------------------------------------------------------------------
21  !
22  !    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
23  !
24  !   ---------------------------------------------------------------------
25
26
27  INCLUDE "comgeom.h"
28  !
29  !    ..........          variables en arguments    ...................
30  !
31  INTEGER :: klevel
32  REAL :: x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
33  INTEGER :: l,ij
34  !
35  !    ...............     variables  locales   .........................
36
37  REAL :: aiy1( iip1 ) , aiy2( iip1 )
38  REAL :: sumypn,sumyps
39  INTEGER :: ijb,ije
40  !    ...................................................................
41  !
42  EXTERNAL  SSUM
43  REAL :: SSUM
44  !
45  !
46  ijb=ij_begin
47  ije=ij_end
48  if (pole_nord) ijb=ij_begin+iip1
49  if(pole_sud)  ije=ij_end-iip1
50
51!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
52  DO l = 1,klevel
53  !
54    DO  ij = ijb, ije - 1
55     div( ij + 1, l )     = &
56           cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) + &
57           cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
58    ENDDO
59  !
60  ! ....  correction pour  div( 1,j,l)  ......
61  ! ....   div(1,j,l)= div(iip1,j,l) ....
62  !
63  !DIR$ IVDEP
64    DO  ij = ijb,ije,iip1
65     div( ij,l ) = div( ij + iim,l )
66    ENDDO
67  !
68  ! ....  calcul  aux poles  .....
69  !
70    if (pole_nord) then
71      DO  ij  = 1,iim
72       aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
73      ENDDO
74      sumypn = SSUM ( iim,aiy1,1 ) / apoln
75  !
76      DO  ij = 1,iip1
77       div(     ij    , l ) = - sumypn
78      ENDDO
79    endif
80
81   if (pole_sud) then
82      DO  ij  = 1,iim
83       aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
84      ENDDO
85      sumyps = SSUM ( iim,aiy2,1 ) / apols
86  !
87      DO  ij = 1,iip1
88       div( ij + ip1jm, l ) =   sumyps
89      ENDDO
90    endif
91
92
93  END DO
94!$OMP END DO NOWAIT
95  !
96
97  !cc        CALL filtreg( div, jjp1, klevel, 2, 2, .TRUE., 1 )
98
99  !
100!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
101    DO l = 1, klevel
102       DO ij = ijb,ije
103        div(ij,l) = div(ij,l) * unsaire(ij)
104      ENDDO
105    ENDDO
106!$OMP END DO NOWAIT
107  !
108   RETURN
109END SUBROUTINE diverg_p
Note: See TracBrowser for help on using the repository browser.