LMDZ
enercin_p.F
Go to the documentation of this file.
1  SUBROUTINE enercin_p ( vcov, ucov, vcont, ucont, ecin )
3  IMPLICIT NONE
4 
5 c=======================================================================
6 c
7 c Auteur: P. Le Van
8 c -------
9 c
10 c Objet:
11 c ------
12 c
13 c *********************************************************************
14 c .. calcul de l'energie cinetique aux niveaux s ......
15 c *********************************************************************
16 c vcov, vcont, ucov et ucont sont des arguments d'entree pour le s-pg .
17 c ecin est un argument de sortie pour le s-pg
18 c
19 c=======================================================================
20 
21 #include "dimensions.h"
22 #include "paramet.h"
23 #include "comgeom.h"
24 
25  REAL vcov( ip1jm,llm ),vcont( ip1jm,llm ),
26  * ucov( ip1jmp1,llm ),ucont( ip1jmp1,llm ),ecin( ip1jmp1,llm )
27 
28  REAL ecinni( iip1 ),ecinsi( iip1 )
29 
30  REAL ecinpn, ecinps
31  INTEGER l,ij,i,ijb,ije
32 
33  EXTERNAL ssum
34  REAL SSUM
35 
36 
37 
38 c . V
39 c i,j-1
40 
41 c alpha4 . . alpha1
42 
43 
44 c U . . P . U
45 c i-1,j i,j i,j
46 
47 c alpha3 . . alpha2
48 
49 
50 c . V
51 c i,j
52 
53 c
54 c L'energie cinetique au point scalaire P(i,j) ,autre que les poles, est :
55 c Ecin = 0.5 * U(i-1,j)**2 *( alpha3 + alpha4 ) +
56 c 0.5 * U(i ,j)**2 *( alpha1 + alpha2 ) +
57 c 0.5 * V(i,j-1)**2 *( alpha1 + alpha4 ) +
58 c 0.5 * V(i, j)**2 *( alpha2 + alpha3 )
59 
60 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
61  DO 5 l = 1,llm
62 
63  ijb=ij_begin
64  ije=ij_end+iip1
65 
66  IF (pole_nord) ijb=ij_begin+iip1
67  IF (pole_sud) ije=ij_end-iip1
68 
69  DO 1 ij = ijb, ije -1
70  ecin( ij+1, l ) = 0.5 *
71  * ( ucov( ij ,l ) * ucont( ij ,l ) * alpha3p4( ij +1 ) +
72  * ucov( ij+1 ,l ) * ucont( ij+1 ,l ) * alpha1p2( ij +1 ) +
73  * vcov(ij-iim,l ) * vcont(ij-iim,l ) * alpha1p4( ij +1 ) +
74  * vcov( ij+ 1,l ) * vcont( ij+ 1,l ) * alpha2p3( ij +1 ) )
75  1 CONTINUE
76 
77 c ... correction pour ecin(1,j,l) ....
78 c ... ecin(1,j,l)= ecin(iip1,j,l) ...
79 
80 CDIR$ IVDEP
81  DO 2 ij = ijb, ije, iip1
82  ecin( ij,l ) = ecin( ij + iim, l )
83  2 CONTINUE
84 
85 c calcul aux poles .......
86 
87  IF (pole_nord) THEN
88 
89  DO i = 1, iim
90  ecinni(i) = vcov( i , l) *
91  * vcont( i ,l) * aire( i )
92  ENDDO
93 
94  ecinpn = 0.5 * ssum( iim,ecinni,1 ) / apoln
95 
96  DO ij = 1,iip1
97  ecin( ij , l ) = ecinpn
98  ENDDO
99 
100  ENDIF
101 
102  IF (pole_sud) THEN
103 
104  DO i = 1, iim
105  ecinsi(i) = vcov(i+ip1jmi1,l)*
106  * vcont(i+ip1jmi1,l) * aire(i+ip1jm)
107  ENDDO
108 
109  ecinps = 0.5 * ssum( iim,ecinsi,1 ) / apols
110 
111  DO ij = 1,iip1
112  ecin( ij+ ip1jm, l ) = ecinps
113  ENDDO
114 
115  ENDIF
116 
117 
118  5 CONTINUE
119 c$OMP END DO NOWAIT
120  RETURN
121  END
!$Header llmm1 INTEGER ip1jmi1
Definition: paramet.h:14
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
!$Header!CDK comgeom COMMON comgeom apols
Definition: comgeom.h:8
!$Header!CDK comgeom COMMON comgeom alpha1p2
Definition: comgeom.h:25
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
!$Header!CDK comgeom COMMON comgeom aire
Definition: comgeom.h:25
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
!$Header!CDK comgeom COMMON comgeom apoln
Definition: comgeom.h:8
subroutine enercin_p(vcov, ucov, vcont, ucont, ecin)
Definition: enercin_p.F:2
!$Header!CDK comgeom COMMON comgeom alpha1p4
Definition: comgeom.h:25
logical, save pole_nord
!$Header!CDK comgeom COMMON comgeom alpha3p4
Definition: comgeom.h:25
integer, save ij_begin
!$Header!CDK comgeom COMMON comgeom alpha2p3
Definition: comgeom.h:25
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
real function ssum(n, sx, incx)
Definition: cray.F:27