Class held_suarez_1994
In: held_suarez_1994/held_suarez_1994.f90

Held and Suarez (1994) による強制と散逸

Forcing and dissipation suggested by Held and Suarez (1994)

Note that Japanese and English are described in parallel.

Held and Suarez (1994) で提案される乾燥大気 GCM ベンチマーク用の 強制と散逸を計算します. 与える強制と散逸として, 温度場の帯状対称場への簡単なニュートン冷却と, 境界層摩擦を表現する下層風のレイリー摩擦を用います. 詳細を以下に記します.

Forcing and dissipation for dry air GCM benchmark suggested by Held and Suarez (1994) are caluclate. We use simple Newtonian relaxation of the temperature field to a zonally symmetric state and Rayleigh damping of low-level winds to represent boundary-layer friction. Their specifications are detailed as follows.

\[

   \left( \DP{\Dvect{v}}{t} \right)_{\mathrm{HS94}} =
       - k_v (\sigma) \Dvect{v}, \] \[
   \left( \DP{T}{t} \right)_{\mathrm{HS94}} =
       - k_T (\phi, \sigma) [T - T_{eq} (\phi,p)], \] \[
   T_{eq} = \mathrm{max}
    \left\{
       200 \mathrm{K},
       \left[
         315 \mathrm{K} - (\Delta T)_y \sin^2\phi
                        - (\Delta \theta)_z
                          \log \left(\frac{p}{p_0}\right) \cos^2\phi
       \right] \left(\frac{p}{p_0}\right)^\kappa
    \right\}, \] \[
   k_T = k_a + (k_s - k_a)
         \mathrm{max}
         \left(0, \frac{\sigma - \sigma_b}{1 - \sigma_b}\right) \cos^4\phi,
    \] \[
   k_v = k_f
         \mathrm{max}
         \left(0, \frac{\sigma - \sigma_b}{1 - \sigma_b}\right),
    \] \[
   \sigma_b = 0.7, \qquad
   k_f = 1 \mathrm{day}^{-1}, \qquad
   k_a = \Dinv{40} \mathrm{day}^{-1}, \qquad
   k_s = \Dinv{4} \mathrm{day}^{-1}, \] \[
   (\Delta T)_y = 60 \mathrm{K}, \qquad
   (\Delta \theta)_z = 10 \mathrm{K}, \qquad
   p_0 = 1000 \mathrm{hPa}, \qquad
   \kappa = \frac{R}{c_p}.

\]

Forcing では, 与えられた速度や温度 ( $ t+Delta t$ を想定) に対して以下のように強制と散逸を適用します.

By Forcing, forcing and dissipation are applied to given wind and temperature ($ t+Delta t$ is expected) as follows.

\[

   \hat{\Dvect{v}}^{t+\Delta t} =
     \Dvect{v}^{t+\Delta t}
     + 2 \Delta t \left( \DP{\Dvect{v}}{t} \right)_{\mathrm{HS94}} \] \[
   \hat{T}^{t+\Delta t} =
     T^{t+\Delta t}
     + 2 \Delta t \left( \DP{T}{t} \right)_{\mathrm{HS94}}

\]

Procedures List

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

References

  • Held, I. M., Suarez, M. J., 1994: A proposal for the intercomparison of the dynamical cores of atmospheric general circuation models. Bull. Am. Meteor. Soc., 75, 1825--1830.

Methods

Included Modules

gridset dc_types dc_message axesset timeset gtool_historyauto constants namelist_util dc_iounit dc_string

Public Instance methods

Subroutine :

モジュール内部の変数の割り付け解除を行います.

Deallocate variables in this module.

[Source]

  subroutine HS94Finalize
    !
    ! モジュール内部の変数の割り付け解除を行います. 
    !
    ! Deallocate variables in this module. 
    !

    ! 宣言文 ; Declaration statements
    !
    implicit none

    ! 実行文 ; Executable statement
    !

    if ( .not. held_suarez_1994_inited ) return

    ! 割り付け解除
    ! Deallocation
    !
    if ( allocated( z_kv  ) ) deallocate( z_kv  )
    if ( allocated( yz_kt ) ) deallocate( yz_kt )

    held_suarez_1994_inited = .false.

  end subroutine HS94Finalize
Subroutine :
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
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T $ . 温度. Temperature
xy_Ps(0:imax-1, 1:jmax) :real(DP), intent(in)
: $ p_s $ . 地表面気圧. Surface pressure
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

引数として与えられた東西風速 xyz_U, 南北風速 xyz_V, 温度 xyz_Temp から, 温度場の帯状対称場への簡単なニュートン冷却と 境界層摩擦を表現する下層風のレイリー摩擦による 風速と温度の変化率を求め, xyz_DUDt, xyz_DVDt, xyz_DTempDt に返します.

Tendencies by simple Newtonian relaxation of the temperature field to a zonally symmetric state and Rayleigh damping of low-level winds to represent boundary-layer friction are calculated from eastward wind "xyz_U", northward wind "xyz_V", temperature "xyz_Temp". And the tencencies are returned as "xyz_DUDt", "xyz_DVDt", "xyz_DTempDt".

[Source]

  subroutine HS94Forcing( xyz_U,    xyz_V,    xyz_Temp, xy_Ps, xyz_DUDt, xyz_DVDt, xyz_DTempDt )
    !
    ! 引数として与えられた東西風速 xyz_U, 南北風速 xyz_V, 
    ! 温度 xyz_Temp から, 
    ! 温度場の帯状対称場への簡単なニュートン冷却と
    ! 境界層摩擦を表現する下層風のレイリー摩擦による
    ! 風速と温度の変化率を求め, 
    ! xyz_DUDt, xyz_DVDt, xyz_DTempDt に返します. 
    !
    ! Tendencies by simple Newtonian relaxation of the temperature field to a
    ! zonally symmetric state and Rayleigh damping of low-level winds to
    ! represent boundary-layer friction are calculated 
    ! from eastward wind "xyz_U", northward wind "xyz_V", 
    ! temperature "xyz_Temp".
    ! And the tencencies are returned as 
    ! "xyz_DUDt", "xyz_DVDt", "xyz_DTempDt". 
    !
    !

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

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

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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    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):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ . 温度. 
                              ! Temperature
    real(DP), intent(in):: xy_Ps (0:imax-1, 1:jmax)
                              ! $ p_s $ . 地表面気圧. 
                              ! Surface pressure
    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

    ! 作業変数
    ! Work variables
    !
    real(DP):: xyz_TempEQ (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T_{eq} $ . 平衡温度. 
                              ! Equilibrium temperature
    real(DP):: xyz_Press (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ . 圧力. 
                              ! Pressure

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

    ! 実行文 ; Executable statement
    !

    ! 初期化確認
    ! Initialization check
    !
    if ( .not. held_suarez_1994_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 $
    !
    do k = 1, kmax
      xyz_DUDt (:,:,k) = - z_kv (k) * xyz_U (:,:,k)
      xyz_DVDt (:,:,k) = - z_kv (k) * xyz_V (:,:,k)
    end do

    ! 温度 $ T $ へニュートン冷却を適用
    ! Apply Newtonian relaxation to temperature $ T $
    !
    do k = 1, kmax
       xyz_Press(:,:,k) = z_Sigma(k) * xy_Ps
    enddo

    do j = 1, jmax
      xyz_TempEQ(:,j,:) = max( 200.0_DP, (   315.0_DP - DelTempY * sin( y_Lat(j) ) ** 2 - DelPotTempZ * log( xyz_Press(:,j,:) / P0 ) * cos( y_Lat(j) ) ** 2 ) * ( xyz_Press(:,j,:) / P0 ) ** Kappa )
    end do

    do k = 1, kmax
      do j = 1, jmax
        xyz_DTempDt (:,j,k) = - yz_kt (j,k) * ( xyz_Temp (:,j,k) - xyz_TempEQ (:,j,k) )
      end do
    end do


    ! ヒストリデータ出力
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'DUDtHS94',    xyz_DUDt )
    call HistoryAutoPut( TimeN, 'DVDtHS94',    xyz_DVDt )
    call HistoryAutoPut( TimeN, 'DTempDtHS94', xyz_DTempDt )
    call HistoryAutoPut( TimeN, 'TempEQHS94',  xyz_TempEQ )


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

  end subroutine HS94Forcing
Subroutine :

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

"held_suarez_1994" module is initialized. "NAMELIST#held_suarez_1994_nml" is loaded in this procedure.

This procedure input/output NAMELIST#held_suarez_1994_nml .

[Source]

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

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

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: GasRDry, 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

    ! 宣言文 ; 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 $ .
                              ! 地表面での Rayleigh 摩擦の緩和係数
    real(DP):: ka             ! $ k_a $ .
                              ! 大気上層における Newton 冷却の緩和係数
    real(DP):: ks             ! $ k_s $ .
                              ! 赤道地表面における Newton 冷却の緩和係数

    real(DP):: kfTimeScaleInDay
    real(DP):: kaTimeScaleInDay
    real(DP):: ksTimeScaleInDay

    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 /held_suarez_1994_nml/ SigmaB, kfTimeScaleInDay, kaTimeScaleInDay, ksTimeScaleInDay
          !
          ! デフォルト値については初期化手続 "held_suarez_1994#HS94Init" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "held_suarez_1994#HS94Init" for the default values. 
          !

    ! 実行文 ; Executable statement
    !

    if ( held_suarez_1994_inited ) return


    ! デフォルト値の設定
    ! Default values settings
    !
    SigmaB           =  0.7_DP
    kfTimeScaleInDay =  1.0_DP
    kaTimeScaleInDay = 40.0_DP
    ksTimeScaleInDay =  4.0_DP

    ! 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 = held_suarez_1994_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
    !
    Kappa = GasRDry / CpDry

    P0          = 1000.0e2_DP
    DelTempY    = 60.0_DP
    DelPotTempZ = 10.0_DP

!!$    kf     = 1.0_DP / day_seconds
!!$    ka     = 1.0_DP / ( 40.0_DP * day_seconds )
!!$    ks     = 1.0_DP / (  4.0_DP * day_seconds )
    kf     = 1.0_DP / ( kfTimeScaleInDay * day_seconds )
    ka     = 1.0_DP / ( kaTimeScaleInDay * day_seconds )
    ks     = 1.0_DP / ( ksTimeScaleInDay * day_seconds )

    allocate( z_kv (1:kmax) )
    z_kv = kf * max( 0.0_DP, ( z_Sigma - SigmaB ) / ( 1.0_DP - SigmaB ) )

    allocate( yz_kt (1:jmax, 1:kmax) )

    do k = 1, kmax
      do j = 1, jmax
        yz_kt(j,k) = ka + ( ks - ka ) * max( 0.0_DP, ( z_Sigma(k) - SigmaB ) / ( 1.0_DP - SigmaB ) ) * cos( y_Lat(j) ) ** 4
      end do
    end do


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

    ! 印字 ; 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, 'kaTimeScaleInDay = %f', d = (/ kaTimeScaleInDay /) )
    call MessageNotify( 'M', module_name, 'ksTimeScaleInDay = %f', d = (/ ksTimeScaleInDay /) )

    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    held_suarez_1994_inited = .true.

  end subroutine HS94Init

Private Instance methods

DelPotTempZ
Variable :
DelPotTempZ :real(DP)
: $ (Delta theta)_z $ . 赤道における鉛直方向の温位差
DelTempY
Variable :
DelTempY :real(DP)
: $ (Delta T)_y $ . 極と赤道の温度差
Kappa
Variable :
Kappa :real(DP)
: $ kappa = R/C_p $ . 気体定数の定圧比熱に対する比. Ratio of gas constant to specific heat
P0
Variable :
P0 :real(DP)
: $ p_0 $ .
held_suarez_1994_inited
Variable :
held_suarez_1994_inited = .false. :logical, save
: 初期設定フラグ. Initialization flag
module_name
Constant :
module_name = ‘held_suarez_1994 :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: held_suarez_1994.f90,v 1.14 2012/04/27 11:24:45 noda Exp $’ :character(*), parameter
: モジュールのバージョン Module version
yz_kt
Variable :
yz_kt(:,:) :real(DP), allocatable
: $ k_T $ .
z_kv
Variable :
z_kv(:) :real(DP), allocatable
: $ k_v $ .