source: trunk/LMDZ.MARS/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.6 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 ! elapsed time (in days) since begining of the run
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     = REAL( INT( itau * dtvrs1j ))
64!       heure     = ( itau*dtvrs1j-rjour ) * 24.
65       heure     = (time-floor(time))*24.
66       imjmp1    = iim * jjp1
67       IF(ABS(heure - 24.).LE.0.0001 ) heure = 0.
68c
69       CALL massbarxy ( masse, massebxy )
70
71c   .....  Calcul  de  rmsdpdt  .....
72
73       CALL multipl(ip1jmp1,dp,dp,ge)
74
75       rmsdpdt = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
76c
77       rmsdpdt = daysec* 1.e-2 * SQRT(rmsdpdt/imjmp1)
78
79       CALL SCOPY( ijp1llm,bern,1,bernf,1 )
80       CALL filtreg(bernf,jjp1,llm,-2,2,.TRUE.,1)
81
82c   .....  Calcul du moment  angulaire   .....
83
84       radsg    = rad /g
85       radomeg  = rad * omeg
86c
87       DO ij=iip2,ip1jm
88          cosphi( ij ) = COS(rlatu((ij-1)/iip1+1))
89          omegcosp(ij) = radomeg   * cosphi(ij)
90       ENDDO
91
92c  ...  Calcul  de l'energie,de l'enstrophie,de l'entropie et de rmsv  .
93
94       DO l=1,llm
95          DO ij = 1,ip1jm
96             vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
97          ENDDO
98          ztotl(l)=(SSUM(ip1jm,vor,1)-SSUM(jjm,vor,iip1))
99
100          DO ij = 1,ip1jmp1
101             ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l)  +
102     s        bernf(ij,l)-phi(ij,l))
103          ENDDO
104          etotl(l) = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
105
106          DO   ij   = 1, ip1jmp1
107             ge(ij) = masse(ij,l)*teta(ij,l)
108          ENDDO
109          stotl(l)= SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
110
111          DO ij=1,ip1jmp1
112             ge(ij)=masse(ij,l)*AMAX1(bernf(ij,l)-phi(ij,l),0.)
113          ENDDO
114          rmsvl(l)=2.*(SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1))
115
116          DO ij =iip2,ip1jm
117             ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) *
118     *               cosphi(ij)
119          ENDDO
120          angl(l) = radsg *
121     s    (SSUM(ip1jm-iip1,ge(iip2),1)-SSUM(jjm-1,ge(iip2),iip1))
122      ENDDO
123
124          DO ij=1,ip1jmp1
125            ge(ij)= ps(ij)*aire(ij)
126          ENDDO
127      ptot  = SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1)
128      etot  = SSUM(     llm, etotl, 1 )
129      ztot  = SSUM(     llm, ztotl, 1 )
130      stot  = SSUM(     llm, stotl, 1 )
131      rmsv  = SSUM(     llm, rmsvl, 1 )
132      ang   = SSUM(     llm,  angl, 1 )
133
134      rday = REAL(INT ( day_ini + time ))
135c
136      IF(ptot0.eq.0.)  THEN
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
156      PRINT 3500, itau, rday, heure, time
157      PRINT 4000, ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
158
159      RETURN
160
1613500   FORMAT('0',10(1h*),4x,'pas',i7,5x,'jour',f5.0,'heure',f5.1,4x
162     *   ,'date',f10.5,4x,10(1h*))
1634000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
164     * ,2x,'entropie',3x,'rmsv',4x,'mt.ang'/6x,f10.6,e13.6,5f10.3/
165     * )
166      END
167
Note: See TracBrowser for help on using the repository browser.