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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 73 - (show annotations)
Fri Nov 15 17:48:30 2013 UTC (10 years, 6 months ago) by guez
File size: 3066 byte(s)
Renamed tpot to teta and psol to ps in etat0.

Replaced calls to flincom by calls to NetCDF95 in startdyn. lon_ini,
lat_ini and levdyn_ini are now pointers.
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, INTENT(IN):: teta(ip1jmp1, llm)
20 real masse(ip1jmp1, llm)
21 REAL, INTENT (IN) :: ps(ip1jmp1)
22 REAL, INTENT (IN) :: phis(ip1jmp1)
23 REAL :: vorpot(ip1jm, llm)
24 REAL :: phi(ip1jmp1, llm), bern(ip1jmp1, llm)
25 REAL :: dp(ip1jmp1)
26 REAL, INTENT (IN) :: pk(ip1jmp1, llm)
27
28 ! Local:
29
30 REAL :: vor(ip1jm), bernf(ip1jmp1, llm), ztotl(llm)
31 REAL :: etotl(llm), stotl(llm), rmsvl(llm), angl(llm), ge(ip1jmp1)
32 REAL :: cosphi(ip1jm), omegcosp(ip1jm)
33 REAL radomeg
34 REAL massebxy(ip1jm, llm)
35 INTEGER l, ij
36
37 REAL :: ssum
38
39 !-----------------------------------------------------------------------
40
41 PRINT *, 'Call sequence information: sortvarc0'
42
43 CALL massbarxy(masse, massebxy)
44
45 ! Calcul de rmsdpdt
46 ge = dp*dp
47 rmsdpdt = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
48 rmsdpdt = daysec*1.E-2*sqrt(rmsdpdt / (iim * jjp1))
49 CALL scopy(ijp1llm, bern, 1, bernf, 1)
50 CALL filtreg(bernf, jjp1, llm, -2, 2, .TRUE.)
51
52 ! Calcul du moment angulaire
53
54 radomeg = rad * omeg
55
56 DO ij = iip2, ip1jm
57 cosphi(ij) = cos(rlatu((ij-1)/iip1+1))
58 omegcosp(ij) = radomeg*cosphi(ij)
59 END DO
60
61 ! Calcul de l'energie, de l'enstrophie, de l'entropie et de rmsv
62
63 DO l = 1, llm
64 DO ij = 1, ip1jm
65 vor(ij) = vorpot(ij, l)*vorpot(ij, l)*massebxy(ij, l)
66 END DO
67 ztotl(l) = (ssum(ip1jm, vor, 1)-ssum(jjm, vor, iip1))
68
69 DO ij = 1, ip1jmp1
70 ge(ij) = masse(ij, l) &
71 *(phis(ij)+teta(ij, l)*pk(ij, l)+bernf(ij, l)-phi(ij, l))
72 END DO
73 etotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
74
75 DO ij = 1, ip1jmp1
76 ge(ij) = masse(ij, l)*teta(ij, l)
77 END DO
78 stotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
79
80 DO ij = 1, ip1jmp1
81 ge(ij) = masse(ij, l)*amax1(bernf(ij, l)-phi(ij, l), 0.)
82 END DO
83 rmsvl(l) = 2.*(ssum(ip1jmp1, ge, 1)-ssum(jjp1, ge, iip1))
84
85 DO ij = iip2, ip1jm
86 ge(ij) = (ucov(ij, l)/cu(ij)+omegcosp(ij))*masse(ij, l)*cosphi(ij)
87 END DO
88 angl(l) = rad / g &
89 * (ssum(ip1jm-iip1, ge(iip2), 1)-ssum(jjm-1, ge(iip2), iip1))
90 END DO
91
92 DO ij = 1, ip1jmp1
93 ge(ij) = ps(ij)*aire(ij)
94 END DO
95 ptot0 = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
96 etot0 = ssum(llm, etotl, 1)
97 ztot0 = ssum(llm, ztotl, 1)
98 stot0 = ssum(llm, stotl, 1)
99 rmsv = ssum(llm, rmsvl, 1)
100 ang0 = ssum(llm, angl, 1)
101
102 PRINT *, 'ptot0 = ', ptot0
103 PRINT *, 'etot0 = ', etot0
104 PRINT *, 'ztot0 = ', ztot0
105 PRINT *, 'stot0 = ', stot0
106 PRINT *, 'ang0 = ', ang0
107
108 END SUBROUTINE sortvarc0

  ViewVC Help
Powered by ViewVC 1.1.21