comp.lang.ada
 help / color / mirror / Atom feed
Search results ordered by [date|relevance]  view[summary|nested|Atom feed]
thread overview below | download mbox.gz: |
* Ada.Numerics.Big_Numbers.Big_Integer has a limit of 300 digits?
@ 2021-12-22  5:57  8% Michael Ferguson
  0 siblings, 0 replies; 200+ results
From: Michael Ferguson @ 2021-12-22  5:57 UTC (permalink / raw)


I just started using the Big_Integer library that is a part of the 202X version of ADA.

It is repeatedly described as an "arbitrary precision library" that has user defined implementation.

I was under the impression that this library would be able to infinitely calculate numbers of any length, but there is clearly a default limit of 300 digits.

Is there any way to get rid of this problem?

Here is some example code:

with Ada.Text_IO; use Ada.Text_IO;
with Ada.Real_Time; use Ada.Real_Time;
with Ada.Numerics.Big_Numbers.Big_Integers;
use Ada.Numerics.Big_Numbers.Big_Integers;
with Ada.Strings.Unbounded; use Ada.Strings.Unbounded;

procedure Test is
package Time_IO is new Fixed_IO(Duration);
start_time, end_time : Ada.Real_Time.Time;
elapsed_seconds : Ada.Real_Time.Time_Span;
solution : Unbounded_String;

rop : Big_Integer;
sum : Big_Integer := 0;

begin
start_time := Ada.Real_Time.Clock;

for i in 1..700 loop
rop := To_Big_Integer(i) ** Natural(i);
sum := sum + rop;
end loop;
solution := To_Unbounded_String(sum'Image);


end_time := Ada.Real_Time.Clock;
elapsed_seconds := end_time - start_time;
Put("Solution: " & solution'Image); New_Line; New_Line;
Put("Program completed in ");
Time_IO.Put(To_Duration(elapsed_seconds), Fore => 0, Aft => 3);
Put(" seconds");
end BigTest;

^ permalink raw reply	[relevance 8%]

* Re: renames usage
  @ 2021-01-02 17:22  5%           ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2021-01-02 17:22 UTC (permalink / raw)


"G.B." <bauhaus@notmyhomepage.invalid> writes:

> On 01.01.21 13:39, DrPi wrote:
>
>> Reading all the answers, I understand that :
>>      X : Float renames Random (Seed);
>> is equivalent to :
>>      X : constant Float := Random (Seed);
>> Right ?
>
> Also remember that limited types do not permit copying,
> whether constant or not. Renaming avoids having to move
> an object at all:

Another reason for renaming, which includes the above, would be
remembering a view conversion. The example to hand involves
Timing_Events.

The spec

   --  Support flashing an LED (for example, to indicate that a
   --  packet has been received from the controller).

   type Flasher (The_LED : not null access Crazyflie_LED)
     is tagged limited private;

   procedure Set (The_Flasher : in out Flasher);
   --  Lights the associated LED for 5 ms.

In the private part

   type Flasher (The_LED : not null access Crazyflie_LED)
     is new Ada.Real_Time.Timing_Events.Timing_Event with null record;

In the body

   protected Flasher_Handler is
      pragma Interrupt_Priority;
      procedure Turn_Off_The_LED            -- the Timing_Event_Handler
        (Event : in out ARTTE.Timing_Event);
      --  We "know" that the Event is actually a Flasher.
   end Flasher_Handler;

.. and finally

   protected body Flasher_Handler is
      procedure Turn_Off_The_LED
        (Event : in out ARTTE.Timing_Event) is
         The_Flasher : Flasher                                  -- <<<<
           renames Flasher (ARTTE.Timing_Event'Class (Event));  -- <<<<
      begin
         Set (The_Flasher.The_LED.all, False);
      end Turn_Off_The_LED;
   end Flasher_Handler;

^ permalink raw reply	[relevance 5%]

* Re: Ada.Real_Time.Time_First
  2020-12-09 14:21  4% ` Ada.Real_Time.Time_First Niklas Holsti
@ 2020-12-09 20:16  6%   ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2020-12-09 20:16 UTC (permalink / raw)


Niklas Holsti <niklas.holsti@tidorum.invalid> writes:

> On 2020-12-09 14:30, Simon Wright wrote:
>> I opened an issue[1] on Cortex GNAT RTS, saying
>>     You’d expect Ada.Real_Time.Time_First to be quite a long time
>>     before any possible value of Ada.Real_Time.Clock; but in fact the
>>     system starts with Clock equal to Time_First.
>
>
> I don't see any reason for expecting Time_First to be far in the past
> relative to program start. In fact, RM D.8(19) says "For example, [the 
> start of Time] can correspond to the time of system initialization".
>
> Contrariwise, it could be useful to know that Clock actually starts
> from Time_First, because I have often needed a "Start_Time" object
> that records the Clock at the start of the program, and it would be
> much simpler to use Time_First, if Time_First is known to equal the
> initial Clock.

OK, I'll back out that last commit!

> To indicate an invalid Last_Flight_Command_Time, I would either use a
> discriminated type wrapping a Time value that depends on a Valid 
> discriminant, as you suggested, or just have a Boolean flag, say
> Flight_Commands_Given that is initially False. I would use the 
> discriminated type only if there is more than one such variable or
> object in the program.

Yes.

> For the overflow, I suggest changing the comparison to
>
>    Now < Last_Flight_Command_Time
>          + To_Time_Span (In_Flight_Time_Threshold)
>
> assuming that Last_Flight_Command_Time is valid in the sense we are
> discussing. That will overflow only when Last_Flight_Command_Time 
> approaches Time_Last, and the program is likely to fail then anyway.

This conversation has been very valuable, particularly in the case of
other similar tests. I suspect, though, that "are we still flying?" is a
question that'll take more thinking to resolve!

>> [1] https://github.com/simonjwright/cortex-gnat-rts/issues/33

^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_First
  2020-12-09 13:16  6% ` Ada.Real_Time.Time_First Dmitry A. Kazakov
@ 2020-12-09 20:07  6%   ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2020-12-09 20:07 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

> I would use Next_Time instead of Last_Time:
>
>    Next_Flight_Command_Time : Time := Time_First;
> begin
>    loop
>       Now := Clock;
>       if Now >= Next_Flight_Command_Time then
>          Fire_All_Rockets;
>          Next_Flight_Command_Time :=
>  

Great idea; the name isn't right in my context, but the method applies
very well. (It's the time by which the next flight command has to have
been given before we decide we're not flying any more. I plead that (a)
this logic seems not to be our Earth logic, (b) it's a translation from
someone's C, (c) the original code has a comment expressing doubt)

^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_First
  2020-12-09 12:30 13% Ada.Real_Time.Time_First Simon Wright
  2020-12-09 13:16  6% ` Ada.Real_Time.Time_First Dmitry A. Kazakov
@ 2020-12-09 14:21  4% ` Niklas Holsti
  2020-12-09 20:16  6%   ` Ada.Real_Time.Time_First Simon Wright
  1 sibling, 1 reply; 200+ results
From: Niklas Holsti @ 2020-12-09 14:21 UTC (permalink / raw)


On 2020-12-09 14:30, Simon Wright wrote:
> I opened an issue[1] on Cortex GNAT RTS, saying
> 
>     You’d expect Ada.Real_Time.Time_First to be quite a long time before
>     any possible value of Ada.Real_Time.Clock; but in fact the system
>     starts with Clock equal to Time_First.


I don't see any reason for expecting Time_First to be far in the past 
relative to program start. In fact, RM D.8(19) says "For example, [the 
start of Time] can correspond to the time of system initialization".

Contrariwise, it could be useful to know that Clock actually starts from 
Time_First, because I have often needed a "Start_Time" object that 
records the Clock at the start of the program, and it would be much 
simpler to use Time_First, if Time_First is known to equal the initial 
Clock.

>     Quad_Is_Flying :=
>       Ada.Real_Time.To_Duration (Now - Last_Flight_Command_Time)
>         < In_Flight_Time_Threshold;


If Time_First, as the initial value of Last_Flight_Command_Time, would 
really be in the far past compared to Now, that computation risks 
overflowing the range of Duration, which may be as small as one day 
(86_400 seconds), RM 9.6(27).

> The workround I used was
> 
>     Quad_Is_Flying :=
>       Last_Flight_Command_Time /= Ada.Real_Time.Time_First
>         and then
>       Ada.Real_Time.To_Duration (Now - Last_Flight_Command_Time)
>         < In_Flight_Time_Threshold;
> 
> In other words, I was using Time_First as a flag to indicate that
> Last_Flight_Command_Time was invalid.


Even that can still overflow Duration, if more than one day can pass 
since the last flight command.

> What would your standard pattern for this sort of problem be?
> Esepecially considering that if I make Time_First a large negative
> number I'll get the opposite problem, e.g. predicting ahead for a very
> large interval, possibly even leading to numeric overflows.


You have two problems: your assumption about Time_First (or perhaps it's 
not an assumption, if you make your own RTS) and the possible overflow 
of Duration.

To indicate an invalid Last_Flight_Command_Time, I would either use a 
discriminated type wrapping a Time value that depends on a Valid 
discriminant, as you suggested, or just have a Boolean flag, say 
Flight_Commands_Given that is initially False. I would use the 
discriminated type only if there is more than one such variable or 
object in the program.

For the overflow, I suggest changing the comparison to

    Now < Last_Flight_Command_Time
          + To_Time_Span (In_Flight_Time_Threshold)

assuming that Last_Flight_Command_Time is valid in the sense we are 
discussing. That will overflow only when Last_Flight_Command_Time 
approaches Time_Last, and the program is likely to fail then anyway.


> [1] https://github.com/simonjwright/cortex-gnat-rts/issues/33

^ permalink raw reply	[relevance 4%]

* Re: Ada.Real_Time.Time_First
  2020-12-09 12:30 13% Ada.Real_Time.Time_First Simon Wright
@ 2020-12-09 13:16  6% ` Dmitry A. Kazakov
  2020-12-09 20:07  6%   ` Ada.Real_Time.Time_First Simon Wright
  2020-12-09 14:21  4% ` Ada.Real_Time.Time_First Niklas Holsti
  1 sibling, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2020-12-09 13:16 UTC (permalink / raw)


On 2020-12-09 13:30, Simon Wright wrote:
> I opened an issue[1] on Cortex GNAT RTS, saying
> 
>     You’d expect Ada.Real_Time.Time_First to be quite a long time before
>     any possible value of Ada.Real_Time.Clock; but in fact the system
>     starts with Clock equal to Time_First.
> 
> On the other hand,
> 
> I had written
> 
>     Last_Flight_Command_Time : Ada.Real_Time.Time
>       := Ada.Real_Time.Time_First;
> 
>     ...
>     
>     Quad_Is_Flying :=
>       Ada.Real_Time.To_Duration (Now - Last_Flight_Command_Time)
>         < In_Flight_Time_Threshold;
> 
> but Now - Last_Flight_Command_Time is going to be quite small, to start
> with, so Quad_Is_Flying is going to be True when it shouldn't be.
> 
> The workround I used was
> 
>     Quad_Is_Flying :=
>       Last_Flight_Command_Time /= Ada.Real_Time.Time_First
>         and then
>       Ada.Real_Time.To_Duration (Now - Last_Flight_Command_Time)
>         < In_Flight_Time_Threshold;
> 
> In other words, I was using Time_First as a flag to indicate that
> Last_Flight_Command_Time was invalid.
> 
> What would your standard pattern for this sort of problem be?
> Esepecially considering that if I make Time_First a large negative
> number I'll get the opposite problem, e.g. predicting ahead for a very
> large interval, possibly even leading to numeric overflows.

I would use Next_Time instead of Last_Time:

    Next_Flight_Command_Time : Time := Time_First;
begin
    loop
       Now := Clock;
       if Now >= Next_Flight_Command_Time then
          Fire_All_Rockets;
          Next_Flight_Command_Time :=
             Next_Flight_Command_Time + In_Flight_Time_Threshold;
       end if;
    end loop;
exception
    when Constraint_Error => -- the End of Times!
       Put_Line ("Thank you for you cooperation!");
       Fire_Death_Star;
       Self_Destroy;
end;

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de

^ permalink raw reply	[relevance 6%]

* Ada.Real_Time.Time_First
@ 2020-12-09 12:30 13% Simon Wright
  2020-12-09 13:16  6% ` Ada.Real_Time.Time_First Dmitry A. Kazakov
  2020-12-09 14:21  4% ` Ada.Real_Time.Time_First Niklas Holsti
  0 siblings, 2 replies; 200+ results
From: Simon Wright @ 2020-12-09 12:30 UTC (permalink / raw)


I opened an issue[1] on Cortex GNAT RTS, saying

   You’d expect Ada.Real_Time.Time_First to be quite a long time before
   any possible value of Ada.Real_Time.Clock; but in fact the system
   starts with Clock equal to Time_First.

On the other hand, 

I had written

   Last_Flight_Command_Time : Ada.Real_Time.Time
     := Ada.Real_Time.Time_First;

   ...
   
   Quad_Is_Flying :=
     Ada.Real_Time.To_Duration (Now - Last_Flight_Command_Time)
       < In_Flight_Time_Threshold;

but Now - Last_Flight_Command_Time is going to be quite small, to start
with, so Quad_Is_Flying is going to be True when it shouldn't be.

The workround I used was 

   Quad_Is_Flying :=
     Last_Flight_Command_Time /= Ada.Real_Time.Time_First
       and then
     Ada.Real_Time.To_Duration (Now - Last_Flight_Command_Time)
       < In_Flight_Time_Threshold;

In other words, I was using Time_First as a flag to indicate that
Last_Flight_Command_Time was invalid.

What would your standard pattern for this sort of problem be?
Esepecially considering that if I make Time_First a large negative
number I'll get the opposite problem, e.g. predicting ahead for a very
large interval, possibly even leading to numeric overflows.

I'm thinking of a Time type with the concept of validity, possibly built
round

   type Time (Valid : Boolean := False) is record
      case Valid is
         when True  => Value : Ada.Real_Time.Time;
         when False => null;
      end case;
   end record;

 and addition, etc with appropriate preconditions.

(not so sure about the discriminated record, might be more trouble than
it's worth)

[1] https://github.com/simonjwright/cortex-gnat-rts/issues/33

^ permalink raw reply	[relevance 13%]

* Re: GNAT vs Matlab - operation on   multidimensional complex matrices
  2020-03-23 23:16  4% GNAT vs Matlab - operation on multidimensional complex matrices darek
@ 2020-06-08 17:42  4% ` Shark8
  0 siblings, 0 replies; 200+ results
From: Shark8 @ 2020-06-08 17:42 UTC (permalink / raw)


Cleaning out my computer, I found this working-file; it might be of interesti to you -- it shows "going all-in" with Generics:
--------------------------------------------------------------
With
Ada.Real_Time,
Ada.Containers.Indefinite_Holders,
Ada.Numerics.Long_Complex_Types,
Ada.Exceptions,
Ada.Text_IO.Complex_IO;

Procedure Demo is
    package TIO renames Ada.Text_IO;
    package CTIO is new TIO.Complex_IO(Ada.Numerics.Long_Complex_Types);

    subtype mReal   is Long_Float;
    subtype Complex is Ada.Numerics.Long_Complex_Types.Complex;


    NumIteration : constant  := 1_000;
    NumChannels  : constant  := 64;
    NumRanges    : constant  := 400;
    NumAngles    : constant  := 30;


    Type Channel is range 1..NumChannels;
    Type Angle   is range 1..NumAngles;
    Type Range_T is range 1..NumRanges;

    type tCubeReal    is array (Channel, Angle, Range_T) of mReal;
    type tCubeComplex is array (Channel, Angle, Range_T) of Complex;

    Generic
        Type T is private;
        Type IndexA is (<>);
        Type IndexB is (<>);
        Type IndexC is (<>);
        Type Cubic is Array(IndexA, IndexB, indexC) of T;
        Zero : in T;
        with Function "+"(Left, Right: T) return T is <>;
    Function Summation( Input : Cubic ) return T
      with Inline;

    Function Summation( Input : Cubic ) return T is
    Begin
        Return Result : T := Zero do
            For A in IndexA loop
                For B in IndexB loop
                    For C in IndexC loop
                        Result:= Result + Input(A, B, C);
                    End loop;
                End loop;
            End loop;
        End return;
    End Summation;

    Generic
        Type Element is private;
        Type Cubic is array (Channel, Angle, Range_T) of Element;
        Zero : In Element;
        with Function "+"(Left, Right: Element) return Element is <>;
    Procedure Timing_Harness(Mtx : in Cubic;  S: out Element; Iterations : in Positive:= 1);

    Procedure Timing_Harness(Mtx : in Cubic;  S: out Element; Iterations : in Positive:= 1) is
        Function Sum is new Summation(Element, Channel, Angle, Range_T, Cubic, Zero);
        Use Ada.Real_Time;
        Start : Time renames Clock;
    Begin
        For Count in 1..Iterations Loop
            S := Sum( Mtx );
        End loop;


        METRICS:
        Declare
            Execution_Time  : Constant Time_Span:= Clock - Start;
            Execution_Image : Constant String:= Duration'Image(To_Duration(Execution_Time));
            T : Constant mReal := mReal(To_Duration(Execution_Time))/mReal(NumIteration);
        Begin
            TIO.New_Line;
            TIO.Put_Line("Computation time:" & Execution_Image );
            TIO.Put_Line("Computation time per iteration:" & mReal'Image(T));
        End METRICS;
    End Timing_Harness;


    Function Image( Input : mReal   )  return string renames mReal'Image;
    Function Image( Input : Complex )  return string is
        ('(' & mReal'Image(Input.Re) & ", " & mReal'Image(Input.Im) & ')');
    
    Generic
        Type T is private;
        Type IndexA is (<>);
        Type IndexB is (<>);
        Type IndexC is (<>);
        Type Cubic is Array(IndexA, IndexB, indexC) of T;
        Default : in T;
    Package Test_Data is
        Type Access_Cubic is not null access all Cubic;

        Access_Data : Constant Access_Cubic := new Cubic'(others => (others => (others => Default)));
        Data        : Cubic renames Access_Data.all;
    End Test_Data;

    Generic
        Type Element    is private;
        Type Cube_Array is array (Channel, Angle, Range_T) of Element;
        Default,
        Zero      : in Element;
        Test_Name : in String;
        with Function "+"(Left, Right: Element) return Element is <>;
        with Function Image( Input : Element )  return string  is <>;
    Procedure TEST;


    Procedure TEST is

        Package Test_Set is new Test_Data(
           T       => Element,
           IndexA  => Channel,
           IndexB  => Angle,
           IndexC  => Range_T,
           Cubic   => Cube_Array,
           Default => Default
          );
        
        procedure SpeedSum is new Timing_Harness(
           Element => Element,
           Cubic   => Cube_Array,
           Zero    => Zero,
           "+"     => TEST."+"
          );
        
        Cube   : Cube_Array renames Test_Set.Data;
        Result : Element;
    Begin
        TIO.Put_Line(Test_Name & " cube");
        TIO.Put_Line(Test_Name & " type size is:" & Integer'Image(Element'Size));

        SpeedSum(
           Mtx          => Cube,
           S            => Result,
           Iterations   => NumIteration
          );

        TIO.Put_Line("Sum is:" & Image(Result));
    End TEST;

Begin
    REAL_CUBE_TEST:
    Declare
        Procedure Do_Test is new Test(
           Element    => mReal,
           Cube_Array => tCubeReal,
           Default    => 1.0,
           Zero       => 0.0,
           Test_Name  => "Real"
          );
    Begin
        Do_Test;
    End REAL_CUBE_TEST;

    TIO.Put_Line( (1..20 => '-') ); -- Separator.

    COMPLEX_CUBE_TEST:
    Declare
        Procedure Do_Test is new Test(
           "+"        => Ada.Numerics.Long_Complex_Types."+",
           Element    => Complex,
           Cube_Array => tCubeComplex,
           Default    => (Re => 1.0, Im => 1.0),
           Zero       => (Re => 0.0, Im => 0.0),
           Test_Name  => "Complex"
          );
    Begin
        Do_Test;
    End COMPLEX_CUBE_TEST;



    TIO.Put_Line( (1..20 => '-') ); -- Separator.


    Ada.Text_IO.Put_Line( "Done." );
End Demo;

^ permalink raw reply	[relevance 4%]

* Re: How can one record component be local and another not?
  @ 2020-05-07 13:25  5%         ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2020-05-07 13:25 UTC (permalink / raw)


Niklas Holsti <niklas.holsti@tidorum.invalid> writes:

>> No, tasks declared in library packages could survive the main program.
>
> And the environment task, yes.

I've seen people suggest aborting the environment task as a way of
ending a program with library tasks .. I suppose the main program could
exit without terminating the environment task .. looking at ARM 10.2,
(25) says "When the environment task completes (normally or abnormally),
it waits for the termination of all such tasks, and then finalizes any
remaining objects of the partition." but (30) says "If the environment
task completes abnormally, the implementation may abort any dependent
tasks.".

Cortex GNAT RTS treats exiting the main program as the same as exiting
any other taks body, i.e. illegal under Ravenscar, but I suppose I could
include 'delay until Ada.Real_Time.Time_Last;' - might result in fewer
surprises and would be more ARM-compliant.

^ permalink raw reply	[relevance 5%]

* Re: Scheduling behaviour issue
  @ 2020-04-23 11:48  8% ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2020-04-23 11:48 UTC (permalink / raw)


I've done some tests on this with GNAT CE 2019.

Test program at the end; the commented-out lines are for checks on host
machines, irrelevant for single-cpu STM32F4 boards.  The test execution
is to be under GDB, but a breakpoint on the null; in task C (line 48),
and set up this script for that breakpoint:

   command
   silent
   print As
   print Bs
   continue
   end

On macOS with 4 CPUs, both As and Bs are updated, and the user load is
~199% (i.e. two CPUs in use).

On debian stretch under VMware (1 CPU), both As and Bs are updated.

Conclusion: the macOS host RTS doesn't respect the CPU
restriction. Can't tell about macOS, but the Linux RTS behaves in the
same way as FreeRTOS.

On STM32F4, with cortex-gnat-rts, the behaviour is as I expected (both
As and Bs updated).

On STM32F4, with ravenscar-{sfp,full}-stm32f4, the behaviour is as
D.2.3(9)[3] (only As updated).

==========================================

with Ada.Real_Time;
with System;
--  with System.Multiprocessors;

package body Priority_Issue is

   type Count is mod 2 ** 64;
   As : Count := 0;
   Bs : Count := 0;

   task A
   with
     --  CPU => 1,
     Priority => System.Default_Priority;

   task B
   with
     --  CPU => 1,
     Priority => System.Default_Priority;

   task C
   with
     --  CPU => 1,
     Priority => System.Default_Priority + 1;

   use type Ada.Real_Time.Time;

   task body A is
   begin
      delay until Ada.Real_Time.Clock + Ada.Real_Time.Milliseconds (300);
      loop
         As := As + 1;
      end loop;
   end A;

   task body B is
   begin
      delay until Ada.Real_Time.Clock + Ada.Real_Time.Milliseconds (600);
      loop
         Bs := Bs + 1;
      end loop;
   end B;

   task body C is
   begin
      loop
         delay until Ada.Real_Time.Clock + Ada.Real_Time.Seconds (1);
         null;  --  break here, print As, Bs
      end loop;
   end C;

end Priority_Issue;

^ permalink raw reply	[relevance 8%]

* GNAT vs Matlab - operation on   multidimensional complex matrices
@ 2020-03-23 23:16  4% darek
  2020-06-08 17:42  4% ` Shark8
  0 siblings, 1 reply; 200+ results
From: darek @ 2020-03-23 23:16 UTC (permalink / raw)


Hi Everyone, 
 I am working on radar signal processing algorithms that use multidimensional complex arrays. 

To my surprise, the performance of some Matlab functions is much better than compiled Ada code. 

Let's start with a simple problem of computing sum of all elements in a 3D real and complex array. 

The Ada code is as follows:

with Ada.Text_IO;
with Ada.Real_Time; use Ada.Real_Time;
with Ada.Unchecked_Deallocation;

with Ada.Numerics.Long_Complex_Types;  use Ada.Numerics.Long_Complex_Types;

with Ada.Text_IO.Complex_IO;

procedure TestSpeed is
   

   
   package TIO renames Ada.Text_IO;
   
   package CTIO is new Ada.Text_IO.Complex_IO(Ada.Numerics.Long_Complex_Types);
   
   subtype mReal is Long_Float;
   
   
   NumIteration : constant := 1_000;
   NumChannels  : constant  := 64;
   NumRanges    : constant  := 400; 
   NumAngles    : constant  := 30;
   
   type tCubeReal is array (1..NumChannels, 1..NumAngles, 1..NumRanges) of mReal;
   type tCubeRealAcc is access all tCubeReal;
   --for tCubeReal'Alignment use 8;
   
   type tCubeComplex is array (1..NumChannels, 1..NumAngles, 1..NumRanges) of Complex;
   type tCubeComplexAcc is access all tCubeComplex;
   --for tCubeComplex'Alignment use 16;
   
   RealCubeAcc : tCubeRealAcc;
   SReal       : mReal;
   
   ComplexCubeAcc : tCubeComplexAcc;
   SComplex    : Complex;

   
   procedure Free is new Ada.Unchecked_Deallocation(tCubeReal, tCubeRealAcc);
   procedure Free is new Ada.Unchecked_Deallocation(tCubeComplex, tCubeComplexAcc);
   
   --| -------------------------------------------------------------------------
   procedure SpeedSumRealCube (NumIteration : Integer; Mtx : in  tCubeReal;  S: out mReal) is
      
      Ts   : Time;
      TEx  : Time_Span; 
      t    : mReal;
   begin
      Ts := Clock;
      S := 0.0;
      for k in 1..NumIteration loop
         for m  in Mtx'Range(1) loop
            for n in   Mtx'Range(2) loop
               for p in   Mtx'Range(3) loop
                  S := S + Mtx(m, n, p);
               end loop;
            end loop;
         end loop;      
      end loop;

      TEx :=  Clock - Ts;
      TIO.New_Line;
      TIO.Put_Line("Computation time:" & Duration'Image(To_Duration(TEx)));
      t := mReal(To_Duration(TEx))/mReal(NumIteration);
      TIO.Put_Line("Computation time per iteration:" & t'Image);
   end SpeedSumRealCube;
   
   --| -------------------------------------------------------------------------
   
   procedure SpeedSumComplexCube (NumIteration : Integer; Mtx : in  tCubeComplex;  S:  out Complex) is
      
      Ts   : Time;
      TEx  : Time_Span; 
      t    : mReal;
   begin
      Ts := Clock;     
      S := 0.0  + i* 0.0; 
      for k in 1..NumIteration loop
         for m  in Mtx'Range(1) loop
            for n in    Mtx'Range(2) loop
               for p in   Mtx'Range(3) loop
                  S := S + Mtx(m, n, p);
               end loop;
            end loop;
         end loop;      
      end loop;
      TEx :=  Clock - Ts;
      TIO.New_Line;
      TIO.Put_Line("Computation time:" & Duration'Image(To_Duration(TEx)));
      t := mReal(To_Duration(TEx))/mReal(NumIteration);
      TIO.Put_Line("Computation time per iteration:" & t'Image);
   end SpeedSumComplexCube;
   
   --| -------------------------------------------------------------------------
   
begin
   TIO.Put_Line("Real cube");
   TIO.Put_Line("Real type size is:" & Integer(mReal'Size)'Image);
   RealCubeAcc := new tCubeReal;
   RealCubeAcc.all := (others =>(others =>( others => 1.0)));
   SpeedSumRealCube(NumIteration => NumIteration,
                    Mtx           => RealCubeAcc.all,
                    S            => SReal);
   
   TIO.Put_Line("Sum is:" & SReal'Image);
   
   TIO.Put_Line("Complex cube");
   TIO.Put_Line("Complex type size is:" & Integer(Complex'Size)'Image);
   ComplexCubeAcc := new tCubeComplex;
   ComplexCubeAcc.all := (others =>(others =>( others => 1.0 + i * 1.0)));
   SpeedSumComplexCube(NumIteration => NumIteration,
                       Mtx          => ComplexCubeAcc.all,
                       S            => SComplex);
   
   TIO.Put("Sum is:"); CTIO.Put(SComplex);
   Free(ComplexCubeAcc);
   Free(RealCubeAcc);   
end TestSpeed;

1. Compiled with:  gcc version 9.2.0 (tdm64-1) ( and gnat community edition 2019), with the -O2 optimisation level. 
2. CPU: AMD64 Family 23 Model 24 Stepping 1  CPU0      2300           AMD Ryzen 7 3750H with Radeon Vega Mobile Gfx
3. Win10 64bit 


The results of the program execution:

Computation time: 0.616710300
Computation time per iteration: 6.16710300000000E-04
Sum is: 7.68000000000000E+08
Complex cube
Complex type size is: 128

Computation time: 3.707091000
Computation time per iteration: 3.70709100000000E-03
Sum is:( 7.68000000000000E+08, 7.68000000000000E+08)


The executable produced by the gcc provide with the gnat community edition gave very similar results.

More interesting part - the Matlab code.

Matlab version : Matlab 2019b, 64bit

function [] = TestSpeed 

NumIterations = 1000;
NumChannels = 64;  
NumRanges  = 400; 
NumAngles = 30;

%--| real matrix 

ReMtx = ones(NumChannels, NumAngles, NumRanges);

tic
SReal =  ComputeSum(NumIterations, ReMtx);
TExR = toc;%cputime-ts;
fprintf('TExe:%f, sum real=%f\n', TExR, SReal);
%--| complex matrix
CplxMtx = complex(ReMtx, ReMtx);
%ts = cputime;
tic
SCplx = ComputeSum(NumIterations, CplxMtx);
TExC = toc; %cputime - ts;
fprintf('TExe:%f, sum complex= <%f,%f> \n', TExC, real(SCplx), imag(SCplx));
fprintf('Complex operations are %f times slower\n', TExC/TExR);
end % function


function [S] = ComputeSum(NumIterations, Mtx)
 S = 0;
 for i = 1:NumIterations   
    S = S + sum(sum(sum(Mtx)));  
 end % for  
end % function 

The results of the program execution:

TExe:0.260718, sum real=768000000.000000
TExe:0.789778, sum complex= <768000000.000000,768000000.000000> 
Complex operations are 3.029242 times slower


What is wrong with my code ? Is it the Ada compiler doing bad job here?
 
If you look at Matlab code, on average the computation that use complex  addition are ~3 times slower than for the real numbers.

In the case of Ada code, the complex operations are ~ 6 times slower that for the real numbers. 

Did I miss something somewhere ? Any ideas how I can improve the performance of the Ada program (different array layout, magic pragmas, or magic compiler switches) ?

It seems that Matlab is performing really well here ...

Any suggestions are  very welcome.

Regards,
  Darek  







^ permalink raw reply	[relevance 4%]

* Re: Gnat Problem - Freezing too soon
  2019-03-02  5:50  0%                 ` Anh Vo
@ 2019-03-02 20:19  0%                   ` russ lyttle
  0 siblings, 0 replies; 200+ results
From: russ lyttle @ 2019-03-02 20:19 UTC (permalink / raw)


On 3/2/19 12:50 AM, Anh Vo wrote:
> On Friday, March 1, 2019 at 7:56:40 PM UTC-8, russ lyttle wrote:
>> On 3/1/19 8:08 PM, Anh Vo wrote:
>>> On Friday, March 1, 2019 at 1:50:12 PM UTC-8, russ lyttle wrote:
>>>> On 3/1/19 11:54 AM, Anh Vo wrote:
>>>>> On Friday, March 1, 2019 at 6:21:26 AM UTC-8, russ lyttle wrote:
>>>>>> On 2/28/19 7:49 PM, Anh Vo wrote:
>>>>>>> On Thursday, February 28, 2019 at 2:11:11 PM UTC-8, russ lyttle wrote:
>>>>>>>> On 2/28/19 4:22 PM, Simon Wright wrote:
>>>>>>>>> russ lyttle <lyttlec@removegmail.com> writes:
>>>>>>>>>
>>>>>>>>>> Example from the bookAnalysable Real-Time Systems :
>>>>>>>>>>
>>>>>>> ---------
>>>>>>>>
>>>>>>>> Would I be submitting a bug report against an already patched version of
>>>>>>>> gnat?
>>>>>>>
>>>>>>> Again, please post sporadics.ads in its entirety. So, we can duplicate your finding or not.
>>>>>>>      
>>>>>>>
>>>>>> Thanks for responding. We found it definitely a bug in gnat and are
>>>>>> submitting a bug report.
>>>>>
>>>>> It is fine to send in a report if you are confident that it is a bug in latest GNAT. Otherwise, we would like to see the content of sporadics.ads. So, we can either confirm or not your finding.
>>>>>     
>>>>>
>>>> Here they are. These are from Analysable Real-Time Systems Progrmmed in
>>>> Ada, Chap.20, Pg. 472-473. Line 29 gives different error from line 44.
>>>>
>>>> Full code for sporadics.ads:
>>>>
>>>> with System; use System;
>>>> with Ada.Real_Time; use Ada.Real_Time;
>>>> package Sporadics is
>>>>
>>>>       type Sporadic_Invoke_Interface is Synchronized Interface;
>>>>       procedure Start (S: in out Sporadic_Invoke_Interface)
>>>>          is abstract;
>>>>       type Any_Sporadic_Invoke_Interface is access all
>>>>         Sporadic_Invoke_Interface'Class;
>>>>
>>>>       type Sporadic_Thread_Interface is Synchronized Interface;
>>>>       procedure Wait_Start (S: in out Sporadic_Thread_Interface)
>>>>          is abstract;
>>>>       type Any_Sporadic_Thread_Interface is access all
>>>>         Sporadic_Thread_Interface'Class;
>>>>
>>>>       type Sporadic_State is abstract tagged
>>>>          record
>>>> 	 Pri : Priority;
>>>> 	 Ceiling_Priority : Priority;
>>>> 	 MIT_In_Mili : Time_Span;
>>>>          end record;
>>>>       procedure Initialize_Code (S: in out Sporadic_State)
>>>>          is abstract;
>>>>       procedure Sporadic_Code (S: in out Sporadic_State)
>>>>          is abstract;
>>>>       type Any_Sporadic_State is access all Sporadic_State'Class;
>>>>
>>>>       protected type Sporadic_Agent (S: Any_Sporadic_State)
>>>>         --with Priority => S.Ceiling_Prioriy
>>>>       is
>>>>          new Sporadic_Invoke_Interface and
>>>>              Sporadic_Thread_Interface
>>>>         with
>>>>         -- for the Start operation
>>>>         overriding procedure Start;
>>>>         overriding entry Wait_Start;
>>>>       private
>>>>          Start_Open : Boolean := False;
>>>>       end Sporadic_Agent;
>>>>
>>>>       task type Sporadic (S : Any_Sporadic_State;
>>>> 		       A : Any_Sporadic_Thread_Interface)
>>>>         with Priority => S.pri
>>>>           is
>>>>
>>>>       end Sporadic;
>>>> end Sporadics;
>>>> -----------------------------------------------------------------------
>>>> Full code for sporadics.adb:
>>>> package body Sporadics is
>>>>       protected body Sporadic_Agent is
>>>>          procedure Start is
>>>>          begin
>>>> 	 Start_Open := False;
>>>>          end Start;
>>>>
>>>>          entry Wait_Start
>>>>          when Start_Open is
>>>>          begin
>>>> 	 Start_Open := False;
>>>>          end Wait_Start;
>>>>       end Sporadic_Agent;
>>>>
>>>>          task body Sporadic is
>>>>          begin
>>>> 	 S.Initialize_Code;
>>>> 	 loop
>>>> 	    A.Wait_Start;
>>>> 	    S.Sporadic_Code;
>>>> 	 end loop;
>>>>          end Sporadic;
>>>>       end Sporadics;
>>>
>>> This problem also occurred with GNAT Community 2018 on Windows.
>>>
>>> While waiting for fixes in GNAT Community 2019, the work around is changing the definition of type Any_Sporadic_State as shown below.
>>>
>>>       type Any_Sporadic_State is not null access all Sporadic_State'Class;
>>>
>> Well, that worked. I may even come to understand why. Is this gnat only?
> 
> It is standard Ada. It means that the access variable must be not null.
> 
I understand that. I meant why it solved this particular problem. As far 
as I can tell, the authors never used the "not null" in any of their 
books. Would other compilers accept the code as written, or should the 
code be considered erroneous?
As Simon pointed out replacing "with Priority => S.pri" with "pragma 
Priority(S.pri)" also works. They never used that form either.

Why would the authors prefer one form over the others?


^ permalink raw reply	[relevance 0%]

* Re: Gnat Problem - Freezing too soon
  2019-03-02  3:55  0%               ` russ lyttle
@ 2019-03-02  5:50  0%                 ` Anh Vo
  2019-03-02 20:19  0%                   ` russ lyttle
  0 siblings, 1 reply; 200+ results
From: Anh Vo @ 2019-03-02  5:50 UTC (permalink / raw)


On Friday, March 1, 2019 at 7:56:40 PM UTC-8, russ lyttle wrote:
> On 3/1/19 8:08 PM, Anh Vo wrote:
> > On Friday, March 1, 2019 at 1:50:12 PM UTC-8, russ lyttle wrote:
> >> On 3/1/19 11:54 AM, Anh Vo wrote:
> >>> On Friday, March 1, 2019 at 6:21:26 AM UTC-8, russ lyttle wrote:
> >>>> On 2/28/19 7:49 PM, Anh Vo wrote:
> >>>>> On Thursday, February 28, 2019 at 2:11:11 PM UTC-8, russ lyttle wrote:
> >>>>>> On 2/28/19 4:22 PM, Simon Wright wrote:
> >>>>>>> russ lyttle <lyttlec@removegmail.com> writes:
> >>>>>>>
> >>>>>>>> Example from the bookAnalysable Real-Time Systems :
> >>>>>>>>
> >>>>> ---------
> >>>>>>
> >>>>>> Would I be submitting a bug report against an already patched version of
> >>>>>> gnat?
> >>>>>
> >>>>> Again, please post sporadics.ads in its entirety. So, we can duplicate your finding or not.
> >>>>>     
> >>>>>
> >>>> Thanks for responding. We found it definitely a bug in gnat and are
> >>>> submitting a bug report.
> >>>
> >>> It is fine to send in a report if you are confident that it is a bug in latest GNAT. Otherwise, we would like to see the content of sporadics.ads. So, we can either confirm or not your finding.
> >>>    
> >>>
> >> Here they are. These are from Analysable Real-Time Systems Progrmmed in
> >> Ada, Chap.20, Pg. 472-473. Line 29 gives different error from line 44.
> >>
> >> Full code for sporadics.ads:
> >>
> >> with System; use System;
> >> with Ada.Real_Time; use Ada.Real_Time;
> >> package Sporadics is
> >>
> >>      type Sporadic_Invoke_Interface is Synchronized Interface;
> >>      procedure Start (S: in out Sporadic_Invoke_Interface)
> >>         is abstract;
> >>      type Any_Sporadic_Invoke_Interface is access all
> >>        Sporadic_Invoke_Interface'Class;
> >>
> >>      type Sporadic_Thread_Interface is Synchronized Interface;
> >>      procedure Wait_Start (S: in out Sporadic_Thread_Interface)
> >>         is abstract;
> >>      type Any_Sporadic_Thread_Interface is access all
> >>        Sporadic_Thread_Interface'Class;
> >>
> >>      type Sporadic_State is abstract tagged
> >>         record
> >> 	 Pri : Priority;
> >> 	 Ceiling_Priority : Priority;
> >> 	 MIT_In_Mili : Time_Span;
> >>         end record;
> >>      procedure Initialize_Code (S: in out Sporadic_State)
> >>         is abstract;
> >>      procedure Sporadic_Code (S: in out Sporadic_State)
> >>         is abstract;
> >>      type Any_Sporadic_State is access all Sporadic_State'Class;
> >>
> >>      protected type Sporadic_Agent (S: Any_Sporadic_State)
> >>        --with Priority => S.Ceiling_Prioriy
> >>      is
> >>         new Sporadic_Invoke_Interface and
> >>             Sporadic_Thread_Interface
> >>        with
> >>        -- for the Start operation
> >>        overriding procedure Start;
> >>        overriding entry Wait_Start;
> >>      private
> >>         Start_Open : Boolean := False;
> >>      end Sporadic_Agent;
> >>
> >>      task type Sporadic (S : Any_Sporadic_State;
> >> 		       A : Any_Sporadic_Thread_Interface)
> >>        with Priority => S.pri
> >>          is
> >>
> >>      end Sporadic;
> >> end Sporadics;
> >> -----------------------------------------------------------------------
> >> Full code for sporadics.adb:
> >> package body Sporadics is
> >>      protected body Sporadic_Agent is
> >>         procedure Start is
> >>         begin
> >> 	 Start_Open := False;
> >>         end Start;
> >>
> >>         entry Wait_Start
> >>         when Start_Open is
> >>         begin
> >> 	 Start_Open := False;
> >>         end Wait_Start;
> >>      end Sporadic_Agent;
> >>
> >>         task body Sporadic is
> >>         begin
> >> 	 S.Initialize_Code;
> >> 	 loop
> >> 	    A.Wait_Start;
> >> 	    S.Sporadic_Code;
> >> 	 end loop;
> >>         end Sporadic;
> >>      end Sporadics;
> > 
> > This problem also occurred with GNAT Community 2018 on Windows.
> > 
> > While waiting for fixes in GNAT Community 2019, the work around is changing the definition of type Any_Sporadic_State as shown below.
> > 
> >      type Any_Sporadic_State is not null access all Sporadic_State'Class;
> > 
> Well, that worked. I may even come to understand why. Is this gnat only?

It is standard Ada. It means that the access variable must be not null.


^ permalink raw reply	[relevance 0%]

* Re: Gnat Problem - Freezing too soon
  2019-03-02  1:08  0%             ` Anh Vo
@ 2019-03-02  3:55  0%               ` russ lyttle
  2019-03-02  5:50  0%                 ` Anh Vo
  0 siblings, 1 reply; 200+ results
From: russ lyttle @ 2019-03-02  3:55 UTC (permalink / raw)


On 3/1/19 8:08 PM, Anh Vo wrote:
> On Friday, March 1, 2019 at 1:50:12 PM UTC-8, russ lyttle wrote:
>> On 3/1/19 11:54 AM, Anh Vo wrote:
>>> On Friday, March 1, 2019 at 6:21:26 AM UTC-8, russ lyttle wrote:
>>>> On 2/28/19 7:49 PM, Anh Vo wrote:
>>>>> On Thursday, February 28, 2019 at 2:11:11 PM UTC-8, russ lyttle wrote:
>>>>>> On 2/28/19 4:22 PM, Simon Wright wrote:
>>>>>>> russ lyttle <lyttlec@removegmail.com> writes:
>>>>>>>
>>>>>>>> Example from the bookAnalysable Real-Time Systems :
>>>>>>>>
>>>>> ---------
>>>>>>
>>>>>> Would I be submitting a bug report against an already patched version of
>>>>>> gnat?
>>>>>
>>>>> Again, please post sporadics.ads in its entirety. So, we can duplicate your finding or not.
>>>>>     
>>>>>
>>>> Thanks for responding. We found it definitely a bug in gnat and are
>>>> submitting a bug report.
>>>
>>> It is fine to send in a report if you are confident that it is a bug in latest GNAT. Otherwise, we would like to see the content of sporadics.ads. So, we can either confirm or not your finding.
>>>    
>>>
>> Here they are. These are from Analysable Real-Time Systems Progrmmed in
>> Ada, Chap.20, Pg. 472-473. Line 29 gives different error from line 44.
>>
>> Full code for sporadics.ads:
>>
>> with System; use System;
>> with Ada.Real_Time; use Ada.Real_Time;
>> package Sporadics is
>>
>>      type Sporadic_Invoke_Interface is Synchronized Interface;
>>      procedure Start (S: in out Sporadic_Invoke_Interface)
>>         is abstract;
>>      type Any_Sporadic_Invoke_Interface is access all
>>        Sporadic_Invoke_Interface'Class;
>>
>>      type Sporadic_Thread_Interface is Synchronized Interface;
>>      procedure Wait_Start (S: in out Sporadic_Thread_Interface)
>>         is abstract;
>>      type Any_Sporadic_Thread_Interface is access all
>>        Sporadic_Thread_Interface'Class;
>>
>>      type Sporadic_State is abstract tagged
>>         record
>> 	 Pri : Priority;
>> 	 Ceiling_Priority : Priority;
>> 	 MIT_In_Mili : Time_Span;
>>         end record;
>>      procedure Initialize_Code (S: in out Sporadic_State)
>>         is abstract;
>>      procedure Sporadic_Code (S: in out Sporadic_State)
>>         is abstract;
>>      type Any_Sporadic_State is access all Sporadic_State'Class;
>>
>>      protected type Sporadic_Agent (S: Any_Sporadic_State)
>>        --with Priority => S.Ceiling_Prioriy
>>      is
>>         new Sporadic_Invoke_Interface and
>>             Sporadic_Thread_Interface
>>        with
>>        -- for the Start operation
>>        overriding procedure Start;
>>        overriding entry Wait_Start;
>>      private
>>         Start_Open : Boolean := False;
>>      end Sporadic_Agent;
>>
>>      task type Sporadic (S : Any_Sporadic_State;
>> 		       A : Any_Sporadic_Thread_Interface)
>>        with Priority => S.pri
>>          is
>>
>>      end Sporadic;
>> end Sporadics;
>> -----------------------------------------------------------------------
>> Full code for sporadics.adb:
>> package body Sporadics is
>>      protected body Sporadic_Agent is
>>         procedure Start is
>>         begin
>> 	 Start_Open := False;
>>         end Start;
>>
>>         entry Wait_Start
>>         when Start_Open is
>>         begin
>> 	 Start_Open := False;
>>         end Wait_Start;
>>      end Sporadic_Agent;
>>
>>         task body Sporadic is
>>         begin
>> 	 S.Initialize_Code;
>> 	 loop
>> 	    A.Wait_Start;
>> 	    S.Sporadic_Code;
>> 	 end loop;
>>         end Sporadic;
>>      end Sporadics;
> 
> This problem also occurred with GNAT Community 2018 on Windows.
> 
> While waiting for fixes in GNAT Community 2019, the work around is changing the definition of type Any_Sporadic_State as shown below.
> 
>      type Any_Sporadic_State is not null access all Sporadic_State'Class;
> 
Well, that worked. I may even come to understand why. Is this gnat only?


^ permalink raw reply	[relevance 0%]

* Re: Gnat Problem - Freezing too soon
  2019-03-01 21:50  6%           ` russ lyttle
@ 2019-03-02  1:08  0%             ` Anh Vo
  2019-03-02  3:55  0%               ` russ lyttle
  0 siblings, 1 reply; 200+ results
From: Anh Vo @ 2019-03-02  1:08 UTC (permalink / raw)


On Friday, March 1, 2019 at 1:50:12 PM UTC-8, russ lyttle wrote:
> On 3/1/19 11:54 AM, Anh Vo wrote:
> > On Friday, March 1, 2019 at 6:21:26 AM UTC-8, russ lyttle wrote:
> >> On 2/28/19 7:49 PM, Anh Vo wrote:
> >>> On Thursday, February 28, 2019 at 2:11:11 PM UTC-8, russ lyttle wrote:
> >>>> On 2/28/19 4:22 PM, Simon Wright wrote:
> >>>>> russ lyttle <lyttlec@removegmail.com> writes:
> >>>>>
> >>>>>> Example from the bookAnalysable Real-Time Systems :
> >>>>>>
> >>> ---------
> >>>>
> >>>> Would I be submitting a bug report against an already patched version of
> >>>> gnat?
> >>>
> >>> Again, please post sporadics.ads in its entirety. So, we can duplicate your finding or not.
> >>>    
> >>>
> >> Thanks for responding. We found it definitely a bug in gnat and are
> >> submitting a bug report.
> > 
> > It is fine to send in a report if you are confident that it is a bug in latest GNAT. Otherwise, we would like to see the content of sporadics.ads. So, we can either confirm or not your finding.
> >   
> > 
> Here they are. These are from Analysable Real-Time Systems Progrmmed in 
> Ada, Chap.20, Pg. 472-473. Line 29 gives different error from line 44.
> 
> Full code for sporadics.ads:
> 
> with System; use System;
> with Ada.Real_Time; use Ada.Real_Time;
> package Sporadics is
> 
>     type Sporadic_Invoke_Interface is Synchronized Interface;
>     procedure Start (S: in out Sporadic_Invoke_Interface)
>        is abstract;
>     type Any_Sporadic_Invoke_Interface is access all
>       Sporadic_Invoke_Interface'Class;
> 
>     type Sporadic_Thread_Interface is Synchronized Interface;
>     procedure Wait_Start (S: in out Sporadic_Thread_Interface)
>        is abstract;
>     type Any_Sporadic_Thread_Interface is access all
>       Sporadic_Thread_Interface'Class;
> 
>     type Sporadic_State is abstract tagged
>        record
> 	 Pri : Priority;
> 	 Ceiling_Priority : Priority;
> 	 MIT_In_Mili : Time_Span;
>        end record;
>     procedure Initialize_Code (S: in out Sporadic_State)
>        is abstract;
>     procedure Sporadic_Code (S: in out Sporadic_State)
>        is abstract;
>     type Any_Sporadic_State is access all Sporadic_State'Class;
> 
>     protected type Sporadic_Agent (S: Any_Sporadic_State)
>       --with Priority => S.Ceiling_Prioriy
>     is
>        new Sporadic_Invoke_Interface and
>            Sporadic_Thread_Interface
>       with
>       -- for the Start operation
>       overriding procedure Start;
>       overriding entry Wait_Start;
>     private
>        Start_Open : Boolean := False;
>     end Sporadic_Agent;
> 
>     task type Sporadic (S : Any_Sporadic_State;
> 		       A : Any_Sporadic_Thread_Interface)
>       with Priority => S.pri
>         is
> 
>     end Sporadic;
> end Sporadics;
> -----------------------------------------------------------------------
> Full code for sporadics.adb:
> package body Sporadics is
>     protected body Sporadic_Agent is
>        procedure Start is
>        begin
> 	 Start_Open := False;
>        end Start;
> 
>        entry Wait_Start
>        when Start_Open is
>        begin
> 	 Start_Open := False;
>        end Wait_Start;
>     end Sporadic_Agent;
> 
>        task body Sporadic is
>        begin
> 	 S.Initialize_Code;
> 	 loop
> 	    A.Wait_Start;
> 	    S.Sporadic_Code;
> 	 end loop;
>        end Sporadic;
>     end Sporadics;

This problem also occurred with GNAT Community 2018 on Windows.

While waiting for fixes in GNAT Community 2019, the work around is changing the definition of type Any_Sporadic_State as shown below.

    type Any_Sporadic_State is not null access all Sporadic_State'Class;


^ permalink raw reply	[relevance 0%]

* Re: Gnat Problem - Freezing too soon
  @ 2019-03-01 21:50  6%           ` russ lyttle
  2019-03-02  1:08  0%             ` Anh Vo
  0 siblings, 1 reply; 200+ results
From: russ lyttle @ 2019-03-01 21:50 UTC (permalink / raw)


On 3/1/19 11:54 AM, Anh Vo wrote:
> On Friday, March 1, 2019 at 6:21:26 AM UTC-8, russ lyttle wrote:
>> On 2/28/19 7:49 PM, Anh Vo wrote:
>>> On Thursday, February 28, 2019 at 2:11:11 PM UTC-8, russ lyttle wrote:
>>>> On 2/28/19 4:22 PM, Simon Wright wrote:
>>>>> russ lyttle <lyttlec@removegmail.com> writes:
>>>>>
>>>>>> Example from the bookAnalysable Real-Time Systems :
>>>>>>
>>> ---------
>>>>
>>>> Would I be submitting a bug report against an already patched version of
>>>> gnat?
>>>
>>> Again, please post sporadics.ads in its entirety. So, we can duplicate your finding or not.
>>>    
>>>
>> Thanks for responding. We found it definitely a bug in gnat and are
>> submitting a bug report.
> 
> It is fine to send in a report if you are confident that it is a bug in latest GNAT. Otherwise, we would like to see the content of sporadics.ads. So, we can either confirm or not your finding.
>   
> 
Here they are. These are from Analysable Real-Time Systems Progrmmed in 
Ada, Chap.20, Pg. 472-473. Line 29 gives different error from line 44.

Full code for sporadics.ads:

with System; use System;
with Ada.Real_Time; use Ada.Real_Time;
package Sporadics is

    type Sporadic_Invoke_Interface is Synchronized Interface;
    procedure Start (S: in out Sporadic_Invoke_Interface)
       is abstract;
    type Any_Sporadic_Invoke_Interface is access all
      Sporadic_Invoke_Interface'Class;

    type Sporadic_Thread_Interface is Synchronized Interface;
    procedure Wait_Start (S: in out Sporadic_Thread_Interface)
       is abstract;
    type Any_Sporadic_Thread_Interface is access all
      Sporadic_Thread_Interface'Class;

    type Sporadic_State is abstract tagged
       record
	 Pri : Priority;
	 Ceiling_Priority : Priority;
	 MIT_In_Mili : Time_Span;
       end record;
    procedure Initialize_Code (S: in out Sporadic_State)
       is abstract;
    procedure Sporadic_Code (S: in out Sporadic_State)
       is abstract;
    type Any_Sporadic_State is access all Sporadic_State'Class;

    protected type Sporadic_Agent (S: Any_Sporadic_State)
      --with Priority => S.Ceiling_Prioriy
    is
       new Sporadic_Invoke_Interface and
           Sporadic_Thread_Interface
      with
      -- for the Start operation
      overriding procedure Start;
      overriding entry Wait_Start;
    private
       Start_Open : Boolean := False;
    end Sporadic_Agent;

    task type Sporadic (S : Any_Sporadic_State;
		       A : Any_Sporadic_Thread_Interface)
      with Priority => S.pri
        is

    end Sporadic;
end Sporadics;
-----------------------------------------------------------------------
Full code for sporadics.adb:
package body Sporadics is
    protected body Sporadic_Agent is
       procedure Start is
       begin
	 Start_Open := False;
       end Start;

       entry Wait_Start
       when Start_Open is
       begin
	 Start_Open := False;
       end Wait_Start;
    end Sporadic_Agent;

       task body Sporadic is
       begin
	 S.Initialize_Code;
	 loop
	    A.Wait_Start;
	    S.Sporadic_Code;
	 end loop;
       end Sporadic;
    end Sporadics;

^ permalink raw reply	[relevance 6%]

* Re: Simple 4 lines hang code using Ravenscar. Its this a Gnat bug?
  2019-02-22 10:01  6% ` Niklas Holsti
@ 2019-02-22 12:48  0%   ` Daniel
  0 siblings, 0 replies; 200+ results
From: Daniel @ 2019-02-22 12:48 UTC (permalink / raw)


El viernes, 22 de febrero de 2019, 11:01:51 (UTC+1), Niklas Holsti  escribió:
> On 19-02-22 10:56 , Daniel wrote:
> >
> > Hello,
> > I found something strange using Ravenscar with Gnat. The code hangs without any explanation when i try to declare a task type...¡even if i dont use any variable of this type!!. If i quit the Ravenscar pragma it works well. This is the code:
> >
> > --MAIN PROCEDURE
> > with tmr;
> > with ada.Text_IO; use ada.Text_IO;
> > procedure main is
> > begin
> >    put_line("Let's hang..");
> > end main;
> >
> > --- TMR.ADS FILE
> > pragma Profile (Ravenscar);
> > package Tmr is
> >    task type K_Timer is
> >    end K_Timer;
> > end Tmr;
> >
> > -- TMR.ADB FILE
> > package body Tmr is
> >    task body K_Timer  is
> >    begin
> >      null;
> >    end K_Timer;
> > end Tmr;
> >
> >
> > Im using GNAT GPL 2017 for windows.
> > Thank you and best regards.
> >
> 
> In a Ravenscar program, no task should terminate, and this includes the 
> environment task. However, your "main" subprogram, which is where the 
> environment task ends up after elaboration, does terminate. Therefore no 
> Ravenscar program is expected to terminate at all!
> 
> My guess is that without the task-type declaration, the tasking part of 
> the Ravenscar run-time is omitted from the program, and the environment 
> task can terminate and this terminates the program. With the task-type 
> declaration, the Ravenscar tasking run-time is included, and termination 
> of the environment task becomes a no-no. Or at least it no longer 
> terminates the program, which therefore seems to "hang".
> 
> This is just a guess, of course.
> 
> You could try to put an eternal loop in the "main", say
> 
>     loop
>        Put_Line ("Idling...");
>        delay until Ada.Real_Time.Clock + Ada.Real_Time.Seconds (1);
>     end loop;
> 
> HTH
> 
> -- 
> Niklas Holsti
> Tidorum Ltd
> niklas holsti tidorum fi
>        .      @       .

It really make sense. Thank you.


^ permalink raw reply	[relevance 0%]

* Re: Simple 4 lines hang code using Ravenscar. Its this a Gnat bug?
  @ 2019-02-22 10:01  6% ` Niklas Holsti
  2019-02-22 12:48  0%   ` Daniel
  0 siblings, 1 reply; 200+ results
From: Niklas Holsti @ 2019-02-22 10:01 UTC (permalink / raw)


On 19-02-22 10:56 , Daniel wrote:
>
> Hello,
> I found something strange using Ravenscar with Gnat. The code hangs without any explanation when i try to declare a task type...¡even if i dont use any variable of this type!!. If i quit the Ravenscar pragma it works well. This is the code:
>
> --MAIN PROCEDURE
> with tmr;
> with ada.Text_IO; use ada.Text_IO;
> procedure main is
> begin
>    put_line("Let's hang..");
> end main;
>
> --- TMR.ADS FILE
> pragma Profile (Ravenscar);
> package Tmr is
>    task type K_Timer is
>    end K_Timer;
> end Tmr;
>
> -- TMR.ADB FILE
> package body Tmr is
>    task body K_Timer  is
>    begin
>      null;
>    end K_Timer;
> end Tmr;
>
>
> Im using GNAT GPL 2017 for windows.
> Thank you and best regards.
>

In a Ravenscar program, no task should terminate, and this includes the 
environment task. However, your "main" subprogram, which is where the 
environment task ends up after elaboration, does terminate. Therefore no 
Ravenscar program is expected to terminate at all!

My guess is that without the task-type declaration, the tasking part of 
the Ravenscar run-time is omitted from the program, and the environment 
task can terminate and this terminates the program. With the task-type 
declaration, the Ravenscar tasking run-time is included, and termination 
of the environment task becomes a no-no. Or at least it no longer 
terminates the program, which therefore seems to "hang".

This is just a guess, of course.

You could try to put an eternal loop in the "main", say

    loop
       Put_Line ("Idling...");
       delay until Ada.Real_Time.Clock + Ada.Real_Time.Seconds (1);
    end loop;

HTH

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-17 21:39  9%     ` Ada.Real_Time.Time_Last Niklas Holsti
  2017-11-18 13:06  6%       ` Ada.Real_Time.Time_Last AdaMagica
@ 2019-01-29 22:03  6%       ` Simon Wright
  1 sibling, 0 replies; 200+ results
From: Simon Wright @ 2019-01-29 22:03 UTC (permalink / raw)


On Friday, 17 November 2017 21:39:51 UTC, Niklas Holsti  wrote:

> No, the environment task becomes one of the working application tasks 
> (why waste its stack space?), so more like
> 
>     loop
>        Wait_For_Trigger_Or_Time;
>        Do_Something_Useful;
>     end loop;

Very late reply: the reason I haven’t done that is because so far I’ve been 
writing just demo applications: for real, one would at least have something 
like system health monitoring or watchdogging to do.

I’ve discovered that elaboration can use surprising amounts of stack, 
especially if there are containers involved.


^ permalink raw reply	[relevance 6%]

* Re: Profiling Ada applications using gprof
  @ 2018-12-04 19:41  6% ` Dennis Lee Bieber
  0 siblings, 0 replies; 200+ results
From: Dennis Lee Bieber @ 2018-12-04 19:41 UTC (permalink / raw)


On Tue, 4 Dec 2018 07:04:40 -0800 (PST), joakimds@kth.se declaimed the
following:

>
>As one can see there is nothing that indicates that something takes around 10 seconds to execute. Is it really impossible to detect the long running entry call A.Stop?
>

	Hypothesis: your profiling is showing CPU time consumed by the program,
not wall-clock time -- but your 10 second DELAY statement could be a
blocking call depending upon how the run-time interface was created (ie:
block waiting for some timer to expire) and consumes no CPU while blocked.
(And your 0.17s could be the time the system takes to load the executable.)

	Change the DELAY to something that actually consumes CPU time and see
what happens.

		Start_T := ada.real_time.clock;
		while (Start_T + 10.0) > ada.real_time.clock loop
			null;
		end loop;


-- 
	Wulfraed                 Dennis Lee Bieber         AF6VN
	wlfraed@ix.netcom.com    HTTP://wlfraed.home.netcom.com/ 

^ permalink raw reply	[relevance 6%]

* Re: SI units updated
  2018-11-05  8:47  5%   ` reinert
@ 2018-11-15 11:46  5%     ` AdaMagica
  0 siblings, 0 replies; 200+ results
From: AdaMagica @ 2018-11-15 11:46 UTC (permalink / raw)


Am Montag, 5. November 2018 09:47:02 UTC+1 schrieb reinert:
> Great attempt! I have been looking after something like this. But you did not consider enumeration variables instead of strings?

You mean enum literals? They're case-insensitive. Note the difference in mS and Ms!

> 
> But will you modify the "Time" issue? "Time" in Ada is "Calendar time" which is thought about as duration since a magic "year 0" on Earth (Middle East?)?  "Time" in physics is normally thought about as duration before/after a reference "event"/point in time/space - or "duration between two events/points in time/space. 

I cannot see what an item with dimension time in some physical equation has to do with Ada.Real_Time.


^ permalink raw reply	[relevance 5%]

* Re: SI units updated
  @ 2018-11-05  8:47  5%   ` reinert
  2018-11-15 11:46  5%     ` AdaMagica
  0 siblings, 1 reply; 200+ results
From: reinert @ 2018-11-05  8:47 UTC (permalink / raw)


Great attempt! I have been looking after something like this. But you did not consider enumeration variables instead of strings?

But will you modify the "Time" issue? "Time" in Ada is "Calendar time" which is thought about as duration since a magic "year 0" on Earth (Middle East?)?  "Time" in physics is normally thought about as duration before/after a reference "event"/point in time/space - or "duration between two events/points in time/space. 

I have though not so far investigated you use of "Ada.Real_Time".

reinert

mandag 1. oktober 2018 21.24.40 UTC+2 skrev Shark8 følgende:
> On Saturday, September 29, 2018 at 2:51:57 PM UTC-6, AdaMagica wrote:
> > This is a package for computing with physical dimensions. Units are given in strings (case sensitive). All symbols and prefixed as defined in SI may be used.
> > 
> > Unit syntax improved: 1.0*"W/(m*K)", the former "W/m/K" (very ugly) is now illegal.
> > 
> > http://www.christ-usch-grein.homepage.t-online.de/Ada/Dimension/SI.html
> > 
> > Enjoy - Christoph
> 
> Thank you for posting this; I was just assessing the possibility of having to use SI units in my new job, and this looks like it would save a lot of time and effort reinventing the wheel.


^ permalink raw reply	[relevance 5%]

* Cortex GNAT RTS: BBC micro:bit tick rate
@ 2018-07-24 11:44  5% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2018-07-24 11:44 UTC (permalink / raw)


As announced recently, Cortex GNAT RTS now supports the BBC micro:bit.

Because the nRF51822 MCU doesn't support SysTick, it has to be simulated
using the RTC peripheral, which runs at 32,768 Hz.

At first I thought it wouldn't generate interrupts faster than 100 Hz
anyway, but this turns out to be because I was disabling/enabling
interrupts every time. It will go much faster than that (I don't know
how much time is left for the CPU to do anything else, though).

So, the question: is there any problem with having Ada.Real_Time.Tick be
1/1024 second? (with GNAT, it's usually/always a decimal fraction).


^ permalink raw reply	[relevance 5%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 22:20  6%               ` Ada.Real_Time.Time_Last Robert A Duff
  2017-11-19 10:50  4%                 ` Ada.Real_Time.Time_Last Niklas Holsti
@ 2017-11-20  5:57  6%                 ` J-P. Rosen
  1 sibling, 0 replies; 200+ results
From: J-P. Rosen @ 2017-11-20  5:57 UTC (permalink / raw)


Le 18/11/2017 à 23:20, Robert A Duff a écrit :
> If Interrupt_Id is an enumeration type (not true for GNAT), you don't
> want to hide the names of the interrupts from clients.  If there's a
> Gizmo_Device_Interrupt, then clients want to attach handlers to that by
> name.
Actually, they are not hidden:
Put (T'Image (T'First));

Or if you want to call a procedure P with the second value of T:
P (T'val (1))

-- 
J-P. Rosen
Adalog
2 rue du Docteur Lombard, 92441 Issy-les-Moulineaux CEDEX
Tel: +33 1 45 29 21 52, Fax: +33 1 45 29 25 00
http://www.adalog.fr


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 22:20  6%               ` Ada.Real_Time.Time_Last Robert A Duff
@ 2017-11-19 10:50  4%                 ` Niklas Holsti
  2017-11-20  5:57  6%                 ` Ada.Real_Time.Time_Last J-P. Rosen
  1 sibling, 0 replies; 200+ results
From: Niklas Holsti @ 2017-11-19 10:50 UTC (permalink / raw)


On 17-11-19 00:20 , Robert A Duff wrote:
> Niklas Holsti <niklas.holsti@tidorum.invalid> writes:
>
>> For various reasons, the developers of the Ada language have seen fit to
>> define in the RM some standard, predefined types for which they have
>> wanted to state the nature of the type, but not its full definition. For
>> example, we have, in package System,
>>
>>    subtype Any_Priority is Integer range implementation-defined;
>
> Yes, and Any_Priority'Last is a static expression.

Hm, I found no explicit statement on that in the RM. I assume it follows 
from the pragma Pure in package System, yes? On the other hand, there is 
an explicit requirement that Default_Bit_Order be static (RM 13.7(35/2)).

> Would it be static in your proposal?

I guess so; in this example, the proposal would only move the actual 
range expression to the private part, so I assume pragma Pure would have 
the same effect (enforce staticness) in the full declaration of the 
semi-private type.

> Programmers need to know the priority range in order to
> write pragmas Priority.  So in what sense is this
> "private" information?

Do you write, unportably:

    pragma Priority (42);

or do you write, as I do:

    Background_Prio : constant Priority := Priority'First;
    One_Herz_Prio   : constant Priority := Background_Prio + 1;
    etc.

and then write

    pragma Priority (Background_Prio);
    etc.?

>> This would enable all discrete-type operations on the Item type, but
>> would hide (keep private) what sort of discrete type it is, as well as
>> the names of the enumeration literals, if it is implemented as an
>> enumerated type. The RM defines just such a type in Ada.Interrupts:
>>
>>    type Interrupt_Id is implementation-defined;
>>
>> with the explanation (RM C.3.2(13)) "The Interrupt_Id type is an
>> implementation-defined discrete type used to identify interrupts."
>
> If Interrupt_Id is an enumeration type (not true for GNAT), you don't
> want to hide the names of the interrupts from clients.  If there's a
> Gizmo_Device_Interrupt, then clients want to attach handlers to that  by
 > name.

The RM defines the package Ada.Interrupts.Names for that (RM C.3.2(26)); 
it contains a set of definitions of constant Interrupt_Id objects, where 
both the names and values of those objects are "implementation-defined". 
This proposal would not change that, but these constants would probably 
become deferred constants, with their actual values in a private part.

For sure, this proposal is not going to remove all 
"implementation-defined" text from the RM. In my mind, that is not the 
goal of the proposal; the goal is to give packages more control over the 
amount of information they publish about their private types. For 
example, I have had cases where I wanted to publish the ability to use a 
private type as an array index type, without revealing much more about 
the type. The RM is only a good source of examples of types which 
should, perhaps, be semi-private in this sense.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .

^ permalink raw reply	[relevance 4%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 15:24  4%             ` Ada.Real_Time.Time_Last Niklas Holsti
  2017-11-18 16:01  6%               ` Ada.Real_Time.Time_Last Dmitry A. Kazakov
@ 2017-11-18 22:20  6%               ` Robert A Duff
  2017-11-19 10:50  4%                 ` Ada.Real_Time.Time_Last Niklas Holsti
  2017-11-20  5:57  6%                 ` Ada.Real_Time.Time_Last J-P. Rosen
  1 sibling, 2 replies; 200+ results
From: Robert A Duff @ 2017-11-18 22:20 UTC (permalink / raw)


Niklas Holsti <niklas.holsti@tidorum.invalid> writes:

> For various reasons, the developers of the Ada language have seen fit to
> define in the RM some standard, predefined types for which they have
> wanted to state the nature of the type, but not its full definition. For
> example, we have, in package System,
>
>    subtype Any_Priority is Integer range implementation-defined;

Yes, and Any_Priority'Last is a static expression.
Would it be static in your proposal?

Programmers need to know the priority range in order to
write pragmas Priority.  So in what sense is this
"private" information?

> This would enable all discrete-type operations on the Item type, but
> would hide (keep private) what sort of discrete type it is, as well as
> the names of the enumeration literals, if it is implemented as an
> enumerated type. The RM defines just such a type in Ada.Interrupts:
>
>    type Interrupt_Id is implementation-defined;
>
> with the explanation (RM C.3.2(13)) "The Interrupt_Id type is an
> implementation-defined discrete type used to identify interrupts."

If Interrupt_Id is an enumeration type (not true for GNAT), you don't
want to hide the names of the interrupts from clients.  If there's a
Gizmo_Device_Interrupt, then clients want to attach handlers to that by
name.

- Bob

^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 16:01  6%               ` Ada.Real_Time.Time_Last Dmitry A. Kazakov
@ 2017-11-18 17:31  6%                 ` Niklas Holsti
  0 siblings, 0 replies; 200+ results
From: Niklas Holsti @ 2017-11-18 17:31 UTC (permalink / raw)


On 17-11-18 18:01 , Dmitry A. Kazakov wrote:
> On 2017-11-18 16:24, Niklas Holsti wrote:
>
>> Making Count'First and Count'Last available is part of the goal of the
>> extension, but the point is that the *expressions* that define their
>> values would still be *private*, which means that the user of the type
>> cannot (or is not meant to) depend on those expressions. The user can
>> access the end result ('First, 'Last) but is not meant to depend on
>> any other properties of those expressions.
>
> The proposal should also encompass other cases where information hiding
> principle gets violated, e.g.:
>
>    procedure Foo (I : Integer := 20);
>
> If I don't want to expose the default or when the parameter is a private
> type, I should be able to provide a private value, just like in your case:
>
>    type Count is range 0..<private-value>;
>
> Same applies to the defaults of record type members, BTW.

Those privacy needs can already be handled by defining the relevant 
values as deferred constants (perhaps modulo some freezing-point 
concerns). Of course this method means that the private constant must be 
given a name; that name may or may not be useful, depending on the case.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 15:24  4%             ` Ada.Real_Time.Time_Last Niklas Holsti
@ 2017-11-18 16:01  6%               ` Dmitry A. Kazakov
  2017-11-18 17:31  6%                 ` Ada.Real_Time.Time_Last Niklas Holsti
  2017-11-18 22:20  6%               ` Ada.Real_Time.Time_Last Robert A Duff
  1 sibling, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2017-11-18 16:01 UTC (permalink / raw)


On 2017-11-18 16:24, Niklas Holsti wrote:

> Making Count'First and Count'Last available is part of the goal of the 
> extension, but the point is that the *expressions* that define their 
> values would still be *private*, which means that the user of the type 
> cannot (or is not meant to) depend on those expressions. The user can 
> access the end result ('First, 'Last) but is not meant to depend on any 
> other properties of those expressions.

The proposal should also encompass other cases where information hiding 
principle gets violated, e.g.:

    procedure Foo (I : Integer := 20);

If I don't want to expose the default or when the parameter is a private 
type, I should be able to provide a private value, just like in your case:

    type Count is range 0..<private-value>;

Same applies to the defaults of record type members, BTW.
  --
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 14:15  6%           ` Ada.Real_Time.Time_Last Jeffrey R. Carter
@ 2017-11-18 15:24  4%             ` Niklas Holsti
  2017-11-18 16:01  6%               ` Ada.Real_Time.Time_Last Dmitry A. Kazakov
  2017-11-18 22:20  6%               ` Ada.Real_Time.Time_Last Robert A Duff
  0 siblings, 2 replies; 200+ results
From: Niklas Holsti @ 2017-11-18 15:24 UTC (permalink / raw)


On 17-11-18 16:15 , Jeffrey R. Carter wrote:
> On 11/18/2017 02:18 PM, Niklas Holsti wrote:
>>>>
>>>>     type Count is private range <>;
>>
>> This proposal is meant to remove this problem, by letting the
>> programmer provide more information about the private type, in the
>> same way as information can now be provided about generic formal
>> types, to equip those types with predefined operators that can be used
>> in the generic.
>
> If by that you mean that all the operations available for a generic formal
>
>    type Count is range <>;
>
> are also available for this private type, then Count'First and
> Count'Last are available, and there's nothing private about the type at
> all. I can't see that this buys anything.

Making Count'First and Count'Last available is part of the goal of the 
extension, but the point is that the *expressions* that define their 
values would still be *private*, which means that the user of the type 
cannot (or is not meant to) depend on those expressions. The user can 
access the end result ('First, 'Last) but is not meant to depend on any 
other properties of those expressions.

For various reasons, the developers of the Ada language have seen fit to 
define in the RM some standard, predefined types for which they have 
wanted to state the nature of the type, but not its full definition. For 
example, we have, in package System,

    subtype Any_Priority is Integer range implementation-defined;

The RM could have said,

    type Priority is private;

but then the RM could not have easily expressed the fact that 
Any_Priority is divided into two sub-ranges, Priority and 
Interrupt_Priority, and the RM would have had to provide several 
operations on type Priority, for example relational operators, which are 
now implicitly provided by the parent type Integer.

The purpose of the proposal is to replace the "implementation-defined" 
in such definitions with some formal, legal expression that has the same 
effect. This would make it possible for SW developers to mark such 
"implementation-defined" things as private, while still keeping their 
code in legal Ada rather than semi-formal RM text.

Perhaps the difference is clearer in the case of a private discrete 
type, which could be written (aping the generic formal discrete type 
syntax) as:

    type Item is private (<>);   -- Not current Ada!

This would enable all discrete-type operations on the Item type, but 
would hide (keep private) what sort of discrete type it is, as well as 
the names of the enumeration literals, if it is implemented as an 
enumerated type. The RM defines just such a type in Ada.Interrupts:

    type Interrupt_Id is implementation-defined;

with the explanation (RM C.3.2(13)) "The Interrupt_Id type is an 
implementation-defined discrete type used to identify interrupts."

I agree that this proposal does not provide major benefits, but on the 
other hand it seems to me that it does not require a whole lot of new 
compiler mechanisms -- the information available about such 
"semi-private" types would be the same as the information available 
about generic formal types.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .


^ permalink raw reply	[relevance 4%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 13:18  6%         ` Ada.Real_Time.Time_Last Niklas Holsti
  2017-11-18 14:00  6%           ` Ada.Real_Time.Time_Last AdaMagica
@ 2017-11-18 14:15  6%           ` Jeffrey R. Carter
  2017-11-18 15:24  4%             ` Ada.Real_Time.Time_Last Niklas Holsti
  1 sibling, 1 reply; 200+ results
From: Jeffrey R. Carter @ 2017-11-18 14:15 UTC (permalink / raw)


On 11/18/2017 02:18 PM, Niklas Holsti wrote:
>>>
>>>     type Count is private range <>;
> 
> This proposal is meant to remove this problem, by letting the 
> programmer provide more information about the private type, in the same way as 
> information can now be provided about generic formal types, to equip those types 
> with predefined operators that can be used in the generic.

If by that you mean that all the operations available for a generic formal

    type Count is range <>;

are also available for this private type, then Count'First and Count'Last are 
available, and there's nothing private about the type at all. I can't see that 
this buys anything.

-- 
Jeff Carter
"I don't know why I ever come in here. The
flies get the best of everything."
Never Give a Sucker an Even Break
102


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 13:18  6%         ` Ada.Real_Time.Time_Last Niklas Holsti
@ 2017-11-18 14:00  6%           ` AdaMagica
  2017-11-18 14:15  6%           ` Ada.Real_Time.Time_Last Jeffrey R. Carter
  1 sibling, 0 replies; 200+ results
From: AdaMagica @ 2017-11-18 14:00 UTC (permalink / raw)


Am Samstag, 18. November 2017 14:18:44 UTC+1 schrieb Niklas Holsti:
> On 17-11-18 15:06 , AdaMagica wrote:
> > Am Freitag, 17. November 2017 22:39:51 UTC+1 schrieb Niklas Holsti:
> >
> >> Long ago, I suggested (on c.l.a) an Ada extension by which a package
> >> could declare private types using the same classes of types that can be
> >> used for generic formal types. That would IMO not only be useful for
> >> programmers, it could formalise some of the informal text in the Ada RM.
> >> For example, RM A.4.8 defines the type Ada.Direct_IO.Count as
> >>
> >>     type Count is range 0 .. implementation defined;
> >>
> >> With the suggested extension, this could be written in legal (extended)
> >> Ada as
> >>
> >>     type Count is private range <>;
> >>
> >> That form still does not show that Count'First = 0, but with a little
> >> further extension one could perhaps leave only the upper bound
> >> unspecified, as in:
> >>
> >>     type Count is private range 0 .. <>;
> >>
> >> Perhaps it is time for me to revive this proposal...
> >>
> > Problem with this is that private types have no predefined operators.
> 
> That is a problem with private types in *current* Ada, where a private 
> type is fully "opaque". This proposal is meant to remove this problem, 
> by letting the programmer provide more information about the private 
> type, in the same way as information can now be provided about generic 
> formal types, to equip those types with predefined operators that can be 
> used in the generic.

Yes - but what do we gain with this new syntax? Is it worth the effort? Which problem does it solve (to rephrase Randy)?


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-18 13:06  6%       ` Ada.Real_Time.Time_Last AdaMagica
@ 2017-11-18 13:18  6%         ` Niklas Holsti
  2017-11-18 14:00  6%           ` Ada.Real_Time.Time_Last AdaMagica
  2017-11-18 14:15  6%           ` Ada.Real_Time.Time_Last Jeffrey R. Carter
  0 siblings, 2 replies; 200+ results
From: Niklas Holsti @ 2017-11-18 13:18 UTC (permalink / raw)


On 17-11-18 15:06 , AdaMagica wrote:
> Am Freitag, 17. November 2017 22:39:51 UTC+1 schrieb Niklas Holsti:
>
>> Long ago, I suggested (on c.l.a) an Ada extension by which a package
>> could declare private types using the same classes of types that can be
>> used for generic formal types. That would IMO not only be useful for
>> programmers, it could formalise some of the informal text in the Ada RM.
>> For example, RM A.4.8 defines the type Ada.Direct_IO.Count as
>>
>>     type Count is range 0 .. implementation defined;
>>
>> With the suggested extension, this could be written in legal (extended)
>> Ada as
>>
>>     type Count is private range <>;
>>
>> That form still does not show that Count'First = 0, but with a little
>> further extension one could perhaps leave only the upper bound
>> unspecified, as in:
>>
>>     type Count is private range 0 .. <>;
>>
>> Perhaps it is time for me to revive this proposal...
>>
> Problem with this is that private types have no predefined operators.

That is a problem with private types in *current* Ada, where a private 
type is fully "opaque". This proposal is meant to remove this problem, 
by letting the programmer provide more information about the private 
type, in the same way as information can now be provided about generic 
formal types, to equip those types with predefined operators that can be 
used in the generic.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-17 21:39  9%     ` Ada.Real_Time.Time_Last Niklas Holsti
@ 2017-11-18 13:06  6%       ` AdaMagica
  2017-11-18 13:18  6%         ` Ada.Real_Time.Time_Last Niklas Holsti
  2019-01-29 22:03  6%       ` Ada.Real_Time.Time_Last Simon Wright
  1 sibling, 1 reply; 200+ results
From: AdaMagica @ 2017-11-18 13:06 UTC (permalink / raw)


Am Freitag, 17. November 2017 22:39:51 UTC+1 schrieb Niklas Holsti:

> Long ago, I suggested (on c.l.a) an Ada extension by which a package 
> could declare private types using the same classes of types that can be 
> used for generic formal types. That would IMO not only be useful for 
> programmers, it could formalise some of the informal text in the Ada RM. 
> For example, RM A.4.8 defines the type Ada.Direct_IO.Count as
> 
>     type Count is range 0 .. implementation defined;
> 
> With the suggested extension, this could be written in legal (extended) 
> Ada as
> 
>     type Count is private range <>;
> 
> That form still does not show that Count'First = 0, but with a little 
> further extension one could perhaps leave only the upper bound 
> unspecified, as in:
> 
>     type Count is private range 0 .. <>;
> 
> Perhaps it is time for me to revive this proposal...
> 
Problem with this is that private types have no predefined operators.

^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-17  9:20  6%   ` Ada.Real_Time.Time_Last Simon Wright
@ 2017-11-17 21:39  9%     ` Niklas Holsti
  2017-11-18 13:06  6%       ` Ada.Real_Time.Time_Last AdaMagica
  2019-01-29 22:03  6%       ` Ada.Real_Time.Time_Last Simon Wright
  0 siblings, 2 replies; 200+ results
From: Niklas Holsti @ 2017-11-17 21:39 UTC (permalink / raw)


On 17-11-17 11:20 , Simon Wright wrote:
> Niklas Holsti <niklas.holsti@tidorum.invalid> writes:
>
>> On 17-11-15 16:28 , Simon Wright wrote:
>>> The only use case I can see for this is to allow us to write
>>>
>>>    delay until Ada.Real_Time.Time_Last;
>>>
>>> at the end of our (Ravenscar) main program.

    [snip]

>> (By the way, my Ravenscar programs always end in an eternal loop,
>> never in a delay until Time_Last.)
>
> Like
>
>    loop
>       null;
>    end loop;
>
> ?

No, the environment task becomes one of the working application tasks 
(why waste its stack space?), so more like

    loop
       Wait_For_Trigger_Or_Time;
       Do_Something_Useful;
    end loop;

> I'd have thought this would prevent the RTS from putting the processor
> to sleep, thus wasting energy.

In the only project I've done where the customer asked for sleep mode, 
and we implemented it (that was in C, not Ada) the customer found, 
during their system tests, that periodically entering and leaving sleep 
mode caused supply-voltage transients that coupled into the analog parts 
of the board and perturbed the instrument's ADC. So the SW was changed 
to use an idle loop instead of sleeping. YMMV.

>> (By the further way, it is a pity that Ada does not let Ada.Real_Time
>> provide the attribute functions Time'Min and Time'Max.)
>
> I suppose there'd have to be a way of indicating that a private type was
> scalar.

Long ago, I suggested (on c.l.a) an Ada extension by which a package 
could declare private types using the same classes of types that can be 
used for generic formal types. That would IMO not only be useful for 
programmers, it could formalise some of the informal text in the Ada RM. 
For example, RM A.4.8 defines the type Ada.Direct_IO.Count as

    type Count is range 0 .. implementation defined;

With the suggested extension, this could be written in legal (extended) 
Ada as

    type Count is private range <>;

That form still does not show that Count'First = 0, but with a little 
further extension one could perhaps leave only the upper bound 
unspecified, as in:

    type Count is private range 0 .. <>;

Perhaps it is time for me to revive this proposal...

However, in the case of Ada.Real_Time.Time, it may be too much to 
require that this type should be a scalar one, as it may need a 
combination of range and precision that exceeds that of the largest 
machine scalar.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .

^ permalink raw reply	[relevance 9%]

* Re: Ada.Real_Time.Time_Last
  2017-11-15 20:03 12% ` Ada.Real_Time.Time_Last Niklas Holsti
@ 2017-11-17  9:20  6%   ` Simon Wright
  2017-11-17 21:39  9%     ` Ada.Real_Time.Time_Last Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2017-11-17  9:20 UTC (permalink / raw)


Niklas Holsti <niklas.holsti@tidorum.invalid> writes:

> On 17-11-15 16:28 , Simon Wright wrote:
>> The only use case I can see for this is to allow us to write
>>
>>    delay until Ada.Real_Time.Time_Last;
>>
>> at the end of our (Ravenscar) main program. Any other offers?
>
> Suppose your program has to consider, say, three possible future
> events, at the future times A, B, C : Ada.Real_Time.Time, and must
> delay until the first of those events happens, so you compute a
> variable Next_Event : Ada.Real_Time.Time as the minimum of A, B, and
> C, and then do "delay until Next_Time".
>
> However, if some or all of the events A, B, C might never happen, the
> value Time_Last is a useful placeholder to indicate "this event will
> never happen", because Time_Last is a "neutral element" for the
> operation "minimum of two Time values": minimum (X, Time_Last) = X for
> any Time X.
>
> Many algorithms working with ordered types need a minimal and a
> maximal value of the type, for such uses.

I found that I'd used Time_First to act as a flag (in my implementation
of Timing_Events). Logically I suppose it should be Time_Last.

> (By the way, my Ravenscar programs always end in an eternal loop,
> never in a delay until Time_Last.)

Like

   loop
      null;
   end loop;

? I'd have thought this would prevent the RTS from putting the processor
to sleep, thus wasting energy.

I used to write

   loop
      delay until Clock + Seconds (2);
   end loop;

(which also wastes a little energy) before realizing that (since Time
isn't to be relied on after Time_Last) I might as well delay until
Time_Last.

> (By the further way, it is a pity that Ada does not let Ada.Real_Time
> provide the attribute functions Time'Min and Time'Max.)

I suppose there'd have to be a way of indicating that a private type was
scalar.


^ permalink raw reply	[relevance 6%]

* Re: Ada.Real_Time.Time_Last
  2017-11-15 14:28 12% Ada.Real_Time.Time_Last Simon Wright
@ 2017-11-15 20:03 12% ` Niklas Holsti
  2017-11-17  9:20  6%   ` Ada.Real_Time.Time_Last Simon Wright
  0 siblings, 1 reply; 200+ results
From: Niklas Holsti @ 2017-11-15 20:03 UTC (permalink / raw)


On 17-11-15 16:28 , Simon Wright wrote:
> The only use case I can see for this is to allow us to write
>
>    delay until Ada.Real_Time.Time_Last;
>
> at the end of our (Ravenscar) main program. Any other offers?

Suppose your program has to consider, say, three possible future events, 
at the future times A, B, C : Ada.Real_Time.Time, and must delay until 
the first of those events happens, so you compute a variable Next_Event 
: Ada.Real_Time.Time as the minimum of A, B, and C, and then do "delay 
until Next_Time".

However, if some or all of the events A, B, C might never happen, the 
value Time_Last is a useful placeholder to indicate "this event will 
never happen", because Time_Last is a "neutral element" for the 
operation "minimum of two Time values": minimum (X, Time_Last) = X for 
any Time X.

Many algorithms working with ordered types need a minimal and a maximal 
value of the type, for such uses.

(By the way, my Ravenscar programs always end in an eternal loop, never 
in a delay until Time_Last.)

(By the further way, it is a pity that Ada does not let Ada.Real_Time 
provide the attribute functions Time'Min and Time'Max.)

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .

^ permalink raw reply	[relevance 12%]

* Ada.Real_Time.Time_Last
@ 2017-11-15 14:28 12% Simon Wright
  2017-11-15 20:03 12% ` Ada.Real_Time.Time_Last Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2017-11-15 14:28 UTC (permalink / raw)


The only use case I can see for this is to allow us to write

   delay until Ada.Real_Time.Time_Last;

at the end of our (Ravenscar) main program. Any other offers?


^ permalink raw reply	[relevance 12%]

* Re: About protected objects: entries with barriers depending on external data = bad practice ?
  @ 2017-11-12 10:02  7% ` Jeffrey R. Carter
  0 siblings, 0 replies; 200+ results
From: Jeffrey R. Carter @ 2017-11-12 10:02 UTC (permalink / raw)


On 11/12/2017 06:23 AM, reinert wrote:
> 
> Assume a protected entry with a barrier depending on external data - and it is waiting for its barrier to become true. It must be laborious to check the barrier depending on something "far-far away"? How is this checking done in practice? The entry waits for other entries, procedures or functions and when they arrive, it may start before them? Or something more efficient?
> 
> Letting barriers depend on external data = asking for trouble?

Barriers are evaluated when the PO's state changes; that is, as others have 
said, when a procedure or entry of the same PO has executed. So having a barrier 
that depends on external data requires some way of notifying the PO that the 
external data have changed. Typically this involves polling:

External : Boolean := False;
pragma Atomic (External); -- or Volatile

protected PO is
    procedure Evaluate_Barrier; -- Causes Wait's barrier to be evaluated
    entry Wait; -- Blocks caller until External becomes True
end PO;

protected body PO is
    procedure Evaluate_Barrier is null;

    entry Wait when External is
       -- Nothing to see here, folks
    begin -- Wait
       External := False;
    end Wait;
end PO;

task Poller;

task body Poller is
    Interval : constant Ada.Real_Time.Time_Span := ...;

    Next : Ada.Real_Time.Time := Ada.Real_Time.Clock + Interval;
begin -- Poller
    Forever : loop
       delay until Next;

       Next := Next + Interval;
       PO.Evaluate_Barrier;
    end loop Forever;
end Poller;

Of course, there are lots of opportunities for error here, so it should be 
avoided if possible.

-- 
Jeff Carter
"Ah, go away or I'll kill ya."
Never Give a Sucker an Even Break
100


^ permalink raw reply	[relevance 7%]

* Re: Community Input for the Maintenance and Revision of the Ada Programming Language
  @ 2017-10-03  6:36  5%           ` G.B.
  0 siblings, 0 replies; 200+ results
From: G.B. @ 2017-10-03  6:36 UTC (permalink / raw)


On 03.10.17 05:30, reinert wrote:
> I noticed that my compiler did not like for example:
> 
>    t1 : time := clock + 10.0;
>    t2 : time := t1 + 20.0;
>    t3 : time range t1 + 10.0 .. t2 + 30.0;
> 
> 
> No room for syntactic sugar here? :-)

For a start, the compiler has no idea what "20.0" should
mean with regard to Time.

Sweets are available from the time unit sellers:
 From Ada.Calendar, you'll get ranges of Year_Number or
Day_Duration or ....
These will all be the result of calling functions that
take Time values and help the programmer to state his
idea of "20.0".
A chapter in Barnes's book shows how to add sugar.

There is more in the Ada.Real_Time store.


^ permalink raw reply	[relevance 5%]

* ANN: Cortex GNAT RTS 2017-08-08
@ 2017-08-08 13:04  5% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2017-08-08 13:04 UTC (permalink / raw)


This release is available at Github[1] - note the move from Sourceforge.

The main motivation for the last two releases has been to support
AdaCore's Certyflie[2], or at least my fork at [3].

There have been compiler interface changes, so some patching will be
required[4] if you're using GNAT GPL 2016 or 2017.

New features:

* Ada.Numerics.* (except random numbers).
* Interfaces.C.Extensions.
* Ada.Real_Time.Timing_Events.
* All free store (bar a 2048-byte allowance for startup and interrupts)
  is available for heap allocation.
* Sequential elaboration (with the configuration pragma
  Partition_Elaboration_Policy (Sequential)) is supported.
* type'Image() and object'Img are supported.

[1] https://github.com/simonjwright/cortex-gnat-rts/releases
[2] https://github.com/AdaCore/Certyflie
[3] https://github.com/simonjwright/Certyflie
[4] https://github.com/simonjwright/cortex-gnat-rts/blob/master/INSTALL.md#compatibility

^ permalink raw reply	[relevance 5%]

* Re: Real tasking problems with Ada.
  2017-07-25 23:19  2% Real tasking problems with Ada Robert Eachus
  @ 2017-08-01  4:41  0% ` Randy Brukardt
  1 sibling, 0 replies; 200+ results
From: Randy Brukardt @ 2017-08-01  4:41 UTC (permalink / raw)


"Robert Eachus" <rieachus@comcast.net> wrote in message 
news:9e51f87c-3b54-4d09-b9ca-e3c6a6e8940a@googlegroups.com...
> First, it should be possible to assign tasks in arrays to CPUs.

Use a discriminant of type CPU and (in Ada 2020) an 
iterated_component_association. (This was suggested way back in Ada 9x, left 
out in the infamous "scope reduction", and then forgotten about until 2013. 
See AI12-0061-1 or the draft RM 
http://www.ada-auth.org/standards/2xaarm/html/AA-4-3-3.html).

...
>1) Add a function Current_CPU or whatever (to System.Multiprocessors) that
> returns the identity of the CPU this task is running on.  Obviously in a 
> rendezvous
> with a protected object, the function would return the ID of the caller.

Why do you say this? Ada doesn't require the task that calls a protected 
object to execute it (the execution can be handdled by the task that 
services the barriers - I don't know if any implementation actually does 
this, but the language rules are written to allow it).

>  Probably do the same thing in a rendezvous between two tasks for 
> consistency.
>  Note that Get_ID function in System.Multiprocessors.Dispatching_Domains
> does that but it requires adding three (unnecessary) packages (DD,
> Ada.Real_Time, and Ada.Task_Identification) to your context without really
> using anything there.

Say what? You're using Get_Id, so clearly you're using something there. 
Get_Id (like the rest of dispatching domains is likely to be expensive, so 
you don't want it dragged into all programs. (And CPU is effectively part of 
all programs.)

> 2) Allow a task to  its CPU assignment after it has started execution.  It
> is no big deal if a task starts on a different CPU than the one it will 
> spend
> the rest of its life on.  At a minimum Set_CPU(Current_CPU) or just
> Set_CPU should cause the task to be anchored to its current CPU core.
>  Note that again you can do this with Dispatching_Domains.

So the capability already exists, but you don't like having to with an extra 
package to use it? Have you lost your freaking mind? You want us to add 
operations that ALREADY EXIST to another package, with all of the 
compatibility problems that doing so would cause (especially for people that 
had withed and used Dispatching_Domains)? When there are lots of problems 
that can't be solved portably at all?

>Next, a huge problem.  I just had some code churn out garbage while I was 
>finding the
> "right" settings to get each chunk of work to have its own portion of an 
> array.  Don't tell
> me how to do this safely, if you do you are missing the point.

No, you're missing the point. Ada is about writing portable code. Nothing at 
the level of "cache lines" is EVER going to be portable in any way. Either 
one writes "safe" code and hopefully the compiler and runtime can take into 
account the characteristics of the target. (Perhaps parallel loop constructs 
will help with that.)

Or otherwise, one writes bleeding edge code that is not portable and not 
safe. And you're on your own in such a case; no programming language could 
possibly help you.

>A function Cache_Line_Size in System or System.Multiprocessors seems right.

No,  it doesn't. It assumes a particular memory organization, and one thing 
that's pretty clear is that whatever memory organization is common now will 
not be common in a bunch of years. Besides, so many systems have multiple 
layers of caches, that a single result won't be enough. And there is no way 
for a general implementation to find this out (neither CPUs nor kernels 
describe such information).

>Is adding these features to Ada worth the effort?

No way. They're much too low level, and they actually aren't enough to allow 
parallelization. You want a language which allows fine-grained parallelism 
from the start (like Parasail); trying to retrofit that on Ada (which is 
mainly sequential, only having coarse parallelism) just will make a mess. 
You might get a few problems solved (those using actual arrays, as opposed 
to containers or user-defined types -- which one hopes are far more common 
in today's programs), but there is nothing general, nor anything that fits 
into Ada's building block approach, at the level that you're discussing.

                             Randy.



^ permalink raw reply	[relevance 0%]

* Re: Real tasking problems with Ada.
  @ 2017-07-27  2:00  4%   ` Robert Eachus
  0 siblings, 0 replies; 200+ results
From: Robert Eachus @ 2017-07-27  2:00 UTC (permalink / raw)


On Wednesday, July 26, 2017 at 3:42:57 PM UTC-4, sbelm...@gmail.com wrote:
> On Tuesday, July 25, 2017 at 7:19:59 PM UTC-4, Robert Eachus wrote:
> >    1) Add a function Current_CPU or whatever (to System.Multiprocessors) that returns the identity of the CPU this task is running on.  
> > 
> >    2) Allow a task to  its CPU assignment after it has started execution. 
> > 
> 
> Are these not exactly what System.Multiprocessors.Dispatching_Domains.Get_CPU and Set_CPU do?

Short answer, not exactly.  Yes, if I had posted the code I'm working on--probably sometime next week--you would have seen me using just that.  But the operations from Dispatching_Domains are pretty heavyweight--even if you ignore bringing in the extra packages.  What I would like are very lightweight operations.  Bringing in Ada.Real_Time and Ada.Task_Identification for default parameters which are never used would be bad enough, the problem is the program ends up checking the values passed.  So a call to Set_CPU(ID); is really a call to: Set_CPU(ID, Ada.Task_Identification.Current_Task), which can't be done before a task has an ID assigned.

If on a particular implementation, they are exactly the same, then all I am asking for is some declarative sugar which requires four lines of source added to Ada.Multitasking.  But what I really want is the ability to start a task on the processor core it will stay on.  Ah, you say, I can set the aspect CPU.  Well, not really.

I can't determine how many CPU cores are available until run-time.  That means if I want to generate tasks on a per CPU core basis, I can/must create them at run-time.  But there is no way for me to set the CPU aspect when I have an array of (identical) tasks.  I can set the aspect for tasks named Tom, Dick, and Harry like in the examples, but if I declare: Worker_Tasks: array(1..Number_of_CPUs), I can't set the CPU other than by an entry, which serializes the tasks when there are lots of them.  Remember, some of those tasks, on some hardware, will need to run on a chip in a socket over there somewhere.

It's just making things harder for non-real-time programmers for no reason.  And when you see the results from the work I am doing, you will be either astonished or appalled.


^ permalink raw reply	[relevance 4%]

* Real tasking problems with Ada.
@ 2017-07-25 23:19  2% Robert Eachus
    2017-08-01  4:41  0% ` Randy Brukardt
  0 siblings, 2 replies; 200+ results
From: Robert Eachus @ 2017-07-25 23:19 UTC (permalink / raw)


This may come across as a rant.  I've tried to keep it down, but a little bit of ranting is probably appropriate.  Some of these problems could have been fixed earlier, but there are some which are only coming of age with new CPU and GPU designs, notably the Zen family of CPUs from AMD.

Let me first explain where I am coming from (at least in this thread).  I want to write code that takes full advantage of the features available to run code as fast as possible.  In particular I'd like to get the time to run some embarrassingly parallel routines in less than twice the total CPU time of a single CPU.  (In other words, a problem that takes T seconds (wall clock) on a single CPU should run in less than 2T/N wall clock time on N processors. Oh, and it shouldn't generate garbage.  I'm working on a test program and it did generate garbage once when I didn't guess some of the system parameters right. 

So what needs to be fixed.  First, it should be possible to assign tasks in arrays to CPUs.  With a half dozen CPU cores the current facilities are irksome.  Oh, and when doing the assignment it would be nice to ask for the facilities you need, rather than have per manufacturer's family code.  Just to start with, AMD has some processors which share floating-point units, so you want to run code on alternate CPU cores on those machines--if the tasks make heavy use of floating point.

Intel makes some processors with Hyperthreading, and some without, even within the same processor family.  Hyperthreading does let you get some extra performance out if you know what you are doing, but much of the time you will want the Hyperthreading alternate to do background and OS processing while allocating your heavy hitting work threads to the main threads.

Now look at AMD's Zen family.  Almost all available today have two threads per core like Intel's Hyperthreading, but these are much more like twins.  With random loads, each thread will do about the same amount of work.  However, if you know what you are doing, you can write code which usefully hogs all of the core's resources if it can.  Back to running on alternate cores...

I know that task array types were considered in Ada 9X.  I don't know what happened to them.  But even without them, two huge improvements would be:

   1) Add a function Current_CPU or whatever (to System.Multiprocessors) that returns the identity of the CPU this task is running on.  Obviously in a rendezvous with a protected object, the function would return the ID of the caller.  Probably do the same thing in a rendezvous between two tasks for consistency.  Note that Get_ID function in System.Multiprocessors.Dispatching_Domains does that but it requires adding three (unnecessary) packages (DD, Ada.Real_Time, and Ada.Task_Identification) to your context without really using anything there. 

   2) Allow a task to  its CPU assignment after it has started execution.  It is no big deal if a task starts on a different CPU than the one it will spend the rest of its life on.  At a minimum Set_CPU(Current_CPU) or just Set_CPU should cause the task to be anchored to its current CPU core.  Note that again you can do this with Dispatching_Domains.

   Stretch goal:  Make it possible to assign tasks to a specific pair of threads. In theory Dispatching_Domains does this, but the environment task messes things up a bit.  You need to leave the partner of the environment task's CPU core in the default dispatching domain.  The problem is that there is no guarantee that the environment task is running on CPU 1 (or CPU 0, the way the hardware numbers them).

Next, a huge problem.  I just had some code churn out garbage while I was finding the "right" settings to get each chunk of work to have its own portion of an array.  Don't tell me how to do this safely, if you do you are missing the point.  If each cache line is only written to by one task, that should be safe.  But to do that I need to determine the size of the cache lines, and how to force the compiler to allocate the data in the array beginning on a cache line boundary.  The second part is not hard, except that the compiler may not support alignment clauses that large.  The first?  A function Cache_Line_Size in System or System.Multiprocessors seems right.  Whether it is in bits or storage_units is no big deal.  Why a function not a constant?  The future looks like a mix of CPUs and GPUs all running parts of the same program.

Finally, caches and NUMA galore.  I mentioned AMD's Zen above.  Right now there are three Zen families with very different system architectures.  In fact, the difference between single and dual socket Epyc makes it four, and the Ryzen 3 and Ryzen APUs when released?  At least one more.  What's the big deal?  Take Threadripper to begin with.  Your choice of 12 or 16 cores each supporting two threads.  But the cache hierarchy is complex.  Each CPU core has two threads and its own L1 and L2 caches.  Then 3 or 4 cores, depending on the model share the same 8 Meg L3 cache. The four blocks of CPU cores and caches are actually split between two different chips.  Doesn't affect the cache timings much, but half the memory is attached to one chip, half to the other.  The memory loads and stores, if to the other chip, compete with L3 and cache probe traffic.  Let's condense that to this: 2 (threads)/(3 or 4) cores/2 (NUMA pairs)/2(chips)/1 (socket).  A Ryzen 7 chip is 2/4/2/1/1, Ryzen 5 is 2/(3 or 2)/2/1/1, Ryzen 3 1/2/2/1/1.  Epyc comes in at 2/(3 or 4)/2/4/2 among other flavors.

Writing a package to recognize these models and sort out for executable programs is going to be a non-trivial exercise--at least if I try to keep it current.  But how to convey the information to the software which is going to try to saturate the system?  No point in creating tasks which won't have a CPU core of their own (or half a core, or what you count Hyperthreading as).  Given the size of some of these systems, even without the HPC environment, it may be better for a program to split the work between chips or boxes.

Is adding these features to Ada worth the effort?  Sure.  Let me give you a very realistic example.  Running on processor cores which share L3 cache may be worthwhile.  Actually with Zen, the difference is that a program that stays on one L3 cache will actually save a lot of time on L2 probes.  (The line you need is in L2 on another CPU core.  Moving it to your core will take less time, and more importantly less latency than moving it from another CPU cluster.)  So we go to write our code.  On Ryzen 7 we want to run on cores 1, 3, 5, and 7 or 9, 11, 13 and 15, or 2, 4, 6, 8 or...  Actually I could choose 1,4,6, and 7, any set of one core from each pair staying within the module (of eight threads).  Move to a low-end Ryzen 3, and I get almost the same performance by choosing all the available cores: 1, 2, 3, and 4.  What about Ryzen 5 1600 and 1600X?  Is it going to be better to run on 3 cores and one L3 cache or 4 cores spread across two caches?    Or maybe choose all six cores on one L3 cache?  Argh!

Is this problem real?  Just took a program from  7.028 seconds on six cores, to 2.229 seconds on (the correct) three cores.  I'll post the program, or put it on-line somewhere once I've confined the memory corruption to very small examples--so you can see which machines do it--and do a bit more cleanup and optimization.

^ permalink raw reply	[relevance 2%]

* GNAT.Sockets Streaming inefficiency
@ 2017-06-08 10:36  7% masterglob
  0 siblings, 0 replies; 200+ results
From: masterglob @ 2017-06-08 10:36 UTC (permalink / raw)


Configuration: X64, Linux & Windows (GNATPRO 7.4.2)
While using GNAT.Sockets.Stream_Access, there is a real performance issue while using String'Output(...).

My test sends 500 times a 1024-long String using String'Output(TCP_Stream on 127.0.0.1) and the result is:
- Linux : average 'output duration = 3 us
- Windows: average 'output duration = 250 us

From prior discussion with AdaCore, the "String" type is the only one for which this latency is NOT observed on Linux.

Any idea on:
- is there a way to get similar performance on Windows (maybe using another type or method?)
- is there any configuration that may solve this issue?


=============
Result on W7/64
---------
OS=Windows_NT  cygwin
GNAT Pro 7.4.2 (20160527-49)
[SERVER] start...
[SERVER]:bind... 127.0.0.1:4264
[CLIENT] connected...
[SERVER]:connection from 127.0.0.1:56008
[SERVER] Sending 500 messages ...
[CLIENT] waiting for 500 messages ...
[CLIENT]:execution time:  0.000000000
[Server] execution time ( 500msg):  0.140400900 s
[Server] Output_Exec time (1 msg):  0.280801800 ms
[Server] Output_Duration time (1 msg):  0.263417164 ms

=============
Result on Ubuntu/64
---------
OS= 
GNAT Pro 7.4.2 (20160527-49)
[SERVER] start...
[SERVER]:bind... 127.0.0.1:4264
[SERVER]:connection from 127.0.0.1:52574
[CLIENT] connected...
[SERVER] Sending 500 messages ...
[CLIENT] waiting for 500 messages ...
[Server] execution time ( 500msg):  0.001783393 s
[Server] Output_Exec time (1 msg):  0.003072174 ms
[Server] Output_Duration time (1 msg):  0.003204778 ms
[CLIENT]:execution time:  0.001561405

=============
Makefile:
---------
all:build exec
build:
	@gprbuild -p -Ptest_stream_socket_string.gpr
exec: 
	@echo "OS=$$OS  $$OSTYPE"
	@echo $$(gnat --version|head -1)
	@obj/test_stream_socket_string



=============
test_stream_socket_string.gpr:
---------
project Test_Stream_Socket_String is

   for Object_Dir  use "obj";
   for Exec_Dir    use "obj";
   for Main        use ("test_stream_socket_string.adb");
   for Source_Dirs use (".");
   for Languages use ("Ada");

   package Builder is
      for Default_Switches ("Ada") use ("-g","-s","-j0");
   end Builder;

   package Compiler is
      Ada_Opt   := ("-O0");
      Ada_Comp    := ("-gnat12","-g","-gnatU","-gnato","-gnatVa","-fstack-check","-fstack-usage","-gnateE","-gnateF");
      Ada_Style   := ("-gnaty3aAbBCdefhiklL15M120nOprStux");
      Ada_Warning := ("-gnatwah.h.o.st.w");
      for Default_Switches ("Ada") use Ada_Opt & Ada_Comp & Ada_Warning & Ada_Style;
   end Compiler;

   package Binder is
      for Default_Switches ("Ada") use ("-v","-E","-R","-T0");
   end Binder;

   package Linker is
      for Default_Switches ("Ada") use ("-g","-v") ;
   end Linker;

end Test_Stream_Socket_String;



=============
test_stream_socket_string.adb
---------
with Ada.Execution_Time,
     Ada.Real_Time,
     Ada.Text_IO,
     Ada.Exceptions,

     GNAT.Sockets,
     GNAT.Traceback.Symbolic,
     GNAT.OS_Lib;
use GNAT,
    Ada;

use type GNAT.Sockets.Selector_Status,
         Ada.Real_Time.Time,
         Ada.Execution_Time.CPU_Time;

procedure Test_Stream_Socket_String is

   Port    : constant Sockets.Port_Type := 4264;
   Ip_Addr : constant String := "127.0.0.1";

   task type Client_Thread_T is
      entry Start;
      entry Synch;
      entry Wait;
   end Client_Thread_T;
   Client_Thread : Client_Thread_T;
   task type Server_Thread_T is
      entry Start;
      entry Wait;
   end Server_Thread_T;
   Server_Thread : Server_Thread_T;
   
   task body Client_Thread_T is
   
   task body Server_Thread_T is
      Nb_Loop         : constant := 500;
      Cpt             : Integer := Nb_Loop;
      Msg_Size        : constant :=  1024; -- 1 Ko
      Exec_Start_Time : Execution_Time.CPU_Time;
      Exec_Output1    : Execution_Time.CPU_Time;
      Exec_Output2    : Real_Time.Time;
      Output_Exec     : Duration := 0.0;
      Output_Duration : Duration := 0.0;
      Listen          : Sockets.Socket_Type;
      Client          : Sockets.Socket_Type;
      Address         : Sockets.Sock_Addr_Type := (Family => Sockets.Family_Inet,
                                                   Addr   => Sockets.Inet_Addr (Ip_Addr),
                                                   Port   => Port);
      Channel         : Sockets.Stream_Access;
   begin
      accept Start;
      Text_IO.Put_Line ("[SERVER] start...");

      Sockets.Create_Socket (Socket => Listen);
      Text_IO.Put_Line ("[SERVER]:bind... " & Sockets.Image (Address));
      Sockets.Bind_Socket (Socket  => Listen,
                           Address => Address);
      Sockets.Listen_Socket (Listen);

      Sockets.Accept_Socket (Listen, Client, Address);
      Text_IO.Put_Line ("[SERVER]:connection from " & Sockets.Image (Sockets.Get_Peer_Name (Client)));
      Channel := Sockets.Stream (Socket => Client);
      Exec_Start_Time := Execution_Time.Clock;

      Integer'Output (Channel, Cpt);
         Text_IO.Put_Line ("[SERVER] Sending" & Cpt'Img & " messages ...");
      
      while Cpt > 0 loop
         -- Text_IO.Put ('+');
         declare
            S : constant String (1 .. Msg_Size) := (others => '?');
         begin
            Exec_Output1 := Execution_Time.Clock;
            Exec_Output2 := Real_Time.Clock;
            String'Output (Channel, S);
            Output_Exec := Output_Exec + 
              Real_Time.To_Duration (Execution_Time.Clock - Exec_Output1);
            Output_Duration := Output_Duration + 
              Real_Time.To_Duration (Real_Time.Clock - Exec_Output2);
         end;

         Cpt := Cpt - 1;

      end loop;

      Text_IO.Put_Line ("[Server] execution time (" & Nb_Loop'Img & "msg): " &
                          Real_Time.To_Duration (Execution_Time.Clock - Exec_Start_Time)'Img & " s");

      Text_IO.Put_Line ("[Server] Output_Exec time (1 msg): " &
                          Duration'Image (1000.0 * Output_Exec / (Nb_Loop - Cpt)) & " ms");
      Text_IO.Put_Line ("[Server] Output_Duration time (1 msg): " &
                          Duration'Image (1000.0 * Output_Duration / (Nb_Loop - Cpt)) & " ms");

      Sockets.Close_Socket (Socket => Listen);

      accept Wait;
      -- Text_IO.New_Line;
   exception
      when E : others =>
         Text_IO.New_Line;
         Text_IO.Put_Line ("[Server] Exception: " & Exceptions.Exception_Information (E));
         Text_IO.Put_Line (Exceptions.Exception_Message (E));
         Text_IO.Put_Line (Traceback.Symbolic.Symbolic_Traceback (E));
         if Cpt /= Nb_Loop then
            Text_IO.Put_Line ("[Server] Output_Duration time: " &
                                Duration'Image (1000.0 * Output_Duration / (Nb_Loop - Cpt)) & " ms");
         end if;
         GNAT.OS_Lib.OS_Abort;
   end Server_Thread_T;
   
begin
   Server_Thread.Start;
   Client_Thread.Start;
   Client_Thread.Synch;
   Server_Thread.Wait;
   
   Client_Thread.Wait;
   -- Text_IO.New_Line;
exception
   when E : others =>
      Text_IO.Put_Line (Exceptions.Exception_Information (E));
      Text_IO.Put_Line (Exceptions.Exception_Message (E));
      Text_IO.Put_Line (Traceback.Symbolic.Symbolic_Traceback (E));
end Test_Stream_Socket_String;

^ permalink raw reply	[relevance 7%]

* Default values
@ 2016-12-25  9:23  6% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2016-12-25  9:23 UTC (permalink / raw)


Given

   with Ada.Real_Time;

   package Sbus.IMU is

      subtype Radians_Per_Second is Float;
      subtype Acceleration is Float;
      subtype Milligauss is Float;

      type Update (Magnetometer_Data_Present : Boolean := False) is record
         Time_Valid : Ada.Real_Time.Time;

         Gx, Gy, Gz : Radians_Per_Second;
         Ax, Ay, Az : Acceleration;

         case Magnetometer_Data_Present is
            when True =>
               Mx, My, Mz : Milligauss;
            when False =>
               null;
         end case;
      end record;

      protected Updater is
         procedure Put_New_Data (Data : Update);
         entry Get_New_Data (Data : out Update);
         procedure Get_Latest_Data (Data : out Update);
      private
         New_Data_Present : Boolean := False;
         Latest_Data : Update := (others => <>);
      end Updater;

   end Sbus.IMU;

is the line

         Latest_Data : Update := (others => <>);

legal? If so, what does it mean? (I've looked at the ARM for Record
Aggregates, 4.3.1, and Record Types. 3.8, and am no wiser).

I do realise that I need to put some default initializations in (or else
supply a proper initialization for Latest_Data!)


^ permalink raw reply	[relevance 6%]

* Re: Building / Modifying the RTS for Cortex
  2016-12-10 16:17  0% ` Simon Wright
@ 2016-12-11 16:58  0%   ` M. Enzmann
  0 siblings, 0 replies; 200+ results
From: M. Enzmann @ 2016-12-11 16:58 UTC (permalink / raw)


Am Samstag, 10. Dezember 2016 17:17:34 UTC+1 schrieb Simon Wright:
> "M. Enzmann" <enzmann.m@googlemail.com> writes:
> 
> > I am having some trouble to understand how the RTS for my STM32F429
> > Discovery board is being built.
> >
> > While tinkering with some of the examples in the Ada Drivers Library
> > from Ada Core, I thought it might be a nice idea to add some
> > funtionality to the Ada.Real_Time package.
> 
> The way to rebuild the runtime is to go to the embedded-runtimes/
> directory at the top level of the repo and say "make".
> 
> This will rebuild all the runtimes as required (provided that all your
> changes are in the appropriate place under embedded-runtimes/).
> 
> I wouldn't bother too much about accidentally changing stuff, that's why
> we use git!
> 
> The -a flag is only available in gnatmake, which isn't the right tool to
> build runtimes (or Cortex code):
> 
>    $ gprbuild -a
>    warning: switch -a is ignored and no additional source is compiled

Simon, thanks for your help! 

At times programming in Ada is frustrating. The compiler is always right. So it would seem.

^ permalink raw reply	[relevance 0%]

* Re: Building / Modifying the RTS for Cortex
  2016-12-10 15:40  6% Building / Modifying the RTS for Cortex M. Enzmann
@ 2016-12-10 16:17  0% ` Simon Wright
  2016-12-11 16:58  0%   ` M. Enzmann
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2016-12-10 16:17 UTC (permalink / raw)


"M. Enzmann" <enzmann.m@googlemail.com> writes:

> I am having some trouble to understand how the RTS for my STM32F429
> Discovery board is being built.
>
> While tinkering with some of the examples in the Ada Drivers Library
> from Ada Core, I thought it might be a nice idea to add some
> funtionality to the Ada.Real_Time package.

The way to rebuild the runtime is to go to the embedded-runtimes/
directory at the top level of the repo and say "make".

This will rebuild all the runtimes as required (provided that all your
changes are in the appropriate place under embedded-runtimes/).

I wouldn't bother too much about accidentally changing stuff, that's why
we use git!

The -a flag is only available in gnatmake, which isn't the right tool to
build runtimes (or Cortex code):

   $ gprbuild -a
   warning: switch -a is ignored and no additional source is compiled

^ permalink raw reply	[relevance 0%]

* Building / Modifying the RTS for Cortex
@ 2016-12-10 15:40  6% M. Enzmann
  2016-12-10 16:17  0% ` Simon Wright
  0 siblings, 1 reply; 200+ results
From: M. Enzmann @ 2016-12-10 15:40 UTC (permalink / raw)


Hi All,

I am having some trouble to understand how the RTS for my STM32F429 Discovery board is being built. 

While tinkering with some of the examples in the Ada Drivers Library from Ada Core, I thought it might be a nice idea to add some funtionality to the Ada.Real_Time package.

First idea: add a child package, so I don't have to play with the files in the "original" RTS. Didn't work. The file newer got compiled. 
Second idea: add a single function to Ada.Real_Time. Didn't work either. The file is being compiled, however I can't find the corresponding symbol in the a-reatim.o 

I assume, this is related to my playing with the RTS and I found some sources on the web discussing the usage of different compiler-switches (e.g. '-a' for gnatmake, ...) but neither did they help, nor do I have an idea why not.

Waiting eagerly for your insightful responses,

TIA,

Marc


^ permalink raw reply	[relevance 6%]

* Re: Ada features supported by SPARK 2014
  @ 2016-12-06 13:26  7%     ` Daniel King
  0 siblings, 0 replies; 200+ results
From: Daniel King @ 2016-12-06 13:26 UTC (permalink / raw)


On Tuesday, 6 December 2016 05:17:56 UTC-4, Simon Wright  wrote:
> Daniel King <danie...@googlemail.com> writes:
> 
> > In addition, for tasking features, SPARK is limited to the "Ravenscar
> > profile", which is basically a set of restrictions on Ada's tasking
> > features, to permit static analysis for formal verification.
> 
> I found that - as soon as there's anything involving time - I couldn't
> work out how to specify flow (when I "fixed" one problem, another would
> pop up somewhere else; if I "fixed" that, the first would pop up
> again). So I left it up to the tool to infer flow for itself according
> to whatever arcane rules it wanted to (not really a satisfactory state
> of affairs for something that's supposed to increase my confidence in
> the code).

Do you mean using "delay until"?

In such cases I've found that I've needed the following annotations:

   with Global => (Input => Ada.Real_Time.Clock_Time),
   Depends => (null => Ada.Real_Time.Clock_Time);


^ permalink raw reply	[relevance 7%]

* Re: Gnat Sockets - UDP timeout too short.
  2016-10-12 14:23  8% Gnat Sockets - UDP timeout too short ahlan
@ 2016-11-04  8:48  0% ` ahlan.marriott
  0 siblings, 0 replies; 200+ results
From: ahlan.marriott @ 2016-11-04  8:48 UTC (permalink / raw)


On Wednesday, 12 October 2016 16:23:39 UTC+2, ah...@marriott.org  wrote:
> Under Microsoft Windows 8.1 (and later) Gnat.Sockets.Receive_Socket returns too early whilst waiting for a UDP datagram.
> In our test program (below) we create a UDP socket, set the timeout for one second, bind it to a port and then call receive on the socket.
> We catch and resolve the Socket_Error exception and process the expected Connection_Timed_Out.
> We note the time before issuing Receive_Socket and the time when we catch the exception and then compare the elapsed time with the receive timeout.
> On Window systems prior to Win8.1 this seems to work as expected, the elapsed time is always greater than the receive timeout.
> However under Win8.1 (and later) the call to Receive_Socket returns approximately half a second too early!
> 
> Curiously, if I write the same thing using the Win32.WinSock API then it works as expected. Which I find odd because I would have thought that Gnat.Sockets would simply be a series of wrappers around a few WinApi calls. But then what do I know?
> 
> The effect of this bug is that programs using UDP protocols timeout earlier than they should do - which often leads to curious behaviour.
> 
> We have tested this on a couple of PCs running a variety of flavours of Ms-Windows. So far it seems that XP & Win7 work as expected whereas Win8 and Win10 fail.
> 
> Has anyone any idea what might cause this problem and how we might go about fixing it?
> 
> Best wishes,
> MfG
> Ahlan
> 
> ------------------------------
> with Ada.Text_IO;
> with Ada.Exceptions;
> with Ada.Real_Time;
> with Ada.Streams;
> with GNAT.Sockets;
> 
> package body Test is
> 
>   package Io  renames Ada.Text_IO;
>   package Net renames GNAT.Sockets;
> 
>   Receive_Timeout : constant Duration := 1.0;
> 
>   Receive_Timeout_Span : constant Ada.Real_Time.Time_Span := Ada.Real_Time.To_Time_Span (Receive_Timeout);
> 
>   procedure Work is
>     The_Datagram : Ada.Streams.Stream_Element_Array (1..20);
>     The_Last     : Ada.Streams.Stream_Element_Offset;
>     The_Socket   : Net.Socket_Type;
>     Start_Time   : Ada.Real_Time.Time;
>     End_Time     : Ada.Real_Time.Time;
>     use type Ada.Real_Time.Time;
>   begin
>     Net.Create_Socket (Socket => The_Socket,
>                        Family => Net.Family_Inet,
>                        Mode   => Net.Socket_Datagram);
>     Net.Set_Socket_Option (Socket => The_Socket,
>                            Option => (Net.Receive_Timeout, Timeout => Receive_Timeout));
>     Net.Bind_Socket (The_Socket, (Family => Net.Family_Inet,
>                                   Addr   => Net.Any_Inet_Addr,
>                                   Port   => 11154));
>     loop
>       begin
>         Start_Time := Ada.Real_Time.Clock;
>         Net.Receive_Socket (Socket => The_Socket,
>                             Item   => The_Datagram,
>                             Last   => The_Last);
>         Io.New_Line;
>         Io.Put_Line ("Unexpected reply!");
>         exit;
>       exception
>       when Occurrence: Net.Socket_Error =>
>         End_Time := Ada.Real_Time.Clock;
>         declare
>           Error : constant Net.Error_Type := Net.Resolve_Exception (Occurrence);
>           use type Net.Error_Type;
>         begin
>           if Error = Net.Connection_Timed_Out then
>             if End_Time >= (Start_Time + Receive_Timeout_Span) then
>               Io.Put (".");
>             else
>               Io.New_Line;
>               declare
>                 use type Ada.Real_Time.Time_Span;
>                 Shortfall : constant Ada.Real_Time.Time_Span := Receive_Timeout_Span - (End_Time - Start_Time);
>               begin
>                 Io.Put_Line ("Timeout too short by" & Ada.Real_Time.To_Duration (Shortfall)'img & "seconds");
>               end;
>             end if;
>           else
>             Io.Put_Line ("Socket_Error : Unexpected error=" & Error'img);
>             exit;
>           end if;
>         end;
>       when Event : others =>
>         Io.Put_Line ("Unexpected exception: " & Ada.Exceptions.Exception_Name (Event));
>       end;
>     end loop;
>   exception
>   when Event : others =>
>     Io.Put_Line ("Internal Error: " & Ada.Exceptions.Exception_Name (Event));
>   end Work;
To answer my own question...
Gnat sockets uses the Winsock function Recv and sets the timeout DWORD SO_RCVTIMEO in Milliseconds.
However according to the Microsoft Developers Network in Feb 2014 (and others articles) there was an undocumented minimum limit of 500ms which seems to have been implemented by Microsoft simply adding 500ms to whatever non-zero value was placed in SO_RECVTIMEO.
The consensus workaround was simply to deduct 500ms from the desired timeout.
This is indeed what Gnat.Sockets seems to have implemented at line 2297 in g-socket.adb
if V4 > 500 then V4 := V4 - 500; elsif v4 > 0 then V4 := 1 endif;
At line 1249 in g-socket.adb the 500 is added again if the timeout is retrieved.

It seems to me that recent versions of Windows no longer adds 500ms to the Recv timeout.
This would explain why under Win8 and Win10 our receive of UDP datagrams timeout half a second too soon.

Gnat.Sockets needs to determine the version of windows and only apply the correction if necessary.

The fun of course is going to be finding our which versions of Windows need the correction and which don’t. ;-)
Win8.1 and Win10 don't, Win7 and WinXp do.
Can anyone add to this list?

Best wishes
MfG
Ahlan


^ permalink raw reply	[relevance 0%]

* Gnat Sockets - UDP timeout too short.
@ 2016-10-12 14:23  8% ahlan
  2016-11-04  8:48  0% ` ahlan.marriott
  0 siblings, 1 reply; 200+ results
From: ahlan @ 2016-10-12 14:23 UTC (permalink / raw)


Under Microsoft Windows 8.1 (and later) Gnat.Sockets.Receive_Socket returns too early whilst waiting for a UDP datagram.
In our test program (below) we create a UDP socket, set the timeout for one second, bind it to a port and then call receive on the socket.
We catch and resolve the Socket_Error exception and process the expected Connection_Timed_Out.
We note the time before issuing Receive_Socket and the time when we catch the exception and then compare the elapsed time with the receive timeout.
On Window systems prior to Win8.1 this seems to work as expected, the elapsed time is always greater than the receive timeout.
However under Win8.1 (and later) the call to Receive_Socket returns approximately half a second too early!

Curiously, if I write the same thing using the Win32.WinSock API then it works as expected. Which I find odd because I would have thought that Gnat.Sockets would simply be a series of wrappers around a few WinApi calls. But then what do I know?

The effect of this bug is that programs using UDP protocols timeout earlier than they should do - which often leads to curious behaviour.

We have tested this on a couple of PCs running a variety of flavours of Ms-Windows. So far it seems that XP & Win7 work as expected whereas Win8 and Win10 fail.

Has anyone any idea what might cause this problem and how we might go about fixing it?

Best wishes,
MfG
Ahlan

------------------------------
with Ada.Text_IO;
with Ada.Exceptions;
with Ada.Real_Time;
with Ada.Streams;
with GNAT.Sockets;

package body Test is

  package Io  renames Ada.Text_IO;
  package Net renames GNAT.Sockets;

  Receive_Timeout : constant Duration := 1.0;

  Receive_Timeout_Span : constant Ada.Real_Time.Time_Span := Ada.Real_Time.To_Time_Span (Receive_Timeout);

  procedure Work is
    The_Datagram : Ada.Streams.Stream_Element_Array (1..20);
    The_Last     : Ada.Streams.Stream_Element_Offset;
    The_Socket   : Net.Socket_Type;
    Start_Time   : Ada.Real_Time.Time;
    End_Time     : Ada.Real_Time.Time;
    use type Ada.Real_Time.Time;
  begin
    Net.Create_Socket (Socket => The_Socket,
                       Family => Net.Family_Inet,
                       Mode   => Net.Socket_Datagram);
    Net.Set_Socket_Option (Socket => The_Socket,
                           Option => (Net.Receive_Timeout, Timeout => Receive_Timeout));
    Net.Bind_Socket (The_Socket, (Family => Net.Family_Inet,
                                  Addr   => Net.Any_Inet_Addr,
                                  Port   => 11154));
    loop
      begin
        Start_Time := Ada.Real_Time.Clock;
        Net.Receive_Socket (Socket => The_Socket,
                            Item   => The_Datagram,
                            Last   => The_Last);
        Io.New_Line;
        Io.Put_Line ("Unexpected reply!");
        exit;
      exception
      when Occurrence: Net.Socket_Error =>
        End_Time := Ada.Real_Time.Clock;
        declare
          Error : constant Net.Error_Type := Net.Resolve_Exception (Occurrence);
          use type Net.Error_Type;
        begin
          if Error = Net.Connection_Timed_Out then
            if End_Time >= (Start_Time + Receive_Timeout_Span) then
              Io.Put (".");
            else
              Io.New_Line;
              declare
                use type Ada.Real_Time.Time_Span;
                Shortfall : constant Ada.Real_Time.Time_Span := Receive_Timeout_Span - (End_Time - Start_Time);
              begin
                Io.Put_Line ("Timeout too short by" & Ada.Real_Time.To_Duration (Shortfall)'img & "seconds");
              end;
            end if;
          else
            Io.Put_Line ("Socket_Error : Unexpected error=" & Error'img);
            exit;
          end if;
        end;
      when Event : others =>
        Io.Put_Line ("Unexpected exception: " & Ada.Exceptions.Exception_Name (Event));
      end;
    end loop;
  exception
  when Event : others =>
    Io.Put_Line ("Internal Error: " & Ada.Exceptions.Exception_Name (Event));
  end Work;


^ permalink raw reply	[relevance 8%]

* Re: Win32.   Task or CreateThread
  2016-08-03 20:31  9% ` Aurele
@ 2016-08-04  2:41  0%   ` George J
  0 siblings, 0 replies; 200+ results
From: George J @ 2016-08-04  2:41 UTC (permalink / raw)


среда, 3 августа 2016 г., 23:31:11 UTC+3 пользователь Aurele написал:
> declare
> Start_Time : Ada.Real_Time.Time;
>       Stop_Time  : Ada.Real_Time.Time;
> 
> 
> loop
> 
>   Start_Time := Ada.Real_Time.Clock;
> 
>   Do_Stuff'
> 
>   Stop_Time        := Ada.Real_Time.Clock; 
>   Performance_Time := Ada.Real_Time.To_Duration( Stop_Time - Start_Time ); 
> 
>   while Performance_Time < 0.2 loop  -- Delay...
>     Winbase.Sleep( 0 );  -- This is a Windows function
>     Stop_Time := Ada.Real_Time.Clock; 
>     Performance_Time := Ada.Real_Time.To_Duration( Stop_Time - Start_Time ); 
>   end loop;
>           
> end loop;

Thanks, Aurele!

^ permalink raw reply	[relevance 0%]

* Re: Win32.   Task or CreateThread
  @ 2016-08-03 20:31  9% ` Aurele
  2016-08-04  2:41  0%   ` George J
  0 siblings, 1 reply; 200+ results
From: Aurele @ 2016-08-03 20:31 UTC (permalink / raw)


declare
Start_Time : Ada.Real_Time.Time;
      Stop_Time  : Ada.Real_Time.Time;


loop

  Start_Time := Ada.Real_Time.Clock;

  Do_Stuff'

  Stop_Time        := Ada.Real_Time.Clock; 
  Performance_Time := Ada.Real_Time.To_Duration( Stop_Time - Start_Time ); 

  while Performance_Time < 0.2 loop  -- Delay...
    Winbase.Sleep( 0 );  -- This is a Windows function
    Stop_Time := Ada.Real_Time.Clock; 
    Performance_Time := Ada.Real_Time.To_Duration( Stop_Time - Start_Time ); 
  end loop;
          
end loop;
  

^ permalink raw reply	[relevance 9%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-06-03 10:03  6%       ` Alejandro R. Mosteo
@ 2016-06-03 12:15  5%         ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2016-06-03 12:15 UTC (permalink / raw)


On 03/06/2016 12:03, Alejandro R. Mosteo wrote:
> On 03/06/16 09:26, Dmitry A. Kazakov wrote:
>> On 02/06/2016 23:25, Alejandro R. Mosteo wrote:
>>
>>> I'm sorry but I don't follow your explanation. To make things simpler,
>>> let's consider only the 1-to-1 case. How's this protected used without a
>>> blocking operation?
>>
>> If you have FIFO, a lock-free implementation is a buffer with one read
>> and one write index (mod buffer length). The read index never advances
>> beyond the write index. Reader updates the read index and looks at the
>> write index, and conversely the writer. Indices must have pragma Atomic,
>> and the buffer not cached. For example:
>>
>> http://www.dmitry-kazakov.de/ada/components.htm#10.1.1
>
> Thanks, I was unsure if you referred to using a lock-free data type, or
> if it could be trivially done with the standard Ada containers with some
> well-known pattern I was ignorant of.

Yes, but the larger point was that using a standard container protected 
by either a monitor task or else by a protected interlocking object is 
IMO a better design that a specialized container in a protected object.

> I'll take a look at your library, I'm very interested in lock-free
> containers.
>
> A friend working on hardware architectures recently told me that a
> widely-used lock-free library (in the c++ world) had been proven with
> SPARK-like methods to be buggy. Alas, I can't remember names/dates.

That is quite possible, however I don't know what technique they used 
for making proofs. It is much about the semantics of the language 
constructs in presence of concurrent access. I am not sure about so many 
things even in Ada. I can imagine proving an implementation wrong, but 
the reverse might be exceptionally tricky. I remember reading some 
papers about this stuff, that used formal mathematical proofs, it was 
very complicated. I believe one could use a brute-force enumeration of 
possible accesses in some simulated time for making the proof in SPARK 
environment.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de

^ permalink raw reply	[relevance 5%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-06-03  7:26  5%     ` Dmitry A. Kazakov
@ 2016-06-03 10:03  6%       ` Alejandro R. Mosteo
  2016-06-03 12:15  5%         ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: Alejandro R. Mosteo @ 2016-06-03 10:03 UTC (permalink / raw)


On 03/06/16 09:26, Dmitry A. Kazakov wrote:
> On 02/06/2016 23:25, Alejandro R. Mosteo wrote:
>
>> I'm sorry but I don't follow your explanation. To make things simpler,
>> let's consider only the 1-to-1 case. How's this protected used without a
>> blocking operation?
>
> If you have FIFO, a lock-free implementation is a buffer with one read
> and one write index (mod buffer length). The read index never advances
> beyond the write index. Reader updates the read index and looks at the
> write index, and conversely the writer. Indices must have pragma Atomic,
> and the buffer not cached. For example:
>
> http://www.dmitry-kazakov.de/ada/components.htm#10.1.1

Thanks, I was unsure if you referred to using a lock-free data type, or 
if it could be trivially done with the standard Ada containers with some 
well-known pattern I was ignorant of.

I'll take a look at your library, I'm very interested in lock-free 
containers.

A friend working on hardware architectures recently told me that a 
widely-used lock-free library (in the c++ world) had been proven with 
SPARK-like methods to be buggy. Alas, I can't remember names/dates.

Thanks,
Alex.

>
> Of course if you want to wait for a FIFO state, e.g. 'not full' or 'not
> empty' you will need an event (a protected object). But you don't need
> to have the FIFO a protected object.
>
> It is an important point not to have containers protected. Operations on
> container might be quite expensive depending on the element types and
> the container structure. As a rule you should not maintain containers on
> the context of a protected action. E.g. if you have to do a binary
> search to get an element, that is not to do in a protected action.
>
>>>> Any ideas? Basically, how to trigger another task (without creating it)
>>>> from within a protected handler?
>
> By changing an entry barrier, of course.
>
> The task to trigger waits for a protected entry to open, it is released
> after leaving the entry.
>

^ permalink raw reply	[relevance 6%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-06-02 21:25  6%   ` Alejandro R. Mosteo
@ 2016-06-03  7:26  5%     ` Dmitry A. Kazakov
  2016-06-03 10:03  6%       ` Alejandro R. Mosteo
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2016-06-03  7:26 UTC (permalink / raw)


On 02/06/2016 23:25, Alejandro R. Mosteo wrote:

> I'm sorry but I don't follow your explanation. To make things simpler,
> let's consider only the 1-to-1 case. How's this protected used without a
> blocking operation?

If you have FIFO, a lock-free implementation is a buffer with one read 
and one write index (mod buffer length). The read index never advances 
beyond the write index. Reader updates the read index and looks at the 
write index, and conversely the writer. Indices must have pragma Atomic, 
and the buffer not cached. For example:

http://www.dmitry-kazakov.de/ada/components.htm#10.1.1

Of course if you want to wait for a FIFO state, e.g. 'not full' or 'not 
empty' you will need an event (a protected object). But you don't need 
to have the FIFO a protected object.

It is an important point not to have containers protected. Operations on 
container might be quite expensive depending on the element types and 
the container structure. As a rule you should not maintain containers on 
the context of a protected action. E.g. if you have to do a binary 
search to get an element, that is not to do in a protected action.

>>> Any ideas? Basically, how to trigger another task (without creating it)
>>> from within a protected handler?

By changing an entry barrier, of course.

The task to trigger waits for a protected entry to open, it is released 
after leaving the entry.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de


^ permalink raw reply	[relevance 5%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-06-02 21:13  6%     ` Alejandro R. Mosteo
@ 2016-06-02 23:16  6%       ` Jeffrey R. Carter
  0 siblings, 0 replies; 200+ results
From: Jeffrey R. Carter @ 2016-06-02 23:16 UTC (permalink / raw)


On 06/02/2016 02:13 PM, Alejandro R. Mosteo wrote:
> On 25/05/16 00:21, Jeffrey R. Carter wrote:
>>
>> This is known as a forwarder. There's a generic forwarder in the
>> PragmAda Reusable Components. The main problem with forwarders is that
>> there's no easy way to terminate them.
> 
> Indeed I was also thinking about this. I can't think of anything besides
> periodical checks to some bail-out flag.

One could complicate the generic significantly to allow this. Custom forwarders
can do it easily, but then you have code duplication.

-- 
Jeff Carter
"It has been my great privilege, many years ago,
whilst traveling through the mountains of Paraguay,
to find the Yack'Wee Indians drinking the juice of
the cacti."
The Old Fashioned Way
152

^ permalink raw reply	[relevance 6%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-25  7:23  5% ` Dmitry A. Kazakov
@ 2016-06-02 21:25  6%   ` Alejandro R. Mosteo
  2016-06-03  7:26  5%     ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: Alejandro R. Mosteo @ 2016-06-02 21:25 UTC (permalink / raw)


On 25/05/16 09:23, Dmitry A. Kazakov wrote:
> On 24/05/2016 16:22, Alejandro R. Mosteo wrote:
>
>> I'm stuck with something not that strange, so I guess I need another
>> viewpoint on it.
>>
>> I want to trigger, in the future, a possibly long computation in the
>> background. For that I had thought of using the built-in Real_Time
>> events.
>>
>> My idea was to queue the job when the event is triggered, and to have a
>> worker thread waiting for jobs in the queue. However, I've just realized
>> that the event handler is itself a protected action, so I can't call
>> another potentially blocking enqueue from there.
>
> Neither is protected action. To enqueue anything into FIFO you need no
> locking. This is lock-free. To dequeue, provided single consumer there
> is no need to lock anything either. If there are several consumers, you
> use a protected object to dequeue only.
> 1-to-n: The dequeue is a waitable entry. Once you have got the packet
> out of the queue you process it outside any protected actions.
>
> 1-to-1: You use a reset-event implemented using protected object to wake
> up the consumer, which dequeues the packet. Reset event is
> race-condition free to query if the queue is empty and if so, to wait
> for the event.

I'm sorry but I don't follow your explanation. To make things simpler, 
let's consider only the 1-to-1 case. How's this protected used without a 
blocking operation?

Thanks.

>> Any ideas? Basically, how to trigger another task (without creating it)
>> from within a protected handler?
>
> Always by waiting for an entry. E.g. as described above.
>

^ permalink raw reply	[relevance 6%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-24 23:52  5% ` Jeffrey R. Carter
@ 2016-06-02 21:22  6%   ` Alejandro R. Mosteo
  0 siblings, 0 replies; 200+ results
From: Alejandro R. Mosteo @ 2016-06-02 21:22 UTC (permalink / raw)


On 25/05/16 01:52, Jeffrey R. Carter wrote:
> On 05/24/2016 07:22 AM, Alejandro R. Mosteo wrote:
>>
>> My idea was to queue the job when the event is triggered, and to have
>> a worker
>> thread waiting for jobs in the queue. However, I've just realized that
>> the event
>> handler is itself a protected action, so I can't call another potentially
>> blocking enqueue from there.
>
> I can see how this would work, with the queue in the same PO as the
> handler as Lorenzen suggested, but it seems messy to me. You need to
> store the Timing_Events somewhere until they're handled, and since
> they're limited that will require using access types. That in turn
> requires doing memory management, and that will probably need another
> task to periodically look at all the events and free those that have
> been handled. This has lots of opportunities for error.
> A simpler approach would be to package up a Time and your job info in a
> record you can put on a priority queue in Time order, and have the
> worker task do a delay until the Time. The only problem with this is
> that you need to have enough tasks to ensure all jobs are started at the
> appropriate time, or a willingness to create a new task if an event is
> queued when there are no workers available. I have used the latter
> approach and it works fine if dynamically created tasks are acceptable.

I'm in no need for strict real time requirements so I can do with this 
softer approach. Thanks for the suggestion.

^ permalink raw reply	[relevance 6%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-24 22:21  6%   ` Jeffrey R. Carter
@ 2016-06-02 21:13  6%     ` Alejandro R. Mosteo
  2016-06-02 23:16  6%       ` Jeffrey R. Carter
  0 siblings, 1 reply; 200+ results
From: Alejandro R. Mosteo @ 2016-06-02 21:13 UTC (permalink / raw)


On 25/05/16 00:21, Jeffrey R. Carter wrote:
> On 05/24/2016 07:39 AM, Mark Lorenzen wrote:
>>
>> If you want to detach the high-priority PO implementing the timer event
>> handler from the PO implementing the job queue, then let a task block
>> on an
>> entry in the first PO and put the job into the second PO. The task is
>> then
>> the active object moving data between the POs and thus detaching them.
>
> This is known as a forwarder. There's a generic forwarder in the
> PragmAda Reusable Components. The main problem with forwarders is that
> there's no easy way to terminate them.

Indeed I was also thinking about this. I can't think of anything besides 
periodical checks to some bail-out flag.

> The PragmARCs are at
>
> pragmada.x10hosting.com
>
> and
>
> github.com/jrcarter

Thanks!


^ permalink raw reply	[relevance 6%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-24 14:22  5% Launching background job from Ada.Real_Time.Timing_Events Alejandro R. Mosteo
  2016-05-24 14:39  6% ` Mark Lorenzen
  2016-05-24 23:52  5% ` Jeffrey R. Carter
@ 2016-05-25  7:23  5% ` Dmitry A. Kazakov
  2016-06-02 21:25  6%   ` Alejandro R. Mosteo
  2 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2016-05-25  7:23 UTC (permalink / raw)


On 24/05/2016 16:22, Alejandro R. Mosteo wrote:

> I'm stuck with something not that strange, so I guess I need another
> viewpoint on it.
>
> I want to trigger, in the future, a possibly long computation in the
> background. For that I had thought of using the built-in Real_Time events.
>
> My idea was to queue the job when the event is triggered, and to have a
> worker thread waiting for jobs in the queue. However, I've just realized
> that the event handler is itself a protected action, so I can't call
> another potentially blocking enqueue from there.

Neither is protected action. To enqueue anything into FIFO you need no 
locking. This is lock-free. To dequeue, provided single consumer there 
is no need to lock anything either. If there are several consumers, you 
use a protected object to dequeue only.

1-to-n: The dequeue is a waitable entry. Once you have got the packet 
out of the queue you process it outside any protected actions.

1-to-1: You use a reset-event implemented using protected object to wake 
up the consumer, which dequeues the packet. Reset event is 
race-condition free to query if the queue is empty and if so, to wait 
for the event.

> Any ideas? Basically, how to trigger another task (without creating it)
> from within a protected handler?

Always by waiting for an entry. E.g. as described above.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de

^ permalink raw reply	[relevance 5%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-24 14:22  5% Launching background job from Ada.Real_Time.Timing_Events Alejandro R. Mosteo
  2016-05-24 14:39  6% ` Mark Lorenzen
@ 2016-05-24 23:52  5% ` Jeffrey R. Carter
  2016-06-02 21:22  6%   ` Alejandro R. Mosteo
  2016-05-25  7:23  5% ` Dmitry A. Kazakov
  2 siblings, 1 reply; 200+ results
From: Jeffrey R. Carter @ 2016-05-24 23:52 UTC (permalink / raw)


On 05/24/2016 07:22 AM, Alejandro R. Mosteo wrote:
>
> My idea was to queue the job when the event is triggered, and to have a worker
> thread waiting for jobs in the queue. However, I've just realized that the event
> handler is itself a protected action, so I can't call another potentially
> blocking enqueue from there.

I can see how this would work, with the queue in the same PO as the handler as 
Lorenzen suggested, but it seems messy to me. You need to store the 
Timing_Events somewhere until they're handled, and since they're limited that 
will require using access types. That in turn requires doing memory management, 
and that will probably need another task to periodically look at all the events 
and free those that have been handled. This has lots of opportunities for error.

A simpler approach would be to package up a Time and your job info in a record 
you can put on a priority queue in Time order, and have the worker task do a 
delay until the Time. The only problem with this is that you need to have enough 
tasks to ensure all jobs are started at the appropriate time, or a willingness 
to create a new task if an event is queued when there are no workers available. 
I have used the latter approach and it works fine if dynamically created tasks 
are acceptable.

-- 
Jeff Carter
"This scene's supposed to be in a saloon, but
the censor cut it out. It'll play just as well
this way." [in a soda fountain]
Never Give a Sucker an Even Break
113


^ permalink raw reply	[relevance 5%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-24 14:39  6% ` Mark Lorenzen
  2016-05-24 15:06  6%   ` Alejandro R. Mosteo
@ 2016-05-24 22:21  6%   ` Jeffrey R. Carter
  2016-06-02 21:13  6%     ` Alejandro R. Mosteo
  1 sibling, 1 reply; 200+ results
From: Jeffrey R. Carter @ 2016-05-24 22:21 UTC (permalink / raw)


On 05/24/2016 07:39 AM, Mark Lorenzen wrote:
>
> If you want to detach the high-priority PO implementing the timer event
> handler from the PO implementing the job queue, then let a task block on an
> entry in the first PO and put the job into the second PO. The task is then
> the active object moving data between the POs and thus detaching them.

This is known as a forwarder. There's a generic forwarder in the PragmAda 
Reusable Components. The main problem with forwarders is that there's no easy 
way to terminate them.

The PragmARCs are at

pragmada.x10hosting.com

and

github.com/jrcarter

-- 
Jeff Carter
"This scene's supposed to be in a saloon, but
the censor cut it out. It'll play just as well
this way." [in a soda fountain]
Never Give a Sucker an Even Break
113


^ permalink raw reply	[relevance 6%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-24 14:39  6% ` Mark Lorenzen
@ 2016-05-24 15:06  6%   ` Alejandro R. Mosteo
  2016-05-24 22:21  6%   ` Jeffrey R. Carter
  1 sibling, 0 replies; 200+ results
From: Alejandro R. Mosteo @ 2016-05-24 15:06 UTC (permalink / raw)


On 24/05/16 16:39, Mark Lorenzen wrote:
> On Tuesday, May 24, 2016 at 4:22:36 PM UTC+2, Alejandro R. Mosteo wrote:
>> Hello all,
>>
>> I'm stuck with something not that strange, so I guess I need another
>> viewpoint on it.
>>
>> I want to trigger, in the future, a possibly long computation in the
>> background. For that I had thought of using the built-in Real_Time events.
>>
>> My idea was to queue the job when the event is triggered, and to have a
>> worker thread waiting for jobs in the queue. However, I've just realized
>> that the event handler is itself a protected action, so I can't call
>> another potentially blocking enqueue from there.
>>
>> Any ideas? Basically, how to trigger another task (without creating it)
>> from within a protected handler?
>>
>> Thanks,
>> Alex.
>
> You can let the PO implementing the job queue be the same as the PO implementing the timing event handler.
>
> If you want to detach the high-priority PO implementing the timer event handler from the PO implementing the job queue, then let a task block on an entry in the first PO and put the job into the second PO. The task is then the active object moving data between the POs and thus detaching them.

Thank you! I don't know what I was thinking...

>
> Regards,
>
> Mark L



^ permalink raw reply	[relevance 6%]

* Re: Launching background job from Ada.Real_Time.Timing_Events
  2016-05-24 14:22  5% Launching background job from Ada.Real_Time.Timing_Events Alejandro R. Mosteo
@ 2016-05-24 14:39  6% ` Mark Lorenzen
  2016-05-24 15:06  6%   ` Alejandro R. Mosteo
  2016-05-24 22:21  6%   ` Jeffrey R. Carter
  2016-05-24 23:52  5% ` Jeffrey R. Carter
  2016-05-25  7:23  5% ` Dmitry A. Kazakov
  2 siblings, 2 replies; 200+ results
From: Mark Lorenzen @ 2016-05-24 14:39 UTC (permalink / raw)


On Tuesday, May 24, 2016 at 4:22:36 PM UTC+2, Alejandro R. Mosteo wrote:
> Hello all,
> 
> I'm stuck with something not that strange, so I guess I need another 
> viewpoint on it.
> 
> I want to trigger, in the future, a possibly long computation in the 
> background. For that I had thought of using the built-in Real_Time events.
> 
> My idea was to queue the job when the event is triggered, and to have a 
> worker thread waiting for jobs in the queue. However, I've just realized 
> that the event handler is itself a protected action, so I can't call 
> another potentially blocking enqueue from there.
> 
> Any ideas? Basically, how to trigger another task (without creating it) 
> from within a protected handler?
> 
> Thanks,
> Alex.

You can let the PO implementing the job queue be the same as the PO implementing the timing event handler.

If you want to detach the high-priority PO implementing the timer event handler from the PO implementing the job queue, then let a task block on an entry in the first PO and put the job into the second PO. The task is then the active object moving data between the POs and thus detaching them.

Regards,

Mark L


^ permalink raw reply	[relevance 6%]

* Launching background job from Ada.Real_Time.Timing_Events
@ 2016-05-24 14:22  5% Alejandro R. Mosteo
  2016-05-24 14:39  6% ` Mark Lorenzen
                   ` (2 more replies)
  0 siblings, 3 replies; 200+ results
From: Alejandro R. Mosteo @ 2016-05-24 14:22 UTC (permalink / raw)


Hello all,

I'm stuck with something not that strange, so I guess I need another 
viewpoint on it.

I want to trigger, in the future, a possibly long computation in the 
background. For that I had thought of using the built-in Real_Time events.

My idea was to queue the job when the event is triggered, and to have a 
worker thread waiting for jobs in the queue. However, I've just realized 
that the event handler is itself a protected action, so I can't call 
another potentially blocking enqueue from there.

Any ideas? Basically, how to trigger another task (without creating it) 
from within a protected handler?

Thanks,
Alex.


^ permalink raw reply	[relevance 5%]

* ANN: Cortex GNAT RTS 20160522
@ 2016-05-22 14:20  4% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2016-05-22 14:20 UTC (permalink / raw)


Available at
https://sourceforge.net/projects/cortex-gnat-rts/files/20160522/

This release includes GNAT Ada Run Time Systems (RTSs) based
on FreeRTOS (http://www.freertos.org) and targeted at boards with
Cortex-M3, -M4, -M4F MCUs (Arduino Due from http://www.arduino.org,
the STM32F4-series evaluation boards from STMicroelectronics at
http://www.st.com).

In each case, the board support for the RTS (configuration for size
and location of Flash, RAM; clock initialization; interrupt naming) is
in $RTS/adainclude. Support for the on-chip peripherals is also
included, in Ada spec files generated by SVD2Ada
(https://github.com/AdaCore/svd2ada).

The Ada source is either original or based on FSF GCC (mainly 4.9.1,
some later releases too).

(1) arduino-due is a Ravenscar-style RTOS based on FreeRTOS from
    http://www.freertos.org for the Arduino Due.

    See arduino-due/COPYING* for licensing terms.

    On-chip peripheral support in atsam3x8e/.

    Tests in test-arduino-due/.

(2) stm32f4 is a Ravenscar-style RTOS based on FreeRTOS from
    http://www.freertos.org for the STM32F4-DISC* board.

    See stm32f4/COPYING* for licensing terms.

    On-chip peripheral support in stm32f40x/.

    Tests in test-stm32f4/.

(3) stm32f429i is a Ravenscar-style RTOS based on FreeRTOS from
    http://www.freertos.org for the STM32F429I-DISC* board.

    See stm32f429i/COPYING* for licensing terms.

    On-chip peripheral support in stm32f429x/.

    Tests in test-stm32f429i/.

In this release,

* There is no longer any dependence on the STMicroelectronics'
  STM32Cube package.

* The support for on-chip peripherals is limited to the
  SVD2Ada-generated spec files. The AdaCore 'bareboard' software
  (currently https://github.com/AdaCore/bareboard, but a name change
  is under consideration) supports the STM32 line.

* Tasking no longer requires an explicit start
  (https://sourceforge.net/p/cortex-gnat-rts/tickets/5/).

* Locking in interrupt-handling protected objects no longer inhibits
  all interrupts, only those of equal or lower priority
  (https://sourceforge.net/p/cortex-gnat-rts/tickets/18/).

The standard packages included (there are more, implementation-specific,
ones) are:

Ada
Ada.Containers
Ada.Containers.Bounded_Hashed_Maps
Ada.Containers.Bounded_Vectors
Ada.Exceptions
Ada.IO_Exceptions
Ada.Interrupts
Ada.Interrupts.Names
Ada.Iterator_Interfaces
Ada.Real_Time
Ada.Streams
Ada.Synchronous_Task_Control
Ada.Tags
Ada.Task_Identification
Interfaces
Interfaces.C
Interfaces.C.Strings
System
System.Assertions
System.Address_To_Access_Conversions
System.Storage_Elements
GNAT
GNAT.Source_Info


^ permalink raw reply	[relevance 4%]

* Re: Roundtrip latency problem using Gnoga, on Linux, when testing at localhost address
  2016-03-31 17:02  4%       ` Olivier Henley
@ 2016-03-31 17:44  4%         ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2016-03-31 17:44 UTC (permalink / raw)


On 2016-03-31 19:02, Olivier Henley wrote:
> On Thursday, March 31, 2016 at 3:39:10 AM UTC-4, Dmitry A. Kazakov wrote:
>
>> Still it could be indication of a problem or a bug. Usual suspects are:
>>
>> 1. The measurement procedure.
>>
>> 1.1. Artifacts of process switching.
>> 1.2. Wrong clock used. System clocks may be very coarse. In many OSes
>> they are driven by the timer interrupts or from an inferior clock
>> source. Real-time clock at the processor's or the front bus' tact must
>> be used in round-trip measurements.
>
> Debian 8 x64 using Adacore GNAT 2015 and within Ada.Real_Time

AFAIK GNAT's Ada.Real_Time and Ada.Calendar use the same time source and 
it must be TSC under Linux.

To test clock quality call Clock twice and compare the results. Good 
clock must have different reading each time you call it.

>> 2. HTTP. It is a very poor protocol. Much depends on the
>> connection/session settings. E.g. if a new session is created for each
>> measurement it is to expect a quite poor performance. Creating and
>> connecting sockets is expensive.
>
> I am using Gnoga and expect everything to go through Websocket and
> not  HTTP (handshake done). I don't suspect my using of the framework, nor
> the framework, to create new connections every time I communicate with a
> particular client.

WebSocket uses a HTTP session. You first establish a HTTP session and 
then switch to WebSocket. An awful idea, but everything related to HTTP 
is awful.

>> 3. Socket settings
>>
>> 3.1. TCP_NO_DELAY and sending packets in full is essential to short
>> latencies. The frame coalescing algorithm timeout depends on the system
>> settings. Usually it is close to 100ms. Which means that you could have
>> sporadic latency spikes depending on the state of the TCP buffer when
>> the traffic is low.
>
> I need to investigate this one.

Yes. This is the major source of latencies. TCP/IP is optimized for 
throughout, not for short latencies.

>> 4. OS, TCP stack system settings
>>
>> 4.1. Poor Ethernet controller, especially bad are integrated ones. The
>> worst are ones connected over USB/COM. Many boards have ones sitting on
>> top of an UART.
>
> ping 127.0.0.1 gives me like 0.02 ms. So to have a ~80ms
> discrepancy,
> I would not suspect my hardware.

OK, loop-back is not related to Ethernet.

>> Then, it could be a software bug. The Simple Components server gets a
>> notification when there is free space in the output buffer, ready to
>> send more data out. When the traffic is low, the output buffer is never
>> full and this means that, in effect, the buffer-ready signal is always
>> set. Thus dealing with the socket output becomes in effect busy waiting.
>> That in turn leads 100% load of the CPU's core running the server. In
>> order to prevent that the server stops waiting for the buffer-ready
>> signal when there was nothing to send. When a new portion of output data
>> appears the socket waiting is resumed. There is a certain timeout to
>> look after the socket regardless. If there is a bug somewhere that
>> prevents the resuming, it may expose itself as sporadically increased
>> latencies during sending data out. The latency must then be close to the
>> timeout value. [This is similar to the effect of TCP_NO_DELAY not set]
>
> Good. In a sense it reassures me because I am effectively sending
> almost nothing, couple of bytes, every half seconds. I should stress
> test and see if it stays the same or even maybe reduce latency.

I would start with TCP_NO_DELAY. Ask David if Gnoga supports it. Note 
that it must be set on both sides if the communication is 
bi-directional. I don't know if it were possible on the client's script 
side.

> Ok but would it hold if I tell you that using Firefox I get around 120ms instead?

That looks consistent with TCP_NO_DELAY being not set.

> What is my best plan to investigate further? Profiling my exec,
> analysing network traffic etc?

In Wireshark (on LAN) you can see the structure of frames. When 
TCP_NO_DELAY is active packets are small because the TCP stack bypasses 
coalescing and sends data as soon as possible regardless the frame size. 
TCP_NO_DELAY is a dangerous thing that leads to flooding the LAN.

If TCP_NO_DELAY does not help and there is a suspicion that there could 
be something wrong with the server and/or client, I would suggest to 
write a small echo server and client program to test QoS of the server 
and the client separately.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de


^ permalink raw reply	[relevance 4%]

* Re: Roundtrip latency problem using Gnoga, on Linux, when testing at localhost address
  @ 2016-03-31 17:02  4%       ` Olivier Henley
  2016-03-31 17:44  4%         ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: Olivier Henley @ 2016-03-31 17:02 UTC (permalink / raw)


On Thursday, March 31, 2016 at 3:39:10 AM UTC-4, Dmitry A. Kazakov wrote:

> Still it could be indication of a problem or a bug. Usual suspects are:
> 
> 1. The measurement procedure.
> 
> 1.1. Artifacts of process switching.
> 1.2. Wrong clock used. System clocks may be very coarse. In many OSes 
> they are driven by the timer interrupts or from an inferior clock 
> source. Real-time clock at the processor's or the front bus' tact must 
> be used in round-trip measurements.

Debian 8 x64 using Adacore GNAT 2015 and within Ada.Real_Time
 
> 2. HTTP. It is a very poor protocol. Much depends on the 
> connection/session settings. E.g. if a new session is created for each 
> measurement it is to expect a quite poor performance. Creating and 
> connecting sockets is expensive.

I am using Gnoga and expect everything to go through Websocket and not HTTP (handshake done). I don't suspect my using of the framework, nor the framework, to create new connections every time I communicate with a particular client.

> 3. Socket settings
> 
> 3.1. TCP_NO_DELAY and sending packets in full is essential to short 
> latencies. The frame coalescing algorithm timeout depends on the system 
> settings. Usually it is close to 100ms. Which means that you could have 
> sporadic latency spikes depending on the state of the TCP buffer when 
> the traffic is low.

I need to investigate this one.


> 4. OS, TCP stack system settings
> 
> 4.1. Poor Ethernet controller, especially bad are integrated ones. The 
> worst are ones connected over USB/COM. Many boards have ones sitting on 
> top of an UART.

ping 127.0.0.1 gives me like 0.02 ms. So to have a ~80ms discrepancy, I would not suspect my hardware.

> Then, it could be a software bug. The Simple Components server gets a 
> notification when there is free space in the output buffer, ready to 
> send more data out. When the traffic is low, the output buffer is never 
> full and this means that, in effect, the buffer-ready signal is always 
> set. Thus dealing with the socket output becomes in effect busy waiting. 
> That in turn leads 100% load of the CPU's core running the server. In 
> order to prevent that the server stops waiting for the buffer-ready 
> signal when there was nothing to send. When a new portion of output data 
> appears the socket waiting is resumed. There is a certain timeout to 
> look after the socket regardless. If there is a bug somewhere that 
> prevents the resuming, it may expose itself as sporadically increased 
> latencies during sending data out. The latency must then be close to the 
> timeout value. [This is similar to the effect of TCP_NO_DELAY not set]

Good. In a sense it reassures me because I am effectively sending almost nothing, couple of bytes, every half seconds. I should stress test and see if it stays the same or even maybe reduce latency.

Ok but would it hold if I tell you that using Firefox I get around 120ms instead?

What is my best plan to investigate further? Profiling my exec, analysing network traffic etc?

Thx 

^ permalink raw reply	[relevance 4%]

* ANN: Cortex GNAT RTS 20160314
@ 2016-03-14 17:42  5% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2016-03-14 17:42 UTC (permalink / raw)


At https://sourceforge.net/projects/cortex-gnat-rts/files/20160314/.

This release includes

* an RTS for the Arduino Due, arduino-due, and a minimal BSP,
  arduino-due-bsp.

* an RTS for the STM32F429I-DISCO, stm32f429i-disco-rtos, based on
  STMicroelectronics' STM32Cube package and FreeRTOS, and a
  corresponding partial BSP, stm32f429i-disco-bsp.

* an RTS for the STM32F429I-DISCO, stm32f429i, based on FreeRTOS, with
  a set of peripheral definition packages created by SVD2Ada.

In this release,

* the Containers support generalized iteration ("for all E of C
  loop"). Note, this is achieved by removing tampering checks. While
  tampering errors are rare, it would be as well to check algorithms
  using a fully-featured desktop compiler.

The standard packages included (there are more, implementation-specific,
ones) are:

Ada
Ada.Containers
Ada.Containers.Bounded_Hashed_Maps
Ada.Containers.Bounded_Vectors
Ada.Exceptions
Ada.IO_Exceptions
Ada.Interrupts
Ada.Interrupts.Names
Ada.Iterator_Interfaces
Ada.Real_Time
Ada.Streams
Ada.Synchronous_Task_Control
Ada.Tags
Ada.Task_Identification
Interfaces
Interfaces.C
Interfaces.C.Strings
System
System.Assertions
System.Address_To_Access_Conversions
System.Storage_Elements
GNAT
GNAT.Source_Info


^ permalink raw reply	[relevance 5%]

* ANN: Cortex GNAT RTS 20160207
@ 2016-02-07 22:45  4% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2016-02-07 22:45 UTC (permalink / raw)


This release is at Sourceforge[1].

This release includes an RTS for the Arduino Due, arduino-due, and a
minimal BSP, arduino-due-bsp.

For the STM32F429I-DISCO, there is one RTS, stm32f429i-disco-rtos, and
one BSP, stm32f429i-disco-bsp.

In this release,

* the Containers support generalized iteration ("for all E of C
  loop"). Note, this is achieved by removing tampering checks. While
  tampering errors are rare, it would be as well to check algorithms
  using a fully-featured desktop compiler.

* FreeRTOS is configured to detect stack overflow (if it is detected,
  the RTS loops inside vApplicationStackOverflowHook()).

The standard packages included (there are more,
implementation-specific, ones) are:

   Ada
   Ada.Containers
   Ada.Containers.Bounded_Hashed_Maps
   Ada.Containers.Bounded_Vectors
   Ada.Exceptions
   Ada.IO_Exceptions
   Ada.Interrupts
   Ada.Interrupts.Names
   Ada.Iterator_Interfaces
   Ada.Real_Time
   Ada.Streams
   Ada.Synchronous_Task_Control
   Ada.Tags
   Ada.Task_Identification
   Interfaces
   Interfaces.C
   Interfaces.C.Strings
   System
   System.Assertions
   System.Address_To_Access_Conversions
   System.Storage_Elements
   GNAT
   GNAT.Source_Info

The software is supplied built with for debugging (-g) and with suitable
optimisation (-Og), using GNAT GPL 2015 on Mac OS X (it should work
out of the box with a Linux-hosted GNAT GPL 2015 cross-compiler, but
will need recompiling for another compiler version).

[1] https://sourceforge.net/projects/cortex-gnat-rts/files/20160207/


^ permalink raw reply	[relevance 4%]

* Re: Abortable Timed Action
  2016-01-06 21:14  0%         ` Anh Vo
@ 2016-01-08 20:24  4%           ` T.G.
  0 siblings, 0 replies; 200+ results
From: T.G. @ 2016-01-08 20:24 UTC (permalink / raw)


On 2016-01-06, Anh Vo <anhvofrcaus@gmail.com> wrote:
> After looking at your original post again, I believe your code
> should work after replacing delay statement by delay until
> statement. The delay until statement does not have time drifting
> issue. In addition, then Entry Finish can be replaced by the
> terminate alternative. The modified version is shown below.

>             select 
>                accept Cancel; 
>             or 
>                delay until (Ada.Calendar.Clock + Timeout); 
>                Put_Line ("Do Something"); 
>             end select; 

The reason why I had an explicit Finish instead of using terminate was
that I was thinking of creating the timer dynamically and then freeing
it with Ada.Unchecked_Deallocation. So I wanted to Finish the task
before freeing it. I'm not sure if calling Free on an access actually
terminates the task Normally.

delay until is an interesting idea. I'm assuming that time drift would
be an issue in periodic actions that repeat at a certain interval, but
in that case delay until could also have issues if it loses some
accuracy on each iteration. For example, modifying the code to run
periodically, with:

      Start_Time : Ada.Calendar.Time;
   begin
      ...
	    accept Exec_After (T : Duration) do
   	       Start_Time := Ada.Calendar.Clock;
	       Timeout    := T;
	    end Exec_After; 
	    Inner : loop
	       select 
		  accept Cancel; 
		  exit Inner;
	       or 
		  delay until (Ada.Calendar.Clock + Timeout); 
		  Put_Line (Duration'Image (Ada.Calendar.Clock - Start_Time));
	       end select; 
	    end loop Inner;

it will drift, however, we can still use delay until but with a
counter, for example:

   task body Timed_Action_Task is 
      Timeout        : Duration;
      Start_Time     : Ada.Calendar.Time;
      Counter        : Positive := 1;
   begin 
      loop 
	 select 
	    accept Exec_After (T : Duration) do 
	       Start_Time := Ada.Calendar.Clock;
	       Timeout    := T;
	       Counter    := 1;
	    end Exec_After; 
	    Inner : loop
	       select 
		  exit Inner;
		  accept Cancel; 
	       or 
		  delay until (Start_Time + (Timeout * Counter));
		  Counter := Counter + 1;
		  Put_Line (Duration'Image (Ada.Calendar.Clock - Start_Time));
	       end select; 
	    end loop Inner;
	 or 
	    terminate;
	 end select; 
      end loop; 
   end Timed_Action_Task;

This avoids the drift from the previous example.

In my actual code, I used Ada.Real_Time.Timing_Events. It ended up
being somewhat complicated, but only because I wanted to pass both
Action and User_Data to the Timer and make a more flexible/reusable
timer. Now after testing the code above, I think I want to recheck my
code for a possible time drift with periodic timed events.


--- news://freenews.netfront.net/ - complaints: news@netfront.net ---

^ permalink raw reply	[relevance 4%]

* Re: Abortable Timed Action
  2015-12-31 18:09  5%       ` T.G.
@ 2016-01-06 21:14  0%         ` Anh Vo
  2016-01-08 20:24  4%           ` T.G.
  0 siblings, 1 reply; 200+ results
From: Anh Vo @ 2016-01-06 21:14 UTC (permalink / raw)


On Thursday, December 31, 2015 at 10:09:30 AM UTC-8, T.G. wrote:
> On 2015-12-31, Anh Vo <anhvofrcaus@gmail.com> wrote:
> > I think accuracy more important than better/simpler way. There is a
> > drifting issue in your codes in term of time since delay statement
> > is involved. In addition, timer has no problem of this kind. If you
> > decide to use timer, take look at
> > http://www.adacore.com/adaanswers/gems/ada-gem-15/. Let me know if
> > have any question.
> >
> > Anh Vo
> 
> Very nice example. I didn't know about Ada.Real_Time.Timing_Events,
> I'll probably go with that. Thanks for the pointer.

After looking at your original post again, I believe your code should work after replacing delay statement by delay until statement. The delay until statement does not have time drifting issue. In addition, then Entry Finish can be replaced by the terminate alternative. The modified version is shown below.

   with Ada.Calendar; use type Ada.Calendar.Time;
   with Ada.Text_Io;  use Ada.Text_Io;
   -- ...

   -- ...
   task type Timed_Action_Task is 
     entry Exec_After (T : Duration); 
     entry Cancel; 
   end Timed_Action_Task; 

   task body Timed_Action_Task is 
      Timeout : Duration; 
   begin 
      loop 
         select 
            accept Exec_After (T : Duration) do 
               Timeout := T; 
            end Exec_After; 
            select 
               accept Cancel; 
            or 
               delay until (Ada.Calendar.Clock + Timeout); 
               Put_Line ("Do Something"); 
            end select; 
         or 
            terminate;
         end select; 
      end loop; 
   end Timed_Action_Task;

^ permalink raw reply	[relevance 0%]

* Re: Abortable Timed Action
  @ 2015-12-31 18:09  5%       ` T.G.
  2016-01-06 21:14  0%         ` Anh Vo
  0 siblings, 1 reply; 200+ results
From: T.G. @ 2015-12-31 18:09 UTC (permalink / raw)


On 2015-12-31, Anh Vo <anhvofrcaus@gmail.com> wrote:
> I think accuracy more important than better/simpler way. There is a
> drifting issue in your codes in term of time since delay statement
> is involved. In addition, timer has no problem of this kind. If you
> decide to use timer, take look at
> http://www.adacore.com/adaanswers/gems/ada-gem-15/. Let me know if
> have any question.
>
> Anh Vo

Very nice example. I didn't know about Ada.Real_Time.Timing_Events,
I'll probably go with that. Thanks for the pointer.

--- news://freenews.netfront.net/ - complaints: news@netfront.net ---

^ permalink raw reply	[relevance 5%]

* Re: A few questions
  2015-11-01 13:42  4% ` brbarkstrom
@ 2015-11-01 13:52  0%   ` Laurent
  0 siblings, 0 replies; 200+ results
From: Laurent @ 2015-11-01 13:52 UTC (permalink / raw)


On Sunday, 1 November 2015 14:42:17 UTC+1, brbar...@gmail.com  wrote:
> You could translate the YYYYMMDD time into a continuous numerical value
> and then use Ada.Real_Time to convert that value to time in seconds from
> some selected starting point.
> 
> The way astronomers track time is to go over to counting seconds from 
> Jan. 0, 2013 BCE.  The variable is called Astronomical Julian Date.
> The current value is fairly large, particularly if you want a time 
> resolution in microseconds.  GPS time is close to Julian Date, but
> uses a starting date closer to the present.
> 
> Seidelmann, P. K., 2006: Explanatory Supplement to the Astronomical
> Almanac, University Science Books, Sausalito, CA
> 
> is the definitive reference.  
> 
> Savage, N., 2015: Split Second, Comm. ACM, 58, No. 9, 12-14
> 
> deals with "The issue of whether to add a `leap second' to square
> the clock with the Earth's orbit pits time specialists against IT."
> (quoting from the index to that issue of CACM).
> 
> To put it simply, Astronomical Julian Date (and relatives) produces 
> a uniform time record in seconds,  It also makes sure that all dates/times
> are reduced to the same time zone at the Greenwich meridian.  The usual
> IT convention (YYYYMMDD) is non-uniform (for example, Feb. may have 28
> or 29 days - while Jul. always has 31).  It would seem that if your
> application might move to a geographically distributed environment,
> the Julian Date would be sensible.  On the other hand, Julian Date is
> not readily interpretable to humans.
> 
> Bruce B.

Thanks for the info but I fear that it is more than overkill. 

It also shows that most "standards" have gotten this status only because things have been like that before and not because they are the best possible solution. 

So if you have a better solution than the actual one but are not part of a large community which supports this, then you can burn it immediately. Only because no one wants to change a thing and prefer to use some crappy solution over changing something and investing time and effort.

Somehow this world sucks.


^ permalink raw reply	[relevance 0%]

* Re: A few questions
  @ 2015-11-01 13:42  4% ` brbarkstrom
  2015-11-01 13:52  0%   ` Laurent
  0 siblings, 1 reply; 200+ results
From: brbarkstrom @ 2015-11-01 13:42 UTC (permalink / raw)


You could translate the YYYYMMDD time into a continuous numerical value
and then use Ada.Real_Time to convert that value to time in seconds from
some selected starting point.

The way astronomers track time is to go over to counting seconds from 
Jan. 0, 2013 BCE.  The variable is called Astronomical Julian Date.
The current value is fairly large, particularly if you want a time 
resolution in microseconds.  GPS time is close to Julian Date, but
uses a starting date closer to the present.

Seidelmann, P. K., 2006: Explanatory Supplement to the Astronomical
Almanac, University Science Books, Sausalito, CA

is the definitive reference.  

Savage, N., 2015: Split Second, Comm. ACM, 58, No. 9, 12-14

deals with "The issue of whether to add a `leap second' to square
the clock with the Earth's orbit pits time specialists against IT."
(quoting from the index to that issue of CACM).

To put it simply, Astronomical Julian Date (and relatives) produces 
a uniform time record in seconds,  It also makes sure that all dates/times
are reduced to the same time zone at the Greenwich meridian.  The usual
IT convention (YYYYMMDD) is non-uniform (for example, Feb. may have 28
or 29 days - while Jul. always has 31).  It would seem that if your
application might move to a geographically distributed environment,
the Julian Date would be sensible.  On the other hand, Julian Date is
not readily interpretable to humans.

Bruce B.


^ permalink raw reply	[relevance 4%]

* Re: Running a preprocessor from GPS?
  @ 2015-07-30 16:15  5%               ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2015-07-30 16:15 UTC (permalink / raw)


EGarrulo <egarrulo@gmail.com> writes:

> KISS solution:
>
>        TickCount := (if System.FreeRTOS.Tasks.In_ISR
>                      then xTaskGetTickCountFromISR
>                      else xTaskGetTickCount)
>        return Tick * Time_Base (TickCount);
>
> or:
>
>        if System.FreeRTOS.Tasks.In_ISR then 
>           TickCount := xTaskGetTickCountFromISR;
>        else 
>           TickCount := xTaskGetTickCount;
>        end if;
>        return Tick * Time_Base (TickCount);

Both of these require Tick_Count (!) to be declared, which adds a little
more verbosity. At least the first means you could declare it constant.

      Tick_Count : constant System.Unsigned_32
        := (if System.FreeRTOS.Tasks.In_ISR
            then xTaskGetTickCountFromISR
            else xTaskGetTickCount);
   begin
      ...

This whole code will need revisiting when I get round to making
Ada.Real_Time.Time capable of running for more than 50 days! at which
point I'll be inhibiting interrupts and managing the 32-to-64 bit
extension, and there'll certainly be an analog of Tick_Count there.

^ permalink raw reply	[relevance 5%]

* [Bounded] Vectors, reference types, and the secondary stack
@ 2015-02-15 16:21  7% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2015-02-15 16:21 UTC (permalink / raw)


It turns out that (GCC 4.9.1) that if you have

   package Interval_Containers
     is new Ada.Containers.Bounded_Vectors
       (Index_Type   => Natural,
        Element_Type => Ada.Real_Time.Time_Span,
        "="          => Ada.Real_Time."=");

   Intervals : Interval_Containers.Vector (5);

and then

   Intervals.Insert_Space (0, 5);
   Intervals (0) := Ada.Real_Time.Milliseconds (50);

then

   function Reference
     (Container : aliased in out Vector;
      Index     : Index_Type) return Reference_Type;

returns its result on the secondary stack!

Why would it need to do that? given the (private) definition

   type Reference_Type
      (Element : not null access Element_Type) is null record;


You ask why I would care. Well, in my STM32F4 RTS the environment task,
in which elaboration happens, isn't actually a task, and doesn't (yet)
have a secondary stack.

The reason it's not a task is that the way to kick off the FreeRTOS
sceduler is to call FreeRTOS.Tasks.Start_Scheduler (aka
vTaskStartScheduler()), which doesn't return unless the scheduler can't
be started; and I haven't found a way to get this behaviour into the
startup code generated by gnatbind, so the poor user has to call it at
the end of their main program.

^ permalink raw reply	[relevance 7%]

* Re: gnat ARM - predefined packages
  @ 2015-01-28 17:30  5%                 ` RasikaSrinivasan
  0 siblings, 0 replies; 200+ results
From: RasikaSrinivasan @ 2015-01-28 17:30 UTC (permalink / raw)


Eventually I found the file (spec for Ada.Interrupts.Names) on my system. It is not in the directory tree where I usually expect. There is a dir called "gnat" in the tree and there is an adainclude and adalib under that. This is where I found the RTS and the specific file.

I don't have the exact dir spec now but I can dig it up later in the night.

It would appear that several other such commands also search in the wrong places. For example the pretty print command from GPS did not work because it could not locate several required specs. (I had with'ed Ada.Real_Time). 

I suspect this will work better with the next GPL version - as indicated in the reply I received from adacore.

cheers, srini

^ permalink raw reply	[relevance 5%]

* ANN: gcc 4.9.1bis for Darwin
@ 2015-01-25 16:41  3% Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2015-01-25 16:41 UTC (permalink / raw)


This is to announce two GCC 4.9.1 compilers, one a Darwin native
compiler (the same as previously uploaded, but can be installed in a
place of your choice) and one a cross-compiler to arm-eabi, aka
arm-none-eabi, as found on the STMicroelectronics[1] STM32F4 series.

Both compilers work on Mavericks and Yosemite.

The compilers are at the usual place[2]. They each have a similar
installation mechanism as that in the GNAT GPL series,so you can choose
where to install them (the default is /opt/gcc-4.9.1, but
/usr/local/gcc-4.9.1 works too; there may be problems with longer
paths). You can install the cross compiler on top of the native one.

The cross-compiler comes without an RTS. You can find suitable RTSs at
[3], together with a compiled copy of stlink (the tools that enable
download to the board and debug). The 20150124 version comes in two
variants: one that just supports the STCube BSP, and - more
interestingly - one that additionally supports Ravenscar tasking via
FreeRTOS[4].

The tasking RTS has the following restrictions (aside from pragma
Profile (Ravenscar)):

   pragma Restrictions (No_Allocators);
   pragma Restrictions (No_Dispatch);
   pragma Restrictions (No_Enumeration_Maps);
   pragma Restrictions (No_Exception_Propagation);
   pragma Restrictions (No_Finalization);
   pragma Restrictions (No_Recursion);
   pragma Restrictions (No_Secondary_Stack);

and the following bugs/features (see the Tickets tab at [3]):

o You have to start tasking by calling FreeRTOS.Tasks.Start_Scheduler
   from your main program (it doesn't return unless something is
   horribly wrong).

o Ada.Real_Time.Clock is only valid for 50 days (and has a tick of 1
  ms).

o The Interrupt_Priority aspect on a PO doesn't affect the actual
  interrupt's priority (it does affect the PO's ceiling priority).

o Some weird interaction between the compiler and the RTS code means
  that a protected spec hides package Interfaces. You can 'use
  Interfaces;' before the protected spec, though.

[1] http://www.st.com
[2]
http://sourceforge.net/projects/gnuada/files/GNAT_GCC%20Mac%20OS%20X/4.9.1bis/
[3] http://sourceforge.net/projects/stm32f4-gnat-rts/files/
[4] http://www.freertos.org


^ permalink raw reply	[relevance 3%]

* Re: Protected handlers & entry bodies
  2015-01-20 22:46  5%       ` Simon Wright
@ 2015-01-21 20:39  0%         ` Randy Brukardt
  0 siblings, 0 replies; 200+ results
From: Randy Brukardt @ 2015-01-21 20:39 UTC (permalink / raw)


"Simon Wright" <simon@pushface.org> wrote in message 
news:lyh9vlnk8v.fsf@pushface.org...
> "Randy Brukardt" <randy@rrsoftware.com> writes:
>
>> I see. Your point is that GNAT is buggy and that's likely to cause 
>> problems
>> in some obscure and non-reproducible cases.
>>
>> But this has nothing to do with the language. Just because there is a
>> permission to do something (use some other task to execute an entry body)
>> does not mean that it should be used, especially if that is potentially
>> causing problems.
>
> Not sure that GNAT's actually buggy. Re-reading C.3.1(17):
>
>   When the aspects Attach_Handler or Interrupt_Handler are specified
>   for a protected procedure, the implementation is allowed to impose
>   implementation-defined restrictions on the corresponding
>   protected_type_declaration and protected_body.
>
> it seems to me it'd be fair to claim that restrictions could be imposed
> on entry bodies. With my current implementation, one such would be to
> disallow the use of Ada.Real_Time.Clock!

Good point. I read that too quickly and confused protected_body with 
subprogram_body.

                     Randy.




^ permalink raw reply	[relevance 0%]

* Re: Protected handlers & entry bodies
  @ 2015-01-20 22:46  5%       ` Simon Wright
  2015-01-21 20:39  0%         ` Randy Brukardt
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2015-01-20 22:46 UTC (permalink / raw)


"Randy Brukardt" <randy@rrsoftware.com> writes:

> I see. Your point is that GNAT is buggy and that's likely to cause problems 
> in some obscure and non-reproducible cases.
>
> But this has nothing to do with the language. Just because there is a 
> permission to do something (use some other task to execute an entry body) 
> does not mean that it should be used, especially if that is potentially 
> causing problems.

Not sure that GNAT's actually buggy. Re-reading C.3.1(17):

   When the aspects Attach_Handler or Interrupt_Handler are specified
   for a protected procedure, the implementation is allowed to impose
   implementation-defined restrictions on the corresponding
   protected_type_declaration and protected_body.

it seems to me it'd be fair to claim that restrictions could be imposed
on entry bodies. With my current implementation, one such would be to
disallow the use of Ada.Real_Time.Clock!

^ permalink raw reply	[relevance 5%]

* Re: Duration for GNAT on ARM
  2014-12-24  0:27  8%     ` Simon Wright
@ 2014-12-24  9:40  4%       ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2014-12-24  9:40 UTC (permalink / raw)


Simon Wright <simon@pushface.org> writes:

> "J-P. Rosen" <rosen@adalog.fr> writes:
>
>> Le 23/12/2014 23:42, Dmitry A. Kazakov a écrit :
>
> Actually, it was me.
>
>>> However, if I do this with both GNAT GPL 2014 and FSF GCC 4.9.1
>>>> cross-compiling to arm-eabi for the STM32F4 family (Cortex M4), I get
>>>> 
>>>>    type Duration is delta 0.020
>>>>      range -((2 ** 31 - 1) * 0.020) ..
>>>>            +((2 ** 31 - 1) * 0.020);
>>>>    for Duration'Small use 0.020;
>>>> 
>>>> I can understand the 32-bit vs 64-bit part - a misguided attempt at
>>>> efficiency, perhaps - but who gets to say that the clock runs at 50
>>>> Hz?
>
>> Duration'small is not related to the accuracy of the hardware clock,
>> it's just the elementary step for time. Ada.Real_Time might be more
>> useful for you.
>
> This is for a Ravenscar RTS, so I have to use Ada.Real_Time.
>
> in GNAT, Ada.Real_Time.Time and Time_Span are both new Durations.
>
> I find the "elementary step for time" concept somewhat confusing. I have
> a clock which ticks every millisecond, but the 32-bit Standard.Duration,
> Ada.Real_Time.Time, and Ada.Real_Time.Time_Span all have the same
> granularity of 20 ms!

I get the point, now.

I've put this in Ada.Real_Time:

      Time_Unit  : constant := 1.0e-9;

      [...]

   private
      type Time_Base is
        delta 0.000000001
        range -((2 ** 63 - 1) * 0.000000001) .. +((2 ** 63 - 1) * 0.000000001);
      for Time_Base'Small use 0.000000001;
      --  Replaces Duration, which has a different representation on
      --  systems with 32-bit Duration.

      type Time is new Time_Base;

      [...]

      type Time_Span is new Time_Base;

      [...]

      Time_Span_Unit  : constant Time_Span := 1.0e-9;

      Tick : constant Time_Span := 0.001;

> Oh. AdaCore's arm-eabi Ada.Real_Time works with very low-level stuff to
> provide for 50 years of running, and doesn't use Duration. For the
> present work, I'm quite happy not to meet that requirement!

They're based on the processor high-res time base, which is typically a
32-bit register that overflows after 7 seconds ... so lots of work
extending that to the 50 years requirement.

When I worked with PowerPC boards (from Radstone, now part of GE
Intelligent Platforms) the on-board crystals were good for 50 ppm, about
5 seconds/day, so after 50 years that's over a day!

My present implementation is only valid up to 10 days. Quite good enough
for school projects, I think, but will consider extending.

> It would be good to work out why my clock is running fast by almost a
> factor of 2 ...

With the above changes, all is good.

^ permalink raw reply	[relevance 4%]

* Re: Duration for GNAT on ARM
  2014-12-23 22:52  5%   ` J-P. Rosen
@ 2014-12-24  0:27  8%     ` Simon Wright
  2014-12-24  9:40  4%       ` Simon Wright
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2014-12-24  0:27 UTC (permalink / raw)


"J-P. Rosen" <rosen@adalog.fr> writes:

> Le 23/12/2014 23:42, Dmitry A. Kazakov a écrit :

Actually, it was me.

>> However, if I do this with both GNAT GPL 2014 and FSF GCC 4.9.1
>>> cross-compiling to arm-eabi for the STM32F4 family (Cortex M4), I get
>>> 
>>>    type Duration is delta 0.020
>>>      range -((2 ** 31 - 1) * 0.020) ..
>>>            +((2 ** 31 - 1) * 0.020);
>>>    for Duration'Small use 0.020;
>>> 
>>> I can understand the 32-bit vs 64-bit part - a misguided attempt at
>>> efficiency, perhaps - but who gets to say that the clock runs at 50
>>> Hz?

> Duration'small is not related to the accuracy of the hardware clock,
> it's just the elementary step for time. Ada.Real_Time might be more
> useful for you.

This is for a Ravenscar RTS, so I have to use Ada.Real_Time.

in GNAT, Ada.Real_Time.Time and Time_Span are both new Durations.

I find the "elementary step for time" concept somewhat confusing. I have
a clock which ticks every millisecond, but the 32-bit Standard.Duration,
Ada.Real_Time.Time, and Ada.Real_Time.Time_Span all have the same
granularity of 20 ms!

Oh. AdaCore's arm-eabi Ada.Real_Time works with very low-level stuff to
provide for 50 years of running, and doesn't use Duration. For the
present work, I'm quite happy not to meet that requirement!

It would be good to work out why my clock is running fast by almost a
factor of 2 ...


^ permalink raw reply	[relevance 8%]

* Re: Duration for GNAT on ARM
    2014-12-23 22:52  5%   ` J-P. Rosen
@ 2014-12-24  0:04  5%   ` Simon Wright
  1 sibling, 0 replies; 200+ results
From: Simon Wright @ 2014-12-24  0:04 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

>> On the STM32's with STMicroelectronics' HAL, the tick is 1 kHz.
>
> But does the RTL assumed by the compiler use this clock?

I'm writing the RTS, it should be up to me to decide the granularity!

Reading the source, one approach would be to tell the compiler to use a
64-bit clock: towards the end of system.ads, I have

   Duration_32_Bits          : constant Boolean := True;

so I could set it to False and put up with some 64-bit arithmetic in
Ada.Real_Time.

^ permalink raw reply	[relevance 5%]

* Re: Duration for GNAT on ARM
  @ 2014-12-23 22:52  5%   ` J-P. Rosen
  2014-12-24  0:27  8%     ` Simon Wright
  2014-12-24  0:04  5%   ` Simon Wright
  1 sibling, 1 reply; 200+ results
From: J-P. Rosen @ 2014-12-23 22:52 UTC (permalink / raw)


Le 23/12/2014 23:42, Dmitry A. Kazakov a écrit :
> However, if I do this with both GNAT GPL 2014 and FSF GCC 4.9.1
>> cross-compiling to arm-eabi for the STM32F4 family (Cortex M4), I get
>> 
>>    type Duration is delta 0.020
>>      range -((2 ** 31 - 1) * 0.020) ..
>>            +((2 ** 31 - 1) * 0.020);
>>    for Duration'Small use 0.020;
>> 
>> I can understand the 32-bit vs 64-bit part - a misguided attempt at
>> efficiency, perhaps - but who gets to say that the clock runs at 50 Hz?
Duration'small is not related to the accuracy of the hardware clock,
it's just the elementary step for time. Ada.Real_Time might be more
useful for you.

-- 
J-P. Rosen
Adalog
2 rue du Docteur Lombard, 92441 Issy-les-Moulineaux CEDEX
Tel: +33 1 45 29 21 52, Fax: +33 1 45 29 25 00
http://www.adalog.fr


^ permalink raw reply	[relevance 5%]

* Re: how to analyze clock drift
  @ 2014-11-24  1:15  4%                         ` Dennis Lee Bieber
  0 siblings, 0 replies; 200+ results
From: Dennis Lee Bieber @ 2014-11-24  1:15 UTC (permalink / raw)


On Sun, 23 Nov 2014 21:15:05 +0100, Emanuel Berg <embe8573@student.uu.se>
declaimed the following:

>I can explain that, and then add like, "If you were to
>employ this system in a critical setting, it would be
>necessary to have a much more reliable clock to
>trigger the interrupts. Although you can have widely
>diverging results due to many factors, to illustrate
>the lack of periodicity, and to some degree how that
>behaves and fluctuates [I'm referring to the stats
>here], run the program with `-l' and study the
>outputs..." (I'm not going to put it exactly like that,
>but you get the idea.) Is that better?

	Well -- but you haven't /tested/ the reliability of the clock itself;
only of the latency in responding to it...

	And just to put this back into an Ada context, I did spend some time
hacking (and I confess to the folks for just how badly hacked this is...
I've not used the packages before, and taking stuff from one package
internal form to something I can manipulate for stats took some klutzing
around) my attempt at collecting some data.

-=-=-=-=-=-
-- Simple experiment of Timer/Clock operation

with Text_IO; use Text_IO;
with Ada.Real_Time;
with Ada.Numerics.Generic_Elementary_Functions;

procedure Timer is

   package Rt renames Ada.Real_Time;

   type Statistic is digits 15;
   package M is new Ada.Numerics.Generic_Elementary_Functions (Statistic);


   procedure Runner (Ivl : Rt.Time_Span) is
      Num_Samples : constant Integer := 500;

      Samples     : array (1 .. Num_Samples) of Statistic;

      -- statistics stuff
      Sum         : Statistic := 0.0;
      Sum_Var     : Statistic := 0.0;
      Mean        : Statistic;
      Min         : Statistic;
      Max         : Statistic;
      Variance    : Statistic;

      Start       : Rt.Time;
      Stop        : Rt.Time;

      Log_File : File_Type;

      use type Rt.Time_Span;

   begin
      Put_Line ("Generating data for Time span: "
		& Duration'Image (Rt.To_Duration (Ivl)));

      Create (File => Log_File,
	      Mode => Out_File,
	      Name => "T"
	      & Duration'Image (Rt.To_Duration (Ivl))
	      & ".log");

      New_Line (Log_File);
      Put_Line (Log_File, "Data for Rt.Time span: "
		& Duration'Image (Rt.To_Duration (Ivl)));
      New_Line (Log_File);

      -- Just a bit of Rt.Time waster before starting actual loop
      -- probably not needed as I'm capturing the Rt.Clock before
      -- and after the delay statement
      delay until Rt.Clock + Ivl + Ivl;

      for I in 1 .. Num_Samples loop

	 -- capture the Rt.Clock at the start of the Rt.Time delay
	 Start := Rt.Clock;

	 -- delay until the captured Rt.Clock plus one Rt.Time-span interval
	 delay until Start + Ivl;

	 -- capture the Rt.Clock after the delay expired
	 Stop := Rt.Clock;

	 -- record the difference between stop and start Rt.Clock values
	 -- less the expected interval;
	 Put_Line (Log_File, Duration'Image (
	    Rt.To_Duration (Stop - Start - Ivl)));
	 Samples (I) := Statistic (Rt.To_Duration (Stop - Start - Ivl));

      end loop;

      -- compute statistics
      Min := Samples (1);
      Max := Samples (1);

      for I in 1 .. Num_Samples loop
	 Sum := Sum + Samples (I);
	 if Samples (I) > Max then
	    Max := Samples (I);
	 end if;
	 if Samples (I) < Min then
	    Min := Samples (I);
	 end if;
      end loop;

      Mean := Sum / Statistic (Num_Samples);

      for I in 1 .. Num_Samples loop
	 Sum_Var := Sum_Var + (Samples (I) - Mean) * (Samples (I) - Mean);
      end loop;
      Variance := Sum_Var / Statistic (Num_Samples - 1);


      Put_Line ("Statistics");
      New_Line;

      Put_Line ("Max:       " & Statistic'Image (Max));
      Put_Line ("Min:       " & Statistic'Image (Min));
      Put_Line ("Mean:      " & Statistic'Image (Mean));
--        Put_Line ("Variance:  " & Statistic'Image (Variance));
      Put_Line ("Std. Dev.: " & Statistic'Image (M.Sqrt (Variance)));

      New_Line(5);

   end Runner;

begin

   Put_Line ("Time Span Unit is " &
	       Duration'Image (Rt.To_Duration (Rt.Time_Span_Unit)));
   New_Line;

   Runner (Rt.Nanoseconds (1));
   Runner (Rt.Nanoseconds (10));
   Runner (Rt.Nanoseconds (100));
   Runner (Rt.Microseconds (1));
   Runner (Rt.Microseconds (10));
   Runner (Rt.Microseconds (100));
   Runner (Rt.Milliseconds (1));
   Runner (Rt.Milliseconds (10));
   Runner (Rt.Milliseconds (100));

end Timer;
-=-=-=-=-
Time Span Unit is  0.000000001

Generating data for Time span:  0.000000001
Statistics

Max:        8.45100000000000E-06
Min:        3.00000000000000E-07
Mean:       8.97321999999994E-07
Std. Dev.:  4.72299434498552E-07





Generating data for Time span:  0.000000010
Statistics

Max:        1.80100000000000E-06
Min:        2.91000000000000E-07
Mean:       8.82286000000004E-07
Std. Dev.:  1.24592289815071E-07





Generating data for Time span:  0.000000100
Statistics

Max:        1.40900000000000E-06
Min:        2.01000000000000E-07
Mean:       7.67528000000000E-07
Std. Dev.:  1.59364913224758E-07





Generating data for Time span:  0.000001000
Statistics

Max:        8.12000000000000E-07
Min:        5.09000000000000E-07
Mean:       7.43505999999995E-07
Std. Dev.:  1.25971025885818E-07





Generating data for Time span:  0.000010000
Statistics

Max:        9.31900000000000E-06
Min:        2.63000000000000E-07
Mean:       6.92286000000001E-07
Std. Dev.:  9.61985163666378E-07





Generating data for Time span:  0.000100000
Statistics

Max:        1.59120000000000E-05
Min:        2.15000000000000E-07
Mean:       7.22622000000002E-07
Std. Dev.:  1.10564358388459E-06





Generating data for Time span:  0.001000000
Statistics

Max:        5.10477000000000E-04
Min:        3.43000000000000E-07
Mean:       2.97962600000000E-06
Std. Dev.:  3.19996443996105E-05





Generating data for Time span:  0.010000000
Statistics

Max:        5.31683000000000E-04
Min:        4.19000000000000E-07
Mean:       5.65434000000001E-06
Std. Dev.:  4.44572946856412E-05





Generating data for Time span:  0.100000000
Statistics

Max:        5.01349000000000E-04
Min:        5.74000000000000E-07
Mean:       3.99113399999998E-06
Std. Dev.:  3.06653091148658E-05

-=-=-=-=-

	One thing not seen in the above, is that under Windows, there are
uncontrollable events that will throw a data point out to the extreme...
Look at the millisecond data (0.001). The max latency was 5.1E-4, while the
mean was 2.9E-6. In a run of 500 samples, only 2 or 3 data points jumped to
that high value. That's a sign of the OS doing some house-keeping and
blocking the program from responding. But to see it requires plotting the
data -- once seen, one can attempt to explain that data point. Excluding
those data points will bring the mean down a small amount, but will reduce
the standard deviation significantly.

	Also note that for intervals less than 1microsecond, the latency swamps
the delay. Even for 1microsecond, the latency is 0.7microseconds (the
numbers shown above are AFTER the expected delay value has been subtracted
from the stop-start clock times, leaving only the latency from delay
expiration to the read).

	
-- 
	Wulfraed                 Dennis Lee Bieber         AF6VN
    wlfraed@ix.netcom.com    HTTP://wlfraed.home.netcom.com/


^ permalink raw reply	[relevance 4%]

* Re: STM32F4 Discovery, communication and libraries
  2014-08-30 22:00  0%                         ` Roy Emmerich
@ 2014-09-01 20:15  6%                           ` Niklas Holsti
  0 siblings, 0 replies; 200+ results
From: Niklas Holsti @ 2014-09-01 20:15 UTC (permalink / raw)


On 14-08-31 01:00 , Roy Emmerich wrote:
> On Friday, 29 August 2014 21:41:18 UTC+2, Niklas Holsti  wrote:
>> On 14-08-29 19:47 , Roy Emmerich wrote:
  ...
>>> This device will effectively aggregate the data from all of these
>>> devices into one, unified format and send control signals to the
>>> generator/inverters.
>> 
>> What is the highest control frequency, or shortest deadline or
>> response time, required of the SW?
> 
> Okay, some new terminology for me here. For this particular
> application the response time doesn't have to be very fast (a few
> seconds). 

Then you can probably ignore all interrupt-handling and just poll for
I/O completion -- if that is much simpler to do.

> ... As this kind of control is
> a lot more dynamic, a much faster response time would be required (20
> ms thumb suck value, considering one 50 Hz period is 20 ms long).

That might or might not require interrupt-handling -- depends on your
overall design.

>>> ... making it important for it to be a low power device (e.g.
>>> much less than say a beaglebone black embedded Linux board), able
>>> to run on a battery for at least 3 days, preferably much more
>> 
>> You may have to modify the Board Support Package and/or the kernel
>> to let the processor sleep between clock interrupts. I don't know
>> if the AdaCore ARM BSP has that ability off-the-shelf.
> 
> Is there an AdaCore ARM BSP yet? I thought this is what Mike Silva
> was referring to when he said:
> 
> "I know that AdaCore is working on comms libraries for the ARM Cortex
> M parts, but I don't know anything about the projected
> availability."
> 
> assuming this would include stuff such as I2C, SPI, UART, etc. which
> is normally also part of the BSP?

In my experience (space domain), the BSP (at least when it comes from a
compiler vendor) usually includes only the functions needed to make the
compiler's run-time system work. For Ada/Ravenscar, this means mainly
that task switching and protected objects work as expected (including
POs used as interrupt handlers) and that some timer or clock HW is
configured to drive Ada.Real_Time and the "delay until" statements. I/O
drivers are not (in my domain) typically included in the BSP -- well,
perhaps the BSP contains a simple serial-port driver to make some
emasculated form of Ada.Text_IO work. I/O drivers typically come separately.

For ground-based embedded systems, I have seen that some compiler or
chip vendors package I/O drivers with their BSPs. Perhaps Mike Silva is
talking about some AdaCore activity in that direction.

> Speaking of which...in order to feel like I'm making progress and Ada
> is going to work for me, I really need to get connecting to my
> peripherals. The only way I can see it happening within the next week
> is to call the STM C drivers supplied with their BSP. Does this make
> sense?

Very much so, at least if the C drivers are designed as a passive
library which does not rely on any specific kernel.

>>> It must keep accurate time (syncing once a day via GPS)

Must the SW actions be accurately synchronized with GPS -- for example,
sample something exactly at the GPS pulse-per-second pulse -- or is it
enough that the SW can accurately label each action/sample with the GPS
time when the sample was taken?

>>> and
>>> (periodically/in emergency) make the data available remotely
>>> (via GPRS).
>> 
>> Time in a Ravenscar system is provided by the predefined package 
>> Ada.Real_Time. It is good for relative timing in seconds and ticks,
>> but does not provide calendar date and time. Probably you will have
>> to write your own Calendar-like package which is synchronised with
>> GPS. Not a very big job.
> 
> Maybe not if you know what you're doing ;)
> 
> This is where it gets a bit vague for me. The STM32F4 has an on-board
> RTC with full calendar functionality.

Nice.

> My thinking is at start up and
> then once a day to enter a "clock_sync" state, fire up the GPS
> receiver, somehow sync the processor's RTC and then continue with
> normal operation.

By "processor's RTC", you mean the one with full calendar functionality?
Sounds like a good plan, if that RTC device allows such synchronisation.

I would not try to sync or adjust whatever HW is driving Ada.Real_Time,
but would let that run in its own time. If necessary, I would adjust the
period of the cyclic tasks to keep them in phase with the GPS and/or the
RTC. That is, if a 1 Hz task finds that it is falling behind -- doing
fewer cycles than there are GPS/RTC 1-second ticks -- it would do a few
"delay untils" with a smaller period than 1 s until it has caught up.

> If I need the absolute date/time I can just get it
> from the RTC, so I don't know why I would want to use the
> Ada.Calendar functionality in the first place. Could you shed some
> light on this?

I agree, you don't need Ada.Calendar if you have a calendar-capable RTC
and do not need to do date/time calculations such as finding the
calendar date of "now + 100_000 seconds".

From what I understand of your application, I think you should be fine
with Ada.Real_Time and the RTC.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
      .      @       .


^ permalink raw reply	[relevance 6%]

* Re: STM32F4 Discovery, communication and libraries
  2014-08-29 19:41  3%                       ` Niklas Holsti
@ 2014-08-30 22:00  0%                         ` Roy Emmerich
  2014-09-01 20:15  6%                           ` Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Roy Emmerich @ 2014-08-30 22:00 UTC (permalink / raw)


On Friday, 29 August 2014 21:41:18 UTC+2, Niklas Holsti  wrote:
> On 14-08-29 19:47 , Roy Emmerich wrote:
> > My requirements for dynamic behaviour don't extend so far as to be
> > plug and play ready. What I do want, being a modular hardware
> > platform, is to define, in a configuration file, which hardware
> > modules are plugged into which socket. At start up the supervisor
> > will read this file and instantiate the relevant software modules.
> 
> So the Ada program contains SW modules that can handle all known and
> possible hardware modules, but the SW modules are all "data/table
> driven" in the sense that the supervisor can tell each SW module where
> (in which socket, &c) its HW, if any, can be found?

Yes.

> As far as I can see, the only problem that the Ravenscar profile can
> cause for that design is the restriction No_Dynamic_Attachment, which
> means that the connection between an interrupt source and its handler
> must be established at elaboration time, by pragmas or aspects, and not
> dynamically using a call of Ada.Interrupts.Attach_Handler.
> 
> In principle, the configuration file could be read at elaboration time,
> and could provide the interrupt numbers to be used in the pragma/aspect
> Attach_Handler. However, doing lots of computation at elaboration time
> can make it tricky for the compiler to find a feasible elaboration order
> (especially if the program has tasks).
> 
> The other solution is to attach handlers to all interrupt sources
> statically, but to decide in each handler, at run time, based on the
> configuration data, which SW module is to handle the interrupt, and to
> call the suitable operation from that SW module. A kind of indirection step.

Okay. I think I got that.

> > This device will effectively aggregate the
> > data from all of these devices into one, unified format and send
> > control signals to the generator/inverters.
> 
> What is the highest control frequency, or shortest deadline or response
> time, required of the SW?

Okay, some new terminology for me here. For this particular application the response time doesn't have to be very fast (a few seconds). It will be monitoring battery state of charge and active power and turning the generator on or off. I do foresee the need to do reactive power control in larger off-grid systems. For this the phase shift between voltage and current is normally measured by a CE/UL certified power analyser (legal/safety issues) and transmitted, once again, via MODBUS RTU, to my device. As this kind of control is a lot more dynamic, a much faster response time would be required (20 ms thumb suck value, considering one 50 Hz period is 20 ms long). Sorry that it is still so vague. A bit of guidance wouldn't go amiss :)

> > ... making it
> > important for it to be a low power device (e.g. much less than say a
> > beaglebone black embedded Linux board), able to run on a battery for
> > at least 3 days, preferably much more
> 
> You may have to modify the Board Support Package and/or the kernel to
> let the processor sleep between clock interrupts. I don't know if the
> AdaCore ARM BSP has that ability off-the-shelf.

Is there an AdaCore ARM BSP yet? I thought this is what Mike Silva was referring to when he said:

"I know that AdaCore is working on comms libraries for the ARM Cortex M parts, but I don't know anything about the projected availability."

assuming this would include stuff such as I2C, SPI, UART, etc. which is normally also part of the BSP?

Speaking of which...in order to feel like I'm making progress and Ada is going to work for me, I really need to get connecting to my peripherals. The only way I can see it happening within the next week is to call the STM C drivers supplied with their BSP. Does this make sense?

> > It must keep accurate time (syncing once a day via GPS)
> > and (periodically/in emergency) make the data available remotely (via
> > GPRS).
> 
> Time in a Ravenscar system is provided by the predefined package
> Ada.Real_Time. It is good for relative timing in seconds and ticks, but
> does not provide calendar date and time. Probably you will have to write
> your own Calendar-like package which is synchronised with GPS. Not a
> very big job.

Maybe not if you know what you're doing ;)

This is where it gets a bit vague for me. The STM32F4 has an on-board RTC with full calendar functionality. My thinking is at start up and then once a day to enter a "clock_sync" state, fire up the GPS receiver, somehow sync the processor's RTC and then continue with normal operation. If I need the absolute date/time I can just get it from the RTC, so I don't know why I would want to use the Ada.Calendar functionality in the first place. Could you shed some light on this?


^ permalink raw reply	[relevance 0%]

* Re: STM32F4 Discovery, communication and libraries
  @ 2014-08-29 19:41  3%                       ` Niklas Holsti
  2014-08-30 22:00  0%                         ` Roy Emmerich
  0 siblings, 1 reply; 200+ results
From: Niklas Holsti @ 2014-08-29 19:41 UTC (permalink / raw)


On 14-08-29 19:47 , Roy Emmerich wrote:
> On Friday, 29 August 2014 15:06:07 UTC+2, Dennis Lee Bieber  wrote:
>> It works if the entire system including the "user application"
>> level is built "as one". It is NOT a very dynamic arrangement
>> wherein you may plug in a new sensor and have it magically install
>> itself to some list of sensors to be reported.
> 
> My requirements for dynamic behaviour don't extend so far as to be
> plug and play ready. What I do want, being a modular hardware
> platform, is to define, in a configuration file, which hardware
> modules are plugged into which socket. At start up the supervisor
> will read this file and instantiate the relevant software modules.

So the Ada program contains SW modules that can handle all known and
possible hardware modules, but the SW modules are all "data/table
driven" in the sense that the supervisor can tell each SW module where
(in which socket, &c) its HW, if any, can be found?

As far as I can see, the only problem that the Ravenscar profile can
cause for that design is the restriction No_Dynamic_Attachment, which
means that the connection between an interrupt source and its handler
must be established at elaboration time, by pragmas or aspects, and not
dynamically using a call of Ada.Interrupts.Attach_Handler.

In principle, the configuration file could be read at elaboration time,
and could provide the interrupt numbers to be used in the pragma/aspect
Attach_Handler. However, doing lots of computation at elaboration time
can make it tricky for the compiler to find a feasible elaboration order
(especially if the program has tasks).

The other solution is to attach handlers to all interrupt sources
statically, but to decide in each handler, at run time, based on the
configuration data, which SW module is to handle the interrupt, and to
call the suitable operation from that SW module. A kind of indirection step.

> This device will effectively aggregate the
> data from all of these devices into one, unified format and send
> control signals to the generator/inverters.

What is the highest control frequency, or shortest deadline or response
time, required of the SW?

> ... making it
> important for it to be a low power device (e.g. much less than say a
> beaglebone black embedded Linux board), able to run on a battery for
> at least 3 days, preferably much more

You may have to modify the Board Support Package and/or the kernel to
let the processor sleep between clock interrupts. I don't know if the
AdaCore ARM BSP has that ability off-the-shelf.

> It must keep accurate time (syncing once a day via GPS)
> and (periodically/in emergency) make the data available remotely (via
> GPRS).

Time in a Ravenscar system is provided by the predefined package
Ada.Real_Time. It is good for relative timing in seconds and ticks, but
does not provide calendar date and time. Probably you will have to write
your own Calendar-like package which is synchronised with GPS. Not a
very big job.

> Let's be frank. This is not a satellite. I WON'T be doing any
> schedulability analyses.

AFAIK few satellites are subjected to formal schedulability analysis...
typically, some kind of "nominal worst-case scenario" is defined and a
simple computation similar to response-time analysis is used to
demonstrate that all important ("hard real time") tasks are fast enough
in this scenario, and that a reasonable fraction of CPU time is left for
the less urgent tasks.

> Today Ada seems like a very good fit, no?

I think so.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
      .      @       .


^ permalink raw reply	[relevance 3%]

* Trouble with Timers on the ARM
@ 2014-08-13  6:24  7% williamjthomas7777
  0 siblings, 0 replies; 200+ results
From: williamjthomas7777 @ 2014-08-13  6:24 UTC (permalink / raw)


I'm using the latest GNAT ARM Elf download (Windows) with the STM32F4 Discovery Board.

The code ends up spinning in the last chance handler (the code generates an exception). The code runs on the Windows x86 native compiler fine.

Am I missing something special that has to be done on the ARM target or with the ARM RTS?

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

with Last_Chance_Handler;  pragma Unreferenced (Last_Chance_Handler);
with System;

with Timer_Pack;

procedure Timer_Main is
   pragma Priority (System.Priority'First);
begin
   Timer_Pack.Set_Timer;
   loop
      null;
   end loop;
end Timer_Main;

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

with Ada.Real_Time.Timing_Events; use Ada.Real_Time.Timing_Events;

package Timer_Pack is

  procedure Set_Timer;

   protected The_Timer is
     procedure The_Callback ( Event : in out Timing_Event );
   private
     State   : Boolean := False;
   end The_Timer;

end Timer_Pack;

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

with Ada.Real_Time; use Ada.Real_Time;

package body Timer_Pack is

   The_Event : Timing_Event;
   R1        : constant Integer := 500;

   procedure Set_Timer is
   begin
     Set_Handler
       (The_Event,
        Clock+Milliseconds(R1),
        The_Timer.The_Callback'Access);
   end Set_Timer;

   protected body The_Timer is

     procedure The_Callback ( Event : in out Timing_Event ) is
     begin
       State := not State;
       Set_Handler
         (Event,
          Clock+Milliseconds(R1),
          The_Timer.The_Callback'Access);
     end The_Callback;

   end The_Timer;

end Timer_Pack;

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

with System;

package Last_Chance_Handler is

   procedure Last_Chance_Handler (Msg : System.Address; Line : Integer);
   pragma Export (C, Last_Chance_Handler, "__gnat_last_chance_handler");
   pragma No_Return (Last_Chance_Handler);

end Last_Chance_Handler;

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

package body Last_Chance_Handler is

   procedure Last_Chance_Handler (Msg : System.Address; Line : Integer) is
      pragma Unreferenced (Msg, Line);
   begin
      --  No return procedure.
      pragma Warnings (Off, "*rewritten as loop");
      <<spin>> goto spin;   -- yes, a goto!
      pragma Warnings (On, "*rewritten as loop");
   end Last_Chance_Handler;

end Last_Chance_Handler;

^ permalink raw reply	[relevance 7%]

* Re: ARM Compiler Locks Up on Declaration of Timing_Event
  2014-08-08 11:21  6% ARM Compiler Locks Up on Declaration of Timing_Event williamjthomas7777
@ 2014-08-08 12:46  0% ` williamjthomas7777
  0 siblings, 0 replies; 200+ results
From: williamjthomas7777 @ 2014-08-08 12:46 UTC (permalink / raw)


On Friday, August 8, 2014 7:21:39 AM UTC-4, williamjt...@gmail.com wrote:
> When I take the LED demo and add this package to it and then "with" it from the main program the compiler locks up (starts to compile, never returns). I'm not using a local timer which is restricted. Please show me the error its choking on.
> 
> 
> 
> with Ada.Real_Time.Timing_Events; 
> 
> use Ada.Real_Time.Timing_Events;
> 

Too many late nights! Forget the post.

> 
> 
> package Timer_Pack is
> 
> 
> 
>    Event_1 : Timing_Event;
> 
>    
> 
>    R1 : constant Integer := 500;
> 
> 
> 
>   procedure Initialize;
> 
> 
> 
>    protected Timers is
> 
>      procedure Rate_1 ( Event : in out Timing_Event );
> 
>    private
> 
>      State : Boolean := False;
> 
>    end Timers;
> 
> 
> 
> end Timer_Pack;
> 
> 
> 
> with LEDs; use LEDs;
> 
> 
> 
> package body Timer_Pack is
> 
> 
> 
>    procedure Initialize is
> 
>    begin
> 
>      Set_Handler(Event1,Milliseconds(R1),Rate_1'Access);
> 
>    end Initialize;
> 
> 
> 
>     protected body Timers is
> 
> 
> 
>      procedure Rate_1 ( Event : in out Timing_Event ) is
> 
>      begin
> 
>         State := not State;
> 
>         if 
> 
>           State 
> 
>         then 
> 
>           On(Green); 
> 
>         else 
> 
>           Off(Green); 
> 
>         end if;
> 
>         Set_Handler(Event,Milliseconds(R1),Current_Event_Handler(Event));
> 
>      end Rate_1;
> 
> 
> 
>    end Timers;
> 
> 
> 
> end Timer_Pack;



^ permalink raw reply	[relevance 0%]

* ARM Compiler Locks Up on Declaration of Timing_Event
@ 2014-08-08 11:21  6% williamjthomas7777
  2014-08-08 12:46  0% ` williamjthomas7777
  0 siblings, 1 reply; 200+ results
From: williamjthomas7777 @ 2014-08-08 11:21 UTC (permalink / raw)


When I take the LED demo and add this package to it and then "with" it from the main program the compiler locks up (starts to compile, never returns). I'm not using a local timer which is restricted. Please show me the error its choking on.

with Ada.Real_Time.Timing_Events; 
use Ada.Real_Time.Timing_Events;

package Timer_Pack is

   Event_1 : Timing_Event;
   
   R1 : constant Integer := 500;

  procedure Initialize;

   protected Timers is
     procedure Rate_1 ( Event : in out Timing_Event );
   private
     State : Boolean := False;
   end Timers;

end Timer_Pack;

with LEDs; use LEDs;

package body Timer_Pack is

   procedure Initialize is
   begin
     Set_Handler(Event1,Milliseconds(R1),Rate_1'Access);
   end Initialize;

    protected body Timers is

     procedure Rate_1 ( Event : in out Timing_Event ) is
     begin
        State := not State;
        if 
          State 
        then 
          On(Green); 
        else 
          Off(Green); 
        end if;
        Set_Handler(Event,Milliseconds(R1),Current_Event_Handler(Event));
     end Rate_1;

   end Timers;

end Timer_Pack;


^ permalink raw reply	[relevance 6%]

* Re: Benchmark Ada, please
  2014-07-05 12:34  5% ` Guillaume Foliard
@ 2014-07-05 13:00  0%   ` Niklas Holsti
  0 siblings, 0 replies; 200+ results
From: Niklas Holsti @ 2014-07-05 13:00 UTC (permalink / raw)


On 14-07-05 14:34 , Guillaume Foliard wrote:
> Victor Porton wrote:
> 
>> Somebody, write an Ada benchmark for this comparison of programming
>> languages:
>>
>> https://github.com/jesusfv/Comparison-Programming-Languages-Economics
> 
> Here is it:

 [most of code snipped]

>    Cpu_Time_End := Ada.Execution_Time.Clock;

I have a question about this, see below.

>    Ada.Text_IO.Put_Line
>       ("Elapsed time is ="
>        & Ada.Real_Time.To_Duration (Cpu_Time_End - Cpu_Time_Start)'Img);
> end Rbc_Ada;
> ---------------------------------------------------------------------
> 
> This is mostly a line to line translation from RBC_CPP.cpp. I have
> added a few type declarations though.
> 
>> It seems that C++ was the fastest (faster than Fortran), but Ada may be
>> even faster.
> 
> Here are the numbers with GNAT GPL 2014 on a Core2 Q9650 @ 3.00GHz:
> 
> $ gnatmake -O3 rbc_ada.adb
> $ time ./rbc_ada
> ...
> Elapsed time is = 1.966112682
> 
> 
> As for the C++ version:
> 
> $ g++ -o testc -O3 RBC_CPP.cpp
> $ time ./testc
> ... 
> Elapsed time is   = 3.12033

Are you sure that Ada.Execution_Time.Clock gives numbers that can be
compared with the get_cpu_time() function in the C++ version? For a
program running under an OS, it is not evident what should be included
in the "processor time" for a program (program loading, process
creation, interrupts, I/O, page faults, ...).

What did the "time" command output in your tests?

Just to be sure that the claim "Ada is faster" is really motivated.
Which would be very nice.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
      .      @       .


^ permalink raw reply	[relevance 0%]

* Re: Benchmark Ada, please
  @ 2014-07-05 12:34  5% ` Guillaume Foliard
  2014-07-05 13:00  0%   ` Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Guillaume Foliard @ 2014-07-05 12:34 UTC (permalink / raw)


Victor Porton wrote:

> Somebody, write an Ada benchmark for this comparison of programming
> languages:
> 
> https://github.com/jesusfv/Comparison-Programming-Languages-Economics

Here is it:

---------------------------------------------------------------------
with Ada.Execution_Time;
with Ada.Numerics.Long_Elementary_Functions;
with Ada.Real_Time;
with Ada.Text_IO;

use Ada.Numerics.Long_Elementary_Functions;

use type Ada.Execution_Time.CPU_Time;

procedure Rbc_Ada
is
   
   Grid_Capital_Length      : constant := 17820;
   Grid_Productivity_Length : constant := 5;
   
   type Grid_Capital_Index is 
      new Integer range 0 .. Grid_Capital_Length - 1;
   
   type Grid_Productivity_Index is
      new Integer range 0 .. Grid_Productivity_Length - 1;
   
   type Grid_Array_Type is
      array (Grid_Capital_Index, Grid_Productivity_Index)
      of Long_Float;
   
   Null_Grid : constant Grid_Array_Type := (others => (others => 0.0));
   
   -- 1. Calibration
   
   -- Elasticity of output w.r.t. capital
   
   Alpha : constant Long_Float := 0.33333333333;
   
   -- Discount factor
   
   Beta : constant Long_Float := 0.95;
   
   -- Productivity values
   
   Productivities : constant
      array (Grid_Productivity_Index) 
      of Long_Float :=
      (0.9792, 0.9896, 1.0000, 1.0106, 1.0212);
   
   -- Transition matrix
   
   Transition : constant
      array (Grid_Productivity_Index, Grid_Productivity_Index) 
      of Long_Float :=
      ((0.9727, 0.0273, 0.0000, 0.0000, 0.0000),
       (0.0041, 0.9806, 0.0153, 0.0000, 0.0000),
       (0.0000, 0.0082, 0.9837, 0.0082, 0.0000),
       (0.0000, 0.0000, 0.0153, 0.9806, 0.0041),
       (0.0000, 0.0000, 0.0000, 0.0273, 0.9727));
   
   -- 2. Steady State
   
   Capital_Steady_State : constant Long_Float :=
      (Alpha * Beta) ** (1.0 / (1.0 - Alpha));
   
   Output_Steady_State : constant Long_Float := 
      Capital_Steady_State ** Alpha;
   
   Consumption_Steady_State : constant Long_Float := 
      Output_Steady_State - Capital_Steady_State;

   Grid_Capital_Next_Index : Grid_Capital_Index;
   
   Grid_Capital : array (Grid_Capital_Index) of Long_Float := 
      (others => 0.0);
  
   Output                  : Grid_Array_Type := Null_Grid;
   Value_Function          : Grid_Array_Type := Null_Grid;
   Value_Function_New      : Grid_Array_Type := Null_Grid;
   Policy_Function         : Grid_Array_Type := Null_Grid;
   Expected_Value_Function : Grid_Array_Type := Null_Grid;

   Max_Difference   : Long_Float := 10.0;
   Diff             : Long_Float;
   Diff_High_So_Far : Long_Float;
   
   Tolerance : constant := 0.0000001;
   
   Value_High_So_Far : Long_Float;
   Value_Provisional : Long_Float;
   Consumption       : Long_Float;
   Capital_Choice    : Long_Float;
   Iteration         : Integer := 0;
   Cpu_Time_Start    : Ada.Execution_Time.CPU_Time;
   Cpu_Time_End      : Ada.Execution_Time.CPU_Time;
begin
   Cpu_Time_Start := Ada.Execution_Time.Clock;
   
   Ada.Text_IO.Put_Line
      ("Output =" & Output_Steady_State'Img
       & ", Capital =" & Capital_Steady_State'Img
       & ", Consumption =" & Consumption_Steady_State'Img);
	
   -- We generate the grid of capital

   for Index in Grid_Capital'Range
   loop
      Grid_Capital (Index) :=
         0.5 * Capital_Steady_State + 0.00001 * Long_Float (Index);
   end loop;

   -- We pre-build output for each point in the grid
   
   for Productivity_Index in Grid_Productivity_Index
   loop
      for Capital_Index in Grid_Capital_Index
      loop
         Output (Capital_Index, Productivity_Index) := 
            Productivities (Productivity_Index)
            * Grid_Capital (Capital_Index) ** Alpha;
      end loop;
   end loop;

   -- Main iteration

   while Max_Difference > Tolerance
   loop
      for Productivity_Index in Grid_Productivity_Index   
      loop
         for Capital_Index in Grid_Capital_Index  
         loop
            Expected_Value_Function (Capital_Index, Productivity_Index) :=
               0.0;
            
            for Productivity_Next_Index in Grid_Productivity_Index   
            loop
               Expected_Value_Function (Capital_Index, Productivity_Index) 
:=
                  Expected_Value_Function (Capital_Index, 
Productivity_Index)
                  + Transition (Productivity_Index, Productivity_Next_Index)
                  * Value_Function (Capital_Index, Productivity_Next_Index);
            end loop;
         end loop;
      end loop;
      
      for Productivity_Index in Grid_Productivity_Index   
      loop
         -- We start from previous choice (monotonicity of policy function)
         
         Grid_Capital_Next_Index := 0;
         
         for Capital_Index in Grid_Capital_Index
         loop
            Value_High_So_Far := -100000.0;
            Capital_Choice    := Grid_Capital (0);
            
            for Capital_Next_Index in 
               Grid_Capital_Next_Index .. Grid_Capital_Index'Last
            loop
               Consumption := 
                  Output (Capital_Index, Productivity_Index)
                  - Grid_Capital (Capital_Next_Index);
               
               Value_Provisional :=
                  (1.0 - Beta) * Log (Consumption)
                  + Beta * Expected_Value_Function (Capital_Next_Index,
                                                    Productivity_Index);
               
               if Value_Provisional > Value_High_So_Far
               then
                  Value_High_So_Far := Value_Provisional;
                  Capital_Choice := Grid_Capital (Capital_Next_Index);
                  Grid_Capital_Next_Index := Capital_Next_Index;
                  
               else
                  exit;
               end if;
               
               Value_Function_New (Capital_Index, Productivity_Index) := 
                  Value_High_So_Far;
               
               Policy_Function (Capital_Index, Productivity_Index) :=
                  Capital_Choice;
            end loop;
         end loop;
      end loop;
      
      Diff_High_So_Far := -100000.0;
      
      for Productivity_Index in Grid_Productivity_Index   
      loop
         for Capital_Index in Grid_Capital_Index
         loop
            Diff := 
               abs (Value_Function (Capital_Index, Productivity_Index)
                   - Value_Function_New (Capital_Index, 
                                        Productivity_Index));
 
            if Diff > Diff_High_So_Far
            then
               Diff_High_So_Far := Diff;
            end if;
            
            Value_Function (Capital_Index, Productivity_Index)
               := Value_Function_New (Capital_Index, Productivity_Index);
         end loop;
      end loop;
      
      Max_Difference := Diff_High_So_Far;

      Iteration := Iteration + 1;
      
      if Iteration mod 10 = 0 or Iteration = 1
      then
         Ada.Text_IO.Put_Line ("Iteration =" & Iteration'Img
                               & ", Sup Diff =" & Max_Difference'Img);
      end if;
   end loop;
   
   Ada.Text_IO.Put_Line ("Iteration =" & Iteration'Img
                         & ", Sup Diff =" & Max_Difference'Img);
   Ada.Text_IO.New_Line;
   Ada.Text_IO.Put_Line ("My check =" & Policy_Function (999, 2)'Img);
   Ada.Text_IO.New_Line;   

   Cpu_Time_End := Ada.Execution_Time.Clock;
   
   Ada.Text_IO.Put_Line
      ("Elapsed time is ="
       & Ada.Real_Time.To_Duration (Cpu_Time_End - Cpu_Time_Start)'Img);
end Rbc_Ada;
---------------------------------------------------------------------

This is mostly a line to line translation from RBC_CPP.cpp. I have
added a few type declarations though.

> It seems that C++ was the fastest (faster than Fortran), but Ada may be
> even faster.

Here are the numbers with GNAT GPL 2014 on a Core2 Q9650 @ 3.00GHz:

$ gnatmake -O3 rbc_ada.adb
$ time ./rbc_ada
...
Elapsed time is = 1.966112682


As for the C++ version:

$ g++ -o testc -O3 RBC_CPP.cpp
$ time ./testc
... 
Elapsed time is   = 3.12033

So the Ada version is significantly faster. I suppose it is mainly because 
the Ada compiler has vectorized more loops than the C++ compiler (add -
ftree-vectorizer-verbose=2 to the above compilation commands to check by 
yourself).

> If we succeed, we would advertise Ada as the fastest(!) programming
> language (after assembler).

Feel free to advertise, using this Ada code as you wish.

-- 
Guillaume Foliard

^ permalink raw reply	[relevance 5%]

* Re: Ada platforms and pricing, was: Re: a new language, designed for safety !
  2014-06-22 23:38  4%                                 ` Randy Brukardt
@ 2014-06-24 12:13  0%                                   ` Simon Clubley
  0 siblings, 0 replies; 200+ results
From: Simon Clubley @ 2014-06-24 12:13 UTC (permalink / raw)


On 2014-06-22, Randy Brukardt <randy@rrsoftware.com> wrote:
> "Simon Clubley" <clubley@remove_me.eisner.decus.org-Earth.UFP> wrote in 
> message news:lo7c2h$ura$1@dont-email.me...
>>
>> To me, I mentally split the problem into two categories: The support
>> for Ada language functionality and the support for peripherals on the
>> specific board. I regard only the first part as really a part of the
>> actual compiler, but it is a required part.
>>
>> However, my feeling is that the Ada RTL support, once implemented, is
>> pretty generic within a MCU architecture and is not really board
>> specific.
>
> That's not my experience. Remember that "basic Ada support" includes things 
> like timers (Ada.Real_Time, delay statements), some method of handling 
> exceptions (which generally means supporting hardware traps), and usually 
> tasking (which means some method of context switching).
>
> All of these require interrupt support on bare boards, and that never seems 
> to be quite the same from board to board.
>

In the ARM world, that's more of a MCU specific issue instead of a board
specific issue. What could be done is to split the Ada RTL into cleanly
separated generic and hardware specific parts and provide a clean detailed
specification for implementing the hardware specific part.

> There's certainly a shared part, but the configurations are different for 
> each board. And you have to be pretty familar with the boards in order to do 
> those; your average tinkerer isn't likely to be able to do that.
>

Some board specific configuration issues which might matter could be
things like memory layout which can be handled with linker scripts.

>> You may need some configuration and interface options for things like
>> I/O operations, with calls to user supplied I/O packages. These packages
>> would only concern themselves with the lowest level, interfacing to
>> the hardware itself and not provide any generic Ada RTL support.
>>
>> In these user supplied packages, I'm thinking about things like an Ada
>> version of, say, putchar() which would just output the passed character
>> to some hardware device without concerning itself about anything other
>> than that.
>
> Fair enough. I found back in the day that you had to be able to connect that 
> with Text_IO for useful output (for instance, the crash messages from the 
> Janus/Ada runtime). But that's clearly a secondary need. I wasn't thinking 
> about full I/O support, for instance, since it usually doesn't make sense in 
> that environment.
>

Sorry, I wasn't clear above.

What I meant was that Text_IO (or something like it) would be
implemented, but at the lowest level, the Text_IO package would just
call a user supplied routine to actually output the character(s) to the
hardware and that user supplied routine would not care about, or even
know anything about, the structure of the Ada RTL package calling it.

Simon.

-- 
Simon Clubley, clubley@remove_me.eisner.decus.org-Earth.UFP
Microsoft: Bringing you 1980s technology to a 21st century world


^ permalink raw reply	[relevance 0%]

* Re: Ada platforms and pricing, was: Re: a new language, designed for safety !
  @ 2014-06-22 23:38  4%                                 ` Randy Brukardt
  2014-06-24 12:13  0%                                   ` Simon Clubley
  0 siblings, 1 reply; 200+ results
From: Randy Brukardt @ 2014-06-22 23:38 UTC (permalink / raw)


"Simon Clubley" <clubley@remove_me.eisner.decus.org-Earth.UFP> wrote in 
message news:lo7c2h$ura$1@dont-email.me...
> On 2014-06-18, Randy Brukardt <randy@rrsoftware.com> wrote:
>> "Simon Clubley" <clubley@remove_me.eisner.decus.org-Earth.UFP> wrote in
>> message news:lnsqus$d4j$1@dont-email.me...
>>> On 2014-06-17, Randy Brukardt <randy@rrsoftware.com> wrote:
>>>>
>>>> It's impractical to have any such cross-compilers. Every such compiler
>>>> (run-time, really) has to be tailored to the specific board in 
>>>> question.
>>>> We
>>>> treated each embedded compiler as something that would require 
>>>> extensive
>>>> support, and I still think we lost money on each.
>>>>
...
>>> Taking the ARM bare metal (C language) world as an example:
>>>
>>> 1) At the bottom layer you have the compiler itself. This just generates
>>> code for a set of ARM architecture variants such as Cortex-M3 and
>>> Cortex-A8 as well as older ARM architecture variants such as the ARMv5
>>> variants. It has absolutely no knowledge of any specific MCU or any
>>> board which that MCU might be placed on. Things like memory layouts
>>> are handled in linker scripts.
>>
>> Yup. But no one can do anything useful with such a thing. It's trivial to
>> take a version of Janus/Ada and use it as a cross-compiler for some 
>> board.
>> But without a runtime, hardware support, and the like, only the most
>> dedicated people could use it for anything.
>>
>
> To me, I mentally split the problem into two categories: The support
> for Ada language functionality and the support for peripherals on the
> specific board. I regard only the first part as really a part of the
> actual compiler, but it is a required part.
>
> However, my feeling is that the Ada RTL support, once implemented, is
> pretty generic within a MCU architecture and is not really board
> specific.

That's not my experience. Remember that "basic Ada support" includes things 
like timers (Ada.Real_Time, delay statements), some method of handling 
exceptions (which generally means supporting hardware traps), and usually 
tasking (which means some method of context switching).

All of these require interrupt support on bare boards, and that never seems 
to be quite the same from board to board.

There's certainly a shared part, but the configurations are different for 
each board. And you have to be pretty familar with the boards in order to do 
those; your average tinkerer isn't likely to be able to do that.

> You may need some configuration and interface options for things like
> I/O operations, with calls to user supplied I/O packages. These packages
> would only concern themselves with the lowest level, interfacing to
> the hardware itself and not provide any generic Ada RTL support.
>
> In these user supplied packages, I'm thinking about things like an Ada
> version of, say, putchar() which would just output the passed character
> to some hardware device without concerning itself about anything other
> than that.

Fair enough. I found back in the day that you had to be able to connect that 
with Text_IO for useful output (for instance, the crash messages from the 
Janus/Ada runtime). But that's clearly a secondary need. I wasn't thinking 
about full I/O support, for instance, since it usually doesn't make sense in 
that environment.

>>> 2) At the next layer up you have code to support a specific MCU. As
>>> well as MCU specific startup code, this includes things like interrupt
>>> handling which is MCU specific in the ARM world. This code generally
>>> comes from the manufacturer of the MCU and is usually free.
>>
>> But it's probably not in a form that could be used for Ada. Certainly not
>> unless you're planning to require having an C compiler around as well 
>> (not
>> really good marketing for Ada).
>>
>
> There is some C code at the very lowest level of GNAT.

Sure, but it's compiled; you don't need a C compiler in order to be able to 
use GNAT. If you require people to use C code in their setup, they'll need 
to get the C compiler working first. At that point, most people will wonder 
why they're spending time to get Ada working rather than working on their 
project (the fun part, hopefully).

...
> I don't really see the support for the peripherals as part of the
> compiler as such. For example, the various MCU and board manufacturers
> may provide their own bare metal support package for a board and all
> you need to do is download it from their website and build it with your
> own C compiler; it's not expected to be a part of gcc.

I'm not talking about "peripherals"; I'm talking about timers and trap 
handlers (for overflow, divide-by-zero, etc.) and the like. These things are 
required for a useful subset of Ada. (No clock and no exceptions means 
you're no longer really doing Ada, just Ada syntax.) I/O is optional, but 
not these other things.

                                  Randy.




^ permalink raw reply	[relevance 4%]

* Termination of periodic tasks
@ 2014-06-15 10:10  6% Natasha Kerensikova
  0 siblings, 0 replies; 200+ results
From: Natasha Kerensikova @ 2014-06-15 10:10 UTC (permalink / raw)


Hello,

I'm still struggling with the termination of tasks hidden in the private
part or the body of libraries, this time with a periodic task.

Basically, I'm looking for a way to have some subprogram called at
roughly regular intervals. Ada.Real_Time.Timing_Events would be
functionally what I needed, except it's accuracy is vastly more than I
need, so it's overhead is mostly wasted.

For the uses I currently have in mind, the periodic subprogram would
be a kind of GC for slowly moving resources, called every 15 min to
every day, with a time tolerance exceeding minutes.

While in GNARL Ada.Real_Time.Timing_Events is implemented using a task
awaken every 100 ms.

And same as before, the task should be able to terminate quickly when
the program terminates.

I would be perfectly happy with something like:

   task body Periodic_Task is
      loop
         select
            delay 86_400.0;
         or
            terminate;
         end select;

         Periodic_Subprogram;
      end loop;
   end task;

Except that's not available in Ada.

The "or terminate" part is only available when waiting for an entry, but
this only move the problem to the periodic calling of the entry.

A timed select to wait for an entry that exists the loop would be fine
too, but how can I detect program termination to call the entry?
Could something be worked with a user-defined Finalize?

I looked at how GNARL is doing it, but it's using an RL-specific
primitive to move the task one level above the main master, so that it's
aborted instead of waited-for on program termination. I'm a bit
reluctant to use a RL-internal primitive...

That leaves Ada.Real_Time.Timing_Events and its comparatively large
overhead, even though (I think) I can afford it, it's not very
satisfying.

How would you do it?


Thanks in advance for your help,
Natasha

^ permalink raw reply	[relevance 6%]

* Re: Raspberry Pi, Real-Time and Ada
  2014-02-07 23:11  8%       ` Rego, P.
@ 2014-02-08  8:56  0%         ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2014-02-08  8:56 UTC (permalink / raw)


On Fri, 7 Feb 2014 15:11:20 -0800 (PST), Rego, P. wrote:

>> I don't think that 10ms would be a problem even for ARM.
>> On an Intel board 200µs loops (read inputs, calculate, write outputs) are
>> doable.
>> Ada has everything you need for that.
>> The main problem is how good the RT clock is. Windows and VxWorks typically
>> have miserable RT clock services on x86. x86 Linux has a decent one.
>> Regarding ARM Linux, I didn't tested its clock, so I cannot tell. The
>> primary test is to call Ada.Real_Time.Clock twice and to compare if the
>> reading is same. If they are you should look for an alternative
>> implementation of. 
> 
> BTW, now I have done a fast test using 
> 
> with Ada.Real_Time; use Ada.Real_Time;
> with Ada.Text_IO;
> 
> procedure My_Clock is
>    First_Time : Time;
>    Second_Time : Time;
>    F_Duration : Time_Span;
>    Time_Duration : Duration;
> 
> begin
>    First_Time := Ada.Real_Time.Clock;
>    Second_Time := Ada.Real_Time.Clock;
>    F_Duration := Second_Time - First_Time;
>    Time_Duration := To_Duration (F_Duration);
> 
>    Ada.Text_IO.Put_Line (Duration'Image (Time_Duration));  
> 
> end My_Clock;
> 
> and the result was in average 17us for the RPi (with Raspbian without the
> preemptive patch), with a variation of 1 us (for just a few executions),

That looks pretty much slow for a 700MHz processor. You should take a look
what exactly the implementation is (in s-oprim.adb, I suppose).

> while the same code running on a Windows 7x64 machine was sometimes 0,
> sometimes 366ns (49 times faster).

If you look at the implementation of you see that it is based on the
performance counter:

http://msdn.microsoft.com/en-us/library/windows/desktop/ms644904%28v=vs.85%29.aspx

MS does not tell which time source they use for this function. There are
many on an Intel board. That you have 0 to 366ns (which is very poor for an
Intel machine) indicates that probably your machine uses the HPET. HPET
runs at 25MHz or so, which is pitiful for a GHz machine.

I suppose there are some architectural problems with using the TSC on
multi-core machines which is why older single-core Windows machines tend to
have better clocks.

Anyway, you could try to play a bit with the BIOS and BOOT.INI in order to
force Windows not to use HPET (or even worse, the programmable timer).

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de


^ permalink raw reply	[relevance 0%]

* Re: Raspberry Pi, Real-Time and Ada
  2014-02-07  8:42  6%     ` Dmitry A. Kazakov
  2014-02-07 12:34  0%       ` Rego, P.
@ 2014-02-07 23:11  8%       ` Rego, P.
  2014-02-08  8:56  0%         ` Dmitry A. Kazakov
  1 sibling, 1 reply; 200+ results
From: Rego, P. @ 2014-02-07 23:11 UTC (permalink / raw)


> I don't think that 10ms would be a problem even for ARM.
> On an Intel board 200µs loops (read inputs, calculate, write outputs) are
> doable.
> Ada has everything you need for that.
> The main problem is how good the RT clock is. Windows and VxWorks typically
> have miserable RT clock services on x86. x86 Linux has a decent one.
> Regarding ARM Linux, I didn't tested its clock, so I cannot tell. The
> primary test is to call Ada.Real_Time.Clock twice and to compare if the
> reading is same. If they are you should look for an alternative
> implementation of. 

BTW, now I have done a fast test using 

with Ada.Real_Time; use Ada.Real_Time;
with Ada.Text_IO;

procedure My_Clock is
   First_Time : Time;
   Second_Time : Time;
   F_Duration : Time_Span;
   Time_Duration : Duration;

begin
   First_Time := Ada.Real_Time.Clock;
   Second_Time := Ada.Real_Time.Clock;
   F_Duration := Second_Time - First_Time;
   Time_Duration := To_Duration (F_Duration);

   Ada.Text_IO.Put_Line (Duration'Image (Time_Duration));  

end My_Clock;

and the result was in average 17us for the RPi (with Raspbian without the preemptive patch), with a variation of 1 us (for just a few executions), while the same code running on a Windows 7x64 machine was sometimes 0, sometimes 366ns (49 times faster).


^ permalink raw reply	[relevance 8%]

* Re: Raspberry Pi, Real-Time and Ada
  2014-02-07  8:42  6%     ` Dmitry A. Kazakov
@ 2014-02-07 12:34  0%       ` Rego, P.
  2014-02-07 23:11  8%       ` Rego, P.
  1 sibling, 0 replies; 200+ results
From: Rego, P. @ 2014-02-07 12:34 UTC (permalink / raw)


On Friday, February 7, 2014 6:42:41 AM UTC-2, Dmitry A. Kazakov wrote:
> I don't think that 10ms would be a problem even for ARM.
> On an Intel board 200µs loops (read inputs, calculate, write outputs) are
> doable.

It turns things much better. 

> Ada has everything you need for that.

That is always as good as it sound :-)

> The main problem is how good the RT clock is. Windows and VxWorks typically
> have miserable RT clock services on x86. x86 Linux has a decent one.
Ok.

> Regarding ARM Linux, I didn't tested its clock, so I cannot tell. The
> primary test is to call Ada.Real_Time.Clock twice and to compare if the
> reading is same. If they are you should look for an alternative
> implementation of. The second test is to measure how close delay 1.0 is to
> 1 second using Ada.Real_Time.Clock. The deviation from 1s tells how coarse
> OS programmable timer services are. There are OS means to attune that (on
> the performance cost).
> Once you have Ada.Real_Time.Clock it is no problem to measure the control
> loop your system does. Usually you would measure several thousands of
> cycles to get min, max and average times. If you have background services
> to run, you do measures under load (with other services) and without load.
Great. I think it will cover most of what I need to know.

> The OS latencies (in the driver etc) is a more difficult stuff. If the OS
> does not have means to measure these times (VxWorks has), you still can
> estimate these by subtracting known durations from the whole cycle time.

Do you remember how can be done on VxWorks? (it could be also good to test it on VxWorks just for curiosity). So I can try to find an alike alternative, maybe in Xenomai it is available.

> You can also use digital outputs which are considerably faster than
> analogue ones and the oscilloscope, etc. You can calibrate digital output
> times by measuring many thousands of write-cycles and taking the mean.
Ok. This will complement the tests. Great.

--
Regards,
Rego.

^ permalink raw reply	[relevance 0%]

* Re: Raspberry Pi, Real-Time and Ada
  @ 2014-02-07  8:42  6%     ` Dmitry A. Kazakov
  2014-02-07 12:34  0%       ` Rego, P.
  2014-02-07 23:11  8%       ` Rego, P.
  0 siblings, 2 replies; 200+ results
From: Dmitry A. Kazakov @ 2014-02-07  8:42 UTC (permalink / raw)


On Thu, 6 Feb 2014 13:04:19 -0800 (PST), Rego, P. wrote:

>> Using the general definition, if your application has deadlines with
>> tolerances on the order of 0.1 seconds, then the answer is clearly
>> "yes".
> Very slow, but based on what?

I don't think that 10ms would be a problem even for ARM.

On an Intel board 200µs loops (read inputs, calculate, write outputs) are
doable.
 
>> For tighter tolerances, you'd have to measure the actual performance,
>> and possibly use an enhanced kernel as you discussed.

> Measuring could be excelent. Do you know some tools that I could use for
> measuring the RPi performance?

Ada has everything you need for that.

The main problem is how good the RT clock is. Windows and VxWorks typically
have miserable RT clock services on x86. x86 Linux has a decent one.

Regarding ARM Linux, I didn't tested its clock, so I cannot tell. The
primary test is to call Ada.Real_Time.Clock twice and to compare if the
reading is same. If they are you should look for an alternative
implementation of. The second test is to measure how close delay 1.0 is to
1 second using Ada.Real_Time.Clock. The deviation from 1s tells how coarse
OS programmable timer services are. There are OS means to attune that (on
the performance cost).

Once you have Ada.Real_Time.Clock it is no problem to measure the control
loop your system does. Usually you would measure several thousands of
cycles to get min, max and average times. If you have background services
to run, you do measures under load (with other services) and without load.

The OS latencies (in the driver etc) is a more difficult stuff. If the OS
does not have means to measure these times (VxWorks has), you still can
estimate these by subtracting known durations from the whole cycle time.
You can also use digital outputs which are considerably faster than
analogue ones and the oscilloscope, etc. You can calibrate digital output
times by measuring many thousands of write-cycles and taking the mean.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de


^ permalink raw reply	[relevance 6%]

* Re: Anonymous access types are evil, why?
  2013-08-28 11:49  8% Anonymous access types are evil, why? ake.ragnar.dahlgren
@ 2013-08-30 16:16  6% ` Gerhard Rummel
  0 siblings, 0 replies; 200+ results
From: Gerhard Rummel @ 2013-08-30 16:16 UTC (permalink / raw)


Am Mittwoch, 28. August 2013 05:49:56 UTC-6 schrieb ake.ragna...@gmail.com:
> Consider the following application that uses anonymous access types and allocates Controlled objects on the heap using two different ways. One way takes 60 times longer than the other:
> 
> ....
> 
> 
> 
> What are the conclusions we can draw?
> 
> 1. Perhaps one conclusion would be that when using anonymous access types then indirect assignment should be preferred over direct assignment. (see Models.B.Direct_Assignment and Models.B.Indirect_Assignment).
> 
> 2. Avoid anonymous access types. Prefer named access types and 'Unchecked_Access.
> 
> 
> 
> Is there anybody who can explain why direct assignment takes approximately 60 times longer than indirect assignment?
> 
> 
> 
> Best regards,
> 
> Åke Ragnar Dahlgren

I think there is a problem with the implementation of Controlled Types in
gnat2012, and NOT with anonymous access types: if you change the declaration of A_Type to a not controlled record there is nearly no difference in runtime: To show that I have declared three versions of your A_Type (in Models.A): as a record, a tagged record and as derived from Ada.Finalization.Controlled. Then I declared six versions of your B_Type, with anonymous and named access variables of each of the three types. Additionally, I cleaned up the heap before the direct or indirect assignments.

The output of the Main program is now:


Output:

Heap clean up before assignment: TRUE
MODELS.B.TYPE_WITH_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.005783000
MODELS.B.TYPE_WITH_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.002435000
MODELS.B.TYPE_WITH_ANONYMOUS_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.002283000
MODELS.B.TYPE_WITH_ANONYMOUS_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.002263000
MODELS.B.TYPE_WITH_TAGGED_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.002298000
MODELS.B.TYPE_WITH_TAGGED_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.002263000
MODELS.B.TYPE_WITH_ANONYMOUS_TAGGED_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.002304000
MODELS.B.TYPE_WITH_ANONYMOUS_TAGGED_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.002553000
MODELS.B.TYPE_WITH_CONTROLLED_ACCESS_TYPE, Duration (direct assignment):    0.005504000
MODELS.B.TYPE_WITH_CONTROLLED_ACCESS_TYPE, Duration (indirect assignment):  0.005505000
MODELS.B.TYPE_WITH_ANONYMOUS_CONTROLLED_ACCESS_TYPE, Duration (direct assignment):    0.010914000
MODELS.B.TYPE_WITH_ANONYMOUS_CONTROLLED_ACCESS_TYPE, Duration (indirect assignment):  0.005706000


As you can see, the quotient of the runtimes of the two methods of assignments is now a factor less than two, if your A_Type is Controlled and more than two, if your A_Type is a simple record instead of a Controlled type.

Things are much worse for Controlled types when you don't clean up the heap before the assignments:


Output:

Heap clean up before assignment: FALSE
MODELS.B.TYPE_WITH_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.066929000
MODELS.B.TYPE_WITH_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.063081000
MODELS.B.TYPE_WITH_ANONYMOUS_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.063031000
MODELS.B.TYPE_WITH_ANONYMOUS_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.062613000
MODELS.B.TYPE_WITH_TAGGED_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.062416000
MODELS.B.TYPE_WITH_TAGGED_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.062329000
MODELS.B.TYPE_WITH_ANONYMOUS_TAGGED_RECORD_ACCESS_TYPE, Duration (direct assignment):    0.061632000
MODELS.B.TYPE_WITH_ANONYMOUS_TAGGED_RECORD_ACCESS_TYPE, Duration (indirect assignment):  0.062526000
MODELS.B.TYPE_WITH_CONTROLLED_ACCESS_TYPE, Duration (direct assignment):    0.064492000
MODELS.B.TYPE_WITH_CONTROLLED_ACCESS_TYPE, Duration (indirect assignment):  0.064068000
MODELS.B.TYPE_WITH_ANONYMOUS_CONTROLLED_ACCESS_TYPE, Duration (direct assignment):    11.441936000
MODELS.B.TYPE_WITH_ANONYMOUS_CONTROLLED_ACCESS_TYPE, Duration (indirect assignment):  0.063594000

In the last four lines you can see that the runtimes for the two methods of assignments are nearly equal for a B_Type with a named access type variable of a Controlled type and very different for anonymous access type variables.

I think there is no important performance difference between anonymous and named access variables if you clean up the heap before assigning new values to them. But there is a problem with the finalization of Controlled type variables on the heap, perhaps due to their implementation in gnat 2012.

The code of the program:

with Ada.Text_IO;
with Models.B;

procedure Main is

   Number_Of_Times : constant Positive := 40000;

begin
   for B in reverse Boolean range False .. True loop
      declare
         RT : Models.B.Type_With_Record_Access_Type;
         ART : Models.B.Type_With_Anonymous_Record_Access_Type;
         TRT : Models.B.Type_With_Tagged_Record_Access_Type;
         ATRT : Models.B.Type_With_Anonymous_Tagged_Record_Access_Type;
         CT : Models.B.Type_With_Controlled_Access_Type;
         ACT : Models.B.Type_With_Anonymous_Controlled_Access_Type;
      begin
         Models.B.With_Heap_Cleaning := B;
         Ada.Text_IO.Put_Line
           (Item => "Heap clean up before assignment: "
            & Boolean'Image (Models.B.With_Heap_Cleaning)
           );
         RT.Measure_Time (Number_Of_Times => Number_Of_Times);
         ART.Measure_Time (Number_Of_Times => Number_Of_Times);
         TRT.Measure_Time (Number_Of_Times => Number_Of_Times);
         ATRT.Measure_Time (Number_Of_Times => Number_Of_Times);
         CT.Measure_Time (Number_Of_Times => Number_Of_Times);
         ACT.Measure_Time (Number_Of_Times => Number_Of_Times);
         Ada.Text_IO.New_Line;
      end;
   end loop;
end Main;

package Models is

end Models;

with Ada.Finalization;
with Ada.Unchecked_Deallocation;
package Models.A is

   type Record_Type is record
      Asdf : Integer;
      qwer : String (1 .. 8000);
   end record;

   type Record_Access_Type is access all Record_Type;

   procedure Delete is new Ada.Unchecked_Deallocation
     (Object => Record_Type, Name => Record_Access_Type);

   type Tagged_Record_Type is tagged record
      Asdf : Integer;
      qwer : String (1 .. 8000);
   end record;

   type Tagged_Record_Access_Type is access all Tagged_Record_Type;

   procedure Delete is new Ada.Unchecked_Deallocation
     (Object => Tagged_Record_Type, Name => Tagged_Record_Access_Type);

   type Controlled_Type is new Ada.Finalization.Controlled with
      record
         Asdf : Integer;
         qwer : String (1 .. 8000);
      end record;

   type Controlled_Access_Type is access all Controlled_Type;

   procedure Delete is new Ada.Unchecked_Deallocation
     (Object => Controlled_Type, Name => Controlled_Access_Type);

end Models.A;

with Ada.Finalization,
     Models.A;

package Models.B is

   With_Heap_Cleaning : Boolean := False;

   type Type_With_Access_Type is abstract new Ada.Finalization.Controlled
     with private;

   overriding
   procedure Finalize (Item : in out Type_With_Access_Type) with Inline;

   function Type_Name (Item : Type_With_Access_Type'Class) return String
   with Inline;

   procedure Cleanup (Item : in out Type_With_Access_Type) is abstract;

   procedure Direct_Assignment (Item : in out Type_With_Access_Type)
   is abstract;

   procedure Indirect_Assignment (Item : in out Type_With_Access_Type)
   is abstract;

   procedure Measure_Time
     (Item : in out Type_With_Access_Type'Class;
      Number_Of_Times : Natural
     );

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

   type Type_With_Record_Access_Type is new Type_With_Access_Type with private;

   overriding
   procedure Adjust (Item : in out Type_With_Record_Access_Type) with Inline;

   overriding
   procedure Cleanup (Item : in out Type_With_Record_Access_Type);

   overriding
   procedure Direct_Assignment (Item : in out Type_With_Record_Access_Type)
   with Inline;

   overriding
   procedure Indirect_Assignment (Item : in out Type_With_Record_Access_Type)
   with Inline;

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

   type Type_With_Anonymous_Record_Access_Type is new Type_With_Access_Type
     with private;

   overriding
   procedure Adjust (Item : in out Type_With_Anonymous_Record_Access_Type)
   with Inline;

   overriding
   procedure Cleanup (Item : in out Type_With_Anonymous_Record_Access_Type);

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Anonymous_Record_Access_Type) with Inline;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Anonymous_Record_Access_Type) with Inline;

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

   type Type_With_Tagged_Record_Access_Type is new Type_With_Access_Type
     with private;

   overriding
   procedure Adjust (Item : in out Type_With_Tagged_Record_Access_Type)
   with Inline;

   overriding
   procedure Cleanup (Item : in out Type_With_Tagged_Record_Access_Type);

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Tagged_Record_Access_Type) with Inline;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Tagged_Record_Access_Type) with Inline;

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

   type Type_With_Anonymous_Tagged_Record_Access_Type is
     new Type_With_Access_Type with private;

   overriding
   procedure Adjust
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type) with Inline;

   overriding
   procedure Cleanup
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type);

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type) with Inline;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type) with Inline;

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

   type Type_With_Controlled_Access_Type is new Type_With_Access_Type
     with private;

   overriding
   procedure Adjust (Item : in out Type_With_Controlled_Access_Type)
   with Inline;

   overriding
   procedure Cleanup (Item : in out Type_With_Controlled_Access_Type);

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Controlled_Access_Type) with Inline;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Controlled_Access_Type) with Inline;

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

   type Type_With_Anonymous_Controlled_Access_Type is new Type_With_Access_Type
     with private;

   overriding
   procedure Adjust (Item : in out Type_With_Anonymous_Controlled_Access_Type)
   with Inline;

   overriding
   procedure Cleanup
     (Item : in out Type_With_Anonymous_Controlled_Access_Type);

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Anonymous_Controlled_Access_Type) with Inline;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Anonymous_Controlled_Access_Type) with Inline;

private

   type Type_With_Access_Type is abstract new Ada.Finalization.Controlled
     with null record;

   type Type_With_Record_Access_Type is new Type_With_Access_Type with record
      A : Models.A.Record_Access_Type;
   end record;

   type Type_With_Anonymous_Record_Access_Type is new Type_With_Access_Type
   with record
      A : access Models.A.Record_Type;
   end record;

   type Type_With_Tagged_Record_Access_Type is new Type_With_Access_Type
   with record
      A : Models.A.Tagged_Record_Access_Type;
   end record;

   type Type_With_Anonymous_Tagged_Record_Access_Type is
     new Type_With_Access_Type with record
      A : access Models.A.Tagged_Record_Type;
   end record;

   type Type_With_Controlled_Access_Type is new Type_With_Access_Type
   with record
      A : Models.A.Controlled_Access_Type;
   end record;

   type Type_With_Anonymous_Controlled_Access_Type is new Type_With_Access_Type
   with record
      A : access Models.A.Controlled_Type;
   end record;

end Models.B;

with Ada.Real_Time;
with Ada.Tags;
with Ada.Text_IO;
package body Models.B is

   overriding
   procedure Finalize (Item : in out Type_With_Access_Type)
   is
   begin
      Type_With_Access_Type'Class (Item).Cleanup;
   end Finalize;

   function Type_Name (Item : Type_With_Access_Type'Class) return String
   is
   begin
      return Ada.Tags.External_Tag (T => Item'Tag);
   end Type_Name;

   procedure Measure_Time
     (Item : in out Type_With_Access_Type'Class;
      Number_Of_Times : Natural
     )
   is
      Start_Time_Stamp : Ada.Real_Time.Time;
      End_Time_Stamp   : Ada.Real_Time.Time;
   begin
      Start_Time_Stamp := Ada.Real_Time.Clock;
      for I in 1 .. Number_Of_Times loop
         Item.Direct_Assignment;
      end loop;
      End_Time_Stamp := Ada.Real_Time.Clock;

      declare
         use type Ada.Real_Time.Time;

         Total_Time : constant Duration
           := Ada.Real_Time.To_Duration (End_Time_Stamp - Start_Time_Stamp);
      begin
         Ada.Text_IO.Put_Line
           (Item.Type_Name
            & ", Duration (direct assignment):   " & Total_Time'Img
           );
      end;

      Start_Time_Stamp := Ada.Real_Time.Clock;
      for I in 1 .. Number_Of_Times loop
         Item.Indirect_Assignment;
      end loop;
      End_Time_Stamp := Ada.Real_Time.Clock;

      declare
         use type Ada.Real_Time.Time;

         Total_Time : constant Duration
           := Ada.Real_Time.To_Duration (End_Time_Stamp - Start_Time_Stamp);
      begin
         Ada.Text_IO.Put_Line
           (Item.Type_Name
            & ", Duration (indirect assignment): " & Total_Time'Img
           );
      end;

   end Measure_Time;

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

   overriding
   procedure Adjust (Item : in out Type_With_Record_Access_Type)
   is
      use Models.A;
   begin
      if Item.A /= null then
         Item.A := new Models.A.Record_Type'(Item.A.all);
      end if;
   end Adjust;

   overriding
   procedure Cleanup (Item : in out Type_With_Record_Access_Type)
   is
      use Models.A;
      X : Models.A.Record_Access_Type := Item.A;
   begin
      Item.A := null;
      if X /= null then
         Delete (X);
      end if;
   end Cleanup;

   overriding
   procedure Direct_Assignment (Item : in out Type_With_Record_Access_Type) is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      Item.A := new Models.A.Record_Type;
   end Direct_Assignment;

   overriding
   procedure Indirect_Assignment (Item : in out Type_With_Record_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      declare
         A : constant Models.A.Record_Access_Type := new Models.A.Record_Type;
      begin
         Item.A := A;
      end;
   end Indirect_Assignment;

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

   overriding
   procedure Adjust (Item : in out Type_With_Anonymous_Record_Access_Type)
   is
      use Models.A;
   begin
      if Item.A /= null then
         Item.A := new Models.A.Record_Type'(Item.A.all);
      end if;
   end Adjust;

   overriding
   procedure Cleanup (Item : in out Type_With_Anonymous_Record_Access_Type)
   is
      use Models.A;
      X : Models.A.Record_Access_Type := Item.A;
   begin
      Item.A := null;
      if X /= null then
         Delete (X);
      end if;
   end Cleanup;

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Anonymous_Record_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      Item.A := new Models.A.Record_Type;
   end Direct_Assignment;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Anonymous_Record_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      declare
         A : constant Models.A.Record_Access_Type := new Models.A.Record_Type;
      begin
         Item.A := A;
      end;
   end Indirect_Assignment;

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

   overriding
   procedure Adjust (Item : in out Type_With_Tagged_Record_Access_Type)
   is
      use Models.A;
   begin
      if Item.A /= null then
         Item.A := new Models.A.Tagged_Record_Type'(Item.A.all);
      end if;
   end Adjust;

   overriding
   procedure Cleanup (Item : in out Type_With_Tagged_Record_Access_Type)
   is
      use Models.A;
      X : Models.A.Tagged_Record_Access_Type := Item.A;
   begin
      Item.A := null;
      if X /= null then
         Delete (X);
      end if;
   end Cleanup;

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Tagged_Record_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      Item.A := new Models.A.Tagged_Record_Type;
   end Direct_Assignment;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Tagged_Record_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      declare
         A : constant Models.A.Tagged_Record_Access_Type
           := new Models.A.Tagged_Record_Type;
      begin
         Item.A := A;
      end;
   end Indirect_Assignment;

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

   overriding
   procedure Adjust
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type)
   is
      use Models.A;
   begin
      if Item.A /= null then
         Item.A := new Models.A.Tagged_Record_Type'(Item.A.all);
      end if;
   end Adjust;

   overriding
   procedure Cleanup
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type)
   is
      use Models.A;
      X : Models.A.Tagged_Record_Access_Type := Item.A;
   begin
      Item.A := null;
      if X /= null then
         Delete (X);
      end if;
   end Cleanup;

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      Item.A := new Models.A.Tagged_Record_Type;
   end Direct_Assignment;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Anonymous_Tagged_Record_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      declare
         A : constant Models.A.Tagged_Record_Access_Type
           := new Models.A.Tagged_Record_Type;
      begin
         Item.A := A;
      end;
   end Indirect_Assignment;

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

   overriding
   procedure Adjust (Item : in out Type_With_Controlled_Access_Type)
   is
      use Models.A;
   begin
      if Item.A /= null then
         Item.A := new Models.A.Controlled_Type'(Item.A.all);
      end if;
   end Adjust;

   overriding
   procedure Cleanup (Item : in out Type_With_Controlled_Access_Type)
   is
      use Models.A;
      X : Models.A.Controlled_Access_Type := Item.A;
   begin
      Item.A := null;
      if X /= null then
         Delete (X);
      end if;
   end Cleanup;

   overriding
   procedure Direct_Assignment (Item : in out Type_With_Controlled_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      Item.A := new Models.A.Controlled_Type;
   end Direct_Assignment;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Controlled_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      declare
         A : constant Models.A.Controlled_Access_Type
           := new Models.A.Controlled_Type;
      begin
         Item.A := A;
      end;
   end Indirect_Assignment;

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

   overriding
   procedure Adjust (Item : in out Type_With_Anonymous_Controlled_Access_Type)
   is
      use Models.A;
   begin
      if Item.A /= null then
         Item.A := new Models.A.Controlled_Type'(Item.A.all);
      end if;
   end Adjust;

   overriding
   procedure Cleanup
     (Item : in out Type_With_Anonymous_Controlled_Access_Type)
   is
      use Models.A;
      X : Models.A.Controlled_Access_Type := Item.A;
   begin
      Item.A := null;
      if X /= null then
         Delete (X);
      end if;
   end Cleanup;

   overriding
   procedure Direct_Assignment
     (Item : in out Type_With_Anonymous_Controlled_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      Item.A := new Models.A.Controlled_Type;
   end Direct_Assignment;

   overriding
   procedure Indirect_Assignment
     (Item : in out Type_With_Anonymous_Controlled_Access_Type)
   is
      use Models.A;
   begin
      if With_Heap_Cleaning then
         Item.Cleanup;
      end if;

      declare
         A : constant Models.A.Controlled_Access_Type
           := new Models.A.Controlled_Type;
      begin
         Item.A := A;
      end;
   end Indirect_Assignment;

end Models.B;



^ permalink raw reply	[relevance 6%]

* Anonymous access types are evil, why?
@ 2013-08-28 11:49  8% ake.ragnar.dahlgren
  2013-08-30 16:16  6% ` Gerhard Rummel
  0 siblings, 1 reply; 200+ results
From: ake.ragnar.dahlgren @ 2013-08-28 11:49 UTC (permalink / raw)


Consider the following application that uses anonymous access types and allocates Controlled objects on the heap using two different ways. One way takes 60 times longer than the other:

C:\huge_performance_problem>C:\huge_performance_problem\obj\main
Duration:  3.306827264
Duration:  0.056302128

C:\huge_performance_problem>

Please review the code:

-- main.adb:

with Ada.Text_IO,
     Models.A,
     Models.B,
     Ada.Real_Time;

procedure Main is

   Number_Of_Times : Positive := 40000;

   type Method_Pointer_Type is access procedure (B : in out Models.B.B_Type);
   
   procedure Measure_Time (Method : Method_Pointer_Type)
   is
      B : Models.B.B_Type;
      
      Start_Time_Stamp : Ada.Real_Time.Time;
      End_Time_Stamp   : Ada.Real_Time.Time;
   begin
      Start_Time_Stamp := Ada.Real_Time.Clock;
      for I in 1 .. Number_Of_Times loop
         Method(B);
      end loop;
      End_Time_Stamp := Ada.Real_Time.Clock;
   
      declare
         use type Ada.Real_Time.Time;
         
         Total_Time : Duration := Ada.Real_Time.To_Duration (End_Time_Stamp - Start_Time_Stamp);
      begin
         Ada.Text_IO.Put_Line ("Duration: " & Total_Time'Img);
      end;
   end Measure_Time;
      
begin
   Measure_Time(Method => Models.B.Direct_Assignment'Access);
   Measure_Time(Method => Models.B.Indirect_Assignment'Access);
end Main;



-- models.ads:

package Models is
      
end Models;



-- models.a.ads:

with Ada.Finalization;

package Models.A is

   type A_Type is new Ada.Finalization.Controlled with
      record
         Asdf : Integer;
         qwer : String(1..8000);
      end record;
   
   type A_Access_Type is access all A_Type;
   
end Models.A;



-- models.b.ads:

with Ada.Finalization,
     Models.A;

package Models.B is

   type B_Type is new Ada.Finalization.Controlled with
      record
         A : access Models.A.A_Type;
      end record;
   
   procedure Direct_Assignment (B : in out B_Type);
   procedure Indirect_Assignment (B : in out B_Type);
   
   type B_Access_Type is access all B_Type;
   
end Models.B;



-- models.b.adb:

with Ada.Text_IO;

package body Models.B is

   procedure Direct_Assignment(B : in out B_Type) is
   begin
      B.A := new Models.A.A_Type;
   end Direct_Assignment;
   
   procedure Indirect_Assignment (B : in out B_Type) is
   begin
      declare
         A : Models.A.A_Access_Type := new Models.A.A_Type;
      begin
         B.A := A;            
      end;
   end Indirect_Assignment;
      
end Models.B;



Now consider the case when the declaration of B_Type is changed to a named access type:
   type B_Type is new Ada.Finalization.Controlled with
      record
         A : Models.A.A_Access_Type;
      end record;

The execution times are now roughly the same:

C:\huge_performance_problem>C:\huge_performance_problem\obj\main
Duration:  0.055985048
Duration:  0.058163538

C:\huge_performance_problem>

What are the conclusions we can draw?
1. Perhaps one conclusion would be that when using anonymous access types then indirect assignment should be preferred over direct assignment. (see Models.B.Direct_Assignment and Models.B.Indirect_Assignment).
2. Avoid anonymous access types. Prefer named access types and 'Unchecked_Access.

Is there anybody who can explain why direct assignment takes approximately 60 times longer than indirect assignment?

Best regards,
Åke Ragnar Dahlgren

^ permalink raw reply	[relevance 8%]

* Re: Ada and OpenMP
  @ 2013-03-08 21:37  5%   ` Brad Moore
  0 siblings, 0 replies; 200+ results
From: Brad Moore @ 2013-03-08 21:37 UTC (permalink / raw)


On 07/03/2013 3:52 PM, Simon Wright wrote:
> "Rego, P." <pvrego@gmail.com> writes:
>
>> I'm trying some exercises of parallel computing using that pragmas
>> from OpenMP in C, but it would be good to use it also in Ada. Is it
>> possible to use that pragmas from OpenMP in Ada? And...does gnat gpl
>> supports it?
>
> GNAT doesn't support OpenMP pragmas.
>
> But you might take a look at Paraffin:
> http://sourceforge.net/projects/paraffin/
>

To give an example using Paraffin libraries,

The following code shows the same problem executed sequentially, and
then executed with Paraffin libraries.

with Ada.Real_Time;    use Ada.Real_Time;
with Ada.Command_Line;
with Ada.Text_IO; use Ada.Text_IO;
with Parallel.Iteration.Work_Stealing;

procedure Test_Loops is

    procedure Integer_Loops is new
      Parallel.Iteration.Work_Stealing (Iteration_Index_Type => Integer);

    Start : Time;

    Array_Size : Natural := 50;
    Iterations : Natural := 10_000_000;

begin

    --  Allow first command line parameter to override default iteration 
count
    if Ada.Command_Line.Argument_Count >= 1 then
       Iterations := Integer'Value (Ada.Command_Line.Argument (1));
    end if;

    --  Allow second command line parameter to override default array size
    if Ada.Command_Line.Argument_Count >= 2 then
       Array_Size := Integer'Value (Ada.Command_Line.Argument (2));
    end if;

    Data_Block : declare
       Data : array (1 .. Array_Size) of Natural := (others => 0);
    begin

       --  Sequential Version of the code, any parallelization must be auto
       --  generated by the compiler

       Start := Clock;

       for I in Data'Range loop
          for J in 1 .. Iterations loop
             Data (I) := Data (I) + 1;
          end loop;
       end loop;

       Put_Line ("Sequential Elapsed=" & Duration'Image (To_Duration 
(Clock - Start)));

       Data := (others => 0);
       Start := Clock;

       --  Parallel Version of the code, explicitly parallelized using 
Paraffin
       declare

          procedure Iterate (First : Integer; Last : Integer) is
          begin
             for I in First .. Last loop
                for J in 1 .. Iterations loop
                   Data (I) := Data (I) + 1;
                end loop;
             end loop;
          end Iterate;

       begin
          Integer_Loops (From         => Data'First,
                         To           => Data'Last,
                         Worker_Count => 4,
                         Process      => Iterate'Access);
       end;

       Put_Line ("Parallel Elapsed=" & Duration'Image (To_Duration 
(Clock - Start)));

    end Data_Block;

end Test_Loops;

When run on my machine AMD Quadcore with parameters 100_000 100_000, 
with full optimization turned on with -ftree-vectorize, I get.

Sequential Elapsed= 6.874298000
Parallel Elapsed= 6.287230000

With optimization turned off, I get

Sequential Elapsed= 32.428908000
Parallel Elapsed= 8.424717000

gcc with GNAT does a good job of optimization when its enabled, for 
these cases as shown, but the differences between optimization and using 
Paraffin can be more pronounced in other cases that are more complex, 
such as loops that involve reduction (e.g. calculating a sum)

Brad



^ permalink raw reply	[relevance 5%]

* Re: Ada and OpenMP
  @ 2013-03-08 10:18  6%     ` Georg Bauhaus
  0 siblings, 0 replies; 200+ results
From: Georg Bauhaus @ 2013-03-08 10:18 UTC (permalink / raw)


On 08.03.13 00:43, Georg Bauhaus wrote:
> "Peter C. Chapin" <PChapin@vtc.vsc.edu> wrote:
>> OpenMP is a different animal than Ada tasks. It provides fine grained
>> parallelism where, for example, it is possible to have the compiler
>> automatically parallelize a loop. In C:
>>
>> #pragma omp parallel for
>> for( i = 0; i < MAX; ++i ) {
>>    array[i]++;
>> }
>
> Fortunately, OpenMP is no longer needed to achieve automatic
> parallelism in either C or Ada at the low level. GCC's vectorizer
> produces code that runs in parallel for a number of loop patterns.
> These are documented, and they work in GNAT GPL or more
> recent FSF GNATs. Later 4.7s IIRC.

For example, adding -ftree-vectorize to the set of options (-O2 ...)
increases the speed of the program below by factors up to 3, depending
to some extent on the value of MAX. (Option -O3 is even easier in this
case, and yields improvements when MAX = 8.)

The assembly listing includes instructions like MOVDQA and PADDD used
with SSE registers.

GNAT will report successful optimizations when -fopt-info-optimized
is among the switches (or -ftree-vectorizer-verbose=2 for older GNATs).

package Fast is

    MAX : constant := 50;

    subtype Number is Integer;
    type Index is new Natural range 0 .. MAX;

    type Vect is array (Index) of Number;

    procedure Inc_Array (V : in out Vect);

end Fast;

package body Fast is

    procedure Inc_Array (V : in out Vect) is
    begin
       for K in Index loop
          V (K) := V (K) + 1;
       end loop;
    end Inc_Array;

end Fast;


with Ada.Real_Time;    use Ada.Real_Time;
with Ada.Text_IO;
with Fast;    use Fast;
procedure Test_Fast is
    Start, Finish : Time;
    Data : Vect;
    Result : Integer := 0;
    pragma Volatile (Result);
begin
    Start := Clock;
    for Run in 1 .. 500_000_000/MAX loop
       Inc_Array (Data);
       if Data (Index(MAX/2 + Run mod MAX/2)) rem 2 = 1 then
          Result := 1;
       end if;
    end loop;
    Finish := Clock;
    Ada.Text_IO.Put_Line
      (Duration'Image (To_Duration (Finish - Start)));
end Test_Fast;





^ permalink raw reply	[relevance 6%]

* Re: Numerical calculations: Why not use fixed point types for everything?
  2013-01-19  6:26  8%           ` Jeffrey Carter
@ 2013-01-24 10:55  0%             ` Ada novice
  0 siblings, 0 replies; 200+ results
From: Ada novice @ 2013-01-24 10:55 UTC (permalink / raw)


On Saturday, January 19, 2013 7:26:25 AM UTC+1, Jeffrey Carter wrote
> 
> 
> jrcarter@jrcarter-gateway-1:~/Code$ ./sum
> 
> Float took 0.007979000
> 
> Fixed took 0.008180000
> 
> jrcarter@jrcarter-gateway-1:~/Code$ ./sum
> 
> Float took 0.007971000
> 
> Fixed took 0.008278000
> 
> jrcarter@jrcarter-gateway-1:~/Code$ ./sum
> 
> Float took 0.007979000
> 
> Fixed took 0.008403000
> 
> 
> 
> It seems that floating-point operations are slightly faster than fixed point on 
> 
> a (sort of) modern processor (AMD Athlon II M300).
> 
> 
> 
> The code:
> 
> 
> 
> with Ada.Real_Time;
> 
> with Ada.Text_IO;
> 
> 
> 
> with PragmARC.Universal_Random;
> 
> 

Hi, When I run your code with GNAT GPL 2011, I get the error message: "file pragmARC.ads" not found. 

Thanks.

YC



^ permalink raw reply	[relevance 0%]

* Re: Numerical calculations: Why not use fixed point types for everything?
  @ 2013-01-19  6:26  8%           ` Jeffrey Carter
  2013-01-24 10:55  0%             ` Ada novice
  0 siblings, 1 reply; 200+ results
From: Jeffrey Carter @ 2013-01-19  6:26 UTC (permalink / raw)


On 01/18/2013 09:41 PM, Dennis Lee Bieber wrote:
>
> 	My emphasis was that, lacking true hardware fixed point operations,
> the compiler has to track the position of the implied point and insert
> operations to (for lack of better term) normalize the results back into
> the declared type. Those the negative impact of those normalization
> instructions may cancel out any expected gain from using integer
> arithmetic operations.

I decided to run a test. My results:

jrcarter@jrcarter-gateway-1:~/Code$ ./sum
Float took 0.007979000
Fixed took 0.008180000
jrcarter@jrcarter-gateway-1:~/Code$ ./sum
Float took 0.007971000
Fixed took 0.008278000
jrcarter@jrcarter-gateway-1:~/Code$ ./sum
Float took 0.007979000
Fixed took 0.008403000

It seems that floating-point operations are slightly faster than fixed point on 
a (sort of) modern processor (AMD Athlon II M300).

The code:

with Ada.Real_Time;
with Ada.Text_IO;

with PragmARC.Universal_Random;

procedure Sum is
    package Random is new PragmARC.Universal_Random (Supplied_Real => Float);

    procedure Process is
       Max : constant := 5_000.0;

       subtype Index_Value is Integer range 1 .. 1_024;

       subtype Value is Float range -Max .. Max;

       type Value_List is array (Index_Value range <>) of Value;

       type Fixed is delta 2.0 ** (-20) range -Max .. Max;

       type Fixed_List is array (Index_Value range <>) of Fixed;

       Value_Length : constant Value := Value (Index_Value'Last);

       function Sum (List : in Value_List) return Value is
          Result : Value := 0.0;
       begin -- Sum
          Add_All : for I in List'Range loop
             Result := Result + List (I) / Value_Length;
          end loop Add_All;

          return Result;
       end Sum;

       Length : constant Index_Value := Index_Value'Last;

       function Sum (List : in Fixed_List) return Fixed is
          Result : Fixed := 0.0;
       begin -- Sum
          Add_All : for I in List'Range loop
             Result := Result + List (I) / Length;
          end loop Add_All;

          return Result;
       end Sum;

       Value_Set : Value_List (Index_Value) := (Index_Value => 
Random.Random_Range (-Max, Max) );
       Fixed_Set : Fixed_List (Index_Value);

       Target_Index : constant Index_Value := Random.Random_Int 
(Index_Value'First, Index_Value'Last);

       Value_Result : Value;
       Fixed_Result : Fixed;
       Start        : Ada.Real_Time.Time;

       use type Ada.Real_Time.Time;
    begin -- Process
       Copy : for I in Value_Set'Range loop
          Fixed_Set (I) := Fixed (Value_Set (I) );
       end loop Copy;

       Start := Ada.Real_Time.Clock;

       Float_Test : for I in Index_Value loop
          Value_Result := Sum (Value_Set);
       end loop Float_Test;

       Ada.Text_IO.Put_Line (Item => "Float took" & Duration'Image 
(Ada.Real_Time.To_Duration (Ada.Real_Time.Clock - Start) ) );

       Start := Ada.Real_Time.Clock;

       Fixed_Test : for I in Index_Value loop
          Fixed_Result := Sum (Fixed_Set);
       end loop Fixed_Test;

       Ada.Text_IO.Put_Line (Item => "Fixed took" & Duration'Image 
(Ada.Real_Time.To_Duration (Ada.Real_Time.Clock - Start) ) );
    end Process;
begin -- Sum
    Random.Randomize;
    Process;
end Sum;

(I realize this actually calculates averages, but it started out doing sums 
until I realized the sum might not fit into the ranges I was using, and I'm too 
lazy to change the names.)

-- 
Jeff Carter
"I wave my private parts at your aunties."
Monty Python & the Holy Grail
13



^ permalink raw reply	[relevance 8%]

* Re: Ada.Calendar and NTP (and Unix Epoch)
  2012-07-24  7:11  5%     ` Dmitry A. Kazakov
@ 2012-07-24  7:50  0%       ` erlo.haugen
  2012-07-24  8:14  0%         ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: erlo.haugen @ 2012-07-24  7:50 UTC (permalink / raw)


Den tirsdag den 24. juli 2012 09.11.57 UTC+2 skrev Dmitry A. Kazakov:
> On Tue, 24 Jul 2012 00:37:13 -0400, Dennis Lee Bieber wrote:
> 
> &gt; On Mon, 23 Jul 2012 15:07:48 -0700 (PDT), Adam Beneschan
> &gt; &lt;adam@irvine.com&gt; declaimed the following in comp.lang.ada:
> &gt; 
> &gt; My gut feeling is that if NTP gives you a time in the range 1-1-1900 to
> &gt; 12-31-1900, something is pretty wrong because computers didn&#39;t exist
> &gt; during that time period.  So I&#39;m not really sure what the issue is.  I
> &gt; think you need 
> &gt; 
> &gt; 	Nonetheless, it appears that a 128bit value of all 0s represents the
> &gt; epoch for Network Time Protocol...
> 
> Is NTP political time? If not, it does not make much sense to convert it
> Ada.Calendar.Time anyway. Ada.Real_Time.Time looks more appropriate.
> 
> -- 
> Regards,
> Dmitry A. Kazakov
> http://www.dmitry-kazakov.de

Enlighten me please, what is meant by 'political time'?

Erlo



^ permalink raw reply	[relevance 0%]

* Re: Ada.Calendar and NTP (and Unix Epoch)
  2012-07-24 18:28  4%       ` Dmitry A. Kazakov
  2012-07-24 19:07  5%         ` Adam Beneschan
@ 2012-07-24 19:43  0%         ` Vasiliy Molostov
  1 sibling, 0 replies; 200+ results
From: Vasiliy Molostov @ 2012-07-24 19:43 UTC (permalink / raw)


Dmitry A. Kazakov <mailbox@dmitry-kazakov.de> писал(а) в своём письме Tue,  
24 Jul 2012 22:28:27 +0400:

> Furthermore, operations like UTC_Time_Offset, Time_Of, Split for some
> distant time in the past, e.g. 1901 are most likely wrong, because  
> OS/Ada's
> RTL cannot keep track of all political changes of all time zones in order
> to be able to evaluate the number of seconds from present time to 1901 in
> the time zone. It is *not* the number of years multiplied by the year's
> duration. (IANA Time Zone Database or alike is required for that)
>
> Calculating future times is absolutely impossible because that depends on
> future decisions of the corresponding governmental bodies having the
> authority over the time zone, from daylight saving time to changing the
> whole zone.

I took a look at  
http://www.ada-auth.org/cgi-bin/cvsweb.cgi/ai05s/ai05-0119-1.txt

And I can say that there is a mis .... "misviewving" of the Time, UTC time  
and Zoned Time (political)

While typical application takes time from some sort of monotonic time  
source (e.g. clock), which is supposed to be one and authoritative for  
such application, it is in the same moment this application also deals  
with time representation, and a "political" time (zoned) is one of such  
representations.

Probably and personally, I don't prefer to convert between representations  
and catch one or two hour diffs, instead I prefer to do calculations  
better done with monotonic time, and then convert result to the required  
representation.

Converting from some representation into authoritative monotonic time is  
"mission impossibe", since important data may be lost, because this  
important data belongs entirely to the representation, and can not be  
expressed in monotonic authoritative source.

Things like "ada.calendar is a fake" are just based on "speculative  
cone-moving" between "time real value" and "time representation".

>
> This is why it is better not to touch Ada.Calendar.Time.
>
> Ada.Real_Time, Duration, Time_Span, some numeric type would be much  
> better
> candidates.
>


-- 
Написано в почтовом клиенте браузера Opera: http://www.opera.com/mail/



^ permalink raw reply	[relevance 0%]

* Re: Ada.Calendar and NTP (and Unix Epoch)
  2012-07-24 19:07  5%         ` Adam Beneschan
@ 2012-07-24 20:17  4%           ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2012-07-24 20:17 UTC (permalink / raw)


On Tue, 24 Jul 2012 12:07:52 -0700 (PDT), Adam Beneschan wrote:

> On Tuesday, July 24, 2012 11:28:27 AM UTC-7, Dmitry A. Kazakov wrote:
>> On Tue, 24 Jul 2012 09:26:46 -0700 (PDT), Adam Beneschan wrote:
>> 
>> &gt; Now, use Ada.Calendar.Time_Of to create a Time T_Base representing 1/1/1901. 
>> &gt; Or, better, if the NTP time is always UTC, then you should probably use
>> &gt; Ada.Calendar.Formatting.Time_Of to create a time that represents midnight
>> &gt; of 1/1/1901 in UTC time; I think you do this by passing Time_Zone =&gt;
>> &gt; Ada.Calendar.Time_Zones.UTC_Time_Offset.  (Somebody please correct me if
>> &gt; I&#39;m supposed to negate the value.)
>> 
>> There is no simple way of converting Ada.Calendar.Time to UTC. At least
>> there was none in Ada 2005. I think Randy Brukardt wanted to fix that, or
>> sort of.
> 
> The problem here, I think, is that the concept of "converting
> Ada.Calendar.Time to UTC" is a broad, general one, and probably somewhat
> vague.  I'm not trying to explain how to work with UTC time in general;
> I'm trying to solve a specific problem.
> 
> The specific problem (as I understood it) was this:  You have an integer
> value that represents a specific *point* *in* *time* T1 by specifying the
> number of seconds that have elapsed since midnight on New Years Day in
> Greenwich.

T1 [GMT]

> You have another value that was returned by Ada.Calendar.Clock at some
> other point in time T2.

T2 [nobody knows what]

>  My contention is that you can create an Ada.Calendar.Time value to
> represent T1 by using Ada.Calendar.Formatting.Time_Of with a suitable
> Time_Offset,

The problem is the Time_Offset, where do you get it? You need
GMT_Time_Offset, which firstly is not defined, and secondly if it were
there, it would be no more constant than the UTC_Time_Offset is.

Once you get T1 and T2 to the same time basis of more or less monotonic
time, e.g. GMT, UTC, whatever, but *not* a political time, there will be no
further problems.

> Furthermore, I don't see how Ada.Real_Time is a solution; that package's
> purpose is, I think, to provide a better way to measure time *intervals*
> with a higher resolution, but it doesn't do all that well with absolute
> time (the RM says that Real_Time is considered relative to an undefined
> "epoch" that could be the last system boot time).  So I don't see how it
> could be involved in a solution to this particular problem.

Ada.Real_Time.Time is not a full solution. It only provides sane time
arithmetic, e.g. "+", "-". A numeric type could do this as well.

Ada.Calendar.Time cannot give even that little. You could not define
arithmetical operations on it in any reasonable way. This is of course
because of time skews, which make some values non-existent and some values
repeating. I presume that any Ada implementation of it is broken in this or
other way, which is irrelevant here, because there is no way to have
arithmetic on something that is not additive anyway. I posted a couple
examples for CET on the topic to Ada Comments some time ago.

So the rule is: do not do any computations with Ada.Calendar.Time. Ada RM
simply does not define the outcome.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 4%]

* Ada.Calendar Question
@ 2012-07-20 17:18  5% awdorrin
  2012-07-20 17:59  0% ` Adam Beneschan
  0 siblings, 1 reply; 200+ results
From: awdorrin @ 2012-07-20 17:18 UTC (permalink / raw)


I have been looking at the Ada.Calendar and Ada.Real_Time packages, trying to update some old Ada code, which interfaces to C.

How do I access the 'Conversion_Operations' package defined within Ada.Calendar?

I have been trying to make use of:
 Conversion_Operations.To_Ada_Time( Unix_Time : Long-Integer );
 Conversion_Operations.To_Struct_Timespec()
and
 Conversion_Operations.To_Duration()

I have seen the C specific versions in Ada.Calendar.Conversion, but those all use the Interfaces.C package types.








^ permalink raw reply	[relevance 5%]

* Re: Ada.Calendar and NTP (and Unix Epoch)
  @ 2012-07-24 18:28  4%       ` Dmitry A. Kazakov
  2012-07-24 19:07  5%         ` Adam Beneschan
  2012-07-24 19:43  0%         ` Vasiliy Molostov
  0 siblings, 2 replies; 200+ results
From: Dmitry A. Kazakov @ 2012-07-24 18:28 UTC (permalink / raw)


On Tue, 24 Jul 2012 09:26:46 -0700 (PDT), Adam Beneschan wrote:

> Now, use Ada.Calendar.Time_Of to create a Time T_Base representing 1/1/1901. 
> Or, better, if the NTP time is always UTC, then you should probably use
> Ada.Calendar.Formatting.Time_Of to create a time that represents midnight
> of 1/1/1901 in UTC time; I think you do this by passing Time_Zone =>
> Ada.Calendar.Time_Zones.UTC_Time_Offset.  (Somebody please correct me if
> I'm supposed to negate the value.)

There is no simple way of converting Ada.Calendar.Time to UTC. At least
there was none in Ada 2005. I think Randy Brukardt wanted to fix that, or
sort of.

The problem is that UTC_Time_Offset has time argument. It is not constant.
UTC_Time_Offset jumps forth and back together with the political time.

Furthermore, operations like UTC_Time_Offset, Time_Of, Split for some
distant time in the past, e.g. 1901 are most likely wrong, because OS/Ada's
RTL cannot keep track of all political changes of all time zones in order
to be able to evaluate the number of seconds from present time to 1901 in
the time zone. It is *not* the number of years multiplied by the year's
duration. (IANA Time Zone Database or alike is required for that)

Calculating future times is absolutely impossible because that depends on
future decisions of the corresponding governmental bodies having the
authority over the time zone, from daylight saving time to changing the
whole zone.

This is why it is better not to touch Ada.Calendar.Time.

Ada.Real_Time, Duration, Time_Span, some numeric type would be much better
candidates.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 4%]

* Re: Ada.Calendar and NTP (and Unix Epoch)
  2012-07-24  7:50  0%       ` erlo.haugen
@ 2012-07-24  8:14  0%         ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2012-07-24  8:14 UTC (permalink / raw)


On Tue, 24 Jul 2012 00:50:15 -0700 (PDT), erlo.haugen@gmail.com wrote:

> Den tirsdag den 24. juli 2012 09.11.57 UTC+2 skrev Dmitry A. Kazakov:
>> On Tue, 24 Jul 2012 00:37:13 -0400, Dennis Lee Bieber wrote:
>> 
>> &gt; On Mon, 23 Jul 2012 15:07:48 -0700 (PDT), Adam Beneschan
>> &gt; &lt;adam@irvine.com&gt; declaimed the following in comp.lang.ada:
>> &gt; 
>> &gt; My gut feeling is that if NTP gives you a time in the range 1-1-1900 to
>> &gt; 12-31-1900, something is pretty wrong because computers didn&#39;t exist
>> &gt; during that time period.  So I&#39;m not really sure what the issue is.  I
>> &gt; think you need 
>> &gt; 
>> &gt; 	Nonetheless, it appears that a 128bit value of all 0s represents the
>> &gt; epoch for Network Time Protocol...
>> 
>> Is NTP political time? If not, it does not make much sense to convert it
>> Ada.Calendar.Time anyway. Ada.Real_Time.Time looks more appropriate.
> 
> Enlighten me please, what is meant by 'political time'?

Political time is one regulated by politicians, localized, daylight saving
etc. Political time is unusable for the purpose of time stamping and clock
synchronization, but of course indispensable for the UI.

Ada.Calendar implicitly represents such a time. NTP, I only guess, because
we are using other mechanisms of time distribution and synchronization, is
not a political time. Is it UTC?

Which is why I second to Adam asking what are going to achieve.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: Ada.Calendar and NTP (and Unix Epoch)
       [not found]       ` <5s8s08lv6dj1i4tkb99roq9roifsgr44vd@invalid.netcom.com>
@ 2012-07-24  7:11  5%     ` Dmitry A. Kazakov
  2012-07-24  7:50  0%       ` erlo.haugen
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2012-07-24  7:11 UTC (permalink / raw)


On Tue, 24 Jul 2012 00:37:13 -0400, Dennis Lee Bieber wrote:

> On Mon, 23 Jul 2012 15:07:48 -0700 (PDT), Adam Beneschan
> <adam@irvine.com> declaimed the following in comp.lang.ada:
> 
> My gut feeling is that if NTP gives you a time in the range 1-1-1900 to
> 12-31-1900, something is pretty wrong because computers didn't exist
> during that time period.  So I'm not really sure what the issue is.  I
> think you need 
> 
> 	Nonetheless, it appears that a 128bit value of all 0s represents the
> epoch for Network Time Protocol...

Is NTP political time? If not, it does not make much sense to convert it
Ada.Calendar.Time anyway. Ada.Real_Time.Time looks more appropriate.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 5%]

* Re: Ada.Calendar Question
  2012-07-20 17:18  5% Ada.Calendar Question awdorrin
@ 2012-07-20 17:59  0% ` Adam Beneschan
  0 siblings, 0 replies; 200+ results
From: Adam Beneschan @ 2012-07-20 17:59 UTC (permalink / raw)


On Friday, July 20, 2012 10:18:22 AM UTC-7, awdorrin wrote:
> I have been looking at the Ada.Calendar and Ada.Real_Time packages, trying to update some old Ada code, which interfaces to C.
> 
> How do I access the 'Conversion_Operations' package defined within
> Ada.Calendar?

This is defined in the *private* part of one implementor's implementation of Ada.Calendar.  They could easily change the semantics of those routines in a future release.  So attempting to access them seems like a very bad idea.

                          -- Adam



^ permalink raw reply	[relevance 0%]

* Re: Ada.Calendar and NTP (and Unix Epoch)
  2012-07-24 18:28  4%       ` Dmitry A. Kazakov
@ 2012-07-24 19:07  5%         ` Adam Beneschan
  2012-07-24 20:17  4%           ` Dmitry A. Kazakov
  2012-07-24 19:43  0%         ` Vasiliy Molostov
  1 sibling, 1 reply; 200+ results
From: Adam Beneschan @ 2012-07-24 19:07 UTC (permalink / raw)


On Tuesday, July 24, 2012 11:28:27 AM UTC-7, Dmitry A. Kazakov wrote:
> On Tue, 24 Jul 2012 09:26:46 -0700 (PDT), Adam Beneschan wrote:
> 
> &gt; Now, use Ada.Calendar.Time_Of to create a Time T_Base representing 1/1/1901. 
> &gt; Or, better, if the NTP time is always UTC, then you should probably use
> &gt; Ada.Calendar.Formatting.Time_Of to create a time that represents midnight
> &gt; of 1/1/1901 in UTC time; I think you do this by passing Time_Zone =&gt;
> &gt; Ada.Calendar.Time_Zones.UTC_Time_Offset.  (Somebody please correct me if
> &gt; I&#39;m supposed to negate the value.)
> 
> There is no simple way of converting Ada.Calendar.Time to UTC. At least
> there was none in Ada 2005. I think Randy Brukardt wanted to fix that, or
> sort of.

The problem here, I think, is that the concept of "converting Ada.Calendar.Time to UTC" is a broad, general one, and probably somewhat vague.  I'm not trying to explain how to work with UTC time in general; I'm trying to solve a specific problem.

The specific problem (as I understood it) was this:  You have an integer value that represents a specific *point* *in* *time* T1 by specifying the number of seconds that have elapsed since midnight on New Years Day in Greenwich.  You have another value that was returned by Ada.Calendar.Clock at some other point in time T2.  My contention is that you can create an Ada.Calendar.Time value to represent T1 by using Ada.Calendar.Formatting.Time_Of with a suitable Time_Offset, and using the "+" functions defined in Ada.Calendar and Ada.Calendar.Formatting, that produces an Ada.Calendar.Time value representing T1 that can correctly be compared with T2 (and subtracted to produce a Duration).

Do you believe my contention is incorrect?  If so, please demonstrate.

It's true, as you say, that UTC_Time_Offset's result isn't constant, and changes when the time zone goes in and out of Daylight Savings Time.  The point is, I was trying to use it in a way that would cancel out the effect of that, producing a result in which the "offsets" factored into the two Ada.Calendar.Time values being compared are the same, which means that you can compare or subtract them correctly, regardless of whether the offsets would be different if you ran the program six months from now.  I may have done it wrong, but I don't believe it is impossible.  If it is, please show why.

There are certainly a lot of things that are difficult to get right with Ada.Calendar for some of the reasons you state.  I don't think any of those are relevant to solving *this* particular problem.  Furthermore, I don't see how Ada.Real_Time is a solution; that package's purpose is, I think, to provide a better way to measure time *intervals* with a higher resolution, but it doesn't do all that well with absolute time (the RM says that Real_Time is considered relative to an undefined "epoch" that could be the last system boot time).  So I don't see how it could be involved in a solution to this particular problem.

                            -- Adam



^ permalink raw reply	[relevance 5%]

* Re: GNAT (GCC) Profile Guided Compilation
  2012-07-01 17:45  4%           ` Georg Bauhaus
@ 2012-07-01 22:57  0%             ` Keean Schupke
  0 siblings, 0 replies; 200+ results
From: Keean Schupke @ 2012-07-01 22:57 UTC (permalink / raw)


On Sunday, 1 July 2012 18:45:22 UTC+1, Georg Bauhaus  wrote:
> On 29.06.12 19:03, Keean Schupke wrote:
> > Note: this is not really answering my question about the lack of improvement due to profile-guided compilation - but perhaps that side of things is more a compiler issue. Does anyone have any ideas about that side of things?
> 
> Some more observations, collected with the help of the simple
> two example programs appended below.
> 
> For Ada and GNAT at least, any advantages to be had from profile-guided
> compilation seem to vary with optimization options and sizes of data.
> The same is true about a 1D approach vs a 2D approach.
> 
> Among the various arrangements, one of the best I have got
> from both GNAT GPL 2012, and from an FSF GNAT as of June 2012
> uses
> *) -O2 -funroll-loops -gnatp
> *)  the 2D approach
> 
> (If it means a anything, adding -ftree-vectorize to the -O2 set
> produces only the second best Ada result, the same as the -O3 times
> listed below. I had chosen -ftree-vectorize as this switch is in the
> O3 set.) Trying profile guided compilation at higher optimization
> levels consistently slowed the Ada program down (other Ada programs
> were faster after profile guided compilation, as mentioned elsewhere).
> 
> The result at -O2 seems nice, though, in that the 2D approach is
> natural, the compiler switches are the ones that the manual recommends.
> and this combination produces the fastest Ada program.
> 
> In short, from worst to best 1D / 2D, Runs = 100:
> 
> Ada profile guided -> .88 / .80   (this program only!)
> Ada at -O3         -> .68 / .66
> C++ at -O3         -> .66
> Ada at -O2 -funr.. -> .68 / .47
> C++ profile guided -> .31
> 
> 
> Some differences seem to vary with hardware, too.
> On one computer I have seen a minor speedup, on another
> a very small slowdown, and a different ratio of 1D / 2D.
> 
> For the C++ case I have tested a 1D approach only, not
> knowing how to write 2D arrays in C++ using C style arrays.
> I'm not a C++ programmer, apologies for my C++.
> 
> 
> Ada at -O2 -funroll-loops -gnatp -mtune=native
> 1D:  0.680750000 27303
> 2D:  0.469094000 27303  <-- Best for Ada!
> 
> Ada at -O3 -gnatNp -fomit-frame-pointer -mtune=native
> 1D:  0.676616000 27303
> 2D:  0.664194000 27303
> 
> previous with profile-guided compilation
> 1D:  0.888206000 27303
> 2D:  0.806196000 27303
> 
> C++ at -O3 -mtune=native
> 1D: 0.681721 0
> 
> previous with profile-guided compilation
> 1D: 0.31165 0
> 
> Clang++
> 1D: 0.611522 0
> 
> The GNU C++ compiler is from the GNAT GPL 2012 distribution for Mac OS X,
> Clang++ is Apple's v 3.1.
> 
> 
> === 8< === 8< === 8< === 8< ===
> 
> package Fringes is
> 
>     pragma Pure (Fringes);
> 
>     type Full_Index is mod 2**32;
>     subtype Num is Full_Index Range 0 .. 100_000;
>     subtype Index is Full_Index range 0 .. 1000;
>     Len : constant Full_Index := Index'Last - Index'First + 1;
> 
>     type Matrix_1D is
>       array (Index'First .. Index'First + Len * Len - 1) of Num;
>     type Matrix_2 is array (Index, Index) of Num;
> 
>     procedure Compute_1D (A : in out Matrix_1D);
>     procedure Compute_2  (A : in out Matrix_2);
> 
> end Fringes;
> 
> package body Fringes is
> 
>     --
>     --  Each Compute procedure has A pointless loop that assigns each
>     --  inner field the sum of non-diagonal neighbors modulo Num'Last
>     --
> 
>     procedure NOT_USED_Compute_1D_Slow (A : in out Matrix_1D) is
>        J : Full_Index;
>     begin
>        J := A'First + Len;
>        loop
>          exit when J > A'Last - Len;
>          for K in J + 1 .. J + Len - 1 - 1 loop
>             A (K) := (A(K + 1)
>                       + A(K - Len)
>                       + A(K - 1)
>                       + A(K + Len)) mod Num'Last;
>          end loop;
>          J := J + Len;
>        end loop;
>     end NOT_USED_Compute_1D_Slow;
> 
>     procedure Compute_1D (A : in out Matrix_1D) is
>     begin
>        for K in A'First + Len + 1 .. A'Last - Len - 1 loop
>           case K mod Len is
>           when 0 | Len - 1 => null;
>           when others =>
>              A (K) := (A(K + 1)
>                        + A(K - Len)
>                        + A(K - 1)
>                        + A(K + Len)) mod Num'Last;
>           end case;
>        end loop;
>     end Compute_1D;
> 
>     procedure Compute_2 (A : in out Matrix_2) is
>     begin
>        for J in A'First(1) + 1 .. A'Last(1) - 1 loop
>           for K in A'First(2) + 1 .. A'Last(2) - 1 loop
>              A (J, K) := (A(J, K + 1)
>                           + A(j - 1, K)
>                           + A(J, K - 1)
>                           + A(j + 1, K)) mod Num'Last;
>           end loop;
>        end loop;
>     end Compute_2;
> 
> end Fringes;
> 
> 
> with Fringes;
> with Ada.Command_Line, Ada.Real_Time;
> procedure Test_Fringes is
> 
>     use Ada.Real_Time;
> 
>     Runs : constant Natural :=
>       Natural'Value (Ada.Command_Line.Argument(1));
> 
>     Start, Stop: Time;
> 
>     package Os_Or_Gnat_Stacksize_Nuisance is
>        use Fringes;
>        type P1 is access Matrix_1D;
>        type P2 is access Matrix_2;
>        M1P : constant P1 := new Matrix_1D'(others => 123);
>        M2p : constant P2 := new Matrix_2'(Index => (Index => 123));
>        M1D : Matrix_1D renames M1P.all;
>        M2 : Matrix_2 renames M2P.all;
>     end Os_Or_Gnat_Stacksize_Nuisance;
>     use Os_Or_Gnat_Stacksize_Nuisance;
> 
>     procedure Print_Timing (Part : String; N : Fringes.Num) is separate;
>     use type Fringes.Full_Index;
> begin
>     Start := Clock;
>     for Run in 1 .. Runs loop
>        Fringes.Compute_1D (M1D);
>     end loop;
>     Stop := Clock;
>     Print_Timing ("1D", M1D ((M1D'First + 1 * Fringes.Len) + (2)));
> 
>     Start := Clock;
>     for Run in 1 .. Runs loop
>        Fringes.Compute_2 (M2);
>     end loop;
>     Stop := Clock;
>     Print_Timing ("2D", M2 (1, 2));
> end Test_Fringes;
> 
> with Ada.Text_IO;
> separate (Test_Fringes)
> procedure Print_Timing (Part : String; N : Fringes.Num) is
>     use Ada.Text_IO;
> begin
>     Put (Part);
>     Put (": ");
>     Put (Duration'Image (To_Duration(Stop - Start)));
>     Put (Fringes.Num'Image (N));
>     New_Line;
> end print_timing;
> 
> 
> === 8< === 8< === 8< === 8< ===
> 
> #include <stdint.h>
> 
> namespace Fringes {
> 
>      typedef  uint32_t Full_Index;
> #define Num_Last 100000
>      typedef Full_Index Num;
> #define Index_Last 1000
>      typedef Full_Index Index;
>      const Full_Index Len = Index_Last + 1;
> 
> #define A_Last ((Len * Len) - 1)
>      typedef Num Matrix_1D[A_Last + 1];
> 
>      void Compute_1D (Matrix_1D&  A);
>      //  Each Compute procedure has a pointless loop that assigns each
>      //  inner field the sum of non-diagonal neighbors modulo Num_Last
>      void Compute_1D (Matrix_1D&  A) {
> 
>          for (Full_Index K = Len + 1; K < A_Last - Len - 1; ++K) {
>              switch (K % Len) {
>              case 0: case Len - 1: break;
>              default:
>                  A [K] = (A[K + 1]
>                            + A[K - Len]
>                            + A[K - 1]
>                            + A[K + Len]) % Num_Last;
>              }
>          }
>      }
> }
> 
> #include <sys/time.h>
> #include <string>
> 
> class Reporter {
>      struct timeval Start, Stop;
> public:
>      void logStart();
>      void logStop();
>      void Print_Timing (const std::string Part, const Fringes::Num N);
> };
> 
> 
> #include <sstream>
> 
> int main(int argc, char* argv[]) {
>      using namespace Fringes;
> 
>      int Runs;
>      Matrix_1D* M1D = new Matrix_1D[Len];
>      Reporter history;
> 
>      if (argc == 0) {
>          throw "usage";
>      } else {
>          std::istringstream converter(argv[1]);
> 
>          if (! ((converter >> Runs) && (Runs >= 0))) {
>              throw "argument error?";
>          }
>      }
>      
>      history.logStart();
>      for (int Run = 1; Run <= Runs; ++Run) {
>          Compute_1D (*M1D);
>      }
>      history.logStop();
>      history.Print_Timing ("1D", (*M1D) [(1 * Len) + (2)]);
> }
> 
> 
> #include <iostream>
> #include <sys/time.h>
> 
> void Reporter::Print_Timing (const std::string Part, const Fringes::Num N) {
>      double difference = (Stop.tv_sec - Start.tv_sec) * 1000000
>              + (Stop.tv_usec - Start.tv_usec);
>      std::cout << Part << ": ";
>      std::cout << (difference / 1000000.0) << " " << N;
>      std::cout << '\n';
> }
> 
> void Reporter::logStart() {
>      gettimeofday(&this->Start, 0);
> }
> 
> void Reporter::logStop() {
>      gettimeofday(&this->Stop, 0);
> }

On Sunday, 1 July 2012 18:45:22 UTC+1, Georg Bauhaus  wrote:
> On 29.06.12 19:03, Keean Schupke wrote:
> > Note: this is not really answering my question about the lack of improvement due to profile-guided compilation - but perhaps that side of things is more a compiler issue. Does anyone have any ideas about that side of things?
> 
> Some more observations, collected with the help of the simple
> two example programs appended below.
> 
> For Ada and GNAT at least, any advantages to be had from profile-guided
> compilation seem to vary with optimization options and sizes of data.
> The same is true about a 1D approach vs a 2D approach.
> 
> Among the various arrangements, one of the best I have got
> from both GNAT GPL 2012, and from an FSF GNAT as of June 2012
> uses
> *) -O2 -funroll-loops -gnatp
> *)  the 2D approach
> 
> (If it means a anything, adding -ftree-vectorize to the -O2 set
> produces only the second best Ada result, the same as the -O3 times
> listed below. I had chosen -ftree-vectorize as this switch is in the
> O3 set.) Trying profile guided compilation at higher optimization
> levels consistently slowed the Ada program down (other Ada programs
> were faster after profile guided compilation, as mentioned elsewhere).
> 
> The result at -O2 seems nice, though, in that the 2D approach is
> natural, the compiler switches are the ones that the manual recommends.
> and this combination produces the fastest Ada program.
> 
> In short, from worst to best 1D / 2D, Runs = 100:
> 
> Ada profile guided -> .88 / .80   (this program only!)
> Ada at -O3         -> .68 / .66
> C++ at -O3         -> .66
> Ada at -O2 -funr.. -> .68 / .47
> C++ profile guided -> .31
> 
> 
> Some differences seem to vary with hardware, too.
> On one computer I have seen a minor speedup, on another
> a very small slowdown, and a different ratio of 1D / 2D.
> 
> For the C++ case I have tested a 1D approach only, not
> knowing how to write 2D arrays in C++ using C style arrays.
> I'm not a C++ programmer, apologies for my C++.
> 
> 
> Ada at -O2 -funroll-loops -gnatp -mtune=native
> 1D:  0.680750000 27303
> 2D:  0.469094000 27303  <-- Best for Ada!
> 
> Ada at -O3 -gnatNp -fomit-frame-pointer -mtune=native
> 1D:  0.676616000 27303
> 2D:  0.664194000 27303
> 
> previous with profile-guided compilation
> 1D:  0.888206000 27303
> 2D:  0.806196000 27303
> 
> C++ at -O3 -mtune=native
> 1D: 0.681721 0
> 
> previous with profile-guided compilation
> 1D: 0.31165 0
> 
> Clang++
> 1D: 0.611522 0
> 
> The GNU C++ compiler is from the GNAT GPL 2012 distribution for Mac OS X,
> Clang++ is Apple's v 3.1.
> 
> 
> === 8< === 8< === 8< === 8< ===
> 
> package Fringes is
> 
>     pragma Pure (Fringes);
> 
>     type Full_Index is mod 2**32;
>     subtype Num is Full_Index Range 0 .. 100_000;
>     subtype Index is Full_Index range 0 .. 1000;
>     Len : constant Full_Index := Index'Last - Index'First + 1;
> 
>     type Matrix_1D is
>       array (Index'First .. Index'First + Len * Len - 1) of Num;
>     type Matrix_2 is array (Index, Index) of Num;
> 
>     procedure Compute_1D (A : in out Matrix_1D);
>     procedure Compute_2  (A : in out Matrix_2);
> 
> end Fringes;
> 
> package body Fringes is
> 
>     --
>     --  Each Compute procedure has A pointless loop that assigns each
>     --  inner field the sum of non-diagonal neighbors modulo Num'Last
>     --
> 
>     procedure NOT_USED_Compute_1D_Slow (A : in out Matrix_1D) is
>        J : Full_Index;
>     begin
>        J := A'First + Len;
>        loop
>          exit when J > A'Last - Len;
>          for K in J + 1 .. J + Len - 1 - 1 loop
>             A (K) := (A(K + 1)
>                       + A(K - Len)
>                       + A(K - 1)
>                       + A(K + Len)) mod Num'Last;
>          end loop;
>          J := J + Len;
>        end loop;
>     end NOT_USED_Compute_1D_Slow;
> 
>     procedure Compute_1D (A : in out Matrix_1D) is
>     begin
>        for K in A'First + Len + 1 .. A'Last - Len - 1 loop
>           case K mod Len is
>           when 0 | Len - 1 => null;
>           when others =>
>              A (K) := (A(K + 1)
>                        + A(K - Len)
>                        + A(K - 1)
>                        + A(K + Len)) mod Num'Last;
>           end case;
>        end loop;
>     end Compute_1D;
> 
>     procedure Compute_2 (A : in out Matrix_2) is
>     begin
>        for J in A'First(1) + 1 .. A'Last(1) - 1 loop
>           for K in A'First(2) + 1 .. A'Last(2) - 1 loop
>              A (J, K) := (A(J, K + 1)
>                           + A(j - 1, K)
>                           + A(J, K - 1)
>                           + A(j + 1, K)) mod Num'Last;
>           end loop;
>        end loop;
>     end Compute_2;
> 
> end Fringes;
> 
> 
> with Fringes;
> with Ada.Command_Line, Ada.Real_Time;
> procedure Test_Fringes is
> 
>     use Ada.Real_Time;
> 
>     Runs : constant Natural :=
>       Natural'Value (Ada.Command_Line.Argument(1));
> 
>     Start, Stop: Time;
> 
>     package Os_Or_Gnat_Stacksize_Nuisance is
>        use Fringes;
>        type P1 is access Matrix_1D;
>        type P2 is access Matrix_2;
>        M1P : constant P1 := new Matrix_1D'(others => 123);
>        M2p : constant P2 := new Matrix_2'(Index => (Index => 123));
>        M1D : Matrix_1D renames M1P.all;
>        M2 : Matrix_2 renames M2P.all;
>     end Os_Or_Gnat_Stacksize_Nuisance;
>     use Os_Or_Gnat_Stacksize_Nuisance;
> 
>     procedure Print_Timing (Part : String; N : Fringes.Num) is separate;
>     use type Fringes.Full_Index;
> begin
>     Start := Clock;
>     for Run in 1 .. Runs loop
>        Fringes.Compute_1D (M1D);
>     end loop;
>     Stop := Clock;
>     Print_Timing ("1D", M1D ((M1D'First + 1 * Fringes.Len) + (2)));
> 
>     Start := Clock;
>     for Run in 1 .. Runs loop
>        Fringes.Compute_2 (M2);
>     end loop;
>     Stop := Clock;
>     Print_Timing ("2D", M2 (1, 2));
> end Test_Fringes;
> 
> with Ada.Text_IO;
> separate (Test_Fringes)
> procedure Print_Timing (Part : String; N : Fringes.Num) is
>     use Ada.Text_IO;
> begin
>     Put (Part);
>     Put (": ");
>     Put (Duration'Image (To_Duration(Stop - Start)));
>     Put (Fringes.Num'Image (N));
>     New_Line;
> end print_timing;
> 
> 
> === 8< === 8< === 8< === 8< ===
> 
> #include <stdint.h>
> 
> namespace Fringes {
> 
>      typedef  uint32_t Full_Index;
> #define Num_Last 100000
>      typedef Full_Index Num;
> #define Index_Last 1000
>      typedef Full_Index Index;
>      const Full_Index Len = Index_Last + 1;
> 
> #define A_Last ((Len * Len) - 1)
>      typedef Num Matrix_1D[A_Last + 1];
> 
>      void Compute_1D (Matrix_1D&  A);
>      //  Each Compute procedure has a pointless loop that assigns each
>      //  inner field the sum of non-diagonal neighbors modulo Num_Last
>      void Compute_1D (Matrix_1D&  A) {
> 
>          for (Full_Index K = Len + 1; K < A_Last - Len - 1; ++K) {
>              switch (K % Len) {
>              case 0: case Len - 1: break;
>              default:
>                  A [K] = (A[K + 1]
>                            + A[K - Len]
>                            + A[K - 1]
>                            + A[K + Len]) % Num_Last;
>              }
>          }
>      }
> }
> 
> #include <sys/time.h>
> #include <string>
> 
> class Reporter {
>      struct timeval Start, Stop;
> public:
>      void logStart();
>      void logStop();
>      void Print_Timing (const std::string Part, const Fringes::Num N);
> };
> 
> 
> #include <sstream>
> 
> int main(int argc, char* argv[]) {
>      using namespace Fringes;
> 
>      int Runs;
>      Matrix_1D* M1D = new Matrix_1D[Len];
>      Reporter history;
> 
>      if (argc == 0) {
>          throw "usage";
>      } else {
>          std::istringstream converter(argv[1]);
> 
>          if (! ((converter >> Runs) && (Runs >= 0))) {
>              throw "argument error?";
>          }
>      }
>      
>      history.logStart();
>      for (int Run = 1; Run <= Runs; ++Run) {
>          Compute_1D (*M1D);
>      }
>      history.logStop();
>      history.Print_Timing ("1D", (*M1D) [(1 * Len) + (2)]);
> }
> 
> 
> #include <iostream>
> #include <sys/time.h>
> 
> void Reporter::Print_Timing (const std::string Part, const Fringes::Num N) {
>      double difference = (Stop.tv_sec - Start.tv_sec) * 1000000
>              + (Stop.tv_usec - Start.tv_usec);
>      std::cout << Part << ": ";
>      std::cout << (difference / 1000000.0) << " " << N;
>      std::cout << '\n';
> }
> 
> void Reporter::logStart() {
>      gettimeofday(&this->Start, 0);
> }
> 
> void Reporter::logStop() {
>      gettimeofday(&this->Stop, 0);
> }


Interesting stuff, I need a bit more time to read and digest, but I did notice one thing that I think is worth pointing out. 

The real benefit (and performance gains) from profile guided compilation come from correcting branch prediction. As such the gains will be most apparent when there is an 'if' statement in the inner loop of the code. Try something where you are taking the sign of an int in the formula and have three cases <0 =0 >0.

The other point is that for any single branch there is at least a 50% chance it is already optimal, for example:

if x > 0 then
    y := 1 + y;
else
    y := 1 - y;
end if;

will get implemented in assembly as something like:

 tst rx
 ble xyz
 ld #1, r0
 sub r0, ry
 bra zyx
.xyz
 add #1, ry
.zyx

OR

 tst rx
 bgt xyz
 add #1, ry
 bra zyx
.xyz
 ld #1, r0
 sub r0, ry
.zyx

whether this is optimal depends on the number of times x <= 0 and on what the CPU's branch predictor guesses for 'ble xyz'. Most branch predictors start with the assumption that a backwards branch will be taken (looping) and a forward branch will not be taken, but then they also build statistical tables based on the address of the branch instruction to improve that guess on future iterations.

The speed difference can be large because a branch predict failure can have a high penalty - a CPU pipe stall. Modern CPUs use speculative execution (they keep the pipe filled by using branch-predict to assume whether the branch will or will not be taken) so if the branch predict guesses correctly there is no pipe stall and the CPU continues through the code at full speed. A pipe stall can cost 10s or 100s of clock cycles each time it happens. 

I initially expected the dynamic branch predictor would be doing a good job and changing the order of the 'if' statements would have no effect, but benchmarking on 64bit x86 hardware showed a strong effect for changing the order of branches.

Anyway the point is, even if you have an 'if' statement in the inner loop, you may be lucky and already have it the 'faster' way round.

So you need to benchmark:

if x > 0 then
    y := 1 + y;
else
    y := 1 - y;
end if;

AND

if x <= 0 then
    y := 1 - y;
else
    y := 1 + y;
end if;

Then you can confirm that profile guided compilation gives you the faster of the two benchmark times, no matter which way round the if statement is written in the code.

Obviously for one if statement in the inner loop you can practically benchmark both alternatives and chose the fastest.

With my Monte-Carlo simulation, the inner loop logic is a complex state-machine, and it would be impractical to try all possibly combinations (due to the explosion of combinations at the speed of 2^N, just 8 branches would require 256 code change and rebuild-cycles, 16 = 65536 etc...

This is where profile-guided compilation is a valuable tool. Both the Ada code and C++ code share the same branching in the state machine, and both have the same initial performance now (approx 40k simulations per second). However the C++ compiler gains 25% from the profile guided compilation (by changing branch orders and re-ordering functions). This gain should be available to the Ada compiler too, as the same branches are getting generated in the output assembly - but its just not working as well.

My latest results are better, I now have both C++ and Ada running from the same GCC-4.7.1 compiler and my latest performance figures are:

Just so its clear, you first build with '-fprofile-generate' then you run the code to build the .gcda profile files, then you build again with '-fprofile-use' to build the 'profile-guided' version. My code runs 1,000,000 iterations between the 'generate' and the 'use' steps.


C++ first compile: 39k
C++ profile guided: 55k

Ada first compile: 41k
Ada profile guided: 46k


So gcc-4.7.1 seems to improve the results slightly for Ada, but it seems to be still falling short of the potential improvement. I am becoming more convinced that there is nothing in the Ada code itself that is causing this, but more likely something about the Ada GCC front-end itself not using the profiling information as effectively as C++. 


Cheers,
Keean.



^ permalink raw reply	[relevance 0%]

* Re: GNAT (GCC) Profile Guided Compilation
  @ 2012-07-01 17:45  4%           ` Georg Bauhaus
  2012-07-01 22:57  0%             ` Keean Schupke
  0 siblings, 1 reply; 200+ results
From: Georg Bauhaus @ 2012-07-01 17:45 UTC (permalink / raw)


On 29.06.12 19:03, Keean Schupke wrote:
> Note: this is not really answering my question about the lack of improvement due to profile-guided compilation - but perhaps that side of things is more a compiler issue. Does anyone have any ideas about that side of things?

Some more observations, collected with the help of the simple
two example programs appended below.

For Ada and GNAT at least, any advantages to be had from profile-guided
compilation seem to vary with optimization options and sizes of data.
The same is true about a 1D approach vs a 2D approach.

Among the various arrangements, one of the best I have got
from both GNAT GPL 2012, and from an FSF GNAT as of June 2012
uses
*) -O2 -funroll-loops -gnatp
*)  the 2D approach

(If it means a anything, adding -ftree-vectorize to the -O2 set
produces only the second best Ada result, the same as the -O3 times
listed below. I had chosen -ftree-vectorize as this switch is in the
O3 set.) Trying profile guided compilation at higher optimization
levels consistently slowed the Ada program down (other Ada programs
were faster after profile guided compilation, as mentioned elsewhere).

The result at -O2 seems nice, though, in that the 2D approach is
natural, the compiler switches are the ones that the manual recommends.
and this combination produces the fastest Ada program.

In short, from worst to best 1D / 2D, Runs = 100:

Ada profile guided -> .88 / .80   (this program only!)
Ada at -O3         -> .68 / .66
C++ at -O3         -> .66
Ada at -O2 -funr.. -> .68 / .47
C++ profile guided -> .31


Some differences seem to vary with hardware, too.
On one computer I have seen a minor speedup, on another
a very small slowdown, and a different ratio of 1D / 2D.

For the C++ case I have tested a 1D approach only, not
knowing how to write 2D arrays in C++ using C style arrays.
I'm not a C++ programmer, apologies for my C++.


Ada at -O2 -funroll-loops -gnatp -mtune=native
1D:  0.680750000 27303
2D:  0.469094000 27303  <-- Best for Ada!

Ada at -O3 -gnatNp -fomit-frame-pointer -mtune=native
1D:  0.676616000 27303
2D:  0.664194000 27303

previous with profile-guided compilation
1D:  0.888206000 27303
2D:  0.806196000 27303

C++ at -O3 -mtune=native
1D: 0.681721 0

previous with profile-guided compilation
1D: 0.31165 0

Clang++
1D: 0.611522 0

The GNU C++ compiler is from the GNAT GPL 2012 distribution for Mac OS X,
Clang++ is Apple's v 3.1.


=== 8< === 8< === 8< === 8< ===

package Fringes is

    pragma Pure (Fringes);

    type Full_Index is mod 2**32;
    subtype Num is Full_Index Range 0 .. 100_000;
    subtype Index is Full_Index range 0 .. 1000;
    Len : constant Full_Index := Index'Last - Index'First + 1;

    type Matrix_1D is
      array (Index'First .. Index'First + Len * Len - 1) of Num;
    type Matrix_2 is array (Index, Index) of Num;

    procedure Compute_1D (A : in out Matrix_1D);
    procedure Compute_2  (A : in out Matrix_2);

end Fringes;

package body Fringes is

    --
    --  Each Compute procedure has A pointless loop that assigns each
    --  inner field the sum of non-diagonal neighbors modulo Num'Last
    --

    procedure NOT_USED_Compute_1D_Slow (A : in out Matrix_1D) is
       J : Full_Index;
    begin
       J := A'First + Len;
       loop
         exit when J > A'Last - Len;
         for K in J + 1 .. J + Len - 1 - 1 loop
            A (K) := (A(K + 1)
                      + A(K - Len)
                      + A(K - 1)
                      + A(K + Len)) mod Num'Last;
         end loop;
         J := J + Len;
       end loop;
    end NOT_USED_Compute_1D_Slow;

    procedure Compute_1D (A : in out Matrix_1D) is
    begin
       for K in A'First + Len + 1 .. A'Last - Len - 1 loop
          case K mod Len is
          when 0 | Len - 1 => null;
          when others =>
             A (K) := (A(K + 1)
                       + A(K - Len)
                       + A(K - 1)
                       + A(K + Len)) mod Num'Last;
          end case;
       end loop;
    end Compute_1D;

    procedure Compute_2 (A : in out Matrix_2) is
    begin
       for J in A'First(1) + 1 .. A'Last(1) - 1 loop
          for K in A'First(2) + 1 .. A'Last(2) - 1 loop
             A (J, K) := (A(J, K + 1)
                          + A(j - 1, K)
                          + A(J, K - 1)
                          + A(j + 1, K)) mod Num'Last;
          end loop;
       end loop;
    end Compute_2;

end Fringes;


with Fringes;
with Ada.Command_Line, Ada.Real_Time;
procedure Test_Fringes is

    use Ada.Real_Time;

    Runs : constant Natural :=
      Natural'Value (Ada.Command_Line.Argument(1));

    Start, Stop: Time;

    package Os_Or_Gnat_Stacksize_Nuisance is
       use Fringes;
       type P1 is access Matrix_1D;
       type P2 is access Matrix_2;
       M1P : constant P1 := new Matrix_1D'(others => 123);
       M2p : constant P2 := new Matrix_2'(Index => (Index => 123));
       M1D : Matrix_1D renames M1P.all;
       M2 : Matrix_2 renames M2P.all;
    end Os_Or_Gnat_Stacksize_Nuisance;
    use Os_Or_Gnat_Stacksize_Nuisance;

    procedure Print_Timing (Part : String; N : Fringes.Num) is separate;
    use type Fringes.Full_Index;
begin
    Start := Clock;
    for Run in 1 .. Runs loop
       Fringes.Compute_1D (M1D);
    end loop;
    Stop := Clock;
    Print_Timing ("1D", M1D ((M1D'First + 1 * Fringes.Len) + (2)));

    Start := Clock;
    for Run in 1 .. Runs loop
       Fringes.Compute_2 (M2);
    end loop;
    Stop := Clock;
    Print_Timing ("2D", M2 (1, 2));
end Test_Fringes;

with Ada.Text_IO;
separate (Test_Fringes)
procedure Print_Timing (Part : String; N : Fringes.Num) is
    use Ada.Text_IO;
begin
    Put (Part);
    Put (": ");
    Put (Duration'Image (To_Duration(Stop - Start)));
    Put (Fringes.Num'Image (N));
    New_Line;
end print_timing;


=== 8< === 8< === 8< === 8< ===

#include <stdint.h>

namespace Fringes {

     typedef  uint32_t Full_Index;
#define Num_Last 100000
     typedef Full_Index Num;
#define Index_Last 1000
     typedef Full_Index Index;
     const Full_Index Len = Index_Last + 1;

#define A_Last ((Len * Len) - 1)
     typedef Num Matrix_1D[A_Last + 1];

     void Compute_1D (Matrix_1D&  A);
     //  Each Compute procedure has a pointless loop that assigns each
     //  inner field the sum of non-diagonal neighbors modulo Num_Last
     void Compute_1D (Matrix_1D&  A) {

         for (Full_Index K = Len + 1; K < A_Last - Len - 1; ++K) {
             switch (K % Len) {
             case 0: case Len - 1: break;
             default:
                 A [K] = (A[K + 1]
                           + A[K - Len]
                           + A[K - 1]
                           + A[K + Len]) % Num_Last;
             }
         }
     }
}

#include <sys/time.h>
#include <string>

class Reporter {
     struct timeval Start, Stop;
public:
     void logStart();
     void logStop();
     void Print_Timing (const std::string Part, const Fringes::Num N);
};


#include <sstream>

int main(int argc, char* argv[]) {
     using namespace Fringes;

     int Runs;
     Matrix_1D* M1D = new Matrix_1D[Len];
     Reporter history;

     if (argc == 0) {
         throw "usage";
     } else {
         std::istringstream converter(argv[1]);

         if (! ((converter >> Runs) && (Runs >= 0))) {
             throw "argument error?";
         }
     }
     
     history.logStart();
     for (int Run = 1; Run <= Runs; ++Run) {
         Compute_1D (*M1D);
     }
     history.logStop();
     history.Print_Timing ("1D", (*M1D) [(1 * Len) + (2)]);
}


#include <iostream>
#include <sys/time.h>

void Reporter::Print_Timing (const std::string Part, const Fringes::Num N) {
     double difference = (Stop.tv_sec - Start.tv_sec) * 1000000
             + (Stop.tv_usec - Start.tv_usec);
     std::cout << Part << ": ";
     std::cout << (difference / 1000000.0) << " " << N;
     std::cout << '\n';
}

void Reporter::logStart() {
     gettimeofday(&this->Start, 0);
}

void Reporter::logStop() {
     gettimeofday(&this->Stop, 0);
}





^ permalink raw reply	[relevance 4%]

* Re: Practicalities of Ada for app development
  @ 2012-06-12 11:44  4%                   ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2012-06-12 11:44 UTC (permalink / raw)


On Tue, 12 Jun 2012 11:48:43 +0200, Georg Bauhaus wrote:

> On 12.06.12 09:55, Dmitry A. Kazakov wrote:
>> On Mon, 11 Jun 2012 22:50:33 +0200, Georg Bauhaus wrote:
>>
>>> Reason: numeric literals typically mean a number of some "arithmetic"
>>> type.
>>
>> No, a numeric literal means what it tells "a number."
> 
> "A number" tells little to an average reader of a program
> seeing just that number.

Sorry for the reader, but numeric literal is just that: a number.

>>>     Some_Time_Object :=  45 * Seconds;
> 
>> Technically Barnes is not quite right.
> 
> Oh, I believe he is right and makes sure this is understood:
> 
> "the expression uses the rule that a fixed[!] point value
> can be multiplied by an integer giving a result of the same fixed
> point type". (�18.3, p.465)
>
> Using whole quantities of Seconds, Minutes, and so on will give
> us aggregates and formulas that do not invite confusion by
> stipulating that the fraction can be anything but 0.

It is very difficult if possible to create dimensioned fixed-point system
due to problems of handling accuracy. Note that the point of using fixed
point is to keep results exact.

>> 2. You cannot multiply time, you do durations (time intervals);
> 
> Like in "two times"? "Time after Time"? "Many times"?

The thing represented by Ada.Calendar.Time or Ada.Real_Time.Time has no
dimension. You can multiply durations by themselves and by other
dimensioned values and scalars. Times can be subtracted. Duration can be
added to time.
 
>> 3. "s" or "second" is the proper name of the unit.
> 
> "Seconds" is the plural of a "second" (one unit of time).

http://physics.nist.gov/cuu/Units/units.html
 
> "s" is asking for trouble, since "s" may well name a parameter
> or variable, like when copied from a formula (s = v * t, say).
> 
> By comparison, is "m" the name of Meter or of Minute?

"m" is meter. Minute is not a SI unit. Yes, there are many conflicting
names when irregular or units outside SI are involved.

As for conflicts with names of variables, that is not a problem in Ada.

>> in a properly typed languages you need no special
>> forms of literals. I guess that U+n stems from C-ish nL, nU etc.
> 
> Uhm, no! U+number is official U-nicode notation. (Also in ISO 10646.)

Yes, but C is where the ears are growing from.

If you want to follow the notation, you should to do it exactly, i.e.
U+0C20, without dashes around the number. If you don't, then use the most
appropriate way from the implementation language perspective. The middle
way would bring nothing but confusion.

>> You can overload numeric literals in almost any context in Ada.
> 
> Overloading literals is the questionable part. It is what got me
> started. No inference, please! Even when compilers can decide
> whether or not there is that single assignable type!
> 
> What I consider silly is to insist that readers infer
> the proper meaning of a sequence of digits when we can
> do better.

Sorry, but the program as a whole is not what it means. You have to
interpret the program in order to understand its semantics. A good language
design is to support trivial inference and require complex things explicit. 

Type annotation of operands of an expression *is* trivial, or else the
program is poorly designed.

>> The proper way to do this is:
>>
>>     UTF8_Pi : constant String := Image (16#0C30#);
> 
> How is that different from
> 
>        UTF8_Pi : constant String := U+16#0C30;

Compare:

   Image (16#0C30#) * 3

and

   U+16#0C30# * 3

Anyway, if U+n notation support seem the only problem with Ada UTF-8, I
gather that the issue is closed. (:-))

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 4%]

* Re: Ada and linux real time
  @ 2012-03-18 22:03  6%                     ` slos
  0 siblings, 0 replies; 200+ results
From: slos @ 2012-03-18 22:03 UTC (permalink / raw)


I am learning Ada, don't laugh please ! ;-)

Here is mine :

with System;
with Ada.Text_IO; use Ada.Text_IO;
with Ada.Real_Time; use Ada.Real_Time;

procedure RT_test is

   procedure cyclic is
      real1 : Float := 10.0;
      real2 : Float := 20.0;
      real3 : Float :=  0.0;
   begin
      for Index in 0 .. 1000000 loop -- should do something useful
instead
         real3 := real1 * real2;
      end loop;
   end cyclic;

   task type Periodic_Task
     (Task_Priority           : System.Priority;
      Period_In_Milliseconds  : Natural) is
      pragma Priority (Task_Priority);
   end Periodic_Task;

   task body Periodic_Task is
      Next_Time  : Ada.Real_Time.Time := Clock;
      MyPeriod   : constant Time_Span := Milliseconds
(Period_In_Milliseconds);
      Max_Times  : Integer := 10000 / Period_In_Milliseconds; -- we
want the test to run 10 s
      Times      : Integer := 0;
      Stats      : array (1 .. 10) of Integer;
      Thresholds : array (1 .. 10) of Duration;
      MyDuration       : Duration;
      MyMinDuration    : Duration;
      MyMaxDuration    : Duration;
      MyPeriodDuration : Duration := To_Duration (MyPeriod);
   begin
      Put_Line ("MyPeriod_Duration    : " & Duration'Image
(MyPeriodDuration));

      for Index in Stats'Range loop
         Stats (Index) := 0;
      end loop;

      Thresholds( 1) := MyPeriodDuration *  0.001;
      Thresholds( 2) := MyPeriodDuration *  0.005;
      Thresholds( 3) := MyPeriodDuration *  0.010;
      Thresholds( 4) := MyPeriodDuration *  0.050;
      Thresholds( 5) := MyPeriodDuration *  0.100;
      Thresholds( 6) := MyPeriodDuration *  0.500;
      Thresholds( 7) := MyPeriodDuration *  1.000;
      Thresholds( 8) := MyPeriodDuration *  5.000;
      Thresholds( 9) := MyPeriodDuration * 10.000;
      Thresholds(10) := MyPeriodDuration * 20.000;
      loop
         Next_Time := Next_Time + MyPeriod;

         cyclic; -- Do something useful

         delay until Next_Time;

         MyDuration := To_Duration (Clock - Next_Time);
         if (Times = 0) then
            MyMinDuration := MyDuration;
            MyMaxDuration := MyDuration;
         else
            if MyMinDuration > MyDuration then
               MyMinDuration := MyDuration;
            else if MyMaxDuration < MyDuration then
                  MyMaxDuration := MyDuration;
               end if;
            end if;
         end if;

         for Index in Stats'Range loop
            if MyDuration < Thresholds (Index) then
               Stats (Index) := Stats (Index) + 1;
               exit;
            end if;
         end loop;

         Times := Times + 1;

         exit when Times > Max_Times;

      end loop;
      Put_Line ("Et Hop ! Times : " & Times'Img & " Duration Min : " &
Duration'Image (MyMinDuration) & " Max : " & Duration'Image
(MyMaxDuration));
      for Index in Stats'Range loop
         Put_Line (Integer'Image(Index) & " | Thresholds := " &
Duration'Image(Thresholds(Index)) & " | Stats := " &
Integer'Image(Stats(Index)));
      end loop;
      Put_Line ("Periodic_Task finished !");
   end Periodic_Task;

   My_Periodic_Task : Periodic_Task (Task_Priority          => 97,
                                     Period_In_Milliseconds => 10);
begin
   Put_Line ("Real Time test...");

end RT_test;

And the results don't tell me anything...
I have to think about putting some load on the system.

The test run for 10 s and outputs the difference between expected
sleep duration and actual, sorting the results in an array.

With no load either and no RT kernel :

Linux debian-sid 3.2.0-2-amd64 #1 SMP Tue Mar 13 16:54:04 UTC 2012
x86_64 GNU/Linux

/home/slos/Ada/NPLC/build/rt_test
Real Time test...
MyPeriod_Duration    :  0.010000000
Et Hop ! Times :  1001 Duration Min :  0.000042000 Max :  0.000276000
 1 | Thresholds :=  0.000010000 | Stats :=  0
 2 | Thresholds :=  0.000050000 | Stats :=  1
 3 | Thresholds :=  0.000100000 | Stats :=  560
 4 | Thresholds :=  0.000500000 | Stats :=  440
 5 | Thresholds :=  0.001000000 | Stats :=  0
 6 | Thresholds :=  0.005000000 | Stats :=  0
 7 | Thresholds :=  0.010000000 | Stats :=  0
 8 | Thresholds :=  0.050000000 | Stats :=  0
 9 | Thresholds :=  0.100000000 | Stats :=  0
 10 | Thresholds :=  0.200000000 | Stats :=  0
Periodic_Task finished !
[2012-03-18 22:39:45] process terminated successfully (elapsed time:
10.12s)




^ permalink raw reply	[relevance 6%]

* Re: Ada and linux real time
  2012-03-07 12:10  4%   ` slos
@ 2012-03-07 14:18  6%     ` Dmitry A. Kazakov
    0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2012-03-07 14:18 UTC (permalink / raw)


On Wed, 7 Mar 2012 04:10:14 -0800 (PST), slos wrote:

> On 7 mar, 09:23, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
> wrote:
>> On Tue, 6 Mar 2012 13:19:24 -0800 (PST), slos wrote:
>>> I have tried some code on both RT and non RT kernels but was not
>>> impressed by the difference.
>>
>> What kind of difference you expected to see?
> 
> I can't post the code from the place I am, so I will just describe it.
> 
> My little test schedules a periodic task with a period of let's say
> 10ms.

I see.

The problem is likely not in the Ada's RTL but in the OS. Usually Ada
(specifically GNAT) maps tasks onto OS-native threads. You should look
after the OS settings which control scheduling. These are OS specific, but
10ms looks quite plausible.

> The periodic task then calls the Ada.Real_Time.Clock and measures the
> difference to the scheduled time.

Ada.Real_Time.Clock would typically use the OS time services, which,
frequently have very low accuracy. In order to check a particular OS, call
Ada.Real_Time.Clock several times and compare the results.

I cannot tell for Linux, because I didn't use it for real-time purposes
yet. Ideally it should derive the system time from the TSC. However
scheduling would likely limited when controlled by timer interrupts. The
minimal waiting time is then determined by the timer's period. You should
look for this kernel setting if you want go below 10ms, or what the actual
limit is.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Re: Ada and linux real time
  @ 2012-03-07 12:10  4%   ` slos
  2012-03-07 14:18  6%     ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: slos @ 2012-03-07 12:10 UTC (permalink / raw)


On 7 mar, 09:23, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:
> On Tue, 6 Mar 2012 13:19:24 -0800 (PST), slos wrote:
> > I have tried some code on both RT and non RT kernels but was not
> > impressed by the difference.
>
> What kind of difference you expected to see?
>
> --
> Regards,
> Dmitry A. Kazakovhttp://www.dmitry-kazakov.de

I can't post the code from the place I am, so I will just describe it.

My little test schedules a periodic task with a period of let's say
10ms.

The periodic task then calls the Ada.Real_Time.Clock and measures the
difference to the scheduled time.
The difference is stored in an array of durations where each index
correspond to an interval.
Difference < 0.1 * period
Difference < 0.2 * period
Difference < 0.5 * period
Difference < 1.0 * period
etc...
The purpose is to characterise the scheduling.
Running the program for a while I get an image of how it behaves.
Using both RT and non RT kernels give about same finding.
Thousands are correct while some are clearly out of specified period.
And I have not put any load on the system yet.

I plan to use tools provided by OSADL to stress the system but of
course it means nothing if I need some real time Ada runtime to
achieve real time performance and can't get it for free.

BR
Stéphane



^ permalink raw reply	[relevance 4%]

* Re: Any leap year issues caused by Ada yesterday?
  @ 2012-03-06 20:22  5%                           ` Simon Wright
  0 siblings, 0 replies; 200+ results
From: Simon Wright @ 2012-03-06 20:22 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

> On Tue, 06 Mar 2012 17:59:04 +0000, Simon Wright wrote:
>
>> The timebase ran off the same crystal as the decrementer, so all were
>> internally sync'd. Internally, our synchronised time was
>> (Ada.Calendar.Clock (at last clock interrupt, of course) + high-res time
>> since last clock interrupt).
>
> You could improve that a bit by putting Ada.Calendar.Clock into a loop.
> When it returns a different value, you exit the loop and take that value
> for the time base.

Ada.Calendar.Clock was basically the POSIX gettimeofday() (?) from
VxWorks; which was (epoch + ticks/clockrate). So it was updated at clock
interrupt.

> If the quartz is same you need not to synchronize it anymore. Since the
> multiplier is known you simply add the RTC minus its value at the base
> multiplied by the factor and converted to Duration (or Time_Span) to the
> base and use that instead of the original Ada's Clock.

Didn't want to mess with the RTS use of Ada.Calendar.Time for delays. No
point in using Ada.Real_Time.Time because (then) it was the same as
Ada.Calendar.Time. So we had AC.Time (for internal use only),
<Project>.Calendar.Time for both internal & external use (but not, of
course, for delays).

> Did you check the kernel settings? It has a variable that sets the time
> source to the RTC. This might work on your PPC's BSP. The effect is that
> the system clock is changed each time when queried rather than upon timer
> interrupts.

Don't remember that one.



^ permalink raw reply	[relevance 5%]

* Re: Any leap year issues caused by Ada yesterday?
  2012-03-05 20:56  5%           ` Simon Wright
@ 2012-03-06  8:47  0%             ` Dmitry A. Kazakov
    0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2012-03-06  8:47 UTC (permalink / raw)


On Mon, 05 Mar 2012 20:56:09 +0000, Simon Wright wrote:

> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
> 
>> On Mon, 05 Mar 2012 18:30:46 +0000, Simon Wright wrote:
>>
>>> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
>>> 
>>>> BTW, I would not wonder to see Real_Time.Time and Calendar.Time same
>>>> or correlated.
>>> 
>>> We were surprised and disappointed to find that earlier releases of GNAT
>>> did have them the same. What happens to your precise timing if you get
>>> an NTP update in the middle of it?
>>
>> Nothing, because I would expect the NTP client to leave alone the clock
>> readings and the arithmetic of. It should rather adjust Split and Time_Of.
> 
> Some people would arrange time sync such that if:
> 
> a) you read the clock
> b) time sync sets the clock back 1 second
> c) after 1 second you read the clock again
> 
> that the time read at a) and c) would be the same. 
> 
>> In our setups we are using a different schema anyway. Instead of
>> adjusting clocks we do the time stamps when sending them from host to
>> host.
> 
> Because of the GNAT bug we couldn't use Ada.Real_Time. So we left
> Ada.Calendar untouched and made our own <project>.Calendar with offsets,
> as you say. Fun with I/O of time,
> 
>>> OK, this is slightly GNAT-related, since (at that time, anyway) "delay
>>> 0.5" translated under the hood into "delay until now + 0.5" on VxWorks,
>>
>> Yes, but NTP should not mingle in that. [I don't know how the VxWorks NTP
>> client works.]
> 
> I don't understand? What else would it do but change the value of
> Ada.Calendar.Clock?

It would be difficult to do. The most straightforward and efficient
implementation of Time is a 64-bit number (N) taken directly from the
corresponding machine register, e.g. the performance counter. Why would you
change it (provided any machine support for doing that existed)? You would
rather leave it as is and adjust the epoch instead (and, unlikely, the
multiplier) when calculating the calendar time:

   Epoch time + N * Multiplier

This is needed only in operations dealing with year, month etc, e.g. Split.
Granted there could issues with delay until <many-days-ahead>, but this is
negligibly comparing to the problems when the performance counter were
indeed adjusted.

>>> so you were always related to the actual clock.
>>
>> VxWorks clock on i7 is a garbage. It is driven by the timer interrupts,
>> i.e. to get 1ms resolution you need 1000 interrupts per second.
>>
>> We keep on asking Wind River to fix the mess, but without much success so
>> far. GNAT simply uses that clock. So delay 0.001 may mean absolutely
>> anything under VxWorks. To fix that one should rewrite the time driver.
> 
> We were quite happy with 1 ms ticks. So delay 0.001 meant "delay at
> least 1 and no more than 2 ms" (like always).

If you set the timer at 1ms rate, you would have 1ms delays. The problem is
that the time stamps would have only 1ms accuracy! For 10kHz measurements
and control we are doing, this is a bit dire. So we are setting the timer
interrupts at 0.01ms (which is our humble contribution to the "man-made"
climate change (:-))

>>> AdaCore accepted the bug report (after we pointed out the "shall" in
>>> ARM95 D.8(32)).
>>
>> Well, I would not blame AdaCore for that, it is Wind River's fault,
>> IMO.
> 
> This was *Ada* running on VxWorks; so it needed fixing. We didn't care
> who fixed it (well, as far as we were concerned, who didn't fix it,
> actually).

Yes, but AdaCore has neither the resources nor desire to patch crappy OSes.
They will have enough to do fixing the problems introduced with the
implementation of Ada 2012...

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: Any leap year issues caused by Ada yesterday?
  @ 2012-03-05 20:56  5%           ` Simon Wright
  2012-03-06  8:47  0%             ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2012-03-05 20:56 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

> On Mon, 05 Mar 2012 18:30:46 +0000, Simon Wright wrote:
>
>> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
>> 
>>> BTW, I would not wonder to see Real_Time.Time and Calendar.Time same
>>> or correlated.
>> 
>> We were surprised and disappointed to find that earlier releases of GNAT
>> did have them the same. What happens to your precise timing if you get
>> an NTP update in the middle of it?
>
> Nothing, because I would expect the NTP client to leave alone the clock
> readings and the arithmetic of. It should rather adjust Split and Time_Of.

Some people would arrange time sync such that if:

a) you read the clock
b) time sync sets the clock back 1 second
c) after 1 second you read the clock again

that the time read at a) and c) would be the same. 

> In our setups we are using a different schema anyway. Instead of
> adjusting clocks we do the time stamps when sending them from host to
> host.

Because of the GNAT bug we couldn't use Ada.Real_Time. So we left
Ada.Calendar untouched and made our own <project>.Calendar with offsets,
as you say. Fun with I/O of time,

>> OK, this is slightly GNAT-related, since (at that time, anyway) "delay
>> 0.5" translated under the hood into "delay until now + 0.5" on VxWorks,
>
> Yes, but NTP should not mingle in that. [I don't know how the VxWorks NTP
> client works.]

I don't understand? What else would it do but change the value of
Ada.Calendar.Clock?

>> so you were always related to the actual clock.
>
> VxWorks clock on i7 is a garbage. It is driven by the timer interrupts,
> i.e. to get 1ms resolution you need 1000 interrupts per second.
>
> We keep on asking Wind River to fix the mess, but without much success so
> far. GNAT simply uses that clock. So delay 0.001 may mean absolutely
> anything under VxWorks. To fix that one should rewrite the time driver.

We were quite happy with 1 ms ticks. So delay 0.001 meant "delay at
least 1 and no more than 2 ms" (like always).

>> AdaCore accepted the bug report (after we pointed out the "shall" in
>> ARM95 D.8(32)).
>
> Well, I would not blame AdaCore for that, it is Wind River's fault,
> IMO.

This was *Ada* running on VxWorks; so it needed fixing. We didn't care
who fixed it (well, as far as we were concerned, who didn't fix it,
actually).

It should have been easy enough on VxWorks: taskDelay(period + 1); (but
there may be all sorts of complicated reasons why that wouldn't be
enough).



^ permalink raw reply	[relevance 5%]

* Re: Need some light on using Ada or not
  @ 2011-02-22  2:15  2%                   ` Shark8
  0 siblings, 0 replies; 200+ results
From: Shark8 @ 2011-02-22  2:15 UTC (permalink / raw)


On Feb 21, 4:52 am, Brian Drummond <brian_drumm...@btconnect.com>
wrote:
>
> As this is my first experiment with tasking, comments are welcome (and I'd be
> interested to see your version). If people think this is worth submitting to the
> shootout, I'll go ahead.
>
> - Brian

I used arrays for the most part, and then expanded it out to a
recursive-definition for the trees which would be too large for
the stack during creation.

It may be going against the spirit of the competition, but nothing
there said that we couldn't use arrays as binary-trees.


-- Package B_Tree
-- by Joey Fish

Package B_Tree is


   -- Contest rules state:
   --	define a tree node class and methods, a tree node record and
procedures,
   --	or an algebraic data type and functions.
   --
   -- B_Tree is the definition of such a record and procedures.

   Type Binary_Tree is Private;

   Function  Build_Tree	(Item : Integer; Depth : Natural)    Return
Binary_Tree;
   Function  Subtree	(Tree : Binary_Tree; Left : Boolean) Return
Binary_Tree;
   Function  Item_Check	(This : Binary_Tree)		     Return Integer;
   Procedure Free	(Tree : In Out Binary_Tree);

Private

   Type Node_Data;
   Type Data_Access		is Access Node_Data;
   SubType Not_Null_Data_Access	is Not Null Data_Access;

   Function Empty Return Not_Null_Data_Access;
   Type Binary_Tree( Extension : Boolean:= False ) is Record
      Data   :  Not_Null_Data_Access:= Empty;
   End Record;

End B_Tree;

--- B_Trees body
with
Ada.Text_IO,
--Ada.Numerics.Generic_Elementary_Functions,
Unchecked_Deallocation;

Package Body B_Tree is

   -- In some cases the allocataion of the array is too large, so we
can split
   -- that off into another tree, for that we have Tree_Array, which
is a
   -- Boolean-indexed array. {The Index is also shorthand for Is_left
on such.}
   Type Tree_Array	is Array (Boolean) of Binary_Tree;

   -- For trees of up to 2**17 items we store the nodes as a simple
array.
   Type Integer_Array	is Array (Positive Range <>) of Integer;
   Type Access_Integers	is Access Integer_Array;
   Type Node_Data(Extended : Boolean:= False) is Record
      Case Extended is
         When False => A : Not Null Access_Integers;
         When True  => B : Tree_Array;
      end Case;
   End Record;


   --  Returns the Empty List's Data.
   Function Empty Return Not_Null_Data_Access is
   begin
      Return New Node_Data'( A => New Integer_Array'(2..1 => 0),
Others => <> );
   end Empty;



      -- We'll need an integer-version of logrithm in base-2
      Function lg( X : In Positive ) Return Natural is
         --------------------------------------------
         --  Base-2 Log with a jump-table for the  --
         --  range 1..2**17-1 and a recursive call --
         --  for all values greater.		   --
         --------------------------------------------
      begin
         Case X Is
            When 2**00..2**01-1	=> Return  0;
            When 2**01..2**02-1	=> Return  1;
            When 2**02..2**03-1	=> Return  2;
            When 2**03..2**04-1	=> Return  3;
            When 2**04..2**05-1	=> Return  4;
            When 2**05..2**06-1	=> Return  5;
            When 2**06..2**07-1	=> Return  6;
            When 2**07..2**08-1	=> Return  7;
            When 2**08..2**09-1	=> Return  8;
            When 2**09..2**10-1	=> Return  9;
            When 2**10..2**11-1	=> Return 10;
            When 2**11..2**12-1	=> Return 11;
            When 2**12..2**13-1	=> Return 12;
            When 2**13..2**14-1	=> Return 13;
            When 2**14..2**15-1	=> Return 14;
            When 2**15..2**16-1	=> Return 15;
            When 2**16..2**17-1	=> Return 16;
            When Others		=> Return 16 + lg( X / 2**16 );
         End Case;
      end lg;

   Function Build_Tree (Item : Integer; Depth : Natural) Return
Binary_Tree is
      -- Now we need a function to allow the calculation of a node's
value
      -- given that node's index.
      Function Value( Index : Positive ) Return Integer is
	Level : Integer:= lg( Index );
	-- Note: That is the same as
	--	Integer( Float'Truncation( Log( Float(Index),2.0 ) ) );
	-- but without the Integer -> Float & Float -> Integer conversions.
      begin
         Return (-2**(1+Level)) + 1 + Index;
      end;

   Begin
      If Depth < 17 then
         Return Result : Binary_Tree do
            Result.Data:= New Node_Data'
		( A => New Integer_Array'(1..2**Depth-1 => <>), Others => <> );
            For Index in Result.Data.A.All'Range Loop
		Result.Data.All.A.All( Index ):= Value(Index) + Item;
            End Loop;
         End Return;
      else
         Return Result : Binary_Tree do
            Result.Data:= New Node_Data'
              ( B =>
                (True => Build_Tree(-1,Depth-1), False =>
Build_Tree(0,Depth-1)),
               Extended => True );
         End Return;

      end if;
   End Build_Tree;

   Function Subtree (Tree : Binary_Tree; Left : Boolean) Return
Binary_Tree is
   Begin
      if Tree.Data.Extended then
         -- If it is a large enough tree, then we already have it
split.
         Return Tree.Data.B(Left);
      else
         -- If not then we just need to calculate the middle and
return the
         -- proper half [excluding the first (root) node.
         Declare
            Data	  : Integer_Array Renames Tree.Data.All.A.All;
            Data_Length : Natural:= Data'Length;

            Mid_Point : Positive:= (Data_Length/2) + 1;
            SubType LeftTree is Positive Range
              Positive'Succ(1)..Mid_Point;
            SubType RightTree is Positive Range
              Positive'Succ(Mid_Point)..Data_Length;
         Begin
            Return Result : Binary_Tree Do
               if Left then
                  Result.Data:= New Node_Data'
                    ( A => New Integer_Array'( Data(LeftTree)  ),
Others => <> );
               else
                  Result.Data:= New Node_Data'
                    ( A => New Integer_Array'( Data(RightTree) ),
Others => <> );
               end if;
            End Return;
         End;
      end if;
   End Subtree;

   Function Check_Sum(	Data: In Integer_Array	) Return Integer is
      Depth : Natural:= lg(Data'Length);
      SubType Internal_Nodes is Positive Range 1..2**Depth-1;
   begin
      Return Result : Integer:= 0 do
         For Index in Internal_Nodes Loop
            Declare
               Left	: Positive:= 2*Index;
               Right	: Positive:= Left+1;
            Begin
               If Index mod 2 = 1 then
                  Result:= Result - Right + Left;
               else
                  Result:= Result + Right - Left;
               end if;
            End;
         End Loop;
      End Return;
   end Check_Sum;

   Function Item_Check	(This : Binary_Tree) Return Integer is
      -- For large trees this function calls itself recursively until
the
      -- smaller format is encountered; otherwise, for small trees, it
acts as
      -- a pass-througn to Check_Sum.
   Begin
      If This.Data.Extended then
         Declare

         Begin
            Return Result: Integer:= -1 do
               Result:=   Result
			+ Item_Check( This.Data.B(False) )
			- Item_Check( This.Data.B(True ) );
            End Return;
         End;
      else
         Declare
            Data : Integer_Array Renames This.Data.All.A.All;
         Begin
            Return Check_Sum( Data );
         End;
      end if;
   End Item_Check;

   Procedure Free	(Tree : In Out Binary_Tree) is
      procedure Deallocate is new
		Unchecked_Deallocation(Integer_Array, Access_Integers);
      procedure Deallocate is new
		Unchecked_Deallocation(Node_Data, Data_Access);

      Procedure Recursive_Free	(Tree : In Out Binary_Tree) is
      begin
         if Tree.Data.All.Extended then
            Recursive_Free( Tree.Data.B(True ) );
            Recursive_Free( Tree.Data.B(False) );
            Declare
               Data : Data_Access;
               For Data'Address Use Tree.Data'Address;
               Pragma Import( Ada, Data );
            Begin
               Deallocate(Data);
            End;
         else
            Declare
               Data : Data_Access;
               For Data'Address Use Tree.Data.All.A'Address;
               Pragma Import( Ada, Data );
            Begin
               Deallocate( Data );
               Data:= Empty;
            End;
         end if;
      end Recursive_Free;

   begin
      Recursive_Free( Tree );
      Tree.Data:= Empty;
   end Free;

Begin
   Null;
End B_Tree;

-- BinaryTrees.adb
-- by Jim Rogers
-- modified by Joey Fish

With
B_Tree,
Ada.Text_Io,
Ada.Real_Time,
Ada.Command_Line,
Ada.Characters.Latin_1,
;

Use
B_Tree,
Ada.Text_Io,
Ada.Command_Line,
Ada.Integer_Text_Io,
Ada.Characters.Latin_1
;

procedure BinaryTrees is
   --Depths
   Min_Depth	: Constant Positive := 4;
   Max_Depth	: Positive;
   Stretch_Depth: Positive;
   N		: Natural := 1;

   -- Trees
   Stretch_Tree,
   Long_Lived_Tree	: Binary_Tree;


   Check,
   Sum		: Integer;
   Depth	: Natural;
   Iterations	: Positive;

   Package Fn is New
Ada.Numerics.Generic_Elementary_Functions( Float );
   Function Value( Index : Positive ) Return Integer is
      Level : Integer:=
	Integer( Float'Truncation( Fn.Log( Float(Index),2.0 ) ) );
   begin
      Return (-2**(1+Level)) + 1 + Index;
   end;


begin
--     For Index in 1..2**3-1 loop
--        Put_Line( Value(Index)'img );
--     end loop;

--     Declare
--        -- allocate new memory:
--        Short_Lived_Tree_1: Binary_Tree:= Build_Tree(0, 20);
--     Begin
--        Sum:= Item_Check (Short_Lived_Tree_1);
--  --        Check := Check + Sum;
--  --        Free( Short_Lived_Tree_1 );
--        Put(Check'Img);
--     End;


   if Argument_Count > 0 then
      N := Positive'Value(Argument(1));
   end if;
   Max_Depth := Positive'Max(Min_Depth + 2, N);
   Stretch_Depth := Max_Depth + 1;
   Stretch_Tree := Build_Tree(0, Stretch_Depth);
   Check:= Item_Check(Stretch_Tree);
   Put("stretch tree of depth ");
   Put(Item => Stretch_Depth, Width => 1);
   Put(Ht & " check: ");
   Put(Item => Check, Width => 1);
   New_Line;

   Long_Lived_Tree := Build_Tree(0, Max_Depth);

   Depth := Min_Depth;
   while Depth <= Max_Depth loop
      Iterations := 2**(Max_Depth - Depth + Min_Depth);
      Check := 0;
      for I in 1..Iterations loop
         Declare
            Short_Lived_Tree_1: Binary_Tree:= Build_Tree(I, Depth);
         Begin
            Sum:= Item_Check (Short_Lived_Tree_1);
            Check := Check + Sum;
            Free( Short_Lived_Tree_1 );
         End;


         Declare
            Short_Lived_Tree_2: Binary_Tree:= Build_Tree(-I, Depth);
         Begin
            Sum:= Item_Check (Short_Lived_Tree_2);
            Check := Check + Sum;
            Free( Short_Lived_Tree_2 );
         End;
      end loop;

      Put(Item => Iterations * 2, Width => 0);
      Put(Ht & " trees of depth ");
      Put(Item => Depth, Width => 0);
      Put(Ht & " check: ");
      Put(Item => Check, Width => 0);
      New_Line;
      Depth := Depth + 2;
   end loop;
   Put("long lived tree of depth ");
   Put(Item => Max_Depth, Width => 0);
   Put(Ht & " check: ");
   check:= Item_Check(Long_Lived_Tree);
   Put(Item => Check, Width => 0);
   New_Line;

end BinaryTrees;




^ permalink raw reply	[relevance 2%]

* Re: How do I write directly to a memory address?
  @ 2011-02-11 20:42  5%                                     ` Vinzent Hoefler
  0 siblings, 0 replies; 200+ results
From: Vinzent Hoefler @ 2011-02-11 20:42 UTC (permalink / raw)


Hyman Rosen wrote:

> On 2/11/2011 3:15 PM, Vinzent Hoefler wrote:
>> Probably because there's no C99 compliant compiler in existance? :)
>
> Like I said, after the first major update, later changes are ignored.

Actually, reading the german version of comp.lang.c I don't think so.

> Do you know how well the Ada 2005 changes are faring?

Personally, I used the container classes, the "raise ... with <<message>>"
statement and the Ada.Real_Time.Timing_Objects thus far. But as the
project still uses an Ada95 compiler that does not really count.


Vinzent.

-- 
You know, we're sitting on four million pounds of fuel, one nuclear weapon,
and a thing that has 270,000 moving parts built by the lowest bidder.
Makes you feel good, doesn't it?
    --  Rockhound, "Armageddon"



^ permalink raw reply	[relevance 5%]

* Re: An Example for Ada.Execution_Time
  2011-01-01 20:25  7%                 ` Niklas Holsti
@ 2011-01-03  8:50  7%                   ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2011-01-03  8:50 UTC (permalink / raw)


On Sat, 01 Jan 2011 22:25:30 +0200, Niklas Holsti wrote:

> Perhaps you mean that CPU_Time is unrelated to Ada.Real_Time.Time over 
> longer periods during which the task is sometimes executing, sometimes 
> not.

I mean that

1. The corresponding clocks can be different. Ada cannot influence this.

2. The clocks are not synchronized, i.e. T1 on the Ada.Real_Time.Clock
cannot be translated into T2 on the Ada.Execution_Time.Clock.

> One of the differences between Ada.Real_Time.Time and 
> Ada.Execution_Time.CPU_Time is that the epoch for the former is not 
> specified in the RM. It follows that even if Ada.Real_Time.Time had a 
> visibly numeric value, its meaning would be unknown to the program.
> 
> In contrast, the epoch for CPU_Time is specified in the RM: the creation 
> of the task, a point in real time known to the program.

That does not define it either. An epoch cannot be defined otherwise than
in terms of other clock. The task start time according to
Ada.Real_Time.Time or Ada.Calendar.Time is unknown.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 7%]

* Re: An Example for Ada.Execution_Time
  2011-01-01 13:39  4%               ` Dmitry A. Kazakov
@ 2011-01-01 20:25  7%                 ` Niklas Holsti
  2011-01-03  8:50  7%                   ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: Niklas Holsti @ 2011-01-01 20:25 UTC (permalink / raw)


Dmitry A. Kazakov wrote:
> On Fri, 31 Dec 2010 20:57:54 +0200, Niklas Holsti wrote:
> 
>> Dmitry A. Kazakov wrote:
>>> On Fri, 31 Dec 2010 14:42:41 +0200, Niklas Holsti wrote:
>>>
>>>> Dmitry A. Kazakov wrote:
>>>>> On Thu, 30 Dec 2010 18:51:30 -0500, BrianG wrote:
>>>>>
>>>>>> Since D.16 defines CPU_Time as if it were a numeric value, is it too 
>>>>>> much to ask why a conversion to some form of numeric value wasn't 
>>>>>> provided?
>>>>> But time is not a number and was not defined as if it were.
>>>> You keep saying that, Dmitri, but your only argument seems to be the 
>>>> absence of some operators like addition for CPU_Time. Since CPU_Time is 
>>>> private, we cannot tell if this absence means that the D.14 authors 
>>>> considered the type non-numeric, or just considered the operators 
>>>> unnecessary for the intended uses.
>>> No, the argument is that time is a state of some recurrent process, like
>>> the position of an Earth's meridian relatively to the Sun. This state is
>>> not numeric, it could be numeric though. That depends on the nature of the
>>> process.
>> This is your view of what the English word "time" means.
> 
> The English word "time" it has many meanings.

Yes indeed....

Dmitry, I think we are arguing this point -- whether 
Ada.Execution_Time.CPU_Time has "numeric" values -- from different 
personal definitions of what "numeric" means, so we are not going to 
agree, and should stop.

Meanwhile, I was reminded that the Ada RM actually defines "numeric 
type" as an integer or real type (RM 3.5(1)). Since CPU_Time and 
Time_Span etc. are all private types, and the RM does not say if they 
are implemented as integer or real types, we cannot know if they are 
"numeric types" using RM terms. Let's stop here, OK?

> It is based on the fact that RM always introduces a distinct type, when it
> means duration, time interval, period, e.g.: Duration, Time_Span. When RM
> uses a type named "time," it does not mean duration.

Yes, I agree that this is the RM principle, but I also think it is a 
different question. You may remember that Randy said that the ARG had 
discussions about type names for Ada.Execution_Time, and were not very 
happy with the name "CPU_Time" (as I understood Randy, at least).

Note that RM D.14 does not say that CPU_Time is a "time type" as "time 
types" are defined in RM 9.6. In contrast, Ada.Real_Time.Time is a "time 
type".

> D.14 reuses Time_Span for
> intervals of CPU_Time, which stresses the difference. If this is not clean,
> then, not because CPU_Time is duration, it is because CPU_Time can be (and
> is) unrelated to the source of Ada.Real_Time.Time.

I definitely don't agree that CPU_Time can be unrelated to the source of 
Ada.Real_Time.Time in an Ada system that is useful for real-time 
programming. Execution time may be measured with a different clock or 
timer than Ada.Real_Time.Time but the rates of the two times must be 
very closely the same while one task is executing. Otherwise 
Ada.Execution_Time would be useless.

Perhaps you mean that CPU_Time is unrelated to Ada.Real_Time.Time over 
longer periods during which the task is sometimes executing, sometimes 
not. Then I agree that the two times increase at different rates, of course.

> Thus reusing Time_Span for its intervals questionable. It would
> be better to introduce a separate type for this, e.g. CPU_Time_Interval.

I strongly disagree, because that would abandon the commensurability of 
CPU_Time (or its intervals) with real time and would destroy the 
usefulness of Ada.Execution_Time in real-time systems.

> Furthermore, the CPU_Time type should be local to the task,

It could be reasonable to have different CPU_Time types for each task. I 
can't immediately think of any reason for comparing or subtracting 
CPU_Time values across tasks. But I don't think this can be implemented 
in Ada.

> preventing its usage anywhere outside the task,

This would prevent or hamper the implementation of scheduling algorithms 
that monitor the execution times of several tasks. I object to it.

> while CPU_Time_Interval could be same for all tasks.

Definitely. And it must be the same as Ada.Real_Time.Time_Span or 
Duration for real-time scheduling purposes.

> RM is consistent here, but, as I said, sloppy, because the zero element of
> a time system has a specific name: "epoch."  RM uses this term in D.8, so
> should it do here.

Manfully resisting the strong temptation to continue to argue about the 
"numeric" issue, based on your statements about "zero", I want to 
comment on this "epoch" thing.

One of the differences between Ada.Real_Time.Time and 
Ada.Execution_Time.CPU_Time is that the epoch for the former is not 
specified in the RM. It follows that even if Ada.Real_Time.Time had a 
visibly numeric value, its meaning would be unknown to the program.

In contrast, the epoch for CPU_Time is specified in the RM: the creation 
of the task, a point in real time known to the program. This brings 
CPU_Time closer to the meaning of Duration or Time_Span. If CPU_Time had 
a visibly numeric value, its meaning would be known: the total execution 
time of the task since the program created the task.

I think the main reason why RM D.14 defines a specific type CPU_Time, 
instead of directly using Duration or Time_Span, is the large range 
required of CPU_Time: up to 50 years. Time_Span is required to hold only 
+- 1 hour, and Duration only +- 1 day.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 7%]

* Re: Ada.Execution_Time
  2011-01-01 16:01  7%                                             ` Ada.Execution_Time Simon Wright
@ 2011-01-01 19:18  0%                                               ` Niklas Holsti
  0 siblings, 0 replies; 200+ results
From: Niklas Holsti @ 2011-01-01 19:18 UTC (permalink / raw)


Simon Wright wrote:
> Simon Wright <simon@pushface.org> writes:
> 
>> Niklas Holsti <niklas.holsti@tidorum.invalid> writes:
>>
>>> The question is then if the compiler/system vendors will take the
>>> trouble and cost to customise Ada.Execution_Time for a particular
>>> board/computer, or if they will just use the general,
>>> lowest-denominator but portable service provided by the kernel. Dmitry
>>> indicates that GNAT on VxWorks takes the latter, easy way out.
>> The latest supported GNAT on VxWorks (5.5) actually doesn't implement
>> Ada.Execution_Time at all (well, the source of the package spec is
>> there, adorned with "pragma Unimplemented_Unit", just like the FSF
>> 4.5.0 sources and the GNAT GPL sources -- unless you're running on
>> Cygwin or MaRTE).
> 
> Actually, Dmitry's complaint was that time (either from
> Ada.Calendar.Clock, or Ada.Real_Time.Clock, I forget) wasn't as precise
> as it can easily be on modern hardware, being incremented at each timer
> interrupt; so if your timer ticks every millisecond, that's your
> granularity.

Thanks for correcting me, Simon, I mis-remembered or misunderstood Dmitry.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  @ 2011-01-01 16:01  7%                                             ` Simon Wright
  2011-01-01 19:18  0%                                               ` Ada.Execution_Time Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2011-01-01 16:01 UTC (permalink / raw)


Simon Wright <simon@pushface.org> writes:

> Niklas Holsti <niklas.holsti@tidorum.invalid> writes:
>
>> The question is then if the compiler/system vendors will take the
>> trouble and cost to customise Ada.Execution_Time for a particular
>> board/computer, or if they will just use the general,
>> lowest-denominator but portable service provided by the kernel. Dmitry
>> indicates that GNAT on VxWorks takes the latter, easy way out.
>
> The latest supported GNAT on VxWorks (5.5) actually doesn't implement
> Ada.Execution_Time at all (well, the source of the package spec is
> there, adorned with "pragma Unimplemented_Unit", just like the FSF
> 4.5.0 sources and the GNAT GPL sources -- unless you're running on
> Cygwin or MaRTE).

Actually, Dmitry's complaint was that time (either from
Ada.Calendar.Clock, or Ada.Real_Time.Clock, I forget) wasn't as precise
as it can easily be on modern hardware, being incremented at each timer
interrupt; so if your timer ticks every millisecond, that's your
granularity.

This could easily be changed (at any rate for Real_Time), but doesn't I
believe necessarily affect what's to be expected from delay/delay until,
or Execution_Time come to that.



^ permalink raw reply	[relevance 7%]

* Re: An Example for Ada.Execution_Time
  @ 2011-01-01 13:39  4%               ` Dmitry A. Kazakov
  2011-01-01 20:25  7%                 ` Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2011-01-01 13:39 UTC (permalink / raw)


On Fri, 31 Dec 2010 20:57:54 +0200, Niklas Holsti wrote:

> Dmitry A. Kazakov wrote:
>> On Fri, 31 Dec 2010 14:42:41 +0200, Niklas Holsti wrote:
>> 
>>> Dmitry A. Kazakov wrote:
>>>> On Thu, 30 Dec 2010 18:51:30 -0500, BrianG wrote:
>>>>
>>>>> Since D.16 defines CPU_Time as if it were a numeric value, is it too 
>>>>> much to ask why a conversion to some form of numeric value wasn't 
>>>>> provided?
>>>> But time is not a number and was not defined as if it were.
>>> You keep saying that, Dmitri, but your only argument seems to be the 
>>> absence of some operators like addition for CPU_Time. Since CPU_Time is 
>>> private, we cannot tell if this absence means that the D.14 authors 
>>> considered the type non-numeric, or just considered the operators 
>>> unnecessary for the intended uses.
>> 
>> No, the argument is that time is a state of some recurrent process, like
>> the position of an Earth's meridian relatively to the Sun. This state is
>> not numeric, it could be numeric though. That depends on the nature of the
>> process.
> 
> This is your view of what the English word "time" means.

The English word "time" it has many meanings.

> It is not based on any text in the RM, as far as I can see.

It is based on the fact that RM always introduces a distinct type, when it
means duration, time interval, period, e.g.: Duration, Time_Span. When RM
uses a type named "time," it does not mean duration. This why it does not
declare it numeric. It does not provide addition of times or multiplication
by a scalar, which were appropriate if time were numeric or had the meaning
duration. CPU_Time is handled accordingly. D.14 reuses Time_Span for
intervals of CPU_Time, which stresses the difference. If this is not clean,
then, not because CPU_Time is duration, it is because CPU_Time can be (and
is) unrelated to the source of Ada.Real_Time.Time. Thus reusing Time_Span
for its intervals questionable. It would be better to introduce a separate
type for this, e.g. CPU_Time_Interval. Furthermore, the CPU_Time type
should be local to the task, preventing its usage anywhere outside the
task, while CPU_Time_Interval could be same for all tasks.

>>> - by RM D.14 (13/2), "the execution time value is set to zero at the 
>>> creation of the task".
>> 
>> I agree that here RM is sloppy. They should rather talk about an "epoch"
>> rather than "zero," if they introduced CPU_Time as a time.
> 
> So, here the RM disagrees with your view that CPU_Time is not numeric,

No it does not. "Zero" is not a numeric term, it denotes a specific element
of a group (an additive identity element), zero object (an initial
element). The number named "zero" is a special case, when the group is
numeric.

RM is consistent here, but, as I said, sloppy, because the zero element of
a time system has a specific name: "epoch." RM uses this term in D.8, so
should it do here.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 4%]

* Re: An Example for Ada.Execution_Time
  2010-12-30 23:51  5%     ` BrianG
  @ 2011-01-01  0:07  4%       ` Randy Brukardt
  1 sibling, 0 replies; 200+ results
From: Randy Brukardt @ 2011-01-01  0:07 UTC (permalink / raw)


"BrianG" <briang000@gmail.com> wrote in message 
news:ifj5u9$rr5$1@news.eternal-september.org...
> Randy Brukardt wrote:
>> "BrianG" <briang000@gmail.com> wrote in message 
>> news:ifbi5c$rqt$1@news.eternal-september.org...
>> ...
>>>    >Neither Execution_Time or Execution_Time.Timers provides any value
>>>    >that can be used directly.
>>
>> This seems like a totally silly question. Giving this some sort of 
>> religious importance is beyond silly...
>>
>>                                    Randy.
>
>
> Apparently, asking how a package, defined in the standard, was intended to 
> be used is now a silly question, and asking for an answer to the question 
> I originally asked (which was to clarify a previous response, not to 
> provide an example of use) is a religious debate.  I need to revise my 
> definitions.

But you didn't ask how a package defined in the standard was intended to be 
used. You asked why you have to use another package (Ada.Real_Time) in order 
for it to be useful. And you've repeated that over and over and over like it 
was meaningful in some way. But that is pretty much the definition of a 
silly question. It's just the way the package was defined, and it doesn't 
matter beyond having to add one additional "with" clause.

And that's pretty much irrelevant. In real Ada programs, there are many with 
clauses in the average compilation unit. In Janus/Ada, the number of withs 
averages 20 or so, and Claw programs are much higher than that. One could 
reduce those numbers by putting everything into a few massive packages, but 
those would be unweldy, poorly encapuslated, and close to unmaintainable.

The need to add one extra with to use a real-time package just falls into 
the noise. Probably it would have been better to offer the option of 
retrieving a value in terms of Duration, but it is just not a significant 
difference.

The answer to the "how do you use" question is simple and has been provided 
many times: use "-" to get a Time_Span, operate on that, and why that would 
be a problem to you or anyone else is beyond my comprehension.

> I won't claim to be an expert on the RM, but I don't recall any other 
> package (I did look at the ones you mention) that define a private type 
> but don't provide operations that make that type useful (for some 
> definition of 'use').  Ada.Directories doesn't require Ada.IO_Exceptions 
> to use Directory_Entry_Type or Search_Type; Ada.Streams.Stream_IO doesn't 
> require Ada.Streams (or Ada.Text_IO) to Create/Open/Read/etc. a File_Type. 
> The only thing provided from a CPU_Time is a count in seconds, or another 
> private type.

Here I completely disagree. If you plan to do anything *practical* with the 
Ada.Directories types, you'll have to use another package (at least 
Ada.Text_IO) to do something with the results. (Indeed, that is true of 
*all* Ada packages -- you have to do I/O somewhere or the results are 
irrelevant.  And you are wrong about Stream_IO.Read; you have to use a 
Stream_Element_Array in order to do that, and that is in Ada.Streams, not in 
Stream_IO.

In any case, I'm done wasting my time answering this question. It's obvious 
that you have lost you mind vis-a-vis this question, and there is no reason 
to waste any more time if/until you get it back. Do not feed the troll (even 
if the troll is someone that is otherwise reasonable).

                                                    Randy.





^ permalink raw reply	[relevance 4%]

* Re: Ada.Execution_Time
  2010-12-31  0:40  0%                                             ` Ada.Execution_Time BrianG
@ 2010-12-31  9:09  0%                                               ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2010-12-31  9:09 UTC (permalink / raw)


On Thu, 30 Dec 2010 19:40:08 -0500, BrianG wrote:

> Dmitry A. Kazakov wrote:
>> On Tue, 28 Dec 2010 14:14:57 +0000, Simon Wright wrote:
>> 
>>> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
>>>
>>>> And conversely, the catastrophic accuracy of the VxWorks real-time
>>>> clock service does not hinder its usability for real-time application.
>>> Catastrophic?
>> 
>> Yes, this thing. In our case it was Pentium VxWorks 6.x. (The PPC we used
>> prior to it had poor performance) The problem was that Ada.Real_Time.Clock
>> had the accuracy of the clock interrupts, i.e. 1ms, which is by all
>> accounts catastrophic for a 1.7GHz processor. You can switch some tasks
>> forth and back between two clock changes.  
> 
> So, we're talking about GNAT's use of VxWorks' features as
> "catastrophic"?  That's not how I read the original statement.

No, GNAT just uses the standard OS clock. It is the OS design flaw. They
should have used the CPU's real time clock, or provide a configurable
clock, so that you could choose its source. Why should AdaCore clean up
Wind River's mess?

Happy New Year,

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-28 15:08  6%                                           ` Ada.Execution_Time Dmitry A. Kazakov
  2010-12-28 16:18  0%                                             ` Ada.Execution_Time Simon Wright
@ 2010-12-31  0:40  0%                                             ` BrianG
  2010-12-31  9:09  0%                                               ` Ada.Execution_Time Dmitry A. Kazakov
  1 sibling, 1 reply; 200+ results
From: BrianG @ 2010-12-31  0:40 UTC (permalink / raw)


Dmitry A. Kazakov wrote:
> On Tue, 28 Dec 2010 14:14:57 +0000, Simon Wright wrote:
> 
>> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
>>
>>> And conversely, the catastrophic accuracy of the VxWorks real-time
>>> clock service does not hinder its usability for real-time application.
>> Catastrophic?
>>
...
> 
> Yes, this thing. In our case it was Pentium VxWorks 6.x. (The PPC we used
> prior to it had poor performance) The problem was that Ada.Real_Time.Clock
> had the accuracy of the clock interrupts, i.e. 1ms, which is by all
> accounts catastrophic for a 1.7GHz processor. You can switch some tasks
> forth and back between two clock changes.
>  

So, we're talking about GNAT's use of VxWorks' features as
"catastrophic"?  That's not how I read the original statement.

(We use GNAT on VxWorks, but since we don't (yet) really use tasks, and 
have our own "delay" equivalent to match external hardware, I don't see 
its performance - but since I'm used to GNAT on DOS/Windows, I don't 
have very high expectations.  It sounds like I should keep that opinion.)

--BrianG



^ permalink raw reply	[relevance 0%]

* Re: An Example for Ada.Execution_Time
  2010-12-29  3:10  4%   ` Randy Brukardt
@ 2010-12-30 23:51  5%     ` BrianG
    2011-01-01  0:07  4%       ` Randy Brukardt
  0 siblings, 2 replies; 200+ results
From: BrianG @ 2010-12-30 23:51 UTC (permalink / raw)


Randy Brukardt wrote:
> "BrianG" <briang000@gmail.com> wrote in message 
> news:ifbi5c$rqt$1@news.eternal-september.org...
> ...
>>    >Neither Execution_Time or Execution_Time.Timers provides any value
>>    >that can be used directly.
> 
> This seems like a totally silly question. 
> 
> Giving this some sort of religious importance is beyond 
> silly...
> 
>                                    Randy.


Apparently, asking how a package, defined in the standard, was intended 
to be used is now a silly question, and asking for an answer to the 
question I originally asked (which was to clarify a previous response, 
not to provide an example of use) is a religious debate.  I need to 
revise my definitions.

I won't claim to be an expert on the RM, but I don't recall any other 
package (I did look at the ones you mention) that define a private type 
but don't provide operations that make that type useful (for some 
definition of 'use').  Ada.Directories doesn't require Ada.IO_Exceptions 
to use Directory_Entry_Type or Search_Type; Ada.Streams.Stream_IO 
doesn't require Ada.Streams (or Ada.Text_IO) to Create/Open/Read/etc. a 
File_Type.  The only thing provided from a CPU_Time is a count in 
seconds, or another private type.

Since D.16 defines CPU_Time as if it were a numeric value, is it too 
much to ask why a conversion to some form of numeric value wasn't 
provided?  Perhaps either a "-" or To_Duration  (and before anyone 
mentions duplicating the existing function, look at all of the 
Open/Close/Create/etc. for all the *_IO File_Types)?  I wasn't asking 
for anything to be changed, merely "why" - because I originally thought 
there might be some use that I hadn't foreseen.  Apparently not.

(Give the RM definition, making it a child of Real_Time might make it 
seem more logical, I guess, but since CPU_Time is not really a time, and 
is not related to "real time" that doesn't seem to make any sense.  I 
would think that would be all the more reason not to relate it to 
Ada.Real_Time.)

--BrianG

-- don't ask me
-- I'm just improvising
--   my illusion of careless flight
-- can't you see
--   my temperature's rising
-- I radiate more heat than light



^ permalink raw reply	[relevance 5%]

* Re: Task execution time test
  @ 2010-12-30  8:54  5%   ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2010-12-30  8:54 UTC (permalink / raw)


On Thu, 30 Dec 2010 00:00:10 +0100, h_poincare wrote:

> Here are the measures of the code on my Windows machines
> which tend to prove that the scheduling is correct.
> 
> On Windows Vista SP2 :
> For 1_000 loops
> Seconds 0 Fraction 0.093600600
> For 10_000 loops
> Seconds 1 Fraction 0.029606600
> 
> On Windows XP2002 SP3 :
> For 1_000 loops
> Seconds 0 Fraction 0.125000000
> Seconds 0 Fraction 0.109375000
> For 10_000 loops
> Seconds 1 Fraction 0.140625000
> 
> GPS 4.4.1 (20091215) hosted on i686-pc-mingw32
> GNAT GPL 2010 (20100603)

I think you have a multi-core processor. In effect the measured task does
not lose the processor as the test intends. Make sure that the number of
worker task is sufficiently high to make busy all cores.

(I have posted a better test in a new thread.)

> I am just curious to know how to get/set Windows performance counters

QueryPerformanceCounter returns a 64-bit integer. QueryPerformanceFrequency
gives the frequency of the counter.

Relation of both may serve a replacement for Ada.Real_Time.Clock. Beware
multi-cores. Each core has its own counter. That means, you cannot mix
counts from different cores. SetThreadAffinityMask can be used to glue the
task to a core.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 5%]

* Task execution time 2
@ 2010-12-30  8:54  6% Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2010-12-30  8:54 UTC (permalink / raw)


Here is a better test for the thing. It measures the execution time using
real-time clock and Windows services. The idea is to give up the processor
after 0.5ms, before the system time quant expires.

The test must run considerably long time. Because the task Measured should
lose the processor each 0.5ms and return back after other tasks would take
their share. If the test completes shortly, that possibly mean something
wrong. Increase the number of worker task.
----------------------------------------------------------------
with Ada.Execution_Time;  use Ada.Execution_Time;
with Ada.Real_Time;       use Ada.Real_Time;
with Ada.Text_IO;         use Ada.Text_IO;

with Ada.Numerics.Elementary_Functions;

procedure Executuion_Time_1 is
   task type Measured;
   task body Measured is
      Count     : Seconds_Count;
      Fraction  : Time_Span;
      Estimated : Time_Span := Time_Span_Zero;
      Start     : Time;
   begin
      for I in 1..1_000 loop
         Start := Clock;
         while To_Duration (Clock - Start) < 0.000_5 loop
            null;
         end loop;
         Estimated := Estimated + Clock - Start;
         delay 0.0;
      end loop;
      Split (Ada.Execution_Time.Clock, Count, Fraction);
      Put_Line
      (  "Measured: seconds" & Seconds_Count'Image (Count) &
         " Fraction " & Duration'Image (To_Duration (Fraction))
      );
      Put_Line
      (  "Estimated:" & Duration'Image (To_Duration (Estimated))
      );
   end Measured;

   task type Worker; -- Used to generate CPU load
   task body Worker is
      use Ada.Numerics.Elementary_Functions;
      X : Float;
   begin
      for I in Positive'Range loop
         X := sin (Float (I));
      end loop;
   end Worker;

begin
   delay 0.1;
   declare
      Workers : array (1..5) of Worker;
      Test    : Measured;
   begin
      null;
   end;
end Executuion_Time_1;
-----------------------------------------------------------
Windows XP SP3

Measured: seconds 0 Fraction  0.000000000
Estimated: 0.690618774

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  2010-12-29 12:48  2%                                 ` Ada.Execution_Time Niklas Holsti
  2010-12-29 14:30  3%                                   ` Ada.Execution_Time Dmitry A. Kazakov
@ 2010-12-30  5:06  0%                                   ` Randy Brukardt
    1 sibling, 1 reply; 200+ results
From: Randy Brukardt @ 2010-12-30  5:06 UTC (permalink / raw)


"Niklas Holsti" <niklas.holsti@tidorum.invalid> wrote in message 
news:8o0p0lF94rU1@mid.individual.net...
> Randy, I'm glad that you are participating in this thread. My duologue 
> with Dmitry is becoming repetitive and our views entrenched.
>
> We have been discussing several things, although the focus is on the 
> intended meaning and properties of Ada.Execution_Time. As I am not an ARG 
> member I have based my understanding on the (A)RM text. If the text does 
> not reflect the intent of the ARG, I will be glad to know it, but perhaps 
> the ARG should then consider resolving the conflict by confirming or 
> changing the text.

Perhaps, but that presumes there is something wrong with the text. A lot is 
purposely left unspecified in the ARM; what causes problems is when people 
start reading stuff that is not there.

...

>> My understanding was that it was intended to provide a window into 
>> whatever facilities the underlying system had for execution "time" 
>> counting.
>
> Of course, as long as those facilities are good enough for the RM 
> requirements and for the users; otherwise, the implementor might improve 
> on the underlying system as required. The same holds for Ada.Real_Time. If 
> the underlying system is a bare-board Ada RTS, the Ada 95 form of the RTS 
> probably had to be extended to support Ada.Execution_Time.
>
> I'm sure that the proposers of the package Ada.Execution_Time expected the 
> implementation to use the facilities of the underlying system. But I am 
> also confident that they had in mind some specific uses of the package and 
> that these uses require that the values provided by Ada.Execution_Time 
> have certain properties that can reasonably be expected of "execution 
> time", whether or not these properties are expressly written as 
> requirements in the RM.

Probably, but quality of implementation is rarely specified in the Ada 
Standard. When it is, it generally is in the form of Implementation Advice 
(as opposed to hard requirements). The expectation is that implementers are 
going to provide the best implementation that they can -- implementers don't 
purposely build crippled or useless implementations. Moreover, that is 
*more* likely when the Standard is overspecified, simply because of the need 
to provide something that meets the standard.

> Examples of these uses are given in the paper by A. Burns and A.J. 
> Wellings, "Programming Execution-Time Servers in Ada 2005," pp.47-56, 27th 
> IEEE International Real-Time Systems Symposium (RTSS'06), 2006. 
> http://doi.ieeecomputersociety.org/10.1109/RTSS.2006.39.
>
> You put "time" in quotes, Randy. Don't you agree that there *is* a valid, 
> physical concept of "the execution time of a task" that can be measured in 
> units of physical time, seconds say? At least for processors that only 
> execute one task at a time, and whether or not the system provides 
> facilities for measuring this time?

I'm honestly not sure. The problem is that while such a concept might 
logicially exist, as a practical matter it cannot be measured outside of the 
most controlled circumstances. Thus, that might make sense in a bare-board 
Ada implementation, but not in any implementation running on top of any OS 
or kernel. As such, whether the concept exists is more of an "angels on the 
head of a pin" question than anything of practical importance.

> I think that the concept exists and that it matches the description in RM 
> D.14 (11/2), using the background from D.2.1, whether or not the ARG 
> intended this match.
>
> If you agree that such "execution time" values are conceptually well 
> defined, do you not think that the "execution time counting facilities" of 
> real-time OSes are meant to measure these values, to some practical level 
> of accuracy?
>
> If so, then even if Ada.Execution_Time is intended as only a window into 
> these facilities, it is still intended to provide measures of the physical 
> execution time of tasks, to some practical level of accuracy.

The problem is that that "practical level of accuracy" isn't realistic. 
Moreover, I've always viewed such facilities as "profiling" ones -- it's the 
relative magnitudes of the values that matter, not the absolute values. In 
that case, the scale of the values is not particularly relevant.

Specifically, I mean that what is important is which task is taking a lot of 
CPU. In that case, it simply is the task that has a large "execution time" 
(whatever that means) compared to the others. Typically, that's more than 
100 times the usage of the other tasks, so the units involved are hardly 
relevant.

>> That had no defined relationship with what Ada calls "time".
>> As usch, I think the name "execution time" is misleading, (and I recall 
>> some discussions about that in the ARG), but no one had a better name 
>> that made any sense at all.
>
> Do you remember if these discussions concerned the name of the package, 
> the name of the type CPU_Time, or the very concept "execution time"? If 
> the question was of the terms "time" versus "duration", I think "duration" 
> would have been more consistent with earlier Ada usage, but "execution 
> time" is more common outside Ada, for example in the acronym WCET for 
> Worst-Case Execution Time.
>
> The fact that Ada.Execution_Time provides a subtraction operator for 
> CPU_Time that yields Time_Span, which can be further converted to 
> Duration, leads the RM reader to assume some relationship, at least that 
> spans of real time and spans of execution time can be measured in the same 
> physical units (seconds).
>
> It has already been said, and not only by me, that Ada.Execution_Time is 
> intended (among other things, perhaps) to be used for implementing task 
> scheduling algorithms that depend on the accumulated execution time of the 
> tasks. This is supported by the Burns and Wellings paper referenced above. 
> In such algorithms I believe it is essential that the execution times are 
> physical times because they are used in formulae that relate (sums of) 
> execution-time spans to spans of real time.

That would be a wrong interpretation of a algorithms, I think. (Either that, 
or the algorithms themselves are heavily flawed!). The important property is 
that all of the execution times have a reasonably proportional relationship 
to the actual time spent executing each task (that hypothetical concept); 
the absolute values shouldn't matter much (just as the exact priority values 
are mostly irrelevant to scheduling decisions). Moreover, when the values 
are close, one would hope that the algorithms don't change behavior much.

The values would be trouble if they bore no relationship at all to the 
"actual time spent executing the task", but it's hard to imagine any 
real-world facility in which that was the case.

...
...
>> In particular, there is no requirement in the RM or anywhere else that 
>> these "times" sum to any particular answer.
>
> I agree that the RM has no such explicit requirement. I made this claim to 
> counter Dmitry's assertion that CPU_Time has no physical meaning, and of 
> course I accept that the sum will usually be less than real elapsed time 
> because the processor spends some time on non-task activities.
>
> The last sentence of RM D.14 (11/2) says "It is implementation defined 
> which task, if any, is charged the execution time that is consumed by 
> interrupt handlers and run-time services on behalf of the system". This 
> sentence strongly suggests to me that the author of this paragraph had in 
> mind that the total available execution time (span) equals the real time 
> (span), that some of this total is charged to the tasks, but that some of 
> the time spent in interrupt handlers etc. need not be charged to tasks.
>
> The question is how much meaning should be read into ordinary words like 
> "time" when used in the RM without a formal definition.
>
> If the RM were to say that L is the length of a piece of string S, 
> measured in meters, and that some parts of S are colored red, some blue, 
> and some parts may not be colored at all, surely we could conclude that 
> the sum of the lengths in meters of the red, blue, and uncolored parts 
> equals L? And that the sum of the lengths of the red and blue parts is at 
> most L? And that, since we like colorful things, we hope that the length 
> of the uncolored part is small?
>
> I think the case of summing task execution time spans is analogous.

I think you are inventing things. There is no such requirement in the 
standard, and that's good: I've never seen a real system in which this has 
been true.

Even the various profilers I wrote for MS-DOS (the closest system to a bare 
machine that will ever be in wide use) never had this property. I used to 
think that it was some sort of bug in my methods, but even using completely 
different ways of measuring time (counting ticks at subprogram heads vs. 
statistical probes -- I tried both) the effects still showed up. I've pretty 
much concluded that is is simply part of the nature of computer time -- much 
like floating point, it is an incomplete abstraction of the "real" time, and 
expecting too much out of it is going to lead immediately to disappointment.

>> I don't quite see how there could be, unless you were going to require a 
>> tailored Ada target system (which is definitely not going to be a 
>> requirement).
>
> I don't want such a requirement. The acceptable overhead (fraction of 
> execution time not charged to tasks) depends on the application.
>
> Moreover, on a multi-process systems (an Ada program running under Windows 
> or Linux, for example) some of the CPU time is spent on other processes, 
> all of which would be "overhead" from the point of view of the Ada 
> program. I don't think that the authors of D.14 had such systems in mind.

I disagree, in the sense that the ARG as a whole certainly considered the 
use of this facility in all environments. (I find that it would be very 
valuable for profiling on Windows, for instance, even if the results only 
have a weak relationship to reality).

It's possible that the people who proposed it originally were thinking as 
you are, but the ARG modified those proposals quite a bit; the result is 
definitely a team effort and not the work on any particular individual.

                               Randy.





^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-29 14:30  3%                                   ` Ada.Execution_Time Dmitry A. Kazakov
  @ 2010-12-29 20:32  5%                                     ` Niklas Holsti
  1 sibling, 0 replies; 200+ results
From: Niklas Holsti @ 2010-12-29 20:32 UTC (permalink / raw)


Dmitry A. Kazakov wrote:
> On Wed, 29 Dec 2010 14:48:20 +0200, Niklas Holsti wrote:
> 
>> Dmitry has agreed with some of my statements on this point, for example:
>>
>> - A task cannot accumulate execution time at a higher rate than real 
>> time. For example, in one real-time second the CPU_Time of a task cannot 
>> increase by more than one second.
> 
> Hold on, that is only true if a certain model of CPU_Time measurement used.

In my view, it is true within the accuracy of the execution-time 
measurement method.

> There are many potential models. The one we discussed was the model A:
> 
> Model A. Get an RTC reading upon activation. Each time CPU_Time is
> requested by Clock get another RTC reading, build the difference, add the
> accumulator to the result. Upon task deactivation, get the difference and
> update the accumulator.

OK. This is, I think, the most natural model, perhaps with some 
processor performance counter or CPU-clock-cycle counter replacing the RTC.

> This is a very strong model. Weaker models:
> 
> Model A.1. Get RTC upon activation and deactivation. Update the accumulator
> upon deactivation. When the task is active CPU_Time does not change.

That model is not permitted, because the value of 
Ada.Execution_Time.Clock must change at every "CPU tick". The duration 
of a CPU tick is Ada.Execution_Time.CPU_Tick, which is at most one 
millisecond (RM D.14(20/2)).

It is true that CPU_Tick is only the "average length" of the 
constant-Clock intervals, but the implementation is also required to 
document an upper bound, which also forbids your model A.1.

(I think that this "average" definition caters for implementations where 
the execution time counter is incremented by an RTC interrrupt handler 
that may suffer some timing jitter.)

> Model B. Use a time source different from RTC. This what Windows actually
> doest.

I don't think that this is a different "model". No time source provides 
ideal, exact real time. If the time source for Ada.Execution_Time.Clock 
differs much from real time, the accuracy of the implementation is poor 
to that extent. It does not surprise me that this happens on Windows.

I admit that the RM does not specify any required accuracy for 
Ada.Execution_Time.Clock. The accuracy required for 
execution-time-dependent scheduling algorithms is generally low, I believe.

Analogously, there are no accuracy requirements on Ada.Real_Time.Clock.

> Model B.1. Like A.1, CPU_Time freezes when the task is active.

Forbidden like A.1 above.

> Model C. Asynchronous task monitoring process

That sounds weird. Please clarify.

> Note that in either model the counter readings are rounded. Windows rounds
> toward zero, which why you never get more load than 100%. But it is
> thinkable and expectable that some systems would round away from zero or to
> the nearest bound. So the statement holds only if you have A (maybe C) + a
> corresponding rounding.

So it holds within the accuracy of the measurement method, which often 
involves some sampling or rounding error. In my view.

>> - If only one task is executing on a processor, the execution time of 
>> that task increases (or "could increase") at the same rate as real time.
> 
> This also may be wrong if a B model is used. In particular, task switching
> may be (and I think is) driven by the programmable timer interrupts. The
> real-time clock may be driven by the TSC. Since these two are physically
> different, unsynchronized time sources, the effect can be any. It is to
> expect a systematic error accumulated with the time.

Again, it holds within the accuracy of the measurement method and the 
time source, which is all that one can expect.

The points I made were meant to show how CPU_Time is related, in 
principle, to real time. I entirely accept that in practice the 
relationships will be affected by measurement inaccuracies.

For the task scheduling methods that depend on actual execution times, I 
believe that long-term drifts or accumulations of errors in CPU_Time are 
unimportant. The execution time (span) measurements need to be 
reasonably accurate only over time spans similar to the period of the 
longest-period task. The overhead (execution time not charged to tasks) 
will probably be much larger, both in mean value and in variability, 
than the time-source errors.

As discussed earlier, the time source for Ada.Real_Time.Clock that 
determines when time-driven tasks are activated may need higher fidelity 
to real time.

>> The question is how much meaning should be read into ordinary words like 
>> "time" when used in the RM without a formal definition.
> 
> Time as physical concept is not absolute. There is no *the* real time, but
> many real times and even more unreal ones.

When RM D.14(11/2) defines "the execution time of a given task" as "the 
time spent by the system executing that task", the only reasonable 
reading of the second "time" is as the common-sense physical time, as 
measured by your wrist-watch or by some more precise clock.

Let's not go into relativity and quantum mechanics for this.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  2010-12-29 16:51  5%                                       ` Ada.Execution_Time Dmitry A. Kazakov
@ 2010-12-29 19:57  0%                                         ` (see below)
  0 siblings, 0 replies; 200+ results
From: (see below) @ 2010-12-29 19:57 UTC (permalink / raw)


On 29/12/2010 16:51, in article jw9ocxiajasa.142oku2z0e6rx$.dlg@40tude.net,
"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote:

> On Wed, 29 Dec 2010 16:19:13 +0000, (see below) wrote:
> 
>> From this I deduce that the intent for CPU_Time is that it be a useful
>> approximation to the sum of the durations (small "d") of the intervals of
>> local inertial-frame physical time in which the task is in the running
>> state.
> 
> There exist more pragmatic considerations than the relativity theory. The
> duration you refer above is according to which clock?

I referred to time dilation to preempt your bringing it up. 8-)

> - Real time CPU counter
> - Programmable timer
> - BIOS clock
> - OS system clock
> - Ada.Real_Time.Clock
> - Ada.Calendar.Clock
> - an NTP server from the given list ...
>   ...

Quite so, but these issues, and rounding, and so on, are all subsumed under
"useful approximation".  They are implementation dependent in the best of
circumstances, and so need to be specified by the implementer.

>> It seems to me that the only grey area is the degree of approximation that
>> is acceptable for the result to be "useful".
> 
> That is the next can of worms to open. Once you decided which clock you
> take, you would have to define the sum of *which* durations according to
> this clock you are going to approximate. This would be way more difficult
> and IMO impossible. What is the "CPU" is presence of many cores? What does
> it mean for the task to be "active" keeping in mind the cases it could get
> blocked without losing the "CPU" (defined above)?

I think you are are creating unnecessary difficulties. Note that I said
nothing about CPUs, only about process states. The elapsed time between
dispatching a task/process and pre-empting or blocking it is a well defined
physical quantity. It has nothing to do with cores, and I've no idea what
"blocked without losing the CPU" means. In my dictionary that is simply
self-contradictory. But if it does mean something in some implementation,
all that is necessary is to inform of the approximation it gives rise to.

> In my humble opinion,

!-)

> ARG defined Ada.Execution_Time in the most
> *reasonable* way, in particular, allowing to deliver whatever garbage the
> underlying OS service spits.

I agree. What else could they do?
And if the implementation documents that, where is the harm?

-- 
Bill Findlay
with blueyonder.co.uk;
use  surname & forename;






^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  @ 2010-12-29 16:51  5%                                       ` Dmitry A. Kazakov
  2010-12-29 19:57  0%                                         ` Ada.Execution_Time (see below)
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-12-29 16:51 UTC (permalink / raw)


On Wed, 29 Dec 2010 16:19:13 +0000, (see below) wrote:

> From this I deduce that the intent for CPU_Time is that it be a useful
> approximation to the sum of the durations (small "d") of the intervals of
> local inertial-frame physical time in which the task is in the running
> state.

There exist more pragmatic considerations than the relativity theory. The
duration you refer above is according to which clock?

- Real time CPU counter
- Programmable timer
- BIOS clock
- OS system clock
- Ada.Real_Time.Clock
- Ada.Calendar.Clock
- an NTP server from the given list ...
  ...

> It seems to me that the only grey area is the degree of approximation that
> is acceptable for the result to be "useful".

That is the next can of worms to open. Once you decided which clock you
take, you would have to define the sum of *which* durations according to
this clock you are going to approximate. This would be way more difficult
and IMO impossible. What is the "CPU" is presence of many cores? What does
it mean for the task to be "active" keeping in mind the cases it could get
blocked without losing the "CPU" (defined above)?

In my humble opinion, ARG defined Ada.Execution_Time in the most
*reasonable* way, in particular, allowing to deliver whatever garbage the
underlying OS service spits.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  2010-12-29 12:48  2%                                 ` Ada.Execution_Time Niklas Holsti
@ 2010-12-29 14:30  3%                                   ` Dmitry A. Kazakov
    2010-12-29 20:32  5%                                     ` Ada.Execution_Time Niklas Holsti
  2010-12-30  5:06  0%                                   ` Ada.Execution_Time Randy Brukardt
  1 sibling, 2 replies; 200+ results
From: Dmitry A. Kazakov @ 2010-12-29 14:30 UTC (permalink / raw)


On Wed, 29 Dec 2010 14:48:20 +0200, Niklas Holsti wrote:

> Dmitry has agreed with some of my statements on this point, for example:
> 
> - A task cannot accumulate execution time at a higher rate than real 
> time. For example, in one real-time second the CPU_Time of a task cannot 
> increase by more than one second.

Hold on, that is only true if a certain model of CPU_Time measurement used.
There are many potential models. The one we discussed was the model A:

Model A. Get an RTC reading upon activation. Each time CPU_Time is
requested by Clock get another RTC reading, build the difference, add the
accumulator to the result. Upon task deactivation, get the difference and
update the accumulator.

This is a very strong model. Weaker models:

Model A.1. Get RTC upon activation and deactivation. Update the accumulator
upon deactivation. When the task is active CPU_Time does not change.

Model B. Use a time source different from RTC. This what Windows actually
doest.

Model B.1. Like A.1, CPU_Time freezes when the task is active.

Model C. Asynchronous task monitoring process

...

Note that in either model the counter readings are rounded. Windows rounds
toward zero, which why you never get more load than 100%. But it is
thinkable and expectable that some systems would round away from zero or to
the nearest bound. So the statement holds only if you have A (maybe C) + a
corresponding rounding.

> - If only one task is executing on a processor, the execution time of 
> that task increases (or "could increase") at the same rate as real time.

This also may be wrong if a B model is used. In particular, task switching
may be (and I think is) driven by the programmable timer interrupts. The
real-time clock may be driven by the TSC. Since these two are physically
different, unsynchronized time sources, the effect can be any. It is to
expect a systematic error accumulated with the time.

> The question is how much meaning should be read into ordinary words like 
> "time" when used in the RM without a formal definition.

Time as physical concept is not absolute. There is no *the* real time, but
many real times and even more unreal ones. I don't think RM can go into
this. Not only because it would be not Ada's business, but because
otherwise it would have to use some reference time. Ada does not have this,
it intentionally refused to have it when introduced Ada.Real_Time.Time. The
same arguments which were used then apply now. CPU_Time is a third time by
default absolutely independent on the other two.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 3%]

* Re: Ada.Execution_Time
  @ 2010-12-29 12:48  2%                                 ` Niklas Holsti
  2010-12-29 14:30  3%                                   ` Ada.Execution_Time Dmitry A. Kazakov
  2010-12-30  5:06  0%                                   ` Ada.Execution_Time Randy Brukardt
  0 siblings, 2 replies; 200+ results
From: Niklas Holsti @ 2010-12-29 12:48 UTC (permalink / raw)


Randy, I'm glad that you are participating in this thread. My duologue 
with Dmitry is becoming repetitive and our views entrenched.

We have been discussing several things, although the focus is on the 
intended meaning and properties of Ada.Execution_Time. As I am not an 
ARG member I have based my understanding on the (A)RM text. If the text 
does not reflect the intent of the ARG, I will be glad to know it, but 
perhaps the ARG should then consider resolving the conflict by 
confirming or changing the text.

Randy Brukardt wrote:
> "Niklas Holsti" <niklas.holsti@tidorum.invalid> wrote in message 
> news:8nm30fF7r9U1@mid.individual.net...
>> Dmitry A. Kazakov wrote:
>>> On Sat, 18 Dec 2010 23:20:20 +0200, Niklas Holsti wrote:
> ...
>>> On a such platform the implementation would be as perverse as RM D.14
>>> is. But the perversion is only because of the interpretation.
>> Bah. I think that when RM D.14 says "time", it really means time. You
>> think it means something else, perhaps a CPU cycle count. I think the 
>> burden of proof is on you.
>>
>> It seems evident to me that the text in D.14 must be interpreted using
>> the concepts in D.2.1, "The Task Dispatching Model", which clearly
>> specifies real-time points when a processor starts to execute a task and
>> stops executing a task. To me, and I believe to most readers of the RM,
>> the execution time of a task is the sum of these time slices, thus a
>> physical, real time.
> 
> For the record, I agree more with Dmitry than Niklas here. At least the 
> interpretation *I* had when this package was proposed was that it had only a 
> slight relationship to real-time.

Oh. What would that slight relationship be? Or was it left unspecified?

> My understanding was that it was intended 
> to provide a window into whatever facilities the underlying system had for 
> execution "time" counting.

Of course, as long as those facilities are good enough for the RM 
requirements and for the users; otherwise, the implementor might improve 
on the underlying system as required. The same holds for Ada.Real_Time. 
If the underlying system is a bare-board Ada RTS, the Ada 95 form of the 
RTS probably had to be extended to support Ada.Execution_Time.

I'm sure that the proposers of the package Ada.Execution_Time expected 
the implementation to use the facilities of the underlying system. But I 
am also confident that they had in mind some specific uses of the 
package and that these uses require that the values provided by 
Ada.Execution_Time have certain properties that can reasonably be 
expected of "execution time", whether or not these properties are 
expressly written as requirements in the RM.

Examples of these uses are given in the paper by A. Burns and A.J. 
Wellings, "Programming Execution-Time Servers in Ada 2005," pp.47-56, 
27th IEEE International Real-Time Systems Symposium (RTSS'06), 2006. 
http://doi.ieeecomputersociety.org/10.1109/RTSS.2006.39.

You put "time" in quotes, Randy. Don't you agree that there *is* a 
valid, physical concept of "the execution time of a task" that can be 
measured in units of physical time, seconds say? At least for processors 
that only execute one task at a time, and whether or not the system 
provides facilities for measuring this time?

I think that the concept exists and that it matches the description in 
RM D.14 (11/2), using the background from D.2.1, whether or not the ARG 
intended this match.

If you agree that such "execution time" values are conceptually well 
defined, do you not think that the "execution time counting facilities" 
of real-time OSes are meant to measure these values, to some practical 
level of accuracy?

If so, then even if Ada.Execution_Time is intended as only a window into 
these facilities, it is still intended to provide measures of the 
physical execution time of tasks, to some practical level of accuracy.

> That had no defined relationship with what Ada calls "time".
> As usch, I think the name "execution time" is misleading, (and 
> I recall some discussions about that in the ARG), but no one had a better 
> name that made any sense at all.

Do you remember if these discussions concerned the name of the package, 
the name of the type CPU_Time, or the very concept "execution time"? If 
the question was of the terms "time" versus "duration", I think 
"duration" would have been more consistent with earlier Ada usage, but 
"execution time" is more common outside Ada, for example in the acronym 
WCET for Worst-Case Execution Time.

The fact that Ada.Execution_Time provides a subtraction operator for 
CPU_Time that yields Time_Span, which can be further converted to 
Duration, leads the RM reader to assume some relationship, at least that 
spans of real time and spans of execution time can be measured in the 
same physical units (seconds).

It has already been said, and not only by me, that Ada.Execution_Time is 
intended (among other things, perhaps) to be used for implementing task 
scheduling algorithms that depend on the accumulated execution time of 
the tasks. This is supported by the Burns and Wellings paper referenced 
above. In such algorithms I believe it is essential that the execution 
times are physical times because they are used in formulae that relate 
(sums of) execution-time spans to spans of real time.

Dmitry has agreed with some of my statements on this point, for example:

- A task cannot accumulate execution time at a higher rate than real 
time. For example, in one real-time second the CPU_Time of a task cannot 
increase by more than one second.

- If only one task is executing on a processor, the execution time of 
that task increases (or "could increase") at the same rate as real time.

Do you agree that we can expect these statements to be true? (On the 
second point, system overhead should of course be taken into account, on 
which more below.)

> In particular, there is no requirement in the RM or anywhere else that these 
> "times" sum to any particular answer.

I agree that the RM has no such explicit requirement. I made this claim 
to counter Dmitry's assertion that CPU_Time has no physical meaning, and 
of course I accept that the sum will usually be less than real elapsed 
time because the processor spends some time on non-task activities.

The last sentence of RM D.14 (11/2) says "It is implementation defined 
which task, if any, is charged the execution time that is consumed by 
interrupt handlers and run-time services on behalf of the system". This 
sentence strongly suggests to me that the author of this paragraph had 
in mind that the total available execution time (span) equals the real 
time (span), that some of this total is charged to the tasks, but that 
some of the time spent in interrupt handlers etc. need not be charged to 
tasks.

The question is how much meaning should be read into ordinary words like 
"time" when used in the RM without a formal definition.

If the RM were to say that L is the length of a piece of string S, 
measured in meters, and that some parts of S are colored red, some blue, 
and some parts may not be colored at all, surely we could conclude that 
the sum of the lengths in meters of the red, blue, and uncolored parts 
equals L? And that the sum of the lengths of the red and blue parts is 
at most L? And that, since we like colorful things, we hope that the 
length of the uncolored part is small?

I think the case of summing task execution time spans is analogous.

> I don't quite see how there could be, 
> unless you were going to require a tailored Ada target system (which is 
> definitely not going to be a requirement).

I don't want such a requirement. The acceptable overhead (fraction of 
execution time not charged to tasks) depends on the application.

Moreover, on a multi-process systems (an Ada program running under 
Windows or Linux, for example) some of the CPU time is spent on other 
processes, all of which would be "overhead" from the point of view of 
the Ada program. I don't think that the authors of D.14 had such systems 
in mind.

> Perhaps the proposers (from the IRTAW meetings) had something else in mind, 
> but if so, they communicated it very poorly.

Do you remember who they were? Are the IRTAW minutes or proposals 
accessible on the web?

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 2%]

* Re: An Example for Ada.Execution_Time
  2010-12-28  2:31  5% ` BrianG
  2010-12-28 13:43  0%   ` anon
@ 2010-12-29  3:10  4%   ` Randy Brukardt
  2010-12-30 23:51  5%     ` BrianG
  1 sibling, 1 reply; 200+ results
From: Randy Brukardt @ 2010-12-29  3:10 UTC (permalink / raw)


"BrianG" <briang000@gmail.com> wrote in message 
news:ifbi5c$rqt$1@news.eternal-september.org...
...
> I asked for:
>    >> An algorithm comparison program might look like:
>    >>
>    >> with Ada.Execution_Time ;
>    >> with Ada.Execution_Time.Timers ;
>    >Given the below program, please add some of the missing details to
>    >show how this can be useful without also "with Ada.Real_Time".
>    >Neither Execution_Time or Execution_Time.Timers provides any value
>    >that can be used directly.

This seems like a totally silly question. There are a lot of well-designed 
packages in Ada that don't do anything useful without at least one or more 
other packages. Indeed, if you consider "Standard" to be a separate package 
(and it is), there are hardly any packages that *don't* require some other 
package to be useful.

More to the point, you probably need Ada.IO_Exceptions to use 
Ada.Directories effectively (use of any package without error handling is 
toy use); Ada.Streams.Stream_IO require use of Ada.Streams (a separate 
package, which you will need separate use clauses for even if you get it 
imported automatically); Ada.Strings.Maps aren't useful for anything unless 
you combine them with one of the string handling packages, and so on.

Perhaps you would have been happier if Ada.Execution_Time had been a child 
of Ada.Real_Time (exactly as in the string case), but this wouldn't change 
anything.

The odd thing is that Duration is defined in Standard, rather than some more 
appropriate package. Giving this some sort of religious importance is beyond 
silly...

                                   Randy.





^ permalink raw reply	[relevance 4%]

* Re: Ada.Execution_Time
  2010-12-28 16:18  0%                                             ` Ada.Execution_Time Simon Wright
@ 2010-12-28 16:34  0%                                               ` Dmitry A. Kazakov
  0 siblings, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2010-12-28 16:34 UTC (permalink / raw)


On Tue, 28 Dec 2010 16:18:11 +0000, Simon Wright wrote:

> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
> 
>> Yes, this thing. In our case it was Pentium VxWorks 6.x. (The PPC we
>> used prior to it had poor performance) The problem was that
>> Ada.Real_Time.Clock had the accuracy of the clock interrupts,
>> i.e. 1ms, which is by all accounts catastrophic for a 1.7GHz
>> processor. You can switch some tasks forth and back between two clock
>> changes.
> 
> Our experience was that where there are timing constraints to be met, or
> cyclic timing behaviours to implement, a milliscond is OK.
> 
> We did consider running the VxWorks tick at 100 us but this was quite
> unnecessary!

We actually have it set at 100 us, I believe.

But we need high accuracy clock not for switching tasks. It is for time
stamping and frequency measurements.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-28 15:08  6%                                           ` Ada.Execution_Time Dmitry A. Kazakov
@ 2010-12-28 16:18  0%                                             ` Simon Wright
  2010-12-28 16:34  0%                                               ` Ada.Execution_Time Dmitry A. Kazakov
  2010-12-31  0:40  0%                                             ` Ada.Execution_Time BrianG
  1 sibling, 1 reply; 200+ results
From: Simon Wright @ 2010-12-28 16:18 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

> Yes, this thing. In our case it was Pentium VxWorks 6.x. (The PPC we
> used prior to it had poor performance) The problem was that
> Ada.Real_Time.Clock had the accuracy of the clock interrupts,
> i.e. 1ms, which is by all accounts catastrophic for a 1.7GHz
> processor. You can switch some tasks forth and back between two clock
> changes.

Our experience was that where there are timing constraints to be met, or
cyclic timing behaviours to implement, a milliscond is OK.

We did consider running the VxWorks tick at 100 us but this was quite
unnecessary!



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-28 14:14  4%                                         ` Ada.Execution_Time Simon Wright
@ 2010-12-28 15:08  6%                                           ` Dmitry A. Kazakov
  2010-12-28 16:18  0%                                             ` Ada.Execution_Time Simon Wright
  2010-12-31  0:40  0%                                             ` Ada.Execution_Time BrianG
  0 siblings, 2 replies; 200+ results
From: Dmitry A. Kazakov @ 2010-12-28 15:08 UTC (permalink / raw)


On Tue, 28 Dec 2010 14:14:57 +0000, Simon Wright wrote:

> "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:
> 
>> And conversely, the catastrophic accuracy of the VxWorks real-time
>> clock service does not hinder its usability for real-time application.
> 
> Catastrophic?
>
> The Radstone PPC7A cards (to take one example) have two facilities: (a)
> the PowerPC decrementer, run off a crystal with some not-too-good quoted
> accuracy (50 ppm, I think), and (b) a "real time clock".
> 
> The RTC would be much better termed a time-of-day clock, since what it
> provides is the date and time to 1 second precision. It also needs
> battery backup, not easy to justify on naval systems (partly because it
> adversely affects the shelf life of the boards, partly because navies
> don't like noxious chemicals in their equipment).
> 
> We never used the RTC.
>
> The decrementer is the facility used by VxWorks, and hence by GNAT under
> VxWorks, to support time; both Ada.Calendar and Ada.Real_Time (we are
> still at Ada 95 so I have no idea about Ada.Execution_Time). We run with
> clock interrupts at 1 ms and (so far as we can tell from using bus
> analysers) the interrupts behave perfectly reliably.

Yes, this thing. In our case it was Pentium VxWorks 6.x. (The PPC we used
prior to it had poor performance) The problem was that Ada.Real_Time.Clock
had the accuracy of the clock interrupts, i.e. 1ms, which is by all
accounts catastrophic for a 1.7GHz processor. You can switch some tasks
forth and back between two clock changes.
 
> For a higher-resolution view of time we've extended Ada.Calendar, using
> the PowerPC's mftb (Move From Time Base) instruction to measure sub-tick
> intervals (down to 40 ns).

So did we in our case. VxWorks has means to access the Pentium high
resolution counter. We took Ada.Real_Time and replaced the Clock function
with one that used the counter multiplied by its frequency.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  2010-12-27 21:53  0%                                       ` Ada.Execution_Time Dmitry A. Kazakov
@ 2010-12-28 14:14  4%                                         ` Simon Wright
  2010-12-28 15:08  6%                                           ` Ada.Execution_Time Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: Simon Wright @ 2010-12-28 14:14 UTC (permalink / raw)


"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

> And conversely, the catastrophic accuracy of the VxWorks real-time
> clock service does not hinder its usability for real-time application.

Catastrophic?

The Radstone PPC7A cards (to take one example) have two facilities: (a)
the PowerPC decrementer, run off a crystal with some not-too-good quoted
accuracy (50 ppm, I think), and (b) a "real time clock".

The RTC would be much better termed a time-of-day clock, since what it
provides is the date and time to 1 second precision. It also needs
battery backup, not easy to justify on naval systems (partly because it
adversely affects the shelf life of the boards, partly because navies
don't like noxious chemicals in their equipment).

We never used the RTC.

The decrementer is the facility used by VxWorks, and hence by GNAT under
VxWorks, to support time; both Ada.Calendar and Ada.Real_Time (we are
still at Ada 95 so I have no idea about Ada.Execution_Time). We run with
clock interrupts at 1 ms and (so far as we can tell from using bus
analysers) the interrupts behave perfectly reliably.

For a higher-resolution view of time we've extended Ada.Calendar, using
the PowerPC's mftb (Move From Time Base) instruction to measure sub-tick
intervals (down to 40 ns).




^ permalink raw reply	[relevance 4%]

* Re: An Example for Ada.Execution_Time
  2010-12-28  2:31  5% ` BrianG
@ 2010-12-28 13:43  0%   ` anon
  2010-12-29  3:10  4%   ` Randy Brukardt
  1 sibling, 0 replies; 200+ results
From: anon @ 2010-12-28 13:43 UTC (permalink / raw)


In <ifbi5c$rqt$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>anon@att.net wrote:
>> You ask for an example.
>I'll assume I am the "you".  (Since you don't specify and didn't relate 
>it to the original thread.)
>
>I asked for:
>    >> An algorithm comparison program might look like:
>    >>
>    >> with Ada.Execution_Time ;
>    >> with Ada.Execution_Time.Timers ;
>    >Given the below program, please add some of the missing details to
>    >show how this can be useful without also "with Ada.Real_Time".
>    >Neither Execution_Time or Execution_Time.Timers provides any value
>    >that can be used directly.
>    >
>    >>
>    >> procedure Compare_Algorithm is
>    >...]
>
>You provided:
>> 
>> Here is an example for packages (Tested using MaRTE):
>....
>> with Ada.Execution_Time ;
>> with Ada.Real_Time ;
>....
>> with Ada.Execution_Time ;
>> with Ada.Execution_Time.Timers ;
>> with Ada.Real_Time ;
>....
>
>As the extracts show, you could not do what I asked for.  You said in 
>the original post you could do it with only the 2 Execution_Time 
>'with's.  My entire point in this thread is that Execution_Time, as 
>defined, is useless by itself.
>
>--BrianG

I changed the title so there was no need for reference lines

Since 2006, a number of people have ask about Ada.Execution_Time package 
and no one has given a true example that uses that package for what it was 
created for. Until now! I gave you a simple example that can be easily 
modified to a more complex program. Problem: may be whats the maximum 
number of timers that can be allocated.


and for your info (changes in work.adb)

  Task_0 : Work_Task ;
  Task_1 : Work_Task ;
  Task_2 : Work_Task ;
  Task_3 : Work_Task ;

begin
  Initialize ( Work_Algorithm'Access ) ;
  Task_0.Start ( False ) ;
  Task_1.Start ( False ) ;
  Task_2.Start ( True ) ;  -- just for a change
  Task_3.Start ( True ) ;
  ...

will gives four tasks with four different timers. 

     2 timers that have the same interval 
     2 timers that changes the interval

All that is needed is protect the Counter variable for each task and change the 
Counter print routine. And I will let others do that modification.





^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-27 21:34  5%                                       ` Ada.Execution_Time Simon Wright
@ 2010-12-28 10:01  0%                                         ` Niklas Holsti
  0 siblings, 0 replies; 200+ results
From: Niklas Holsti @ 2010-12-28 10:01 UTC (permalink / raw)


Simon Wright wrote:
> Niklas Holsti <niklas.holsti@tidorum.invalid> writes:
> 
>> Nonsense. I spend some part of my time asleep, some time awake. Both
>> "sleeping time" and "awake time" are (pieces of) real time. A task
>> spends some of its time being executed, some of its time not being
>> executed (waiting or ready).
> 
> And, just to be clear, CPU_Time corresponds to the "awake time"?

Perhaps that is the natural choice, but I did not mean the choice to be 
significant. Dmitry was saying that "execution time" is not "time", just 
because it uses the prefix or qualification "execution". By that 
reasoning, "awake time" would not be "time", "chicken soup" would not be 
"soup", etc.

> I thought I understood pretty much what was intended in the execution
> time annex, even if it didn't seem to have much relevance to my work,
> but this discussion has managed to confuse me thoroughly.

Randy's last post in this thread, in which he agrees with Dmitry, has 
the same effect on me. I hope that further discussion with Randy will 
converge to something.

Did your earlier understanding resemble Dmitry's, or mine? Or neither?

> A minor aside -- as a user, I find the use of Time_Span here and in
> Ada.Real_Time very annoying. It's perfectly clear that what's meant is
> Duration.

I think Time_Span and Duration are different representations of the same 
physical thing, a span of time that can be physically measured in 
seconds. The reasons for having two (possibly) different representations 
(two types) have been discussed before: different requirements on range 
and precision. Still, the differences are important only for processors 
that are very small and weak, in today's scale, so perhaps this 
distinction is no longer needed and the types could be merged.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 0%]

* Re: An Example for Ada.Execution_Time
  2010-12-27 18:26  7% An Example for Ada.Execution_Time anon
@ 2010-12-28  2:31  5% ` BrianG
  2010-12-28 13:43  0%   ` anon
  2010-12-29  3:10  4%   ` Randy Brukardt
  0 siblings, 2 replies; 200+ results
From: BrianG @ 2010-12-28  2:31 UTC (permalink / raw)


anon@att.net wrote:
> You ask for an example.
I'll assume I am the "you".  (Since you don't specify and didn't relate 
it to the original thread.)

I asked for:
    >> An algorithm comparison program might look like:
    >>
    >> with Ada.Execution_Time ;
    >> with Ada.Execution_Time.Timers ;
    >Given the below program, please add some of the missing details to
    >show how this can be useful without also "with Ada.Real_Time".
    >Neither Execution_Time or Execution_Time.Timers provides any value
    >that can be used directly.
    >
    >>
    >> procedure Compare_Algorithm is
    >...]

You provided:
> 
> Here is an example for packages (Tested using MaRTE):
...
> with Ada.Execution_Time ;
> with Ada.Real_Time ;
...
> with Ada.Execution_Time ;
> with Ada.Execution_Time.Timers ;
> with Ada.Real_Time ;
...

As the extracts show, you could not do what I asked for.  You said in 
the original post you could do it with only the 2 Execution_Time 
'with's.  My entire point in this thread is that Execution_Time, as 
defined, is useless by itself.

--BrianG



^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  2010-12-27 20:11  2%                                     ` Ada.Execution_Time Niklas Holsti
  2010-12-27 21:34  5%                                       ` Ada.Execution_Time Simon Wright
@ 2010-12-27 21:53  0%                                       ` Dmitry A. Kazakov
  2010-12-28 14:14  4%                                         ` Ada.Execution_Time Simon Wright
  1 sibling, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-12-27 21:53 UTC (permalink / raw)


On Mon, 27 Dec 2010 22:11:18 +0200, Niklas Holsti wrote:

> Dmitry A. Kazakov wrote:
>> Technically, CPU_Time is not a number in any sense. It is not a numeric Ada
>> type and it is not a model of a mathematical number (not even additive).
> 
> RM D.14(12/2): "The type CPU_Time represents the execution time of a 
> task. The set of values of this type corresponds one-to-one with an 
> implementation-defined range of mathematical integers". Thus, a number.

This is true for any value of any type due to finiteness. I think
D.14(12/2) refers to an ability to implement Split. But that is irrelevant.
CPU_Time is not declared numeric, it does not have +.

>>>> it is the Ada.Execution_Time implementation, which needs some
>>>> input from the scheduler.
>>> We must be precise about our terms, here. Using terms as defined in 
>>> http://en.wikipedia.org/wiki/Task_scheduling, Ada.Execution_Time needs 
>>> input from the task *dispatcher* -- the part of the kernel that suspends 
>>> and resumes tasks.
>> 
>> Let's call it dispatcher. Time sharing needs some measure of consumed CPU
>> time. My points stand:
>> 
>> 1. Time sharing has little to do with real-time systems.
> 
> What do you mean by "time sharing"? The classical mainframe system used 
> interactively by many terminals? What on earth does that have to do with 
> our discussion? Such a system of course must have concurrent tasks or 
> processes in some form, but so what?

Because this is the only case where execution time might be any relevant to
the algorithm of task switching.

> If by "time sharing algorithms" (below in your point 2) you mean what is 
> usually called "task scheduling algorithms", where several tasks 
> time-share the same processor by a task-switching (dispatching) 
> mechanism, your point 1 is bizarre. Priority-scheduled task switching is 
> the canonical architecture for real-time systems.

, which architecture makes execution time irrelevant to switching
decisions.

>> 2. It would be extremely ill-advised to use Ada.Execution_Time instead of
>> direct measures for an implementation of time sharing algorithms.
> 
> If by "direct measures" you mean the use of some external measuring 
> device such as an oscilloscope or logic analyzer, such measures are 
> available only externally, to the developers, not within the Ada program 
> itself.

You forgot one external device called real time clock.

> The whole point of Ada.Execution_Time is that it is available to 
> the Ada program itself, enabling run-time decisions based on the actual 
> execution times of tasks.

, which would be ill-advised to do.

>>>>> You have
>>>>> not given any arguments, based on the RM text, to support your position.
>>>> I am not a language lawyer to interpret the RM texts. My argument was to
>>>> common sense.
>>> To me it seems that your argument is based on the difficulty (in your 
>>> opinion) of implementing Ada.Execution_Time in some OSes such as MS 
>>> Windows, if the RM word "time" is taken to mean real time.
>>>
>>> It is common sense that some OSes are not designed (or not well 
>>> designed) for real-time systems. Even a good real-time OS may not 
>>> support all real-time methodologies, for example scheduling algorithms 
>>> that depend on actual execution times.
>> 
>> I disagree with almost everything here. To start with, comparing real-time
>> clock services of Windows and of VxWorks, we would notice that Windows is
>> far superior in both accuracy and precision.
> 
> So what? Real-time systems need determinism. The clock only has to be 
> accurate enough.

Sorry, are you saying that lesser accuracy of real-time clock is a way to
achieve determinism?
 
> If your tasks suffer arbitrary millisecond-scale suspensions or 
> dispatching delays (as is rumored for Windows) a microsecond-level clock 
> accuracy is no help.

And conversely, the catastrophic accuracy of the VxWorks real-time clock
service does not hinder its usability for real-time application. Which is
my point. You don't need good real-time clock in so many real-time
applications, and you never need execution time there.

> Anyway, your point has do to with the "time" that *activates* tasks, not 
> with the measurement of task-specific execution times.

Exactly

> So this is irrelevant.

No, it is the execution time which is irrelevant for real-time systems,
because of the way tasks are activated there.

>> I don't
>> care how much processor time my control loop takes so long it manages to
>> write the outputs when the actuators expect them.
> 
> You should care, if the processor must also have time for some other 
> tasks of lower priority, which are preempted by the control-loop task.

Why? It is straightforward: the task of higher priority level owns the
processor.

>> Measuring the CPU time
>> would bring me nothing. It is useless before the run, because it is not a
>> proof that the deadlines will be met.
> 
> In some cases (simple code or extensive tests, deterministic processor) 
> CPU-time measurements can be used to prove that deadlines are met.

It is difficult to imagine. This is done either statically or else by
running tests. Execution time has drawbacks of both approaches and
advantages of none.

> For example, assume that the computation in a control algorithm consists 
> of two consecutive stages where the first stage processes the inputs 
> into a state model and the second stage computes the control outputs 
> from the state model. Using Ada.Execution_Time or 
> Ada.Execution_Time.Timers the program could detect an unexpectedly high 
> CPU usage in the first stage, and fall back to a simpler, faster 
> algorithm in the second stage, to ensure that some control outputs are 
> computed before the deadline.

No, in our systems we use a different schema. The "fall back" values are
always evaluated first. They must become ready at the end of each cycle. A
finer estimation is evaluated in background and used when ready. Actually,
according to your schema, the finer estimation always "fail" because it is
guaranteed too complex for one cycle. It takes 10-100 cycles to compute at
least. So your schema would not work. In general, real-time systems are
usually designed for the worst case scenario, because when something
unanticipated indeed happens you could have no time to do anything else.
 
>>> Is your point that Ada.Execution_Time was accepted only because the ARG 
>>> decided that the word "time" in RM D.14 should not be understood to mean 
>>> real time? I doubt that very much... Surely such an unusual meaning of 
>>> "time" should have been explained in the RM.
>> 
>> It is explained by its name: "execution time." Execution means not real,
>> unreal time (:-)).
> 
> Nonsense. I spend some part of my time asleep, some time awake. Both 
> "sleeping time" and "awake time" are (pieces of) real time. A task 
> spends some of its time being executed, some of its time not being 
> executed (waiting or ready).

A very good example. Now consider your perception of time. Does it
correspond to the real time? No it does not. The time spent in sleep can be
sensed from very short to very long. This felt time is an analogue of the
task execution time. You better do not use this subjective time to decide
when to have next meal. That could end in obesity.

>>>> If that was the intent, then I really do not understand why CPU_Time was
>>>> introduced in addition to Ada.Real_Time.Time / Time_Span.
>>> Because (as I understand it) different processors/OSes have different 
>>> mechanisms for measuring execution times and real times, and the 
>>> mechanism most convenient for CPU_Time may use a different numerical 
>>> type (range, scale, and precision) than the mechanisms and types used 
>>> for Ada.Real_Time.Time, Time_Span, and Duration.
>> 
>> I see no single reason why this could happen. Obviously, if talking about a
>> real-time system as you insist, the only possible choice for CPU_Time is
>> Time_Span, because to be consistent with the interpretation you propose it
>> must be derived from Ada.Real_Time clock.
> 
> I have only said that the sum of the CPU_Times of all tasks executing on 
> the same processor should be close to the real elapsed time, since the 
> CPU's time is shared between the tasks. This does not mean that 
> Ada.Execution_Time.CPU_Time and Ada.Real_Time.Time must have a common 
> time source, only that both time sources must approximate physical, real 
> time.

What is the reason to use different sources?

>> My point is that RM intentionally leaves it up to the implementation to
>> choose a CPU_Time source independent on Ada.Real_Time.Clock. This why
>> different range and precision come into consideration.
> 
> I agree. But in both cases the intent is to approximate physical, real 
> time, not some "simulation time" where one "simulation second" could be 
> one year of real time.

Certainly the latter. Consider a system with n-processors. The execution
time second will be 1/n of the real time second. With shared memory it will
be f*1/n, where f is some unknown factor. That works in both directions, on
a single processor board with memory connected over some bus system, it
could be f<1, because some external devices might block CPU (and thus your
task) while accessing the memory. Note that the error is systematic. It is
not an approximation of real time.

>> Under some conditions (e.g. no task switching) an execution time interval
>> could be numerically equal to a real time interval.
> 
> Yes! Therefore, under these conditions, CPU_Time (when converted to a 
> Time_Span or Duration) does have a physical meaning. So we agree. At last.

Since these conditions are never met, the model you have in mind is
inadequate (wrong).

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-27 20:11  2%                                     ` Ada.Execution_Time Niklas Holsti
@ 2010-12-27 21:34  5%                                       ` Simon Wright
  2010-12-28 10:01  0%                                         ` Ada.Execution_Time Niklas Holsti
  2010-12-27 21:53  0%                                       ` Ada.Execution_Time Dmitry A. Kazakov
  1 sibling, 1 reply; 200+ results
From: Simon Wright @ 2010-12-27 21:34 UTC (permalink / raw)


Niklas Holsti <niklas.holsti@tidorum.invalid> writes:

> Nonsense. I spend some part of my time asleep, some time awake. Both
> "sleeping time" and "awake time" are (pieces of) real time. A task
> spends some of its time being executed, some of its time not being
> executed (waiting or ready).

And, just to be clear, CPU_Time corresponds to the "awake time"?

I thought I understood pretty much what was intended in the execution
time annex, even if it didn't seem to have much relevance to my work,
but this discussion has managed to confuse me thoroughly.

A minor aside -- as a user, I find the use of Time_Span here and in
Ada.Real_Time very annoying. It's perfectly clear that what's meant is
Duration.



^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  2010-12-27 15:28  4%                                   ` Ada.Execution_Time Dmitry A. Kazakov
@ 2010-12-27 20:11  2%                                     ` Niklas Holsti
  2010-12-27 21:34  5%                                       ` Ada.Execution_Time Simon Wright
  2010-12-27 21:53  0%                                       ` Ada.Execution_Time Dmitry A. Kazakov
  0 siblings, 2 replies; 200+ results
From: Niklas Holsti @ 2010-12-27 20:11 UTC (permalink / raw)


Dmitry A. Kazakov wrote:
> On Mon, 27 Dec 2010 14:44:53 +0200, Niklas Holsti wrote:
> 
>> Dmitry A. Kazakov wrote:
>>> On Sat, 25 Dec 2010 13:31:27 +0200, Niklas Holsti wrote:
>>>
>>>> Dmitry A. Kazakov wrote:
>>>>> On Sat, 18 Dec 2010 23:20:20 +0200, Niklas Holsti wrote:
>>>> ...
>>>>>> The concept and measurement of "the execution time of a task" does
>>>>>> become problematic in complex processors that have hardware 
>>>>>> multi-threading and can run several tasks in more or less parallel
>>>>>> fashion, without completely isolating the tasks from each other.
>>>>> No, the concept is just fine,
>>>> Fine for what? For schedulability analysis, fine for on-line scheduling,
>>>> ... ?
>>> Applicability of a concept is not what makes it wrong or right.
>> I think it does. This concept, "the execution time of a task", stands 
>> for a number. A number is useless if it has no application in a 
>> calculation.
> 
> Technically, CPU_Time is not a number in any sense. It is not a numeric Ada
> type and it is not a model of a mathematical number (not even additive).

RM D.14(12/2): "The type CPU_Time represents the execution time of a 
task. The set of values of this type corresponds one-to-one with an 
implementation-defined range of mathematical integers". Thus, a number.

However, the sub-thread above was not about CPU_Time in 
Ada.Execution_Time, but about the general concept "the execution time of 
a task". (Serves me right for introducing side issues, although my 
intentions were good, I think.)

> Anyway, the execution time can be used in calculations independently on
> whether and how you could apply the results of such calculations.
> 
> You can add the height of your house to the distance to the Moon, the
> interpretation is up to you.

You are being absurd.

Dmitri, your arguments are becoming so weird that I am starting to think 
that you are just trolling or goading me.

>>> it is the Ada.Execution_Time implementation, which needs some
>>> input from the scheduler.
>> We must be precise about our terms, here. Using terms as defined in 
>> http://en.wikipedia.org/wiki/Task_scheduling, Ada.Execution_Time needs 
>> input from the task *dispatcher* -- the part of the kernel that suspends 
>> and resumes tasks.
> 
> Let's call it dispatcher. Time sharing needs some measure of consumed CPU
> time. My points stand:
> 
> 1. Time sharing has little to do with real-time systems.

What do you mean by "time sharing"? The classical mainframe system used 
interactively by many terminals? What on earth does that have to do with 
our discussion? Such a system of course must have concurrent tasks or 
processes in some form, but so what?

If by "time sharing algorithms" (below in your point 2) you mean what is 
usually called "task scheduling algorithms", where several tasks 
time-share the same processor by a task-switching (dispatching) 
mechanism, your point 1 is bizarre. Priority-scheduled task switching is 
the canonical architecture for real-time systems.

> 2. It would be extremely ill-advised to use Ada.Execution_Time instead of
> direct measures for an implementation of time sharing algorithms.

If by "direct measures" you mean the use of some external measuring 
device such as an oscilloscope or logic analyzer, such measures are 
available only externally, to the developers, not within the Ada program 
itself. The whole point of Ada.Execution_Time is that it is available to 
the Ada program itself, enabling run-time decisions based on the actual 
execution times of tasks.

> Real-time systems work with the real-time, they real-time intervals
> (durations) are of much minor interest. Execution time is of no interest,
> because a real-time system does not care to balance the CPU load.

I am made speechless (or should I say "typing-less"). If that is your 
view, there is no point in continuing this discussion because we do not 
agree on what a real-time program is.

>>>> You have
>>>> not given any arguments, based on the RM text, to support your position.
>>> I am not a language lawyer to interpret the RM texts. My argument was to
>>> common sense.
>> To me it seems that your argument is based on the difficulty (in your 
>> opinion) of implementing Ada.Execution_Time in some OSes such as MS 
>> Windows, if the RM word "time" is taken to mean real time.
>>
>> It is common sense that some OSes are not designed (or not well 
>> designed) for real-time systems. Even a good real-time OS may not 
>> support all real-time methodologies, for example scheduling algorithms 
>> that depend on actual execution times.
> 
> I disagree with almost everything here. To start with, comparing real-time
> clock services of Windows and of VxWorks, we would notice that Windows is
> far superior in both accuracy and precision.

So what? Real-time systems need determinism. The clock only has to be 
accurate enough.

If your tasks suffer arbitrary millisecond-scale suspensions or 
dispatching delays (as is rumored for Windows) a microsecond-level clock 
accuracy is no help.

> Yet Windows is a half-baked
> time-sharing OS, while VxWorks is one of the leading real-time OSes. Why is
> it so? Because real-time applications do not need clock much. They are
> real-time because their sources of time are *real*. These are hardware
> interrupts, while timer interrupts are of a much lesser interest.

Both are important. Many control systems are driven by timers that 
trigger periodic tasks. In my experience (admittedly limited), it is 
rare for sensors to generate periodic input streams on their own, they 
must usually be sampled by periodic reads. You are right, however, that 
some systems, such as automobile engine control units, have external 
triggers, such as shaft-rotation interrupts.

Anyway, your point has do to with the "time" that *activates* tasks, not 
with the measurement of task-specific execution times. So this is 
irrelevant.

> I don't
> care how much processor time my control loop takes so long it manages to
> write the outputs when the actuators expect them.

You should care, if the processor must also have time for some other 
tasks of lower priority, which are preempted by the control-loop task.

> Measuring the CPU time
> would bring me nothing. It is useless before the run, because it is not a
> proof that the deadlines will be met.

In some cases (simple code or extensive tests, deterministic processor) 
CPU-time measurements can be used to prove that deadlines are met. But 
of course static analysis of the worst-case execution time is better.

> It useless at run-time because there
> are easier and safer ways to detect faults.

If you mean "deadline missed" or "task overrun" faults, you are right 
that there are other detection methods. Still, Ada.Execution_Time may 
help to *anticipate*, and thus mitigate, such faults.

For example, assume that the computation in a control algorithm consists 
of two consecutive stages where the first stage processes the inputs 
into a state model and the second stage computes the control outputs 
from the state model. Using Ada.Execution_Time or 
Ada.Execution_Time.Timers the program could detect an unexpectedly high 
CPU usage in the first stage, and fall back to a simpler, faster 
algorithm in the second stage, to ensure that some control outputs are 
computed before the deadline.

But you are again ignoring other run-time uses of execution-time 
measurements, such as advanced scheduling algorithms.

>> Is your point that Ada.Execution_Time was accepted only because the ARG 
>> decided that the word "time" in RM D.14 should not be understood to mean 
>> real time? I doubt that very much... Surely such an unusual meaning of 
>> "time" should have been explained in the RM.
> 
> It is explained by its name: "execution time." Execution means not real,
> unreal time (:-)).

Nonsense. I spend some part of my time asleep, some time awake. Both 
"sleeping time" and "awake time" are (pieces of) real time. A task 
spends some of its time being executed, some of its time not being 
executed (waiting or ready).

>>> If that was the intent, then I really do not understand why CPU_Time was
>>> introduced in addition to Ada.Real_Time.Time / Time_Span.
>> Because (as I understand it) different processors/OSes have different 
>> mechanisms for measuring execution times and real times, and the 
>> mechanism most convenient for CPU_Time may use a different numerical 
>> type (range, scale, and precision) than the mechanisms and types used 
>> for Ada.Real_Time.Time, Time_Span, and Duration.
> 
> I see no single reason why this could happen. Obviously, if talking about a
> real-time system as you insist, the only possible choice for CPU_Time is
> Time_Span, because to be consistent with the interpretation you propose it
> must be derived from Ada.Real_Time clock.

I have only said that the sum of the CPU_Times of all tasks executing on 
the same processor should be close to the real elapsed time, since the 
CPU's time is shared between the tasks. This does not mean that 
Ada.Execution_Time.CPU_Time and Ada.Real_Time.Time must have a common 
time source, only that both time sources must approximate physical, real 
time.

> My point is that RM intentionally leaves it up to the implementation to
> choose a CPU_Time source independent on Ada.Real_Time.Clock. This why
> different range and precision come into consideration.

I agree. But in both cases the intent is to approximate physical, real 
time, not some "simulation time" where one "simulation second" could be 
one year of real time.

> Under some conditions (e.g. no task switching) an execution time interval
> could be numerically equal to a real time interval.

Yes! Therefore, under these conditions, CPU_Time (when converted to a 
Time_Span or Duration) does have a physical meaning. So we agree. At last.

And under the task dispatching model in RM D.2.1, these conditions can 
be extended to task switching scenarios with the result that the sum of 
the CPU_Times of the tasks (for one processor) will be numerically close 
to the elapsed real time interval.

> But in my view the execution time is not even a simulation time of some
> ideal (real) clock. It is a simulation time of some lax recurrent process,
> e.g. scheduling activity, of which frequency is not even considered
> constant.

You may well have this view, but I don't see that your view has anything 
to do with Ada.Execution_Time as defined in the Ada RM.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 2%]

* An Example for Ada.Execution_Time
@ 2010-12-27 18:26  7% anon
  2010-12-28  2:31  5% ` BrianG
  0 siblings, 1 reply; 200+ results
From: anon @ 2010-12-27 18:26 UTC (permalink / raw)


You ask for an example.

Here is an example for packages (Tested using MaRTE):
  Ada.Execution_Time         -- Defines Time type and main operations as
                             -- well as the primary Clock for this type

  Ada.Execution_Time.Timers  -- Links to Timers 


Altering this example one could use a number of timers to be set 
using different times. Or testing a number of algorithms using 
the timer.

Also, I do have a Real_Time non-Task version that this example was 
based on.


-------------------------------
-- Work.adb -- Main program

with Ada.Integer_Text_IO ;
with Ada.Text_IO ;
with Work_Algorithm ;         -- Contains worker algorithm
with Work_Execution_Time ;    -- Contains execution Timing routines

procedure Work is

  use Ada.Integer_Text_IO ;
  use Ada.Text_IO ;
  use Work_Execution_Time ; 

  Task_0 : Work_Task ;

begin -- Work
  Initialize ( Work_Algorithm'Access ) ;
  Task_0.Start ( False ) ;

  -- Prints results of Test

  New_Line ;
  Put ( "Event occured " ) ;
  Put ( Item => Counter, Width => 3 ) ;
  Put_Line ( " Times." ) ;
  New_Line ;

end Work ;

-------------------------------
-- Work_Algorithm.ads

procedure Work_Algorithm ;

-------------------------------
-- Work_Algorithm.adb

with Ada.Integer_Text_IO ;
with Ada.Text_IO ;

procedure Work_Algorithm is
    use Ada.Integer_Text_IO ;
    use Ada.Text_IO ;
  begin
    for Index in 0 .. 15 loop
      Put ( "Paused =>" ) ;
      Put ( Index ) ;
      New_Line ;
      delay 1.0 ;
    end loop ;
  end Work_Algorithm ;


-------------------------------
-- Work.Execution_Time.ads

with Ada.Execution_Time ;
with Ada.Real_Time ;

package Work_Execution_Time is

  type Algorithm_Type is access procedure ;

  task type Work_Task is
    entry Start ( Active : in Boolean ) ;
  end Work_Task ;


  Counter    : Natural ;

  procedure Initialize ( A : in Algorithm_Type ) ;

private 

  Algorithm  : Algorithm_Type ;

  Start_Time : Ada.Execution_Time.CPU_Time ;
  At_Time    : Ada.Execution_Time.CPU_Time ;
  In_Time    : Ada.Real_Time.Time_Span ;

end Work_Execution_Time ;

-------------------------------
-- Work_Execution_Time ;
with Ada.Integer_Text_IO ;
with Ada.Text_IO ;
with Ada.Execution_Time ;
with Ada.Execution_Time.Timers ;
with Ada.Real_Time ;
with Ada.Task_Identification ;

package body Work_Execution_Time is


    use Ada.Execution_Time ;
    use Ada.Real_Time ;
    use Timers ;

    package D_IO is new Ada.Text_IO.Fixed_IO ( Duration ) ;
    package S_IO is new Ada.Text_IO.Integer_IO
                                      ( Ada.Real_Time.Seconds_Count ) ;

  protected Handlers is
    -- Handler: Single Event
      procedure Handler_1 ( TM : in out Timer ) ;

    -- Handler: Multple Event
      procedure Handler_2 ( TM : in out Timer ) ;
  end Handlers ;



  task body Work_Task is

      use Ada.Task_Identification ;

    ID         : aliased Task_Id := Current_Task ;
    TM         : Timers.Timer ( ID'Access ) ;

    Cancelled  : Boolean := False ;

  begin
    Counter := 0 ;
    loop
      select
        Accept Start ( Active : in Boolean ) do
          if Active then
            Start_Time := Ada.Execution_Time.Clock ;
            At_Time := Start_Time + Milliseconds ( 5 ) ;
            Set_Handler ( TM, AT_Time, Handlers.Handler_2'Access ) ;
          else
            Start_Time := Ada.Execution_Time.Clock ;
            In_Time := Milliseconds ( 10 ) ;
            Set_Handler ( TM, In_Time, Handlers.Handler_2'Access ) ;
          end if ;

          Algorithm.all ;  -- Execute Test algorithm

          Timers.Cancel_Handler ( TM, Cancelled ) ;
        end Start ;
      or
        terminate ;
      end select ;
    end loop ;
  end Work_Task ;


  --
  -- Timer Event Routines
  --
  protected body Handlers is 

    -- Handler: Single Event

    procedure Handler_1 ( TM : in out Timer ) is

        Value     : Time_Span ;
        Cancelled : Boolean ;

      begin
        Value := Time_Remaining ( TM ) ;
        Ada.Text_IO.Put ( "Timing Event Occured at " ) ;
        D_IO.Put ( To_Duration ( Value ) ) ;
        Ada.Text_IO.New_Line ;
        Counter := Counter + 1 ;
        Cancel_Handler ( TM, Cancelled ) ;
      end Handler_1 ;

    -- Handler: Multple Event

    procedure Handler_2 ( TM : in out Timer ) is

        Value   : Time_Span ;

      begin
        Value := Time_Remaining ( TM ) ;
        Ada.Text_IO.Put ( "Timing Event Occured at " ) ;
        D_IO.Put ( To_Duration ( Value ) ) ;
        Ada.Text_IO.New_Line ;
        Counter := Counter + 1 ;

        Start_Time := Ada.Execution_Time.Clock ;
        In_Time := Ada.Real_Time.Milliseconds ( 10 ) ;
        Set_Handler ( TM, In_Time, Handlers.Handler_2'Access ) ;
      end Handler_2 ;

  end Handlers ;


  -- Initialize: Set Algorithm and Counter

  procedure Initialize ( A : in Algorithm_Type ) is
    begin
      Algorithm := A ;
      Counter := 0 ;
    end Initialize ;

end Work_Execution_Time ;




^ permalink raw reply	[relevance 7%]

* Re: Ada.Execution_Time
  2010-12-27 12:44  3%                                 ` Ada.Execution_Time Niklas Holsti
@ 2010-12-27 15:28  4%                                   ` Dmitry A. Kazakov
  2010-12-27 20:11  2%                                     ` Ada.Execution_Time Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-12-27 15:28 UTC (permalink / raw)


On Mon, 27 Dec 2010 14:44:53 +0200, Niklas Holsti wrote:

> Dmitry A. Kazakov wrote:
>> On Sat, 25 Dec 2010 13:31:27 +0200, Niklas Holsti wrote:
>> 
>>> Dmitry A. Kazakov wrote:
>>>> On Sat, 18 Dec 2010 23:20:20 +0200, Niklas Holsti wrote:
>>> ...
>>>>> The concept and measurement of "the execution time of a task" does
>>>>> become problematic in complex processors that have hardware 
>>>>> multi-threading and can run several tasks in more or less parallel
>>>>> fashion, without completely isolating the tasks from each other.
>>>> No, the concept is just fine,
>>> Fine for what? For schedulability analysis, fine for on-line scheduling,
>>> ... ?
>> 
>> Applicability of a concept is not what makes it wrong or right.
> 
> I think it does. This concept, "the execution time of a task", stands 
> for a number. A number is useless if it has no application in a 
> calculation.

Technically, CPU_Time is not a number in any sense. It is not a numeric Ada
type and it is not a model of a mathematical number (not even additive).

Anyway, the execution time can be used in calculations independently on
whether and how you could apply the results of such calculations.

You can add the height of your house to the distance to the Moon, the
interpretation is up to you.

>>> However, this is a side issue, since we are (or at least I am)
>>> discussing what the RM intends with Ada.Execution_Time, which must be
>>> read in the context of D.2.1, which assumes that there is a clearly
>>> defined set of "processors" and each processor executes exactly one
>>> task at a time.
>> 
>> Why?
> 
> Because RM D.14 uses terms defined in RM D.2.1, for example "executing".

These terms stay valid for non-real time systems.

>> Scheduling does not need Ada.Execution_Time,
> 
> The standard schedulers defined in the RM do no not need 
> Ada.Execution_Time but, as remarked earlier in this thread, one of the 
> purposes of Ada.Execution_Time is to support the implementation of 
> non-standard scheduling algorithms that may make on-line scheduling 
> decisions that depend on the actual execution times of tasks. For 
> example, scheduling based on "slack time".

Even if somebody liked to undergo such an adventure, he also could use
Elementary_Functions in the scheduler. That would not make the nature of
Elementary_Functions any different.

>> it is the Ada.Execution_Time implementation, which needs some
>> input from the scheduler.
> 
> We must be precise about our terms, here. Using terms as defined in 
> http://en.wikipedia.org/wiki/Task_scheduling, Ada.Execution_Time needs 
> input from the task *dispatcher* -- the part of the kernel that suspends 
> and resumes tasks.

Let's call it dispatcher. Time sharing needs some measure of consumed CPU
time. My points stand:

1. Time sharing has little to do with real-time systems.

2. It would be extremely ill-advised to use Ada.Execution_Time instead of
direct measures for an implementation of time sharing algorithms.

>> How do you explain that CPU_Time, a thing about time sharing, appears in
>> the real-time systems annex D?
> 
> You don't think that execution time is important for real-time systems?

Real-time systems work with the real-time, they real-time intervals
(durations) are of much minor interest. Execution time is of no interest,
because a real-time system does not care to balance the CPU load.

> In my view, CPU_Time is a measure of "real time", so its place in annex 
> D is natural. In your view, CPU_Time is not "real time", which should 
> make *you* surprised that it appears in annex D.

It does not surprise me, because there is no "time-sharing systems" annex,
or better it be "it is not what you think" or "if you think you need this,
your are wrong." There are some other Ada features we could move there.
(:-))

>>> You have
>>> not given any arguments, based on the RM text, to support your position.
>> 
>> I am not a language lawyer to interpret the RM texts. My argument was to
>> common sense.
> 
> To me it seems that your argument is based on the difficulty (in your 
> opinion) of implementing Ada.Execution_Time in some OSes such as MS 
> Windows, if the RM word "time" is taken to mean real time.
> 
> It is common sense that some OSes are not designed (or not well 
> designed) for real-time systems. Even a good real-time OS may not 
> support all real-time methodologies, for example scheduling algorithms 
> that depend on actual execution times.

I disagree with almost everything here. To start with, comparing real-time
clock services of Windows and of VxWorks, we would notice that Windows is
far superior in both accuracy and precision. Yet Windows is a half-baked
time-sharing OS, while VxWorks is one of the leading real-time OSes. Why is
it so? Because real-time applications do not need clock much. They are
real-time because their sources of time are *real*. These are hardware
interrupts, while timer interrupts are of a much lesser interest. I don't
care how much processor time my control loop takes so long it manages to
write the outputs when the actuators expect them. Measuring the CPU time
would bring me nothing. It is useless before the run, because it is not a
proof that the deadlines will be met. It useless at run-time because there
are easier and safer ways to detect faults.

>>>>>> I am not a language lawyer, but I bet that an implementation of 
>>>>>> Ada.Execution_Time.Split that ignores any CPU frequency changes
>>>>>> when summing up processor ticks consumed by the task would be
>>>>>> legal.
>>>>> Whether or not such an implementation is formally legal, that would
>>>>> require very perverse interpretations of the text in RM D.14.
>>>> RM D.14 defines CPU_Tick constant, of which physical equivalent (if
>>>> we tried to enforce your interpretation) is not constant for many
>>>> CPU/OS combinations.
>>> The behaviour of some CPU/OS is irrelevant to the intent of the RM.
>> 
>> Nope, one of the killer arguments ARG people deploy to reject most
>> reasonable AI's is: too difficult to implement on some obscure platform for
>> which Ada never existed and never will. (:-))
> 
> Apparently such arguments, if any were made in this case, were not valid 
> enough to prevent the addition of Ada.Execution_Time to the RM.

That is because ARG didn't intend to reject it! Somebody wanted it no
matter what (like interfaces, limited results, asserts, then, like, I am
afraid, if-operators now). The rest was minimizing the damage...

> Is your point that Ada.Execution_Time was accepted only because the ARG 
> decided that the word "time" in RM D.14 should not be understood to mean 
> real time? I doubt that very much... Surely such an unusual meaning of 
> "time" should have been explained in the RM.

It is explained by its name: "execution time." Execution means not real,
unreal time (:-)).

>>> As already said, an Ada implementation on such CPU/OS could
>>> use its own mechanisms for execution-time measurements.
>> 
>> Could or must? Does GNAT this?
> 
> I don't much care, it is irrelevant for understanding what the RM means. 
> Perhaps the next version of MS Windows will have better support for 
> measuring real task execution times; would that change the intent of the 
> RM? Of course not.

You suggested that Ada implementations would/could attempt to be consistent
with your interpretation of CPU_Time. But it seems that at least one of the
leading Ada vendors does not care. Is it a laziness on their side or maybe
you just expected too much?

>>> It seems evident to me that the text in D.14 must be interpreted using
>>> the concepts in D.2.1, "The Task Dispatching Model", which clearly
>>> specifies real-time points when a processor starts to execute a task and
>>> stops executing a task. To me, and I believe to most readers of the RM,
>>> the execution time of a task is the sum of these time slices, thus a
>>> physical, real time.
>> 
>> If that was the intent, then I really do not understand why CPU_Time was
>> introduced in addition to Ada.Real_Time.Time / Time_Span.
> 
> Because (as I understand it) different processors/OSes have different 
> mechanisms for measuring execution times and real times, and the 
> mechanism most convenient for CPU_Time may use a different numerical 
> type (range, scale, and precision) than the mechanisms and types used 
> for Ada.Real_Time.Time, Time_Span, and Duration.

I see no single reason why this could happen. Obviously, if talking about a
real-time system as you insist, the only possible choice for CPU_Time is
Time_Span, because to be consistent with the interpretation you propose it
must be derived from Ada.Real_Time clock.

My point is that RM intentionally leaves it up to the implementation to
choose a CPU_Time source independent on Ada.Real_Time.Clock. This why
different range and precision come into consideration.

>>> And you still have not defined what you mean by "simulation time", and
>>> how you come there from the RM text.
>> 
>> Simulation time is a model of real time a physical process might have under
>> certain conditions.
> 
> Thank you. But I still do not see how your definition could be applied 
> in this context, so we are back at the start of the post... :-)

Under some conditions (e.g. no task switching) an execution time interval
could be numerically equal to a real time interval.

But in my view the execution time is not even a simulation time of some
ideal (real) clock. It is a simulation time of some lax recurrent process,
e.g. scheduling activity, of which frequency is not even considered
constant. It can be any garbage, and it likely is.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 4%]

* Re: Ada.Execution_Time
  2010-12-26 10:25  5%                               ` Ada.Execution_Time Dmitry A. Kazakov
@ 2010-12-27 12:44  3%                                 ` Niklas Holsti
  2010-12-27 15:28  4%                                   ` Ada.Execution_Time Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: Niklas Holsti @ 2010-12-27 12:44 UTC (permalink / raw)


Dmitry A. Kazakov wrote:
> On Sat, 25 Dec 2010 13:31:27 +0200, Niklas Holsti wrote:
> 
>> Dmitry A. Kazakov wrote:
>>> On Sat, 18 Dec 2010 23:20:20 +0200, Niklas Holsti wrote:
>> ...
>>>> The concept and measurement of "the execution time of a task" does
>>>> become problematic in complex processors that have hardware 
>>>> multi-threading and can run several tasks in more or less parallel
>>>> fashion, without completely isolating the tasks from each other.
>>> No, the concept is just fine,
>> Fine for what? For schedulability analysis, fine for on-line scheduling,
>> ... ?
> 
> Applicability of a concept is not what makes it wrong or right.

I think it does. This concept, "the execution time of a task", stands 
for a number. A number is useless if it has no application in a 
calculation. I don't know of any other meaning of "wrongness" for a 
numerical concept.

>> However, this is a side issue, since we are (or at least I am)
>> discussing what the RM intends with Ada.Execution_Time, which must be
>> read in the context of D.2.1, which assumes that there is a clearly
>> defined set of "processors" and each processor executes exactly one
>> task at a time.
> 
> Why?

Because RM D.14 uses terms defined in RM D.2.1, for example "executing".

> Scheduling does not need Ada.Execution_Time,

The standard schedulers defined in the RM do no not need 
Ada.Execution_Time but, as remarked earlier in this thread, one of the 
purposes of Ada.Execution_Time is to support the implementation of 
non-standard scheduling algorithms that may make on-line scheduling 
decisions that depend on the actual execution times of tasks. For 
example, scheduling based on "slack time".

> it is the Ada.Execution_Time implementation, which needs some
> input from the scheduler.

We must be precise about our terms, here. Using terms as defined in 
http://en.wikipedia.org/wiki/Task_scheduling, Ada.Execution_Time needs 
input from the task *dispatcher* -- the part of the kernel that suspends 
and resumes tasks. It does not need input from the *scheduler*, which is 
the kernel part that selects the next task to be executed from among the 
ready tasks.

The term "dispatching" is defined differently in RM D.2.1 to mean the 
same as "scheduling" in the Wikipedia entry.

> How do you explain that CPU_Time, a thing about time sharing, appears in
> the real-time systems annex D?

You don't think that execution time is important for real-time systems?

In my view, CPU_Time is a measure of "real time", so its place in annex 
D is natural. In your view, CPU_Time is not "real time", which should 
make *you* surprised that it appears in annex D.

>> You have
>> not given any arguments, based on the RM text, to support your position.
> 
> I am not a language lawyer to interpret the RM texts. My argument was to
> common sense.

To me it seems that your argument is based on the difficulty (in your 
opinion) of implementing Ada.Execution_Time in some OSes such as MS 
Windows, if the RM word "time" is taken to mean real time.

It is common sense that some OSes are not designed (or not well 
designed) for real-time systems. Even a good real-time OS may not 
support all real-time methodologies, for example scheduling algorithms 
that depend on actual execution times.

>>>>> I am not a language lawyer, but I bet that an implementation of 
>>>>> Ada.Execution_Time.Split that ignores any CPU frequency changes
>>>>> when summing up processor ticks consumed by the task would be
>>>>> legal.
>>>> Whether or not such an implementation is formally legal, that would
>>>> require very perverse interpretations of the text in RM D.14.
>>> RM D.14 defines CPU_Tick constant, of which physical equivalent (if
>>> we tried to enforce your interpretation) is not constant for many
>>> CPU/OS combinations.
>> The behaviour of some CPU/OS is irrelevant to the intent of the RM.
> 
> Nope, one of the killer arguments ARG people deploy to reject most
> reasonable AI's is: too difficult to implement on some obscure platform for
> which Ada never existed and never will. (:-))

Apparently such arguments, if any were made in this case, were not valid 
enough to prevent the addition of Ada.Execution_Time to the RM.

Is your point that Ada.Execution_Time was accepted only because the ARG 
decided that the word "time" in RM D.14 should not be understood to mean 
real time? I doubt that very much... Surely such an unusual meaning of 
"time" should have been explained in the RM.

>> As already said, an Ada implementation on such CPU/OS could
>> use its own mechanisms for execution-time measurements.
> 
> Could or must? Does GNAT this?

I don't much care, it is irrelevant for understanding what the RM means. 
Perhaps the next version of MS Windows will have better support for 
measuring real task execution times; would that change the intent of the 
RM? Of course not.

>> It seems evident to me that the text in D.14 must be interpreted using
>> the concepts in D.2.1, "The Task Dispatching Model", which clearly
>> specifies real-time points when a processor starts to execute a task and
>> stops executing a task. To me, and I believe to most readers of the RM,
>> the execution time of a task is the sum of these time slices, thus a
>> physical, real time.
> 
> If that was the intent, then I really do not understand why CPU_Time was
> introduced in addition to Ada.Real_Time.Time / Time_Span.

Because (as I understand it) different processors/OSes have different 
mechanisms for measuring execution times and real times, and the 
mechanism most convenient for CPU_Time may use a different numerical 
type (range, scale, and precision) than the mechanisms and types used 
for Ada.Real_Time.Time, Time_Span, and Duration. This is evident in the 
different minimum ranges and precisions defined in the RM for these 
types. Randy remarked on this earlier in this thread.

>> And you still have not defined what you mean by "simulation time", and
>> how you come there from the RM text.
> 
> Simulation time is a model of real time a physical process might have under
> certain conditions.

Thank you. But I still do not see how your definition could be applied 
in this context, so we are back at the start of the post... :-)

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 3%]

* Task execution time test
@ 2010-12-26 10:25  6% Dmitry A. Kazakov
    0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-12-26 10:25 UTC (permalink / raw)


Here is a small test for task execution time.

Five worker tasks are used to generate background CPU load. When the
measured task enters delay 0.1ms (on a system where delay is non-busy) it
should lose the CPU prematurely.

Under at least some Windows systems the test might fail because Windows
performance counters are CPU quants 1ms or 10ms, depending on settings.

Under VxWorks the test may fail because real-time clock there is driven by
the timer interrupts, so it is impossible to have non-busy wait for 0.1ms.

(I cannot say anything about Linux, because I never used it for RT
applications, maybe other people could comment)

----------------------------------------------------
with Ada.Execution_Time;  use Ada.Execution_Time;
with Ada.Real_Time;       use Ada.Real_Time;
with Ada.Text_IO;         use Ada.Text_IO;

with Ada.Numerics.Elementary_Functions;

procedure Executuion_Time is
   task type Measured;
   task body Measured is
      Count    : Seconds_Count;
      Fraction : Time_Span;
   begin
      for I in 1..1_000 loop
         delay 0.000_1;
      end loop;
      Split (Ada.Execution_Time.Clock, Count, Fraction);
      Put_Line
      (  "Seconds" & Seconds_Count'Image (Count) &
         " Fraction" & Duration'Image (To_Duration (Fraction))
      );
   end Measured;

   task type Worker; -- Used to generate CPU load
   task body Worker is
      use Ada.Numerics.Elementary_Functions;
      X : Float;
   begin
      for I in Positive'Range loop
         X := sin (Float (I));
      end loop;
   end Worker;
   
begin
   delay 0.1; -- This might be needed for some buggy versions of GNAT
   declare
      Workers : array (1..5) of Worker;
      Test    : Measured;
   begin
      null;
   end;
end Executuion_Time;
-----------------------------------------------------
On my Windows XP SP3 the test yields 0-0.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  @ 2010-12-26 10:25  5%                               ` Dmitry A. Kazakov
  2010-12-27 12:44  3%                                 ` Ada.Execution_Time Niklas Holsti
    1 sibling, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-12-26 10:25 UTC (permalink / raw)


On Sat, 25 Dec 2010 13:31:27 +0200, Niklas Holsti wrote:

> Dmitry A. Kazakov wrote:
>> On Sat, 18 Dec 2010 23:20:20 +0200, Niklas Holsti wrote:
> ...
>>> The concept and measurement of "the execution time of a task" does
>>> become problematic in complex processors that have hardware 
>>> multi-threading and can run several tasks in more or less parallel
>>> fashion, without completely isolating the tasks from each other.
>> 
>> No, the concept is just fine,
> 
> Fine for what? For schedulability analysis, fine for on-line scheduling,
> ... ?

Applicability of a concept is not what makes it wrong or right.

> However, this is a side issue, since we are (or at least I am)
> discussing what the RM intends with Ada.Execution_Time, which must be
> read in the context of D.2.1, which assumes that there is a clearly
> defined set of "processors" and each processor executes exactly one
> task at a time.

Why? Scheduling does not need Ada.Execution_Time, it is the
Ada.Execution_Time implementation, which needs some input from the
scheduler.

How do you explain that CPU_Time, a thing about time sharing, appears in
the real-time systems annex D?

> You have
> not given any arguments, based on the RM text, to support your position.

I am not a language lawyer to interpret the RM texts. My argument was to
common sense.

>>>> I am not a language lawyer, but I bet that an implementation of 
>>>> Ada.Execution_Time.Split that ignores any CPU frequency changes
>>>> when summing up processor ticks consumed by the task would be
>>>> legal.
>>> Whether or not such an implementation is formally legal, that would
>>> require very perverse interpretations of the text in RM D.14.
>> 
>> RM D.14 defines CPU_Tick constant, of which physical equivalent (if
>> we tried to enforce your interpretation) is not constant for many
>> CPU/OS combinations.
> 
> The behaviour of some CPU/OS is irrelevant to the intent of the RM.

Nope, one of the killer arguments ARG people deploy to reject most
reasonable AI's is: too difficult to implement on some obscure platform for
which Ada never existed and never will. (:-))

> As 
> already said, an Ada implementation on such CPU/OS could use its own 
> mechanisms for execution-time measurements.

Could or must? Does GNAT this?

>> On a such platform the implementation would be as perverse as RM D.14
>> is. But the perversion is only because of the interpretation.
> 
> Bah. I think that when RM D.14 says "time", it really means time. You
> think it means something else, perhaps a CPU cycle count. I think the 
> burden of proof is on you.
> 
> It seems evident to me that the text in D.14 must be interpreted using
> the concepts in D.2.1, "The Task Dispatching Model", which clearly
> specifies real-time points when a processor starts to execute a task and
> stops executing a task. To me, and I believe to most readers of the RM,
> the execution time of a task is the sum of these time slices, thus a
> physical, real time.

If that was the intent, then I really do not understand why CPU_Time was
introduced in addition to Ada.Real_Time.Time / Time_Span.

> And you still have not defined what you mean by "simulation time", and
> how you come there from the RM text.

Simulation time is a model of real time a physical process might have under
certain conditions.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  2010-12-22 14:30  6%                 ` Ada.Execution_Time anon
@ 2010-12-22 20:09  4%                   ` BrianG
  0 siblings, 0 replies; 200+ results
From: BrianG @ 2010-12-22 20:09 UTC (permalink / raw)


anon@att.net wrote:
> In <iemhm8$4up$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>> anon@att.net wrote:
>> I have no problem with what Execution_Time does (as evidenced by the 
>> fact that I asked a question about its use) - it measures exactly what I 
>> want, an estimate of the CPU time used by a task.  My problem is with 
>> the way it is defined - it provides, by itself, no "value" of that that 
>> a using program can make use of to print or calculate (i.e. you also 
>> need Real_Time for that, which is silly - and I disagree that that is 
>> necessarily required in any case - my program didn't need it otherwise).
>> --BrianG
> There has been many third party versions of this package over the years 
> and most of them included a Linux version. The Windows is specific to GNAT. 
> And it just like GNAT the Windows version is not complete either.
My comments have been about the RM-defined package and its lack of 
usability (if that wasn't already clear).  What may or may not be 
provided by implementation-specific packages is irrelevant.

> 
> For Execution_Time there are three package. GNAT has 
>   Ada.Execution_Time                    for both Linux-MaRTE and Windows
>   Ada.Execution_Time.Timers             only for Linux-MaRTE
>   Ada.Execution_Time.Group_Budgets      Unimplemented Yet
> 
When you say "GNAT" here you should probably specify what version you 
mean.  I haven't looked in this area, but I was under the impression 
that GNAT has implemented all of Ada'05 for quite a while now (in Pro; 
maybe it has not yet all reached GCC or GPL releases?).

> 
> 
> In using the Linux-MaRTE version ( 2 packages ) 
>   Ada.Execution_Time 
>   Ada.Execution_Time.Timers 
See below.
> 
> Of course in this example you could use ( Note: they are fully implemented )
>   Ada.Real_Time
>   Ada.Real_Time.Timing_Events
So, instead of using a functionality already provided (with a slight 
kludgy issue), I should implement it entirely myself?  I still don't see 
how this could get me CPU_Time (even a "simulation" value).

> 
> 
> An algorithm comparison program might look like:
> 
> with Ada.Execution_Time ;
> with Ada.Execution_Time.Timers ;
Given the below program, please add some of the missing details to show 
how this can be useful without also "with Ada.Real_Time".  Neither 
Execution_Time or Execution_Time.Timers provides any value that can be 
used directly.

> 
> procedure Compare_Algorithm is
> 
>     task type Algorithm_1 is
>       use Ada.Execution_Time.Timers ;
>     begin
>       begin
>         Set_Handler ( ... ) ; -- start timer
>         Algorithm_1 ;
>         Time_Remaining ( ... ) ; -- sample timer
>       end ;
>       Cancel_Handler ( ... ) ; release timer
>     end ;    
> 
>     task type Algorithm_2 is
>       use Ada.Execution_Time.Timers ;
>     begin
>       begin
>         Set_Handler ( ... ) ; -- start timer
>         Algorithm_2 ;
>         Time_Remaining ( ... ) ; -- sample timer
>       end ;
>       Cancel_Handler ( ... ) ; release timer
>     end ;    
> 
>   use Ada.Execution_Time ;
> 
> begin
>   -- Start tasks
>   -- wait until all tasks finish
>   -- compare times using Execution_Time
Provide details here (line above and line below)- without relying on 
CPU_Time or Time_Span, which are both private.
>   -- Print summary of comparison
> end ;
> 
> 
--BrianG



^ permalink raw reply	[relevance 4%]

* Re: Ada.Execution_Time
  @ 2010-12-22 14:30  6%                 ` anon
  2010-12-22 20:09  4%                   ` Ada.Execution_Time BrianG
  0 siblings, 1 reply; 200+ results
From: anon @ 2010-12-22 14:30 UTC (permalink / raw)


In <iemhm8$4up$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>anon@att.net wrote:
>> In <iejsu9$lct$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>>> anon@att.net wrote:
>>>> In <ie91co$cko$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>>>>> Georg Bauhaus wrote:
>>>>>> On 12/12/10 10:59 PM, BrianG wrote:
>>> ....
>> 
>> Kind of funny you cutting down "TOP" which can be found on most Linux 
>> boxes  Which allow anyone with the CPU options turn on to see both the 
>> Real_Time and CPU_Time.
>Please provide any comment I made for/against "top".  Since my original 
>question was based on Windows and I've stated that my (current) Linux 
>doesn't support this package, that seems unlikely (even if I didn't 
>trust my memory).
>> 
>....
>> Note: Not sure of the name for the Windows version of Linux's top.
>There is (that I know of) no real equiv to "top" - as in a command-line 
>program.  The equiv to GNOME's "System Monitor" (for example - a gui 
>program) would be Task Manager (and I made no comment about that either).
>> 
>....
>> 
>> How to you think these or any other web hosting company could measure the 
>> complete system resources without measuring the CPU Execution Time on a 
>> given user or application! In Ada, the routines can now use the package 
>> called "Ada.CPU_Execution_Time".
>> 
>I have no problem with what Execution_Time does (as evidenced by the 
>fact that I asked a question about its use) - it measures exactly what I 
>want, an estimate of the CPU time used by a task.  My problem is with 
>the way it is defined - it provides, by itself, no "value" of that that 
>a using program can make use of to print or calculate (i.e. you also 
>need Real_Time for that, which is silly - and I disagree that that is 
>necessarily required in any case - my program didn't need it otherwise).
>> 
>--BrianG
There has been many third party versions of this package over the years 
and most of them included a Linux version. The Windows is specific to GNAT. 
And it just like GNAT the Windows version is not complete either.

For Execution_Time there are three package. GNAT has 
  Ada.Execution_Time                    for both Linux-MaRTE and Windows
  Ada.Execution_Time.Timers             only for Linux-MaRTE
  Ada.Execution_Time.Group_Budgets      Unimplemented Yet



In using the Linux-MaRTE version ( 2 packages ) 
  Ada.Execution_Time 
  Ada.Execution_Time.Timers 

Of course in this example you could use ( Note: they are fully implemented )
  Ada.Real_Time
  Ada.Real_Time.Timing_Events


An algorithm comparison program might look like:

with Ada.Execution_Time ;
with Ada.Execution_Time.Timers ;

procedure Compare_Algorithm is

    task type Algorithm_1 is
      use Ada.Execution_Time.Timers ;
    begin
      begin
        Set_Handler ( ... ) ; -- start timer
        Algorithm_1 ;
        Time_Remaining ( ... ) ; -- sample timer
      end ;
      Cancel_Handler ( ... ) ; release timer
    end ;    

    task type Algorithm_2 is
      use Ada.Execution_Time.Timers ;
    begin
      begin
        Set_Handler ( ... ) ; -- start timer
        Algorithm_2 ;
        Time_Remaining ( ... ) ; -- sample timer
      end ;
      Cancel_Handler ( ... ) ; release timer
    end ;    

  use Ada.Execution_Time ;

begin
  -- Start tasks
  -- wait until all tasks finish
  -- compare times using Execution_Time
  -- Print summary of comparison
end ;





^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  2010-12-19  3:07  0%           ` Ada.Execution_Time BrianG
  2010-12-19  4:01  8%             ` Ada.Execution_Time Vinzent Hoefler
@ 2010-12-19 22:54  0%             ` anon
    1 sibling, 1 reply; 200+ results
From: anon @ 2010-12-19 22:54 UTC (permalink / raw)


In <iejsu9$lct$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>anon@att.net wrote:
>> In <ie91co$cko$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>>> Georg Bauhaus wrote:
>>>> On 12/12/10 10:59 PM, BrianG wrote:
>....
>[Lots of meaningless comments deleted.]
>> For the average Ada programmer, its another Ada package that most will 
>> never use because they will just use Ada.Real_Time.  
>[etc.]
>>  In some cases the Ada.Execution_Time
>> package can replace the Ada.Real_Time with only altering the with/use 
>> statements.
>If you mean that they both define a Clock and a Split, maybe.  If you mean
>any program that actually does anything, that's not possible.  That was my
>original comment:  Execution_Time does not provide any types/operations
>useful, without also 'with'ing Real_Time.
>> 
>[etc.]
>(Don't know why I bother w/ this msg.)


Kind of funny you cutting down "TOP" which can be found on most Linux 
boxes  Which allow anyone with the CPU options turn on to see both the 
Real_Time and CPU_Time.

An Example: Just use you your favorite music/video player and play a 2 
min song.  Real_Time will show the 2 min for the song and the 1 to 3 
seconds for the CPU_Time. 

And I know one professor that is now station in Poland that did enjoy 
giving his student assignment to decrease the amount of CPU execution 
time that an algorithm used. Which meant a student normally had to 
rewrite the algorithm. His student just loved him for that!


Note: Not sure of the name for the Windows version of Linux's top.


As for "Pragmas" that may effect the "CPU Execution Time. 
Three may pragmas that have been disabled in GNAT and they are:

    pragma Optimize     :  Gnat uses gcc command line -O(0,1,2,3.4).
                           Which does effect compiler language 
                           translation.

    pragma System_Name  :  Gnat uses default or gcc command line to 
    pragma Storage_Unit :  determine target. Target processor and its 
                           normal data size can effect CPU time.



And for web Servers:

Check with any main web hosting for the "Terms" or "Agreement".  In 
the document you will see a paragraph that states the web site excess 
from 10 to 25% of the resources will be shutdown.

Examples: 

    From Host: http://www.micfo.com/agreement

    6 SERVER RESOURCE USAGE


        The Client agrees to utilize "micfo's" Server Resources as set 
        out in clause 6.2.1, 6.2,2:

    6.2.1
        Shared Hosting; 7% of the CPU in any given twenty two (22) 
        Business Days.
    6.2.2
        Reseller Hosting; 10% of the CPU in any given twenty two 
        (22) Business Days.


        Also: from Host: http://www.hostgator.com/tos/tos.php

        User may not: 

        1) Use 25% or more of system resources for longer then 90 
           seconds. There are numerous activities that could cause 
           such problems; these include: CGI scripts, FTP, PHP, 
           HTTP, etc.

       12) Only use https protocol when necessary; encrypting and 
           decrypting communications is noticeably more CPU-intensive 
           than unencrypted communications.


How to you think these or any other web hosting company could measure the 
complete system resources without measuring the CPU Execution Time on a 
given user or application! In Ada, the routines can now use the package 
called "Ada.CPU_Execution_Time".





^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-19  4:01  8%             ` Ada.Execution_Time Vinzent Hoefler
  2010-12-19 11:00  7%               ` Ada.Execution_Time Niklas Holsti
@ 2010-12-19 12:27  6%               ` Dmitry A. Kazakov
  1 sibling, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2010-12-19 12:27 UTC (permalink / raw)


On Sun, 19 Dec 2010 05:01:22 +0100, Vinzent Hoefler wrote:

> And well, if you're ranting about CPU_Time, Real_Time.Time_Span is not much
> better. It's a pain in the ass to convert an Ada.Real.Time_Span to another
> type to interface with OS-specific time types (like time_t) if you're opting
> for speed, portability and accuracy.

Well, speaking from my experience, the OS-specific time types are hardly
usable because of the OS services working with these types. The problem is
not conversion, but the implementations, which *do* use these [broken]
services. They might have a catastrophic accuracy. For example, under
VxWorks we had to replace the AdaCore implementation of Ada.Real_Time with
our own implementation. This stuff is inherently non-portable.

But the interface of Ada.Real_Time is portable, so I see absolutely no
point in replacing it with something OS-specific. It won't get either
portability or accuracy.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  2010-12-19  4:01  8%             ` Ada.Execution_Time Vinzent Hoefler
@ 2010-12-19 11:00  7%               ` Niklas Holsti
  2010-12-19 12:27  6%               ` Ada.Execution_Time Dmitry A. Kazakov
  1 sibling, 0 replies; 200+ results
From: Niklas Holsti @ 2010-12-19 11:00 UTC (permalink / raw)


Vinzent Hoefler wrote:
> BrianG wrote:
> 
>> If you mean that they both define a Clock and a Split, maybe.  If you 
>> meanany program that actually does anything, that's not possible.
>> That was my original comment:  Execution_Time does not provide any
>>types/operations useful, without also 'with'ing Real_Time.
> 
> Yes, but so what? The intention of Ada.Execution_Time wasn't to provide the
> user with means to instrument the software and to Text_IO some mostly
> meaningless values (any decent profiler can do that for you), but rather a
> way to implement user-defined schedulers based on actual CPU usage.

That is also my understanding of the intention. Moreover, since task 
scheduling for real-time systems unavoidably deals both with execution 
times and with real times, I think it is natural that both 
Ada.Execution_Time and Ada.Real_Time are required.

> And well, if you're ranting about CPU_Time, Real_Time.Time_Span is not much
> better. It's a pain in the ass to convert an Ada.Real.Time_Span to another
> type to interface with OS-specific time types (like time_t) if you're 
> opting for speed, portability and accuracy.

If your target type is OS-specific, it seems harsh to require full 
portability of the conversion.

> BTW, has anyone any better ideas to convert TimeSpan into a record 
> containing seconds and nanoseconds than this:

I may not have better ideas, but I do have some comments on your code.

>    function To_Interval (TS : in Ada.Real_Time.Time_Span)
>                          return ASAAC_Types.TimeInterval is

The following are constants independent of the parameters:

>       Nanos_Per_Sec : constant                         := 1_000_000_000.0;
>       One_Second    : constant Ada.Real_Time.Time_Span :=
>                         Ada.Real_Time.Milliseconds (1000);

(Why not ... := Ada.Real_Time.Seconds (1) ?)

>       Max_Interval  : constant Ada.Real_Time.Time_Span :=
>                         Integer (ASAAC_Types.Second'Last) * One_Second;

... so I would move the above declarations into the surrounding package, 
at least for One_Second and Max_Interval. Of course a compiler might do 
that optimization in the code, too. (By the way, Max_Interval is a bit 
less than the largest value of TimeInterval, since the above expression 
has no NSec part.)

>       Seconds       : ASAAC_Types.Second;
>       Nano_Seconds  : ASAAC_Types.Nanosec;
>    begin
>       declare
>          Sub_Seconds : Ada.Real_Time.Time_Span;
>       begin

The following tests for ranges seem unavoidable in any conversion 
between types defined by different sources. I don't see how 
Ada.Real_Time can be blamed for this.  Of course I cannot judge if the 
result (saturation at 'Last or 'First) is right for your application. As 
you say, there are potential overflow problems, already in the 
computation of Max_Interval above.

>          if TS >= Max_Interval then
>             Seconds      := ASAAC_Types.Second'Last;
>             Nano_Seconds := ASAAC_Types.Nanosec'Last;

An alternative approach to the over-range condition TS >= Max_Interval 
is to make the definition of the application-specific type 
ASAAC_Types.Second depend on the actual range of Ada.Real_Time.Time_Span 
so that over-range becomes impossible. Unfortunately I don't see how 
this could be done portably by static expressions in the declaration of 
ASAAC_Types.Second, so it would have to be a subtype declaration with an 
upper bound of To_Duration(Time_Span_Last)-1.0. This raises 
Constraint_Error at elaboration if the base type is too narrow.

>          elsif TS < Ada.Real_Time.Time_Span_Zero then
>             Seconds      := ASAAC_Types.Second'First;
>             Nano_Seconds := ASAAC_Types.Nanosec'First;

The above under-range test seems to be forced by the fact that 
ASAAC_Types.TimeInterval is unable to represent negative time intervals, 
  while Ada.Real_Time.Time_Span can do that. This problem is hardly a 
shortcoming in Ada.Real_Time.

>          else
>             Seconds      := ASAAC_Types.Second (TS / One_Second);
>             Sub_Seconds  := TS - (Integer (Seconds) * One_Second);
>             Nano_Seconds :=
>               ASAAC_Types.Nanosec
>                 (Nanos_Per_Sec * Ada.Real_Time.To_Duration (Sub_Seconds));

An alternative method converts the whole TS to Duration and then 
extracts the seconds and nanoseconds:

    TS_Dur : Duration;

    TS_Dur := To_Duration (TS);
    Seconds := ASAAC_Types.Second (TS_Dur - 0.5);
    Nano_Seconds := ASAAC_Types.Nanosec (
       Nanos_Per_Sec * (TS_Dur - Duration (Seconds)));

This, too, risks overflow in the multiplication, since the guaranteed 
range of Duration only extends to 86_400. Moreover, using Duration may 
lose precision (see below).

>          end if;
>       end;
> 
>       return
>         ASAAC_Types.TimeInterval'(Sec  => Seconds,
>                                   NSec => Nano_Seconds);
>    end To_Interval;
> 
> The solution I came up with here generally works, but suffers some 
> potential overflow problems

I think they are unavoidable unless you take care to make the range of 
the application-defined types (ASAAC_Types) depend on the range of the 
implementations of the standard types and also do the multiplication in 
some type with sufficient range, that you define.

> and doesn't look very efficient to me (although that'a minor
> problem given the context it's usually used in).

Apart from the definition of the constants (which can be moved out of 
the function), and the range checks (which depend on the application 
types in ASAAC_Types), the real conversion consists of a division, a 
subtraction, two multiplications and one call of To_Duration. This does 
not seem excessive to me, considering the nature of that target type. 
The alternative method that starts by converting all of TS to Duration 
avoids the division.

Still, this example suggests that Ada.Real_Time perhaps should provide a 
Split operation that divides a Time_Span into an integer number of 
Seconds and a sub-second Duration.

A problem that you don't mention is that the use of Duration may cause 
loss of precision. Duration'Small may be as large as 20 milliseconds (RM 
9.6(27)), although at most 100 microseconds are advised (RM 9.6(30)), 
while the Time_Span resolution must be 20 microseconds or better (RM 
D.8(30)). Perhaps Annex D should require better Duration resolution?

Loss of precision could be avoided by doing the multiplication in 
Time_Span instead of in Duration:

    Nano_Seconds := ASAAC_Types.Nanosec (
       To_Duration (Nanos_Per_Sec * Sub_Seconds));

but the overflow risk is perhaps larger, since Time_Span_Last may not be 
larger than 3600 (RM D.8(31)).

I have met with similar tricky problems in conversions between types of 
different origins in other contexts, too. I don't think that these 
problems mean that Ada.Real_Time is defective.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 7%]

* Re: Ada.Execution_Time
  2010-12-19  3:07  0%           ` Ada.Execution_Time BrianG
@ 2010-12-19  4:01  8%             ` Vinzent Hoefler
  2010-12-19 11:00  7%               ` Ada.Execution_Time Niklas Holsti
  2010-12-19 12:27  6%               ` Ada.Execution_Time Dmitry A. Kazakov
  2010-12-19 22:54  0%             ` Ada.Execution_Time anon
  1 sibling, 2 replies; 200+ results
From: Vinzent Hoefler @ 2010-12-19  4:01 UTC (permalink / raw)


BrianG wrote:

> If you mean that they both define a Clock and a Split, maybe.  If you mean
> any program that actually does anything, that's not possible.  That was my
> original comment:  Execution_Time does not provide any types/operations
> useful, without also 'with'ing Real_Time.

Yes, but so what? The intention of Ada.Execution_Time wasn't to provide the
user with means to instrument the software and to Text_IO some mostly
meaningless values (any decent profiler can do that for you), but rather a
way to implement user-defined schedulers based on actual CPU usage. You may
want to take a look at the child packages Timers and Group_Budget to see the
intended usage.

And well, if you're ranting about CPU_Time, Real_Time.Time_Span is not much
better. It's a pain in the ass to convert an Ada.Real.Time_Span to another
type to interface with OS-specific time types (like time_t) if you're opting
for speed, portability and accuracy.

BTW, has anyone any better ideas to convert TimeSpan into a record containing
seconds and nanoseconds than this:

    function To_Interval (TS : in Ada.Real_Time.Time_Span)
                          return ASAAC_Types.TimeInterval is
       Nanos_Per_Sec : constant                         := 1_000_000_000.0;
       One_Second    : constant Ada.Real_Time.Time_Span :=
                         Ada.Real_Time.Milliseconds (1000);
       Max_Interval  : constant Ada.Real_Time.Time_Span :=
                         Integer (ASAAC_Types.Second'Last) * One_Second;
       Seconds       : ASAAC_Types.Second;
       Nano_Seconds  : ASAAC_Types.Nanosec;
    begin
       declare
          Sub_Seconds : Ada.Real_Time.Time_Span;
       begin
          if TS >= Max_Interval then
             Seconds      := ASAAC_Types.Second'Last;
             Nano_Seconds := ASAAC_Types.Nanosec'Last;
          elsif TS < Ada.Real_Time.Time_Span_Zero then
             Seconds      := ASAAC_Types.Second'First;
             Nano_Seconds := ASAAC_Types.Nanosec'First;
          else
             Seconds      := ASAAC_Types.Second (TS / One_Second);
             Sub_Seconds  := TS - (Integer (Seconds) * One_Second);
             Nano_Seconds :=
               ASAAC_Types.Nanosec
                 (Nanos_Per_Sec * Ada.Real_Time.To_Duration (Sub_Seconds));
          end if;
       end;

       return
         ASAAC_Types.TimeInterval'(Sec  => Seconds,
                                   NSec => Nano_Seconds);
    end To_Interval;

The solution I came up with here generally works, but suffers some potential
overflow problems and doesn't look very efficient to me (although that'a minor
problem given the context it's usually used in).


Vinzent.

-- 
You know, we're sitting on four million pounds of fuel, one nuclear weapon,
and a thing that has 270,000 moving parts built by the lowest bidder.
Makes you feel good, doesn't it?
   --  Rockhound, "Armageddon"



^ permalink raw reply	[relevance 8%]

* Re: Ada.Execution_Time
  2010-12-17  8:59  6%         ` Ada.Execution_Time anon
@ 2010-12-19  3:07  0%           ` BrianG
  2010-12-19  4:01  8%             ` Ada.Execution_Time Vinzent Hoefler
  2010-12-19 22:54  0%             ` Ada.Execution_Time anon
  0 siblings, 2 replies; 200+ results
From: BrianG @ 2010-12-19  3:07 UTC (permalink / raw)


anon@att.net wrote:
> In <ie91co$cko$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>> Georg Bauhaus wrote:
>>> On 12/12/10 10:59 PM, BrianG wrote:
...
[Lots of meaningless comments deleted.]
> For the average Ada programmer, its another Ada package that most will 
> never use because they will just use Ada.Real_Time.  
[etc.]
>  In some cases the Ada.Execution_Time
> package can replace the Ada.Real_Time with only altering the with/use 
> statements.
If you mean that they both define a Clock and a Split, maybe.  If you mean
any program that actually does anything, that's not possible.  That was my
original comment:  Execution_Time does not provide any types/operations
useful, without also 'with'ing Real_Time.
> 
[etc.]
(Don't know why I bother w/ this msg.)



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-15  0:16  5%       ` Ada.Execution_Time BrianG
  2010-12-15 19:17  6%         ` Ada.Execution_Time jpwoodruff
  2010-12-15 22:05  5%         ` Ada.Execution_Time Randy Brukardt
@ 2010-12-17  8:59  6%         ` anon
  2010-12-19  3:07  0%           ` Ada.Execution_Time BrianG
  2 siblings, 1 reply; 200+ results
From: anon @ 2010-12-17  8:59 UTC (permalink / raw)


In <ie91co$cko$1@news.eternal-september.org>, BrianG <briang000@gmail.com> writes:
>Georg Bauhaus wrote:
>> On 12/12/10 10:59 PM, BrianG wrote:
>> 
>> 
>>> But my question still remains: What's the intended use of 
>>> Ada.Execution_Time? Is there an intended use where its content 
>>> (CPU_Time, Seconds_Count and Time_Span, "+", "<", etc.) is useful?
>> 
>> I think that your original posting mentions a use that is quite
>> consistent with what the rationale says: each task has its own time.
>> Points in time objects can be split into values suitable for
>> arithmetic, using Time_Span objects.  Then, from the result of
>> arithmetic, produce an object suitable for print, as desired.
>> 
>> 
>> While this seems like having to write a bit much,
>> it makes things explicit, like Ada forces one to be
>> in many cases.   That' how I explain the series of
>> steps to myself.
>> 
>> Isn't it just like "null;" being required to express
>> the null statement?  It seems to me to be a logical
>> consequence of requiring that intents must be stated
>> explicitly.
>> 
>I have no problem with verbosity or explicitness, and that's not what I 
>was asking about.
>
>My problem is that what is provided in the package in question does not 
>provide any "values suitable for arithmetic" or provide "an object 
>suitable for print" (unless all you care about is the number of whole 
>seconds with no information about the (required) fraction, which seems 
>rather limiting).  Time_Span is a private type, defined in another 
>package.  If all I want is CPU_Time (in some form), why do I need 
>Ada.Real_Time?  Also, why are "+" and "-" provided as they are defined? 
>  (And why Time_Span?  I thought that was the difference between two 
>times, not the fractional part of time.)
>
>Given the rest of this thread, I would guess my answer is "No, no one 
>actually uses Ada.Execution_Time".
>
>--BrianG

Ada.Execution_Time is use for performance and reliability monitoring of the 
cpu resource aka a MCP (Tron). The control program can monitor the cpu 
usage of each task and decide which task needs to give up the CPU for the 
next task. 

With a shared server system it monitors which web site is over using the 
cpu and shutdown that web site temporality or permanent. One example too 
many Java Servlet on a web site.

For Ada 2012, it will mostly like will be use in the Ada runtime to balance 
the load for an Ada partition on multiple cores. Aka job scheduler for multiple 
tasks on multiple CPUs.

For the average Ada programmer, its another Ada package that most will 
never use because they will just use Ada.Real_Time.  The only problem 
is that Ada.Real_Time is an accumulation of times. A small list of these 
times includes VS swapping, IO processing, any cpu handled interrupts, 
as well as times for the task to execute as well as time the task sleeps 
while other tasks are executing. In some cases the Ada.Execution_Time
package can replace the Ada.Real_Time with only altering the with/use 
statements.

Some programmers might use this package to try to improve performance of 
an algorithm.

And a few might use this package for debugging like to prevent tasks from 
running away with the CPU resources. Such as stopping this type of 
logical condition from occurring at runtime:

  with x86 ; -- defines x86 instructions subset
  use  x86 ;

  task body run is

    begin
      Disable_Interrupts ;
      loop            -- Endless loop. 
        null ;        -- Which optimizes to one jump instruction
      end loop ;
    end run ;


Which when optimize can shutdown a cpu or computer system. And requires 
either a non-maskable reset or a full power cold restart without being able 
to save critical data or closing files.

Also, in history this package would be use to calculate the cpu usage charges 
for a customer.




^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  2010-12-16 17:52  6%               ` Ada.Execution_Time Dmitry A. Kazakov
@ 2010-12-17  8:49  5%                 ` Niklas Holsti
    0 siblings, 1 reply; 200+ results
From: Niklas Holsti @ 2010-12-17  8:49 UTC (permalink / raw)



>>> On Wed, 15 Dec 2010 16:05:16 -0600, Randy Brukardt wrote:
>>>
>>>> I think you are missing the point of CPU_Time. It is an abstract 
>>>> representation of some underlying counter. There is no requirement that this 
>>>> counter have any particular value -- in particular it is not necessarily 
>>>> zero when a task is created.

Are you sure, Randy? RM D.14 13/2 says "For each task, the execution 
time value is set to zero at the creation of the task."

>>>> So the only operations that are meaningful on a 
>>>> value of type CPU_Time are comparisons and differences. Arguably, CPU_Time 
>>>> is misnamed, because it is *not* some sort of time type.

Additions of CPU_Time values should also be meaningful. As I understand 
it, Ada.Execution_Time is meant for use in task scheduling, where it is 
essential that when several tasks start at the same time on one 
processor, the sum of their CPU_Time values at any later instant is 
close to the real elapsed time, Ada.Real_Time.Time_Span. Assuming that 
CPU_Time starts at zero for each task, see above.

Dmitry A. Kazakov wrote:
> CPU_Time has no physical meaning. 2s might be 2.5s
> real time or 1 year real time.

CPU_Time values have physical meaning after being summed over all tasks. 
The sum should be the real time, as closely as possible.

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  @ 2010-12-16 17:52  6%               ` Dmitry A. Kazakov
  2010-12-17  8:49  5%                 ` Ada.Execution_Time Niklas Holsti
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-12-16 17:52 UTC (permalink / raw)


On Thu, 16 Dec 2010 11:49:13 -0500, BrianG wrote:

> Dmitry A. Kazakov wrote:
>> On Wed, 15 Dec 2010 16:05:16 -0600, Randy Brukardt wrote:
>> 
>>> I think you are missing the point of CPU_Time. It is an abstract 
>>> representation of some underlying counter. There is no requirement that this 
>>> counter have any particular value -- in particular it is not necessarily 
>>> zero when a task is created. So the only operations that are meaningful on a 
>>> value of type CPU_Time are comparisons and differences. Arguably, CPU_Time 
>>> is misnamed, because it is *not* some sort of time type.
>> 
>> Any computer time is a representation of some counter. I think the point is
>> CPU_Time is not a real time, i.e. a time (actually the process driving the
>> corresponding counter) related to what people used to call "time" in the
>> external world. CPU_Time is what is usually called "simulation time." One
>> could use Duration or Time_Span in place of CPU_Time, but the concern is
>> that on some architectures, with multiple time sources, this would
>> introduce an additional inaccuracy. Another argument against it is that
>> there could be no fair translation from the CPU usage counter to
>> Duration/Time_Span (which is the case for Windows).
>> 
> Isn't any "time" related to a computer nothing but a "simulation time"? 

No, Ada.Calendar.Time and Ada.Real_Time.Time are derived from quartz
generators, which are physical devices. CPU_Time is derived from the time
the task owned a processor. This is a task time, the time in a simulated
Universe where nothing but the task exists. This Universe is not real, so
its time is not.

Or to put it otherwise, when Time has a value T, then under certain
conditions this has some meaning invariant to the program and the task
being run. For Ada.Real_Time.Time it is only the time differences T2 - T1,
which have this meaning. CPU_Time has no physical meaning. 2s might be 2.5s
real time or 1 year real time.

> Yes, some times may be intended to emulate clock-on-the-wall-time, but 
> that doesn't mean they're a very good emulation (ever measure the 
> accuracy of a PC that's not synched to something?

But the intent was to emulate the real time, whatever accuracy the result
night have.

> CPU_Time is 
> obviously an approximation, dependent on the RTS, OS, task scheduler, etc.

An approximation of what?

> What's so particularly bad about Windows (aside from the normal Windows 
> things)?

Windows counts full quants. It means that if the task (thread) enters a
non-busy waiting, e.g. for I/O or for other event, *before* it has spent
its quant, the quant is not counted (if I correctly remember). In effect,
you theoretically could have 0 CPU time with 99% processor load. Using the
task manager, you might frequently observe the effect of this: moderate CPU
load, but everything is frozen.

(I don't checked this behavior since Windows Server 2003, maybe they fixed
it in Vista, 7 etc).

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  2010-12-15 22:05  5%         ` Ada.Execution_Time Randy Brukardt
@ 2010-12-16  1:14  0%           ` BrianG
    1 sibling, 0 replies; 200+ results
From: BrianG @ 2010-12-16  1:14 UTC (permalink / raw)


Randy Brukardt wrote:
> "BrianG" <briang000@gmail.com> wrote in message 
> news:ie91co$cko$1@news.eternal-september.org...
> ...
>> My problem is that what is provided in the package in question does not 
>> provide any "values suitable for arithmetic" or provide "an object 
>> suitable for print" (unless all you care about is the number of whole 
>> seconds with no information about the (required) fraction, which seems 
>> rather limiting).
> 
> Having missed your original question, I'm confused as to where you are 
> finding the quoted text above. I don't see anything like that in the 
> Standard. Since it is not in the standard, there is no reason to expect 
> those statements to be true. (Even the standard is wrong occassionally, 
> other materials are wrong a whole lot more often.)
> 
The quoted text was from the post I responded to.  It was Georg's 
attempt to explain the package.  I agree that they are not in the RM; my 
original question was what is the intended purpose of the package - the 
content doesn't seem useful for any use I can think of.

>>  Time_Span is a private type, defined in another package.  If all I want 
>> is CPU_Time (in some form), why do I need Ada.Real_Time?  Also, why are 
>> "+" and "-" provided as they are defined? (And why Time_Span?  I thought 
>> that was the difference between two times, not the fractional part of 
>> time.)
> 
> I think you are missing the point of CPU_Time. It is an abstract 
> representation of some underlying counter. There is no requirement that this 
> counter have any particular value -- in particular it is not necessarily 
> zero when a task is created. So the only operations that are meaningful on a 
> value of type CPU_Time are comparisons and differences. Arguably, CPU_Time 
> is misnamed, because it is *not* some sort of time type.
Then the package is misnamed too - How is "Execution_Time" not a time? 
Wouldn't tying it explicitly to Real_Time imply some relation to "real 
time" (whether that makes sense or not)?  Using Duration could help 
that, since it's implementation-defined.

One of my problems is that difference (and sum) isn't provided between 
CPU_Time's, only with a Time_Span.  But you can only convert a portion 
of a CPU_Time to Time_Span.  When is that useful (as opposed to 
Splitting both CPU_Times)?

A function "-" (L, R : CPU_Time) return Time_Span (or better, Duration) 
would be required for what you describe above (actually, if what you say 
is true, then that and Clock are all that's required).

> 
> The package uses Ada.Real_Time because no one wanted to invent a new kind of 
> time. The only alternative would have been to use Calendar, which does not 
> have to be as accurate. (Of course, the real accuracy depends on the 
> underlying target; CPU_Time has to be fairly inaccurate on Windows simply 
> because the underlying counters are not very accurate, at least in the 
> default configuration.)
(I think that is inherent in anything of this type, but I'd think it's 
hard to specify that in the RM:)
> 
> My guess is that no one thought about the fact that Time_Span is only an 
> alias for Duration; it's definitely something that I didn't know until you 
> complained. (I know I've confused Time and Time_Span before, must have done 
> that here, too). So there probably was no good reason that Time_Span was 
> used instead of Duration in the package. But that seems to indicate a flaw 
> in Ada.Real_Time, not one for execution time.
I wasn't aware that it was an alias.  I had assumed it was there in case 
Duration didn't have the range or precision required for Time_Span (or 
something like that).

The other part of my problem is that I can only convert to another 
private type (for part of the value).  It seems to me equivalent to 
defining Sequential_IO and Direct_IO (etc) without File_Type - requiring 
the use of Text_IO any time you want to Open, Close, etc a file.  :-)

> 
> In any case, the presumption is that interesting CPU_Time differences are 
> relatively short, so that Time_Span is sufficient (as it will hold at least 
> one day).
But that is not provided - that would require a "-" between two 
CPU_Time's returning a Time_Span.  Unless all CPU_Time's are always less 
than a second, you can't get there easily.

> 
>> Given the rest of this thread, I would guess my answer is "No, no one 
>> actually uses Ada.Execution_Time".
> 
> Can't answer that. I intended to use it to replace some hacked debugging 
> code, but I've never gotten around to actually implementing it (I did do a 
> design, but there is of course a difference...).
> 
>                                   Randy.
> 



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-15  0:16  5%       ` Ada.Execution_Time BrianG
  2010-12-15 19:17  6%         ` Ada.Execution_Time jpwoodruff
@ 2010-12-15 22:05  5%         ` Randy Brukardt
  2010-12-16  1:14  0%           ` Ada.Execution_Time BrianG
    2010-12-17  8:59  6%         ` Ada.Execution_Time anon
  2 siblings, 2 replies; 200+ results
From: Randy Brukardt @ 2010-12-15 22:05 UTC (permalink / raw)


"BrianG" <briang000@gmail.com> wrote in message 
news:ie91co$cko$1@news.eternal-september.org...
...
> My problem is that what is provided in the package in question does not 
> provide any "values suitable for arithmetic" or provide "an object 
> suitable for print" (unless all you care about is the number of whole 
> seconds with no information about the (required) fraction, which seems 
> rather limiting).

Having missed your original question, I'm confused as to where you are 
finding the quoted text above. I don't see anything like that in the 
Standard. Since it is not in the standard, there is no reason to expect 
those statements to be true. (Even the standard is wrong occassionally, 
other materials are wrong a whole lot more often.)

>  Time_Span is a private type, defined in another package.  If all I want 
> is CPU_Time (in some form), why do I need Ada.Real_Time?  Also, why are 
> "+" and "-" provided as they are defined? (And why Time_Span?  I thought 
> that was the difference between two times, not the fractional part of 
> time.)

I think you are missing the point of CPU_Time. It is an abstract 
representation of some underlying counter. There is no requirement that this 
counter have any particular value -- in particular it is not necessarily 
zero when a task is created. So the only operations that are meaningful on a 
value of type CPU_Time are comparisons and differences. Arguably, CPU_Time 
is misnamed, because it is *not* some sort of time type.

The package uses Ada.Real_Time because no one wanted to invent a new kind of 
time. The only alternative would have been to use Calendar, which does not 
have to be as accurate. (Of course, the real accuracy depends on the 
underlying target; CPU_Time has to be fairly inaccurate on Windows simply 
because the underlying counters are not very accurate, at least in the 
default configuration.)

My guess is that no one thought about the fact that Time_Span is only an 
alias for Duration; it's definitely something that I didn't know until you 
complained. (I know I've confused Time and Time_Span before, must have done 
that here, too). So there probably was no good reason that Time_Span was 
used instead of Duration in the package. But that seems to indicate a flaw 
in Ada.Real_Time, not one for execution time.

In any case, the presumption is that interesting CPU_Time differences are 
relatively short, so that Time_Span is sufficient (as it will hold at least 
one day).

> Given the rest of this thread, I would guess my answer is "No, no one 
> actually uses Ada.Execution_Time".

Can't answer that. I intended to use it to replace some hacked debugging 
code, but I've never gotten around to actually implementing it (I did do a 
design, but there is of course a difference...).

                                  Randy.





^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  2010-12-15 19:17  6%         ` Ada.Execution_Time jpwoodruff
@ 2010-12-15 21:42  0%           ` Pascal Obry
  0 siblings, 0 replies; 200+ results
From: Pascal Obry @ 2010-12-15 21:42 UTC (permalink / raw)
  To: jpwoodruff

Le 15/12/2010 20:17, jpwoodruff a �crit :
> Unfortunately introduction of Ada.Real_Time can  cause an otherwise
> successful program to raise STORAGE_ERROR :EXCEPTION_STACK_OVERFLOW.
> This happens even if the program formerly ran only in an environment
> task.
> 
> 
> with Ada.Real_Time ;   -- This context leads to failure
> Procedure Stack_Splat is
>    Too_Big : array (1..1_000_000) of Float ;
> begin
>    null ;
> end Stack_Splat ;

Probably because the stack size is smaller in the context of tasking
runtime. Just increase the stack (see corresponding linker option) for
the environment task. Nothing really blocking or I did I miss your point?

Pascal.

-- 

--|------------------------------------------------------
--| Pascal Obry                           Team-Ada Member
--| 45, rue Gabriel Peri - 78114 Magny Les Hameaux FRANCE
--|------------------------------------------------------
--|    http://www.obry.net  -  http://v2p.fr.eu.org
--| "The best way to travel is by means of imagination"
--|
--| gpg --keyserver keys.gnupg.net --recv-key F949BD3B




^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-15  0:16  5%       ` Ada.Execution_Time BrianG
@ 2010-12-15 19:17  6%         ` jpwoodruff
  2010-12-15 21:42  0%           ` Ada.Execution_Time Pascal Obry
  2010-12-15 22:05  5%         ` Ada.Execution_Time Randy Brukardt
  2010-12-17  8:59  6%         ` Ada.Execution_Time anon
  2 siblings, 1 reply; 200+ results
From: jpwoodruff @ 2010-12-15 19:17 UTC (permalink / raw)


BrianG's discussion spurred my interest, so now I am able to
contradict his

On Dec 14, 5:16 pm, BrianG <briang...@gmail.com> wrote:
>
> Given the rest of this thread, I would guess my answer is "No, no one
> actually uses Ada.Execution_Time".
>

Let me describe my experiment, which ends in a disappointing
observation about Ada.Execution_Time.

For some years I've had a package that defines a "Counter" object that
resembles a stop-watch.  Made curious by BrianG's question, I
re-implemented the abstraction over Ada.Execution_Time.

Unfortunately introduction of Ada.Real_Time can  cause an otherwise
successful program to raise STORAGE_ERROR :EXCEPTION_STACK_OVERFLOW.
This happens even if the program formerly ran only in an environment
task.


with Ada.Real_Time ;   -- This context leads to failure
Procedure Stack_Splat is
   Too_Big : array (1..1_000_000) of Float ;
begin
   null ;
end Stack_Splat ;


I haven't found the documentation that explains my observation, but
it's pretty clear that Ada.Real_Time in the context implies
substantially different run-time memory strategy.  I suppose there are
compile options to affect this; it can be an exercise for a later day.

Here is the package CPU, which is potentially useful in programs that
use stack gently.

-- PACKAGE FOR CPU TIME CALCULATIONS.
-----------------------------------------------------------------------
--
--              Author:         John P Woodruff
--                              jpwoodruff@gmail.com
--

-- This package owes a historic debt to the similarly named service
-- Created 19-SEP-1986 by Mats Weber.  This specification is largely
-- defined by that work.

--  15-apr-2004: However, Weber's package was implemented by unix
calls
--  (alternatively VMS calls).  JPW has adapted this package
--  specification twice: first to use the Ada.Calendar.Clock
--  functions, then later (when I discovered deMontmollin's WIN-PAQ)
--  to use windows32 low-level calls. Now only the thinnest of Mats
--  Weber's traces can be seen.

--  December 2010: the ultimate version is possible now that Ada2005
--  gives us Ada.Execution_Time.  The object CPU_Counter times a task
--  (presently limited to the current task), and a Report about a
--  CPU_Counter might make interesting reading. Unhappily when this
--  package is introduced, gnat allocates smaller space for the
--  environment task than in the absence of tasking.  Therefore
--  instrumented programs may blow stack in cases that uninstrumented
--  programs do not.

with Ada.Execution_Time ;

package CPU is

   -- Type of a CPU time counter.  Each object of this type is an
   --  independent stop-watch that times the task in which it is
   --  declared.  Possible enhancement: bind a CPU_Counter to a
   --  Task_ID different from Current_Task.

   type CPU_Counter is limited private;

   ------------------------------------------------------------------
   -- The operations for a counter are Start, Stop and Clear.
   -- A counter that is Stopped retains the time already accrued,
until
   -- it is Cleared.

   --  A stopped counter can be started and will add to the time
   --  already accrued - just as though it had run continuously.
   --  It is not necessary to stop a counter in order to read
   --  its value.

   procedure Start_Counter (The_Counter : in out CPU_Counter);
   procedure Stop_Counter  (The_Counter : in out CPU_Counter);
   procedure Clear_Counter (The_Counter : in out CPU_Counter);

   ------------------------------------------------------------------
   -- There are two groups of reporting functions:

   --  CPU_Time returns the time used during while the counter has
   --  been running.


   function CPU_Time (Of_Counter : CPU_Counter) return Duration ;

   -- Process_Lifespan returns the total CPU since the process
   --  started.  (Does not rely on any CPU_counter having been
   --  started.)

   function Process_Lifespan  return Duration ;


   Counter_Not_Started : exception;

   --------------------------------------------------------------
   --  The other reporting functions produce printable reports for
   --  a counter, or for the process as a whole (the procedure
   --  writes to standard output). Reports do not effect the
   --  counter.  Use a prefix string to label the output according
   --  to the activity being timed.

   procedure Report_Clock (Watch      : in CPU_Counter;
                           Prefix     : in String := "") ;

   function  Report_Clock (Watch      : in CPU_Counter) return
String ;


   procedure Report_Process_Lifespan ;

   function  Report_Process_Lifespan return String ;

private

   type CPU_Counter is
      record
         Identity       : Natural := 0 ;
         Accrued_Time   : Ada.Execution_Time.CPU_Time
                        := Ada.Execution_Time.CPU_Time_First ;
         Running        : Boolean := False;
         Start_CPU      : Ada.Execution_Time.Cpu_Time
                        := Ada.Execution_Time.Clock ;
      end record;

end CPU ;

---------------------------------
-- Creation : 19-SEP-1986 by Mats Weber.
-- Revision : 16-Jul-1992 by Mats Weber, enhanced portability by
adding
--                                       separate package
System_Interface.
-- JPW 23 Sep 00 use ada.calendar.clock (because it works on Windows)
-- jpw 14apr04 *found* the alternative.  Montmollin's win-paq product
--     defines win32_timing: the operating system function.
-- jpw 14dec10  reimplement and substantially simplify using
Ada.Execution_Time


with Ada.Text_Io;
with Ada.Real_Time ;

package body CPU is
   ----------------
   use type Ada.Execution_Time.Cpu_Time ;

   Next_Counter_Identity : Natural := 0 ;

   function To_Duration (Time : Ada.Execution_Time.CPU_Time) return
Duration is
      -- thanks to Jeff Carter comp.lang.ada 11dec10
      Seconds  : Ada.Real_Time.Seconds_Count;
      Fraction : Ada.Real_Time.Time_Span;
   begin     -- To_Duration
      Ada.Execution_Time.Split (Time, Seconds, Fraction);
      return Duration (Seconds) + Ada.Real_Time.To_Duration
(Fraction);
   end To_Duration;


   procedure Start_Counter (The_Counter : in out CPU_Counter) is
   begin
      if The_Counter.Identity > 0 then
         --  This is a restart:  identity and accrued times remain
         if not The_Counter.Running then
            The_Counter.Start_CPU := Ada.Execution_Time.Clock ;
         end if ;
         The_Counter.Running   := True ;
      else   -- this clock has never started before
         Next_Counter_Identity       := Next_Counter_Identity + 1;
         The_Counter.Identity        := Next_Counter_Identity ;
         The_Counter.Running         := True ;
         The_Counter.Start_CPU       := Ada.Execution_Time.Clock ;
      end if ;
   end Start_Counter;


   procedure Stop_Counter  (The_Counter : in out CPU_Counter)is
      Now : Ada.Execution_Time.Cpu_Time
          := Ada.Execution_Time.Clock ;
   begin
      if  The_Counter.Identity > 0 and The_Counter.Running then
         -- accrue time observed up to now
         The_Counter.Accrued_Time := The_Counter.Accrued_Time +
           (Now - The_Counter.Start_CPU) ;
         The_Counter.Running := False ;
      end if ;
   end Stop_Counter ;


   procedure Clear_Counter  (The_Counter : in out CPU_Counter) is
      -- the counter becomes "as new" ready to start.
   begin
      The_Counter.Running := False ;
      The_Counter.Accrued_Time := Ada.Execution_Time.CPU_Time_First ;
   end Clear_Counter ;


   function CPU_Time (Of_Counter  : CPU_Counter) return Duration is
      Now : Ada.Execution_Time.Cpu_Time
          := Ada.Execution_Time.Clock ;
   begin
      if Of_Counter.Identity <= 0 then
         raise Counter_Not_Started ;
      end if;
      if not Of_Counter.Running then
         return To_Duration (Of_Counter.Accrued_Time) ;
      else
         return To_Duration (Of_Counter.Accrued_Time +
                             (Now - Of_Counter.Start_CPU)) ;
      end if ;
   end CPU_Time;

   function Process_Lifespan return Duration is
   begin
      return To_Duration (Ada.Execution_Time.Clock) ;
   end Process_Lifespan ;

   function Report_Duration (D : in Duration) return String is
   begin
      if D < 1.0 then
         declare
            Millisec : String := Duration'Image (1_000.0 * D);
         begin
            return  MilliSec(MilliSec'First .. MilliSec'Last-6) & "
msec" ;
         end ;
      elsif D < 60.0 then
         declare Sec : String :=  Duration'Image (D);
         begin
            return Sec(Sec'First .. Sec'Last-6)  & " sec" ;  -- fewer
signficant figs
         end ;
      else
         declare
            Minutes : Integer := Integer(D) / 60 ;
            Seconds : Duration := D - Duration(Minutes) * 60.0 ;
            Sec : String := Duration'Image (Seconds) ;
         begin
            return Integer'Image (Minutes) & " min " &
              Sec(Sec'First .. Sec'Last-6) & " sec" ;
         end ;
      end if ;
   end Report_Duration ;


   procedure Report_Clock (Watch      : in CPU_Counter;
                           Prefix     : in String := "") is
      use Ada.Text_IO ;
   begin
      Put (Prefix & Report_Clock (Watch)) ;
      New_Line ;
   end Report_Clock;


   function Report_Clock (Watch      : in CPU_Counter) return String
is
   begin
      return
        " <" & Integer'Image(Watch.Identity) & "> " &
        Report_Duration (CPU_Time (Watch)) ;
   end Report_Clock ;


   procedure Report_Process_Lifespan is
      use Ada.Text_IO ;
   begin
      Put (Report_Process_Lifespan) ;
      New_Line ;
   end Report_Process_Lifespan ;


   function  Report_Process_Lifespan return String is
      use Ada.Text_IO ;
   begin
      return "Process Lifespan: " & Report_Duration
(Process_Lifespan) ;
   end Report_Process_Lifespan ;

end CPU ;



^ permalink raw reply	[relevance 6%]

* Re: Ada.Execution_Time
  @ 2010-12-15  0:16  5%       ` BrianG
  2010-12-15 19:17  6%         ` Ada.Execution_Time jpwoodruff
                           ` (2 more replies)
  0 siblings, 3 replies; 200+ results
From: BrianG @ 2010-12-15  0:16 UTC (permalink / raw)


Georg Bauhaus wrote:
> On 12/12/10 10:59 PM, BrianG wrote:
> 
> 
>> But my question still remains: What's the intended use of 
>> Ada.Execution_Time? Is there an intended use where its content 
>> (CPU_Time, Seconds_Count and Time_Span, "+", "<", etc.) is useful?
> 
> I think that your original posting mentions a use that is quite
> consistent with what the rationale says: each task has its own time.
> Points in time objects can be split into values suitable for
> arithmetic, using Time_Span objects.  Then, from the result of
> arithmetic, produce an object suitable for print, as desired.
> 
> 
> While this seems like having to write a bit much,
> it makes things explicit, like Ada forces one to be
> in many cases.   That' how I explain the series of
> steps to myself.
> 
> Isn't it just like "null;" being required to express
> the null statement?  It seems to me to be a logical
> consequence of requiring that intents must be stated
> explicitly.
> 
I have no problem with verbosity or explicitness, and that's not what I 
was asking about.

My problem is that what is provided in the package in question does not 
provide any "values suitable for arithmetic" or provide "an object 
suitable for print" (unless all you care about is the number of whole 
seconds with no information about the (required) fraction, which seems 
rather limiting).  Time_Span is a private type, defined in another 
package.  If all I want is CPU_Time (in some form), why do I need 
Ada.Real_Time?  Also, why are "+" and "-" provided as they are defined? 
  (And why Time_Span?  I thought that was the difference between two 
times, not the fractional part of time.)

Given the rest of this thread, I would guess my answer is "No, no one 
actually uses Ada.Execution_Time".

--BrianG



^ permalink raw reply	[relevance 5%]

* Re: Ada.Execution_Time
  2010-12-12 16:56  8% ` Ada.Execution_Time Jeffrey Carter
@ 2010-12-12 21:59  0%   ` BrianG
    0 siblings, 1 reply; 200+ results
From: BrianG @ 2010-12-12 21:59 UTC (permalink / raw)


Jeffrey Carter wrote:
> On 12/11/2010 09:19 PM, BrianG wrote:
>>
...
> I think you're over complicating things.
> 
> function To_Duration (Time : Ada.Execution_Time.CPU_Time) return 
> Duration is
>    Seconds  : Ada.Real_Time.Seconds_Count;
>    Fraction : Ada.Real_Time.Time_Span;
> begin -- To_Duration
>    Ada.Execution_Time.Split (Time, Seconds, Fraction);
> 
>    return Duration (Seconds) + Ada.Real_Time.To_Duration (Fraction);
> end To_Duration;
> 
That's what I get for evolving thru several iterations before coming up 
with a function.  (BTW, where is To_Duration defined for integer types? 
  The only one in the Index is for Time_Span.)

But my question still remains:  What's the intended use of 
Ada.Execution_Time?  Is there an intended use where its content 
(CPU_Time, Seconds_Count and Time_Span, "+", "<", etc.) is useful?

--BrianG



^ permalink raw reply	[relevance 0%]

* Re: Ada.Execution_Time
  2010-12-12  4:19  6% Ada.Execution_Time BrianG
  2010-12-12  5:27  8% ` Ada.Execution_Time Jeffrey Carter
@ 2010-12-12 16:56  8% ` Jeffrey Carter
  2010-12-12 21:59  0%   ` Ada.Execution_Time BrianG
  1 sibling, 1 reply; 200+ results
From: Jeffrey Carter @ 2010-12-12 16:56 UTC (permalink / raw)


On 12/11/2010 09:19 PM, BrianG wrote:
>
> function Task_CPU_Time return Duration (T : ...) is
> Sec : Ada.Execution_Time.Seconds_Count;
> Fraction : Ada.Real_Time.Time_Span;
> begin
> Ada.Execution_Time.Split(Ada.Execution_Time.Clock(T), Sec, Fraction);
> return To_Duration(Ada.Real_Time.Seconds(Integer(Sec)))
> + To_Duration(Fraction);
> end Task_CPU_Time;

I think you're over complicating things.

function To_Duration (Time : Ada.Execution_Time.CPU_Time) return Duration is
    Seconds  : Ada.Real_Time.Seconds_Count;
    Fraction : Ada.Real_Time.Time_Span;
begin -- To_Duration
    Ada.Execution_Time.Split (Time, Seconds, Fraction);

    return Duration (Seconds) + Ada.Real_Time.To_Duration (Fraction);
end To_Duration;

-- 
Jeff Carter
"This school was here before you came,
and it'll be here before you go."
Horse Feathers
48



^ permalink raw reply	[relevance 8%]

* Re: Ada.Execution_Time
  2010-12-12  4:19  6% Ada.Execution_Time BrianG
@ 2010-12-12  5:27  8% ` Jeffrey Carter
  2010-12-12 16:56  8% ` Ada.Execution_Time Jeffrey Carter
  1 sibling, 0 replies; 200+ results
From: Jeffrey Carter @ 2010-12-12  5:27 UTC (permalink / raw)


On 12/11/2010 09:19 PM, BrianG wrote:
>
> function Task_CPU_Time return Duration (T : ...) is
> Sec : Ada.Execution_Time.Seconds_Count;
> Fraction : Ada.Real_Time.Time_Span;
> begin
> Ada.Execution_Time.Split(Ada.Execution_Time.Clock(T), Sec, Fraction);
> return To_Duration(Ada.Real_Time.Seconds(Integer(Sec)))
> + To_Duration(Fraction);
> end Task_CPU_Time;

I think you're over complicating things.

function To_Duration (Time : Ada.Execution_Time.CPU_Time) return Duration is
    Seconds  : Ada.Real_Time.Seconds_Count;
    Fraction : Ada.Real_Time.Time_Span;
begin -- To_Duration
    Ada.Execution_Time.Split (Time, Seconds, Fraction);

    return Duration (Seconds) + Ada.Real_Time.To_Duration (Fraction);
end To_Duration;

-- 
Jeff Carter
"This school was here before you came,
and it'll be here before you go."
Horse Feathers
48



^ permalink raw reply	[relevance 8%]

* Ada.Execution_Time
@ 2010-12-12  4:19  6% BrianG
  2010-12-12  5:27  8% ` Ada.Execution_Time Jeffrey Carter
  2010-12-12 16:56  8% ` Ada.Execution_Time Jeffrey Carter
  0 siblings, 2 replies; 200+ results
From: BrianG @ 2010-12-12  4:19 UTC (permalink / raw)


Has anyone actually used Ada.Execution_Time?  How is it supposed to be used?

I tried to use it for two (what I thought would be) simple uses: 
display the execution time of one task and sum the of execution time of 
a group of related tasks.

In both cases, I don't see anything in that package (or in 
Ada.Real_Time, which appears to be needed to use it) that provides any 
straightforward way to use the value reported.

For display, you can't use CPU_Time directly, since it's private.  You 
can Split it, but you get a Time_Span, which is also private.  So the 
best you can do is Split it, and then convert the parts to a type that 
can be used (like duration).

For summing, there is "+", but only between CPU_Time and Time_Span, so 
you can't add two CPU_Times.  Perhaps you can use Split, sum the 
seconds, and then use "+" to add the fractions to the next Clock (before 
repeating Split/add/"+" with it, then you need to figure out what to do 
with the last fractional second), but that seems an odd intended use.

The best I could come up with was to create my own function, like this 
(using the same definition for T as in Clock), which can be used for both:

function Task_CPU_Time return Duration (T : ...) is
    Sec      : Ada.Execution_Time.Seconds_Count;
    Fraction : Ada.Real_Time.Time_Span;
begin
    Ada.Execution_Time.Split(Ada.Execution_Time.Clock(T), Sec, Fraction);
    return To_Duration(Ada.Real_Time.Seconds(Integer(Sec)))
         + To_Duration(Fraction);
end Task_CPU_Time;

Wouldn't it make sense to put something like this into that package? 
Then, at least, there'd be something that's directly available to use - 
and you wouldn't need another package.  (I'm not sure about the 
definitions of CPU_Time and Duration, and whether the conversions would 
be guaranteed to work.)

--BrianG



^ permalink raw reply	[relevance 6%]

* Re: GNAT's Protected Objects
  2010-11-08 22:32  7%   ` Jeffrey Carter
@ 2010-11-09  1:50  0%     ` Anh Vo
  0 siblings, 0 replies; 200+ results
From: Anh Vo @ 2010-11-09  1:50 UTC (permalink / raw)


On Nov 8, 2:32 pm, Jeffrey Carter <spam.jrcarter....@spam.not.acm.org>
wrote:
> On 11/08/2010 02:38 PM, Anh Vo wrote:
>
>
>
> > How may tasks used, two or four, when slowness was observed when
> > compared to simple task? I will be supprised if the answer is two. It
> > is logically expected that two tasks should perform better than single
> > task. However, when it comes to four or greater task, the result may
> > not be true due to task switching cost.
>
> That's what I expected. However, any number of tasks > 1 took longer than a
> single task.
>
> > I would be glad to test it on my two core CPU mahine if the your
> > little program is posted.
>
> I have appended the code to this message. Watch for line wrapping.
>
> --
> Jeff Carter
> "Sir Robin the not-quite-so-brave-as-Sir-Lancelot,
> who had nearly fought the Dragon of Angnor,
> who nearly stood up to the vicious Chicken of Bristol,
> and who had personally wet himself at the
> Battle of Badon Hill."
> Monty Python & the Holy Grail
> 68
>
> with Ada.Exceptions;
> with Ada.Numerics.Float_Random;
> with Ada.Real_Time;
> with Ada.Text_IO;
>
> with System.Task_Info;
>
> procedure MP_Mult_PO is
>     Num_Processors : constant Positive := System.Task_Info.Number_Of_Processors;
>
>     subtype Index_Value is Integer range 1 .. 500;
>
>     type Matrix is array (Index_Value, Index_Value) of Float;
>
>     function Mult (Left : in Matrix; Right : in Matrix; Num_Tasks : in Positive)
> return Matrix;
>     -- Perform a concurrent multiplication of Left * Right using Num_Tasks tasks
>
>     function Mult (Left : in Matrix; Right : in Matrix; Num_Tasks : in Positive)
> return Matrix is
>        task type Calc_One;
>
>        protected Control is
>           procedure Get (Row : out Natural; Col : out Natural);
>           -- Returns the row and column of a result to calculate.
>           -- Returns zero for both when there are no more results to calculate.
>        private -- Control
>           Next_Row : Positive := 1;
>           Next_Col : Positive := 1;
>           Done     : Boolean  := False;
>        end Control;
>
>        Result : Matrix;
>
>        task body Calc_One is
>           Row : Natural;
>           Col : Natural;
>        begin -- Calc_One
>           All_Results : loop
>              Control.Get (Row => Row, Col => Col);
>
>              exit All_Results when Row = 0;
>
>              Result (Row, Col) := 0.0;
>
>              Sum : for K in Index_Value loop
>                 Result (Row, Col) := Result (Row, Col) + Left (Row, K) * Right
> (K, Col);
>              end loop Sum;
>           end loop All_Results;
>        exception -- Calc_One
>        when E : others =>
>           Ada.Text_IO.Put_Line (Item => "Calc_One " &
> Ada.Exceptions.Exception_Information (E) );
>        end Calc_One;
>
>        protected body Control is
>           procedure Get (Row : out Natural; Col : out Natural) is
>           begin -- Get
>              if Done then
>                 Row := 0;
>                 Col := 0;
>
>                 return;
>              end if;
>
>              Row := Next_Row;
>              Col := Next_Col;
>
>              if Next_Col < Index_Value'Last then
>                 Next_Col := Next_Col + 1;
>
>                 return;
>              end if;
>
>              Next_Col := 1;
>              Next_Row := Next_Row + 1;
>
>              Done := Next_Row > Index_Value'Last;
>           end Get;
>        end Control;
>     begin -- Mult
>        Create_Tasks : declare
>           type Task_List is array (1 .. Num_Tasks) of Calc_One;
>
>           Tasks : Task_List;
>        begin -- Create_Tasks
>           null; -- Wait for all tasks to complete
>        end Create_Tasks;
>
>        return Result;
>     exception -- Mult
>     when E : others =>
>        Ada.Text_IO.Put_Line (Item => "Mult " &
> Ada.Exceptions.Exception_Information (E) );
>
>        raise;
>     end Mult;
>
>     function Random return Float;
>
>     Gen : Ada.Numerics.Float_Random.Generator;
>
>     function Random return Float is
>     begin -- Random
>        return 200.0 * Ada.Numerics.Float_Random.Random (Gen) - 100.0; -- -100 ..
> 100.
>     end Random;
>
>     A : constant Matrix := Matrix'(others => (others => Random) );
>     B : constant Matrix := Matrix'(others => (others => Random) );
>
>     C : Matrix;
>
>     Elapsed   : Duration;
>     Prev      : Duration := Duration'Last;
>     Start     : Ada.Real_Time.Time;
>     Num_Tasks : Positive := 1;
>
>     use type Ada.Real_Time.Time;
> begin -- MP_Mult_PO
>     Ada.Text_IO.Put_Line (Item => "Num processors" & Integer'Image
> (Num_Processors) );
>
>     All_Calls : loop
>        Start := Ada.Real_Time.Clock;
>        C := Mult (A, B, Num_Tasks);
>        Elapsed := Ada.Real_Time.To_Duration (Ada.Real_Time.Clock - Start);
>        Ada.Text_IO.Put_Line (Item => Integer'Image (Num_Tasks) & ' ' &
> Duration'Image (Elapsed) );
>
>        exit All_Calls when Num_Tasks > 2 * Num_Processors and Elapsed > Prev;
>
>        Prev := Elapsed;
>        Num_Tasks := Num_Tasks + 1;
>     end loop All_Calls;
> exception -- MP_Mult_PO
> when E : others =>
>     Ada.Text_IO.Put_Line (Item => "MP_Mult_PO " &
> Ada.Exceptions.Exception_Information (E) );
> end MP_Mult_PO;

Below are the test results conducted on GNAT 2010 running on Windows
XP.

Num processors 2
 1  0.077000009
 2  0.055627741
 3  0.023719495
 4  0.018366580
 5  0.018512129

The output looks reasonable. The speed is improved up to 4 tasks. It
slows down with 5 tasks due to tasking switch. However, it is still
better than single task.

As Robert suggested, I would divide work among tasks by passing
paramter into each task. For example, in case of two tasks, one task
handles from rows 1 .. 250 while the other task handle from rows
251 .. 500. By the way, the protected singleton type Control is no
longer needed.

Anh Vo



^ permalink raw reply	[relevance 0%]

* Re: GNAT's Protected Objects
  @ 2010-11-08 22:32  7%   ` Jeffrey Carter
  2010-11-09  1:50  0%     ` Anh Vo
  0 siblings, 1 reply; 200+ results
From: Jeffrey Carter @ 2010-11-08 22:32 UTC (permalink / raw)


On 11/08/2010 02:38 PM, Anh Vo wrote:
>
> How may tasks used, two or four, when slowness was observed when
> compared to simple task? I will be supprised if the answer is two. It
> is logically expected that two tasks should perform better than single
> task. However, when it comes to four or greater task, the result may
> not be true due to task switching cost.

That's what I expected. However, any number of tasks > 1 took longer than a 
single task.

> I would be glad to test it on my two core CPU mahine if the your
> little program is posted.

I have appended the code to this message. Watch for line wrapping.

-- 
Jeff Carter
"Sir Robin the not-quite-so-brave-as-Sir-Lancelot,
who had nearly fought the Dragon of Angnor,
who nearly stood up to the vicious Chicken of Bristol,
and who had personally wet himself at the
Battle of Badon Hill."
Monty Python & the Holy Grail
68

with Ada.Exceptions;
with Ada.Numerics.Float_Random;
with Ada.Real_Time;
with Ada.Text_IO;

with System.Task_Info;

procedure MP_Mult_PO is
    Num_Processors : constant Positive := System.Task_Info.Number_Of_Processors;

    subtype Index_Value is Integer range 1 .. 500;

    type Matrix is array (Index_Value, Index_Value) of Float;

    function Mult (Left : in Matrix; Right : in Matrix; Num_Tasks : in Positive) 
return Matrix;
    -- Perform a concurrent multiplication of Left * Right using Num_Tasks tasks

    function Mult (Left : in Matrix; Right : in Matrix; Num_Tasks : in Positive) 
return Matrix is
       task type Calc_One;

       protected Control is
          procedure Get (Row : out Natural; Col : out Natural);
          -- Returns the row and column of a result to calculate.
          -- Returns zero for both when there are no more results to calculate.
       private -- Control
          Next_Row : Positive := 1;
          Next_Col : Positive := 1;
          Done     : Boolean  := False;
       end Control;

       Result : Matrix;

       task body Calc_One is
          Row : Natural;
          Col : Natural;
       begin -- Calc_One
          All_Results : loop
             Control.Get (Row => Row, Col => Col);

             exit All_Results when Row = 0;

             Result (Row, Col) := 0.0;

             Sum : for K in Index_Value loop
                Result (Row, Col) := Result (Row, Col) + Left (Row, K) * Right 
(K, Col);
             end loop Sum;
          end loop All_Results;
       exception -- Calc_One
       when E : others =>
          Ada.Text_IO.Put_Line (Item => "Calc_One " & 
Ada.Exceptions.Exception_Information (E) );
       end Calc_One;

       protected body Control is
          procedure Get (Row : out Natural; Col : out Natural) is
          begin -- Get
             if Done then
                Row := 0;
                Col := 0;

                return;
             end if;

             Row := Next_Row;
             Col := Next_Col;

             if Next_Col < Index_Value'Last then
                Next_Col := Next_Col + 1;

                return;
             end if;

             Next_Col := 1;
             Next_Row := Next_Row + 1;

             Done := Next_Row > Index_Value'Last;
          end Get;
       end Control;
    begin -- Mult
       Create_Tasks : declare
          type Task_List is array (1 .. Num_Tasks) of Calc_One;

          Tasks : Task_List;
       begin -- Create_Tasks
          null; -- Wait for all tasks to complete
       end Create_Tasks;

       return Result;
    exception -- Mult
    when E : others =>
       Ada.Text_IO.Put_Line (Item => "Mult " & 
Ada.Exceptions.Exception_Information (E) );

       raise;
    end Mult;

    function Random return Float;

    Gen : Ada.Numerics.Float_Random.Generator;

    function Random return Float is
    begin -- Random
       return 200.0 * Ada.Numerics.Float_Random.Random (Gen) - 100.0; -- -100 .. 
100.
    end Random;

    A : constant Matrix := Matrix'(others => (others => Random) );
    B : constant Matrix := Matrix'(others => (others => Random) );

    C : Matrix;

    Elapsed   : Duration;
    Prev      : Duration := Duration'Last;
    Start     : Ada.Real_Time.Time;
    Num_Tasks : Positive := 1;

    use type Ada.Real_Time.Time;
begin -- MP_Mult_PO
    Ada.Text_IO.Put_Line (Item => "Num processors" & Integer'Image 
(Num_Processors) );

    All_Calls : loop
       Start := Ada.Real_Time.Clock;
       C := Mult (A, B, Num_Tasks);
       Elapsed := Ada.Real_Time.To_Duration (Ada.Real_Time.Clock - Start);
       Ada.Text_IO.Put_Line (Item => Integer'Image (Num_Tasks) & ' ' & 
Duration'Image (Elapsed) );

       exit All_Calls when Num_Tasks > 2 * Num_Processors and Elapsed > Prev;

       Prev := Elapsed;
       Num_Tasks := Num_Tasks + 1;
    end loop All_Calls;
exception -- MP_Mult_PO
when E : others =>
    Ada.Text_IO.Put_Line (Item => "MP_Mult_PO " & 
Ada.Exceptions.Exception_Information (E) );
end MP_Mult_PO;



^ permalink raw reply	[relevance 7%]

* Re: Timing code blocks
  @ 2010-03-08 12:16  6%                 ` Alex Mentis
  0 siblings, 0 replies; 200+ results
From: Alex Mentis @ 2010-03-08 12:16 UTC (permalink / raw)


On Mar 6, 8:02 pm, Georg Bauhaus <rm-host.bauh...@maps.futureapps.de>
wrote:
> On 3/6/10 1:06 PM, Simon Wright wrote:
>
> > Georg Bauhaus<rm-host.bauh...@maps.futureapps.de>  writes:
>
> >> On 3/6/10 12:35 AM, Simon Wright wrote:
> >>> Alex Mentis<asmen...@gmail.com>   writes:
>
> >>>> Confirmed: the bug is still present in GNAT GPL 2009.
>
> >>> Not on Mac OS X (Snow Leopard), it isn't.
>
> >> Seeing the different behavior, what should be the best update
> >> for
> >>http://en.wikibooks.org/wiki/Ada_Programming/Tips#Quirks
>
> > That looks _quite_ explicit ("Using GNAT on Windows, ..."). It would be
> > nice to have a reference to the (Bugzilla?) report!
>
> Interesting in itself, and by coincidence, while reading
> Pat Rogers's new contribution to the Shootout, I noticed
> some lines that read
>
>    delay 0.0;  -- yield
>
> http://shootout.alioth.debian.org/u64q/program.php?test=chameneosredu...

Forward from AdaCore, FYI:

> We are able to reproduce the problem.

The problem is now understood and corrected in the development version
of GNAT.
It will most probably be corrected in GNAT GPL 2010.

What is happening here is that there is a missing call to
System.OS_Primitives.Initialize, when you use Ada.Real_Time but not
Ada.Calendar or any of the real time features of Ada, such as a delay
statement.

The fix consists in calling System.OS_Primitives.Initialize during
elaboration of Ada.Real_Time.

On POSIX platforms, because System.OS_Primitives.Initialize is a null
procedure, this missing call did not really matter.

Thank you for this report,

--  Vincent Celier




^ permalink raw reply	[relevance 6%]

* Re: Timing code blocks
  2010-03-05  8:49  0%     ` Dmitry A. Kazakov
@ 2010-03-05 12:41  0%       ` Alex Mentis
    0 siblings, 1 reply; 200+ results
From: Alex Mentis @ 2010-03-05 12:41 UTC (permalink / raw)


On Mar 5, 3:49 am, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:
> On Fri, 5 Mar 2010 00:16:52 -0800 (PST), deadlyhead wrote:
> > On Mar 4, 11:55 pm, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
> > wrote:
>
> >> This is an ancient bug, which managed to survive a number of GNAT compiler
> >> versions.
>
> >> As a workaround, add delay 0.0 at the beginning of your program:
>
> >>> ----------------------------------------------------------------------
>
> >>> --  A test of the cost of conditionals
>
> >>> with Ada.Text_IO;  use Ada.Text_IO;
> >>> with Ada.Real_Time; use Ada.Real_Time;
> >>> procedure Conditional_Test is
>
> > Exactly what was needed.  Thank you!
>
> > Do you happen to know if this bug has been fixed in the current
> > development branch? (At home I compile GNAT based on GCC 4.4, but
> > haven't done any real-time tests with it yet.)
>
> AFAIK it is still present in GNAT Pro 6.3.1, which is the latest version of
> GNAT.
>
> > This seems like an
> > unfortunate bug to have lying around in an otherwise respected
> > compiler.
>
> Yes, but in real-life applications it does not show itself, because tasking
> stuff somehow wakes the RTL up. That is probably the reason, I suggest, why
> none of paying customers had yet reported it to AdaCore.
>
> > BTW, my test results with -O3 and -Os, there is no difference in
> > performance between the two loops, and -Os produces code that is about
> > 33% faster than -O3.  With -O0, the second loop is faster by an
> > average of 10%.  I would have thought the extra conditional would have
> > been costlier.
>
> Niklas has posted an excellent comment regarding performance measures. It
> is quite difficult to do time measurements right in presence of -O2/3.
>
> As a small addition, here is a technique I am using to subtract looping
> overhead:
>
> T := Clock;
> for I in 1..N loop
>    ... -- measured stuff
> end loop;
> D1 := Clock - T;
>
> T := Clock;
> for I in 1..N loop
>    ... -- measured stuff
>    ... -- measured stuff (do it twice)
> end loop;
> D2 := Clock - T;
>
> (D2 - D1) / N is the average time spent on measured stuff without the
> overhead caused by looping. Important, as Niklas has pointed out, to fool
> the compiler so, that it will not optimize out the things you are
> measuring...
>
> --
> Regards,
> Dmitry A. Kazakovhttp://www.dmitry-kazakov.de

Confirmed: the bug is still present in GNAT GPL 2009.  The same code,
timed using Ada.Calendar seems to work just fine, though.
Interesting, and good to know about.



^ permalink raw reply	[relevance 0%]

* Re: Timing code blocks
  2010-03-05  8:16  0%   ` deadlyhead
@ 2010-03-05  8:49  0%     ` Dmitry A. Kazakov
  2010-03-05 12:41  0%       ` Alex Mentis
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-03-05  8:49 UTC (permalink / raw)


On Fri, 5 Mar 2010 00:16:52 -0800 (PST), deadlyhead wrote:

> On Mar 4, 11:55�pm, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
> wrote:
>>
>> This is an ancient bug, which managed to survive a number of GNAT compiler
>> versions.
>>
>> As a workaround, add delay 0.0 at the beginning of your program:
>>
>>> ----------------------------------------------------------------------
>>
>>> -- �A test of the cost of conditionals
>>
>>> with Ada.Text_IO; �use Ada.Text_IO;
>>> with Ada.Real_Time; use Ada.Real_Time;
>>> procedure Conditional_Test is
>>
> 
> Exactly what was needed.  Thank you!
> 
> Do you happen to know if this bug has been fixed in the current
> development branch? (At home I compile GNAT based on GCC 4.4, but
> haven't done any real-time tests with it yet.)

AFAIK it is still present in GNAT Pro 6.3.1, which is the latest version of
GNAT.

> This seems like an
> unfortunate bug to have lying around in an otherwise respected
> compiler.

Yes, but in real-life applications it does not show itself, because tasking
stuff somehow wakes the RTL up. That is probably the reason, I suggest, why
none of paying customers had yet reported it to AdaCore.

> BTW, my test results with -O3 and -Os, there is no difference in
> performance between the two loops, and -Os produces code that is about
> 33% faster than -O3.  With -O0, the second loop is faster by an
> average of 10%.  I would have thought the extra conditional would have
> been costlier.

Niklas has posted an excellent comment regarding performance measures. It
is quite difficult to do time measurements right in presence of -O2/3.

As a small addition, here is a technique I am using to subtract looping
overhead:

T := Clock;
for I in 1..N loop
   ... -- measured stuff
end loop;
D1 := Clock - T;

T := Clock;
for I in 1..N loop
   ... -- measured stuff
   ... -- measured stuff (do it twice)
end loop;
D2 := Clock - T;

(D2 - D1) / N is the average time spent on measured stuff without the
overhead caused by looping. Important, as Niklas has pointed out, to fool
the compiler so, that it will not optimize out the things you are
measuring...

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: Timing code blocks
  2010-03-05  6:34  5% Timing code blocks deadlyhead
  2010-03-05  7:55  0% ` Dmitry A. Kazakov
@ 2010-03-05  8:21  0% ` Niklas Holsti
  1 sibling, 0 replies; 200+ results
From: Niklas Holsti @ 2010-03-05  8:21 UTC (permalink / raw)


deadlyhead wrote:
> I've been trying to determine if there is any significant performance
> difference between two functionally equivalent pieces of code. I've
> done the standard thing and, using the Ada.Real_Time package, I'm
> saving the time when the code starts, then the time when the code
> ends, then examining the difference between them after the code runs.
> 
> The problem I'm having, though, is that the timing just isn't
> happening.  This code will run for 15 seconds and when I examine the
> time span, it tells me that no time passed.
> 
> Here's my actual code

[ code elided ]

Dmitry's already answered your main question. But your code also ha some 
other issues that I would like point out, in a friendly spirit. I have 
tried your code on Debian Lenny with the Debian GNAT compiler.

Firstly, if I compile with my normal options, -g -O2 -gnato 
-fstack-check, the code fails after some seconds with Constraint_Error 
due to overflow in the assignment Junk_In := Junk_In + 1 on line 42 
(counting the line with all '-' as line 1). This is expected, since this 
statement would be executed about (10**10)/2 times, leading to overflow 
with a 32-bit Natural counter.

Secondly, if I compile without overflow checks (-g -O2) the program runs 
very quickly and displays

---Starting per-branch assignment test---
Assignment within each branch took 0.000006000000

---Starting combined-branch assignment test---
Assignment outside of the branching took 0.000002000000

I believe that GNAT optimizes out almost everything in your loops, 
because the results are not used in the program. To disable some of this 
optimization you can use pragma Volatile to force GNAT to generate code 
that actually executes all the accesses to the variables, for example 
like this:

    Is_Even    : Boolean;  pragma Volatile (Is_Even);
    Is_Odd     : Boolean;  pragma Volatile (Is_Odd);
    Junk       : Positive;  pragma Volatile (Junk);
    Junk_In    : Natural := 0;  pragma Volatile (Junk_In);

With this change, and compiling with "-g -O2", the code takes about 1 
minute 30 seconds to run on my laptop and displays:

---Starting per-branch assignment test---
Assignment within each branch took 44.178160000000

---Starting combined-branch assignment test---
Assignment outside of the branching took 45.378627000000

I don't think you are not going to find valid performance differences 
between different styles of code using this kind of artificial test 
programs, because the compiler's code generation and optimization make 
such profound changes to the code, depending on the surroundings, data 
types, etc.

If you have a real performance problem in a real application, I suggest 
that you experiment with changes to the real application code. Use a 
profiler to find out where the time is spent and focus on that code.

HTH,

-- 
Niklas Holsti
Tidorum Ltd
niklas holsti tidorum fi
       .      @       .



^ permalink raw reply	[relevance 0%]

* Re: Timing code blocks
  2010-03-05  7:55  0% ` Dmitry A. Kazakov
@ 2010-03-05  8:16  0%   ` deadlyhead
  2010-03-05  8:49  0%     ` Dmitry A. Kazakov
  0 siblings, 1 reply; 200+ results
From: deadlyhead @ 2010-03-05  8:16 UTC (permalink / raw)


On Mar 4, 11:55 pm, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:
>
> This is an ancient bug, which managed to survive a number of GNAT compiler
> versions.
>
> As a workaround, add delay 0.0 at the beginning of your program:
>
> > ----------------------------------------------------------------------
>
> > --  A test of the cost of conditionals
>
> > with Ada.Text_IO;  use Ada.Text_IO;
> > with Ada.Real_Time; use Ada.Real_Time;
> > procedure Conditional_Test is
>

Exactly what was needed.  Thank you!

Do you happen to know if this bug has been fixed in the current
development branch? (At home I compile GNAT based on GCC 4.4, but
haven't done any real-time tests with it yet.) This seems like an
unfortunate bug to have lying around in an otherwise respected
compiler. The ease of the workaround, and likewise that it seems so
pointless to have to insert a dummy delay statement, would lead many
to believe that this bug was just a sloppy error, even if the real
reasons it exists are somewhat more complex.

BTW, my test results with -O3 and -Os, there is no difference in
performance between the two loops, and -Os produces code that is about
33% faster than -O3.  With -O0, the second loop is faster by an
average of 10%.  I would have thought the extra conditional would have
been costlier.

Again, thanks for the reply!
-- deadlyhead



^ permalink raw reply	[relevance 0%]

* Re: Timing code blocks
  2010-03-05  6:34  5% Timing code blocks deadlyhead
@ 2010-03-05  7:55  0% ` Dmitry A. Kazakov
  2010-03-05  8:16  0%   ` deadlyhead
  2010-03-05  8:21  0% ` Niklas Holsti
  1 sibling, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2010-03-05  7:55 UTC (permalink / raw)


On Thu, 4 Mar 2010 22:34:47 -0800 (PST), deadlyhead wrote:

> I've been trying to determine if there is any significant performance
> difference between two functionally equivalent pieces of code. I've
> done the standard thing and, using the Ada.Real_Time package, I'm
> saving the time when the code starts, then the time when the code
> ends, then examining the difference between them after the code runs.
> 
> The problem I'm having, though, is that the timing just isn't
> happening.  This code will run for 15 seconds and when I examine the
> time span, it tells me that no time passed.
> 
> Here's my actual code

This is an ancient bug, which managed to survive a number of GNAT compiler
versions.

As a workaround, add delay 0.0 at the beginning of your program:

> ----------------------------------------------------------------------
> 
> --  A test of the cost of conditionals
> 
> with Ada.Text_IO;  use Ada.Text_IO;
> with Ada.Real_Time; use Ada.Real_Time;
> procedure Conditional_Test is
> 
>    Test_Dur : constant := 100_000;

Test_Dur : constant := 10_000; -- 100_000 overflows on a 32-bit machine

>    -- We require the input/output for Duration
>    package Duration_IO is new Fixed_IO (Duration);
>    use Duration_IO;
> 
> 
>    Start_Time : Time;
>    End_Time   : Time;
>    Is_Even    : Boolean;
>    Is_Odd     : Boolean;
>    Junk       : Positive;
>    Junk_In    : Natural := 0;
> 
> begin   -- Conditional_test

delay 0.0; -- Wake up that dozing Ada RTL!

>    Put_Line ("---Starting per-branch assignment test---");
> 
>    Start_Time := Clock;
>    for I in 1 .. Test_Dur loop
>       if I rem 2 = 1 then
>          Is_Odd  := True;
>       else
>          Is_Even := True;
>       end if;
> 
>       if Is_Even then
>          for J in reverse 1 .. Test_Dur loop
>             Junk_In := Junk_In + 1;
>          end loop;
>          Junk := I;
>       elsif Is_Odd then
>          for J in reverse 1 .. Test_Dur loop
>             Junk_In := Junk_In + 1;
>          end loop;
>          Junk := I;
>       end if;
> 
>       Is_Even := False;
>       Is_Odd  := False;
>    end loop;
>    End_Time := Clock;
> 
>    Put ("Assignment within each branch took ");
>    Put (To_Duration (End_Time - Start_Time), 1, 12, 0);
>    New_Line (2);
> 
> 
>    Put_Line ("---Starting combined-branch assignment test---");
> 
>    Start_Time := Clock;
>    for I in 1 .. Test_Dur loop
>       if I rem 2 = 1 then
>          Is_Odd  := True;
>       else
>          Is_Even := True;
>       end if;
> 
>       if Is_Even then
>          for J in reverse 1 .. Test_Dur loop
>             Junk_In := Junk_In + 1;
>          end loop;
>       elsif Is_Odd then
>          for J in reverse 1 .. Test_Dur loop
>             Junk_In := Junk_In + 1;
>          end loop;
>       end if;
> 
>       if Is_Even or Is_Odd then
>          Junk := I;
>       end if;
> 
>       Is_Even := False;
>       Is_Odd  := False;
>    end loop;
>    End_Time := Clock;
> 
>    Put ("Assignment outside of the branching took ");
>    Put (To_Duration (End_Time - Start_Time), 1, 12, 0);
>    New_Line (2);
> 
> end Conditional_Test;

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Timing code blocks
@ 2010-03-05  6:34  5% deadlyhead
  2010-03-05  7:55  0% ` Dmitry A. Kazakov
  2010-03-05  8:21  0% ` Niklas Holsti
  0 siblings, 2 replies; 200+ results
From: deadlyhead @ 2010-03-05  6:34 UTC (permalink / raw)


I've been trying to determine if there is any significant performance
difference between two functionally equivalent pieces of code. I've
done the standard thing and, using the Ada.Real_Time package, I'm
saving the time when the code starts, then the time when the code
ends, then examining the difference between them after the code runs.

The problem I'm having, though, is that the timing just isn't
happening.  This code will run for 15 seconds and when I examine the
time span, it tells me that no time passed.

Here's my actual code

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

--  A test of the cost of conditionals

with Ada.Text_IO;  use Ada.Text_IO;
with Ada.Real_Time; use Ada.Real_Time;
procedure Conditional_Test is

   Test_Dur : constant := 100_000;

   -- We require the input/output for Duration
   package Duration_IO is new Fixed_IO (Duration);
   use Duration_IO;


   Start_Time : Time;
   End_Time   : Time;
   Is_Even    : Boolean;
   Is_Odd     : Boolean;
   Junk       : Positive;
   Junk_In    : Natural := 0;

begin   -- Conditional_test

   Put_Line ("---Starting per-branch assignment test---");

   Start_Time := Clock;
   for I in 1 .. Test_Dur loop
      if I rem 2 = 1 then
         Is_Odd  := True;
      else
         Is_Even := True;
      end if;

      if Is_Even then
         for J in reverse 1 .. Test_Dur loop
            Junk_In := Junk_In + 1;
         end loop;
         Junk := I;
      elsif Is_Odd then
         for J in reverse 1 .. Test_Dur loop
            Junk_In := Junk_In + 1;
         end loop;
         Junk := I;
      end if;

      Is_Even := False;
      Is_Odd  := False;
   end loop;
   End_Time := Clock;

   Put ("Assignment within each branch took ");
   Put (To_Duration (End_Time - Start_Time), 1, 12, 0);
   New_Line (2);


   Put_Line ("---Starting combined-branch assignment test---");

   Start_Time := Clock;
   for I in 1 .. Test_Dur loop
      if I rem 2 = 1 then
         Is_Odd  := True;
      else
         Is_Even := True;
      end if;

      if Is_Even then
         for J in reverse 1 .. Test_Dur loop
            Junk_In := Junk_In + 1;
         end loop;
      elsif Is_Odd then
         for J in reverse 1 .. Test_Dur loop
            Junk_In := Junk_In + 1;
         end loop;
      end if;

      if Is_Even or Is_Odd then
         Junk := I;
      end if;

      Is_Even := False;
      Is_Odd  := False;
   end loop;
   End_Time := Clock;

   Put ("Assignment outside of the branching took ");
   Put (To_Duration (End_Time - Start_Time), 1, 12, 0);
   New_Line (2);

end Conditional_Test;

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

The output of this code is as follows:


---Starting per-branch assignment test---
Assignment within each branch took 0.000000000000

---Starting combined-branch assignment test---
Assignment outside of the branching took 0.000000000000


Why wouldn't any time passage be registered?

I know the code above is convoluted, but I've been trying to find a
way to get _some_ timing to happen. I originally ran a test with delay
statements instead of multiple loops, and the timing worked then, but
I felt that there was a real possibility that the delay statements
could be introducing inaccuracies into the timing, with the overhead
of switching processes in the OS and there being no guarantee of
consistently resuming the code. (Ada does not guarantee that code will
resume exactly delay_time from now, it guarantees that the code will
sleep for _at least_ delay_time.)

Anyway, if I'm missing something here, I'd like to know it.  I've read
section D.8 of the ARM several times and I'm just about convinced that
something's broken in my compilers (I'm using GNAT on windows, both
the AdaCore binary and a cygwin binary, both with the same output). Is
there something that I'm missing, like the real-time clock doesn't
advance unless the program delays at some point?

I appreciate any insight.  This is baffling me.



^ permalink raw reply	[relevance 5%]

* Re: Multiple Delay alternatives : what it is useful to ?
  @ 2010-02-04 18:48  0%   ` Hibou57 (Yannick Duchêne)
  0 siblings, 0 replies; 200+ results
From: Hibou57 (Yannick Duchêne) @ 2010-02-04 18:48 UTC (permalink / raw)


On 4 fév, 05:47, "Jeffrey R. Carter" <spam.jrcarter....@spam.acm.org>
wrote:
> Ada.Calendar.Time and Ada.Real_Time.Time are 2 different time types, and an
> implementation may provide others.
>
> --
> Jeff Carter
Will have a look (I will have to come to it anyway if I want to go
further)

On 4 fév, 10:26, Jean-Pierre Rosen <ro...@adalog.fr> wrote:
> The shortest one will be triggered. Why allow several? Because the
> delays need not be static, so which is one is shorter may not be
> determined at compile time, and several time-out may correspond to
> different conditions, with different attached processing.
Ok, so that's a matter of variables (while the word “ static ” better
express things, that's true).

> > Are they some real life examples of useful multiple delays
> > alternatives ?
>
> See above ;-)
It was a good one indeed :) Thanks



^ permalink raw reply	[relevance 0%]

* Re: Multiple Delay alternatives : what it is useful to ?
  @ 2010-02-04  4:47  5% ` Jeffrey R. Carter
    1 sibling, 0 replies; 200+ results
From: Jeffrey R. Carter @ 2010-02-04  4:47 UTC (permalink / raw)


Hibou57 (Yannick Duch�ne) wrote:
> 
> By the way, a sentence is unclear to me : at 9.7.1(10), there is a �
> If a selective_accept contains more than one delay_alternative, then
> all shall be delay_relative_statements, or all shall be
> delay_until_statements for the same time type. � .... same time type ?
> I could not construe these last three words.

Ada.Calendar.Time and Ada.Real_Time.Time are 2 different time types, and an 
implementation may provide others.

-- 
Jeff Carter
"Now go away or I shall taunt you a second time."
Monty Python & the Holy Grail
07



^ permalink raw reply	[relevance 5%]

* Re: Task Priorities on Ubuntu Linux
  2009-12-09 21:20  0% ` sjw
@ 2009-12-10  8:27  0%   ` singo
  0 siblings, 0 replies; 200+ results
From: singo @ 2009-12-10  8:27 UTC (permalink / raw)


On Dec 9, 10:20 pm, sjw <simon.j.wri...@mac.com> wrote:
> On Dec 9, 2:34 pm, singo <sander.i...@gmail.com> wrote:
>
>
>
> > Hi,
>
> > Another question on the real-time annex and its implementation in
> > gnat-4.3 (Ubuntu Linux).
>
> > When I use different task priorities I get an - at least for me -
> > unexpected behavior... I have defined 10 tasks with different
> > priority. When I run my program, I expect only one task per processor
> > (this means four on my quad-core machine) to run. However,
> > unexpectedly all 10 tasks are run on my machine.
>
> > Is this because the tasks are mapped on the underlying OS (here
> > Linux), which then instead schedules the tasks of different priority
> > with some kind of time-slicing (round-robin) approach? I would
> > appreciate some clarification in this matter.
>
> > Best regards
>
> > Ingo
>
> > P.S: Here comes my example program:
>
> > pragma Task_Dispatching_Policy(FIFO_Within_Priorities);
> > pragma Queuing_Policy(Priority_Queuing);
>
> > with Ada.Text_IO;
> > use Ada.Text_IO;
>
> > with Ada.Real_Time;
> > use Ada.Real_Time;
>
> > procedure TaskPriorities is
>
> >    task type T(Id: Integer) is
> >       pragma Priority(Id);
> >    end;
>
> >    task body T is
> >    begin
> >       loop
> >          Put(Integer'Image(Id));
> >       end loop;
> >    end T;
>
> >    Task10 : T(11);
> >    Task9  : T(12);
> >    Task8  : T(13);
> >    Task7  : T(14);
> >    Task6  : T(15);
> >    Task5  : T(16);
> >    Task4  : T(17);
> >    Task3  : T(18);
> >    Task2  : T(19);
> >    Task1  : T(20);
>
> > begin
> >    null;
> > end TaskPriorities;
>
> It used to be that on Linux you would have to run as root for
> specified priorities to be respected.
>
> FWIW, on Mac OS X Dmitry's program behaves much the same as an
> ordinary user and as root: variously,
>
> $ ./taskpriorities
>  11 13 12 15 14 18 17 20 19^C
> $ ./taskpriorities
>  19 20 18 16 14^C
> $ ./taskpriorities
>  19 20 18 17^C
> $ sudo ./taskpriorities
> Password:
>  19 20 18 16 14^C

Thanks a lot for the information!

Yes, you are right! In order to get a correct behavior I have to run
the program as root (which I was not aware of). I made a small change
of Dimitri's program (I moved the 'Put' statement after the loop),
i.e.

   task body T is
      I : Integer;
   begin
      for Index in Integer'Range loop
         I := Index;
      end loop;
      Put (Integer'Image (Id));
   end T;

and then I get the following expected output:

On a machine with four cores:

> sudo ./taskpriorities
 17 18 20 19 16 15 14 13 12 11

On a machine with one core:

> sudo ./taskpriorities
 20 19 18 17 16 15 14 13 12 11

Best regards

Ingo



^ permalink raw reply	[relevance 0%]

* Re: Task Priorities on Ubuntu Linux
  2009-12-09 14:34  6% Task Priorities on Ubuntu Linux singo
  2009-12-09 15:10  6% ` Dmitry A. Kazakov
@ 2009-12-09 21:20  0% ` sjw
  2009-12-10  8:27  0%   ` singo
  1 sibling, 1 reply; 200+ results
From: sjw @ 2009-12-09 21:20 UTC (permalink / raw)


On Dec 9, 2:34 pm, singo <sander.i...@gmail.com> wrote:
> Hi,
>
> Another question on the real-time annex and its implementation in
> gnat-4.3 (Ubuntu Linux).
>
> When I use different task priorities I get an - at least for me -
> unexpected behavior... I have defined 10 tasks with different
> priority. When I run my program, I expect only one task per processor
> (this means four on my quad-core machine) to run. However,
> unexpectedly all 10 tasks are run on my machine.
>
> Is this because the tasks are mapped on the underlying OS (here
> Linux), which then instead schedules the tasks of different priority
> with some kind of time-slicing (round-robin) approach? I would
> appreciate some clarification in this matter.
>
> Best regards
>
> Ingo
>
> P.S: Here comes my example program:
>
> pragma Task_Dispatching_Policy(FIFO_Within_Priorities);
> pragma Queuing_Policy(Priority_Queuing);
>
> with Ada.Text_IO;
> use Ada.Text_IO;
>
> with Ada.Real_Time;
> use Ada.Real_Time;
>
> procedure TaskPriorities is
>
>    task type T(Id: Integer) is
>       pragma Priority(Id);
>    end;
>
>    task body T is
>    begin
>       loop
>          Put(Integer'Image(Id));
>       end loop;
>    end T;
>
>    Task10 : T(11);
>    Task9  : T(12);
>    Task8  : T(13);
>    Task7  : T(14);
>    Task6  : T(15);
>    Task5  : T(16);
>    Task4  : T(17);
>    Task3  : T(18);
>    Task2  : T(19);
>    Task1  : T(20);
>
> begin
>    null;
> end TaskPriorities;

It used to be that on Linux you would have to run as root for
specified priorities to be respected.

FWIW, on Mac OS X Dmitry's program behaves much the same as an
ordinary user and as root: variously,

$ ./taskpriorities
 11 13 12 15 14 18 17 20 19^C
$ ./taskpriorities
 19 20 18 16 14^C
$ ./taskpriorities
 19 20 18 17^C
$ sudo ./taskpriorities
Password:
 19 20 18 16 14^C



^ permalink raw reply	[relevance 0%]

* Re: Task Priorities on Ubuntu Linux
  2009-12-09 14:34  6% Task Priorities on Ubuntu Linux singo
@ 2009-12-09 15:10  6% ` Dmitry A. Kazakov
  2009-12-09 21:20  0% ` sjw
  1 sibling, 0 replies; 200+ results
From: Dmitry A. Kazakov @ 2009-12-09 15:10 UTC (permalink / raw)


On Wed, 9 Dec 2009 06:34:45 -0800 (PST), singo wrote:

> When I use different task priorities I get an - at least for me -
> unexpected behavior... I have defined 10 tasks with different
> priority. When I run my program, I expect only one task per processor
> (this means four on my quad-core machine) to run. However,
> unexpectedly all 10 tasks are run on my machine.
> 
> Is this because the tasks are mapped on the underlying OS (here
> Linux), which then instead schedules the tasks of different priority
> with some kind of time-slicing (round-robin) approach? I would
> appreciate some clarification in this matter.

No, there could be a different reason from that. You perform I/O, which
leads to task switching. Once I/O is initiated the OS completes it anyway
(if the kernel is non-preemptive for your tasks). This is what you
observed. I guess.

Try this instead:

pragma Task_Dispatching_Policy (FIFO_Within_Priorities);
pragma Queuing_Policy (Priority_Queuing);

with Ada.Text_IO;    use Ada.Text_IO;
with Ada.Real_Time;  use Ada.Real_Time;

procedure TaskPriorities is

   task type T (Id: Integer) is
      pragma Priority (Id);
   end;

   task body T is
      I : Integer;
   begin
      Put (Integer'Image (Id));
      for Index in Integer'Range loop
         I := Index;
      end loop;
   end T;
   Task10 : T (11);
   Task9  : T (12);
   Task8  : T (13);
   Task7  : T (14);
   Task6  : T (15);
   Task5  : T (16);
   Task4  : T (17);
   Task3  : T (18);
   Task2  : T (19);
   Task1  : T (20);
begin
   null;
end TaskPriorities;

It should print 20 19 (on two cores), then you would like to reset your
computer, if under Windows, because there non-preemptive priorities are the
real-time ones. They override pretty much everything, unless tasks end you
will have to reboot.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 6%]

* Task Priorities on Ubuntu Linux
@ 2009-12-09 14:34  6% singo
  2009-12-09 15:10  6% ` Dmitry A. Kazakov
  2009-12-09 21:20  0% ` sjw
  0 siblings, 2 replies; 200+ results
From: singo @ 2009-12-09 14:34 UTC (permalink / raw)


Hi,

Another question on the real-time annex and its implementation in
gnat-4.3 (Ubuntu Linux).

When I use different task priorities I get an - at least for me -
unexpected behavior... I have defined 10 tasks with different
priority. When I run my program, I expect only one task per processor
(this means four on my quad-core machine) to run. However,
unexpectedly all 10 tasks are run on my machine.

Is this because the tasks are mapped on the underlying OS (here
Linux), which then instead schedules the tasks of different priority
with some kind of time-slicing (round-robin) approach? I would
appreciate some clarification in this matter.

Best regards

Ingo

P.S: Here comes my example program:

pragma Task_Dispatching_Policy(FIFO_Within_Priorities);
pragma Queuing_Policy(Priority_Queuing);

with Ada.Text_IO;
use Ada.Text_IO;

with Ada.Real_Time;
use Ada.Real_Time;

procedure TaskPriorities is

   task type T(Id: Integer) is
      pragma Priority(Id);
   end;

   task body T is
   begin
      loop
	 Put(Integer'Image(Id));
      end loop;
   end T;

   Task10 : T(11);
   Task9  : T(12);
   Task8  : T(13);
   Task7  : T(14);
   Task6  : T(15);
   Task5  : T(16);
   Task4  : T(17);
   Task3  : T(18);
   Task2  : T(19);
   Task1  : T(20);

begin
   null;
end TaskPriorities;



^ permalink raw reply	[relevance 6%]

* Re: gnat: Execution_Time is not supported in this configuration
  2009-12-04 12:10  5% ` Georg Bauhaus
@ 2009-12-07  8:08  0%   ` singo
  0 siblings, 0 replies; 200+ results
From: singo @ 2009-12-07  8:08 UTC (permalink / raw)


On Dec 4, 1:10 pm, Georg Bauhaus <rm.dash-bauh...@futureapps.de>
wrote:

> The reason are explained in the GNAT source files.  The ones I have show
> a note, after the © box:
> ------------------------------------------------------------------------------
> --                                                                          --
> --                         GNAT RUN-TIME COMPONENTS                         --
> --                                                                          --
> --                   A D A . E X E C U T I O N _ T I M E                    --
> --                                                                          --
> --                                 S p e c                                  --
> --                                                                          --
> -- This specification is derived from the Ada Reference Manual for use with --
> -- GNAT.  In accordance with the copyright of that document, you can freely --
> -- copy and modify this specification,  provided that if you redistribute a --
> -- modified version,  any changes that you have made are clearly indicated. --
> --                                                                          --
> ------------------------------------------------------------------------------
>
> --  This unit is not implemented in typical GNAT implementations that lie on
> --  top of operating systems, because it is infeasible to implement in such
> --  environments.
>
> --  If a target environment provides appropriate support for this package
> --  then the Unimplemented_Unit pragma should be removed from this spec and
> --  an appropriate body provided.
>
> with Ada.Task_Identification;
> with Ada.Real_Time;
>
> package Ada.Execution_Time is
>    pragma Preelaborate;
>
>    pragma Unimplemented_Unit;

Thanks to all of you for your help!

Still I wonder why it is written in the GNAT reference specification
that the real time annex is fully implemented [1].

"Real-Time Systems (Annex D) The Real-Time Systems Annex is fully
implemented."

According to the ARM 'Execution Time' is part of the real-time annex
[2], so it should be implemented.

So, does "fully implemented" mean that it only in principle is fully
implemented, but that the underlying OS/hardware (in my case 64-bit
Ubuntu-Linux (9.10) on an Intel QuadCore) has to support this features
as well?

Or how do I have to read "fully implemented"?

Best regards

Ingo

[1] http://gcc.gnu.org/onlinedocs/gnat_rm/Specialized-Needs-Annexes.html#Specialized-Needs-Annexes
[2] http://www.adaic.org/standards/05rm/html/RM-D-14.html




^ permalink raw reply	[relevance 0%]

* Re: gnat: Execution_Time is not supported in this configuration
  2009-12-04 19:01  0%   ` Dmitry A. Kazakov
@ 2009-12-04 21:50  5%     ` John B. Matthews
  0 siblings, 0 replies; 200+ results
From: John B. Matthews @ 2009-12-04 21:50 UTC (permalink / raw)


In article <1wjhklygzok25.t79koxbbtlcj$.dlg@40tude.net>,
 "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote:

> On Fri, 04 Dec 2009 13:28:24 -0500, John B. Matthews wrote:
> 
> > In article 
> > <5e5d6fb5-e719-4195-925c-d1286699393d@f16g2000yqm.googlegroups.com>,
> >  singo <sander.ingo@gmail.com> wrote:
> > 
[...]
> > I defer to Dmitry A. Kazakov about Windows, but this variation 
> > produces similar results on MacOS 10.5 & Ubuntu 9.10 using GNAT 
> > 4.3.4:
> > 
> > <code>
> > with Ada.Text_IO; use Ada.Text_IO;
> > with Ada.Real_Time; use Ada.Real_Time;
> > 
> > procedure ExecutionTime is
> >    task T;
> > 
> >    task body T is
> >       Start : Time := Clock;
> >       Interval : Time_Span := Milliseconds(100);
> >    begin
> >       loop
> >          Put_Line(Duration'Image(To_Duration(Clock - Start)));
> >          delay To_Duration(Interval);
> >       end loop;
> >    end T;
> > begin
> >    null;
> > end ExecutionTime;
> > </code>
> > 
> > <console>
> > $ ./executiontime 
> >  0.000008000
> >  0.100168000
> >  0.200289000
> >  0.300409000
> >  0.400527000
> >  0.500575000
> > ...
> > </console>
> 
> Your code counts the wall clock time. On the contrary 
> Ada.Execution_Time should do the task time, i.e. the time the task 
> actually owned the processor or, maybe, the time the system did 
> something on the task's behalf.

Ah, thank you for clarifying this. Indeed, one sees the secular growth 
in the output as overhead accumulates. I meant to suggest that other 
parts of Annex D may be supported on a particular platform, even if 
Ada.Execution_Time is not.

> This package heavily depends on the OS services at least when the 
> tasks are mapped onto the OS scheduling items (like threads).
> 
> As far as I know it is impossible to implement it reasonably under 
> Windows, because the corresponding service (used by the Task Manager 
> too) counts time quants instead of the time. This causes a massive 
> systematic error if tasks are switched before they consume their 
> quants. I.e. *always* when you do I/O or communicate to other tasks. 
> The bottom line, under Windows Ada.Execution_Time can be used only 
> for tasks that do lengthy computations interrupted by only by the 
> scheduler, so that all counted quants were consumed and no time were 
> spent in uncounted quants.
> 
> I don't know, if or how, this works under Linux or Max OS.

I should have mentioned that both systems specify "pragma 
Unimplemented_Unit" in Ada.Execution_Time. On Mac OS X 10.5, 
Ada.Real_Time.Time_Span_Unit is 0.000000001, but I'm unaware of a Mac 
clock having better that microsecond resolution, as suggested in the 
output above. I'm running Linux in VirtualBox, so I suspect any results 
reflect the host OS more than anything else.

-- 
John B. Matthews
trashgod at gmail dot com
<http://sites.google.com/site/drjohnbmatthews>



^ permalink raw reply	[relevance 5%]

* Re: gnat: Execution_Time is not supported in this configuration
  2009-12-04 18:28  6% ` John B. Matthews
@ 2009-12-04 19:01  0%   ` Dmitry A. Kazakov
  2009-12-04 21:50  5%     ` John B. Matthews
  0 siblings, 1 reply; 200+ results
From: Dmitry A. Kazakov @ 2009-12-04 19:01 UTC (permalink / raw)


On Fri, 04 Dec 2009 13:28:24 -0500, John B. Matthews wrote:

> In article 
> <5e5d6fb5-e719-4195-925c-d1286699393d@f16g2000yqm.googlegroups.com>,
>  singo <sander.ingo@gmail.com> wrote:
> 
>> I have recently become very interested of Ada 2005, and it's 
>> real-time annex. However, as a new user of Ada I face some problems 
>> with the software.
>> 
>> I cannot get the package Ada.Execution_Time to work with gnat, 
>> although the gnat documentation says that the real-time annex is 
>> fully supported... I use the gnat version 4.4 on a Ubuntu 9.10 
>> distribution.
>> 
>> The typical error message I get is
>> 
>> gcc -c executiontime.adb
>> Execution_Time is not supported in this configuration
>> compilation abandoned
> 
> Georg Bauhaus has helpfully referred you to comments in 
> Ada.Execution_Time.
> 
>> How can I configure gnat to support the Ada.Execution_Time package?
> 
> I defer to Dmitry A. Kazakov about Windows, but this variation produces 
> similar results on MacOS 10.5 & Ubuntu 9.10 using GNAT 4.3.4:
> 
> <code>
> with Ada.Text_IO; use Ada.Text_IO;
> with Ada.Real_Time; use Ada.Real_Time;
> 
> procedure ExecutionTime is
>    task T;
> 
>    task body T is
>       Start : Time := Clock;
>       Interval : Time_Span := Milliseconds(100);
>    begin
>       loop
>          Put_Line(Duration'Image(To_Duration(Clock - Start)));
>          delay To_Duration(Interval);
>       end loop;
>    end T;
> begin
>    null;
> end ExecutionTime;
> </code>
> 
> <console>
> $ ./executiontime 
>  0.000008000
>  0.100168000
>  0.200289000
>  0.300409000
>  0.400527000
>  0.500575000
> ...
> </console>

Your code counts the wall clock time. On the contrary Ada.Execution_Time
should do the task time, i.e. the time the task actually owned the
processor or, maybe, the time the system did something on the task's
behalf.

This package heavily depends on the OS services at least when the tasks are
mapped onto the OS scheduling items (like threads).

As far as I know it is impossible to implement it reasonably under Windows,
because the corresponding service (used by the Task Manager too) counts
time quants instead of the time. This causes a massive systematic error if
tasks are switched before they consume their quants. I.e. *always* when you
do I/O or communicate to other tasks. The bottom line, under Windows
Ada.Execution_Time can be used only for tasks that do lengthy computations
interrupted by only by the scheduler, so that all counted quants were
consumed and no time were spent in uncounted quants.

I don't know, if or how, this works under Linux or Max OS.

-- 
Regards,
Dmitry A. Kazakov
http://www.dmitry-kazakov.de



^ permalink raw reply	[relevance 0%]

* Re: gnat: Execution_Time is not supported in this configuration
    2009-12-04 12:10  5% ` Georg Bauhaus
@ 2009-12-04 18:28  6% ` John B. Matthews
  2009-12-04 19:01  0%   ` Dmitry A. Kazakov
  1 sibling, 1 reply; 200+ results
From: John B. Matthews @ 2009-12-04 18:28 UTC (permalink / raw)


In article 
<5e5d6fb5-e719-4195-925c-d1286699393d@f16g2000yqm.googlegroups.com>,
 singo <sander.ingo@gmail.com> wrote:

> I have recently become very interested of Ada 2005, and it's 
> real-time annex. However, as a new user of Ada I face some problems 
> with the software.
> 
> I cannot get the package Ada.Execution_Time to work with gnat, 
> although the gnat documentation says that the real-time annex is 
> fully supported... I use the gnat version 4.4 on a Ubuntu 9.10 
> distribution.
> 
> The typical error message I get is
> 
> gcc -c executiontime.adb
> Execution_Time is not supported in this configuration
> compilation abandoned

Georg Bauhaus has helpfully referred you to comments in 
Ada.Execution_Time.

> How can I configure gnat to support the Ada.Execution_Time package?

I defer to Dmitry A. Kazakov about Windows, but this variation produces 
similar results on MacOS 10.5 & Ubuntu 9.10 using GNAT 4.3.4:

<code>
with Ada.Text_IO; use Ada.Text_IO;
with Ada.Real_Time; use Ada.Real_Time;

procedure ExecutionTime is
   task T;

   task body T is
      Start : Time := Clock;
      Interval : Time_Span := Milliseconds(100);
   begin
      loop
         Put_Line(Duration'Image(To_Duration(Clock - Start)));
         delay To_Duration(Interval);
      end loop;
   end T;
begin
   null;
end ExecutionTime;
</code>

<console>
$ ./executiontime 
 0.000008000
 0.100168000
 0.200289000
 0.300409000
 0.400527000
 0.500575000
...
</console>

-- 
John B. Matthews
trashgod at gmail dot com
<http://sites.google.com/site/drjohnbmatthews>



^ permalink raw reply	[relevance 6%]

* Re: gnat: Execution_Time is not supported in this configuration
  @ 2009-12-04 12:10  5% ` Georg Bauhaus
  2009-12-07  8:08  0%   ` singo
  2009-12-04 18:28  6% ` John B. Matthews
  1 sibling, 1 reply; 200+ results
From: Georg Bauhaus @ 2009-12-04 12:10 UTC (permalink / raw)


singo schrieb:

> I cannot get the package Ada.Execution_Time to work with gnat,
> although the gnat documentation says that the real-time annex is fully
> supported... I use the gnat version 4.4 on a Ubuntu 9.10 distribution.

The reason are explained in the GNAT source files.  The ones I have show
a note, after the � box:
------------------------------------------------------------------------------
--                                                                          --
--                         GNAT RUN-TIME COMPONENTS                         --
--                                                                          --
--                   A D A . E X E C U T I O N _ T I M E                    --
--                                                                          --
--                                 S p e c                                  --
--                                                                          --
-- This specification is derived from the Ada Reference Manual for use with --
-- GNAT.  In accordance with the copyright of that document, you can freely --
-- copy and modify this specification,  provided that if you redistribute a --
-- modified version,  any changes that you have made are clearly indicated. --
--                                                                          --
------------------------------------------------------------------------------

--  This unit is not implemented in typical GNAT implementations that lie on
--  top of operating systems, because it is infeasible to implement in such
--  environments.

--  If a target environment provides appropriate support for this package
--  then the Unimplemented_Unit pragma should be removed from this spec and
--  an appropriate body provided.

with Ada.Task_Identification;
with Ada.Real_Time;

package Ada.Execution_Time is
   pragma Preelaborate;

   pragma Unimplemented_Unit;





^ permalink raw reply	[relevance 5%]

Results 1-200 of ~600   | reverse | options above
-- pct% links below jump to the message on this page, permalinks otherwise --
2009-12-04 11:09     gnat: Execution_Time is not supported in this configuration singo
2009-12-04 12:10  5% ` Georg Bauhaus
2009-12-07  8:08  0%   ` singo
2009-12-04 18:28  6% ` John B. Matthews
2009-12-04 19:01  0%   ` Dmitry A. Kazakov
2009-12-04 21:50  5%     ` John B. Matthews
2009-12-09 14:34  6% Task Priorities on Ubuntu Linux singo
2009-12-09 15:10  6% ` Dmitry A. Kazakov
2009-12-09 21:20  0% ` sjw
2009-12-10  8:27  0%   ` singo
2010-02-04  3:47     Multiple Delay alternatives : what it is useful to ? Hibou57 (Yannick Duchêne)
2010-02-04  4:47  5% ` Jeffrey R. Carter
2010-02-04  9:26     ` Jean-Pierre Rosen
2010-02-04 18:48  0%   ` Hibou57 (Yannick Duchêne)
2010-03-05  6:34  5% Timing code blocks deadlyhead
2010-03-05  7:55  0% ` Dmitry A. Kazakov
2010-03-05  8:16  0%   ` deadlyhead
2010-03-05  8:49  0%     ` Dmitry A. Kazakov
2010-03-05 12:41  0%       ` Alex Mentis
2010-03-05 23:35             ` Simon Wright
2010-03-06  9:50               ` Georg Bauhaus
2010-03-06 12:06                 ` Simon Wright
2010-03-07  1:02                   ` Georg Bauhaus
2010-03-08 12:16  6%                 ` Alex Mentis
2010-03-05  8:21  0% ` Niklas Holsti
2010-11-08 20:34     GNAT's Protected Objects Jeffrey Carter
2010-11-08 21:38     ` Anh Vo
2010-11-08 22:32  7%   ` Jeffrey Carter
2010-11-09  1:50  0%     ` Anh Vo
2010-12-12  4:19  6% Ada.Execution_Time BrianG
2010-12-12  5:27  8% ` Ada.Execution_Time Jeffrey Carter
2010-12-12 16:56  8% ` Ada.Execution_Time Jeffrey Carter
2010-12-12 21:59  0%   ` Ada.Execution_Time BrianG
2010-12-13  9:28         ` Ada.Execution_Time Georg Bauhaus
2010-12-15  0:16  5%       ` Ada.Execution_Time BrianG
2010-12-15 19:17  6%         ` Ada.Execution_Time jpwoodruff
2010-12-15 21:42  0%           ` Ada.Execution_Time Pascal Obry
2010-12-15 22:05  5%         ` Ada.Execution_Time Randy Brukardt
2010-12-16  1:14  0%           ` Ada.Execution_Time BrianG
2010-12-16  8:45               ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-16 16:49                 ` Ada.Execution_Time BrianG
2010-12-16 17:52  6%               ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-17  8:49  5%                 ` Ada.Execution_Time Niklas Holsti
2010-12-17  9:32                       ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-17 11:50                         ` Ada.Execution_Time Niklas Holsti
2010-12-17 13:10                           ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-18 21:20                             ` Ada.Execution_Time Niklas Holsti
2010-12-19  9:57                               ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-25 11:31                                 ` Ada.Execution_Time Niklas Holsti
2010-12-26 10:25  5%                               ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-27 12:44  3%                                 ` Ada.Execution_Time Niklas Holsti
2010-12-27 15:28  4%                                   ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-27 20:11  2%                                     ` Ada.Execution_Time Niklas Holsti
2010-12-27 21:34  5%                                       ` Ada.Execution_Time Simon Wright
2010-12-28 10:01  0%                                         ` Ada.Execution_Time Niklas Holsti
2010-12-27 21:53  0%                                       ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-28 14:14  4%                                         ` Ada.Execution_Time Simon Wright
2010-12-28 15:08  6%                                           ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-28 16:18  0%                                             ` Ada.Execution_Time Simon Wright
2010-12-28 16:34  0%                                               ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-31  0:40  0%                                             ` Ada.Execution_Time BrianG
2010-12-31  9:09  0%                                               ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-27 22:11                                   ` Ada.Execution_Time Randy Brukardt
2010-12-29 12:48  2%                                 ` Ada.Execution_Time Niklas Holsti
2010-12-29 14:30  3%                                   ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-29 16:19                                         ` Ada.Execution_Time (see below)
2010-12-29 16:51  5%                                       ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-29 19:57  0%                                         ` Ada.Execution_Time (see below)
2010-12-29 20:32  5%                                     ` Ada.Execution_Time Niklas Holsti
2010-12-30  5:06  0%                                   ` Ada.Execution_Time Randy Brukardt
2010-12-30 23:49                                         ` Ada.Execution_Time Niklas Holsti
2010-12-31 23:34                                           ` Ada.Execution_Time Randy Brukardt
2011-01-01 13:52                                             ` Ada.Execution_Time Niklas Holsti
2011-01-01 14:42                                               ` Ada.Execution_Time Simon Wright
2011-01-01 16:01  7%                                             ` Ada.Execution_Time Simon Wright
2011-01-01 19:18  0%                                               ` Ada.Execution_Time Niklas Holsti
2010-12-17  8:59  6%         ` Ada.Execution_Time anon
2010-12-19  3:07  0%           ` Ada.Execution_Time BrianG
2010-12-19  4:01  8%             ` Ada.Execution_Time Vinzent Hoefler
2010-12-19 11:00  7%               ` Ada.Execution_Time Niklas Holsti
2010-12-19 12:27  6%               ` Ada.Execution_Time Dmitry A. Kazakov
2010-12-19 22:54  0%             ` Ada.Execution_Time anon
2010-12-20  3:14                   ` Ada.Execution_Time BrianG
2010-12-22 14:30  6%                 ` Ada.Execution_Time anon
2010-12-22 20:09  4%                   ` Ada.Execution_Time BrianG
2010-12-26 10:25  6% Task execution time test Dmitry A. Kazakov
2010-12-29 23:00     ` h_poincare
2010-12-30  8:54  5%   ` Dmitry A. Kazakov
2010-12-27 18:26  7% An Example for Ada.Execution_Time anon
2010-12-28  2:31  5% ` BrianG
2010-12-28 13:43  0%   ` anon
2010-12-29  3:10  4%   ` Randy Brukardt
2010-12-30 23:51  5%     ` BrianG
2010-12-31  9:11           ` Dmitry A. Kazakov
2010-12-31 12:42             ` Niklas Holsti
2010-12-31 14:15               ` Dmitry A. Kazakov
2010-12-31 18:57                 ` Niklas Holsti
2011-01-01 13:39  4%               ` Dmitry A. Kazakov
2011-01-01 20:25  7%                 ` Niklas Holsti
2011-01-03  8:50  7%                   ` Dmitry A. Kazakov
2011-01-01  0:07  4%       ` Randy Brukardt
2010-12-30  8:54  6% Task execution time 2 Dmitry A. Kazakov
2011-02-03  5:52     How do I write directly to a memory address? Syntax Issues
2011-02-09 20:29     ` Shark8
2011-02-09 21:26       ` Hyman Rosen
2011-02-09 21:40         ` Shark8
2011-02-09 22:09           ` Hyman Rosen
2011-02-09 22:23             ` Shark8
2011-02-09 22:31               ` Hyman Rosen
2011-02-09 23:07                 ` Shark8
2011-02-09 23:24                   ` Hyman Rosen
2011-02-10  0:35                     ` Shark8
2011-02-10 15:38                       ` Hyman Rosen
2011-02-10 17:05                         ` Shark8
2011-02-10 17:40                           ` Hyman Rosen
2011-02-11  8:26                             ` Ludovic Brenta
2011-02-11 16:10                               ` Hyman Rosen
2011-02-11 18:43                                 ` Vinzent Hoefler
2011-02-11 18:57                                   ` Hyman Rosen
2011-02-11 20:15                                     ` Vinzent Hoefler
2011-02-11 20:29                                       ` Hyman Rosen
2011-02-11 20:42  5%                                     ` Vinzent Hoefler
2011-02-18 22:52     Need some light on using Ada or not Luis P. Mendes
2011-02-19 13:07     ` Brian Drummond
2011-02-19 14:36       ` Georg Bauhaus
2011-02-19 18:25         ` Brian Drummond
2011-02-20 14:34           ` Brian Drummond
2011-02-20 15:45             ` jonathan
2011-02-20 19:49               ` Pascal Obry
2011-02-20 19:57                 ` Brian Drummond
2011-02-20 22:47                   ` Simon Wright
2011-02-21 12:52                     ` Brian Drummond
2011-02-22  2:15  2%                   ` Shark8
2012-03-01 13:06     Any leap year issues caused by Ada yesterday? Georg Bauhaus
2012-03-05 11:07     ` tonyg
2012-03-05 15:59       ` Shark8
2012-03-05 18:03         ` Dmitry A. Kazakov
2012-03-05 18:30           ` Simon Wright
2012-03-05 20:17             ` Dmitry A. Kazakov
2012-03-05 20:56  5%           ` Simon Wright
2012-03-06  8:47  0%             ` Dmitry A. Kazakov
2012-03-06  9:20                   ` Simon Wright
2012-03-06 10:07                     ` Dmitry A. Kazakov
2012-03-06 16:46                       ` Simon Wright
2012-03-06 17:37                         ` Dmitry A. Kazakov
2012-03-06 17:59                           ` Simon Wright
2012-03-06 19:18                             ` Dmitry A. Kazakov
2012-03-06 20:22  5%                           ` Simon Wright
2012-03-06 21:19     Ada and linux real time slos
2012-03-07  8:23     ` Dmitry A. Kazakov
2012-03-07 12:10  4%   ` slos
2012-03-07 14:18  6%     ` Dmitry A. Kazakov
2012-03-08  2:38           ` Eilie
2012-03-08 12:04             ` Simon Clubley
2012-03-08 21:45               ` slos
2012-03-15  2:35                 ` BrianG
2012-03-16 20:36                   ` slos
2012-03-17 12:34                     ` Simon Wright
2012-03-17 15:50                       ` Simon Wright
2012-03-18 22:03  6%                     ` slos
2012-06-10 19:33     Practicalities of Ada for app development Dmitry A. Kazakov
2012-06-10 21:36     ` Nomen Nescio
2012-06-11  8:22       ` Dmitry A. Kazakov
2012-06-11 14:27         ` Georg Bauhaus
2012-06-11 14:43           ` Dmitry A. Kazakov
2012-06-11 17:14             ` Georg Bauhaus
2012-06-11 18:38               ` Dmitry A. Kazakov
2012-06-11 20:50                 ` Georg Bauhaus
2012-06-12  7:55                   ` Dmitry A. Kazakov
2012-06-12  9:48                     ` Georg Bauhaus
2012-06-12 11:44  4%                   ` Dmitry A. Kazakov
2012-06-29  9:17     GNAT (GCC) Profile Guided Compilation Keean Schupke
2012-06-29 12:39     ` gautier_niouzes
2012-06-29 12:52       ` Keean Schupke
2012-06-29 14:14         ` gautier_niouzes
2012-06-29 15:05           ` gautier_niouzes
2012-06-29 17:03             ` Keean Schupke
2012-07-01 17:45  4%           ` Georg Bauhaus
2012-07-01 22:57  0%             ` Keean Schupke
2012-07-20 17:18  5% Ada.Calendar Question awdorrin
2012-07-20 17:59  0% ` Adam Beneschan
2012-07-23 21:42     Ada.Calendar and NTP (and Unix Epoch) erlo
2012-07-23 22:07     ` Adam Beneschan
     [not found]       ` <5s8s08lv6dj1i4tkb99roq9roifsgr44vd@invalid.netcom.com>
2012-07-24  7:11  5%     ` Dmitry A. Kazakov
2012-07-24  7:50  0%       ` erlo.haugen
2012-07-24  8:14  0%         ` Dmitry A. Kazakov
2012-07-24  7:24       ` erlo.haugen
2012-07-24 16:26         ` Adam Beneschan
2012-07-24 18:28  4%       ` Dmitry A. Kazakov
2012-07-24 19:07  5%         ` Adam Beneschan
2012-07-24 20:17  4%           ` Dmitry A. Kazakov
2012-07-24 19:43  0%         ` Vasiliy Molostov
2013-01-17 10:33     Numerical calculations: Why not use fixed point types for everything? Ada novice
2013-01-17 16:25     ` Adam Beneschan
2013-01-18  9:17       ` Ada novice
2013-01-18 18:15         ` Dennis Lee Bieber
2013-01-18 18:59           ` Adam Beneschan
2013-01-19  4:41             ` Dennis Lee Bieber
2013-01-19  6:26  8%           ` Jeffrey Carter
2013-01-24 10:55  0%             ` Ada novice
2013-03-07 18:04     Ada and OpenMP Rego, P.
2013-03-07 22:52     ` Simon Wright
2013-03-08 21:37  5%   ` Brad Moore
2013-03-07 20:04     Ludovic Brenta
2013-03-07 22:22     ` Peter C. Chapin
2013-03-07 23:43       ` Georg Bauhaus
2013-03-08 10:18  6%     ` Georg Bauhaus
2013-08-28 11:49  8% Anonymous access types are evil, why? ake.ragnar.dahlgren
2013-08-30 16:16  6% ` Gerhard Rummel
2014-02-06  0:53     Raspberry Pi, Real-Time and Ada Rego, P.
2014-02-06  7:50     ` Stephen Leake
2014-02-06 21:04       ` Rego, P.
2014-02-07  8:42  6%     ` Dmitry A. Kazakov
2014-02-07 12:34  0%       ` Rego, P.
2014-02-07 23:11  8%       ` Rego, P.
2014-02-08  8:56  0%         ` Dmitry A. Kazakov
2014-06-03  1:37     a new language, designed for safety ! Nasser M. Abbasi
2014-06-09 10:03     ` Pascal Obry
2014-06-10  9:36       ` Stephen Leake
2014-06-10 12:28         ` Simon Clubley
2014-06-10 12:42           ` Lucretia
2014-06-10 12:50             ` J-P. Rosen
2014-06-10 13:00               ` Lucretia
2014-06-10 14:43                 ` Brad Moore
2014-06-10 15:33                   ` Lucretia
2014-06-10 19:49                     ` J-P. Rosen
2014-06-10 22:09                       ` Luke A. Guest
2014-06-16 16:22                         ` Randy Brukardt
2014-06-16 17:11                           ` Ada platforms and pricing, was: " Simon Clubley
2014-06-17 19:34                             ` Randy Brukardt
2014-06-18 19:57                               ` Simon Clubley
2014-06-19  3:46                                 ` Randy Brukardt
2014-06-22 19:50                                   ` Simon Clubley
2014-06-22 23:38  4%                                 ` Randy Brukardt
2014-06-24 12:13  0%                                   ` Simon Clubley
2014-06-15 10:10  6% Termination of periodic tasks Natasha Kerensikova
2014-07-04 17:23     Benchmark Ada, please Victor Porton
2014-07-05 12:34  5% ` Guillaume Foliard
2014-07-05 13:00  0%   ` Niklas Holsti
2014-08-08 11:21  6% ARM Compiler Locks Up on Declaration of Timing_Event williamjthomas7777
2014-08-08 12:46  0% ` williamjthomas7777
2014-08-13  6:24  7% Trouble with Timers on the ARM williamjthomas7777
2014-08-26 22:38     STM32F4 Discovery, communication and libraries roy.emmerich
2014-08-27 13:08     ` Dennis Lee Bieber
2014-08-27 16:03       ` Roy Emmerich
2014-08-28  1:48         ` Dennis Lee Bieber
2014-08-28 10:12           ` Roy Emmerich
2014-08-28 13:00             ` Dmitry A. Kazakov
2014-08-28 16:28               ` Mike Silva
2014-08-28 20:09                 ` Dmitry A. Kazakov
2014-08-28 21:17                   ` Niklas Holsti
2014-08-29  7:41                     ` Dmitry A. Kazakov
2014-08-29 16:31                       ` Niklas Holsti
2014-08-29 16:47                         ` Roy Emmerich
2014-08-29 19:41  3%                       ` Niklas Holsti
2014-08-30 22:00  0%                         ` Roy Emmerich
2014-09-01 20:15  6%                           ` Niklas Holsti
2014-11-19  2:51     how to analyze clock drift Emanuel Berg
2014-11-19  9:01     ` Dmitry A. Kazakov
2014-11-19 22:12       ` Emanuel Berg
2014-11-20  9:42         ` Dmitry A. Kazakov
2014-11-20 20:41           ` Emanuel Berg
2014-11-20 21:27             ` Dmitry A. Kazakov
2014-11-20 21:54               ` Emanuel Berg
2014-11-21  2:27                 ` Dennis Lee Bieber
2014-11-21  3:02                   ` Emanuel Berg
2014-11-21 16:49                     ` Dennis Lee Bieber
2014-11-21 21:06                       ` Emanuel Berg
2014-11-22 18:18                         ` Dennis Lee Bieber
2014-11-23 20:15                           ` Emanuel Berg
2014-11-24  1:15  4%                         ` Dennis Lee Bieber
2014-12-23 21:21     Duration for GNAT on ARM Simon Wright
2014-12-23 22:42     ` Dmitry A. Kazakov
2014-12-23 22:52  5%   ` J-P. Rosen
2014-12-24  0:27  8%     ` Simon Wright
2014-12-24  9:40  4%       ` Simon Wright
2014-12-24  0:04  5%   ` Simon Wright
2015-01-18 23:15     Protected handlers & entry bodies Simon Wright
2015-01-19 20:18     ` Randy Brukardt
2015-01-19 21:36       ` Simon Wright
2015-01-20 22:05         ` Randy Brukardt
2015-01-20 22:46  5%       ` Simon Wright
2015-01-21 20:39  0%         ` Randy Brukardt
2015-01-25 16:41  3% ANN: gcc 4.9.1bis for Darwin Simon Wright
2015-01-27 16:09     gnat ARM - predefined packages RasikaSrinivasan
2015-01-27 16:49     ` Simon Wright
2015-01-27 16:50       ` Simon Wright
2015-01-27 18:29         ` RasikaSrinivasan
2015-01-27 21:55           ` Simon Wright
2015-01-28  7:03             ` Egil H H
2015-01-28  7:52               ` Simon Wright
2015-01-28  8:41                 ` J-P. Rosen
2015-01-28 13:11                   ` Simon Wright
2015-01-28 17:30  5%                 ` RasikaSrinivasan
2015-02-15 16:21  7% [Bounded] Vectors, reference types, and the secondary stack Simon Wright
2015-07-27 14:28     Running a preprocessor from GPS? EGarrulo
2015-07-27 20:26     ` Randy Brukardt
2015-07-28 11:36       ` EGarrulo
2015-07-28 21:12         ` Randy Brukardt
2015-07-29  6:46           ` Simon Wright
2015-07-29 19:57             ` Randy Brukardt
2015-07-29 20:38               ` Simon Wright
2015-07-30 15:13                 ` EGarrulo
2015-07-30 16:15  5%               ` Simon Wright
2015-10-31 20:29     A few questions Laurent
2015-11-01 13:42  4% ` brbarkstrom
2015-11-01 13:52  0%   ` Laurent
2015-12-31  4:15     Abortable Timed Action T.G.
2015-12-31  6:40     ` Anh Vo
2015-12-31  7:32       ` T.G.
2015-12-31 16:21         ` Anh Vo
2015-12-31 18:09  5%       ` T.G.
2016-01-06 21:14  0%         ` Anh Vo
2016-01-08 20:24  4%           ` T.G.
2016-02-07 22:45  4% ANN: Cortex GNAT RTS 20160207 Simon Wright
2016-03-14 17:42  5% ANN: Cortex GNAT RTS 20160314 Simon Wright
2016-03-30 15:35     Roundtrip latency problem using Gnoga, on Linux, when testing at localhost address Olivier Henley
2016-03-31  4:47     ` rieachus
2016-03-31  5:23       ` Jeffrey R. Carter
2016-03-31  7:38         ` Dmitry A. Kazakov
2016-03-31 17:02  4%       ` Olivier Henley
2016-03-31 17:44  4%         ` Dmitry A. Kazakov
2016-05-22 14:20  4% ANN: Cortex GNAT RTS 20160522 Simon Wright
2016-05-24 14:22  5% Launching background job from Ada.Real_Time.Timing_Events Alejandro R. Mosteo
2016-05-24 14:39  6% ` Mark Lorenzen
2016-05-24 15:06  6%   ` Alejandro R. Mosteo
2016-05-24 22:21  6%   ` Jeffrey R. Carter
2016-06-02 21:13  6%     ` Alejandro R. Mosteo
2016-06-02 23:16  6%       ` Jeffrey R. Carter
2016-05-24 23:52  5% ` Jeffrey R. Carter
2016-06-02 21:22  6%   ` Alejandro R. Mosteo
2016-05-25  7:23  5% ` Dmitry A. Kazakov
2016-06-02 21:25  6%   ` Alejandro R. Mosteo
2016-06-03  7:26  5%     ` Dmitry A. Kazakov
2016-06-03 10:03  6%       ` Alejandro R. Mosteo
2016-06-03 12:15  5%         ` Dmitry A. Kazakov
2016-08-02 14:38     Win32. Task or CreateThread George J
2016-08-03 20:31  9% ` Aurele
2016-08-04  2:41  0%   ` George J
2016-10-12 14:23  8% Gnat Sockets - UDP timeout too short ahlan
2016-11-04  8:48  0% ` ahlan.marriott
2016-12-05 20:36     Ada features supported by SPARK 2014 pault.eg
2016-12-05 22:01     ` Daniel King
2016-12-06  9:17       ` Simon Wright
2016-12-06 13:26  7%     ` Daniel King
2016-12-10 15:40  6% Building / Modifying the RTS for Cortex M. Enzmann
2016-12-10 16:17  0% ` Simon Wright
2016-12-11 16:58  0%   ` M. Enzmann
2016-12-25  9:23  6% Default values Simon Wright
2017-06-08 10:36  7% GNAT.Sockets Streaming inefficiency masterglob
2017-07-25 23:19  2% Real tasking problems with Ada Robert Eachus
2017-07-26 19:42     ` sbelmont700
2017-07-27  2:00  4%   ` Robert Eachus
2017-08-01  4:41  0% ` Randy Brukardt
2017-08-03  5:45     Community Input for the Maintenance and Revision of the Ada Programming Language Randy Brukardt
2017-10-02 10:06     ` reinert
2017-10-02 15:02       ` G.B.
2017-10-02 16:23         ` reinert
2017-10-02 19:14           ` Jeffrey R. Carter
2017-10-03  3:30             ` reinert
2017-10-03  6:36  5%           ` G.B.
2017-08-08 13:04  5% ANN: Cortex GNAT RTS 2017-08-08 Simon Wright
2017-11-12  5:23     About protected objects: entries with barriers depending on external data = bad practice ? reinert
2017-11-12 10:02  7% ` Jeffrey R. Carter
2017-11-15 14:28 12% Ada.Real_Time.Time_Last Simon Wright
2017-11-15 20:03 12% ` Ada.Real_Time.Time_Last Niklas Holsti
2017-11-17  9:20  6%   ` Ada.Real_Time.Time_Last Simon Wright
2017-11-17 21:39  9%     ` Ada.Real_Time.Time_Last Niklas Holsti
2017-11-18 13:06  6%       ` Ada.Real_Time.Time_Last AdaMagica
2017-11-18 13:18  6%         ` Ada.Real_Time.Time_Last Niklas Holsti
2017-11-18 14:00  6%           ` Ada.Real_Time.Time_Last AdaMagica
2017-11-18 14:15  6%           ` Ada.Real_Time.Time_Last Jeffrey R. Carter
2017-11-18 15:24  4%             ` Ada.Real_Time.Time_Last Niklas Holsti
2017-11-18 16:01  6%               ` Ada.Real_Time.Time_Last Dmitry A. Kazakov
2017-11-18 17:31  6%                 ` Ada.Real_Time.Time_Last Niklas Holsti
2017-11-18 22:20  6%               ` Ada.Real_Time.Time_Last Robert A Duff
2017-11-19 10:50  4%                 ` Ada.Real_Time.Time_Last Niklas Holsti
2017-11-20  5:57  6%                 ` Ada.Real_Time.Time_Last J-P. Rosen
2019-01-29 22:03  6%       ` Ada.Real_Time.Time_Last Simon Wright
2018-07-24 11:44  5% Cortex GNAT RTS: BBC micro:bit tick rate Simon Wright
2018-09-29 20:51     SI units updated AdaMagica
2018-10-01 19:24     ` Shark8
2018-11-05  8:47  5%   ` reinert
2018-11-15 11:46  5%     ` AdaMagica
2018-12-04 15:04     Profiling Ada applications using gprof joakimds
2018-12-04 19:41  6% ` Dennis Lee Bieber
2019-02-22  8:56     Simple 4 lines hang code using Ravenscar. Its this a Gnat bug? Daniel
2019-02-22 10:01  6% ` Niklas Holsti
2019-02-22 12:48  0%   ` Daniel
2019-02-28 18:34     Gnat Problem - Freezing too soon russ lyttle
2019-02-28 21:22     ` Simon Wright
2019-02-28 22:11       ` russ lyttle
2019-03-01  0:49         ` Anh Vo
2019-03-01 14:21           ` russ lyttle
2019-03-01 16:54             ` Anh Vo
2019-03-01 21:50  6%           ` russ lyttle
2019-03-02  1:08  0%             ` Anh Vo
2019-03-02  3:55  0%               ` russ lyttle
2019-03-02  5:50  0%                 ` Anh Vo
2019-03-02 20:19  0%                   ` russ lyttle
2020-03-23 23:16  4% GNAT vs Matlab - operation on multidimensional complex matrices darek
2020-06-08 17:42  4% ` Shark8
2020-04-22 11:34     Scheduling behaviour issue Simon Wright
2020-04-23 11:48  8% ` Simon Wright
2020-05-05 11:04     How can one record component be local and another not? hreba
2020-05-05 17:32     ` hreba
2020-05-06 17:30       ` Niklas Holsti
2020-05-07  9:07         ` J-P. Rosen
2020-05-07 10:15           ` Niklas Holsti
2020-05-07 13:25  5%         ` Simon Wright
2020-12-09 12:30 13% Ada.Real_Time.Time_First Simon Wright
2020-12-09 13:16  6% ` Ada.Real_Time.Time_First Dmitry A. Kazakov
2020-12-09 20:07  6%   ` Ada.Real_Time.Time_First Simon Wright
2020-12-09 14:21  4% ` Ada.Real_Time.Time_First Niklas Holsti
2020-12-09 20:16  6%   ` Ada.Real_Time.Time_First Simon Wright
2020-12-31 11:48     renames usage DrPi
2020-12-31 14:49     ` Jeffrey R. Carter
2020-12-31 15:55       ` DrPi
2020-12-31 18:48         ` Dmitry A. Kazakov
2021-01-01 12:39           ` DrPi
2021-01-02 16:00             ` G.B.
2021-01-02 17:22  5%           ` Simon Wright
2021-12-22  5:57  8% Ada.Numerics.Big_Numbers.Big_Integer has a limit of 300 digits? Michael Ferguson

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