source: trunk/libf/dyn3d/disvert_noterre.F @ 110

Last change on this file since 110 was 110, checked in by slebonnois, 14 years ago

SL: corrections de bugs suite a compilations venus et titan de la version 109.

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