source: LMDZ5/trunk/libf/dyn3d_common/sortvarc.F @ 2601

Last change on this file since 2601 was 2601, checked in by Ehouarn Millour, 8 years ago

Cleanup in the dynamics: turn temps.h into module temps_mod.F90
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.5 KB
Line 
1!
2! $Id: sortvarc.F 2601 2016-07-24 09:51:55Z emillour $
3!
4      SUBROUTINE sortvarc
5     $(itau,ucov,teta,ps,masse,pk,phis,vorpot,phi,bern,dp,time ,
6     $ vcov )
7
8      USE control_mod, ONLY: resetvarc
9      USE comconst_mod, ONLY: dtvr, daysec, g, rad, omeg
10      IMPLICIT NONE
11
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      INCLUDE "ener.h"
32      INCLUDE "logic.h"
33      INCLUDE "iniprint.h"
34
35c   Arguments:
36c   ----------
37
38      INTEGER,INTENT(IN) :: itau
39      REAL,INTENT(IN) :: ucov(ip1jmp1,llm)
40      REAL,INTENT(IN) :: teta(ip1jmp1,llm)
41      REAL,INTENT(IN) :: masse(ip1jmp1,llm)
42      REAL,INTENT(IN) :: vcov(ip1jm,llm)
43      REAL,INTENT(IN) :: ps(ip1jmp1)
44      REAL,INTENT(IN) :: phis(ip1jmp1)
45      REAL,INTENT(IN) :: vorpot(ip1jm,llm)
46      REAL,INTENT(IN) :: phi(ip1jmp1,llm)
47      REAL,INTENT(IN) :: bern(ip1jmp1,llm)
48      REAL,INTENT(IN) :: dp(ip1jmp1)
49      REAL,INTENT(IN) :: time
50      REAL,INTENT(IN) :: pk(ip1jmp1,llm)
51
52c   Local:
53c   ------
54
55      REAL vor(ip1jm),bernf(ip1jmp1,llm),ztotl(llm)
56      REAL etotl(llm),stotl(llm),rmsvl(llm),angl(llm),ge(ip1jmp1)
57      REAL cosphi(ip1jm),omegcosp(ip1jm)
58      REAL dtvrs1j,rjour,heure,radsg,radomeg
59      REAL massebxy(ip1jm,llm)
60      INTEGER  l, ij, imjmp1
61
62      REAL       SSUM
63      LOGICAL,SAVE :: firstcal=.true.
64      CHARACTER(LEN=*),PARAMETER :: modname="sortvarc"
65
66c-----------------------------------------------------------------------
67! Ehouarn: when no initialization fields from file, resetvarc should be
68!          set to false
69       if (firstcal) then
70         if (.not.read_start) then
71           resetvarc=.true.
72         endif
73       endif
74
75       dtvrs1j   = dtvr/daysec
76       rjour     = REAL( INT( itau * dtvrs1j ))
77       heure     = ( itau*dtvrs1j-rjour ) * 24.
78       imjmp1    = iim * jjp1
79       IF(ABS(heure - 24.).LE.0.0001 ) heure = 0.
80c
81       CALL massbarxy ( masse, massebxy )
82
83c   .....  Calcul  de  rmsdpdt  .....
84
85       ge(:)=dp(:)*dp(:)
86
87       rmsdpdt = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
88c
89       rmsdpdt = daysec* 1.e-2 * SQRT(rmsdpdt/imjmp1)
90
91       CALL SCOPY( ijp1llm,bern,1,bernf,1 )
92       CALL filtreg(bernf,jjp1,llm,-2,2,.TRUE.,1)
93
94c   .....  Calcul du moment  angulaire   .....
95
96       radsg    = rad /g
97       radomeg  = rad * omeg
98c
99       DO ij=iip2,ip1jm
100          cosphi( ij ) = COS(rlatu((ij-1)/iip1+1))
101          omegcosp(ij) = radomeg   * cosphi(ij)
102       ENDDO
103
104c  ...  Calcul  de l'energie,de l'enstrophie,de l'entropie et de rmsv  .
105
106       DO l=1,llm
107          DO ij = 1,ip1jm
108             vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
109          ENDDO
110          ztotl(l)=(SSUM(ip1jm,vor,1)-SSUM(jjm,vor,iip1))
111
112          DO ij = 1,ip1jmp1
113             ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l)  +
114     s        bernf(ij,l)-phi(ij,l))
115          ENDDO
116          etotl(l) = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
117
118          DO   ij   = 1, ip1jmp1
119             ge(ij) = masse(ij,l)*teta(ij,l)
120          ENDDO
121          stotl(l)= SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
122
123          DO ij=1,ip1jmp1
124             ge(ij)=masse(ij,l)*AMAX1(bernf(ij,l)-phi(ij,l),0.)
125          ENDDO
126          rmsvl(l)=2.*(SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1))
127
128          DO ij =iip2,ip1jm
129             ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) *
130     *               cosphi(ij)
131          ENDDO
132          angl(l) = rad *
133     s    (SSUM(ip1jm-iip1,ge(iip2),1)-SSUM(jjm-1,ge(iip2),iip1))
134      ENDDO
135
136          DO ij=1,ip1jmp1
137            ge(ij)= ps(ij)*aire(ij)
138          ENDDO
139      ptot  = SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1)
140      etot  = SSUM(     llm, etotl, 1 )
141      ztot  = SSUM(     llm, ztotl, 1 )
142      stot  = SSUM(     llm, stotl, 1 )
143      rmsv  = SSUM(     llm, rmsvl, 1 )
144      ang   = SSUM(     llm,  angl, 1 )
145
146      IF (firstcal.and.resetvarc) then
147         WRITE(lunout,3500) itau, rjour, heure, time
148         WRITE(lunout,*) trim(modname),
149     &     ' WARNING!!! Recomputing initial values of : '
150         WRITE(lunout,*) 'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
151         WRITE(lunout,*) ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
152         etot0 = etot
153         ptot0 = ptot
154         ztot0 = ztot
155         stot0 = stot
156         ang0  = ang
157      END IF
158
159      ! compute relative changes in etot,... (except if 'reference' values
160      ! are zero, which can happen when using iniacademic)
161      if (etot0.ne.0) then
162        etot= etot/etot0
163      else
164        etot=1.
165      endif
166      rmsv= SQRT(rmsv/ptot)
167      if (ptot0.ne.0) then
168        ptot= ptot/ptot0
169      else
170        ptot=1.
171      endif
172      if (ztot0.ne.0) then
173        ztot= ztot/ztot0
174      else
175        ztot=1.
176      endif
177      if (stot0.ne.0) then
178        stot= stot/stot0
179      else
180        stot=1.
181      endif
182      if (ang0.ne.0) then
183        ang = ang /ang0
184      else
185        ang=1.
186      endif
187
188      firstcal = .false.
189
190      WRITE(lunout,3500) itau, rjour, heure, time
191      WRITE(lunout,4000) ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
192
1933500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f9.0,'heure',f5.1,4x
194     *   ,'date',f14.4,4x,10("*"))
1954000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
196     * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB  '
197     .  ,f10.6,e13.6,5f10.3/
198     * )
199      END
200
Note: See TracBrowser for help on using the repository browser.