|  Subroutine  : | 
 | 
| FlagSSModelSO      : | logical , intent(in ), optional
|  : |  スラブオーシャン オン/オフ. flag for use of slab ocean on/off
 |  
 
 | 
| 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
 | 
| xy_SurfHumidCoef(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_SeaIceConc(0:imax-1,1:jmax)      : | real(DP), intent(inout), optional
|  : |  海氷密度 (0 <= xy_SeaIceConc <= 1) Sea ice concentration (0 <=
xy_SeaIceConc <= 1)
 |  
 
 | 
惑星表面特性を設定します.
Set surface properties.
          
  subroutine SetSurfaceProperties( FlagSSModelSO, xy_SoilMoistB, xy_SurfSnowB, xy_SurfTemp, xy_SurfAlbedo, xy_SurfHumidCoef, xy_SurfRoughLength, xy_SurfHeatCapacity, xy_GroundTempFlux, xy_SurfCond, xy_SurfHeight, xy_SeaIceConc )
    !
    ! 惑星表面特性を設定します. 
    !
    ! Set surface properties. 
    !
    ! モジュール引用 ; USE statements
    !
    ! 雪と海氷の定数の設定
    ! Setting constants of snow and sea ice
    !
    use constants_snowseaice, only: SeaIceThreshold
    ! 地表面データ提供
    ! Prepare surface data
    !
    use surface_data, only: SetSurfData
    ! Matthews のデータに基づく惑星表面アルベド設定
    ! set surface albedo based on data by Matthews
    !
    use albedo_Matthews, only: SetAlbedoMathews
    ! バケツモデル
    ! Bucket model
    !
    use Bucket_Model, only : BucketModHumidCoef
    ! 雪と海氷によるアルベド変化
    ! modification of surface albedo on the snow covered ground and on the sea ice
    !
    use modify_albedo_snowseaice, only: ModAlbedoDueToSnowSeaIce
    ! 粗度長の設定, 陸面と海洋の差のみ考慮
    ! 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
    use read_time_series, only: SetValuesFromTimeSeriesWrapper
    ! 宣言文 ; Declaration statements
    !
    implicit none
    logical , intent(in   ), optional:: FlagSSModelSO
                              ! スラブオーシャン オン/オフ.
                              ! flag for use of slab ocean on/off
    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_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. 
    real(DP), intent(inout), optional:: xy_SeaIceConc(0:imax-1,1:jmax)
                              ! 海氷密度 (0 <= xy_SeaIceConc <= 1)
                              ! Sea ice concentration (0 <= xy_SeaIceConc <= 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, save:: flag_first_SurfCond = .true.
                              ! 初回を示すフラグ. 
                              ! Flag that indicates first loop
                              !
    logical, save:: flag_first_SeaIceConc       = .true.
    logical, save:: flag_first_SurfTemp         = .true.
    logical, save:: flag_first_SurfHeight       = .true.
    logical, save:: flag_first_SurfAlbedo       = .true.
    logical, save:: flag_first_SurfHumidCoef    = .true.
    logical, save:: flag_first_SurfRoughLength  = .true.
    logical, save:: flag_first_SurfHeatCapacity = .true.
    logical, save:: flag_first_GroundTempFlux   = .true.
    logical:: flag_mpi_init
#ifdef LIB_MPI
    integer:: err_mpi
#endif
    integer:: i               ! 経度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in longitude
    integer:: j               ! 緯度方向に回る DO ループ用作業変数
                              ! Work variables for DO loop in latitude
    ! 実行文 ; Executable statement
    !
    if ( .not. surface_properties_inited ) call SurfacePropertiesInit
#ifdef LIB_MPI
    ! MPI における初期化が行われているかを確認する. 
    ! Confirm initialization of MPI
    !
    call MPI_Initialized(flag_mpi_init, err_mpi)
#else
    flag_mpi_init = .false.
#endif
    ! 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:
    ! The sea ice distribution has to be set, before set surface temperature. 
    !
    ! 海氷面密度
    ! 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
        !
        if ( flag_first_SeaIceConc ) then
          call HistoryGet( SeaIceFile, SeaIceName, xy_SeaIceConcSave, flag_mpi_split = flag_mpi_init )   ! (in) optional
        end if
        call SetValuesFromTimeSeriesWrapper( SeaIceFile, SeaIceName, xy_SeaIceConcSave, 'SIC' )
      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
      flag_first_SeaIceConc = .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, xy_SurfTempSave, 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         ) .and. ( xy_SeaIceConc(i,j)   < SeaIceThreshold ) ) then
              if ( ( .not. present( FlagSSModelSO ) ) .or. ( .not. FlagSSModelSO ) ) then
                xy_SurfTemp(i,j) = xy_SurfTempSave(i,j)
              end if
            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
    ! NOTICE:
    ! The surface condition and sea ice concentration have to be set, before albedo 
    ! is set.
    !
    ! アルベド
    ! Albedo
    !
    if ( present(xy_SurfAlbedo) ) then
      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
      else if ( AlbedoSetting == 'Matthews' ) then
        ! アルベドを Matthews のデータをもとに設定
        ! Surface albedo is set based on Matthews' data
        !
        call SetAlbedoMathews( xy_SurfCond, 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_SurfCond ) ) then
        ! 雪と海氷によるアルベド変化
        ! modification of surface albedo on the snow covered ground and on the sea ice
        !
        call ModAlbedoDueToSnowSeaIce( xy_SurfCond, xy_SurfSnowB, xy_SeaIceConc, xy_SurfAlbedo )
      else
        call MessageNotify( 'E', module_name, ' xy_SurfCond has to be present to modify albedo due to snow and sea ice.' )
      end if
      flag_first_SurfAlbedo = .false.
    end if
    ! NOTICE:
    ! The surface condition has to be set, before humidity coefficient is set.
    !
    ! 惑星表面湿潤度
    ! Surface humidity coefficient
    !
    if ( present(xy_SurfHumidCoef) ) then
      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 ( ( present( xy_SurfCond   ) ) .and. ( present( xy_SoilMoistB ) ) .and. ( present( xy_SurfSnowB  ) ) ) then
        ! バケツモデルに関わる地表面湿潤度の設定
        ! Setting of surface humidity coefficient
        !
        call BucketModHumidCoef( xy_SurfCond, xy_SoilMoistB, xy_SurfSnowB, xy_SurfHumidCoef )
      else
        call MessageNotify( 'E', module_name, ' xy_SurfCond and xy_SoilMoistB and Xy_SurfSnowB have to be present to modify humidity coefficient with bucket model.' )
      end if
      flag_first_SurfHumidCoef = .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
  end subroutine SetSurfaceProperties