Class sl09_diffusion
In: held_suarez_1994/sl09_diffusion.f90

Schneider and Liu (2009) による鉛直混合課程

Vertical diffusion by Schneider and Liu (2009)

Note that Japanese and English are described in parallel.

Procedures List

!$ ! Hs94Forcing :強制と散逸の計算
!$ ! Hs94Finalize :終了処理 (モジュール内部の変数の割り付け解除)
!$ ! ———— :————
!$ ! Hs94Forcing :Calculate forcing and dissipation
!$ ! Hs94Finalize :Termination (deallocate variables in this module)

References

 Schneider, T. and J. Liu,
   Formation of jets and equatorial superrotation on Jupiter,
   J. Atmos. Sci., 69, 579, 2009.

Methods

Included Modules

gridset composition dc_types dc_message timeset gtool_historyauto constants vdiffusion_my constants0 axesset namelist_util dc_iounit dc_string

Public Instance methods

Subroutine :
xy_SurfHeight(0:imax-1, 1:jmax) :real(DP), intent(in)
xyz_Height(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
xyz_U(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ u $ . 東西風速. Eastward wind
xyz_V(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ v $ . 南北風速. Northward wind
xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(in)
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ p_s $ . 地表面気圧. Surface pressure
xyr_VirTemp(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
xyz_DUDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ DP{u}{t} $ . 東西風速変化. Eastward wind tendency
xyz_DVDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ DP{v}{t} $ . 南北風速変化. Northward wind tendency
xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(out)
: $ DP{T}{t} $ . 温度変化. Temperature tendency
xyzf_DQMixDt(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(out)

[Source]

  subroutine SL09Diffusion( xy_SurfHeight, xyz_Height, xyz_U, xyz_V, xyzf_QMix, xyr_Press, xyr_VirTemp, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyzf_DQMixDt )
    !
    !
    !

    ! モジュール引用 ; USE statements
    !

    ! 時刻管理
    ! Time control
    !
    use timeset, only: TimeN, TimesetClockStart, TimesetClockStop

    ! ヒストリデータ出力
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: GasRDry, CpDry    ! $ C_p $ [J kg-1 K-1].
                                  ! 乾燥大気の定圧比熱.
                                  ! Specific heat of air at constant pressure

    ! 鉛直拡散フラックス
    ! Vertical diffusion flux
    !
    use vdiffusion_my, only: VDiffusionExpTendency

    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), intent(in):: xy_SurfHeight(0:imax-1, 1:jmax)
    real(DP), intent(in):: xyz_Height   (0:imax-1, 1:jmax, 1:kmax)
    real(DP), intent(in):: xyz_U    (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u $ . 東西風速. 
                              ! Eastward wind
    real(DP), intent(in):: xyz_V    (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v $ . 南北風速. 
                              ! Northward wind
    real(DP), intent(in):: xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
    real(DP), intent(in):: xyr_Press(0:imax-1, 1:jmax, 0:kmax)
                              ! $ p_s $ . 地表面気圧. 
                              ! Surface pressure
    real(DP), intent(in):: xyr_VirTemp  (0:imax-1, 1:jmax, 0:kmax)
    real(DP), intent(out):: xyz_DUDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{u}{t} $ . 東西風速変化. 
                              ! Eastward wind tendency
    real(DP), intent(out):: xyz_DVDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{v}{t} $ . 南北風速変化. 
                              ! Northward wind tendency
    real(DP), intent(out):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . 温度変化. 
                              ! Temperature tendency
    real(DP), intent(out):: xyzf_DQMixDt (0:imax-1, 1:jmax, 1:kmax, 1:ncmax)

    ! 作業変数
    ! Work variables
    !
    real(DP) :: xyr_HeatFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 熱フラックス. 
                              ! Heat flux
    real(DP) :: xyrf_QMixFlux (0:imax-1, 1:jmax, 0:kmax, 1:ncmax)

    real(DP) :: xy_SurfQMixTransCoef(0:imax-1, 1:jmax)

!!$    integer:: j               ! 緯度方向に回る DO ループ用作業変数
!!$                              ! Work variables for DO loop in latitude
    integer:: k               ! 鉛直方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in vertical direction
    integer:: n


    ! 実行文 ; Executable statement
    !

    ! 初期化
    ! Initialization
    !
    if ( .not. sl09_diffusion_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if

    ! 計算時間計測開始
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )

    ! 東西風速 $ u $ と南北風速 $ v $ へレイリー摩擦を適用
    ! Apply Rayleigh damping to eastward wind $ u $ and northward wind $ v $
    !
    xyz_DUDt = - xyz_kv * xyz_U
    xyz_DVDt = - xyz_kv * xyz_V


    ! Set heat flux at the lower boundary
    !
    xyr_HeatFlux(:,:,0     ) = LBHeatFlux
    xyr_HeatFlux(:,:,1:kmax) = 0.0_DP

    ! Set moisture flux at the lower boundary
    !
    xyrf_QMixFlux = 0.0_DP
    n = IndexH2OVap
    k = 0
    xy_SurfQMixTransCoef = SurfQMixDiffCoef * xyr_Press(:,:,k) / ( GasRDry * xyr_VirTemp(:,:,k) ) / ( xyz_Height(:,:,k+1) - xy_SurfHeight )
    xyrf_QMixFlux(:,:,k,n) = - xy_SurfQMixTransCoef * ( xyzf_QMix(:,:,k+1,n) - SurfQVap )



    ! 時間変化率の計算を行います.
    ! Calculate tendencies.
    !
    call VDiffusionExpTendency( xyr_Press, xyr_HeatFlux  = xyr_HeatFlux, xyrf_QMixFlux = xyrf_QMixFlux, xyz_DTempDt  = xyz_DTempDt, xyzf_DQMixDt = xyzf_DQMixDt )


    ! This is commented out (yot, 2013/05/12) to be consistent with SL09.
    ! Temporarily, xyzf_DQMixDt is overwritten.
!!$    xyzf_DQMixDt = 0.0_DP
!!$    k = 1
!!$    n = IndexH2OVap
!!$    xyzf_DQMixDt(:,:,k,n) = ( SurfQVap - xyzf_QMix(:,:,k,n) ) &
!!$      & / ( 2.0_DP * DelTime )
!!$    xyzf_DQMixDt(:,:,k,n) = ( SurfQVap - xyzf_QMix(:,:,k,n) ) &
!!$      & / ( 2.0_DP * DelTime )


    !
    ! Add heating due to MHD drag dissipation
    !
    xyz_DTempDt = xyz_DTempDt - ( xyz_DUDt * xyz_U + xyz_DVDt * xyz_V ) / CpDry


    ! ヒストリデータ出力
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'DUDtVDiffSL09',    xyz_DUDt    )
    call HistoryAutoPut( TimeN, 'DVDtVDiffSL09',    xyz_DVDt    )
    call HistoryAutoPut( TimeN, 'DTempDtVDiffSL09', xyz_DTempDt )


    ! 計算時間計測一時停止
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )

  end subroutine SL09Diffusion
Subroutine :

sl09_diffusion モジュールの初期化を行います. NAMELIST#sl09_diffusion_nml の読み込みはこの手続きで行われます.

"sl09_diffusion" module is initialized. "NAMELIST#sl09_diffusion_nml" is loaded in this procedure.

This procedure input/output NAMELIST#sl09_diffusion_nml .

[Source]

  subroutine SL09DiffusionInit
    !
    ! sl09_diffusion モジュールの初期化を行います. 
    ! NAMELIST#sl09_diffusion_nml の読み込みはこの手続きで行われます. 
    !
    ! "sl09_diffusion" module is initialized. 
    ! "NAMELIST#sl09_diffusion_nml" is loaded in this procedure. 
    !

    ! モジュール引用 ; USE statements
    !

    ! 物理・数学定数設定
    ! Physical and mathematical constants settings
    !
    use constants0, only: PI
                              ! $ \pi $ .
                              ! 円周率.  Circular constant

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: CpDry
                              ! $ C_p $ [J kg-1 K-1]. 
                              ! 乾燥大気の定圧比熱. 
                              ! Specific heat of air at constant pressure

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: y_Lat, z_Sigma               ! $ \sigma $ レベル (整数). 
                              ! Full $ \sigma $ level

    ! NAMELIST ファイル入力に関するユーティリティ
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg, NmlutilAryValid

    ! ファイル入出力補助
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! 種別型パラメタ
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! 標準出力の装置番号. Unit number of standard output

    ! 文字列操作
    ! Character handling
    !
    use dc_string, only: StoA

    ! ヒストリデータ出力
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoAddVariable

    ! 鉛直拡散フラックス
    ! Vertical diffusion flux
    !
    use vdiffusion_my, only: VDiffusionInit


    ! 宣言文 ; Declaration statements
    !
    implicit none

    real(DP), parameter :: day_seconds = 86400.0_DP
                              ! 1 日の秒数. 
                              ! Seconds in day. 
    real(DP):: SigmaB         ! $ \sigma_b $ .
    real(DP):: kf             ! $ k_f $ .

    real(DP):: kfTimeScaleInDay
    real(DP):: FrictionLBLat

    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    integer:: k               ! 鉛直方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in vertical direction

    integer:: unit_nml        ! NAMELIST ファイルオープン用装置番号. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読み込み時の IOSTAT. 
                              ! IOSTAT of NAMELIST read

    ! NAMELIST 変数群
    ! NAMELIST group name
    !
    namelist /sl09_diffusion_nml/ SigmaB, kfTimeScaleInDay, FrictionLBLat, LBHeatFlux, SurfQMixDiffCoef, SurfQVap

          !
          ! デフォルト値については初期化手続 "sl09_diffusion#SL09DiffusionInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "sl09_diffusion#SL09DiffusionInit" for the default values. 
          !

    ! 実行文 ; Executable statement
    !

    if ( sl09_diffusion_inited ) return

    ! デフォルト値の設定
    ! Default values settings
    !
    SigmaB           =  0.8_DP
    kfTimeScaleInDay = 20.0_DP
    FrictionLBLat    = 16.3_DP
    LBHeatFlux       =  5.7_DP
    SurfQMixDiffCoef =  0.0_DP
!!$    SurfQMixDiffCoef = 800.0d2    ! Sugiyama et al. (2009) Nagare Multimedia
    SurfQVap         =  0.0_DP
!!$    SurfQVap         = 7.816d-4   ! Sugiyama et al. (2009) Nagare Multimedia


    ! NAMELIST の読み込み
    ! NAMELIST is input
    !
    if ( trim(namelist_filename) /= '' ) then
      call FileOpen( unit_nml, namelist_filename, mode = 'r' ) ! (in)

      rewind( unit_nml )
      read( unit_nml, nml = sl09_diffusion_nml, iostat = iostat_nml )               ! (out)
      close( unit_nml )

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
!!$      if ( iostat_nml == 0 ) write( STDOUT, nml = held_suarez_1994_nml )
    end if

    ! 係数の設定
    ! Configure coefficients
    !
    kf     = 1.0_DP / ( kfTimeScaleInDay * day_seconds )

    allocate( xyz_kv (0:imax-1, 1:jmax, 1:kmax) )
    do k = 1, kmax
      do j = 1, jmax
        if ( abs( y_Lat(j) ) * 180.0_DP / PI <= FrictionLBLat ) then
          xyz_kv(:,j,k) = 0.0_DP
        else
          xyz_kv(:,j,k) = kf * max( 0.0_DP, ( z_Sigma(k) - SigmaB ) / ( 1.0_DP - SigmaB ) )
        end if
      end do
    end do


    ! 鉛直拡散フラックス (Mellor and Yamada, 1974, レベル 2)
    ! Vertical diffusion flux (Mellor and Yamada, 1974, Level 2)
    !
    call VDiffusionInit


    ! ヒストリデータ出力のためのへの変数登録
    ! Register of variables for history data output
    !
    call HistoryAutoAddVariable( 'DUDtVDiffSL09', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'eastward wind tendency', 'm s-2' )
    call HistoryAutoAddVariable( 'DVDtVDiffSL09', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'northward wind tendency', 'm s-2' )
    call HistoryAutoAddVariable( 'DTempDtVDiffSL09', (/ 'lon ', 'lat ', 'sig ', 'time' /), 'temperature tendency', 'K s-1' )

    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'SigmaB           = %f', d = (/ SigmaB /) )
    call MessageNotify( 'M', module_name, 'kfTimeScaleInDay = %f', d = (/ kfTimeScaleInDay /) )
    call MessageNotify( 'M', module_name, 'FrictionLBLat    = %f', d = (/ FrictionLBLat /) )
    call MessageNotify( 'M', module_name, 'LBHeatFlux       = %f', d = (/ LBHeatFlux /) )
    call MessageNotify( 'M', module_name, 'SurfQMixDiffCoef = %f', d = (/ SurfQMixDiffCoef /) )
    call MessageNotify( 'M', module_name, 'SurfQVap         = %f', d = (/ SurfQVap /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    sl09_diffusion_inited = .true.
  end subroutine SL09DiffusionInit
sl09_diffusion_inited
Variable :
sl09_diffusion_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag

Private Instance methods

LBHeatFlux
Variable :
LBHeatFlux :real(DP), save
SurfQMixDiffCoef
Variable :
SurfQMixDiffCoef :real(DP), save
SurfQVap
Variable :
SurfQVap :real(DP), save
module_name
Constant :
module_name = ‘sl09_diffusion :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: sl09_diffusion.f90,v 1.8 2013/09/16 12:20:02 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version
xyz_kv
Variable :
xyz_kv(:,:,:) :real(DP), save, allocatable
: $ k_v $ .