LMDZ
nxgrarot_p.F
Go to the documentation of this file.
1  SUBROUTINE nxgrarot_p (klevel,xcov, ycov, lr, grx_out, gry_out )
2 c ***********************************************************
3 c
4 c Auteur : P.Le Van
5 c
6 c lr
7 c calcul de ( nXgrad (rot) ) du vect. v ....
8 c
9 c xcov et ycov etant les compos. covariantes de v
10 c ***********************************************************
11 c xcov , ycov et lr sont des arguments d'entree pour le s-prog
12 c grx et gry sont des arguments de sortie pour le s-prog
13 c
14 c
15  USE parallel_lmdz
16  USE times
17  USE write_field_p
18  IMPLICIT NONE
19 c
20 c
21 #include "dimensions.h"
22 #include "paramet.h"
23 #include "comdissipn.h"
24 #include "logic.h"
25 c
26  INTEGER klevel
27  REAL xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
28  REAL grx_out( ip1jmp1,klevel ), gry_out( ip1jm,klevel )
29  REAL,SAVE :: grx( ip1jmp1,llm ), gry( ip1jm,llm )
30 
31 c
32  REAL,SAVE :: rot(ip1jm,llm)
33 
34  INTEGER l,ij,iter,lr
35 c
36  INTEGER ijb,ije,jjb,jje
37 c
38 c
39 c CALL SCOPY ( ip1jmp1*klevel, xcov, 1, grx, 1 )
40 c CALL SCOPY ( ip1jm*klevel, ycov, 1, gry, 1 )
41 c
42  ijb=ij_begin
43  ije=ij_end
44 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
45  DO l = 1, klevel
46  grx(ijb:ije,l)=xcov(ijb:ije,l)
47  ENDDO
48 c$OMP END DO NOWAIT
49 
50  if(pole_sud) ije=ij_end-iip1
51 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
52  DO l = 1, klevel
53  gry(ijb:ije,l)=ycov(ijb:ije,l)
54  ENDDO
55 c$OMP END DO NOWAIT
56 
57  DO 10 iter = 1,lr
58 c$OMP BARRIER
59 c$OMP MASTER
61  call exchange_hallo(grx,ip1jmp1,llm,0,1)
63 c$OMP END MASTER
64 c$OMP BARRIER
65 
66  CALL rotat_p (klevel,grx, gry, rot )
67 c call write_field3d_p('rot',reshape(rot,(/iip1,jjm,llm/)))
68 
69  jjb=jj_begin
70  jje=jj_end
71  if (pole_sud) jje=jj_end-1
72  CALL filtreg_p( rot,jjb,jje, jjm, klevel, 2,1, .false.,2)
73 
74 c$OMP BARRIER
75 c$OMP MASTER
77  call exchange_hallo(rot,ip1jm,llm,1,0)
79 c$OMP END MASTER
80 c$OMP BARRIER
81 
82  CALL nxgrad_p (klevel,rot, grx, gry )
83 c
84 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
85  DO 5 l = 1, klevel
86  if(pole_sud) ije=ij_end-iip1
87  DO 2 ij = ijb, ije
88  gry_out( ij,l ) = - gry( ij,l ) * crot
89  2 CONTINUE
90  if(pole_sud) ije=ij_end
91  DO 3 ij = ijb, ije
92  grx_out( ij,l ) = - grx( ij,l ) * crot
93  3 CONTINUE
94  5 CONTINUE
95 c$OMP END DO NOWAIT
96 c call write_field3d_p('grx',reshape(grx,(/iip1,jjp1,llm/)))
97 c call write_field3d_p('gry',reshape(gry,(/iip1,jjm,llm/)))
98 c stop
99  10 CONTINUE
100  RETURN
101  END
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
subroutine rotat_p(klevel, x, y, rot)
Definition: rotat_p.F:2
subroutine filtreg_p(champ, ibeg, iend, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg_p.F:5
integer, save jj_end
integer, save jj_begin
integer, save ij_end
logical, save pole_sud
!$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 exchange_hallo(Field, ij, ll, up, down)
subroutine resume_timer(no_timer)
Definition: times.F90:87
subroutine nxgrad_p(klevel, rot, x, y)
Definition: nxgrad_p.F:2
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
integer, parameter timer_dissip
Definition: times.F90:9
!$Header crot
Definition: comdissipn.h:11
!$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
subroutine nxgrarot_p(klevel, xcov, ycov, lr, grx_out, gry_out)
Definition: nxgrarot_p.F:2
Definition: times.F90:1
integer, save ij_begin
subroutine suspend_timer(no_timer)
Definition: times.F90:70