Class intg_surftemp
In: util/intg_surftemp.f90

地面温度, 土壌温度の時間積分

Time integration of surface temperature and soil temperature

Note that Japanese and English are described in parallel.

地面温度と土壌温度の時間積分を行います.

Time integration of surface temperature and soiltemperature

Procedures List

IntegralSurfTemp :地面温度, 土壌温度の時間積分
————— :—————
IntegralSurfTemp :Time integration of surface temperature and soil temperature

Methods

Included Modules

gridset dc_types dc_message timeset namelist_util dc_iounit dc_string constants axesset

Public Instance methods

Subroutine :
xy_DSurfTempDt(0:imax-1, 1:jmax) :real(DP), intent(in)
: 地表面温度変化率 (K s-1) Surface temperature tendency (K s-1)
xyz_DSoilTempDt(0:imax-1, 1:jmax, 1:kslmax) :real(DP), intent(in)
: $ DP{Tg}{t} $ . 土壌温度変化 (K s-1) Temperature tendency (K s-1)
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(inout)
: 地表面温度. Surface temperature
xyz_SoilTemp(0:imax-1, 1:jmax, 1:kslmax) :real(DP), intent(inout)
: 土壌温度 (K) Soil temperature (K)

地面温度, 土壌温度の時間積分を行います.

Time integration of surface temperature and soil temperature

[Source]

  subroutine IntegralSurfTemp( xy_DSurfTempDt, xyz_DSoilTempDt, xy_SurfTemp   , xyz_SoilTemp )
    !
    ! 地面温度, 土壌温度の時間積分を行います. 
    !
    ! Time integration of surface temperature and soil temperature
    !
    !

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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(in):: xy_DSurfTempDt (0:imax-1, 1:jmax)
                              ! 地表面温度変化率 (K s-1)
                              ! Surface temperature tendency (K s-1)
    real(DP), intent(in):: xyz_DSoilTempDt (0:imax-1, 1:jmax, 1:kslmax)
                              ! $ \DP{Tg}{t} $ . 土壌温度変化 (K s-1)
                              ! Temperature tendency (K s-1)
    real(DP), intent(inout):: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature
    real(DP), intent(inout):: xyz_SoilTemp(0:imax-1, 1:jmax, 1:kslmax)
                              ! 土壌温度 (K)
                              ! Soil temperature (K)


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


    ! 実行文 ; Executable statement
    !

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

    ! 初期化
    ! Initialization
    !
    if ( .not. intg_surftemp_inited ) call IntgSurfTempInit

    ! 地表面温度時間積分
    ! Time integration of surface temperature
    !
    xy_SurfTemp = xy_SurfTemp + xy_DSurfTempDt * DelTime

    ! 土壌温度時間積分
    ! Time integration of subsurface temperature
    !
    xyz_SoilTemp = xyz_SoilTemp + xyz_DSoilTempDt * DelTime

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

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

Private Instance methods

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 :

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

"intg_surftemp" module is initialized. "NAMELIST#intg_surftemp_nml" is loaded in this procedure.

[Source]

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

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

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

    ! ファイル入出力補助
    ! 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

    ! 宣言文 ; 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 /intg_surftemp_nml/
          !
          ! デフォルト値については初期化手続 "intg_surftemp#IntgSurfTempInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "intg_surftemp#IntgSurfTempInit" for the default values. 
          !

    ! 実行文 ; Executable statement
    !

    if ( intg_surftemp_inited ) return
    call InitCheck

    ! デフォルト値の設定
    ! Default values settings
    !

!!$    ! NAMELIST の読み込み
!!$    ! NAMELIST is input
!!$    !
!!$    if ( trim(namelist_filename) /= '' ) then
!!$      call FileOpen( unit_nml, &          ! (out)
!!$        & namelist_filename, mode = 'r' ) ! (in)
!!$
!!$      rewind( unit_nml )
!!$      read( unit_nml, &           ! (in)
!!$        & nml = intg_surftemp_nml, &  ! (out)
!!$        & iostat = iostat_nml )   ! (out)
!!$      close( unit_nml )
!!$
!!$      call NmlutilMsg( iostat_nml, module_name ) ! (in)
!!$    end if

    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    intg_surftemp_inited = .true.
  end subroutine IntgSurfTempInit
module_name
Constant :
module_name = ‘intg_surftemp :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: dcpam5-20110407 $’ // ’$Id: intg_surftemp.f90,v 1.8 2010-03-24 12:01:15 yot Exp $’ :character(*), parameter
: モジュールのバージョン Module version