LMDZ
sortvarc.F
Go to the documentation of this file.
1 !
2 ! $Id: sortvarc.F 2083 2014-07-09 14:43:31Z 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  IMPLICIT NONE
10 
11 
12 c=======================================================================
13 c
14 c Auteur: P. Le Van
15 c -------
16 c
17 c Objet:
18 c ------
19 c
20 c sortie des variables de controle
21 c
22 c=======================================================================
23 c-----------------------------------------------------------------------
24 c Declarations:
25 c -------------
26 
27  include "dimensions.h"
28  include "paramet.h"
29  include "comconst.h"
30  include "comvert.h"
31  include "comgeom.h"
32  include "ener.h"
33  include "logic.h"
34  include "temps.h"
35  include "iniprint.h"
36 
37 c Arguments:
38 c ----------
39 
40  INTEGER,INTENT(IN) :: itau
41  REAL,INTENT(IN) :: ucov(ip1jmp1,llm)
42  REAL,INTENT(IN) :: teta(ip1jmp1,llm)
43  REAL,INTENT(IN) :: masse(ip1jmp1,llm)
44  REAL,INTENT(IN) :: vcov(ip1jm,llm)
45  REAL,INTENT(IN) :: ps(ip1jmp1)
46  REAL,INTENT(IN) :: phis(ip1jmp1)
47  REAL,INTENT(IN) :: vorpot(ip1jm,llm)
48  REAL,INTENT(IN) :: phi(ip1jmp1,llm)
49  REAL,INTENT(IN) :: bern(ip1jmp1,llm)
50  REAL,INTENT(IN) :: dp(ip1jmp1)
51  REAL,INTENT(IN) :: time
52  REAL,INTENT(IN) :: pk(ip1jmp1,llm)
53 
54 c Local:
55 c ------
56 
57  REAL vor(ip1jm),bernf(ip1jmp1,llm),ztotl(llm)
58  REAL etotl(llm),stotl(llm),rmsvl(llm),angl(llm),ge(ip1jmp1)
59  REAL cosphi(ip1jm),omegcosp(ip1jm)
60  REAL dtvrs1j,rjour,heure,radsg,radomeg
61  REAL massebxy(ip1jm,llm)
62  INTEGER l, ij, imjmp1
63 
64  REAL SSUM
65  LOGICAL,SAVE :: firstcal=.true.
66  CHARACTER(LEN=*),PARAMETER :: modname="sortvarc"
67 
68 c-----------------------------------------------------------------------
69 ! Ehouarn: when no initialization fields from file, resetvarc should be
70 ! set to false
71  if (firstcal) then
72  if (.not.read_start) then
73  resetvarc=.true.
74  endif
75  endif
76 
77  dtvrs1j = dtvr/daysec
78  rjour = REAL( int( itau * dtvrs1j ))
79  heure = ( itau*dtvrs1j-rjour ) * 24.
80  imjmp1 = iim * jjp1
81  IF(abs(heure - 24.).LE.0.0001 ) heure = 0.
82 c
83  CALL massbarxy ( masse, massebxy )
84 
85 c ..... Calcul de rmsdpdt .....
86 
87  ge(:)=dp(:)*dp(:)
88 
89  rmsdpdt = ssum(ip1jmp1,ge,1) - ssum(jjp1,ge,iip1)
90 c
91  rmsdpdt = daysec* 1.e-2 * sqrt(rmsdpdt/imjmp1)
92 
93  CALL scopy( ijp1llm,bern,1,bernf,1 )
94  CALL filtreg(bernf,jjp1,llm,-2,2,.true.,1)
95 
96 c ..... Calcul du moment angulaire .....
97 
98  radsg = rad /g
99  radomeg = rad * omeg
100 c
101  DO ij=iip2,ip1jm
102  cosphi( ij ) = cos(rlatu((ij-1)/iip1+1))
103  omegcosp(ij) = radomeg * cosphi(ij)
104  ENDDO
105 
106 c ... Calcul de l'energie,de l'enstrophie,de l'entropie et de rmsv .
107 
108  DO l=1,llm
109  DO ij = 1,ip1jm
110  vor(ij)=vorpot(ij,l)*vorpot(ij,l)*massebxy(ij,l)
111  ENDDO
112  ztotl(l)=(ssum(ip1jm,vor,1)-ssum(jjm,vor,iip1))
113 
114  DO ij = 1,ip1jmp1
115  ge(ij)= masse(ij,l)*(phis(ij)+teta(ij,l)*pk(ij,l) +
116  s bernf(ij,l)-phi(ij,l))
117  ENDDO
118  etotl(l) = ssum(ip1jmp1,ge,1) - ssum(jjp1,ge,iip1)
119 
120  DO ij = 1, ip1jmp1
121  ge(ij) = masse(ij,l)*teta(ij,l)
122  ENDDO
123  stotl(l)= ssum(ip1jmp1,ge,1) - ssum(jjp1,ge,iip1)
124 
125  DO ij=1,ip1jmp1
126  ge(ij)=masse(ij,l)*amax1(bernf(ij,l)-phi(ij,l),0.)
127  ENDDO
128  rmsvl(l)=2.*(ssum(ip1jmp1,ge,1)-ssum(jjp1,ge,iip1))
129 
130  DO ij =iip2,ip1jm
131  ge(ij)=(ucov(ij,l)/cu(ij)+omegcosp(ij))*masse(ij,l) *
132  * cosphi(ij)
133  ENDDO
134  angl(l) = rad *
135  s (ssum(ip1jm-iip1,ge(iip2),1)-ssum(jjm-1,ge(iip2),iip1))
136  ENDDO
137 
138  DO ij=1,ip1jmp1
139  ge(ij)= ps(ij)*aire(ij)
140  ENDDO
141  ptot = ssum(ip1jmp1,ge,1)-ssum(jjp1,ge,iip1)
142  etot = ssum( llm, etotl, 1 )
143  ztot = ssum( llm, ztotl, 1 )
144  stot = ssum( llm, stotl, 1 )
145  rmsv = ssum( llm, rmsvl, 1 )
146  ang = ssum( llm, angl, 1 )
147 
148  IF (firstcal.and.resetvarc) then
149  WRITE(lunout,3500) itau, rjour, heure, time
150  WRITE(lunout,*) trim(modname),
151  & ' WARNING!!! Recomputing initial values of : '
152  WRITE(lunout,*) 'ptot,rmsdpdt,etot,ztot,stot,rmsv,ang'
154  etot0 = etot
155  ptot0 = ptot
156  ztot0 = ztot
157  stot0 = stot
158  ang0 = ang
159  END IF
160 
161  ! compute relative changes in etot,... (except if 'reference' values
162  ! are zero, which can happen when using iniacademic)
163  if (etot0.ne.0) then
164  etot= etot/etot0
165  else
166  etot=1.
167  endif
168  rmsv= sqrt(rmsv/ptot)
169  if (ptot0.ne.0) then
170  ptot= ptot/ptot0
171  else
172  ptot=1.
173  endif
174  if (ztot0.ne.0) then
175  ztot= ztot/ztot0
176  else
177  ztot=1.
178  endif
179  if (stot0.ne.0) then
180  stot= stot/stot0
181  else
182  stot=1.
183  endif
184  if (ang0.ne.0) then
185  ang = ang /ang0
186  else
187  ang=1.
188  endif
189 
190  firstcal = .false.
191 
192  WRITE(lunout,3500) itau, rjour, heure, time
193  WRITE(lunout,4000) ptot,rmsdpdt,etot,ztot,stot,rmsv,ang
194 
195 3500 FORMAT(10("*"),4x,'pas',i7,5x,'jour',f9.0,'heure',f5.1,4x
196  * ,'date',f14.4,4x,10("*"))
197 4000 FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
198  * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB '
199  . ,f10.6,e13.6,5f10.3/
200  * )
201  END
202 
!$Header iip2
Definition: paramet.h:14
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
!$Id mode_top_bound COMMON comconstr g
Definition: comconst.h:7
!$Id ysinus read_start
Definition: logic.h:10
subroutine massbarxy(masse, massebxy)
Definition: massbarxy.F90:2
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
!$Id && ang
Definition: ener.h:11
!$Header!CDK comgeom COMMON comgeom aire
Definition: comgeom.h:25
!$Header!CDK comgeom COMMON comgeom rlatu
Definition: comgeom.h:25
subroutine scopy(n, sx, incx, sy, incy)
Definition: cray.F:9
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
!$Id etot0
Definition: ener.h:11
!$Id ptot
Definition: ener.h:11
!$Id mode_top_bound COMMON comconstr rad
Definition: comconst.h:7
!$Header jjp1
Definition: paramet.h:14
!$Id etot
Definition: ener.h:11
!$Id rmsdpdt
Definition: ener.h:11
!$Id mode_top_bound COMMON comconstr daysec
Definition: comconst.h:7
!$Id ztot0
Definition: ener.h:11
!$Id ***************************************!ECRITURE DU phis
Definition: write_histrac.h:9
!$Header!c c INCLUDE fxyprim h c c c Fonctions in line c c REAL fyprim REAL rj c c il faut la calculer avant d appeler ces fonctions c c c Fonctions a changer selon x(x) et y(y) choisis.c-----------------------------------------------------------------c c.....ici
logical, save resetvarc
Definition: control_mod.F90:40
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
!$Id!Parameters for parameters that control the rate of approach!to quasi equilibrium noff nlm real tlcrit real entp real sigd real coeffs real dtmax real cu real betad real damp real delta COMMON cvparam nlm tlcrit sigd coeffs cu
Definition: cvparam.h:12
!$Id mode_top_bound COMMON comconstr dtvr
Definition: comconst.h:7
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
subroutine filtreg(champ, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg.F:6
!$Id stot0
Definition: ener.h:11
!$Id stot
Definition: ener.h:11
!$Id ztot
Definition: ener.h:11
!$Id && rmsv
Definition: ener.h:11
!$Id ptot0
Definition: ener.h:11
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7
subroutine sortvarc(itau, ucov, teta, ps, masse, pk, phis, vorpot, phi, bern, dp, time, vcov)
Definition: sortvarc.F:7