1 SUBROUTINE nxgraro2_loc(klevel,xcov,ycov,lr,grx_out,gry_out)
4 c ***********************************************************
6 c calcul
de(
nxgrad(rot) ) du vect. v ....
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
22 #include "dimensions.h"
24 #include "comdissipn.h"
26 c ...... variables en arguments .......
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)
32 c ...... variables locales ........
36 Type(Request),SAVE :: Request_dissip
37 !$OMP THREADPRIVATE(Request_dissip)
38 c ........................................................
40 INTEGER :: ijb,ije,jjb,jje
45 nugradrs = signe * crot
47 c CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 )
48 c CALL SCOPY ( ip1jm * klevel, ycov, 1, gry, 1 )
53 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
55 grx(ijb:ije,l)=xcov(ijb:ije,l)
60 call Register_Hallo_u(grx,llm,0,1,1,0,Request_dissip)
61 call SendRequest(Request_dissip)
63 call WaitRequest(Request_dissip)
68 if(pole_sud) ije=ij_end-iip1
70 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
72 gry(ijb:ije,l)=ycov(ijb:ije,l)
77 CALL rotatf_loc ( klevel, grx, gry, rot )
78 c call write_field3d_p('rot1
',reshape(rot,(/iip1,jjm,llm/)))
81 call Register_Hallo_v(rot,llm,1,1,1,1,Request_dissip)
82 call SendRequest(Request_dissip)
84 call WaitRequest(Request_dissip)
87 CALL laplacien_rot_loc ( klevel, rot, rot,grx,gry )
88 c call write_field3d_p('rot2
',reshape(rot,(/iip1,jjm,llm/)))
94 call register_hallo_v(rot,
llm,1,1,1,1,request_dissip)
95 call sendrequest(request_dissip)
97 call waitrequest(request_dissip)
103 c
call write_field3d_p(
'rot3',reshape(rot,(/iip1,jjm,
llm/)))
109 if (pole_sud) jje=jj_end-1
111 CALL filtreg_p( rot, jjb_v,jje_v, jjb,jje,jjm,
112 & klevel, 2,1, .
false.,1)
114 call register_hallo_v(rot,
llm,1,0,0,1,request_dissip)
115 call sendrequest(request_dissip)
117 call waitrequest(request_dissip)
126 c$omp
DO schedule(static,omp_chunk)
129 if(pole_sud) ije=ij_end-iip1
131 gry_out(
ij,
l ) = gry(
ij,
l ) * nugradrs
134 if(pole_sud) ije=ij_end
136 grx_out(
ij,
l ) = grx(
ij,
l ) * nugradrs
subroutine nxgrad_loc(klevel, rot, x, y)
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
subroutine filtreg_p(champ, ibeg, iend, nlat, nbniv, ifiltre, iaire, griscal, iter)
subroutine nxgrad(klevel, rot, x, y)
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
!$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)