segment Derived Type

type, public, extends(ddeabm_class) :: segment

a ballistic segment in the mission

  • central body is the Moon (8x8 gravity), with Earth and Sun as third-bodies.
  • Inputs are: t0, tf', andx0_rotating`.
  • Output are: xf, xf_rotating

Inherits

type~~segment~~InheritsGraph type~segment segment ddeabm_class ddeabm_class type~segment->ddeabm_class geopotential_model_pines geopotential_model_pines type~segment->geopotential_model_pines grav jpl_ephemeris jpl_ephemeris type~segment->jpl_ephemeris eph type~segment_data segment_data type~segment->type~segment_data data, cached_data type~trajectory trajectory type~segment->type~trajectory traj_inertial, traj_rotating, traj_se_rotating

Inherited by

type~~segment~~InheritedByGraph type~segment segment type~mission_type mission_type type~mission_type->type~segment segs type~my_solver_type my_solver_type type~my_solver_type->type~mission_type mission

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: name

the segment name

type(segment_data), public :: data
type(segment_data), public :: cached_data

used when computing gradients

type(geopotential_model_pines), public, pointer :: grav => null()

central body geopotential model [global]

class(jpl_ephemeris), public, pointer :: eph => null()

the ephemeris [global]

logical, public :: pointmass_central_body = .false.
type(trajectory), public :: traj_inertial

in the inertial frame (j2000-moon)

type(trajectory), public :: traj_rotating

in the rotating frame (moon-earth, moon-centered)

type(trajectory), public :: traj_se_rotating

in the rotating frame (sun-earth, earth-centered)


Type-Bound Procedures

procedure, public :: set_input => set_segment_inputs

  • public subroutine set_segment_inputs(me, t0, tf, x0_rotating)

    Sets all the info in a segment for it to be propagated.

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(inout) :: me
    real(kind=wp), intent(in) :: t0

    [days]

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

    [days]

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

    state in rotating frame

procedure, public :: get_inputs => get_segment_inputs

  • public subroutine get_segment_inputs(me, t0, x0_rotating)

    Gets the initial states of a segment

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(in) :: me
    real(kind=wp), intent(out), optional :: t0
    real(kind=wp), intent(out), optional, dimension(6) :: x0_rotating

    rotating frame

procedure, public :: get_outputs => get_segment_outputs

  • public subroutine get_segment_outputs(me, xf, xf_rotating, x0_rotating)

    After propagating a segment, this gets the outputs.

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(in) :: me
    real(kind=wp), intent(out), optional, dimension(6) :: xf

    inertial frame

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

    rotating frame

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

procedure, public :: set_outputs => set_segment_outputs

  • public subroutine set_segment_outputs(me, xf, xf_rotating)

    Set the outputs of a segment, assuming it has been propagated elsewhere

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(inout) :: me
    real(kind=wp), intent(in), dimension(6) :: xf

    inertial frame

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

    inertial frame

procedure, public :: propagate => propagate_segment

  • public subroutine propagate_segment(me, mode, tstep)

    Propagate a segment (assumes the inputs have already been populated)

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(inout) :: me
    integer, intent(in), optional :: mode

    1 - don't report steps, 2 - report steps (for plotting)

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

    fixed time step for mode=2

procedure, public :: cache

  • public subroutine cache(me)

    Cache all the data in a segment.

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(inout) :: me

procedure, public :: uncache

  • public subroutine uncache(me)

    Restore all the segment data form the cache.

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(inout) :: me

procedure, public :: put_data_in_segment

  • public subroutine put_data_in_segment(me, d)

    Set all the data in a segment.

    Arguments

    Type IntentOptional Attributes Name
    class(segment), intent(inout) :: me
    type(segment_data), intent(in) :: d

Source Code

    type,extends(ddeabm_class)  :: segment

        !! a ballistic segment in the mission
        !!
        !! * central body is the Moon (8x8 gravity),
        !!   with Earth and Sun as third-bodies.
        !! * Inputs are: `t0`, `tf', and `x0_rotating`.
        !! * Output are: `xf`, `xf_rotating`

        character(len=:),allocatable :: name  !! the segment name

        type(segment_data) :: data
        type(segment_data) :: cached_data  !! used when computing gradients

        ! These can be pointers that are pointing to the global ones in the mission,
        ! Or, when using OpenMP, they are allocated in each segment.
        type(geopotential_model_pines),pointer :: grav => null() !! central body geopotential model [global]
        class(jpl_ephemeris),pointer :: eph => null()  !! the ephemeris [global]
        logical :: pointmass_central_body = .false.

        ! for saving the trajectory for plotting:
        type(trajectory) :: traj_inertial  !! in the inertial frame (j2000-moon)
        type(trajectory) :: traj_rotating  !! in the rotating frame (moon-earth, moon-centered)
        type(trajectory) :: traj_se_rotating  !! in the rotating frame (sun-earth, earth-centered)

        contains

        procedure,public :: set_input   => set_segment_inputs
        procedure,public :: get_inputs  => get_segment_inputs
        procedure,public :: get_outputs => get_segment_outputs
        procedure,public :: set_outputs => set_segment_outputs
        procedure,public :: propagate   => propagate_segment

        procedure :: cache
        procedure :: uncache
        procedure :: put_data_in_segment

    end type segment