/[lmdze]/trunk/libf/dyn3d/sortvarc0.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/sortvarc0.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 27 - (show annotations)
Thu Mar 25 14:29:07 2010 UTC (14 years, 1 month ago) by guez
File size: 3052 byte(s)
"dyn3d" and "filtrez" do not contain any included file so make rules
have been updated.

"comdissip.f90" was useless, removed it.

"dynredem0" wrote undefined value in "controle(31)", that was
overwritten by "dynredem1". Now "dynredem0" just writes 0 to
"controle(31)".

Removed arguments of "inidissip". "inidissip" now accesses the
variables by use association.

In program "etat0_lim", "itaufin" is not defined so "dynredem1" wrote
undefined value to "controle(31)". Added argument "itau" of
"dynredem1" to correct that.

"itaufin" does not need to be a module variable (of "temps"), made it
a local variable of "leapfrog".

Removed calls to "diagedyn" from "leapfrog".

1 SUBROUTINE sortvarc0(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp)
2
3 ! From dyn3d/sortvarc0.F, v 1.1.1.1 2004/05/19 12:53:07
4 ! Auteur : P. Le Van
5 ! Objet : sortie des variables de contrĂ´le
6
7 USE dimens_m, ONLY : iim, jjm, llm
8 USE paramet_m, ONLY : iip1, iip2, ijp1llm, ip1jm, ip1jmp1, jjp1
9 USE comconst, ONLY : daysec, g, omeg, rad
10 USE comgeom, ONLY : aire, cu, rlatu
11 USE ener, ONLY : ang0, etot0, ptot0, rmsdpdt, rmsv, stot0, ztot0
12 use filtreg_m, only: filtreg
13
14 IMPLICIT NONE
15
16 ! Arguments:
17
18 REAL, INTENT (IN) :: ucov(ip1jmp1, llm)
19 REAL :: teta(ip1jmp1, llm), masse(ip1jmp1, llm)
20 REAL, INTENT (IN) :: ps(ip1jmp1)
21 REAL, INTENT (IN) :: phis(ip1jmp1)
22 REAL :: vorpot(ip1jm, llm)
23 REAL :: phi(ip1jmp1, llm), bern(ip1jmp1, llm)
24 REAL :: dp(ip1jmp1)
25 REAL, INTENT (IN) :: pk(ip1jmp1, llm)
26
27 ! Local:
28
29 REAL :: vor(ip1jm), bernf(ip1jmp1, llm), ztotl(llm)
30 REAL :: etotl(llm), stotl(llm), rmsvl(llm), angl(llm), ge(ip1jmp1)
31 REAL :: cosphi(ip1jm), omegcosp(ip1jm)
32 REAL radomeg
33 REAL massebxy(ip1jm, llm)
34 INTEGER l, ij
35
36 REAL :: ssum
37
38 !-----------------------------------------------------------------------
39
40 PRINT *, 'Call sequence information: sortvarc0'
41
42 CALL massbarxy(masse, massebxy)
43
44 ! Calcul de rmsdpdt
45 ge = dp*dp
46 rmsdpdt = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
47 rmsdpdt = daysec*1.E-2*sqrt(rmsdpdt / (iim * jjp1))
48 CALL scopy(ijp1llm, bern, 1, bernf, 1)
49 CALL filtreg(bernf, jjp1, llm, -2, 2, .TRUE., 1)
50
51 ! Calcul du moment angulaire
52
53 radomeg = rad * omeg
54
55 DO ij = iip2, ip1jm
56 cosphi(ij) = cos(rlatu((ij-1)/iip1+1))
57 omegcosp(ij) = radomeg*cosphi(ij)
58 END DO
59
60 ! Calcul de l'energie, de l'enstrophie, de l'entropie et de rmsv
61
62 DO l = 1, llm
63 DO ij = 1, ip1jm
64 vor(ij) = vorpot(ij, l)*vorpot(ij, l)*massebxy(ij, l)
65 END DO
66 ztotl(l) = (ssum(ip1jm, vor, 1)-ssum(jjm, vor, iip1))
67
68 DO ij = 1, ip1jmp1
69 ge(ij) = masse(ij, l) &
70 *(phis(ij)+teta(ij, l)*pk(ij, l)+bernf(ij, l)-phi(ij, l))
71 END DO
72 etotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
73
74 DO ij = 1, ip1jmp1
75 ge(ij) = masse(ij, l)*teta(ij, l)
76 END DO
77 stotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
78
79 DO ij = 1, ip1jmp1
80 ge(ij) = masse(ij, l)*amax1(bernf(ij, l)-phi(ij, l), 0.)
81 END DO
82 rmsvl(l) = 2.*(ssum(ip1jmp1, ge, 1)-ssum(jjp1, ge, iip1))
83
84 DO ij = iip2, ip1jm
85 ge(ij) = (ucov(ij, l)/cu(ij)+omegcosp(ij))*masse(ij, l)*cosphi(ij)
86 END DO
87 angl(l) = rad / g &
88 * (ssum(ip1jm-iip1, ge(iip2), 1)-ssum(jjm-1, ge(iip2), iip1))
89 END DO
90
91 DO ij = 1, ip1jmp1
92 ge(ij) = ps(ij)*aire(ij)
93 END DO
94 ptot0 = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
95 etot0 = ssum(llm, etotl, 1)
96 ztot0 = ssum(llm, ztotl, 1)
97 stot0 = ssum(llm, stotl, 1)
98 rmsv = ssum(llm, rmsvl, 1)
99 ang0 = ssum(llm, angl, 1)
100
101 PRINT *, 'ptot0 = ', ptot0
102 PRINT *, 'etot0 = ', etot0
103 PRINT *, 'ztot0 = ', ztot0
104 PRINT *, 'stot0 = ', stot0
105 PRINT *, 'ang0 = ', ang0
106
107 END SUBROUTINE sortvarc0

  ViewVC Help
Powered by ViewVC 1.1.21