public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/40962]  New: [4.5.0,4.4.0,4.3.2] conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
@ 2009-08-04 14:24 reuter at physik dot uni-freiburg dot de
  2009-08-04 14:25 ` [Bug fortran/40962] " reuter at physik dot uni-freiburg dot de
                   ` (11 more replies)
  0 siblings, 12 replies; 13+ messages in thread
From: reuter at physik dot uni-freiburg dot de @ 2009-08-04 14:24 UTC (permalink / raw)
  To: gcc-bugs

The following test code below (which works with the NAG 5.2 Fortran Compiler) 
seems to choke over the conversion f-allocatable -> cptr -> fptr ->
f-allocatable. With NAG the output should be:
--------------------------------------------------
nagfor tab3.f90 -o tab3 && ./tab3
NAG Fortran Compiler Release 5.2(686)
[NAG Fortran Compiler normal termination]
In:   1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
Tmp:  1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
Out:  1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
-------------------------------------------------


For gfortran 4.5.0 the result is:
In:   1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
Tmp:  1  2  3 -1 -2 -3 -1 -2 -3 -4 -5 -6
Out:  1  2  3 -1 -2 -3 -4 -5 -6  0  0  0


while for gfortran 4.3.2 the result is:
-------------------------------------------------
In:   1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
Tmp:  1  2  3 -1 -2 -3 -1 -2 -3 -4 -5 -6
Out:  1  2  3 -1 -2 -3 -4 -5 -6 ** **  0

It looks as if the order of indices gets confused by gfortran in changing the
corresponding pointers. According to the F2003 Handbook this code should be
allowed. 


TEST PROGRAM:


----------------------------------------------------------
program main

   use iso_c_binding
   implicit none

   character(*), parameter :: fmt = "(A,40(1x,I2))"

   integer, parameter :: n1 = 2
   integer, parameter :: n2 = 3
   integer, parameter :: n3 = 2

   integer, dimension(2), parameter :: shape2 = (/ n1, n2 /)
   integer, dimension(3), parameter :: shape3 = (/ n1, n2, n3 /)

   integer, dimension(n1, n2), parameter :: &
     c0001 = reshape ( (/  1, 2,  3, 4,  5, 6 /), shape2)
   integer, dimension(n1, n2), parameter :: &
     c0002 = reshape ( (/ -1,-2, -3,-4, -5,-6 /), shape2)
   integer, dimension(n1, n2, n3), parameter :: &
     table_in = reshape ( (/ c0001, c0002 /), shape3)

   integer, dimension(:,:,:), allocatable, target :: table_out

   print fmt, "In: ", table_in

   ! Allocate table_out with shape=shape3
   allocate (table_out (n1, n2, n3))

   ! Set table_out via a C pointer
   call set_table (c_loc (table_out))

   print fmt, "Out:", table_out

contains

   subroutine set_table (cptr)

     type(c_ptr), intent(in) :: cptr
     integer, dimension(:,:,:), pointer :: table_tmp

     ! This should make table_tmp an alias to table_out
     call c_f_pointer (cptr, table_tmp, shape3)

     ! Now set the value of table_tmp
     table_tmp = table_in

     print fmt, "Tmp:", table_tmp

   end subroutine set_table

end program main
--------------------------------------------------


-- 
           Summary: [4.5.0,4.4.0,4.3.2] conversion problem for  f-
                    allocatable -> cptr -> fptr -> f-allocatable
           Product: gcc
           Version: 4.5.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: reuter at physik dot uni-freiburg dot de
 GCC build triplet: 4.5.0 Ref. svn r
  GCC host triplet: Linux 32bit, 64bit, MAC OS X
GCC target triplet: gcc, gfortran 4.3.2, 4.4.0, 4.5.0


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] [4.5.0,4.4.0,4.3.2] conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
@ 2009-08-04 14:25 ` reuter at physik dot uni-freiburg dot de
  2009-08-04 14:25 ` reuter at physik dot uni-freiburg dot de
                   ` (10 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: reuter at physik dot uni-freiburg dot de @ 2009-08-04 14:25 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from reuter at physik dot uni-freiburg dot de  2009-08-04 14:25 -------
Created an attachment (id=18297)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=18297&action=view)
test program for the bug report


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] [4.5.0,4.4.0,4.3.2] conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
  2009-08-04 14:25 ` [Bug fortran/40962] " reuter at physik dot uni-freiburg dot de
@ 2009-08-04 14:25 ` reuter at physik dot uni-freiburg dot de
  2009-08-04 16:10 ` [Bug fortran/40962] Conversion " burnus at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: reuter at physik dot uni-freiburg dot de @ 2009-08-04 14:25 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from reuter at physik dot uni-freiburg dot de  2009-08-04 14:25 -------
Created an attachment (id=18298)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=18298&action=view)
iso_varying_string.f90 needed for the example 


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
  2009-08-04 14:25 ` [Bug fortran/40962] " reuter at physik dot uni-freiburg dot de
  2009-08-04 14:25 ` reuter at physik dot uni-freiburg dot de
@ 2009-08-04 16:10 ` burnus at gcc dot gnu dot org
  2009-08-17 21:41 ` burnus at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-08-04 16:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from burnus at gcc dot gnu dot org  2009-08-04 16:09 -------
Thomas, as you know a bit about the array descriptor, can you have a look? The
problem seems to be in libgfortran/intrinsics/iso_c_binding.c's c_f_pointer*

Simplified test case:
One:  1  2 -1 -2
Two:  1  2  2 -1  
           ^^^^^

The dump is trival:
      D.1581 = (void *) &table;
      D.1582 = D.1581;
      set_table (&D.1582);
and
    c_f_pointer_i4 (*cptr, &table_tmp, &parm.1);

Thus the issue must be in
    c_f_pointer_i4


program main
   use iso_c_binding, only: c_ptr, c_loc, c_f_pointer
   implicit none
   integer, dimension(2,1,2), target :: table
   table = reshape ( (/ 1,2,-1,-2/), (/2,1,2/))
!   print '(a,12i3)', "One:", table
   call set_table (c_loc (table))
contains
   subroutine set_table (cptr)
     type(c_ptr), intent(in) :: cptr
     integer, dimension(:,:,:), pointer :: table_tmp
     call c_f_pointer (cptr, table_tmp, (/2,1,2/))
!     print '(a,12i3)', "Two:", table_tmp
   end subroutine set_table
end program main


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org, tkoenig at gcc dot gnu
                   |                            |dot org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
  GCC build triplet|4.5.0 Ref. svn r150253      |
   GCC host triplet|Linux 32bit, 64bit, MAC OS X|
 GCC target triplet|gcc, gfortran 4.3.2, 4.4.0, |
                   |4.5.0                       |
           Keywords|                            |wrong-code
      Known to fail|                            |4.5.0 4.4.0 4.3.2
   Last reconfirmed|0000-00-00 00:00:00         |2009-08-04 16:09:45
               date|                            |
            Summary|[4.5.0,4.4.0,4.3.2]         |Conversion problem for  f-
                   |conversion problem for  f-  |allocatable -> cptr -> fptr
                   |allocatable -> cptr -> fptr |-> f-allocatable
                   |-> f-allocatable            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (2 preceding siblings ...)
  2009-08-04 16:10 ` [Bug fortran/40962] Conversion " burnus at gcc dot gnu dot org
@ 2009-08-17 21:41 ` burnus at gcc dot gnu dot org
  2009-08-17 22:12 ` tkoenig at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-08-17 21:41 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from burnus at gcc dot gnu dot org  2009-08-17 21:41 -------
Another report - presumably the same problem:
http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/b184bd431c8dd3da#


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (3 preceding siblings ...)
  2009-08-17 21:41 ` burnus at gcc dot gnu dot org
@ 2009-08-17 22:12 ` tkoenig at gcc dot gnu dot org
  2009-08-20 17:16 ` tkoenig at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2009-08-17 22:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from tkoenig at gcc dot gnu dot org  2009-08-17 22:12 -------
I'll look at this for a bit.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (4 preceding siblings ...)
  2009-08-17 22:12 ` tkoenig at gcc dot gnu dot org
@ 2009-08-20 17:16 ` tkoenig at gcc dot gnu dot org
  2009-08-20 20:16 ` tkoenig at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2009-08-20 17:16 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from tkoenig at gcc dot gnu dot org  2009-08-20 17:16 -------
I have a patch.


-- 

tkoenig at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |tkoenig at gcc dot gnu dot
                   |dot org                     |org
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2009-08-04 16:09:45         |2009-08-20 17:16:12
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (5 preceding siblings ...)
  2009-08-20 17:16 ` tkoenig at gcc dot gnu dot org
@ 2009-08-20 20:16 ` tkoenig at gcc dot gnu dot org
  2009-08-20 20:43 ` tkoenig at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2009-08-20 20:16 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from tkoenig at gcc dot gnu dot org  2009-08-20 20:16 -------
Subject: Bug 40962

Author: tkoenig
Date: Thu Aug 20 20:16:15 2009
New Revision: 150974

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=150974
Log:
2009-08-20  Thomas Koenig  <tkoenig@gcc.gnu.org>

        PR libfortran/40962
        * iso_c_binding.c (c_f_pointer_u0):  Multiply stride by
        previous stride.

2009-08-20  Thomas Koenig  <tkoenig@gcc.gnu.org>

        PR libfortran/40962
        * c_f_pointer_tests_4.f90:  New test.


Added:
    trunk/gcc/testsuite/gfortran.dg/c_f_pointer_tests_4.f90
Modified:
    trunk/gcc/testsuite/ChangeLog
    trunk/libgfortran/ChangeLog
    trunk/libgfortran/intrinsics/iso_c_binding.c


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (6 preceding siblings ...)
  2009-08-20 20:16 ` tkoenig at gcc dot gnu dot org
@ 2009-08-20 20:43 ` tkoenig at gcc dot gnu dot org
  2009-08-20 20:56 ` tkoenig at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2009-08-20 20:43 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from tkoenig at gcc dot gnu dot org  2009-08-20 20:42 -------
Subject: Bug 40962

Author: tkoenig
Date: Thu Aug 20 20:42:38 2009
New Revision: 150975

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=150975
Log:
2009-08-20  Thomas Koenig  <tkoenig@gcc.gnu.org>

        PR libfortran/40962
        * iso_c_binding.c (c_f_pointer_u0):  Multiply stride by
        previous stride.

2009-08-20  Thomas Koenig  <tkoenig@gcc.gnu.org>

        PR libfortran/40962
        * c_f_pointer_tests_4.f90:  New test.


Added:
    branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/c_f_pointer_tests_4.f90
Modified:
    branches/gcc-4_4-branch/gcc/testsuite/ChangeLog
    branches/gcc-4_4-branch/libgfortran/ChangeLog
    branches/gcc-4_4-branch/libgfortran/intrinsics/iso_c_binding.c


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (7 preceding siblings ...)
  2009-08-20 20:43 ` tkoenig at gcc dot gnu dot org
@ 2009-08-20 20:56 ` tkoenig at gcc dot gnu dot org
  2009-09-12 13:44 ` J-A dot Martin at sympatico dot ca
                   ` (2 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2009-08-20 20:56 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from tkoenig at gcc dot gnu dot org  2009-08-20 20:56 -------
Fixed on trunk and 4.4, closing.

If anybody wants to backport the fix to 4.3, be my guest :-)


-- 

tkoenig at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (8 preceding siblings ...)
  2009-08-20 20:56 ` tkoenig at gcc dot gnu dot org
@ 2009-09-12 13:44 ` J-A dot Martin at sympatico dot ca
  2009-09-12 14:00 ` tkoenig at gcc dot gnu dot org
  2009-09-12 16:17 ` J-A dot Martin at sympatico dot ca
  11 siblings, 0 replies; 13+ messages in thread
From: J-A dot Martin at sympatico dot ca @ 2009-09-12 13:44 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from J-A dot Martin at sympatico dot ca  2009-09-12 13:43 -------
(In reply to comment #8)
> Subject: Bug 40962
> 
> Author: tkoenig
> Date: Thu Aug 20 20:42:38 2009
> New Revision: 150975
> 
> URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=150975
> Log:
> 2009-08-20  Thomas Koenig  <tkoenig@gcc.gnu.org>
> 
>         PR libfortran/40962
>         * iso_c_binding.c (c_f_pointer_u0):  Multiply stride by
>         previous stride.
> 
> 2009-08-20  Thomas Koenig  <tkoenig@gcc.gnu.org>
> 
>         PR libfortran/40962
>         * c_f_pointer_tests_4.f90:  New test.
> 
> 
> Added:
>     branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/c_f_pointer_tests_4.f90
> Modified:
>     branches/gcc-4_4-branch/gcc/testsuite/ChangeLog
>     branches/gcc-4_4-branch/libgfortran/ChangeLog
>     branches/gcc-4_4-branch/libgfortran/intrinsics/iso_c_binding.c
> 

It doesn't work if the  3rd dimension is > 2
The test case only shows the array shape. It should fill the sample arrays and
compares.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (9 preceding siblings ...)
  2009-09-12 13:44 ` J-A dot Martin at sympatico dot ca
@ 2009-09-12 14:00 ` tkoenig at gcc dot gnu dot org
  2009-09-12 16:17 ` J-A dot Martin at sympatico dot ca
  11 siblings, 0 replies; 13+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2009-09-12 14:00 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from tkoenig at gcc dot gnu dot org  2009-09-12 14:00 -------
(In reply to comment #10)

> It doesn't work if the  3rd dimension is > 2
> The test case only shows the array shape.
> It should fill the sample arrays and
> compares.

The test case is:

! { dg-do run }
program main
   use iso_c_binding, only: c_ptr, c_loc, c_f_pointer
   implicit none
   integer, dimension(2,1,2), target :: table
   table = reshape ( (/ 1,2,-1,-2/), (/2,1,2/))
   call set_table (c_loc (table))
contains
   subroutine set_table (cptr)
     type(c_ptr), intent(in) :: cptr
     integer, dimension(:,:,:), pointer :: table_tmp
     call c_f_pointer (cptr, table_tmp, (/2,1,2/))
     if (any(table_tmp /= table)) call abort
     ! ^^^^^^^^^^^^^^^^^^^^^^
     ! comparison happens here
   end subroutine set_table
end program main

Output for the original test case is:

$ gfortran original.f90
$ ./a.out
In:   1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
Tmp:  1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
Out:  1  2  3  4  5  6 -1 -2 -3 -4 -5 -6


Do you have a failing test case?  If so, please
post it.  Are you using the wrong libraries, possibly?


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

* [Bug fortran/40962] Conversion problem for  f-allocatable -> cptr -> fptr -> f-allocatable
  2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
                   ` (10 preceding siblings ...)
  2009-09-12 14:00 ` tkoenig at gcc dot gnu dot org
@ 2009-09-12 16:17 ` J-A dot Martin at sympatico dot ca
  11 siblings, 0 replies; 13+ messages in thread
From: J-A dot Martin at sympatico dot ca @ 2009-09-12 16:17 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from J-A dot Martin at sympatico dot ca  2009-09-12 16:17 -------
(In reply to comment #11)
> (In reply to comment #10)
> 
> > It doesn't work if the  3rd dimension is > 2
> > The test case only shows the array shape.
> > It should fill the sample arrays and
> > compares.
> 
> The test case is:
> 
> ! { dg-do run }
> program main
>    use iso_c_binding, only: c_ptr, c_loc, c_f_pointer
>    implicit none
>    integer, dimension(2,1,2), target :: table
>    table = reshape ( (/ 1,2,-1,-2/), (/2,1,2/))
>    call set_table (c_loc (table))
> contains
>    subroutine set_table (cptr)
>      type(c_ptr), intent(in) :: cptr
>      integer, dimension(:,:,:), pointer :: table_tmp
>      call c_f_pointer (cptr, table_tmp, (/2,1,2/))
>      if (any(table_tmp /= table)) call abort
>      ! ^^^^^^^^^^^^^^^^^^^^^^
>      ! comparison happens here
>    end subroutine set_table
> end program main
> 
> Output for the original test case is:
> 
> $ gfortran original.f90
> $ ./a.out
> In:   1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
> Tmp:  1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
> Out:  1  2  3  4  5  6 -1 -2 -3 -4 -5 -6
> 
> 
> Do you have a failing test case?  If so, please
> post it.  Are you using the wrong libraries, possibly?
> 

I was using the wrong libraries.
Thank you.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=40962


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

end of thread, other threads:[~2009-09-12 16:17 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-08-04 14:24 [Bug fortran/40962] New: [4.5.0,4.4.0,4.3.2] conversion problem for f-allocatable -> cptr -> fptr -> f-allocatable reuter at physik dot uni-freiburg dot de
2009-08-04 14:25 ` [Bug fortran/40962] " reuter at physik dot uni-freiburg dot de
2009-08-04 14:25 ` reuter at physik dot uni-freiburg dot de
2009-08-04 16:10 ` [Bug fortran/40962] Conversion " burnus at gcc dot gnu dot org
2009-08-17 21:41 ` burnus at gcc dot gnu dot org
2009-08-17 22:12 ` tkoenig at gcc dot gnu dot org
2009-08-20 17:16 ` tkoenig at gcc dot gnu dot org
2009-08-20 20:16 ` tkoenig at gcc dot gnu dot org
2009-08-20 20:43 ` tkoenig at gcc dot gnu dot org
2009-08-20 20:56 ` tkoenig at gcc dot gnu dot org
2009-09-12 13:44 ` J-A dot Martin at sympatico dot ca
2009-09-12 14:00 ` tkoenig at gcc dot gnu dot org
2009-09-12 16:17 ` J-A dot Martin at sympatico dot ca

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).