source: trunk/LMDZ.MARS/libf/dyn3d/disvert.F @ 222

Last change on this file since 222 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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      DO l=1,llm
141        nivsigs(l) = REAL(l)
142      ENDDO
143
144      DO l=1,llmp1
145        nivsig(l)= REAL(l)
146      ENDDO
147
148 
149c-----------------------------------------------------------------------
150c    ....  Calculs  de ap(l) et de bp(l)  ....
151c    .........................................
152c
153c   .....  pa et preff sont lus  sur les fichiers start par dynetat0 .....
154c-----------------------------------------------------------------------
155c
156
157      if (hybrid) then
158         write(*,*) "*******************************"
159         write(*,*) "Systeme en coordonnees hybrides"
160         write(*,*)
161c        Coordonnees hybrides avec mod
162         DO l = 1, llm
163
164         call sig_hybrid(sig(l),pa,preff,newsig)
165            bp(l) = EXP( 1. - 1./(newsig**2)  )
166            ap(l) = pa * (newsig - bp(l) )
167         enddo
168         bp(llmp1) = 0.
169         ap(llmp1) = 0.
170      else
171         write(*,*) "****************************"
172         write(*,*) "Systeme en coordonnees sigma"
173         write(*,*)
174c        Pour ne pas passer en coordonnees hybrides
175         DO l = 1, llm
176            ap(l) = 0.
177            bp(l) = sig(l)
178         ENDDO
179         ap(llmp1) = 0.
180      endif
181
182      bp(llmp1) =   0.
183
184      PRINT *,' BP '
185      PRINT *,  bp
186      PRINT *,' AP '
187      PRINT *,  ap
188
189c     Calcul au milieu des couches :
190c     WARNING : le choix de placer le milieu des couches au niveau de
191c     pression intermédiaire est arbitraire et pourrait etre modifié.
192c     Le calcul du niveau pour la derniere couche
193c     (on met la meme distance (en log pression)  entre P(llm)
194c     et P(llm -1) qu'entre P(llm-1) et P(llm-2) ) est
195c     Specifique.  Ce choix est spécifié ici ET dans exner_hyb.F
196
197      DO l = 1, llm-1
198       aps(l) =  0.5 *( ap(l) +ap(l+1))
199       bps(l) =  0.5 *( bp(l) +bp(l+1))
200      ENDDO
201     
202      if (hybrid) then
203         aps(llm) = aps(llm-1)**2 / aps(llm-2)
204         bps(llm) = 0.5*(bp(llm) + bp(llm+1))
205      else
206         bps(llm) = bps(llm-1)**2 / bps(llm-2)
207         aps(llm) = 0.
208      end if
209
210      PRINT *,' BPs '
211      PRINT *,  bps
212      PRINT *,' APs'
213      PRINT *,  aps
214
215      DO l = 1, llm
216       presnivs(l) = aps(l)+bps(l)*preff
217       pseudoalt(l) = -10.*log(presnivs(l)/preff)
218      ENDDO
219
220      PRINT *,' PRESNIVS'
221      PRINT *,presnivs
222      PRINT *,'Pseudo altitude des Presnivs : '
223      PRINT *,pseudoalt
224
225c     --------------------------------------------------
226c     This can be used to plot the vertical discretization
227c     (> xmgrace -nxy testhybrid.tab       (z = H*log(p(l)/pref))
228c     --------------------------------------------------
229c     open (53,file='testhybrid.tab')
230c     do iz=0,60
231c       z = -10 + min(iz,60-iz)
232c       ps = preff*exp(-z/10)
233c       do l=1,llm
234c          zsig(l)= -10.*log((aps(l) + bps(l)*ps)/preff)
235c       end do
236c       write(53,*)iz, (zsig(l),l=1,llm,1)
237c      end do
238c      close(53)
239c     --------------------------------------------------
240
241
242      RETURN
243      END
244
245c ************************************************************
246      subroutine sig_hybrid(sig,pa,preff,newsig)
247c     ----------------------------------------------
248c     Subroutine utilisee pour calculer des valeurs de sigma modifie
249c     pour conserver les coordonnees verticales decrites dans
250c     esasig.def/z2sig.def lors du passage en coordonnees hybrides
251c     F. Forget 2002
252c     Connaissant sig (niveaux "sigma" ou on veut mettre les couches)
253c     L'objectif est de calculer newsig telle que
254c       (1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig = sig
255c     Cela ne se résoud pas analytiquement:
256c     => on résoud par iterration bourrine
257c     ----------------------------------------------
258c     Information  : where exp(1-1./x**2) become << x
259c           x      exp(1-1./x**2) /x
260c           1           1
261c           0.68       0.5
262c           0.5        1.E-1
263c           0.391      1.E-2
264c           0.333      1.E-3
265c           0.295      1.E-4
266c           0.269      1.E-5
267c           0.248      1.E-6
268c        => on peut utiliser newsig = sig*preff/pa si sig*preff/pa < 0.25
269
270
271      implicit none
272      real x1, x2, sig,pa,preff, newsig, F
273      integer j
274
275      newsig = sig
276      x1=0
277      x2=1
278          if (sig.ge.1) then
279               newsig= sig
280      else if (sig*preff/pa.ge.0.25) then
281        DO J=1,9999  ! nombre d''iteration max
282          F=((1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig)/sig
283c         write(0,*) J, ' newsig =', newsig, ' F= ', F
284          if (F.gt.1) then
285              X2 = newsig
286              newsig=(X1+newsig)*0.5
287          else
288              X1 = newsig
289              newsig=(X2+newsig)*0.5
290          end if
291c         Test : on arete lorsque on approxime sig à moins de 0.01 m près
292c         (en pseudo altiude) :
293          IF(abs(10.*log(F)).LT.1.E-5) goto 999
294        END DO
295       else   !    if (sig*preff/pa.le.0.25) then
296                newsig= sig*preff/pa
297       end if
298 999   continue
299       Return
300      END
Note: See TracBrowser for help on using the repository browser.