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

Contents of /trunk/libf/dyn3d/sortvarc.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3 - (show annotations)
Wed Feb 27 13:16:39 2008 UTC (16 years, 2 months ago) by guez
File size: 4539 byte(s)
Initial import
1 !
2 ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/sortvarc.F,v 1.1.1.1 2004/05/19 12:53:07 lmdzadmin Exp $
3 !
4 SUBROUTINE sortvarc
5 $(itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time ,
6 $ vcov )
7
8 c=======================================================================
9 c
10 c Auteur: P. Le Van
11 c -------
12 c
13 c Objet:
14 c ------
15 c
16 c sortie des variables de controle
17 c
18 c=======================================================================
19 c-----------------------------------------------------------------------
20 c Declarations:
21 c -------------
22
23 use dimens_m
24 use paramet_m
25 use comconst
26 use comvert
27 use logic
28 use comgeom
29 use temps
30 use ener
31 IMPLICIT NONE
32
33 c Arguments:
34 c ----------
35
36 INTEGER, intent(in):: itau
37 REAL ucov(ip1jmp1,llm),teta(ip1jmp1,llm),masse(ip1jmp1,llm)
38 REAL vcov(ip1jm,llm)
39 REAL ps(ip1jmp1),phis(ip1jmp1)
40 REAL vorpot(ip1jm,llm)
41 REAL phi(ip1jmp1,llm),bern(ip1jmp1,llm)
42 REAL dp(ip1jmp1)
43 REAL time
44 REAL, intent(in):: pk(ip1jmp1,llm)
45
46 c Local:
47 c ------
48
49 REAL vor(ip1jm),bernf(ip1jmp1,llm),ztotl(llm)
50 REAL etotl(llm),stotl(llm),rmsvl(llm),angl(llm),ge(ip1jmp1)
51 REAL cosphi(ip1jm),omegcosp(ip1jm)
52 REAL dtvrs1j,rjour,heure,radsg,radomeg
53 REAL rday, massebxy(ip1jm,llm)
54 INTEGER l, ij, imjmp1
55
56 REAL SSUM
57
58 c-----------------------------------------------------------------------
59
60 dtvrs1j = dtvr/daysec
61 rjour = FLOAT( INT( itau * dtvrs1j ))
62 heure = ( itau*dtvrs1j-rjour ) * 24.
63 imjmp1 = iim * jjp1
64 IF(ABS(heure - 24.).LE.0.0001 ) heure = 0.
65 c
66 CALL massbarxy ( masse, massebxy )
67
68 c ..... Calcul de rmsdpdt .....
69
70 ge(:)=dp(:)*dp(:)
71
72 rmsdpdt = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
73 c
74 rmsdpdt = daysec* 1.e-2 * SQRT(rmsdpdt/imjmp1)
75
76 CALL SCOPY( ijp1llm,bern,1,bernf,1 )
77 CALL filtreg(bernf,jjp1,llm,-2,2,.TRUE.,1)
78
79 c ..... Calcul du moment angulaire .....
80
81 radsg = rad /g
82 radomeg = rad * omeg
83 c
84 DO ij=iip2,ip1jm
85 cosphi( ij ) = COS(rlatu((ij-1)/iip1+1))
86 omegcosp(ij) = radomeg * cosphi(ij)
87 ENDDO
88
89 c ... Calcul de l'energie,de l'enstrophie,de l'entropie et de rmsv .
90
91 DO l=1,llm
92 DO ij = 1,ip1jm
93 vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
94 ENDDO
95 ztotl(l)=(SSUM(ip1jm,vor,1)-SSUM(jjm,vor,iip1))
96
97 DO ij = 1,ip1jmp1
98 ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l) +
99 s bernf(ij,l)-phi(ij,l))
100 ENDDO
101 etotl(l) = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
102
103 DO ij = 1, ip1jmp1
104 ge(ij) = masse(ij,l)*teta(ij,l)
105 ENDDO
106 stotl(l)= SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
107
108 DO ij=1,ip1jmp1
109 ge(ij)=masse(ij,l)*AMAX1(bernf(ij,l)-phi(ij,l),0.)
110 ENDDO
111 rmsvl(l)=2.*(SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1))
112
113 DO ij =iip2,ip1jm
114 ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) *
115 * cosphi(ij)
116 ENDDO
117 angl(l) = radsg *
118 s (SSUM(ip1jm-iip1,ge(iip2),1)-SSUM(jjm-1,ge(iip2),iip1))
119 ENDDO
120
121 DO ij=1,ip1jmp1
122 ge(ij)= ps(ij)*aire(ij)
123 ENDDO
124 ptot = SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1)
125 etot = SSUM( llm, etotl, 1 )
126 ztot = SSUM( llm, ztotl, 1 )
127 stot = SSUM( llm, stotl, 1 )
128 rmsv = SSUM( llm, rmsvl, 1 )
129 ang = SSUM( llm, angl, 1 )
130
131 rday = FLOAT(INT ( day_ini + time ))
132 c
133 IF(ptot0.eq.0.) THEN
134 PRINT 3500, itau, rday, heure,time
135 PRINT*,'WARNING!!! On recalcule les valeurs initiales de :'
136 PRINT*,'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
137 PRINT *, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
138 etot0 = etot
139 ptot0 = ptot
140 ztot0 = ztot
141 stot0 = stot
142 ang0 = ang
143 END IF
144
145 etot= etot/etot0
146 rmsv= SQRT(rmsv/ptot)
147 ptot= ptot/ptot0
148 ztot= ztot/ztot0
149 stot= stot/stot0
150 ang = ang /ang0
151
152
153 PRINT 3500, itau, rday, heure, time
154 PRINT 4000, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
155
156 RETURN
157
158 3500 FORMAT(4x,'pas',i7,5x,'jour',f5.0,'heure',f5.1,4x
159 * ,'date',f10.5)
160 4000 FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
161 * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB '
162 . ,f10.6,e13.6,5f10.3/
163 * )
164 END
165

  ViewVC Help
Powered by ViewVC 1.1.21