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

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

Serie de modifs SL pour homogeneisation des phytitan et phyvenus
Ca touche aussi aux liens phy/dyn (surtout a propos de clesphy0),
a verifier avec les autres, donc...

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