/[lmdze]/trunk/Sources/dyn3d/enercin.f
ViewVC logotype

Annotation of /trunk/Sources/dyn3d/enercin.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 81 - (hide annotations)
Wed Mar 5 14:38:41 2014 UTC (10 years, 2 months ago) by guez
Original Path: trunk/dyn3d/enercin.f90
File size: 2269 byte(s)
 Converted to free source form files which were still in fixed source
form. The conversion was done using the polish mode of the NAG Fortran
Compiler.

In addition to converting to free source form, the processing of the
files also:

-- indented the code (including comments);

-- set Fortran keywords to uppercase, and set all other identifiers
to lower case;

-- added qualifiers to end statements (for example "end subroutine
conflx", instead of "end");

-- changed the terminating statements of all DO loops so that each
loop ends with an ENDDO statement (instead of a labeled continue).

1 guez 3
2 guez 81 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/enercin.F,v 1.1.1.1 2004/05/19
3     ! 12:53:06 lmdzadmin Exp $
4 guez 3
5 guez 81 SUBROUTINE enercin(vcov, ucov, vcont, ucont, ecin)
6     USE dimens_m
7     USE paramet_m
8     USE comgeom
9     IMPLICIT NONE
10 guez 3
11 guez 81 ! =======================================================================
12 guez 3
13 guez 81 ! Auteur: P. Le Van
14     ! -------
15 guez 3
16 guez 81 ! Objet:
17     ! ------
18 guez 3
19 guez 81 ! *********************************************************************
20     ! .. calcul de l'energie cinetique aux niveaux s ......
21     ! *********************************************************************
22     ! vcov, vcont, ucov et ucont sont des arguments d'entree pour le s-pg .
23     ! ecin est un argument de sortie pour le s-pg
24 guez 3
25 guez 81 ! =======================================================================
26 guez 3
27    
28 guez 81 REAL, INTENT (IN) :: vcov(ip1jm, llm), ucov(ip1jmp1, llm)
29     REAL vcont(ip1jm, llm), ucont(ip1jmp1, llm), ecin(ip1jmp1, llm)
30 guez 3
31 guez 81 REAL ecinni(iip1), ecinsi(iip1)
32 guez 3
33 guez 81 REAL ecinpn, ecinps
34     INTEGER l, ij, i
35 guez 3
36 guez 81 REAL ssum
37 guez 3
38    
39    
40 guez 81 ! . V
41     ! i,j-1
42 guez 3
43 guez 81 ! alpha4 . . alpha1
44 guez 3
45    
46 guez 81 ! U . . P . U
47     ! i-1,j i,j i,j
48 guez 3
49 guez 81 ! alpha3 . . alpha2
50 guez 3
51    
52 guez 81 ! . V
53     ! i,j
54 guez 3
55    
56 guez 81 ! L'energie cinetique au point scalaire P(i,j) ,autre que les poles, est :
57     ! Ecin = 0.5 * U(i-1,j)**2 *( alpha3 + alpha4 ) +
58     ! 0.5 * U(i ,j)**2 *( alpha1 + alpha2 ) +
59     ! 0.5 * V(i,j-1)**2 *( alpha1 + alpha4 ) +
60     ! 0.5 * V(i, j)**2 *( alpha2 + alpha3 )
61 guez 3
62    
63 guez 81 DO l = 1, llm
64 guez 3
65 guez 81 DO ij = iip2, ip1jm - 1
66     ecin(ij+1, l) = 0.5*(ucov(ij,l)*ucont(ij,l)*alpha3p4(ij+1)+ucov(ij+1,l) &
67     *ucont(ij+1,l)*alpha1p2(ij+1)+vcov(ij-iim,l)*vcont(ij-iim,l)*alpha1p4 &
68     (ij+1)+vcov(ij+1,l)*vcont(ij+1,l)*alpha2p3(ij+1))
69     END DO
70 guez 3
71 guez 81 ! ... correction pour ecin(1,j,l) ....
72     ! ... ecin(1,j,l)= ecin(iip1,j,l) ...
73    
74     ! DIR$ IVDEP
75     DO ij = iip2, ip1jm, iip1
76     ecin(ij, l) = ecin(ij+iim, l)
77     END DO
78    
79     ! calcul aux poles .......
80    
81    
82     DO i = 1, iim
83     ecinni(i) = vcov(i, l)*vcont(i, l)*aire(i)
84     ecinsi(i) = vcov(i+ip1jmi1, l)*vcont(i+ip1jmi1, l)*aire(i+ip1jm)
85     END DO
86    
87     ecinpn = 0.5*ssum(iim, ecinni, 1)/apoln
88     ecinps = 0.5*ssum(iim, ecinsi, 1)/apols
89    
90     DO ij = 1, iip1
91     ecin(ij, l) = ecinpn
92     ecin(ij+ip1jm, l) = ecinps
93     END DO
94    
95     END DO
96     RETURN
97     END SUBROUTINE enercin

  ViewVC Help
Powered by ViewVC 1.1.21