comp.lang.ada
 help / color / mirror / Atom feed
* Allocation questions
@ 2009-05-28  9:46 Olivier Scalbert
  2009-05-28 10:02 ` Martin
                   ` (2 more replies)
  0 siblings, 3 replies; 16+ messages in thread
From: Olivier Scalbert @ 2009-05-28  9:46 UTC (permalink / raw)


Hello,

In the context of my small audio project, I need to create an object to 
introduce a delay in a signal. With some of these objects and other 
stuff it is possible to simulate nice reverberation.

Here is the code (As delay is a reserved word in Ada, I use Delay_T as I 
found nothing better !):

package audio.effect is

     type Sample is new Float;
     type Time   is new Float;

     type Samples_Array is array (Positive range <>) of Sample;

     type Delay_T is tagged record
         Delay_Time: Time;
         Output    : Sample;
         Samples   : access Samples_Array;
     end record;

     function Create_Delay (Time_Value: Time) return Delay_T;

     procedure Input (D: Delay_T; Input: Sample);
     function Output (D: Delay_T) return Sample;
     procedure  Next (D: Delay_T); -- compute next output

end audio.effect;

package body audio.effect is

     function Create_Delay(Time_Value: Time) return Delay_T is
         Result:      Delay_T;
         Nb_Samples:  Integer;
     begin
         Result.Delay_Time := Time_Value;
         Nb_Samples := Integer(Time_Value * 44_100.0);
         Result.Samples := new Samples_Array(1..Nb_Samples);
         Result.Output  := 0.0;
         return Result;
     end Create_Delay;

     procedure Input (D: Delay_T; Input: Sample) is
     begin
         null; --TBD
     end Input;

     function Output(D: Delay_T) return Sample is
     begin
         return D.Output;
     end Output;

     procedure Next(D: Delay_T) is
     begin
         null; --TBD
     end Next;

end audio.effect;
-- --------------------------------
Here are my questions:

1) Is there a way to avoid the dynamic array allocation, as I do not 
know the Time_Value at compile time ?

2) Is it possible to release the array automatically when the Delay 
object died ?

3) I have read that there is a program call gnatmem to detect memory 
leaks. Is there somewhere a package for Linux (Debian) ?

Thanks for the help,

Olivier



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

* Re: Allocation questions
  2009-05-28  9:46 Allocation questions Olivier Scalbert
@ 2009-05-28 10:02 ` Martin
  2009-05-28 11:55   ` xavier grave
  2009-05-28 10:05 ` Dmitry A. Kazakov
  2009-05-28 16:59 ` Jeffrey R. Carter
  2 siblings, 1 reply; 16+ messages in thread
From: Martin @ 2009-05-28 10:02 UTC (permalink / raw)


On May 28, 10:46 am, Olivier Scalbert <olivier.scalb...@algosyn.com>
wrote:
> Hello,
>
> In the context of my small audio project, I need to create an object to
> introduce a delay in a signal. With some of these objects and other
> stuff it is possible to simulate nice reverberation.
>
> Here is the code (As delay is a reserved word in Ada, I use Delay_T as I
> found nothing better !):
>
> package audio.effect is
>
>      type Sample is new Float;
>      type Time   is new Float;
>
>      type Samples_Array is array (Positive range <>) of Sample;
>
>      type Delay_T is tagged record
>          Delay_Time: Time;
>          Output    : Sample;
>          Samples   : access Samples_Array;
>      end record;
>
>      function Create_Delay (Time_Value: Time) return Delay_T;
>
>      procedure Input (D: Delay_T; Input: Sample);
>      function Output (D: Delay_T) return Sample;
>      procedure  Next (D: Delay_T); -- compute next output
>
> end audio.effect;
>
> package body audio.effect is
>
>      function Create_Delay(Time_Value: Time) return Delay_T is
>          Result:      Delay_T;
>          Nb_Samples:  Integer;
>      begin
>          Result.Delay_Time := Time_Value;
>          Nb_Samples := Integer(Time_Value * 44_100.0);
>          Result.Samples := new Samples_Array(1..Nb_Samples);
>          Result.Output  := 0.0;
>          return Result;
>      end Create_Delay;
>
>      procedure Input (D: Delay_T; Input: Sample) is
>      begin
>          null; --TBD
>      end Input;
>
>      function Output(D: Delay_T) return Sample is
>      begin
>          return D.Output;
>      end Output;
>
>      procedure Next(D: Delay_T) is
>      begin
>          null; --TBD
>      end Next;
>
> end audio.effect;
> -- --------------------------------
> Here are my questions:
>
> 1) Is there a way to avoid the dynamic array allocation, as I do not
> know the Time_Value at compile time ?

You could look at Ada.Container.Vectors and the Reserve_Capacity
subprogram. The container libraries should offer perfectly acceptable
performance, esp if you only need to reserve once.

Or you could use a discriminant:

   type Samples (No_Of_Samples : Natural := 0) is
      record
         S : array (1 .. No_Of_Samples) of Sample;
      end record;


> 2) Is it possible to release the array automatically when the Delay
> object died ?

Checkout package Ada.Finalization.


> 3) I have read that there is a program call gnatmem to detect memory
> leaks. Is there somewhere a package for Linux (Debian) ?

Sorry, no idea.

Cheers
-- Martin



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

* Re: Allocation questions
  2009-05-28  9:46 Allocation questions Olivier Scalbert
  2009-05-28 10:02 ` Martin
@ 2009-05-28 10:05 ` Dmitry A. Kazakov
  2009-05-28 10:40   ` Martin
  2009-05-28 16:59 ` Jeffrey R. Carter
  2 siblings, 1 reply; 16+ messages in thread
From: Dmitry A. Kazakov @ 2009-05-28 10:05 UTC (permalink / raw)


On Thu, 28 May 2009 11:46:51 +0200, in comp.lang.ada you wrote:

> In the context of my small audio project, I need to create an object to 
> introduce a delay in a signal. With some of these objects and other 
> stuff it is possible to simulate nice reverberation.
> 
> Here is the code (As delay is a reserved word in Ada, I use Delay_T as I 
> found nothing better !):
> 
> package audio.effect is
> 
>      type Sample is new Float;
>      type Time   is new Float;
> 
>      type Samples_Array is array (Positive range <>) of Sample;
> 
>      type Delay_T is tagged record
>          Delay_Time: Time;
>          Output    : Sample;
>          Samples   : access Samples_Array;
>      end record;

     type Delay_T (Size : Natural) is tagged record
         Delay_Time: Time;
         Output    : Sample;
         Samples   : Samples_Array (1..Size);
     end record;

(A side note, I suppose that Delay_Time is not of Time but of Duration.)

>      function Create_Delay (Time_Value: Time) return Delay_T;
> 
>      procedure Input (D: Delay_T; Input: Sample);
>      function Output (D: Delay_T) return Sample;
>      procedure  Next (D: Delay_T); -- compute next output
> 
> end audio.effect;
> 
> package body audio.effect is
> 
>      function Create_Delay(Time_Value: Time) return Delay_T is
>          Result:      Delay_T;
>          Nb_Samples:  Integer;
>      begin
>          Result.Delay_Time := Time_Value;
>          Nb_Samples := Integer(Time_Value * 44_100.0);
>          Result.Samples := new Samples_Array(1..Nb_Samples);
>          Result.Output  := 0.0;
>          return Result;
>      end Create_Delay;

     function Create_Delay(Time_Value: Time) return Delay_T is
        Result : Delay_T (Natural (Time_Value * 44_100.0));
     begin
        Result.Delay_Time := Time_Value;
        Result.Output  := 0.0;
        return Result;
     end Create_Delay;

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



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

* Re: Allocation questions
  2009-05-28 10:05 ` Dmitry A. Kazakov
@ 2009-05-28 10:40   ` Martin
  2009-05-28 12:32     ` Olivier Scalbert
  0 siblings, 1 reply; 16+ messages in thread
From: Martin @ 2009-05-28 10:40 UTC (permalink / raw)


On May 28, 11:05 am, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
wrote:
[snip]
>      function Create_Delay(Time_Value: Time) return Delay_T is
>         Result : Delay_T (Natural (Time_Value * 44_100.0));
>      begin
>         Result.Delay_Time := Time_Value;
>         Result.Output  := 0.0;
>         return Result;
>      end Create_Delay;

It would be even better to do it all in a single assignment, so that
when new components are added to the record the compiler will complain
and force you to initialise them too.

Cheers
-- Martin

p.s. here's a demo:

with Ada.Text_IO; use Ada.Text_IO;
procedure Demo is
   package D is
      type No_Of_Samples is range 0 .. 1_000;
      type A_of_F is array (No_Of_Samples range <>) of Float;
      type R (S : No_Of_Samples := 0) is private;
      function Create (N : No_Of_Samples) return R;
      procedure Put_Line (This_R : R);
   private
      type R (S : No_Of_Samples := 0) is
         record
            I : Integer;
            B : Boolean;
            A : A_Of_F (1 .. S);
         end record;
   end D;
   package body D is
      function Create (N : No_Of_Samples) return R is
      begin
         return (S => N,
                 I => 0,
                 B => False,
                 A => (others => 0.0));
      end Create;
      procedure Put_Line (This_R : R) is
      begin
         Put_Line (Integer'Image (This_R.I));
         Put_Line (Boolean'Image (This_R.B));
         Put_Line (No_Of_Samples'Image (This_R.S));
         for I in This_R.A'Range loop
            Put_Line (Float'Image (This_R.A (I)));
         end loop;
      end Put_Line;
   end D;

   R_1 : D.R := D.Create (1);
   R_5 : D.R := D.Create (5);
begin
   D.Put_Line (R_1);
   D.Put_Line (R_5);
end Demo;



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

* Re: Allocation questions
  2009-05-28 10:02 ` Martin
@ 2009-05-28 11:55   ` xavier grave
  2009-05-28 12:19     ` Ludovic Brenta
  0 siblings, 1 reply; 16+ messages in thread
From: xavier grave @ 2009-05-28 11:55 UTC (permalink / raw)


-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1


> Or you could use a discriminant:
> 
>    type Samples (No_Of_Samples : Natural := 0) is
>       record
>          S : array (1 .. No_Of_Samples) of Sample;
>       end record;
> 

My two cents about variant discriminant : IMHO one should avoid to
declare No_Of_Samples as Natural and with a default value, because as
far as I remember some compilers will book for S (1 .. Natural'Last) of
Sample which can be a lot...

May be some compiler guru can confirm or infirm this ?

xavier

-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAkoee5sACgkQVIZi0A5BZF6aJQCeKvvUfImZxi0hBfrOevIJddTB
qJMAnRfDe03mMlNL/XHUayFVTHFdv9WV
=xdXN
-----END PGP SIGNATURE-----



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

* Re: Allocation questions
  2009-05-28 11:55   ` xavier grave
@ 2009-05-28 12:19     ` Ludovic Brenta
  2009-05-28 13:00       ` Georg Bauhaus
  2009-05-28 23:13       ` Robert A Duff
  0 siblings, 2 replies; 16+ messages in thread
From: Ludovic Brenta @ 2009-05-28 12:19 UTC (permalink / raw)


xavier grave:
> > Or you could use a discriminant:
>
> >    type Samples (No_Of_Samples : Natural := 0) is
> >       record
> >          S : array (1 .. No_Of_Samples) of Sample;
> >       end record;
>
> My two cents about variant discriminant : IMHO one should avoid to
> declare No_Of_Samples as Natural and with a default value, because as
> far as I remember some compilers will book for S (1 .. Natural'Last) of
> Sample which can be a lot...
>
> May be some compiler guru can confirm or infirm this ?

I confirm this with GNAT even though I'm no guru. Well spotted,
Xavier.

--
Ludovic Brenta.



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

* Re: Allocation questions
  2009-05-28 10:40   ` Martin
@ 2009-05-28 12:32     ` Olivier Scalbert
  2009-05-28 13:39       ` Martin
  2009-05-28 14:04       ` Dmitry A. Kazakov
  0 siblings, 2 replies; 16+ messages in thread
From: Olivier Scalbert @ 2009-05-28 12:32 UTC (permalink / raw)


Martin wrote:
> On May 28, 11:05 am, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>

> 
> p.s. here's a demo:
> 
> with Ada.Text_IO; use Ada.Text_IO;
> procedure Demo is
>    package D is
>       type No_Of_Samples is range 0 .. 1_000;
>       type A_of_F is array (No_Of_Samples range <>) of Float;
>       type R (S : No_Of_Samples := 0) is private;
>       function Create (N : No_Of_Samples) return R;
>       procedure Put_Line (This_R : R);
>    private
>       type R (S : No_Of_Samples := 0) is
>          record
>             I : Integer;
>             B : Boolean;
>             A : A_Of_F (1 .. S);
>          end record;
>    end D;
>    package body D is
>       function Create (N : No_Of_Samples) return R is
>       begin
>          return (S => N,
>                  I => 0,
>                  B => False,
>                  A => (others => 0.0));
>       end Create;
>       procedure Put_Line (This_R : R) is
>       begin
>          Put_Line (Integer'Image (This_R.I));
>          Put_Line (Boolean'Image (This_R.B));
>          Put_Line (No_Of_Samples'Image (This_R.S));
>          for I in This_R.A'Range loop
>             Put_Line (Float'Image (This_R.A (I)));
>          end loop;
>       end Put_Line;
>    end D;
> 
>    R_1 : D.R := D.Create (1);
>    R_5 : D.R := D.Create (5);
> begin
>    D.Put_Line (R_1);
>    D.Put_Line (R_5);
> end Demo;

Thanks Martin, it works!

2 more questions:

1) In fact (due to my background!), I would like to use the dot notation:
object.method.
So I have add "tagged":

     type Delay_Type (Size : Nb_Of_Samples := 0) is tagged private;
     ...
private
     type Delay_Type (Size : Nb_Of_Samples :=0) is tagged record
      ...

When I compile, I have:
"discriminants of tagged type cannot have defaults"
How can I fix it ?

2) If Nb_Of_Samples range is too large, around 1..5_000_000, I have a 
nice Segmentation fault. How can I fix that ?

Thanks

Olivier







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

* Re: Allocation questions
  2009-05-28 12:19     ` Ludovic Brenta
@ 2009-05-28 13:00       ` Georg Bauhaus
  2009-05-28 23:13       ` Robert A Duff
  1 sibling, 0 replies; 16+ messages in thread
From: Georg Bauhaus @ 2009-05-28 13:00 UTC (permalink / raw)


Ludovic Brenta schrieb:
> xavier grave:
>>> Or you could use a discriminant:
>>>    type Samples (No_Of_Samples : Natural := 0) is
>>>       record
>>>          S : array (1 .. No_Of_Samples) of Sample;
>>>       end record;
>> My two cents about variant discriminant : IMHO one should avoid to
>> declare No_Of_Samples as Natural and with a default value, because as
>> far as I remember some compilers will book for S (1 .. Natural'Last) of
>> Sample which can be a lot...
>>
>> May be some compiler guru can confirm or infirm this ?
> 
> I confirm this with GNAT even though I'm no guru. Well spotted,
> Xavier.

Using GNAT and -fstack-check, this will stem towards the
stack limit (Dummy just declares Samples records of
increasing No_Of_Samples):

with Ada.Text_IO;

procedure GNAT_Varrec is

   type Sample is new Float range 0.0 .. 1.0;
   type Run is array (Natural range <>) of Sample;

   type Samples (No_Of_Samples : Natural := 0) is
      record
         S : Run (1 .. No_Of_Samples);
      end record;

   procedure Dummy (N: Natural) is
      Scratch: Samples(No_Of_Samples => N);
   begin
      if N in Scratch.S'Range then
         Scratch.S(N) := 0.5;
      end if;
   end Dummy;

   K : Natural;

   package Text_IO renames Ada.Text_IO;
begin
   K := 0;
   while K < Natural'Last loop
      Text_IO.Put_Line("Size is " &
	Natural'Image(K * Sample'Size / 8) & " octets");
      Text_IO.Flush;
      Dummy(K);
      K := K + 4096;
   end loop;
end GNAT_Varrec;



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

* Re: Allocation questions
  2009-05-28 12:32     ` Olivier Scalbert
@ 2009-05-28 13:39       ` Martin
  2009-05-28 13:57         ` Olivier Scalbert
  2009-05-28 14:51         ` Adam Beneschan
  2009-05-28 14:04       ` Dmitry A. Kazakov
  1 sibling, 2 replies; 16+ messages in thread
From: Martin @ 2009-05-28 13:39 UTC (permalink / raw)


On May 28, 1:32 pm, Olivier Scalbert <olivier.scalb...@algosyn.com>
wrote:
> Martin wrote:
> > On May 28, 11:05 am, "Dmitry A. Kazakov" <mail...@dmitry-kazakov.de>
>
> > p.s. here's a demo:
>
> > with Ada.Text_IO; use Ada.Text_IO;
> > procedure Demo is
> >    package D is
> >       type No_Of_Samples is range 0 .. 1_000;
> >       type A_of_F is array (No_Of_Samples range <>) of Float;
> >       type R (S : No_Of_Samples := 0) is private;
> >       function Create (N : No_Of_Samples) return R;
> >       procedure Put_Line (This_R : R);
> >    private
> >       type R (S : No_Of_Samples := 0) is
> >          record
> >             I : Integer;
> >             B : Boolean;
> >             A : A_Of_F (1 .. S);
> >          end record;
> >    end D;
> >    package body D is
> >       function Create (N : No_Of_Samples) return R is
> >       begin
> >          return (S => N,
> >                  I => 0,
> >                  B => False,
> >                  A => (others => 0.0));
> >       end Create;
> >       procedure Put_Line (This_R : R) is
> >       begin
> >          Put_Line (Integer'Image (This_R.I));
> >          Put_Line (Boolean'Image (This_R.B));
> >          Put_Line (No_Of_Samples'Image (This_R.S));
> >          for I in This_R.A'Range loop
> >             Put_Line (Float'Image (This_R.A (I)));
> >          end loop;
> >       end Put_Line;
> >    end D;
>
> >    R_1 : D.R := D.Create (1);
> >    R_5 : D.R := D.Create (5);
> > begin
> >    D.Put_Line (R_1);
> >    D.Put_Line (R_5);
> > end Demo;
>
> Thanks Martin, it works!
>
> 2 more questions:
>
> 1) In fact (due to my background!), I would like to use the dot notation:
> object.method.
> So I have add "tagged":
>
>      type Delay_Type (Size : Nb_Of_Samples := 0) is tagged private;
>      ...
> private
>      type Delay_Type (Size : Nb_Of_Samples :=0) is tagged record
>       ...
>
> When I compile, I have:
> "discriminants of tagged type cannot have defaults"
> How can I fix it ?

Just remove the " := 0" bit.

> 2) If Nb_Of_Samples range is too large, around 1..5_000_000, I have a
> nice Segmentation fault. How can I fix that ?

Works fine with 2_000_00 with GNAT GPL 2009 Win32... ;-)

What OS are you using?

Cheers
-- Martin



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

* Re: Allocation questions
  2009-05-28 13:39       ` Martin
@ 2009-05-28 13:57         ` Olivier Scalbert
  2009-05-28 14:51         ` Adam Beneschan
  1 sibling, 0 replies; 16+ messages in thread
From: Olivier Scalbert @ 2009-05-28 13:57 UTC (permalink / raw)


Martin wrote:

>>
>> 2 more questions:
>>
>> 1) In fact (due to my background!), I would like to use the dot notation:
>> object.method.
>> So I have add "tagged":
>>
>>      type Delay_Type (Size : Nb_Of_Samples := 0) is tagged private;
>>      ...
>> private
>>      type Delay_Type (Size : Nb_Of_Samples :=0) is tagged record
>>       ...
>>
>> When I compile, I have:
>> "discriminants of tagged type cannot have defaults"
>> How can I fix it ?
> 
> Just remove the " := 0" bit.
Ok, thanks.

> 
>> 2) If Nb_Of_Samples range is too large, around 1..5_000_000, I have a
>> nice Segmentation fault. How can I fix that ?
> 
> Works fine with 2_000_00 with GNAT GPL 2009 Win32... ;-)
> 
> What OS are you using?
> 
> Cheers
> -- Martin

A 32 bits linux + gnat 4.3.3

Olivier



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

* Re: Allocation questions
  2009-05-28 12:32     ` Olivier Scalbert
  2009-05-28 13:39       ` Martin
@ 2009-05-28 14:04       ` Dmitry A. Kazakov
  1 sibling, 0 replies; 16+ messages in thread
From: Dmitry A. Kazakov @ 2009-05-28 14:04 UTC (permalink / raw)


On Thu, 28 May 2009 14:32:01 +0200, Olivier Scalbert wrote:

> 1) In fact (due to my background!), I would like to use the dot notation:
> object.method.
> So I have add "tagged":
> 
>      type Delay_Type (Size : Nb_Of_Samples := 0) is tagged private;
>      ...
> private
>      type Delay_Type (Size : Nb_Of_Samples :=0) is tagged record
>       ...
> 
> When I compile, I have:
> "discriminants of tagged type cannot have defaults"
> How can I fix it ?

That depends. The default values are used in order to fix the object size
(to maximum possible). That is not your case. Since you have Create_Delay
that returns Delay_T, you can do:

    type Delay_Type (<>) is tagged private;
    function Create_Delay (Time_Value: Time) return Delay_T;
private
    type Delay_Type (Size : Nb_Of_Samples) is tagged record

> 2) If Nb_Of_Samples range is too large, around 1..5_000_000, I have a 
> nice Segmentation fault. How can I fix that ?

You should increase the stack (allocated per task).

Since Delay_Type is potentially huge, I suggest to make it limited in order
to prevent accidental copying:

    type Delay_T (<>) is tagged limited private;
    function Create_Delay (Time_Value: Time) return Delay_T;
private
    type Delay_T (Size : Natural) is tagged limited record
       Delay_Time: Time;
       Output    : Sample;
       Samples   : Samples_Array (1..Size);
   end record;

The "function" Create_Delay will look like (Ada 2005):

   function Create_Delay (Time_Value: Time) return Delay_T is
   begin
      return Result : Delay_T (Natural  (Time_Value * 44_100.0)) do
         Result.Delay_Time := Time_Value;
         Result.Output  := 0.0;
      end return;
   end Create_Delay;

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



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

* Re: Allocation questions
  2009-05-28 13:39       ` Martin
  2009-05-28 13:57         ` Olivier Scalbert
@ 2009-05-28 14:51         ` Adam Beneschan
  2009-05-28 17:58           ` Randy Brukardt
  1 sibling, 1 reply; 16+ messages in thread
From: Adam Beneschan @ 2009-05-28 14:51 UTC (permalink / raw)


On May 28, 6:39 am, Martin <martin.do...@btopenworld.com> wrote:
> > 2 more questions:
>
> > 1) In fact (due to my background!), I would like to use the dot notation:
> > object.method.
> > So I have add "tagged":

I'm not sure I'd recommend declaring a type "tagged" JUST to get the
dot notation.  There's a small amount of overhead involved with making
a type tagged; but more importantly, a fair number of language rules
are different for tagged types than for untagged types.  (You ran into
one different rule below; another one that comes to mind immediately
is that there are differences in the semantics of "=".  There are
others.  You might not run into any of them, though.)


> >      type Delay_Type (Size : Nb_Of_Samples := 0) is tagged private;
> >      ...
> > private
> >      type Delay_Type (Size : Nb_Of_Samples :=0) is tagged record
> >       ...
>
> > When I compile, I have:
> > "discriminants of tagged type cannot have defaults"
> > How can I fix it ?
>
> Just remove the " := 0" bit.

To elaborate, the main advantage of using the default is that after
you declare an object of type Delay_Type, you can change its Size by
reassigning the whole object.  If you don't need to use this feature---
i.e. if you will declare an object of type Delay_Type(Size=>N) and
then never change the Size of that object afterwards---then I don't
think there's any need to use the default.


> > 2) If Nb_Of_Samples range is too large, around 1..5_000_000, I have a
> > nice Segmentation fault. How can I fix that ?

As Xavier pointed out, using a default could cause a lot larger array
to be allocated (because the Size could be changed later).  If you
remove the default, this problem may go away on its own.  I don't see
how an array of five million floats would cause a problem.  (Not these
days, anyway.  Back when I used to work on a mainframe that took up a
whole room and had a whopping ONE MEGABYTE of RAM, maybe it would have
been a problem.  I also used to put my COBOL programs on punch cards
and walk five miles to school, uphill both ways...)

                                  -- Adam



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

* Re: Allocation questions
  2009-05-28  9:46 Allocation questions Olivier Scalbert
  2009-05-28 10:02 ` Martin
  2009-05-28 10:05 ` Dmitry A. Kazakov
@ 2009-05-28 16:59 ` Jeffrey R. Carter
  2009-05-28 17:26   ` Olivier Scalbert
  2 siblings, 1 reply; 16+ messages in thread
From: Jeffrey R. Carter @ 2009-05-28 16:59 UTC (permalink / raw)


Olivier Scalbert wrote:
> 
> Here is the code (As delay is a reserved word in Ada, I use Delay_T as I 
> found nothing better !):

Delay_Info
Delay_Data

> 1) Is there a way to avoid the dynamic array allocation, as I do not 
> know the Time_Value at compile time ?

You cannot avoid dynamic allocation. However, you can do the dynamic allocation 
on the stack (variable-sized record), or on the heap (explicit access values or 
an unbounded data structure such as Ada.Containers.Vectors).

An object allocated on the stack is likely to have a smaller maximum size than 
one allocated on the heap.

If you are going to use the heap, I would recommend using a data structure, as 
it will do the memory management for you. The memory management in 
Ada.Containers is more likely to be correct than something you write yourself, 
and to remain correct as you modify your code.

If you are going to use a variable-sized record, you should declare (sub)types 
that reflect the constraints implicit in the implementation. For example, there 
is a maximum usable value of type Time, since you have to be able to multiply 
any supplied value by the sampling rate. This also implies a maximum number of 
samples that may be handled at a time:

type Time_Base is new Float;

Sampling_Rate : constant := 44_100;

Max_Time : constant Time_Base := Time_Base'Last / Sampling_Rate;

subtype Time is Time_Base range 0.0 .. Max_Time;

Max_Samples : constant Positive :=
    Integer (Time'Truncation (Max_Time * Sampling_Rate) );

As this last declaration is likely to raise Constraint_Error, it's probably 
better to start with the maximum number of samples and work backward:

Max_Samples : constant := 30_000;
-- Arbitrary value; replace with something meaningful from the application.

Max_Time : constant Time_Base := Time_Base (Max_Samples) / Sampling_Rate;

subtype Sample_Index is Positive range 1 .. Max_Samples;

type Sample_List is array (Sample_Index range <>) of Sample;

package Sample_Lists is new Ada.Containers.Vectors
    (Index_Type => Sample_Index, Element_Type => Sample);

-- 
Jeff Carter
"What lazy lout left these wires all over the lawn?"
Poppy
98



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

* Re: Allocation questions
  2009-05-28 16:59 ` Jeffrey R. Carter
@ 2009-05-28 17:26   ` Olivier Scalbert
  0 siblings, 0 replies; 16+ messages in thread
From: Olivier Scalbert @ 2009-05-28 17:26 UTC (permalink / raw)


Jeffrey R. Carter wrote:
> Olivier Scalbert wrote:
>>
>> Here is the code (As delay is a reserved word in Ada, I use Delay_T as 
>> I found nothing better !):
> 
> Delay_Info
> Delay_Data

You know, I already have Reverb, Filter, Envelope, Synthy objects, so 
Delay (the name used in audio) would be nicer !
However, I think I will go for Delay_Line !

Thanks for your help Jeffrey,

Olivier.



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

* Re: Allocation questions
  2009-05-28 14:51         ` Adam Beneschan
@ 2009-05-28 17:58           ` Randy Brukardt
  0 siblings, 0 replies; 16+ messages in thread
From: Randy Brukardt @ 2009-05-28 17:58 UTC (permalink / raw)


>"Adam Beneschan" <adam@irvine.com> wrote in message 
>news:336b285f-2245-4ede-8528-841a2c713e80@b7g2000pre.googlegroups.com...
>On May 28, 6:39 am, Martin <martin.do...@btopenworld.com> wrote:
>> > 2 more questions:
>>
>> > 1) In fact (due to my background!), I would like to use the dot 
>> > notation:
>> > object.method.
>> > So I have add "tagged":
>
>I'm not sure I'd recommend declaring a type "tagged" JUST to get the
>dot notation.  There's a small amount of overhead involved with making
>a type tagged; but more importantly, a fair number of language rules
>are different for tagged types than for untagged types.  (You ran into
>one different rule below; another one that comes to mind immediately
>is that there are differences in the semantics of "=".  There are
>others.  You might not run into any of them, though.)

That's strange advice, given that the mantra of the Ada 95 team was that 
"tagged types work right". Yes, there are minor differences in semantics, 
but in all cases that I know of, tagged types work more logically than 
untagged types (mainly because of compatibility issues). I'd be more likely 
to reverse the advice and suggest that you declare all of your records 
tagged. (Well, I'd go further and suggest that pretty much everything ought 
to be declared controlled, which of course subsumes tagged, but that isn't 
as clear cut.)

I can understand a concern about the overhead of a tag, but that only 
matters if there are going to be many of these objects and the objects are 
relatively small (given that tags are fairly small). Neither of those seems 
to be true in this case.

                                               Randy.








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

* Re: Allocation questions
  2009-05-28 12:19     ` Ludovic Brenta
  2009-05-28 13:00       ` Georg Bauhaus
@ 2009-05-28 23:13       ` Robert A Duff
  1 sibling, 0 replies; 16+ messages in thread
From: Robert A Duff @ 2009-05-28 23:13 UTC (permalink / raw)


Ludovic Brenta <ludovic@ludovic-brenta.org> writes:

> xavier grave:
>> > Or you could use a discriminant:
>>
>> > � �type Samples (No_Of_Samples : Natural := 0) is
>> > � � � record
>> > � � � � �S : array (1 .. No_Of_Samples) of Sample;
>> > � � � end record;
>>
>> My two cents about variant discriminant : IMHO one should avoid to
>> declare No_Of_Samples as Natural and with a default value, because as
>> far as I remember some compilers will book for S (1 .. Natural'Last) of
>> Sample which can be a lot...
>>
>> May be some compiler guru can confirm or infirm this ?
>
> I confirm this with GNAT even though I'm no guru. Well spotted,
> Xavier.

A defaulted discriminant means you are allowed to declare unconstrained
objects of the type.  Yes, GNAT and some other compilers will allocate
the max size for such unconstrained objects.  In this case, that's
some gigabytes, which you never want.  GNAT warns on the above, I
think.

If you create constrained objects of type Samples, it will use the right
size.  But if all your objects are constrained, there's no point in
having the default.

You want one of:

    type Samples (No_Of_Samples : Natural) is ...
    -- You can only have constrained objects, and they will tend to
    -- have reasonable size.

Or:

    subtype My_Range is Natural range 0..1000; -- or some tolerable max
    type Samples (No_Of_Samples : My_Range := 0) is ...
    -- Now you can have unconstrained objects, and waste a modest amount
    -- of memory.

When in doubt, don't have a default.  It's also less efficient for
parameter passing, because the compiler has to pass extra information
"is this thing constrained".  Without the default, the compiler knows
all objects are constrained.

Except if the type is limited: then you can use defaults on discrims
freely, no problem.

- Bob



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

end of thread, other threads:[~2009-05-28 23:13 UTC | newest]

Thread overview: 16+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-05-28  9:46 Allocation questions Olivier Scalbert
2009-05-28 10:02 ` Martin
2009-05-28 11:55   ` xavier grave
2009-05-28 12:19     ` Ludovic Brenta
2009-05-28 13:00       ` Georg Bauhaus
2009-05-28 23:13       ` Robert A Duff
2009-05-28 10:05 ` Dmitry A. Kazakov
2009-05-28 10:40   ` Martin
2009-05-28 12:32     ` Olivier Scalbert
2009-05-28 13:39       ` Martin
2009-05-28 13:57         ` Olivier Scalbert
2009-05-28 14:51         ` Adam Beneschan
2009-05-28 17:58           ` Randy Brukardt
2009-05-28 14:04       ` Dmitry A. Kazakov
2009-05-28 16:59 ` Jeffrey R. Carter
2009-05-28 17:26   ` Olivier Scalbert

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