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

Contents of /trunk/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 43 - (show annotations)
Fri Apr 8 12:43:31 2011 UTC (13 years, 1 month ago) by guez
Original Path: trunk/libf/dyn3d/sortvarc.f90
File size: 4346 byte(s)
"start_init_phys" is now called directly by "etat0" instead of through
"start_init_dyn". "qsol_2d" is no longer a variable of module
"start_init_phys_m", it is an argument of
"start_init_phys". "start_init_dyn" now receives "tsol_2d" from
"etat0".

Split file "vlspltqs.f" into "vlspltqs.f90", "vlxqs.f90" and
""vlyqs.f90".

In "start_init_orog", replaced calls to "flin*" by calls to NetCDF95.

1 module sortvarc_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE sortvarc(itau, ucov, teta, ps, masse, pk, phis, vorpot, phi, &
8 bern, dp, time_0)
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Ă´le
13
14 USE conf_gcm_m, ONLY: day_step
15 USE dimens_m, ONLY : iim, jjm, llm
16 USE paramet_m, ONLY : iip1, iip2, ijp1llm, ip1jm, ip1jmp1, jjp1
17 USE comconst, ONLY : daysec, dtvr, g, omeg, rad
18 USE comgeom, ONLY : aire, cu, rlatu
19 USE dynetat0_m, ONLY : day_ini
20 USE ener, ONLY : ang, ang0, etot, etot0, ptot, ptot0, rmsdpdt, rmsv, &
21 stot, stot0, ztot, ztot0
22 use filtreg_m, only: filtreg
23
24 ! Arguments:
25 INTEGER, INTENT (IN) :: itau
26 REAL :: ucov(ip1jmp1, llm), masse(ip1jmp1, llm)
27 real, intent(in):: teta(ip1jmp1, llm)
28 REAL :: ps(ip1jmp1), phis(ip1jmp1)
29 REAL :: vorpot(ip1jm, llm)
30 REAL :: phi(ip1jmp1, llm), bern(ip1jmp1, llm)
31 REAL :: dp(ip1jmp1)
32 REAL, INTENT (IN):: time_0
33 REAL, INTENT (IN):: pk(ip1jmp1, llm)
34
35 ! Local:
36 REAL :: vor(ip1jm), bernf(ip1jmp1, llm), ztotl(llm)
37 REAL :: etotl(llm), stotl(llm), rmsvl(llm), angl(llm), ge(ip1jmp1)
38 REAL :: cosphi(ip1jm), omegcosp(ip1jm)
39 REAL :: dtvrs1j, rjour, heure, radsg, radomeg
40 real massebxy(ip1jm, llm)
41 INTEGER :: l, ij, imjmp1
42 REAL :: ssum
43 real time
44
45 !-----------------------------------------------------------------------
46
47 time = real(itau) / day_step + time_0
48 dtvrs1j = dtvr/daysec
49 rjour = real(int(itau*dtvrs1j))
50 heure = (itau*dtvrs1j-rjour)*24.
51 imjmp1 = iim*jjp1
52 IF (abs(heure-24.)<=0.0001) heure = 0.
53
54 CALL massbarxy(masse, massebxy)
55
56 ! Calcul de rmsdpdt
57 ge(:) = dp(:)*dp(:)
58 rmsdpdt = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
59 rmsdpdt = daysec*1.E-2*sqrt(rmsdpdt/imjmp1)
60 CALL scopy(ijp1llm, bern, 1, bernf, 1)
61 CALL filtreg(bernf, jjp1, llm, -2, 2, .TRUE., 1)
62
63 ! Calcul du moment angulaire
64 radsg = rad/g
65 radomeg = rad*omeg
66 DO ij = iip2, ip1jm
67 cosphi(ij) = cos(rlatu((ij-1)/iip1+1))
68 omegcosp(ij) = radomeg*cosphi(ij)
69 END DO
70
71 ! Calcul de l'energie, de l'enstrophie, de l'entropie et de rmsv
72 DO l = 1, llm
73 DO ij = 1, ip1jm
74 vor(ij) = vorpot(ij, l)*vorpot(ij, l)*massebxy(ij, l)
75 END DO
76 ztotl(l) = (ssum(ip1jm, vor, 1)-ssum(jjm, vor, iip1))
77
78 DO ij = 1, ip1jmp1
79 ge(ij) = masse(ij, l) * (phis(ij) + teta(ij, l) * pk(ij, l) &
80 + bernf(ij, l)-phi(ij, l))
81 END DO
82 etotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
83
84 DO ij = 1, ip1jmp1
85 ge(ij) = masse(ij, l)*teta(ij, l)
86 END DO
87 stotl(l) = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
88
89 DO ij = 1, ip1jmp1
90 ge(ij) = masse(ij, l)*amax1(bernf(ij, l)-phi(ij, l), 0.)
91 END DO
92 rmsvl(l) = 2.*(ssum(ip1jmp1, ge, 1)-ssum(jjp1, ge, iip1))
93
94 DO ij = iip2, ip1jm
95 ge(ij) = (ucov(ij, l)/cu(ij)+omegcosp(ij))*masse(ij, l)*cosphi(ij)
96 END DO
97 angl(l) = radsg * (ssum(ip1jm-iip1, ge(iip2), 1) &
98 - ssum(jjm-1, ge(iip2), iip1))
99 END DO
100
101 DO ij = 1, ip1jmp1
102 ge(ij) = ps(ij)*aire(ij)
103 END DO
104 ptot = ssum(ip1jmp1, ge, 1) - ssum(jjp1, ge, iip1)
105 etot = ssum(llm, etotl, 1)
106 ztot = ssum(llm, ztotl, 1)
107 stot = ssum(llm, stotl, 1)
108 rmsv = ssum(llm, rmsvl, 1)
109 ang = ssum(llm, angl, 1)
110
111 IF (ptot0 == 0.) THEN
112 PRINT *, 'WARNING!!! On recalcule les valeurs initiales de :'
113 PRINT *, 'ptot, rmsdpdt, etot, ztot, stot, rmsv, ang'
114 PRINT *, ptot, rmsdpdt, etot, ztot, stot, rmsv, ang
115 etot0 = etot
116 ptot0 = ptot
117 ztot0 = ztot
118 stot0 = stot
119 ang0 = ang
120 END IF
121
122 etot = etot/etot0
123 rmsv = sqrt(rmsv/ptot)
124 ptot = ptot/ptot0
125 ztot = ztot/ztot0
126 stot = stot/stot0
127 ang = ang/ang0
128
129 PRINT 3500, itau, int(day_ini + time), heure, time
130 PRINT 4000, ptot, rmsdpdt, etot, ztot, stot, rmsv, ang
131
132 3500 FORMAT (4X, 'pas', I7, 5X, 'jour', i5, 1X, 'heure', F5.1, 4X, 'date', &
133 F10.5)
134 4000 FORMAT (10X, 'masse', 4X, 'rmsdpdt', 7X, 'energie', 2X, 'enstrophie', &
135 2X, 'entropie', 3X, 'rmsv', 4X, 'mt.ang', /, 'GLOB ', F10.6, &
136 E13.6, 5F10.3/)
137
138 END SUBROUTINE sortvarc
139
140 end module sortvarc_m

  ViewVC Help
Powered by ViewVC 1.1.21