1 | SUBROUTINE nxgraro2_p (klevel,xcov, ycov, lr, grx, gry ) |
---|
2 | c |
---|
3 | c P.Le Van . |
---|
4 | c *********************************************************** |
---|
5 | c lr |
---|
6 | c calcul de ( nxgrad (rot) ) du vect. v .... |
---|
7 | c |
---|
8 | c xcov et ycov etant les compos. covariantes de v |
---|
9 | c *********************************************************** |
---|
10 | c xcov , ycov et lr sont des arguments d'entree pour le s-prog |
---|
11 | c grx et gry sont des arguments de sortie pour le s-prog |
---|
12 | c |
---|
13 | c |
---|
14 | USE write_Field_p |
---|
15 | USE parallel |
---|
16 | USE times |
---|
17 | IMPLICIT NONE |
---|
18 | c |
---|
19 | #include "dimensions.h" |
---|
20 | #include "paramet.h" |
---|
21 | #include "comdissipn.h" |
---|
22 | c |
---|
23 | c ...... variables en arguments ....... |
---|
24 | c |
---|
25 | INTEGER klevel |
---|
26 | REAL xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel ) |
---|
27 | REAL grx( ip1jmp1,klevel ), gry( ip1jm,klevel ) |
---|
28 | c |
---|
29 | c ...... variables locales ........ |
---|
30 | c |
---|
31 | REAL rot(ip1jm,llm) , signe, nugradrs |
---|
32 | INTEGER l,ij,iter,lr |
---|
33 | c ........................................................ |
---|
34 | c |
---|
35 | EXTERNAL filtreg |
---|
36 | EXTERNAL SCOPY, rotatf, nxgrad, laplacien_rotgam |
---|
37 | INTEGER :: ijb,ije,jjb,jje |
---|
38 | |
---|
39 | c |
---|
40 | c |
---|
41 | signe = (-1.)**lr |
---|
42 | nugradrs = signe * crot |
---|
43 | c |
---|
44 | c CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 ) |
---|
45 | c CALL SCOPY ( ip1jm * klevel, ycov, 1, gry, 1 ) |
---|
46 | |
---|
47 | ijb=ij_begin |
---|
48 | ije=ij_end |
---|
49 | grx(ijb:ije,1:klevel)=xcov(ijb:ije,1:klevel) |
---|
50 | |
---|
51 | call suspend_timer(timer_dissip) |
---|
52 | call exchange_Hallo(grx,ip1jmp1,llm,0,1) |
---|
53 | call resume_timer(timer_dissip) |
---|
54 | |
---|
55 | ijb=ij_begin |
---|
56 | ije=ij_end |
---|
57 | if(pole_sud) ije=ij_end-iip1 |
---|
58 | gry(ijb:ije,1:klevel)=ycov(ijb:ije,1:klevel) |
---|
59 | c |
---|
60 | CALL rotatf_p ( klevel, grx, gry, rot ) |
---|
61 | c call write_field3d_p('rot1',reshape(rot,(/iip1,jjm,llm/))) |
---|
62 | |
---|
63 | call suspend_timer(timer_dissip) |
---|
64 | call exchange_Hallo(rot,ip1jm,llm,1,1) |
---|
65 | call resume_timer(timer_dissip) |
---|
66 | |
---|
67 | CALL laplacien_rot_p ( klevel, rot, rot,grx,gry ) |
---|
68 | c call write_field3d_p('rot2',reshape(rot,(/iip1,jjm,llm/))) |
---|
69 | c |
---|
70 | c ..... Iteration de l'operateur laplacien_rotgam ..... |
---|
71 | c |
---|
72 | DO iter = 1, lr -2 |
---|
73 | call suspend_timer(timer_dissip) |
---|
74 | call exchange_Hallo(rot,ip1jm,llm,1,1) |
---|
75 | call resume_timer(timer_dissip) |
---|
76 | CALL laplacien_rotgam_p ( klevel, rot, rot ) |
---|
77 | ENDDO |
---|
78 | |
---|
79 | c call write_field3d_p('rot3',reshape(rot,(/iip1,jjm,llm/))) |
---|
80 | |
---|
81 | c |
---|
82 | c |
---|
83 | jjb=jj_begin |
---|
84 | jje=jj_end |
---|
85 | if (pole_sud) jje=jj_end-1 |
---|
86 | |
---|
87 | CALL filtreg_p( rot, jjb,jje,jjm, klevel, 2,1, .FALSE.,1) |
---|
88 | call suspend_timer(timer_dissip) |
---|
89 | call exchange_Hallo(rot,ip1jm,llm,1,0) |
---|
90 | call resume_timer(timer_dissip) |
---|
91 | CALL nxgrad_p ( klevel, rot, grx, gry ) |
---|
92 | |
---|
93 | c |
---|
94 | ijb=ij_begin |
---|
95 | ije=ij_end |
---|
96 | |
---|
97 | DO l = 1, klevel |
---|
98 | |
---|
99 | if(pole_sud) ije=ij_end-iip1 |
---|
100 | DO ij = ijb, ije |
---|
101 | gry( ij,l ) = gry( ij,l ) * nugradrs |
---|
102 | ENDDO |
---|
103 | |
---|
104 | if(pole_sud) ije=ij_end |
---|
105 | DO ij = ijb, ije |
---|
106 | grx( ij,l ) = grx( ij,l ) * nugradrs |
---|
107 | ENDDO |
---|
108 | |
---|
109 | ENDDO |
---|
110 | c |
---|
111 | RETURN |
---|
112 | END |
---|