REAL-TIME SYSTEMS AND PROGRAMMING LANGUAGES Solutions to Selected Exercises A. Burns and A.J. Wellings Department of Computer Science, University of York, UK email fburns,andyg@cs.york.ac.uk September 1998 Abstract begin null; end; This note gives examples of solutions to the exercises in our book "Real-Time Systems and Programming Languages". No guarantee is given that the questions or answers are correct or consistent. with Look; function Get_Punctuation return Punctuation is P : Punctuation; begin loop begin P := Look.Read; exit; exception when others => null; end; end loop; return P; end Get_Punctuation; Chapter 6 { Question 6.2 with Character_Io; package body Look is function Test_Char(C : Character) return Boolean is begin -- returns true is valid alpha -- numeric character else false end; Question 6.3 function Read return Punctuation is C :Character; begin loop C := Character_Io.Get; if Test_Char(C) /= True then if C = `.' then Character_Io.Flush; return Period; end if; if C = `,' then Character_Io.Flush; return Comma; end if; if C = `;' then Character_Io.Flush; return Semicolon; end if; raise Illegal_Punctuation; end if; end loop; exception when Illegal_Punctuation => Character_Io.Flush; raise; -- or raise ILLEGAL_PUNCTUATION when Io_Error => Character_Io.Flush; raise; end Read; procedure Reliable_Heater_Off is type Stage is (First, Second, Third, Fourth); begin for I in Stage loop begin case I is when First => Heater_Off; exit; when Second => Increase_Coolant; exit; when Third => Open_Valve; exit; when Fourth => Panic; exit; end case; exception when Heater_Stuck_On | Temperature_Still_Rising | Valve_Stuck => null; end; end loop; end Reliable_Heater_Off; 1 Question 6.7 parent can busy-wait using the 'terminated ag. However, if busy-waiting is to be avoided then some form of IPC mechanism must be used. In the rst code fragment, the exception cannot be handled by the Do Something procedure. The domain is the calling code. In the second code fragment, the exception can be handled by the Do Something procedure. The domain is the procedure. In the third code fragment, the exception can be handled within the inner block declared within the procedure. This block is the domain. Question 7.4 211 we think! Question 7.8 Chapter 7 { Question 7.1 The following points need to be made: Although arrays of tasks can be created easily, assigning values to their discriminants is awkward. An early version of Ada 95 incorporated new syntax to allow this; however, during the language's scope reduction, this was removed. The same eect can be achieved by calling a function with a side eect. an exception will not propagate beyond a task, even if it caused the task to terminate a scope cannot exit (even to propagate an exception) if they are none terminated tasks dependent on that scope. package Count is function Assign_Number return Index; end Count; an exception raised in the elaboration of the declarative part of a task will cause that task to fail (without beginning its execution); moreover the parent of that task will have "tasking error" raised before it can state executing. task type X(I : Index := Count.Assign_Number); type Xa is array (Index) of X; These points are illustrated by the behaviour (output) of the program. If C = 2 then no exceptions are raised and the following output is generated: Where the body of Count is package body Count is Number : Index := Index'First; function Assign_Number return Index is begin return Number; Number := Number + 1; end Assign_Number; end Count; A Started Main Procedure Started P Started P Finished (* DELAY 10 second *) T Finished A Finished Xtasks : Xa; Note the output "Main Procedure Started" could occur rst second or third. When C = 1 then the procedure P will fail. But the exception (constraint error or numeric error) cannot propagate for 10 seconds until task T has completed. Its propagation will cause A to fail (hence no A nished message) but the main program will be unaected: Question 7.2 For two tasks: procedure Cobegin is task A; task B; A Started Main Procedure Started P Started (* DELAY 10 second *) T Finished task body A is separate; task body B is separate; begin null; end Cobegin; Finally when C=0 then A will fail during elaboration of its declarative part and hence it will never start to execute; moreover the main program will get tasking error raised at its starts and hence it will not begin. The output is simply: Question 7.3 A fork is simply creation of a process dynamically. This can be done easily in Ada. The join is more problematic. Notionally, given the identity of the task created, the Main Procedure Failed 2 Question 7.9 var For task A, the parent is the main task, its children are and D, its master is Hierarchy and its dependents are and D. For task Pointerb.all, the parent is C, it has no children, its master is Hierarchy and it has no dependents. For task Another Pointerb.all, the parent is D, it has no children, its master is Hierarchy and it has no dependents. For task C, the parent is A, its child is Pointerb.all, its master is A and it has no dependents. For task D, the parent is A, its child is Another Pointerb.all, its master is A and it has no dependents. Procedure Main has no direct parent, children, master or dependents Procedure Hierarchy has no direct parent, children, or master. Its dependents are A, Pointerb.all, and Another Pointerb.all. x_count : integer :=0; x_temp : integer :=0; C C P(x_mutex) B x_count := x_count +1; V(x_mutex); P(x_wait); B x_temp := x_temp +1; x_temp =< x_count V(x_wait); if not mutex( if x_count > 0 x_temp := 1; V(x_wait); then else V(x_mutex); end ; Question 8.4 1); readcount := 0; (* reader processes *) For mutual exclusion: mutex : semaphore(initial 1); For signalling processes suspended: next : semaphore(initial 0); For each condition: x_sem : semaphore(0); Counts: next_count : integer :=0; x_count : integer :=0; P(mutex) readcount := readcount +1; readcount = 1 P(wrt); V(mutex) then (* read data structure *) P(mutex) readcount := readcount -1; readcount = 0 V(wrt); V(mutex) if then S1; initial 1); wrt( initial if then while not do if else V(x_mutex); end if ; P(x_wait); end loop ; x_count := x_count -1; end if ; Chapter 8 { Question 8.2 var semaphore ( initial 1); semaphore ( initial x_mutex x_wait then For each procedure: P(mutex); body; next_count > 0 V(next); if else V(mutex); end if ; (* writer processes *) P(wrt) (* write data structure *) V(wrt) then For each wait on condition x Question 8.3 x_count := x_count +1; next_count > 0 V(next); if else Hoare's conditional critical region is of the form: region x when B do S1; then V(mutex); P(x_sem); x_count := x_count -1; In the following solution: x wait is a semaphore used for processes waiting for their guard to be TRUE; and x count is the number waiting. When the region is left we scan down the queue to see if any process can continue. We use x temp to keep track of the number of processes we have rescheduled (otherwise we would just loop). For each signal on condition x if end if 3 then x_count > 0 next_count := next_count + 1; V(x_sem); P(next); next_count := next_count - 1; ; 0); Question 8.5 readers : integer; writing : boolean; oktoread, oktowrite : signals; interface module semaphores; dene semaphore, P, V, init; type semaphore = record taken : boolean; free : signal; end ; procedure P(var s:semaphore); begin if s.taken then wait(s.free) end; s.taken := true; end P; procedure begin V( var procedure startread; begin if writing or waited(oktowrite) then wait(oktoread) end ; readers := readers+1; send(oktoread) startread; end procedure endread; begin readers := readers -1; if readers = 0 then send(oktowrite) end end endread; procedure startwrite; begin if readers <> 0 OR writing then wait(oktowrite) end ; writing := true end startwrite; procedure endwrite; begin writing := false; if waited(oktowrite) then send(oktowrite) else send(oktoread) end endwrite; begin s:semaphore); s.taken := false; send(s.free); ; end procedure init( var begin s.taken := false; end ; end s:semaphore) ; To extend to the general semaphore the boolean becomes a count. Init takes an initial value of type integer. P only blocks when the count is 0. Question 8.6 interface module diskheadscheduler; dene request, release; use maxcyl; var headpos : integer; reader :=0; writing := false sharedfile; up, down : boolean; upsweep, downsweep : signal; end procedure request(dest:integer); begin if busy then if headpos < dest then wait(upsweep,dest) else wait(downsweep,maxcyl-dest) end end ; busy := true; headpos := dest; end request; procedure release; begin busy := false; if up then if awaited(upsweep) then send(upsweep) else up:= false; send(downsweep) end else if awaited(downsweep) then send(downsweep) else up := true; send(upsweep) end end release; end diskheadscheduler; Question 8.8 INTERFACE MODULE lights; DEFINE enter_cars, exit_cars; USE set_lights; CONST N = ...; VAR in_tunnel : NATURAL; lights_green, more_cars : signal; PROCEDURE enter_cars(I : NATURAL); BEGIN in_tunnel := in_tunnel + I; IF in_tunnel >= N THEN set_lights(RED); wait(lights_green); END; signal(more_cars); END enter_cars; Question 8.7 interface module var sharedfile; PROCEDURE exit_cars(I : NATURAL); BEGIN in_tunnel := in_tunnel - I; 4 IF in_tunnel < N THEN set_lights(GREEN); signal(lights_green); END; IF in_tunnel = 0 THEN wait(more_cars); END; END enter_cars; procedure produce(char : character); ... WaitUntil buffer.size < N -- place char in buffer end ; function consume return character; ... WaitUntil buffer.size > 0 BEGIN in_tunnel := 0; set_lights(GREEN); END lights; -- take char out of buffer; char; return end; end; PROCESS entrance_monitor; BEGIN LOOP lights.enter_cars(cars_entered); delay_10_seconds; END; END; Question 8.10 MODULE smokers ; TYPE ingredients = (TOBandMAT,TOBandPAP,PAPandMAT); PROCESS exit_monitor; BEGIN LOOP lights.exit_cars(cars_exited); delay_10_seconds; END; END; INTERFACE MODULE controller; DEFINE get, put, release; USE ingredients; VAR TP, MP, PP : signal; TAM, TAP, PAM : signal; Question 8.9 PROCEDURE get ( ingred : ingredients); BEGIN (* called by smokers *) CASE ingred OF TOBandMAT: BEGIN (* Paper Process *) IF NOT awaited(PP) THEN wait(TAM) END; (* ingredients available *) END; The criticism of condition synchronisation is that wait and signal are like sempahore operations and therefore unstructured. A signal on the wrong condition may be dicult to detect. They are therefore too low level and unstructured. The WaitUntil primitive removes the need for condition variables and therefor wait and signal. the problem how to implement it. If a process is blocked because its boolean expression is false then it must give up the monitor lock to allow other processes to enter and change the variables in the expression. So the issue is when to reevaluate the guards. As the monitor does not know if the variables in a boolean expression have been altered, all boolean expressions must be revaluated EVERY TIME a process releases the monitor lock. This is inecient and therefore not used. The object to this approach may be invalid if we have a multi processor system with shared memory where each processor only executes a single process. If this is the case then the process can continually check its guards as the processor is unable to execute another process. buffer_controller : monitor type buffer_t is record slots : array (1..N) of character; size : integer range 0..N; head, tail : integer range 1..N; end record ; TOBandPAP: BEGIN (* Matches Process *) IF NOT awaited(MP) THEN wait(TAP) END; (* ingredients available *) END; PAPandMAT: BEGIN (* Tobacco Process *) IF NOT awaited(TP) THEN wait(PAM) END; (* ingredients available *) END END END get; PROCEDURE release ( ingred : ingredients); BEGIN (* called by smokers *) (* releases agent *) CASE ingred OF TOBandMAT: BEGIN (* Paper Process *) send (PP) END; buffer : buffer_t; 5 int waiting_writers; /* data */ g shared_data; TOBandPAP: BEGIN (* Matches Process *) send (MP) END; int start_read(shared_data *D) f PTHREAD_MUTEX_LOCK(&D->mutex); while(D->writing > 0 || D->waiting_writers > 0) f PTHREAD_COND_WAIT(&(D->ok_to_read), &(D->mutex)); PAPandMAT: BEGIN (* Tobacco Process *) send (TP) END END END release; g g; PROCEDURE put ( ingred : ingredients); BEGIN (* called by agent *) (* place ingredients on the table *) CASE ingred OF TOBandMAT: BEGIN (* looking for Paper Process *) IF awaited(TAM) THEN send(TAM) END; wait(PP) END; D->readers++; PTHREAD_MUTEX_UNLOCK(&D->mutex); return 0; int end_read(shared_data *D) f PTHREAD_MUTEX_LOCK(&D->mutex); if(--D->readers == 0 ) f PTHREAD_COND_SIGNAL(&D-> ok_to_write); g; PTHREAD_MUTEX_UNLOCK(&D->mutex); return 0; g int start_write(shared_data *D) f PTHREAD_MUTEX_LOCK(&D->mutex); D->waiting_writers++; while(D->writing > 0 || D->readers > 0) f PTHREAD_COND_WAIT(&(D->ok_to_write), &(D->mutex)); TOBandPAP: BEGIN (* Matches Process *) IF awaited(TAP) THEN send(TAP) END; wait(MP) END; g g; PAPandMAT: BEGIN (* looking for Tobacco Process *) IF awaited(PAM) THEN send(PAM) END; wait(TP) END D->writing++; D->waiting_writers--; PTHREAD_MUTEX_UNLOCK(&D->mutex); return 0; int end_write(shared_data *D) f PTHREAD_MUTEX_LOCK(&D->mutex); D->writing = 0; if(D->waiting_writers != 0 ) f PTHREAD_COND_SIGNAL(&D-> ok_to_write); END END put; END controller; g PROCESS smoker (requires : ingredients); BEGIN LOOP controller.get(requires); (* roll and smoke cigarette *) controller.release(requires) END END smoker; PTHREAD_MUTEX_UNLOCK(&D->mutex); return 0; else f PTHREAD_COND_BROADCAST(&D-> ok_to_read); g g int main() f /* ensure all mutexes and condition variables are initialised */ g Question 8.18 BEGIN smoker(TOBandMAT); smoker(TOBandPAP); smoker(PAPandMAT) END smokers. with Ada.Text_Io; use Ada.Text_Io; with Ada.Exceptions; use Ada.Exceptions; with Ada.Numerics.Discrete_Random; procedure Smokers2 is Question 8.14 type Need is (T_P, T_M, M_P); package Smoking_Io is new Enumeration_Io(Need); package Random_Ingredients is new Ada.Numerics.Discrete_Random(Need); #include "mutex.h" typedef struct f pthread_mutex_t mutex; pthread_cond_t ok_to_read; pthread_cond_t ok_to_write; int readers; int writing; task type Smoker(My_Needs : Need); task Active_Agent; 6 protected Agent is procedure Give(Ingredients : Need); entry Give_Matches(N : Need; Ok : out Boolean); entry Give_Paper(N : Need; Ok : out Boolean); entry Give_Tobacco(N : Need; Ok : out Boolean); procedure Cigarette_Finished; entry Wait_Smokers; private T_Available, M_Available, P_Available : Boolean := False; Allocated_T, Allocated_P, Allocated_M : Boolean; All_Done : Boolean := False; Ingredients : Need; end Agent; protected body Agent is procedure Give(Ingredients : Need) is begin case Ingredients is when T_P => T_Available := True; P_Available := True; M_Available := False; Put("agent has "); when T_M => T_Available := True; M_Available := True; P_Available := False; when M_P => M_Available := True; P_Available := True; T_Available := False; end case; Put("agent has "); Smoking_Io.Put(Ingredients); Put_Line(" for smokers"); Allocated_T := False; Allocated_P := False; Allocated_M := False; end Give; task body Smoker is Got : Boolean; begin Smoking_Io.Put(My_Needs); loop Got := False; case My_Needs is when T_P => while not Got loop Agent.Give_Tobacco(My_Needs, Got); delay 0.1; end loop; Agent.Give_Paper(My_Needs, Got); when T_M => while not Got loop Agent.Give_Tobacco(My_Needs, Got); delay 0.1; end loop; Agent.Give_Matches(My_Needs, Got); when M_P => while not Got loop Agent.Give_Matches(My_Needs, Got); delay 0.1; end loop; Agent.Give_Paper(My_Needs, Got); end case; if not Got then raise Program_Error; end if; -- make and smoke cigarette Smoking_Io.Put(My_Needs); Put_Line(" smoking!"); delay 1.0; Agent.Cigarette_Finished; end loop; exception when E: others => Put(Exception_Name(E)); Put(" exception caught in "); Smoking_Io.Put(My_Needs);Put_Line("smoker"); end Smoker; entry Give_Tobacco(N : Need; Ok : out Boolean) when T_Available and not Allocated_T is begin if (Allocated_M and N = T_M) or (Allocated_P and N = T_P ) or (M_Available and N = T_M) or (P_Available and N = T_P) then Ok := True; Allocated_T := True; else Ok := False; end if; if Ok then Put("agent: given out tobacco to "); Smoking_Io.Put(N); Put_Line(" smoker"); else Put("agent: refusing tobacco to "); Smoking_Io.Put(N); Put_Line(" smoker"); end if; end Give_Tobacco; entry Give_Matches(N : Need; Ok : out Boolean) when M_Available and not Allocated_M is begin if (Allocated_T and N = T_M) or (Allocated_P and N = M_P) or (T_Available and N = T_M) or (P_Available and N = M_P) then Ok := True; Allocated_M := True; else Ok := False; end if; if Ok then Put("agent: given out matches to "); Smoking_Io.Put(N); Put_Line(" smoker"); else Put("agent: refusing matches to "); Smoking_Io.Put(N); Put_Line(" smoker"); end if; end Give_Matches; task body Active_Agent is Gen : Random_Ingredients.Generator; Ingredients : Need; begin Random_Ingredients.Reset(Gen); loop -- chose two items randomly and set -- t_available, m_available, p_available to -- true or false correspondingly Ingredients := Random_Ingredients.Random(Gen); Agent.Give(Ingredients); Agent.Wait_Smokers; end loop; end Active_Agent; entry Give_Paper(N : Need; Ok : out Boolean) when P_Available and not Allocated_P is 7 begin if (Allocated_M and N = M_P) or (Allocated_T and N = T_P) or (M_Available and N = M_P) or (T_Available and N = T_P ) then Ok := True; Allocated_P := True; else Ok := False; end if; if Ok then Put("agent: given out paper to "); Smoking_Io.Put(N); Put_Line(" smoker"); else Put("agent: refusing paper to "); Smoking_Io.Put(N); Put_Line(" smoker"); end if; end Give_Paper; procedure Cigarette_Finished is begin All_Done := True; end; end select; end loop; end Semaphore; If task is aborted, the semaphore is deadlocked. Question 9.3 A tasking implementation might be more expensive but it allows the semaphore to timeout on the signal operation and release it for other tasks. Question 9.4 Assuming a task which implements a sempahore. For mutual exclusion: mutex : semaphore; For signalling processes suspended: next : semaphore; For each condition: x_cond : semaphore; entry Wait_Smokers when All_Done is begin All_Done := False; end Wait_Smokers; next and x_cond must be initialised so next.P; x_cond.P; end Agent; Tp : Smoker(T_P); Tm : Smoker(T_M); Mp: Smoker(M_P); For each procedure: mutex.P; body; next.P'count > 0 next.V; if else mutex.V end if begin null; end Smokers2; then For each wait on condition x next.wait'count > 0 next.V; if else Chapter 9 { Question 9.1 then mutex.V; x_cond.P; NO, each queue is in FIFO order, there is no time information available. For each signal on condition x x_cond.P > 0 x_cond.V; next.P; ; if Question 9.2 then end if This will not work because of 'count; we must keep explicit count to avoid the race condition. subtype Binary_Value is Integer range 0 ..1 ; task type Semaphore(Value : Binary_Value := 0) is entry P; entry V; end Semaphore; Question 9.5 task body Semaphore is begin loop select when Value = One => accept P; Value := 0; or accept V; Value := 1; or terminate; PROC voter(CHAN OF INT in1, in2, in3, out1, out2, switch) INT Data BOOL Chan1 BOOL swt SEQ WHILE TRUE SEQ chan1 := TRUE swt := FALSE PRI ALT switch ? any SEQ 8 chan1 := NOT chan1 swt := TRUE in1 ? Data in2 ? Data in3 ? Data end select; end loop; end Light_Controller; Question 9.8 IF not swt if chan1 out1 ! Data TRUE out2 ! Data TRUE SKIP #include "sig.h" #include "mqueue.h" #define #define #define #define #define #define #define : Question 9.7 SWITCH_CHAN SIGRTMIN +1 CHANS SIGRTMIN +2 OUT1 1 OUT2 2 IN1 1 IN2 2 IN3 2 #define DEFAULT_NBYTES 1 int nbytes = DEFAULT_NBYTES; task Entry_Detector; task Exit_Detector; task Lights_Controller is entry Cars_Left(X : Natural); entry Cars_Arrived(X : Natural); end Lights_Controller; #define MQ_IN1 "/mq_in1" #define MQ_IN2 "/mq_in2" #define MQ_IN3 "/mq_in3" #define MQ_OUT1 "/mq_out1" #define MQ_OUT2 "/mq_out2" #define MQ_SWITCH "/mq_switch" int current_chan = OUT1; task body Entry_Detector is Tmp : Natural; begin loop Tmp := Cars_Entered; if Tmp > 0 then Lights_Controller.Cars_Arrived(Tmp); end if; delay 10.0; end loop; end Entry_Detector; mqd_t mq_in1, mq_in2, mq_in3; /* one queue for each input channel */ mqd_t mq_out1, mq_out2; /* one queue for each output */ mqd_t mq_switch; /* one queue for switch */ struct mq_attr ma; /* queue attributes */ int err; char buf[1]; void change_chan(int signum, siginfo_t *data, void *extra) f if(current_chan == 1) current_chan = 2; else current_chan = 1; task body Exit_Detector is Tmp : Natural; begin loop Tmp := Cars_Exited; if Tmp > 0 then Lights_Controller.Cars_Left(Tmp); end if; delay 10.0; end loop; end Exit_Detector; g void input_chans(int signum, siginfo_t *data, void *extra) f unsigned int pri; if(data -> si_value.sival_int == IN1) f if((err = mq_receive(mq_in1, &buf[0], nbytes, &pri)) < 0) f exit(3); g; gelse f /* similarly for IN2 and IN3 */ g; if(current_chan == 1) f if((err = mq_send(mq_out1, &buf[0], nbytes, 0)) < 0) f exit(3); g; gelse f if((err = mq_send(mq_out1, &buf[0], nbytes, 0)) < 0) f exit(3); g; task body Lights_Controller is N : constant Natural := ??; -- varies according to tunnel Current : Natural := 0; begin loop select accept Cars_Arrived(X : Natural) do Current := Current + X; end Cars_Arrived; if Current > N then Set_Lights(Red); end if; or accept Cars_Left(X : Natural) do Current := Current - X; end Cars_Left; if Current < N then Set_Lights(Green); end if; or terminate; g g int select() f sigset_t mask, omask; 9 g struct sigaction s, os; struct sigevent se; Question 9.9 /* set up signal mask */ sigemptyset(&mask); sigaddset(&mask, SWITCH_CHAN); sigaddset(&mask, CHANS); with Ada.Text_Io; use Ada.Text_Io; with Ada.Exceptions; use Ada.Exceptions; with Ada.Numerics.Discrete_Random; procedure Smokers is s.sa_flags = 0; s.sa_mask = mask; /* set up handlers */ s.sa_sigaction = & change_chan; sigaction(SWITCH_CHAN, &s, &os); type Need is (T_P, T_M, M_P); package Smoking_Io is new Enumeration_Io(Need); package Random_Ingredients is new Ada.Numerics.Discrete_Random(Need); s.sa_sigaction = &input_chans; sigaction(CHANS, &s, &os); task type Smoker(My_Needs : Need); /* set message queues attributes*/ ma.mq_flags = 0; /* No special behaviour */ ma.mq_maxmsg = 1; ma.mq_msgsize = nbytes; task Agent is entry Give_Matches(N : Need; Ok : out Boolean); entry Give_Paper(N : Need; Ok : out Boolean); entry Give_Tobacco(N : Need; Ok : out Boolean); entry Cigarette_Finished; end Agent; if (( mq_in1 = mq_open(MQ_IN1, O_RDONLY, MODE, &ma)) < 0) f /* indicate error */ exit(1); g; /* similarly for the other two input queues */ task body Smoker is Got : Boolean; begin Smoking_Io.Put(My_Needs); loop Got := False; if (( mq_out1 = mq_open(MQ_OUT1, O_CREAT|O_EXCL, MODE, &ma)) < 0) f /* indicate error */ exit(1); g; /* similarly for the other output queues */ case My_Needs is when T_P => while not Got loop Agent.Give_Tobacco(My_Needs, Got); end loop; Agent.Give_Paper(My_Needs, Got); when T_M => while not Got loop Agent.Give_Tobacco(My_Needs, Got); end loop; Agent.Give_Matches(My_Needs, Got); when M_P => while not Got loop Agent.Give_Matches(My_Needs, Got); end loop; Agent.Give_Paper(My_Needs, Got); end case; if not Got then raise Program_Error; end if; -- make and smoke cigarette Smoking_Io.Put(My_Needs); Put_Line(" Smoking!"); delay 1.0; Agent.Cigarette_Finished; end loop; exception when E: others => Put(Exception_Name(E)); Put(" exception caught in "); Smoking_Io.Put(My_Needs);Put_Line("smoker"); end Smoker; if (( mq_switch = mq_open(MQ_SWITCH, O_RDONLY, MODE, &ma)) < 0) f /* indicate error */ exit(1); g; sigprocmask(SIG_BLOCK, &mask, &omask); se.sigev_notify = SIGNAL; se.sigev_signo = CHANS; se.sigev_value.sival_int = IN1; if((err = mq_notify(mq_in1, & se)) < 0) f exit(3); g; /* similarly for other input channels */ se.sigev_notify = SIGNAL; se.sigev_signo = SWITCH_CHAN; se.sigev_value.sival_int = 0; if((err = mq_notify(mq_switch, & se)) < 0) f exit(3); g; Tp : Smoker(T_P); Tm : Smoker(T_M); Mp: Smoker(M_P); sigprocmask(SIG_UNBLOCK, &mask, &omask); task body Agent is T_Available, M_Available, P_Available : Boolean; /* need to sleep here*/ 10 Allocated_T, Allocated_P, Allocated_M : Boolean; Gen : Random_Ingredients.Generator; Ingredients : Need; begin Random_Ingredients.Reset(Gen); loop -- chose two items randomly and set -- T_AVAILABLE, M_AVAILABLE, P_AVAILABLE to -- TRUE or FALSE correspondingly Ingredients := Random_Ingredients.Random(Gen); case Ingredients is when T_P => T_Available := True; P_Available := True; M_Available := False; Put("Agent has "); when T_M => T_Available := True; M_Available := True; P_Available := False; when M_P => M_Available := True; P_Available := True; T_Available := False; end case; Put("Agent has "); Smoking_Io.Put(Ingredients); Put_Line(" for smokers"); Allocated_T := False; Allocated_P := False; Allocated_M := False; loop select when T_Available and not Allocated_T => accept Give_Tobacco(N : Need; Ok : out Boolean) do if (Allocated_M and N = T_M) or (Allocated_P and N = T_P ) or (M_Available and N = T_M) or (P_Available and N = T_P) then Ok := True; Allocated_T := True; else Ok := False; end if; if Ok then Put("Agent: given out Tobacco to "); Smoking_Io.Put(N); Put_Line(" Smoker"); else Put("Agent: refusing Tobacco to "); Smoking_Io.Put(N); Put_Line(" Smoker"); end if; end Give_Tobacco; or when M_Available and not Allocated_M => accept Give_Matches(N : Need; Ok : out Boolean) do if (Allocated_T and N = T_M) or (Allocated_P and N = M_P) or (T_Available and N = T_M) or (P_Available and N = M_P) then Ok := True; Allocated_M := True; else Ok := False; end if; if Ok then Put("Agent: given out Matches to "); Smoking_Io.Put(N); Put_Line(" Smoker"); else Put("Agent: refusing Matches to "); 11 Smoking_Io.Put(N); Put_Line(" Smoker"); end if; end Give_Matches; or when P_Available and not Allocated_P=> accept Give_Paper(N : Need; Ok : out Boolean) do if (Allocated_M and N = M_P) or (Allocated_T and N = T_P) or (M_Available and N = M_P) or (T_Available and N = T_P ) then Ok := True; Allocated_P := True; else Ok := False; end if; if Ok then Put("Agent: given out Paper to "); Smoking_Io.Put(N); Put_Line(" Smoker"); else Put("Agent: refusing Paper to "); Smoking_Io.Put(N); Put_Line(" Smoker"); end if; end Give_Paper; end select; if (Allocated_P and Allocated_T) or (Allocated_M and Allocated_T) or (Allocated_P and Allocated_M) then accept Cigarette_Finished; exit; end if; end loop; end loop; exception when E: others => Put(Exception_Name(E)); Put_Line(" exception caught in Agent"); end Agent; begin null; end Smokers; Question 9.10 task body Server is type Service is (A, B, C); Next : Service := A; begin loop select when Next = A or (Next = B and Service_B'Count = 0 and Service_C'Count = 0) or (Next = C and Service_C'Count = 0) => accept Service_A do Next := B; end; or when Next = B or (Next = C and Service_A'Count = 0 and Service_C'Count = 0) or (Next = A and Service_A'Count = 0) => accept Service_B do Next := C; end; or when Next = C or (Next = A and Service_A'Count = 0 and Service_B'Count = 0) or (Next = B and Service_B'Count = 0) => accept Service_C do Next := A; end; or terminate; raised but unhandled (note the exception doesn't propagate to main). The exception will also propagate to block Z is task TWO where it will be handled, the handler however raises exception C which is handled by block Y. The following will therefore be printed: "B trapped in sync" "B trapped in block Z" "C trapped in Y" "B trapped in one" (3) If exception C is raised it is trapped inside the rendezvous. The handler then raises D which is propagated the task ONE and block Z. Block Z catches D with when others and then raises C which is trapped by block Y's when others. The following will therefore be printed: "C trapped in sync" "others trapped in Z" "C trapped in Y" "C trapped in one". (4) If exception D is raised it is not trapped by sync and therefore propagates to ONE. Block Z catches D with when others and then raises C which is trapped by block Y's when others. The following will therefore be printed: "others trapped in Z" "C trapped in Y" "D trapped in one". end select; end loop; end Server; Question 9.11 It is not possible for the select statement to select the task which has been waiting the longest time for service. The server would have to be modied so that it had a single entry, all tasks would then queue up in FIFO. Question 9.12 VAL INT ATurn is 1: VAL INT BTurn is 2: VAL INT CTurn is 3: INT Turn: SEQ Turn := ATurn WHILE True SEQ PRI ALT Turn = ATurn & serviceA ? any -- service request Turn := BTurn SKIP IF Turn = ATurn Turn := BTurn TRUE SKIP PRI ALT Turn = BTurn & serviceB ? any -- service request Turn := CTurn SKIP IF Turn = BTurn Turn := CTurn TRUE SKIP PRI ALT Turn = CTurn & serviceC ? any -- service request Turn := ATurn SKIP PRI ALT serviceA ? any -- service request Turn := BTurn serviceB ? any -- service request Turn := CTurn serviceC ? any -- service request Turn := ATurn Question 10.8 INT x,y,z; DIALOG primary SHARES (x,y); DIALOG secondary SHARES (y,z); FUNCTION primary IS BEGIN RETURN TRUE; END primary; FUNCTION secondary IS BEGIN RETURN TRUE; END primary; PROCESS A BEGIN ... SELECT DISCUSS primary BY -- A_primary -- uses x,y TO ARRANGE A_acceptance_test; OR DISCUSS secondary BY -- A_secondary -- uses y,z TO ARRANGE A_acceptance_test; ELSE ERROR; END SELECT; Question 9.13 ... END A; (1) If exception A is raised it is trapped inside the rendezvous and therefore the only message to appear is "A trapped in sync". (2) If exception B is raised it is trapped inside the rendezvous but then re-raised. This will propagate the exception to task ONE where it will be trapped and C PROCESS B BEGIN ... SELECT DISCUSS primary BY -- B_primary 12 -- uses x,y TO ARRANGE B_acceptance_test; end loop; end loop; end Controller; OR DISCUSS secondary BY -- B_secondary -- uses y,z TO ARRANGE B_acceptance_test; ELSE ERROR; END SELECT; Question 11.4 Assuming that tasks are queued on entries in priority order: ... END B; type Request_Range is range 1..Max; Note that there is no need for the global acceptance test. protected Resource_Controller is entry Request(R : out Resource; Amount : Request_Range); procedure Free(R : Resource; Amount : Request_Range); private Freed : Request_Range := Request_Range'Last; Queued : Natural := 0; ... end Resource_Controller; Chapter 11 { Question 11.1 It will fail because of the execution of the select statement is not an atomic operation. It is possible for a task calling the urgent entry to timeout or abort after the evaluation of the guards to the medium or low priority entries but before the rendezvous is accepted. If this is the only task on the queue then both the other entries are closed even though there is no available entry on the urgent entry. An entries on the medium and low priority queues are blocked. The reason you cannot extend the solution to a numeric solution with a range of 0 to 1000 is that it is not practical to enumerate all the members of the family. protected body Resource_Controller is entry Request(R : out Resource; Amount : Request_Range) when Freed > 0 and Queued < Request'Count is begin if Amount <= Freed then Freed := Freed - Amount; -- allocate Queued := 0; else Queued := Request'Count + 1; requeue Request; end if; end Request; subtype Level is Integer range 0 .. 1000; task Controller is entry Sign_In(L : Level) entry Request(Level)(D:Data); end Controller; task body Controller is Total :Integer; Pending : array (Level) of Integer; begin -- init pending to 0 loop if Total = 0 then accept Sign_In(L:Level) do Total := Total + 1; Pending(L) := Pending + 1; end; else loop select accept Sign_In(L:Level) do Total := Total + 1; Pending(L) := Pending + 1; end; else exit; end select; end loop; procedure Free(R : Resource; Amount : Request_Range) is begin Freed := Freed + Amount; -- free resources Queued := 0; end Free; end Resource_Controller; Question 11.5 The system is in deadlock because P2 is waiting for R5 which has been allocated to P4, P4 is waiting for R2 which has been allocated to R2. There is only one instance of R2 and R5 therefore the circular wait cannot be broken. (A resources allocation graph helps see the cycle.) for I in Level loop if Pending(I) > 0 then accept(I)(D:Data) do null end; Pending(I) := Pending -1; Total := Total - 1; exit; -- look for new calls end if; Question 11.6 The system is safe because we can run the following processes to completion: P6; P5; P3; P2; P1; P7 13 Question 11.7 The WCET ERROR can only "go o" when the task is actually running; it has the diculty that each time the task is switched out the time must be stopped. A run-time may use an interval timer to count down the "budget"; the current value being stored in the TCB. However both checks have the problem of nested blocks which could, theoretically, mean an arbitrary number of time (or CPU time) values need to be accommodated. 3. The exceptions are only useful if the application can program error recovery. With WCET E this is relatively easy to do. Correct (time-wise) run-time behaviour is dependent on no task (process) taking more CPU time then was allocated to it during the schedualability analysis. If a task takes more then it is at fault and it should recover. Hence a task (or block within) has two WCET values; one for the code and the other for the recovery code. If the recovery code fails then the task had better be aborted. The schedualability analysis must guarantee the both values. If no task uses more than its WCET, and the schedualability analysis was correct then arguably no task (or block) can miss its deadline! and hence D E is not useful. If only D E is available and is raised how can a block guarantee to execute the recovery action in a timely fashion? It did not complete the real code so it is unlikely to complete the recovery code. A language may thus need to raise the priority of a task that is handling a D E. A system may be unsafe but not deadlock because a process may release some resources before requesting its maximum load. Eg P1 has 2 requires 4 P2 has 2 requires 4 available 1 This is unsafe because P1 and P2 could request a further 2 resources and there are not enough to go around. However if P1 releases 1 before requesting 3, P2 can run to completion so at this point the state is safe. Chapter 12 { Question 12.1 A timing failure is dened to be the delivery of a service outside its dened delivery interval - typically beyond some dened deadline. Often the service is delivered late because of the time needed to construct the correct value for the service. If the system was designed to always deliver a value in the correct interval then the "lack of time" would be manifest as an incorrect value (delivered on time). Hence timing and value failures cannot be considered orthogonal. The converse to the above can also be true. A service that has failed because the value it delivers is incorrect may be able to deliver a correct value if it is given more (CPU) time; hence a correct value may be delivered but too late. However this is not universally true; a value failure (or error) can be due to many reasons (e.g. software error, hardware error) other than insucient allocation of processor cycles. A good answer should argue that WCET E is more useful then D E (or have convincing arguments the other way!). Question 12.3 Question 12.4 1. The handling of both exceptions can use the standard Ada syntax. The dicult with both exceptions is getting the associated "time" value to the run-time. A static approach might use a pragma, although arguable these static values should be set at link time. A dynamic approach must use a call into the run-time (via some CIFO like entry). Unfortunately this is not really satisafactory for the D E because time will have progressed before this call is made and hence the deadline would not be accurately measured. 2. For DEADLINE ERROR (D E) the delay queue can be used. As a block is entered a value corresponding to the deadline is placed in the queue; if the block ends before the deadline expires then it is removed from the queue. If the delay (deadline) expires then the run-time must transfer this to an exception in the task; the diculty is that that task may not be executing hence it must be marked appropriately for when it next executes. If Hoare semantics for signal are used then a signal that wakes a process is blocking - in the sense that the process that wakes another up waits until that process has exited (or become suspended) before continuing. A cascade wake up can thus be used for delay: monitor body time is CV : condition; procedure tick is begin signal(CV); end; procedure delay(D : natural) is count_down : natural := D; begin while count_down > 0 loop wait(CV); signal(CV); -- will block if this -- wakes another process count_down := count_down - 1; end loop; 14 time process total time for current period end delay; end time; 1 P 1 2 Q 1 3 Q 2 4 P 1 5 S 1 6 S 2 7 P 1 8 Q 1 9 Q 2 10 P 1 11 S 3 12 S 4 13 P 1 14 Q 1 15 Q 2 16 P 1 17 S 5 18 idle The three processes may be scheduled using the cyclic executive approach by splitting up process S into 5 equal parts S1, S2, S3, S4, and S5. (from the above rate monotonic solution). The loop is given by: Question 12.5 The dicult with Ada is the avoidance semantics on guards. In order to know how many ticks must be waited for, the rendezvous must be accepted. Then for each tick every waiting task will need to rendezvous with the server task and recall when necessary A solution will have the following for: package body Time is task Timer is entry Tick; entry Await; end Timer; procedure Tick is begin Timer.Tick; end; procedure delay(D : Natural) is Count_Down : Natural := D; begin while Count_Down > 0 loop Timer.Await; Count_Down := Count_Down - 1 end loop; end delay; task body Timer is begin loop accept Tick; N := Await'Count; for I := 1 To N loop accept Await; end loop; end loop; end Timer; end Time; loop P; Q; P; S1; S2; P; Q; P; S3; S4; P; Q; P; S5 end loop; Question 13.2 There is actually a typo in this question! Q should be the second most important (after P) and with requirement of 6 1. Question 13.2 a As P has the highest priority it will run rst for 30 This solution is however not resilient against abort. ms. Then Q will run for 1 ms; unfortunately it has missed its rst ve deadline at 6ms, 12ms, 18, 24ms and 30ms. S will run last (after 31ms) but have missed its deadline at 25ms. Chapter 13 { Question 13.1 b Utility of P is 30%. Utility of Q is 16.67%. Utility With the rate monotic scheduling approach, all processes are allocated a priority according to their periods. The shorter the period the higher the priority. Process P would there have a higher priority than Q which would have a higher priority than S. A preemptive scheduler is used and therefore the processes would be scheduled in the following order. c Two approaches could be used. If scheduling is based of S is 20%. Total utility is 66.67%. on earliest deadline then the test is that total utilisation is less than 100priority model is used then the rate monotonic test could be applied. It will not be assumed that the general test can be remembered by the student, although the lower bound value of 69% should be. As total untilisation is less than 15 69% the process set is scheduable. The rate monotonic scheme assigns priorities in an inverse relation to period length. P R Q R P Q P R Q R d For rate monotonic Q will have highest static priority, then S and then P. The execution sequence will be: Process Q S Q P Q P Q P Q S Q P Q P Q P Q idle Execution Time 1 5 1 5 1 5 1 5 1 5 1 5 1 5 1 5 1 1 Total Time 1 6 7 12 13 18 19 24 25 30 31 36 37 42 43 48 49 50 Question 13.4 The new diagram will look as follows: A A’ B’ B Pw S B A T B’ A’ Px T S Py S A T A’ Pz T S 0 2 4 6 8 10 12 14 16 18 The result of inheritance is that the highest priority process now nishes at time 12 (rather than 16) and P1 (the next highest) now completes at time 13 (rather than 17). There are also less context switches. Question 13.3 At the minimum execution of R its utility is 10% (Total now 76.67%). At the maximum execution R utility is 50% (Total now 116.67%). As R is not safety critical then it must miss its deadline (if any process must). The earliest deadline scheme will not ensure this. The approach that should be taken is to use rate monotonic scheme and to transform P so that its period is less than R; ie P becomes a process with a period of 10 and a requirement of 3ms (per period). With the new scheme Q will still have the highest static priority, then P, then S and lowest priority will go to R. The execution sequence will be: Execution Time 1 3 2 1 3 2 1 1 4 1 1 3 1 1 5 1 34 36 37 40 42 43 44 48 49 50 With this scheme S gets 16ms in its rst period. For earliest deadline the execution sequence will be the same up to the rst idle time. Process Q P S Q S P Q P R Q R P R Q S Q 3 2 1 3 2 1 1 4 1 1 13.6 The rule for calculating blocking is: the maximum critical section with a ceiling equal or higher than the task but used by a task with a priority lower. The rst part is to calculate the ceilings of each resource. We shall let the letters A,B,C,D,E stand for the tasks and their priorities. Resource Used By Ceiling R1 B,D B R2 B,E B R3 A,C A R4 C C R5 C,D C R6 D,E D Note R4 is only used by one task and hence can be ignored. Applying the rule to Task A: R3 has a ceiling equal and is used by C (lower) hence blocking is 75ms. Task B: R1, R2 and R3 all have higher or equal ceilings and are used by lower; the maximum value is thus 150ms. Task C: Resources to consider, R1, R2, R5 (not R3 as it is not used by lower); the maximum value is thus 250ms. Total Time 1 4 6 7 10 12 13 14 18 19 20 23 24 25 30 31 16 Task D: All ceilings are higher (or equal) but only R2 and R6 are used by E; the maximum value is thus 175ms. The lowest priority task cannot experience a block; hence maximum is 0. for Cnt_Fld use record at mod Byte; Indicator at 0 range Sequence at 0 range Pf at 0 range Next at 0 range end record; 13.7 for Cnt_Fld use One_Byte; The task set is schedulable as U(P1) = 0.2 U(P2) = 0.25 U(P3) = 0.3 Hence U = 0.75 which is below the threshold of 0.780 for thress processes. Supervisory Field: Byte : constant := 1; One_Byte : constant := 8; Cnt_Fld_Indicator : constant Integer := 2; type Supervisory_Class is (Ready, Reject, Not_Ready, Selective_Reject); for Supervisory_Class use ( Ready => 0, Reject => 1, Not_Ready => 2, Selective_Reject => 4 ); type Poll is (No, Yes); for Poll use (No => 0, Yes => 1); subtype Sequence_Number is Integer range 0..7; 13.8 The task set is unschedulable because priorities have been assigned that are not optimal. It must have period transformation applied to it. P1 is transformed to a task that has period 6 and computation time 1. RMS now gives P1 the highest priority (ie P1 is highest and the allocation is optimal). The utilisation of the task set is .1666 + .333 + .25 which is below the bound for schedulability. Hence system is OK. type Supervisory_Field is record Indicator : Cnt_Fld_Indicator; Class : Supervisory_Class; Pf : Poll; Next : Sequence_Number; end record; for Supervisory_Field use record at mod Byte; Indicator at 0 range 0..1; Class at 0 range 2..3; Pf at 0 range 4..4 Next at 0 range 5..7; end record; 13.9 The key here is to note that the formulae is necessary but not sucient. This means that if a task set passes the test it is schedulable but if it failes the test it may or may not be scheduable. The worst phases for periods is when they are relative primes. The given task set has one task as half the frequency of the other and hence the utilisation bound on this set is above that predicted by the formulae. for Supervisory_Field use One_Byte; Unnumbered Field: Byte : constant := 1; One_Byte : constant := 8; Cnt_Fld_Indicator : constant Integer := 3; type Unnum_Cls is (Sabm, Disc, Ua, Cmdr); for Unnum_Cls use ( Sabm => 0, Disc => 1, Ua => 2, Cmdr => 4 ); type Poll is (No, Yes); for Poll use (No => 0, Yes => 1); subtype Modifier is Integer range 0..7; Chapter 15 { Question 15.1 This has not been updated for Ada 95 yet! Control Field: Byte : constant := 1; One_Byte : constant := 8; Cnt_Fld_Indicator : constant Integer := 0; subtype Sequence_Number is Integer range 0..7; type Poll is (No, Yes); for Poll use (No => 0, Yes => 1); type Cnt_Fld is record Indicator : Sequence : Pf : Next : end record; 0..0; 1..3; 4..4; 5..7; type Unnumbered_Field is record Indicator : Cnt_Fld_Indicator; Class : Supervisory_Class; Pf : Poll; mod : Modifier; end record; Cnt_Fld_Indicator; Sequence_Number; Poll; Sequence_Number; for Unnumbered_Field use record at mod Byte; Indicator at 0 range 0..1; Class at 0 range 2..3; Pf at 0 range 4..4 17 mod at 0 range 5..7; end record; procedure Handler is begin Interrupt_Occured := True; end Handler; for Unnumbered_Field use One_Byte; Combined supervisory and unnumbered elds: entry Wait_Heart_Beat when Interrupt_Occured is begin Interrupt_Occured := False; end Wait_Heart_Beat; end Interrupt_Handle; type Cntl_Class is ( Supervisory, Unnumbered ); for Cntl_Class use ( Supervisory => 2, Unnumbered => 3 ); task body Patient_Monitor is Control_Reg_Addr : constant Address := 8##177760#; Ecsr : Csr; for Ecsr'Address use Control_Reg_Addr; Volts : Csr := 5; begin loop select Interrupt.Wait_Heart_Beat; Volts := 5; or delay 5.0; select Supervisor.Sound_Alarm; else null; end select; Ecsr := Volts; Volts := Volts +1; end select; end loop; end Patient_Monitor; type Cnt_Fld(Class : Cntl_Class;) is record case Class is when Supervisory => -- supervisory fields Super_Class : Supervisory_Class; when Unnumbered => -- unnumbered fields Unnum_Class : Unnum_Cls end case; Pf : Poll; case Class is when Supervisory => -- supervisory fields Next : Sequence_Number; when Unnumbered => -- unnumbered fields mod : Modifier; end case; end record; for Cnt_Fld use record at mod Byte Class at 0 range 0..1; Super_Class at 0 range 2..3; Unnum_Class at 0 range 2..3; Pf at 0 range 4; Next at 0 range 5..7; mod at 0 range 5..7; end record; Question 15.3 NEEDS UPDATING FOR ADA 95 package Motorway_Charges is end Motorway_Charges; with Journey_Details; use Journey_Details; with Display_Interface; use Display_Interface; with System; use System; package body Motorway_Charges is Question 15.2 -- assuming System is already withed and used type Transmit_T is (No, Yes); for Transmit_T use (No => 0, Yes => 1); Heart_Monitor : constant Interrrupt_Id := ....; Word : constant := 2; -- number of storage units in a word Bits_In_Word : constant := 16; -- bits in work type Csr is new Integer; for Csr'Size use Bits_In_Word; for Csr'Alignment use Word; for Csr'Bit_order use Low_Order_First; protected Interrupt_Handler is entry Wait_Heart_Beat; private procedure Handler; pragma Attach_Handler(Handler, Heart_Monitor); pragma Interrupt_Priority(Interrupt_Priority'Last); Interrupt_Occured : Boolean := False; end Interrupt_Handler; type Cr_T is record -- have not used string because of the length tag C1 : Character; C2 : Character; C3 : Character; C4 : Character; C5 : Character; C6 : Character; C7 : Character; C8 : Character; Go : Transmit_T; Details : Travel_Details; Code : Security_Code; end record; task Patient_Monitor; for Cr_T use record at mod 2; C1 at 0 range 0 .. 7; C2 at 0 range 8 .. 15; protected body Interrupt_Handler is 18 C3 C4 C5 C6 C7 C8 at at at at at at 1 1 2 2 3 3 range range range range range range 0 8 0 8 0 8 Go at 4 range .. .. .. .. .. .. 7; 15; 7; 15; 7; 15; -- etc procedure Transmit (To_Station : Station_Id; Data : Integer); 0 .. 0; procedure Receive (From_Station : out Station_Id; Data : out Integer); private Details at 4 range 1 .. 4; Code at 4 range 5 .. 15; end record; type Station_Id is new Short_Integer; --for station_id'Size use 16; Station1 : constant Station_Id := 1; Station2 : constant Station_Id := 2; Station3 : constant Station_Id := 3; Station4 : constant Station_Id := 4; Station5 : constant Station_Id := 5; -- etc end Slotted_Ring_Driver; Cr : Cr_T; for Cr use at 8#177762#; Shadow : Cr_T; Dr : Integer; for Cr use at 8#177760#; Current_Cost : Integer := 0; package body Slotted_Ring_Driver is task Handler is entry Interrupt; for Interrupt use at 8#60#; pragma Hardware_Priority(6); -- other solutions acceptable end Handler; task body Handler is begin Shadow.C1 := Registration_Number(1); Shadow.C2 := Registration_Number(2); Shadow.C3 := Registration_Number(3); Shadow.C4 := Registration_Number(4); Shadow.C5 := Registration_Number(5); Shadow.C6 := Registration_Number(6); Shadow.C7 := Registration_Number(7); Shadow.C8 := Registration_Number(8); Shadow.Details := Current_Journey; Shadow.Code := Code; Shadow.Go := Yes; loop accept Interrupt do Cr:= Shadow; Current_Cost := Current_Cost + Dr; select Display_Driver.Put_Cost(Current_Cost); else null; end select; end Interrupt; end loop; end Handler; type Response_Bits is (Cleared, Accepted); for Response_Bits use (Cleared => 0, Accepted => 3); type Csr_T is record Parity : Boolean; Response : Response_Bits; Monitor_Seen : Boolean; Full : Boolean; Ienable : Boolean; Transmit : Boolean; end record; for Csr_T use record at mod 2; Parity at 0 range 0 ..0; Response at 0 range 1 .. 2; Monitor_Seen at 0 range 3 .. 3; Full at 0 range 4 .. 4; Ienable at 0 range 6 .. 6; Transmit at 0 range 10 .. 10; end record; Csr : Csr_T; for Csr use at 8#177760#; --for csr_t'Size use 16; Src_Addr : Station_Id; for Src_Addr use at 8#177762#; Dest_Addr : Station_Id; for Src_Addr use at 8#177764#; end Motorway_Charges; Question 15.4 Data_Reg : Integer; for Src_Addr use at 8#177766#; In Ada (83, solution has not been updated yet): My_Id : Station_Id := 3; Obuffer_Empty : Boolean; with System; use System; package Slotted_Ring_Driver is task Input_Buffer is --pragma PRIORITY(6); -- pragma signal(append); entry Append; entry Take(I : out Integer; From_Station : out Station_Id); end Input_Buffer; type Station_Id is private; Station1 : constant Station_Id; Station2 : constant Station_Id; Station3 : constant Station_Id; Station4 : constant Station_Id; Station5 : constant Station_Id; 19 task Output_Buffer is --pragma PRIORITY(6); -- pragma signal(take); entry Append(I : Integer; From_Station : Station_Id); entry Take; end Output_Buffer; -- store in data_reg and DEST_ADDR -- buffer empty set obuffer_empty Csr.Response := Cleared; Csr.Monitor_Seen := False; Csr.Full := True; else null; end select; end if; Csr.Transmit := True; -- send packet on its way end Interrupt; end loop; end Interrupt_Handler; task Interrupt_Handler is --pragma FAST_INTERRUPT; entry Interrupt; --for interrupt use at 8#60#; end Interrupt_Handler; task body Input_Buffer is Buffer_Empty, Buffer_Full : Boolean; begin loop select when not Buffer_Full => accept Append; -- read data from data_reg and -- src address from SRC_ADDR or when not Buffer_Empty => accept Take(I : out Integer; From_Station : out Station_Id) do null; end Take; end select; end loop; end Input_Buffer; procedure Transmit (To_Station : Station_Id; Data : Integer) is begin Output_Buffer.Append(Data, To_Station); end Transmit; procedure Receive (From_Station : out Station_Id; Data : out Integer) is begin Input_Buffer.Take(Data, From_Station); end Receive ; begin null; end; In Modula. task body Output_Buffer is Buffer_Full : Boolean; begin loop select when not Buffer_Full => accept Append(I : Integer; From_Station : Station_Id ) do -- place data in buffer; null; end Append; or when not Obuffer_Empty => accept Take; end select; end loop; end Output_Buffer; DEVICE MODULE ring[6]; DEFINE transmit, receive; CONST n=64; (* buffer size *) TYPE buffer_item = RECORD item : integer; addr : cardinal END; VAR (* two bounded buffers *) in1, out1, n1 : integer; nonempty1 : signal; buf1 : ARRAY 1:n OF buffer_item; in2, out2, n2 : integer; nonfull2 : signal; buf2 : ARRAY 1:n OF buffer_item; task body Interrupt_Handler is begin loop accept Interrupt do if Csr.Full then if Dest_Addr = My_Id then select Input_Buffer.Append; else null; end select; elsif Src_Addr = My_Id then -- check response bits etc Csr.Full := False; end if; else -- packet empty select Output_Buffer.Take; -- get data from buffer and myid : cardinal; (* ring address *) PROCEDURE receive(VAR from : cardinal; VAR data : integer); BEGIN IF n1 = 0 THEN wait(nonempty1) END; data := buf1[out1].item; from := buf1[out1].addr; out1 := (out1 MOD n)+1; dec(n1) END receive; PROCEDURE transmit(to : cardinal; data : integer); BEGIN IF n2 = n THEN wait(nonfull2) END; buf2[in2].item := data; 20 buf2[in2].addr := to; in2 := (in2 MOD n)+1; inc(n2) END transmit; LOOP doio; IF csr[4] = true THEN IF csr[3] = true THEN (* packet in error *) csr[4] := false; (*clear full bit *) ELSE csr[3] := false; (* set monitor bit *) END; END; csr[10] := true; (* send packet on its way *) END; END interrupt; BEGIN interrupt; END. Z PROCESS interrupt[60B]; VAR csr[177760B] : bits; source[177762B] : cardinal; destination[177764B] : cardinal; datab[177766B] :integer; BEGIN csr[6] := true; LOOP doio; IF csr[4] = true THEN (* packet full, check to see *) (* if it is for us *) IF destination = myid THEN (* packet is addresses to *) (* this station remove data*) (* and place in buffer *) IF n1 <> n THEN (* buffer not full *) buf1[in1].item := datab; buf1[in1].addr := source; in1 := (in1 MOD n) +1; inc(n1); send(nonempty1); (* set response bits *) csr[1] := true; csr[2] := true; END; (* if buf full ignore packet *) Question 15.5 IN occam. CHAN OF ANY SOUND.ALARM: PROC HANDLER CHAN OF ANY interrupt: PLACE interrupt AT #40#: PORT OF INT16 Control.Register: PLACE Control.Register AT #AA14#: TIMER Clock: INT time: INT shock: SEQ shock := 5 WHILE TRUE SEQ Clock ? time ALT Interrupt ? Any shock := 5 Clock ? AFTER time PLUS 5 * G SEQ PAR SOUND.ALARM ! shock SEQ Control.Register ! shock shock := shock + 1 ELSIF source = myid THEN (* check response bits etc *) csr[4] := true; (* set packet empty *) END; ELSE (* packet empty see if we *) (* have anything to transmit *) IF n2 <> 0 THEN datab := buf2[out2].item; destination := buf2[out2].addr; source := myid; out2 := (out2 MOD n) +1; dec(n2); send(nonfull2); csr[1] := false; (* clear response bits *) csr[2] := false; csr[3] := false; (* clear monitor bit *) csr[4] := true; (* set full bit *) END; END; csr[10] := true; (* send packet on its way *) END; END interrupt; BEGIN interrupt; END ring. : PRI PAR supervisor handler PAR -- rest of program : Question 15.6 device module arm(4); dene move_to_position; dbr [177234B] : integer; csr [177236B] : bits; ready : signal; DEVICE MODULE monitor[6]; PROCESS interrupt[60B]; VAR csr[177760B] : bits; BEGIN csr[6] := true; procedure begin end 21 move_to_position(X:integer); dbr := X; wait(ready); move_to_position; process driver[56B]; begin loop csr[6] := true; doio ; INT Next, Now: VAL Interval IS 60 * G: SEQ OK := 4097 WHILE TRUE Clock ? Now Next := Now PLUS Interval WHILE OK > 4096 Limit.Register ? Speed.Limit DBR.Register ! Speed.Limit CSR.Register ! GO CSR.Register ? OK Clock ? AFTER Next csr[6] := false; send(ready); end end driver; begin driver; end arm; Question 15.7 SEQ WHILE TRUE Interrupt ? Any Flash.Register ! 1 device module timing[6]; dene delay; var tick : signal; procedure delay(n:integer); var count : integer; begin count := n; while count > 0 do wait(tick); dec(count); end ; end delay; process clock[100B]; var csr[177546] : bits begin loop csr[6] := true; doio; awaited(tick) send(tick) while end Question 15.11 DEVICE MODULE SpeedControlSystem [5]; VAR Light[177750B] : INTEGER; CurrentLimit[177760B] : INTEGER; CSR[177762B] : bits; DBR[177764B] : INTEGER; PROCESS SpeedInterrupt[60B]; BEGIN LOOP doio; IF CSR[15] = 0 AND CSR[14] = 0 AND CSR[13] = 0 AND CSR[12] = 0 THEN Light := 1 END END END SpeedInterrupt; do end end ; begin clock; end timing; PROCESS SpeedController; BEGIN LOOP DBR := CurrentLimit; (* set current limit*) CSR[1] := TRUE; (* Check *); Delay60Seconds (* delay *) END END; BEGIN CSR[0] := TRUE; (* enable device *) CSR[6] := TRUE; (* enable interrupt*) Light := 0 END SpeedControlSystem; Question 15.10 PORT OF INT16 Limit.Register: PLACE Limit.Register AT #AA14#: PORT OF INT16 CSR.Register: PLACE CSR.Register AT #AA16#: Question 15.12 PORT OF INT16 DBR.Register: PLACE CSR.Register AT #AA18#: PORT OF INT16 Flash.Register: PLACE Flash.Register AT #AA12#: Shared memory approach is Modula-1, message passing is occam2. We compare them considering: CHAN of Any Interrupt: PLACE Interrupt at #60# encapsulation facility Modula-1 has the device module; occam2 only has the proc VAL INT16 G0 is 66: communication between CPU and devices INT Speed.Limit: INT OK: Modula-1 uses shared variables; occam2 sends messages via channels PRI PAR 22 X Ri Ri CT IH + c Tclk k2;s Tk + I ;p device registers representation program data structure in Modula-1; special program channel called a port in occam2 + addressing device registers memory address associated with the variable in Modula-1: I ;p = if K V : V CT s else K CT s + (V ; K ) CT m VAR rdb[177562B] CHAR address associated with the port in occam2: Question 16.4 PORT OF INT16 P: PLACE P AT #AA12#: manipulating device regsiters arrays of bits only in This periodic task suers release jitter. It the worst case this is 20 milliseconds. Use equations 13.11 and 13.12 to calculate response time with this jitter. Modula-1;bit operators only in occam2 Interrupt handling In Modula-1: interrupt associated with modula signal-like operations; DOIO waits for the signal to occur; interrupt is equivalent to sending the signal. In occam2: interrupt associated with a channel; driver receives null input on the channel; device sends null output down the channel. representation of hardware priority parameter to device module in Modula-1; have to use a PRI PAR in occam2 interrupt identication by an address clause on the interrupt handling process in Modula-1; by address clause on interrupt channel in occam2 Chapter 16 { Question 16.2 In any interval being considered, it is possible to calculate the number of time, K , the clock handler could have executed: K = TRi clk It is also possible to calculate the number of movements, V , there has been from the delay queue to the dispatch queue: V = X Ri g2;p Tg where ;p is the set of periodic tasks. If K V , we must assume, for the worst case, that each movement occurs on a dierent clock tick (and hence must be costed at CT c). If this is not the case, a reduuced cost can be used. Hence equation 16.4 becomes: Ri = CS 1 + C i + Bi X Ri + (CS 1 + CS 2 + Cj ) T j j 2hp(i) 23