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

Annotation of /trunk/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log


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

  ViewVC Help
Powered by ViewVC 1.1.21