Ignore:
Timestamp:
May 9, 2012, 3:14:48 PM (12 years ago)
Author:
lguez
Message:

Created logical variable "pressure_exner". "pressure_exner" replaces
"disvert_type" to choose between calls to "exner_hyb" and
"exner_milieu". If "pressure_exner" is true, pressure inside layers is
computed from Exner function ("exner_hyb"), else it is the mean of
pressure values at interfaces ("exner_milieu"). "disvert_type" now
only chooses between "disvert" and "disvert_noterre". Default value
for "pressure_exner" is true if "disvert_type" equals 1.

Location:
LMDZ5/trunk/libf/dyn3d
Files:
7 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/comvert.h

    r1520 r1625  
    99     &               aps(llm),bps(llm),scaleheight
    1010
    11       common/comverti/disvert_type
     11      common/comverti/disvert_type, pressure_exner
    1212
    1313      real ap     ! hybrid pressure contribution at interlayers
     
    3030                           !     using 'z2sig.def' (or 'esasig.def) file
    3131
     32      logical pressure_exner
     33!     compute pressure inside layers using Exner function, else use mean
     34!     of pressure values at interfaces
     35
    3236 !-----------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3d/etat0_netcdf.F90

    r1520 r1625  
    251251!*******************************************************************************
    252252  CALL pression(ip1jmp1, ap, bp, psol, p3d)
    253   if (disvert_type.eq.1) then
     253  if (pressure_exner) then
    254254    CALL exner_hyb(ip1jmp1, psol, p3d, alpha, beta, pks, pk, y)
    255   else ! we assume that we are in the disvert_type==2 case
     255  else
    256256    CALL exner_milieu(ip1jmp1,psol,p3d,beta,pks,pk,y)
    257257  endif
  • LMDZ5/trunk/libf/dyn3d/exner_hyb.F

    r1520 r1625  
    5656      ! Sanity check
    5757      if (firstcall) then
    58         ! check that vertical discretization is compatible
    59         ! with this routine
    60         if (disvert_type.ne.1) then
    61           call abort_gcm(modname,
    62      &     "this routine should only be called if disvert_type==1",42)
    63         endif
    64        
    6558        ! sanity checks for Shallow Water case (1 vertical layer)
    6659        if (llm.eq.1) then
  • LMDZ5/trunk/libf/dyn3d/exner_milieu.F

    r1520 r1625  
    5353      ! Sanity check
    5454      if (firstcall) then
    55         ! check that vertical discretization is compatible
    56         ! with this routine
    57         if (disvert_type.ne.2) then
    58           call abort_gcm(modname,
    59      &     "this routine should only be called if disvert_type==2",42)
    60         endif
    61        
    6255        ! sanity checks for Shallow Water case (1 vertical layer)
    6356        if (llm.eq.1) then
  • LMDZ5/trunk/libf/dyn3d/guide_mod.F90

    r1520 r1625  
    644644! -----------------------------------------------------------------
    645645    CALL pression( ip1jmp1, ap, bp, psi, p )
    646     if (disvert_type==1) then
     646    if (pressure_exner) then
    647647      CALL exner_hyb(ip1jmp1,psi,p,alpha,beta,pks,pk,pkf)
    648     else ! we assume that we are in the disvert_type==2 case
     648    else
    649649      CALL exner_milieu(ip1jmp1,psi,p,beta,pks,pk,pkf)
    650650    endif
  • LMDZ5/trunk/libf/dyn3d/iniacademic.F90

    r1561 r1625  
    222222
    223223        CALL pression ( ip1jmp1, ap, bp, ps, p       )
    224         if (disvert_type.eq.1) then
     224        if (pressure_exner) then
    225225          CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
    226         elseif (disvert_type.eq.2) then
     226        else
    227227          call exner_milieu(ip1jmp1,ps,p,beta,pks,pk,pkf)
    228         else
    229           write(abort_message,*) "Wrong value for disvert_type: ", &
    230                               disvert_type
    231           call abort_gcm(modname,abort_message,0)
    232228        endif
    233229        CALL massdair(p,masse)
  • LMDZ5/trunk/libf/dyn3d/iniconst.F90

    r1624 r1625  
    22! $Id$
    33!
    4       SUBROUTINE iniconst
     4SUBROUTINE iniconst
    55
    6       USE control_mod
     6  USE control_mod
    77#ifdef CPP_IOIPSL
    8       use IOIPSL
     8  use IOIPSL
    99#else
    10 ! if not using IOIPSL, we still need to use (a local version of) getin
    11       use ioipsl_getincom
     10  ! if not using IOIPSL, we still need to use (a local version of) getin
     11  use ioipsl_getincom
    1212#endif
    1313
    14       IMPLICIT NONE
    15 c
    16 c      P. Le Van
    17 c
    18 c-----------------------------------------------------------------------
    19 c   Declarations:
    20 c   -------------
    21 c
    22 #include "dimensions.h"
    23 #include "paramet.h"
    24 #include "comconst.h"
    25 #include "temps.h"
    26 #include "comvert.h"
    27 #include "iniprint.h"
     14  IMPLICIT NONE
     15  !
     16  !      P. Le Van
     17  !
     18  !   Declarations:
     19  !   -------------
     20  !
     21  include "dimensions.h"
     22  include "paramet.h"
     23  include "comconst.h"
     24  include "temps.h"
     25  include "comvert.h"
     26  include "iniprint.h"
    2827
    29       character(len=*),parameter :: modname="iniconst"
    30       character(len=80) :: abort_message
    31 c
    32 c
    33 c
    34 c-----------------------------------------------------------------------
    35 c   dimension des boucles:
    36 c   ----------------------
     28  character(len=*),parameter :: modname="iniconst"
     29  character(len=80) :: abort_message
     30  !
     31  !
     32  !
     33  !-----------------------------------------------------------------------
     34  !   dimension des boucles:
     35  !   ----------------------
    3736
    38       im      = iim
    39       jm      = jjm
    40       lllm    = llm
    41       imp1    = iim
    42       jmp1    = jjm + 1
    43       lllmm1  = llm - 1
    44       lllmp1  = llm + 1
     37  im      = iim
     38  jm      = jjm
     39  lllm    = llm
     40  imp1    = iim
     41  jmp1    = jjm + 1
     42  lllmm1  = llm - 1
     43  lllmp1  = llm + 1
    4544
    46 c-----------------------------------------------------------------------
     45  !-----------------------------------------------------------------------
    4746
    48       dtphys  = iphysiq * dtvr
    49       unsim   = 1./iim
    50       pi      = 2.*ASIN( 1. )
     47  dtphys  = iphysiq * dtvr
     48  unsim   = 1./iim
     49  pi      = 2.*ASIN( 1. )
    5150
    52 c-----------------------------------------------------------------------
    53 c
     51  !-----------------------------------------------------------------------
     52  !
    5453
    55       r       = cpp * kappa
     54  r       = cpp * kappa
    5655
    57       write(lunout,*) trim(modname),': R  CP  Kappa ',r,cpp,kappa
    58 c
    59 c-----------------------------------------------------------------------
     56  write(lunout,*) trim(modname),': R  CP  Kappa ',r,cpp,kappa
     57  !
     58  !-----------------------------------------------------------------------
    6059
    61 ! vertical discretization: default behavior depends on planet_type flag
    62       if (planet_type=="earth") then
    63         disvert_type=1
    64       else
    65         disvert_type=2
    66       endif
    67       ! but user can also specify using one or the other in run.def:
    68       call getin('disvert_type',disvert_type)
    69       write(lunout,*) trim(modname),': disvert_type=',disvert_type
    70      
    71       if (disvert_type==1) then
    72        ! standard case for Earth (automatic generation of levels)
    73        call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,
    74      &              scaleheight)
    75       else if (disvert_type==2) then
    76         ! standard case for planets (levels generated using z2sig.def file)
    77         call disvert_noterre
    78       else
    79         write(abort_message,*) "Wrong value for disvert_type: ",
    80      &                        disvert_type
    81         call abort_gcm(modname,abort_message,0)
    82       endif
     60  ! vertical discretization: default behavior depends on planet_type flag
     61  if (planet_type=="earth") then
     62     disvert_type=1
     63  else
     64     disvert_type=2
     65  endif
     66  ! but user can also specify using one or the other in run.def:
     67  call getin('disvert_type',disvert_type)
     68  write(lunout,*) trim(modname),': disvert_type=',disvert_type
    8369
    84       END
     70  pressure_exner = disvert_type == 1 ! default value
     71  call getin('pressure_exner', pressure_exner)
     72
     73  if (disvert_type==1) then
     74     ! standard case for Earth (automatic generation of levels)
     75     call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig, scaleheight)
     76  else if (disvert_type==2) then
     77     ! standard case for planets (levels generated using z2sig.def file)
     78     call disvert_noterre
     79  else
     80     write(abort_message,*) "Wrong value for disvert_type: ", disvert_type
     81     call abort_gcm(modname,abort_message,0)
     82  endif
     83
     84END SUBROUTINE iniconst
  • LMDZ5/trunk/libf/dyn3d/leapfrog.F

    r1616 r1625  
    212212      dq(:,:,:)=0.
    213213      CALL pression ( ip1jmp1, ap, bp, ps, p       )
    214       if (disvert_type==1) then
     214      if (pressure_exner) then
    215215        CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
    216       else ! we assume that we are in the disvert_type==2 case
     216      else
    217217        CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    218218      endif
     
    369369
    370370         CALL pression (  ip1jmp1, ap, bp, ps,  p      )
    371          if (disvert_type==1) then
     371         if (pressure_exner) then
    372372           CALL exner_hyb(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
    373          else ! we assume that we are in the disvert_type==2 case
     373         else
    374374           CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    375375         endif
     
    485485
    486486        CALL pression ( ip1jmp1, ap, bp, ps, p                  )
    487         if (disvert_type==1) then
     487        if (pressure_exner) then
    488488          CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
    489         else ! we assume that we are in the disvert_type==2 case
     489        else
    490490          CALL exner_milieu( ip1jmp1, ps, p, beta, pks, pk, pkf )
    491491        endif
Note: See TracChangeset for help on using the changeset viewer.