source: trunk/LMDZ.GENERIC/libf/dyn3d/disvert.F @ 205

Last change on this file since 205 was 135, checked in by aslmd, 14 years ago

CHANGEMENT ARBORESCENCE ETAPE 2 -- NON COMPLET

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