LMDZ
gradiv_p.F
Go to the documentation of this file.
1  SUBROUTINE gradiv_p(klevel, xcov, ycov, ld, gdx_out, gdy_out )
2 c
3 c Auteur : P. Le Van
4 c
5 c ***************************************************************
6 c
7 c ld
8 c calcul de (grad (div) ) du vect. v ....
9 c
10 c xcov et ycov etant les composant.covariantes de v
11 c ****************************************************************
12 c xcov , ycov et ld sont des arguments d'entree pour le s-prog
13 c gdx et gdy sont des arguments de sortie pour le s-prog
14 c
15 c
16  USE parallel_lmdz
17  USE times
18  IMPLICIT NONE
19 c
20 #include "dimensions.h"
21 #include "paramet.h"
22 #include "comdissipn.h"
23 #include "logic.h"
24 
25  INTEGER klevel
26 c
27  REAL xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
28  REAL,SAVE :: gdx( ip1jmp1,llm ), gdy( ip1jm,llm )
29 
30  REAL gdx_out( ip1jmp1,klevel ), gdy_out( ip1jm,klevel )
31 
32  REAL,SAVE :: div(ip1jmp1,llm)
33 
34  INTEGER l,ij,iter,ld
35 c
36  INTEGER ijb,ije,jjb,jje
37 c
38 c
39 c CALL SCOPY( ip1jmp1*klevel,xcov,1,gdx,1 )
40 c CALL SCOPY( ip1jm*klevel, ycov,1,gdy,1 )
41 
42  ijb=ij_begin
43  ije=ij_end
44 
45 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
46  DO l = 1,klevel
47  gdx(ijb:ije,l)=xcov(ijb:ije,l)
48  ENDDO
49 c$OMP END DO NOWAIT
50 
51  ijb=ij_begin
52  ije=ij_end
53  if(pole_sud) ije=ij_end-iip1
54 
55 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
56  DO l = 1,klevel
57  gdy(ijb:ije,l)=ycov(ijb:ije,l)
58  ENDDO
59 c$OMP END DO NOWAIT
60 
61 c
62  DO 10 iter = 1,ld
63 
64 c$OMP BARRIER
65 c$OMP MASTER
67  call exchange_hallo(gdy,ip1jm,llm,1,0)
69 c$OMP END MASTER
70 c$OMP BARRIER
71 
72  CALL diverg_p( klevel, gdx , gdy, div )
73 
74  jjb=jj_begin
75  jje=jj_end
76  CALL filtreg_p( div,jjb,jje, jjp1, klevel, 2,1, .true.,2 )
77 
78 c call exchange_Hallo(div,ip1jmp1,llm,0,1)
79 
80 c$OMP BARRIER
81 c$OMP MASTER
83  call exchange_hallo(div,ip1jmp1,llm,1,1)
85 c$OMP END MASTER
86 c$OMP BARRIER
87 
88  CALL grad_p( klevel, div, gdx, gdy )
89 c
90 
91 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
92  DO 5 l = 1, klevel
93 
94  if(pole_sud) ije=ij_end
95  DO 3 ij = ijb, ije
96  gdx_out( ij,l ) = - gdx( ij,l ) * cdivu
97  3 CONTINUE
98 
99  if(pole_sud) ije=ij_end-iip1
100  DO 4 ij = ijb, ije
101  gdy_out( ij,l ) = - gdy( ij,l ) * cdivu
102  4 CONTINUE
103 
104  5 CONTINUE
105 c$OMP END DO NOWAIT
106 c
107  10 CONTINUE
108  RETURN
109  END
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
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
!$Header cdivu
Definition: comdissipn.h:11
!$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 diverg_p(klevel, x, y, div)
Definition: diverg_p.F:2
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
integer, parameter timer_dissip
Definition: times.F90:9
!$Header jjp1
Definition: paramet.h:14
Definition: times.F90:1
!$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 ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
integer, save ij_begin
subroutine suspend_timer(no_timer)
Definition: times.F90:70
subroutine grad_p(klevel, pg, pgx, pgy)
Definition: grad_p.F:2
subroutine gradiv_p(klevel, xcov, ycov, ld, gdx_out, gdy_out)
Definition: gradiv_p.F:2