/[lmdze]/trunk/dyn3d/sortvarc.f
ViewVC logotype

Contents of /trunk/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 258 - (show annotations)
Tue Mar 6 15:17:17 2018 UTC (6 years, 2 months ago) by guez
File size: 3222 byte(s)
Remove unnecessary intermediary variables stotl and rmsvl. Move lines
around to group related computations.

1 module sortvarc_m
2
3 IMPLICIT NONE
4
5 real, save:: ang, etot, ptot, ztot, stot, rmsdpdt, rmsv
6
7 contains
8
9 SUBROUTINE sortvarc(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, &
10 resetvarc)
11
12 ! From dyn3d/sortvarc.F, version 1.1.1.1, 2004/05/19 12:53:07
13 ! Author: P. Le Van
14 ! Objet : sortie des variables de contr\^ole
15
16 USE comconst, ONLY: daysec, g, omeg, rad
17 USE comgeom, ONLY: aire_2d, cu_2d
18 USE dimens_m, ONLY: iim, jjm, llm
19 use dynetat0_m, ONLY: rlatu
20 USE ener, ONLY: ang0, etot0, ptot0, stot0, ztot0
21 use filtreg_scal_m, only: filtreg_scal
22 use massbarxy_m, only: massbarxy
23 USE paramet_m, ONLY: jjp1
24
25 REAL, INTENT(IN):: ucov(iim + 1, jjm + 1, llm)
26 REAL, INTENT(IN):: teta(iim + 1, jjm + 1, llm)
27 REAL, INTENT(IN):: ps(iim + 1, jjm + 1)
28 REAL, INTENT(IN):: masse(iim + 1, jjm + 1, llm)
29 REAL, INTENT(IN):: pk(iim + 1, jjm + 1, llm)
30 REAL, INTENT(IN):: phis(iim + 1, jjm + 1)
31 REAL, INTENT(IN):: vorpot(:, :, :) ! (iim + 1, jjm, llm)
32 REAL, intent(in):: phi(iim + 1, jjm + 1, llm)
33 real, intent(in):: bern(iim + 1, jjm + 1, llm)
34 REAL, intent(in):: dp(iim + 1, jjm + 1)
35 logical, intent(in):: resetvarc
36
37 ! Local:
38 REAL bernf(iim + 1, jjm + 1, llm)
39 REAL etotl(llm), angl(llm), ge(iim, 2:jjm)
40 REAL cosphi(2:jjm)
41 REAL radsg, radomeg
42 REAL massebxy(iim + 1, jjm, llm)
43 INTEGER j, l
44
45 !-----------------------------------------------------------------------
46
47 PRINT *, "Call sequence information: sortvarc"
48
49 rmsdpdt = daysec * 0.01 * sqrt(sum(dp(:iim, :)**2) / (iim * jjp1))
50
51 ! Calcul du moment angulaire :
52
53 radsg = rad / g
54 radomeg = rad * omeg
55 cosphi = cos(rlatu(2:jjm))
56
57 DO l = 1, llm
58 forall (j = 2:jjm) ge(:, j) = (ucov(:iim, j, l) / cu_2d(:iim, j) &
59 + radomeg * cosphi(j)) * masse(:iim, j, l) * cosphi(j)
60 angl(l) = radsg * sum(ge)
61 END DO
62
63 ang = sum(angl)
64
65 ! Calcul de l'energie, de l'enstrophie, de l'entropie et de rmsv :
66
67 bernf = bern
68 CALL filtreg_scal(bernf, direct = .false., intensive = .false.)
69
70 ptot = sum(ps(:iim, :) * aire_2d(:iim, :))
71
72 forall (l = 1:llm) etotl(l) = sum(masse(:iim, :, l) * (phis(:iim, :) &
73 + teta(:iim, :, l) * pk(:iim, :, l) + bernf(:iim, :, l) &
74 - phi(:iim, :, l)))
75 etot = sum(etotl)
76
77 CALL massbarxy(masse, massebxy)
78 ztot = sum(vorpot(:iim, :, :)**2 * massebxy(:iim, :, :))
79
80 stot = sum(masse(:iim, :, :) * teta(:iim, :, :))
81 rmsv = 2. &
82 * sum(masse(:iim, :, :) * max(bernf(:iim, :, :) - phi(:iim, :, :), 0.))
83
84 IF (resetvarc .or. ptot0 == 0.) then
85 print *, 'sortvarc: recomputed initial values.'
86 etot0 = etot
87 ptot0 = ptot
88 ztot0 = ztot
89 stot0 = stot
90 ang0 = ang
91 PRINT *, 'ptot0 = ', ptot0
92 PRINT *, 'etot0 = ', etot0
93 PRINT *, 'ztot0 = ', ztot0
94 PRINT *, 'stot0 = ', stot0
95 PRINT *, 'ang0 = ', ang0
96 END IF
97
98 IF (.not. resetvarc) then
99 etot = etot / etot0
100 rmsv = sqrt(rmsv / ptot)
101 ptot = ptot / ptot0
102 ztot = ztot / ztot0
103 stot = stot / stot0
104 ang = ang / ang0
105 end IF
106
107 END SUBROUTINE sortvarc
108
109 end module sortvarc_m

  ViewVC Help
Powered by ViewVC 1.1.21