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

Last change on this file since 5348 was 5285, checked in by abarral, 5 weeks ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

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