source: trunk/LMDZ.GENERIC/libf/dyn3d/sortvarc.F @ 1422

Last change on this file since 1422 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

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