comp.lang.ada
 help / color / mirror / Atom feed
* 2-dimensional view on 1 dimensional array
@ 2022-10-23 12:31 Marek
  2022-10-24 10:31 ` AdaMagica
  2022-10-25 12:57 ` J-P. Rosen
  0 siblings, 2 replies; 10+ messages in thread
From: Marek @ 2022-10-23 12:31 UTC (permalink / raw)


Hi.
Assume we have:

     generic
        type T is private;
        type T_Array is array (Natural range <>) of aliased T;
        type T_Array_Access is access all T_Array;
     package Buffers is

        type Row_Array is array (Natural range <>) of aliased 
T_Array_Access;

        type Row_Array_Access is access all Row_Array;

        type Buffer is tagged
           record
              Raw_Buffer : T_Array_Access   := null;
              Rows_Table : Row_Array_Access := null;
              Rows       : Natural          := 0;
              Columns    : Natural          := 0;
              Step       : Integer          := 0;
              Max_Rows   : Natural          := 0;
           end record;

        procedure Init
          (This    : in out Buffer;
           Buffer  :        T_Array_Access;
           Rows    :        Natural;
           Columns :        Natural;
           Step    :        Integer);

        procedure Set_Value
          (This  : in out Buffer;
           Value :        T);

     end Buffers;

..and:

     with Ada.Unchecked_Deallocation;

     package body Buffers is

        type T_Access is access all T;

        ------------
        --  Init  --
        ------------

        procedure Init
          (This    : in out Buffer;
           Buffer  :        T_Array_Access;
           Rows    :        Natural;
           Columns :        Natural;
           Step    :        Integer)
        is
           procedure Free is
             new Ada.Unchecked_Deallocation (Row_Array, Row_Array_Access);

           Row_Index : Integer := 0;
        begin
           This.Raw_Buffer := Buffer;
           This.Rows       := Rows;
           This.Columns    := Columns;
           This.Step       := Step;

           if Rows > This.Max_Rows then
              if This.Rows_Table /= null then
                 Free (This.Rows_Table);
              end if;

              declare
                 New_Rows : constant Row_Array_Access :=
                              new Row_Array (0 .. Rows - 1);
              begin
                 This.Rows_Table := New_Rows;
                 This.Max_Rows := Rows;
              end;
           end if;

           for H in 0 .. Rows - 1 loop
              declare
                 Row_Start : constant T_Access :=
                               This.Raw_Buffer (Row_Index * Step)'Access;
              begin
                 This.Rows_Table (H) := ...  -- What code here?

                 Row_Index := Row_Index + 1;
              end;
           end loop;

        end Init;

        -----------------
        --  Set_Value  --
        -----------------

        procedure Set_Value
          (This  : in out Buffer;
           Value :        T)
        is
        begin
           if This.Rows > 0 then
              for Y in 0 .. This.Rows - 1 loop
                 declare
                    Row : constant T_Array_Access := This.Rows_Table (Y);
                 begin
                    if This.Step > 0 then
                       for X in 0 .. This.Step - 1 loop
                          Row (X) := Value;
                       end loop;
                    end if;
                 end;
              end loop;
           end if;
        end Set_Value;

     end Buffers;

and finally:

     with Buffers;

     procedure Test is

        type Float_Array is array (Natural range <>) of aliased Float;

        type Float_Array_Access is access all Float_Array;

        package Buffer_Package is
          new Buffers (Float, Float_Array, Float_Array_Access);

        use Buffer_Package;

        A : aliased Float_Array := (0 .. 99 => 0.0);
        B : Buffer_Package.Buffer;
     begin

        B.Init (A'Access, 10, 10, 10);
        B.Set_Value (10.0);
     end Test;

Is there any possibilities to get this working?
Idea is to have another (2 dimensional) view on 1 dimensional array.
Unchecked_Conversion is not working (different sizes of objects).
Address_To_Access conversion also (unconstrained array);

Marek

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-23 12:31 Marek
@ 2022-10-24 10:31 ` AdaMagica
  2022-10-24 10:35   ` AdaMagica
  2022-10-25 12:57 ` J-P. Rosen
  1 sibling, 1 reply; 10+ messages in thread
From: AdaMagica @ 2022-10-24 10:31 UTC (permalink / raw)


Your code looks rather ununderstandable to me.
A quick attempt on what you claimed you are trying to do (no guarantee):

generic

  type T is private;

  type T_Array is array (Integer range <>) of T;

package Dim1_to_2 is

  -- type T_Array_2Dim is array (Integer range <>, Integer range <>) of T;

  procedure Set (TA: in T_Array; Row, Num_Row, Col, Num_Col: Positive; Value: T)
    with Pre => Row in 1 .. Num_Row and Col in 1 .. Num_Col and
                Num_Row * Num_col = TA'Length;

end Dim1_to_2;
package body Dim1_to_2 is

  type T_Array_2Dim is array (Integer range <>, Integer range <>) of T;

  procedure Set (TA: in T_Array; Row, Num_Row, Col, Num_Col: Positive; Value: T) is
    TA2: T_Array_2Dim (1 .. Num_Row, 1 .. Num_Col);
    for TA2'Address use TA'Address;
  begin
    if Num_Row * Num_Col /= TA'Length or
       Row not in 1 .. Num_Row or Col not in 1 .. Num_Col then
      raise Constraint_Error;
    end if;
    TA2 (Row, Col) := Value;
  end Set;

end Dim1_to_2;
with Dim1_to_2;

procedure Ausprobieren is

  type A is array (Integer range <>) of Integer;

  X: aliased A (-10 .. 10) := (others => 0);

  package To_2D is new Dim1_to_2 (Integer, A);

begin

  To_2D.Set (X, Row => 2, Num_Row => 7, Col => 1, Num_Col => 3, Value => -1);

  for V of X loop
    Put_Line (V'Image);
  end loop;

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-24 10:31 ` AdaMagica
@ 2022-10-24 10:35   ` AdaMagica
  2022-10-25 11:05     ` AdaMagica
  0 siblings, 1 reply; 10+ messages in thread
From: AdaMagica @ 2022-10-24 10:35 UTC (permalink / raw)


The object X must be aliased because of the address clauses.

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-24 10:35   ` AdaMagica
@ 2022-10-25 11:05     ` AdaMagica
  0 siblings, 0 replies; 10+ messages in thread
From: AdaMagica @ 2022-10-25 11:05 UTC (permalink / raw)


Also interesting: The array is an in-parameter. You get a variable view with the overlay. Clever Gnat gives you a warning. Don't know what other cmpilers say.

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-23 12:31 Marek
  2022-10-24 10:31 ` AdaMagica
@ 2022-10-25 12:57 ` J-P. Rosen
  2022-10-25 15:53   ` Jeffrey R.Carter
  1 sibling, 1 reply; 10+ messages in thread
From: J-P. Rosen @ 2022-10-25 12:57 UTC (permalink / raw)


Le 23/10/2022 à 14:31, Marek a écrit :
> generic
>         type T is private;
>         type T_Array is array (Natural range <>) of aliased T;
>         type T_Array_Access is access all T_Array;
>      package Buffers is
> 
>         type Row_Array is array (Natural range <>) of aliased 
> T_Array_Access;
> 
>         type Row_Array_Access is access all Row_Array;
Here I see a pointer to an array of pointers to an array whose 
components can pointed to...
That's too much for my small head ( (c) Hoare)
Can you explain what you try to accomplish?

-- 
J-P. Rosen
Adalog
2 rue du Docteur Lombard, 92441 Issy-les-Moulineaux CEDEX
https://www.adalog.fr https://www.adacontrol.fr

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-25 12:57 ` J-P. Rosen
@ 2022-10-25 15:53   ` Jeffrey R.Carter
  2022-10-25 19:55     ` J-P. Rosen
  0 siblings, 1 reply; 10+ messages in thread
From: Jeffrey R.Carter @ 2022-10-25 15:53 UTC (permalink / raw)


On 2022-10-25 14:57, J-P. Rosen wrote:
> That's too much for my small head ( (c) Hoare)

I am familiar with the Dijkstra quote, "I have a very small head and I had 
better learn to live with it". Did Hoare say something along those lines, too?

-- 
Jeff Carter
"[Many] programmers do not use [languages with
automatic run-time checks] because 'They're not
efficient.' (Presumably this means that it is
vital to get the wrong answers quickly.)"
Elements of Programming Style
193


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

* Re: 2-dimensional view on 1 dimensional array
@ 2022-10-25 16:59 Marek
  2022-10-26  8:57 ` J-P. Rosen
  2022-10-26 15:08 ` AdaMagica
  0 siblings, 2 replies; 10+ messages in thread
From: Marek @ 2022-10-25 16:59 UTC (permalink / raw)


I want just to know if it is possible to make different "view" on 1 
dimensional array. And of course I meant not 2-dimensional array but 
array of arrays. Reason for that is that I want to use slicing on that view.

Ok, here is full specification:

     generic
        type T is private;
        type T_Array is array (Natural range <>) of aliased T;
        type T_Array_Access is access all T_Array;
     package Buffers is

        type Row_Array is array (Natural range <>) of aliased 
T_Array_Access;

        type Row_Array_Access is access all Row_Array;

        type Buffer is tagged
           record
              Raw_Buffer : T_Array_Access   := null;
              Rows_Table : Row_Array_Access := null;
              Rows       : Natural          := 0;
              Columns    : Natural          := 0;
              Step       : Integer          := 0;
              Max_Rows   : Natural          := 0;
           end record;

        procedure Init
          (This    : in out Buffer;
           Buffer  :        T_Array_Access;
           Rows    :        Natural;
           Columns :        Natural;
           Step    :        Integer);

        procedure Set_Value
          (This  : in out Buffer;
           Value :        T);

       function Get_Buffer
         (This : Rendering_Buffer)
          return T_Array_Access
       is (This.Buffer);

       function Get_Rows_Table
         (This : Rendering_Buffer)
          return Row_Array_Access
       is (This.Rows);

       function Get_Columns
         (This : Rendering_Buffer)
          return Natural
       is (This.Columns);

       function Get_Rows
         (This : Rendering_Buffer)
          return Natural
       is (This.Rows);

       function Get_Step
         (This : Rendering_Buffer)
          return Integer
       is (This.Step);

       function Move_Start
         (This       : Rendering_Buffer;
          Col_Offset : Natural;
          Row_Offset : Natural)
          return T_Array_Access;

       function Row
         (This   : Rendering_Buffer;
          R      : Natural)
          return T_Array_Access;

       procedure Copy_From
         (This   : in out Rendering_Buffer;
          Source :        Rendering_Buffer);

     end Buffers;

I consider this package to be a kind of template that I can apply to the 
raw data and get what it expects. That is why I am using access types.
I know this is very C-ish but...

thank you for your answers everybody
Marek
p.s. Be aware that this group is read not only by software engineers. 
Carpenters may also happen ... :)

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-25 15:53   ` Jeffrey R.Carter
@ 2022-10-25 19:55     ` J-P. Rosen
  0 siblings, 0 replies; 10+ messages in thread
From: J-P. Rosen @ 2022-10-25 19:55 UTC (permalink / raw)


Le 25/10/2022 à 17:53, Jeffrey R.Carter a écrit :
> I am familiar with the Dijkstra quote, "I have a very small head and I 
> had better learn to live with it". Did Hoare say something along those 
> lines, too?
My confusion, must be Dijkstra. But that's the quote I wanted...

-- 
J-P. Rosen
Adalog
2 rue du Docteur Lombard, 92441 Issy-les-Moulineaux CEDEX
https://www.adalog.fr https://www.adacontrol.fr

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-25 16:59 2-dimensional view on 1 dimensional array Marek
@ 2022-10-26  8:57 ` J-P. Rosen
  2022-10-26 15:08 ` AdaMagica
  1 sibling, 0 replies; 10+ messages in thread
From: J-P. Rosen @ 2022-10-26  8:57 UTC (permalink / raw)


Le 25/10/2022 à 18:59, Marek a écrit :
> I want just to know if it is possible to make different "view" on 1 
> dimensional array. And of course I meant not 2-dimensional array but 
> array of arrays. Reason for that is that I want to use slicing on that 
> view.
Any one dimensional array can be sliced. If you have an (1 dimensional) 
array of arrays, it can be sliced, as well as any of its components. 
Still puzzled about what you want to achieve (and the depth of your 
pointers-to-pointers-to-pointers....)

-- 
J-P. Rosen
Adalog
2 rue du Docteur Lombard, 92441 Issy-les-Moulineaux CEDEX
https://www.adalog.fr https://www.adacontrol.fr

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

* Re: 2-dimensional view on 1 dimensional array
  2022-10-25 16:59 2-dimensional view on 1 dimensional array Marek
  2022-10-26  8:57 ` J-P. Rosen
@ 2022-10-26 15:08 ` AdaMagica
  1 sibling, 0 replies; 10+ messages in thread
From: AdaMagica @ 2022-10-26 15:08 UTC (permalink / raw)


ficorax@gmail.com schrieb am Dienstag, 25. Oktober 2022 um 18:59:15 UTC+2:
> I want just to know if it is possible to make different "view" on 1 
> dimensional array. And of course I meant not 2-dimensional array but 
> array of arrays. Reason for that is that I want to use slicing on that view. 
> 
> Ok, here is full specification:
> generic 
> type T is private; 
> type T_Array is array (Natural range <>) of aliased T; 
> type T_Array_Access is access all T_Array; 
> package Buffers is 

and so on ununderstandably.
Have you ever heard of something like comments? Or more fundamentally, of design? This is just a lump of code fragments hurting my brain.

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

end of thread, other threads:[~2022-10-26 15:08 UTC | newest]

Thread overview: 10+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2022-10-25 16:59 2-dimensional view on 1 dimensional array Marek
2022-10-26  8:57 ` J-P. Rosen
2022-10-26 15:08 ` AdaMagica
  -- strict thread matches above, loose matches on Subject: below --
2022-10-23 12:31 Marek
2022-10-24 10:31 ` AdaMagica
2022-10-24 10:35   ` AdaMagica
2022-10-25 11:05     ` AdaMagica
2022-10-25 12:57 ` J-P. Rosen
2022-10-25 15:53   ` Jeffrey R.Carter
2022-10-25 19:55     ` J-P. Rosen

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