LMDZ
nxgraro2_loc.F
Go to the documentation of this file.
1  SUBROUTINE nxgraro2_loc(klevel,xcov,ycov,lr,grx_out,gry_out)
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_lmdz
16  USE times
17  USE mod_hallo
18  USE mod_filtreg_p
19  USE nxgraro2_mod
20  IMPLICIT NONE
21 c
22 #include "dimensions.h"
23 #include "paramet.h"
24 #include "comdissipn.h"
25 c
26 c ...... variables en arguments .......
27 c
28  INTEGER klevel
29  REAL xcov( ijb_u:ije_u,klevel ), ycov( ijb_v:ije_v,klevel )
30  REAL grx_out( ijb_u:ije_u,klevel ),gry_out(ijb_v:ije_v,klevel)
31 c
32 c ...... variables locales ........
33 c
34  REAL signe, nugradrs
35  INTEGER l,ij,iter,lr
36  Type(Request),SAVE :: Request_dissip
37 !$OMP THREADPRIVATE(Request_dissip)
38 c ........................................................
39 c
40  INTEGER :: ijb,ije,jjb,jje
41 
42 c
43 c
44  signe = (-1.)**lr
45  nugradrs = signe * crot
46 c
47 c CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 )
48 c CALL SCOPY ( ip1jm * klevel, ycov, 1, gry, 1 )
49 
50  ijb=ij_begin
51  ije=ij_end
52 
53 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
54  DO l = 1, klevel
55  grx(ijb:ije,l)=xcov(ijb:ije,l)
56  ENDDO
57 c$OMP END DO NOWAIT
58 
59 c$OMP BARRIER
60  call Register_Hallo_u(grx,llm,0,1,1,0,Request_dissip)
61  call SendRequest(Request_dissip)
62 c$OMP BARRIER
63  call WaitRequest(Request_dissip)
64 c$OMP BARRIER
65 
66  ijb=ij_begin
67  ije=ij_end
68  if(pole_sud) ije=ij_end-iip1
69 
70 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
71  DO l = 1, klevel
72  gry(ijb:ije,l)=ycov(ijb:ije,l)
73  ENDDO
74 c$OMP END DO NOWAIT
75 
76 c
77  CALL rotatf_loc ( klevel, grx, gry, rot )
78 c call write_field3d_p('rot1',reshape(rot,(/iip1,jjm,llm/)))
79 
80 c$OMP BARRIER
81  call Register_Hallo_v(rot,llm,1,1,1,1,Request_dissip)
82  call SendRequest(Request_dissip)
83 c$OMP BARRIER
84  call WaitRequest(Request_dissip)
85 c$OMP BARRIER
86 
87  CALL laplacien_rot_loc ( klevel, rot, rot,grx,gry )
88 c call write_field3d_p('rot2',reshape(rot,(/iip1,jjm,llm/)))
89 c
90 c ..... Iteration de l'operateur laplacien_rotgam .....
91 c
92  DO iter = 1, lr -2
93 c$omp barrier
94  call register_hallo_v(rot,llm,1,1,1,1,request_dissip)
95  call sendrequest(request_dissip)
96 c$omp barrier
97  call waitrequest(request_dissip)
98 c$omp barrier
99 
100  CALL laplacien_rotgam_loc( klevel, rot, rot )
101  ENDDO
102 
103 c call write_field3d_p('rot3',reshape(rot,(/iip1,jjm,llm/)))
104 
105 c
106 c
107  jjb=jj_begin
108  jje=jj_end
109  if (pole_sud) jje=jj_end-1
110 
111  CALL filtreg_p( rot, jjb_v,jje_v, jjb,jje,jjm,
112  & klevel, 2,1, .false.,1)
113 c$omp barrier
114  call register_hallo_v(rot,llm,1,0,0,1,request_dissip)
115  call sendrequest(request_dissip)
116 c$omp barrier
117  call waitrequest(request_dissip)
118 c$omp barrier
119 
120  CALL nxgrad_loc ( klevel, rot, grx, gry )
121 
122 c
123  ijb=ij_begin
124  ije=ij_end
125 
126 c$omp DO schedule(static,omp_chunk)
127  DO l = 1, klevel
128 
129  if(pole_sud) ije=ij_end-iip1
130  DO ij = ijb, ije
131  gry_out( ij,l ) = gry( ij,l ) * nugradrs
132  ENDDO
133 
134  if(pole_sud) ije=ij_end
135  DO ij = ijb, ije
136  grx_out( ij,l ) = grx( ij,l ) * nugradrs
137  ENDDO
138 
139  ENDDO
140 c$omp END DO nowait
141 c
142  RETURN
143  END
subroutine nxgrad_loc(klevel, rot, x, y)
Definition: nxgrad_loc.F:2
c c $Id c c calculs statistiques distribution nuage ftion du regime dynamique c c Ce calcul doit etre fait a partir de valeurs mensuelles CALL nbregdyn DO kmaxm1 DO l
Definition: calcul_REGDYN.h:13
subroutine filtreg_p(champ, ibeg, iend, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg_p.F:5
subroutine nxgrad(klevel, rot, x, y)
Definition: nxgrad.F:5
subroutine laplacien_rotgam(klevel, rotin, rotout)
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
subroutine laplacien_rotgam_loc(klevel, rotin, rotout)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
!$Id klon klev DO klon!IM klev DO klon klon nbp_lat DO nbp_lon ij
subroutine nxgraro2_loc(klevel, xcov, ycov, lr, grx_out, gry_out)
Definition: nxgraro2_loc.F:2
do llm!au dessus de