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

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

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

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