source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/diverg_gam_loc.f90 @ 5209

Last change on this file since 5209 was 5159, checked in by abarral, 3 months ago

Put dimensions.h and paramet.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.4 KB
Line 
1SUBROUTINE diverg_gam_loc(klevel,cuvscvgam,cvuscugam,unsairegam, &
2        unsapolnga,unsapolsga,  x, y,  div )
3
4  ! P. Le Van
5
6  !  *********************************************************************
7  !  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
8  ! x et y...
9  !          x et y  etant des composantes covariantes   ...
10  !  *********************************************************************
11  USE parallel_lmdz
12  USE lmdz_ssum_scopy, ONLY: ssum
13  USE lmdz_comgeom
14
15  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
16  USE lmdz_paramet
17  IMPLICIT NONE
18
19  !  x  et  y  sont des arguments  d'entree pour le s-prog
20  !    div      est  un argument  de sortie pour le s-prog
21
22
23
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  REAL :: cuvscvgam(ip1jm),cvuscugam(ip1jmp1),unsairegam(ip1jmp1)
31  REAL :: unsapolnga,unsapolsga
32
33  !    ...............     variables  locales   .........................
34
35  REAL :: aiy1( iip1 ) , aiy2( iip1 )
36  REAL :: sumypn,sumyps
37  INTEGER :: l,ij
38  !    ...................................................................
39  INTEGER :: ijb,ije,jjb,jje
40
41
42  ijb=ij_begin
43  ije=ij_end
44  IF (pole_nord) ijb=ij_begin+iip1
45  IF(pole_sud)  ije=ij_end-iip1
46
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           cvuscugam( ij+1 ) * x( ij+1,l ) - cvuscugam( ij ) * x( ij , l) + &
53           cuvscvgam(ij-iim) * y(ij-iim,l) - cuvscvgam(ij+1) * y(ij+1,l) )* &
54           unsairegam( ij+1 )
55    ENDDO
56
57  ! ....  correction pour  div( 1,j,l)  ......
58  ! ....   div(1,j,l)= div(iip1,j,l) ....
59
60  !DIR$ IVDEP
61    DO  ij = ijb,ije,iip1
62     div( ij,l ) = div( ij + iim,l )
63    ENDDO
64
65  ! ....  calcul  aux poles  .....
66
67   IF (pole_nord) THEN
68      DO  ij  = 1,iim
69       aiy1(ij) =    cuvscvgam(    ij       ) * y(     ij     , l )
70      ENDDO
71      sumypn = SSUM ( iim,aiy1,1 ) * unsapolnga
72
73      DO  ij = 1,iip1
74       div(     ij    , l ) = - sumypn
75      ENDDO
76   endif
77
78    IF (pole_sud) THEN
79      DO  ij  = 1,iim
80       aiy2(ij) =    cuvscvgam( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
81      ENDDO
82      sumyps = SSUM ( iim,aiy2,1 ) * unsapolsga
83
84      DO  ij = 1,iip1
85       div( ij + ip1jm, l ) =   sumyps
86      ENDDO
87   endif
88  END DO
89!$OMP END DO NOWAIT
90  !
91
92
93END SUBROUTINE diverg_gam_loc
Note: See TracBrowser for help on using the repository browser.