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

Annotation of /trunk/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 259 - (hide annotations)
Tue Mar 6 16:19:52 2018 UTC (6 years, 2 months ago) by guez
File size: 2593 byte(s)
Try to clarify the logic. Remove module ener. Move variables from
module ener to module dynetat0_m, where they are defined in program
gcm. In sortvarc, I do not see how ptot0 could be 0, discard this possibility.

Remove dummy argument resetvarc of procedure sortvarc. The difference
is that sortvarc is called by caldyn or caldyn0 so just do different
processing in caldyn and caldyn0 instead of inside sortvarc.

No need for variables ang, etot, ptot, rmsdpdt, rmsv, stot, ztot to be
at module level in module sortvarc_m, downgrade them to arguments of
sortvarc. Instead of modyfying the meaning of ang, etot, ptot,
rmsdpdt, rmsv, stot, ztot from absolute quantities to variations of
these quantities, print the ratio in caldyn.

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

  ViewVC Help
Powered by ViewVC 1.1.21