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

Last change on this file since 5403 was 5298, checked in by abarral, 6 weeks 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
File size: 2.6 KB
RevLine 
[5246]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  !  *********************************************************************
[5281]10  USE comgeom_mod_h
[5246]11  USE parallel_lmdz
12  USE mod_filtreg_p
[5271]13  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
[5285]14USE paramet_mod_h
[5271]15IMPLICIT NONE
[5246]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  !
[5271]21
[5272]22
[5298]23
[5246]24  !
25  !    ..........          variables en arguments    ...................
26  !
27  INTEGER :: klevel
28  REAL :: x( ijb_u:ije_u,klevel ),y( ijb_v:ije_v,klevel )
29  REAL :: div( ijb_u:ije_u,klevel )
30  INTEGER :: l,ij
31  !
32  !    ...............     variables  locales   .........................
[1632]33
[5246]34  REAL :: aiy1( iip1 ) , aiy2( iip1 )
35  REAL :: sumypn,sumyps
36  !    ...................................................................
37  !
38  EXTERNAL  SSUM
39  REAL :: SSUM
40  INTEGER :: ijb,ije,jjb,jje
41  !
42  !
43  ijb=ij_begin
44  ije=ij_end
45  if (pole_nord) ijb=ij_begin+iip1
46  if(pole_sud)  ije=ij_end-iip1
[1632]47
[5246]48!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
49  DO l = 1,klevel
50  !
51    DO  ij = ijb, ije - 1
52     div( ij + 1, l )     = &
53           cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) + &
54           cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
55    ENDDO
[1632]56
[5246]57  !
58  ! ....  correction pour  div( 1,j,l)  ......
59  ! ....   div(1,j,l)= div(iip1,j,l) ....
60  !
61  !DIR$ IVDEP
62    DO  ij = ijb,ije,iip1
63     div( ij,l ) = div( ij + iim,l )
64    ENDDO
65  !
66  ! ....  calcul  aux poles  .....
67  !
68    if (pole_nord) then
[1632]69
[5246]70      DO  ij  = 1,iim
71       aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
72      ENDDO
73      sumypn = SSUM ( iim,aiy1,1 ) / apoln
[1632]74
[5246]75  !
76      DO  ij = 1,iip1
77       div(     ij    , l ) = - sumypn
78      ENDDO
79
80    endif
81
82    if (pole_sud) then
83
84      DO  ij  = 1,iim
85       aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
86      ENDDO
87      sumyps = SSUM ( iim,aiy2,1 ) / apols
88  !
89      DO  ij = 1,iip1
90       div( ij + ip1jm, l ) =   sumyps
91      ENDDO
92
93    endif
94
95  END DO
96!$OMP END DO NOWAIT
97
98  !
99    jjb=jj_begin
100    jje=jj_end
101    if (pole_sud) jje=jj_end-1
102
103    CALL filtreg_p( div,jjb_u,jje_u,jjb,jje, jjp1, &
104          klevel, 2, 2, .TRUE., 1 )
105
106  !
107!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
108    DO l = 1, klevel
109       DO ij = ijb,ije
110        div(ij,l) = div(ij,l) * unsaire(ij)
111      ENDDO
112    ENDDO
113!$OMP END DO NOWAIT
114  !
115   RETURN
116END SUBROUTINE divergf_loc
Note: See TracBrowser for help on using the repository browser.