Class lb_flux_simple
In: surface_flux/lb_flux_simple.f90

����������������

Lower boundary flux

Note that Japanese and English are described in parallel.

References

!$ ! Louis, J-F., M. Tiedtke, and J-F. Geleyn, !$ ! A short history of the PBL parameterization at ECMWF, !$ ! Workshop on Planetary Boundary Layer Parameterization, 59-80, ECMWF, Reading, U.K., !$ ! 1982.

Procedures List

!$ ! SurfaceFlux :�°è¡¨�¢ã���������¹ã���ç®�
!$ ! SurfaceFluxOutput :�°è¡¨�¢ã���������¹ã���ºå��
!$ ! ———— :————
!$ ! SurfaceFlux :Calculate surface fluxes
!$ ! SurfaceFluxOutput :Output surface fluxes

NAMELIST

NAMELIST#lb_flux_simple_nml

Methods

Included Modules

gridset composition dc_types dc_message constants0 constants saturate axesset timeset dc_trace gtool_historyauto namelist_util dc_iounit dc_string dc_calendar

Public Instance methods

Subroutine :
xyz_U(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ u $ . �±è¥¿é¢���. Eastward wind
xyz_V(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ v $ . �������. Northward wind
xyz_Temp(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ T $ . æ¸�º¦ (�´æ�°ã������). Temperature (full level)
xyr_VirTemp(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ T_v $ . ä»�¸©åº� (���´æ�°ã������). Virtual temperature (half level)
xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(in)
: $ q $ . ��. Specific humidity
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ p_s $ . �°è¡¨�¢æ��� (���´æ�°ã������). Surface pressure (half level)
xy_SurfHeight(0:imax-1,1:jmax) :real(DP), intent(in)
: $ z_s $ . �°è¡¨�¢é�åº�. Surface height.
xyz_Height(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: é«�åº� (�´æ�°ã������). Height (full level)
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: Exner �¢æ�� (�´æ�°ã������). Exner function (full level)
xyr_Exner(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: Exner �¢æ�� (���´æ�°ã������). Exner function (half level)
xyr_MomFluxX(0:imax-1, 1:jmax, 0:0) :real(DP), intent(out)
: �±è¥¿�¹å�����������������. Eastward momentum flux
xyr_MomFluxY(0:imax-1, 1:jmax, 0:0) :real(DP), intent(out)
: �����¹å�����������������. Northward momentum flux
xyr_HeatFlux(0:imax-1, 1:jmax, 0:0) :real(DP), intent(out)
: �±ã����������. Heat flux
xyrf_QMixFlux(0:imax-1, 1:jmax, 0:0, 1:ncmax) :real(DP), intent(out)
: �湿���������. Specific humidity flux
xy_SurfVelTransCoef(0:imax-1, 1:jmax) :real(DP), intent(out)
: 輸é��ä¿��°ï�������. Diffusion coefficient: velocity
xy_SurfTempTransCoef(0:imax-1, 1:jmax) :real(DP), intent(out)
: 輸é��ä¿��°ï�æ¸�º¦. Transfer coefficient: temperature
xy_SurfQVapTransCoef(0:imax-1, 1:jmax) :real(DP), intent(out)
: 輸é��ä¿��°ï�æ°´è�¸æ� Transfer coefficient: water vapor

æ¸�º¦, æ¯�æ¹�, æ°��§ã����, �¾å����������¹ã��è¨�ç®����¾ã��.

Calculate radiation flux from temperature, specific humidity, and air pressure.

[Source]

  subroutine LBFluxSimple( xyz_U, xyz_V, xyz_Temp, xyr_VirTemp, xyzf_QMix, xyr_Press, xy_SurfHeight, xyz_Height, xyz_Exner, xyr_Exner, xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef )
    !
    ! æ¸�º¦, æ¯�æ¹�, æ°��§ã����, �¾å����������¹ã��è¨�ç®����¾ã��. 
    !
    ! Calculate radiation flux from temperature, specific humidity, and 
    ! air pressure. 
    !

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

    ! �����»æ�°å­¦å®��°è¨­å®�
    ! Physical and mathematical constants settings
    !
    use constants0, only: PI
                              ! $ \pi $ .
                              ! �����.  Circular constant

    ! ����å®��°è¨­å®�
    ! Physical constants settings
    !
    use constants, only: Grav, GasRDry, CpDry
                              ! $ C_p $ [J kg-1 K-1]. 
                              ! ä¹¾ç�¥å¤§æ°�����§æ���. 
                              ! Specific heat of air at constant pressure

    ! 飽��湿����
    ! Evaluate saturation specific humidity
    !
    use saturate, only: xy_CalcQVapSat

    ! 座æ����¼ã�¿è¨­å®�
    ! Axes data settings
    !
    use axesset, only: y_Lat                 ! $ \varphi $ [rad.] . ç·�º¦. Latitude

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

    ! �������°ç�����¼ã���£ã������
    ! Utilities for debug
    !
    use dc_trace, only: DbgMessage, BeginSub, EndSub

    ! 宣�� ; Declaration statements
    !

    real(DP), intent(in):: xyz_U (0:imax-1, 1:jmax, 1:kmax)
                              ! $ u $ . �±è¥¿é¢���. Eastward wind
    real(DP), intent(in):: xyz_V (0:imax-1, 1:jmax, 1:kmax)
                              ! $ v $ . �������. Northward wind

    real(DP), intent(in):: xyz_Temp (0:imax-1, 1:jmax, 1:kmax)
                              ! $ T $ . æ¸�º¦ (�´æ�°ã������). 
                              ! Temperature (full level)
    real(DP), intent(in):: xyr_VirTemp (0:imax-1, 1:jmax, 0:kmax)
                              ! $ T_v $ . ä»�¸©åº� (���´æ�°ã������). 
                              ! Virtual temperature (half level)
    real(DP), intent(in):: xyzf_QMix(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ q $ .     ��. Specific humidity
    real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
                              ! $ p_s $ . �°è¡¨�¢æ��� (���´æ�°ã������). 
                              ! Surface pressure (half level)
    real(DP), intent(in):: xy_SurfHeight(0:imax-1,1:jmax)
                              ! $ z_s $ . �°è¡¨�¢é�åº�. 
                              ! Surface height. 
    real(DP), intent(in):: xyz_Height (0:imax-1, 1:jmax, 1:kmax)
                              ! é«�åº� (�´æ�°ã������). 
                              ! Height (full level)
    real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
                              ! Exner �¢æ�� (�´æ�°ã������). 
                              ! Exner function (full level)
    real(DP), intent(in):: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
                              ! Exner �¢æ�� (���´æ�°ã������). 
                              ! Exner function (half level)
    real(DP), intent(out):: xyr_MomFluxX (0:imax-1, 1:jmax, 0:0)
                              ! �±è¥¿�¹å�����������������. 
                              ! Eastward momentum flux
    real(DP), intent(out):: xyr_MomFluxY (0:imax-1, 1:jmax, 0:0)
                              ! �����¹å�����������������. 
                              ! Northward momentum flux
    real(DP), intent(out):: xyr_HeatFlux (0:imax-1, 1:jmax, 0:0)
                              ! �±ã����������. 
                              ! Heat flux
    real(DP), intent(out):: xyrf_QMixFlux(0:imax-1, 1:jmax, 0:0, 1:ncmax)
                              ! �湿���������. 
                              ! Specific humidity flux
    real(DP), intent(out):: xy_SurfVelTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�������. 
                              ! Diffusion coefficient: velocity
    real(DP), intent(out):: xy_SurfTempTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�æ¸�º¦. 
                              ! Transfer coefficient: temperature
    real(DP), intent(out):: xy_SurfQVapTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�æ°´è�¸æ�
                              ! Transfer coefficient: water vapor

    ! �業��
    ! Work variables
    !
    real(DP) :: xy_TempAtLB   (0:imax-1, 1:jmax)
    real(DP) :: xy_QH2OVapAtLB(0:imax-1, 1:jmax)

    integer:: j
    integer:: n               ! çµ����¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in dimension of constituents

    ! ���� ; Executable statement
    !

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


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


    ! 輸é��ä¿��°ã���ç®�
    ! Calculate transfer coefficient
    !
    select case ( IDLBMomFluxMode )
    case ( IDLBMomFluxModeNoFlux )
      xy_SurfVelTransCoef = 0.0_DP
    case ( IDLBMomFluxModeFixTimeConst )
      if ( FricTimeConstAtLB <= 0.0_DP ) then
        call MessageNotify( 'E', module_name, 'FricTimeConstAtLB must be greater than or equal to zero.' )
      end if
      do j = 1, jmax
        if ( abs( y_Lat(j) ) >= FricLowestLatAtLB * PI / 180.0_DP ) then
          xy_SurfVelTransCoef(:,j) = - ( xyr_Press(:,j,1) - xyr_Press(:,j,0) ) / Grav / FricTimeConstAtLB
        else
          xy_SurfVelTransCoef(:,j) = 0.0_DP
        end if
      end do
    end select

    select case ( IDLBHeatFluxMode )
    case ( IDLBHeatFluxModeFixFlux )
      xy_SurfTempTransCoef = HeatFluxAtLB
    case ( IDLBHeatFluxModeFixTemp )
      xy_SurfTempTransCoef = xyr_Press(:,:,0) / ( GasRDry * xyr_VirTemp(:,:,0) ) * DiffCoefHeatMass / ( xyz_Height(:,:,1) - xy_SurfHeight )
    end select

    select case( IDLBH2OVapFluxMode )
    case ( IDLBH2OVapFluxModeFixFlux )
      xy_SurfQVapTransCoef = H2OVapFluxAtLB
    case ( IDLBH2OVapFluxModeFixMixRt )
      xy_SurfQVapTransCoef = xyr_Press(:,:,0) / ( GasRDry * xyr_VirTemp(:,:,0) ) * DiffCoefHeatMass / ( xyz_Height(:,:,1) - xy_SurfHeight )
    end select


    ! ä¸���������������¹ã���ç®�
    ! Calculate fluxes at lower boundary
    !
    !   Momentum
    !
    xyr_MomFluxX(:,:,0) = - xy_SurfVelTransCoef * xyz_U(:,:,1)
    xyr_MomFluxY(:,:,0) = - xy_SurfVelTransCoef * xyz_V(:,:,1)

    !   Heat
    !
    select case ( IDLBHeatFluxMode )
    case ( IDLBHeatFluxModeFixFlux )
      xyr_HeatFlux = HeatFluxAtLB
    case ( IDLBHeatFluxModeFixTemp )
      xy_TempAtLB = TempAtLB
      xyr_HeatFlux(:,:,0) = - CpDry * xyr_Exner(:,:,0) * xy_SurfTempTransCoef * (   xyz_Temp(:,:,1) / xyz_Exner(:,:,1) - xy_TempAtLB     / xyr_Exner(:,:,0) )
    end select

    !   Mass
    !
    select case( IDLBH2OVapFluxMode )
    case ( IDLBH2OVapFluxModeFixFlux )
      xyrf_QMixFlux(:,:,0,IndexH2OVap) = H2OVapFluxAtLB
    case ( IDLBH2OVapFluxModeFixMixRt )
      xy_QH2OVapAtLB = QH2OVapAtLB
      xyrf_QMixFlux(:,:,0,IndexH2OVap) = - xy_SurfQVapTransCoef * ( xyzf_QMix(:,:,1,IndexH2OVap) - xy_QH2OVapAtLB )
    end select
    !
    xyrf_QMixFlux(:,:,0,1:IndexH2OVap-1)     = 0.0_DP
    xyrf_QMixFlux(:,:,0,IndexH2OVap+1:ncmax) = 0.0_DP

    ! Surface flux of constituents except for water vapor is zero.
!!$    write( 6, * ) "MEMO: Surface flux of constituents except for water vapor is zero. (YOT, 2013/05/15)"


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !

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

  end subroutine LBFluxSimple
Subroutine :

surface_flux_bulk �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. NAMELIST#surface_flux_bulk_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��.

"surface_flux_bulk" module is initialized. "NAMELIST#surface_flux_bulk_nml" is loaded in this procedure.

This procedure input/output NAMELIST#lb_flux_simple_nml .

[Source]

  subroutine LBFluxSimpleInit
    !
    ! surface_flux_bulk �¢ã�¸ã�¥ã�¼ã������������è¡����¾ã��. 
    ! NAMELIST#surface_flux_bulk_nml ����¿è¾¼�¿ã��������ç¶����§è�����¾ã��. 
    !
    ! "surface_flux_bulk" module is initialized. 
    ! "NAMELIST#surface_flux_bulk_nml" is loaded in this procedure. 
    !

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

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

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

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

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


    ! �¥ä������³æ���»ã������±ã��
    ! Date and time handler
    !
    use dc_calendar, only: DCCalConvertByUnit

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

    ! ����å®��°è¨­å®�
    ! Physical constant settings
    !
    use constants, only: GasRDry, CpDry
                              ! $ C_p $ [J kg-1 K-1]. 
                              ! ä¹¾ç�¥å¤§æ°�����§æ���. 
                              ! Specific heat of air at constant pressure

    ! 宣�� ; Declaration statements
    !
    real(DP)         :: FricTimeConstAtLBValue
    character(TOKEN) :: FricTimeConstAtLBUnit

    character(STRING) :: LBMomFluxMode
    character(STRING) :: LBHeatFluxMode
    character(STRING) :: LBH2OVapFluxMode

    integer:: unit_nml        ! NAMELIST ���¡ã�¤ã�����¼ã���³ç���ç½����. 
                              ! Unit number for NAMELIST file open
    integer:: iostat_nml      ! NAMELIST 読ã�¿è¾¼�¿æ���� IOSTAT. 
                              ! IOSTAT of NAMELIST read

    ! NAMELIST å¤��°ç¾¤
    ! NAMELIST group name
    !
    namelist /lb_flux_simple_nml/ LBMomFluxMode, FricTimeConstAtLBValue, FricTimeConstAtLBUnit, FricLowestLatAtLB, LBHeatFluxMode, HeatFluxAtLB, TempAtLB, LBH2OVapFluxMode, H2OVapFluxAtLB, QH2OVapAtLB, DiffCoefHeatMass
          !
          ! �����������¤ã���¤ã��������������ç¶� "lb_flux_simple#LBFluxSimpleInit" 
          ! ���½ã�¼ã�¹ã�³ã�¼ã�������§ã������. 
          !
          ! Refer to source codes in the initialization procedure
          ! "lb_flux_simple#LBFluxSimpleInit" for the default values. 
          !

    ! ���� ; Executable statement
    !

    if ( lb_flux_simple_inited ) return


    ! �����������¤ã��¨­å®�
    ! Default values settings
    !
    LBMomFluxMode            = 'FixTimeConst'
    FricTimeConstAtLBValue   = 20.0_DP   ! Schneider and Liou (2009)
    FricTimeConstAtLBUnit    = 'day'
    FricLowestLatAtLB        = 16.3_DP   ! Schneider and Liou (2009)

    LBHeatFluxMode           = 'FixFlux'
    HeatFluxAtLB             =  5.7_DP   ! Schneider and Liou (2009)
    TempAtLB                 =  160.0_DP * ( 30.0_DP / 0.6_DP )**( GasRDry / CpDry )
                                 ! Sugiyama et al. (2009), Nagare Multimedia
                                 ! Potential Temperature of 160 K with 
                                 ! reference pressure of 0.6 bars

    LBH2OVapFluxMode         = 'FixFlux'
    H2OVapFluxAtLB           =  0.0_DP
    QH2OVapAtLB              =  7.816e-4_DP
                                 ! Sugiyama et al. (2009), Nagare Multimedia
    DiffCoefHeatMass         = 800.0_DP
                                 ! Sugiyama et al. (2009), Nagare Multimedia

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

      call NmlutilMsg( iostat_nml, module_name ) ! (in)
    end if


    FricTimeConstAtLB = DCCalConvertByUnit( FricTimeConstAtLBValue, FricTimeConstAtLBUnit, 'sec' ) ! (in)


    ! Identification of calculation method for momentum flux
    !
    call MessageNotify( 'M', module_name, 'LBMomFluxMode=<%c>.', c1 = trim(LBMomFluxMode) )
    select case ( LBMomFluxMode )
    case ( 'NoFlux' )
      IDLBMomFluxMode = IDLBMomFluxModeNoFlux
    case ( 'FixTimeConst' )
      IDLBMomFluxMode = IDLBMomFluxModeFixTimeConst
    case default
      call MessageNotify( 'E', module_name, 'LBMomFluxMode=<%c> is not supported.', c1 = trim(LBMomFluxMode) )
    end select

    ! Identification of calculation method for heat flux
    !
    call MessageNotify( 'M', module_name, 'LBHeatFluxMode=<%c>.', c1 = trim(LBHeatFluxMode) )
    select case ( LBHeatFluxMode )
    case ( 'FixFlux' )
      IDLBHeatFluxMode = IDLBHeatFluxModeFixFlux
    case ( 'FixTemp' )
      IDLBHeatFluxMode = IDLBHeatFluxModeFixFlux
    case default
      call MessageNotify( 'E', module_name, 'LBHeatFluxMode=<%c> is not supported.', c1 = trim(LBHeatFluxMode) )
    end select

    ! Identification of calculation method for H2O vapor flux
    !
    call MessageNotify( 'M', module_name, 'LBH2OVapFluxMode=<%c>.', c1 = trim(LBH2OVapFluxMode) )
    select case ( LBH2OVapFluxMode )
    case ( 'FixFlux' )
      IDLBH2OVapFluxMode = IDLBH2OVapFluxModeFixFlux
    case ( 'FixMixRt' )
      IDLBH2OVapFluxMode = IDLBH2OVapFluxModeFixMixRt
    case default
      call MessageNotify( 'E', module_name, 'LBH2OVapFluxMode=<%c> is not supported.', c1 = trim(LBH2OVapFluxMode) )
    end select



    ! ���¹ã�������¼ã�¿å�ºå�����������¸ã����°ç�»é��
    ! Register of variables for history data output
    !
    call HistoryAutoAddVariable( 'TauX', (/ 'lon ', 'lat ', 'time' /), 'surface stress(x)  ', 'N m-2' )
    call HistoryAutoAddVariable( 'TauY', (/ 'lon ', 'lat ', 'time' /), 'surface stress(y)  ', 'N m-2' )
    call HistoryAutoAddVariable( 'Sens', (/ 'lon ', 'lat ', 'time' /), 'sensible heat flux', 'W m-2' )
    call HistoryAutoAddVariable( 'SurfH2OVapFlux', (/ 'lon ', 'lat ', 'time' /), 'surface H2O vapor flux  ', 'kg m-2 s-1' )
    call HistoryAutoAddVariable( 'Evap', (/ 'lon ', 'lat ', 'time' /), 'latent heat flux  ', 'W m-2' )

    call HistoryAutoAddVariable( 'TauXB', (/ 'lon ', 'lat ', 'time' /), 'surface stress(x)  ', 'N m-2' )
    call HistoryAutoAddVariable( 'TauYB', (/ 'lon ', 'lat ', 'time' /), 'surface stress(y)  ', 'N m-2' )
    call HistoryAutoAddVariable( 'SensB', (/ 'lon ', 'lat ', 'time' /), 'sensible heat flux', 'W m-2' )
    call HistoryAutoAddVariable( 'SurfH2OVapFluxB', (/ 'lon ', 'lat ', 'time' /), 'surface H2O vapor flux  ', 'kg m-2 s-1' )
    call HistoryAutoAddVariable( 'EvapB', (/ 'lon ', 'lat ', 'time' /), 'latent heat flux  ', 'W m-2' )

    call HistoryAutoAddVariable( 'TauXA', (/ 'lon ', 'lat ', 'time' /), 'surface stress(x)  ', 'N m-2' )
    call HistoryAutoAddVariable( 'TauYA', (/ 'lon ', 'lat ', 'time' /), 'surface stress(y)  ', 'N m-2' )
    call HistoryAutoAddVariable( 'SensA', (/ 'lon ', 'lat ', 'time' /), 'sensible heat flux', 'W m-2' )
    call HistoryAutoAddVariable( 'SurfH2OVapFluxA', (/ 'lon ', 'lat ', 'time' /), 'surface H2O vapor flux  ', 'kg m-2 s-1' )
    call HistoryAutoAddVariable( 'EvapA', (/ 'lon ', 'lat ', 'time' /), 'latent heat flux  ', 'W m-2' )

    call HistoryAutoAddVariable( 'SurfH2OVapFluxU', (/ 'lon ', 'lat ', 'time' /), 'surface H2O vapor flux  ', 'kg m-2 s-1' )
    call HistoryAutoAddVariable( 'EvapU', (/ 'lon ', 'lat ', 'time' /), 'latent heat flux  ', 'W m-2' )

    ! �°å� ; Print
    !
    call MessageNotify( 'M', module_name, '----- Initialization Messages -----' )
    call MessageNotify( 'M', module_name, 'LBMomFluxMode            = %c', c1 = trim( LBMomFluxMode ) )
    call MessageNotify( 'M', module_name, 'FricTimeConstAtLB        = %f', d = (/ FricTimeConstAtLB /) )
    call MessageNotify( 'M', module_name, 'FricLowestLatAtLB        = %f', d = (/ FricLowestLatAtLB /) )
    call MessageNotify( 'M', module_name, 'LBHeatFluxMode           = %c', c1 = trim( LBHeatFluxMode ) )
    call MessageNotify( 'M', module_name, 'HeatFluxAtLB             = %f', d = (/ HeatFluxAtLB /) )
    call MessageNotify( 'M', module_name, 'TempAtLB                 = %f', d = (/ TempAtLB /) )
    call MessageNotify( 'M', module_name, 'LBH2OVapFluxMode         = %c', c1 = trim( LBH2OVapFluxMode ) )
    call MessageNotify( 'M', module_name, 'H2OVapFluxAtLB           = %f', d = (/ H2OVapFluxAtLB /) )
    call MessageNotify( 'M', module_name, 'QH2OVapAtLB              = %f', d = (/ QH2OVapAtLB /) )
    call MessageNotify( 'M', module_name, 'DiffCoefHeatMass         = %f', d = (/ DiffCoefHeatMass /) )
    call MessageNotify( 'M', module_name, '-- version = %c', c1 = trim(version) )

    lb_flux_simple_inited = .true.

  end subroutine LBFluxSimpleInit

Private Instance methods

DiffCoefHeatMass
Variable :
DiffCoefHeatMass :real(DP), save
FricLowestLatAtLB
Variable :
FricLowestLatAtLB :real(DP), save
: ä¸�����������������ä½�·¯åº� (degree). Lowest latitude where the friction is applied (degree)
FricTimeConstAtLB
Variable :
FricTimeConstAtLB :real(DP), save
: ��������������� (s). Time constant of surface friction (s).
H2OVapFluxAtLB
Variable :
H2OVapFluxAtLB :real(DP), save
: ä¸�������§ã�� H2O �¸æ�è³������������ (W m-2). å®��������¼ã�­ã���ºå�����������½¿��ç¨�åº�������使ã������������. H2O vapor flux at the lower boundary (kg m-2 s-1).
HeatFluxAtLB
Variable :
HeatFluxAtLB :real(DP), save
: ä¸�������§ã���±ã���������� (W m-2). Heat flux at the lower boundary (W m-2).
IDLBH2OVapFluxMode
Variable :
IDLBH2OVapFluxMode :integer, save
IDLBH2OVapFluxModeFixFlux
Constant :
IDLBH2OVapFluxModeFixFlux = 30 :integer, parameter
IDLBH2OVapFluxModeFixMixRt
Constant :
IDLBH2OVapFluxModeFixMixRt = 31 :integer, parameter
IDLBHeatFluxMode
Variable :
IDLBHeatFluxMode :integer, save
IDLBHeatFluxModeFixFlux
Constant :
IDLBHeatFluxModeFixFlux = 20 :integer, parameter
IDLBHeatFluxModeFixTemp
Constant :
IDLBHeatFluxModeFixTemp = 21 :integer, parameter
IDLBMomFluxMode
Variable :
IDLBMomFluxMode :integer, save
IDLBMomFluxModeFixTimeConst
Constant :
IDLBMomFluxModeFixTimeConst = 11 :integer, parameter
IDLBMomFluxModeNoFlux
Constant :
IDLBMomFluxModeNoFlux = 10 :integer, parameter
QH2OVapAtLB
Variable :
QH2OVapAtLB :real(DP), save
Subroutine :
xyr_MomFluxX(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �±è¥¿�¹å�����������������. Eastward momentum flux
xyr_MomFluxY(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �����¹å�����������������. Northward momentum flux
xyr_HeatFlux(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: �±ã����������. Heat flux
xyrf_QMixFlux(0:imax-1, 1:jmax, 0:kmax, 1:ncmax) :real(DP), intent(in)
: �湿���������. Specific humidity flux
xy_SurfH2OVapFluxA(0:imax-1, 1:jmax) :real(DP), intent(in)
: ����è¡��¢æ°´�¸æ�����������. Water vapor flux at the surface
xy_SurfLatentHeatFluxA(0:imax-1, 1:jmax) :real(DP), intent(in)
: ����è¡��¢æ��±ã����������. Latent heat flux at the surface
xyz_DUDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{u}{t} $ . �±è¥¿é¢�������å¤�����. Eastward wind tendency
xyz_DVDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{v}{t} $ . ����������������. Northward wind tendency
xyz_DTempDt(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: $ DP{T}{t} $ . æ¸�º¦����å¤�����. Temperature tendency
xyzf_DQMixDt(0:imax-1, 1:jmax, 1:kmax, 1:ncmax) :real(DP), intent(in)
: $ DP{q}{t} $ . �湿��������. Specific humidity tendency
xy_SurfTemp(0:imax-1, 1:jmax) :real(DP), intent(in)
: �°è¡¨�¢æ¸©åº�. Surface temperature
xy_DSurfTempDt(0:imax-1, 1:jmax) :real(DP), intent(in)
: �°è¡¨�¢æ¸©åº�����å¤�����. Surface temperature tendency
xyr_Press(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: $ hat{p} $ . æ°��� (���´æ�°ã������). Air pressure (half level)
xyz_Exner(0:imax-1, 1:jmax, 1:kmax) :real(DP), intent(in)
: Exner �¢æ�� (�´æ�°ã������). Exner function (full level)
xyr_Exner(0:imax-1, 1:jmax, 0:kmax) :real(DP), intent(in)
: Exner �¢æ�� (���´æ�°ã������). Exner function (half level)
xy_SurfHumidCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: �°è¡¨æ¹¿æ½¤åº�. Surface humidity coefficient
xy_SurfVelTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸é��ä¿��°ï�������. Diffusion coefficient: velocity
xy_SurfTempTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸é��ä¿��°ï�æ¸�º¦. Transfer coefficient: temperature
xy_SurfQVapTransCoef(0:imax-1, 1:jmax) :real(DP), intent(in)
: 輸é��ä¿��°ï�æ°´è�¸æ� Transfer coefficient: water vapor

���������� (xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux). ���¤ã����, ���������°ã���������æ­£ã��, �ºå����è¡���.

Fluxes (xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux) are corrected by using other arguments, and the corrected values are output.

[Source]

  subroutine SurfaceFluxOutput( xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux, xy_SurfH2OVapFluxA, xy_SurfLatentHeatFluxA, xyz_DUDt, xyz_DVDt, xyz_DTempDt, xyzf_DQMixDt, xy_SurfTemp, xy_DSurfTempDt, xyr_Press, xyz_Exner, xyr_Exner, xy_SurfHumidCoef, xy_SurfVelTransCoef, xy_SurfTempTransCoef, xy_SurfQVapTransCoef )
    !
    ! ���������� (xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux). 
    ! ���¤ã����, ���������°ã���������æ­£ã��, �ºå����è¡���. 
    !
    ! Fluxes (xyr_MomFluxX, xyr_MomFluxY, xyr_HeatFlux, xyrf_QMixFlux) are
    ! corrected by using other arguments, and the corrected values are output.
    !

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

    ! ����å®��°è¨­å®�
    ! Physical constant settings
    !
    use constants, only: GasRDry, CpDry, LatentHeat
                              ! $ L $ [J kg-1] . 
                              ! ��������. 
                              ! Latent heat of condensation

    ! 飽��湿����
    ! Evaluation of saturation specific humidity
    !
    use saturate, only: xy_CalcQVapSat, xy_CalcDQVapSatDTemp

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

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

    ! 宣�� ; Declaration statements
    !

    real(DP), intent(in):: xyr_MomFluxX (0:imax-1, 1:jmax, 0:kmax)
                              ! �±è¥¿�¹å�����������������. 
                              ! Eastward momentum flux
    real(DP), intent(in):: xyr_MomFluxY (0:imax-1, 1:jmax, 0:kmax)
                              ! �����¹å�����������������. 
                              ! Northward momentum flux
    real(DP), intent(in):: xyr_HeatFlux (0:imax-1, 1:jmax, 0:kmax)
                              ! �±ã����������. 
                              ! Heat flux
    real(DP), intent(in):: xyrf_QMixFlux(0:imax-1, 1:jmax, 0:kmax, 1:ncmax)
                              ! �湿���������. 
                              ! Specific humidity flux
    real(DP), intent(in):: xy_SurfH2OVapFluxA    (0:imax-1, 1:jmax)
                              ! ����è¡��¢æ°´�¸æ�����������.
                              ! Water vapor flux at the surface
    real(DP), intent(in):: xy_SurfLatentHeatFluxA(0:imax-1, 1:jmax)
                              ! ����è¡��¢æ��±ã����������.
                              ! Latent heat flux at the surface
    real(DP), intent(in):: xyz_DUDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{u}{t} $ . �±è¥¿é¢�������å¤�����. 
                              ! Eastward wind tendency
    real(DP), intent(in):: xyz_DVDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{v}{t} $ . ����������������. 
                              ! Northward wind tendency
    real(DP), intent(in):: xyz_DTempDt (0:imax-1, 1:jmax, 1:kmax)
                              ! $ \DP{T}{t} $ . æ¸�º¦����å¤�����. 
                              ! Temperature tendency
    real(DP), intent(in):: xyzf_DQMixDt(0:imax-1, 1:jmax, 1:kmax, 1:ncmax)
                              ! $ \DP{q}{t} $ . �湿��������. 
                              ! Specific humidity tendency
    real(DP), intent(in):: xy_SurfTemp (0:imax-1, 1:jmax)
                              ! �°è¡¨�¢æ¸©åº�. 
                              ! Surface temperature
    real(DP), intent(in):: xy_DSurfTempDt (0:imax-1, 1:jmax)
                              ! �°è¡¨�¢æ¸©åº�����å¤�����. 
                              ! Surface temperature tendency
    real(DP), intent(in):: xyr_Press (0:imax-1, 1:jmax, 0:kmax)
                              ! $ \hat{p} $ . æ°��� (���´æ�°ã������). 
                              ! Air pressure (half level)
    real(DP), intent(in):: xyz_Exner (0:imax-1, 1:jmax, 1:kmax)
                              ! Exner �¢æ�� (�´æ�°ã������). 
                              ! Exner function (full level)
    real(DP), intent(in):: xyr_Exner (0:imax-1, 1:jmax, 0:kmax)
                              ! Exner �¢æ�� (���´æ�°ã������). 
                              ! Exner function (half level)
    real(DP), intent(in):: xy_SurfHumidCoef (0:imax-1, 1:jmax)
                              ! �°è¡¨æ¹¿æ½¤åº�. 
                              ! Surface humidity coefficient
    real(DP), intent(in):: xy_SurfVelTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�������. 
                              ! Diffusion coefficient: velocity
    real(DP), intent(in):: xy_SurfTempTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�æ¸�º¦. 
                              ! Transfer coefficient: temperature
    real(DP), intent(in):: xy_SurfQVapTransCoef (0:imax-1, 1:jmax)
                              ! 輸é��ä¿��°ï�æ°´è�¸æ�
                              ! Transfer coefficient: water vapor

    ! �ºå�����������業å���
    ! Work variables for output
    !
    real(DP):: xyr_MomFluxXCor (0:imax-1, 1:jmax, 0:kmax)
                              ! �±è¥¿�¹å�����������������. 
                              ! Eastward momentum flux
    real(DP):: xyr_MomFluxYCor (0:imax-1, 1:jmax, 0:kmax)
                              ! �����¹å�����������������. 
                              ! Northward momentum flux
    real(DP):: xyr_HeatFluxCor (0:imax-1, 1:jmax, 0:kmax)
                              ! �±ã����������. 
                              ! Heat flux
    real(DP):: xyrf_QMixFluxCor(0:imax-1, 1:jmax, 0:kmax, 1:ncmax)
                              ! �湿���������. 
                              ! Specific humidity flux
    real(DP):: xyr_LatentHeatFluxCor(0:imax-1, 1:jmax, 0:kmax)
                              ! è¡��¢æ��±ã����������.
                              ! Latent heat flux
    real(DP):: xy_SurfQVapSat (0:imax-1, 1:jmax)
                              ! �°è¡¨é£½å��æ¯�æ¹�. 
                              ! Saturated specific humidity on surface
    real(DP):: xy_SurfDQVapSatDTemp (0:imax-1, 1:jmax)
                              ! �°è¡¨é£½å��æ¯�湿å���. 
                              ! Saturated specific humidity tendency on surface

    ! �業��
    ! Work variables
    !
    integer:: i               ! çµ�åº��¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in longitude
    integer:: j               ! ç·�º¦�¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in latitude
    integer:: n               ! çµ����¹å�������� DO ���¼ã�����業å���
                              ! Work variables for DO loop in dimension of constituents


    ! ���� ; Executable statement
    !

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


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


    ! 飽��湿���
    ! Calculate saturated specific humidity
    !
    xy_SurfQVapSat       = xy_CalcQVapSat      ( xy_SurfTemp, xyr_Press(:,:,0) )
    xy_SurfDQVapSatDTemp = xy_CalcDQVapSatDTemp( xy_SurfTemp, xy_SurfQVapSat   )

    ! Output of fluxes at t
    !

    ! é¢���, æ¸�º¦, æ¯�湿ã���������¹è�æ­�
    ! Correct fluxes of wind, temperature, specific humidity
    !
    do j = 1, jmax
      do i = 0, imax-1
        xyr_MomFluxXCor( i,j,0 ) = xyr_MomFluxX( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DUDt( i,j,1 ) * DelTime

        xyr_MomFluxYCor( i,j,0 ) = xyr_MomFluxY( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DVDt( i,j,1 ) * DelTime

        xyr_HeatFluxCor( i,j,0 ) = xyr_HeatFlux( i,j,0 ) - CpDry * xyr_Exner( i,j,0 ) * xy_SurfTempTransCoef( i,j ) * ( xyz_DTempDt( i,j,1 ) / xyz_Exner( i,j,1 ) - xy_DSurfTempDt( i,j ) / xyr_Exner( i,j,0 ) ) * DelTime
      end do
    end do
    n = IndexH2OVap
    do j = 1, jmax
      do i = 0, imax-1
        xyrf_QMixFluxCor( i,j,0,n ) = xyrf_QMixFlux( i,j,0,n ) - xy_SurfHumidCoef( i,j ) * xy_SurfQVapTransCoef( i,j ) * ( xyzf_DQMixDt( i,j,1,n ) - xy_SurfDQVapSatDTemp( i,j ) * xy_DSurfTempDt( i,j ) ) * DelTime
      end do
    end do
    do n = 1, IndexH2OVap-1
      xyrf_QMixFluxCor(:,:,0,n) = xyrf_QMixFlux(:,:,0,n)
    end do
    do n = IndexH2OVap+1, ncmax
      xyrf_QMixFluxCor(:,:,0,n) = xyrf_QMixFlux(:,:,0,n)
    end do
    n = IndexH2OVap
    do j = 1, jmax
      do i = 0, imax-1
        xyr_LatentHeatFluxCor( i,j,0 ) = LatentHeat * xyrf_QMixFluxCor( i,j,0,n )
      end do
    end do


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'TauX'          , xyr_MomFluxXCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'TauY'          , xyr_MomFluxYCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'Sens'          , xyr_HeatFluxCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'SurfH2OVapFlux', xyrf_QMixFluxCor(:,:,0,IndexH2OVap) )
    call HistoryAutoPut( TimeN, 'Evap'          , xyr_LatentHeatFluxCor(:,:,0) )


    ! Output of fluxes at t - \Delta t
    !

    ! é¢���, æ¸�º¦, æ¯�湿ã���������¹è�æ­�
    ! Correct fluxes of wind, temperature, specific humidity
    !
    do j = 1, jmax
      do i = 0, imax-1
        xyr_MomFluxXCor( i,j,0 ) = xyr_MomFluxX( i,j,0 )
        xyr_MomFluxYCor( i,j,0 ) = xyr_MomFluxY( i,j,0 )
        xyr_HeatFluxCor( i,j,0 ) = xyr_HeatFlux( i,j,0 )
      end do
    end do
    n = IndexH2OVap
    do j = 1, jmax
      do i = 0, imax-1
        xyrf_QMixFluxCor( i,j,0,n ) = xyrf_QMixFlux( i,j,0,n )
      end do
    end do
    do n = 1, IndexH2OVap-1
      xyrf_QMixFluxCor(:,:,0,n) = xyrf_QMixFlux(:,:,0,n)
    end do
    do n = IndexH2OVap+1, ncmax
      xyrf_QMixFluxCor(:,:,0,n) = xyrf_QMixFlux(:,:,0,n)
    end do
    n = IndexH2OVap
    do j = 1, jmax
      do i = 0, imax-1
        xyr_LatentHeatFluxCor( i,j,0 ) = LatentHeat * xyrf_QMixFluxCor( i,j,0,n )
      end do
    end do

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'TauXB'          , xyr_MomFluxXCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'TauYB'          , xyr_MomFluxYCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'SensB'          , xyr_HeatFluxCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'SurfH2OVapFluxB', xyrf_QMixFluxCor(:,:,0,IndexH2OVap) )
    call HistoryAutoPut( TimeN, 'EvapB'          , xyr_LatentHeatFluxCor(:,:,0) )


    ! Output of fluxes at t + \Delta t
    !

    ! é¢���, æ¸�º¦, æ¯�湿ã���������¹è�æ­�
    ! Correct fluxes of wind, temperature, specific humidity
    !
    do j = 1, jmax
      do i = 0, imax-1
        xyr_MomFluxXCor( i,j,0 ) = xyr_MomFluxX( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DUDt( i,j,1 ) * 2.0_DP * DelTime

        xyr_MomFluxYCor( i,j,0 ) = xyr_MomFluxY( i,j,0 ) - xy_SurfVelTransCoef( i,j ) * xyz_DVDt( i,j,1 ) * 2.0_DP * DelTime

        xyr_HeatFluxCor( i,j,0 ) = xyr_HeatFlux( i,j,0 ) - CpDry * xyr_Exner( i,j,0 ) * xy_SurfTempTransCoef( i,j ) * ( xyz_DTempDt( i,j,1 ) / xyz_Exner( i,j,1 ) - xy_DSurfTempDt( i,j ) / xyr_Exner( i,j,0 ) ) * 2.0_DP * DelTime
      end do
    end do
    n = IndexH2OVap
    do j = 1, jmax
      do i = 0, imax-1
        xyrf_QMixFluxCor( i,j,0,n ) = xyrf_QMixFlux( i,j,0,n ) - xy_SurfHumidCoef( i,j ) * xy_SurfQVapTransCoef( i,j ) * ( xyzf_DQMixDt( i,j,1,n ) - xy_SurfDQVapSatDTemp( i,j ) * xy_DSurfTempDt( i,j ) ) * 2.0_DP * DelTime
      end do
    end do
    do n = 1, IndexH2OVap-1
      xyrf_QMixFluxCor(:,:,0,n) = xyrf_QMixFlux(:,:,0,n)
    end do
    do n = IndexH2OVap+1, ncmax
      xyrf_QMixFluxCor(:,:,0,n) = xyrf_QMixFlux(:,:,0,n)
    end do
    n = IndexH2OVap
    do j = 1, jmax
      do i = 0, imax-1
        xyr_LatentHeatFluxCor( i,j,0 ) = LatentHeat * xyrf_QMixFluxCor( i,j,0,n )
      end do
    end do

    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'TauXA'          , xyr_MomFluxXCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'TauYA'          , xyr_MomFluxYCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'SensA'          , xyr_HeatFluxCor (:,:,0) )
    call HistoryAutoPut( TimeN, 'SurfH2OVapFluxA', xyrf_QMixFluxCor(:,:,0,IndexH2OVap) )
    call HistoryAutoPut( TimeN, 'EvapA'          , xyr_LatentHeatFluxCor(:,:,0) )


    ! ���¹ã�������¼ã�¿å�ºå��
    ! History data output
    !
    call HistoryAutoPut( TimeN, 'SurfH2OVapFluxU', xy_SurfH2OVapFluxA     )
    call HistoryAutoPut( TimeN, 'EvapU'          , xy_SurfLatentHeatFluxA )


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

  end subroutine SurfaceFluxOutput
TempAtLB
Variable :
TempAtLB :real(DP), save
lb_flux_simple_inited
Variable :
lb_flux_simple_inited = .false. :logical, save
: ����設������. Initialization flag
module_name
Constant :
module_name = ‘lb_flux_simple :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã������ç§�. Module name
version
Constant :
version = ’$Name: $’ // ’$Id: lb_flux_simple.f90,v 1.2 2014/05/07 09:39:22 murashin Exp $’ :character(*), parameter
: �¢ã�¸ã�¥ã�¼ã�������¼ã�¸ã�§ã�� Module version