comp.lang.ada
 help / color / mirror / Atom feed
* Activating tasks at global scope
@ 1993-03-10  3:32 Scott Meyers
  1993-03-10 17:11 ` Robert I. Eachus
  1993-03-11  2:51 ` Michael Feldman
  0 siblings, 2 replies; 7+ messages in thread
From: Scott Meyers @ 1993-03-10  3:32 UTC (permalink / raw)


The code below implements a producer-consumer system containing one
producing task, two consuming tasks, and a bounded buffer task.  I am only
interested in the tasking interactions, so I've omitted the actual buffer
manipulations.  This code works fine under the Ada/ED compiler.  However, I
would prefer to put the tasks at global scope rather than nest them inside
the producer_consumer procedure.  I tried to do this by putting each task
inside a package, but then I couldn't figure out how to activate the tasks
when producer_consumer was invoked.  What I'd like is an architecture where
the tasks are automatically started before or at the same time the the main
subprogram is invoked.

If I've done anything particularly gross, feel free to comment
appropriately.  Nobody here knows Ada, so I put this together by copying
fairly liberally from Ben-Ari's book, "Principles of Concurrent and
Distributed Programming."

Thanks,

Scott


with Text_IO;
use Text_IO;

procedure producer_consumer is
  task Buffer is
    entry insert(item: in Integer);
    entry remove(item: out Integer);
  end Buffer;

  task body Buffer is
    count: Integer := 0;

    begin
      loop
        select when count < 10 =>
          accept insert(item: in Integer) do
            -- insert item into the buffer
            null;
          end insert;
          count := count + 1;

        or when count > 0 =>
          accept remove(item: out Integer) do
            -- remove an object from the buffer and assign it to item
            null;
          end remove;
          count := count - 1;
        end select;

      end loop;
    end Buffer;

  task Producer;
  task body Producer is
    n: integer;
    
    begin
      loop
        -- give n an appropriate value
        Buffer.insert(n);
      end loop;
  end Producer;

  task Consumer1;
  task body Consumer1 is
    n: integer;
    
    begin
      loop
        Buffer.remove(n);
        -- do something with n
      end loop;
  end Consumer1;

  task Consumer2;
  task body Consumer2 is
    n: integer;
    
    begin
      loop
        Buffer.remove(n);
        -- do something with n
      end loop;
  end Consumer2;


  begin
    null;
  end;

-------------------------------------------------------------------------------
What do you say to a convicted felon in Providence?  "Hello, Mr. Mayor."



^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: Activating tasks at global scope
  1993-03-10  3:32 Activating tasks at global scope Scott Meyers
@ 1993-03-10 17:11 ` Robert I. Eachus
  1993-03-11  3:56   ` Scott Meyers
  1993-03-11  2:51 ` Michael Feldman
  1 sibling, 1 reply; 7+ messages in thread
From: Robert I. Eachus @ 1993-03-10 17:11 UTC (permalink / raw)


In article <1993Mar10.033256.24718@cs.brown.edu> sdm@cs.brown.edu (Scott Meyers) writes:

  > The code below implements a producer-consumer system containing one
  > producing task, two consuming tasks, and a bounded buffer task.  I am only
  > interested in the tasking interactions, so I've omitted the actual buffer
  > manipulations.  This code works fine under the Ada/ED compiler.  However, I
  > would prefer to put the tasks at global scope rather than nest them inside
  > the producer_consumer procedure.  I tried to do this by putting each task
  > inside a package, but then I couldn't figure out how to activate the tasks
  > when producer_consumer was invoked.  What I'd like is an architecture where
  > the tasks are automatically started before or at the same time the the main
  > subprogram is invoked.

  You were doing fine, but got bitten by a very subtle feature of Ada.
The tasks were all created and elaborated before the main program
executed, but then the main program immediately exited.  The language
reference manual leaves it unspecifed what happens to library tasks in
such a situation, but most implementations now terminate them all if
they are quiescent.  So your tasks disappeared from view before they
could act.

   In any case try hanging your main program, either by putting in a
delay statement or by waiting for input...the elegent final version
should have a clean way of terminating the program, but this will do
for testing.

--

					Robert I. Eachus

with Standard_Disclaimer;
use  Standard_Disclaimer;
function Message (Text: in Clever_Ideas) return Better_Ideas is...



^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: Activating tasks at global scope
  1993-03-10  3:32 Activating tasks at global scope Scott Meyers
  1993-03-10 17:11 ` Robert I. Eachus
@ 1993-03-11  2:51 ` Michael Feldman
  1993-03-11  2:54   ` second half of portable diners Michael Feldman
  1 sibling, 1 reply; 7+ messages in thread
From: Michael Feldman @ 1993-03-11  2:51 UTC (permalink / raw)


In article <1993Mar10.033256.24718@cs.brown.edu> sdm@cs.brown.edu (Scott Meyers) writes:
>The code below implements a producer-consumer system containing one
>producing task, two consuming tasks, and a bounded buffer task.  I am only
>interested in the tasking interactions, so I've omitted the actual buffer
>manipulations.  This code works fine under the Ada/ED compiler.  However, I
>would prefer to put the tasks at global scope rather than nest them inside
>the producer_consumer procedure.  I tried to do this by putting each task
>inside a package, but then I couldn't figure out how to activate the tasks
>when producer_consumer was invoked.  What I'd like is an architecture where
>the tasks are automatically started before or at the same time the the main
>subprogram is invoked.
>
Put the tasks in a package. Attached is a comparable example, though a bit
more involved than yours. It's a re-post of my Portable Diners Kit, which
is now being distributed as one of the Ada/Ed demos, and also appears in
the Ada Quality & Style Guide. Have a look and have fun.

The various compilation units can be separated or left in one file; they
appear in a correct compilation order, so one compiler invocation will do
it. Link and run "diners".

Mike Feldman
---- cut here ----
--::::::::::
--io_libs.ada
--::::::::::
-- Precompiled instantiations of Integer_IO and
-- Float_IO for the predefined Integer and Float types
 
WITH Text_IO;
PACKAGE My_Int_IO IS
  NEW Text_IO.Integer_IO (Num => Integer);
 
WITH Text_IO;
PACKAGE My_Flt_IO IS
  NEW Text_IO.Float_IO   (Num => Float);
--::::::::::
--random.ads
--::::::::::
PACKAGE Random IS
 
-- Simple pseudo-random number generator package.
-- Adapated from the Ada literature by
-- Michael B. Feldman, The George Washington University, November 1990.
 
  PROCEDURE Set_Seed (N : Positive);
 
  FUNCTION  Unit_Random RETURN Float;
 
    --returns a float >=0.0 and <1.0
 
  FUNCTION  Random_Int (N : Positive) RETURN Positive;
 
    --return a random integer in the range 1..N
 
END Random;
--::::::::::
--chop.ads
--::::::::::
PACKAGE Chop IS
 
  TASK TYPE Stick IS
    ENTRY Pick_Up;
    ENTRY Put_Down;
  END Stick;
 
END Chop;
--::::::::::
--phil.ads
--::::::::::
PACKAGE Phil IS
  
  TASK TYPE Philosopher IS
    
    ENTRY Come_To_Life (My_ID :      Positive; 
                        Chopstick1 : Positive;
                        Chopstick2 : Positive);
 
  END Philosopher;
 
  TYPE States IS (Breathing, Thinking, Eating, Done_Eating,
                    Got_One_Stick, Got_Other_Stick);
 
END Phil;
--::::::::::
--room.ads
--::::::::::
WITH Chop;
WITH Phil;
PACKAGE Room IS
 
  Table_Size: CONSTANT := 5;
  SUBTYPE Table_Type IS Positive RANGE 1..Table_Size;
 
  Sticks:     ARRAY(Table_Type) OF Chop.Stick;
 
  TASK Head_Waiter IS
    ENTRY Open_The_Room;
    ENTRY Report_State(Which_Phil: Table_Type;
                       State: Phil.States;
                       How_Long: Natural := 0);
  END Head_Waiter;
 
END Room;
--::::::::::
--diners.ada
--::::::::::
WITH Room;
PROCEDURE Diners IS
 
BEGIN
  Room.Head_Waiter.Open_The_Room;
  LOOP
    DELAY 20.0;
  END LOOP;
END Diners;
--::::::::::
--random.adb
--::::::::::
WITH Calendar;
USE  Calendar;
 
PACKAGE BODY Random IS
 
-- Body of random number generator package.
-- Adapted from the Ada literature by
-- Michael B. Feldman, The George Washington University, November 1990.
 
  Modulus      : CONSTANT := 9317;
 
  TYPE Int_16 IS RANGE - 2 ** 15 .. 2 ** 15 - 1;
 
  TYPE Int_32 IS RANGE - 2 ** 31 .. 2 ** 31 - 1;
 
  SUBTYPE Seed_Range IS Int_16 RANGE 0 .. (Modulus - 1);
 
  Seed,
  Default_Seed : Seed_Range;
 
  PROCEDURE Set_Seed (N : Positive) IS SEPARATE;
 
  FUNCTION  Unit_Random RETURN Float IS SEPARATE;
 
  FUNCTION  Random_Int (N : Positive) RETURN Positive IS SEPARATE;
BEGIN
  Default_Seed := Int_16 (Int_32 (Seconds (Clock)) MOD Modulus);
  Seed := Default_Seed;
END Random;
 
SEPARATE (Random)
 
PROCEDURE Set_Seed (N : Positive) IS
BEGIN
  Seed := Seed_Range (N);
END Set_Seed;
 
SEPARATE (Random)
 
FUNCTION  Unit_Random RETURN Float IS
  Multiplier : CONSTANT := 421;
  Increment  : CONSTANT := 2073;
  Result     : Float;
BEGIN
  Seed := (Multiplier * Seed + Increment) MOD Modulus;
  Result := Float (Seed) / Float (Modulus);
  RETURN Result;
EXCEPTION
  WHEN Constraint_Error | Numeric_Error =>
    Seed := Int_16 ((Multiplier * Int_32 (Seed) + Increment) MOD Modulus);
    Result := Float (Seed) / Float (Modulus);
    RETURN Result;
 
END Unit_Random;
 
SEPARATE (Random)
 
FUNCTION  Random_Int (N : Positive) RETURN Positive IS
  Result : Integer RANGE 1 .. N;
BEGIN
  Result := Integer (Float (N) * Unit_Random + 0.5);
  RETURN Result;
EXCEPTION
  WHEN Constraint_Error | Numeric_Error =>
    RETURN 1;
 
END Random_Int;
--::::::::::
--chop.adb
--::::::::::
PACKAGE BODY Chop IS
 
  TASK BODY Stick IS
 
  BEGIN
    
    LOOP
      SELECT
        ACCEPT Pick_Up;
        ACCEPT Put_Down;
      OR
        TERMINATE;
      END SELECT;
    END LOOP;
 
  END Stick;
 
END Chop;
--::::::::::
--phil.adb
--::::::::::
WITH Room;
WITH Random;
PACKAGE BODY Phil IS
  
  TASK BODY Philosopher IS
 
    Who_Am_I   : Positive;
    First_Grab : Positive;
    Second_Grab: Positive;
    Meal_Time  : Natural;
    Think_Time : Natural;
    
  BEGIN
    ACCEPT Come_To_Life (My_ID :     Positive; 
                        Chopstick1 : Positive;
                        Chopstick2 : Positive) DO
      Who_Am_I    := My_ID;
      First_Grab  := Chopstick1;
      Second_Grab := Chopstick2;
 
    END Come_To_Life;
 
    Room.Head_Waiter.Report_State(Who_Am_I, Breathing);
 
    LOOP
 
      Room.Sticks(First_Grab).Pick_Up;
      Room.Head_Waiter.Report_State(Who_Am_I, Got_One_Stick, First_Grab);
 
      Room.Sticks(Second_Grab).Pick_Up;
      Room.Head_Waiter.Report_State(Who_Am_I, Got_Other_Stick, Second_Grab);
 
      Meal_Time := Random.Random_Int(10);
      Room.Head_Waiter.Report_State(Who_Am_I, Eating, Meal_Time);
 
      DELAY Duration(Meal_Time);
      Room.Head_Waiter.Report_State(Who_Am_I, Done_Eating);
 
      Room.Sticks(First_Grab).Put_Down;
      Room.Sticks(Second_Grab).Put_Down;
 
      Think_Time := Random.Random_Int(10);
      Room.Head_Waiter.Report_State(Who_Am_I, Thinking, Think_Time);
      DELAY Duration(Think_Time);
 
    END LOOP;
 
  END Philosopher;
 
END Phil;
--::::::::::
--roomline.adb
--::::::::::
WITH Text_IO;
WITH Chop;
WITH Phil;
WITH Calendar;
PRAGMA Elaborate(Phil);
PACKAGE BODY Room IS
 
-- A line-oriented version of the Room package, for line-oriented
-- terminals like IBM 3270's where the user cannot do ASCII screen control.
-- This is the only file in the dining philosophers system that needs
-- changing to use in a line-oriented environment.
-- Michael B. Feldman, The George Washington University, November 1990.
 
 
  Phils:      ARRAY(Table_Type) OF Phil.Philosopher;
 
  TYPE Phil_Names IS (Dijkstra, Texel, Booch, Ichbiah, Stroustrup);
 
  TASK BODY Head_Waiter IS
 
    T : Integer;
    Start_Time: Calendar.Time;
    Phil_Names: CONSTANT ARRAY(1..5) OF String(1..18) :=
     ("Eddy Dijkstra     ",
      "Putnam Texel      ",
      "Grady Booch       ",
      "Jean Ichbiah      ",
      "Bjarne Stroustrup ");
    Blanks : CONSTANT String := "     ";
 
  BEGIN
 
    ACCEPT Open_The_Room;
    Start_Time := Calendar.Clock;
 
    Phils(1).Come_To_Life(1,1,2);
    Phils(3).Come_To_Life(3,3,4);
    Phils(2).Come_To_Life(2,2,3);
    Phils(5).Come_To_Life(5,1,5);
    Phils(4).Come_To_Life(4,4,5);
 
    LOOP
      SELECT
        ACCEPT Report_State(Which_Phil: Table_Type;
                         State: Phil.States;
                         How_Long: Natural := 0) DO
          T := Integer(Calendar."-"(Calendar.Clock,Start_Time));
          Text_IO.Put( "T=" & Integer'Image(T) & " "
            & Blanks(1..Which_Phil) & Phil_Names(Which_Phil));
 
          CASE State IS
 
            WHEN Phil.Breathing =>
              Text_IO.Put("Breathing");
            WHEN Phil.Thinking =>
              Text_IO.Put( "Thinking"
                         & Integer'Image(How_Long)
                         & " seconds.");
            WHEN Phil.Eating =>
              Text_IO.Put( "Eating"
                         & Integer'Image(How_Long)
                         & " seconds.");
            WHEN Phil.Done_Eating =>
              Text_IO.Put("Yum-yum (burp)");
            WHEN Phil.Got_One_Stick =>
              Text_IO.Put( "First chopstick"
                          & Integer'Image(How_Long));
            WHEN Phil.Got_Other_Stick =>
              Text_IO.Put( "Second chopstick"
                          & Integer'Image(How_Long));
 
          END CASE;
          Text_IO.New_Line;
 
         END Report_State;
        OR
          TERMINATE;
        END SELECT;
 
      END LOOP;
 
    END Head_Waiter;
 
END Room;



^ permalink raw reply	[flat|nested] 7+ messages in thread

* second half of portable diners
  1993-03-11  2:51 ` Michael Feldman
@ 1993-03-11  2:54   ` Michael Feldman
  0 siblings, 0 replies; 7+ messages in thread
From: Michael Feldman @ 1993-03-11  2:54 UTC (permalink / raw)


Once you get the line-oriented diners running, compile this second group
of units and re-link diners. You'll get a cute cheap-windows version.

Mike Feldman
---- cut here ----
--::::::::::
--screen.ads
--::::::::::
PACKAGE Screen IS

-- Procedures for drawing pictures on ANSI Terminal Screen

  ScreenDepth : CONSTANT Integer := 24;
  ScreenWidth : CONSTANT Integer := 80;

  SUBTYPE Depth IS Integer RANGE 1..ScreenDepth;
  SUBTYPE Width IS Integer RANGE 1..ScreenWidth;

  PROCEDURE Beep; 
  PROCEDURE ClearScreen; 
  PROCEDURE MoveCursor (Column : Width; Row : Depth);

END Screen;   
--::::::::::
--windows.ads
--::::::::::
WITH Screen;
USE Screen;
PACKAGE Windows IS

  TYPE Window IS PRIVATE;

  PROCEDURE Open (W      : IN OUT Window; -- Window variable returned 
                  Row    : Depth; -- Upper left corner
                  Column : Width;
                  Height : Depth; -- Size of window
                  Width  : Screen.Width);

  -- Create a window variable and open the window for writing.  
  -- No checks for overlap of windows are made. 


  PROCEDURE Close (W : IN OUT Window);
  -- Close window and clear window variable. 


  PROCEDURE Title (W     : IN OUT Window;
                   Name  : String;
                   Under : Character);

  -- Put a title name at the top of the window.  If the parameter 
  -- under <> 0C or ' ', underline the title with the specified character. 


  PROCEDURE Borders (W                    : IN OUT Window;
                     Corner, Down, Across : Character);

  -- Draw border around current writable area in window with characters
  -- specified.  Call this BEFORE Title.  


  PROCEDURE Gotorowcolumn (W      : IN OUT Window;
                           Row    : Depth;
                           Column : Width);

  -- Goto the row and column specified.  Coordinates are relative to the
  -- upper left corner of window, which is (1, 1) 


  PROCEDURE Put (W  : IN OUT Window;
                 Ch : Character);

  -- put one character to the window.
  -- If end of column, go to the next row.
  -- If end of window, go to the top of the window. 


  PROCEDURE Put_String (W : IN OUT Window;
                        S : String);

  -- put a string to window. 


  PROCEDURE New_Line (W : IN OUT Window);

  -- Go to beginning of next line.  Next line is
  -- not blanked until next character is written  


PRIVATE
  TYPE Window IS
    RECORD
      Currentrow, -- Current cursor row 
      Firstrow,
      Lastrow : Depth;
      Currentcolumn, -- Current cursor column 
      Firstcolumn,
      Lastcolumn : Width;
    END RECORD;

END Windows;
--::::::::::
--screen.adb
--::::::::::
WITH Text_IO;
WITH My_Int_IO;
PACKAGE BODY Screen IS

-- Procedures for drawing pictures on ANSI Terminal Screen


  PROCEDURE Beep IS
  BEGIN
    Text_IO.Put (Item => ASCII.BEL);
  END Beep;

  PROCEDURE ClearScreen IS
  BEGIN
    Text_IO.Put (Item => ASCII.ESC);
    Text_IO.Put (Item => "[2J");
  END ClearScreen;

  PROCEDURE MoveCursor (Column : Width; Row : Depth) IS
  BEGIN                                                
    Text_IO.New_Line;
    Text_IO.Put (Item => ASCII.ESC);
    Text_IO.Put ("[");
    My_Int_IO.Put (Item => Row, Width => 1);
    Text_IO.Put (Item => ';');
    My_Int_IO.Put (Item => Column, Width => 1);
    Text_IO.Put (Item => 'f');
  END MoveCursor;  

END Screen;
--::::::::::
--windows.adb
--::::::::::
WITH Text_IO, My_Int_IO, Screen;
USE Text_IO, My_Int_IO, Screen;
PACKAGE BODY Windows IS

  CursorRow : Depth := 1; -- Current cursor position
  CursorCol : Width := 1;

  PROCEDURE Open (W      : IN OUT Window;
                  Row    : Depth;
                  Column : Width;
                  Height : Depth;
                  Width  : Screen.Width) IS
    --Put the Window's cursor in upper left corner
  BEGIN
    W.CurrentRow    := Row;
    W.FirstRow      := Row;
    W.LastRow       := Row + Height - 1;
    W.CurrentColumn := Column;
    W.FirstColumn   := Column;
    W.LastColumn    := Column + Width - 1;
  END Open;

  PROCEDURE Close (W : IN OUT Window) IS
  BEGIN
    NULL;
  END Close;

  PROCEDURE Title (W     : IN OUT Window;
                   name  : String;
                   under : CHARACTER) IS
    -- Put name at the top of the Window.  If under <>  ' ', underline
    -- the title. 
    i : Width;
  BEGIN
    -- Put name on top line
    W.CurrentColumn := W.FirstColumn;
    W.CurrentRow    := W.FirstRow;
    Put_String (w, name);
    new_line (w);
    -- Underline name if desired, and move the First line of the Window
    -- below the title 
    IF under = ' ' THEN
      W.FirstRow := W.FirstRow + 1;
    ELSE
      FOR i IN W.FirstColumn .. W.LastColumn LOOP
        Put (w, under);
      END LOOP;
      new_line (w);
      W.FirstRow := W.FirstRow + 2;
    END IF;
  END Title;


  PROCEDURE GotoRowColumn (w      : IN OUT Window;
                           Row    : Depth;
                           Column : Width) IS
    -- Relative to writable Window boundaries, of course
  BEGIN
    W.CurrentRow    := W.FirstRow + Row;
    W.CurrentColumn := W.FirstColumn + Column;
  END GotoRowColumn;


  PROCEDURE Borders (w                    : IN OUT Window;
                     corner, down, across : CHARACTER) IS
    -- Draw border around current writable area in Window with characters.
    -- Call this BEFORE Title.  
    i : Depth;
    j : Width;
  BEGIN
    -- Put top line of border
    MoveCursor (W.FirstColumn, W.FirstRow);
    Text_IO.Put (corner);
    FOR j IN W.FirstColumn + 1 .. W.LastColumn - 1 LOOP
      Text_IO.Put (across);
    END LOOP;
    Text_IO.Put (corner);

    -- Put the two side lines
    FOR i IN W.FirstRow + 1 .. W.LastRow - 1 LOOP
      MoveCursor (W.FirstColumn, i);
      Text_IO.Put (down);
      MoveCursor (W.LastColumn, i);
      Text_IO.Put (down);
    END LOOP;

    -- Put the bottom line of the border
    MoveCursor (W.FirstColumn, W.LastRow);
    Text_IO.Put (corner);
    FOR j IN W.FirstColumn + 1 .. W.LastColumn - 1 LOOP
      Text_IO.Put (across);
    END LOOP;
    Text_IO.Put (corner);

    -- Put the cursor at the very end of the Window
    CursorRow := W.LastRow;
    CursorCol := W.LastColumn + 1;

    -- Make the Window smaller by one character on each side
    W.FirstRow      := W.FirstRow + 1;
    W.CurrentRow    := W.FirstRow;
    W.LastRow       := W.LastRow - 1;
    W.FirstColumn   := W.FirstColumn + 1;
    W.CurrentColumn := W.FirstColumn;
    W.LastColumn    := W.LastColumn - 1;
  END Borders;


  PROCEDURE EraseToEndOfLine (W : IN OUT Window) IS
    i : Width;
  BEGIN
    MoveCursor (W.CurrentColumn, W.CurrentRow);
    FOR i IN W.CurrentColumn .. W.LastColumn LOOP
      Text_IO.Put (' ');
    END LOOP;
    MoveCursor (W.CurrentColumn, W.CurrentRow);
    CursorCol := W.CurrentColumn;
    CursorRow := W.CurrentRow;
  END EraseToEndOfLine;


  PROCEDURE Put (W  : IN OUT Window;
                 ch : CHARACTER) IS

    -- If after end of line, move to First character of next line
    -- If about to write First character on line, blank rest of line.
    -- Put character.

  BEGIN
    IF Ch = ASCII.CR THEN
      New_Line (W);
      RETURN;
    END IF;

    -- If at end of current line, move to next line 
    IF W.CurrentColumn > W.LastColumn THEN
      IF W.CurrentRow = W.LastRow THEN
        W.CurrentRow := W.FirstRow;
      ELSE
        W.CurrentRow := W.CurrentRow + 1;
      END IF;
      W.CurrentColumn := W.FirstColumn;
    END IF;

    -- If at W.First char, erase line
    IF W.CurrentColumn = W.FirstColumn THEN
      EraseToEndOfLine (W);
    END IF;

    -- Put physical cursor at Window's cursor
    IF (CursorCol /= W.CurrentColumn) OR (CursorRow /= W.CurrentRow) THEN
      MoveCursor (W.CurrentColumn, W.CurrentRow);
      CursorRow := W.CurrentRow;
    END IF;

    IF Ch = ASCII.BS THEN
      -- Special backspace handling 
      IF W.CurrentColumn /= W.FirstColumn THEN
        Text_IO.Put (Ch);
        W.CurrentColumn := W.CurrentColumn - 1;
      END IF;
    ELSE
      Text_IO.Put (Ch);
      W.CurrentColumn := W.CurrentColumn + 1;
    END IF;
    CursorCol := W.CurrentColumn;
  END Put;


  PROCEDURE new_line (W : IN OUT Window) IS
    col : Width;

    -- If not after line, blank rest of line.
    -- Move to First character of next line

  BEGIN
    IF W.CurrentColumn = 0 THEN
      EraseToEndOfLine (W);
    END IF;
    IF W.CurrentRow = W.LastRow THEN
      W.CurrentRow := W.FirstRow;
    ELSE
      W.CurrentRow := W.CurrentRow + 1;
    END IF;
    W.CurrentColumn := W.FirstColumn;
  END new_line;


  PROCEDURE Put_String (W : IN OUT Window;
                        S : String) IS
  BEGIN
    FOR I IN S'FIRST .. S'LAST LOOP
      Put (W, S (i));
    END LOOP;
  END Put_String;


BEGIN -- Windows
  ClearScreen;
  MoveCursor (1, 1);
END Windows;
--::::::::::
--roomwind.adb
--::::::::::
WITH Windows;
WITH Chop;
WITH Phil;
WITH Calendar; 
PRAGMA Elaborate(Phil);
PACKAGE BODY Room IS

  Phils:      ARRAY(Table_Type) OF Phil.Philosopher;
  Phil_Windows: ARRAY(Table_Type) OF Windows.Window;

  TYPE Phil_Names IS (Dijkstra, Texel, Booch, Ichbiah, Stroustrup);

  TASK BODY Head_Waiter IS

    T : Integer; 
    Start_Time: Calendar.Time;

  BEGIN

    ACCEPT Open_The_Room;
    Start_Time := Calendar.Clock;

    Windows.Open(Phil_Windows(1),1,23,7,30);
    Windows.Borders(Phil_Windows(1),'+','|','-');
    Windows.Title(Phil_Windows(1), "Eddy Dijkstra",'-');
    Phils(1).Come_To_Life(1,1,2);

    Windows.Open(Phil_Windows(3),9,50,7,30); 
    Windows.Borders(Phil_Windows(3),'+','|','-');
    Windows.Title(Phil_Windows(3), "Grady Booch",'-');
    Phils(3).Come_To_Life(3,3,4);

    Windows.Open(Phil_Windows(2),9,2,7,30); 
    Windows.Borders(Phil_Windows(2),'+','|','-');
    Windows.Title(Phil_Windows(2), "Putnam Texel",'-');
    Phils(2).Come_To_Life(2,2,3);

    Windows.Open(Phil_Windows(5),17,41,7,30); 
    Windows.Borders(Phil_Windows(5),'+','|','-');
    Windows.Title(Phil_Windows(5), "Bjarne Stroustrup",'-');
    Phils(5).Come_To_Life(5,1,5);

    Windows.Open(Phil_Windows(4),17,8,7,30); 
    Windows.Borders(Phil_Windows(4),'+','|','-');
    Windows.Title(Phil_Windows(4), "Jean Ichbiah",'-');
    Phils(4).Come_To_Life(4,4,5);

    LOOP
      SELECT
        ACCEPT Report_State(Which_Phil: Table_Type;
                         State: Phil.States;
                         How_Long: Natural := 0) DO
          T := Integer(Calendar."-"(Calendar.Clock,Start_Time));
          Windows.Put_String(Phil_Windows(Which_Phil),
            "T=" & Integer'Image(T) & " ");
          CASE State IS
            WHEN Phil.Breathing =>
              Windows.Put_String(Phil_Windows(Which_Phil), "Breathing...");
              Windows.New_Line(Phil_Windows(Which_Phil));

            WHEN Phil.Thinking =>
              Windows.Put_String(Phil_Windows(Which_Phil),
                         "Thinking"
                         & Integer'Image(How_Long)
                         & " seconds.");
              Windows.New_Line(Phil_Windows(Which_Phil));

            WHEN Phil.Eating =>
              Windows.Put_String(Phil_Windows(Which_Phil),
                         "Eating"   
                         & Integer'Image(How_Long)
                         & " seconds.");
              Windows.New_Line(Phil_Windows(Which_Phil));

            WHEN Phil.Done_Eating =>
              Windows.Put_String(Phil_Windows(Which_Phil), "Yum-yum (burp)");
              Windows.New_Line(Phil_Windows(Which_Phil));

            WHEN Phil.Got_One_Stick =>
              Windows.Put_String(Phil_Windows(Which_Phil), 
                         "First chopstick"
                          & Integer'Image(How_Long));
              Windows.New_Line(Phil_Windows(Which_Phil));

            WHEN Phil.Got_Other_Stick =>
              Windows.Put_String(Phil_Windows(Which_Phil), 
                         "Second chopstick"
                          & Integer'Image(How_Long));
              Windows.New_Line(Phil_Windows(Which_Phil));

          END CASE;

         END Report_State;
        OR
          TERMINATE;
        END SELECT;

      END LOOP;

    END Head_Waiter;

END Room;



^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: Activating tasks at global scope
  1993-03-10 17:11 ` Robert I. Eachus
@ 1993-03-11  3:56   ` Scott Meyers
  1993-03-11 17:57     ` Dave Collard x7468
  0 siblings, 1 reply; 7+ messages in thread
From: Scott Meyers @ 1993-03-11  3:56 UTC (permalink / raw)


In article <EACHUS.93Mar10121115@goldfinger.mitre.org> eachus@goldfinger.mitre.org (Robert I. Eachus) writes:
|   You were doing fine, but got bitten by a very subtle feature of Ada.
| The tasks were all created and elaborated before the main program
| executed, but then the main program immediately exited.  The language
| reference manual leaves it unspecifed what happens to library tasks in
| such a situation, but most implementations now terminate them all if
| they are quiescent.  So your tasks disappeared from view before they
| could act.
| 
|    In any case try hanging your main program, either by putting in a
| delay statement or by waiting for input...the elegent final version
| should have a clean way of terminating the program, but this will do
| for testing.

I tried to follow this advice, but none of the tasks appears to run;
certainly the output statements in their initialization blocks are never
executed.  I've appended the full program below, and I'd appreciate it if
somebody could help me figure out what's wrong.  Trust me when I tell you
I've tried to solve this problem myself.  (I had quite a lovely time
determining that the behavior of the Ada/Ed compiler is dependent in part
on the name of the file containing the source, and I don't mean the file
extensions.  In particular, the compiler generates an internal error on a
whole host of file names.  Names containing numbers seem to be particularly
offensive to it...)

Thanks for your help,

Scott




with Text_IO;
use Text_IO;

package Buffer_Package is
  task Buffer is
    entry insert(item: in Integer);
    entry remove(item: out Integer);
  end Buffer;
end Buffer_Package;

package body Buffer_Package is
  task body Buffer is
    count: Integer := 0;

    begin
      loop
        select when count < 10 =>
          accept insert(item: in Integer) do
            -- insert item into the buffer
            PUT_LINE("ACCEPTING AN INSERTION");
            null;
          end insert;
          count := count + 1;

        or when count > 0 =>
          accept remove(item: out Integer) do
            -- remove an object from the buffer and assign it to item
            PUT_LINE("ACCEPTING A REMOVAL");
            null;
          end remove;
          count := count - 1;
        end select;

      end loop;
    end Buffer;
    
begin
  PUT_LINE("STARTING BUFFER_PACKAGE"); 
end Buffer_Package;

--------------------------------------------------------------------------

with Text_IO;
use Text_IO;
with Buffer_Package;
use Buffer_Package;

package Producer_Package is
  task Producer;
end Producer_Package;

package body Producer_Package is
  task body Producer is
    n: integer;
    
    begin
      loop
        -- give n an appropriate value
        PUT_LINE("INSERTING");
        Buffer.insert(n);
      end loop;
  end Producer;

begin
  PUT_LINE("STARTING PRODUCER_PACKAGE"); 
end Producer_Package;

--------------------------------------------------------------------------

with Text_IO;
use Text_IO;
with Buffer_Package;
use Buffer_Package;

package Consumer1_Package is
  task Consumer1;
end Consumer1_Package;

package body Consumer1_Package is
  task body Consumer1 is
    n: integer;
    
    begin
      loop
        PUT_LINE("REMOVING2");
        Buffer.remove(n);
        -- do something with n
      end loop;
  end Consumer1;

begin
  PUT_LINE("STARTING CONSUMER1_PACKAGE"); 
end Consumer1_Package;

--------------------------------------------------------------------------

with Text_IO;
use Text_IO;
with Buffer_Package;
use Buffer_Package;

package Consumer2_Package is
  task Consumer2;
end Consumer2_Package;

package body Consumer2_Package is
  task body Consumer2 is
    n: integer;
    
    begin
      loop
        PUT_LINE("REMOVING2");
        Buffer.remove(n);
        -- do something with n
      end loop;
  end Consumer2;

begin
  PUT_LINE("STARTING CONSUMER2_PACKAGE"); 
end Consumer2_Package;

--------------------------------------------------------------------------

with Text_IO;
use Text_IO;

procedure producer_consumer is
begin
  PUT_LINE("STARING DELAY...");
  delay 5.0;
  PUT_LINE("DONE.");
end producer_consumer;


-------------------------------------------------------------------------------
What do you say to a convicted felon in Providence?  "Hello, Mr. Mayor."



^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re: Activating tasks at global scope
  1993-03-11  3:56   ` Scott Meyers
@ 1993-03-11 17:57     ` Dave Collard x7468
  0 siblings, 0 replies; 7+ messages in thread
From: Dave Collard x7468 @ 1993-03-11 17:57 UTC (permalink / raw)


>with Text_IO;
>use Text_IO;
>package Buffer_Package is
  ...
>end Buffer_Package;

>package body Buffer_Package is
>  task body Buffer is
>    end Buffer;
>    
>begin
>  PUT_LINE("STARTING BUFFER_PACKAGE"); 
>end Buffer_Package;

>with Text_IO;
>use Text_IO;
>with Buffer_Package;
>use Buffer_Package;
>package Producer_Package is
>  task Producer;
>end Producer_Package;

>package body Producer_Package is
>  task body Producer is
>  end Producer;

>begin
>  PUT_LINE("STARTING PRODUCER_PACKAGE"); 
>end Producer_Package;

>with Text_IO;
>use Text_IO;
>with Buffer_Package;
>use Buffer_Package;
>package Consumer1_Package is
>  task Consumer1;
>end Consumer1_Package;

>package body Consumer1_Package is
>  task body Consumer1 is
>  end Consumer1;

>begin
>  PUT_LINE("STARTING CONSUMER1_PACKAGE"); 
>end Consumer1_Package;

>with Text_IO;
>use Text_IO;
>with Buffer_Package;
>use Buffer_Package;
>package Consumer2_Package is
>  task Consumer2;
>end Consumer2_Package;

>package body Consumer2_Package is
>  task body Consumer2 is
>  end Consumer2;

>begin
>  PUT_LINE("STARTING CONSUMER2_PACKAGE"); 
>end Consumer2_Package;


>with Text_IO;
>use Text_IO;

-- Perhaps you need to add a few with statements here!  When
-- you link producer_consumer, the only thing you are linking
-- with is Text_IO!  Try adding:
with Buffer_Package;
with Producer_Package;
with Consumer1_Package;
with Consumer2_Package;
>procedure producer_consumer is
>begin
>  PUT_LINE("STARING DELAY...");
>  delay 5.0;
>  PUT_LINE("DONE.");
>end producer_consumer;

--Thor
dlc@ddsdx2.jhuapl.edu
collard@capsrv.jhuapl.edu



^ permalink raw reply	[flat|nested] 7+ messages in thread

* Re:  Activating tasks at Global Scope
@ 1993-03-15 14:58 Cheryl Marquis
  0 siblings, 0 replies; 7+ messages in thread
From: Cheryl Marquis @ 1993-03-15 14:58 UTC (permalink / raw)


>The code below implements a producer-consumer system containing one
>producing task, two consuming tasks, and a bounded buffer task.  I am only
>interested in the tasking interactions, so I've omitted the actual buffer
>manipulations.  This code works fine under the Ada/ED compiler.  However, I
>would prefer to put the tasks at global scope rather than nest them inside
>the producer_consumer procedure.  I tried to do this by putting each task
>inside a package, but then I couldn't figure out how to activate the tasks
>when producer_consumer was invoked.  What I'd like is an architecture where
>the tasks are automatically started before or at the same time the the main
>subprogram is invoked.

>If I've done anything particularly gross, feel free to comment
>appropriately.  Nobody here knows Ada, so I put this together by copying
>fairly liberally from Ben-Ari's book, "Principles of Concurrent and
>Distributed Programming."

>Thanks,

>Scott

Scott as I see it you have two package options that will allow you a more
elegant start up without using delays.

They look basically alike the only difference is where the starting up of
the task is done.  Below is some code that I hope will help you.


with Text_IO;
use Text_IO;

package My_Task_Stuff is
  task Buffer is
--**** This entry provides a means of controlled task 
--     start ups.  Look at body to see how this works
    entry Start_Up;       
--****
    entry insert(item: in Integer);
    entry remove(item: out Integer);
--**** This entry provides a means of controlled task 
--     shut downs.  Look at body to see how this works
    entry Shut_Down;       
--****
  end Buffer;


  task Producer is
--**** This entry provides a means of controlled task 
--     start ups.  Look at body to see how this works
    entry Start_Up;       
--****
--**** This entry provides a means of controlled task 
--     shut downs.  Look at body to see how this works
    entry Shut_Down;       
--****


  task Consumer1;
--**** This entry provides a means of controlled task 
--     start ups.  Look at body to see how this works
    entry Start_Up;       
--****
--**** This entry provides a means of controlled task 
--     shut downs.  Look at body to see how this works
    entry Shut_Down;       
--****

  task Consumer2;
--**** This entry provides a means of controlled task 
--     start ups.  Look at body to see how this works
    entry Start_Up;       
--****
--**** This entry provides a means of controlled task 
--     shut downs.  Look at body to see how this works
    entry Shut_Down;       
--****


end My_Task_Stuff;


package body My_Task_Stuff is

  task body Buffer is
    count: Integer := 0;

    begin
--**** put Start up before loop.  Task will have to
--     wait here until the start up is called.

      accept Start_Up;
      -- any initializing can be done here also

      loop
        select when count < 10 =>
          accept insert(item: in Integer) do
            -- insert item into the buffer
            null;
          end insert;
          count := count + 1;

        or when count > 0 =>
          accept remove(item: out Integer) do
            -- remove an object from the buffer and assign it to item
            null;
          end remove;
          count := count - 1;
        or 

--**** This will give you controlled task exits.  You decide
--     when the task should end
          accept Shut_Down;
          exit;

        end select;

      end loop;
    end Buffer;

  task body Producer is
    n: integer;
    
    begin
--**** put Start up before loop.  Task will have to
--     wait here until the start up is called.

      accept Start_Up;
      -- any initializing can be done here also

      loop
--**** This will give you controlled task exits.  You decide
--     when the task should end
        select
           accept Shut_Down;
           exit;

        else
           -- give n an appropriate value
           Buffer.insert(n);

        end select;
      end loop;
  end Producer;

  task body Consumer1 is
    n: integer;
    
    begin
--**** put Start up before loop.  Task will have to
--     wait here until the start up is called.

      accept Start_Up;
      -- any initializing can be done here also

      loop

--**** This will give you controlled task exits.  You decide
--     when the task should end.
        select 
           accept Shut_Down;
           exit;

        else
           Buffer.remove(n);
           -- do something with n
        end select;
      end loop;
  end Consumer1;

  task body Consumer2 is
    n: integer;
    
    begin
--**** put Start up before loop.  Task will have to
--     wait here until the start up is called.

      accept Start_Up;
      -- any initializing can be done here also

      loop
--**** This will give you controlled task exits.  You decide
--     when the task should end
        select
           accept Shut_Down;
           exit;

        else
           Buffer.remove(n);
           -- do something with n
        end select;
      end loop;
  end Consumer2;

--**** Now here you have a choice.  You can either start these tasks
--     in the elaboration area of this package... 

begin -- My_Task_Stuff

  Producer.Start_Up;
  Consumer1.Start_Up;
  Consumer2.Start_Up;

end My_Task_Stuff;


with My_Task_Stuff;
procedure producer_consumer is

begin
  null;   -- will not terminate until all dependent
          -- tasks terminate
end producer_consumer;


--**** ... or call the Start_Ups from the main procedure
end My_Task_Stuff

with My_Task_Stuff;
procedure producer_consumer is

begin

   Producer.Start_Up;
   Consumer1.Start_Up;
   Consumer2.Start_Up;

end producer_consumer;

--**** One last thing; you can have procedure calls to your tasks
--     and hide the task inside the body instead of having a direct
--     task call specified in the Package Spec.



I hope I have helped and not confused you too badly.  If you have
any questions feel free to email me.


Cheryl R.S. Marquis
cmarquis@unode1.nswc.navy.mil

<no clever quote to put here...............YET!>




^ permalink raw reply	[flat|nested] 7+ messages in thread

end of thread, other threads:[~1993-03-15 14:58 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1993-03-10  3:32 Activating tasks at global scope Scott Meyers
1993-03-10 17:11 ` Robert I. Eachus
1993-03-11  3:56   ` Scott Meyers
1993-03-11 17:57     ` Dave Collard x7468
1993-03-11  2:51 ` Michael Feldman
1993-03-11  2:54   ` second half of portable diners Michael Feldman
  -- strict thread matches above, loose matches on Subject: below --
1993-03-15 14:58 Activating tasks at Global Scope Cheryl Marquis

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox