comp.lang.ada
 help / color / mirror / Atom feed
* Interfaces.C + generics: stack overflow
@ 2017-03-23  7:43 hreba
  2017-03-23  7:46 ` hreba
                   ` (2 more replies)
  0 siblings, 3 replies; 14+ messages in thread
From: hreba @ 2017-03-23  7:43 UTC (permalink / raw)


My last posting was buried deep inside the thread and somewhat lengthy, 
so here in a compact form. What works is (everything compiles and test 
application executes):

--------------------------------------------------------------------
with Interfaces;

package GSL is
    subtype Real is Interfaces.IEEE_Float_32;

    gsl_Ex:	Exception;
    error_code:	Integer;	-- of the last operation

    type Real_Function is access function (x: Real) return Real;

    procedure Integration_QNG
      (f:			Real_Function;
       a, b, epsabs, epsrel:	Real;
       result, abserr:		out Real;
       neval:			out Natural);

end GSL;
---------------------------------------------------------------------

Now when pass the type real as a generic parameter:

---------------------------------------------------------------------
generic
    type Real is digits <>;
when not used.
package GSL is
...
---------------------------------------------------------------------

and instanciate GSL with exactly the same type as above, I get a
STORAGE_ERROR : stack overflow or erroneous memory access.

I wrote a simpler example too, where just a function (gsl_bessl_j0) is 
called from the C library, and no function reference is passed as a 
parameter. This worked in the non-generic as well in the generic version.

For completeness, here follows the body of GSL

----------------------------------------------------------------------
with Interfaces.C;	use Interfaces;

package body GSL is

    type Void_Ptr is access all Integer;
    pragma Convention (C, Void_Ptr);

    type GSL_Inner_Function is
      access function (x: C.double; params: Void_Ptr) return C.double;
    pragma Convention (C, GSL_Inner_Function);

    type GSL_Function is record
       func:	GSL_Inner_Function;
       params:	Void_Ptr;
    end record;


    real_func:	Real_Function;

    ---------------------------------------------------------------------
    --	Auxiliary Subprograms
    ---------------------------------------------------------------------

    function func (x: C.double; params: Void_Ptr) return C.double;
    pragma Convention (C, func);

    function func (x: C.double; params: Void_Ptr) return C.double is
    begin return C.double (real_func (Real(x)));
    end func;


    function gsl_integration_qng
      (f: access GSL_Function;
       a, b, epsabs, epsrel: C.double;
       result, abserr: out C.double;
       neval: out C.size_t)
      return C.int;
    pragma Import (C, gsl_integration_qng,	"gsl_integration_qng");


    ---------------------------------------------------------------------
    -- Exported Subprograms
    ---------------------------------------------------------------------

    procedure Integration_QNG
      (f: Real_Function;
       a, b, epsabs, epsrel:	Real;
       result, abserr:		out Real;
       neval:			out Natural)
    is
       use type C.int;
       gslf:	aliased GSL_Function;
       status:	C.int;
       res, ae:	C.double;
       ne:	C.size_t;
    begin
       real_func:= f;
       gslf.func:= func'Access;
       gslf.params:= null;
       status:= gsl_integration_qng
	(gslf'Access,
	 C.double(a), C.double(b), C.double(epsabs), C.double(epsrel),
	 res, ae, ne);
       if status /= 0 then
	 error_code:= Integer (status);
	 raise gsl_Ex with
	   "gsl_integration_qng() returns error code " & C.int'Image(status);
       end if;
       result:= Real(res);
       abserr:= Real(ae);
       neval:= Natural(ne);
    end Integration_QNG;
----------------------------------------------------------------------

-- 
Frank Hrebabetzky		+49 / 6355 / 989 5070

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

* Re: Interfaces.C + generics: stack overflow
  2017-03-23  7:43 Interfaces.C + generics: stack overflow hreba
@ 2017-03-23  7:46 ` hreba
  2017-03-23 17:45 ` Jeffrey R. Carter
  2017-03-23 20:03 ` Randy Brukardt
  2 siblings, 0 replies; 14+ messages in thread
From: hreba @ 2017-03-23  7:46 UTC (permalink / raw)


On 03/23/2017 08:43 AM, hreba wrote:
> when not used.

Please disconsider this line.
-- 
Frank Hrebabetzky		+49 / 6355 / 989 5070


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

* Re: Interfaces.C + generics: stack overflow
  2017-03-23  7:43 Interfaces.C + generics: stack overflow hreba
  2017-03-23  7:46 ` hreba
@ 2017-03-23 17:45 ` Jeffrey R. Carter
  2017-03-24 12:20   ` hreba
  2017-03-23 20:03 ` Randy Brukardt
  2 siblings, 1 reply; 14+ messages in thread
From: Jeffrey R. Carter @ 2017-03-23 17:45 UTC (permalink / raw)


On 03/23/2017 08:43 AM, hreba wrote:
>
> Now when pass the type real as a generic parameter:
>
> ---------------------------------------------------------------------
> generic
>    type Real is digits <>;
> package GSL is
> ...
> ---------------------------------------------------------------------
>
> and instanciate GSL with exactly the same type as above, I get a
> STORAGE_ERROR : stack overflow or erroneous memory access.

Where do you instantiate the package? Where do you declare the function you pass 
to Integration_QNG?

>    function gsl_integration_qng
>      (f: access GSL_Function;

This should not need to be an access parameter. It should be passed by reference 
as an "in" parameter. You can make it "in out" if you want.

-- 
Jeff Carter
"My little plum, I am like Robin Hood. I take from
the rich, and I give to the poor. ... Us poor."
Poppy
96


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

* Re: Interfaces.C + generics: stack overflow
  2017-03-23  7:43 Interfaces.C + generics: stack overflow hreba
  2017-03-23  7:46 ` hreba
  2017-03-23 17:45 ` Jeffrey R. Carter
@ 2017-03-23 20:03 ` Randy Brukardt
  2017-03-24 12:42   ` hreba
  2 siblings, 1 reply; 14+ messages in thread
From: Randy Brukardt @ 2017-03-23 20:03 UTC (permalink / raw)


"hreba" <f_hreba@yahoo.com.br> wrote in message 
news:ejhckeF1tg7U1@mid.individual.net...
> My last posting was buried deep inside the thread and somewhat lengthy, so 
> here in a compact form. What works is (everything compiles and test 
> application executes):

I agree with Jeff, there's not enough detail here to even see if there is a 
bug or your mistake. We need to know how/where the generic is instantiated, 
where/how the access-to-function value is created, and probably more.

But let me say that the rules for access-to-subprogram types are different 
inside of generics than they are in normal packages, in order to allow for 
the possibility of generic sharing. That ought to manifest as compile-time 
errors and/or the raising of Program_Error, so it seems that there might be 
a compiler bug in your code. But to find that, one needs to see the whole 
thing, not just a little corner.

If you really want to write portable interfacing code, you would not use any 
generics in the raw interface. (Have the generics call non-generic interface 
code with appropriate type conversions.) Janus/Ada doesn't allow any 
convention C stuff in generic units, because it is incompatible with the 
extra dope needed to implemented universal generic sharing. I'd expect 
something similar to happen for any implementation that supports almost any 
form of generic sharing. (If you only care about GNAT, do what ever you 
want.)

                              Randy.




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

* Re: Interfaces.C + generics: stack overflow
  2017-03-23 17:45 ` Jeffrey R. Carter
@ 2017-03-24 12:20   ` hreba
  0 siblings, 0 replies; 14+ messages in thread
From: hreba @ 2017-03-24 12:20 UTC (permalink / raw)


On 03/23/2017 06:45 PM, Jeffrey R. Carter wrote:
> On 03/23/2017 08:43 AM, hreba wrote:
>>
>> Now when pass the type real as a generic parameter:
>>
>> ---------------------------------------------------------------------
>> generic
>>    type Real is digits <>;
>> package GSL is
>> ...
>> ---------------------------------------------------------------------
>>
>> and instanciate GSL with exactly the same type as above, I get a
>> STORAGE_ERROR : stack overflow or erroneous memory access.
>
> Where do you instantiate the package? Where do you declare the function
> you pass to Integration_QNG?
>
>>    function gsl_integration_qng
>>      (f: access GSL_Function;
>
> This should not need to be an access parameter. It should be passed by
> reference as an "in" parameter. You can make it "in out" if you want.
>

Did as you suggested. Clearly better. Unfortunately the stack overflow 
persists. For the complete code please see my answer to Randy.

-- 
Frank Hrebabetzky		+49 / 6355 / 989 5070

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

* Re: Interfaces.C + generics: stack overflow
  2017-03-23 20:03 ` Randy Brukardt
@ 2017-03-24 12:42   ` hreba
  2017-03-24 20:13     ` Randy Brukardt
  2017-03-24 22:03     ` Dmitry A. Kazakov
  0 siblings, 2 replies; 14+ messages in thread
From: hreba @ 2017-03-24 12:42 UTC (permalink / raw)


On 03/23/2017 09:03 PM, Randy Brukardt wrote:
> I agree with Jeff, there's not enough detail here to even see if there is a
> bug or your mistake. We need to know how/where the generic is instantiated,
> where/how the access-to-function value is created, and probably more.
>
The complete code follows below. The suggestion from Jeffrey is already 
realized. The packages are:
  - GSL			wrapper for the C library
  - Test_Integration	main program, instantiates GSL
  - Integ_Aux		defines the function to be handed over

> But let me say that the rules for access-to-subprogram types are different
> inside of generics than they are in normal packages, in order to allow for
> the possibility of generic sharing. That ought to manifest as compile-time
> errors and/or the raising of Program_Error, so it seems that there might be
> a compiler bug in your code. But to find that, one needs to see the whole
> thing, not just a little corner.
>
> If you really want to write portable interfacing code, you would not use any
> generics in the raw interface. (Have the generics call non-generic interface
> code with appropriate type conversions.) Janus/Ada doesn't allow any
> convention C stuff in generic units, because it is incompatible with the
> extra dope needed to implemented universal generic sharing. I'd expect
> something similar to happen for any implementation that supports almost any
> form of generic sharing. (If you only care about GNAT, do what ever you
> want.)
>
I am not writing this program only for its result, but also as an 
exercise in Ada programming. So I want to do it the right way. So far I 
know basically the book from John Barnes, where this topic is not 
treated, so thanks for your comments, I will modify my program accordingly.

---------------------------------------------------------------------------
generic
    type Real is digits <>;
    type Parameters is private;	-- for future use
package GSL is

    gsl_Ex:	Exception;
    error_code:	Integer;    -- of the last operation

    type Real_Function is access function (x: Real) return Real;

    procedure Integration_QNG
      (f:			Real_Function;
       a, b, epsabs, epsrel:	Real;
       result, abserr:		out Real;
       neval:			out Natural);

end GSL;
-----------------------------------------------------------------------------
with Interfaces.C;    use Interfaces;

package body GSL is

    type Void_Ptr is access all Parameters;
    pragma Convention (C, Void_Ptr);

    type GSL_Inner_Function is
      access function (x: C.double; params: Void_Ptr) return C.double;
    pragma Convention (C, GSL_Inner_Function);

    type GSL_Function is record
       func:	GSL_Inner_Function;
       params:	Void_Ptr;
    end record;

    real_func:    Real_Function;

    ---------------------------------------------------------------------
    --    Auxiliary Subprograms
    ---------------------------------------------------------------------

    function func (x: C.double; params: Void_Ptr) return C.double;
    pragma Convention (C, func);

    function func (x: C.double; params: Void_Ptr) return C.double is
    begin return C.double (real_func (Real(x)));
    end func;


    function gsl_integration_qng
      (f:			in out GSL_Function;
       a, b, epsabs, epsrel:	C.double;
       result, abserr:		out C.double;
       neval:			out C.size_t)
      return C.int;
    pragma Import (C, gsl_integration_qng,    "gsl_integration_qng");


    ---------------------------------------------------------------------
    -- Exported Subprograms
    ---------------------------------------------------------------------

    procedure Integration_QNG
      (f:			Real_Function;
       a, b, epsabs, epsrel:	Real;
       result, abserr:		out Real;
       neval:			out Natural)
    is
       use type C.int;
       gslf:	GSL_Function;
       status:	C.int;
       res, ae:	C.double;
       ne:	C.size_t;
    begin
       real_func:= f;
       gslf.func:= func'Access;
       gslf.params:= null;
       status:= gsl_integration_qng    -- <-- STORAGE_ERROR occurs here
         (gslf,
          C.double(a), C.double(b), C.double(epsabs), C.double(epsrel),
          res, ae, ne);
       if status /= 0 then
          error_code:= Integer (status);
          raise gsl_Ex with
	   "gsl_integration_qng() returns error code " &
	   C.int'Image(status);
       end if;
       result:= Real(res);
       abserr:= Real(ae);
       neval:= Natural(ne);
    end Integration_QNG;

end GSL;
------------------------------------------------------------------------------
with Ada.Text_IO;    use Ada.Text_IO;
with GSL;
with Integ_Aux;

procedure Test_Integration
is
    package GSL_Test is new GSL (Integ_Aux.Real, Integer);
    use type Integ_Aux.Real;
    a, abserr:	Integ_Aux.Real;
    neval:	Natural;
begin
    GSL_Test.Integration_QNG
      (Integ_Aux.Circle'Access, 0.0, 1.0, 0.001, 0.001, a, abserr, neval);
    Put_Line("4*int_0^1 sqrt(1-x^2) dx = " & Integ_Aux.Real'Image(4.0*a));
    Put_Line(Natural'Image(neval) & " function evaluations, " &
           Integ_Aux.Real'Image(abserr) & " abs. error");
end Test_Integration;
------------------------------------------------------------------------------
with Interfaces;

package Integ_Aux is

    type Real is new Interfaces.IEEE_Float_32;
    function Circle (x: Real) return Real;

end Integ_Aux;
------------------------------------------------------------------------------
with Ada.Numerics.Generic_Elementary_Functions;

package body Integ_Aux is

    package Functions is new
      Ada.Numerics.Generic_Elementary_Functions (Real);

    function Circle (x: Real) return Real is
    begin return Functions.Sqrt(abs(1.0-x*x));
    end Circle;

end Integ_Aux;
-------------------------------------------------------------------------------
-- 
Frank Hrebabetzky		+49 / 6355 / 989 5070

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

* Re: Interfaces.C + generics: stack overflow
  2017-03-24 12:42   ` hreba
@ 2017-03-24 20:13     ` Randy Brukardt
  2017-03-24 22:03     ` Dmitry A. Kazakov
  1 sibling, 0 replies; 14+ messages in thread
From: Randy Brukardt @ 2017-03-24 20:13 UTC (permalink / raw)


I don't see anything obviously wrong with your code (Janus/Ada can't compile 
it for various reasons, including that it doesn't yet support "in out" 
parameters on functions, so I didn't learn much from that attempt.)

What I would suggest is moving all of the actual C interface stuff out of 
the generic, making the generic part of the think binding rather than trying 
to do it all in one. That's likely to get rid of any bugs and make the code 
more portable.
The body of the generic would use type conversions (and if necessary, 
Unchecked_Conversion) to match up the formal types with the types of the 
thin binding. As I noted yesterday, that would make it a lot more portable 
to compilers that support some form of code sharing (which can't, in 
general, support C interfacing in a generic body).

Hope the above gives you some suggestions to try.

                 Randy.


"hreba" <f_hreba@yahoo.com.br> wrote in message 
news:ejkigvFlkjbU1@mid.individual.net...
> On 03/23/2017 09:03 PM, Randy Brukardt wrote:
>> I agree with Jeff, there's not enough detail here to even see if there is 
>> a
>> bug or your mistake. We need to know how/where the generic is 
>> instantiated,
>> where/how the access-to-function value is created, and probably more.
>>
> The complete code follows below. The suggestion from Jeffrey is already 
> realized. The packages are:
>  - GSL wrapper for the C library
>  - Test_Integration main program, instantiates GSL
>  - Integ_Aux defines the function to be handed over
>
>> But let me say that the rules for access-to-subprogram types are 
>> different
>> inside of generics than they are in normal packages, in order to allow 
>> for
>> the possibility of generic sharing. That ought to manifest as 
>> compile-time
>> errors and/or the raising of Program_Error, so it seems that there might 
>> be
>> a compiler bug in your code. But to find that, one needs to see the whole
>> thing, not just a little corner.
>>
>> If you really want to write portable interfacing code, you would not use 
>> any
>> generics in the raw interface. (Have the generics call non-generic 
>> interface
>> code with appropriate type conversions.) Janus/Ada doesn't allow any
>> convention C stuff in generic units, because it is incompatible with the
>> extra dope needed to implemented universal generic sharing. I'd expect
>> something similar to happen for any implementation that supports almost 
>> any
>> form of generic sharing. (If you only care about GNAT, do what ever you
>> want.)
>>
> I am not writing this program only for its result, but also as an exercise 
> in Ada programming. So I want to do it the right way. So far I know 
> basically the book from John Barnes, where this topic is not treated, so 
> thanks for your comments, I will modify my program accordingly.
>
> ---------------------------------------------------------------------------
> generic
>    type Real is digits <>;
>    type Parameters is private; -- for future use
> package GSL is
>
>    gsl_Ex: Exception;
>    error_code: Integer;    -- of the last operation
>
>    type Real_Function is access function (x: Real) return Real;
>
>    procedure Integration_QNG
>      (f: Real_Function;
>       a, b, epsabs, epsrel: Real;
>       result, abserr: out Real;
>       neval: out Natural);
>
> end GSL;
> -----------------------------------------------------------------------------
> with Interfaces.C;    use Interfaces;
>
> package body GSL is
>
>    type Void_Ptr is access all Parameters;
>    pragma Convention (C, Void_Ptr);
>
>    type GSL_Inner_Function is
>      access function (x: C.double; params: Void_Ptr) return C.double;
>    pragma Convention (C, GSL_Inner_Function);
>
>    type GSL_Function is record
>       func: GSL_Inner_Function;
>       params: Void_Ptr;
>    end record;
>
>    real_func:    Real_Function;
>
>    ---------------------------------------------------------------------
>    --    Auxiliary Subprograms
>    ---------------------------------------------------------------------
>
>    function func (x: C.double; params: Void_Ptr) return C.double;
>    pragma Convention (C, func);
>
>    function func (x: C.double; params: Void_Ptr) return C.double is
>    begin return C.double (real_func (Real(x)));
>    end func;
>
>
>    function gsl_integration_qng
>      (f: in out GSL_Function;
>       a, b, epsabs, epsrel: C.double;
>       result, abserr: out C.double;
>       neval: out C.size_t)
>      return C.int;
>    pragma Import (C, gsl_integration_qng,    "gsl_integration_qng");
>
>
>    ---------------------------------------------------------------------
>    -- Exported Subprograms
>    ---------------------------------------------------------------------
>
>    procedure Integration_QNG
>      (f: Real_Function;
>       a, b, epsabs, epsrel: Real;
>       result, abserr: out Real;
>       neval: out Natural)
>    is
>       use type C.int;
>       gslf: GSL_Function;
>       status: C.int;
>       res, ae: C.double;
>       ne: C.size_t;
>    begin
>       real_func:= f;
>       gslf.func:= func'Access;
>       gslf.params:= null;
>       status:= gsl_integration_qng    -- <-- STORAGE_ERROR occurs here
>         (gslf,
>          C.double(a), C.double(b), C.double(epsabs), C.double(epsrel),
>          res, ae, ne);
>       if status /= 0 then
>          error_code:= Integer (status);
>          raise gsl_Ex with
>    "gsl_integration_qng() returns error code " &
>    C.int'Image(status);
>       end if;
>       result:= Real(res);
>       abserr:= Real(ae);
>       neval:= Natural(ne);
>    end Integration_QNG;
>
> end GSL;
> ------------------------------------------------------------------------------
> with Ada.Text_IO;    use Ada.Text_IO;
> with GSL;
> with Integ_Aux;
>
> procedure Test_Integration
> is
>    package GSL_Test is new GSL (Integ_Aux.Real, Integer);
>    use type Integ_Aux.Real;
>    a, abserr: Integ_Aux.Real;
>    neval: Natural;
> begin
>    GSL_Test.Integration_QNG
>      (Integ_Aux.Circle'Access, 0.0, 1.0, 0.001, 0.001, a, abserr, neval);
>    Put_Line("4*int_0^1 sqrt(1-x^2) dx = " & Integ_Aux.Real'Image(4.0*a));
>    Put_Line(Natural'Image(neval) & " function evaluations, " &
>           Integ_Aux.Real'Image(abserr) & " abs. error");
> end Test_Integration;
> ------------------------------------------------------------------------------
> with Interfaces;
>
> package Integ_Aux is
>
>    type Real is new Interfaces.IEEE_Float_32;
>    function Circle (x: Real) return Real;
>
> end Integ_Aux;
> ------------------------------------------------------------------------------
> with Ada.Numerics.Generic_Elementary_Functions;
>
> package body Integ_Aux is
>
>    package Functions is new
>      Ada.Numerics.Generic_Elementary_Functions (Real);
>
>    function Circle (x: Real) return Real is
>    begin return Functions.Sqrt(abs(1.0-x*x));
>    end Circle;
>
> end Integ_Aux;
> -------------------------------------------------------------------------------
> -- 
> Frank Hrebabetzky +49 / 6355 / 989 5070
> 


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

* Re: Interfaces.C + generics: stack overflow
  2017-03-24 12:42   ` hreba
  2017-03-24 20:13     ` Randy Brukardt
@ 2017-03-24 22:03     ` Dmitry A. Kazakov
  2017-03-25 14:17       ` hreba
  1 sibling, 1 reply; 14+ messages in thread
From: Dmitry A. Kazakov @ 2017-03-24 22:03 UTC (permalink / raw)


On 2017-03-24 13:42, hreba wrote:

> generic
>    type Real is digits <>;
>    type Parameters is private;    -- for future use
> package GSL is
>
>    gsl_Ex:    Exception;
>    error_code:    Integer;    -- of the last operation
>
>    type Real_Function is access function (x: Real) return Real;
[...]

Your design looks wrong to me.

An important objection is that the code is not re-entrant. You store 
data in the package body during the call.

Another issue is that you forgot C convention for GSL_Function.

If you want to pass an Ada function to the integrator you must use a C 
wrapper for it. An alternative would be to use C convention for 
Real_Function, but let us put that aside.

Now the Params component is just for this case. What you should do is to 
pass a pointer to the Ada function via Params plus parameter for the 
function if any. E.g.

    type Arguments is record
       Func   : Real_Function;
       Params : Parameters; -- You can use parameters later
    end record;
    type Arguments_Ptr is access all Arguments;
    pragma Convention (C, Arguments_Ptr);

    type GSL_Inner_Function is
       access function
              (  x      : C.double;
                 params : Arguments_Ptr
              )  return C.double;
    pragma Convention (C, GSL_Inner_Function);

    type GSL_Function is record
       func   : GSL_Inner_Function;
       params : Arguments_Ptr;
    end record;
    pragma Convention (C, GSL_Function); -- Do not forget this!

    function C_Func (X : C.double; Params : Arguments_Ptr)
       return C.double;
    pragma Convention (C, C_Func);

    function C_Func (X : C.double; Params : Arguments_Ptr)
       return C.double is
    begin -- Params is pointer to Ada function + its parameters
       return C.double (Params.Func (Real (x)));
    exception
       when others => -- You never propagate Ada exceptions from C
          return 0.0; -- code! Do tracing here if you want or call
    end C_Func;       -- Exit() to kill the program

    function gsl_integration_qng
             ( f                    : in out GSL_Function;
               a, b, epsabs, epsrel : C.double;
               result, abserr       : out C.double;
               neval                : out C.size_t
             ) return C.int;
    pragma Import (C, gsl_integration_qng, "gsl_integration_qng");

    procedure Integration_QNG
              (  f                    : Real_Function;
                 a, b, epsabs, epsrel : Real;
                 result, abserr       : out Real;
                 neval                : out Natural
              )  is
       use type C.int;
       Ada_Data : aliased Arguments;
       C_Data   : GSL_Function :=
                     (C_Func'Access, Ada_Data'Unchecked_Access);
       status   : C.int;
       res, ae  : C.double;
       ne       : C.size_t;
    begin
       Ada_Data.Func := f;
       status :=
          gsl_integration_qng
          (  C_Data,
             C.double (a),
             C.double (b),
             C.double (epsabs),
             C.double (epsrel),
             res, ae, ne
          );
    ...

No data stored in the package body.

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


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

* Re: Interfaces.C + generics: stack overflow
  2017-03-24 22:03     ` Dmitry A. Kazakov
@ 2017-03-25 14:17       ` hreba
  2017-03-25 15:21         ` hreba
  2017-03-25 15:23         ` Dmitry A. Kazakov
  0 siblings, 2 replies; 14+ messages in thread
From: hreba @ 2017-03-25 14:17 UTC (permalink / raw)


On 03/24/2017 11:03 PM, Dmitry A. Kazakov wrote:

Thanks for your convincing suggestions and the detailed code. I changed 
my program accordingly - still STORAGE_ERROR.

Then I followed the advice from Randy, transferring the exported 
function of the C library to another, non-generic package, changing the 
first parameter from

    function gsl_integration_qng
      (f: in out GSL_Function; ...
to
    function gsl_integration_qng
      (f: System.Address; ...

Result - STORAGE_ERROR

To be continued ...

-- 
Frank Hrebabetzky		+49 / 6355 / 989 5070

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

* Re: Interfaces.C + generics: stack overflow
  2017-03-25 14:17       ` hreba
@ 2017-03-25 15:21         ` hreba
  2017-03-26 22:34           ` Robert Eachus
  2017-03-25 15:23         ` Dmitry A. Kazakov
  1 sibling, 1 reply; 14+ messages in thread
From: hreba @ 2017-03-25 15:21 UTC (permalink / raw)


On 03/25/2017 03:17 PM, hreba wrote:
>
> To be continued ...
>

It works finally, I just don't know the reason. All I did is take 
Dmitrys suggestion, and move the package instantiation from the main 
program to package Integ_Aux (that is where the function to be passed to 
the C-library-integrator is defined.)

-- 
Frank Hrebabetzky		+49 / 6355 / 989 5070

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

* Re: Interfaces.C + generics: stack overflow
  2017-03-25 14:17       ` hreba
  2017-03-25 15:21         ` hreba
@ 2017-03-25 15:23         ` Dmitry A. Kazakov
  1 sibling, 0 replies; 14+ messages in thread
From: Dmitry A. Kazakov @ 2017-03-25 15:23 UTC (permalink / raw)


On 2017-03-25 15:17, hreba wrote:
> On 03/24/2017 11:03 PM, Dmitry A. Kazakov wrote:
>
> Thanks for your convincing suggestions and the detailed code. I changed
> my program accordingly - still STORAGE_ERROR.
>
> Then I followed the advice from Randy, transferring the exported
> function of the C library to another, non-generic package, changing the
> first parameter from
>
>    function gsl_integration_qng
>      (f: in out GSL_Function; ...
> to
>    function gsl_integration_qng
>      (f: System.Address; ...
>
> Result - STORAGE_ERROR

1. You could try to replace out T with access T. Especially because you 
apply a conversion to the argument.

2. You should also read the library documentation for memory allocation 
issues. Storage_Error is a usual result when an Ada allocated object is 
passed where a C malloc result expected. If some of the arguments are 
allocated by callee to be freed by the caller or conversely you must use 
Interfaces.C.Pointers to deal with these.

3. And you could debug it to get an idea where it fails. If the stack 
frame becomes corrupted, that means wrong call convention. An error in 
the heap indicates an allocator issue as above etc.

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


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

* Re: Interfaces.C + generics: stack overflow
  2017-03-25 15:21         ` hreba
@ 2017-03-26 22:34           ` Robert Eachus
  2017-03-27  7:21             ` Dmitry A. Kazakov
  0 siblings, 1 reply; 14+ messages in thread
From: Robert Eachus @ 2017-03-26 22:34 UTC (permalink / raw)


On Saturday, March 25, 2017 at 11:21:41 AM UTC-4, hreba wrote:

> It works finally, I just don't know the reason. All I did is take 
> Dmitrys suggestion, and move the package instantiation from the main 
> program to package Integ_Aux (that is where the function to be passed to 
> the C-library-integrator is defined.)

I'm glad you found a solution.  Dave Emery used to call Storage_Error a parachute that opened on impact.  (Think Roadrunner cartoons.) Things have gotten a lot better, and GNAT in particular tries to identify all cases where Storage_Error will always be raised (as warnings).  But the real issue is that it is in general not possible to create a stack frame or allocate an object after an occurrence of Storage_Error.

It would be nice if there was a parameter which identified where in that particular compiler the Storage_Error came from.  Yes, Storage_Error is raised during execution, but the generated code or sometimes even the run-time library code has no clue you can use during debugging.  I wonder how much could be done with Exception_Message.  If the compiler had a collection of strings to be returned, there would be no need to allocate space for a string after the Storage_Error..

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

* Re: Interfaces.C + generics: stack overflow
  2017-03-26 22:34           ` Robert Eachus
@ 2017-03-27  7:21             ` Dmitry A. Kazakov
  2017-03-30 17:12               ` Robert Eachus
  0 siblings, 1 reply; 14+ messages in thread
From: Dmitry A. Kazakov @ 2017-03-27  7:21 UTC (permalink / raw)


On 27/03/2017 00:34, Robert Eachus wrote:
> On Saturday, March 25, 2017 at 11:21:41 AM UTC-4, hreba wrote:
>
>> It works finally, I just don't know the reason. All I did is take
>> Dmitrys suggestion, and move the package instantiation from the main
>> program to package Integ_Aux (that is where the function to be passed to
>> the C-library-integrator is defined.)
>
> I'm glad you found a solution. Dave Emery used to call Storage_Error
> a  parachute that opened on impact. (Think Roadrunner cartoons.) Things
> have gotten a lot better, and GNAT in particular tries to identify all
> cases where Storage_Error will always be raised (as warnings). But the
> real issue is that it is in general not possible to create a stack frame
> or allocate an object after an occurrence of Storage_Error.

I never got Storage_Error otherwise than in infinite recursion calls. 
The most frequent case lies outside Ada when interfacing C.

> It would be nice if there was a parameter which identified where in
> that particular compiler the Storage_Error came from.

Stack and local memory should be a part of the contract. E.g. "I don't 
raise Storage_Error when there is more than X storage elements free."

> Yes, Storage_Error
> is raised during execution, but the generated code or sometimes even the
> run-time library code has no clue you can use during debugging. I wonder
> how much could be done with Exception_Message.

Probably nothing because in most cases the information necessary is 
already lost.

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

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

* Re: Interfaces.C + generics: stack overflow
  2017-03-27  7:21             ` Dmitry A. Kazakov
@ 2017-03-30 17:12               ` Robert Eachus
  0 siblings, 0 replies; 14+ messages in thread
From: Robert Eachus @ 2017-03-30 17:12 UTC (permalink / raw)


On Monday, March 27, 2017 at 3:21:19 AM UTC-4, Dmitry A. Kazakov wrote:
>
> I never got Storage_Error otherwise than in infinite recursion calls. 
> The most frequent case lies outside Ada when interfacing C.

Dave and I worked at MITRE, mostly on software embedded in radar systems.  Since these systems were hard real time (a late answer is worse than wrong) virtual memory was used only on software development systems.  Debugging on real hardware usually cramped the actual software by using up any "spare" memory to load the debugger.  So not only did Storage_Error indicate a problem somewhere, but the site where Storage_Error was raised often had nothing to do with the "real" error where some component of the system used more than its allocated amount of memory.

On virtual memory systems, Storage_Error should occur only in two cases.  One where the limited assets allocate for some purpose are exhausted.  (Overflowing a task stack is the most usual, and pushing up the stack size the obvious fix.) The other is where you exhaust the virtual address space.  Those usually occur where array dimensions were not constrained.  (Notice that today, on 64-bit systems allocating a (2**31 byte) string when allocating the max for unbounded objects may sail right along. ;-)


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

end of thread, other threads:[~2017-03-30 17:12 UTC | newest]

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2017-03-23  7:43 Interfaces.C + generics: stack overflow hreba
2017-03-23  7:46 ` hreba
2017-03-23 17:45 ` Jeffrey R. Carter
2017-03-24 12:20   ` hreba
2017-03-23 20:03 ` Randy Brukardt
2017-03-24 12:42   ` hreba
2017-03-24 20:13     ` Randy Brukardt
2017-03-24 22:03     ` Dmitry A. Kazakov
2017-03-25 14:17       ` hreba
2017-03-25 15:21         ` hreba
2017-03-26 22:34           ` Robert Eachus
2017-03-27  7:21             ` Dmitry A. Kazakov
2017-03-30 17:12               ` Robert Eachus
2017-03-25 15:23         ` Dmitry A. Kazakov

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