source: trunk/LMDZ.COMMON/libf/dyn3dpar/disvert_noterre.F @ 832

Last change on this file since 832 was 124, checked in by emillour, 14 years ago

EM: suite mise au point discretisation verticale et quelques corrections de bugs dans le version de reference parallele.

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