lighting_module Module

Routines for computing solar fraction, lighting, eclipses, etc.


Uses

  • module~~lighting_module~~UsesGraph module~lighting_module lighting_module module~celestial_body_module celestial_body_module module~lighting_module->module~celestial_body_module module~conversion_module conversion_module module~lighting_module->module~conversion_module module~ephemeris_module ephemeris_module module~lighting_module->module~ephemeris_module module~kind_module kind_module module~lighting_module->module~kind_module module~math_module math_module module~lighting_module->module~math_module module~numbers_module numbers_module module~lighting_module->module~numbers_module module~transformation_module transformation_module module~lighting_module->module~transformation_module module~vector_module vector_module module~lighting_module->module~vector_module module~celestial_body_module->module~kind_module module~celestial_body_module->module~numbers_module module~base_class_module base_class_module module~celestial_body_module->module~base_class_module module~conversion_module->module~kind_module module~conversion_module->module~numbers_module module~ephemeris_module->module~celestial_body_module module~ephemeris_module->module~kind_module iso_fortran_env iso_fortran_env module~kind_module->iso_fortran_env module~math_module->module~kind_module module~math_module->module~numbers_module module~numbers_module->module~kind_module module~transformation_module->module~celestial_body_module module~transformation_module->module~ephemeris_module module~transformation_module->module~kind_module module~transformation_module->module~numbers_module module~transformation_module->module~vector_module module~transformation_module->iso_fortran_env module~iau_orientation_module iau_orientation_module module~transformation_module->module~iau_orientation_module module~time_module time_module module~transformation_module->module~time_module module~vector_module->module~kind_module module~vector_module->module~numbers_module module~iau_orientation_module->module~conversion_module module~iau_orientation_module->module~kind_module module~iau_orientation_module->module~numbers_module module~time_module->module~kind_module

Used by

  • module~~lighting_module~~UsedByGraph module~lighting_module lighting_module module~fortran_astrodynamics_toolkit fortran_astrodynamics_toolkit module~fortran_astrodynamics_toolkit->module~lighting_module

Functions

public function solar_radiation_pressure(area, cr, r_sc_sun, sunfrac) result(srp)

Compute the solar radiation pressure force vector on a spacecraft.

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: area

cross-sectional area of spacecraft [m^2]

real(kind=wp), intent(in) :: cr

coefficient of reflectivity

real(kind=wp), intent(in), dimension(3) :: r_sc_sun

vector from spacecraft to sun [km]

real(kind=wp), intent(in) :: sunfrac

sun fraction [0=total eclipse, 1=no eclipse]

Return Value real(kind=wp), dimension(3)

solar radiation pressure force vector [N]

public function get_sun_fraction(b, rad_body, rad_sun, eph, et, rv, model, rbubble, use_geometric, info) result(phi)

Compute the "sun fraction" using the selected shadow model.

Arguments

Type IntentOptional Attributes Name
type(celestial_body), intent(in) :: b

eclipsing body

real(kind=wp), intent(in) :: rad_body

radius of the eclipsing body [km]

real(kind=wp), intent(in) :: rad_sun

radius of the Sun [km]

class(ephemeris_class), intent(inout) :: eph

the ephemeris to use for sun and ssb (if necessary)

real(kind=wp), intent(in) :: et

observer ephemeris time (sec)

real(kind=wp), intent(in), dimension(6) :: rv

state of the spacecraft (j2000-body frame)

integer, intent(in) :: model

algorithm to use:

Read more…
real(kind=wp), intent(in) :: rbubble

eclipse bubble [km]. see the reference. if rbubble=0, then no bubble is used. only used if model=1

logical, intent(in), optional :: use_geometric

if true, use geometric positions (no light time or stellar aberration correction) default = false

character(len=:), intent(out), optional, allocatable :: info

info string

Return Value real(kind=wp)

solar fraction returned:

  • if model=1, circular cubic sun frac value:
    • >0 no eclipse
    • <0 eclipse
    • =0 on the eclipse line
  • if model=2, true solar fraction value [0=total eclipse, 1=no eclipse], with model of umbra/penumbra/antumbra (Wertz, 1978)
  • if model=3, alternate version of solar fraction (Montenbruck and Gill)
  • if model=4, alternate version of solar fraction (nyxspace)

Subroutines

public subroutine solar_fraction(d_s, rs, d_p, rp, fraction, info)

Compute the solar fraction visible due to an eclipse by another body.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in), dimension(3) :: d_s

vector from the spacecraft to the Sun

real(kind=wp), intent(in) :: rs

radius of the Sun

real(kind=wp), intent(in), dimension(3) :: d_p

vector from the spacecraft to the planet

real(kind=wp), intent(in) :: rp

radius of the planet

real(kind=wp), intent(out) :: fraction

fraction of the Sun visible [0=total eclipse, 1=no eclipse]

character(len=:), intent(out), optional, allocatable :: info

info string

public subroutine from_j2000body_to_j2000ssb(b, eph, et, rv, rv_ssb)

convert from a j2000-body frame to a j2000-ssb frame.

Arguments

Type IntentOptional Attributes Name
type(celestial_body), intent(in) :: b

eclipsing body

class(ephemeris_class), intent(inout) :: eph

the ephemeris to use for body and ssb

real(kind=wp), intent(in) :: et

ephemeris time (sec)

real(kind=wp), intent(in), dimension(6) :: rv

j2000-body state (km, km/s)

real(kind=wp), intent(out), dimension(6) :: rv_ssb

j2000-ssb state (km, km/s)

public subroutine apparent_position(eph, b_target, et, rv_obs_ssb, r_target, status_ok)

Return the position of a target body relative to an observer, corrected for light time and stellar aberration.

Read more…

Arguments

Type IntentOptional Attributes Name
class(ephemeris_class), intent(inout) :: eph

the ephemeris

type(celestial_body), intent(in) :: b_target

target body

real(kind=wp), intent(in) :: et

observer ephemeris time (sec)

real(kind=wp), intent(in), dimension(6) :: rv_obs_ssb

state of the observer (j2000 frame w.r.t. solar system barycenter)

real(kind=wp), intent(out), dimension(3) :: r_target

apparant state of the target (j2000 frame) Corrected for one-way light time and stellar aberration

logical, intent(out) :: status_ok

true if no problems

public subroutine cubic_shadow_model(rsun, radsun, rplanet, radplanet, sunfrac, rbubble)

The "circular cubic" shadow model.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in), dimension(3) :: rsun

apparent position vector of sun wrt spacecraft [km]

real(kind=wp), intent(in) :: radsun

radius of sun [km]

real(kind=wp), intent(in), dimension(3) :: rplanet

apparent position vector of eclipsing body wrt spacecraft [km]

real(kind=wp), intent(in) :: radplanet

radius of the eclipsing body [km]

real(kind=wp), intent(out) :: sunfrac

value of the function (>0 no eclipse, <0 eclipse, =0 on the shadow line)

real(kind=wp), intent(in), optional :: rbubble

eclipse bubble radius. if present, then sunfrac is the value along an arc length of rbubble in the direction of the max eclipse line.

public subroutine solar_fraction_alt(d_s, rs, d_p, rp, percentsun, info)

Another eclipse model, using circular area assumptions.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in), dimension(3) :: d_s

vector from the spacecraft to the Sun

real(kind=wp), intent(in) :: rs

radius of the Sun

real(kind=wp), intent(in), dimension(3) :: d_p

vector from the spacecraft to the planet

real(kind=wp), intent(in) :: rp

radius of the planet

real(kind=wp), intent(out) :: percentsun

fraction of the Sun visible [0=total eclipse, 1=no eclipse]

character(len=:), intent(out), optional, allocatable :: info

info string

public subroutine solar_fraction_alt2(r_l, Rl, r_e, Re, percentsun, info)

Another eclipse model, using circular area assumptions, coded up based on the nixspace documentation. The results are very similar to solar_fraction_alt.

Read more…

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in), dimension(3) :: r_l

vector from the spacecraft to the Sun

real(kind=wp), intent(in) :: Rl

radius of the Sun

real(kind=wp), intent(in), dimension(3) :: r_e

vector from the spacecraft to the planet

real(kind=wp), intent(in) :: Re

radius of the planet

real(kind=wp), intent(out) :: percentsun

fraction of the Sun visible [0=total eclipse, 1=no eclipse]

character(len=:), intent(out), optional, allocatable :: info

info string

public subroutine lighting_module_test()

Unit tests for the listing module.

Arguments

None