Area_Rad_BLE_T Derived Type

type, public, abstract, extends(Rad_LE_T) :: Area_Rad_BLE_T


Inherits

type~~area_rad_ble_t~~InheritsGraph type~area_rad_ble_t Area_Rad_BLE_T type~rad_le_t Rad_LE_T type~area_rad_ble_t->type~rad_le_t

Inherited by

type~~area_rad_ble_t~~InheritedByGraph type~area_rad_ble_t Area_Rad_BLE_T type~area_vrad_ble_t Area_VRad_BLE_T type~area_vrad_ble_t->type~area_rad_ble_t type~area_srad_ble_t Area_SRad_BLE_T type~area_srad_ble_t->type~area_rad_ble_t

Contents


Components

TypeVisibility AttributesNameInitial
character(len=512), public :: OutFile
logical, public :: PRNBat =.false.
real(kind=krs), public :: adfpmin
real(kind=krs), public :: anxr
real(kind=krs), public :: anyr
real(kind=krs), public :: difr0
real(kind=krs), public :: difr1
integer(kind=kis), public :: ntgt
real(kind=krd), public :: MeanTiming

Type-Bound Procedures

procedure(init_Rad_LE), public, deferred :: init_Rad_LE

  • function init_Rad_LE(this, prob, GeoGrd, SrcOPT, OutFile, err) result(istat) Prototype

    initialize radiance estimators for local estimate

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    type(MSCART_Problem_T), intent(in) :: prob
    class(GeomGrid_T), intent(in) :: GeoGrd
    class(SrcOPT_T), intent(in) :: SrcOPT
    character(len=*), intent(in) :: OutFile
    type(erro_t), intent(inout) :: err

    Return Value integer(kind=kis)

procedure(free_Rad_LE), public, deferred :: free_Rad_LE

  • function free_Rad_LE(this, err) result(istat) Prototype

    free memory of radiance estimators

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    type(erro_t), intent(inout) :: err

    Return Value integer(kind=kis)

procedure(init_ncfile), public, deferred :: init_ncfile

  • function init_ncfile(this, GeoGrd, SrcOPT, nbat, err) result(istat) Prototype

    initialize output result of radiance estimators in NETCDF format

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    class(GeomGrid_T), intent(in) :: GeoGrd
    class(SrcOPT_T), intent(in) :: SrcOPT
    integer(kind=kis), intent(in) :: nbat
    type(erro_t), intent(inout) :: err

    Return Value integer(kind=kis)

procedure(estm_RadPsi), public, deferred :: estm_RadPsi

  • subroutine estm_RadPsi(this, itgt, photon, GeoGrd, AtmOPT, SrcOPT, istat, PFunTab, ftdcf, SfcOPT, pac) Prototype

    estimate scattering order-dependent radiance contributions

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    integer(kind=kis), intent(in) :: itgt
    type(photon_T), intent(in) :: photon
    class(GeomGrid_T), intent(in) :: GeoGrd
    class(AtmOPT_T), intent(in) :: AtmOPT
    class(SrcOPT_T), intent(in) :: SrcOPT
    integer(kind=kis), intent(in) :: istat
    class(PhsMatTab_T), intent(in), optional :: PFunTab
    real(kind=krs), intent(in), optional :: ftdcf
    class(SfcOPT_T), intent(in), optional :: SfcOPT
    real(kind=krs), intent(in), optional :: pac(:)

procedure(get_TgtDir), public, deferred :: get_TgtDir

  • subroutine get_TgtDir(this, SrcOPT, photon) Prototype

    get target direction for current radiance estimator

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(in) :: this
    class(SrcOPT_T), intent(in) :: SrcOPT
    type(photon_T), intent(inout) :: photon

procedure(sum_RadPsi_OneBatch), public, deferred :: sum_RadPsi_OneBatch

  • subroutine sum_RadPsi_OneBatch(this, SrcOPT, nPho, Timing) Prototype

    accumulate estimated radiation from one batch of photons

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    class(SrcOPT_T), intent(in) :: SrcOPT
    real(kind=krs), intent(in) :: nPho
    real(kind=krs), intent(in) :: Timing

procedure(sum_RadPsi_AllBatch), public, deferred :: sum_RadPsi_AllBatch

  • subroutine sum_RadPsi_AllBatch(this, SrcOPT, nbat, nph) Prototype

    accumulate estimated radiation from all batches of photons

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    class(SrcOPT_T), intent(in) :: SrcOPT
    integer(kind=kis), intent(in) :: nbat
    real(kind=krs), intent(in) :: nph

procedure(reset_RadPsi_OneBatch), public, deferred :: reset_RadPsi_OneBatch

  • subroutine reset_RadPsi_OneBatch(this) Prototype

    reset all variables of radiance estimators zeros

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this

procedure(reset_RadPsi_AllBatch), public, deferred :: reset_RadPsi_AllBatch

  • subroutine reset_RadPsi_AllBatch(this) Prototype

    reset all variables of radiance estimators zeros

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this

procedure(write_Rad_LE_result), public, deferred :: write_Rad_LE_result

  • function write_Rad_LE_result(this, SrcOPT, ibat, nPho, Timing, err) result(istat) Prototype

    write radiance results of each batch simulation

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    class(SrcOPT_T), intent(in) :: SrcOPT
    integer(kind=kis), intent(in) :: ibat
    real(kind=krs), intent(in) :: nPho
    real(kind=krs), intent(in) :: Timing
    type(erro_t), intent(inout) :: err

    Return Value integer(kind=kis)

procedure(write_Rad_LE_census), public, deferred :: write_Rad_LE_census

  • function write_Rad_LE_census(this, SrcOPT, nbat, nph, err) result(istat) Prototype

    write radiance results of all batch simulations

    Arguments

    Type IntentOptional AttributesName
    class(Rad_LE_T), intent(inout) :: this
    class(SrcOPT_T), intent(in) :: SrcOPT
    integer(kind=kis), intent(in) :: nbat
    real(kind=krs), intent(in) :: nph
    type(erro_t), intent(inout) :: err

    Return Value integer(kind=kis)

procedure(birth_RadPho), public, deferred :: birth_RadPho

  • subroutine birth_RadPho(this, photon) Prototype

    give birth of a new photon from are-averaged radiance estimators

    Arguments

    Type IntentOptional AttributesName
    class(Area_Rad_BLE_T), intent(inout) :: this
    type(photon_T), intent(inout) :: photon

procedure(set_HGrdId), public, deferred :: set_HGrdId

  • subroutine set_HGrdId(this, igrd) Prototype

    set a viewing horizontal grid index [ix,iy] for current area-averaged radiance estimator

    Arguments

    Type IntentOptional AttributesName
    class(Area_Rad_BLE_T), intent(inout) :: this
    integer(kind=kis), intent(in) :: igrd

procedure(set_DirHgtId), public, deferred :: set_DirHgtId

  • subroutine set_DirHgtId(this, IdPR) Prototype

    set current are-averaged radiance estimator index i_PRad

    Arguments

    Type IntentOptional AttributesName
    class(Area_Rad_BLE_T), intent(inout) :: this
    integer(kind=kis), intent(in) :: IdPR

procedure(get_HGrdNum), public, deferred :: get_HGrdNum

  • function get_HGrdNum(this) result(res) Prototype

    get total viewing horizontal grid number nx * ny

    Arguments

    Type IntentOptional AttributesName
    class(Area_Rad_BLE_T), intent(inout) :: this

    Return Value integer(kind=kis)

procedure(get_DirHgtNum), public, deferred :: get_DirHgtNum

  • function get_DirHgtNum(this) result(res) Prototype

    get total area-averaged radiance estimator number n_PRad

    Arguments

    Type IntentOptional AttributesName
    class(Area_Rad_BLE_T), intent(inout) :: this

    Return Value integer(kind=kis)