determining economic news coverage

33
REAL-TIME SYSTEMS AND PROGRAMMING LANGUAGES: 3rd Edition Solutions to Selected Exercises A. Burns and A.J. Wellings Department of Computer Science, University of York, UK email {burns,andy}@cs.york.ac.uk January 2001 Abstract This note gives examples of solutions to the exercises in- volving problems in our book ”Real-Time Systems and Programming Languages: 3rd Edition”. Answers to questions involving more general discussion topics, or understanding of material presented in the chapters, are not given. No guarantee is given that the questions or answers are correct or consistent. Question 5.3 ensure Array_Is_Sorted by Bubble sort else by Exchange sort else error Question 5.5 If an error is detected at P1 at time t, P1 is rolled back to recovery point R13. No other processes are affected. If an error is detected at P2 at time t, P2 is rolled back to R23, unfortunately, it has communicated with P1, so P1 is rolled back to R12. If P3 detected error, it is rolled back to R32, this re- quires communication with P2 and P4 to be undone; therefore P2 must be rolled back to R22 and P4 to R42. Rolling back P2 requires P1 to be rolled back to R12. If P4 detected error, it is rolled back to R43, this re- quires communication with P3 to be undone; P3 is rolled back to R32. This requires communication with P2 and P4 to be undone; therefore P2 must be rolled back to R22. Rolling back P2 requires P1 to be rolled back to R12. Finally, P4 must be rolled back again to R42. Question 6.2 1. any assertion check 2. a watch dog timer detecting a missed deadline in another processes 3. array bounds violation 4. failure of a health monitoring check Question 6.3 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; 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; 1

Upload: others

Post on 12-Sep-2021

2 views

Category:

Documents


0 download

TRANSCRIPT

Page 1: Determining Economic News Coverage

REAL-TIME SYSTEMS AND PROGRAMMING LANGUAGES: 3rd

Edition

Solutions to Selected Exercises

A. Burns and A.J. WellingsDepartment of Computer Science, University of York, UK

email {burns,andy}@cs.york.ac.uk

January 2001

Abstract

This note gives examples of solutions to the exercises in-volving problems in our book ”Real-Time Systems andProgramming Languages: 3rd Edition”. Answers toquestions involving more general discussion topics, orunderstanding of material presented in the chapters, arenot given. No guarantee is given that the questions oranswers are correct or consistent.

Question 5.3

ensure Array_Is_Sorted

by

Bubble sort

else by

Exchange sort

else

error

Question 5.5

If an error is detected at P1 at time t, P1 is rolled backto recovery point R13. No other processes are affected.

If an error is detected at P2 at time t, P2 is rolledback to R23, unfortunately, it has communicated withP1, so P1 is rolled back to R12.

If P3 detected error, it is rolled back to R32, this re-quires communication with P2 and P4 to be undone;therefore P2 must be rolled back to R22 and P4 to R42.Rolling back P2 requires P1 to be rolled back to R12.

If P4 detected error, it is rolled back to R43, this re-quires communication with P3 to be undone; P3 is rolledback to R32. This requires communication with P2 andP4 to be undone; therefore P2 must be rolled back toR22. Rolling back P2 requires P1 to be rolled back toR12. Finally, P4 must be rolled back again to R42.

Question 6.2

1. any assertion check

2. a watch dog timer detecting a missed deadline inanother processes

3. array bounds violation

4. failure of a health monitoring check

Question 6.3

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;

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;

1

Page 2: Determining Economic News Coverage

raise;

-- or raise ILLEGAL_PUNCTUATION

when Io_Error =>

Character_Io.Flush;

raise;

end Read;

begin

null;

end;

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;

Question 6.4

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;

Question 6.8

In the first code fragment, the exception cannot be han-dled by the Do Something procedure. The domain is thecalling code.

In the second code fragment, the exception can behandled by the Do Something procedure. The domainis the procedure.

In the third code fragment, the exception can be han-dled within the inner block declared within the proce-dure. This block is the domain.

Chapter 6 – Question 6.10

All the alternatives will fail in the recovery block en-vironment because the state is restored have each hasfailed. Hence, the else clause is executed.

In the exception handling environment, no staterestoration occurs so the secondary sets I to 20.

Chapter 6 – Question 6.13

The equivalent expression of the temperature controlclass would be:

public class ValveStuck extends Exception;

public class HeaterStuckOn extends Exception;

public class TemperatureStillRising extends Exception;

public class TemperatureControl

{public void heaterOn();

public void heaterOff() throws HeaterStuckOn;

public void increaseCoolant()

throws TemperatureStillRising;

public void openValve() throws ValveStuck;

public void panic();

}

And the turning the heater off reliably:

public static void reliableHeaterOff()

{TemperatureControl TC = new TemperatureControl();

boolean done = false;

int I = 1;

while(!done) {try {

if(I == 1) {TC.heaterOff(); done = true;

} else if(I == 2) {TC.increaseCoolant(); done = true;

} else if(I == 3) {TC.openValve(); done = true;

} else {TC.panic(); done = true;

System.out.println("panic called");

}}catch (Exception E) I++;

}}

Chapter 6 – Question 6.14

If an object is thrown which is not a subclass ofException. It will not be caught by the catch state-

2

Page 3: Determining Economic News Coverage

ment.

Chapter 7 – Question 7.1

with Ada.Text_Io; use Ada.Text_Io;

procedure Main is

procedure One is

begin

delay 1.0;

Put_Line("one finished");

end One;

procedure Two is

begin

delay 2.0;

Put_Line("two finished");

end Two;

procedure Three is

begin

delay 3.0;

Put_Line("three finished");

end Three;

type Pointer is access procedure;

type Parameters is array(Positive range <>)

of Pointer;

procedure Run_Concurrently(These : Parameters) is

task type Worker(This: Pointer);

task body Worker is

begin

This;

end Worker;

type Worker_Pointer is access Worker;

Starter : Worker_Pointer;

begin

Put_Line("Run started");

for I in These’Range loop

Starter := new Worker(These(I));

end loop;

Put_Line("Run Finishing");

end Run_Concurrently;

begin

Put_Line("Main started");

Run_Concurrently((One’access, Two’access,

Three’Access));

Put_Line("Main Finished");

end Main;

Chapter 7 – Question 7.2

Although arrays of tasks can be created easily, assign-ing values to their discriminants is awkward. An earlyversion of Ada 95 incorporated new syntax to allow this;however, during the language’s scope reduction, this wasremoved. The same effect can be achieved by calling afunction with a side effect.

package Count is

function Assign_Number return Index;

end Count;

task type X(I : Index :=

Count.Assign_Number);

type Xa is array (Index) of X;

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;

Xtasks : Xa;

Question 7.3

For two tasks:

procedure Cobegin is

task A;

task B;

task body A is separate;

task body B is separate;

begin

null;

end Cobegin;

Question 7.4

A fork is simply creation of a process dynamically. Thiscan be done easily in Ada. The join is more problematic.Notionally, given the identity of the task created, theparent can busy-wait using the ’terminated flag. How-ever, if busy-waiting is to be avoided then some form ofIPC mechanism must be used.

Question 7.5

211 we think!

Question 7.9

The following points need to be made:

• an exception will not propagate beyond a task, evenif it caused the task to terminate

• a scope cannot exit (even to propagate an excep-tion) if they are none terminated tasks dependenton that scope.

3

Page 4: Determining Economic News Coverage

• an exception raised in the elaboration of the declar-ative part of a task will cause that task to fail (with-out beginning its execution); moreover the parent ofthat task will have ”tasking error” raised before itcan state executing.

These points are illustrated by the behaviour (output)of the program. If C = 2 then no exceptions are raisedand the following output is generated:

A Started

Main Procedure Started

P Started

P Finished

(* DELAY 10 second *)

T Finished

A Finished

Note the output ”Main Procedure Started” could oc-cur first second or third.

When C = 1 then the procedure P will fail. But the ex-ception (constraint error or numeric error) cannot prop-agate for 10 seconds until task T has completed. Itspropagation will cause A to fail (hence no A finishedmessage) but the main program will be unaffected:

A Started

Main Procedure Started

P Started

(* DELAY 10 second *)

T Finished

Finally when C=0 then A will fail during elaborationof its declarative part and hence it will never start to ex-ecute; moreover the main program will get tasking errorraised at its starts and hence it will not begin. Theoutput is simply:

Main Procedure Failed

Question 7.10

For task A, the parent is the main task, its children areC and D, its master is Hierarchy and its dependents areC and D.

For task Pointerb.all, the parent is C, it has no chil-dren, its master is Hierarchy and it has no dependents.

For task Another Pointerb.all, the parent is D, ithas no children, its master is Hierarchy and it has nodependents.

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 isAnother Pointerb.all, its master is A and it hasno dependents.

Procedure Main has no direct parent, children, masteror dependents

Procedure Hierarchy has no direct parent, children,or master. Its dependents are A, Pointerb.all, andAnother Pointerb.all.

Chapter 7 – Question 7.12

MyCalculation.run(); runs the run procedure sequen-tially.

whereas the

new Thread(MyCalculation).start();

will create a new thread.

Question 8.2

The algorithm works by keeping four slots for the data:two banks of two slots. The reader and the writer neveraccess the same bank of slots at the same time. Theatomic variable Latest contains the index of the bank towhich the last data item was written and the Next Slotarray indexed by this value indicates which slot in thatbank contains the data.

1. a Write is followed by a Read – the reader gets thelast value written

2. a Read is preempted by a Write – the writer willwrite to a different bank of slots than being accessedby the current reader.

3. a Write is preempted by a Read– the reader willread from a different bank of slots than being ac-cessed by the current writer.

4. a Read is preempted by more than on Write – thefirst writer will write to one of the slots in the bankwhich is not being currently read, the other willwrite into the other slot.

5. a Write is preempted by more than one Read – allthe readers will read from the same slot in the bankother than the one being written to.

Consider some arbitrary time when the latest valueof the data item is in Four Slot(Second, First). Inthis case Latest equals Second and Next(Second) =First. Assume also that this is the last value read. Ifanother read request comes in and is interleaved witha write request, the write request will chose the firstbank of slots and the first slot, and so on. Thus it ispossible that the reader will obtain an old value butnever an inconsistent one. If the write comes in againbefore the read has finished, it will write to the firstbank and second slot, and then the first bank and firstslot. When the reader next comes in, it will obtain thelast value that was completely written (that is, the valuewritten by the last full invocation of Write).

Question 8.3

var mutex( initial 1);

wrt( initial 1);

4

Page 5: Determining Economic News Coverage

readcount := 0;

(* reader processes *)

P(mutex)

readcount := readcount +1;

if readcount = 1 then P(wrt);

V(mutex)

(* read data structure *)

P(mutex)

readcount := readcount -1;

if readcount = 0 then V(wrt);

V(mutex)

(* writer processes *)

P(wrt)

(* write data structure *)

V(wrt)

Question 8.4

Hoare’s conditional critical region is of the form:

region x when B do S1;

In the following solution: x wait is a semaphore usedfor processes waiting for their guard to be TRUE; andx count is the number waiting. When the region is leftwe scan down the queue to see if any process can con-tinue. We use x temp to keep track of the number ofprocesses we have rescheduled (otherwise we would justloop).

var x_mutex semaphore ( initial 1);

x_wait semaphore ( initial 0);

x_count : integer :=0;

x_temp : integer :=0;

P(x_mutex)

if not B thenx_count := x_count +1;

V(x_mutex);

P(x_wait);

while not B dox_temp := x_temp +1;

if x_temp =< x_count thenV(x_wait);

elseV(x_mutex);

end if ;

P(x_wait);

end loop ;

x_count := x_count -1;

end if ;

S1;

if x_count > 0 thenx_temp := 1;

V(x_wait);

elseV(x_mutex);

end ;

Question 8.5

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;

For each procedure:

P(mutex);

body;

if next_count > 0 thenV(next);

elseV(mutex);

end if ;

For each wait on condition x

x_count := x_count +1;

if next_count > 0 thenV(next);

elseV(mutex);

P(x_sem);

x_count := x_count -1;

For each signal on condition x

if x_count > 0 thennext_count := next_count + 1;

V(x_sem);

P(next);

next_count := next_count - 1;

end if ;

Question 8.6

interface module semaphores;

define semaphore, P, V, init;

type semaphore = record taken : boolean;

free : signal;

end ;

procedure P(var s:semaphore);

beginif s.taken then wait(s.free) end;s.taken := true;

end P;

procedure V( var s:semaphore);

begins.taken := false;

send(s.free);

end ;

procedure init( var s:semaphore)

begins.taken := false;

end ;

end ;

To extend to the general semaphore the boolean be-comes a count. Init takes an initial value of type integer.

5

Page 6: Determining Economic News Coverage

P only blocks when the count is 0.

Question 8.7

interface module diskheadscheduler;

define request, release;

use maxcyl;

var headpos : integer;

up, down : boolean;

upsweep, downsweep : signal;

procedure request(dest:integer);

beginif busy then

if headpos < dest then wait(upsweep,dest)

else wait(downsweep,maxcyl-dest) endend ;

busy := true; headpos := dest;

end request;

procedure release;

beginbusy := false;

if up thenif awaited(upsweep) then send(upsweep)

else up:= false; send(downsweep) end

elseif awaited(downsweep) then send(downsweep)

else up := true; send(upsweep)

endend release;

end diskheadscheduler;

Question 8.8

interface module sharedfile;

varreaders : integer;

writing : boolean;

oktoread, oktowrite : signals;

procedure startread;

beginif writing or waited(oktowrite) then

wait(oktoread)

end ;

readers := readers+1;

send(oktoread)

end startread;

procedure endread;

beginreaders := readers -1;

if readers = 0 thensend(oktowrite)

endend endread;

procedure startwrite;

beginif readers <> 0 OR writing then

wait(oktowrite)

end ;

writing := true

end startwrite;

procedure endwrite;

begin

writing := false;

if waited(oktowrite) thensend(oktowrite)

elsesend(oktoread)

end endwrite;

beginreader :=0;

writing := false

end sharedfile;

Question 8.9

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;

PROCEDURE exit_cars(I : NATURAL);

BEGIN

in_tunnel := in_tunnel - I;

IF in_tunnel < N THEN

set_lights(GREEN);

signal(lights_green);

END;

IF in_tunnel = 0 THEN

wait(more_cars);

END;

END enter_cars;

BEGIN

in_tunnel := 0;

set_lights(GREEN);

END lights;

PROCESS entrance_monitor;

BEGIN

LOOP

lights.enter_cars(cars_entered);

delay_10_seconds;

END;

END;

PROCESS exit_monitor;

BEGIN

LOOP

lights.exit_cars(cars_exited);

delay_10_seconds;

END;

END;

6

Page 7: Determining Economic News Coverage

Question 8.10

The criticism of condition synchronisation is that waitand signal are like sempahore operations and thereforeunstructured. A signal on the wrong condition may bedifficult to detect. They are therefore too low level andunstructured.

The WaitUntil primitive removes the need for condi-tion variables and therefor wait and signal. the problemhow to implement it. If a process is blocked because itsboolean expression is false then it must give up the mon-itor lock to allow other processes to enter and change thevariables in the expression. So the issue is when to re-evaluate the guards. As the monitor does not know if thevariables in a boolean expression have been altered, allboolean expressions must be revaluated EVERY TIMEa process releases the monitor lock. This is inefficientand therefore not used.

The object to this approach may be invalid if we have amulti processor system with shared memory where eachprocessor only executes a single process. If this is thecase then the process can continually check its guards asthe processor is unable to execute another process.

buffer_controller : monitor

type buffer_t is recordslots : array (1..N) of character;

size : integer range 0..N;

head, tail : integer range 1..N;

end record ;

buffer : buffer_t;

procedure produce(char : character);

...

WaitUntil buffer.size < N

-- place char in buffer

end ;

function consume return character;

...

WaitUntil buffer.size > 0

-- take char out of buffer;

return char;

end;end;

Question 8.11

MODULE smokers ;

TYPE

ingredients = (TOBandMAT,TOBandPAP,PAPandMAT);

INTERFACE MODULE controller;

DEFINE get, put, release;

USE ingredients;

VAR

TP, MP, PP : signal;

TAM, TAP, PAM : signal;

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;

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;

TOBandPAP: BEGIN

(* Matches Process *)

send (MP)

END;

PAPandMAT: BEGIN

(* Tobacco Process *)

send (TP)

END

END

END release;

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;

TOBandPAP: BEGIN

(* Matches Process *)

IF awaited(TAP) THEN

send(TAP)

END;

wait(MP)

END;

7

Page 8: Determining Economic News Coverage

PAPandMAT: BEGIN

(* looking for Tobacco Process *)

IF awaited(PAM) THEN

send(PAM)

END;

wait(TP)

END

END

END put;

END controller;

PROCESS smoker (requires : ingredients);

BEGIN

LOOP

controller.get(requires);

(* roll and smoke cigarette *)

controller.release(requires)

END

END smoker;

BEGIN

smoker(TOBandMAT);

smoker(TOBandPAP);

smoker(PAPandMAT)

END smokers.

Question 8.15

#include "mutex.h"

typedef struct {pthread_mutex_t mutex;

pthread_cond_t ok_to_read;

pthread_cond_t ok_to_write;

int readers;

int writing;

int waiting_writers;

/* data */

} shared_data;

int start_read(shared_data *D) {PTHREAD_MUTEX_LOCK(&D->mutex);

while(D->writing > 0 || D->waiting_writers > 0) {PTHREAD_COND_WAIT(&(D->ok_to_read), &(D->mutex));

}D->readers++;

PTHREAD_MUTEX_UNLOCK(&D->mutex);

return 0;

};

int end_read(shared_data *D) {PTHREAD_MUTEX_LOCK(&D->mutex);

if(--D->readers == 0 ) {PTHREAD_COND_SIGNAL(&D-> ok_to_write);

};PTHREAD_MUTEX_UNLOCK(&D->mutex);

return 0;

}

int start_write(shared_data *D) {PTHREAD_MUTEX_LOCK(&D->mutex);

D->waiting_writers++;

while(D->writing > 0 || D->readers > 0) {PTHREAD_COND_WAIT(&(D->ok_to_write), &(D->mutex));

}D->writing++;

D->waiting_writers--;

PTHREAD_MUTEX_UNLOCK(&D->mutex);

return 0;

};

int end_write(shared_data *D) {PTHREAD_MUTEX_LOCK(&D->mutex);

D->writing = 0;

if(D->waiting_writers != 0 ) {PTHREAD_COND_SIGNAL(&D-> ok_to_write);

}else {

PTHREAD_COND_BROADCAST(&D-> ok_to_read);

}PTHREAD_MUTEX_UNLOCK(&D->mutex);

return 0;

}

int main() {/* ensure all mutexes and condition

variables are initialised */

}

Question 8.16

#include "mutex.h"

const int N = 32;

typedef struct

pthread_mutex_t mutex;

pthread_cond_t free;

int free_resources;

resource;

void allocate(int size, resource *R)

pthread_mutex_lock(&R->mutex);

while(size > (R->free_resources))

pthread_cond_wait(&(R->free), &(R->mutex));

R->free_resources = R->free_resources - size;

pthread_mutex_unlock(&R->mutex);

void deallocate(int size, resource *R)

pthread_mutex_lock(&R->mutex);

R->free_resources = R->free_resources + size;

pthread_cond_broadcast(&R-> free);

pthread_mutex_unlock(&R->mutex);

void initialize(resource *R)

R->free_resources = N;

/* initialise mutex and condition variables */

Question 8.19

with Ada.Text_Io; use Ada.Text_Io;

with Ada.Exceptions; use Ada.Exceptions;

with Ada.Numerics.Discrete_Random;

procedure Smokers2 is

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);

task type Smoker(My_Needs : Need);

task Active_Agent;

8

Page 9: Determining Economic News Coverage

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;

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;

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;

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;

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;

entry Give_Paper(N : Need; Ok : out Boolean)

when P_Available and not Allocated_P is

9

Page 10: Determining Economic News Coverage

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;

entry Wait_Smokers when All_Done is

begin

All_Done := False;

end Wait_Smokers;

end Agent;

Tp : Smoker(T_P);

Tm : Smoker(T_M);

Mp: Smoker(M_P);

begin

null;

end Smokers2;

Question 8.22

Client tasks call the Wait entry and are queued untilthere are “Needed” number of tasks. At which pointthey are all released. The value of “Needed” is deter-mined when an instance of the protected type is created.

with Pthreads; use Pthreads;

package Barriers is

type Barrier(Needed : Positive) is limited private;

procedure Wait(B : in out Barrier);

procedure Initialise(B : in out Barrier);

private

type Barrier(Needed : Positive) is

record

M : Mutex_T;

C : Cond_T;

Arrived : Natural;

end record;

end Barriers;

package body Barriers is

procedure Wait(B : in out Barrier) is

begin

Mutex_Lock(B.M);

B.Arrived := B.Arrived + 1;

if Arrived = B.Needed then

B.Arrived := 0;

Cond_Broadcast(B.C);

else

Cond_Wait(B.C, B.M);

end if;

Mutex_Unlock(B.M);

end Wait;

procedure Initialise(B : in out Barrier) is

begin

Mutex_Initialise(B.M);

Cond_Initialise(B.C);

end Initialise;

end Barriers;

Question 8.23

with Mutexes; use Mutexes;

package body Disk_Head_Scheduler is

Headpos : Cylinder_Address;;

Busy : Boolean := False;

Waiting : array (Cylinder_Address) of Cond_T;

Number_Waiting : array (Cylinder_Address) of Natural;

Lock: Mutex_T;

procedure Request(Dest: Cylinder_Address) is

begin

Mutex_Lock(Lock);

Number_Waiting(Dest) := Number_Waiting(Dest) +1;

while Busy then

Cond_Wait(Waiting(Dest));

end if;

Busy := True;

Headpos := Dest;

Mutex_Unlock(Lock);

end Request;

procedure Release(Dest: Cylinder_Address) is

Next_Found : Boolean := False;

Next : Cylinder_Address;

begin

Mutex_Unlock(Lock);

-- Headpos should equal Dest.

Busy := False;

Number_Waiting(Headpos) := Number_Waiting(Headpos) - 1;

if Number_Waiting(Headpos) /= 0 then

Cond_Broadcast(Waiting(Headpos),Lock);

else

Next := Headpos + 1;

loop

if Number_Waiting(Next) /= 0 then

Cond_Broadcast(Waiting(Next),Lock);

exit;

end if;

Next := Next + 1;

exit when Next = Headpos;

end loop;

end if;

Unlock(Mutex);

10

Page 11: Determining Economic News Coverage

end Release;

end Diskheadscheduler;

Question 8.24

package body Multicast is

package Cond_Sem is new Semaphore_Package(0);

package Binary_Sem is new Semaphore_Package(1);

use Binary_Sem; use Cond_Sem;

Data_Available : Cond_Sem.Semaphore;

Mutex : Binary_Sem.Semaphore;

Waiting : Integer := 0;

The_Data : Integer;

procedure Send(I : Integer) is

begin

Wait(Mutex);

The_Data := I;

if Waiting /= 0 then

Signal(Data_Available);

else

Signal(Mutex);

end if;

end;

procedure Receive(I: out Integer) is

begin

Wait(Mutex)

Waiting := Waiting + 1;

Signal(Mutex);

Wait(Data_Available);

Waiting := Waiting -1;

I := The_Data;

if Waiting /= 0 then

Signal(Data_Available);

else

Signal(Mutex)

end if;

end Receive;

end Multicast;

Question 8.25

package body BROADCAST is

package COND_SEM is new SEMAPHORE_PACKAGE(0);

package BINARY_SEM is new SEMAPHORE_PACKAGE(1);

use BINARY_SEM; use COND_SEM;

DATA_AVAILABLE : COND_SEM.SEMAPHORE;

RECEIVERS_READY : COND_SEM.SEMAPHORE;

MUTEX : BINARY_SEM.SEMAPHORE;

NEW_SEND : BINARY_SEM.SEMAPHORE;

WAITING : INTEGER := 0;

THE_DATA : INTEGER;

procedure SEND(I : INTEGER) is

begin

WAIT(NEW_SEND);

WAIT(MUTEX);

THE_DATA := I;

if WAITING = 10 then

SIGNAL(DATA_AVAILABLE);

else

SIGNAL(MUTEX);

WAIT(RECEIVERS_READY);

end if;

SEND(NEW_SEND);

end;

procedure RECEIVE(I: out INTEGER) is

begin

WAIT(MUTEX)

WAITING := WAITING + 1;

if WAITING = 10 then SIGNAL(RECEIVERS_READY);

else

SIGNAL(MUTEX);

WAIT(DATA_AVAILABLE);

end if;

I := THE_DATA;

WAITING := WAITING -1;

if WAITING /= 0 then

SIGNAL(DATA_AVAILABLE);

else

SIGNAL(MUTEX)

end if;

end RECEIVE;

end BROADCAST;

Question 8.26

protected Total_Count is

procedure Car_In(Upper_Just_Passed : out Boolean);

procedure Car_Out(Lower_Just_Passed : out Boolean);

private

Total_Cars : Natural := 0;

Upper_Threshold_Passed : Boolean := False;

Lower_Threshold_Passed : Boolean := False;

end Total_Count;

protected body Total_Count is

procedure Car_In(Upper_Just_Passed : out Boolean) is

begin

Total_Cars := Total_Cars + 1;

if Total_Cars >= Maximum_Cars_In_City_For_Red_Light

and then not Upper_Threshold_Passed then

Upper_Threshold_Passed := True;

Upper_Just_Passed := True;

else

Upper_Just_Passed := False;

end if;

end Car_In;

procedure Car_Out(Lower_Just_Passed : out Boolean) is

begin

Total_Cars := Total_Cars - 1;

if Total_Cars <= Minimum_Cars_In_City_For_Green_Light

and Thennot Lower_Threshold_Passed then

Lower_Just_Passed := True;

Lower_Threshold_Passed := True;

else

Lower_Threshold_Passed := False;

end if;

end Car_Out;

end Total_Count;

task body Bar_Controller is

City_Just_Full : Boolean;

City_Just_Space : Boolean;

begin

11

Page 12: Determining Economic News Coverage

loop

City_Just_Full := False;

City_Just_Space := False;

select

accept Car_Entered do

Total_Count.Car_In(City_Just_Full);

end Car_Entered;

or

accept Car_Exited do

Total_Count.Car_Out(City_Just_Space);

end Car_Exited;

end select;

if City_Just_Full then

City_Traffic_Lights_Controller.City_Is_Full;

elsif City_Just_Space then

City_Traffic_Lights_Controller.City_Has_Space;

end if;

end loop;

end Bar_Controller;

Question 8.28

public class ReadersWriters2

{

private int readers = 0;

private int waitingReaders = 0;

private int waitingWriters = 0;

private boolean writing = false;

ConditionVariable OkToRead = new ConditionVariable();

ConditionVariable OkToWrite = new ConditionVariable();

public void startWrite() throws InterruptedException

{synchronized(OkToWrite) // get lock on condition variable

{synchronized(this) // get monitor lock

{if(writing | readers > 0 | waitingReaders > 0) {

waitingWriters++;

OkToWrite.wantToSleep = true;

} else {writing = true;

OkToWrite.wantToSleep = false;

}} //give up monitor lock

if(OkToWrite.wantToSleep) {OkToWrite.wait();

}}}

public void stopWrite()

{System.out.println("StopWrite Called ");

synchronized(OkToRead)

{synchronized(OkToWrite)

{synchronized(this)

if(waitingReaders > 0) {writing = false;

readers = waitingReaders;

waitingReaders = 0;

OkToRead.notifyAll();

} else if(waitingWriters > 0) {waitingWriters--;

OkToWrite.notify();

} else writing = false;

}}}}

public synchronized void startRead()

throws InterruptedException

{synchronized(OkToRead) {

synchronized(this)

{if(writing) {

waitingReaders++;

OkToRead.wantToSleep = true;

} else {readers++;

OkToRead.wantToSleep = false;

}}if(OkToRead.wantToSleep) {

OkToRead.wait();

}}}

public synchronized void stopRead()

{synchronized(OkToWrite)

{synchronized(this)

{readers--;

if(readers == 0 & waitingWriters > 0) {waitingWriters--;

writing = true;

OkToWrite.notify();

}}}}}

Question 8.29

public class ResourceManager

{

private final int maxResources = 15;

protected int resourcesFree;

public ResourceManager()

{resourcesFree = maxResources;

}

public synchronized void allocate(int size) throws

TooManyResourcesRequested, InterruptedException

{if(size > maxResources) throw new

TooManyResourcesRequested();

while(size > resourcesFree) {wait();

}resourcesFree = resourcesFree - size;

}

12

Page 13: Determining Economic News Coverage

public synchronized void deallocate(int size)

{resourcesFree = resourcesFree + size;

System.out.println("resources left " + resourcesFree);

notifyAll();

}}

Question 8.30

public class QuantitySemaphore

{

int value;

public QuantitySemaphore(int I)

{value = I;

}

public synchronized void wait(int I)

{try {

while(I > value) wait();

value = value - I;

}catch (Exception E) ;

}

public synchronized void signal(int I)

{value = value + I;

notifyAll();

}}

Question 8.31

public class NewBoundedBuffer

private int buffer[];

private int first;

private int last;

private int numberInBuffer = 0;

private int size;

ConditionVariable bufferNotFull, bufferNotEmpty;

public NewBoundedBuffer(int length)

size = length;

buffer = new int[size];

last = 0;

first = 0;

bufferNotFull = new ConditionVariable();

bufferNotEmpty = new ConditionVariable();

;

public void put(int item)

throws InterruptedException

synchronized(bufferNotFull)

System.out.println("put trying for this");

synchronized(this)

if (numberInBuffer == size)

bufferNotFull.wantToSleep = true;

else

bufferNotFull.wantToSleep = false;

if(bufferNotFull.wantToSleep)

System.out.println("waiting buffer Not Full");

bufferNotFull.wait();

synchronized(bufferNotEmpty)

System.out.println("put trying for this again");

synchronized(this)

last = (last + 1) % size ; // % is modulus

numberInBuffer++;

buffer[last] = item;

System.out.println("signalling bufferNotEmpty");

bufferNotEmpty.notify();

;

public synchronized int get()

throws InterruptedException

int I;

synchronized(bufferNotEmpty)

System.out.println("get trying for this");

synchronized(this)

if (numberInBuffer == 0)

bufferNotEmpty.wantToSleep = true;

else

bufferNotEmpty.wantToSleep = false;

if(bufferNotEmpty.wantToSleep)

System.out.println("waiting buffer Not empty");

bufferNotEmpty.wait();

synchronized(bufferNotFull)

System.out.println("get trying for this again");

synchronized(this)

first = (first + 1) % size ; // % is modulus

numberInBuffer--;

System.out.println("signalling bufferfull");

bufferNotFull.notify();

return buffer[first];

;

;

Question 8.33

Given the class specification, it would be very messy toimplement the algorithm. It would be necessary to keepa count of high priority waiters. The signaller would no-tifyAll. All low priority waiters would wait again if therewere high priority waiters. High priority waiters wouldneed to decide amongst themselves wich one should con-tinue, the others would wait again.

If we change the specification so that the methods arenot synchronized, then the following solution is possible.

public class Event

{private int highPriorityWaiting;

private int lowPriorityWaiting;

13

Page 14: Determining Economic News Coverage

private ConditionVariable highWaiter;

private ConditionVariable lowWaiter;

public Event()

{highPriorityWaiting = 0;

lowPriorityWaiting = 0;

highWaiter = new ConditionVariable();

lowWaiter = new ConditionVariable();

}

public void highPriorityWait()

{synchronized(highWaiter) {

synchronized(this) {highPriorityWaiting++;

}try {

highWaiter.wait();

} catch(Exception E) {};}};

public synchronized void lowPriorityWait()

{synchronized(lowWaiter) {

synchronized(this) {lowPriorityWaiting++;

}try {

lowWaiter.wait();

} catch(Exception E) {};}};public synchronized void signalEvent()

{synchronized(highWaiter) {

synchronized(lowWaiter) {synchronized(this) {

if(highPriorityWaiting > 0) {highWaiter.notify();

highPriorityWaiting--;

} else if (lowPriorityWaiting > 0) {lowWaiter.notify();

lowPriorityWaiting--;

}}}}

};}

To modify this, so that an individual thread is woken,requires a notifyAll, and each thread to test an indendedID with their own Id. Messy.

Question 9.1

Yes: protected objects are flexible, they can implementsemaphores, and therefore can implement the same ex-pressive power as the rendezvous.

No: Although it may have the same expressive power,it is not easy to program a selective waiting construct.It is not possible for example to have a multi-way selectand therefore the ”ease of use” is sacrificed.

Question 9.2

NO, each queue is in FIFO order, there is no time infor-mation available.

Question 9.3

subtype Binary_Value is Integer range 0 ..1 ;

task type Semaphore(Value :

Binary_Value := 0) is

entry P;

entry V;

end Semaphore;

task body Semaphore is

begin

loop

select

when Value = One =>

accept P;

Value := 0;

or

accept V;

Value := 1;

or

terminate;

end select;

end loop;

end Semaphore;

If task is aborted, the semaphore is deadlocked.

Question 9.4

A tasking implementation might be more expensive butit allows the semaphore to timeout on the signal opera-tion and release it for other tasks.

Question 9.5

Assuming a task which implements a sempahore.

For mutual exclusion:

mutex : semaphore;

For signalling processes suspended:

next : semaphore;

For each condition:

x_cond : semaphore;

next and x_cond must be initialised so

next.P;

x_cond.P;

For each procedure:

mutex.P;

body;

if next.P’count > 0 thennext.V;

elsemutex.V

end if

For each wait on condition x

if next.wait’count > 0 thennext.V;

14

Page 15: Determining Economic News Coverage

elsemutex.V;

x_cond.P;

For each signal on condition x

if x_cond.P > 0 thenx_cond.V;

next.P;

end if ;

This will not work because of ’count; we must keepexplicit count to avoid the race condition.

Question 9.6

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

chan1 := NOT chan1

swt := TRUE

in1 ? Data

in2 ? Data

in3 ? Data

IF

not swt

if

chan1

out1 ! Data

TRUE

out2 ! Data

TRUE

SKIP

:

Question 9.8

task Entry_Detector;

task Exit_Detector;

task Lights_Controller is

entry Cars_Left(X : Natural);

entry Cars_Arrived(X : Natural);

end Lights_Controller;

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;

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;

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;

end select;

end loop;

end Light_Controller;

Question 9.9

#include "sig.h"

#include "mqueue.h"

#define SWITCH_CHAN SIGRTMIN +1

#define CHANS SIGRTMIN +2

#define OUT1 1

#define OUT2 2

#define IN1 1

#define IN2 2

#define IN3 2

#define DEFAULT_NBYTES 1

int nbytes = DEFAULT_NBYTES;

#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;

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) {if(current_chan == 1) current_chan = 2;

else current_chan = 1;

15

Page 16: Determining Economic News Coverage

}

void input_chans(int signum, siginfo_t *data,

void *extra) {unsigned int pri;

if(data -> si_value.sival_int == IN1) {if((err = mq_receive(mq_in1, &buf[0],

nbytes, &pri)) < 0) {exit(3);

};}else { /* similarly for IN2 and IN3 */

};if(current_chan == 1) {

if((err = mq_send(mq_out1,

&buf[0], nbytes, 0)) < 0) {exit(3);

};}else {

if((err = mq_send(mq_out1,

&buf[0], nbytes, 0)) < 0) {exit(3);

};}

}

int select() {

sigset_t mask, omask;

struct sigaction s, os;

struct sigevent se;

/* set up signal mask */

sigemptyset(&mask);

sigaddset(&mask, SWITCH_CHAN);

sigaddset(&mask, CHANS);

s.sa_flags = 0;

s.sa_mask = mask;

/* set up handlers */

s.sa_sigaction = & change_chan;

sigaction(SWITCH_CHAN, &s, &os);

s.sa_sigaction = &input_chans;

sigaction(CHANS, &s, &os);

/* set message queues attributes*/

ma.mq_flags = 0; /* No special behaviour */

ma.mq_maxmsg = 1;

ma.mq_msgsize = nbytes;

if (( mq_in1 = mq_open(MQ_IN1, O_RDONLY,

MODE, &ma)) < 0) {/* indicate error */

exit(1);

};/* similarly for the other two input queues */

if (( mq_out1 = mq_open(MQ_OUT1, O_CREAT|O_EXCL,

MODE, &ma)) < 0) {/* indicate error */

exit(1);

};/* similarly for the other output queues */

if (( mq_switch = mq_open(MQ_SWITCH, O_RDONLY,

MODE, &ma)) < 0) {/* indicate error */

exit(1);

};

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) {exit(3);

};

/* 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) {exit(3);

};

sigprocmask(SIG_UNBLOCK, &mask, &omask);

/* need to sleep here*/

}

Question 9.10

with Ada.Text_Io; use Ada.Text_Io;

with Ada.Exceptions; use Ada.Exceptions;

with Ada.Numerics.Discrete_Random;

procedure Smokers is

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);

task type Smoker(My_Needs : Need);

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;

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);

end loop;

Agent.Give_Paper(My_Needs, Got);

when T_M =>

while not Got loop

Agent.Give_Tobacco(My_Needs, Got);

16

Page 17: Determining Economic News Coverage

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;

Tp : Smoker(T_P);

Tm : Smoker(T_M);

Mp: Smoker(M_P);

task body Agent is

T_Available, M_Available,

P_Available : Boolean;

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 ");

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;

17

Page 18: Determining Economic News Coverage

Question 9.11

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;

end select;

end loop;

end Server;

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 9.13

(1) If exception A is raised it is trapped inside the ren-dezvous and therefore the only message to appear is “Atrapped in sync”.

(2) If exception B is raised it is trapped inside therendezvous but then re-raised. This will propagate theexception to task ONE where it will be trapped and Craised but unhandled (note the exception doesn’t prop-agate to main). The exception will also propagate toblock Z is task TWO where it will be handled, the han-dler however raises exception C which is handled byblock Y. The following will therefore be printed: “Btrapped in sync”, “B trapped in block Z”, “C trappedin Y” and “B trapped in one”

(3) If exception C is raised it is trapped inside the ren-dezvous. The handler then raises D which is propagatedthe task ONE and block Z. Block Z catches D with whenothers and then raises C which is trapped by block Y’swhen others. The following will therefore be printed: “Ctrapped in sync”, “others trapped in Z”, “C trapped inY” and “C trapped in one”.

(4) If exception D is raised it is not trapped by syncand therefore propagates to ONE. Block Z catches Dwith when others and then raises C which is trapped byblock Y’s when others. The following will therefore beprinted: “others trapped in Z”, “C trapped in Y” and“D trapped in one”.

Question 9.14

[Number.Of.Procs] CHAN of Any Bar:

[Number.Of.Procs] CHAN of Any Wait:

PROC Stop.Go(VAL INT ID)

SEQ

Bar(ID)!Any

Wait(ID)?Any

:

PROC Controller

SEQ

SEQ j = 0 FOR 6

ALT i = 0 FOR Number.Of.Procs

Bar[i] ? Any

SKIP

PAR

SEQ j = 0 FOR 4

ALT i = 0 FOR Number.Of.Procs

Bar[i] ? Any

SKIP

PAR J = 0 FOR Number.Of.Procs

Wait(j) ! Any

:

18

Page 19: Determining Economic News Coverage

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;

...

END A;

PROCESS B

BEGIN

...

SELECT

DISCUSS primary BY

-- B_primary

-- uses x,y

TO ARRANGE B_acceptance_test;

OR

DISCUSS secondary BY

-- B_secondary

-- uses y,z

TO ARRANGE B_acceptance_test;

ELSE

ERROR;

END SELECT;

...

END B;

Note that there is no need for the global acceptance test.

Question 10.11

Fragment 1Case (1): Flag = ACase (2): Flag = BCase (3): Flag = ACase (4): Flag = AFragment 2

Case (1): Flag = ACase (2): Flag = BCase (3): Flag = BCase (4): Flag = BFragment 3Case (1): Flag = ACase (2): Flag = BCase (3): Flag = ACase (4): Flag = AFragment 4Case (1): Flag = BCase (2): Flag = ACase (3): Flag = BCase (4): Flag = A

Question 10.12

protected Controller is

entry Stop(At_Location : out Array_Bounds);

procedure Found(At_Location : in Array_Bounds);

private

Found_At : Array_Bounds;

Found_String : Boolean := False;

end Controller;

protected body Controller is

entry Stop(At_Location : out Array_Bounds)

when Found_String is

begin

At_Location := Found_At;

end Stop;

procedure Found(At_Location : in Array_Bounds) is

begin

Found_At := At_Location;

Found_String := True;

end Found;

end Controller;

task body Searcher is

Found : Boolean := False;

At_Loc : Array_Bounds;

Str : Search_String;

begin

accept Find (Looking_For : Search_String) do

Str := Looking_For;

end Find;

loop

select

Controller.Stop(At_Location);

then abort

Search_Support.Search(Search_Array, Lower, Upper,

Str, Found, At_Loc);

if Found then

Controller.Found(At_Loc);

end if;

end select;

-- At_Loc is location of string

select

accept Get_Result (At_Location : out Array_Bounds) do

At_Location = At_Loc;

end select;

or

accept Find (Looking_For : Search_String) do

19

Page 20: Determining Economic News Coverage

Str := Looking_For;

end Find;

end select;

end loop;

end Searcher;

Question 10.13

There are three possible interleavings of interest.

1. Error 1 is raised before Watch executes its raisestatement. In this case, the then abort clauseis abandoned and the message ”Error 1 Caught”printed.

2. Error 2 is raised before Signaller calls Go andcauses Error 1 to be raised. Furthermore, the ex-ception propagates outside the select statement be-fore this happens. In this case, entry is cancelledand the message ”Error 2 Caught” printed.

3. Error 2 is raised before Signaller calls Go andcauses Error 1 to be raised. However, before theexception propagates outside the select statement,Error 1 is raised. In this case, the then abort clauseis abandoned, the Error 2 exception lost and themessage ”Error 1 Caught” printed.

Question 10.14

#include "sig.h"

#define MODE_A 1

#define MODE_B 2

#define MODE_CHANGE SIGRTMIN +1

int mode = MODE_A;

void change_mode(int signum, siginfo_t *data, void *extra) {mode = data -> si_value.sival_int;

}

int main2() {

sigset_t mask, omask, allmask;

struct sigaction s, os;

int local_mode;

s.sa_flags = 0;

s.sa_mask = mask;

s.sa_sigaction = & change_mode;

/* mask used to mask out mode changes whilst accessing */

/* current mode */

sigemptyset(&mask);

sigaddset(&mask, MODE_CHANGE);

sigaction(MODE_CHANGE, &s, &os);

/* allmask used to mask all signals except mode change, */

/* whilst waiting for the new mode */

sigfillset(&allmask);

sigdelset(&mask, MODE_CHANGE);

while(1) {

sigprocmask(SIG_BLOCK, &mask, &omask);

local_mode = mode;

sigprocmask(SIG_UNBLOCK, &mask, &omask);

/* periodic operation using mode*/

if(local_mode != MODE_A) {/* wait for mode change */

sigsuspend(&allmask);

} else{/* code for mode A */

WAIT_NEXT_PERIOD;

}}return 0;

}

Question 11.1

It will fail because of the execution of the select state-ment is not an atomic operation. It is possible for a taskcalling the urgent entry to timeout or abort after theevaluation of the guards to the medium or low priorityentries but before the rendezvous is accepted. If this isthe only task on the queue then both the other entriesare closed even though there is no available entry on theurgent entry. An entries on the medium and low priorityqueues are blocked.

The reason you cannot extend the solution to a nu-meric solution with a range of 0 to 1000 is that it is notpractical to enumerate all the members of the family.

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;

for I in Level loop

if Pending(I) > 0 then

accept(I)(D:Data) do null end;

20

Page 21: Determining Economic News Coverage

Pending(I) := Pending -1;

Total := Total - 1;

exit; -- look for new calls

end if;

end loop;

end loop;

end Controller;

Question 11.2

public class ResourceManager

{

private final int maxResources = 100;

private int resourcesFree;

public ResourceManager()

{resourcesFree = maxResources;

}

public synchronized void allocate(int size)

throws IntegerConstraintError

// see ** for definition of IntegerConstraintError

{if(size > maxResources) throw

new IntegerConstraintError(1,maxResources, size);

while(size< resourcesFree) wait();

resourcesFree = resourcesFree - size;

}

public synchronized void free(int size)

{resourcesFree = resourcesFree + size;

notifyAll();

}}

Question 11.5

Assuming that tasks are queued on entries in priorityorder:

type Request_Range is range 1..Max;

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;

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;

procedure Free(R : Resource;

Amount : Request_Range) is

begin

Freed := Freed + Amount;

-- free resources

Queued := 0;

end Free;

end Resource_Controller;

Question 11.6

#include "mutex.h"

const int N = 32;

typedef struct

pthread_mutex_t mutex;

pthread_cond_t free;

int free_resources;

resource;

void allocate(int size, resource *R)

pthread_mutex_lock(&R->mutex);

while(size > (R->free_resources))

pthread_cond_wait(&(R->free), &(R->mutex));

R->free_resources = R->free_resources - size;

pthread_mutex_unlock(&R->mutex);

void deallocate(int size, resource *R)

pthread_mutex_lock(&R->mutex);

R->free_resources = R->free_resources + size;

pthread_cond_broadcast(&R-> free);

pthread_mutex_unlock(&R->mutex);

void initialize(resource *R)

R->free_resources = N;

/* initialise mutex and condition variables */

Question 11.7

The system is in deadlock because P2 is waiting for R5which has been allocated to P4, P4 is waiting for R2which has been allocated to R2. There is only one in-stance of R2 and R5 therefore the circular wait cannotbe broken. (A resources allocation graph helps see thecycle.)

Question 11.8

The system is safe because we can run the following pro-cesses to completion: P6; P5; P3; P2; P1; P7

Question 11.9

A system may be unsafe but not deadlock because aprocess may release some resources before requesting its

21

Page 22: Determining Economic News Coverage

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 fur-ther 2 resources and there are not enough to go around.However if P1 releases 1 before requesting 3, P2 can runto completion so at this point the state is safe.

Question 11.10

public class RequestData {...};

public class LineController extends Thread

{

private RequestData[] queue;

private int capacity;

private int size;

private int head;

private int tail;

private boolean overLoaded = false;

public LineController(int c)

{capacity = c;

queue = new RequestData[capacity];

}

public synchronized boolean request(RequestData R)

{

if (size == capacity - 1) overLoaded = true;

else {queue[head] = R;

head = (head + 1) % capacity;

size++;

if(size < capacity - (capacity % 2)) overLoaded = false;

notifyAll();

}return overLoaded;

}

public void run()

{RequestData R;

while(true) {synchronized(this) {

try {while(size == 0) wait();

R = queue[tail];

tail = (tail + 1) % capacity;

size --;

}catch (InterruptedException IE) {};}}}

}

public class network

{public final int lineA = 0;

public final int lineB = 1;

public final int lineC = 2;

public LineController la = new LineController(lineA);

public LineController lb = new LineController(lineB);

public LineController lc = new LineController(lineC);

}

public class Router

{

private network net;

private boolean ok[] = {true, true, true};

public Router( network n)

{net = n;

}

public synchronized boolean send()(...)

{boolean nowOverloaded = true;

RequestData R = new RequestData();

if(ok[net.lineA]) {if (nowOverloaded == net.la.request(R)(...))

ok[net.lineA] = false;

else

ok[net.lineA] = true;

} else if(ok[net.lineB]) {if (nowOverloaded == net.lb.request(R)(...))

ok[net.lineB] = false;

else

ok[net.lineB] = true;

} else if(ok[net.lineC]) {if (nowOverloaded == net.lc.request(R)(...))

ok[net.lineC] = false;

else

ok[net.lineC] = true;

} else {// all lines full

return false;

}return true;

}}

Question 12.1

A timing failure is defined to be the delivery of a serviceoutside its defined delivery interval - typically beyondsome defined deadline. Often the service is delivered latebecause of the time needed to construct the correct valuefor the service. If the system was designed to alwaysdeliver a value in the correct interval then the ”lack oftime” would be manifest as an incorrect value (deliveredon time). Hence timing and value failures cannot beconsidered orthogonal.

The converse to the above can also be true. A servicethat has failed because the value it delivers is incorrectmay be able to deliver a correct value if it is given more(CPU) time; hence a correct value may be delivered buttoo late. However this is not universally true; a valuefailure (or error) can be due to many reasons (e.g. soft-ware error, hardware error) other than insufficient allo-cation of processor cycles.

22

Page 23: Determining Economic News Coverage

Question 12.3

1. The handling of both exceptions can use the stan-dard Ada syntax. The difficult with both excep-tions is getting the associated ”time” value to therun-time. A static approach might use a pragma,although arguable these static values should be setat link time. A dynamic approach must use a callinto the run-time (via some CIFO like entry). Un-fortunately this is not really satisafactory for theD E because time will have progressed before thiscall is made and hence the deadline would not beaccurately measured.

2. For DEADLINE ERROR (D E) the delay queuecan be used. As a block is entered a value cor-responding to the deadline is placed in the queue;if the block ends before the deadline expires thenit is removed from the queue. If the delay (dead-line) expires then the run-time must transfer thisto an exception in the task; the difficulty is thatthat task may not be executing hence it must bemarked appropriately for when it next executes.The WCET ERROR can only ”go off” when thetask is actually running; it has the difficulty thateach time the task is switched out the time must bestopped. A run-time may use an interval timer tocount down the ”budget”; the current value beingstored in the TCB. However both checks have theproblem 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 canprogram error recovery. With WCET E this is rel-atively easy to do. Correct (time-wise) run-timebehaviour is dependent on no task (process) tak-ing more CPU time then was allocated to it duringthe schedualability analysis. If a task takes morethen it is at fault and it should recover. Hence atask (or block within) has two WCET values; onefor the code and the other for the recovery code. Ifthe recovery code fails then the task had better beaborted. The schedualability analysis must guaran-tee the both values. If no task uses more than itsWCET, and the schedualability analysis was cor-rect then arguably no task (or block) can miss itsdeadline! and hence D E is not useful. If only D Eis available and is raised how can a block guaranteeto execute the recovery action in a timely fashion?It did not complete the real code so it is unlikely tocomplete the recovery code. A language may thusneed to raise the priority of a task that is handlinga D E.

A good answer should argue that WCET E is more use-ful then D E (or have convincing arguments the otherway!).

Question 12.4

If Hoare semantics for signal are used then a signal thatwakes a process is blocking - in the sense that the processthat wakes another up waits until that process has exited(or become suspended) before continuing. A cascadewake 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;

end delay;

end time;

Question 12.5

The difficult with Ada is the avoidance semantics onguards. In order to know how many ticks must be waitedfor, the rendezvous must be accepted. Then for eachtick every waiting task will need to rendezvous with theserver task and recall when necessary A solution willhave 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;

This solution is however not resilient against abort.

23

Page 24: Determining Economic News Coverage

Question 13.1

With the rate monotic scheduling approach, all processesare allocated a priority according to their periods. Theshorter the period the higher the priority. Process Pwould there have a higher priority than Q which wouldhave a higher priority than S. A preemptive scheduler isused and therefore the processes would be scheduled inthe following order.

time process total time forcurrent period

1 P 12 Q 13 Q 24 P 15 S 16 S 27 P 18 Q 19 Q 210 P 111 S 312 S 413 P 114 Q 115 Q 216 P 117 S 518 idle

The three processes may be scheduled using the cyclicexecutive approach by splitting up process S into 5 equalparts S1, S2, S3, S4, and S5. (from the above rate mono-tonic solution). The loop is given by:

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 thesecond most important (after P) and with requirementof 6 1.

Question 13.2

a As P has the highest priority it will run first for 30ms. Then Q will run for 1 ms; unfortunately it hasmissed its first five deadline at 6ms, 12ms, 18, 24msand 30ms. S will run last (after 31ms) but havemissed its deadline at 25ms.

b Utility of P is 30%. Utility of Q is 16.67%. Utilityof S is 20%. Total utility is 66.67%.

c Two approaches could be used. If scheduling is basedon earliest deadline then the test is that total util-isation is less than 100priority model is used thenthe rate monotonic test could be applied. It willnot be assumed that the general test can be remem-bered by the student, although the lower bound valueof 69% should be. As total untilisation is less than69% the process set is scheduable. The rate mono-tonic scheme assigns priorities in an inverse relationto period length.

d For rate monotonic Q will have highest static prior-ity, then S and then P. The execution sequence willbe:

Process Execution Time Total Time

Q 1 1

S 5 6

Q 1 7

P 5 12

Q 1 13

P 5 18

Q 1 19

P 5 24

Q 1 25

S 5 30

Q 1 31

P 5 36

Q 1 37

P 5 42

Q 1 43

P 5 48

Q 1 49

idle 1 50

For earliest deadline the execution sequence will be thesame up to the first idle time.

Question 13.3

At the minimum execution of R its utility is 10% (To-tal now 76.67%). At the maximum execution R utilityis 50% (Total now 116.67%). As R is not safety criti-cal then it must miss its deadline (if any process must).The earliest deadline scheme will not ensure this. Theapproach that should be taken is to use rate monotonicscheme and to transform P so that its period is less thanR; ie P becomes a process with a period of 10 and a re-quirement of 3ms (per period). With the new scheme Qwill still have the highest static priority, then P, then Sand lowest priority will go to R. The execution sequencewill be:

Process Execution Time Total Time

Q 1 1

P 3 4

S 2 6

Q 1 7

S 3 10

P 2 12

Q 1 13

P 1 14

24

Page 25: Determining Economic News Coverage

R 4 18

Q 1 19

R 1 20

P 3 23

R 1 24

Q 1 25

S 5 30

Q 1 31

P 3 34

R 2 36

Q 1 37

R 3 40

P 2 42

Q 1 43

P 1 44

R 4 48

Q 1 49

R 1 50

With this scheme S gets 16ms in its first period.

Question 13.4

The new diagram will look as follows:

1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 200

Time

A A’

S T

B A A’ B’

TS

S T

S T

A B’BA’

y

w

x

z

The result of inheritance is that the highest priorityprocess now finishes at time 12 (rather than 16) and P1(the next highest) now completes at time 13 (rather than17). There are also less context switches.

Question 13.6

The rule for calculating blocking is: the maximum crit-ical section with a ceiling equal or higher than the taskbut used by a task with a priority lower.

The first part is to calculate the ceilingsof each resource. We shall let the letters

A,B,C,D,E stand for the tasks and their priorities.Resource Used By CeilingR1 B,D BR2 B,E BR3 A,C AR4 C CR5 C,D CR6 D,E DNote 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 thus250ms.

Task D: All ceilings are higher (or equal) but only R2and R6 are used by E; the maximum value is thus 175ms.

The lowest priority task cannot experience a block;hence maximum is 0.

Question 13.7

The task set is schedulable asU(P1) = 0.2U(P2) = 0.25U(P3) = 0.3Hence U = 0.75 which is below the threshold of 0.780

for thress processes.

Question 13.8

The task set is unschedulable because priorities havebeen assigned that are not optimal. It must have pe-riod transformation applied to it. P1 is transformed toa task that has period 6 and computation time 1. RMSnow gives P1 the highest priority (ie P1 is highest andthe allocation is optimal).

The utilisation of the task set is .1666 + .333 + .25which is below the bound for schedulability. Hence sys-tem is OK.

Question 13.9

The key here is to note that the formulae is necessarybut not sufficient. This means that if a task set passesthe test it is schedulable but if it failes the test it mayor may not be scheduable. The worst phases for periodsis when they are relative primes. The given task set hasone task as half the frequency of the other and hence theutilisation bound on this set is above that predicted bythe formulae.

25

Page 26: Determining Economic News Coverage

Question 13.13

The key here is to recognise that the period of the pro-cess has to be at least half the deadline of the event.

Question 13.14

The processes must be given priorities in rate order soC Event, E Event, B Event, A Event and D Event is thecorrect order.

Utilisation for each process must be worked out:A Event 11.11%B Event 8.33%C Event 20%D Event 16.67%E Event 16.67%Giving a total of 72.78%The lower bound test of 69% would imply not schedu-

lable. But for 5 tasks the bound is 74the process set isschedulable

Question 13.15

To schedule optimally the priorities must be assigned bythe deadline monotonic rule. This gives process b thehighest priority, then process a, then process c. Premp-tive scheduling must be used. Applying equation theresponse time equation gives R b = 4, R a = 8 and R c= 29 Hence all tasks are schedulable.

Question 13.16

Basically, WCET and blocking time can be wrong, spo-radics can be invoked more often that anticipated, andthe application periodic processes could compute thewrong delay value. The tools may be wrong.

RTS could handle the timing events for periodics, andcheck that sporadics don’t go off more often than antic-ipate. Watdog timers?

Still can’t really guarantee without memory firewalls.

Question 13.17

See Concurrency in Ada, by Burns and Wellings, 2ndEdition page 287.

Question 13.18

standard code for sporadic - needs a protected:

protected Guard is

entry Proceed;

procedure Go;

private

Ok : Boolean := False;

end Guard;

protected body Guard is

entry Proceed when Ok is

begin

Ok := False;

end;

procedure Go is

begin

Ok := True;

end;

end Guard;

task Sporadic;

task body Sporadic is

...

begin

loop

Guard.Proceed;

-- code for sporadic

end loop;

end Sporadic;

To protect itself against executing too early requires theuse of a delay statement. A simple scheme would justhave:

task body Sporadic is

...

begin

loop

Guard.Proceed;

-- code for sporadic

delay(Separation);

end loop;

end Sporadic;

This is pessimistic in that it delays the sporadic too long.A good solution will time stamp the release event:

protected Guard is

entry Proceed(Release_Time : out Time);

procedure Go;

private

Ok : Boolean := False;

T : Time; -- from either time package

end Guard;

protected body Guard is

entry Proceed(Release_Time : out Time) when Ok is

begin

Ok := False;

Release_Time := T;

end;

procedure Go is

begin

Ok := True;

T := Clock;

end;

end Guard;

task body Sporadic is

...

Next : Time := Clock;

T : Time;

begin

loop

Guard.Proceed(T);

Next := Max(Next, T) + Separation;

-- code for sporadic

26

Page 27: Determining Economic News Coverage

delay until (Next);

end loop;

end Sporadic;

Question 13.19

See M. Gonzalez Harbour and J.J. Gutierrez Garciaand J.C. Palencia Gutierrez, Implementing Application-Level Sporadic Server Schedulers in Ada 95, ReliableSoftware Technologies - Ada Europe 97 Lecture Notesin Computer Science, Vol 1251, pp 125-136, 1997

Question 13.20

With the mode change example, a number of tasks needto have their priorities changed. Typically, these changesshould take place atomically (that is, all changed to-gether). To achieve this, a protected object with a highceiling priority could be used. For example, in the fol-lowing, a group of N tasks can exist in one of four modes.A call of Set Mode will change the priorities of the tasks.Each task must, however, first call Register, so that itsidentity can be held:

with Ada.Task_Identification;

with Ada.Dynamic_Priorities;

use Ada.Dynamic_Priorities;

with System;

package Flight_Management is

N : constant Positive := ...;

type Task_Range is range 1..N;

type Mode is (Taxiing, Take_Off, Cruising, Landing);

Mode_Priorities : array(Task_Range, Mode) of System.Priority;

-- priorities are set during an

-- initialisation phase of the program

type Labels is array(Task_Range) of

Ada.Task_Identification.Task_Id;

protected Mode_Changer is

pragma Priority(System.Priority’Last);

procedure Register(Name : Task_Range);

procedure Set_Mode(M : Mode);

private

Current_Mode : Mode := Taxiing;

Task_Labels : Labels;

end Mode_Changer;

end Flight_Management;

The body of Mode Changer will be

protected body Mode_Changer is

procedure Register(Name : Task_Range) is

begin

Task_Labels(Name) :=

Ada.Task_Identification.Current_Task;

end Register;

procedure Set_Mode(M : Mode) is

begin

if M /= Current_Mode then

Current_Mode := M;

for T in Task_Range loop

Set_Priority(Mode_Priorities(T,M),Task_Labels(T));

end loop;

end if;

end Set_Mode;

end Mode_Changer;

Note that this will only work if all the tasks first register.

13.23

TBD

Question 15.1

-- assuming System is already withed and used

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;

task Patient_Monitor;

protected body Interrupt_Handler is

procedure Handler is

begin

Interrupt_Occured := True;

end Handler;

entry Wait_Heart_Beat when Interrupt_Occured is

begin

Interrupt_Occured := False;

end Wait_Heart_Beat;

end Interrupt_Handle;

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;

27

Page 28: Determining Economic News Coverage

end loop;

end Patient_Monitor;

Question 15.2

This is an Ada 83 solution. The Ada 95 is TBD.

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

type Transmit_T is (No, Yes);

for Transmit_T use (No => 0, Yes => 1);

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;

for Cr_T use record at mod 2;

C1 at 0 range 0 .. 7;

C2 at 0 range 8 .. 15;

C3 at 1 range 0 .. 7;

C4 at 1 range 8 .. 15;

C5 at 2 range 0 .. 7;

C6 at 2 range 8 .. 15;

C7 at 3 range 0 .. 7;

C8 at 3 range 8 .. 15;

Go at 4 range 0 .. 0;

Details at 4 range 1 .. 4;

Code at 4 range 5 .. 15;

end record;

Cr : Cr_T;

for Cr use at 8#177762#;

Shadow : Cr_T;

Dr : Integer;

for Cr use at 8#177760#;

Current_Cost : Integer := 0;

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;

end Motorway_Charges;

Question 15.3

In Ada (83, solution has not been updated yet):

with System; use System;

package Slotted_Ring_Driver is

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;

-- etc

procedure Transmit

(To_Station : Station_Id;

Data : Integer);

procedure Receive

(From_Station : out Station_Id;

Data : out Integer);

private

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;

package body Slotted_Ring_Driver is

type Response_Bits is (Cleared, Accepted);

for Response_Bits use (Cleared => 0,

Accepted => 3);

type Csr_T is

record

28

Page 29: Determining Economic News Coverage

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#;

Data_Reg : Integer;

for Src_Addr use at 8#177766#;

My_Id : Station_Id := 3;

Obuffer_Empty : Boolean;

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;

task Output_Buffer is

--pragma PRIORITY(6);

-- pragma signal(take);

entry Append(I : Integer;

From_Station : Station_Id);

entry Take;

end Output_Buffer;

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;

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;

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

-- 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;

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;

29

Page 30: Determining Economic News Coverage

In Modula.

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;

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;

buf2[in2].addr := to;

in2 := (in2 MOD n)+1;

inc(n2)

END transmit;

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 *)

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.

DEVICE MODULE monitor[6];

PROCESS interrupt[60B];

VAR

csr[177760B] : bits;

BEGIN

csr[6] := true;

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.

Question 15.4

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:

30

Page 31: Determining Economic News Coverage

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

:

PRI PAR

supervisor

handler

PAR

-- rest of program

:

Question 15.5

device module arm(4);

define move_to_position;

dbr [177234B] : integer;

csr [177236B] : bits;

ready : signal;

procedure move_to_position(X:integer);

begindbr := X;

wait(ready);

end move_to_position;

process driver[56B];

beginloop

csr[6] := true;

doio ;

csr[6] := false;

send(ready);

endend driver;

begindriver;

end arm;

Question 15.6

device module timing[6];

define delay;

var tick : signal;

procedure delay(n:integer);

var count : integer;

begincount := n;

while count > 0 dowait(tick); dec(count);

end ;

end delay;

process clock[100B];

var csr[177546] : bits

beginloop

csr[6] := true;

doio;

while awaited(tick) dosend(tick)

endend

end ;

beginclock;

end timing;

Question 15.9

PORT OF INT16 Limit.Register:

PLACE Limit.Register AT #AA14#:

PORT OF INT16 CSR.Register:

PLACE CSR.Register AT #AA16#:

PORT OF INT16 DBR.Register:

PLACE CSR.Register AT #AA18#:

PORT OF INT16 Flash.Register:

PLACE Flash.Register AT #AA12#:

CHAN of Any Interrupt:

PLACE Interrupt at #60#

VAL INT16 G0 is 66:

INT Speed.Limit:

INT OK:

PRI PAR

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

SEQ

WHILE TRUE

Interrupt ? Any

Flash.Register ! 1

Question 15.10

DEVICE MODULE SpeedControlSystem [5];

VAR

Light[177750B] : INTEGER;

CurrentLimit[177760B] : INTEGER;

CSR[177762B] : bits;

DBR[177764B] : INTEGER;

31

Page 32: Determining Economic News Coverage

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;

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;

In Ada:

package Beacon is

procedure Start_Monitor;

procedure Stop_Monitor;

end Beacon;

with System; use System;

with System.Storage_Elements;

with Ada.Interrupts; use Ada.Interrupts;

package body Beacon is

Word : constant := 2;

Bits_In_Word : constant := 16;

type Flag is (Clear, Set);

for Flag use (Clear => 0, Set => 1);

type Errors is range 0 .. 15;

type Control_And_Status_Register is

record

D_Enable : Flag;

Go : Flag;

I_Enable : Flag;

Error : Errors;

end record;

for Control_And_Status_Register use

record

D_Enable at 0 range 0 .. 0;

Go at 0 range 1 .. 1;

I_Enable at 0 range 6 .. 6;

Error at 0 range 12 .. 15;

end record;

for Control_And_Status_Register’Size use Bits_In_Word;

for Control_And_Status_Register’Alignment use Word;

for Control_And_Status_Register’Bit_order

use High_Order_First;

Csr : Control_And_Status_Register;

for Csr’Address use

System.Storage_Elements.To_Address(8#177762#);

type Speed is range 0 .. 200;

Current_Speed_Limit : Speed;

for Current_Speed_Limit’Address use

System.Storage_Elements.To_Address(8#177760#);

Required_Speed : Speed;

for Required_Speed’Address use

System.Storage_Elements.To_Address(8#177764#);

type Flash is (Off, On);

for Flash use (Off => 0, On => 1);

Flasher : Flash;

for Flasher’Address use

System.Storage_Elements.To_Address(8#177750#);

Beacon_Interrupt : Interrupt_Id := 8#60#;

protected Road_Side_Beacon is

--pragma Interrupt_Priority(5);

private

procedure Broken_Limit;

pragma Attach_Handler(Broken_Limit, Beacon_Interrupt);

end Road_Side_Beacon;

protected body Road_Side_Beacon is

procedure Broken_Limit is

begin

if Csr.Error != 0 then

Flasher := On;

end if;

end Broken_Limit;

end Road_Side_Beacon;

task Monitoring is

entry Start;

entry Stop;

end Monitoring;

task body Monitoring is

Next : Time := Clock;

Shadow : Control_And_Status_Register;

begin

loop

accept Start;

Required_Speed := Current_Speed_Limit;

Shadow := (D_Enable => Set, I_Enable => Set,

Go => Set, Error => 0);

Csr := Shadow;

loop

Next := Next + 60.0;

delay until Next;

Required_Speed := Current_Speed_Limit;

select

accept Stop;

exit;

else

null;

end select;

end loop;

end loop;

end Monitoring;

procedure Start_Monitor is

begin

Monitoring.Start;

end Start_Monitor;

32

Page 33: Determining Economic News Coverage

procedure Stop_Monitor is

begin

Monitoring.Stop;

end Stop_Monitor;

end Beacon;

Question 15.11

Shared memory approach is Modula-1, message passingis occam2. We compare them considering:

encapsulation facility Modula-1 has the device mod-ule; occam2 only has the proc

communication between CPU and devicesModula-1 uses shared variables; occam2 sendsmessages via channels

device registers representation program datastructure in Modula-1; special program channelcalled a port in occam2

addressing device registers memory address associ-ated with the variable in Modula-1:

VAR rdb[177562B] CHAR

address associated with the port in occam2:

PORT OF INT16 P:

PLACE P AT #AA12#:

manipulating device regsiters arrays of bits only inModula-1;bit operators only in occam2

Interrupt handling In Modula-1: interrupt associ-ated with modula signal-like operations; DOIOwaits for the signal to occur; interrupt is equiva-lent to sending the signal. In occam2: interruptassociated with a channel; driver receives null inputon the channel; device sends null output down thechannel.

representation of hardware priority parameter todevice module in Modula-1; have to use a PRI PARin occam2

interrupt identification by an address clause on theinterrupt handling process in Modula-1; by addressclause on interrupt channel in occam2

Question 16.2

In any interval being considered, it is possible to calcu-late the number of time, K, the clock handler could haveexecuted:

K =⌈RiTclk

It is also possible to calculate the number of move-ments, V , there has been from the delay queue to thedispatch queue:

V =∑g∈Γp

⌈RiTg

⌉where Γp is the set of periodic tasks.

If K ≥ V , we must assume, for the worst case, thateach movement occurs on a different clock tick (andhence must be costed at CT c). If this is not the case,a reduuced cost can be used. Hence equation 16.4 be-comes:

Ri = CS1 + Ci + Bi

+∑

j∈hp(i)

⌈RiTj

⌉(CS1 + CS2 + Cj)

+∑k∈Γs

⌈RiTk

⌉IH +

⌈RiTclk

⌉CTc

+ IΓp

IΓp = if K ≥ V : V ∗ CT s

else K ∗ CT s + (V −K) ∗ CTm

Question 16.4

This periodic task suffers release jitter. It the worst casethis is 20 milliseconds. Use equations 13.11 and 13.12 tocalculate response time with this jitter.

33