source: trunk/libf/dyn3dpar/sortvarc.F @ 109

Last change on this file since 109 was 101, checked in by slebonnois, 14 years ago

SL: modifications pour arriver a compiler le gcm VENUS !
Ca marche !
A noter: modifs de makelmdz

File size: 4.6 KB
Line 
1!
2! $Id: sortvarc.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4      SUBROUTINE sortvarc
5     $(itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time ,
6     $ vcov )
7
8      use control_mod,only:resetvarc
9      IMPLICIT NONE
10
11c=======================================================================
12c
13c   Auteur:    P. Le Van
14c   -------
15c
16c   Objet:
17c   ------
18c
19c   sortie des variables de controle
20c
21c=======================================================================
22c-----------------------------------------------------------------------
23c   Declarations:
24c   -------------
25
26#include "dimensions.h"
27#include "paramet.h"
28#include "comconst.h"
29#include "comvert.h"
30#include "comgeom.h"
31#include "ener.h"
32#include "logic.h"
33#include "temps.h"
34
35c   Arguments:
36c   ----------
37
38      INTEGER itau
39      REAL ucov(ip1jmp1,llm),teta(ip1jmp1,llm),masse(ip1jmp1,llm)
40      REAL vcov(ip1jm,llm)
41      REAL ps(ip1jmp1),phis(ip1jmp1)
42      REAL vorpot(ip1jm,llm)
43      REAL phi(ip1jmp1,llm),bern(ip1jmp1,llm)
44      REAL dp(ip1jmp1)
45      REAL time
46      REAL pk(ip1jmp1,llm)
47
48c   Local:
49c   ------
50
51      REAL vor(ip1jm),bernf(ip1jmp1,llm),ztotl(llm)
52      REAL etotl(llm),stotl(llm),rmsvl(llm),angl(llm),ge(ip1jmp1)
53      REAL cosphi(ip1jm),omegcosp(ip1jm)
54      REAL dtvrs1j,rjour,heure,radsg,radomeg
55      REAL rday, massebxy(ip1jm,llm)
56      INTEGER  l, ij, imjmp1
57
58      REAL       SSUM
59
60      logical  firstcal
61      data     firstcal/.true./
62      save     firstcal
63
64c-----------------------------------------------------------------------
65
66       dtvrs1j   = dtvr/daysec
67       rjour     = REAL( INT( itau * dtvrs1j ))
68       heure     = ( itau*dtvrs1j-rjour ) * 24.
69       imjmp1    = iim * jjp1
70       IF(ABS(heure - 24.).LE.0.0001 ) heure = 0.
71c
72       CALL massbarxy ( masse, massebxy )
73
74c   .....  Calcul  de  rmsdpdt  .....
75
76       ge(:)=dp(:)*dp(:)
77
78       rmsdpdt = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
79c
80       rmsdpdt = daysec* 1.e-2 * SQRT(rmsdpdt/imjmp1)
81
82       CALL SCOPY( ijp1llm,bern,1,bernf,1 )
83       CALL filtreg(bernf,jjp1,llm,-2,2,.TRUE.,1)
84
85c   .....  Calcul du moment  angulaire   .....
86
87       radsg    = rad /g
88       radomeg  = rad * omeg
89c
90       DO ij=iip2,ip1jm
91          cosphi( ij ) = COS(rlatu((ij-1)/iip1+1))
92          omegcosp(ij) = radomeg   * cosphi(ij)
93       ENDDO
94
95c  ...  Calcul  de l'energie,de l'enstrophie,de l'entropie et de rmsv  .
96
97       DO l=1,llm
98          DO ij = 1,ip1jm
99             vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
100          ENDDO
101          ztotl(l)=(SSUM(ip1jm,vor,1)-SSUM(jjm,vor,iip1))
102
103          DO ij = 1,ip1jmp1
104             ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l)  +
105     s        bernf(ij,l)-phi(ij,l))
106          ENDDO
107          etotl(l) = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
108
109          DO   ij   = 1, ip1jmp1
110             ge(ij) = masse(ij,l)*teta(ij,l)
111          ENDDO
112          stotl(l)= SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
113
114          DO ij=1,ip1jmp1
115             ge(ij)=masse(ij,l)*AMAX1(bernf(ij,l)-phi(ij,l),0.)
116          ENDDO
117          rmsvl(l)=2.*(SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1))
118
119          DO ij =iip2,ip1jm
120             ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) *
121     *               cosphi(ij)
122          ENDDO
123          angl(l) = radsg *
124     s    (SSUM(ip1jm-iip1,ge(iip2),1)-SSUM(jjm-1,ge(iip2),iip1))
125      ENDDO
126
127          DO ij=1,ip1jmp1
128            ge(ij)= ps(ij)*aire(ij)
129          ENDDO
130      ptot  = SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1)
131      etot  = SSUM(     llm, etotl, 1 )
132      ztot  = SSUM(     llm, ztotl, 1 )
133      stot  = SSUM(     llm, stotl, 1 )
134      rmsv  = SSUM(     llm, rmsvl, 1 )
135      ang   = SSUM(     llm,  angl, 1 )
136
137      IF (firstcal.and.resetvarc) then
138       rday = REAL(INT(time-jD_ref-jH_ref))
139         PRINT 3500, itau, rday, heure,time
140         PRINT*,'WARNING!!! On recalcule les valeurs initiales de :'
141         PRINT*,'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
142         PRINT *, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
143         etot0 = etot
144         ptot0 = ptot
145         ztot0 = ztot
146         stot0 = stot
147         ang0  = ang
148      END IF
149
150      etot= etot/etot0
151      rmsv= SQRT(rmsv/ptot)
152      ptot= ptot/ptot0
153      ztot= ztot/ztot0
154      stot= stot/stot0
155      ang = ang /ang0
156
157      firstcal = .false.
158
159      PRINT 3500, itau, rday, heure, time
160      PRINT 4000, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
161
162      RETURN
163
1643500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f9.0,'heure',f5.1,4x
165     *   ,'date',f14.4,4x,10("*"))
1664000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
167     * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB  '
168     .  ,f10.6,e13.6,5f10.3/
169     * )
170      END
171
Note: See TracBrowser for help on using the repository browser.