source: LMDZ6/trunk/libf/dyn3d_common/sortvarc.f90 @ 5272

Last change on this file since 5272 was 5272, checked in by abarral, 23 hours ago

Turn paramet.h into a module

  • 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.3 KB
Line 
1!
2! $Id: sortvarc.f90 5272 2024-10-24 15:53:15Z abarral $
3!
4SUBROUTINE 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  USE logic_mod, ONLY: read_start
11  USE ener_mod, ONLY: etot,ptot,ztot,stot,ang, &
12        etot0,ptot0,ztot0,stot0,ang0, &
13        rmsdpdt,rmsv
14  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
15USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
16          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
17IMPLICIT NONE
18
19
20  !=======================================================================
21  !
22  !   Auteur:    P. Le Van
23  !   -------
24  !
25  !   Objet:
26  !   ------
27  !
28  !   sortie des variables de controle
29  !
30  !=======================================================================
31  !-----------------------------------------------------------------------
32  !   Declarations:
33  !   -------------
34
35
36
37  INCLUDE "comgeom.h"
38  INCLUDE "iniprint.h"
39
40  !   Arguments:
41  !   ----------
42
43  INTEGER,INTENT(IN) :: itau
44  REAL,INTENT(IN) :: ucov(ip1jmp1,llm)
45  REAL,INTENT(IN) :: teta(ip1jmp1,llm)
46  REAL,INTENT(IN) :: masse(ip1jmp1,llm)
47  REAL,INTENT(IN) :: vcov(ip1jm,llm)
48  REAL,INTENT(IN) :: ps(ip1jmp1)
49  REAL,INTENT(IN) :: phis(ip1jmp1)
50  REAL,INTENT(IN) :: vorpot(ip1jm,llm)
51  REAL,INTENT(IN) :: phi(ip1jmp1,llm)
52  REAL,INTENT(IN) :: bern(ip1jmp1,llm)
53  REAL,INTENT(IN) :: dp(ip1jmp1)
54  REAL,INTENT(IN) :: time
55  REAL,INTENT(IN) :: pk(ip1jmp1,llm)
56
57  !   Local:
58  !   ------
59
60  REAL :: vor(ip1jm),bernf(ip1jmp1,llm),ztotl(llm)
61  REAL :: etotl(llm),stotl(llm),rmsvl(llm),angl(llm),ge(ip1jmp1)
62  REAL :: cosphi(ip1jm),omegcosp(ip1jm)
63  REAL :: dtvrs1j,rjour,heure,radsg,radomeg
64  REAL :: massebxy(ip1jm,llm)
65  INTEGER :: l, ij, imjmp1
66
67  REAL :: SSUM
68  LOGICAL,SAVE :: firstcal=.true.
69  CHARACTER(LEN=*),PARAMETER :: modname="sortvarc"
70
71  !-----------------------------------------------------------------------
72  ! Ehouarn: when no initialization fields from file, resetvarc should be
73       ! set to false
74   if (firstcal) then
75     if (.not.read_start) then
76       resetvarc=.true.
77     endif
78   endif
79
80   dtvrs1j   = dtvr/daysec
81   rjour     = REAL( INT( itau * dtvrs1j ))
82   heure     = ( itau*dtvrs1j-rjour ) * 24.
83   imjmp1    = iim * jjp1
84   IF(ABS(heure - 24.).LE.0.0001 ) heure = 0.
85  !
86   CALL massbarxy ( masse, massebxy )
87
88  !   .....  Calcul  de  rmsdpdt  .....
89
90   ge(:)=dp(:)*dp(:)
91
92   rmsdpdt = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
93  !
94   rmsdpdt = daysec* 1.e-2 * SQRT(rmsdpdt/imjmp1)
95
96   CALL SCOPY( ijp1llm,bern,1,bernf,1 )
97   CALL filtreg(bernf,jjp1,llm,-2,2,.TRUE.,1)
98
99  !   .....  Calcul du moment  angulaire   .....
100
101   radsg    = rad /g
102   radomeg  = rad * omeg
103  !
104   DO ij=iip2,ip1jm
105      cosphi( ij ) = COS(rlatu((ij-1)/iip1+1))
106      omegcosp(ij) = radomeg   * cosphi(ij)
107   ENDDO
108
109  !  ...  Calcul  de l'energie,de l'enstrophie,de l'entropie et de rmsv  .
110
111   DO l=1,llm
112      DO ij = 1,ip1jm
113         vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
114      ENDDO
115      ztotl(l)=(SSUM(ip1jm,vor,1)-SSUM(jjm,vor,iip1))
116
117      DO ij = 1,ip1jmp1
118         ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l)  + &
119               bernf(ij,l)-phi(ij,l))
120      ENDDO
121      etotl(l) = SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
122
123      DO   ij   = 1, ip1jmp1
124         ge(ij) = masse(ij,l)*teta(ij,l)
125      ENDDO
126      stotl(l)= SSUM(ip1jmp1,ge,1) - SSUM(jjp1,ge,iip1)
127
128      DO ij=1,ip1jmp1
129         ge(ij)=masse(ij,l)*AMAX1(bernf(ij,l)-phi(ij,l),0.)
130      ENDDO
131      rmsvl(l)=2.*(SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1))
132
133      DO ij =iip2,ip1jm
134         ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) * &
135               cosphi(ij)
136      ENDDO
137      angl(l) = rad * &
138            (SSUM(ip1jm-iip1,ge(iip2),1)-SSUM(jjm-1,ge(iip2),iip1))
139  ENDDO
140
141      DO ij=1,ip1jmp1
142        ge(ij)= ps(ij)*aire(ij)
143      ENDDO
144  ptot  = SSUM(ip1jmp1,ge,1)-SSUM(jjp1,ge,iip1)
145  etot  = SSUM(     llm, etotl, 1 )
146  ztot  = SSUM(     llm, ztotl, 1 )
147  stot  = SSUM(     llm, stotl, 1 )
148  rmsv  = SSUM(     llm, rmsvl, 1 )
149  ang   = SSUM(     llm,  angl, 1 )
150
151  IF (firstcal.and.resetvarc) then
152     WRITE(lunout,3500) itau, rjour, heure, time
153     WRITE(lunout,*) trim(modname), &
154           ' WARNING!!! Recomputing initial values of : '
155     WRITE(lunout,*) 'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
156     WRITE(lunout,*) ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
157     etot0 = etot
158     ptot0 = ptot
159     ztot0 = ztot
160     stot0 = stot
161     ang0  = ang
162  END IF
163
164  ! ! compute relative changes in etot,... (except if 'reference' values
165  ! ! are zero, which can happen when using iniacademic)
166  if (etot0.ne.0) then
167    etot= etot/etot0
168  else
169    etot=1.
170  endif
171  rmsv= SQRT(rmsv/ptot)
172  if (ptot0.ne.0) then
173    ptot= ptot/ptot0
174  else
175    ptot=1.
176  endif
177  if (ztot0.ne.0) then
178    ztot= ztot/ztot0
179  else
180    ztot=1.
181  endif
182  if (stot0.ne.0) then
183    stot= stot/stot0
184  else
185    stot=1.
186  endif
187  if (ang0.ne.0) then
188    ang = ang /ang0
189  else
190    ang=1.
191  endif
192
193  firstcal = .false.
194
195  WRITE(lunout,3500) itau, rjour, heure, time
196  WRITE(lunout,4000) ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
197
1983500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f9.0,'heure',f5.1,4x &
199             ,'date',f14.4,4x,10("*"))
2004000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie' &
201             ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB  ' &
202             ,f10.6,e13.6,5f10.3/ &
203             )
204END SUBROUTINE sortvarc
205
Note: See TracBrowser for help on using the repository browser.