source: LMDZ5/trunk/libf/dyn3d/disvert.F90 @ 1523

Last change on this file since 1523 was 1520, checked in by Ehouarn Millour, 13 years ago

Implementation of a different vertical discretization (from/for planets, but
can in principle also be used for Earth).
Choice of vertical discretization is set by flag 'disvert_type';
'disvert_type=1' is Earth standard (default; ie set to 1 if
planet_type=="earth") case.
With 'disvert_type=2', approximate altitude of layers and reference atmospheric
scale height must be given using an input file ("z2sig.def", first line
should give scale height, in km, following lines must specify the altitude,
in km above surface, of mid-layers, one per line; see disvert_noterre.F).

Checked that these changes do not impact on 'bench' results, on Vargas.

EM.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.1 KB
Line 
1! $Id: disvert.F90 1520 2011-05-23 11:37:09Z idelkadi $
2
3SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,scaleheight)
4
5  ! Auteur : P. Le Van
6
7  IMPLICIT NONE
8
9  include "dimensions.h"
10  include "paramet.h"
11  include "iniprint.h"
12  include "logic.h"
13
14  ! s = sigma ** kappa : coordonnee verticale
15  ! dsig(l) : epaisseur de la couche l ds la coord. s
16  ! sig(l) : sigma a l'interface des couches l et l-1
17  ! ds(l) : distance entre les couches l et l-1 en coord.s
18
19  real,intent(in) :: pa, preff
20  real,intent(out) :: ap(llmp1), bp(llmp1)
21  real,intent(out) :: dpres(llm), nivsigs(llm), nivsig(llmp1)
22  real,intent(out) :: presnivs(llm)
23  real,intent(out) :: scaleheight
24
25  REAL sig(llm+1), dsig(llm)
26  real zk, zkm1, dzk1, dzk2, k0, k1
27
28  INTEGER l
29  REAL dsigmin
30  REAL alpha, beta, deltaz,scaleheight
31  INTEGER iostat
32  REAL x
33  character(len=*),parameter :: modname="disvert"
34
35  !-----------------------------------------------------------------------
36
37  ! default scaleheight is 8km for earth
38  scaleheight=8.
39
40  OPEN(99, file='sigma.def', status='old', form='formatted', iostat=iostat)
41
42  IF (iostat == 0) THEN
43     ! cas 1 on lit les options dans sigma.def:
44     READ(99, *) scaleheight ! hauteur d'echelle 8.
45     READ(99, *) deltaz ! epaiseur de la premiere couche 0.04
46     READ(99, *) beta ! facteur d'acroissement en haut 1.3
47     READ(99, *) k0 ! nombre de couches dans la transition surf
48     READ(99, *) k1 ! nombre de couches dans la transition haute
49     CLOSE(99)
50     alpha=deltaz/(llm*scaleheight)
51     write(lunout, *)trim(modname),':scaleheight, alpha, k0, k1, beta', &
52                               scaleheight, alpha, k0, k1, beta
53
54     alpha=deltaz/tanh(1./k0)*2.
55     zkm1=0.
56     sig(1)=1.
57     do l=1, llm
58        sig(l+1)=(cosh(l/k0))**(-alpha*k0/scaleheight) &
59             *exp(-alpha/scaleheight*tanh((llm-k1)/k0) &
60                  *beta**(l-(llm-k1))/log(beta))
61        zk=-scaleheight*log(sig(l+1))
62
63        dzk1=alpha*tanh(l/k0)
64        dzk2=alpha*tanh((llm-k1)/k0)*beta**(l-(llm-k1))/log(beta)
65        write(lunout, *)l, sig(l+1), zk, zk-zkm1, dzk1, dzk2
66        zkm1=zk
67     enddo
68
69     sig(llm+1)=0.
70
71     DO l = 1, llm
72        dsig(l) = sig(l)-sig(l+1)
73     end DO
74  ELSE
75     if (ok_strato) then
76        if (llm==39) then
77           dsigmin=0.3
78        else if (llm==50) then
79           dsigmin=1.
80        else
81           write(lunout,*) trim(modname), &
82           ' ATTENTION discretisation z a ajuster'
83           dsigmin=1.
84        endif
85        write(lunout,*) trim(modname), &
86        ' Discretisation verticale DSIGMIN=',dsigmin
87     endif
88
89     DO l = 1, llm
90        x = 2*asin(1.) * (l - 0.5) / (llm + 1)
91
92        IF (ok_strato) THEN
93           dsig(l) =(dsigmin + 7. * SIN(x)**2) &
94                *(0.5*(1.-tanh(1.*(x-asin(1.))/asin(1.))))**2
95        ELSE
96           dsig(l) = 1.0 + 7.0 * SIN(x)**2
97        ENDIF
98     ENDDO
99     dsig = dsig / sum(dsig)
100     sig(llm+1) = 0.
101     DO l = llm, 1, -1
102        sig(l) = sig(l+1) + dsig(l)
103     ENDDO
104  ENDIF
105
106  DO l=1, llm
107     nivsigs(l) = REAL(l)
108  ENDDO
109
110  DO l=1, llmp1
111     nivsig(l)= REAL(l)
112  ENDDO
113
114  ! .... Calculs de ap(l) et de bp(l) ....
115  ! ..... pa et preff sont lus sur les fichiers start par lectba .....
116
117  bp(llmp1) = 0.
118
119  DO l = 1, llm
120     bp(l) = EXP( 1. -1./( sig(l)*sig(l)) )
121     ap(l) = pa * ( sig(l) - bp(l) )
122  ENDDO
123
124  bp(1)=1.
125  ap(1)=0.
126
127  ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) )
128
129  write(lunout, *)  trim(modname),': BP '
130  write(lunout, *) bp
131  write(lunout, *)  trim(modname),': AP '
132  write(lunout, *) ap
133
134  write(lunout, *) 'Niveaux de pressions approximatifs aux centres des'
135  write(lunout, *)'couches calcules pour une pression de surface =', preff
136  write(lunout, *) 'et altitudes equivalentes pour une hauteur d echelle de '
137  write(lunout, *) scaleheight,' km'
138  DO l = 1, llm
139     dpres(l) = bp(l) - bp(l+1)
140     presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
141     write(lunout, *)'PRESNIVS(', l, ')=', presnivs(l), ' Z ~ ', &
142          log(preff/presnivs(l))*scaleheight &
143          , ' DZ ~ ', scaleheight*log((ap(l)+bp(l)*preff)/ &
144          max(ap(l+1)+bp(l+1)*preff, 1.e-10))
145  ENDDO
146
147  write(lunout, *) trim(modname),': PRESNIVS '
148  write(lunout, *) presnivs
149
150END SUBROUTINE disvert
Note: See TracBrowser for help on using the repository browser.