source: LMDZ4/trunk/libf/dyn3dpar/nxgraro2_p.F @ 773

Last change on this file since 773 was 764, checked in by Laurent Fairhead, 17 years ago

Merge entre la version V3_conv et le HEAD
YM, JG, LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.5 KB
Line 
1       SUBROUTINE nxgraro2_p (klevel,xcov, ycov, lr, grx_out, gry_out )
2c
3c      P.Le Van .
4c   ***********************************************************
5c                                 lr
6c      calcul de  ( nxgrad (rot) )   du vect. v  ....
7c
8c       xcov et ycov  etant les compos. covariantes de  v
9c   ***********************************************************
10c     xcov , ycov et lr  sont des arguments  d'entree pour le s-prog
11c      grx   et  gry     sont des arguments de sortie pour le s-prog
12c
13c
14      USE write_Field_p
15      USE parallel
16      USE times
17      IMPLICIT NONE
18c
19#include "dimensions.h"
20#include "paramet.h"
21#include "comdissipn.h"
22c
23c    ......  variables en arguments  .......
24c
25      INTEGER klevel
26      REAL xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
27      REAL,SAVE ::  grx( ip1jmp1,llm ),  gry( ip1jm,llm )
28      REAL  grx_out( ip1jmp1,klevel ),  gry_out( ip1jm,klevel )
29c
30c    ......   variables locales     ........
31c
32      REAL,SAVE :: rot(ip1jm,llm)
33      REAL  signe, nugradrs
34      INTEGER l,ij,iter,lr
35c    ........................................................
36c
37      INTEGER :: ijb,ije,jjb,jje
38     
39c
40c
41      signe    = (-1.)**lr
42      nugradrs = signe * crot
43c
44c      CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 )
45c      CALL SCOPY (  ip1jm * klevel, ycov, 1, gry, 1 )
46 
47      ijb=ij_begin
48      ije=ij_end
49
50c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
51      DO    l = 1, klevel
52        grx(ijb:ije,l)=xcov(ijb:ije,l)
53      ENDDO
54c$OMP END DO NOWAIT
55
56c$OMP BARRIER
57c$OMP MASTER         
58      call suspend_timer(timer_dissip)
59      call exchange_Hallo(grx,ip1jmp1,llm,0,1)
60      call resume_timer(timer_dissip)
61c$OMP END MASTER
62c$OMP BARRIER
63
64      ijb=ij_begin
65      ije=ij_end
66      if(pole_sud) ije=ij_end-iip1
67
68c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
69      DO    l = 1, klevel
70        gry(ijb:ije,l)=ycov(ijb:ije,l)
71      ENDDO
72c$OMP END DO NOWAIT
73 
74c
75      CALL     rotatf_p     ( klevel, grx, gry, rot )
76c      call write_field3d_p('rot1',reshape(rot,(/iip1,jjm,llm/)))
77
78c$OMP BARRIER
79c$OMP MASTER     
80      call suspend_timer(timer_dissip)
81      call exchange_Hallo(rot,ip1jm,llm,1,1)
82      call resume_timer(timer_dissip)
83c$OMP END MASTER
84c$OMP BARRIER
85     
86      CALL laplacien_rot_p ( klevel, rot, rot,grx,gry      )
87c       call write_field3d_p('rot2',reshape(rot,(/iip1,jjm,llm/)))
88c
89c    .....   Iteration de l'operateur laplacien_rotgam  .....
90c
91      DO  iter = 1, lr -2
92c$OMP BARRIER
93c$OMP MASTER
94        call suspend_timer(timer_dissip)
95        call exchange_Hallo(rot,ip1jm,llm,1,1)
96        call resume_timer(timer_dissip)
97c$OMP END MASTER
98c$OMP BARRIER
99        CALL laplacien_rotgam_p ( klevel, rot, rot )
100      ENDDO
101     
102c       call write_field3d_p('rot3',reshape(rot,(/iip1,jjm,llm/)))
103     
104c
105c
106      jjb=jj_begin
107      jje=jj_end
108      if (pole_sud) jje=jj_end-1
109       
110      CALL filtreg_p( rot, jjb,jje,jjm, klevel, 2,1, .FALSE.,1)
111c$OMP BARRIER
112c$OMP MASTER
113      call suspend_timer(timer_dissip)
114      call exchange_Hallo(rot,ip1jm,llm,1,0)
115      call resume_timer(timer_dissip)
116c$OMP END MASTER
117c$OMP BARRIER
118      CALL nxgrad_p ( klevel, rot, grx, gry )
119
120c
121      ijb=ij_begin
122      ije=ij_end
123     
124c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)   
125      DO    l = 1, klevel
126       
127         if(pole_sud) ije=ij_end-iip1
128         DO  ij = ijb, ije
129          gry_out( ij,l ) = gry( ij,l ) * nugradrs
130         ENDDO
131       
132         if(pole_sud) ije=ij_end
133         DO  ij = ijb, ije
134          grx_out( ij,l ) = grx( ij,l ) * nugradrs
135         ENDDO
136     
137      ENDDO
138c$OMP END DO NOWAIT
139c
140      RETURN
141      END
Note: See TracBrowser for help on using the repository browser.