propagate_segment Subroutine

public subroutine propagate_segment(me, mode, tstep)

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

Type Bound

segment

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


Calls

proc~~propagate_segment~~CallsGraph proc~propagate_segment segment%propagate_segment first_call first_call proc~propagate_segment->first_call icrf_frame icrf_frame proc~propagate_segment->icrf_frame integrate integrate proc~propagate_segment->integrate proc~set_segment_outputs segment%set_segment_outputs proc~propagate_segment->proc~set_segment_outputs transform transform proc~propagate_segment->transform two_body_rotating_frame two_body_rotating_frame proc~propagate_segment->two_body_rotating_frame

Called by

proc~~propagate_segment~~CalledByGraph proc~propagate_segment segment%propagate_segment proc~constraint_violations mission_type%constraint_violations proc~constraint_violations->proc~propagate_segment proc~export_trajectory_json_file mission_type%export_trajectory_json_file proc~export_trajectory_json_file->proc~propagate_segment proc~generate_eclipse_data mission_type%generate_eclipse_data proc~generate_eclipse_data->proc~propagate_segment proc~plot_trajectory mission_type%plot_trajectory proc~plot_trajectory->proc~propagate_segment proc~halo_solver_main halo_solver_main proc~halo_solver_main->proc~constraint_violations proc~halo_solver_main->proc~export_trajectory_json_file proc~halo_solver_main->proc~generate_eclipse_data proc~halo_solver_main->proc~plot_trajectory

Source Code

    subroutine propagate_segment(me,mode,tstep)

    implicit none

    class(segment),intent(inout) :: me
    integer,intent(in),optional :: mode  !! 1 - don't report steps, 2 - report steps (for plotting)
    real(wp),intent(in),optional :: tstep !! fixed time step for mode=2

    integer  :: idid
    real(wp) :: t
    real(wp) :: tf
    real(wp),dimension(6) :: x
    type(icrf_frame) :: inertial
    type(two_body_rotating_frame) :: rotating
    real(wp) :: etf
    real(wp),dimension(6) :: xf !! inertial - from the propagation
    real(wp),dimension(6) :: xf_rotating
    logical :: status_ok
    integer :: integration_mode

    if (present(mode)) then
        integration_mode = mode
    else
        integration_mode = 1
    end if

    t  = me%data%t0 * day2sec  ! initial time in seconds from epoch
    tf = me%data%tf * day2sec  ! final time in seconds from epoch
    x  = me%data%x0   ! inertial state

    !write(*,*) ''
    !write(*,*) 'propagate segment '//me%name, t0, tf
    !write(*,*) 't0:',t0
    !write(*,'(A,*(F15.3,1X))') 'x0:',x
    !write(*,*) 'tf:',tf

    call me%first_call()  !restarting the integration
    if (present(tstep)) then
        call me%integrate(t,x,tf,idid=idid,integration_mode=integration_mode,tstep=tstep)
    else
        call me%integrate(t,x,tf,idid=idid,integration_mode=integration_mode)
    end if
    if (idid<0) then
        write(*,'(A,*(I5/))')    'idid: ',idid
        error stop 'error in integrator'
    end if

    xf = x  ! final state [inertial frame]

    ! also save the rotating frame state at tf (to compute the constraint violations):
    etf = me%data%et_ref + tf  ! convert to ephemeris time [sec]
    inertial = icrf_frame(b=body_moon)
    rotating = two_body_rotating_frame(primary_body=body_earth,&
                                       secondary_body=body_moon,&
                                       center=center_at_secondary_body,&
                                       et=etf)

    ! from inertial to rotating:
    call inertial%transform(x,rotating,etf,me%eph,xf_rotating,status_ok)
    if (.not. status_ok) error stop 'transformation error in propagate_segment'

    ! put final states in the segment:
    call me%set_outputs(xf,xf_rotating)

    end subroutine propagate_segment