Class surface_flux_bulk
In: surface_flux/surface_flux_bulk_primitive.f90

地表面フラックス

Surface flux

Note that Japanese and English are described in parallel.

Louis et al. (1982) の方法に基づいて地表面フラックスを計算.

Surface fluxes are calculated by using the scheme by Louis et al. (1982).

References

Louis, J-F., M. Tiedtke, and J-F. Geleyn, A short history of the PBL parameterization at ECMWF, Workshop on Planetary Boundary Layer Parameterization, 59-80, ECMWF, Reading, U.K., 1982.

Procedures List

SurfaceFlux :地表面フラックスの計算
SurfaceFluxOutput :地表面フラックスの出力
———— :————
SurfaceFlux :Calculate surface fluxes
SurfaceFluxOutput :Output surface fluxes

NAMELIST

NAMELIST#surface_flux_bulk_nml

Methods

Included Modules

gridset dc_types dc_message constants timeset dc_trace gtool_historyauto namelist_util dc_iounit dc_string axesset

Public Instance methods

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 (full level)
xyr_Temp(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ T $ . 温度 (半整数レベル). Temperature (half level)
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ p_s $ . 地表面気圧 (半整数レベル). Surface pressure (half level)
xy_SurfHeight(0:imax-1,1:jmax) :real(DP), intent(in)
: $ z_s $ . 地表面高度. Surface height.
xyz_Height(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: 高度 (整数レベル). Height (full level)
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: Exner 関数 (整数レベル). Exner function (full level)
xyr_Exner(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: Exner 関数 (半整数レベル). Exner function (half level)
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(in)
: 地表面温度. Surface temperature
xy_SurfRoughLength(0:imax-1, 1:jmax) :real(DP), intent(in)
: 地表粗度長. Surface rough length
xyr_UFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(inout)
: 東西風速フラックス. Eastward wind flux
xyr_VFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(inout)
: 南北風速フラックス. Northward wind flux
xyr_TempFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(inout)
: 温度フラックス. Temperature flux
xy_SurfVelTransCoef(0:imax-1, 1:jmax) :real(DP), intent(out)
: 輸送係数:運動量. Diffusion coefficient: velocity
xy_SurfTempTransCoef(0:imax-1, 1:jmax) :real(DP), intent(out)
: 輸送係数:温度. Transfer coefficient: temperature

速度, 温度の表面フラックスと輸送係数を計算します.

Surface fluxes and transfer coefficients of velocity and temperature.

[Source]

  subroutine SurfaceFlux( xyz_U, xyz_V, xyz_Temp, xyr_Temp, xyr_Press, xy_SurfHeight, xyz_Height, xyz_Exner, xyr_Exner, xy_SurfTemp, xy_SurfRoughLength, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xy_SurfVelTransCoef, xy_SurfTempTransCoef )
    !
    ! 速度, 温度の表面フラックスと輸送係数を計算します. 
    !
    ! Surface fluxes and transfer coefficients of velocity and temperature.
    ! 
    !

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

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

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

    ! デバッグ用ユーティリティ
    ! Utilities for debug
    !
    use dc_trace, only: DbgMessage, BeginSub, EndSub

    ! 宣言文 ; 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 (full level)
    real(DP), intent(in):: xyr_Temp (0:imax-1, 1:jmax, 0:kmax)
                              ! $ T $ . 温度 (半整数レベル). 
                              ! Temperature (half level)
    real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
                              ! $ p_s $ . 地表面気圧 (半整数レベル). 
                              ! Surface pressure (half level)
    real(DP), intent(in):: xy_SurfHeight(0:imax-1,1:jmax)
                              ! $ z_s $ . 地表面高度. 
                              ! Surface height. 
    real(DP), intent(in):: xyz_Height (0:imax-1, 1:jmax, 1:kmax)
                              ! 高度 (整数レベル). 
                              ! Height (full level)
    real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
                              ! Exner 関数 (整数レベル). 
                              ! Exner function (full level)
    real(DP), intent(in):: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
                              ! Exner 関数 (半整数レベル). 
                              ! Exner function (half level)
    real(DP), intent(in):: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature
    real(DP), intent(in):: xy_SurfRoughLength (0:imax-1, 1:jmax)
                              ! 地表粗度長. 
                              ! Surface rough length
    real(DP), intent(inout):: xyr_UFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 東西風速フラックス. 
                              ! Eastward wind flux
    real(DP), intent(inout):: xyr_VFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 南北風速フラックス. 
                              ! Northward wind flux
    real(DP), intent(inout):: xyr_TempFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 温度フラックス. 
                              ! Temperature flux
    real(DP), intent(out):: xy_SurfVelTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:運動量. 
                              ! Diffusion coefficient: velocity
    real(DP), intent(out):: xy_SurfTempTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:温度. 
                              ! Transfer coefficient: temperature

    ! 作業変数
    ! Work variables
    !
    real(DP):: xy_SurfBulkRiNum (0:imax-1, 1:jmax)
                              ! バルク $ R_i $ 数. 
                              ! Bulk $ R_i $ number
    real(DP):: xy_SurfTempBulkCoef (0:imax-1, 1:jmax)
                              ! バルク係数:温度. 
                              ! Bulk coefficient: temperature
    real(DP):: xy_SurfVelBulkCoef (0:imax-1, 1:jmax)
                              ! バルク係数:運動量. 
                              ! Bulk coefficient: temperature
    real(DP):: xy_SurfVelAbs (0:imax-1, 1:jmax)
                              ! 風速絶対値. 
                              ! Absolute velocity

    real(DP):: xy_UFluxSurf (0:imax-1, 1:jmax)
                              ! 地表面の東西風速フラックス. 
                              ! Eastward wind flux on surface
    real(DP):: xy_VFluxSurf (0:imax-1, 1:jmax)
                              ! 地表面の南北風速フラックス. 
                              ! Northward wind flux on surface
    real(DP):: xy_TempFluxSurf (0:imax-1, 1:jmax)
                              ! 地表面の温度フラックス. 
                              ! Temperature flux on surface

    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    integer:: n               ! 組成方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in dimension of constituents

    ! 実行文 ; Executable statement
    !

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

    ! 初期化
    ! Initialization
    !
    if ( .not. surface_flux_bulk_inited ) call SurfFluxInit

    ! バルク $ R_i $ 数算出
    ! Calculate bulk $ R_i $
    !
    do j = 1, jmax
      do i = 0, imax-1
        xy_SurfVelAbs(i,j) = sqrt ( xyz_U(i,j,1)**2 + xyz_V(i,j,1)**2 )

        xy_SurfBulkRiNum(i,j) = Grav / ( xy_SurfTemp(i,j) / xyr_Exner(i,j,0) ) * ( xyz_Temp(i,j,1) / xyz_Exner(i,j,1) - xy_SurfTemp(i,j) / xyr_Exner(i,j,0) ) / max( xy_SurfVelAbs(i,j), VelMinForRi )**2 * ( xyz_Height(i,j,1) - xy_SurfHeight(i,j) )
      end do
    end do


    ! バルク係数算出
    ! Calculate bulk coefficients
    !
    call BulkCoef( xy_SurfBulkRiNum, xy_SurfRoughLength, xy_SurfHeight, xyz_Height, xy_SurfVelBulkCoef, xy_SurfTempBulkCoef )


    ! 輸送係数の計算
    ! Calculate transfer coefficient
    !
    do i = 0, imax-1
      do j = 1, jmax
        xy_SurfVelTransCoef(i,j) = xy_SurfVelBulkCoef(i,j) * xyr_Press(i,j,0) / ( GasRDry * xyr_Temp(i,j,0) ) * min( max( xy_SurfVelAbs(i,j), VelMinForVel ), VelMaxForVel )

        xy_SurfTempTransCoef(i,j) = xy_SurfTempBulkCoef(i,j) * xyr_Press(i,j,0) / ( GasRDry * xyr_Temp(i,j,0) ) * min( max( xy_SurfVelAbs(i,j), VelMinForTemp ), VelMaxForTemp )
      end do
    end do


    ! 地表面フラックスの計算
    ! Calculate fluxes on flux
    !
    xy_UFluxSurf    = - xy_SurfVelTransCoef * xyz_U(:,:,1)
    xy_VFluxSurf    = - xy_SurfVelTransCoef * xyz_V(:,:,1)
!!$    xy_TempFluxSurf =   CpDry * xy_SurfTempTransCoef &
!!$      &                   * (   xy_SurfTemp           &
!!$      &                       - xyz_Temp(:,:,1) / xy_SurfExner )
    xy_TempFluxSurf = - CpDry * xyr_Exner(:,:,0) * xy_SurfTempTransCoef * (   xyz_Temp(:,:,1) / xyz_Exner(:,:,1) - xy_SurfTemp     / xyr_Exner(:,:,0) )

    ! フラックスの計算
    ! Calculate fluxes
    !
    xyr_UFlux(:,:,0)    = xyr_UFlux(:,:,0)    + xy_UFluxSurf
    xyr_VFlux(:,:,0)    = xyr_VFlux(:,:,0)    + xy_VFluxSurf
    xyr_TempFlux(:,:,0) = xyr_TempFlux(:,:,0) + xy_TempFluxSurf

    ! ヒストリデータ出力
    ! History data output
    !

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

  end subroutine SurfaceFlux
Subroutine :
xyr_UFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: 東西風速フラックス. Eastward wind flux
xyr_VFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: 南北風速フラックス. Northward wind flux
xyr_TempFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: 温度フラックス. Temperature flux
xyz_DUDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{u}{t} $ . 東西風速変化. Eastward wind tendency
xyz_DVDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{v}{t} $ . 南北風速変化. Northward wind tendency
xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{T}{t} $ . 温度変化. Temperature tendency
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(in)
: 地表面温度. Surface temperature
xy_DSurfTempDt(0:imax-1, 1:jmax) :real(DP), intent(in)
: 地表面温度変化率. Surface temperature tendency
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ hat{p} $ . 気圧 (半整数レベル). Air pressure (half level)
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: Exner 関数 (整数レベル). Exner function (full level)
xyr_Exner(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: Exner 関数 (半整数レベル). Exner function (half level)
xy_SurfVelTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸送係数:運動量. Diffusion coefficient: velocity
xy_SurfTempTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸送係数:温度. Transfer coefficient: temperature

フラックス (xyr_UFlux, xyr_VFlux, xyr_TempFlux) について, その他の引数を用いて補正し, 出力を行う.

Fluxes (xyr_UFlux, xyr_VFlux, xyr_TempFlux) are corrected by using other arguments, and the corrected values are output.

[Source]

  subroutine SurfaceFluxOutput( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xy_SurfTemp, xy_DSurfTempDt, xyr_Press, xyz_Exner, xyr_Exner, xy_SurfVelTransCoef, xy_SurfTempTransCoef )
    !
    ! フラックス (xyr_UFlux, xyr_VFlux, xyr_TempFlux)
    ! について, その他の引数を用いて補正し, 出力を行う. 
    !
    ! Fluxes (xyr_UFlux, xyr_VFlux, xyr_TempFlux) are
    ! corrected by using other arguments, and the corrected values are output.
    !

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

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

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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xyr_UFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 東西風速フラックス. 
                              ! Eastward wind flux
    real(DP), intent(in):: xyr_VFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 南北風速フラックス. 
                              ! Northward wind flux
    real(DP), intent(in):: xyr_TempFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 温度フラックス. 
                              ! Temperature flux

    real(DP), intent(in):: xyz_DUDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{u}{t} $ . 東西風速変化. 
                              ! Eastward wind tendency
    real(DP), intent(in):: xyz_DVDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{v}{t} $ . 南北風速変化. 
                              ! Northward wind tendency
    real(DP), intent(in):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . 温度変化. 
                              ! Temperature tendency

    real(DP), intent(in):: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature
    real(DP), intent(in):: xy_DSurfTempDt (0:imax-1, 1:jmax)
                              ! 地表面温度変化率. 
                              ! Surface temperature tendency
    real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
                              ! $ \hat{p} $ . 気圧 (半整数レベル). 
                              ! Air pressure (half level)
    real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
                              ! Exner 関数 (整数レベル). 
                              ! Exner function (full level)
    real(DP), intent(in):: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
                              ! Exner 関数 (半整数レベル). 
                              ! Exner function (half level)
    real(DP), intent(in):: xy_SurfVelTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:運動量. 
                              ! Diffusion coefficient: velocity
    real(DP), intent(in):: xy_SurfTempTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:温度. 
                              ! Transfer coefficient: temperature

    ! 出力のための作業変数
    ! Work variables for output
    !
    real(DP):: xyr_UFluxCor (0:imax-1, 1:jmax, 0:kmax)
                              ! 東西風速フラックス. 
                              ! Eastward wind flux
    real(DP):: xyr_VFluxCor (0:imax-1, 1:jmax, 0:kmax)
                              ! 南北風速フラックス. 
                              ! Northward wind flux
    real(DP):: xyr_TempFluxCor (0:imax-1, 1:jmax, 0:kmax)
                              ! 温度フラックス. 
                              ! Temperature flux

    ! 作業変数
    ! Work variables
    !
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    integer:: n               ! 組成方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in dimension of constituents


    ! 実行文 ; Executable statement
    !

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

    ! 初期化
    ! Initialization
    !
    if ( .not. surface_flux_bulk_inited ) call SurfFluxInit


    ! Output of fluxes at t
    !

    ! 風速, 温度, 比湿フラックス補正
    ! Correct fluxes of wind, temperature, specific humidity
    !
    do j = 1, jmax
      do i = 0, imax-1
        xyr_UFluxCor( i,j,0 ) = xyr_UFlux( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DUDt( i,j,1 ) * DelTime

        xyr_VFluxCor( i,j,0 ) = xyr_VFlux( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DVDt( i,j,1 ) * DelTime

        xyr_TempFluxCor( i,j,0 ) = xyr_TempFlux( i,j,0 ) - CpDry * xyr_Exner( i,j,0 ) * xy_SurfTempTransCoef( i,j ) * ( xyz_DTempDt( i,j,1 ) / xyz_Exner( i,j,1 ) - xy_DSurfTempDt( i,j ) / xyr_Exner( i,j,0 ) ) * DelTime
      end do
    end do

    ! ヒストリデータ出力
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'TauX' , xyr_UFluxCor    (:,:,0) )
    call HistoryAutoPut( TimeN, 'TauY' , xyr_VFluxCor    (:,:,0) )
    call HistoryAutoPut( TimeN, 'Sens' , xyr_TempFluxCor (:,:,0) )


    ! Output of fluxes at t - \Delta t
    !

    ! 風速, 温度, 比湿フラックス補正
    ! Correct fluxes of wind, temperature, specific humidity
    !
    do j = 1, jmax
      do i = 0, imax-1
        xyr_UFluxCor( i,j,0 ) = xyr_UFlux( i,j,0 )
        xyr_VFluxCor( i,j,0 ) = xyr_VFlux( i,j,0 )
        xyr_TempFluxCor( i,j,0 ) = xyr_TempFlux( i,j,0 )
      end do
    end do

    ! ヒストリデータ出力
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'TauXB', xyr_UFluxCor    (:,:,0) )
    call HistoryAutoPut( TimeN, 'TauYB', xyr_VFluxCor    (:,:,0) )
    call HistoryAutoPut( TimeN, 'SensB', xyr_TempFluxCor (:,:,0) )

    ! Output of fluxes at t + \Delta t
    !

    ! 風速, 温度, 比湿フラックス補正
    ! Correct fluxes of wind, temperature, specific humidity
    !
    do j = 1, jmax
      do i = 0, imax-1
        xyr_UFluxCor( i,j,0 ) = xyr_UFlux( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DUDt( i,j,1 ) * 2.0d0 * DelTime

        xyr_VFluxCor( i,j,0 ) = xyr_VFlux( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DVDt( i,j,1 ) * 2.0d0 * DelTime

        xyr_TempFluxCor( i,j,0 ) = xyr_TempFlux( i,j,0 ) - CpDry * xyr_Exner( i,j,0 ) * xy_SurfTempTransCoef( i,j ) * ( xyz_DTempDt( i,j,1 ) / xyz_Exner( i,j,1 ) - xy_DSurfTempDt( i,j ) / xyr_Exner( i,j,0 ) ) * 2.0d0 * DelTime
      end do
    end do

    ! ヒストリデータ出力
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'TauXA' , xyr_UFluxCor    (:,:,0) )
    call HistoryAutoPut( TimeN, 'TauYA' , xyr_VFluxCor    (:,:,0) )
    call HistoryAutoPut( TimeN, 'SensA' , xyr_TempFluxCor (:,:,0) )


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

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

Private Instance methods

Subroutine :
xy_SurfBulkRiNum(0:imax-1, 1:jmax) :real(DP), intent(in)
: バルク $ R_i $ 数. Bulk $ R_i $ number
xy_SurfRoughLength(0:imax-1, 1:jmax) :real(DP), intent(in)
: 地表粗度長 Surface rough length
xy_SurfHeight(0:imax-1,1:jmax) :real(DP), intent(in)
: $ z_s $ . 地表面高度. Surface height.
xyz_Height(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: 高度. Height
xy_SurfVelBulkCoef(0:imax-1, 1:jmax) :real(DP), intent(out)
: バルク係数:運動量. Bulk coefficient: temperature
xy_SurfTempBulkCoef(0:imax-1, 1:jmax) :real(DP), intent(out)
: バルク係数:温度. Bulk coefficient: temperature

バルク係数を算出します.

Bulk coefficients are calculated.

[Source]

  subroutine BulkCoef( xy_SurfBulkRiNum, xy_SurfRoughLength, xy_SurfHeight, xyz_Height, xy_SurfVelBulkCoef, xy_SurfTempBulkCoef )
    !
    ! バルク係数を算出します.
    !
    ! Bulk coefficients are calculated.
    !

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

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: FKarm                 ! $ k $ .
                              ! カルマン定数. 
                              ! Karman constant

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xy_SurfBulkRiNum (0:imax-1, 1:jmax)
                              ! バルク $ R_i $ 数. 
                              ! Bulk $ R_i $ number

!!$    real(DP), intent(in):: xy_SurfVelAbs (0:imax-1, 1:jmax)
!!$                              ! 風速絶対値. 
!!$                              ! Absolute velocity
    real(DP), intent(in):: xy_SurfRoughLength (0:imax-1, 1:jmax)
                              ! 地表粗度長
                              ! Surface rough length
    real(DP), intent(in):: xy_SurfHeight(0:imax-1,1:jmax)
                              ! $ z_s $ . 地表面高度. 
                              ! Surface height. 
    real(DP), intent(in):: xyz_Height (0:imax-1, 1:jmax, 1:kmax)
                              ! 高度. 
                              ! Height
    real(DP), intent(out):: xy_SurfVelBulkCoef (0:imax-1, 1:jmax)
                              ! バルク係数:運動量. 
                              ! Bulk coefficient: temperature
    real(DP), intent(out):: xy_SurfTempBulkCoef (0:imax-1, 1:jmax)
                              ! バルク係数:温度. 
                              ! Bulk coefficient: temperature

    ! 作業変数
    ! Work variables
    !
    real(DP) :: xy_SurfBulkCoefInNeutCond    (0:imax-1, 1:jmax)

    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude

    ! 実行文 ; Executable statement
    !

    if ( FlagConstBulkCoef ) then

      ! Use of constant bulk coefficient
      !

      xy_SurfVelBulkCoef  = ConstBulkCoef
      xy_SurfTempBulkCoef = ConstBulkCoef

    else

      ! Parameterization by Louis et al. (1981)
      !

      ! 中立バルク係数の計算
      ! Calculate bulk coefficient in neutral condition
      !
      xy_SurfBulkCoefInNeutCond  = ( FKarm / log ( ( xyz_Height(:,:,1) - xy_SurfHeight ) / xy_SurfRoughLength ) )**2

      if ( FlagUseOfBulkCoefInNeutralCond ) then

        ! 中立条件でのバルク係数の設定
        ! Set bulk coefficient in neutral condition
        !

        xy_SurfVelBulkCoef  = xy_SurfBulkCoefInNeutCond
        xy_SurfTempBulkCoef = xy_SurfBulkCoefInNeutCond

      else

        ! 非中立条件でのバルク係数の計算
        ! Calculate bulk coefficients in non-neutral condition
        !

        do j = 1, jmax
          do i = 0, imax-1

            if ( xy_SurfBulkRiNum(i,j) > 0.0_DP ) then 

              xy_SurfVelBulkCoef(i,j) = xy_SurfBulkCoefInNeutCond(i,j) / (   1.0_DP + 10.0_DP * xy_SurfBulkRiNum(i,j) / sqrt( 1.0_DP + 5.0_DP * xy_SurfBulkRiNum(i,j) ) )

              xy_SurfTempBulkCoef(i,j) = xy_SurfBulkCoefInNeutCond(i,j) / (   1.0_DP + 15.0_DP * xy_SurfBulkRiNum(i,j) * sqrt( 1.0_DP + 5.0_DP * xy_SurfBulkRiNum(i,j) ) )

            else

              xy_SurfVelBulkCoef(i,j) = xy_SurfBulkCoefInNeutCond(i,j) * (   1.0_DP - 10.0_DP * xy_SurfBulkRiNum(i,j) / (   1.0_DP + 75.0_DP * xy_SurfBulkCoefInNeutCond(i,j) * sqrt( - ( xyz_Height(i,j,1) - xy_SurfHeight(i,j) ) / xy_SurfRoughLength(i,j) * xy_SurfBulkRiNum(i,j) ) ) )

              xy_SurfTempBulkCoef(i,j) = xy_SurfBulkCoefInNeutCond(i,j) * (   1.0_DP - 15.0_DP * xy_SurfBulkRiNum(i,j) / (   1.0_DP + 75.0_DP * xy_SurfBulkCoefInNeutCond(i,j) * sqrt( - ( xyz_Height(i,j,1) - xy_SurfHeight(i,j) ) / xy_SurfRoughLength(i,j) * xy_SurfBulkRiNum(i,j) ) ) )

            end if
          end do
        end do

      end if

    end if


    ! 最大/最小 判定
    ! Measure maximum/minimum
    !
    do i = 0, imax-1
      do j = 1, jmax

        xy_SurfVelBulkCoef(i,j)  = max( min( xy_SurfVelBulkCoef(i,j), VelBulkCoefMax ), VelBulkCoefMin )

        xy_SurfTempBulkCoef(i,j) = max( min( xy_SurfTempBulkCoef(i,j), TempBulkCoefMax ), TempBulkCoefMin )

      end do
    end do


  end subroutine BulkCoef
ConstBulkCoef
Variable :
ConstBulkCoef :real(DP), save
: バルク係数一定値. Steady value of bulk coefficient
FlagConstBulkCoef
Variable :
FlagConstBulkCoef :logical, save
: Flag for using constant bulk coefficient
FlagUseOfBulkCoefInNeutralCond
Variable :
FlagUseOfBulkCoefInNeutralCond :logical, save
: Flag for using bulk coefficient in neutral condition
Subroutine :

依存モジュールの初期化チェック

Check initialization of dependency modules

[Source]

  subroutine InitCheck
    !
    ! 依存モジュールの初期化チェック
    !
    ! Check initialization of dependency modules

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

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

    ! 格子点設定
    ! Grid points settings
    !
    use gridset, only: gridset_inited

    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: constants_inited

    ! 座標データ設定
    ! Axes data settings
    !
    use axesset, only: axesset_inited

    ! 時刻管理
    ! Time control
    !
    use timeset, only: timeset_inited

    ! 実行文 ; Executable statement
    !

    if ( .not. namelist_util_inited ) call MessageNotify( 'E', module_name, '"namelist_util" module is not initialized.' )

    if ( .not. gridset_inited ) call MessageNotify( 'E', module_name, '"gridset" module is not initialized.' )

    if ( .not. constants_inited ) call MessageNotify( 'E', module_name, '"constants" module is not initialized.' )

    if ( .not. axesset_inited ) call MessageNotify( 'E', module_name, '"axesset" module is not initialized.' )

    if ( .not. timeset_inited ) call MessageNotify( 'E', module_name, '"timeset" module is not initialized.' )

  end subroutine InitCheck
Subroutine :

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

"surface_flux_bulk" module is initialized. "NAMELIST#surface_flux_bulk_nml" is loaded in this procedure.

This procedure input/output NAMELIST#surface_flux_bulk_nml .

[Source]

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

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

    ! 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

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

    ! NAMELIST 変数群
    ! NAMELIST group name
    !
    namelist /surface_flux_bulk_nml/ FlagConstBulkCoef, FlagUseOfBulkCoefInNeutralCond, ConstBulkCoef, VelMinForRi, VelMinForVel, VelMinForTemp, VelMaxForVel, VelMaxForTemp, VelBulkCoefMin, TempBulkCoefMin  , VelBulkCoefMax, TempBulkCoefMax
          !
          ! デフォルト値については初期化手続 "surface_flux_bulk#SurfFluxInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "surface_flux_bulk#SurfFluxInit" for the default values. 
          !

    ! 実行文 ; Executable statement
    !

    if ( surface_flux_bulk_inited ) return
    call InitCheck

    ! デフォルト値の設定
    ! Default values settings
    !
    FlagConstBulkCoef              = .false.
    FlagUseOfBulkCoefInNeutralCond = .false.
    ConstBulkCoef                  =  0.0_DP

    VelMinForRi   = 0.01_DP
    VelMinForVel  = 0.01_DP
    VelMinForTemp = 0.01_DP
    VelMaxForVel  = 1000.0_DP
    VelMaxForTemp = 1000.0_DP


    VelBulkCoefMin  =  0.0_DP
    TempBulkCoefMin =  0.0_DP
    VelBulkCoefMax  =  1.0_DP
    TempBulkCoefMax =  1.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 = surface_flux_bulk_nml, iostat = iostat_nml )        ! (out)
      close( unit_nml )

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if

    ! ヒストリデータ出力のためのへの変数登録
    ! Register of variables for history data output
    !
    call HistoryAutoAddVariable( 'TauX', (/ 'lon ', 'lat ', 'time' /), 'surface stress(x)  ', 'N m-2' )

    call HistoryAutoAddVariable( 'TauY', (/ 'lon ', 'lat ', 'time' /), 'surface stress(y)  ', 'N m-2' )

    call HistoryAutoAddVariable( 'Sens', (/ 'lon ', 'lat ', 'time' /), 'sensible heat flux', 'W m-2' )

    call HistoryAutoAddVariable( 'TauXB', (/ 'lon ', 'lat ', 'time' /), 'surface stress(x)  ', 'N m-2' )

    call HistoryAutoAddVariable( 'TauYB', (/ 'lon ', 'lat ', 'time' /), 'surface stress(y)  ', 'N m-2' )

    call HistoryAutoAddVariable( 'SensB', (/ 'lon ', 'lat ', 'time' /), 'sensible heat flux', 'W m-2' )

    call HistoryAutoAddVariable( 'TauXA', (/ 'lon ', 'lat ', 'time' /), 'surface stress(x)  ', 'N m-2' )

    call HistoryAutoAddVariable( 'TauYA', (/ 'lon ', 'lat ', 'time' /), 'surface stress(y)  ', 'N m-2' )

    call HistoryAutoAddVariable( 'SensA', (/ 'lon ', 'lat ', 'time' /), 'sensible heat flux', 'W m-2' )

    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )

    call MessageNotify( 'M', module_name, '  VelMinForRi       = %f', d = (/ VelMinForRi   /) )
    call MessageNotify( 'M', module_name, '  VelMinForVel      = %f', d = (/ VelMinForVel  /) )
    call MessageNotify( 'M', module_name, '  VelMinForTemp     = %f', d = (/ VelMinForTemp /) )
    call MessageNotify( 'M', module_name, '  VelMaxForVel      = %f', d = (/ VelMaxForVel  /) )
    call MessageNotify( 'M', module_name, '  VelMaxForTemp     = %f', d = (/ VelMaxForTemp /) )
    call MessageNotify( 'M', module_name, 'Bulk coefficients:' )
    call MessageNotify( 'M', module_name, '  FlagConstBulkCoef              = %b', l = (/ FlagConstBulkCoef /) )
    call MessageNotify( 'M', module_name, '  FlagUseOfBulkCoefInNeutralCond = %b', l = (/ FlagUseOfBulkCoefInNeutralCond /) )
    call MessageNotify( 'M', module_name, '  ConstBulkCoef   = %f', d = (/ ConstBulkCoef   /) )
    call MessageNotify( 'M', module_name, '  VelBulkCoefMin  = %f', d = (/ VelBulkCoefMin  /) )
    call MessageNotify( 'M', module_name, '  TempBulkCoefMin = %f', d = (/ TempBulkCoefMin /) )
    call MessageNotify( 'M', module_name, '  VelBulkCoefMax  = %f', d = (/ VelBulkCoefMax  /) )
    call MessageNotify( 'M', module_name, '  TempBulkCoefMax = %f', d = (/ TempBulkCoefMax /) )

    surface_flux_bulk_inited = .true.
  end subroutine SurfFluxInit
TempBulkCoefMax
Variable :
TempBulkCoefMax :real(DP), save
: $ T $ バルク係数最大値. Maximum value of $ T $ bulk coefficient
TempBulkCoefMin
Variable :
TempBulkCoefMin :real(DP), save
: $ T $ バルク係数最小値. Minimum value of $ T $ bulk coefficient
VelBulkCoefMax
Variable :
VelBulkCoefMax :real(DP), save
: $ u $ バルク係数最大値. Maximum value of $ u $ bulk coefficient
VelBulkCoefMin
Variable :
VelBulkCoefMin :real(DP), save
: $ u $ バルク係数最小値. Minimum value of $ u $ bulk coefficient
VelMaxForTemp
Variable :
VelMaxForTemp :real(DP), save
: 熱用風最大値. Maximum value of velocity for thermal
VelMaxForVel
Variable :
VelMaxForVel :real(DP), save
: 運動量用風最大値. Maximum value of velocity for momentum
VelMinForRi
Variable :
VelMinForRi :real(DP), save
: $ R_i $ 数用風最小値. Minimum value of velocity for $ R_i $ number
VelMinForTemp
Variable :
VelMinForTemp :real(DP), save
: 熱用風最小値. Minimum value of velocity for thermal
VelMinForVel
Variable :
VelMinForVel :real(DP), save
: 運動量用風最小値. Minimum value of velocity for momentum
module_name
Constant :
module_name = ‘surface_flux_bulk :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: surface_flux_bulk_primitive.f90,v 1.1.1.1 2010-08-17 05:24:51 takepiro Exp $’ :character(*), parameter
: モジュールのバージョン Module version