|
|
DataMuseum.dkPresents historical artifacts from the history of: Rational R1000/400 Tapes |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about Rational R1000/400 Tapes Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - metrics - downloadIndex: B T
Length: 40520 (0x9e48)
Types: TextFile
Names: »B«
└─⟦149519bd4⟧ Bits:30000546 8mm tape, Rational 1000, !projects 93-07-13
└─⟦124ff5788⟧ »DATA«
└─⟦this⟧
└─⟦a7d1ea751⟧ Bits:30000550 8mm tape, Rational 1000, !users!projects 94_04_11
└─⟦129cab021⟧ »DATA«
└─⟦this⟧
└─⟦f64eaa120⟧ Bits:30000752 8mm tape, Rational 1000, !projects 93 02 16
└─⟦6f12a12be⟧ »DATA«
└─⟦this⟧
└─⟦2f6cfab89⟧ Bits:30000547 8mm tape, Rational 1000, !projects 94-01-04
└─⟦d65440be7⟧ »DATA«
└─⟦this⟧
with Octet, Mot, Periph, Erreur, Text_Io, Ihm, Bus, Verif_Input;
use Periph;
package body Ptm_Pack is
Bit0 : constant Octet.Num_Bit := 0;
Bit1 : constant Octet.Num_Bit := 1;
Bit2 : constant Octet.Num_Bit := 2;
Bit3 : constant Octet.Num_Bit := 3;
Bit4 : constant Octet.Num_Bit := 4;
Bit5 : constant Octet.Num_Bit := 5;
Bit6 : constant Octet.Num_Bit := 6;
Bit7 : constant Octet.Num_Bit := 7;
Not_Available : constant Natural := 50;
Unknown_Id : constant Natural := 51;
Unknown_Conf : constant Natural := 52;
Unknown_Event : constant Natural := 53;
Window_Already_Open : constant Natural := 54;
Bad_Value : constant Natural := 55;
Identifier_Field : constant String := "BB.Number";
Vector_Field : constant String := "BB.F1.Vector";
Address_Field : constant String := "BB.F1.Base";
Mem_Mapped_Field : constant String := "BB.F1.Memory";
It_Connect_Field : constant String := "BB.F1.It";
Control1_Field : constant String := "BB.T.Control1";
Buffer1_Field : constant String := "BB.T.Buffer1";
Counter1_Field : constant String := "BB.T.Counter1";
Control2_Field : constant String := "BB.T.Control2";
Buffer2_Field : constant String := "BB.T.Buffer2";
Counter2_Field : constant String := "BB.T.Counter2";
Control3_Field : constant String := "BB.T.Control3";
Buffer3_Field : constant String := "BB.T.Buffer3";
Counter3_Field : constant String := "BB.T.Counter3";
Status_Field : constant String := "BB.F2.Status";
Close_Window : constant String := "Cancel";
Window_Name : constant String := "PTM";
type Mode is (Put, Get);
type Fnct_Mode is (Continu, One_Shot, None);
task type Ptm_Task is
entry Init (Periph_Id : Periph.T_Periph_Number;
It_Vector : Octet.T_Octet;
Basic_Address : Mot.T_Mot;
Memory_Mapped : Boolean;
It_Connected : Boolean;
Identifier : T_Ptm_Number;
Number_Of_Register : out Natural);
entry Access_Register (Mode) (Register_Number : Natural;
Value : in out Octet.T_Octet);
entry Clock;
entry Reset;
entry Kill;
entry Open_Window (Wid : Ihm.Window_Id);
entry Do_Event (What_Kind : Ihm.Event.Kind;
Field_Name : String;
Value : String);
end Ptm_Task;
type P_Ptm_Task is access Ptm_Task;
type Object is
record
Task_Access : P_Ptm_Task;
Window : Boolean := False;
end record;
type Object_Table is array (T_Ptm_Number) of Object;
type Object_Manager is
record
Table : Object_Table;
Last : T_Ptm_Number := T_Ptm_Number'First;
end record;
task type Intern_Clock is
entry Kill;
end Intern_Clock;
type P_Intern_Clock is access Intern_Clock;
type Byte_Table is array (1 .. 3) of Octet.T_Octet;
type Word_Table is array (1 .. 3) of Mot.T_Mot;
type Bool_Table is array (1 .. 3) of Boolean;
type Fnct_Table is array (1 .. 3) of Fnct_Mode;
type Ptm_Config is
record
Identifier : T_Ptm_Number;
Periph_Id : Periph.T_Periph_Number;
Vector : Octet.T_Octet;
Address : Mot.T_Mot;
Mem_Mapped : Boolean;
It_Connect : Boolean;
Control : Byte_Table;
Buffer : Word_Table;
Counter : Word_Table;
State : Octet.T_Octet;
Count_16 : Bool_Table;
It_Enable : Bool_Table;
Count : Bool_Table;
Fnct : Fnct_Table;
Count_8div : Boolean;
Actual : Natural;
Intern_Init : Boolean;
end record;
Ptm_Manager : Object_Manager;
The_Clock : P_Intern_Clock;
------------------------------ exports -------------------------------------
procedure Init (Periph_Id : Periph.T_Periph_Number;
It_Vector : Octet.T_Octet;
Basic_Address : Mot.T_Mot;
Memory_Mapped : Boolean;
It_Connected : Boolean;
Number_Of_Register : out Natural;
Identifier : out T_Ptm_Number) is
begin
if Ptm_Manager.Last >= T_Ptm_Number'Last then
Erreur.Detectee (Not_Available);
Identifier := T_Ptm_Number'First;
Number_Of_Register := 0;
else
Ptm_Manager.Last := Ptm_Manager.Last + 1;
Ptm_Manager.Table (Ptm_Manager.Last).Task_Access := new Ptm_Task;
Ptm_Manager.Table (Ptm_Manager.Last).Task_Access.Init
(Periph_Id, It_Vector, Basic_Address, Memory_Mapped,
It_Connected, Ptm_Manager.Last, Number_Of_Register);
Identifier := Ptm_Manager.Last;
if Ptm_Manager.Last = 1 then
The_Clock := new Intern_Clock;
end if;
end if;
end Init;
procedure Put_Register (Identifier : T_Ptm_Number;
Register_Number : Natural;
Value : Octet.T_Octet) is
Register_Value : Octet.T_Octet;
begin
if Identifier > Ptm_Manager.Last or Identifier = T_Ptm_Number'First then
Erreur.Detectee (Unknown_Id);
else
Register_Value := Value;
Ptm_Manager.Table (Identifier).Task_Access.Access_Register (Put)
(Register_Number, Register_Value);
end if;
end Put_Register;
function Get_Register (Identifier : T_Ptm_Number; Register_Number : Natural)
return Octet.T_Octet is
Register_Value : Octet.T_Octet;
begin
if Identifier > Ptm_Manager.Last or Identifier = T_Ptm_Number'First then
Erreur.Detectee (Unknown_Id);
else
Ptm_Manager.Table (Identifier).Task_Access.Access_Register (Get)
(Register_Number, Register_Value);
end if;
return Register_Value;
end Get_Register;
procedure Reset (Identifier : T_Ptm_Number) is
begin
if Identifier > Ptm_Manager.Last or Identifier = T_Ptm_Number'First then
Erreur.Detectee (Unknown_Id);
else
Ptm_Manager.Table (Identifier).Task_Access.Reset;
end if;
end Reset;
procedure Receive (Register_Number : Natural;
Value : Octet.T_Octet;
Bit_Number : Natural;
Identifier : Natural) is
Identifier1 : T_Ptm_Number;
Control_Value : Octet.T_Octet;
begin
Identifier1 := T_Ptm_Number (Identifier);
Control_Value := Value;
if Identifier1 > Ptm_Manager.Last or
Identifier1 = T_Ptm_Number'First then
Erreur.Detectee (Unknown_Id);
else
Ptm_Manager.Table (Identifier1).Task_Access.Access_Register (Put)
(3, Control_Value);
end if;
end Receive;
procedure Kill is
begin
if Ptm_Manager.Last > T_Ptm_Number'First then
The_Clock.Kill;
end if;
for I in 1 .. Ptm_Manager.Last loop
Ptm_Manager.Table (I).Window := False;
Ptm_Manager.Table (I).Task_Access.Kill;
end loop;
Ptm_Manager.Last := T_Ptm_Number'First;
end Kill;
function Open_Window (Identifier : Natural) return Boolean is
Id : T_Ptm_Number;
begin
Id := T_Ptm_Number (Identifier);
if Id > Ptm_Manager.Last or Id = T_Ptm_Number'First then
Erreur.Detectee (Unknown_Id);
return False;
elsif Ptm_Manager.Table (Id).Window then
Erreur.Detectee (Window_Already_Open);
return False;
else
return True;
end if;
end Open_Window;
procedure Open_Window (Identifier : Natural; Window_Id : Ihm.Window_Id) is
Id : T_Ptm_Number;
begin
Id := T_Ptm_Number (Identifier);
Ptm_Manager.Table (Id).Window := True;
Ptm_Manager.Table (Id).Task_Access.Open_Window (Window_Id);
end Open_Window;
procedure Dispatch_Event (Identifier : Natural;
What_Kind : Ihm.Event.Kind;
Field_Name : String;
Value : String) is
Id : T_Ptm_Number;
begin
Id := T_Ptm_Number (Identifier);
if Id > Ptm_Manager.Last or Id = T_Ptm_Number'First then
Erreur.Detectee (Unknown_Id);
else
if Ihm.Event."=" (What_Kind, Ihm.Event.Pushbutton) and
Field_Name = Close_Window then
Ptm_Manager.Table (Id).Window := False;
end if;
Ptm_Manager.Table (Id).Task_Access.Do_Event
(What_Kind, Field_Name, Value);
end if;
end Dispatch_Event;
------------------------------ internals ------------------------------------
procedure Clock is
begin
for I in 1 .. Ptm_Manager.Last loop
Ptm_Manager.Table (I).Task_Access.Clock;
end loop;
end Clock;
task body Intern_Clock is
begin
loop
select
accept Kill;
exit;
else
delay 1.0;
Clock;
end select;
end loop;
end Intern_Clock;
procedure Write_Window
(Configuration : Ptm_Config;
Window_Id : Ihm.Window_Id;
Window_Enable : Boolean;
Identifier_Show, Vector_Show, Address_Show, Mem_Mapped_Show,
It_Connect_Show, Control1_Show, Buffer1_Show,
Counter1_Show, Control2_Show, Buffer2_Show, Counter2_Show,
Control3_Show, Buffer3_Show, Counter3_Show, State_Show :
Boolean := False) is
begin
if Window_Enable then
if Identifier_Show then
Ihm.Window.Put_Field
(Window_Id, Identifier_Field,
T_Ptm_Number'Image (Configuration.Identifier));
end if;
if Vector_Show then
Ihm.Window.Put_Field (Window_Id, Vector_Field,
Octet.Convert_Octet_String
(Configuration.Vector));
end if;
if Address_Show then
Ihm.Window.Put_Field (Window_Id, Address_Field,
Mot.Convert_Mot_String
(Configuration.Address));
end if;
if Mem_Mapped_Show then
if Configuration.Mem_Mapped then
Ihm.Window.Put_Field (Window_Id, Mem_Mapped_Field, " On");
else
Ihm.Window.Put_Field (Window_Id, Mem_Mapped_Field, "Off");
end if;
end if;
if It_Connect_Show then
if Configuration.It_Connect then
Ihm.Window.Put_Field (Window_Id, It_Connect_Field, " On");
else
Ihm.Window.Put_Field (Window_Id, It_Connect_Field, "Off");
end if;
end if;
if Control1_Show then
Ihm.Window.Put_Field (Window_Id, Control1_Field,
Octet.Convert_Binaire_String
(Configuration.Control (1)));
end if;
if Buffer1_Show then
Ihm.Window.Put_Field (Window_Id, Buffer1_Field,
Mot.Convert_Mot_String
(Configuration.Buffer (1)));
end if;
if Counter1_Show then
Ihm.Window.Put_Field (Window_Id, Counter1_Field,
Mot.Convert_Mot_String
(Configuration.Counter (1)));
end if;
if Control2_Show then
Ihm.Window.Put_Field (Window_Id, Control2_Field,
Octet.Convert_Binaire_String
(Configuration.Control (2)));
end if;
if Buffer2_Show then
Ihm.Window.Put_Field (Window_Id, Buffer2_Field,
Mot.Convert_Mot_String
(Configuration.Buffer (2)));
end if;
if Counter2_Show then
Ihm.Window.Put_Field (Window_Id, Counter2_Field,
Mot.Convert_Mot_String
(Configuration.Counter (2)));
end if;
if Control3_Show then
Ihm.Window.Put_Field (Window_Id, Control3_Field,
Octet.Convert_Binaire_String
(Configuration.Control (3)));
end if;
if Buffer3_Show then
Ihm.Window.Put_Field (Window_Id, Buffer3_Field,
Mot.Convert_Mot_String
(Configuration.Buffer (3)));
end if;
if Counter3_Show then
Ihm.Window.Put_Field (Window_Id, Counter3_Field,
Mot.Convert_Mot_String
(Configuration.Counter (3)));
end if;
if State_Show then
Ihm.Window.Put_Field (Window_Id, Status_Field,
Octet.Convert_Binaire_String
(Configuration.State));
end if;
end if;
end Write_Window;
procedure Display (Configuration : Ptm_Config) is
use Text_Io;
Carac1, Carac2 : Character;
begin
Put_Line ("===================================================");
Put_Line ("TIMER " & T_Ptm_Number'Image (Configuration.Identifier));
Put (" V:");
Octet.Afficher_Octet_Binaire (Configuration.Vector);
Put (" ADR: ");
Mot.Afficher_Mot_Hexa (Configuration.Address);
Put (" MAP:" & Boolean'Image (Configuration.Mem_Mapped));
Put (" ITC:" & Boolean'Image (Configuration.It_Connect));
New_Line;
for I in 1 .. 3 loop
Put_Line ("counter " & Integer'Image (I));
Put (" CWR:");
Octet.Afficher_Octet_Binaire (Configuration.Control (I));
Put (" BUF:");
Mot.Afficher_Mot_Hexa (Configuration.Buffer (I));
Put (" CNT:");
Mot.Afficher_Mot_Hexa (Configuration.Counter (I));
New_Line;
Put ("Cpt16:" & Boolean'Image (Configuration.Count_16 (I)) &
" Itc:" & Boolean'Image (Configuration.It_Enable (I)) &
" en cours:" & Boolean'Image (Configuration.Count (I)));
Put_Line (" Fnct:" & Fnct_Mode'Image (Configuration.Fnct (I)));
end loop;
Put_Line ("Div8:" & Boolean'Image (Configuration.Count_8div) &
" Init:" & Boolean'Image (Configuration.Intern_Init));
Put ("%8:" & Natural'Image (Configuration.Actual) & " STATE:");
Octet.Afficher_Octet_Binaire (Configuration.State);
New_Line;
end Display;
procedure Reset_Ptm (Configuration : in out Ptm_Config;
Window_Id : Ihm.Window_Id;
Window_Enable : Boolean) is
begin
for I in 1 .. 3 loop
Configuration.Control (I) := 0;
Configuration.Counter (I) := 65535;
Configuration.Buffer (I) := 65535;
Configuration.Count_16 (I) := False;
Configuration.It_Enable (I) := False;
Configuration.Fnct (I) := None;
Configuration.Count (I) := True;
end loop;
Configuration.Control (1) := 1;
Configuration.State := 0;
Configuration.Count_8div := False;
Configuration.Actual := 0;
Configuration.Intern_Init := True;
Write_Window (Configuration, Window_Id, Window_Enable,
Identifier_Show => True,
Vector_Show => True,
Address_Show => True,
Mem_Mapped_Show => True,
It_Connect_Show => True,
Control1_Show => True,
Buffer1_Show => True,
Counter1_Show => True,
Control2_Show => True,
Buffer2_Show => True,
Counter2_Show => True,
Control3_Show => True,
Buffer3_Show => True,
Counter3_Show => True,
State_Show => True);
end Reset_Ptm;
procedure Initialize_Timer (Configuration : in out Ptm_Config;
Window_Id : Ihm.Window_Id;
Window_Enable : Boolean;
Register_Number : Natural) is
use Octet;
Timer_Mode : T_Octet;
begin
case Register_Number is
when 1 =>
if Test_Bit (Configuration.Control (1), Bit0) then
Configuration.Intern_Init := True;
for I in 1 .. 3 loop
Configuration.Counter (I) := Configuration.Buffer (I);
Configuration.Count (I) := False;
Res_Bit (Configuration.State, Num_Bit (I - 1));
end loop;
Res_Bit (Configuration.State, Bit7);
else
Configuration.Intern_Init := False;
for I in 1 .. 3 loop
Configuration.Count (I) := True;
end loop;
Configuration.Actual := 0;
end if;
when 3 =>
if Test_Bit (Configuration.Control (3), Bit0) then
Configuration.Count_8div := True;
else
Configuration.Count_8div := False;
end if;
when others =>
null;
end case;
if Test_Bit (Configuration.Control (Register_Number), Bit2) then
Configuration.Count_16 (Register_Number) := False;
else
Configuration.Count_16 (Register_Number) := True;
end if;
if Test_Bit (Configuration.Control (Register_Number), Bit6) then
Configuration.It_Enable (Register_Number) := True;
else
Configuration.It_Enable (Register_Number) := False;
end if;
Timer_Mode := "and" (Configuration.Control (Register_Number), 56);
Timer_Mode := Timer_Mode / 8;
case Timer_Mode is
when 0 | 2 =>
Configuration.Fnct (Register_Number) := Continu;
when 4 | 6 =>
Configuration.Fnct (Register_Number) := One_Shot;
when others =>
Configuration.Fnct (Register_Number) := None;
end case;
Write_Window (Configuration, Window_Id, Window_Enable,
Control1_Show => True,
Buffer1_Show => True,
Counter1_Show => True,
Control2_Show => True,
Buffer2_Show => True,
Counter2_Show => True,
Control3_Show => True,
Buffer3_Show => True,
Counter3_Show => True,
State_Show => True);
end Initialize_Timer;
procedure Receive_Clock (Configuration : in out Ptm_Config;
Window_Id : Ihm.Window_Id;
Window_Enable : Boolean) is
use Octet;
Msb_Byte : T_Octet;
Lsb_Byte : T_Octet;
begin
for I in 1 .. 3 loop
if Configuration.Count (I) then
if I = 3 and Configuration.Count_8div and
Configuration.Actual < 7 then
Configuration.Actual := Configuration.Actual + 1;
else
if I = 3 and Configuration.Count_8div then
Configuration.Actual := 0;
end if;
if Configuration.Count_16 (I) then
Configuration.Counter (I) :=
Configuration.Counter (I) - 1;
else
Msb_Byte := Mot.Poids_Fort (Configuration.Counter (I));
Lsb_Byte := Mot.Poids_Faible
(Configuration.Counter (I));
if Lsb_Byte = 0 then
Msb_Byte := Msb_Byte - 1;
Lsb_Byte := Mot.Poids_Faible
(Configuration.Buffer (I));
else
Lsb_Byte := Lsb_Byte - 1;
end if;
Configuration.Counter (I) :=
Mot.Construire (Msb_Byte, Lsb_Byte);
end if;
if Configuration.Counter (I) = 0 then
if Configuration.It_Enable (I) then
Set_Bit (Configuration.State, Num_Bit (I - 1));
if not Test_Bit (Configuration.State, Bit7) then
Set_Bit (Configuration.State, Bit7);
if Configuration.It_Connect then
Bus.It_From_Periph (Configuration.Periph_Id,
Configuration.Vector);
end if;
end if;
end if;
case Configuration.Fnct (I) is
when Continu =>
Configuration.Counter (I) :=
Configuration.Buffer (I);
when One_Shot =>
Configuration.Count (I) := False;
when None =>
Erreur.Detectee (Unknown_Conf);
end case;
end if;
end if;
end if;
end loop;
Write_Window (Configuration, Window_Id, Window_Enable,
Counter1_Show => True,
Counter2_Show => True,
Counter3_Show => True,
State_Show => True);
end Receive_Clock;
procedure Raz_Bit_It (Configuration : in out Ptm_Config;
Bit_Number : Octet.Num_Bit) is
begin
case Bit_Number is
when 0 =>
Octet.Res_Bit (Configuration.State, Bit0);
if not Octet.Test_Bit (Configuration.State, Bit1) and
not Octet.Test_Bit (Configuration.State, Bit2) then
Octet.Res_Bit (Configuration.State, Bit7);
end if;
when 1 =>
Octet.Res_Bit (Configuration.State, Bit1);
if not Octet.Test_Bit (Configuration.State, Bit0) and
not Octet.Test_Bit (Configuration.State, Bit2) then
Octet.Res_Bit (Configuration.State, Bit7);
end if;
when 2 =>
Octet.Res_Bit (Configuration.State, Bit2);
if not Octet.Test_Bit (Configuration.State, Bit0) and
not Octet.Test_Bit (Configuration.State, Bit1) then
Octet.Res_Bit (Configuration.State, Bit7);
end if;
when others =>
null;
end case;
end Raz_Bit_It;
procedure Do_Event_Window (Configuration : in out Ptm_Config;
Window_Id : Ihm.Window_Id;
Window_Enable : in out Boolean;
What_Kind : Ihm.Event.Kind;
Field_Name : String;
Str_Value : String) is
Value : Octet.T_Octet;
begin
case What_Kind is
when Ihm.Event.Pushbutton =>
if Field_Name = Close_Window then
Window_Enable := False;
end if;
when Ihm.Event.Fieldenter =>
if Field_Name = Control1_Field then
if Verif_Input.Is_Binary_Byte_Value (Str_Value) then
Configuration.Control (1) :=
Octet.Convert_String_Binaire (Str_Value);
Initialize_Timer (Configuration, Window_Id,
Window_Enable, 1);
else
Erreur.Detectee (Bad_Value);
Write_Window (Configuration, Window_Id, Window_Enable,
Control1_Show => True);
end if;
end if;
if Field_Name = Buffer1_Field then
if Verif_Input.Is_Hexadecimal_Word_Value (Str_Value) then
Configuration.Buffer (1) :=
Mot.Convert_String_Mot (Str_Value);
Configuration.Counter (1) := Configuration.Buffer (1);
Configuration.Count (1) := True;
Raz_Bit_It (Configuration, 0);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer1_Show => True,
Counter1_Show => True,
State_Show => True);
else
Erreur.Detectee (Bad_Value);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer1_Show => True);
end if;
end if;
if Field_Name = Control2_Field then
if Verif_Input.Is_Binary_Byte_Value (Str_Value) then
Configuration.Control (2) :=
Octet.Convert_String_Binaire (Str_Value);
Initialize_Timer (Configuration, Window_Id,
Window_Enable, 2);
else
Erreur.Detectee (Bad_Value);
Write_Window (Configuration, Window_Id, Window_Enable,
Control2_Show => True);
end if;
end if;
if Field_Name = Buffer2_Field then
if Verif_Input.Is_Hexadecimal_Word_Value (Str_Value) then
Configuration.Buffer (2) :=
Mot.Convert_String_Mot (Str_Value);
Configuration.Counter (2) := Configuration.Buffer (2);
Configuration.Count (2) := True;
Raz_Bit_It (Configuration, 1);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer2_Show => True,
Counter2_Show => True,
State_Show => True);
else
Erreur.Detectee (Bad_Value);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer2_Show => True);
end if;
end if;
if Ihm.Event.Get_Field (Window_Id) = Control3_Field then
if Verif_Input.Is_Binary_Byte_Value (Str_Value) then
Configuration.Control (3) :=
Octet.Convert_String_Binaire (Str_Value);
Initialize_Timer (Configuration, Window_Id,
Window_Enable, 3);
else
Erreur.Detectee (Bad_Value);
Write_Window (Configuration, Window_Id, Window_Enable,
Control3_Show => True);
end if;
end if;
if Field_Name = Buffer3_Field then
if Verif_Input.Is_Hexadecimal_Word_Value (Str_Value) then
Configuration.Buffer (3) :=
Mot.Convert_String_Mot (Str_Value);
Configuration.Counter (3) := Configuration.Buffer (3);
Configuration.Count (3) := True;
Raz_Bit_It (Configuration, 2);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer3_Show => True,
Counter3_Show => True,
State_Show => True);
else
Erreur.Detectee (Bad_Value);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer3_Show => True);
end if;
end if;
when others =>
Erreur.Detectee (Unknown_Event);
end case;
end Do_Event_Window;
task body Ptm_Task is
Configuration : Ptm_Config;
Register_Type : Natural;
Msb_Buffer : Octet.T_Octet := 0;
Lsb_Buffer : Octet.T_Octet := 0;
Is_Ctrl_1 : Boolean;
State_Lect : Boolean := False;
Window_Enable : Boolean := False;
Window_Id : Ihm.Window_Id;
begin
select
accept Init (Periph_Id : Periph.T_Periph_Number;
It_Vector : Octet.T_Octet;
Basic_Address : Mot.T_Mot;
Memory_Mapped : Boolean;
It_Connected : Boolean;
Identifier : T_Ptm_Number;
Number_Of_Register : out Natural) do
Number_Of_Register := 8;
Configuration.Vector := It_Vector;
Configuration.Address := Basic_Address;
Configuration.Mem_Mapped := Memory_Mapped;
Configuration.It_Connect := It_Connected;
Configuration.Identifier := Identifier;
Configuration.Periph_Id := Periph_Id;
end Init;
Reset_Ptm (Configuration, Window_Id, Window_Enable);
or
terminate;
end select;
loop
select
accept Reset do
null;
end Reset;
Reset_Ptm (Configuration, Window_Id, Window_Enable);
or
accept Access_Register (Put) (Register_Number : Natural;
Value : in out Octet.T_Octet) do
State_Lect := False;
Register_Type := Register_Number;
case Register_Type is
when 1 =>
Lsb_Buffer := Mot.Poids_Faible
(Configuration.Control (2));
if Octet.Test_Bit (Lsb_Buffer, 0) then
Configuration.Control (1) := Value;
Is_Ctrl_1 := True;
else
Configuration.Control (3) := Value;
Is_Ctrl_1 := False;
end if;
when 2 =>
Configuration.Control (2) := Value;
when 3 =>
Msb_Buffer := Value;
when 4 =>
if not Octet.Test_Bit
(Configuration.Control (1), Bit4) or
Configuration.Intern_Init then
Configuration.Buffer (1) :=
Mot.Construire (Msb_Buffer, Value);
Configuration.Counter (1) :=
Configuration.Buffer (1);
Configuration.Count (1) := True;
end if;
when 5 =>
Msb_Buffer := Value;
when 6 =>
if not Octet.Test_Bit
(Configuration.Control (2), Bit4) or
Configuration.Intern_Init then
Configuration.Buffer (2) :=
Mot.Construire (Msb_Buffer, Value);
Configuration.Counter (2) :=
Configuration.Buffer (2);
Configuration.Count (2) := True;
end if;
when 7 =>
Msb_Buffer := Value;
when 8 =>
if not Octet.Test_Bit
(Configuration.Control (3), Bit4) or
Configuration.Intern_Init then
Configuration.Buffer (3) :=
Mot.Construire (Msb_Buffer, Value);
Configuration.Counter (3) :=
Configuration.Buffer (3);
Configuration.Count (3) := True;
end if;
when others =>
null;
end case;
end Access_Register;
case Register_Type is
when 1 =>
if Is_Ctrl_1 then
Initialize_Timer (Configuration, Window_Id,
Window_Enable, 1);
else
Initialize_Timer (Configuration, Window_Id,
Window_Enable, 3);
end if;
when 2 =>
Initialize_Timer (Configuration, Window_Id,
Window_Enable, 2);
when 4 =>
Raz_Bit_It (Configuration, 0);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer1_Show => True,
Counter1_Show => True,
State_Show => True);
when 6 =>
Raz_Bit_It (Configuration, 1);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer2_Show => True,
Counter2_Show => True,
State_Show => True);
when 8 =>
Raz_Bit_It (Configuration, 2);
Write_Window (Configuration, Window_Id, Window_Enable,
Buffer3_Show => True,
Counter3_Show => True,
State_Show => True);
when others =>
null;
end case;
or
accept Access_Register (Get) (Register_Number : Natural;
Value : in out Octet.T_Octet) do
Register_Type := Register_Number;
case Register_Type is
when 2 =>
Value := Configuration.State;
when 3 =>
Value := Mot.Poids_Fort (Configuration.Counter (1));
when 4 =>
Value := Mot.Poids_Faible
(Configuration.Counter (1));
when 5 =>
Value := Mot.Poids_Fort (Configuration.Counter (2));
when 6 =>
Value := Mot.Poids_Faible
(Configuration.Counter (2));
when 7 =>
Value := Mot.Poids_Fort (Configuration.Counter (3));
when 8 =>
Value := Mot.Poids_Faible
(Configuration.Counter (3));
when others =>
null;
end case;
end Access_Register;
if State_Lect and (Register_Type = 3 or Register_Type = 5 or
Register_Type = 7) then
case Register_Type is
when 3 =>
Raz_Bit_It (Configuration, Bit0);
Write_Window (Configuration, Window_Id,
Window_Enable,
State_Show => True);
when 5 =>
Raz_Bit_It (Configuration, Bit1);
Write_Window (Configuration, Window_Id,
Window_Enable,
State_Show => True);
when 7 =>
Raz_Bit_It (Configuration, Bit2);
Write_Window (Configuration, Window_Id,
Window_Enable,
State_Show => True);
when others =>
null;
end case;
end if;
if Register_Type /= 2 then
State_Lect := False;
else
State_Lect := True;
end if;
or
accept Clock do
null;
end Clock;
if not Configuration.Intern_Init then
Receive_Clock (Configuration, Window_Id, Window_Enable);
end if;
or
accept Kill;
exit;
or
accept Open_Window (Wid : Ihm.Window_Id) do
Window_Id := Wid;
Window_Enable := True;
end Open_Window;
Write_Window (Configuration, Window_Id, Window_Enable,
Identifier_Show => True,
Vector_Show => True,
Address_Show => True,
Mem_Mapped_Show => True,
It_Connect_Show => True,
Control1_Show => True,
Buffer1_Show => True,
Counter1_Show => True,
Control2_Show => True,
Buffer2_Show => True,
Counter2_Show => True,
Control3_Show => True,
Buffer3_Show => True,
Counter3_Show => True,
State_Show => True);
or
accept Do_Event (What_Kind : Ihm.Event.Kind;
Field_Name : String;
Value : String) do
if Window_Enable then
Do_Event_Window (Configuration, Window_Id,
Window_Enable, What_Kind,
Field_Name, Value);
end if;
end Do_Event;
or
terminate;
end select;
end loop;
end Ptm_Task;
end Ptm_Pack;