source: LMDZ6/trunk/libf/dyn3dpar/gradiv2_p.F @ 3981

Last change on this file since 3981 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.8 KB
Line 
1      SUBROUTINE gradiv2_p(klevel, xcov, ycov, ld, gdx_out, gdy_out )
2c
3c     P. Le Van
4c
5c   **********************************************************
6c                                ld
7c       calcul  de  (grad (div) )   du vect. v ....
8c
9c     xcov et ycov etant les composant.covariantes de v
10c   **********************************************************
11c     xcont , ycont et ld  sont des arguments  d'entree pour le s-prog
12c      gdx   et  gdy       sont des arguments de sortie pour le s-prog
13c
14c
15      USE parallel_lmdz
16      USE times
17      USE Write_field_p
18      USE mod_hallo
19      IMPLICIT NONE
20c
21#include "dimensions.h"
22#include "paramet.h"
23#include "comgeom.h"
24#include "comdissipn.h"
25c
26c     ........    variables en arguments      ........
27
28      INTEGER klevel
29      REAL  xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
30      REAL,SAVE ::  gdx( ip1jmp1,llm ),  gdy( ip1jm,llm )
31      REAL   gdx_out( ip1jmp1,klevel ), gdy_out( ip1jm,klevel )
32c
33c     ........       variables locales       .........
34c
35      REAL,SAVE :: div(ip1jmp1,llm)
36      REAL      :: tmp_div2(ip1jmp1,llm)
37      REAL signe, nugrads
38      INTEGER l,ij,iter,ld
39      INTEGER :: ijb,ije,jjb,jje
40      Type(Request)  :: request_dissip
41     
42c    ........................................................
43c
44c
45c      CALL SCOPY( ip1jmp1 * klevel, xcov, 1, gdx, 1 )
46c      CALL SCOPY(   ip1jm * klevel, ycov, 1, gdy, 1 )
47     
48      ijb=ij_begin
49      ije=ij_end
50     
51c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
52      DO   l = 1, klevel
53        gdx(ijb:ije,l)=xcov(ijb:ije,l)
54      ENDDO
55c$OMP END DO NOWAIT     
56     
57      ijb=ij_begin
58      ije=ij_end
59      if(pole_sud) ije=ij_end-iip1
60
61c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)     
62      DO   l = 1, klevel
63        gdy(ijb:ije,l)=ycov(ijb:ije,l)
64      ENDDO
65c$OMP END DO NOWAIT
66
67c$OMP BARRIER
68       call Register_Hallo(gdy,ip1jm,llm,1,0,0,1,Request_dissip)
69       call SendRequest(Request_dissip)
70c$OMP BARRIER
71       call WaitRequest(Request_dissip)
72c$OMP BARRIER
73c
74c
75      signe   = (-1.)**ld
76      nugrads = signe * cdivu
77c
78
79
80      CALL    divergf_p( klevel, gdx,   gdy , div )
81c      call write_field3d_p('div1',reshape(div,(/iip1,jjp1,llm/)))
82
83      IF( ld.GT.1 )   THEN
84c$OMP BARRIER
85       call Register_Hallo(div,ip1jmp1,llm,1,1,1,1,Request_dissip)
86       call SendRequest(Request_dissip)
87c$OMP BARRIER
88       call WaitRequest(Request_dissip)
89c$OMP BARRIER
90        CALL laplacien_p ( klevel, div,  div     )
91
92c    ......  Iteration de l'operateur laplacien_gam   .......
93c         call write_field3d_p('div2',reshape(div,(/iip1,jjp1,llm/)))
94
95        DO iter = 1, ld -2
96c$OMP BARRIER
97       call Register_Hallo(div,ip1jmp1,llm,1,1,1,1,Request_dissip)
98       call SendRequest(Request_dissip)
99c$OMP BARRIER
100       call WaitRequest(Request_dissip)
101
102c$OMP BARRIER
103
104         CALL laplacien_gam ( klevel,cuvscvgam1,cvuscugam1,unsair_gam1,
105     *                       unsapolnga1, unsapolsga1,  div, div       )
106        ENDDO
107c        call write_field3d_p('div3',reshape(div,(/iip1,jjp1,llm/)))
108      ENDIF
109
110       jjb=jj_begin
111       jje=jj_end
112       
113       CALL filtreg_p( div   ,jjb,jje, jjp1, klevel, 2, 1, .TRUE., 1 )
114c       call exchange_Hallo(div,ip1jmp1,llm,0,1)
115c$OMP BARRIER
116       call Register_Hallo(div,ip1jmp1,llm,1,1,1,1,Request_dissip)
117       call SendRequest(Request_dissip)
118c$OMP BARRIER
119       call WaitRequest(Request_dissip)
120
121c$OMP BARRIER
122
123
124       CALL  grad_p  ( klevel,  div,   gdx,  gdy             )
125
126c
127      ijb=ij_begin
128      ije=ij_end
129         
130c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)     
131       DO   l = 1, klevel
132         
133         if (pole_sud) ije=ij_end
134         DO  ij = ijb, ije
135          gdx_out( ij,l ) = gdx( ij,l ) * nugrads
136         ENDDO
137         
138         if (pole_sud) ije=ij_end-iip1
139         DO  ij = ijb, ije
140          gdy_out( ij,l ) = gdy( ij,l ) * nugrads
141         ENDDO
142       
143       ENDDO
144c$OMP END DO NOWAIT
145c
146       RETURN
147       END
Note: See TracBrowser for help on using the repository browser.