Class hs94forcing_mod
In: physics/hs94forcing.f90

begin

Dependency

Methods

Included Modules

type_mod constants_mod grid_3d_mod axis_type_mod io_gt4_out_mod dc_string dc_trace gt4_history

Public Instance methods

Subroutine :
xyz_VelLon_b(:,:,:) :real(DBKIND), intent(in)
: 地表面気圧 (t-Δt)
xyz_VelLat_b(:,:,:) :real(DBKIND), intent(in)
: 地表面気圧 (t-Δt)
xyz_Temp_b(:,:,:) :real(DBKIND), intent(in)
: 地表面気圧 (t-Δt)
xy_Ps_b(:,:) :real(DBKIND), intent(in)
: 地表面気圧 (t-Δt)
xyz_VelLon_phy(:,:,:) :real(DBKIND), intent(out)
: 温度の加熱散逸効果 =end
xyz_VelLat_phy(:,:,:) :real(DBKIND), intent(out)
: 温度の加熱散逸効果 =end
xyz_Temp_phy(:,:,:) :real(DBKIND), intent(out)
: 温度の加熱散逸効果 =end

[Source]

  subroutine hs94forcing( xyz_VelLon_b  , xyz_VelLat_b  , xyz_Temp_b  , xy_Ps_b    , xyz_VelLon_phy, xyz_VelLat_phy, xyz_Temp_phy            )

  !==== Dependency
    use type_mod,      only: INTKIND, STRING, TOKEN, REKIND, DBKIND
    use constants_mod, only: RAir, Cp, SecPerDay
    use grid_3d_mod  , only: im, jm, km
    use io_gt4_out_mod,only: io_gt4_out_Put
    use dc_trace     , only: DbgMessage, BeginSub, EndSub, DataDump
                                                                 !=end
    implicit none
                                                                 !=begin
    !==== Input
    !
    real(DBKIND), intent(in) :: xyz_VelLon_b(:,:,:) , xyz_VelLat_b(:,:,:) , xyz_Temp_b(:,:,:)   , xy_Ps_b(:,:)            ! 地表面気圧   (t-Δt)

    !==== Output
    !
    real(DBKIND), intent(out) :: xyz_VelLon_phy(:,:,:) , xyz_VelLat_phy(:,:,:) , xyz_Temp_phy(:,:,:)       ! 温度の加熱散逸効果
                                                                 !=end

    !----------------------------------------------------------------
    !   全体で用いる変数
    !----------------------------------------------------------------
    real(DBKIND) :: SigmaB  ! σ_b

    !----------------------------------------------------------------
    !   xyz_VelLon_phy, xyz_VelLat_phy を求めるための変数
    !----------------------------------------------------------------
    real(DBKIND) :: kf     ! k_f

    !----------------------------------------------------------------
    !   xyz_Temp_phy を求めるための変数
    !----------------------------------------------------------------
    real(DBKIND) :: Kappa             , Press0            , ka                , ks                , DelTempY          , DelPotTempZ           ! (Δθ)_z

    !----------------------------------------------------------------
    !   汎用変数
    !----------------------------------------------------------------
    integer(INTKIND) :: i, j, k

    character(STRING),  parameter:: subname = "hs94forcing"
  continue

    !----------------------------------------------------------------
    !   Check Initialization
    !----------------------------------------------------------------
    call BeginSub(subname)
    if (.not. hs94forcing_initialized) then
       call EndSub( subname, 'Call hs94forcing_init before call %c', c1=trim(subname) )
       return
    endif

    !----------------------------------------------------------------
    !   全体で用いる変数
    !----------------------------------------------------------------
    SigmaB    = 0.7d0

    !----------------------------------------------------------------
    !   xyz_VelLon_phy, xyz_VelLat_phy を求める
    !----------------------------------------------------------------
    kf        = 1.0d0 / SecPerDay

    xyz_kv = kf * max(  0.0d0, ( xyz_Sigma - SigmaB ) /( 1.0d0 - SigmaB )  )

    xyz_VelLon_phy = - xyz_kv * xyz_VelLon_b
    xyz_VelLat_phy = - xyz_kv * xyz_VelLat_b

    call DbgMessage('kf=<%f>', d=(/kf/))
    call io_gt4_out_Put('xyz_VelLon_phy', xyz_VelLon_phy)
    call io_gt4_out_Put('xyz_VelLat_phy', xyz_VelLat_phy)
    call io_gt4_out_Put('xyz_kv', xyz_kv)

    !----------------------------------------------------------------
    !   xyz_Temp_phy を求める
    !----------------------------------------------------------------
    do k = 1, km
       xyz_Press_b(:,:,k) = xyz_Sigma(:,:,k) * xy_Ps_b(:,:)
    enddo

    Kappa = RAir / Cp    ! κ=R/Cp (気体定数/定圧比熱)
    Press0    = 1000.0d0 * 1.0d2

    ka        = 1.0d0 / ( 40.0d0 * SecPerDay )
    ks        = 1.0d0 / ( 4.0d0 * SecPerDay )
    DelTempY    = 60.0d0
    DelPotTempZ = 10.0d0


    xyz_TempEQ = max( 200.0d0, ( 315.0d0 - DelTempY * xyz_SinLat**2 - DelPotTempZ * log( xyz_Press_b / Press0 ) * xyz_CosLat**2 ) * ( xyz_Press_b / Press0 )**Kappa )


    xyz_kt = ka + ( ks - ka ) * max(  0.0d0, ( xyz_Sigma - SigmaB ) / ( 1.0d0 - SigmaB ) ) * xyz_CosLat**4

    xyz_Temp_phy = - xyz_kt * ( xyz_Temp_b - xyz_TempEQ )

    call io_gt4_out_Put('xyz_Temp_phy', xyz_Temp_phy)

    call io_gt4_out_Put('xyz_TempEQ', xyz_TempEQ)
    call io_gt4_out_Put('xyz_PotTempEQ', xyz_TempEQ * ( xyz_Sigma )**( -Kappa )  )

!!$    call io_gt4_out_Put('1.0/max(xyz_kv, 1.0/86400d2)/86400.0', &
!!$         & 1.0/max(xyz_kv, 1.0/86400d2)/86400.0 )
!!$    call io_gt4_out_Put('1.0/xyz_kt', 1.0/xyz_kt)

!!$    call DataDump('1.0/xyz_kt', 1.0/xyz_kt, strlen=60)
!!$
!!$    call DataDump('xyz_Press_b', xyz_Press_b, strlen=60)
!!$
!!$    call DataDump('xyz_TempEQ1', &
!!$         &      ( 315.0d0 - DelTempY * xyz_SinLat**2 &
!!$         &        - DelPotTempZ * log( xyz_Press_b / Press0 ) &
!!$         &                          * xyz_CosLat**2 &
!!$         &      ) &
!!$         &      * ( xyz_Press_b / Press0 )**Kappa  &
!!$         & , strlen=60 )
!!$
!!$    call DataDump('xyz_TempEQ2', &
!!$         &       - DelTempY * xyz_SinLat**2 &
!!$         & , strlen=60 )
!!$
!!$    call DataDump('xyz_TempEQ3', &
!!$         &      ( - DelPotTempZ * log( xyz_Press_b / Press0 ) &
!!$         &                          * xyz_CosLat**2 &
!!$         &      ) &
!!$         & , strlen=60 )

    call EndSub(subname)
  end subroutine hs94forcing
Subroutine :

Dependency

[Source]

  subroutine hs94forcing_end
  !==== Dependency
    use type_mod, only: STRING, DBKIND, INTKIND
    use dc_trace, only: BeginSub, EndSub, DbgMessage
                                                                 !=end
    implicit none

    !-----------------------------------------------------------------
    !   変数定義
    !-----------------------------------------------------------------
    !----- 作業用内部変数 -----
    character(STRING),  parameter:: subname = "hs94forcing_end"

  continue

    !-----------------------------------------------------------------
    !   Check Initialization
    !-----------------------------------------------------------------
    call BeginSub(subname)
    if ( .not. hs94forcing_initialized) then
       call EndSub( subname, 'hs94forcing_init was not called', c1=trim(subname) )
       return
    else
       hs94forcing_initialized = .false.
    endif

    !-----------------------------------------------------------------
    !   Deallocate Variables
    !-----------------------------------------------------------------
    deallocate( xyz_Sigma    , xyz_kv       , xyz_Press_b  , xyz_SinLat   , xyz_CosLat   , xyz_TempEQ   , xyz_kt      )    ! k_t


    call EndSub(subname)
  end subroutine hs94forcing_end
Subroutine :
x_Lon :type(AXISINFO), intent(in)
: σレベル(整数)座標 =end
y_Lat :type(AXISINFO), intent(in)
: σレベル(整数)座標 =end
z_Sigma :type(AXISINFO), intent(in)
: σレベル(整数)座標 =end

[Source]

  subroutine hs94forcing_init( x_Lon         , y_Lat         , z_Sigma )

  !==== Dependency
    use type_mod,      only: INTKIND, STRING, TOKEN, REKIND, DBKIND
    use constants_mod, only: constants_init, pi
    use grid_3d_mod  , only: grid_3d_init, im, jm, km
    use axis_type_mod, only: AXISINFO
    use io_gt4_out_mod,only: io_gt4_out_init, io_gt4_out_SetVars
    use dc_string    , only: LChar, StrHead
    use dc_trace     , only: DbgMessage, BeginSub, EndSub, DataDump
    use gt4_history  , only: HistoryAxisInquire
                                                                 !=end
    implicit none
                                                                 !=begin
    !==== Input
    !
    type(AXISINFO), intent(in) :: x_Lon                , y_Lat                , z_Sigma                  ! σレベル(整数)座標
                                                                 !=end
    integer(INTKIND) :: i, j, k
    real(DBKIND)     :: RadDegFact     ! ラジアンと度数の変換係数

    character(STRING) :: axis_units
    character(STRING),  parameter:: subname = "hs94forcing_init"
  continue

    !----------------------------------------------------------------
    !   Check Initialization
    !----------------------------------------------------------------
    call BeginSub(subname)
    if (hs94forcing_initialized) then
       call EndSub( subname, '%c is already called.', c1=trim(subname) )
       return
    else
       hs94forcing_initialized = .true.
    endif

    !----------------------------------------------------------------
    !   Version identifier
    !----------------------------------------------------------------
    call DbgMessage('%c :: %c', c1=trim(version), c2=trim(tagname))

    !-----------------------------------------------------------------
    !   Initialize Dependent modules
    !-----------------------------------------------------------------
    call constants_init
    call grid_3d_init
    call io_gt4_out_init

    !-------------------------------------------------------------------
    !   Setting Ouput Data by io_gt4_out_set_Vars
    !-------------------------------------------------------------------
    call io_gt4_out_SetVars('xyz_VelLon_phy')
    call io_gt4_out_SetVars('xyz_VelLat_phy')
    call io_gt4_out_SetVars('xyz_Temp_phy')
    call io_gt4_out_SetVars('xyz_TempEQ')
    call io_gt4_out_SetVars('xyz_PotTempEQ')
    call io_gt4_out_SetVars('1.0/xyz_kt')
    call io_gt4_out_SetVars('1.0/max(xyz_kv, 1.0/86400d2)/86400.0')
    call io_gt4_out_SetVArs('xyz_kv')


    !-----------------------------------------------------------------
    !   Allocate variables
    !-----------------------------------------------------------------
    allocate( xyz_Sigma(im, jm, km)    , xyz_kv(im, jm, km)       , xyz_Press_b(im, jm, km)  , xyz_SinLat(im, jm, km)   , xyz_CosLat(im, jm, km)   , xyz_TempEQ(im,jm,km)     , xyz_kt(im,jm,km)      )      ! k_t

    !----------------------------------------------------------------
    !   全体で用いる変数
    !----------------------------------------------------------------
    do k = 1, km
       xyz_Sigma(:,:,k) = z_Sigma%a_Dim(k)
    enddo

    !----------------------------------------------------------------
    !   xyz_Temp_phy を求めるための変数
    !----------------------------------------------------------------
    call HistoryAxisInquire(y_Lat % axisinfo, units=axis_units)
    if (  StrHead( 'radians', trim(LChar(axis_units)) ) .or. StrHead( 'rad.', trim(LChar(axis_units)) ) ) then
       RadDegFact = 1.
    else
       RadDegFact = pi / 180.
    end if

    do j = 1, jm
       xyz_SinLat(:,j,:) = sin( y_Lat%a_Dim(j) * RadDegFact )
       xyz_CosLat(:,j,:) = cos( y_Lat%a_Dim(j) * RadDegFact )
    enddo

    call DataDump('xyz_SinLat', xyz_SinLat, strlen=70)
    call DataDump('xyz_CosLat', xyz_CosLat, strlen=70)

    call EndSub(subname)
  end subroutine hs94forcing_init

[Validate]