| Class | surface_flux_bulk | 
| In: | surface_flux/surface_flux_bulk.F90 | 
Note that Japanese and English are described in parallel.
地表面フラックスを計算します.
Surface fluxes are calculated.
| SurfaceFlux : | 地表面フラックスの計算 | 
| SurfaceFluxOutput : | 地表面フラックスの出力 | 
| ———— : | ———— | 
| SurfaceFlux : | Calculate surface fluxes | 
| SurfaceFluxOutput : | Output surface fluxes | 
| Subroutine : | |||
| xyz_U(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyz_V(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyz_Temp(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyr_Temp(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyz_QVap(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyr_Press(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyz_Height(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyz_Exner(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyr_Exner(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTemp(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfHumidCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfRoughLength(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xyr_UFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(inout) 
 | ||
| xyr_VFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(inout) 
 | ||
| xyr_TempFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(inout) 
 | ||
| xyr_QVapFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(inout) 
 | ||
| xy_SurfVelTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | ||
| xy_SurfTempTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | ||
| xy_SurfQVapTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | 
温度, 比湿, 気圧から, 放射フラックスを計算します.
Calculate radiation flux from temperature, specific humidity, and air pressure.
  subroutine SurfaceFlux( xyz_U, xyz_V, xyz_Temp, xyr_Temp, xyz_QVap, xyr_Press, xyz_Height, xyz_Exner, xyr_Exner, xy_SurfTemp, xy_SurfHumidCoef, xy_SurfRoughLength, xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef )
    !
    ! 温度, 比湿, 気圧から, 放射フラックスを計算します. 
    !
    ! Calculate radiation flux from temperature, specific humidity, and 
    ! air pressure. 
    !
    ! モジュール引用 ; USE statements
    !
    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: Grav, GasRDry, CpDry, LatentHeat
                              ! $ L $ [J kg-1] . 
                              ! 凝結の潜熱. 
                              ! Latent heat of condensation
    ! 飽和比湿計算
    ! Evaluate saturation specific humidity
    !
#ifdef LIB_SATURATE_NHA1992
    use saturate_nha1992, only: CalcQVapSat
#elif LIB_SATURATE_T1930
    use saturate_t1930, only: CalcQVapSat
#else
    use saturate_t1930, only: CalcQVapSat
#endif
    ! 時刻管理
    ! 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):: xyz_QVap (0:imax-1, 1:jmax, 1:kmax)
                              ! $ q $ .     比湿. Specific humidity
    real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
                              ! $ p_s $ . 地表面気圧 (半整数レベル). 
                              ! Surface pressure (half level)
    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_SurfHumidCoef (0:imax-1, 1:jmax)
                              ! 地表湿潤度. 
                              ! Surface humidity coefficient
    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(inout):: xyr_QVapFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 比湿フラックス. 
                              ! Specific humidity 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
    real(DP), intent(out):: xy_SurfQVapTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:比湿. 
                              ! Transfer coefficient: specific humidity
    ! 作業変数
    ! 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_SurfQVapBulkCoef (0:imax-1, 1:jmax)
                              ! バルク係数:比湿. 
                              ! Bulk coefficient: specific humidity
    real(DP):: xy_SurfVelBulkCoef (0:imax-1, 1:jmax)
                              ! バルク係数:運動量. 
                              ! Bulk coefficient: temperature
    real(DP):: xy_SurfExner (0:imax-1, 1:jmax)
                              ! Exner 関数. 
                              ! Exner function
    real(DP):: xy_SurfVelAbs (0:imax-1, 1:jmax)
                              ! 風速絶対値. 
                              ! Absolute velocity
    real(DP):: xy_SurfQVapSat (0:imax-1, 1:jmax)
                              ! 地表飽和比湿. 
                              ! Saturated specific humidity on surface
    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
    real(DP):: xy_QVapFluxSurf (0:imax-1, 1:jmax)
                              ! 地表面の比湿フラックス. 
                              ! Specific humidity flux on surface
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    ! 実行文 ; Executable statement
    !
    ! 計算時間計測開始
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )
    ! 初期化
    ! Initialization
    !
    if ( .not. surface_flux_bulk_inited ) call SurfFluxInit
    ! Exner 関数算出
    ! Calculate Exner functions
    !
    xy_SurfExner = xyz_Exner(:,:,1) / xyr_Exner(:,:,0)
    ! バルク $ R_i $ 数算出
    ! Calculate bulk $ R_i $
    !
    do i = 0, imax-1
      do j = 1, jmax
        xy_SurfVelAbs(i,j) = sqrt ( xyz_U(i,j,1)**2 + xyz_V(i,j,1)**2 )
        xy_SurfBulkRiNum(i,j) = Grav / BasePotTemp * ( xyz_Temp(i,j,1) / xy_SurfExner(i,j) - xy_SurfTemp(i,j)  ) / max( xy_SurfVelAbs(i,j), VelMinForRi )**2 * xyz_Height(i,j,1)
      end do
    end do
    
    ! バルク係数算出
    ! Calculate bulk coefficients
    !
    call BulkCoef( xy_SurfBulkRiNum, xy_SurfRoughLength, xy_SurfRoughLength, xyz_Height(:,:,1), xy_SurfVelBulkCoef, xy_SurfTempBulkCoef, xy_SurfQVapBulkCoef )   ! (out)
    ! 輸送係数の計算
    ! 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 )
        
        xy_SurfQVapTransCoef(i,j) = xy_SurfQVapBulkCoef(i,j) * xyr_Press(i,j,0) / ( GasRDry * xyr_Temp(i,j,0) ) * min( max( xy_SurfVelAbs(i,j), VelMinForQVap ), VelMaxForQVap )
        
      end do
    end do
    
    ! 飽和比湿の計算
    ! Calculate saturated specific humidity
    !
    do i = 0, imax-1
      do j = 1, jmax
        xy_SurfQVapSat(i,j) = CalcQVapSat( xy_SurfTemp(i,j), xyr_Press(i,j,0) )
      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_QVapFluxSurf =   LatentHeat * xy_SurfQVapTransCoef * xy_SurfHumidCoef * ( xy_SurfQVapSat - xyz_QVap(:,:,1) )
    ! フラックスの計算
    ! 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
    xyr_QVapFlux(:,:,0) = xyr_QVapFlux(:,:,0) + xy_QVapFluxSurf
    
    ! ヒストリデータ出力
    ! 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) 
 | ||
| xyr_VFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_TempFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyr_QVapFlux(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyz_DUDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyz_DVDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyz_DQVapDt(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTemp(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_DSurfTempDt(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xyr_Press(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xyz_Exner(0:imax-1, 1:jmax, 1:kmax) : | real(DP), intent(in) 
 | ||
| xyr_Exner(0:imax-1, 1:jmax, 0:kmax) : | real(DP), intent(in) 
 | ||
| xy_SurfHumidCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfVelTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTempTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfQVapTransCoef(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | 
フラックス (xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux). について, その他の引数を用いて補正し, 出力を行う.
Fluxes (xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux) are corrected by using other arguments, and the corrected values are output.
  subroutine SurfaceFluxOutput( xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyz_DQVapDt, xy_SurfTemp, xy_DSurfTempDt, xyr_Press, xyz_Exner, xyr_Exner, xy_SurfHumidCoef, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef )
    !
    ! フラックス (xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux). 
    ! について, その他の引数を用いて補正し, 出力を行う. 
    !
    ! Fluxes (xyr_UFlux, xyr_VFlux, xyr_TempFlux, xyr_QVapFlux) are
    ! corrected by using other arguments, and the corrected values are output.
    !
    ! モジュール引用 ; USE statements
    !
    ! 物理定数設定
    ! Physical constants settings
    !
    use constants, only: Grav, GasRDry, CpDry, LatentHeat
                              ! $ L $ [J kg-1] . 
                              ! 凝結の潜熱. 
                              ! Latent heat of condensation
    ! 飽和比湿計算
    ! Evaluate saturation specific humidity
    !
#ifdef LIB_SATURATE_NHA1992
    use saturate_nha1992, only: CalcQVapSat, CalcDQVapSatDTemp
#elif LIB_SATURATE_T1930
    use saturate_t1930, only: CalcQVapSat, CalcDQVapSatDTemp
#else
    use saturate_t1930, only: CalcQVapSat, CalcDQVapSatDTemp
#endif
    ! 時刻管理
    ! 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):: xyr_QVapFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! 比湿フラックス. 
                              ! Specific humidity 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):: xyz_DQVapDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{q}{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_SurfHumidCoef (0:imax-1, 1:jmax)
                              ! 地表湿潤度. 
                              ! Surface humidity coefficient
    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
    real(DP), intent(in):: xy_SurfQVapTransCoef (0:imax-1, 1:jmax)
                              ! 輸送係数:比湿. 
                              ! Transfer coefficient: specific humidity
    ! 出力のための作業変数
    ! 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
    real(DP):: xyr_QVapFluxCor (0:imax-1, 1:jmax, 0:kmax)
                              ! 比湿フラックス. 
                              ! Specific humidity flux
    real(DP):: xy_SurfExner (0:imax-1, 1:jmax)
                              ! Exner 関数. 
                              ! Exner function
    real(DP):: xy_SurfQVapSat (0:imax-1, 1:jmax)
                              ! 地表飽和比湿. 
                              ! Saturated specific humidity on surface
    real(DP):: xy_SurfDQVapSatDTemp (0:imax-1, 1:jmax)
                              ! 地表飽和比湿変化. 
                              ! Saturated specific humidity tendency on surface
    ! 作業変数
    ! Work variables
    !
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    real(DP):: LCp
                              ! $ L / C_p $ [K]. 
    ! 実行文 ; Executable statement
    !
    ! 計算時間計測開始
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )
    ! 初期化
    ! Initialization
    !
    if ( .not. surface_flux_bulk_inited ) call SurfFluxInit
    ! Exner 関数算出
    ! Calculate Exner functions
    !
    xy_SurfExner = xyz_Exner(:,:,1) / xyr_Exner(:,:,0)
    ! 飽和比湿の計算
    ! Calculate saturated specific humidity
    !
    do i = 0, imax-1
      do j = 1, jmax
        xy_SurfQVapSat(i,j) = CalcQVapSat( xy_SurfTemp(i,j), xyr_Press(i,j,0) )
      end do
    end do
    do i = 0, imax-1
      do j = 1, jmax
        xy_SurfDQVapSatDTemp(i,j) = CalcDQVapSatDTemp( xy_SurfTemp(i,j), xy_SurfQVapSat(i,j) )
      end do
    end do
    ! 風速, 温度, 比湿フラックス補正
    ! Correct fluxes of wind, temperature, specific humidity
    !
    LCp = LatentHeat / CpDry
    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 * xy_SurfTempTransCoef( i,j ) / xy_SurfExner( i,j ) * xyz_DTempDt( i,j,1 )  * DelTime + CpDry * xy_SurfTempTransCoef( i,j ) * xy_DSurfTempDt( i,j ) * DelTime
        xyr_QVapFluxCor( i,j,0 ) = xyr_QVapFlux( i,j,0 ) - CpDry * xy_SurfQVapTransCoef( i,j ) * xy_SurfHumidCoef( i,j ) * xyz_DQVapDt( i,j,1 ) * LCp * DelTime + LatentHeat * xy_SurfQVapTransCoef( i,j ) * xy_SurfHumidCoef( i,j ) * xy_SurfDQVapSatDTemp( i,j ) * xy_DSurfTempDt( i,j ) * 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) )
    call HistoryAutoPut( TimeN, 'EVap', xyr_QVapFluxCor(:,:,0) )
    ! 計算時間計測一時停止
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )
  end subroutine SurfaceFluxOutput
          | Variable : | |||
| surface_flux_bulk_inited = .false. : | logical, save, public 
 | 
| Subroutine : | |||
| xy_SurfBulkRiNum(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfVelRoughLength(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfTempRoughLength(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfHeight(0:imax-1, 1:jmax) : | real(DP), intent(in) 
 | ||
| xy_SurfVelBulkCoef(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | ||
| xy_SurfTempBulkCoef(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | ||
| xy_SurfQVapBulkCoef(0:imax-1, 1:jmax) : | real(DP), intent(out) 
 | 
バルク係数を算出します.
Bulk coefficients are calculated.
  subroutine BulkCoef( xy_SurfBulkRiNum, xy_SurfVelRoughLength, xy_SurfTempRoughLength, xy_SurfHeight, xy_SurfVelBulkCoef, xy_SurfTempBulkCoef, xy_SurfQVapBulkCoef )
    !
    ! バルク係数を算出します.
    !
    ! 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_SurfVelRoughLength (0:imax-1, 1:jmax)
                              ! 地表粗度長 (運動量). 
                              ! Surface rough length (momentum)
    real(DP), intent(in):: xy_SurfTempRoughLength (0:imax-1, 1:jmax)
                              ! 地表粗度長 (熱). 
                              ! Surface rough length (thermal)
    real(DP), intent(in):: xy_SurfHeight (0:imax-1, 1:jmax)
                              ! 最下層の高度. 
                              ! Height of lowest layer
    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
    real(DP), intent(out):: xy_SurfQVapBulkCoef (0:imax-1, 1:jmax)
                              ! バルク係数:比湿. 
                              ! Bulk coefficient: specific humidity
    ! 作業変数
    ! Work variables
    !
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    ! 実行文 ; Executable statement
    !
    ! 中立バルク係数の計算
    ! Calculate neutral bulk coefficients
    !
    if ( ConstBulkCoef < 0.0_DP ) then
      
      xy_SurfVelBulkCoef  = ( FKarm / log ( xy_SurfHeight / xy_SurfVelRoughLength ) )**2
      xy_SurfTempBulkCoef = ( FKarm / log ( xy_SurfHeight / xy_SurfTempRoughLength ) )**2
      xy_SurfQVapBulkCoef = xy_SurfTempBulkCoef
      
    else
      xy_SurfVelBulkCoef  = ConstBulkCoef
      xy_SurfTempBulkCoef = ConstBulkCoef
      xy_SurfQVapBulkCoef = ConstBulkCoef
    end if
    
    ! 非中立バルク係数の計算
    ! Calculate non-neutral bulk coefficients
    !
    if ( .not. Neutral ) then
      
      do i = 0, imax-1
        do j = 1, jmax
          if ( xy_SurfBulkRiNum(i,j) > 0.0_DP ) then 
            xy_SurfVelBulkCoef(i,j) = xy_SurfVelBulkCoef(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_SurfTempBulkCoef(i,j) / (   1.0_DP + 15.0_DP * xy_SurfBulkRiNum(i,j) / sqrt( 1.0_DP + 5.0_DP * xy_SurfBulkRiNum(i,j) ) )
            xy_SurfQVapBulkCoef(i,j) = xy_SurfTempBulkCoef(i,j)
          else
            xy_SurfVelBulkCoef(i,j) = xy_SurfVelBulkCoef(i,j) * (   1.0_DP - 10.0_DP * xy_SurfBulkRiNum(i,j) / (   1.0_DP + 75.0_DP * xy_SurfVelBulkCoef(i,j) * sqrt( - xy_SurfHeight(i,j) / xy_SurfVelRoughLength(i,j) * xy_SurfBulkRiNum(i,j) ) ) )
            
            xy_SurfTempBulkCoef(i,j) = xy_SurfTempBulkCoef(i,j) * (   1.0_DP - 15.0_DP * xy_SurfBulkRiNum(i,j) / (   1.0_DP + 75.0_DP * xy_SurfTempBulkCoef(i,j) * sqrt( - xy_SurfHeight(i,j) / xy_SurfTempRoughLength(i,j) * xy_SurfBulkRiNum(i,j) ) ) )
            xy_SurfQVapBulkCoef(i,j) = xy_SurfTempBulkCoef(i,j)
          end if
        end do
      end do
      
    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 )
        xy_SurfQVapBulkCoef(i,j) = max( min( xy_SurfQVapBulkCoef(i,j), QVapBulkCoefMax ), QVapBulkCoefMin )
      end do
    end do
  end subroutine BulkCoef
          | Subroutine : | 
依存モジュールの初期化チェック
Check initialization of dependency modules
  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
          | Variable : | |||
| QVapBulkCoefMax : | real(DP), save 
 | 
| Variable : | |||
| QVapBulkCoefMin : | real(DP), save 
 | 
| 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 .
  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/ VelMinForRi, VelMinForVel, VelMinForTemp, VelMinForQVap, VelMaxForVel, VelMaxForTemp, VelMaxForQVap, Neutral, ConstBulkCoef, VelBulkCoefMin, TempBulkCoefMin, QVapBulkCoefMin, VelBulkCoefMax, TempBulkCoefMax, QVapBulkCoefMax
          !
          ! デフォルト値については初期化手続 "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
    !
    BasePotTemp   = 300.0_DP
    VelMinForRi   = 0.01_DP
    VelMinForVel  = 0.01_DP
    VelMinForTemp = 0.01_DP
    VelMinForQVap = 0.01_DP
    VelMaxForVel  = 1000.0_DP
    VelMaxForTemp = 1000.0_DP
    VelMaxForQVap = 1000.0_DP
    Neutral         = .false.
    ConstBulkCoef   = -1.0_DP
    VelBulkCoefMin  =  0.0_DP
    TempBulkCoefMin =  0.0_DP
    QVapBulkCoefMin =  0.0_DP
    VelBulkCoefMax  =  1.0_DP
    TempBulkCoefMax =  1.0_DP
    QVapBulkCoefMax =  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( 'EVap', (/ 'lon ', 'lat ', 'time' /), 'latent 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, '  VelMinForQVap = %f', d = (/ VelMinForQVap /) )
    call MessageNotify( 'M', module_name, '  VelMaxForVel  = %f', d = (/ VelMaxForVel  /) )
    call MessageNotify( 'M', module_name, '  VelMaxForTemp = %f', d = (/ VelMaxForTemp /) )
    call MessageNotify( 'M', module_name, '  VelMaxForQVap = %f', d = (/ VelMaxForQVap /) )
    call MessageNotify( 'M', module_name, 'Bulk coefficients:' )
    call MessageNotify( 'M', module_name, '  Neutral         = %b', l = (/ Neutral          /) )
    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, '  QVapBulkCoefMin = %f', d = (/ QVapBulkCoefMin /) )
    call MessageNotify( 'M', module_name, '  VelBulkCoefMax  = %f', d = (/ VelBulkCoefMax  /) )
    call MessageNotify( 'M', module_name, '  TempBulkCoefMax = %f', d = (/ TempBulkCoefMax /) )
    call MessageNotify( 'M', module_name, '  QVapBulkCoefMax = %f', d = (/ QVapBulkCoefMax /) )
    call MessageNotify( 'M', module_name, 'Saturation:' )
    call MessageNotify( 'M', module_name, '  Scheme of saturation = %c', c1 = saturate_scheme )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )
    surface_flux_bulk_inited = .true.
  end subroutine SurfFluxInit
          | Variable : | |||
| TempBulkCoefMax : | real(DP), save 
 | 
| Variable : | |||
| TempBulkCoefMin : | real(DP), save 
 | 
| Variable : | |||
| VelBulkCoefMax : | real(DP), save 
 | 
| Variable : | |||
| VelBulkCoefMin : | real(DP), save 
 | 
| Variable : | |||
| VelMaxForQVap : | real(DP), save 
 | 
| Variable : | |||
| VelMaxForTemp : | real(DP), save 
 | 
| Variable : | |||
| VelMaxForVel : | real(DP), save 
 | 
| Variable : | |||
| VelMinForQVap : | real(DP), save 
 | 
| Variable : | |||
| VelMinForRi : | real(DP), save 
 | 
| Variable : | |||
| VelMinForTemp : | real(DP), save 
 | 
| Variable : | |||
| VelMinForVel : | real(DP), save 
 | 
| Constant : | |||
| module_name = ‘surface_flux_bulk‘ : | character(*), parameter 
 | 
| Constant : | |
| saturate_scheme = ifdef LIB_SATURATE_NHA1992 elif LIB_SATURATE_T1930 else endif : | character(*), parameter | 
| Constant : | |||
| version = ’$Name: dcpam5-20090317 $’ // ’$Id: surface_flux_bulk.F90,v 1.13 2009-03-17 05:53:23 morikawa Exp $’ : | character(*), parameter 
 |