Ignore:
Timestamp:
May 23, 2011, 1:37:09 PM (13 years ago)
Author:
Ehouarn Millour
Message:

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.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dpar/disvert.F90

    r1492 r1520  
    11! $Id$
    22
    3 SUBROUTINE disvert(pa, preff, ap, bp, dpres, presnivs, nivsigs, nivsig)
     3SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,scaleheight)
    44
    55  ! Auteur : P. Le Van
     
    1717  ! ds(l) : distance entre les couches l et l-1 en coord.s
    1818
    19   REAL pa, preff
    20   REAL ap(llmp1), bp(llmp1), dpres(llm), nivsigs(llm), nivsig(llmp1)
    21   REAL presnivs(llm)
     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
    2224
    2325  REAL sig(llm+1), dsig(llm)
     
    2628  INTEGER l
    2729  REAL dsigmin
    28   REAL alpha, beta, deltaz, h
     30  REAL alpha, beta, deltaz,scaleheight
    2931  INTEGER iostat
    30   REAL pi, x
     32  REAL x
     33  character(len=*),parameter :: modname="disvert"
    3134
    3235  !-----------------------------------------------------------------------
    3336
    34   pi = 2 * ASIN(1.)
     37  ! default scaleheight is 8km for earth
     38  scaleheight=8.
    3539
    3640  OPEN(99, file='sigma.def', status='old', form='formatted', iostat=iostat)
     
    3842  IF (iostat == 0) THEN
    3943     ! cas 1 on lit les options dans sigma.def:
    40      READ(99, *) h ! hauteur d'echelle 8.
     44     READ(99, *) scaleheight ! hauteur d'echelle 8.
    4145     READ(99, *) deltaz ! epaiseur de la premiere couche 0.04
    4246     READ(99, *) beta ! facteur d'acroissement en haut 1.3
     
    4448     READ(99, *) k1 ! nombre de couches dans la transition haute
    4549     CLOSE(99)
    46      alpha=deltaz/(llm*h)
    47      write(lunout, *)'h, alpha, k0, k1, beta'
     50     alpha=deltaz/(llm*scaleheight)
     51     write(lunout, *)trim(modname),':scaleheight, alpha, k0, k1, beta', &
     52                               scaleheight, alpha, k0, k1, beta
    4853
    4954     alpha=deltaz/tanh(1./k0)*2.
     
    5156     sig(1)=1.
    5257     do l=1, llm
    53         sig(l+1)=(cosh(l/k0))**(-alpha*k0/h) &
    54              *exp(-alpha/h*tanh((llm-k1)/k0)*beta**(l-(llm-k1))/log(beta))
    55         zk=-h*log(sig(l+1))
     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))
    5662
    5763        dzk1=alpha*tanh(l/k0)
     
    7379           dsigmin=1.
    7480        else
    75            WRITE(LUNOUT,*) 'ATTENTION discretisation z a ajuster'
     81           write(lunout,*) trim(modname), &
     82           ' ATTENTION discretisation z a ajuster'
    7683           dsigmin=1.
    7784        endif
    78         WRITE(LUNOUT,*) 'Discretisation verticale DSIGMIN=',dsigmin
     85        write(lunout,*) trim(modname), &
     86        ' Discretisation verticale DSIGMIN=',dsigmin
    7987     endif
    8088
     
    119127  ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) )
    120128
    121   write(lunout, *)' BP '
     129  write(lunout, *)  trim(modname),': BP '
    122130  write(lunout, *) bp
    123   write(lunout, *)' AP '
     131  write(lunout, *)  trim(modname),': AP '
    124132  write(lunout, *) ap
    125133
    126134  write(lunout, *) 'Niveaux de pressions approximatifs aux centres des'
    127135  write(lunout, *)'couches calcules pour une pression de surface =', preff
    128   write(lunout, *) 'et altitudes equivalentes pour une hauteur d echelle de'
    129   write(lunout, *)'8km'
     136  write(lunout, *) 'et altitudes equivalentes pour une hauteur d echelle de '
     137  write(lunout, *) scaleheight,' km'
    130138  DO l = 1, llm
    131139     dpres(l) = bp(l) - bp(l+1)
    132140     presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
    133141     write(lunout, *)'PRESNIVS(', l, ')=', presnivs(l), ' Z ~ ', &
    134           log(preff/presnivs(l))*8. &
    135           , ' DZ ~ ', 8.*log((ap(l)+bp(l)*preff)/ &
     142          log(preff/presnivs(l))*scaleheight &
     143          , ' DZ ~ ', scaleheight*log((ap(l)+bp(l)*preff)/ &
    136144          max(ap(l+1)+bp(l+1)*preff, 1.e-10))
    137145  ENDDO
    138146
    139   write(lunout, *) 'PRESNIVS '
     147  write(lunout, *) trim(modname),': PRESNIVS '
    140148  write(lunout, *) presnivs
    141149
Note: See TracChangeset for help on using the changeset viewer.