Area_VRad_FLE_Mod Module


Uses

  • module~~area_vrad_fle_mod~~UsesGraph module~area_vrad_fle_mod Area_VRad_FLE_Mod module~rad_le_mod Rad_LE_Mod module~area_vrad_fle_mod->module~rad_le_mod Cons_Pack Cons_Pack module~area_vrad_fle_mod->Cons_Pack module~rand_pack Rand_Pack module~area_vrad_fle_mod->module~rand_pack Kind_Pack Kind_Pack module~area_vrad_fle_mod->Kind_Pack Erro_Pack Erro_Pack module~area_vrad_fle_mod->Erro_Pack Math_Pack Math_Pack module~area_vrad_fle_mod->Math_Pack netcdf netcdf module~area_vrad_fle_mod->netcdf module~pstat_parm_mod PStat_Parm_Mod module~area_vrad_fle_mod->module~pstat_parm_mod module~rad_le_mod->module~rand_pack module~rad_le_mod->Kind_Pack module~rand_pack->Kind_Pack module~pstat_parm_mod->Kind_Pack module~pstat_parm_mod->Erro_Pack

Used by

  • module~~area_vrad_fle_mod~~UsedByGraph module~area_vrad_fle_mod Area_VRad_FLE_Mod module~mcrt_pack Mcrt_Pack module~mcrt_pack->module~area_vrad_fle_mod program~mscart MSCART program~mscart->module~mcrt_pack

Contents


Variables

TypeVisibility AttributesNameInitial
character(len=*), private, parameter:: modName ='Area_VRad_FLE_Mod'

Derived Types

type, public, extends(Rad_LE_T) :: Area_VRad_FLE_T

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
integer(kind=kis), public :: npx
integer(kind=kis), public :: npy
real(kind=krs), public :: fpx
real(kind=krs), public :: fpy
real(kind=krs), public :: dpx
real(kind=krs), public :: dpy
real(kind=krs), public, allocatable:: PZps(:)
real(kind=krs), public, allocatable:: PVec(:,:)
real(kind=krs), public, allocatable:: Ppxy(:,:)
real(kind=krd), public, allocatable:: PRad(:,:,:,:)
real(kind=krd), public, allocatable:: MeanPRad(:,:,:,:)
real(kind=krd), public, allocatable:: RMSEPRad(:,:,:,:)
real(kind=krd), public, allocatable:: MeanPRadNth(:,:,:,:,:)
real(kind=krd), public, allocatable:: RMSEPRadNth(:,:,:,:,:)

Type-Bound Procedures

procedure, public :: init_Rad_LE => init_Area_VRad_FLE
procedure, public :: free_Rad_LE => free_Area_VRad_FLE
procedure, public :: init_ncfile
procedure, public :: estm_RadPsi => estm_Area_VRadPsi
procedure, public :: sum_RadPsi_OneBatch => sum_Area_VRad_FLE_RadPsi_OneBatch
procedure, public :: sum_RadPsi_AllBatch => sum_Area_VRad_FLE_RadPsi_AllBatch
procedure, public :: reset_RadPsi_OneBatch => reset_Area_VRad_FLE_PadPsi_OneBatch
procedure, public :: reset_RadPsi_AllBatch => reset_Area_VRad_FLE_PadPsi_AllBatch
procedure, public :: write_Rad_LE_result => write_Area_VRad_FLE_result
procedure, public :: write_Rad_LE_census => write_Area_VRad_FLE_census
procedure, public :: get_TgtDir

Functions

private function init_Area_VRad_FLE(this, prob, GeoGrd, SrcOPT, OutFile, err) result(istat)

initialize area-averaged radiance estimators for vector radiative transfer simulation with forward Monte Carlo algorithm

Arguments

Type IntentOptional AttributesName
class(Area_VRad_FLE_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)

private function free_Area_VRad_FLE(this, err) result(istat)

free memory of area-averaged radiance estimators for vector radiative transfer simulation with forward Monte Carlo algorithm

Arguments

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

Return Value integer(kind=kis)

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

initialize output results of area-averaged radiance estimators for vector radiative transfer simulation with forward Monte Carlo algorithm in NETCDF format

Arguments

Type IntentOptional AttributesName
class(Area_VRad_FLE_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)

private function write_Area_VRad_FLE_result(this, SrcOPT, ibat, nPho, Timing, err) result(istat)

write area-averaged radiance results of each batch simulation of vector radiative transfer using forward Monte Carlo algorithm in netcdf format

Arguments

Type IntentOptional AttributesName
class(Area_VRad_FLE_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)

private function write_Area_VRad_FLE_census(this, SrcOPT, nbat, nph, err) result(istat)

write area-averaged radiance results of all batch simulations of vector radiative transfer using forward Monte Carlo algorithm in netcdf format

Read more…

Arguments

Type IntentOptional AttributesName
class(Area_VRad_FLE_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)


Subroutines

private subroutine estm_Area_VRadPsi(this, itgt, photon, GeoGrd, AtmOPT, SrcOPT, istat, PFunTab, ftdcf, SfcOPT, pac)

estimate area-averaged radiance contributions for vector radiative transfer simulation using forward Monte Carlo algorithm

Read more…

Arguments

Type IntentOptional AttributesName
class(Area_VRad_FLE_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(:)

private subroutine diff_Area_VRadPsi(this, GeoGrd, AtmOPT, ixr, iyr, irdc, p, rnx, rny, x2, y2, iz, ichi)

distribute radiance contributions to adjecent areas using numerical diffusion technique for vector radiative transfer simulation with forward Monte Carlo algorithm

Arguments

Type IntentOptional AttributesName
class(Area_VRad_FLE_T), intent(inout) :: this
class(GeomGrid_T), intent(in) :: GeoGrd
class(AtmOPT_T), intent(in) :: AtmOPT
integer(kind=kis), intent(in) :: ixr
integer(kind=kis), intent(in) :: iyr
integer(kind=kis), intent(in) :: irdc
real(kind=krs), intent(inout) :: p(4)
real(kind=krs), intent(in) :: rnx
real(kind=krs), intent(in) :: rny
real(kind=krs), intent(in) :: x2
real(kind=krs), intent(in) :: y2
integer(kind=kis), intent(in) :: iz
integer(kind=kis), intent(in) :: ichi

private subroutine setup_RadDiffLUT1(ilut, ndlo, ndhi, npos, ngrd)

setup grid indices of horizontal diffusion region in viewing coordinate

Arguments

Type IntentOptional AttributesName
integer(kind=kis), intent(out) :: ilut(-ndlo:ndhi)
integer(kind=kis), intent(in) :: ndlo
integer(kind=kis), intent(in) :: ndhi
integer(kind=kis), intent(in) :: npos
integer(kind=kis), intent(in) :: ngrd

private subroutine setup_RadDiffLUT2(ilut, ndlo, ndhi, npos, ndiff, ngrd)

setup grid indices of horizontal diffusion region in atmospheric field coordinate

Arguments

Type IntentOptional AttributesName
integer(kind=kis), intent(out) :: ilut(-ndlo:ndhi)
integer(kind=kis), intent(in) :: ndlo
integer(kind=kis), intent(in) :: ndhi
real(kind=krs), intent(in) :: npos
real(kind=krs), intent(in) :: ndiff
integer(kind=kis), intent(in) :: ngrd

private subroutine sum_Area_VRad_FLE_RadPsi_OneBatch(this, SrcOPT, nPho, Timing)

normalize and accumulate area-averaged radiance of each batch simulation of vector radiative transfer using forward Monte Carlo algorithm

Arguments

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

private subroutine sum_Area_VRad_FLE_RadPsi_AllBatch(this, SrcOPT, nbat, nph)

accumulate area-averaged radiance of all batch simulations of vector radiative transfer using forward Monte Carlo algorithm

Arguments

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

private subroutine reset_Area_VRad_FLE_PadPsi_OneBatch(this)

reset all variables of area-averaged radiance estimators zeros for vector radiative transfer simulation with forward Monte Carlo algorithm

Arguments

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

private subroutine reset_Area_VRad_FLE_PadPsi_AllBatch(this)

reset all variables of area-averaged radiance estimators zeros for vector radiative transfer simulation with forward Monte Carlo algorithm

Arguments

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

private subroutine get_TgtDir(this, SrcOPT, photon)

get detector direction of current area-averaged radiance estimator for forward Monte Carlo simulation

Arguments

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