Changeset 2040


Ignore:
Timestamp:
May 9, 2014, 12:50:34 PM (10 years ago)
Author:
Ehouarn Millour
Message:

Added a "strato_custom" mode in disvert (for development purposes).
This is triggered by setting "vert_sampling=strato_custom" in a def file.

More work is needed to clean disvert (and merge it with disvert_noterre).
DC+EM

Location:
LMDZ5/trunk/libf
Files:
3 edited

Legend:

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

    r1959 r2040  
    11! $Id$
    22
    3 SUBROUTINE disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,scaleheight)
    4 
    5   ! Auteur : P. Le Van
    6 
     3SUBROUTINE disvert()
     4
     5#ifdef CPP_IOIPSL
     6  use ioipsl, only: getin
     7#else
     8  USE ioipsl_getincom, only: getin
     9#endif
    710  use new_unit_m, only: new_unit
    8   use ioipsl, only: getin
    911  use assert_m, only: assert
    1012
     
    1315  include "dimensions.h"
    1416  include "paramet.h"
     17  include "comvert.h"
     18  include "comconst.h"
    1519  include "iniprint.h"
    1620  include "logic.h"
    1721
    18   ! s = sigma ** kappa : coordonnee verticale
    19   ! dsig(l) : epaisseur de la couche l ds la coord. s
    20   ! sig(l) : sigma a l'interface des couches l et l-1
    21   ! ds(l) : distance entre les couches l et l-1 en coord.s
    22 
    23   real,intent(in) :: pa, preff
    24   real,intent(out) :: ap(llmp1) ! in Pa
    25   real, intent(out):: bp(llmp1)
    26   real,intent(out) :: dpres(llm), nivsigs(llm), nivsig(llmp1)
    27   real,intent(out) :: presnivs(llm)
    28   real,intent(out) :: scaleheight
    29 
     22!-------------------------------------------------------------------------------
     23! Purpose: Vertical distribution functions for LMDZ.
     24!          Triggered by the levels number llm.
     25!-------------------------------------------------------------------------------
     26! Read    in "comvert.h":
     27! pa                         !--- PURE PRESSURE COORDINATE FOR P<pa (in Pascals)
     28! preff                      !--- REFERENCE PRESSURE                 (101325 Pa)
     29! Written in "comvert.h":
     30! ap(llm+1), bp(llm+1)       !--- Ap, Bp HYBRID COEFFICIENTS AT INTERFACES
     31! aps(llm),  bps(llm)        !--- Ap, Bp HYBRID COEFFICIENTS AT MID-LAYERS
     32! dpres(llm)                 !--- PRESSURE DIFFERENCE FOR EACH LAYER
     33! presnivs(llm)              !--- PRESSURE AT EACH MID-LAYER
     34! scaleheight                !--- VERTICAL SCALE HEIGHT            (Earth: 8kms)
     35! nivsig(llm+1)              !--- SIGMA INDEX OF EACH LAYER INTERFACE
     36! nivsigs(llm)               !--- SIGMA INDEX OF EACH MID-LAYER
     37!-------------------------------------------------------------------------------
     38! Local variables:
    3039  REAL sig(llm+1), dsig(llm)
    31   real zk, zkm1, dzk1, dzk2, k0, k1
     40  REAL sig0(llm+1), zz(llm+1)
     41  REAL zk, zkm1, dzk1, dzk2, z, k0, k1
    3242
    3343  INTEGER l, unit
     
    3747  character(len=*),parameter :: modname="disvert"
    3848
    39   character(len=6):: vert_sampling
     49  character(len=24):: vert_sampling
    4050  ! (allowed values are "param", "tropo", "strato" and "read")
    4151
    4252  !-----------------------------------------------------------------------
    4353
    44   print *, "Call sequence information: disvert"
     54  WRITE(lunout,*) TRIM(modname)//" starts"
    4555
    4656  ! default scaleheight is 8km for earth
     
    4959  vert_sampling = merge("strato", "tropo ", ok_strato) ! default value
    5060  call getin('vert_sampling', vert_sampling)
    51   print *, 'vert_sampling = ' // vert_sampling
     61  WRITE(lunout,*) TRIM(modname)//' vert_sampling = ' // vert_sampling
    5262  if (llm==39 .and. vert_sampling=="strato") then
    5363     dsigmin=0.3 ! Vieille option par défaut pour CMIP5
     
    144154     ap(1)=0.
    145155     ap(2: llm + 1) = pa * (sig(2: llm + 1) - bp(2: llm + 1))
     156  CASE("strato_custom")
     157    ! custumize strato distribution with specific alpha & beta values and function
     158    ! depending on llm (experimental and temporary)!
     159    SELECT CASE (llm)
     160      CASE(55)
     161        alpha=0.45
     162        beta=4.0
     163      CASE(63)
     164        alpha=0.45
     165        beta=5.0
     166      CASE(71)
     167        alpha=3.05
     168        beta=65.
     169      CASE(79)
     170        alpha=3.20
     171        ! alpha=2.05 ! FLOTT 79 (PLANTE)
     172        beta=70.
     173    END SELECT
     174    ! Or used values provided by user in def file:
     175    CALL getin("strato_alpha",alpha)
     176    CALL getin("strato_beta",beta)
     177   
     178    ! Build geometrical distribution
     179    scaleheight=7.
     180    zz(1)=0.
     181    IF (llm==55.OR.llm==63) THEN
     182      DO l=1,llm
     183        z=zz(l)/scaleheight
     184        zz(l+1)=zz(l)+0.03+z*1.5*(1.-TANH(z-0.5))+alpha*(1.+TANH(z-1.5))     &
     185                            +5.0*EXP((l-llm)/beta)
     186      ENDDO
     187    ELSEIF (llm==71) THEN !.OR.llm==79) THEN      ! FLOTT 79 (PLANTE)
     188      DO l=1,llm
     189        z=zz(l)
     190        zz(l+1)=zz(l)+0.02+0.88*TANH(z/2.5)+alpha*(1.+TANH((z-beta)/15.))
     191      ENDDO
     192    ELSEIF (llm==79) THEN
     193      DO l=1,llm
     194        z=zz(l)
     195        zz(l+1)=zz(l)+0.02+0.80*TANH(z/3.8)+alpha*(1+TANH((z-beta)/17.))     &
     196                            +0.03*TANH(z/.25)
     197      ENDDO
     198    ENDIF ! of IF (llm==55.OR.llm==63) ...
     199   
     200    ! Build sigma distribution
     201    sig0=EXP(-zz(:)/scaleheight)
     202    sig0(llm+1)=0.
     203    sig=ridders(sig0)
     204   
     205    ! Compute ap() and bp()
     206    bp(1)=1.
     207    bp(2:llm)=EXP(1.-1./sig(2:llm)**2)
     208    bp(llm+1)=0.
     209    ap=pa*(sig-bp)
     210
    146211  case("read")
    147212     ! Read "ap" and "bp". First line is skipped (title line). "ap"
     
    191256  write(lunout, *) presnivs
    192257
     258CONTAINS
     259
     260!-------------------------------------------------------------------------------
     261!
     262FUNCTION ridders(sig) RESULT(sg)
     263!
     264!-------------------------------------------------------------------------------
     265  IMPLICIT NONE
     266!-------------------------------------------------------------------------------
     267! Purpose: Search for s solving (Pa/Preff)*s+(1-Pa/Preff)*EXP(1-1./s**2)=sg
     268! Notes:   Uses Ridders' method, quite robust. Initial bracketing: 0<=sg<=1.
     269! Reference: Ridders, C. F. J. "A New Algorithm for Computing a Single Root of a
     270!       Real Continuous Function" IEEE Trans. Circuits Systems 26, 979-980, 1979
     271!-------------------------------------------------------------------------------
     272! Arguments:
     273  REAL, INTENT(IN)  :: sig(:)
     274  REAL              :: sg(SIZE(sig))
     275!-------------------------------------------------------------------------------
     276! Local variables:
     277  INTEGER :: it, ns, maxit
     278  REAL :: c1, c2, x1, x2, x3, x4, f1, f2, f3, f4, s, xx, distrib
     279!-------------------------------------------------------------------------------
     280  ns=SIZE(sig); maxit=9999
     281  c1=Pa/Preff; c2=1.-c1
     282  DO l=1,ns
     283    xx=HUGE(1.)
     284    x1=0.0; f1=distrib(x1,c1,c2,sig(l))
     285    x2=1.0; f2=distrib(x2,c1,c2,sig(l))
     286    DO it=1,maxit
     287      x3=0.5*(x1+x2); f3=distrib(x3,c1,c2,sig(l))
     288      s=SQRT(f3**2-f1*f2);                 IF(s==0.) EXIT
     289      x4=x3+(x3-x1)*(SIGN(1.,f1-f2)*f3/s); IF(ABS(10.*LOG(x4-xx))<=1E-5) EXIT
     290      xx=x4; f4=distrib(x4,c1,c2,sig(l));  IF(f4==0.) EXIT
     291      IF(SIGN(f3,f4)/=f3) THEN;      x1=x3; f1=f3; x2=xx; f2=f4
     292      ELSE IF(SIGN(f1,f4)/=f1) THEN; x2=xx; f2=f4
     293      ELSE IF(SIGN(f2,f4)/=f2) THEN; x1=xx; f1=f4
     294      ELSE; CALL abort_gcm("ridders",'Algorithm failed (which is odd...')
     295      END IF
     296      IF(ABS(10.*LOG(ABS(x2-x1)))<=1E-5) EXIT       !--- ERROR ON SIG <= 0.01m           
     297    END DO
     298    IF(it==maxit+1) WRITE(lunout,'(a,i3)')'WARNING in ridder: failed to converg&
     299     &e for level ',l
     300    sg(l)=xx
     301  END DO
     302  sg(1)=1.; sg(ns)=0.
     303
     304END FUNCTION ridders
     305
    193306END SUBROUTINE disvert
     307
     308!-------------------------------------------------------------------------------
     309
     310FUNCTION distrib(x,c1,c2,x0) RESULT(res)
     311!
     312!-------------------------------------------------------------------------------
     313! Arguments:
     314  REAL, INTENT(IN) :: x, c1, c2, x0
     315  REAL             :: res
     316!-------------------------------------------------------------------------------
     317  res=c1*x+c2*EXP(1-1/(x**2))-x0
     318
     319END FUNCTION distrib
     320
     321
  • LMDZ5/trunk/libf/dyn3d_common/iniconst.F90

    r1952 r2040  
    7373  if (disvert_type==1) then
    7474     ! standard case for Earth (automatic generation of levels)
    75      call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig, scaleheight)
     75     call disvert()
    7676  else if (disvert_type==2) then
    7777     ! standard case for planets (levels generated using z2sig.def file)
  • LMDZ5/trunk/libf/phylmd/lmdz1d.F90

    r2037 r2040  
    488488        print *,'On utilise disvert0'
    489489      ELSE
    490         call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,          &
    491      &                 scaleheight)
     490        call disvert()
    492491        print *,'On utilise disvert'
    493492!       Nouvelle version disvert permettant d imposer ap,bp (modif L.Guez) MPL 18092012
Note: See TracChangeset for help on using the changeset viewer.