source: LMDZ6/trunk/libf/dyn3dmem/divergf_loc.f90 @ 5279

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