source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3d_common/disvert_noterre.F @ 298

Last change on this file since 298 was 298, checked in by milmd, 10 years ago

Less output messages are written. On 20000 cores it is better. In LMDZ, only master of MPI and OpenMP can write.

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