source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/disvert_noterre.f90 @ 5139

Last change on this file since 5139 was 5134, checked in by abarral, 4 months ago

Replace academic.h, alpale.h, comdissip.h, comdissipn.h, comdissnew.h by modules
Remove unused clesph0.h

  • 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
File size: 9.2 KB
Line 
1! $Id: $
2SUBROUTINE disvert_noterre
3
4  !    Auteur :  F. Forget Y. Wanherdrick, P. Levan
5  !    Nouvelle version 100% Mars !!
6  !    On l'utilise aussi pour Venus et Titan, legerment modifiee.
7
8  USE IOIPSL
9  USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt, &
10        nivsig,nivsigs,pa,preff,scaleheight
11  USE comconst_mod, ONLY: kappa
12  USE logic_mod, ONLY: hybrid
13  USE lmdz_iniprint, ONLY: lunout, prt_level
14
15  IMPLICIT NONE
16
17  INCLUDE "dimensions.h"
18  INCLUDE "paramet.h"
19  !
20  !=======================================================================
21  !    Discretisation verticale en coordonnée hybride (ou sigma)
22  !
23  !=======================================================================
24  !
25  !   declarations:
26  !   -------------
27  !
28  !
29  INTEGER :: l,ll
30  REAL :: snorm
31  REAL :: alpha,beta,gama,delta,deltaz
32  REAL :: quoi,quand
33  REAL :: zsig(llm),sig(llm+1)
34  INTEGER :: np,ierr
35  INTEGER :: ierr1,ierr2,ierr3,ierr4
36  REAL :: x
37
38  REAL :: newsig
39  REAL :: dz0,dz1,nhaut,sig1,esig,csig,zz
40  REAL :: tt,rr,gg, prevz
41  REAL :: s(llm),dsig(llm)
42
43  INTEGER :: iz
44  REAL :: z, ps,p
45  CHARACTER(LEN=*),parameter :: modname="disvert_noterre"
46
47  !
48  !-----------------------------------------------------------------------
49  !
50  ! Initializations:
51  !  pi=2.*ASIN(1.) ! already done in iniconst
52
53  hybrid=.TRUE. ! default value for hybrid (ie: use hybrid coordinates)
54  CALL getin('hybrid',hybrid)
55  WRITE(lunout,*) trim(modname),': hybrid=',hybrid
56
57  ! Ouverture possible de fichiers typiquement E.T.
58
59     open(99,file="esasig.def",status='old',form='formatted', &
60           iostat=ierr2)
61     IF(ierr2/=0) THEN
62          close(99)
63          open(99,file="z2sig.def",status='old',form='formatted', &
64                iostat=ierr4)
65     endif
66
67  !-----------------------------------------------------------------------
68  !   cas 1 on lit les options dans esasig.def:
69  !   ----------------------------------------
70
71  IF(ierr2==0) THEN
72     ! Lecture de esasig.def :
73     ! Systeme peu souple, mais qui respecte en theorie
74     ! La conservation de l'energie (conversion Energie potentielle
75     ! <-> energie cinetique, d'apres la note de Frederic Hourdin...
76
77     WRITE(lunout,*)'*****************************'
78     WRITE(lunout,*)'WARNING reading esasig.def'
79     WRITE(lunout,*)'*****************************'
80     READ(99,*) scaleheight
81     READ(99,*) dz0
82     READ(99,*) dz1
83     READ(99,*) nhaut
84     CLOSE(99)
85
86     dz0=dz0/scaleheight
87     dz1=dz1/scaleheight
88
89     sig1=(1.-dz1)/tanh(.5*(llm-1)/nhaut)
90
91     esig=1.
92
93     do l=1,20
94        esig=-log((1./sig1-1.)*exp(-dz0)/esig)/(llm-1.)
95     enddo
96     csig=(1./sig1-1.)/(exp(esig)-1.)
97
98     DO L = 2, llm
99        zz=csig*(exp(esig*(l-1.))-1.)
100        sig(l) =1./(1.+zz) &
101              * tanh(.5*(llm+1-l)/nhaut)
102     ENDDO
103     sig(1)=1.
104     sig(llm+1)=0.
105     quoi      = 1. + 2.* kappa
106     s( llm )  = 1.
107     s(llm-1) = quoi
108     IF( llm>2 )  THEN
109        DO  ll = 2, llm-1
110           l         = llm+1 - ll
111           quand     = sig(l+1)/ sig(l)
112           s(l-1)    = quoi * (1.-quand) * s(l)  + quand * s(l+1)
113        ENDDO
114     END IF
115  !
116     snorm=(1.-.5*sig(2)+kappa*(1.-sig(2)))*s(1)+.5*sig(2)*s(2)
117     DO l = 1, llm
118        s(l)    = s(l)/ snorm
119     ENDDO
120
121  !-----------------------------------------------------------------------
122  !   cas 2 on lit les options dans z2sig.def:
123  !   ----------------------------------------
124
125  ELSE IF(ierr4==0) THEN
126     WRITE(lunout,*)'****************************'
127     WRITE(lunout,*)'Reading z2sig.def'
128     WRITE(lunout,*)'****************************'
129
130     READ(99,*) scaleheight
131     do l=1,llm
132        read(99,*) zsig(l)
133     END DO
134     CLOSE(99)
135
136     sig(1) =1
137     do l=2,llm
138       sig(l) = 0.5 * ( exp(-zsig(l)/scaleheight) + &
139             exp(-zsig(l-1)/scaleheight) )
140     END DO
141     sig(llm+1) =0
142
143  !-----------------------------------------------------------------------
144  ELSE
145     WRITE(lunout,*) 'didn t you forget something ??? '
146     WRITE(lunout,*) 'We need file  z2sig.def ! (OR esasig.def)'
147     stop
148  ENDIF
149  !-----------------------------------------------------------------------
150
151  DO l=1,llm
152    nivsigs(l) = REAL(l)
153  ENDDO
154
155  DO l=1,llmp1
156    nivsig(l)= REAL(l)
157  ENDDO
158
159
160  !-----------------------------------------------------------------------
161  !    ....  Calculs  de ap(l) et de bp(l)  ....
162  !    .........................................
163  !
164  !   .....  pa et preff sont lus  sur les fichiers start par dynetat0 .....
165  !-----------------------------------------------------------------------
166  !
167
168  IF (hybrid) then  ! use hybrid coordinates
169     WRITE(lunout,*) "*********************************"
170     WRITE(lunout,*) "Using hybrid vertical coordinates"
171     WRITE(lunout,*)
172     ! Coordonnees hybrides avec mod
173     DO l = 1, llm
174
175     CALL sig_hybrid(sig(l),pa,preff,newsig)
176        bp(l) = EXP( 1. - 1./(newsig**2)  )
177        ap(l) = pa * (newsig - bp(l) )
178     enddo
179     bp(llmp1) = 0.
180     ap(llmp1) = 0.
181  else ! use sigma coordinates
182     WRITE(lunout,*) "********************************"
183     WRITE(lunout,*) "Using sigma vertical coordinates"
184     WRITE(lunout,*)
185     ! Pour ne pas passer en coordonnees hybrides
186     DO l = 1, llm
187        ap(l) = 0.
188        bp(l) = sig(l)
189     ENDDO
190     ap(llmp1) = 0.
191  ENDIF
192
193  bp(llmp1) =   0.
194
195  WRITE(lunout,*) trim(modname),': BP '
196  WRITE(lunout,*)  bp
197  WRITE(lunout,*) trim(modname),': AP '
198  WRITE(lunout,*)  ap
199
200  ! Calcul au milieu des couches :
201  ! WARNING : le choix de placer le milieu des couches au niveau de
202  ! pression intermédiaire est arbitraire et pourrait etre modifié.
203  ! Le calcul du niveau pour la derniere couche
204  ! (on met la meme distance (en log pression)  entre P(llm)
205  ! et P(llm -1) qu'entre P(llm-1) et P(llm-2) ) est
206  ! Specifique.  Ce choix est spécifié ici ET dans exner_milieu.F
207
208  DO l = 1, llm-1
209   aps(l) =  0.5 *( ap(l) +ap(l+1))
210   bps(l) =  0.5 *( bp(l) +bp(l+1))
211  ENDDO
212
213  IF (hybrid) THEN
214     aps(llm) = aps(llm-1)**2 / aps(llm-2)
215     bps(llm) = 0.5*(bp(llm) + bp(llm+1))
216  else
217     bps(llm) = bps(llm-1)**2 / bps(llm-2)
218     aps(llm) = 0.
219  end if
220
221  WRITE(lunout,*) trim(modname),': BPs '
222  WRITE(lunout,*)  bps
223  WRITE(lunout,*) trim(modname),': APs'
224  WRITE(lunout,*)  aps
225
226  DO l = 1, llm
227   presnivs(l) = aps(l)+bps(l)*preff
228   pseudoalt(l) = -scaleheight*log(presnivs(l)/preff)
229  ENDDO
230
231  WRITE(lunout,*)trim(modname),' : PRESNIVS'
232  WRITE(lunout,*)presnivs
233  WRITE(lunout,*)'Pseudo altitude of Presnivs : (for a scale ', &
234        'height of ',scaleheight,' km)'
235  WRITE(lunout,*)pseudoalt
236
237  ! --------------------------------------------------
238  ! This can be used to plot the vertical discretization
239  ! (> xmgrace -nxy testhybrid.tab )
240  ! --------------------------------------------------
241  ! open (53,file='testhybrid.tab')
242  ! scaleheight=15.5
243  ! do iz=0,34
244  !   z = -5 + min(iz,34-iz)
245  ! approximation of scale height for Venus
246  !   scaleheight = 15.5 - z/55.*10.
247  !   ps = preff*exp(-z/scaleheight)
248  !   zsig(1)= -scaleheight*log((aps(1) + bps(1)*ps)/preff)
249  !   do l=2,llm
250  ! approximation of scale height for Venus
251  !      if (zsig(l-1).le.55.) THEN
252  !         scaleheight = 15.5 - zsig(l-1)/55.*10.
253  !      else
254  !         scaleheight = 5.5 - (zsig(l-1)-55.)/35.*2.
255  !      endif
256  !      zsig(l)= zsig(l-1)-scaleheight*
257  !    .    log((aps(l) + bps(l)*ps)/(aps(l-1) + bps(l-1)*ps))
258  !   END DO
259  !   WRITE(53,'(I3,50F10.5)') iz, zsig
260  !  END DO
261  !  close(53)
262  ! --------------------------------------------------
263
264
265  RETURN
266END SUBROUTINE disvert_noterre
267
268! ************************************************************
269SUBROUTINE sig_hybrid(sig,pa,preff,newsig)
270  ! ----------------------------------------------
271  ! Subroutine utilisee pour calculer des valeurs de sigma modifie
272  ! pour conserver les coordonnees verticales decrites dans
273  ! esasig.def/z2sig.def lors du passage en coordonnees hybrides
274  ! F. Forget 2002
275  ! Connaissant sig (niveaux "sigma" ou on veut mettre les couches)
276  ! L'objectif est de calculer newsig telle que
277  !   (1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig = sig
278  ! Cela ne se résoud pas analytiquement:
279  ! => on résoud par iterration bourrine
280  ! ----------------------------------------------
281  ! Information  : where exp(1-1./x**2) become << x
282  !       x      exp(1-1./x**2) /x
283  !       1           1
284  !       0.68       0.5
285  !       0.5        1.E-1
286  !       0.391      1.E-2
287  !       0.333      1.E-3
288  !       0.295      1.E-4
289  !       0.269      1.E-5
290  !       0.248      1.E-6
291  !    => on peut utiliser newsig = sig*preff/pa si sig*preff/pa < 0.25
292
293
294  IMPLICIT NONE
295  REAL :: x1, x2, sig,pa,preff, newsig, F
296  INTEGER :: j
297
298  newsig = sig
299  x1=0
300  x2=1
301  IF (sig>=1) THEN
302        newsig= sig
303  ELSE IF (sig*preff/pa>=0.25) THEN
304    DO J=1,9999  ! nombre d''iteration max
305      F=((1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig)/sig
306      ! WRITE(0,*) J, ' newsig =', newsig, ' F= ', F
307      IF (F>1) THEN
308          X2 = newsig
309          newsig=(X1+newsig)*0.5
310      else
311          X1 = newsig
312          newsig=(X2+newsig)*0.5
313      end if
314      ! Test : on arete lorsque on approxime sig à moins de 0.01 m près
315      ! (en pseudo altitude) :
316      IF(abs(10.*log(F))<1.E-5) goto 999
317    END DO
318   else   !    if (sig*preff/pa.le.0.25) THEN
319         newsig= sig*preff/pa
320   end if
321 999   continue
322   Return
323END SUBROUTINE sig_hybrid
Note: See TracBrowser for help on using the repository browser.