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

Last change on this file since 2236 was 1621, checked in by emillour, 8 years ago

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

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