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

Last change on this file since 5113 was 5113, checked in by abarral, 2 months ago

Rename modules in misc from *_mod > lmdz_*
Put cbrt.f90, ch*.f90, pch*.f90 in new lmdz_libmath_pch.f90

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