Class surface_properties
In: surface_properties/surface_properties_primitive.f90

惑星表面特性の設定

Setting planetary surface properties

Note that Japanese and English are described in parallel.

海面温度や地表面諸量を設定します.

Data about sea surface temperature (SST) or various values on surface are set.

Procedures List

SetSurfaceProperties :惑星表面特性の設定
———— :————
SetSurfaceProperties :Setting surface properties

NAMELIST

NAMELIST#surface_properties_nml

Methods

Included Modules

gridset dc_types dc_message gtool_history surface_data roughlen_landoceancontrast roughlen_Matthews dc_string timeset read_time_series namelist_util dc_iounit fileset constants axesset

Public Instance methods

Subroutine :
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: 地表面温度. Surface temperature
xy_SurfRoughLength(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: 地表粗度長. Surface rough length
xy_SurfHeatCapacity(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: 地表熱容量. Surface heat capacity
xy_GroundTempFlux(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: 地中熱フラックス. Ground temperature flux
xy_SurfCond(0:imax-1, 1:jmax) :integer , intent(inout), optional
: 地表状態 (0: 固定, 1: 可変). Surface condition (0: fixed, 1: variable)
xy_SurfHeight(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: $ z_s $ . 地表面高度. Surface height.

惑星表面特性を設定します.

Set surface properties.

[Source]

  subroutine SetSurfaceProperties( xy_SurfTemp, xy_SurfRoughLength, xy_SurfHeatCapacity, xy_GroundTempFlux, xy_SurfCond, xy_SurfHeight )
    !
    ! 惑星表面特性を設定します. 
    !
    ! Set surface properties. 
    !

    ! モジュール引用 ; USE statements
    !
    ! 地表面データ提供
    ! Prepare surface data
    !
    use surface_data, only: SetSurfData

    ! 粗度長の設定, 陸面と海洋の差のみ考慮
    ! Set roughness length, only considering land-ocean contrast
    !
    use roughlen_landoceancontrast, only: SetRoughLenLandOceanContrast

    ! Matthews のデータに基づく地面粗度の設定
    ! set roughness length on land surface based on data by Matthews
    !
    use roughlen_Matthews, only: SetRoughLenLandMatthews

    ! gtool4 データ入力
    ! Gtool4 data input
    !
    use gtool_history, only: HistoryGet

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

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


    use read_time_series, only: SetValuesFromTimeSeriesWrapper


    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(inout), optional:: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature
    real(DP), intent(inout), optional:: xy_SurfRoughLength (0:imax-1, 1:jmax)
                              ! 地表粗度長. 
                              ! Surface rough length
    real(DP), intent(inout), optional:: xy_SurfHeatCapacity (0:imax-1, 1:jmax)
                              ! 地表熱容量. 
                              ! Surface heat capacity
    real(DP), intent(inout), optional:: xy_GroundTempFlux (0:imax-1, 1:jmax)
                              ! 地中熱フラックス. 
                              ! Ground temperature flux
    integer , intent(inout), optional:: xy_SurfCond (0:imax-1, 1:jmax)
                              ! 地表状態 (0: 固定, 1: 可変). 
                              ! Surface condition (0: fixed, 1: variable)
    real(DP), intent(inout), optional:: xy_SurfHeight (0:imax-1, 1:jmax)
                              ! $ z_s $ . 地表面高度. 
                              ! Surface height. 

    ! 作業変数
    ! Work variables
    !
    real(DP), allocatable, save:: xy_SurfTempSave (:,:)
                              ! 地表面温度の保存値 (K)
                              ! Saved values of surface temperature (K)

    logical, save:: flag_first_SurfCond = .true.
                              ! 初回を示すフラグ. 
                              ! Flag that indicates first loop

    logical, save:: flag_first_SurfTemp         = .true.
    logical, save:: flag_first_SurfHeight       = .true.
    logical, save:: flag_first_SurfRoughLength  = .true.
    logical, save:: flag_first_SurfHeatCapacity = .true.
    logical, save:: flag_first_GroundTempFlux   = .true.

    logical:: flag_mpi_init

    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_properties_inited ) call SurfacePropertiesInit


    flag_mpi_init = .true.


    ! NOTICE:
    ! The surface condition has to be set, before other fields are set.
    !
    !
    ! 地表状態
    ! Surface condition
    !
    if ( present(xy_SurfCond) ) then

      if ( SurfCondSetting == 'file' ) then
        ! データをファイルから取得
        ! Data is input from files
        !
        if ( flag_first_SurfCond ) then
          call HistoryGet( SurfCondFile, SurfCondName, xy_SurfCond, flag_mpi_split = flag_mpi_init )  ! (in) optional
        end if
      else if ( SurfCondSetting == 'generate_internally' ) then
        ! データ (デフォルト値) を surface_data モジュールから取得
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SurfCond ) then
          call SetSurfData( xy_SurfCond = xy_SurfCond )
        end if
      else
        call MessageNotify( 'E', module_name, ' SurfCondSetting = %c is not appropriate.', c1 = trim(SurfCondSetting) )
      end if

      flag_first_SurfCond = .false.

    end if

    ! NOTICE:
    ! Before set surface temperature, sea ice distribution has to be set.
    !
    ! 地表面温度
    ! surface temperature
    !
    if ( present(xy_SurfTemp) ) then

      if ( flag_first_SurfTemp ) then
        ! 保存用変数の割付
        ! Allocate a variable for save
        !
        allocate( xy_SurfTempSave  (0:imax-1, 1:jmax) )
      end if
      if ( SurfTempSetting == 'file' ) then
        ! データをファイルから取得
        ! Data is input from files
        !
!!$        if ( flag_first_SurfTemp ) then
!!$          call HistoryGet( &
!!$            & SurfTempFile, SurfTempName, &    ! (in)
!!$            & xy_SurfTempSave, &               ! (out)
!!$            & flag_mpi_split = flag_mpi_init ) ! (in) optional
!!$        end if
        call SetValuesFromTimeSeriesWrapper( SurfTempFile, SurfTempName, xy_SurfTempSave, 'SST' )
      else if ( SurfTempSetting == 'generate_internally' ) then
        ! データ (デフォルト値) を surface_data モジュールから取得
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SurfTemp ) then
          call SetSurfData( xy_SurfTemp = xy_SurfTempSave )
        end if
      else
        call MessageNotify( 'E', module_name, ' SurfTempSetting = %c is not appropriate.', c1 = trim(SurfTempSetting) )
      end if
      ! 地表面温度を SST で置き換え ( xy_SurfCond <=0 の場所のみ )
      ! Surface temperature is replaced with SST ( only xy_SurfCond <=0 )
      !
      if ( present(xy_SurfTemp) ) then
        do j = 1, jmax
          do i = 0, imax-1
            if ( ( xy_SurfCond(i,j)     <= 0              ) .and. ( xy_SurfTempSave(i,j) >  0.0_DP         ) ) then
                xy_SurfTemp(i,j) = xy_SurfTempSave(i,j)
            end if
          end do
        end do
      end if

      flag_first_SurfTemp = .false.
    end if

    ! 地形
    ! Topography
    !
    if ( present(xy_SurfHeight) ) then

      if ( SurfHeightSetting == 'file' ) then
        ! データをファイルから取得
        ! Data is input from files
        !
        if ( flag_first_SurfHeight ) then
          call HistoryGet( SurfHeightFile, SurfHeightName, xy_SurfHeight, flag_mpi_split = flag_mpi_init )   ! (in) optional
        end if
      else if ( SurfHeightSetting == 'generate_internally' ) then
        if ( flag_first_SurfHeight ) then
          xy_SurfHeight = 0.0_DP
        end if
      else
        call MessageNotify( 'E', module_name, ' SurfHeightSetting = %c is not appropriate.', c1 = trim(SurfHeightSetting) )
      end if

      flag_first_SurfHeight = .false.
    end if

    ! 粗度長
    ! Roughness length
    !
    if ( present(xy_SurfRoughLength) ) then

      if ( RoughLengthSetting == 'file' ) then
        ! データをファイルから取得
        ! Data is input from files
        !
        if ( flag_first_SurfRoughLength ) then
          call HistoryGet( RoughLengthFile, RoughLengthName, xy_SurfRoughLength, flag_mpi_split = flag_mpi_init )    ! (in) optional
        end if
      else if ( RoughLengthSetting == 'LOContrast' ) then
        ! 粗度長の設定, 陸面と海洋の差のみ考慮
        ! Set roughness length, only considering land-ocean contrast
        !
        call SetRoughLenLandOceanContrast( xy_SurfCond, xy_SurfRoughLength )
      else if ( RoughLengthSetting == 'Matthews' ) then
        ! 粗度長の設定, Matthews のデータに基づく
        ! Set roughness length based on Matthews dataset
        !
        call SetRoughLenLandMatthews( xy_SurfCond, xy_SurfRoughLength )
      else if ( RoughLengthSetting == 'generate_internally' ) then
        ! データ (デフォルト値) を surface_data モジュールから取得
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SurfRoughLength ) then
          call SetSurfData( xy_SurfRoughLength = xy_SurfRoughLength )
        end if
      else
        call MessageNotify( 'E', module_name, ' RoughLengthSetting = %c is not appropriate.', c1 = trim(RoughLengthSetting) )
      end if

      flag_first_SurfRoughLength = .false.
    end if


    ! 地表熱容量
    ! Surface heat capacity
    !
    if ( present(xy_SurfHeatCapacity) ) then

      if ( HeatCapacitySetting == 'file' ) then
        ! データをファイルから取得
        ! Data is input from files
        !
        if ( flag_first_SurfHeatCapacity ) then
          call HistoryGet( HeatCapacityFile, HeatCapacityName, xy_SurfHeatCapacity, flag_mpi_split = flag_mpi_init )      ! (in) optional
        end if
      else if ( HeatCapacitySetting == 'generate_internally' ) then
        ! データ (デフォルト値) を surface_data モジュールから取得
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SurfHeatCapacity ) then
          call SetSurfData( xy_SurfHeatCapacity = xy_SurfHeatCapacity )
        end if
      else
        call MessageNotify( 'E', module_name, ' HeatCapacitySetting = %c is not appropriate.', c1 = trim(HeatCapacitySetting) )
      end if

      flag_first_SurfHeatCapacity = .false.
    end if

    ! 地中熱フラックス
    ! Ground temperature flux
    !
    if ( present(xy_GroundTempFlux) ) then

      if ( TempFluxSetting == 'file' ) then
        ! データをファイルから取得
        ! Data is input from files
        !
        if ( flag_first_GroundTempFlux ) then
          call HistoryGet( TempFluxFile, TempFluxName, xy_GroundTempFlux, flag_mpi_split = flag_mpi_init )  ! (in) optional
        end if
      else if ( TempFluxSetting == 'generate_internally' ) then
        ! データ (デフォルト値) を surface_data モジュールから取得
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_GroundTempFlux ) then
          call SetSurfData( xy_GroundTempFlux = xy_GroundTempFlux )
        end if
      else
        call MessageNotify( 'E', module_name, ' TempFluxSetting = %c is not appropriate.', c1 = trim(TempFluxSetting) )
      end if

      flag_first_GroundTempFlux = .false.
    end if

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


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

Private Instance methods

HeatCapacityFile
Variable :
HeatCapacityFile :character(STRING), save
: 地表熱容量のファイル名. File name of surface heat capacity
HeatCapacityName
Variable :
HeatCapacityName :character(TOKEN) , save
: 地表熱容量の変数名. Variable name of surface heat capacity
HeatCapacitySetting
Variable :
HeatCapacitySetting :character(STRING), save
: 地表熱容量の設定方法 Setting of surface heat capacity
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

    ! 出力ファイルの基本情報管理
    ! Management basic information for output files
    !
    use fileset, only: fileset_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. fileset_inited ) call MessageNotify( 'E', module_name, '"fileset" 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
RoughLengthFile
Variable :
RoughLengthFile :character(STRING), save
: 地表粗度長のファイル名. File name of surface rough length
RoughLengthName
Variable :
RoughLengthName :character(TOKEN) , save
: 地表粗度長の変数名. Variable name of surface rough length
RoughLengthSetting
Variable :
RoughLengthSetting :character(STRING), save
: 地表粗度長の設定方法 Setting of surface rough length
SurfCondFile
Variable :
SurfCondFile :character(STRING), save
: 地表状態のファイル名. File name of surface condition
SurfCondName
Variable :
SurfCondName :character(TOKEN) , save
: 地表状態の変数名. Variable name of surface condition
SurfCondSetting
Variable :
SurfCondSetting :character(STRING), save
: 地表状態の設定方法 Setting of surface condition
SurfHeightFile
Variable :
SurfHeightFile :character(STRING), save
: 地表面高度のファイル名. File name of surface height
SurfHeightName
Variable :
SurfHeightName :character(TOKEN) , save
: 地表面高度の変数名. Variable name of surface height
SurfHeightSetting
Variable :
SurfHeightSetting :character(STRING), save
: 地表面高度の設定方法 Setting of surface height
SurfTempFile
Variable :
SurfTempFile :character(STRING), save
: 地表面温度のファイル名. File name of surface temperature
SurfTempName
Variable :
SurfTempName :character(TOKEN) , save
: 地表面温度の変数名.
SurfTempSetting
Variable :
SurfTempSetting :character(STRING), save
: 地表面温度の設定方法 Setting of surface temperature
Subroutine :

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

"surface_properties" module is initialized. "NAMELIST#surface_properties_nml" is loaded in this procedure.

This procedure input/output NAMELIST#surface_properties_nml .

[Source]

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

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

    ! 時刻管理
    ! Time control
    !
    use timeset, only: DelTime  ! $ \Delta t $ [s]

    ! 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

    ! 宣言文 ; Declaration statements
    !
    implicit none

    ! 作業変数
    ! Work variables
    !
    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_properties_nml/ SurfTempSetting, SurfTempFile, SurfTempName, RoughLengthSetting, RoughLengthFile, RoughLengthName, HeatCapacitySetting, HeatCapacityFile, HeatCapacityName, TempFluxSetting, TempFluxFile, TempFluxName, SurfCondSetting, SurfCondFile, SurfCondName, SurfHeightSetting, SurfHeightFile, SurfHeightName

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

!!$      & OutputFile, &
!!$      & IntValue, IntUnit


    ! 実行文 ; Executable statement
    !

    if ( surface_properties_inited ) return
    call InitCheck
    ! デフォルト値の設定
    ! Default values settings
    !
    SurfTempSetting     = 'generate_internally'
    SurfTempFile        = ''
    SurfTempName        = ''
    RoughLengthSetting  = 'generate_internally'
    RoughLengthFile     = ''
    RoughLengthName     = ''
    HeatCapacitySetting = 'generate_internally'
    HeatCapacityFile    = ''
    HeatCapacityName    = ''
    TempFluxSetting     = 'generate_internally'
    TempFluxFile        = ''
    TempFluxName        = ''
    SurfCondSetting     = 'generate_internally'
    SurfCondFile        = ''
    SurfCondName        = ''
    SurfHeightSetting   = 'generate_internally'
    SurfHeightFile      = ''
    SurfHeightName      = ''

!!$    OutputFile = 'sst.nc'
!!$    IntValue   = 1.0_DP
!!$    IntUnit    = 'day'

    ! 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_properties_nml, iostat = iostat_nml )
      close( unit_nml )

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

!!$    ! 出力時間間隔の設定
!!$    ! Configure time interval of output 
!!$    !
!!$    call DCDiffTimeCreate( PrevOutputTime, & ! (out)
!!$      & sec = 0.0_DP )                       ! (in)
!!$    call DCDiffTimeCreate( IntTime, & ! (out)
!!$      & IntValue, IntUnit )           ! (in)

    ! 印字 ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'Input:: ' )
    call MessageNotify( 'M', module_name, '  SurfTempSetting     = %c', c1 = trim(SurfTempSetting) )
    call MessageNotify( 'M', module_name, '  SurfTempFile        = %c', c1 = trim(SurfTempFile) )
    call MessageNotify( 'M', module_name, '  SurfTempName        = %c', c1 = trim(SurfTempName        ) )
    call MessageNotify( 'M', module_name, '  RoughLengthSetting  = %c', c1 = trim(RoughLengthSetting ) )
    call MessageNotify( 'M', module_name, '  RoughLengthFile     = %c', c1 = trim(RoughLengthFile ) )
    call MessageNotify( 'M', module_name, '  RoughLengthName     = %c', c1 = trim(RoughLengthName ) )
    call MessageNotify( 'M', module_name, '  HeatCapacitySetting = %c', c1 = trim(HeatCapacitySetting) )
    call MessageNotify( 'M', module_name, '  HeatCapacityFile    = %c', c1 = trim(HeatCapacityFile) )
    call MessageNotify( 'M', module_name, '  HeatCapacityName    = %c', c1 = trim(HeatCapacityName) )
    call MessageNotify( 'M', module_name, '  TempFluxSetting     = %c', c1 = trim(TempFluxSetting  ) )
    call MessageNotify( 'M', module_name, '  TempFluxFile        = %c', c1 = trim(TempFluxFile  ) )
    call MessageNotify( 'M', module_name, '  TempFluxName        = %c', c1 = trim(TempFluxName  ) )
    call MessageNotify( 'M', module_name, '  SurfCondSetting     = %c', c1 = trim(SurfCondSetting   ) )
    call MessageNotify( 'M', module_name, '  SurfCondFile        = %c', c1 = trim(SurfCondFile   ) )
    call MessageNotify( 'M', module_name, '  SurfCondName        = %c', c1 = trim(SurfCondName   ) )
    call MessageNotify( 'M', module_name, '  SurfHeightSetting   = %c', c1 = trim(SurfHeightSetting   ) )
    call MessageNotify( 'M', module_name, '  SurfHeightFile      = %c', c1 = trim(SurfHeightFile   ) )
    call MessageNotify( 'M', module_name, '  SurfHeightName      = %c', c1 = trim(SurfHeightName   ) )


!!$    call MessageNotify( 'M', module_name, 'Output:: ' )
!!$    call MessageNotify( 'M', module_name, '  OutputFile = %c', c1 = trim(OutputFile) )
!!$    call MessageNotify( 'M', module_name, '  IntTime    = %f [%c]', d = (/ IntValue /), c1 = trim(IntUnit) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    surface_properties_inited = .true.
  end subroutine SurfacePropertiesInit
TempFluxFile
Variable :
TempFluxFile :character(STRING), save
: 地中熱フラックスのファイル名. File name of ground temperature flux
TempFluxName
Variable :
TempFluxName :character(TOKEN) , save
: 地中熱フラックスの変数名. Variable name of ground temperature flux
TempFluxSetting
Variable :
TempFluxSetting :character(STRING), save
: 地中熱フラックスの設定方法 Setting of ground temperature flux
module_name
Constant :
module_name = ‘surface_properties :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: surface_properties_primitive.f90,v 1.1.1.1 2010-08-17 05:24:51 takepiro Exp $’ :character(*), parameter
: モジュールのバージョン Module version