LMDZ
massdair_loc.F
Go to the documentation of this file.
1  SUBROUTINE massdair_loc( p, masse )
3 c
4 c *********************************************************************
5 c .... Calcule la masse d'air dans chaque maille ....
6 c *********************************************************************
7 c
8 c Auteurs : P. Le Van , Fr. Hourdin .
9 c ..........
10 c
11 c .. p est un argum. d'entree pour le s-pg ...
12 c .. masse est un argum.de sortie pour le s-pg ...
13 c
14 c .... p est defini aux interfaces des llm couches .....
15 c
16  IMPLICIT NONE
17 c
18 #include "dimensions.h"
19 #include "paramet.h"
20 #include "comconst.h"
21 #include "comgeom.h"
22 c
23 c ..... arguments ....
24 c
25  REAL p(ijb_u:ije_u,llmp1), masse(ijb_u:ije_u,llm)
26 
27 c .... Variables locales .....
28 
29  INTEGER l,ij
30  INTEGER ijb,ije
31  REAL massemoyn, massemoys
32 
33  REAL SSUM
34  EXTERNAL ssum
35 c
36 c
37 c Methode pour calculer massebx et masseby .
38 c ----------------------------------------
39 c
40 c A chaque point scalaire P (i,j) est affecte 4 coefficients d'aires
41 c alpha1(i,j) calcule au point ( i+1/4,j-1/4 )
42 c alpha2(i,j) calcule au point ( i+1/4,j+1/4 )
43 c alpha3(i,j) calcule au point ( i-1/4,j+1/4 )
44 c alpha4(i,j) calcule au point ( i-1/4,j-1/4 )
45 c
46 c Avec alpha1(i,j) = aire(i+1/4,j-1/4)/ aire(i,j)
47 c
48 c N.B . Pour plus de details, voir s-pg ... iniconst ...
49 c
50 c
51 c
52 c alpha4 . . alpha1 . alpha4
53 c (i,j) (i,j) (i+1,j)
54 c
55 c P . U . . P
56 c (i,j) (i,j) (i+1,j)
57 c
58 c alpha3 . . alpha2 .alpha3
59 c (i,j) (i,j) (i+1,j)
60 c
61 c V . Z . . V
62 c (i,j)
63 c
64 c alpha4 . . alpha1 .alpha4
65 c (i,j+1) (i,j+1) (i+1,j+1)
66 c
67 c P . U . . P
68 c (i,j+1) (i+1,j+1)
69 c
70 c
71 c
72 c On a :
73 c
74 c massebx(i,j) = masse(i ,j) * ( alpha1(i ,j) + alpha2(i,j)) +
75 c masse(i+1,j) * ( alpha3(i+1,j) + alpha4(i+1,j) )
76 c localise au point ... U (i,j) ...
77 c
78 c masseby(i,j) = masse(i,j ) * ( alpha2(i,j ) + alpha3(i,j ) +
79 c masse(i,j+1) * ( alpha1(i,j+1) + alpha4(i,j+1)
80 c localise au point ... V (i,j) ...
81 c
82 c
83 c=======================================================================
84 
85 
86 
87 
88  ijb=ij_begin-iip1
89  ije=ij_end+2*iip1
90 
91  if (pole_nord) ijb=ij_begin
92  if (pole_sud) ije=ij_end
93 
94 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
95  DO 100 l = 1 , llm
96 c
97  DO ij = ijb, ije
98  masse(ij,l) = airesurg(ij) * ( p(ij,l) - p(ij,l+1) )
99  ENDDO
100 c
101  DO ij = ijb, ije,iip1
102  masse(ij+ iim,l) = masse(ij,l)
103  ENDDO
104 c
105 c DO ij = 1, iim
106 c masse( ij ,l) = masse( ij ,l) * aire( ij )
107 c masse(ij+ip1jm,l) = masse(ij+ip1jm,l) * aire(ij+ip1jm)
108 c ENDDO
109 c massemoyn = SSUM(iim,masse( 1 ,l),1)/ apoln
110 c massemoys = SSUM(iim,masse(ip1jm+1,l),1)/ apols
111 c DO ij = 1, iip1
112 c masse( ij ,l ) = massemoyn
113 c masse(ij+ip1jm,l ) = massemoys
114 c ENDDO
115 
116 100 CONTINUE
117 c$OMP END DO NOWAIT
118 c
119  RETURN
120  END
!$Header!CDK comgeom COMMON comgeom airesurg
Definition: comgeom.h:25
!$Header llmp1
Definition: paramet.h:14
integer, save ij_end
logical, save pole_sud
subroutine massdair_loc(p, masse)
Definition: massdair_loc.F:2
!$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
logical, save pole_nord
integer, save ij_begin
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
integer, save ije_u
integer, save ijb_u