source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3d_common/sortvarc.F @ 232

Last change on this file since 232 was 222, checked in by ymipsl, 10 years ago

Creating temporary dynamico/lmdz/saturn branche

YM

File size: 5.2 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 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! Ehouarn: when no initialization fields from file, resetvarc should be
66!          set to false
67       if (firstcal) then
68         if (.not.read_start) then
69           resetvarc=.true.
70         endif
71       endif
72
73       dtvrs1j   = dtvr/daysec
74       rjour     = REAL( INT( itau * dtvrs1j ))
75       heure     = ( itau*dtvrs1j-rjour ) * 24.
76       imjmp1    = iim * jjp1
77       IF(ABS(heure - 24.).LE.0.0001 ) heure = 0.
78c
79       CALL massbarxy ( masse, massebxy )
80
81c   .....  Calcul  de  rmsdpdt  .....
82
83       ge(:)=dp(:)*dp(:)
84
85       rmsdpdt = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
86c
87       rmsdpdt = daysec* 1.e-2 * SQRT(rmsdpdt/imjmp1) 
88
89       CALL SCOPY( ijp1llm,bern,1,bernf,1 )
90       CALL filtreg(bernf,jjp1,llm,-2,2,.TRUE.,1)
91
92c   .....  Calcul du moment  angulaire   .....
93
94       radsg    = rad /g
95       radomeg  = rad * omeg
96c
97       DO ij=iip2,ip1jm
98          cosphi( ij ) = COS(rlatu((ij-1)/iip1+1))
99          omegcosp(ij) = radomeg   * cosphi(ij)
100       ENDDO
101
102c  ...  Calcul  de l'energie,de l'enstrophie,de l'entropie et de rmsv  .
103
104       DO l=1,llm
105          DO ij = 1,ip1jm
106             vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
107          ENDDO
108          ztotl(l)=(SSUM(ip1jm,vor,1)-SSUM(jjm,vor,iip1))
109
110          DO ij = 1,ip1jmp1
111             ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l)  +
112     s        bernf(ij,l)-phi(ij,l))
113          ENDDO
114          etotl(l) = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
115
116          DO   ij   = 1, ip1jmp1
117             ge(ij) = masse(ij,l)*teta(ij,l)
118          ENDDO
119          stotl(l)= SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
120
121          DO ij=1,ip1jmp1
122             ge(ij)=masse(ij,l)*AMAX1(bernf(ij,l)-phi(ij,l),0.)
123          ENDDO
124          rmsvl(l)=2.*(SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1))
125
126          DO ij =iip2,ip1jm
127             ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) *
128     *               cosphi(ij)
129          ENDDO
130          angl(l) = rad *
131     s    (SSUM(ip1jm-iip1,ge(iip2),1)-SSUM(jjm-1,ge(iip2),iip1))
132      ENDDO
133
134          DO ij=1,ip1jmp1
135            ge(ij)= ps(ij)*aire(ij)
136          ENDDO
137      ptot  = SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1)
138      etot  = SSUM(     llm, etotl, 1 )
139      ztot  = SSUM(     llm, ztotl, 1 )
140      stot  = SSUM(     llm, stotl, 1 )
141      rmsv  = SSUM(     llm, rmsvl, 1 )
142      ang   = SSUM(     llm,  angl, 1 )
143
144      IF (firstcal.and.resetvarc) then
145         PRINT 3500, itau, rjour, heure,time
146         PRINT*,'WARNING!!! On recalcule les valeurs initiales de :'
147         PRINT*,'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
148         PRINT *, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
149         etot0 = etot
150         ptot0 = ptot
151         ztot0 = ztot
152         stot0 = stot
153         ang0  = ang
154      END IF
155
156      ! compute relative changes in etot,... (except if 'reference' values
157      ! are zero, which can happen when using iniacademic)
158      if (etot0.ne.0) then
159        etot= etot/etot0
160      else
161        etot=1.
162      endif
163      rmsv= SQRT(rmsv/ptot)
164      if (ptot0.ne.0) then
165        ptot= ptot/ptot0
166      else
167        ptot=1.
168      endif
169      if (ztot0.ne.0) then
170        ztot= ztot/ztot0
171      else
172        ztot=1.
173      endif
174      if (stot0.ne.0) then
175        stot= stot/stot0
176      else
177        stot=1.
178      endif
179      if (ang0.ne.0) then
180        ang = ang /ang0
181      else
182        ang=1.
183      endif
184
185      firstcal = .false.
186
187      PRINT 3500, itau, rjour, heure, time
188      PRINT 4000, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
189
190      RETURN
191
1923500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f9.0,'heure',f5.1,4x 
193     *   ,'date',f14.4,4x,10("*"))
1944000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
195     * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB  '
196     .  ,f10.6,e13.6,5f10.3/
197     * )
198      END
199
Note: See TracBrowser for help on using the repository browser.