comp.lang.ada
 help / color / mirror / Atom feed
* Disabling string evaluation in a logging system
@ 2010-05-18  7:48 dhenry
  2010-05-18  8:15 ` Dmitry A. Kazakov
                   ` (3 more replies)
  0 siblings, 4 replies; 20+ messages in thread
From: dhenry @ 2010-05-18  7:48 UTC (permalink / raw)


Hello,

I have a logging system controlled by a log level (let's say 0 =
disabled, 1 = errors, 2 = error + warnings, ..., 5 = all previous ones
+ debug messages).

A Logging line may look like that:

Log.Write (Text => "Blabla...", Level => 5);

Often, I'll have some formatted text, requiring string conversions and
concatenations. Example:

Log.Write ("Parameter " & To_String (Param_Name) & " Value = " &
Integer'Image (X), Log_Level);

If the Log_Level variable is set to 0 (logging disabled), the
application will still evaluate the Text parameter, before testing the
Level parameter to know if we finally must write it into the file or
not.

I'd like to avoid the string evaluation if the logging is disabled
(because it consumes CPU resources).

A possible solution would be to test the log level before the
procedure call:

if Log_Level > 0 then
  Log.Write ("Parameter " & To_String (Param_Name) & " Value = " &
Integer'Image (X), Log_Level);
end if;

But with thousands of logging lines everywhere in my application, it
will make the code quite unreadable and introduces a lot of if-test
pollution (and it's really boring to write).

In a language like C or C++, I would use the preprocessor:
#define LOG(text, level) if (level > 0) { log.write (text, level) }

I'm wondering how in Ada 95 and/or Ada 2005 I could write such a
logging system (if it's possible). The goal is that logging should not
be too intrusive in my code.

Yours,
David.



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  7:48 Disabling string evaluation in a logging system dhenry
@ 2010-05-18  8:15 ` Dmitry A. Kazakov
  2010-05-18  8:45   ` Dmitry A. Kazakov
  2010-05-18  9:45   ` Cyrille
  2010-05-18  9:32 ` Gautier write-only
                   ` (2 subsequent siblings)
  3 siblings, 2 replies; 20+ messages in thread
From: Dmitry A. Kazakov @ 2010-05-18  8:15 UTC (permalink / raw)


On Tue, 18 May 2010 00:48:38 -0700 (PDT), dhenry wrote:

> I'd like to avoid the string evaluation if the logging is disabled
> (because it consumes CPU resources).
> 
> A possible solution would be to test the log level before the
> procedure call:
> 
> if Log_Level > 0 then
>   Log.Write ("Parameter " & To_String (Param_Name) & " Value = " &
> Integer'Image (X), Log_Level);
> end if;

I am using this way, but rather as:

if Log.Level in Warning..Severe then
   Log.Write (...);
end if;

> But with thousands of logging lines everywhere in my application, it
> will make the code quite unreadable and introduces a lot of if-test
> pollution (and it's really boring to write).

I don't see much more pollution than a call to Log.Write has already
inflicted.

> I'm wondering how in Ada 95 and/or Ada 2005 I could write such a
> logging system (if it's possible). The goal is that logging should not
> be too intrusive in my code.

AFAIK, there is no way.

But if I were to make a proposal, then I would do the useless pargma Assert
useful. E.g.

   pragma Assert (Condition, Message);

[Change]
Dynamic semantics: Message is evaluated only if Condition is evaluated to
true. Then a user-defined assertion handler is called, if any (to be set by
Assertion_Policy). Otherwise Assertion_Error is propagated.

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



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  8:15 ` Dmitry A. Kazakov
@ 2010-05-18  8:45   ` Dmitry A. Kazakov
  2010-05-18  9:45   ` Cyrille
  1 sibling, 0 replies; 20+ messages in thread
From: Dmitry A. Kazakov @ 2010-05-18  8:45 UTC (permalink / raw)


On Tue, 18 May 2010 10:15:48 +0200, Dmitry A. Kazakov wrote:

> [Change]
> Dynamic semantics: Message is evaluated only if Condition is evaluated to
> true. Then a user-defined assertion handler is called, if any (to be set by
  ^^^^
False, of course


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



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  7:48 Disabling string evaluation in a logging system dhenry
  2010-05-18  8:15 ` Dmitry A. Kazakov
@ 2010-05-18  9:32 ` Gautier write-only
  2010-05-18  9:37   ` Gautier write-only
  2010-05-18 11:27   ` Gautier write-only
  2010-05-18 10:13 ` stefan-lucks
  2010-05-18 18:40 ` tmoran
  3 siblings, 2 replies; 20+ messages in thread
From: Gautier write-only @ 2010-05-18  9:32 UTC (permalink / raw)


On 18 Mai, 09:48, dhenry <tfc.d...@gmail.com> wrote:

> In a language like C or C++, I would use the preprocessor:
> #define LOG(text, level) if (level > 0) { log.write (text, level) }
>
> I'm wondering how in Ada 95 and/or Ada 2005 I could write such a
> logging system (if it's possible). The goal is that logging should not
> be too intrusive in my code.

Yes. You can get the same in (and within) Ada with the magic of the
Inline pragma.
Gnatchop the following:

--8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<---
package Log is
  procedure Write (Text: String; Level: Natural);
  pragma Inline(Write);
end Log;
--
with Ada.Text_IO;
package body Log is
  procedure Write (Text: String; Level: Natural) is
  begin
    if Level > 0 then
      Ada.Text_IO.Put_Line("Log: " & Text);
    end if;
  end Write;
end Log;
--
with Log;
procedure Test_Opti_inline is
begin
  Log.Write (Text => "Blabla...", Level => 5);
  Log.Write (Text => "No no no!", Level => 0);
end;
--8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<-----8<---
Then:
gcc -S -gnatn test_opti_inline.adb
The string "No no no!" doesn't even appear in the assembler
listing :-)
HTH
______________________________________________________________
Gautier's Ada programming -- http://gautiersblog.blogspot.com/
NB: For a direct answer, e-mail address on the following web site:
http://www.fechtenafz.ethz.ch/wm_email.htm



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  9:32 ` Gautier write-only
@ 2010-05-18  9:37   ` Gautier write-only
  2010-05-18 11:27   ` Gautier write-only
  1 sibling, 0 replies; 20+ messages in thread
From: Gautier write-only @ 2010-05-18  9:37 UTC (permalink / raw)


> gcc -S -gnatn test_opti_inline.adb

Errrh! -O2 was missing there.
It's gcc -S -O2 -gnatn test_opti_inline.adb
G.



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  8:15 ` Dmitry A. Kazakov
  2010-05-18  8:45   ` Dmitry A. Kazakov
@ 2010-05-18  9:45   ` Cyrille
  2010-05-18 10:26     ` Dmitry A. Kazakov
  1 sibling, 1 reply; 20+ messages in thread
From: Cyrille @ 2010-05-18  9:45 UTC (permalink / raw)


On May 18, 10:15 am, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:

> But if I were to make a proposal, then I would do the useless pargma Assert
> useful. E.g.
>
>    pragma Assert (Condition, Message);
>
> [Change]
> Dynamic semantics: Message is evaluated only if Condition is evaluated to
> true. Then a user-defined assertion handler is called, if any (to be set by
> Assertion_Policy). Otherwise Assertion_Error is propagated.

something like pragma Check & Check_Policy in GNAT, right?
see http://www.adacore.com/wp-content/files/auto_update/gnat-unw-docs/html/gnat_rm_2.html#SEC18

btw, concerning logging facilities, there is a relatively complete one
provided as part of GNATColl. See
http://www.adacore.com/wp-content/files/auto_update/gnatcoll-docs/gnatcoll.html#Logging-information



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  7:48 Disabling string evaluation in a logging system dhenry
  2010-05-18  8:15 ` Dmitry A. Kazakov
  2010-05-18  9:32 ` Gautier write-only
@ 2010-05-18 10:13 ` stefan-lucks
  2010-05-18 18:17   ` Jeffrey R. Carter
  2010-05-18 18:40 ` tmoran
  3 siblings, 1 reply; 20+ messages in thread
From: stefan-lucks @ 2010-05-18 10:13 UTC (permalink / raw)


On Tue, 18 May 2010, dhenry wrote:

[...]
> Log.Write ("Parameter " & To_String (Param_Name) & " Value = " &
> Integer'Image (X), Log_Level);
> 
> If the Log_Level variable is set to 0 (logging disabled), the
> application will still evaluate the Text parameter, before testing the
> Level parameter to know if we finally must write it into the file or
> not.
[...]
> if Log_Level > 0 then
>   Log.Write ("Parameter " & To_String (Param_Name) & " Value = " &
> Integer'Image (X), Log_Level);
> end if;
> 
> But with thousands of logging lines everywhere in my application, it
> will make the code quite unreadable and introduces a lot of if-test
> pollution (and it's really boring to write).

How about the following?

package Log is 

  type Level_Type is range 0 .. 5;

  procedure Write(Message: String; 
                  Log_Level: Level_Type);

  -- The above is, what you have, so far. 
  -- The stuff below is new:

  procedure Write(Message_1: String; 
                  Message_2: String;
                  Log_Level: Level_Type);
  -- if Log_Level>0 then 
  --    Write(Message_1 & Message_2, Log_Level); 
  -- end if

  procedure Write(Message_1: String; 
                  Message_2: String;
                  Message_3: String
                  Log_Level: Level_Type);
  -- if Log_Level>0 then ... 

  ...

end Log;

If you are willing to change the order of your parameters, one flexible 
Write-procedure would suffice:

with Log;

package Flexi_Log is

  procedure Write(Log_Level: Log.Level_Type;
                  Message_1: String := "";
                  Message_2: String := "";
                  Message_3: String := "";
                  ...
                  Message_9: String := "");
  -- if Log_Level>0 then
  --   Log.Write(Message_1 & Message_2 & ... , Log_Level);
  -- end if;

end Flexi_Log;

In any case, the number of different strings to make one message is 
constant. The constant is under your control, but it is constant. If your 
support goes for up to, say, Message_9, a message for the log which 
consists of 10 or more parts may still trouble you. So change the constant 
sufficiently large that it doesn't trouble you too often ...

I hope that helps!

Stefan


-- 
------ Stefan Lucks   --  Bauhaus-University Weimar  --   Germany  ------
               Stefan dot Lucks at uni minus weimar dot de
------  I  love  the  taste  of  Cryptanalysis  in  the  morning!  ------




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

* Re: Disabling string evaluation in a logging system
  2010-05-18  9:45   ` Cyrille
@ 2010-05-18 10:26     ` Dmitry A. Kazakov
  2010-05-18 12:10       ` Georg Bauhaus
  0 siblings, 1 reply; 20+ messages in thread
From: Dmitry A. Kazakov @ 2010-05-18 10:26 UTC (permalink / raw)


On Tue, 18 May 2010 02:45:35 -0700 (PDT), Cyrille wrote:

> On May 18, 10:15�am, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
> wrote:
> 
>> But if I were to make a proposal, then I would do the useless pargma Assert
>> useful. E.g.
>>
>> � �pragma Assert (Condition, Message);
>>
>> [Change]
>> Dynamic semantics: Message is evaluated only if Condition is evaluated to
>> true. Then a user-defined assertion handler is called, if any (to be set by
>> Assertion_Policy). Otherwise Assertion_Error is propagated.
> 
> something like pragma Check & Check_Policy in GNAT, right?

Important is laziness in the evaluation of the message expression.
Switching off by compiler is rather a disadvantage, because logging is to
be configured dynamically.

BTW, it could be a statement, e.g. conditional call:

   <procedure/entry-call> when <condition>;

A similar thing is badly needed for declarations as well, e.g. awful:

   if Object in T'Class then
      declare
         T_Object : T'Class renames T'Class (Object);
      begin
         ...
      end;
   end if;

(cannot invent any good syntax for that)

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



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  9:32 ` Gautier write-only
  2010-05-18  9:37   ` Gautier write-only
@ 2010-05-18 11:27   ` Gautier write-only
  2010-05-18 12:18     ` dhenry
  1 sibling, 1 reply; 20+ messages in thread
From: Gautier write-only @ 2010-05-18 11:27 UTC (permalink / raw)


OK, I missed the point about "&", To_String etc., as the example below
shows.
If you combine Stefan's solution and the Inline pragma, it should be
fine...
Gautier
_____________
with Log;
-- Try preventing compiler from optimizing parameters out...
-- -> Dynamic data.
with Ada.Command_Line, Ada.Strings.Unbounded;
--
procedure Test_Opti_inline is
  use Ada.Strings.Unbounded;
  --
  procedure Tricky(Param_Name: Unbounded_String; X: Integer) is
  pragma Inline(Tricky);
  begin
    Log.Write (Text => "Parameter " & To_String (Param_Name) & " Value
= " & Integer'Image (X), Level => 0);
  end Tricky;
  --
  Param_Name: Unbounded_String:=
To_Unbounded_String(Ada.Command_Line.Command_Name);
  X: Integer:= Ada.Command_Line.Argument_Count;

begin
  Log.Write (Text => "Blabla...", Level => 5);
  Log.Write (Text => "No no no!", Level => 0);
  Tricky (Param_Name => Param_Name, X => X); -- Hope: this is
optimized out.
end;



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

* Re: Disabling string evaluation in a logging system
  2010-05-18 10:26     ` Dmitry A. Kazakov
@ 2010-05-18 12:10       ` Georg Bauhaus
  2010-05-18 12:15         ` Georg Bauhaus
  2010-05-18 12:54         ` Dmitry A. Kazakov
  0 siblings, 2 replies; 20+ messages in thread
From: Georg Bauhaus @ 2010-05-18 12:10 UTC (permalink / raw)


On 18.05.10 12:26, Dmitry A. Kazakov wrote:

> BTW, it could be a statement, e.g. conditional call:
> 
>    <procedure/entry-call> when <condition>;

Wouldn't conditional expression work this way?

   Proc ((if Condition then This else That));




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

* Re: Disabling string evaluation in a logging system
  2010-05-18 12:10       ` Georg Bauhaus
@ 2010-05-18 12:15         ` Georg Bauhaus
  2010-05-18 12:54         ` Dmitry A. Kazakov
  1 sibling, 0 replies; 20+ messages in thread
From: Georg Bauhaus @ 2010-05-18 12:15 UTC (permalink / raw)


On 18.05.10 14:10, Georg Bauhaus wrote:
> On 18.05.10 12:26, Dmitry A. Kazakov wrote:
> 
>> BTW, it could be a statement, e.g. conditional call:
>>
>>    <procedure/entry-call> when <condition>;
> 
> Wouldn't conditional expression work this way?
> 
>    Proc ((if Condition then This else That));

(except they don't make the call conditional, yes.)



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

* Re: Disabling string evaluation in a logging system
  2010-05-18 11:27   ` Gautier write-only
@ 2010-05-18 12:18     ` dhenry
  2010-05-19  9:04       ` Stephen Leake
  0 siblings, 1 reply; 20+ messages in thread
From: dhenry @ 2010-05-18 12:18 UTC (permalink / raw)


Thank you for all your replies.

As Dmitry said, the log level may dynamically change. Therefore,
inlining in order to let the compiler do the optimization doesn't
work.

Neither is the "Tricky" procedure tip. The example I gave with a
"parameter name" stored in an unbounded string was just an
illustration of a complex string to log. But of course, it could be
any variable and of any type, for a lot of different sentences, so I
can't write a new procedure each time (I'd prefer writing the if-test
each time).

There may be no solution as I'd like. I'll prefer to let the
application perform a lot of useless string conversion and
concatenations rather have an optimized but heavy to use logging
system. (For the moment, I don't have serious performance issues so
that I would need to reduce those useless string operations).



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

* Re: Disabling string evaluation in a logging system
  2010-05-18 12:10       ` Georg Bauhaus
  2010-05-18 12:15         ` Georg Bauhaus
@ 2010-05-18 12:54         ` Dmitry A. Kazakov
  1 sibling, 0 replies; 20+ messages in thread
From: Dmitry A. Kazakov @ 2010-05-18 12:54 UTC (permalink / raw)


On Tue, 18 May 2010 14:10:15 +0200, Georg Bauhaus wrote:

> On 18.05.10 12:26, Dmitry A. Kazakov wrote:
> 
>> BTW, it could be a statement, e.g. conditional call:
>> 
>>    <procedure/entry-call> when <condition>;
> 
> Wouldn't conditional expression work this way?
> 
>    Proc ((if Condition then This else That));

Yes, if we wanted to introduce a full-blown lazy evaluation in Ada. But
then I wished a better, lighter syntax and cleaner semantics.

procedure Write (Where : in out Log; Message : lazy String);

BTW, another case for lazy evaluation is controlling side effects and
evaluation order. E.g.

   function Read (From : access Stream) return Byte;
   function Read (From : access Stream) return Byte;
   function "&" (Left : Byte_Array; Right : lazy Byte) return Byte_Array;

then:

   X : Byte_Array := Read (S) & Read (S); -- This is unambiguous

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



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

* Re: Disabling string evaluation in a logging system
  2010-05-18 10:13 ` stefan-lucks
@ 2010-05-18 18:17   ` Jeffrey R. Carter
  0 siblings, 0 replies; 20+ messages in thread
From: Jeffrey R. Carter @ 2010-05-18 18:17 UTC (permalink / raw)


stefan-lucks@see-the.signature wrote:
> 
> package Flexi_Log is
> 
>   procedure Write(Log_Level: Log.Level_Type;
>                   Message_1: String := "";
>                   Message_2: String := "";
>                   Message_3: String := "";
>                   ...
>                   Message_9: String := "");
>   -- if Log_Level>0 then
>   --   Log.Write(Message_1 & Message_2 & ... , Log_Level);
>   -- end if;
> 
> end Flexi_Log;
> 
> In any case, the number of different strings to make one message is 
> constant. The constant is under your control, but it is constant. If your 
> support goes for up to, say, Message_9, a message for the log which 
> consists of 10 or more parts may still trouble you. So change the constant 
> sufficiently large that it doesn't trouble you too often ...

You could also do something like:

type Message_List is array (Positive range <>) of Ada.Strings.Unbounded;

procedure Write (Level : Log.Level_ID; Message : Message_List);
-- If Level > No_Logging and Message'Length > 0 then log the concatenation of
-- the strings in Message.

But I don't see that it buys you much, if anything.

Ultimately, this sounds like a case of premature optimization, given that the 
string operations are not impacting your timing requirements, according to 
another post.

-- 
Jeff Carter
"You've got the brain of a four-year-old boy,
and I bet he was glad to get rid of it."
Horse Feathers
47



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

* Re: Disabling string evaluation in a logging system
  2010-05-18  7:48 Disabling string evaluation in a logging system dhenry
                   ` (2 preceding siblings ...)
  2010-05-18 10:13 ` stefan-lucks
@ 2010-05-18 18:40 ` tmoran
  2010-05-19  7:47   ` dhenry
  3 siblings, 1 reply; 20+ messages in thread
From: tmoran @ 2010-05-18 18:40 UTC (permalink / raw)


> In a language like C or C++, I would use the preprocessor:
> #define LOG(text, level) if (level > 0) { log.write (text, level) }
   So write your own specialized preprocessor that adds the "if"
statement to calls on log.write before handing the result to the compiler.

> I'd like to avoid the string evaluation if the logging is disabled
> (because it consumes CPU resources).
  As usual with "optimizations", the first question is "will this
obfuscation actually save significant time?".  If the answer,
surprisingly, is "yes", then find the few places where log.write
is actually called millions of times and manually insert the "if"
test in those places.



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

* Re: Disabling string evaluation in a logging system
  2010-05-18 18:40 ` tmoran
@ 2010-05-19  7:47   ` dhenry
  0 siblings, 0 replies; 20+ messages in thread
From: dhenry @ 2010-05-19  7:47 UTC (permalink / raw)


On 18 mai, 20:40, tmo...@acm.org wrote:
>    So write your own specialized preprocessor that adds the "if"
> statement to calls on log.write before handing the result to the compiler.

That may be a possible solution to my problem.

>   As usual with "optimizations", the first question is "will this
> obfuscation actually save significant time?".  If the answer,
> surprisingly, is "yes", then find the few places where log.write
> is actually called millions of times and manually insert the "if"
> test in those places.

Yes, this may be seen as a premature optimization. I was just looking
for a possible opportunity (and maybe learn some new Ada tricks). If I
encounter some real performance issues, I'll probably do that.

I prefer something "elegant" (code readability and maintenance is
important) but with "poor" performances, as long as it respects
performance requirements.



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

* Re: Disabling string evaluation in a logging system
  2010-05-18 12:18     ` dhenry
@ 2010-05-19  9:04       ` Stephen Leake
  2010-05-19 12:38         ` Dmitry A. Kazakov
  0 siblings, 1 reply; 20+ messages in thread
From: Stephen Leake @ 2010-05-19  9:04 UTC (permalink / raw)


dhenry <tfc.duke@gmail.com> writes:

> As Dmitry said, the log level may dynamically change. Therefore,
> inlining in order to let the compiler do the optimization doesn't
> work.

I don't follow this. Inlining is the same as writing the if-test. Given
this:

    procedure Inlined_Log (S : in string; Level : in Level_Type)
    is begin
        if Level > Global_Level then
            put (S);
        end if;
    end Inlined_Log;


then the compiler (with the right switches) should convert this:

    begin
        Inlined_Log (<expression>, A_Log_Level);
    end;

to this:

    begin
        if A_Log_Level > Global_Level then
            put (A_Log_Level);
        end if;
    end;

What is the problem?

-- 
-- Stephe



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

* Re: Disabling string evaluation in a logging system
  2010-05-19  9:04       ` Stephen Leake
@ 2010-05-19 12:38         ` Dmitry A. Kazakov
  2010-05-19 18:02           ` (see below)
  0 siblings, 1 reply; 20+ messages in thread
From: Dmitry A. Kazakov @ 2010-05-19 12:38 UTC (permalink / raw)


On Wed, 19 May 2010 05:04:32 -0400, Stephen Leake wrote:

> dhenry <tfc.duke@gmail.com> writes:
> 
>> As Dmitry said, the log level may dynamically change. Therefore,
>> inlining in order to let the compiler do the optimization doesn't
>> work.
> 
> I don't follow this. Inlining is the same as writing the if-test.

That depends on the compiler.

procedure Log (Barrier : Boolean; Message : String) is
begin
   if Barrier then
      Put (Message);
   end if;
end Log;

can be inlined as:

1. moving evaluation of temporaries down:

   declare
      Barrier : constant Boolean := <condition-expression>;
   begin
      if Barrier then
         declare
            Message : constant String := <message-expression>;
         begin
            Put (Message);
         end;
      end if;
   end;

or as

2. moving evaluation of temporaries up:

   declare
      Barrier : constant Boolean := <condition-expression>;
      Message : constant String := <message-expression>;
   begin
      if Barrier then
        Put (Message);
      end if;
   end;

The language mandates nothing regarding this. The compiler can even ignore
the pragma Inline.

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



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

* Re: Disabling string evaluation in a logging system
  2010-05-19 12:38         ` Dmitry A. Kazakov
@ 2010-05-19 18:02           ` (see below)
  2010-05-19 19:08             ` Adam Beneschan
  0 siblings, 1 reply; 20+ messages in thread
From: (see below) @ 2010-05-19 18:02 UTC (permalink / raw)


On 19/05/2010 13:38, in article 1p3xrphlq60da.1cq62wm0ajal2$.dlg@40tude.net,
"Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> wrote:

> On Wed, 19 May 2010 05:04:32 -0400, Stephen Leake wrote:
> 
>> dhenry <tfc.duke@gmail.com> writes:
>> 
>>> As Dmitry said, the log level may dynamically change. Therefore,
>>> inlining in order to let the compiler do the optimization doesn't
>>> work.
>> 
>> I don't follow this. Inlining is the same as writing the if-test.
> 
> That depends on the compiler.
> 
> procedure Log (Barrier : Boolean; Message : String) is
> begin
>    if Barrier then
>       Put (Message);
>    end if;
> end Log;
> 
> can be inlined as:
> 
> 1. moving evaluation of temporaries down:
> 
>    declare
>       Barrier : constant Boolean := <condition-expression>;
>    begin
>       if Barrier then
>          declare
>             Message : constant String := <message-expression>;
>          begin
>             Put (Message);
>          end;
>       end if;
>    end;
> 
> or as
> 
> 2. moving evaluation of temporaries up:
> 
>    declare
>       Barrier : constant Boolean := <condition-expression>;
>       Message : constant String := <message-expression>;
>    begin
>       if Barrier then
>         Put (Message);
>       end if;
>    end;
> 
> The language mandates nothing regarding this. The compiler can even ignore
> the pragma Inline.

I thought the second would be required, to allow side effects to take place
as they would normally.

-- 
Bill Findlay
<surname><forename> chez blueyonder.co.uk





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

* Re: Disabling string evaluation in a logging system
  2010-05-19 18:02           ` (see below)
@ 2010-05-19 19:08             ` Adam Beneschan
  0 siblings, 0 replies; 20+ messages in thread
From: Adam Beneschan @ 2010-05-19 19:08 UTC (permalink / raw)


On May 19, 11:02 am, "(see below)" <yaldni...@blueyonder.co.uk> wrote:
> On 19/05/2010 13:38, in article 1p3xrphlq60da.1cq62wm0ajal2$....@40tude.net,
> "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de> wrote:
>
>
>
>
>
> > On Wed, 19 May 2010 05:04:32 -0400, Stephen Leake wrote:
>
> >> dhenry <tfc.d...@gmail.com> writes:
>
> >>> As Dmitry said, the log level may dynamically change. Therefore,
> >>> inlining in order to let the compiler do the optimization doesn't
> >>> work.
>
> >> I don't follow this. Inlining is the same as writing the if-test.
>
> > That depends on the compiler.
>
> > procedure Log (Barrier : Boolean; Message : String) is
> > begin
> >    if Barrier then
> >       Put (Message);
> >    end if;
> > end Log;
>
> > can be inlined as:
>
> > 1. moving evaluation of temporaries down:
>
> >    declare
> >       Barrier : constant Boolean := <condition-expression>;
> >    begin
> >       if Barrier then
> >          declare
> >             Message : constant String := <message-expression>;
> >          begin
> >             Put (Message);
> >          end;
> >       end if;
> >    end;
>
> > or as
>
> > 2. moving evaluation of temporaries up:
>
> >    declare
> >       Barrier : constant Boolean := <condition-expression>;
> >       Message : constant String := <message-expression>;
> >    begin
> >       if Barrier then
> >         Put (Message);
> >       end if;
> >    end;
>
> > The language mandates nothing regarding this. The compiler can even ignore
> > the pragma Inline.
>
> I thought the second would be required, to allow side effects to take place
> as they would normally.

I think that if the compiler can determine that the message-expression
will not have any side effects, or that the only possible side effects
are language-defined exceptions (or something like that), it doesn't
have to evaluate it if it can tell the result won't be used.  In the
OP's original example, assuming that To_String is
Ada.Strings.Unbounded.To_String (we can't tell), it should be OK.

                                   -- Adam



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

end of thread, other threads:[~2010-05-19 19:08 UTC | newest]

Thread overview: 20+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2010-05-18  7:48 Disabling string evaluation in a logging system dhenry
2010-05-18  8:15 ` Dmitry A. Kazakov
2010-05-18  8:45   ` Dmitry A. Kazakov
2010-05-18  9:45   ` Cyrille
2010-05-18 10:26     ` Dmitry A. Kazakov
2010-05-18 12:10       ` Georg Bauhaus
2010-05-18 12:15         ` Georg Bauhaus
2010-05-18 12:54         ` Dmitry A. Kazakov
2010-05-18  9:32 ` Gautier write-only
2010-05-18  9:37   ` Gautier write-only
2010-05-18 11:27   ` Gautier write-only
2010-05-18 12:18     ` dhenry
2010-05-19  9:04       ` Stephen Leake
2010-05-19 12:38         ` Dmitry A. Kazakov
2010-05-19 18:02           ` (see below)
2010-05-19 19:08             ` Adam Beneschan
2010-05-18 10:13 ` stefan-lucks
2010-05-18 18:17   ` Jeffrey R. Carter
2010-05-18 18:40 ` tmoran
2010-05-19  7:47   ` dhenry

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