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

Last change on this file since 1634 was 1623, checked in by lguez, 12 years ago

The default value of 'vert_sampling' is now 'strato' if 'ok_strato' and 'tropo' if not 'ok_strato'.

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