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

Annotation of /trunk/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 255 - (hide annotations)
Tue Mar 6 13:39:57 2018 UTC (6 years, 2 months ago) by guez
File size: 3499 byte(s)
Use two dimensions of arrays for two space dimensions in procedure
sortvarc. Replace call to ssum by call to sum.

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

  ViewVC Help
Powered by ViewVC 1.1.21