Matthew Heaney1 Implementing Design Patterns in Ada95 Tips, Tricks,and Idioms by Matthew Heaney.

Post on 27-Mar-2015

214 views 0 download

Tags:

transcript

Matthew Heaney 1

Implementing Design Patterns

in Ada95Tips, Tricks,and Idioms

by Matthew Heaney<mailto:matthew_heaney@acm.org>

Matthew Heaney 2

Send a message with the body

subscribe patterns <your full name>

to the ACM mailing list server:

<mailto:listserv@acm.org>

Search the archives for pattern implementations:

<http://www.acm.org/archives/patterns.html>

Join the Ada95 patterns list!

Matthew Heaney 3

Interpreter

Matthew Heaney 4

What’s An Interpreter?

• Interpret sentences in a language specified by a grammar.

• Each production in the grammar is implemented as a type.

• As a lexical expression is parsed, an object is created for each production in the sentence.

Matthew Heaney 5

Boolean Expression Grammar

<exp> ::= <and exp> | <or exp> |<not exp> | <var exp> | <const exp>

<and exp> ::= <exp> and <exp>

<or exp> ::= <exp> or <exp>

<not exp> ::= not <exp>

<var exp> ::= <name>

<const exp> ::= true | false

Matthew Heaney 6

package Bool_Exps is

type Bool_Exp (<>) is abstract tagged limited private;

type Bool_Exp_Access is access all Bool_Exp'Class;

function Eval (Exp : access Bool_Exp; Context : in Exp_Context) return Boolean is abstract;

function Copy (Exp : access Bool_Exp) return Bool_Exp_Access is abstract; ...

Matthew Heaney 7

... procedure Free (Exp : in out Bool_Exp_Access);

private

type Bool_Exp is abstract tagged limited null record; procedure Do_Free (Exp : access Bool_Exp);

...end Bool_Exps;

Matthew Heaney 8

The Need For Indirection

• Some expressions (<and>, <or>, <not>) contain other expressions.

• We don’t know the size of the expression component (of type Bool_Exp’Class, which is indefinite), so we must refer to it indirectly.

• “Containment by reference” instead of “containment by value.”

Matthew Heaney 9

package Bool_Exps.And_Exps is

type And_Exp is new Bool_Exp with private;

function New_And (L, R : access Bool_Exp'Class) return Bool_Exp_Access;

function Eval (Exp : access And_Exp; Context : in Exp_Context) return Boolean;...

Matthew Heaney 10

...private

type And_Exp is new Bool_Exp with record L, R : Bool_Exp_Access; end record;

procedure Do_Free (Exp : access And_Exp);

end Bool_Exps.And_Exps;

Matthew Heaney 11

Desiderata

• We want prevent the client from creating or destroying instances directly, to allow each type to define and enforce its own storage management policy, and hide the details.

• We want to minimize syntactic overhead (don’t want to have to explicitly dereference a pointer).

Matthew Heaney 12

Implementation

• Designated type is limited and indefinite. Limited-ness prevents (shallow) copies, and indefinite-ness prevents direct allocation.

• Each specific type declares a constructor, so a client can create instances of type. (A client never calls allocator new directly.)

Matthew Heaney 13

• Primitive operations take access parameters. Therefore, no explicit dereferencing is necessary.

• Each type declares its own private deconstructor, which performs type-specific clean-up prior to actual deallocation.

• The client reclaims storage for an object by explicitly calling a public, class-wide deconstructor, which is implemented by calling the type’s private deconstructor.

Matthew Heaney 14

((True and X) or (Y and (not X)))

declare Exp : Bool_Exp_Access := New_Or (New_And (New_Const (True), New_Var ('X')), New_And (New_Var ('Y'), New_Not (New_Var ('X'))));

Exp_Value : constant Boolean := Eval (Exp, Context); begin Free (Exp);end;

Matthew Heaney 15

package body Bool_Exps.And_Exps is ... function Eval (Exp : access And_Exp; Context : in Exp_Context) return Boolean is begin return Eval (Exp.L, Context) and Eval (Exp.R, Context); end Eval;

Matthew Heaney 16

package body Bool_Exps.And_Exps is

type And_Exp_Access is access all And_Exp;

function New_And (L, R : access Bool_Exp'Class) return Bool_Exp_Access is

Exp : constant And_Exp_Access := new And_Exp; begin Exp.L := Bool_Exp_Access (L); Exp.R := Bool_Exp_Access (R);

return Bool_Exp_Access (Exp); end New_And;

Matthew Heaney 17

Deallocation• Client manually calls a class-wide Free

operation to deallocate an expression object.

• Free can’t deallocate the (class-wide) object directly, because type-specific clean-up may be required.

• Free internally calls the private operation Do_Free, which dispatches according to the object’s tag. The type itself does the clean-up and actual deallocation.

• Free is an example of a “template method.”

Matthew Heaney 18

body Bool_Exps is ... procedure Free (Exp : in out Bool_Exp_Access) is begin if Exp /= null then

Do_Free (Exp); -- dispatches

Exp := null;

end if; end Free;

end Bool_Exps;

Matthew Heaney 19

package body Bool_Exps.And_Exps is ... procedure Do_Free (Exp : access And_Exp) is

procedure Deallocate is new Ada.Unchecked_Deallocation (And_Exp, And_Exp_Access);

EA : And_Exp_Access := And_Exp_Access (Exp);

begin

Do_Free (Exp.L); Do_Free (Exp.R);

Deallocate (EA);

end Do_Free;

end Bool_Exps.And_Exps;

Matthew Heaney 20

Constant Expressions

• The type Const_Exp has only two values: True and False.

• Because objects are referred to indirectly, multiple clients can share the same object, thus avoiding allocation of duplicate values.

• This is an example of the Flyweight pattern.

Matthew Heaney 21

package Bool_Exps.Const_Exps is pragma Elaborate_Body;

type Const_Exp is new Bool_Exp with private;

...

function New_Const (Value : Boolean) return Bool_Exp_Access;

...

Matthew Heaney 22

package body Bool_Exps.Const_Exps is

type Const_Exp_Array is array (Boolean) of aliased Const_Exp;

Const_Exps : Const_Exp_Array;

function New_Const (Value : Boolean) return Bool_Exp_Access is begin return Const_Exps (Value)'Access; end;

...

Matthew Heaney 23

...

begin

for Value in Const_Exps'Range loop Const_Exps (Value).Value := Value; end loop;

end Bool_Exps.Const_Exps;

Matthew Heaney 24

Smart Pointers

Matthew Heaney 25

Motivation

• One issue with the Interpreter example is that deallocation of expression objects must be done manually by the client, by explicitly calling Free.

• This is an obvious source of memory leaks and dangling references.

• Besides its being prone to error, explicit deallocation also carries a fair amount of syntactic overhead.

Matthew Heaney 26

Perform_Mental_Gymnastics: declare Replacement : Bool_Exp_Access := New_Not (New_Var ('Z'));

Rep_Exp : constant Bool_Exp_Access := Replace (Exp, 'Y', Replacement); begin Free (Replacement); Free (Exp); Exp := Rep_Exp; end Perform_Mental_Gymnastics;

Matthew Heaney 27

Desiderata

• Low syntactic overhead. Manipulation of smart pointers should be similar to regular access objects.

• By-reference semantics implies a reference-counting scheme.

• No explicit deallocation is ever required. Implies use of a Controlled type.

Matthew Heaney 28

package Bool_Exps is

type Bool_Exp (<>) is abstract tagged limited private;

type Bool_Exp_Access is access all Bool_Exp'Class;

type Exp_Handle is private;

function "+" (Handle : Exp_Handle) return Bool_Exp_Access;

function Null_Handle return Exp_Handle; ...

Matthew Heaney 29

private

type Bool_Exp is abstract tagged limited record Count : Natural; end record;

type Exp_Handle_Rep is new Controlled with record Exp : Bool_Exp_Access; end record;

procedure Adjust (Handle : ...)

procedure Finalize (Handle : ...);

type Exp_Handle is record Rep : Exp_Handle_Rep; end record;

Matthew Heaney 30

((True and X) or (Y and (not X)))declare Exp : constant Exp_Handle := New_Or (New_And (New_Const (True), New_Var ('X')), New_And (New_Var ('Y'), New_Not (New_Var ('X'))));

Exp_Value : constant Boolean := Eval (+Exp, Context);begin null;end;

Matthew Heaney 31

declare Replacement : Bool_Exp_Access := New_Not (New_Var ('Z'));

Rep_Exp : constant Bool_Exp_Access := Replace (Exp, 'Y', Replacement);begin Free (Replacement); Free (Exp); Exp := Rep_Exp;end;

Without Smart Pointers

Matthew Heaney 32

declare Replacement : constant Exp_Handle := New_Not (New_Var ('Z'));begin Exp := Replace (+Exp, 'Y', Replacement);end;

With Smart Pointers

Matthew Heaney 33

function Eval (Exp : access And_Exp; Context : in Exp_Context) return Boolean is begin return Eval (+Exp.L, Context) and Eval (+Exp.R, Context); end Eval;

Matthew Heaney 34

Implementation

• A “smart pointer” is a non-limited type that privately derives from Controlled, and has an access object as its only component.

• It uses unary plus “+” to return the value of the internal access object, which is used immediately as the actual parameter in subprogram calls.

Matthew Heaney 35

• The type designated by the access type has a Count component to store the number of references.

• When the reference count drops to zero (meaning there are no more references to the object), the designated object is automatically returned to storage.

Matthew Heaney 36

Consequences

• Constructors now return Exp_Handle instead of Bool_Exp_Access.

• Expression components (of <and>, <or>, and <not> expressions) are now of type Exp_Handle.

• Small syntactic penalty necessary to dereference handle object.

Matthew Heaney 37

package Bool_Exps.And_Exps is

type And_Exp is new Bool_Exp with private;

function New_And (L, R : Exp_Handle) return Exp_Handle;

function Eval (Exp : access And_Exp; Context : in Exp_Context) return Boolean; ...

Matthew Heaney 38

...private

type And_Exp is new Bool_Exp with record L, R : Exp_Handle; end record;

procedure Do_Free (Exp : access And_Exp);

end Bool_Exps.And_Exps;

Matthew Heaney 39

function New_And (L, R : Exp_Handle) return Exp_Handle is

Exp : constant And_Exp_Access := new And_Exp;

Handle_Rep : constant Exp_Handle_Rep := (Controlled with Exp => Exp.all’Access); begin Exp.Count := 1; Exp.L := L; Exp.R := R;

return (Rep => Handle_Rep); end New_And;

Allocation

Matthew Heaney 40

Assignment

• During assignment, the private operation Adjust is called to increment the reference count of the object designated by the pointer.

Matthew Heaney 41

package body Bool_Exps is

...

procedure Adjust (Handle : in out Exp_Handle_Rep) is begin if Handle.Exp /= null then

Handle.Exp.Count := Handle.Exp.Count + 1;

end if; end Adjust;

...

Matthew Heaney 42

Deallocation

• When a smart pointer is assigned a new value, or goes out of scope, then the private operation Finalize is called.

• Finalize decrements the reference count of the designated object.

• If the reference count is zero, then Finalize also returns the object to storage, by calling (dispatching operation) Do_Free.

Matthew Heaney 43

package body Bool_Exps is ... procedure Finalize (Handle : in out Exp_Handle_Rep) is begin if Handle.Exp /= null then

Handle.Exp.Count := Handle.Exp.Count - 1;

if Handle.Exp.Count = 0 then Do_Free (Handle.Exp); end if;

end if; end Finalize;

Matthew Heaney 44

package body Bool_Exps.And_Exps is ... procedure Do_Free (Exp : access And_Exp) is

EA : And_Exp_Access := And_Exp_Access (Exp);

procedure Deallocate is new Ada.Unchecked_Deallocation (And_Exp, And_Exp_Access); begin pragma Assert (Exp.Count = 0); Exp.L := Null_Handle; Exp.R := Null_Handle; Deallocate (EA); end;

end Bool_Exps.And_Exps;

Matthew Heaney 45

Dereferencing• The “deference” operator (“+”) for the smart

pointer has a trivial implementation: it simply returns the internal access value.

• A weakness of the whole approach is that it depends on clients never making a copy or otherwise manipulating the access value.

• Limited access types or garbage-collecting storage pools would be a helpful addition to the language.

Matthew Heaney 46

package body Bool_Exps is ... function "+" (Handle : Exp_Handle) return Bool_Exp_Access is begin return Handle.Rep.Exp; end;

function Null_Handle return Exp_Handle is begin return (Rep => Controlled with null); end; ...end Bool_Exps;

Matthew Heaney 47

Observer

Matthew Heaney 48

Motivation

• It’s often the case that when the state changes in one object, another object needs to be notified of the change. There are a couple of ways of implementing this.

• The subject can know who its observers are by name, and tell them directly about the state change; or,

Matthew Heaney 49

• The subject only knows that it’s being observed. It tells its observer that its state has changed, and then the observer queries the subject for the new state.

• A consequence of the former approach is that every time a new observer is added to the system, the subject must be modified to update yet another observer.

• The latter approach doesn’t suffer from this, because the observer just inserts itself into a list of anonymous observers.

Matthew Heaney 50

package Subjects_And_Observers is

type Subject is tagged limited private;

procedure Notify (Sub : in out Subject'Class);

type Observer is abstract tagged limited private;

procedure Update (Obs : access Observer) is abstract; ...

Matthew Heaney 51

... procedure Attach (Obs : access Observer'Class; To : in out Subject);

procedure Detach (Obs : access Observer'Class; From : in out Subject);

private ...end Subjects_And_Observers;

Matthew Heaney 52

Subjects_And_Observers (public)

• Abstractions that wish to be observed derive from Subject. When the state changes, the abstraction calls Notify to let observers know about the change.

• Abstractions that wish to observe a subject derive from Observer, and Attach themselves to a subject. They must override Update, which is called by the subject during the notification.

Matthew Heaney 53

private

type Observer_Access is access all Observer’Class;

type Subject is tagged limited record Head : Observer_Access; end record;

type Observer is abstract tagged limited record Next : Observer_Access; end record;

end Subjects_And_Observers;

Matthew Heaney 54

Subjects_And_Obsrvrs (private)

• The subject type is implemented as a linked list of observers.

• When an observer wants to be notified of a state change in the subject, it places itself on the subject’s list of observers.

• During a notification, the subject traverses the list, updating each observer in turn.

Matthew Heaney 55

package body Subjects_And_Observers is

procedure Notify (Sub : in out Subject'Class) is

Obs : Observer_Access := Sub.Head; begin

while Obs /= null loop

Update (Obs);

Obs := Obs.Next;

end loop;

end Notify; ...

Matthew Heaney 56

package Clock_Timers is

type Clock_Timer is new Subject with private;

procedure Tick (Timer : in out Clock_Timer);

subtype Hour_Number is Natural range 0 .. 23;

function Get_Hour (Timer : Clock_Timer) return Hour_Number;

...end Clock_Timers;

Matthew Heaney 57

Clock_Timer Subject

• The subject Clock_Timer publicly derives from Subject, which allows it to be observed.

• Tick is the operation that updates the state of the clock timer, and then notifies any observers.

• Selector operations Get_Hour, Get_Minute, etc allow an observer to query the state.

Matthew Heaney 58

Alternate Technique

• Derive from Subject privately, and provide public operations to attach an observer.

Matthew Heaney 59

package Clock_Timers is

type Clock_Timer is private;

procedure Attach (Obs : access Observer’Class; To : in out Clock_Timer);…private

type Clock_Timer is new Subject with record ...

Matthew Heaney 60

package body Clock_Timers is

procedure Tick (Timer : in out Clock_Timer) is

begin

<update hour, min, sec attributes>

Notify (Timer); -- Update observers

end Tick; ...end Clock_Timers;

Matthew Heaney 61

package Digital_Clocks is

type Digital_Clock (Timer : access Clock_Timer'Class) is new Observer with null record;

procedure Update (Clock : access Digital_Clock);

end Digital_Clocks;

Matthew Heaney 62

Digital_Clock Observer

• The observer Digital_Clock derives from Observer type.

• The clock observer binds to its timer subject via an access discriminant. This guarantees that the (clock) subject lives at least as long as the observer, and therefore ensures that no dangling references from observer to subject can occur.

Matthew Heaney 63

• Update is called by Notify, which is called by the timer subject just after it (the subject) has changed its state.

• The clock observer can “see” its timer subject through its access discriminant. During the Update, the clock queries the state of the timer, and then displays the time in a format specific to that observer.

Matthew Heaney 64

package body Digital_Clocks is

procedure Update (Clock : access Digital_Clock) is

Hour : constant Hour_Number := Get_Hour (Clock.Timer.all);

Hour_Image : constant String := Integer'Image (Hour); ... Clock_Image : constant String := Hour_Image & ...; begin Put_Line (Clock_Image); end Update;

Matthew Heaney 65

declare Timer : aliased Clock_Timer; Clock : aliased Digital_Clock (Timer'Access);begin Attach (Clock’Access, To => Timer); Tick (Timer);end;

Matthew Heaney 66

Dynamic Observers

• You may have an application in which observers of a subject are added and removed dynamically.

• We need to automate calls to Attach and Detach, to ensure no dangling reference from subject to observer occurs.

Matthew Heaney 67

declare Timer : aliased Clock_Timer;begin … declare Clock : aliased Digital_Clock(Timer’Access); begin Attach (Clock’Access, To => Timer); Tick (Timer); end; -- Oops! Forget to Detach...

Tick (Timer); -- Notify non-existent observer!end;

Matthew Heaney 68

package Digital_Clocks is

type Digital_Clock (Timer : access Clock_Timer'Class) is limited private;

private

end Digital_Clocks;

Matthew Heaney 69

private

type Control_Type (Clock : access Digital_Clock) is new Limited_Controlled with null record;

procedure Initialize (Control : in out Control_Type);

procedure Finalize (Control : in out Control_Type);

type Digital_Clock (Timer : access Clock_Timer'Class) is new Observer with record Control : Control_Type (Digital_Clock'Access); end record;

procedure Update (Clock : access Digital_Clock);

end Digital_Clocks;

Matthew Heaney 70

Adding Controlled-ness

• We don’t really need to advertise that Digital_Clock derives from Observer, so we declare the partial view of the type as limited private, and implement the full view as a derivation.

• Controlled-ness is added as a component of the extension, because Ada doesn’t have multiple inheritance (and doesn’t need it).

Matthew Heaney 71

• During its initialization, the observer inserts itself on its subject’s observer list.

• During its finalization, the observer removes itself from its subject’s observer list. This guarantees that no dangling reference from subject to observer can occur, because removal is automatic when the lifetime of the observer ends.

Matthew Heaney 72

package body Digital_Clocks is

procedure Initialize (Control : in out Control_Type) is

Clock : Digital_Clock renames Control.Clock.all; Timer : Clock_Timer renames Clock.Timer.all; begin Attach (Clock’Access, To => Timer); end;

procedure Finalize (Control : in out Control_Type) is

Clock : Digital_Clock renames Control.Clock.all; Timer : Clock_Timer renames Clock.Timer.all; begin Detach (Clock'Access, From => Timer); end;…

Matthew Heaney 73

declare Timer : aliased Clock_Timer;begin… declare Clock : Digital_Clock (Timer’Access); -- automatically Attach begin Tick (Timer); end; -- automatically Detach

Tick (Timer); -- OKend;

Matthew Heaney 74

Dynamic Observer Note

• This example was rather contrived, and was really designed to illustrate how to add Controlled-ness to an existing type hierarchy.

• Realistically, a dynamic observer would be declared on the heap. In that case, you could simply Attach in the constructor, and Detach in the deconstructor. A Controlled observer wouldn’t be necessary.

Matthew Heaney 75

package Digital_Clocks is

type Digital_Clock(<>) is limited private;

function New_Clock (Timer : access Clock_Timer) return Digital_Clock_Access;...private

type Digital_Clock (Timer : access Clock_Timer) is new Observer with record ...;

Matthew Heaney 76

package body Digital_Clocks is

function New_Clock (Timer : access Clock_Timer) return Digital_Clock_Access is

Clock : constant Digital_Clock_Access := new Digital_Clock(Timer);begin

Attach(Clock, To => Timer);

return Clock;end;

Matthew Heaney 77

Subject Displays Itself

• You might argue that a subject should be able to display itself, and that providing public selector operations to query the state is actually exposing implementation details about the abstraction.

• In that case, you may decide to make the observer more closely related to the subject, so that it can privately get the state it needs.

Matthew Heaney 78

• We can do this very simply in Ada95, by making the observer a child of the subject. This gives the observer access to the private part of the subject, obviating the need for the subject to provide any public query functions.

Matthew Heaney 79

package Clock_Timers is

type Clock_Timer is limited private;

procedure Tick (Timer : in out Clock_Timer);

private ... type Clock_Timer is new Subject with record Hour : Hour_Number; Minute : Minute_Number; Second : Second_Number; end record;

end Clock_Timers;

Matthew Heaney 80

Clock_Timer Subject

• Since the Digital_Clock observers are going to be children, we can privately derive the Clock_Timer subject from Subject.

• Since non-observer clients don’t care that it’s a subject, the public view of the Clock_Timer type is just (non-tagged) limited private.

Matthew Heaney 81

package Clock_Timers.Digital_Clocks is

type Digital_Clock (Timer : access Clock_Timer) is limited private;

private ... type Digital_Clock (Timer : access Clock_Timer) is new Observer with null record Control : Control_Type (D_Clock’Access); end record;

procedure Update (Clock : access Digital_Clock);

end Clock_Timers.Digital_Clocks;

Matthew Heaney 82

Digital_Clock Observer

• The package Digital_Clocks is now a (public) child of Clock_Timers.

• As before, the Digital_Clock type privately derives from Observer.

• Update now queries the state of the timer directly, without using a query function. The clock has visibility to its subject’s representation because the clock is a child.

Matthew Heaney 83

package body Clock_Timers.Digital_Clocks is

procedure Update (Clock : access Digital_Clock) is

Hour_Image : constant String := Integer'Image (Clock.Timer.Hour + 100); ... Clock_Image : constant String := ...; begin Put_Line (Clock_Image); end Update;

end Clock_Timers.Digital_Clocks;

Matthew Heaney 84

Observers Observed

• We now introduce another variation of our original example, which allows an observer itself to be observed, by another observer.

• As before, a Digital_Clock observes a Clock_Timer. Here, we add another observer, a Clock_Watcher, to observe the Digital_Clock.

Matthew Heaney 85

package Digital_Clocks is

type Digital_Clock (Timer : access Clock_Timer'Class) is new Subject with private;

type Meridian_Type is (AM, PM);

function Get_Meridian (Clock : Digital_Clock) return Meridian_Type;

private …

Matthew Heaney 86

Digital_Clock (public)• The Digital_Clock must announce the fact that it

can be observed, so it publicly derives from Subject.

• But it’s also an observer, so it binds to its Clock_Timer subject via an access discriminant.

• Like any subject, the Digital_Clock provides selector operations to allow its state to be queried by observers.

Matthew Heaney 87

type Timer_Obs_Type (Clock : access Digital_Clock) is new Observer with null record;

procedure Update (Timer_Obs : access Timer_Obs_Type);

type Control_Type (Clock : access Digital_Clock) is new Limited_Controlled with record Timer_Obs : aliased Timer_Obs_Type (Clock); end record;

procedure Initialize (Control : in out Control_Type);

procedure Finalize (Control : in out Control_Type);

type Digital_Clock (Timer : access Clock_Timer'Class) is new Subject with record Control : Control_Type (Digital_Clock'Access); Meridian : Meridian_Type; end record;

end Digital_Clocks;

Matthew Heaney 88

Digital_Clock (private)

• The Digital_Clock already derives from Subject, so in order to be an observer too it will have to have an Observer component.

• A helper type, Timer_Obs_Type, which derives from Observer, is used as the component.

• Here we also use a Controlled type to automatically Attach and Detach the observer. This wouldn’t be necessary if you were to manually Attach to the subject.

Matthew Heaney 89

package body Digital_Clocks is

procedure Initialize (Control : in out Control_Type) is begin Attach (Obs => Control.Timer_Obs'Access, To => Control.Clock.Timer.all); end;

procedure Finalize (Control : in out Control_Type) is begin Detach (Obs => Control.Timer_Obs'Access, From => Control.Clock.Timer.all); end;

Matthew Heaney 90

• The Control_Type can see its enclosing record (Digital_Clock) via its access discriminant.

• The Digital_Clock observer can see its Clock_Timer subject via its access discriminant.

• Together, these allow the Control_Type to Attach its Timer_Obs component to the Timer subject during Initialize, and Detach it during Finalize.

Matthew Heaney 91

procedure Update (Timer_Obs : access Timer_Obs_Type) is begin

<get time from Timer_Obs.Clock.Timer.all> <display new time>

if Hour < 12 then Timer_Obs.Clock.Meridian := AM; else Timer_Obs.Clock.Meridian := PM; end if;

Notify (Timer_Obs.Clock.all);

end Update;

end Digital_Clocks;

Matthew Heaney 92

• As an observer, the Clock_Timer (really, the Timer_Obs_Type) must provide an implementation of Update.

• Update displays the new time (plays its observer role), then updates its own state and Notify’s its own observers (plays its subject role).

• This organization has the effect of propagating a signal all the way back from the ultimate subject to the ultimate observer.

Matthew Heaney 93

Clock_Watcher

• A very simple observer that observes a Digital_Clock.

• Per the idiom, it binds to its subject via an access discriminant.

• Here we manually Attach and Detach to the subject, instead of using Controlled-ness to do it automatically.

Matthew Heaney 94

package Clock_Watchers is

type Clock_Watcher (Clock : access Digital_Clock'Class) is limited private;

procedure Start_Watching_Clock (Watcher : access Clock_Watcher);

procedure Stop_Watching_Clock (Watcher : access Clock_Watcher);

private

type Clock_Watcher (Clock : access Digital_Clock'Class) is new Observer with null record;

procedure Update (Watcher : access Clock_Watcher);

end Clock_Watchers;

Matthew Heaney 95

package body Clock_Watchers is

procedure Start_Watching_Clock (Watcher : access Clock_Watcher) is begin Attach (Watcher, To => Watcher.Clock.all); end;

procedure Stop_Watching_Clock (Watcher : access Clock_Watcher) is begin Detach (Watcher, From => Watcher.Clock.all); end; ...

Matthew Heaney 96

... procedure Update (Watcher : access Clock_Watcher) is begin case Get_Meridian (Watcher.Clock.all) is when AM => Put_Line ("It's still morning."); when PM => Put_Line ("It's afternoon."); end case; end Update;

end Clock_Watchers;

Matthew Heaney 97

declare

Timer : aliased Clock_Timer;

Clock : aliased Digital_Clock (Timer'Access);

Watcher : aliased Clock_Watcher (Clock'Access);

begin

Start_Watching_Clock (Watcher);

Tick (Timer);

end;

Matthew Heaney 98

Observable-Observer Note

• There is another way to allow an observer to be both an observer and a subject.

• Simply change the declaration of Observer type in package Subjects_And_Observers so that it derives from Subject.

• Implementing the observing subject with an observer component isn’t necessary, because the type is already an observer.

Matthew Heaney 99

package Subjects_And_Observers is

type Subject is tagged limited private;

...

type Observer is abstract new Subject with private;

...

end Subjects_And_Observers;

Matthew Heaney 100

package Digital_Clocks is

type Digital_Clock (Timer : access C_Timer'Class) is new Subject with private; ...private

type Control_Type (Clock : access Digital_Clock) is new Limited_Controlled with null record; ... type Digital_Clock (Timer : access C_Timer'Class) is new Observer with record Control : Control_Type (D_Clock'Access); Meridian : Meridian_Type; end record;

procedure Update (Clock : access Digital_Clock);

end Digital_Clocks;

Matthew Heaney 101

Observing Multiple Subjects

• We introduce yet another variation of the observer pattern, this time allowing an observer to observe multiple subjects.

• Now the digital clock simultaneously observes both a timer and a battery. The battery subject notifies its observer when it is drained or charged.

Matthew Heaney 102

package Batteries is

type Battery_Type is new Subject with private;

procedure Charge (...);

procedure Drain (...);

function Is_Low (...) return Boolean;

private

type Battery_Type is new Subject with record State : Positive := 1; end record;

Matthew Heaney 103

Battery Subject (spec)

• The battery is observable, asserting this by publicly deriving from Subject.

• Modifier operations Charge and Drain adjust the available energy, and then Notify any observers.

• A selector operation, Is_Low, queries whether there is any energy remaining.

Matthew Heaney 104

package body Batteries is

procedure Charge (Battery : in out Battery_Type) is begin Battery.State := 1; Notify (Battery); end;

procedure Drain (Battery : in out Battery_Type) is begin Battery.State := Battery.State + 1; Notify (Battery); end;

function Is_Low (Battery : in Battery_Type) return Boolean is begin return Battery.State > 3; end;

Matthew Heaney 105

package Digital_Clocks is

type Digital_Clock (Timer : access Clock_Timer'Class; Battery : access Battery_Type'Class) is limited private;

private ...end Digital_Clocks;

Matthew Heaney 106

Digital_Clock (public)

• The public part of the observer type Digital_Clock has been modified to accept two access discriminants, one for each subject it observes.

Matthew Heaney 107

private

type Timer_Obs_Type (Clock : access Digital_Clock) is new Observer with null record;

procedure Update (Observer : access Timer_Obs_Type);

type Battery_Obs_Type (Clock : access Digital_Clock) is new Observer with null record;

procedure Update (Observer : access Battery_Obs_Type);

...

Matthew Heaney 108

... type Digital_Clock (Timer : access Clock_Timer'Class; Battery : access Battery_Type'Class) is new Limited_Controlled with record

Timer_Obs : aliased Timer_Obs_Type (D_Clock'Access);

Battery_Obs : aliased Battery_Obs_Type (D_Clock'Access);

end record;

procedure Initialize (Clock : in out Digital_Clock);

procedure Finalize (Clock : in out Digital_Clock);

end Digital_Clocks;

Matthew Heaney 109

Digital_Clock (private)• There has to be some type that derives from

Observer and overrides Update to process Clock_Timer notifications.

• There has to be some type that derives from Observer and overrides Update to process Battery_Type notifications.

• The same type can’t do both, because we don’t have multiple inheritance in Ada95. No problem, we just use the “multiple views” idiom.

Matthew Heaney 110

• An internal type, Timer_Obs_Type, observes just the Clock_Timer.

• Another internal type, Battery_Obs_Type, observes just the Battery_Type.

• Each type is bound to its enclosing record, the Digital_Clock, via an access discriminant.

• These internal types will be used to declare the observer components of the Digital_Clock type, which itself already derives from Limited_Controlled.

Matthew Heaney 111

package body Digital_Clocks is

procedure Update (Observer : access Timer_Obs_Type) is …;

procedure Update (Observer : access Battery_Obs_Type) is

Clock : Digital_Clock renames Observer.Clock.all;

Battery : Battery_Type'Class renames Clock.Battery.all; begin if Is_Low (Battery) then ... end Update;

Matthew Heaney 112

procedure Initialize (Clock : in out Digital_Clock) is

begin Attach (Obs => Clock.Timer_Obs'Access, To => Clock.Timer.all);

Attach (Obs => Clock.Battery_Obs'Access, To => Clock.Battery.all);end Initialize;

Matthew Heaney 113

Observing Multiple Attributes

• One issue is that when a subject notifies an observer that a state change has occurred, the observer has no way of knowing which specific attribute has changed.

• This may require the observer to redo all her processing (say, redraw a window), which may be inefficient.

Matthew Heaney 114

• One solution is to make observation more fine-grained; that is, to be able to observe individual attributes of a object, instead of just one monolithic object.

• When an object being observed changes the value of an attribute, he can notify the observers of that one attribute.

• It’s analogous to observing multiple subjects, but here, all the subjects are part of a single object.

Matthew Heaney 115

package Clock_Timers is

type Clock_Timer is limited private; ... subtype Hour_Number is Natural range 0 .. 23;

function Get_Hour (Timer : access Clock_Timer) return Hour_Number;

function Get_Hour_Subject (Timer : access Clock_Timer) return Subject_Access;

Matthew Heaney 116

...private type Clock_Timer is limited record Hour : Integer := -1; Hour_Subject : aliased Subject; Minute : Integer := -1; Minute_Subject : aliased Subject; Second : Integer := -1; Second_Subject : aliased Subject; end record;

end Clock_Timers;

Matthew Heaney 117

package body Clock_Timers is

procedure Tick (Timer : in out Clock_Timer) is begin

<update time>

if Timer.Hour /= Hour then

Timer.Hour := Hour;

Notify (Timer.Hour_Subject);

end if; ... end Tick;

Matthew Heaney 118

function Get_Hour_Subject (Timer : access Clock_Timer) return Subject_Access is begin return Timer.Hour_Subject'Access; end;

Matthew Heaney 119

package Digital_Clocks is

type Digital_Clock (Timer : access Clock_Timer) is limited private;

private

type H_Obs_Type (Timer : access Clock_Timer) is new Observer with null record;

procedure Update (H_Obs : access H_Obs_Type); ... type Digital_Clock (Timer : access Clock_Timer) is new Limited_Controlled with record H_Obs : aliased H_Obs_Type (Timer); ... end record;

...

Matthew Heaney 120

package body Digital_Clocks is

procedure Update (H_Obs : access H_Obs_Type) is

Image : constant String := Integer'Image (Get_Hour (H_Obs.Timer) + 100); begin <display hour> end;

procedure Initialize (Clock : in out Digital_Clock) is begin

Attach (Obs => Clock.H_Obs'Access, To => Get_Hour_Subject (Clock.Timer));

Matthew Heaney 121

Factory Method

Matthew Heaney 122

Motivation

• Suppose we have a family of stack types, and we want to provide a class-wide operation to print a stack.

• We plan on using an active iterator to implement the operation. Each type in the class has its own iterator.

• Here’s the problem: if the stack parameter has a class-wide type, then how do we get an iterator that works for this stack object?

Matthew Heaney 123

procedure Stacks.Put (Stack : in Root_Stack_Type’Class) is

Iterator : <what’s its type?> := <how do we get one for Stack’s type?>begin while not Is_Done (Iterator) loop ...

Matthew Heaney 124

What's A Factory Method?

• If you need an iterator for this type of stack, then just ask the stack for one.

• A “factory method” is a constructor that dispatches on one type, and returns a value of some other type.

• In Ada95, the return type has to be class–wide, since an operation can only be primitive for one type.

Matthew Heaney 125

generic type Item_Type is private;package Stacks is

type Root_Stack_Type is abstract tagged limited null record;

type Root_Iterator_Type is abstract tagged null record;

-- Here’s the factory method: -- function Start_At_Top (Stack : Root_Stack_Type) return Root_Iterator_Type'Class is abstract;

Matthew Heaney 126

procedure Stacks.Put (Stack : in Root_Stack_Type’Class) is

Iterator : Root_Iterator_Type’Class := Start_At_Top (Stack);begin while not Is_Done (Iterator) loop

… Get_Item (Iterator) …

Advance (Iterator);

end loop;

New_Line;end Stacks.Put;

Matthew Heaney 127

generic

Max_Depth : in Positive;

package Stacks.Bounded_G is

type Stack_Type is new Root_Stack_Type with private;

type Iterator_Type is new Root_Iterator_Type with private;

function Start_At_Top (Stack : Stack_Type) return Root_Iterator_Type'Class;

Matthew Heaney 128

Copying A Stack• Requires care, because it’s easy to populate the

target stack in reverse order.• You can either (1) traverse the items in the source

stack in bottom-to-top order, and populate the target stack in the normal way (using Push); or,

• You can (2) traverse the items in the source stack in top-to-bottom order, and populate the target stack in reverse order, using a special operation (like Copy).

Matthew Heaney 129

procedure Copy_That_Does_Not_Work (From : in Root_Stack_Type’Class; To : in out Root_Stack_Type’Class) is Iter : Root_Iterator_Type’Class := Start_At_Top (From);begin if <From and To are the same stack> then return; end if;

Clear (To); while not Is_Done (Iter) loop Push (Get_Item (Iter), On => To); Advance (Iter); end loop;end Copy_That_Does_Not_Work;

Matthew Heaney 130

procedure Stacks.Copy -- technique (1) (From : in Root_Stack_Type’Class; To : in out Root_Stack_Type’Class) is

Iterator : Root_Iterator_Type’Class := Start_At_Bottom (From);begin if From’Address = To’Address then -- per RM95 3.10 (9) and 13.3 (16) return; end if;

Clear (To); while not Is_Done (Iterator) loop Push (Get_Item (Iterator), On => To); Backup (Iterator); end loop;end Stacks.Copy;

Matthew Heaney 131

package body Stacks.Bounded_G is

procedure Copy -- technique (2) (From : in Root_Stack_Type'Class; To : in out Stack_Type) is

Depth : constant Natural := Get_Depth (From);

Iterator : Root_Iterator_Type'Class := Start_At_Top (From);

use type System.Address; begin ...

Matthew Heaney 132

... if From'Address = To'Address then return; end if;

if Depth > Max_Depth then raise Storage_Error; end if;

To.Top := Depth;

for I in reverse 1 .. Depth loop To.Items (I) := Get_Item (Iterator); Advance (Iterator); end loop; end Copy;

Matthew Heaney 133

Summary of Stack Copying

• Technique (1) requires that you be able to traverse stacks in reverse order.

• Technique (1) can be implemented as a class-wide operation, or as a primitive operation with a default implementation.

• Technique (2) must be implemented as a primitive operation, for each type, because it needs to know the type’s representation.

Matthew Heaney 134

Singleton

Matthew Heaney 135

Using a State Machine Package

• The package itself is the object – an instance of an anonymous type.

• State data is declared in the package body and manipulated via public operations.

• Popular in Ada because static-ness is the default for objects and operations.

Matthew Heaney 136

with Ownship_Types; use Ownship_Types;

package Ownship is

procedure Update;

function Get_Speed_In_Knots return Speed_In_Knots_Type;

function Get_Heading_In_Deg return Heading_In_Deg_Type;

procedure Set_Heading (Heading : in Heading_In_Deg_Type);

... end Ownship;

Matthew Heaney 137

with Ownship;

package body P is

… procedure Op is

Ownship_Speed : constant Speed_In_Knots_Type := Ownship.Get_Speed_In_Knots; begin

<do something with speed>

end Op;

Matthew Heaney 138

Using a Named Type

• Instance creation can be controlled by the abstraction by declaring the type as limited and indefinite.

• The (single) instance of the type is declared in the package body.

• A public operation returns an access object designating the singleton instance.

• All operations of the type take access parameters (so no explicit deref is req’d).

Matthew Heaney 139

package Ownships is

type Ownship_Type (<>) is limited private;

function Get_Speed_In_Knots (Ownship : access Ownship_Type) return Speed_In_Knots_Type; ... type Ownship_Access is access all Ownship_Type;

function Ownship return Ownship_Access;

private

type Ownship_Type is …;

end Ownships;

Matthew Heaney 140

with Ownships; use Ownships;

package body P is

… procedure Op is

Ownship_Speed : constant Speed_In_Knots_Type := Get_Speed_In_Knots (Ownship); begin

<do something with speed>

end Op;

Matthew Heaney 141

package body Ownships is

function Get_Speed_In_Knots (Ownship : access Ownship_Type) return Speed_In_Knots_Type is begin return Ownship.Speed; end; ... Singleton : aliased Ownship_Type;

function Ownship return Ownship_Access is begin return Singleton'Access; end;

end Ownships;

Matthew Heaney 142

Well-Known Objects

• Well-known objects are global abstractions that have a defined cardinality.

• They tend to be passive holders of system–wide state.

• A singleton is a well-known object whose cardinality happens to be 1.

• Use a discrete identifier to refer to a specific instance.

Matthew Heaney 143

with Rodmeter_Types; use Rodmeter_Types;package Rodmeters is

type Rodmeter_Id is range 1 .. 2;

procedure Update (Rodmeter : in Rodmeter_Id);

function Get_Speed_In_Knots (Rodmeter : Rodmeter_Id) return Speed_In_Knots_Type;

procedure Set_Bias (Rodmeter : in Rodmeter_Id; Bias : in Bias_In_Knots_Type);

function Get_Bias (Rodmeter : Rodmeter_Id) return Bias_In_Knots_Type;

end Rodmeters;

Matthew Heaney 144

with Ownships, Ownship_Types;

package body Rodmeters is

type Speed_Array_Type is array (Rodmeter_Id) of Speed_In_Knots_Type;

Speed_Array : Speed_Array_Type;

type Bias_Array_Type is array (Rodmeter_Id) of Bias_In_Knots_Type;

Bias_Array : Bias_Array_Type;

...

Matthew Heaney 145

function Get_Speed_In_Knots (Rodmeter : Rodmeter_Id) return Speed_In_Knots_Type is begin return Speed_Array (Rodmeter); end;

procedure Set_Bias (Rodmeter : in Rodmeter_Id; Bias : in Bias_In_Knots_Type) is begin Bias_Array (Rodmeter) := Bias; end;

function Get_Bias (Rodmeter : Rodmeter_Id) return Bias_In_Knots_Type is begin return Bias_Array (Rodmeter); end;

Matthew Heaney 146

procedure Update (Rodmeter : in Rodmeter_Id) is

OS_Speed : constant OS_Types.Speed_In_Knots_Type := Get_Speed_In_Knots (Ownship);

Speed : Speed_In_Knots_Type'Base := Speed_In_Knots_Type'Base (OS_Speed) + Speed_In_Knots_Type'Base (Bias_Array (Rodmeter));

begin

if Speed < 0.0 then Speed := 0.0; elsif Speed > Speed_In_Knots_Type'Last then Speed := Speed_In_Knots_Type'Last; end if;

Speed_Array (Rodmeter) := Speed;

end Update;

Matthew Heaney 147

package TCP.States is

type Root_State_Type (<>) is abstract tagged limited private;

type State_Access is access all Root_State_Type'Class;

type Root_Connection_Type is abstract tagged limited null record;

procedure Set_State (Connection : in out Root_Connection_Type; State : in State_Access) is abstract;

procedure Transmit (State : access Root_State_Type; Connection : in out Root_Connection_Type'Class; Item : in Stream_Element_Array); ...

Matthew Heaney 148

package TCP.States.Listen is

type Listen_State_Type is new Root_State_Type with private;

procedure Send (State : access Listen_State_Type; Connection : in out Root_Connection_Type'Class);

function State return State_Access;

private

type Listen_State_Type is new Root_State_Type with null record;

end TCP.States.Listen;

Matthew Heaney 149

with TCP.States.Established;

package body TCP.States.Listen is

Singleton : aliased Listen_State_Type;

procedure Send (State : access Listen_State_Type; Connection : in out Root_Connection_Type'Class) is begin ... Set_State (Connection, Established.State); end Send;

function State return State_Access is begin return Singleton'Access; end;

end TCP.States.Listen;

Matthew Heaney 150

package TCP.Connections is

type Connection_Type is limited private; ...private

function Get_Default return State_Access;

type Connection_Type is new Root_Connection_Type with record State : State_Access := Get_Default; File : Streams.File_Type; end record;

procedure Set_State (Connection : in out Connection_Type; State : in State_Access);

end TCP.Connections;

Matthew Heaney 151

Strategy

Matthew Heaney 152

What’s A Strategy?

• The simple answer: a fancy name for a generic formal subprogram.

• It’s a way to parameterize a component.

• You effect different behavior by plugging in a different algorithm (the “strategy”).

Matthew Heaney 153

generic

type Item_Type is limited private;

package Storage_Nodes is

type Storage_Node; type Storage_Node_Access is access all Storage_Node;

type Storage_Node is limited record Item : aliased Item_Type; Next : Storage_Node_Access; end record;

procedure Do_Nothing (Node : in out Storage_Node);

end Storage_Nodes;

Matthew Heaney 154

with Storage_Nodes;

generic

with package Nodes is new Storage_Nodes (<>);

use Nodes;

with procedure Finalize (Node : in out Storage_Node) is Do_Nothing;

package Storage is

function New_Node return Storage_Node_Access;

procedure Free (Node : in out Storage_Node_Access);

end Storage;

Matthew Heaney 155

package body Storage is

Free_List : Storage_Node_Access;

function New_Node return Storage_Node_Access is ...

procedure Free (Node : in out Storage_Node_Access) is begin if Node = null then return; end if;

Finalize (Node.all);

Node.Next := Free_List; Free_List := Node; Node := null; end Free;

end Storage;

Matthew Heaney 156

with Storage_Nodes;

generic type Item_Type is private;package Unbounded_Stacks is

type Stack_Type is limited private; ...private

package Nodes is new Storage_Nodes (Item_Type); use Nodes;

type Stack_Type is limited record Top : Storage_Node_Access; end record;

end Unbounded_Stacks;

Matthew Heaney 157

with Storage;

package body Unbounded_Stacks is

package Stack_Storage is new Storage (Nodes); use Stack_Storage;

procedure Pop (Stack : in out Stack_Type) is

Node : Storage_Node_Access := Stack.Top; begin Stack.Top := Stack.Top.Next; Free (Node); end Pop;

…end Unbounded_Stacks;

Matthew Heaney 158

with Storage_Nodes;

generic type Item_Type is private;package Lists is

type List_Type is private; … procedure Clear (List : in out List_Type);

private

package Nodes is new Storage_Nodes (Item_Type); use Nodes;

type List_Type is record Head : Storage_Node_Access; end record;

end Lists;

Matthew Heaney 159

with Storage;

package body Lists is

procedure Finalize (Node : in out Storage_Node);

package List_Storage is new Storage (Nodes, Finalize); use List_Storage;

procedure Finalize (Node : in out Storage_Node) is begin Free (Node.Next); end; ... procedure Clear (List : in out List_Type) is begin Free (List.Head); end;

end Lists;

Matthew Heaney 160

Generic Dispatching

Matthew Heaney 161

Motivation

• Suppose we want to import, as generic formal parameters, a tagged type and one of its primitive operations, and we want dynamically dispatch the operation inside the generic.

• The problem is that you can’t dispatch on a formal subprogram, because a formal subprogram isn’t primitive for a formal type.

Matthew Heaney 162

package P is

type T is tagged limited private;

procedure Op (O : in out T); …end P;

package P.C is

type NT is new T with private;

procedure Op (O : in out NT); …end P.C;

Matthew Heaney 163

generic

type T (<>) is abstract tagged limited private;

with procedure Op (O : in out T) is <>;

package GQ is

procedure Do_Something (O : in out T'Class);

end GQ;

Matthew Heaney 164

• Here’s what we want to do:

with P, GQ;

package Q is new GQ (T => P.T, Op => P.Op);

Matthew Heaney 165

package body GQ is

procedure Do_Something (O : in out T'Class) is begin Op (O); --here’s the offending line end;

end GQ;

gq.adb:6:10: class-wide argument not allowed heregq.adb:6:10: "Op" is not a primitive operation of "T"

Matthew Heaney 166

• The problem is that the compiler has no way of knowing (at the time of compilation of the generic) that formal procedure Op is really primitive for type T. So it assumes the worst, and doesn’t allow you to dispatch on a formal operation.

• The actual operation we import must be statically bound to T. What we can do is import the class-wide type, T’Class, and import a class-wide operation (that takes an object of type T’Class) that calls the (primitive) dispatching operation.

Matthew Heaney 167

Changes to Client

• Implement a new, class-wide operation (as a child, if you don’t have it already):

procedure P.Call_Op (O : in out T'Class) isbegin Op (O); -- dispatchesend;

Matthew Heaney 168

Changes to Server

• Declare the formal type as non-tagged and indefinite. This allows a class-wide type to be used as the generic actual.

• In the generic operations, declare the formal parameters to be of type T instead of T’Class. (This is required anyway, because the formal type isn’t tagged anymore.)

Matthew Heaney 169

generic

type T (<>) is limited private;

with procedure Op (O : in out T) is <>;

package GQ is

procedure Do_Something (O : in out T);

end GQ;

Matthew Heaney 170

package body GQ is

procedure Do_Something (O : in out T) is begin ... Op (O); -- legal (static call) ... end;

end GQ;

Matthew Heaney 171

Changes to Instantiation

• Now let’s instantiate the new version of the generic using T’Class as the actual type, and our special class-wide operation as the actual operation:

with GQ, P.Call_Op;

package Q is new GQ (P.T'Class, P.Call_Op);

Matthew Heaney 172

with P.C, Q;

procedure Test_Q is

OT : P.T; -- T is root of class

ONT : P.C.NT; -- NT derives from T

begin

Q.Do_Something (OT); -- call T’s Op

Q.Do_Something (ONT); -- call NT’s Op

end Test_Q;

Matthew Heaney 173

The Rosen Trick

Matthew Heaney 174

Ada I/O Model

• A “communication path,” such as disk I/O, socket I/O, etc, is modeled as a “file.”

• You “open the file” to establish communication with a device.

• You “close the file” to sever the connection to the device.

Matthew Heaney 175

• The “communication path” to a device is represented as a handle, which designates connection state. The state may change, but the handle itself does not.

Matthew Heaney 176

package Files is

type File_Type is limited private;

procedure Open(File : in out File_Type; Name : in String);

procedure Close(File : in out File_Type);

procedure Read(File : in File_Type; Item : out Item_Type);

procedure Write(File : in File_Type; Item : in Item_Type);

Matthew Heaney 177

Issue

• Read and Write are state-changing operations, yet the File object (the “handle”) is passed as an in-mode parameter.

• How to we implement File_Type in order to implement this model?

Matthew Heaney 178

Use the Heap

private

type Connection_State;

type File_Type is access all Connection_State;

end Files;

Matthew Heaney 179

Use the Heap (cont’d)procedure Open (File : in out File_Type; Name : in String) isbegin File := new Connection_State;...end Open;

procedure Write (File : in File_Type ...) isbegin File.all := ...end;

Matthew Heaney 180

Use the Heap: Consequences

• Well, requires heap use. In general, if given a choice, we’d rather use the stack.

• The declaration of a named access type means you can’t declare the package using pragma Pure.

• In order to prevent memory leaks, you have to implement File_Type as controlled. This adds a certain amount of heaviness.

Matthew Heaney 181

Use Static Allocation

private

type File_Type is limited record Index : Natural := 0; end record;

end Files;

Matthew Heaney 182

Use Static Allocation (cont’d)package body Files is

type Descriptor_Type is ... Descriptors : array (1 .. 20) of Descriptor_Type;

procedure Open (File : in out File_Type; ...) is begin File.Index := Get_Descriptor_Index;

Matthew Heaney 183

Static Allocation: Consequences

• Limits number of file objects (although there’s probably a system-defined limit anyway).

• Having package state means you won’t be able to declare the package using pragma Pure.

Matthew Heaney 184

Use Chapter 13 Tricks

private

type File_Type is limited record <connection state> end record;

end Files;

Matthew Heaney 185

Chapter 13 (cont’d)

package body Files is

package Address_To_Access_Conversions is new System.Addr_To_Acc_Conversions...

procedure Write (File : in File_Type; ...) is FA : const Object_Pointer := To_Pointer(File’Address);

F : File_Type renames FA.all; begin

Matthew Heaney 186

Chapter 13: Consequences

• Using ‘Address turns off type-checking.

Matthew Heaney 187

The Rosen Trick

• A clean way to modify a limited (by–reference) in-mode subprogram parameter, that doesn’t require any Chap 13 tricks.

• Allocate memory for the handle directly adjacent to the connection state, on the stack. No package state is necessary.

Matthew Heaney 188

generic type Result_Subtype is (<>);

package Ada.Numerics.Discrete_Random is

type Generator is limited private;

function Random (Gen : Generator) return Result_Subtype;...private

type Handle_Type (Gen : access Generator) is limited null record;

type Generator is limited record Handle : Handle_Type (Generator’Access); Gen_State : State; end record;

Matthew Heaney 189

function Random (Gen : Generator) return Result_Subtype is

Gen_State : State renames Gen.Handle.Gen.Gen_State;

begin

<modify Gen_State as necessary>

return <random number>;

end Random;

Matthew Heaney 190

type File_Type is limited private; ... procedure Read (File : in File_Type; Key : in Key_Type; Item : out Item_Type);

procedure Write (File : in File_Type; Item : in Item_Type);

procedure Remove (File : in File_Type; Key : in Key_Type);

Matthew Heaney 191

private

...

type Handle_Type (File : access File_Type) is limited null record;

type File_Type is limited record Handle : Handle_Type (File_Type'Access); File : Stream_IO.File_Type; File_Index : Stream_IO.Positive_Count; Root_Page : Page_Type; end record;

Matthew Heaney 192

procedure Read (File : in File_Type; Key : in Key_Type; Item : out Item_Type) is

Index : Natural; Found : Boolean;

File_Index : Stream_IO.Count; Page : Page_Type;

begin

Set_Mode (File.Handle.File.File, In_File);

...

Matthew Heaney 193

procedure Write (File : in out File_Type; Item : in Item_Type) is

...

begin

Set_Mode (File.Handle.File.File, In_File); ...

Reset (File.Handle.File.File); Count'Write (Stream (File.File), File.File_Index);

Flush (File.Handle.File.File);

end Write;

Matthew Heaney 194

Collections Of Limited Items

Matthew Heaney 195

• Generic data structures typically declare the generic formal item type as non-limited:

generic

type Item_Type is private;

Max_Depth : in Positive;

package Stacks is …;

Matthew Heaney 196

• This gives you assignment, allowing you to implement the insertion operation by copying the formal parameter:

procedure Push (Item : in Item_Type; On : in out Stack_Type) isbegin On.Top := On.Top + 1; On.Items (On.Top) := Item; -- copyend Push;

Matthew Heaney 197

• Other modifier operations are implemented the same way, by copying the formal parameter:

procedure Set_Top (Stack : in out Stack_Type; Item : in Item_Type) isbegin Stack.Items (Stack.Top) := Item; -- copyend;

Matthew Heaney 198

• But suppose you need a collection of items whose type is limited?

with Stacks;with Ada.Text_IO; use Ada.Text_IO;

package File_Stacks is new Stacks (Item_Type => File_Type, -- illegal Max_Depth => 10);

Matthew Heaney 199

• We can solve the problem by rewriting modifier operations as functions that return a reference to the object.

• This works because assignment isn’t necessary for the implementation of these special modifiers.

• It’s the client who does the modify, by manipulating the actual item (instead of the supplier internally replacing it with a copy).

Matthew Heaney 200

Stack : aliased Stack_Type;...declare File : File_Type renames Push (Stack’Access).all; -- -- There’s now a new File object on -- the top of the Stack.begin Open (File, Out_File, “myfile.dat”); ... Reset (File); ... Close (File);end;

Pop (Stack);

Matthew Heaney 201

• Now let’s see what Set_Top will look like:

Stack : aliased Stack_Type;…Reset (File => Set_Top (Stack’Access).all);…Close (File => Set_Top (Stack’Access).all);

Matthew Heaney 202

• Strictly speaking, Push doesn’t have to be implemented by returning an access object, if you have Set_Top too:

Push (Stack); -- note: no Item parameter…Open (File => Set_Top (Stack’Access).all, Mode => Out_File, Name => “myfile.dat”);

Matthew Heaney 203

How do we do it? (public part)

• Declare the generic formal item type as limited private.

• Declare a general access type that designates the item type.

• Declare the modifier operations as functions that return the access type, and take the stack as an access parameter.

Matthew Heaney 204

generic type Item_Type is limited private; Max_Depth : in Positive;package Stacks is

type Stack_Type is limited private;

type Item_Access is access all Item_Type;

function Push (Stack : access Stack_Type) return Item_Access;

function Set_Top (Stack : access Stack_Type) return Item_Access; ...

Matthew Heaney 205

How do we do it? (private part)

• Declare the item array with aliased components.

Matthew Heaney 206

private

type Item_Array is array (1 .. Max_Depth) of aliased Item_Type;

subtype Top_Range is Natural range 0 .. Max_Depth;

type Stack_Type is limited record Items : Item_Array; Top : Top_Range := 0; end record;

end Stacks;

Matthew Heaney 207

How do we do it? (body)

• Implement the modifier operations by returning an access object designating the item on the top of the stack.

Matthew Heaney 208

package body Stacks is

function Push (Stack : access Stack_Type) return Item_Access is begin Stack.Top := Stack.Top + 1; return Stack.Items (Stack.Top)’Access; end;

function Set_Top (Stack : access Stack_Type) return Item_Access is begin return Stack.Items (Stack.Top)’Access; end; ...

Matthew Heaney 209

How do we do it? (body)

• The alternate version of Push only needs to increment the Top index (you actually modify the item later, using Set_Top):

procedure Push (Stack : in out Stack_Type) isbegin Stack.Top := Stack.Top + 1;end;

Matthew Heaney 210

For non-limited items too

• This technique isn’t specific to collections of limited items. You could use it for non-limited items too, if you prefer to modify the actual item in place, instead of (internally) replacing the item with a copy.

Set_Top (Stack’Access).all := Value;

Modify (Item => Set_Top (Stack’Access).all);

Matthew Heaney 211

Applied to active iterators

• You can generalize this idea, allowing you to modify any item in the collection, by using an active iterator:

Set_Item (Iterator).all := Value;

Modify (Item => Set_Item (Iterator).all);

Matthew Heaney 212

Command

Matthew Heaney 213

What’s A Command Object?

• An object that manages the processing that occurs when a user issues a command.

• Store the command in a ring and use it to implement undo and redo.

• Store the command on disk to implement record and playback.

• Store the command in a queue and execute it later.

Matthew Heaney 214

package Commands is

type Root_Command_Type (<>) is abstract tagged limited private;

type Command_Access is access all Root_Command_Type'Class;

procedure Execute (Command : access Root_Command_Type) is abstract;

procedure Free (Command : in out Command_Access); …

Matthew Heaney 215

…private

type Root_Command_Type is abstract tagged limited null record;

procedure Do_Free (Command : access Root_Command_Type);

end Commands;

Matthew Heaney 216

package body Commands is

procedure Free (Command : in out Command_Access) is begin if Command /= null then Do_Free (Command); Command := null; end if; end Free;

procedure Do_Free (Command : access Root_Command_Type) is begin null; end;

end Commands;

Matthew Heaney 217

package Commands.Open_Commands is

type Command_Type is new Root_Command_Type with private;

function New_Command (App : access Application_Type'Class) return Command_Access;

procedure Execute (Command : access Command_Type); …

Matthew Heaney 218

...private

type Command_Type (App : access Application_Type'Class) is new Root_Command_Type with null record;

procedure Do_Free (Command : access Command_Type);

end Commands.Open_Commands;

Matthew Heaney 219

package body Commands.Open_Commands is

type Open_Command_Access is access all Command_Type;

procedure Deallocate is new Ada.Unchecked_Deallocation (Command_Type, Open_Command_Access);

function New_Command (App : access Application_Type'Class) return Command_Access is

Command : constant Open_Command_Access := new Command_Type (App); begin return Command_Access (Command); end;

Matthew Heaney 220

procedure Do_Free (Command : access Command_Type) is

CA : Open_Command_Access := Open_Command_Access (Command); begin Deallocate (CA); end;

procedure Execute (Command : access Command_Type) is

Doc : constant Document_Access := New_Doc (Name => Get_Filename_From_User); begin Add (Doc, To => Command.App); Documents.Open (Doc); end Execute;

end Commands.Open_Commands;

Matthew Heaney 221

App : aliased Application_Type; ... declare Command : Command_Access := Open_Commands.New_Command (App'Access); begin <install command as value of Open button> end; …

procedure Execute_Menu_Function_CB (W : in Widget) is begin Execute (W.Command); end;

Matthew Heaney 222

generic

type Receiver_Type (<>) is limited private;

with procedure Action (Receiver : in out Receiver_Type);

package Commands.Simple is

type Command_Type is new Root_Command_Type with private;

function New_Command (Receiver : access Receiver_Type) return Command_Access;

procedure Execute (Command : access Command_Type); ...end Commands.Simple;

Matthew Heaney 223

package body Commands.Simple is ... procedure Execute (Command : access Command_Type) is begin Action (Command.Receiver.all); end;

end Commands.Simple;

Matthew Heaney 224

package Applications is

type Application_Type is tagged limited private; ...end Applications;

procedure Applications.Count_Docs (App : in out Application_Type'Class);

Matthew Heaney 225

with Applications.Count_Docs; use Applications;with Commands.Simple;

package Commands.App_Commands is new Simple (Receiver_Type => Application_Type'Class, Action => Count_Docs);

(This is similar to the “generic dispatching” trick.)

Matthew Heaney 226

Composite

Matthew Heaney 227

What’s A Composite?

• Technique for assembling recursive data structures.

• Example: a macro command (a command comprising a set of commands).

• Example: UNIX directory tree (a directory is a file comprising other files).

Matthew Heaney 228

package Equipment is

type Equipment_Type (<>) is abstract tagged limited private;

type Equipment_Access is access all Equipment_Type'Class;

type Power_In_Watts_Type is delta 0.1 range 0.0 .. 100.0;

type Dollars_Type is delta 0.01 digits 6;

function Get_Power_In_Watts (Equipment : access Equipment_Type) return Power_In_Watts_Type is abstract;

function Get_Price_In_Dollars (Equipment : access Equipment_Type) return Dollars_Type is abstract;

Matthew Heaney 229

type Composite_Type is abstract new Equipment_Type with private;

type Composite_Access is access all Composite_Type'Class;

function Get_Power_In_Watts (Composite : access Composite_Type) return Power_In_Watts_Type;

function Get_Price_In_Dollars (Composite : access Composite_Type) return Dollars_Type;

procedure Add (Equipment : access Equipment_Type'Class; To : access Composite_Type);

Matthew Heaney 230

procedure Free (Equipment : in out Equipment_Access);

private

type Equipment_Type is abstract tagged limited record Next : Equipment_Access; end record;

procedure Do_Free (Equipment : access Equipment_Type);

Matthew Heaney 231

type Composite_Type is abstract new Equipment_Type with record Head : Equipment_Access; end record;

function Do_Get_Price (Composite : Composite_Type) return Dollars_Type;

function Do_Get_Power (Composite : Composite_Type) return Power_In_Watts_Type;

procedure Free_Items (Composite : access Composite_Type'Class);

end Equipment;

Matthew Heaney 232

package body Equipment is

procedure Do_Free (Equipment : access Equipment_Type) is begin raise Program_Error; end;

procedure Free (Equipment : in out Equipment_Access) is begin if Equipment /= null then Do_Free (Equipment); Equipment := null; end if; end Free;

Matthew Heaney 233

function Do_Get_Price (Composite : Composite_Type) return Dollars_Type is begin return 0.0; end;

function Do_Get_Power (Composite : Composite_Type) return Power_In_Watts_Type is begin return 0.0; end;

Matthew Heaney 234

function Get_Power_In_Watts (Composite : access Composite_Type) return Power_In_Watts_Type is

Power : Power_In_Watts_Type := Do_Get_Power (Composite_Type’Class (Composite.all));

Item : Equipment_Access := Composite.Head;

begin

while Item /= null loop Power := Power + Get_Power_In_Watts (Item); Item := Item.Next; end loop;

return Power;

end Get_Power_In_Watts;

Matthew Heaney 235

function Get_Price_In_Dollars (Composite : access Composite_Type) return Dollars_Type is

Price : Dollars_Type := Do_Get_Price (Composite_Type’Class (Composite.all));

Item : Equipment_Access := Composite.Head;

begin

while Item /= null loop Price := Price + Get_Price_In_Dollars (Item); Item := Item.Next; end loop;

return Price;

end Get_Price_In_Dollars;

Matthew Heaney 236

procedure Add (Equipment : access Equipment_Type'Class; To : access Composite_Type) is

Item : constant Equipment_Access := Equipment_Access (Equipment);

begin

pragma Assert (Equipment.Next = null, "equipment already on another list");

Item.Next := To.Head; To.Head := Item;

end Add;

Matthew Heaney 237

procedure Free_Items (Composite : access Composite_Type'Class) is

Item : Equipment_Access; Head : Equipment_Access renames Composite.Head;

begin

while Head /= null loop Item := Head; Head := Head.Next; Do_Free (Item); end loop;

end Free_Items;

end Equipment;

Matthew Heaney 238

package Equipment.Hard_Disks is

type Hard_Disk_Type is new Equipment_Type with private;

function New_Hard_Disk return Equipment_Access;

function Get_Price_In_Dollars (Hard_Disk : access Hard_Disk_Type) return Dollars_Type;

function Get_Power_In_Watts (Hard_Disk : access Hard_Disk_Type) return Power_In_Watts_Type;

Matthew Heaney 239

...private

type Hard_Disk_Type is new Equipment_Type with null record;

procedure Do_Free (Hard_Disk : access Hard_Disk_Type);

end Equipment.Hard_Disks;

Matthew Heaney 240

package body Equipment.Hard_Disks is

type Hard_Disk_Access is access all Hard_Disk_Type;

procedure Free is new Ada.Unchecked_Deallocation (Hard_Disk_Type, Hard_Disk_Access);

...

Matthew Heaney 241

function New_Hard_Disk return Equipment_Access is

Hard_Disk : constant Hard_Disk_Access := new Hard_Disk_Type; begin return Equipment_Access (Hard_Disk); end;

procedure Do_Free (Hard_Disk : access Hard_Disk_Type) is

Hard_Disk_A : Hard_Disk_Access := Hard_Disk_Access (Hard_Disk); begin Free (Hard_Disk_A); end;

Matthew Heaney 242

function Get_Price_In_Dollars (Hard_Disk : access Hard_Disk_Type) return Dollars_Type is begin return 350.0; end;

function Get_Power_In_Watts (Hard_Disk : access Hard_Disk_Type) return Power_In_Watts_Type is begin return 20.0; end;

end Equipment.Hard_Disks;

Matthew Heaney 243

package Equipment.Cabinets is

type Cabinet_Type is new Composite_Type with private;

function New_Cabinet return Composite_Access;

private

type Cabinet_Type is new Composite_Type with null record;

procedure Do_Free (Cabinet : access Cabinet_Type);

function Do_Get_Price (Cabinet : Cabinet_Type) return Dollars_Type;

end Equipment.Cabinets;

Matthew Heaney 244

package body Equipment.Cabinets is

type Cabinet_Access is access all Cabinet_Type;

procedure Free is new Ada.Unchecked_Deallocation (Cabinet_Type, Cabinet_Access);

function New_Cabinet return Composite_Access is

Cabinet : constant Cabinet_Access := new Cabinet_Type; begin return Composite_Access (Cabinet); end;

Matthew Heaney 245

procedure Do_Free (Cabinet : access Cabinet_Type) is

Cabinet_A : Cabinet_Access := Cabinet_Access (Cabinet); begin Free_Items (Cabinet); Free (Cabinet_A); end Do_Free;

function Do_Get_Price (Cabinet : Cabinet_Type) return Dollars_Type is begin return Dollars_Type'(125.0); end;

end Equipment.Cabinets;

Matthew Heaney 246

declare Cabinet : Composite_Access := New_Cabinet; Chassis : Composite_Access := New_Chassis;

Price : Price_In_Dollars_Type; Power : Power_In_Watts_Type;begin Add (New_Floppy_Disk, To => Cabinet); Add (New_CD_ROM, To => Cabinet);

Add (New_Hard_Disk, To => Chassis);

Add (Chassis, To => Cabinet);

Price := Get_Price_In_Dollars (Cabinet); Power := Get_Power_In_Watts (Cabinet);end;

Matthew Heaney 247

package Commands.Macro_Commands is

type Command_Type is new Root_Command_Type with private;

type Macro_Command_Access is access all Command_Type;

function New_Command return Macro_Command_Access;

procedure Execute (Command : access Command_Type);

procedure Add (Command : access Root_Command_Type'Class; To : access Command_Type);

...

Matthew Heaney 248

private

type Command_Type is new Root_Command_Type with record Head : Command_Access; -- really, a queue end record;

procedure Do_Free (Command : access Command_Type);

end Commands.Macro_Commands;

Matthew Heaney 249

package body Commands.Macro_Commands is … procedure Execute (Command : access Command_Type) is

procedure Traverse_Then_Execute (C : in Command_Access) is begin if C /= null then Traverse_Then_Execute (C.Next); Execute (C); end if; end Traverse_Then_Execute;

begin

Traverse_Then_Execute (Command.Head);

end Execute;

Matthew Heaney 250

procedure Add (Command : access Root_Command_Type'Class; To : access Command_Type) is begin pragma Assert (Command.Next = null, "command already on another list");

Command.Next := To.Head; To.Head := Command_Access (Command); end;

end Commands.Macro_Commands;

Matthew Heaney 251

declare Command : constant Macro_Command_Access := New_Command;begin Add (New_Open (App’Access), To => Command); Add (New_Paste (Doc), To => Command); … Execute (Command); -- Execute all the commands contained by -- the macro command.end;

Matthew Heaney 252

Bounded Buffer

Matthew Heaney 253

What’s A Bounded Buffer?

• Classic way of asynchronously transferring data between producer(s) and consumer(s).

• Consumer gets an item from the buffer; it blocks if there’s nothing to get.

• Producer puts an item in the buffer; it blocks if the buffer is full.

Matthew Heaney 254

generic

type Item_Type is private;

package Buffers is

type Item_Array is array (Positive range <>) of Item_Type;

protected type Buffer_Type (Size : Positive) is

entry Put (Item : in Item_Type);

entry Get (Item : out Item_Type); ...

Matthew Heaney 255

...

private

Items : Item_Array (1 .. Size); Get_Index : Positive := 1; Put_Index : Positive := Size; Count : Natural := 0;

end Buffer_Type;

end Buffers;

Matthew Heaney 256

with Buffers;package Character_Buffers is new Buffers (Character);

Matthew Heaney 257

with Character_Buffers; use Character_Buffers;

package Consumers is

type Consumer_Type (Buffer : access Buffer_Type) is limited private;

private

task type Consumer_Type (Buffer : access Buffer_Type) is end;

end Consumers;

Matthew Heaney 258

declare Buffer : aliased Buffer_Type (Size => 5);

Consumer : Consumer_Type (Buffer'Access);begin for C in Character range ‘a’ .. ‘z’ loop Buffer.Put (C); end loop;end;

Matthew Heaney 259

package body Consumers is

task body Consumer_Type is

C : Character; begin

Main: loop Buffer.Get (C); <do something with character> end loop Main;

end Consumer_Type;

end Consumers;

Matthew Heaney 260

package body Buffers is

protected body Buffer_Type is

entry Put (Item : in Item_Type) when Count < Size is begin Put_Index := Put_Index mod Size + 1; Items (Put_Index) := Item; Count := Count + 1; end; ...

Matthew Heaney 261

... entry Get (Item : out Item_Type) when Count > 0 is begin Item := Items (Get_Index); Get_Index := Get_Index mod Size + 1; Count := Count - 1; end Get;

end Buffer_Type;

end Buffers;

Matthew Heaney 262

Termination Problem

• There’s a slight problem with this implementation: How do you terminate the consumer task?

• One way is to designate a value in the set of Item_Type as a meta-item that means “no more items.”

• This will work for discrete types like Character, but not easily for more complex data, or when there are multiple consumers.

Matthew Heaney 263

task body Consumer_Type is

C : Character; begin Main: loop

Buffer.Get (C);

exit Main when C = Latin_1.EOT;

<do something with character>

end loop Main; end Consumer_Type;

Matthew Heaney 264

declare Buffer : aliased Buffer_Type (Size => 5);

Consumer : Consumer_Type (Buffer'Access);begin for C in Character range ‘a’ .. ‘z’ loop Buffer.Put (C); end loop;

Buffer.Put (Latin_1.EOT);end;

Matthew Heaney 265

Termination Solution

• Give the producer a way to indicate explicitly that there are no more items.

• Pass status back to the consumer, to let her know all the items have been consumed.

• This solution is completely general, and works for any kind of data, and for any number of consumers.

Matthew Heaney 266

protected type Buffer_Type (Size : Positive) is

entry Put (Item : in Item_Type);

procedure Put_EOF;

entry Get (Item : out Item_Type; EOF : out Boolean); private

Items : Item_Array (1 .. Size); Get_Index : Positive := 1; Put_Index : Positive := Size; Count : Natural := 0; End_Of_File : Boolean := False;

end Buffer_Type;

Matthew Heaney 267

task body Consumer_Type is

C : Character; EOF : Boolean; begin Main: loop

Buffer.Get (C, EOF);

exit Main when EOF;

<do something with character>

end loop Main; end Consumer_Type;

Matthew Heaney 268

declare Buffer : aliased Buffer_Type (Size => 5);

Consumer : Consumer_Type (Buffer'Access);begin for C in Character range ‘a’ .. ‘z’ loop Buffer.Put (C); end loop;

Buffer.Put_EOF;end;

Matthew Heaney 269

protected body Buffer_Type is

entry Put (Item : in Item_Type) …; procedure Put_EOF is begin End_Of_File := True; end;

...

Matthew Heaney 270

entry Get (Item : out Item_Type; EOF : out Boolean) when Count > 0 or End_Of_File is begin if Count > 0 then

Item := Items (Get_Index); Get_Index := Get_Index mod Size + 1; Count := Count - 1;

EOF := False;

else

EOF := True;

end if; end Get;

Matthew Heaney 271

Resource Control

Lots O’ Stuff For Task Synchronization

Matthew Heaney 272

Canonical Form

• A protected object with protected subprograms that set and get the data.

• Simplicity has a price: protected operations cannot make blocking calls, and should only require a short amount of time to execute. These restrictions allow us to solve simple synchronization problems efficiently.

Matthew Heaney 273

type Time_Type is record Hour, Min, Sec : Natural; end record;

protected Protected_Time is procedure Set_Time (Time : in Time_Type);

function Get_Time return Time_Type;private Time : Time_Type;end Protected_Time;

Matthew Heaney 274

protected body Protected_Time is

procedure Set (Time : in Time_Type) is begin Protected_Time.Time := Time; end;

function Get_Time return Time_Type is begin return Time; end;

end Protected_Time;

Matthew Heaney 275

Semaphore

• A semaphore is a low-level primitive used to synchronize concurrent access to a resource.

• Yes, it’s still necessary in Ada95, even though we have protected types now. You’ll need it when you need to make blocking calls in the critical region.

• Use it only if you’re unable to satisfy the constraints of the canonical form.

Matthew Heaney 276

package Binary_Semaphores is

protected type Semaphore_Type is

procedure Release;

entry Seize;

private

In_Use : Boolean := False;

end Semaphore_Type;

end Binary_Semaphores;

Matthew Heaney 277

package body Binary_Semaphores is

protected body Semaphore_Type is

procedure Release is begin In_Use := False; end;

entry Seize when not In_Use is begin In_Use := True; end;

end Semaphore_Type;

end Binary_Semaphores;

Matthew Heaney 278

Semaphore : Semaphore_Type;Resource : Resource_Type;Task_1 : Task_1_Type;Task_2 : Task_2_Type;...task body Task_x_Type is begin … Semaphore.Seize;

<manipulate resource>

Semaphore.Release; …end Task_x_Type;

Matthew Heaney 279

package Message_IO is

procedure Put_Line (Message : in String);

end Message_IO;

Matthew Heaney 280

with Ada.Text_IO;

package body Message_IO is

protected Synchronization is

procedure Put_Line (Message : in String);

end Synchronization;

procedure Put_Line (Message : in String) is begin Synchronization.Put_Line (Message); end; ...

Matthew Heaney 281

... protected body Synchronization is

procedure Put_Line (Message : in String) is begin -- Wrong! Per RM95 9.5.1 (8, 18) Ada.Text_IO.Put_Line (Message); end;

end Synchronization;

end Message_IO;

Matthew Heaney 282

package body Message_IO is

Semaphore : Semaphore_Type;

procedure Put_Line (…) is begin Semaphore.Seize;

-- OK; not inside a protected op. Ada.Text_IO.Put_Line (Message);

Semaphore.Release; end;

end Message_IO;

Matthew Heaney 283

Deadlock

X, Y, Z : Integer;Semaphore : Semaphore_Type;...Semaphore.Seize;…X := 0;…Z := Y / X; -- Oops! Raises CE...Semaphore.Release; -- Bigger oops! -- Sema not released.

Matthew Heaney 284

package Binary_Semaphores.Controls is

type Semaphore_Control (Semaphore : access Semaphore_Type) is limited private;

private

type Semaphore_Control (Semaphore : access Semaphore_Type) is new Limited_Controlled with null record;

procedure Initialize (...); procedure Finalize (...);

end Binary_Semaphores.Controls;

Matthew Heaney 285

package body Binary_Semaphores.Controls is

procedure Initialize (Control : in out Semaphore_Control) is begin Control.Semaphore.Seize; end;

procedure Finalize (Control : in out Semaphore_Control) is begin Control.Semaphore.Release; end;

end Binary_Semaphores.Controls;

Matthew Heaney 286

Deadlock AvoidedX, Y, Z : Integer;Sema : aliased Semaphore_Type;…declare Control : Semaphore_Control (Sema’Access); -- Automatically seizes semaphore.begin … X := 0; … Z := Y / X; -- Oops! Raises CE. …end;-- OK; semaphore released automatically.

Matthew Heaney 287

Concurrent Stackgeneric ...package Stacks is

type Stack_Type is limited private;

procedure Push (Item : in Item_Type; On : in out Stack_Type);

procedure Pop (Stack : in out Stack_Type);

function Get_Top (Stack : Stack_Type) return Item_Type;

Matthew Heaney 288

...private

type Item_Array is array (1 .. Max_Depth) of Item_Type;

type Stack_Type is limited record Items : Item_Array; Top : Natural := 0; Sema : aliased Semaphore_Type; end record;

end Stacks;

Matthew Heaney 289

package body Stacks is

procedure Push (Item : in Item_Type; On : in out Stack_Type) is

Control : Semaphore_Control (On.Sema'Access); begin On.Top := On.Top + 1; On.Items (On.Top) := Item; end;

procedure Pop (Stack : in out Stack_Type) is

Control : Semaphore_Control (Stack.Sema'Access); begin Stack.Top := Stack.Top - 1; end;

Matthew Heaney 290

... function Get_Top (Stack : Stack_Type) return Item_Type is

Control : Semaphore_Control (Stack.Sema'Access); ^^^^^^^^^^^^^^^^^ begin

return SA.Items (SA.Top);

end Get_Top;

end Stacks;

stacks.adb:42:40: access-to-variable designates constant

Matthew Heaney 291

package body Stacks is

package Addr_To_Acc_Conversions is new System.Address_To_Access_Conversions (Stack_Type); ... function Get_Top (Stack : Stack_Type) return Item_Type is

SA : constant Object_Pointer := To_Pointer (Stack'Address); -- OK, per RM95 13.3 (16), because Stack_Type is -- a by-reference type (full view is limited).

Control : Semaphore_Control (SA.Sema'Access);

begin

return SA.Items (SA.Top);

end Get_Top;

end Stacks;

Matthew Heaney 292

package Stacks is

type Stack_Type is limited private; ...private ... type Handle_Type (Stack : access Stack_Type) is limited null record;

type Stack_Type is limited record Handle : Handle_Type (Stack_Type'Access); Items : Item_Array; Top : Natural := 0; Sema : aliased Semaphore_Type; end record;

end Stacks;

Matthew Heaney 293

function Get_Top (Stack : Stack_Type) return Item_Type is

Control : Semaphore_Control (Stack.Handle.Stack.Sema'Access);

begin

return Stack.Items (Stack.Top);

end Get_Top;

Matthew Heaney 294

Concurrent Stack Note

• To be honest: the example is a bit contrived, and was really designed to show a couple of ways of converting from a constant view of an object to a variable view.

• We don’t really need a semaphore here, because no blocking calls are made. The canonical monitor form satisfies our synchronization needs, and is probably more efficient anyway.

Matthew Heaney 295

• In general, you want to advertise that your abstraction synchronizes its callers.

• This is especially true if the abstraction has blocking behavior. This allows your callers to make timed or conditional entry calls.

• In practice this will mean wrapping the data inside a protected object. Clients that need access to the resource use the protected interface explicitly.

Matthew Heaney 296

protected Stack is

procedure Push (I : Integer);

procedure Pop;

function Top return Integer;

private

List : List_Type;

end Stack;

Matthew Heaney 297

protected body Stack is

procedure Push (I : Integer) is begin Push_Back (List, I); end;

procedure Pop is begin Pop_Back (List); end;

function Top return Integer is begin return Get_Back (List); end;

end Stack;

Matthew Heaney 298

protected Queue is

entry Remove (Item : out Integer);

procedure Add (Item : in Integer);

private

List : List_Type;

end Queue;

Matthew Heaney 299

protected body Queue is

entry Remove (Item : out Integer) when not Is_Empty (List) is begin Item := Get_Front (List); Pop_Front (List); end;

procedure Add (Item : in Integer) is begin Push_Back (List, Item); end;

end Queue;

Matthew Heaney 300

generic ...package Stacks is

type Stack_Type is limited private;

function "=" (L, R : Stack_Type) return Boolean; …end Stacks;

Static Locking Order

Matthew Heaney 301

package body Stacks is function Do_Equality (L, R : Stack_Type) return Boolean is begin

if L.Top /= R.Top then return False; end if;

for I in Integer range 1 .. L.Top loop if L.Items (I) /= R.Items (I) then return False; end if; end loop;

return True;

end Do_Equality; ...

Matthew Heaney 302

... function "=" (L, R : Stack_Type) return Boolean is

LA : constant Object_Pointer := To_Pointer (L'Address);

RA : constant Object_Pointer := To_Pointer (R'Address);

L_Control : Semaphore_Control (LA.Sema'Access);

R_Control : Semaphore_Control (RA.Sema'Access);

begin

return Do_Equality (L, R);

end "="; ...end Stacks;

Matthew Heaney 303

Deadlock Again

• First, if you compare a stack to itself, you’ll deadlock the second time you seize the semaphore (here, when you seize R).

• Second, the seizing of the pair of stacks is not an atomic operation. You’ll still deadlock because of circularity.

Matthew Heaney 304

S1, S2 : Stack_Type;T1 : Task_1_Type;T2 : Task_2_Type;

task body Task_1_Type isbegin … if S1 = S2 then …end;

task body Task_2_Type isbegin … if S2 = S1 then …end;

Matthew Heaney 305

A possible ordering of actions is:

Seize (S1.Sema); -- T1Seize (S2.Sema); -- T2Seize (S2.Sema); -- T1Seize (S1.Sema); -- T2

T1 is waiting for S2, which has already been seized by T2.

T2 is waiting for S1, which has already been seized by T1.

Circularity has caused deadlock.

Matthew Heaney 306

Removing the Circularity

• Define an order over the set of resources.

• Clients needing exclusive access to multiple resources lock them in resource order.

• By-reference resources already have an implicit order -- their address.

• Use RM95 13.3 (6) to get the address, and lock resources in order of their address.

Matthew Heaney 307

function "=" (L, R : Stack_Type) return Boolean is

LA : constant Object_Pointer := To_Pointer (L'Address);

RA : constant Object_Pointer := To_Pointer (R'Address);

begin

if L'Address < R'Address then

declare L_Control : Semaphore_Control (LA.Sema'Access); R_Control : Semaphore_Control (RA.Sema'Access); begin return Do_Equality (L, R); end;

...

Matthew Heaney 308

...

elsif L'Address = R'Address then

return True;

else -- R'Address < L'Address

declare R_Control : Semaphore_Control (RA.Sema'Access); L_Control : Semaphore_Control (LA.Sema'Access); begin return Do_Equality (L, R); end;

end if;

end "=";

Matthew Heaney 309

package Multiple_Reader_Semaphores is

type Seize_Kind is (For_Reading, For_Writing);

protected type Semaphore_Type is

entry Seize (Kind : in Seize_Kind);

procedure Release_For_Reading; procedure Release_For_Writing;

private

entry Waiting_To_Write;

Reader_Count : Natural := 0;

Writing : Boolean := False;

end Semaphore_Type;

end Multiple_Reader_Semaphores;

Matthew Heaney 310

package body Multiple_Reader_Semaphores is

protected body Semaphore_Type is

entry Seize (Kind : in Seize_Kind) when Waiting_To_Write'Count = 0 and not Writing is begin case Kind is when For_Reading => Reader_Count := Reader_Count + 1;

when For_Writing => requeue Waiting_To_Write with abort;

end case; end Seize;

...

Matthew Heaney 311

procedure Release_For_Reading is begin Reader_Count := Reader_Count - 1; end;

procedure Release_For_Writing is begin Writing := False; end;

entry Waiting_To_Write when Reader_Count = 0 is begin Writing := True; end;

end Semaphore_Type;

end Multiple_Reader_Semaphores;

Matthew Heaney 312

task body Reader_Type isbegin … Sema.Seize (For_Reading);

<read resource state> <make blocking calls> <read resource state again>

Sema.Release_For_Reading; …end Reader_Type;

Matthew Heaney 313

task body Writer_Type isbegin … Sema.Seize (For_Writing);

<change state of resource> <make blocking calls> <change state again>

Sema.Release_For_Writing; …end Writer_Type;

Matthew Heaney 314

package Counting_Semaphores is

protected type Semaphore_Type (Default : Natural := 1) is

entry Wait;

procedure Signal;

private

Count : Natural := Default;

end Semaphore_Type;

end Counting_Semaphores;

Matthew Heaney 315

package body Counting_Semaphores is

protected body Semaphore_Type is

entry Wait when Count > 0 is begin Count := Count - 1; end;

procedure Signal is begin Count := Count + 1; end;

end Semaphore_Type;

end Counting_Semaphores;

Matthew Heaney 316

Maitre_D : Semaphore_Type (Default => 4); -- Not req’d if you pick up chopsticks in order.

task body Philosopher_Task_Type is begin loop Maitre_D.Wait; -- to sit down at table

Pick_Up (Left); Pick_Up (Right);

delay Delay_Time; -- eat

Put_Down (Left); Put_Down (Right);

Maitre_D.Signal; -- leave the table

delay Delay_Time; -- think end loop;

Matthew Heaney 317

-- No maitre d’ is req’d, since we pick up the -- chopsticks according to their locking order.

task body Philosopher_Task_Type is begin loop Pick_Up (Chopstick_Id’Min (Left, Right)); Pick_Up (Chopstick_Id’Max (Left, Right));

delay Delay_Time; -- eat

Put_Down (Left); Put_Down (Right);

delay Delay_Time; -- think end loop; end Philosopher_Task_Type;

Matthew Heaney 318

Producer-Consumer

• When a producer of a resource must wait for it to be consumed, and the consumer must wait until the resource is produced.

• You can implement the communication using a task rendevous (the high-level way), or using a pair of semaphores (the low-level way).

Matthew Heaney 319

task Producer is

entry Get(Item : out Item_Type);end;

task body Producer isbegin

<produce item>

accept Get (Item : out Item_Type) Item := ... end;

...end Producer;

Matthew Heaney 320

task body Consumer isbegin

... Producer.Get(Item);

...

end Consumer;

Matthew Heaney 321

package Binary_Semaphores is

protected type Semaphore_Type (Default : Boolean := False) is

entry Wait;

procedure Signal;

private

Signaled : Boolean := Default;

end Semaphore_Type;

end Binary_Semaphores;

Matthew Heaney 322

Producer_Semaphore : Semaphore_Type (Default => False); Consumer_Semaphore : Semaphore_Type (Default => True);

task body Producer is begin loop -- Wait for consumer to finish consuming. Consumer_Semaphore.Wait;

<produce resource>

-- Let consumer know producer is done producing. Producer_Semaphore.Signal; end loop; end Producer;

Matthew Heaney 323

task body Consumer is begin loop -- Wait for producer to finish producing. Producer_Semaphore.Wait;

<consume resource> -- Let producer know consumer has consumed. Consumer_Semaphore.Signal; end loop; end Consumer;

Matthew Heaney 324

Recursive Semaphore

• When a task needs to seize a semaphore more than once prior to releasing it.

• Task that owns semaphore is allowed to call Seize multiple times without blocking.

• Other tasks wait if a task already owns semaphore. A new task assumes ownership when current task has Released every Seize.

Matthew Heaney 325

package Recursive_Semaphores is

protected type Semaphore_Type is

procedure Release;

entry Seize;

private

entry Waiting;

Owner : Ada.Task_Identification.Task_Id; Count : Natural := 0;

end Semaphore_Type;

end Recursive_Semaphores;

Matthew Heaney 326

package body Recursive_Semaphores is

protected body Semaphore_Type is

procedure Release is begin Count := Count - 1; end;

entry Seize when True is begin if Seize'Caller = Owner then Count := Count + 1; else requeue Waiting with abort; end if; end;

Matthew Heaney 327

entry Waiting when Count = 0 is begin Count := 1; Owner := Waiting'Caller; end;

end Semaphore_Type;

end Recursive_Semaphores;

Matthew Heaney 328

Semaphore : Semaphore_Type;

procedure Op1 isbegin Semaphore.Seize; ... if P then Op2; end if; ... Semaphore.Release;end Op1;

procedure Op2 isbegin Semaphore.Seize; … Semaphore.Release;end Ops;

Matthew Heaney 329

Persistent Signal

• To permanently record that an event has happened.

• Keep task(s) waiting until the event occurs. If the event has already happened, then task proceeds immediately.

• Useful for removing a task’s Initialize or Start entry that only gets called once.

Matthew Heaney 330

protected Task_Initialization is

entry Wait;

procedure Start;

private

OK_To_Start : Boolean := False;

end Task_Initialization;

Matthew Heaney 331

protected body Task_Initialization is

entry Wait when OK_To_Start is begin null; end;

procedure Start is begin OK_To_Start := True; end;

end Task_Initialization;

Matthew Heaney 332

task Philosopher_Task_Type (…); -- no Init entry req’d

Philosophers : Philosopher_Task_Array; …

task body Philosopher_Task_Type isbegin

Task_Initialization.Wait; -- wait until it’s OK -- to philosophize loop … end loop;

end Philosopher_Task_Type;

Matthew Heaney 333

Barrier

• Blocks a group of tasks until all have arrived.

Matthew Heaney 334

protected Task_Finalization is

entry Wait;

private

Release_All : Boolean := False;

end Task_Finalization;

Matthew Heaney 335

protected body Task_Finalization is

entry Wait when Wait'Count = Philosopher_Id'Last or Release_All is begin Release_All := True; end;

end Task_Finalization;

Matthew Heaney 336

task Philosopher_Task_Type (…); -- no Init entry req’d

Philosophers : Philosopher_Task_Array; …task body Philosopher_Task_Type isbegin

Task_Initialization.Wait; -- they aren’t necessarily -- born together... loop … end loop;

Task_Finalization.Wait; -- … but they do all -- die togetherend Philosopher_Task_Type;

Matthew Heaney 337

All-or-Nothing Resource Allocation

• Suppose one philosopher is eating, and the other three philosophers at the table have each picked up their left chopstick.

• The issue is that two philosophers could be eating. Now, one eats and three wait.

• Make a new rule: if both chopsticks are available, then pick them both up; otherwise, wait to eat.

Matthew Heaney 338

protected Chopsticks is

entry Pick_Up (Id : Philosopher_Id);

procedure Put_Down (Id : Philosopher_Id);

private

entry Waiting (Id : Philosopher_Id);

Available : Boolean_Array := (others => True);

Retrying : Boolean := False;

end Chopsticks;

Matthew Heaney 339

task body Philosopher_Task_Type is begin loop

Chopsticks.Pick_Up (Id);

delay Delay_Time; -- eat

Chopsticks.Put_Down (Id);

delay Delay_Time; -- think

end loop; end Philosopher_Task_Type;

Matthew Heaney 340

protected body Chopsticks is

entry Pick_Up (Id : Philosopher_Id) when not Retrying is

Next : constant Philosopher_Id := Id mod 5 + 1;

begin

if Available (Id) and Available (Next) then Available (Id) := False; Available (Next) := False; else requeue Waiting with abort; end if;

end Pick_Up; ...

Matthew Heaney 341

procedure Put_Down (Id : Philosopher_Id) is

Next : constant Philosopher_Id := Id mod 5 + 1; begin Available (Id) := True; Available (Next) := True;

Retrying := Waiting'Count > 0; end;

entry Waiting (Id : Philosopher_Id) when Retrying is begin if Waiting'Count = 0 then Retrying := False; end if;

requeue Pick_Up with abort; end Waiting;

end Chopsticks;

Matthew Heaney 342

ATC

• Abort just the processing being done by a task, without aborting the task.

• Done through a protected object. The task doesn’t have to interrupt its own processing to poll a Shutdown or Cancel entry.

• Need to carefully think about whether to requeue with abort, or to just requeue (without abort), if you’re using ATC.

Matthew Heaney 343

protected type Signal_Type is

entry Wait;

procedure Send;

private

Occurred : Boolean := False;

end Signal_Type;

-- This is a “permanent signal.”

Matthew Heaney 344

protected body Signal_Type is

entry Wait when Occurred is begin null; end;

procedure Send is begin Occurred := True; end;

end Signal_Type;

Matthew Heaney 345

Task_Initialization : Signal_Type; Task_Finalization : Signal_Type;

procedure Start (Update : in Update_Access) is begin Task_Initialization.Send; end;

procedure Stop is begin Task_Finalization.Send; end;

Matthew Heaney 346

task body Philosopher_Task_Type is begin

Task_Initialization.Wait;

select Task_Finalization.Wait; then abort

loop Chopsticks.Pick_Up (Id); delay Delay_Time; -- eat Chopsticks.Put_Down (Id); delay Delay_Time; -- think end loop;

end select;

end Philosopher_Task_Type;