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

Contents of /trunk/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 265 - (show annotations)
Tue Mar 20 09:35:59 2018 UTC (6 years, 1 month ago) by guez
File size: 2595 byte(s)
Rename module dimens_m to dimensions.
1 module sortvarc_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE sortvarc(ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, &
8 ang, etot, ptot, ztot, stot, rmsdpdt, rmsv)
9
10 ! From dyn3d/sortvarc.F, version 1.1.1.1, 2004/05/19 12:53:07
11 ! Author: P. Le Van
12 ! Objet : sortie des variables de contr\^ole
13
14 USE comconst, ONLY: daysec, g, omeg, rad
15 USE comgeom, ONLY: aire_2d, cu_2d
16 USE dimensions, ONLY: iim, jjm, llm
17 use dynetat0_m, ONLY: rlatu
18 use filtreg_scal_m, only: filtreg_scal
19 use massbarxy_m, only: massbarxy
20 USE paramet_m, ONLY: jjp1
21
22 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 REAL, INTENT(IN):: vorpot(:, :, :) ! (iim + 1, jjm, llm)
29 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 real, intent(out):: ang, etot, ptot, ztot, stot, rmsdpdt, rmsv
33
34 ! Local:
35 REAL bernf(iim + 1, jjm + 1, llm)
36 REAL etotl(llm), angl(llm), ge(iim, 2:jjm)
37 REAL cosphi(2:jjm)
38 REAL radsg, radomeg
39 REAL massebxy(iim + 1, jjm, llm)
40 INTEGER j, l
41
42 !-----------------------------------------------------------------------
43
44 PRINT *, "Call sequence information: sortvarc"
45
46 rmsdpdt = daysec * 0.01 * sqrt(sum(dp(:iim, :)**2) / (iim * jjp1))
47
48 ! Calcul du moment angulaire :
49
50 radsg = rad / g
51 radomeg = rad * omeg
52 cosphi = cos(rlatu(2:jjm))
53
54 DO l = 1, llm
55 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 END DO
59
60 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 ptot = sum(ps(:iim, :) * aire_2d(:iim, :))
68
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 etot = sum(etotl)
73
74 CALL massbarxy(masse, massebxy)
75 ztot = sum(vorpot(:iim, :, :)**2 * massebxy(:iim, :, :))
76
77 stot = sum(masse(:iim, :, :) * teta(:iim, :, :))
78 rmsv = 2. &
79 * sum(masse(:iim, :, :) * max(bernf(:iim, :, :) - phi(:iim, :, :), 0.))
80
81 END SUBROUTINE sortvarc
82
83 end module sortvarc_m

  ViewVC Help
Powered by ViewVC 1.1.21