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

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

In LMDZ.GENERIC replacement of all phystd .h files by module files.

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