Re: Patch to enable unlimited polymorphism to gfortran

2012-12-20 Thread Dominique Dhumieres
Dear Paul,

Apparently you have forgotten to commit the update for
same_type_as_1.f03.

Dominique


Re: Patch to enable unlimited polymorphism to gfortran

2012-12-19 Thread Paul Richard Thomas
Dear All,

Committed as revision 194622 and corrigendum 194626 (removes one test
from unlimited_polymorphic_2.f03).


Thanks to one and all for the help.


Paul

On 19 December 2012 07:17, Paul Richard Thomas
paul.richard.tho...@gmail.com wrote:
 Thanks Tobias and Dominique,

 I'll make the corrections that you have requested.  I believe that the
 2*(GFC_MAX_SYMBOL_LEN+1) has a historic origin - I had not thought
 about it until last night, when you pointed it out.

 As for the segfault - that line should go.  The automatic nulling of
 the _vptr of 'u1', on scope entry, has gone and so its value is
 indeterminate.  same_type_as takes the _vptrs as arguments - hence the
 segfault.

 I'll commit tonight unless anybody has any objections.

 Cheers

 Paul

 On 19 December 2012 00:18, Dominique Dhumieres domi...@lps.ens.fr wrote:
 Dear Paul,

 With your patch applied on top of a clean revision 194590, the executable
 for unlimited_polymorphic_1.f03 gives a Segmentation fault -
 invalid memory reference at

 Program received signal SIGSEGV, Segmentation fault.
 0x00011d1c in MAIN__ () at 
 /opt/gcc/p_work/gcc/testsuite/gfortran.dg/unlimited_polymorphic_1.f03:69
 69if (SAME_TYPE_AS (obj1, u1) .neqv. .FALSE.) call abort

 This segmentation fault disappears if I compile the test with
 -fsanitize=address, while valgrind gives an endless

 ==14264== Signal 11 being dropped from thread 0's queue

 Indeed this is on x86_64-apple-darwin10.

 TIA

 Dominique




 --
 The knack of flying is learning how to throw yourself at the ground and miss.
--Hitchhikers Guide to the Galaxy



-- 
The knack of flying is learning how to throw yourself at the ground and miss.
   --Hitchhikers Guide to the Galaxy


Re: Patch to enable unlimited polymorphism to gfortran

2012-12-18 Thread Tobias Burnus

Paul Richard Thomas wrote:

Please find attached an updated version of the patch, which I believe
answers your comments/objections.


Thanks for the patch. They patch is OK from my side, if you address the 
issues below.



+ /* Assign a hash value for an intrinsic type. The algorithm is that of SDBM.  
*/
+
+ unsigned int
+ gfc_intrinsic_hash_value (gfc_typespec *ts)
+ {
+   unsigned int hash = 0;
+   char c[2*(GFC_MAX_SYMBOL_LEN+1)];
+   int i, len;
+
+   strcpy (c[0], gfc_typename (ts));


I think you should simply use
   const char *c = gfc_typename (ts);
as you do not modify c. That saves some memory on the stack and avoids 
a function call. Additionally, it prevents me from wondering why you 
need more than GFC_MAX_SYMBOL_LEN.




+ /* Find (or generate) the symbol for an intrinsic types's vtab.  This is
+need to support unlimited polymorphism.  */


types's - type's



+   gfc_error (Actual argument to '%s' at %L must be unlimited 
+  polymorphic since the formal argument is %s, 
+  unlimited polymorphic entity [F2008: 12.5.2.5],
+  formal-name, actual-where,
+  CLASS_DATA (formal)-attr.class_pointer ?
+  a pointer : an allocatable);


I fear that translators will hate you for the %s with a pointer / 
an allocatable. At least when a pointer/an allocatable occurs 
elsewhere, they cannot properly translate it as the translation might 
depend whether it is subject or object in the sentence. Even if not, 
translators will not (easily) see that those strings belong to this 
error message.



+ if (UNLIMITED_POLY (tail-expr))
+   gfc_error (Unlimited polymorphic allocate-object at %L 
+  requires either a type-spec or SOURCE tag,
+  tail-expr-where);


That's not true. The standard also allows MOLD=. Thus, either add or 
MOLD or change SOURCE tag to source-expr(ession), which covers both.


I haven't checked the source code, but you might have to add an  
!mold as well.



Tobias


Re: Patch to enable unlimited polymorphism to gfortran

2012-12-18 Thread Dominique Dhumieres
Dear Paul,

With your patch applied on top of a clean revision 194590, the executable
for unlimited_polymorphic_1.f03 gives a Segmentation fault - 
invalid memory reference at

Program received signal SIGSEGV, Segmentation fault.
0x00011d1c in MAIN__ () at 
/opt/gcc/p_work/gcc/testsuite/gfortran.dg/unlimited_polymorphic_1.f03:69
69if (SAME_TYPE_AS (obj1, u1) .neqv. .FALSE.) call abort

This segmentation fault disappears if I compile the test with
-fsanitize=address, while valgrind gives an endless

==14264== Signal 11 being dropped from thread 0's queue

Indeed this is on x86_64-apple-darwin10.

TIA

Dominique



Re: Patch to enable unlimited polymorphism to gfortran

2012-12-18 Thread Paul Richard Thomas
Thanks Tobias and Dominique,

I'll make the corrections that you have requested.  I believe that the
2*(GFC_MAX_SYMBOL_LEN+1) has a historic origin - I had not thought
about it until last night, when you pointed it out.

As for the segfault - that line should go.  The automatic nulling of
the _vptr of 'u1', on scope entry, has gone and so its value is
indeterminate.  same_type_as takes the _vptrs as arguments - hence the
segfault.

I'll commit tonight unless anybody has any objections.

Cheers

Paul

On 19 December 2012 00:18, Dominique Dhumieres domi...@lps.ens.fr wrote:
 Dear Paul,

 With your patch applied on top of a clean revision 194590, the executable
 for unlimited_polymorphic_1.f03 gives a Segmentation fault -
 invalid memory reference at

 Program received signal SIGSEGV, Segmentation fault.
 0x00011d1c in MAIN__ () at 
 /opt/gcc/p_work/gcc/testsuite/gfortran.dg/unlimited_polymorphic_1.f03:69
 69if (SAME_TYPE_AS (obj1, u1) .neqv. .FALSE.) call abort

 This segmentation fault disappears if I compile the test with
 -fsanitize=address, while valgrind gives an endless

 ==14264== Signal 11 being dropped from thread 0's queue

 Indeed this is on x86_64-apple-darwin10.

 TIA

 Dominique




-- 
The knack of flying is learning how to throw yourself at the ground and miss.
   --Hitchhikers Guide to the Galaxy


Re: Patch to enable unlimited polymorphism to gfortran

2012-12-16 Thread Tobias Burnus
Thanks for the patch, here is a first but incomplete review. I think the 
patch looks mostly okay.



Running your test cases through crayftn, I found:

  if (SAME_TYPE_AS (obj1, u1) .neqv. .FALSE.) call abort
  ^
ftn-1698 crayftn: ERROR $MAIN, File = unlimited_polymorphic_1.f03, Line 
= 67, Column = 27
Type INTEGER(kind=4) is not allowed for the B argument of intrinsic 
SAME_TYPE_AS.


The message itself is correct. However, Paul mentioned off-list that 
obj1 and u1 are both extensible types and, hence, neither is an 
integer(kind=4). In any case, if either of them were an integer(4) it 
would be invalid:


From Fortran 2008's 13.7.142 SAME_TYPE_AS (A, B)
Arguments.
A shall be an object of extensible declared type or unlimited 
polymorphic. If it is a pointer, it shall not have an undefined 
association status.
B shall be an object of extensible declared type or unlimited 
polymorphic. If it is a pointer, it shall

not have an undefined association status.

Ditto for 13.7.60 EXTENDS TYPE OF (A, MOLD).

At least for -std=f2003/f2008 we have to reject nonextensible, 
non-unlimited-polymorphic arguments. - Even if a supporting intrinsic 
types were a nice addition.



Paul Richard Thomas wrote:

+
+   if (UNLIMITED_POLY (c-expr))
+   {
+ gfc_error (F08: C4106 array constructor value at %L shall not be 
+ unlimited polymorphic, c-expr-where);
+ t = FAILURE;


You have a   at both then end and the beginning of the line. 
Additionally, I wonder how we want to inform the user about those 
constrains. So far, we always had the message only without reference to 
the standard. Having one, is not bad, the question is only where. I 
would favor to have the information at the end, given that gfortran 
currently prints Fortran 2008: if a something is only valid in Fortran 
2008 and later. Additionally, I personally don't like F08 that much 
and prefer Fortran 2008 (or at least F2008). Thus, I'd use something 
like:


+ gfc_error (Array constructor value at %L shall not be unlimited
+ polymorphic [Fortran 2008, C4106], c-expr-where);


(Except for the double  , that's bikeshadding; hence, I leave it to 
you. The F08: C... also occures at other places in the patch)




+sprintf (dt_name, %s, $tar);

(Off-topic question for mere curiosity: Why $tar?)


+ gfc_find_intrinsic_vtab (gfc_typespec *ts)

+   if (ts-type == BT_CHARACTER  ts-deferred)
+ {
+   gfc_error (TODO: Deferred character length variable at %C cannot 
+yet be associated with unlimited polymorphic entities);


The same issue also applies to assumed-length strings. At least the 
following program prints:

   0 
   0 
I think we have to fill a PR which lists all of the known deficits of 
the current implementation. Besides the string issue, that's also the 
renaming of gfc_find_intrinsic_vtab into gfc_find_derived_vtab.


Here's the test case:

call foo(Hello)
call foo(World!)
contains
subroutine foo(str)
  character(len=*), target :: str
  class(*), pointer :: up
  up = str
  call bar(up)
end subroutine foo
subroutine bar(x)
  class(*) :: x

  select type(x)
type is (character(len=*))
  print *, len(x), ''//x//''
  end select
end subroutine bar
end




+ #define UNLIMITED_POLY(sym) (sym != NULL  sym-ts.type == BT_CLASS  
CLASS_DATA (sym) \
+CLASS_DATA (sym)-ts.u.derived \
+CLASS_DATA 
(sym)-ts.u.derived-attr.unlimited_polymorphic)


The lines are way too long: 90 and 86 characters.



+   sprintf (name, __tmp_%s_%d, gfc_basic_typename (ts-type),
+  ts-type == BT_CHARACTER ? charlen : ts-kind);


How do you distinguish between character(kind=1) and character(kind=4)? 
The same issue exists for a like-wise code in resolve_select_type.



+  /* Unlimited polymorphic pointers should have their vptr nullified.  */
+  if (UNLIMITED_POLY (sym)  CLASS_DATA (sym)-attr.pointer)
+gfc_defer_symbol_init (sym);


Why? If the pointer has never been pointer-associated, one shouldn't 
access it. Thus, the code is not need. If it is needed, I fear that code 
will also break when one later deallocates/nullifies the pointer. I 
think _vptr should only be set when also nonpolymorphic CLASS get their 
_vptr set. For pointers, that's presumably only ALLOCATE and 
pointer-association.



Tobias


Re: Patch to enable unlimited polymorphism to gfortran

2012-12-16 Thread Paul Richard Thomas
Dear Tobias,

Up front, thanks for this initial feedback.  Dominique informed me on
#gfortran that the patch works as advertised.

...snip...
 Running your test cases through crayftn, I found:

   if (SAME_TYPE_AS (obj1, u1) .neqv. .FALSE.) call abort
   ^
 ftn-1698 crayftn: ERROR $MAIN, File = unlimited_polymorphic_1.f03, Line =
 67, Column = 27
 Type INTEGER(kind=4) is not allowed for the B argument of intrinsic
 SAME_TYPE_AS.
...snip...
 At least for -std=f2003/f2008 we have to reject nonextensible,
 non-unlimited-polymorphic arguments. - Even if a supporting intrinsic types
 were a nice addition.

gfortran was already giving an error at the right place - see
same_type_as_1.f03  I have improved the message to contain the name of
the offending type, like the Cray compiler.  I believe the Cray
compiler has a bug at this point.
.
..snip...

 You have a   at both then end and the beginning of the line. Additionally,

Indeed - thanks

...snip...

 F2008). Thus, I'd use something like:

 + gfc_error (Array constructor value at %L shall not be unlimited
 + polymorphic [Fortran 2008, C4106], c-expr-where);



That's fine by me. I have changed all the messages, as suggested.
However, F03/08 is so widespread in comments that I have left well
alone.


 (Off-topic question for mere curiosity: Why $tar?)

Well '$' is non-alphanumeric but is just an 's' with a bar through it :-)


 The same issue also applies to assumed-length strings. At least the
 following program prints:
0 
0 

Adding an error to pick up assumed length is proving to be problematic
because the TYPE IS selector is assumed length.  I'll think about it
some  more.

 I think we have to fill a PR which lists all of the known deficits of the
 current implementation. Besides the string issue, that's also the renaming
 of gfc_find_intrinsic_vtab into gfc_find_derived_vtab.

I did not do this immediately because the latter takes the derived
type, whilst the former uses the typespec. When the two are rolled
into one function, the typespec will be used.

I agree that a catch-all PR is needed for class(*) limitations.

...snip...



 + #define UNLIMITED_POLY(sym) (sym != NULL  sym-ts.type == BT_CLASS 
 CLASS_DATA (sym) \
 +CLASS_DATA (sym)-ts.u.derived \
 +CLASS_DATA
 (sym)-ts.u.derived-attr.unlimited_polymorphic)


 The lines are way too long: 90 and 86 characters.

Blush - yes, you are right. Done.



 +   sprintf (name, __tmp_%s_%d, gfc_basic_typename (ts-type),
 +  ts-type == BT_CHARACTER ? charlen : ts-kind);


 How do you distinguish between character(kind=1) and character(kind=4)? The
 same issue exists for a like-wise code in resolve_select_type.

I have introduced that distinction seemingly without anything breaking!
TYPE IS (CHARACTER(*, kind = 4) works fine.



 +  /* Unlimited polymorphic pointers should have their vptr nullified.  */
 +  if (UNLIMITED_POLY (sym)  CLASS_DATA (sym)-attr.pointer)
 +gfc_defer_symbol_init (sym);


 Why? If the pointer has never been pointer-associated, one shouldn't access

It's so that SAME_TYPE_AS and EXTENDS_TYPE_OF do the right thing with
unassociated pointers.  I am not sure that I understand your concern
if the code is needed.

Cheers

Paul


Re: Patch to enable unlimited polymorphism to gfortran

2012-12-16 Thread Tobias Burnus

Paul Richard Thomas wrote:

+  /* Unlimited polymorphic pointers should have their vptr nullified.  */
+  if (UNLIMITED_POLY (sym)  CLASS_DATA (sym)-attr.pointer)
+gfc_defer_symbol_init (sym);


Why? If the pointer has never been pointer-associated, one shouldn't access

It's so that SAME_TYPE_AS and EXTENDS_TYPE_OF do the right thing with
unassociated pointers.  I am not sure that I understand your concern
if the code is needed.


It's not really a concern. I just see it as missed code-size/performance 
optimization as I believe that it is not needed.


Adding
  ptr-_vptr = NULL
directly after declaration of a local pointer variable is pointless. 
Such a variable has an undefined pointer association status. And for 
same_type_as and extends_type_of the argument may not be such a pointer. 
Only unassociated pointers are allowed. In order to create such a 
pointer, one either needs an initialization like in

  class(*), pointer :: ptr = null()
or has to explicitly call ptr=null() or nullify(ptr). That's not 
different to other pointers and in particular not different to 
CLASS(name) types.


In other words, the following program is invalid as ptr has an 
undefined pointer association status:


type(t), target :: x
class(*), pointer :: ptr
print *, same_type_as (ptr, x)  !  invalid: foo is an undefined pointer

while the following code is valid (and causes an ICE):

type(t), target :: x
class(*), pointer :: ptr = NULL()  ! pointer initialization
print *, same_type_as (ptr, x)

as is

type(t), target :: x
class(*), pointer :: ptr
! ptr = x  ! optionally
ptr = NULL()
print *, same_type_as (ptr, x)

 * * *

By the way, the following code also causes an ICE. I think it is valid 
since Fortran 2008:


type t
end type t
type(t), target :: x
class(*), pointer :: ptr = x
print *, same_type_as (ptr, x)
end

Namely:

R442   component-initialization is   [...]  or   = initial-data-target
C460 (R442) If initial-data-target appears, component-name shall be 
data-pointer-initialization compatible with it.
If initial-data-target appears for a data pointer component, that 
component in any object of the type is initially associated with the 
target or becomes associated with the target as specied in 16.5.2.3.


Tobias


Re: Patch to enable unlimited polymorphism to gfortran

2012-12-16 Thread Tobias Burnus

Paul Richard Thomas wrote:

The problem is with the way in which extends_type_of is organised.  It
takes the _vptr directly.  Unless it is null for undefined pointers, a
segfault is triggered.


So what? If I have:
  integer, pointer :: ptr
  ptr = 5
will also lead to a segfault (or a bus error); I do not see the 
difference. Here, the integer pointer ptr is not defj ned while for

  class(*), pointer :: poly_ptr
both the value (poly_ptr-_data) and the pointer to the virtual table 
(poly_ptr-_vptr) is uninitialized. I really do not see a difference. In 
any case, the Fortran standard explicitly doesn't allow code like

   class(*), pointer :: ptr, ptr2
   print *, same_type_as(ptr, ptr2)
as if either of the arguments is an undefined pointer. That's different 
to allocatables. Those are automatically in the nonallocatable state and 
hence

   class(*), allocatable :: ptr, ptr2
   print *, same_type_as(ptr, ptr2)
is valid.



Side remark: I think the following code is always true as you use 
attr.pointer instead of attr.class_pointer:


 +  if (UNLIMITED_POLY (sym)  CLASS_DATA (sym)-attr.pointer)
 +gfc_defer_symbol_init (sym);

Still, I believe that the automatic definition of sym-_vptr should only 
be done for allocatables (i.e. nonpointers). As CLASS(...), allocatable 
is already handled, the three lines should go for good.



I guess that I could achieve the same thing with the default initialization.


I am not sure whether I correctly understand this remark. I am think 
poly_ptr shouldn't be automatically be set, only via an explict pointer 
assignment, explict initialization, explict default initialization and 
explict nullify(). Hence, I believe adding code which does so 
automatically - and not when the user explicitly ask for it - is a 
missed optimization (useless gfortran code plus in extra instructions 
(code size/performance) for the generated code).



Initialization of class(*) pointers appears to be stuffed, as you
point out.  I'll try to figure it out tomorrow night.


Thanks! Please also ensure that

integer, target :: tgt
type t
   class(*), pointer :: poly1 = null()
   class(*), pointer :: poly2 = tgt
! class(*), pointer :: poly3 = poly2  ! Invalid*
end type

is supported. (* I believe this line is invalid: the data-target needs to be something which is 
link-time resolvable and poly3 = poly2 isn't as poly3 has to point to the 
target of poly2 not to poly2.)


Tobias