Class surface_properties
In: surface_properties/surface_properties.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

dc_types dc_message gtool_history gridset dc_string gtool_historyauto read_time_series timeset surface_data gabls albedo_Matthews Bucket_Model modify_albedo_snowseaice surface_properties_lo roughlen_Matthews soil_thermdiffcoef snowice_frac dc_iounit namelist_util

Public Instance methods

Subroutine :
xy_SurfMajCompIceB(0:imax-1, 1:jmax) :real(DP), intent(in ), optional
: $ M_mcs (t-\Delta t) $ . Surface major component ice amount (kg m-2)
xy_SoilMoistB(0:imax-1, 1:jmax) :real(DP), intent(in ), optional
: $ M_ws (t-\Delta t) $ . ���水� (kg m-2) Soil moisture (kg m-2)
xy_SurfSnowB(0:imax-1, 1:jmax) :real(DP), intent(in ), optional
: $ M_ss (t-\Delta t) $ . ����� (kg m-2) Surface snow amount (kg m-2)
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_SurfHumidCoef(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: �°è¡¨æ¹¿æ½¤åº�. Surface humidity coefficient
xy_SurfRoughLenMom(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: �°è¡¨ç²�åº���. Surface rough length for momentum
xy_SurfRoughLenHeat(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: �°è¡¨ç²�åº���. Surface rough length for heat
xy_SurfHeatCapacity(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: �°è¡¨�±å���. Surface heat capacity
xy_DeepSubSurfHeatFlux(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: �°ä¸­�±ã����������. "Deep subsurface heat flux" Heat flux at the bottom of surface/soil layer.
xy_SurfCond(0:imax-1, 1:jmax) :integer , intent(inout), optional
: ����è¡��¢ç�¶æ�� (0: �ºå�, 1: ���). Surface condition (0: fixed, 1: variable)
xy_SurfType(0:imax-1, 1:jmax) :integer , intent(inout), optional
: ����è¡��¢ã�¿ã�¤ã�� (���°å����) Surface type (land use)
xy_SurfHeight(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: $ z_s $ . �°è¡¨�¢é�åº�. Surface height.
xy_SurfHeightStd(0:imax-1, 1:jmax) :real(DP), intent(inout), optional
: $ z_s $ . �°è¡¨�¢é�åº�. Surface height.
xy_SeaIceConc(0:imax-1,1:jmax) :real(DP), intent(inout), optional
: 海氷�� (0 <= xy_SeaIceConc <= 1) Sea ice concentration (0 <= xy_SeaIceConc <= 1)
xy_SoilHeatCap(0:imax-1,1:jmax) :real(DP), intent(inout), optional
: ��å£��±å��� (J K-1 kg-1) Specific heat of soil (J K-1 kg-1)
xy_SoilHeatDiffCoef(0:imax-1,1:jmax) :real(DP), intent(inout), optional
: ��å£��±ä�å°�� (W m-1 K-1) Heat conduction coefficient of soil (W m-1 K-1)

����è¡��¢ç�¹æ�§ã��設å����¾ã��.

Set surface properties.

[Source]

  subroutine SetSurfaceProperties( xy_SurfMajCompIceB, xy_SoilMoistB, xy_SurfSnowB, xy_SurfTemp, xy_SurfAlbedo, xy_SurfHumidCoef, xy_SurfRoughLenMom, xy_SurfRoughLenHeat, xy_SurfHeatCapacity, xy_DeepSubSurfHeatFlux, xy_SurfCond, xy_SurfType, xy_SurfHeight, xy_SurfHeightStd, xy_SeaIceConc, xy_SoilHeatCap, xy_SoilHeatDiffCoef )
    !
    ! ����è¡��¢ç�¹æ�§ã��設å����¾ã��. 
    !
    ! Set surface properties. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ��������
    ! Character handling
    !
    use dc_string, only: toChar

    ! gtool4 ���¼ã�¿å�¥å��
    ! Gtool4 data input
    !
    use gtool_history, only: HistoryGet

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoPut

    ! ��ç³»å�����¼ã�¿ã����¿è¾¼��
    ! Reading time series
    !
    use read_time_series, only: SetValuesFromTimeSeriesWrapper

    ! ���»ç���
    ! Time control
    !
    use timeset, only: TimeN, EndTime, TimesetClockStart, TimesetClockStop

    ! �°è¡¨�¢ã���¼ã�¿æ�ä¾�
    ! Prepare surface data
    !
    use surface_data, only: SetSurfData

    !
    ! Routines for GABLS tests
    !
    use gabls, only : SetGabls2SurfTemp

    ! Matthews �����¼ã�¿ã���ºã�¥ã�����è¡��¢ã�¢ã������設å�
    ! set surface albedo based on data by Matthews
    !
    use albedo_Matthews, only: SetAlbedoMatthews, ModAlbedoMatthewsCultivation

    ! ���±ã���¢ã����
    ! Bucket model
    !
    use Bucket_Model, only : BucketSetFlagOceanFromMatthews, BucketModHumidCoef

    ! ����µ·æ°·ã�������¢ã������å¤���
    ! modification of surface albedo on the snow covered ground and on the sea ice
    !
    use modify_albedo_snowseaice, only: ModAlbedoDueToSnowSeaIce

    ! �¢ã������, ç²�åº��·ã��¨­å®�, �¸é�¢ã��µ·æ´���·®���¿è����
    ! Set albedo and roughness length, only considering land-ocean contrast
    !
    use surface_properties_lo, only: SetAlbedoLO, SetRoughLenLO

    ! Matthews �����¼ã�¿ã���ºã�¥ã��°é�¢ç�åº���¨­å®�
    ! set roughness length on land surface based on data by Matthews
    !
    use roughlen_Matthews, only: SetRoughLenLandMatthews, ModRoughLenMatthewsCultivation

    ! ��å£��±ä�å°���°ã��¨­å®�
    ! set soil thermal diffusion coefficient
    !
    use soil_thermdiffcoef, only : SetSoilThermDiffCoefSimple

    ! ��, æ°·ã���²å��
    ! snow/ice fraction
    !
    use snowice_frac, only : SeaIceAboveThreshold

    ! 宣�� ; Declaration statements
    !
    real(DP), intent(in   ), optional:: xy_SurfMajCompIceB(0:imax-1, 1:jmax)
                              ! $ M_mcs (t-\Delta t) $ .
                              ! Surface major component ice amount (kg m-2)
    real(DP), intent(in   ), optional:: xy_SoilMoistB(0:imax-1, 1:jmax)
                              ! $ M_ws (t-\Delta t) $ . ���水� (kg m-2)
                              ! Soil moisture (kg m-2)
    real(DP), intent(in   ), optional:: xy_SurfSnowB(0:imax-1, 1:jmax)
                              ! $ M_ss (t-\Delta t) $ . ����� (kg m-2)
                              ! Surface snow amount (kg m-2)
    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_SurfHumidCoef (0:imax-1, 1:jmax)
                              ! �°è¡¨æ¹¿æ½¤åº�. 
                              ! Surface humidity coefficient
    real(DP), intent(inout), optional:: xy_SurfRoughLenMom (0:imax-1, 1:jmax)
                              ! �°è¡¨ç²�åº���. 
                              ! Surface rough length for momentum
    real(DP), intent(inout), optional:: xy_SurfRoughLenHeat(0:imax-1, 1:jmax)
                              ! �°è¡¨ç²�åº���. 
                              ! Surface rough length for heat
    real(DP), intent(inout), optional:: xy_SurfHeatCapacity (0:imax-1, 1:jmax)
                              ! �°è¡¨�±å���. 
                              ! Surface heat capacity
    real(DP), intent(inout), optional:: xy_DeepSubSurfHeatFlux (0:imax-1, 1:jmax)
                              ! �°ä¸­�±ã����������. 
                              ! "Deep subsurface heat flux"
                              ! Heat flux at the bottom of surface/soil layer.
    integer , intent(inout), optional:: xy_SurfCond (0:imax-1, 1:jmax)
                              ! ����è¡��¢ç�¶æ�� (0: �ºå�, 1: ���). 
                              ! Surface condition (0: fixed, 1: variable)
    integer , intent(inout), optional:: xy_SurfType (0:imax-1, 1:jmax)
                              ! ����è¡��¢ã�¿ã�¤ã�� (���°å����)
                              ! Surface type (land use)
    real(DP), intent(inout), optional:: xy_SurfHeight   (0:imax-1, 1:jmax)
                              ! $ z_s $ . �°è¡¨�¢é�åº�. 
                              ! Surface height. 
    real(DP), intent(inout), optional:: xy_SurfHeightStd(0:imax-1, 1:jmax)
                              ! $ z_s $ . �°è¡¨�¢é�åº�. 
                              ! Surface height. 
    real(DP), intent(inout), optional:: xy_SeaIceConc(0:imax-1,1:jmax)
                              ! 海氷�� (0 <= xy_SeaIceConc <= 1)
                              ! Sea ice concentration (0 <= xy_SeaIceConc <= 1)
    real(DP), intent(inout), optional:: xy_SoilHeatCap(0:imax-1,1:jmax)
                              ! ��å£��±å��� (J K-1 kg-1)
                              ! Specific heat of soil (J K-1 kg-1)
    real(DP), intent(inout), optional:: xy_SoilHeatDiffCoef(0:imax-1,1:jmax)
                              ! ��å£��±ä�å°�� (W m-1 K-1)
                              ! Heat conduction coefficient of soil (W m-1 K-1)

    ! �業��
    ! Work variables
    !
    real(DP), allocatable, save:: xy_SurfTempSave (:,:)
                              ! �°è¡¨�¢æ¸©åº����å­��� (K)
                              ! Saved values of surface temperature (K)
    real(DP), allocatable, save:: xy_SeaIceConcSave(:,:)
                              ! æµ·æ°·�¢å�åº����å­���
                              ! Saved values of sea ice concentration
    real(DP), allocatable, save:: xy_SurfAlbedoSave(:,:)
                              ! �¢ã���������å­���
                              ! Saved values of albedo

    logical      :: xy_BucketFlagOceanGrid(0:imax-1,1:jmax)
                              !
                              ! Flag for ocean grid point used in bucket model
    real(DP), allocatable, save:: xy_SurfCulIntSave(:,:)
    real(DP)                   :: xy_SurfCulInt    (0:imax-1,1:jmax)
                              !
                              ! Surface cultivation intensity

    logical, save:: flag_first_SurfCond            = .true.
                              ! ������示�������. 
                              ! Flag that indicates first loop
                              !
    logical, save:: flag_first_SurfType            = .true.
    logical, save:: flag_first_SurfCulInt          = .true.
    logical, save:: flag_first_SeaIceConc          = .true.
    logical, save:: flag_first_SurfTemp            = .true.
    logical, save:: flag_first_SurfHeight          = .true.
    logical, save:: flag_first_SurfHeightStd       = .true.
    logical, save:: flag_first_SurfAlbedo          = .true.
    logical, save:: flag_first_SurfHumidCoef       = .true.
    logical, save:: flag_first_SurfRoughLen        = .true.
    logical, save:: flag_first_SurfHeatCapacity    = .true.
    logical, save:: flag_first_DeepSubSurfHeatFlux = .true.
    logical, save:: flag_first_SoilHeatCap         = .true.
    logical, save:: flag_first_SoilHeatDiffCoef    = .true.

    logical :: FlagSetSurfType
    logical :: FlagSetSeaIceConc
    logical :: FlagSetSurfCond
    logical :: FlagSetSurfCulInt
    logical :: FlagSetSurfTemp
    logical :: FlagSetSurfHeight
    logical :: FlagSetSurfHeightStd
    logical :: FlagSetSurfAlbedo
    logical :: FlagSetSurfHumidCoef
    logical :: FlagSetSurfRoughLenMom
    logical :: FlagSetSurfRoughLenHeat
    logical :: FlagSetSurfHeatCapacity
    logical :: FlagSetDeepSubSurfHeatFlux
    logical :: FlagSetSoilHeatCap
    logical :: FlagSetSoilHeatDiffCoef

    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
    !

    ! ������確è�
    ! Initialization check
    !
    if ( .not. surface_properties_inited ) then
      call MessageNotify( 'E', module_name, 'This module has not been initialized.' )
    end if


    ! �����������
    ! Start measurement of computation time
    !
    call TimesetClockStart( module_name )


    flag_mpi_init = .true.

    FlagSetSurfType            = .false.
    FlagSetSeaIceConc          = .false.
    FlagSetSurfCond            = .false.
    FlagSetSurfCulInt          = .false.
    FlagSetSurfTemp            = .false.
    FlagSetSurfHeight          = .false.
    FlagSetSurfHeightStd       = .false.
    FlagSetSurfAlbedo          = .false.
    FlagSetSurfHumidCoef       = .false.
    FlagSetSurfRoughLenMom     = .false.
    FlagSetSurfRoughLenHeat    = .false.
    FlagSetSurfHeatCapacity    = .false.
    FlagSetDeepSubSurfHeatFlux = .false.
    FlagSetSoilHeatCap         = .false.
    FlagSetSoilHeatDiffCoef    = .false.


    ! NOTICE:
    ! The surface condition has to be set, before other fields are set.
    !
    ! ����è¡��¢ã�¿ã�¤ã�� (���°å����)
    ! Surface type (land use)
    !
    if ( present(xy_SurfType) ) then

      if ( SurfTypeSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SurfType ) then
          call HistoryGet( SurfTypeFile, SurfTypeName, xy_SurfType, flag_mpi_split = flag_mpi_init )  ! (in) optional
        end if
        if ( SurfCondSetting /= 'generate_from_SurfType' ) then
          call MessageNotify( 'E', module_name, " SurfCond has to be 'generate_from_SurfType', if SurfTypeSetting = %c.", c1 = trim(SurfTypeSetting) )
        end if
      else if ( SurfTypeSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SurfType ) then
          call SetSurfData( xy_SurfType = xy_SurfType )
        end if
      else
        call MessageNotify( 'E', module_name, ' SurfTypeSetting = %c is not appropriate.', c1 = trim(SurfTypeSetting) )
      end if

      FlagSetSurfType = .true.

      flag_first_SurfType = .false.

    end if


    ! NOTICE:
    ! The sea ice distribution has to be set, 
    ! before set SurfTemp (surface temperature) and SurfCond. 
    !
    ! æµ·æ°·�¢å�åº�
    ! Sea ice concentration
    !
    if ( present(xy_SeaIceConc) ) then

      if ( flag_first_SeaIceConc ) then
        ! ä¿�å­�����°ã���²ä�
        ! Allocate a variable for save
        !
        allocate( xy_SeaIceConcSave(0:imax-1, 1:jmax) )
      end if
      if ( SeaIceSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !

        ! This will be deleted near future (yot, 2010/10/11)
!!$        if ( flag_first_SeaIceConc ) then
!!$          call HistoryGet( &
!!$            & SeaIceFile, SeaIceName,          & ! (in)
!!$            & xy_SeaIceConcSave,               & ! (out)
!!$            & flag_mpi_split = flag_mpi_init )   ! (in) optional
!!$        end if
        call SetValuesFromTimeSeriesWrapper( 'SIC', SeaIceFile, SeaIceName, xy_SeaIceConcSave )
      else if ( SeaIceSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SeaIceConc ) then
          call SetSurfData( xy_SeaIceConc = xy_SeaIceConcSave )
        end if
      else
        call MessageNotify( 'E', module_name, ' SeaIceSetting = %c is not appropriate.', c1 = trim(SeaIceSetting) )
      end if
      ! æµ·æ°·�¢å�åº���¨­å®� ( xy_SurfCond == 0 ���´æ������ )
      ! Setting of sea ice concentration ( where xy_SurfCond == 0 only )
      !
      xy_SeaIceConc = xy_SeaIceConcSave

      FlagSetSeaIceConc = .true.

      flag_first_SeaIceConc = .false.

    end if


    ! ����è¡��¢ç�¶æ��
    ! Surface condition
    ! Flag whether surface temperature is calculated or not
    ! 0 : surface temperature is not calculated
    ! 1 : surface temperature is     calculated
    !
    if ( present(xy_SurfCond) ) then

      ! NOTICE:
      ! Before set SurfCond, SeaIceConc has to be set.
      if ( .not. FlagSetSeaIceConc ) then
        call MessageNotify( 'E', module_name, " SeaIceConc has to be set before setting SurfCond is set." )
      end if

      if ( SurfCondSetting == 'generate_from_SurfType' ) then
        if ( flag_first_SurfCond ) then
!!$          if ( ( SurfTypeSetting /= 'file' ) .and. ( SurfTypeSetting /= 'generate_internally' ) ) then
!!$            call MessageNotify( 'E', module_name, &
!!$              & " SurfCond has to be 'generate_from_SurfType' or 'generate_internally', if SurfTypeSetting = %c.", &
!!$              & c1 = trim(SurfTypeSetting) )
!!$          end if
          call MessageNotify( 'M', module_name, ' xy_SurfCond is constructed by use of xy_SurfType values because SurfTypeSetting = %c.', c1 = trim(SurfTypeSetting) )
        end if
        do j = 1, jmax
          do i = 0, imax-1
            if ( xy_SurfType(i,j) == 0 ) then
              if ( SeaIceAboveThreshold( xy_SeaIceConc(i,j) ) ) then
                xy_SurfCond(i,j) = 1
              else if ( FlagSlabOcean ) then
                xy_SurfCond(i,j) = 1
              else
                xy_SurfCond(i,j) = 0
              end if
            else
              xy_SurfCond(i,j) = 1
            end if
          end do
        end do

      else 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

      ! Check of SurfCond values
      !
      do j = 1, jmax
        do i = 0, imax-1
          if ( ( xy_SurfCond(i,j) < 0 ) .or. ( xy_SurfCond(i,j) > 1 ) ) then
            call MessageNotify( 'E', module_name, ' SurfCond value of %d is not appropriate.', i = (/ xy_SurfCond(i,j) /) )
          end if
        end do
      end do

      FlagSetSurfCond = .true.

      flag_first_SurfCond = .false.

    end if


    ! 
    ! Surface cultivation index
    !
    ! Cultivation intensity is set only when xy_SurfType is present.
    if ( present( xy_SurfType ) ) then

      ! NOTICE:
      ! Before set SurfCulInt, SurfType has to be set.
      if ( .not. FlagSetSurfType ) then
        call MessageNotify( 'E', module_name, " SurfType has to be set before setting SurfCulInt is set." )
      end if

      if ( flag_first_SurfCulInt ) then
        ! ä¿�å­�����°ã���²ä�
        ! Allocate a variable for save
        !
        allocate( xy_SurfCulIntSave(0:imax-1, 1:jmax) )
      end if
      if ( SurfCulIntSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( SurfTypeSetting /= 'file' ) then
          call MessageNotify( 'E', module_name, " SurfType has to be 'file', when SurfCulIntSetting = %c.", c1 = trim(SurfCulIntSetting) )
        end if
        call SetValuesFromTimeSeriesWrapper( 'CI', SurfCulIntFile, SurfCulIntName, xy_SurfCulIntSave )
      else if ( SurfCulIntSetting == 'generate_internally' ) then
        xy_SurfCulIntSave = 0.0_DP
      else
        call MessageNotify( 'E', module_name, ' SurfCulIntSetting = %c is not appropriate.', c1 = trim(SurfCulIntSetting) )
      end if
      !
      xy_SurfCulInt = xy_SurfCulIntSave

      FlagSetSurfCulInt = .true.
      flag_first_SurfCulInt = .false.
    else
      xy_SurfCulInt = 0.0_DP

      FlagSetSurfCulInt = .true.
    end if



    ! �°è¡¨�¢æ¸©åº�
    ! surface temperature
    !
    if ( present(xy_SurfTemp) ) then

      ! NOTICE:
      ! Before set surface temperature, sea ice distribution has to be set.
      if ( .not. FlagSetSeaIceConc ) then
        call MessageNotify( 'E', module_name, " SeaIceConc has to be set before setting SurfTemp is set." )
      end if

      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
        !

        ! This will be deleted near future (yot, 2010/10/11)
!!$        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( 'SST', SurfTempFile, SurfTempName, xy_SurfTempSave )
      else if ( SurfTempSetting == 'GABLS2' ) then
        !
        ! Routines for GABLS tests
        !
        call SetGabls2SurfTemp( xy_SurfTempSave )
      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

        if ( .not. present( xy_SurfCond ) ) then
          call MessageNotify( 'E', module_name, ' xy_SurfCond has to be present to set xy_SurfTemp.' )
        end if
        if ( .not. present( xy_SeaIceConc ) ) then
          call MessageNotify( 'E', module_name, ' xy_SeaIceConc has to be present to set xy_SurfTemp.' )
        end if

        do j = 1, jmax
          do i = 0, imax-1
            if ( xy_SurfCond(i,j) == 0 ) then
              xy_SurfTemp(i,j) = xy_SurfTempSave(i,j)
            end if
          end do
        end do

      end if

      FlagSetSurfTemp = .true.

      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

      FlagSetSurfHeight = .true.

      flag_first_SurfHeight = .false.
    end if

    ! 
    ! Surface height standard deviation
    !
    if ( present(xy_SurfHeightStd) ) then

      if ( SurfHeightStdSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SurfHeightStd ) then
          call HistoryGet( SurfHeightStdFile, SurfHeightStdName, xy_SurfHeightStd, flag_mpi_split = flag_mpi_init )        ! (in) optional
        end if
      else if ( SurfHeightStdSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        ! 
        if ( flag_first_SurfHeightStd ) then
          call SetSurfData( xy_SurfHeightStd = xy_SurfHeightStd )
        end if
      else
        call MessageNotify( 'E', module_name, ' SurfHeightStdSetting = %c is not appropriate.', c1 = trim(SurfHeightStdSetting) )
      end if

      FlagSetSurfHeightStd = .true.

      flag_first_SurfHeightStd = .false.
    end if


    ! �¢ã������
    ! Albedo
    !
    if ( present(xy_SurfAlbedo) ) then

      ! NOTICE:
      ! The surface condition and sea ice concentration have to be set, 
      ! before albedo is set.
      if ( ( .not. FlagSetSurfCond ) .or. ( .not. FlagSetSeaIceConc ) ) then
        call MessageNotify( 'E', module_name, " SurfCond and SeaIceConc have to be set before setting SurfAlbedo is set." )
      end if

      if ( flag_first_SurfAlbedo ) then
        ! ä¿�å­�����°ã���²ä�
        ! Allocate a variable for save
        !
        allocate( xy_SurfAlbedoSave(0:imax-1, 1:jmax) )
      end if
      if ( AlbedoSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SurfAlbedo ) then
          call HistoryGet( AlbedoFile, AlbedoName, xy_SurfAlbedoSave, flag_mpi_split = flag_mpi_init ) ! (in) optional
        end if
!!$        call SetValuesFromTimeSeriesWrapper(    &
!!$          & 'surface_albedo',                   &
!!$          & AlbedoFile, AlbedoName,             &
!!$          & xy_SurfAlbedoSave                   &               ! (inout)
!!$          & )
      else if ( AlbedoSetting == 'Matthews' ) then
        ! �¢ã�������� Matthews �����¼ã�¿ã��������¨­å®�
        ! Surface albedo is set based on Matthews' data
        !
        if ( .not. present( xy_SurfType ) ) then
          call MessageNotify( 'E', module_name, ' xy_SurfType has to be present to set xy_SurfAlbedo.' )
        end if
        if ( SurfTypeSetting /= 'file' ) then
          call MessageNotify( 'E', module_name, " SurfType has to be 'file', when AlbedoSetting = %c.", c1 = trim(AlbedoSetting) )
        end if
        call SetAlbedoMatthews( xy_SurfType, xy_SurfAlbedoSave )
        ! Modify albedo due to cultivation
        call ModAlbedoMatthewsCultivation( xy_SurfType, xy_SurfCulInt, xy_SurfAlbedoSave )
      else if ( AlbedoSetting == 'LOContrast' ) then
        ! �¢ã��������¨­å®�, �¸é�¢ã��µ·æ´���·®���¿è����
        ! Set albedo, only considering land-ocean contrast
        !
        if ( .not. present( xy_SurfType ) ) then
          call MessageNotify( 'E', module_name, ' xy_SurfType has to be present to set xy_SurfAlbedo.' )
        end if
        if ( SurfTypeSetting /= 'file' ) then
          call MessageNotify( 'E', module_name, " SurfType has to be 'file', when AlbedoSetting = %c.", c1 = trim(AlbedoSetting) )
        end if
        call SetAlbedoLO( xy_SurfType, xy_SurfAlbedoSave )
      else if ( AlbedoSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        ! 
        if ( flag_first_SurfAlbedo ) then
          call SetSurfData( xy_SurfAlbedo = xy_SurfAlbedoSave )
        end if
      else
        call MessageNotify( 'E', module_name, ' AlbedoSetting = %c is not appropriate.', c1 = trim(AlbedoSetting) )
      end if
      ! �¢ã��������¨­å®�
      ! Setting of albedo
      !
      xy_SurfAlbedo = xy_SurfAlbedoSave


      if ( present( xy_SurfType ) ) then
        ! ����µ·æ°·ã�������¢ã������å¤���
        ! modification of surface albedo on the snow covered ground and on the sea ice
        !

        if ( .not. present( xy_SurfMajCompIceB ) ) then
          call MessageNotify( 'E', module_name, ' xy_SurfMajCompIceB has to be present to set xy_SurfAlbedo.' )
        end if
        if ( .not. present( xy_SurfSnowB ) ) then
          call MessageNotify( 'E', module_name, ' xy_SurfSnowB has to be present to set xy_SurfAlbedo.' )
        end if
        if ( .not. present( xy_SeaIceConc ) ) then
          call MessageNotify( 'E', module_name, ' xy_SeaIceConc has to be present to set xy_SurfAlbedo.' )
        end if

        if ( .not. present( xy_SurfType ) ) then
          call MessageNotify( 'E', module_name, ' xy_SurfType has to be present to set xy_SurfAlbedo.' )
        end if
!!$        if ( SurfTypeSetting /= 'file' ) then
!!$          call MessageNotify( 'E', module_name, &
!!$            & " SurfType has to be 'file'." )
!!$        end if

        call ModAlbedoDueToSnowSeaIce( xy_SurfType, xy_SurfMajCompIceB, xy_SurfSnowB, xy_SeaIceConc, xy_SurfAlbedo )
      else
        call MessageNotify( 'E', module_name, ' xy_SurfType has to be present to modify albedo due to snow and sea ice.' )
      end if

      FlagSetSurfAlbedo = .true.

      flag_first_SurfAlbedo = .false.
    end if


    ! ����è¡��¢æ¹¿æ½¤åº¦
    ! Surface humidity coefficient
    !
    if ( present(xy_SurfHumidCoef) ) then

      ! NOTICE:
      ! The surface condition has to be set, before humidity coefficient 
      ! is set.
      if ( .not. FlagSetSurfCond ) then
        call MessageNotify( 'E', module_name, " SurfCond has to be set before setting SurfHumidCoef is set." )
      end if

      if ( HumidCoefSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SurfHumidCoef ) then
          call HistoryGet( HumidcoefFile, HumidcoefName, xy_SurfHumidcoef, flag_mpi_split = flag_mpi_init ) ! (in) optional
        end if
      else if ( HumidCoefSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SurfHumidCoef ) then
          call SetSurfData( xy_SurfHumidCoef = xy_SurfHumidCoef )
        end if
      else
        call MessageNotify( 'E', module_name, ' HumidCoefSetting = %c is not appropriate.', c1 = trim(HumidCoefSetting) )
      end if

      if ( FlagUseBucket ) then
        if ( ( present( xy_SurfType   ) ) .and. ( present( xy_SoilMoistB ) ) .and. ( present( xy_SurfSnowB  ) ) ) then
          ! ���±ã���¢ã�������¢ã����°è¡¨�¢æ¹¿æ½¤åº¦��¨­å®�
          ! Setting of surface humidity coefficient
          !
          call BucketSetFlagOceanFromMatthews( xy_SurfType, xy_BucketFlagOceanGrid )
          call BucketModHumidCoef( xy_BucketFlagOceanGrid, xy_SoilMoistB, xy_SurfSnowB, xy_SurfHumidCoef )
        else
          call MessageNotify( 'E', module_name, ' xy_SurfType, xy_SoilMoistB and xy_SurfSnowB have to be present to modify humidity coefficient with bucket model.' )
        end if
      end if

      FlagSetSurfHumidCoef = .true.

      flag_first_SurfHumidCoef = .false.
    end if


    ! ����
    ! Roughness length
    !
    if ( present(xy_SurfRoughLenMom) ) then
      if ( .not. present(xy_SurfRoughLenHeat) ) then
        call MessageNotify( 'E', module_name, ' xy_SurfRoughLenHeat has to be present if xy_SurfRoughLenMom is present.' )
      end if
    else
      if ( present(xy_SurfRoughLenHeat) ) then
        call MessageNotify( 'E', module_name, ' xy_SurfRoughLenMom has to be present if xy_SurfRoughLenHeat is present.' )
      end if
    end if
    if ( present(xy_SurfRoughLenMom) .and. present(xy_SurfRoughLenHeat) ) then

      if ( RoughLengthSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SurfRoughLen ) then
          call HistoryGet( RoughLengthFile, RoughLengthName, xy_SurfRoughLenMom, flag_mpi_split = flag_mpi_init )    ! (in) optional
          ! set roughness length for heat
          xy_SurfRoughLenHeat = xy_SurfRoughLenMom * RoughLenHeatFactor
        end if
      else if ( RoughLengthSetting == 'LOContrast' ) then
        ! ç²�åº��·ã��¨­å®�, �¸é�¢ã��µ·æ´���·®���¿è����
        ! Set roughness length, only considering land-ocean contrast
        !
        if ( .not. present( xy_SurfType ) ) then
          call MessageNotify( 'E', module_name, ' xy_SurfType has to be present to set xy_SurfAlbedo.' )
        end if
        if ( SurfTypeSetting /= 'file' ) then
          call MessageNotify( 'E', module_name, " SurfType has to be 'file', when RoughLengthSetting = %c.", c1 = trim(RoughLengthSetting) )
        end if
        call SetRoughLenLO( xy_SurfType, xy_SurfRoughLenMom )
        ! set roughness length for heat
        xy_SurfRoughLenHeat = xy_SurfRoughLenMom * RoughLenHeatFactor
      else if ( RoughLengthSetting == 'Matthews' ) then
        ! ç²�åº��·ã��¨­å®�, Matthews �����¼ã�¿ã���ºã�¥ã��
        ! Set roughness length based on Matthews dataset
        !
        if ( .not. FlagSetSurfType ) then
          call MessageNotify( 'E', module_name, ' xy_SurfType has to be set to set xy_SurfRoughLenMom.' )
        end if
        if ( SurfTypeSetting /= 'file' ) then
          call MessageNotify( 'E', module_name, " SurfType has to be 'file', when RoughLengthSetting = %c.", c1 = trim(RoughLengthSetting) )
        end if
        call SetRoughLenLandMatthews( "Mom", xy_SurfType, xy_SurfRoughLenMom )
        ! Modify albedo due to cultivation
        call ModRoughLenMatthewsCultivation( "Mom", xy_SurfType, xy_SurfCulInt, xy_SurfRoughLenMom )

        ! set roughness length for heat
        call SetRoughLenLandMatthews( "Heat", xy_SurfType, xy_SurfRoughLenHeat )
        ! Modify albedo due to cultivation
        call ModRoughLenMatthewsCultivation( "Heat", xy_SurfType, xy_SurfCulInt, xy_SurfRoughLenHeat )

      else if ( RoughLengthSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SurfRoughLen ) then
          call SetSurfData( xy_SurfRoughLength = xy_SurfRoughLenMom )
          ! set roughness length for heat
          xy_SurfRoughLenHeat = xy_SurfRoughLenMom * RoughLenHeatFactor
        end if
      else
        call MessageNotify( 'E', module_name, ' RoughLengthSetting = %c is not appropriate.', c1 = trim(RoughLengthSetting) )
      end if

      FlagSetSurfRoughLenMom  = .true.
      FlagSetSurfRoughLenHeat = .true.

      flag_first_SurfRoughLen = .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

      FlagSetSurfHeatCapacity = .true.

      flag_first_SurfHeatCapacity = .false.
    end if


    ! �°ä¸­�±ã����������
    ! Ground temperature flux
    !
    if ( present(xy_DeepSubSurfHeatFlux) ) then

      if ( TempFluxSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_DeepSubSurfHeatFlux ) then
          call HistoryGet( TempFluxFile, TempFluxName, xy_DeepSubSurfHeatFlux, 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_DeepSubSurfHeatFlux ) then
          call SetSurfData( xy_DeepSubSurfHeatFlux = xy_DeepSubSurfHeatFlux )
        end if
      else
        call MessageNotify( 'E', module_name, ' TempFluxSetting = %c is not appropriate.', c1 = trim(TempFluxSetting) )
      end if

      FlagSetDeepSubSurfHeatFlux = .true.

      flag_first_DeepSubSurfHeatFlux = .false.
    end if


    ! ��å£��±å��� (J K-1 kg-1)
    ! Specific heat of soil (J K-1 kg-1)
    !
    if ( present(xy_SoilHeatCap) ) then

      if ( SoilHeatCapSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SoilHeatCap ) then
          call HistoryGet( SoilHeatCapFile, SoilHeatCapName, xy_SoilHeatCap, flag_mpi_split = flag_mpi_init )  ! (in) optional
        end if
      else if ( SoilHeatCapSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SoilHeatCap ) then
          call SetSurfData( xy_SoilHeatCap = xy_SoilHeatCap )
        end if
      else
        call MessageNotify( 'E', module_name, ' SoilHeatCapSetting = %c is not appropriate.', c1 = trim(SoilHeatCapSetting) )
      end if

      FlagSetSoilHeatCap = .true.

      flag_first_SoilHeatCap = .false.
    end if


    ! ��å£��±ä�å°�� (W m-1 K-1)
    ! Heat conduction coefficient of soil (W m-1 K-1)
    !
    if ( present(xy_SoilHeatDiffCoef) ) then

      if ( SoilHeatDiffCoefSetting == 'file' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SoilHeatDiffCoef ) then
          call HistoryGet( SoilHeatDiffCoefFile, SoilHeatDiffCoefName, xy_SoilHeatDiffCoef, flag_mpi_split = flag_mpi_init )  ! (in) optional
        end if
      else if ( SoilHeatDiffCoefSetting == 'file_thermal_inertia' ) then
        ! ���¼ã�¿ã�����¡ã�¤ã��������å¾�
        ! Data is input from files
        !
        if ( flag_first_SoilHeatDiffCoef ) then
          call HistoryGet( SoilHeatDiffCoefFile, SoilHeatDiffCoefName, xy_SoilHeatDiffCoef, flag_mpi_split = flag_mpi_init )  ! (in) optional

          if ( present( xy_SoilHeatCap ) ) then
            xy_SoilHeatDiffCoef = xy_SoilHeatDiffCoef**2 / xy_SoilHeatCap
          else
            call MessageNotify( 'E', module_name, ' xy_SoilHeatCap has to be present to calculate heat diffusion coefficient of soil from thermal inertia.' )
          end if
        end if
      else if ( SoilHeatDiffCoefSetting == 'generate_internally' ) then
        ! ���¼ã�� (������������) �� surface_data �¢ã�¸ã�¥ã�¼ã��������å¾�
        ! Data (default values) is input from "surface_data" module
        !
        if ( flag_first_SoilHeatDiffCoef ) then
          call SetSurfData( xy_SoilHeatDiffCoef = xy_SoilHeatDiffCoef )
        end if
      else if ( SoilHeatDiffCoefSetting == 'simple' ) then
        if ( .not. FlagUseBucket ) then
          call MessageNotify( 'E', module_name, ' FlagUseBucket has to be .true. to set soil thermal diffusion coefficient.' )
        end if
        if ( ( FlagSetSurfType          ) .and. ( present( xy_SoilMoistB ) ) ) then
          ! ��å£��±ä�å°���°ã��¨­å®�
          ! set soil thermal diffusion coefficient
          !
          call SetSoilThermDiffCoefSimple( xy_SurfType, xy_SoilMoistB, xy_SoilHeatDiffCoef )
        else
          call MessageNotify( 'E', module_name, ' xy_SurfType and xy_SoilMoistB have to be present to set soil thermal diffusion coefficient.' )
        end if
      else
        call MessageNotify( 'E', module_name, ' SoilHeatDiffCoefSetting = %c is not appropriate.', c1 = trim(TempFluxSetting) )
      end if

      FlagSetSoilHeatDiffCoef = .true.

      flag_first_SoilHeatDiffCoef = .false.
    end if


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'SurfCulInt', xy_SurfCulInt )


    ! ��������������
    ! Pause measurement of computation time
    !
    call TimesetClockStop( module_name )


  end subroutine SetSurfaceProperties
Subroutine :
ArgFlagSlabOcean :logical, intent(in )
: �¹ã�������¼ã�·ã�£ã�� ���³ï�����. flag for use of slab ocean on/off
ArgFlagUseBucket :logical, intent(in )
: flag for bucket model
ArgFlagSnow :logical, intent(in )
: flag for snow

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( ArgFlagSlabOcean, ArgFlagUseBucket, ArgFlagSnow )
    !
    ! surface_properties �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. 
    ! NAMELIST#surface_properties_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��. 
    !
    ! "surface_properties" module is initialized. 
    ! "NAMELIST#surface_properties_nml" is loaded in this procedure. 
    !

    ! �¢ã�¸ã�¥ã�¼ã����� ; USE statements
    !

    ! ç¨��¥å�������¡ã��
    ! Kind type parameter
    !
    use dc_types, only: STDOUT ! æ¨�æº��ºå�����ç½����. Unit number of standard output

    ! ���¡ã�¤ã���¥å�ºå��è£���
    ! File I/O support
    !
    use dc_iounit, only: FileOpen

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    use gtool_historyauto, only: HistoryAutoAddVariable

    ! NAMELIST ���¡ã�¤ã���¥å�����¢ã�������¼ã���£ã������
    ! Utilities for NAMELIST file input
    !
    use namelist_util, only: namelist_filename, NmlutilMsg

    ! ���»ç���
    ! Time control
    !
    use timeset, only: DelTime  ! $ \Delta t $ [s]

    !
    ! Routines for GABLS tests
    !
    use gabls, only : GablsInit

    ! Matthews �����¼ã�¿ã���ºã�¥ã�����è¡��¢ã�¢ã������設å�
    ! set surface albedo based on data by Matthews
    !
    use albedo_Matthews, only : AlbedoMatthewsInit

    ! ���±ã���¢ã����
    ! Bucket model
    !
    use Bucket_Model, only : BucketModelInit

    ! ����µ·æ°·ã�������¢ã������å¤���
    ! modification of surface albedo on the snow covered ground and on the sea ice
    !
    use modify_albedo_snowseaice, only : ModAlbedoSnowSeaIceInit

    ! �¢ã������, ç²�åº��·ã��¨­å®�, �¸é�¢ã��µ·æ´���·®���¿è����
    ! Set albedo and roughness length, only considering land-ocean contrast
    !
    use surface_properties_lo, only : SurfacePropertiesLOInit

    ! Matthews �����¼ã�¿ã���ºã�¥ã��°é�¢ç�åº���¨­å®�
    ! set roughness length on land surface based on data by Matthews
    !
    use roughlen_Matthews, only : RoughLenMatthewsInit

    ! ��å£��±ä�å°���°ã��¨­å®�
    ! set soil thermal diffusion coefficient
    !
    use soil_thermdiffcoef, only : SoilThermDiffCoefInit


    ! 宣�� ; Declaration statements
    !
    logical, intent(in ) :: ArgFlagSlabOcean
                              ! �¹ã�������¼ã�·ã�£ã�� ���³ï�����.
                              ! flag for use of slab ocean on/off
    logical, intent(in ) :: ArgFlagUseBucket
                              ! 
                              ! flag for bucket model
    logical, intent(in ) :: ArgFlagSnow
                              ! 
                              ! flag for snow

    ! �業��
    ! 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, SeaIceSetting, SeaIceFile, SeaIceName, AlbedoSetting, AlbedoFile, AlbedoName, HumidCoefSetting, HumidCoefFile, HumidCoefName, RoughLengthSetting, RoughLengthFile, RoughLengthName, HeatCapacitySetting, HeatCapacityFile, HeatCapacityName, TempFluxSetting, TempFluxFile, TempFluxName, SurfCondSetting, SurfCondFile, SurfCondName, SurfTypeSetting, SurfTypeFile, SurfTypeName, SurfCulIntSetting, SurfCulIntFile, SurfCulIntName, SurfHeightSetting, SurfHeightFile, SurfHeightName, SurfHeightStdSetting, SurfHeightStdFile, SurfHeightStdName, SoilHeatCapSetting, SoilHeatCapFile, SoilHeatCapName, SoilHeatDiffCoefSetting, SoilHeatDiffCoefFile, SoilHeatDiffCoefName, RoughLenHeatFactor

          ! �����������¤ã���¤ã��������������ç¶� "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


    ! Set flag for slab ocean
    FlagUseBucket = ArgFlagUseBucket

    FlagSlabOcean = ArgFlagSlabOcean


    ! �����������¤ã��¨­å®�
    ! Default values settings
    !
    SurfTempSetting         = 'generate_internally'
    SurfTempFile            = ''
    SurfTempName            = ''
    SeaIceSetting           = 'generate_internally'
    SeaIceFile              = ''
    SeaIceName              = ''
    AlbedoSetting           = 'generate_internally'
    AlbedoFile              = ''
    AlbedoName              = ''
    HumidCoefSetting        = 'generate_internally'
    HumidCoefFile           = ''
    HumidCoefName           = ''
    RoughLengthSetting      = 'generate_internally'
    RoughLengthFile         = ''
    RoughLengthName         = ''
    HeatCapacitySetting     = 'generate_internally'
    HeatCapacityFile        = ''
    HeatCapacityName        = ''
    TempFluxSetting         = 'generate_internally'
    TempFluxFile            = ''
    TempFluxName            = ''
    SurfCondSetting         = 'generate_internally'
    SurfCondFile            = ''
    SurfCondName            = ''
    SurfTypeSetting         = 'generate_internally'
    SurfTypeFile            = ''
    SurfTypeName            = ''
    SurfCulIntSetting       = 'generate_internally'
    SurfCulIntFile          = ''
    SurfCulIntName          = ''
    SurfHeightSetting       = 'generate_internally'
    SurfHeightFile          = ''
    SurfHeightName          = ''
    SurfHeightStdSetting    = 'generate_internally'
    SurfHeightStdFile       = ''
    SurfHeightStdName       = ''
    SoilHeatCapSetting      = 'generate_internally'
    SoilHeatCapFile         = ''
    SoilHeatCapName         = ''
    SoilHeatDiffCoefSetting = 'generate_internally'
    SoilHeatDiffCoefFile    = ''
    SoilHeatDiffCoefName    = ''

    RoughLenHeatFactor = 1.0_DP

!!$    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)


    ! A Value of "SurfTempSetting" is checked.
    !
    if ( ( SurfTempSetting == 'file' ) .and. ( FlagSlabOcean ) ) then
      call MessageNotify( 'E', module_name, "If FlagSlabOcean is .true., SurfTempSetting must not be 'file'." )
    end if


    ! Initialization of modules used in this module
    !

    ! Matthews �����¼ã�¿ã���ºã�¥ã�����è¡��¢ã�¢ã������設å�
    ! set surface albedo based on data by Matthews
    !
    call AlbedoMatthewsInit

    if ( FlagUseBucket ) then
      ! ���±ã���¢ã����
      ! Bucket model
      !
      call BucketModelInit( ArgFlagSnow )
    end if

    !
    ! Routines for GABLS tests
    !
    call GablsInit

    ! ����µ·æ°·ã�������¢ã������å¤���
    ! modification of surface albedo on the snow covered ground and on the sea ice
    !
    call ModAlbedoSnowSeaIceInit

    ! �¢ã������, ç²�åº��·ã��¨­å®�, �¸é�¢ã��µ·æ´���·®���¿è����
    ! Set albedo and roughness length, only considering land-ocean contrast
    !
    call SurfacePropertiesLOInit

    ! Matthews �����¼ã�¿ã���ºã�¥ã��°é�¢ç�åº���¨­å®�
    ! set roughness length on land surface based on data by Matthews
    !
    call RoughLenMatthewsInit

    ! ��å£��±ä�å°���°ã��¨­å®�
    ! set soil thermal diffusion coefficient
    !
    call SoilThermDiffCoefInit( ArgFlagSnow )


    ! ���¹ã�������¼ã�¿å�ºå�����������¸ã����°ç�»é��
    ! Register of variables for history data output
    !
    call HistoryAutoAddVariable( 'SurfCulInt' , (/ 'lon ', 'lat ', 'time' /), 'cultivation intensity', '1' )             ! (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, '  SeaIceSetting           = %c', c1 = trim(SeaIceSetting) )
    call MessageNotify( 'M', module_name, '  SeaIceFile              = %c', c1 = trim(SeaIceFile) )
    call MessageNotify( 'M', module_name, '  SeaIceName              = %c', c1 = trim(SeaIceName        ) )
    call MessageNotify( 'M', module_name, '  AlbedoSetting           = %c', c1 = trim(AlbedoSetting      ) )
    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, '  HumidCoefSetting        = %c', c1 = trim(HumidCoefSetting ) )
    call MessageNotify( 'M', module_name, '  HumidCoefFile           = %c', c1 = trim(HumidCoefFile  ) )
    call MessageNotify( 'M', module_name, '  HumidCoefName           = %c', c1 = trim(HumidCoefName  ) )
    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, '  SurfTypeSetting         = %c', c1 = trim(SurfTypeSetting   ) )
    call MessageNotify( 'M', module_name, '  SurfTypeFile            = %c', c1 = trim(SurfTypeFile   ) )
    call MessageNotify( 'M', module_name, '  SurfTypeName            = %c', c1 = trim(SurfTypeName   ) )
    call MessageNotify( 'M', module_name, '  SurfCulIntSetting       = %c', c1 = trim(SurfCulIntSetting   ) )
    call MessageNotify( 'M', module_name, '  SurfCulIntFile          = %c', c1 = trim(SurfCulIntFile   ) )
    call MessageNotify( 'M', module_name, '  SurfCulIntName          = %c', c1 = trim(SurfCulIntName   ) )
    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, '  SurfHeightStdSetting    = %c', c1 = trim(SurfHeightStdSetting   ) )
    call MessageNotify( 'M', module_name, '  SurfHeightStdFile       = %c', c1 = trim(SurfHeightStdFile   ) )
    call MessageNotify( 'M', module_name, '  SurfHeightStdName       = %c', c1 = trim(SurfHeightStdName   ) )
    call MessageNotify( 'M', module_name, '  SoilHeatCapSetting      = %c', c1 = trim(SoilHeatCapSetting   ) )
    call MessageNotify( 'M', module_name, '  SoilHeatCapFile         = %c', c1 = trim(SoilHeatCapFile   ) )
    call MessageNotify( 'M', module_name, '  SoilHeatCapName         = %c', c1 = trim(SoilHeatCapName   ) )
    call MessageNotify( 'M', module_name, '  SoilHeatDiffCoefSetting = %c', c1 = trim(SoilHeatDiffCoefSetting   ) )
    call MessageNotify( 'M', module_name, '  SoilHeatDiffCoefFile    = %c', c1 = trim(SoilHeatDiffCoefFile   ) )
    call MessageNotify( 'M', module_name, '  SoilHeatDiffCoefName    = %c', c1 = trim(SoilHeatDiffCoefName   ) )

    call MessageNotify( 'M', module_name, '  RoughLenHeatFactor      = %f', d = (/RoughLenHeatFactor/) )


!!$    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

Private Instance methods

AlbedoFile
Variable :
AlbedoFile :character(STRING), save
: �°è¡¨�¢ã�����������¡ã�¤ã����. File name of surface albedo
AlbedoName
Variable :
AlbedoName :character(TOKEN) , save
: �°è¡¨�¢ã����������°å��. Variable name of surface albedo
AlbedoSetting
Variable :
AlbedoSetting :character(STRING), save
: �°è¡¨�¢ã��������¨­å®��¹æ� Settingof surface albedo
FlagSlabOcean
Variable :
FlagSlabOcean :logical , save
: �¹ã�������¼ã�·ã�£ã�� ���³ï�����. flag for use of slab ocean on/off
FlagUseBucket
Variable :
FlagUseBucket :logical, save
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
HumidCoefFile
Variable :
HumidCoefFile :character(STRING), save
: �°è¡¨æ¹¿æ½¤åº������¡ã�¤ã����. File name of surface humidity coefficient
HumidCoefName
Variable :
HumidCoefName :character(TOKEN) , save
: �°è¡¨æ¹¿æ½¤åº�����°å��. Variable name of surface humidity coefficient
HumidCoefSetting
Variable :
HumidCoefSetting :character(STRING), save
: �°è¡¨æ¹¿æ½¤åº���¨­å®��¹æ� Setting of surface humidity coefficient
RoughLenHeatFactor
Variable :
RoughLenHeatFactor :real(DP), save
: ��������±ã���°è¡¨ç²�åº��·ã���. Ratio of roughness length for momentum and heat
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
SeaIceFile
Variable :
SeaIceFile :character(STRING), save
: æµ·æ°·�¢å�åº������¡ã�¤ã����. File name of sea ice concentration
SeaIceName
Variable :
SeaIceName :character(TOKEN) , save
: æµ·æ°·�¢å�åº�����°å��. Variable name of sea ice concentration
SeaIceSetting
Variable :
SeaIceSetting :character(STRING), save
: æµ·æ°·�¢å�åº���¨­å®��¹æ� Setting of sea ice concentration
SoilHeatCapFile
Variable :
SoilHeatCapFile :character(STRING), save
: ��å£��±å�������¡ã�¤ã����. File name of heat conduction coefficient of soil
SoilHeatCapName
Variable :
SoilHeatCapName :character(TOKEN) , save
: ��å£��±å������°å��. Variable name of heat conduction coefficient of soil
SoilHeatCapSetting
Variable :
SoilHeatCapSetting :character(STRING), save
: ��å£��±å����¨­å®��¹æ� Setting of heat conduction coefficient of soil
SoilHeatDiffCoefFile
Variable :
SoilHeatDiffCoefFile :character(STRING), save
: ��å£��±ä�å°�������¡ã�¤ã����. File name of heat conduction coefficient of soil
SoilHeatDiffCoefName
Variable :
SoilHeatDiffCoefName :character(TOKEN) , save
: ��å£��±ä�å°������°å��. Variable name of heat conduction coefficient of soil
SoilHeatDiffCoefSetting
Variable :
SoilHeatDiffCoefSetting :character(STRING), save
: ��å£��±ä�å°����¨­å®��¹æ� Setting of heat conduction coefficient of soil
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
SurfCulIntFile
Variable :
SurfCulIntFile :character(STRING), save
: … �����¡ã�¤ã����. File name of surface cultivation intensity
SurfCulIntName
Variable :
SurfCulIntName :character(TOKEN) , save
: … ����°å��. Variable name of surface cultivation intensity
SurfCulIntSetting
Variable :
SurfCulIntSetting :character(STRING), save
: … ��¨­å®��¹æ� Setting of surface cultivation intensity
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
SurfHeightStdFile
Variable :
SurfHeightStdFile :character(STRING), save
: File name of surface height standard deviation
SurfHeightStdName
Variable :
SurfHeightStdName :character(TOKEN) , save
: Variable name of surface height standard deviation
SurfHeightStdSetting
Variable :
SurfHeightStdSetting :character(STRING), save
: Setting of surface height standard deviation
SurfTempFile
Variable :
SurfTempFile :character(STRING), save
: �°è¡¨�¢æ¸©åº������¡ã�¤ã����. File name of surface temperature
SurfTempName
Variable :
SurfTempName :character(TOKEN) , save
: �°è¡¨�¢æ¸©åº�����°å��. Variable name of surface temperature
SurfTempSetting
Variable :
SurfTempSetting :character(STRING), save
: �°è¡¨�¢æ¸©åº���¨­å®��¹æ� Setting of surface temperature
SurfTypeFile
Variable :
SurfTypeFile :character(STRING), save
: ����è¡��¢ã�¿ã�¤ã�� (���°å����) �����¡ã�¤ã����. File name of surface type (land use)
SurfTypeName
Variable :
SurfTypeName :character(TOKEN) , save
: ����è¡��¢ã�¿ã�¤ã�� (���°å����) ����°å��. Variable name of surface type (land use)
SurfTypeSetting
Variable :
SurfTypeSetting :character(STRING), save
: ����è¡��¢ã�¿ã�¤ã�� (���°å����) ��¨­å®��¹æ� Setting of surface type (land use)
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
surface_properties_inited
Variable :
surface_properties_inited = .false. :logical, save
: ����設������. Initialization flag
version
Constant :
version = ’$Name: $’ // ’$Id: surface_properties.f90,v 1.20 2015/01/31 06:16:26 yot Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version