Commit d821e7d5 authored by Claire Dross's avatar Claire Dross

Layer2_MMS_SW_SPARK: Split functional behavior of F_MM in distinct parts

parent 0b6802ab
......@@ -30,7 +30,7 @@ ACTIVITIES:
2 - Review of the specification for translatability in Ada contracts:
* Design:
Each component provides a Run procedure located in a child package Comp.Behavior. This procedure is responsible from updating the internal state of the component at each step. Scheduling, as well as handling of inputs and outputs are not considered here. The procedure Run may have a contract, representing the part of its behavioural specification which is translatable into Ada contracts. Contracts from the specification document are stored in a distinct unit, named Comp.Behavior.Guarantees. Parts of specification contracts and of functional behaviours which are not fit for translation into SPARK contracts will be listed here.
Each component provides one or more procedures located in a child package Comp.Behavior. They are responsible of updating the internal state of the component at each step. Scheduling is not considered here. These procedures may have a contract, representing the part of behavioural specification of the component which is translatable into Ada contracts. Contracts from the specification document are translated as Ada contracts of a Run procedure located in a distinct unit, named Comp.Behavior.Guarantees. Parts of specification contracts and of functional behaviours which are not fit for translation into SPARK contracts will be listed here.
* Report for translatability into Ada contracts:
- MMS.F_PT.F_MM:
......@@ -55,7 +55,7 @@ ACTIVITIES:
Assumptions A. B, C, E: Not translated (linked with AV's electrical and mechanical behavior)
6.9.3.2:
Guarantees A, B: Not translated
Guaranted C: Not translated (arbitration has been moved from F_CM)
Guarantee C: Translated as a postcondition on F_MM.Behavior.garantees.Run (arbitration has been moved to F_MM).
- MMS.F_EL:
7.3.2:
......@@ -63,6 +63,6 @@ ACTIVITIES:
* Verifications:
The SPARK toolset can be used to check that:
- Ada contracts are consistent. If it is a case by case contract, SPARK can check that all cases are covered and that no two cases can apply to the same inputs. If some properties or some information can only be checked in some cases, these cases can be expressed as preconditions on property or information functions and SPARK will check that they are always used in valid context.
- Ada contracts are consistent. If it is a case by case contract, SPARK can check that all cases are covered and that no two cases can apply to the same inputs. If some properties or some information can only be accessed in some cases, these cases can be expressed as preconditions on property or information functions and SPARK will check that they are always used in valid context.
- Guarantees are implied by the behavioral specification. If both can be expressed as Ada contracts, SPARK can check that, if the behavioural specification of a component is respected by its implementation, then the implementation will also respect the guarantees as stated in the specification contracts.
- Guarantees are implied by the behavioral specification. If both can be expressed as Ada contracts, SPARK can check that, if the behavioural specification of a component is respected by its implementation, then the implementation will also respect the guarantees as stated in the specification contracts. For this, a body has to be provided for Behavior.garantees.Run, calling explicitely the procedures declared in Behavior in a meaningful order.
......@@ -15,10 +15,10 @@ package MMS.F_PT.F_FC.Behavior.Guarantees with SPARK_Mode is
range BRAKING .. WAITING_PROP;
function Engine_State_In_Braking return Boolean is
(Mission_State = RUNNING and then Engine_State in Braking_State_Type);
(Mission_State = FLIGHT and then Engine_State in Braking_State_Type);
function Engine_State_In_Propulsion return Boolean is
(Mission_State = RUNNING and then Engine_State in Propulsion_State_Type);
(Mission_State = FLIGHT and then Engine_State in Propulsion_State_Type);
-----------------------------------
-- High-Level Garantees for F_FC --
......
......@@ -19,7 +19,7 @@ package MMS.F_PT.F_FC.Behavior with SPARK_Mode is
function Start_Landing return Boolean with
Global => Private_State,
Pre => Mission_State = RUNNING;
Pre => Mission_State = FLIGHT;
function Operating_Point return Operating_Point_Type with
Global => Private_State;
......@@ -41,21 +41,21 @@ package MMS.F_PT.F_FC.Behavior with SPARK_Mode is
-- States --
------------
type Mission_State_Type is (INIT, RUNNING, ABORTED, COMPLETE);
type Mission_State_Type is (INIT, FLIGHT, LANDING, ABORTED, COMPLETE);
function Mission_State return Mission_State_Type with
Global => Private_State;
function Flight_Phase_State return Flight_Phase_Type with
Global => Private_State,
Pre => Mission_State = RUNNING;
Pre => Mission_State = FLIGHT;
type Engine_State_Type is
(PROPULSION, WAITING_BRAK, BRAKING, WAITING_PROP);
function Engine_State return Engine_State_Type with
Global => Private_State,
Pre => Mission_State = RUNNING;
Pre => Mission_State = FLIGHT;
----------------
-- Properties --
......@@ -75,20 +75,30 @@ package MMS.F_PT.F_FC.Behavior with SPARK_Mode is
when DESCENT =>
Q_Dot in MMS.F_PT.F_FC.Data.Qdot_MinDs .. MMS.F_PT.F_FC.Data.Qdot_MaxDs
and Q < MMS.F_PT.F_FC.Data.Q_MaxDs)
with Pre => Mission_State = RUNNING;
with Pre => Mission_State = FLIGHT;
function Time_Since_In_Safety_Escape return Time_Type with
Global => Private_State,
Pre => (Mission_State = RUNNING and then not In_Safety_Envelope)
Pre => (Mission_State = FLIGHT and then not In_Safety_Envelope)
or else Mission_State = ABORTED;
function Fast_Evolving_Safety_Escape return Boolean with
Global => Private_State,
Pre => Mission_State = RUNNING and then not In_Safety_Envelope;
Pre => Mission_State = FLIGHT and then not In_Safety_Envelope;
function Time_Since_Stopped return Time_Type with
Global => Private_State,
Pre => Mission_State = RUNNING;
Pre => Mission_State = FLIGHT;
-------------
-- Outputs --
-------------
function Propulsion_Torque return Torque_Type with
Global => Private_State;
function Braking_Torque return Torque_Type with
Global => Private_State;
---------------------------------------
-- Behavioural Specification of F_FC --
......@@ -115,7 +125,7 @@ package MMS.F_PT.F_FC.Behavior with SPARK_Mode is
(Mission_State = INIT
and then Start_Take_Off
=>
Mission_State = RUNNING
Mission_State = FLIGHT
and then Engine_State = PROPULSION,
Mission_State = INIT
......@@ -123,17 +133,23 @@ package MMS.F_PT.F_FC.Behavior with SPARK_Mode is
=>
Mission_State = INIT,
Mission_State = RUNNING
Mission_State = FLIGHT
and then Start_Landing
=>
Mission_State = COMPLETE,
Mission_State = LANDING,
Mission_State = RUNNING
Mission_State = FLIGHT
and then not Start_Landing
=>
(if Time_Since_In_Safety_Escape > MMS.F_PT.F_FC.Data.Escape_Time then
Mission_State = ABORTED
else Mission_State = RUNNING),
else Mission_State = FLIGHT),
Mission_State = LANDING
=>
(if P_Dot = 0.0 and then Q_Dot = 0.0 then
Mission_State = COMPLETE
else Mission_State = LANDING),
(Mission_State in COMPLETE | ABORTED)
=>
......@@ -158,7 +174,7 @@ package MMS.F_PT.F_FC.Behavior with SPARK_Mode is
-- 6.7.4 Propulsion braking mutual exclusion
and then
(if Mission_State = RUNNING and then Mission_State'Old = RUNNING then
(if Mission_State = FLIGHT and then Mission_State'Old = FLIGHT then
(case Engine_State'Old is
when PROPULSION =>
(if not In_Safety_Envelope
......@@ -191,6 +207,13 @@ package MMS.F_PT.F_FC.Behavior with SPARK_Mode is
elsif Time_Since_Stopped > MMS.F_PT.F_FC.Data.Commutation_Duration
then Engine_State = BRAKING
else Engine_State = WAITING_BRAK
and then Time_Since_Stopped > Time_Since_Stopped'Old)));
and then Time_Since_Stopped > Time_Since_Stopped'Old)))
and then
(if Mission_State = FLIGHT and then Engine_State /= PROPULSION then
Propulsion_Torque = 0.0)
and then
(if Mission_State = FLIGHT and then Engine_State /= BRAKING then
Braking_Torque = 0.0);
end MMS.F_PT.F_FC.Behavior;
......@@ -2,9 +2,67 @@ with Types; use Types;
package body MMS.F_PT.F_MM.Behavior.Guarantees with SPARK_Mode is
Initial_Energy_Test_Done : Boolean with Ghost;
In_Flight_Energy_Test_Done : Boolean with Ghost;
Energy_Test_Succeded : Boolean with Ghost;
function Initial_Energy_Test_Succeeded return Boolean is
(Initial_Energy_Test_Done and then Energy_Test_Succeded);
function In_Flight_Energy_Test_Failed return Boolean is
(In_Flight_Energy_Test_Done and then not Energy_Test_Succeded);
procedure Run is
begin
MMS.F_PT.F_MM.Behavior.Run;
Initial_Energy_Test_Done := False;
In_Flight_Energy_Test_Done := False;
Energy_Test_Succeded := False;
Read_Inputs;
if Power_On then
Management_Of_Navigation_Modes_Options_Parameters;
if Power_State = On then
if On_State in INIT | RUNNING
and then Mission_Parameters_Defined
then
Operating_Point_Update_Management;
end if;
if (On_State = RUNNING
and then Running_State = FLIGHT
and then Current_Flight_Phase = CRUISE)
or else
(On_State = INIT
and then Init_Completed)
then
Mission_Viability_Logic;
if On_State = RUNNING then
In_Flight_Mission_Viability_Logic;
In_Flight_Energy_Test_Done := True;
Energy_Test_Succeded :=
In_Flight_Energy_Compatible_With_Mission;
else
Initial_Mission_Viability_Logic;
Initial_Energy_Test_Done := True;
Energy_Test_Succeded :=
Initial_Energy_Compatible_With_Mission;
end if;
elsif On_State = RUNNING
and then Running_State = FLIGHT
and then Current_Flight_Phase = DESCENT
then
Mission_Termination_Control;
end if;
end if;
end if;
Update_States;
Write_Outputs;
end Run;
end MMS.F_PT.F_MM.Behavior.Guarantees;
-- This package provides a wrapper above MMS.F_PT.F_MM.Behavior.Run which
-- is used to verify in SPARK that high level guarantees on F_MM are implied
-- by its behavioural specification.
-- This package provides a Run procedure which simulates execution of the
-- main loop of F_MM and is used to verify in SPARK that high level guarantees
-- on F_MM are implied by its behavioural specification.
with Types; use Types;
......@@ -14,11 +14,13 @@ package MMS.F_PT.F_MM.Behavior.Guarantees with SPARK_Mode is
function In_Take_Off_State return Boolean is
(Power_State = On
and then On_State = RUNNING
and then Running_State = TAKE_OFF);
and then Running_State = TAKE_OFF)
with Global => Private_State;
function Mission_Aborted return Boolean is
(Power_State = On
and then On_State = ABORTED);
and then On_State = ABORTED)
with Global => Private_State;
function Mission_Cancelled return Boolean is
(Power_State = On
......@@ -26,6 +28,10 @@ package MMS.F_PT.F_MM.Behavior.Guarantees with SPARK_Mode is
and then Init_State = CANCELLED)
with Global => Private_State;
function Initial_Energy_Test_Succeeded return Boolean with Ghost;
function In_Flight_Energy_Test_Failed return Boolean with Ghost;
-----------------------------------
-- High-Level Garantees for F_MM --
-----------------------------------
......@@ -37,16 +43,14 @@ package MMS.F_PT.F_MM.Behavior.Guarantees with SPARK_Mode is
-- incompatible with mission completion.
(if In_Take_Off_State and then not In_Take_Off_State'Old then
Initial_Energy_Compatible_With_Mission)
Initial_Energy_Test_Succeeded)
-- 6.6.3.B Any mission cancellation is signaled to CP and GS.
and then
(if Mission_Aborted and then not Mission_Aborted'Old then
Mission_Aborted_Signaled)
(if Mission_Aborted then Mission_Aborted_Signaled)
and then
(if Mission_Cancelled and then not Mission_Cancelled'Old then
Mission_Cancelled_Signaled)
(if Mission_Cancelled then Mission_Cancelled_Signaled)
-- 6.6.3.2.A Missions cancelled for energy reasons can be proven
-- infeasible.
......@@ -54,6 +58,18 @@ package MMS.F_PT.F_MM.Behavior.Guarantees with SPARK_Mode is
and then
(if Mission_Aborted and then not Mission_Aborted'Old
and then Aborted_For_Energy_Reasons
then not In_Flight_Energy_Compatible_With_Mission);
then In_Flight_Energy_Test_Failed)
-- 6.9.3.2.C When A mode is set on CP, the navigation options/parameters
-- are that of USB key or initialization is not complete.
and then
(if Power_On
and then Navigation_Mode_From_CP = A
and then Mission_Parameters_Defined
then
USB_Key_Present
and then Operating_Mode = Operating_Mode_From_CP
and then Navigation_Parameters = Navigation_Parameters_From_USB_Key);
end MMS.F_PT.F_MM.Behavior.Guarantees;
......@@ -24,186 +24,191 @@ package MMS.F_PT.F_MM.Behavior with SPARK_Mode is
function Power_On return Boolean;
function Payload_Bay_Closed return Boolean with
Pre => Power_State = ON
and then On_State = INIT;
Pre => Power_On;
function Payload_Mass_Given return Boolean with
Pre => Power_State = ON;
Pre => Power_On;
-- ??? Should we assume that Payload_Mass is always given after takeoff?
-- same question for usb key
function Payload_Mass return Payload_Mass_Type with
Pre => Power_State = ON;
Pre => Power_On;
function Navigation_Mode_From_CP return Navigation_Mode_Type;
function Navigation_Mode_From_CP return Navigation_Mode_Type with
Pre => Power_On;
function Navigation_Mode_From_GS_Received return Boolean;
function Navigation_Mode_From_GS_Received return Boolean with
Pre => Power_On;
function Navigation_Mode_From_GS return Navigation_Mode_Type with
Pre => Navigation_Mode_From_GS_Received;
Pre => Power_On and then Navigation_Mode_From_GS_Received;
function Operating_Mode_From_CP return Navigation_Option_Type;
function Operating_Mode_From_CP return Navigation_Option_Type with
Pre => Power_On;
function Operating_Mode_From_GS_Received return Boolean;
function Operating_Mode_From_GS_Received return Boolean with
Pre => Power_On;
function Operating_Mode_From_GS return Navigation_Option_Type with
Pre => Operating_Mode_From_GS_Received;
Pre => Power_On and then Operating_Mode_From_GS_Received;
function Navigation_Parameters_From_GS_Received return Boolean;
function Navigation_Parameters_From_GS_Received return Boolean with
Pre => Power_On;
function Navigation_Parameters_From_GS return Navigation_Parameters_Type with
Pre => Navigation_Parameters_From_GS_Received;
Pre => Power_On and then Navigation_Parameters_From_GS_Received;
function USB_Key_Present return Boolean;
function USB_Key_Present return Boolean with
Pre => Power_On;
function Navigation_Parameters_From_USB_Key return Navigation_Parameters_Type
with
Pre => USB_Key_Present;
Pre => Power_On and then USB_Key_Present;
function Mission_Abort_Received return Boolean with
Pre => Power_State = ON;
Pre => Power_On;
function Start_Or_Go_Received return Boolean with
Pre => Power_State = ON
and then On_State = INIT;
Pre => Power_On;
function Current_Range return Current_Range_Type;
function Current_Range return Current_Range_Type with
Pre => Power_On;
function Current_Speed return Current_Speed_Type;
function Current_Speed return Current_Speed_Type with
Pre => Power_On;
function Current_Altitude return Current_Altitude_Type;
function Current_Altitude return Current_Altitude_Type with
Pre => Power_On;
function Current_Flight_Phase return Flight_Phase_Type with
Pre => Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT;
Pre => Power_On;
function Energy_Level return Energy_Level_Type with
Pre => Power_State = ON;
Pre => Power_On;
function Mission_Parameters_Defined return Boolean is
(USB_Key_Present
or else (Navigation_Mode_From_CP = RP
and then Navigation_Parameters_From_GS_Received));
and then Navigation_Parameters_From_GS_Received))
with
Pre => Power_On;
function Init_Completed return Boolean is
(Payload_Bay_Closed
and then Payload_Mass_Given
and then Mission_Parameters_Defined)
with
Pre => Power_State = ON
and then On_State = INIT;
Pre => Power_On;
-----------------------------------------
-- States of the automaton in Figure 3 --
-----------------------------------------
type Power_State_Type is (ON, OFF);
function Power_State return Power_State_Type with
Global => Private_State;
type On_State_Type is (INIT, RUNNING, COMPLETE, ABORTED);
function Power_State return Power_State_Type;
function On_State return On_State_Type with
Global => Private_State,
Pre => Power_State = ON;
type Running_State_Type is (TAKE_OFF, FLIGHT, LANDING);
function Running_State return Running_State_Type with
Global => Private_State,
Pre => Power_State = ON
and then On_State = RUNNING;
type Init_State_Type is (PREPARATION, READY, CANCELLED);
function Init_State return Init_State_Type with
Global => Private_State,
Pre => Power_State = ON
and then On_State = INIT;
function Aborted_For_Energy_Reasons return Boolean with
Pre => Power_State = ON
and then On_State = ABORTED;
-----------------------------
-- Properties and Entities --
-----------------------------
function Power_Off return Boolean is (not Power_On);
function Take_Off_Over return Boolean with
Global => Private_State,
Pre => Power_State = ON
and then On_State = RUNNING
and then Running_State = TAKE_OFF;
function Navigation_Mode return Navigation_Mode_Type with
Pre => Power_On;
function Descent_Over return Boolean with
Global => Private_State,
Pre => Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT;
function Operating_Mode return Navigation_Option_Type with
Pre => Power_On;
function Landed return Boolean is
(Current_Speed = 0 and Current_Altitude = 0)
with
Pre => Power_State = ON
and then On_State = RUNNING
and then Running_State = LANDING;
function Navigation_Parameters return Navigation_Parameters_Type
with Pre => Power_On
and then Mission_Parameters_Defined;
function Mission_Range_From_Navigation_Parameters
return Current_Range_Type
with Pre => Mission_Parameters_Defined;
-- Fetch distance from State.Navigation_Parameters and do the appropriate
with Global =>
(Input => Operating_Point_State, Proof_In => Input_State),
Pre => Power_On
and then Mission_Parameters_Defined;
-- Fetch distance from Navigation_Parameters and do the appropriate
-- conversion.
function Operating_Point_From_Navigation_Parameters
return Operating_Point_Type
with Pre => Mission_Parameters_Defined;
-- Fetch altitude and speed from State.Navigation_Parameters and do the
with Global =>
(Input => Operating_Point_State, Proof_In => Input_State),
Pre => Power_On
and then Mission_Parameters_Defined;
-- Fetch altitude and speed from Navigation_Parameters and do the
-- appropriate conversions.
function Navigation_Mode return Navigation_Mode_Type with
Global => Private_State,
Pre => Power_State = ON
and then On_State in INIT | RUNNING;
function Mission_Range return Current_Range_Type with
Pre => Power_On
and then Power_State = On
and then On_State in INIT | RUNNING
and then Mission_Parameters_Defined;
function Operating_Mode return Navigation_Option_Type with
Global => Private_State,
Pre => Power_State = ON
function Operating_Point return Operating_Point_Type with
Pre => Power_On
and then Power_State = On
and then On_State in INIT | RUNNING
and then Mission_Parameters_Defined;
function Initial_Energy_Compatible_With_Mission return Boolean
with
Pre => Power_On
and then Power_State = ON
and then On_State = INIT
and then Init_Completed;
function In_Flight_Energy_Compatible_With_Mission return Boolean
with
Pre => Power_On
and then Power_State = ON
and then On_State = RUNNING
and then Navigation_Mode = RP;
and then Running_State = FLIGHT
and then Current_Flight_Phase = CRUISE;
function Initial_Energy_Compatible_With_Mission return Boolean with
Global => Private_State;
function Take_Off_Over return Boolean with
Pre => Power_On
and then Power_State = ON
and then On_State = RUNNING
and then Running_State = TAKE_OFF;
function In_Flight_Energy_Compatible_With_Mission return Boolean with
Global => Private_State;
function Descent_Over return Boolean with
Pre => Power_On
and then Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT
and then Current_Flight_Phase = DESCENT;
function Emergency_Landing return Boolean is
(On_State = ABORTED)
function Landed return Boolean is
(Current_Speed = 0 and Current_Altitude = 0)
with
Global => Private_State,
Pre => Power_State = ON;
function Mission_Range return Current_Range_Type with
Global => (Input => Private_State, Proof_In => Input_State),
Pre => Mission_Parameters_Defined;
Pre => Power_On
and then Power_State = ON
and then On_State = RUNNING
and then Running_State = LANDING;
function Operating_Point return Operating_Point_Type with
Global => (Input => Private_State, Proof_In => Input_State),
Pre => Mission_Parameters_Defined;
function Emergency_Landing return Boolean with
Global => Output_State;
function Mission_Aborted_Signaled return Boolean with
Global => Private_State,
Pre => Power_State = ON;
Global => Output_State;
function Mission_Cancelled_Signaled return Boolean with
Global => Private_State,
Pre => Power_State = ON
and then On_State = INIT;
function Aborted_For_Energy_Reasons return Boolean with
Global => Private_State,
Pre => Power_State = ON
and then On_State = ABORTED;
Global => Output_State;
---------------------------------------
-- Behavioural Specification of F_MM --
......@@ -217,44 +222,305 @@ package MMS.F_PT.F_MM.Behavior with SPARK_Mode is
procedure Write_Outputs with
-- Compute values of outputs from the current state
Global => (Input => Private_State,
Output => Output_State);
Output => Output_State),
Post =>
(if Power_State = ON and then On_State = ABORTED then
Emergency_Landing
and then Mission_Aborted_Signaled)
and then
(if Power_State = ON
and then On_State = INIT
and then Init_State = CANCELLED
then Mission_Cancelled_Signaled);
procedure Run with
-- Do:
-- - Compute the new state of the automaton
-------------------
-- Tasks of F_MM --
-------------------
Global => (In_Out => Private_State, Input => Input_State),
Post =>
------------------------------------------------------------
-- Management of Navigation Modes / Options / Parameters --
------------------------------------------------------------
-- RP mode enables modification of range parameter before take-off.
procedure Management_Of_Navigation_Modes_Options_Parameters with
-- Compute the value of Navigation_Mode / Options / Parameters (see 6.9.4)
(if not (Power_State'Old = ON
and then On_State'Old = INIT
and then Navigation_Mode'Old = RP)
then Mission_Range = Mission_Range'Old
elsif Mission_Parameters_Defined
then Mission_Range = Mission_Range_From_Navigation_Parameters)
Global => (Input => (Input_State, Private_State),
Output => Navigation_Parameter_State),
Pre => Power_On,
Post => Navigation_Mode =
-- RP mode enables modification of altitude and speed parameters at any
-- time (but not at landing, it is frozen...).
-- In case of conflict on the navigation mode, CP prevails over GS.
and then
(if (Power_State'Old = ON
and then On_State'Old in INIT | RUNNING
and then Navigation_Mode'Old = A)
then Operating_Point = Operating_Point'Old)
(if Navigation_Mode_From_CP = A
or else not Navigation_Mode_From_GS_Received
then Navigation_Mode_From_CP
-- The operating point is frozen once landing is activated.
-- If CP states the mode to RC then GS can choose the navigation mode.
else Navigation_Mode_From_GS)
and then Operating_Mode =
(if Navigation_Mode = A
or else not Operating_Mode_From_GS_Received
then Operating_Mode_From_CP
else Operating_Mode_From_GS)
and then
(if Power_State'Old = ON
and then On_State'Old = RUNNING
and then Running_State = LANDING
then Operating_Point = Operating_Point'Old),
(if Mission_Parameters_Defined then
Navigation_Parameters =
(if Navigation_Mode_From_CP = A
or else not Navigation_Parameters_From_GS_Received
then Navigation_Parameters_From_USB_Key
else Navigation_Parameters_From_GS));
---------------------------------------
-- Operating Point Update Management --
---------------------------------------
procedure Operating_Point_Update_Management with
-- Compute the value of Operating_Point and Mission_Range
Global => (Input =>
(Input_State, Private_State, Navigation_Parameter_State),
In_Out => Operating_Point_State),
Pre => Power_On
and then Mission_Parameters_Defined
and then Power_State = ON
and then On_State in INIT | RUNNING,
-- F_MM ensures freeze of the operating point once landing is activated.
Post =>
(if Power_State = ON
and then On_State = RUNNING
and then Running_State = LANDING
then Operating_Point = Operating_Point'Old
else Operating_Point = Operating_Point_From_Navigation_Parameters)
-- RP mode enables modification of range parameter before take-off.
and then
(if Navigation_Mode = RP
then Mission_Range = Mission_Range'Old
else Mission_Range = Mission_Range_From_Navigation_Parameters);
------------------------------
-- Mission_Viability_Logic --
------------------------------
function Mission_Profile return Mission_Profile_Type with
Global => Viability_Logic_State;
function Appropriate_Tabulating_Function return Viability_Domain_Mesh_Type
with
Global => Viability_Logic_State;
function Distance_With_Neighbour
(Neighbour : Mission_Profile_Type) return Mission_Profile_Distance_Type
with
Global => Viability_Logic_State;
-- Compute the distance between Mission_Profile and its Neighbour.
function Nearest_Neighbours return Neighbour_Mission_Profiles with
Global => Viability_Logic_State;
function Extract_Energy_Level_For_Neighbours return Energy_Levels
with
Global => Viability_Logic_State;
function Interpolated_Energy_Level return Energy_Level_Type with
Global => Viability_Logic_State;
-- Compute the interpolation of the energy levels of the neighbours of
-- Mission_Profile by distance-based averaging.
procedure Mission_Viability_Logic with
Global => (Input =>
(Input_State,
Private_State,
Navigation_Parameter_State,
Operating_Point_State),
In_Out => Viability_Logic_State),
Pre => Power_State = ON,
Post =>
-- 1. Assembling mission profile.
Mission_Profile =
(Mass => Payload_Mass,
Distance => Current_Range,
Altitude => Current_Altitude,
Speed => Current_Speed)
-- 2. Selecting tabulating function that corresponds to navigation mode.
and then Appropriate_Tabulating_Function =
(if On_State = INIT and then Navigation_Mode = A
then Data.Amode_Initial_Domain_Mesh
elsif On_State = INIT and then Navigation_Mode = RP
then Data.RPmode_Initial_Domain_Mesh
elsif Navigation_Mode = A
then Data.Amode_Cruise_Domain_Mesh
else Data.RPmode_Cruise_Domain_Mesh)
-- 3. Computing the nearest neighbours of Mission_Profile in
-- Appropriate_Tabulating_Function, and the distance of Mission_Profile to
-- its nearest neignbours.
and then
(for all Neighbour_Center of Nearest_Neighbours.Neighbours =>
Neighbour_Center.Mission_Profile.M in
MMS.F_PT.Data.Payload_Mass_Grid'Range
and then Neighbour_Center.Mission_Profile.D in
Appropriate_Tabulating_Function'Range (1)
and then Neighbour_Center.Mission_Profile.A in
Appropriate_Tabulating_Function'Range (2)
and then Neighbour_Center.Mission_Profile.S in
Appropriate_Tabulating_Function'Range (3)
and then Neighbour_Center.Distance =
Distance_With_Neighbour
(Mission_Profile_Type'
(Mass =>
MMS.F_PT.Data.Payload_Mass_Grid
(Neighbour_Center.Mission_Profile.M),
Distance =>
Appropriate_Tabulating_Function
(Neighbour_Center.Mission_Profile.D,
Neighbour_Center.Mission_Profile.A,
Neighbour_Center.Mission_Profile.S).Distance,
Altitude =>
Appropriate_Tabulating_Function
(Neighbour_Center.Mission_Profile.D,
Neighbour_Center.Mission_Profile.A,
Neighbour_Center.Mission_Profile.S).Altitude,
Speed =>
Appropriate_Tabulating_Function
(Neighbour_Center.Mission_Profile.D,
Neighbour_Center.Mission_Profile.A,
Neighbour_Center.Mission_Profile.S).Speed)))
-- 4. Extracting energy level for the neighbours.
and then Extract_Energy_Level_For_Neighbours.Size =
Nearest_Neighbours.Size
and then
(for all I in 1 .. Extract_Energy_Level_For_Neighbours.Size =>
Extract_Energy_Level_For_Neighbours.Neighbours (I) =
(if On_State = INIT and then Navigation_Mode = A
then Data.Viability_Amode_Initial
(M => Nearest_Neighbours.Neighbours (I).Mission_Profile.M,
D => Nearest_Neighbours.Neighbours (I).Mission_Profile.D,
A => Nearest_Neighbours.Neighbours (I).Mission_Profile.A,
S => Nearest_Neighbours.Neighbours (I).Mission_Profile.S)
elsif On_State = INIT and then Navigation_Mode = RP
then Data.Viability_RPmode_Initial
(M => Nearest_Neighbours.Neighbours (I).Mission_Profile.M,
D => Nearest_Neighbours.Neighbours (I).Mission_Profile.D,
A => Nearest_Neighbours.Neighbours (I).Mission_Profile.A,
S => Nearest_Neighbours.Neighbours (I).Mission_Profile.S)
elsif Navigation_Mode = A
then Data.Viability_Amode_Cruise
(M => Nearest_Neighbours.Neighbours (I).Mission_Profile.M,
D => Nearest_Neighbours.Neighbours (I).Mission_Profile.D,
A => Nearest_Neighbours.Neighbours (I).Mission_Profile.A,
S => Nearest_Neighbours.Neighbours (I).Mission_Profile.S)
else Data.Viability_RPmode_Cruise
(M => Nearest_Neighbours.Neighbours (I).Mission_Profile.M,
D => Nearest_Neighbours.Neighbours (I).Mission_Profile.D,
A => Nearest_Neighbours.Neighbours (I).Mission_Profile.A,
S => Nearest_Neighbours.Neighbours (I).Mission_Profile.S)))
-- 5. Compute MP's enery level by interpolation of its neighbours
-- Set appropriate value to Interpolated_Energy_Level
;
procedure Initial_Mission_Viability_Logic with
-- Compute the value of Initial_Energy_Compatible_With_Mission. It should
-- be computed when Init_Completed is True.
Global => (Input =>
(Input_State,
Private_State,
Navigation_Parameter_State,
Operating_Point_State),
In_Out => Viability_Logic_State),
Pre => Power_On
and then Power_State = ON
and then On_State = INIT
and then Init_Completed,
Post => Initial_Energy_Compatible_With_Mission =
-- In A mode, use a 30% energy margin.
((if Navigation_Mode = A then Interpolated_Energy_Level * 13 / 10
-- In RP mode, use a 10% energy margin.
else Interpolated_Energy_Level * 11 / 10) >= Energy_Level);
procedure In_Flight_Mission_Viability_Logic with
-- Compute the value of In_Flight_Energy_Compatible_With_Mission. It should
-- be repeated at a periodic rate of F_Viability.
-- Set In_Flight_Energy_Compatible_With_Mission to True if Energy_Level is
-- at least the Interpolated_Energy_Level plus an enery margin. When
-- EstimatedTotalMass increases, and even more so if it increases quickly,
-- F_MM applies greater safety margins (see #17).
Global => (Input =>
(Input_State,
Private_State,
Navigation_Parameter_State,
Operating_Point_State),
In_Out => Viability_Logic_State),
Pre => Power_On
and then Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT
and then Current_Flight_Phase = CRUISE;
---------------------------------
-- Mission Termination Control --
---------------------------------
function Current_Glide_Distance return Current_Range_Type with
Global => Mission_Termination_State;
-- Compute the glide distance associated with Current_Altitude using the
-- Glide_Distance_Domain_Mesh table and the Glide_Distance tabulated
-- function.
procedure Mission_Termination_Control with
-- Monitor Current_Range and activate landing.
Global => (Input =>
(Input_State,
Private_State,
Navigation_Parameter_State,
Operating_Point_State),
In_Out => Mission_Termination_State),
Pre => Power_On
and then Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT
and then Current_Flight_Phase = DESCENT,
Post => Descent_Over =
(Mission_Range - Current_Range < Current_Glide_Distance);
--------------------------------
-- Update the State Automaton --
--------------------------------
procedure Update_States with
Global => (Input =>
(Input_State,
Navigation_Parameter_State,
Operating_Point_State,
Viability_Logic_State,
Mission_Termination_State),
In_Out => Private_State),
Contract_Cases =>
(Power_State = OFF
and then Power_Off
(not Power_On
=>
Power_State = OFF,
......@@ -265,11 +531,6 @@ package MMS.F_PT.F_MM.Behavior with SPARK_Mode is
and then On_State = INIT
and then Init_State = PREPARATION,
Power_State = ON
and then Power_Off
=>
Power_State = OFF,
Power_State = ON
and then Power_On
and then (On_State in INIT | RUNNING)
......@@ -277,8 +538,7 @@ package MMS.F_PT.F_MM.Behavior with SPARK_Mode is
=>
Power_State = ON
and then On_State = ABORTED
and then Aborted_For_Energy_Reasons = False
and then Mission_Aborted_Signaled,
and then Aborted_For_Energy_Reasons = False,
Power_State = ON
and then Power_On
......@@ -296,15 +556,11 @@ package MMS.F_PT.F_MM.Behavior with SPARK_Mode is
and then not Mission_Abort_Received
and then Init_Completed
and then not Start_Or_Go_Received
and then Initial_Energy_Compatible_With_Mission
=>
Power_State = ON
and then On_State = INIT
and then
(if Initial_Energy_Compatible_With_Mission then
Init_State = READY
else
Init_State = CANCELLED
and then Mission_Cancelled_Signaled),
and then Init_State = READY,
Power_State = ON
and then Power_On
......@@ -312,16 +568,22 @@ package MMS.F_PT.F_MM.Behavior with SPARK_Mode is
and then not Mission_Abort_Received
and then Init_Completed
and then Start_Or_Go_Received
and then Initial_Energy_Compatible_With_Mission
=>
Power_State = ON
and then On_State = RUNNING
and then Running_State = TAKE_OFF,
Power_State = ON
and then Power_On
and then On_State = INIT
and then not Mission_Abort_Received
and then Init_Completed
and then not Initial_Energy_Compatible_With_Mission
=>
(if Initial_Energy_Compatible_With_Mission then
Power_State = ON
and then On_State = RUNNING
and then Running_State = TAKE_OFF
else
Power_State = ON
and then On_State = INIT
and then Init_State = CANCELLED
and then Mission_Cancelled_Signaled),
Power_State = ON
and then On_State = INIT
and then Init_State = CANCELLED,
Power_State = ON
and then On_State = RUNNING
......@@ -350,25 +612,40 @@ package MMS.F_PT.F_MM.Behavior with SPARK_Mode is
and then Running_State = FLIGHT
and then Power_On
and then not Mission_Abort_Received
and then Current_Flight_Phase = CRUISE
and then not In_Flight_Energy_Compatible_With_Mission
=>
(if Current_Flight_Phase = CRUISE
and then not In_Flight_Energy_Compatible_With_Mission
then
Power_State = ON
and then On_State = ABORTED
and then Aborted_For_Energy_Reasons = True
and then Mission_Aborted_Signaled
and then Emergency_Landing
elsif Current_Flight_Phase = DESCENT
and then Descent_Over
then
Power_State = ON
and then On_State = RUNNING
and then Running_State = LANDING
else
Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT),
Power_State = ON
and then On_State = ABORTED
and then Aborted_For_Energy_Reasons = True
and then Mission_Aborted_Signaled
and then Emergency_Landing,
Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT
and then Power_On
and then not Mission_Abort_Received
and then Current_Flight_Phase = DESCENT
and then Descent_Over
=>
Power_State = ON
and then On_State = RUNNING
and then Running_State = LANDING,
Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT
and then Power_On
and then not Mission_Abort_Received
and then
(if Current_Flight_Phase = CRUISE then
In_Flight_Energy_Compatible_With_Mission
elsif Current_Flight_Phase = DESCENT then not Descent_Over)
=>
Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT,
Power_State = ON
and then On_State = RUNNING
......@@ -467,195 +744,50 @@ private
function Energy_Level return Energy_Level_Type is
(State.Input_Energy_Level);
-------------------
-- Tasks of F_MM --
-------------------
function Navigation_Parameters return Navigation_Parameters_Type is
(State.Navigation_Parameters)
with Pre => Mission_Parameters_Defined;
procedure Management_Of_Navigation_Mode with
-- Compute the value of Navigation_Mode / Options / Parameters (see 6.9.4)
Post => Navigation_Mode =
-- In case of conflict on the navigation mode, CP prevails over GS.
(if Navigation_Mode_From_CP = A
or else not Navigation_Mode_From_GS_Received
then Navigation_Mode_From_CP
-- If CP states the mode to RC then GS can choose the navigation mode.
else Navigation_Mode_From_GS)
and then Operating_Mode =
(if Navigation_Mode = A
or else not Operating_Mode_From_GS_Received
then Operating_Mode_From_CP
else Operating_Mode_From_GS)
and then
(if Mission_Parameters_Defined then
Navigation_Parameters =
(if Navigation_Mode = A
or else not Navigation_Parameters_From_GS_Received
then Navigation_Parameters_From_USB_Key
else Navigation_Parameters_From_GS));
procedure Operating_Point_Update_Management with
-- Compute the value of Operating_Point
------------------------------------
-- Definitions of Internal State --
------------------------------------
Pre =>
Mission_Parameters_Defined
and then Power_State = ON
and then On_State in INIT | RUNNING,
function Power_State return Power_State_Type is
(State.Power_State);
-- F_MM ensures freeze of the operating point once landing is activated.
function On_State return On_State_Type is
(State.On_State);
Post =>
(if Power_State = ON
and then On_State = RUNNING
and then Running_State = LANDING
then Operating_Point = Operating_Point'Old
else Operating_Point = Operating_Point_From_Navigation_Parameters);
function Running_State return Running_State_Type is
(State.Running_State);
------------------------------
-- Mission_Viability_Logic --
------------------------------
function Init_State return Init_State_Type is
(State.Init_State);
function Mission_Profile return Mission_Profile_Type with
-- Assemble the mission profile
function Aborted_For_Energy_Reasons return Boolean is
(State.Aborted_For_Energy_Reasons);
Pre => Power_State = ON,
Post => Mission_Profile'Result =
(Mass => Payload_Mass,
Distance => Current_Range,
Altitude => Current_Altitude,
Speed => Current_Speed);
function Take_Off_Over return Boolean is (True);
-- ??? When is take off over?
function Appropriate_Tabulating_Function return Viability_Domain_Mesh_Type
-- Select the tabulated function corresponding to the navigation mode
function Descent_Over return Boolean is
(State.Descent_Over);
with
Pre => Power_State = ON
and then On_State in INIT | RUNNING,
Post => Appropriate_Tabulating_Function'Result =
(if On_State = INIT and then Navigation_Mode = A
then Data.Amode_Initial_Domain_Mesh
elsif On_State = INIT and then Navigation_Mode = RP
then Data.RPmode_Initial_Domain_Mesh
elsif Navigation_Mode = A
then Data.Amode_Cruise_Domain_Mesh
else Data.RPmode_Cruise_Domain_Mesh);
function Distance_With_Neighbour
(Neighbour : Mission_Profile_Type) return Mission_Profile_Distance_Type
with
Pre => Power_State = ON
and then On_State in INIT | RUNNING;
-- Compute the distance between Mission_Profile and its Neighbour.
function Nearest_Neighbours return Neighbour_Mission_Profile_Array_Type with
-- Compute the nearest neighbous of Mission_Profile in
-- Appropriate_Tabulating_Function, and the distance of Mission_Profile to
-- its nearest neignbours.
Pre => Power_State = ON
and then On_State in INIT | RUNNING,
Post =>
(for all Neighbour_Center of Nearest_Neighbours'Result =>
Neighbour_Center.Mission_Profile.M in
MMS.F_PT.Data.Payload_Mass_Grid'Range
and then Neighbour_Center.Mission_Profile.D in
Appropriate_Tabulating_Function'Range (1)
and then Neighbour_Center.Mission_Profile.A in
Appropriate_Tabulating_Function'Range (2)
and then Neighbour_Center.Mission_Profile.S in
Appropriate_Tabulating_Function'Range (3)
and then Neighbour_Center.Distance =
Distance_With_Neighbour
(Mission_Profile_Type'
(Mass =>
MMS.F_PT.Data.Payload_Mass_Grid
(Neighbour_Center.Mission_Profile.M),
Distance =>
Appropriate_Tabulating_Function
(Neighbour_Center.Mission_Profile.D,
Neighbour_Center.Mission_Profile.A,
Neighbour_Center.Mission_Profile.S).Distance,
Altitude =>
Appropriate_Tabulating_Function
(Neighbour_Center.Mission_Profile.D,
Neighbour_Center.Mission_Profile.A,
Neighbour_Center.Mission_Profile.S).Altitude,
Speed =>
Appropriate_Tabulating_Function
(Neighbour_Center.Mission_Profile.D,
Neighbour_Center.Mission_Profile.A,
Neighbour_Center.Mission_Profile.S).Speed)));
function Extract_Energy_Level_For_Neighbour
(Neighbour : Center_Mission_Profile_Type) return Energy_Level_Type
-- Extract energy level for the neighbour.
with
Pre => Power_State = ON
and then On_State in INIT | RUNNING,
Post => Extract_Energy_Level_For_Neighbour'Result =
(if On_State = INIT and then Navigation_Mode = A
then Data.Viability_Amode_Initial (M => Neighbour.M,
D => Neighbour.D,
A => Neighbour.A,
S => Neighbour.S)
elsif On_State = INIT and then Navigation_Mode = RP
then Data.Viability_RPmode_Initial (M => Neighbour.M,
D => Neighbour.D,
A => Neighbour.A,
S => Neighbour.S)
elsif Navigation_Mode = A
then Data.Viability_Amode_Cruise (M => Neighbour.M,
D => Neighbour.D,
A => Neighbour.A,
S => Neighbour.S)
else Data.Viability_RPmode_Cruise (M => Neighbour.M,
D => Neighbour.D,
A => Neighbour.A,
S => Neighbour.S));
function Interpolated_Energy_Level return Energy_Level_Type;
-- Compute the interpolation of the energy levels of the neighbours of
-- Mission_Profile by distance-based averaging.
procedure Initial_Mission_Viability_Logic with
-- Compute the value of Initial_Energy_Compatible_With_Mission. It should
-- be computed when Init_Completed is True.
Pre => Power_State = ON
and then On_State = INIT
and then Init_Completed,
Post => Initial_Energy_Compatible_With_Mission =
function Navigation_Parameters return Navigation_Parameters_Type is
(State.Navigation_Parameters);
-- In A mode, use a 30% energy margin.
function Navigation_Mode return Navigation_Mode_Type is
(State.Navigation_Mode);
((if Navigation_Mode = A then Interpolated_Energy_Level * 13 / 10
function Operating_Mode return Navigation_Option_Type is
(State.Operating_Mode);
-- In RP mode, use a 10% energy margin.
function Initial_Energy_Compatible_With_Mission return Boolean is
(State.Initial_Energy_Compatible_With_Mission);
else Interpolated_Energy_Level * 11 / 10) >= Energy_Level);
function In_Flight_Energy_Compatible_With_Mission return Boolean is
(State.In_Flight_Energy_Compatible_With_Mission);
procedure In_Flight_Mission_Viability_Logic with
-- Compute the value of In_Flight_Energy_Compatible_With_Mission. It should
-- be repeated at a periodic rate of F_Viability.
-- Set In_Flight_Energy_Compatible_With_Mission to True if Energy_Level is
-- at least the Interpolated_Energy_Level plus an enery margin. When
-- EstimatedTotalMass increases, and even more so if it increases quickly,
-- F_MM applies greater safety margins (see #17).
function Mission_Range return Current_Range_Type is
(State.Mission_Range);
Pre => Power_State = ON
and then On_State = RUNNING
and then Running_State = FLIGHT
and then Current_Flight_Phase = CRUISE;
function Operating_Point return Operating_Point_Type is
(State.Operating_Point);
end MMS.F_PT.F_MM.Behavior;
......@@ -48,22 +48,53 @@ package MMS.F_PT.F_MM.State is
-- Private_State --
-------------------
Navigation_Mode : Navigation_Mode_Type with Part_Of => Private_State;
Power_State : Power_State_Type with Part_Of => Private_State;
Operating_Mode : Navigation_Option_Type with Part_Of => Private_State;
On_State : On_State_Type with Part_Of => Private_State;
Init_State : Init_State_Type with Part_Of => Private_State;
Running_State : Running_State_Type with Part_Of => Private_State;
Aborted_For_Energy_Reasons : Boolean with Part_Of => Private_State;
--------------------------------
-- Navigation_Parameter_State --
--------------------------------
Navigation_Mode : Navigation_Mode_Type with
Part_Of => Navigation_Parameter_State;
Operating_Mode : Navigation_Option_Type with
Part_Of => Navigation_Parameter_State;
Navigation_Parameters : Navigation_Parameters_Type with
Part_Of => Private_State;
Part_Of => Navigation_Parameter_State;
---------------------------
-- Operating_Point_State --
---------------------------
Mission_Range : Current_Range_Type with Part_Of => Operating_Point_State;
Operating_Point : Operating_Point_Type with Part_Of => Private_State;
Operating_Point : Operating_Point_Type with
Part_Of => Operating_Point_State;
---------------------------
-- Viability_Logic_State --
---------------------------
Initial_Energy_Compatible_With_Mission : Boolean with
Part_Of => Private_State;
Part_Of => Viability_Logic_State;
In_Flight_Energy_Compatible_With_Mission : Boolean with
Part_Of => Private_State;
Part_Of => Viability_Logic_State;
-------------------------------
-- Mission_Termination_State --
-------------------------------
Descent_Over : Boolean with Part_Of => Private_State;
Descent_Over : Boolean with Part_Of => Mission_Termination_State;
------------------
-- Output_State --
......
with MMS.F_PT.F_MM.State; use MMS.F_PT.F_MM.State;
package body MMS.F_PT.F_MM with
SPARK_Mode,
Refined_State => (Input_State => (Input_Navigation_Parameters,
Input_Navigation_Mode,
Input_Navigation_Option,
Input_Go,
Input_On_OFF_Push_Button,
Input_Start_Push_Button,
Input_Mode_Switch,
Input_Bay_Switch,
Input_Payload_Mass,
Input_USB_Key,
Input_Mission_Abort,
Input_Estimated_Total_Mass,
Input_Current_Range,
Input_Current_Speed,
Input_Current_Altitude,
Input_Current_Flight_Phase,
Input_Energy_Level),
Output_State => (Output_Mission_Cancelled,
Output_Mission_Complete,
Output_Mission_Aborted,
Output_Emergency_Landing,
Output_Start_Take_Off,
Output_Start_Landing,
Output_Operating_Point,
Output_Operating_Mode,
Output_Mission_Range),
Private_State => (Navigation_Mode,
Operating_Mode,
Navigation_Parameters,
Operating_Point,
Initial_Energy_Compatible_With_Mission,
In_Flight_Energy_Compatible_With_Mission,
Descent_Over))
SPARK_Mode,
Refined_State => (Input_State =>
(Input_Navigation_Parameters,
Input_Navigation_Mode,
Input_Navigation_Option,
Input_Go,
Input_On_OFF_Push_Button,
Input_Start_Push_Button,
Input_Mode_Switch,
Input_Bay_Switch,
Input_Payload_Mass,
Input_USB_Key,
Input_Mission_Abort,
Input_Estimated_Total_Mass,
Input_Current_Range,
Input_Current_Speed,
Input_Current_Altitude,
Input_Current_Flight_Phase,
Input_Energy_Level),
Output_State =>
(Output_Mission_Cancelled,
Output_Mission_Complete,
Output_Mission_Aborted,
Output_Emergency_Landing,
Output_Start_Take_Off,
Output_Start_Landing,
Output_Operating_Point,
Output_Operating_Mode,
Output_Mission_Range),
Private_State =>
(Power_State,
On_State,
Init_State,
Running_State,
Aborted_For_Energy_Reasons),
Navigation_Parameter_State =>
(Navigation_Mode,
Operating_Mode,
Navigation_Parameters),
Operating_Point_State =>
(Mission_Range,
Operating_Point),
Viability_Logic_State =>
(Initial_Energy_Compatible_With_Mission,
In_Flight_Energy_Compatible_With_Mission),
Mission_Termination_State =>
(Descent_Over))
is
end MMS.F_PT.F_MM;
......@@ -2,10 +2,25 @@ with Types; use Types;
package MMS.F_PT.F_MM with
SPARK_Mode,
Abstract_State => (Private_State, Output_State, Input_State)
Abstract_State =>
(Navigation_Parameter_State,
Operating_Point_State,
Viability_Logic_State,
Mission_Termination_State,
Private_State,
Output_State,
Input_State)
is
pragma Elaborate_Body (MMS.F_PT.F_MM);
type Power_State_Type is (ON, OFF);
type On_State_Type is (INIT, RUNNING, COMPLETE, ABORTED);
type Running_State_Type is (TAKE_OFF, FLIGHT, LANDING);
type Init_State_Type is (PREPARATION, READY, CANCELLED);
type Viability_Cell_Center_Type is record
Distance : Current_Range_Type;
Altitude : Current_Altitude_Type;
......@@ -48,7 +63,22 @@ is
Distance : Mission_Profile_Distance_Type;
end record;
type Neighbour_Mission_Profile_Array_Type is array (Positive range 1 .. 16)
type Num_Of_Neighbours is new Positive range 1 .. 16;
type Neighbour_Mission_Profile_Array_Type is array
(Num_Of_Neighbours range <>)
of Neighbour_Mission_Profile_Type;
type Neighbour_Mission_Profiles (Size : Num_Of_Neighbours) is record
Neighbours : Neighbour_Mission_Profile_Array_Type (1 .. Size);
end record;
type Energy_Level_Array_Type is array
(Num_Of_Neighbours range <>)
of Energy_Level_Type;
type Energy_Levels (Size : Num_Of_Neighbours) is record
Neighbours : Energy_Level_Array_Type (1 .. Size);
end record;
end MMS.F_PT.F_MM;
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment