source: trunk/LMDZ.COMMON/libf/dyn3d_common/sortvarc0.F

Last change on this file 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: 3.8 KB
Line 
1!
2! $Id: sortvarc0.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4      SUBROUTINE sortvarc0
5     $(itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time ,
6     $ vcov)
7
8      USE comconst_mod, ONLY: daysec,dtvr,rad,g,omeg
9      USE ener_mod, ONLY: etot0,ptot0,ztot0,stot0,ang0,rmsv,rmsdpdt
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      REAL       SSUM
56      integer  ismin,ismax
57
58c-----------------------------------------------------------------------
59
60       dtvrs1j   = dtvr/daysec
61       rjour     = REAL( INT( itau * dtvrs1j ))
62       heure     = ( itau*dtvrs1j-rjour ) * 24.
63       imjmp1    = iim * jjp1
64       IF(ABS(heure - 24.).LE.0.0001 ) heure = 0.
65c
66       CALL massbarxy ( masse, massebxy )
67
68c   .....  Calcul  de  rmsdpdt  .....
69
70       ge=dp*dp
71
72       rmsdpdt = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
73c
74       rmsdpdt = daysec* 1.e-2 * SQRT(rmsdpdt/imjmp1)
75
76       CALL SCOPY( ijp1llm,bern,1,bernf,1 )
77       CALL filtreg(bernf,jjp1,llm,-2,2,.TRUE.,1)
78
79c   .....  Calcul du moment  angulaire   .....
80
81       radsg    = rad /g
82       radomeg  = rad * omeg
83c
84       DO ij=iip2,ip1jm
85          cosphi( ij ) = COS(rlatu((ij-1)/iip1+1))
86          omegcosp(ij) = radomeg   * cosphi(ij)
87       ENDDO
88
89c  ...  Calcul  de l'energie,de l'enstrophie,de l'entropie et de rmsv  .
90
91       DO l=1,llm
92          DO ij = 1,ip1jm
93             vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
94          ENDDO
95          ztotl(l)=(SSUM(ip1jm,vor,1)-SSUM(jjm,vor,iip1))
96
97          DO ij = 1,ip1jmp1
98             ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l)  +
99     s        bernf(ij,l)-phi(ij,l))
100          ENDDO
101          etotl(l) = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
102
103          DO   ij   = 1, ip1jmp1
104             ge(ij) = masse(ij,l)*teta(ij,l)
105          ENDDO
106          stotl(l)= SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
107
108          DO ij=1,ip1jmp1
109             ge(ij)=masse(ij,l)*AMAX1(bernf(ij,l)-phi(ij,l),0.)
110          ENDDO
111          rmsvl(l)=2.*(SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1))
112
113          DO ij =iip2,ip1jm
114             ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) *
115     *               cosphi(ij)
116          ENDDO
117          angl(l) = rad *
118     s    (SSUM(ip1jm-iip1,ge(iip2),1)-SSUM(jjm-1,ge(iip2),iip1))
119      ENDDO
120
121          DO ij=1,ip1jmp1
122            ge(ij)= ps(ij)*aire(ij)
123          ENDDO
124      ptot0  = SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1)
125      etot0  = SSUM(     llm, etotl, 1 )
126      ztot0  = SSUM(     llm, ztotl, 1 )
127      stot0  = SSUM(     llm, stotl, 1 )
128      rmsv   = SSUM(     llm, rmsvl, 1 )
129      ang0   = SSUM(     llm,  angl, 1 )
130
131      rday = REAL(INT (time ))
132c
133      PRINT 3500, itau, rday, heure, time
134      PRINT *, ptot0,etot0,ztot0,stot0,ang0
135
1363500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f5.0,'heure',f5.1,4x
137     *   ,'date',f10.5,4x,10("*"))
138      RETURN
139      END
140
Note: See TracBrowser for help on using the repository browser.