source: trunk/LMDZ.MARS/libf/dyn3d/sortvarc.F @ 937

Last change on this file since 937 was 791, checked in by emillour, 12 years ago

Mars GCM:

Adapted code so that it can run fractions of days: e.g. if "nday=1.5" in

run.def, then run a sol and a half, "nday=0.75" to run three quarters of
a sol... Of course the fraction should correspond to a number of complete
dynamics/physics cycles. The fraction of the sol that a (re)start.nc
file corresponds to is (read)written as 'Time' in the file.

EM

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