source: trunk/LMDZ.TITAN/libf/dyn3d/disvert.F @ 2212

Last change on this file since 2212 was 1790, checked in by jvatant, 7 years ago

Update 1D model that hasn't been cleaned since migration from generic

+ remove co2,water, kcm ...
+ added moyzon

Also correct deftank according to r1788
--JVO

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