source: trunk/LMDZ.PLUTO.old/libf/dyn3d/disvert.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

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