source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/divergf_loc.f90 @ 5153

Last change on this file since 5153 was 5140, checked in by abarral, 8 weeks ago

Put comsoil.h, conema3.h, cvflag.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
File size: 2.5 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 lmdz_filtreg_p
12  USE lmdz_ssum_scopy, ONLY: ssum
13  USE lmdz_comgeom
14
15  IMPLICIT 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  INCLUDE "dimensions.h"
21  INCLUDE "paramet.h"
22  !
23  !    ..........          variables en arguments    ...................
24  !
25  INTEGER :: klevel
26  REAL :: x( ijb_u:ije_u,klevel ),y( ijb_v:ije_v,klevel )
27  REAL :: div( ijb_u:ije_u,klevel )
28  INTEGER :: l,ij
29  !
30  !    ...............     variables  locales   .........................
31
32  REAL :: aiy1( iip1 ) , aiy2( iip1 )
33  REAL :: sumypn,sumyps
34  !    ...................................................................
35  INTEGER :: ijb,ije,jjb,jje
36  !
37  !
38  ijb=ij_begin
39  ije=ij_end
40  IF (pole_nord) ijb=ij_begin+iip1
41  IF(pole_sud)  ije=ij_end-iip1
42
43!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
44  DO l = 1,klevel
45  !
46    DO  ij = ijb, ije - 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  !
53  ! ....  correction pour  div( 1,j,l)  ......
54  ! ....   div(1,j,l)= div(iip1,j,l) ....
55  !
56  !DIR$ IVDEP
57    DO  ij = ijb,ije,iip1
58     div( ij,l ) = div( ij + iim,l )
59    ENDDO
60  !
61  ! ....  calcul  aux poles  .....
62  !
63    IF (pole_nord) THEN
64      DO  ij  = 1,iim
65       aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
66      ENDDO
67      sumypn = SSUM ( iim,aiy1,1 ) / apoln
68
69  !
70      DO  ij = 1,iip1
71       div(     ij    , l ) = - sumypn
72      ENDDO
73
74    endif
75
76    IF (pole_sud) THEN
77      DO  ij  = 1,iim
78       aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
79      ENDDO
80      sumyps = SSUM ( iim,aiy2,1 ) / apols
81  !
82      DO  ij = 1,iip1
83       div( ij + ip1jm, l ) =   sumyps
84      ENDDO
85
86    endif
87
88  END DO
89!$OMP END DO NOWAIT
90
91  !
92    jjb=jj_begin
93    jje=jj_end
94    IF (pole_sud) jje=jj_end-1
95
96    CALL filtreg_p( div,jjb_u,jje_u,jjb,jje, jjp1, &
97          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
109END SUBROUTINE divergf_loc
Note: See TracBrowser for help on using the repository browser.