Class ground_file_io
In: io/ground_file_io.f90

地表面データの入力

Ground data input

Note that Japanese and English are described in parallel.

海面温度や地表面諸量に関するデータを NetCDF ファイル, もしくは surface_data モジュールから入力します.

Data about sea surface temperature (SST) or various values on surface are input from a NetCDF file or "surface_data" module.

Procedures List

GroundFileGet :地表面データファイルの入力
———— :————
GroundFileGet :Input ground data file

NAMELIST

NAMELIST#ground_file_io_nml

Methods

Included Modules

gridset dc_types dc_message gtool_history surface_data dc_string timeset 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_SurfAlbedo(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: 地表アルベド. Surface albedo
xy_SurfHumidCoeff(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: 地表湿潤度. Surface humidity coefficient
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.

地表面の諸々のデータを設定します. xy_SurfTemp 以外は一回目に呼ばれた時のみ設定されます.

Get various data on ground. Arguments excluding "xy_SurfTemp" are configured at first only.

[Source]

  subroutine GroundFileGet( xy_SurfTemp, xy_SurfAlbedo, xy_SurfHumidCoeff, xy_SurfRoughLength, xy_SurfHeatCapacity, xy_GroundTempFlux, xy_SurfCond, xy_SurfHeight )
    !
    ! 地表面の諸々のデータを設定します. 
    ! xy_SurfTemp 以外は一回目に呼ばれた時のみ設定されます. 
    !
    ! Get various data on ground. 
    ! Arguments excluding "xy_SurfTemp" are configured at first only. 
    !

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

    ! 地表面データ提供
    ! Prepare surface data
    !
    use surface_data, only: SurfDataGet

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

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

    ! 宣言文 ; Declaration statements
    !
    implicit none
    real(DP), intent(inout), optional:: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! 地表面温度. 
                              ! Surface temperature
    real(DP), intent(inout), optional:: xy_SurfAlbedo (0:imax-1, 1:jmax)
                              ! 地表アルベド. 
                              ! Surface albedo
    real(DP), intent(inout), optional:: xy_SurfHumidCoeff (0:imax-1, 1:jmax)
                              ! 地表湿潤度. 
                              ! Surface humidity coefficient
    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 (:,:)
                              ! 地表面温度の保存値. 
                              ! Saved values surface temperature

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

    ! 実行文 ; Executable statement
    !

    if ( .not. ground_file_io_inited ) call GroundFileInit

    ! 初回はデータを読み込む
    ! Load data at first
    ! 
    if ( flag_first ) then

      ! 地表面温度の保存用変数の割付
      ! Allocate a variable for save of surface temperature
      !
      allocate( xy_SurfTempSave (0:imax-1, 1:jmax) )

      ! データ (デフォルト値) を surface_data モジュールから取得
      ! Data (default values) is input from "surface_data" module
      ! 
      call SurfDataGet( xy_SurfTempSave, xy_SurfAlbedo, xy_SurfHumidCoeff, xy_SurfRoughLength, xy_SurfHeatCapacity, xy_GroundTempFlux, xy_SurfCond )                     ! (out)

      ! 地形はデフォルトでは平坦
      ! Geography is flat by default
      !
      if ( present(xy_SurfHeight) ) xy_SurfHeight = 0.0_DP

      ! データをファイルから取得
      ! Data is input from files
      ! 
      if ( trim(SurfTempFile) /= '' .or. trim(SurfTempName) /= '' ) then
        call HistoryGet( SurfTempFile, SurfTempName, xy_SurfTempSave )
      end if

      if ( trim(AlbedoFile) /= '' .or. trim(AlbedoName) /= '' ) then
        if ( present(xy_SurfAlbedo) ) then
          call HistoryGet( AlbedoFile, AlbedoName, xy_SurfAlbedo )
        end if
      end if

      if ( trim(HumidcoeffFile) /= '' .or. trim(HumidcoeffName) /= '' ) then
        if ( present(xy_SurfHumidcoeff) ) then
          call HistoryGet( HumidcoeffFile, HumidcoeffName, xy_SurfHumidcoeff )
        end if
      end if

      if ( trim(RoughLengthFile) /= '' .or. trim(RoughLengthName) /= '' ) then
        if ( present(xy_SurfRoughLength) ) then
          call HistoryGet( RoughLengthFile, RoughLengthName, xy_SurfRoughLength )
        end if
      end if

      if ( trim(HeatCapacityFile) /= '' .or. trim(HeatCapacityName) /= '' ) then
        if ( present(xy_SurfHeatCapacity) ) then
          call HistoryGet( HeatCapacityFile, HeatCapacityName, xy_SurfHeatCapacity )
        end if
      end if

      if ( trim(TempFluxFile) /= '' .or. trim(TempFluxName) /= '' ) then
        if ( present(xy_GroundTempFlux) ) then
          call HistoryGet( TempFluxFile, TempFluxName, xy_GroundTempFlux )
        end if
      end if

      if ( trim(SurfCondFile) /= '' .or. trim(SurfCondName) /= '' ) then
        if ( present(xy_SurfCond) ) then
          call HistoryGet( SurfCondFile, SurfCondName, xy_SurfCond )
        end if
      end if

      if ( trim(SurfHeightFile) /= '' .or. trim(SurfHeightName) /= '' ) then
        if ( present(xy_SurfHeight) ) then
          call HistoryGet( SurfHeightFile, SurfHeightName, xy_SurfHeight )
        end if
      end if

      flag_first = .false.
    end if

    ! 地表面温度を SST で置き換え ( xy_SurfCond <=0 の場所のみ )
    ! Surface temperature is replaced with SST ( only xy_SurfCond <=0 )
    ! 
    if ( present(xy_SurfTemp) ) then
      where( xy_SurfCond <= 0 .and. xy_SurfTempSave > 0.0_DP  )
        xy_SurfTemp = xy_SurfTempSave
      end where
    end if

  end subroutine GroundFileGet
ground_file_io_inited
Variable :
ground_file_io_inited = .false. :logical, save, public
: 初期設定フラグ. Initialization flag
ground_file_opened
Variable :
ground_file_opened = .false. :logical, save, public
: 地表面データファイルのオープンに関するフラグ. Flag of ground data file open

Private Instance methods

AlbedoFile
Variable :
AlbedoFile :character(TOKEN), save
: 地表アルベドのファイル名. File name of surface albedo
AlbedoName
Variable :
AlbedoName :character(TOKEN), save
: 地表アルベドの変数名. Variable name of surface albedo
Subroutine :

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

"ground_file_io" module is initialized. "NAMELIST#ground_file_io_nml" is loaded in this procedure.

This procedure input/output NAMELIST#ground_file_io_nml .

[Source]

  subroutine GroundFileInit
    !
    ! ground_file_io モジュールの初期化を行います. 
    ! NAMELIST#ground_file_io_nml の読み込みはこの手続きで行われます. 
    !
    ! "ground_file_io" module is initialized. 
    ! "NAMELIST#ground_file_io_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 /ground_file_io_nml/ SurfTempFile, SurfTempName, AlbedoFile, AlbedoName, HumidCoeffFile, HumidCoeffName, RoughLengthFile, RoughLengthName, HeatCapacityFile, HeatCapacityName, TempFluxFile, TempFluxName, SurfCondFile, SurfCondName, SurfHeightFile, SurfHeightName
          !
          ! デフォルト値については初期化手続 "ground_file_io#GroundFileInit" 
          ! のソースコードを参照のこと. 
          !
          ! Refer to source codes in the initialization procedure
          ! "ground_file_io#GroundFileInit" for the default values. 
          !

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


    ! 実行文 ; Executable statement
    !

    if ( ground_file_io_inited ) return
    call InitCheck

    ! デフォルト値の設定
    ! Default values settings
    !
    SurfTempFile     = ''
    SurfTempName     = ''
    AlbedoFile       = ''
    AlbedoName       = ''
    HumidCoeffFile   = ''
    HumidCoeffName   = ''
    RoughLengthFile  = ''
    RoughLengthName  = ''
    HeatCapacityFile = ''
    HeatCapacityName = ''
    TempFluxFile     = ''
    TempFluxName     = ''
    SurfCondFile     = ''
    SurfCondName     = ''
    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 = ground_file_io_nml, iostat = iostat_nml ) ! (out)
      close( unit_nml )

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
      if ( iostat_nml == 0 ) write( STDOUT, nml = ground_file_io_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, '  SurfTempFile     = %c', c1 = trim(SurfTempFile) )
    call MessageNotify( 'M', module_name, '  SurfTempName     = %c', c1 = trim(SurfTempName        ) )
    call MessageNotify( 'M', module_name, '  AlbedoFile       = %c', c1 = trim(AlbedoFile      ) )
    call MessageNotify( 'M', module_name, '  AlbedoName       = %c', c1 = trim(AlbedoName      ) )
    call MessageNotify( 'M', module_name, '  HumidCoeffFile   = %c', c1 = trim(HumidCoeffFile  ) )
    call MessageNotify( 'M', module_name, '  HumidCoeffName   = %c', c1 = trim(HumidCoeffName  ) )
    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, '  HeatCapacityFile = %c', c1 = trim(HeatCapacityFile) )
    call MessageNotify( 'M', module_name, '  HeatCapacityName = %c', c1 = trim(HeatCapacityName) )
    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, '  SurfCondFile     = %c', c1 = trim(SurfCondFile   ) )
    call MessageNotify( 'M', module_name, '  SurfCondName     = %c', c1 = trim(SurfCondName   ) )
    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) )

    ground_file_io_inited = .true.
  end subroutine GroundFileInit
HeatCapacityFile
Variable :
HeatCapacityFile :character(TOKEN), save
: 地表熱容量のファイル名. File name of surface heat capacity
HeatCapacityName
Variable :
HeatCapacityName :character(TOKEN), save
: 地表熱容量の変数名. Variable name of surface heat capacity
HumidCoeffFile
Variable :
HumidCoeffFile :character(TOKEN), save
: 地表湿潤度のファイル名. File name of surface humidity coefficient
HumidCoeffName
Variable :
HumidCoeffName :character(TOKEN), save
: 地表湿潤度の変数名. Variable name of surface humidity coefficient
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(TOKEN), save
: 地表粗度長のファイル名. File name of surface rough length
RoughLengthName
Variable :
RoughLengthName :character(TOKEN), save
: 地表粗度長の変数名. Variable name of surface rough length
SurfCondFile
Variable :
SurfCondFile :character(TOKEN), save
: 地表状態 (0: 固定, 1: 可変) のファイル名. File name of surface condition (0: fixed, 1: variable)
SurfCondName
Variable :
SurfCondName :character(TOKEN), save
: 地表状態 (0: 固定, 1: 可変) の変数名. Variable name of surface condition (0: fixed, 1: variable)
SurfHeightFile
Variable :
SurfHeightFile :character(STRING), save
: 地表面高度のファイル名. File name of surface height
SurfHeightName
Variable :
SurfHeightName :character(TOKEN), save
: 地表面高度の変数名. Variable name of surface height
SurfTempFile
Variable :
SurfTempFile :character(STRING), save
: 地表面温度のファイル名. File name of surface temperature
SurfTempName
Variable :
SurfTempName :character(TOKEN), save
: 地表面温度の変数名. Variable name of surface temperature
TempFluxFile
Variable :
TempFluxFile :character(TOKEN), save
: 地中熱フラックスのファイル名. File name of ground temperature flux
TempFluxName
Variable :
TempFluxName :character(TOKEN), save
: 地中熱フラックスの変数名. Variable name of ground temperature flux
module_name
Constant :
module_name = ‘ground_file_io :character(*), parameter
: モジュールの名称. Module name
version
Constant :
version = ’$Name: dcpam5-20090306 $’ // ’$Id: ground_file_io.f90,v 1.7 2009-01-21 11:45:30 morikawa Exp $’ :character(*), parameter
: モジュールのバージョン Module version

[Validate]