[Bug fortran/24518] Intrinsic MOD incorrect for large arg1/arg2 and slow.

2006-10-31 Thread paul dot richard dot thomas at cea dot fr


--- Comment #16 from paul dot richard dot thomas at cea dot fr  2006-10-31 
16:14 ---
Subject: RE:  Intrinsic MOD incorrect for large arg1/arg2 and slow.

FX,

> 
> --- Comment #15 from fxcoudert at gcc dot gnu dot org  
> 2006-10-31 16:05 ---
> (In reply to comment #14)
> > It also does MODULO correctly
> 
> Why not use remainder{f,,l}? Is it incorrect?

I understood that remainder (a, b) = a - round (a/b) * b, whereas
  mod (a, b) = a - int (a/b) * b
  and modulo (a, b) = a - floor (a/b) * b

but I am ready to stand corrected on the first.  The latter two are taken from
the fortran standard.

Paul


-- 


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



[Bug fortran/25708] Module loading is not good at all

2006-10-31 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-10-31 
08:29 ---
Subject: RE:  Module loading is not good at all

FX

> -Message d'origine-
> De : fxcoudert at gcc dot gnu dot org 
> [mailto:[EMAIL PROTECTED]
> Envoyé : mardi 31 octobre 2006 08:01
>
> I like that idea. I've looked at the code in symbol.c, and 
> don't see clearly
> how to get it done (where do you get the master symtree from, eg?)
> 

I haven't really thought about this enough yet but.

(i) I think that a namespace will have to be built for each module.  This will
allow the initial part of read_module to be left completely unmodified. *grin*

(ii) The namespaces should be contained in a linked list or binary tree; the
structures should be something like

typedef struct gfc_module_namespace
{
  const char *name;
  struct gfc_module_namespace *next;
  maybe some attributes?;
}
gfc_module_namespace;

I think that a list should be sufficient, since numbers of modules are likely
to remain limited for real-life codes aren't they?  Or is your 25Mb monster
an indication that I am wrong?

(iii) As the modules get USEd, new symtrees are added to the current namespace
and I think that it is OK to point to the symbols in the module namespaces.
This would simplify derived type association a lot.  I have not the foggiest
idea what to do about interfaces; they are on my list of urgent things to try
to understand.  I am about to create a meta-bug of interface PRs. I had a
notion to look at modules after I had had a stab at that.

(There is a PR on doubly USEd interfaces that I had a stab at in the airport
last Friday - I got absolutely nowhere; even though I thought that I was
touching the right places, it had no effect on the fault!  This is one and the
same problem of doubly USEd variables that I fixed by explicitly going through
and checking each against the other.  To do likewise for interfaces requires
some understanding!  I note, however, that these problems are fixed in g95 and
there is no sign whatsoever of the corresponding fixes... It is a crying shame
that Andy Vaught is not on-side.) 

(iv) As at present, the symtree carries the local name and the symbol the true
name - that's why I think that the symbols can be shared.

Regards

Paul

(v) Clearly, a clean-up at the end of the compilation of the file will have to
be done but all the mechanisms to do that exist already.

As I say, the problems are a) interfaces, b) interfaces and c) interfaces.

Ciao

Paul


-- 


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



[Bug fortran/27701] Two routines with the same name cause an interna; error in gfortran

2006-10-02 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-10-02 
14:32 ---
(In reply to comment #1)
> The problem occurs on i386-*-freebsd

Noting that adding a dummy to the first of the subroutine declarations allows
the compiler to detect that there are two subroutines of the same name, we are
led by the error mesage to decl.c:636. The condition for detection of a
previously defined procedure is sym->formal [!= NULL].  Thus the case above
escapes. Patching this with:

Index: gcc/fortran/decl.c
===
*** gcc/fortran/decl.c  (révision 117367)
--- gcc/fortran/decl.c  (copie de travail)
*** get_proc_name (const char *name, gfc_sym
*** 635,641 
 accessible names.  */
if (sym->attr.flavor != 0
&& sym->attr.proc != 0
!   && sym->formal)
gfc_error_now ("Procedure '%s' at %C is already defined at %L",
   name, &sym->declared_at);

--- 635,642 
 accessible names.  */
if (sym->attr.flavor != 0
&& sym->attr.proc != 0
!   && (sym->attr.subroutine || sym->attr.function)
!   && sym->attr.if_source != IFSRC_UNKNOWN)
gfc_error_now ("Procedure '%s' at %C is already defined at %L",
   name, &sym->declared_at);

seems to do the right thing.  The attributes subroutine and function are not of
themselves enough, as I discovered when I had to correct the original patch.
This condition was replaced with that on sym->formal and tested with
internal_references_2.f90. Adding the check that the symbol has an interface
source to the subroutine/function test accomplishes the same thing and scoops
up procedures without dummies.

It regtests OK on Cygwin_NT/PIV.

Paul


-- 


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



[Bug fortran/29315] error passing an array derived from type element

2006-10-02 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-10-02 
08:09 ---
(In reply to comment #2)
> Confirmed, we don't set the stride correctly as far as I can tell.

This comes about because of the admitted kludge in the mechanism for passing
components of derived type arrays. At line 1588 in trans-exp.c, you will find
the comment:

/* Returns a reference to a temporary array into which a component of
   an actual argument derived type array is copied and then returned
   after the function call.
   TODO Get rid of this kludge, when array descriptors are capable of
   handling aliased arrays.  */

Maybe the time has come for byte size strides, although it will be a horrific
job to implement.

Paul


-- 


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



[Bug fortran/25818] Problem with handling optional and entry master arguments

2006-09-18 Thread paul dot richard dot thomas at cea dot fr


--- Comment #7 from paul dot richard dot thomas at cea dot fr  2006-09-18 
15:33 ---
I mixed up my types above; using a gfc_array_index_type seems to
cover every circumstance where missing arguments can be addressed
with legal code.

Regtests on FC5/Athlon.

Index: gcc/fortran/trans-decl.c
===
*** gcc/fortran/trans-decl.c(revision 116268)
--- gcc/fortran/trans-decl.c(working copy)
*** build_entry_thunks (gfc_namespace * ns)
*** 1561,1566 
--- 1561,1568 
tree args;
tree string_args;
tree tmp;
+   tree zero;
+   bool zero_flag;
locus old_loc;

/* This should always be a toplevel function.  */
*** build_entry_thunks (gfc_namespace * ns)
*** 1580,1585 
--- 1582,1590 

gfc_start_block (&body);

+   zero_flag = false;
+   zero = NULL_TREE;
+
/* Pass extra parameter identifying this entry point.  */
tmp = build_int_cst (gfc_array_index_type, el->id);
args = tree_cons (NULL_TREE, tmp, NULL_TREE);
*** build_entry_thunks (gfc_namespace * ns)
*** 1616,1621 
--- 1621,1627 
  if (thunk_formal)
{
  /* Pass the argument.  */
+ /* TODO - missing optional arguments.  */
  DECL_ARTIFICIAL (thunk_formal->sym->backend_decl) = 1;
  args = tree_cons (NULL_TREE, thunk_formal->sym->backend_decl,
args);
*** build_entry_thunks (gfc_namespace * ns)
*** 1627,1634 
}
  else
{
! /* Pass NULL for a missing argument.  */
! args = tree_cons (NULL_TREE, null_pointer_node, args);
  if (formal->sym->ts.type == BT_CHARACTER)
{
  tmp = build_int_cst (gfc_charlen_type_node, 0);
--- 1633,1651 
}
  else
{
! /* Pass the address of a long zero for any argument that
!is not used in this thunk.  */
! if (!zero_flag)
!   {
! tmp = build_int_cst (intQI_type_node, 0);
! zero = gfc_create_var (intQI_type_node, NULL);
! gfc_add_modify_expr (&body, zero, tmp);
! zero = fold_convert (pvoid_type_node,
!  build_fold_addr_expr (zero));
! zero_flag = true;
!   }
! args = tree_cons (NULL_TREE, zero, args);
!
  if (formal->sym->ts.type == BT_CHARACTER)
{
  tmp = build_int_cst (gfc_charlen_type_node, 0);


-- 


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



[Bug fortran/29115] ICE in structure constructor for array, ponter component with non-pointer data

2006-09-18 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-09-18 
15:29 ---
This is still better and even regtests!

Index: gcc/fortran/resolve.c
===
*** gcc/fortran/resolve.c   (révision 116697)
--- gcc/fortran/resolve.c   (copie de travail)
*** resolve_structure_cons (gfc_expr * expr)
*** 583,588 
--- 593,599 
gfc_constructor *cons;
gfc_component *comp;
try t;
+   symbol_attribute a;

t = SUCCESS;
cons = expr->value.constructor;
*** resolve_structure_cons (gfc_expr * expr)
*** 597,606 
for (; comp; comp = comp->next, cons = cons->next)
  {
if (! cons->expr)
!   {
! t = FAILURE;
! continue;
!   }

if (gfc_resolve_expr (cons->expr) == FAILURE)
{
--- 608,614 
for (; comp; comp = comp->next, cons = cons->next)
  {
if (! cons->expr)
!   continue;

if (gfc_resolve_expr (cons->expr) == FAILURE)
{
*** resolve_structure_cons (gfc_expr * expr)
*** 622,627 
--- 630,648 
  else
t = gfc_convert_type (cons->expr, &comp->ts, 1);
}
+ 
+   if (!comp->pointer || cons->expr->expr_type == EXPR_NULL)
+   continue;
+ 
+   a = gfc_expr_attr (cons->expr);
+ 
+   if (!a.pointer && !a.target)
+   {
+ t = FAILURE;
+ gfc_error ("The element in the derived type constructor at %L, "
+"for pointer component '%s' should be a POINTER or "
+"a TARGET", &cons->expr->where, comp->name);
+   }
  }

return t;


-- 


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



[Bug fortran/29098] allocation of a pointer to a derived type crashes

2006-09-15 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-09-15 
14:16 ---
Created an attachment (id=12276)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12276&action=view)
A fix for the problem

The handling of default initializers can never have been quite right. The
moment that there is an interface assignement, this is called by ALLOCATE, for
example.  Adding a dimension(2) array to your structure, ALLOCATE produces,
with the patch applied:

  {
void * * ptr.1;

ptr.1 = (void * *) &matrix;
_gfortran_allocate (ptr.1, 80, 0);
  }
  {
struct block D.943;
struct block block.2;

{
  int4 S.3;

  S.3 = 1;
  while (1)
{
  if (S.3 > 2) goto L.2; else (void) 0;
  block.2.blank[NON_LVALUE_EXPR  + -1] = 0;
  S.3 = S.3 + 1;
}
  L.2:;
}
block.2.r.data = 0B;
block.2.c.data = 0B;
block.2.no.data = 0B;
D.943 = block.2;
blassign (matrix, &D.943);
  }

If I now make formal argument a INTENT(OUT), this last block of code is
repeated but with a structure assignment this time, rather than blassign!

Some furthr sorting out is needed!

Paul   


-- 


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



[Bug fortran/29098] allocation of a pointer to a derived type crashes

2006-09-15 Thread paul dot richard dot thomas at cea dot fr


--- Comment #1 from paul dot richard dot thomas at cea dot fr  2006-09-15 
13:12 ---
Olav,

Thanks for the contribution:

   TYPE BLOCK
  INTEGER, DIMENSION(:), POINTER ::  R => NULL(),C => NULL()
  TYPE(BAS), POINTER, DIMENSION(:) :: NO => NULL ()
   END TYPE BLOCK

gives you a workaround that loses you nothing.

ALLOCATE (matrix) then produces

  {
void * * ptr.0;

ptr.0 = (void * *) &matrix;
_gfortran_allocate (ptr.0, 72, 0);
  }
  {
struct block D.929;
struct block block.1;

block.1.r.data = 0B;
block.1.c.data = 0B;
block.1.no.data = 0B;
D.929 = block.1;
blassign (matrix, &D.929);
  }

It is the last line that triggers the error.

Paul


-- 


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



[Bug fortran/28526] 'end' is recognized as a variable incorrectly

2006-09-14 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-09-14 
15:23 ---
> module m
>   public function
>   interface function
>  module procedure foo4
>   end interface
> contains
>   subroutine foo4
>   end subroutine foo4
>   function foo5
> foo5 = 0
>   end function foo5
> end module

If function foo5 is declared with a formal arglist or with empty brackets, this
example compiles correctly. The matcher is certainly behaving oddly!

This cures the original problem and does not seem to cause any regressions up
to "contained_1.f90" (I ran out of time this afternoon!).

Index: gcc/fortran/parse.c
===
*** gcc/fortran/parse.c (révision 116697)
--- gcc/fortran/parse.c (copie de travail)
*** decode_statement (void)
*** 110,115 
--- 110,120 
input "REALFUNCTIONA(N)" can mean several things in different
contexts, so it (and its relatives) get special treatment.  */

+   if (gfc_match_end (&st) == MATCH_YES)
+ return st;
+   gfc_undo_symbols ();
+   gfc_current_locus = old_locus;
+
if (gfc_current_state () == COMP_NONE
|| gfc_current_state () == COMP_INTERFACE
|| gfc_current_state () == COMP_CONTAINS)
*** decode_statement (void)
*** 208,215 
match ("else if", gfc_match_elseif, ST_ELSEIF);
match ("enum , bind ( c )", gfc_match_enum, ST_ENUM);

-   if (gfc_match_end (&st) == MATCH_YES)
-   return st;

match ("entry% ", gfc_match_entry, ST_ENTRY);
match ("equivalence", gfc_match_equivalence, ST_EQUIVALENCE);
--- 213,218 
*** parse_derived (void)
*** 1499,1504 
--- 1502,1509 
int compiling_type, seen_private, seen_sequence, seen_component,
error_flag;

gfc_statement st;
gfc_state_data s;
+   gfc_symbol *sym;
+   gfc_component *c;

error_flag = 0;

The matching of END can be moved after the next if block but no more.  One or
more of the matchers are not cleaning up after figuring "END" to be a variable
(a LHS?) and trying a match to an assignment or data statement.

Paul


-- 


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



[Bug fortran/28817] [gfortran] problems with -Wunused

2006-09-14 Thread paul dot richard dot thomas at cea dot fr


--- Comment #1 from paul dot richard dot thomas at cea dot fr  2006-09-14 
09:09 ---
> This is most likely related to (or identical with) PR21918.

Martin, that is spot on.  In fact, Tobi's patch works fine; albeit a bit more
verbosely.  Also, the locii need to be indirectly referenced, otherwise a
segfault occurs.

Paul


-- 


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



[Bug fortran/29060] spread causes ICE in gfc_trans_array_constructor

2006-09-14 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-09-14 
08:45 ---
Created an attachment (id=12265)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12265&action=view)
Patch to provide the shape of the SPREAD intrinsic + testcase

(In reply to comment #1)
> Yes, it appears to be related to spread.  If you comment out the 
> spread() in the subroutine the compiles.  Additionally, if you
> change "x%position(:,1:2)" to "x%position(1:3,1:2)", then the
> code compiles.  So, it looks like gfortran isn't interpreting the
> index ranges from spread correctly if the lefthand side doesn't
> have explicit ranges of indicies.
Steve,

That's right; neither the parameter array nor the call to SPREAD are passing
the shape information to the scalarizer. Replacing the parameter by a variable
permits the compilation to succeed.

This is a minimal test case that illustrates the problem:

  real,dimension(:,:),pointer :: ptr
  real,dimension(1,2),parameter :: u = reshape((/ 0.25,0.75 /),(/1,2/))
  ptr(:,:) = u + spread((/1.0/),2,size(u,2))
end

It is fixed by the attached, as yet, unregtested patch.  You will also find a
dejagnuified testcase.

I will do the regtest this afternoon and will submit tonight.

Best regards

Paul


-- 


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



[Bug fortran/28890] ICE on write

2006-09-11 Thread paul dot richard dot thomas at cea dot fr


--- Comment #6 from paul dot richard dot thomas at cea dot fr  2006-09-11 
08:15 ---
The patch did not apply cleanly to 4.1; I will take a look tonight to try to
understand why.

Paul


-- 


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



[Bug fortran/28914] Code inside loop hangs; outside loop runs normally; runs OK on other compilers

2006-09-04 Thread paul dot richard dot thomas at cea dot fr


--- Comment #8 from paul dot richard dot thomas at cea dot fr  2006-09-04 
12:08 ---
Even simpler is:

trans-array.c(gfc_trans_array_constructor_value)

replace   loopvar = se.expr;
byloopvar = gfc_evaluate_now (se.expr, pblock);

gfc_expand_constructor is called from resolve_expr and from three places in
expr.c.  As far as I can tell, non-initialization expressions only try the
expansion from resolve_expr.  If I flag the calls to distinguish them and limit
the maximum number of expanded elements to 10, say, in gfc_expand_constructor,
the code reflects this but the compilation time does not.  Something, somewhere
is doing a temporary expansion of the constructor, which is taking all the
time.

I have to leave this again but I will get to the bottom of it.

Paul


-- 


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



[Bug fortran/28908] [4.1/4.2 Regression]: fold_convert fails for Fortran operator

2006-09-04 Thread paul dot richard dot thomas at cea dot fr


--- Comment #29 from paul dot richard dot thomas at cea dot fr  2006-09-04 
10:31 ---
Created an attachment (id=12183)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12183&action=view)
Fix for HJ's problems

HJ,

Could you try this one, please?  I am pretty certain it will do the job.

Thanks

Paul


-- 


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



[Bug fortran/28914] Code inside loop hangs; outside loop runs normally; runs OK on other compilers

2006-09-01 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-09-01 
13:48 ---
Created an attachment (id=12168)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12168&action=view)
A provisional fix for the problem

This is not regtested.

Also, I know that there is a better way to detect a declared variable; however,
I am up to my eyeballs getting TR15541 out of the door... wait a few days, I
will sort this one.

Paul


-- 


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



[Bug fortran/28914] Code inside loop hangs; outside loop runs normally; runs OK on other compilers

2006-09-01 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-09-01 
13:45 ---
(In reply to comment #3)
> Setting the parameter n=65535, the program appears to execute correctly. 
> However, the pr28914.f90.003t.original file is 706800 bytes long and embedded
> with a very large static declaration of the array.  As if it has been inlined.
> With n=66536, the dump file is 4436 bytes long and has code to initialize the
> array with a loop.  That looping code appears broken.

The looping code, of itself, is not broken.  If one of the 'i's, say in the
implied do-loop, is changed to 'j', the code runs to completion.  The problem
is that the implied do-loop counter uses a variable declaration and so a
symbol.  This clashes with the variable i.

Since do-loops can run with +ve or -ve steps, the end condition is enforced
through:

L.1:;
D.931 = i == 1;
i = i + 1;
if (D.931) goto L.2; else (void) 0;

ie. with an equality.  The implied do-loop sets this larger than 1 so the loop
never stops.

For n < 65536, the loop is simplified out of existence and the large static
array makes its appearance.  This seems to be an undesirable consequence of
treating array initializers and array constructors with the same limit.

I would:

(i) Change the size limit for simplification of array constructors; and
(ii) Store the current value of the loop counter in a temporary and restore it
after the array constructor has done its thing (patch follows).

Paul


-- 


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



[Bug fortran/28908] [4.1/4.2 Regression]: fold_convert fails for Fortran operator

2006-09-01 Thread paul dot richard dot thomas at cea dot fr


--- Comment #22 from paul dot richard dot thomas at cea dot fr  2006-09-01 
08:11 ---
Created an attachment (id=12166)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12166&action=view)
A partial reversion to the previous method of type association.

This regests OK on trunk and fixes the problems(regressions!) below. 
Sufficient of the original patch remains that the PRs that it was intended to
fix remain fixed.

My apologies to one and all for this struggle but the result has been an
improved gfortran.

HJ, you will see that in submitting to the list , I have required your green
light before committing.  If you have time today, I would be very grateful if
you would test the patch, relative to trunk.

Best regards

Paul

2006-09-01 Paul Thomas <[EMAIL PROTECTED]>

PR fortran/28908
REGRESSION FIX
* gfortran.h : Restore the gfc_dt_list structure and reference
to it in gfc_namespace.
* resolve.c (resolve_fl_derived): Restore the building of the
list of derived types for the current namespace.
* symbol.c (gfc_free_dt_list): Restore.
(gfc_free_namespace): Restore call to previous.
* trans-types.c (copy_dt_decls_ifequal): Restore.
(gfc_get_derived_type): Restore all the paraphenalia for
association of derived types, including calls to previous.

2006-09-01 Paul Thomas <[EMAIL PROTECTED]>

PR fortran/28908
* gfortran.dg/used_types_7.f90: New test.
* gfortran.dg/used_types_8.f90: New test.


-- 


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



[Bug fortran/28890] ICE on write

2006-08-30 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-08-30 
13:11 ---
(In reply to comment #2)

The standard is unambiguous: A string element must be written as charr(i:i).

character(*) :: charr
.
print *, charr(i)

will always be interpreted as a call to an assumed character length function
charr, which is allowed if charr is a dummy function.

As to its being easy... *sigh* we'll see!

Paul 


-- 


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



[Bug fortran/28885] ICE passing components of array of derived type

2006-08-29 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-08-29 
13:12 ---
(In reply to comment #2)
> Created an attachment (id=12148)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12148&action=view) [edit]
> Provisional fix for the problem
> This is regtesting as I write but I have little doubt that this is incorrect.
> Paul

duuuhh! I have been staring too long at PRs:

I have little doubt that it is correct!

Paul


-- 


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



[Bug fortran/28885] ICE passing components of array of derived type

2006-08-29 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-08-29 
13:09 ---
Created an attachment (id=12148)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12148&action=view)
Provisional fix for the problem

This is regtesting as I write but I have little doubt that this is incorrect.

Paul


-- 


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



[Bug fortran/28885] ICE passing components of array of derived type

2006-08-29 Thread paul dot richard dot thomas at cea dot fr


--- Comment #1 from paul dot richard dot thomas at cea dot fr  2006-08-29 
13:05 ---
(In reply to comment #0)
Drew,

You are really uncovering them! A simplified version of your testcase that
produces the same fault is:

program test
  type t
integer :: i
integer :: j
  end type
  type (t) :: a(5) 
  call sub('one',a%j)
  call sub('two',a%i)
contains
  subroutine sub(key,a)
integer, intent(out):: a(:) 
character(*),intent(in) :: key
a = 1   
  end subroutine
end program 

This produces the code below.  You will see that the first call uses a
temporary for the integer array, atmp.5, and this in its turn points, via its
data field to a temporary A.6 which has disappeared off the face of the
earth!  The second call points to A.10, which is properly declared in MAIN.

Now, if you get rid of the INTENT(OUT), the declarations to the temporaries are
both present and the compilation proceeds correctly.  In fact, this could be a
temporary workaround for your existing code.  Note that is is only components
of arrays of derived types that will cause this problem (the fault is around
line 1703 of trans-expr.c).

I have a patch regtesting right now. I will post it on this PR in just a
moment.  If you are in a position to try it out, I would be very grateful.

Paul


MAIN__ ()
{
  struct t a[5];
  int4 A.10[5];
  struct array1_int4 atmp.9;

  _gfortran_set_std (70, 127, 0);
  {
int4 S.11;

{
  int4 D.935;

  atmp.5.dtype = 265;
  atmp.5.dim[0].stride = 1;
  atmp.5.dim[0].lbound = 0;
  atmp.5.dim[0].ubound = 4;
  atmp.5.data = (void *) &A.6;
  atmp.5.offset = 0;
  sub ("one", &atmp.5, 3);
  {
int4 S.8;

D.935 = -1;
S.8 = 1;
while (1)
  {
if (S.8 > 5) goto L.2; else (void) 0;
a[NON_LVALUE_EXPR  + -1].j = (*(int4[0:] *) atmp.5.data)[S.8 +
D.935];
S.8 = S.8 + 1;
  }
L.2:;
  }
}
{
  int4 D.941;

  atmp.9.dtype = 265;
  atmp.9.dim[0].stride = 1;
  atmp.9.dim[0].lbound = 0;
  atmp.9.dim[0].ubound = 4;
  atmp.9.data = (void *) &A.10;
  atmp.9.offset = 0;
  sub ("two", &atmp.9, 3);
  {
int4 S.12;

D.941 = -1;
S.12 = 1;
while (1)
  {
if (S.12 > 5) goto L.3; else (void) 0;
a[NON_LVALUE_EXPR  + -1].i = (*(int4[0:] *) atmp.9.data)[S.12
+ D.941];
S.12 = S.12 + 1;
  }
L.3:;
  }
}
  }
}


-- 


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



[Bug fortran/28873] Cannot resolve subroutine calls when modules are used in different scopes

2006-08-29 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-08-29 
10:22 ---
I have just posted the fix to the fortran list.

Thanks for the report.

Paul


-- 


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



[Bug fortran/20067] gfortran: misleading error message resolving generic subroutine

2006-08-29 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-08-29 
07:55 ---
Harald,

In fixing PR28873, I have fixed this PR.  Will

CALL ice(23.0)   ! { dg-error "no specific subroutine" }
   1
Error: There is no specific subroutine for the generic 'ice' at (1)

for gfortran.dg/generic_5.f90 do it for you?

Paul


-- 


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



[Bug fortran/28788] [gfortran: 4.1, 4.2 regression] ICE on valid code

2006-08-28 Thread paul dot richard dot thomas at cea dot fr


--- Comment #15 from paul dot richard dot thomas at cea dot fr  2006-08-28 
11:56 ---
Created an attachment (id=12146)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12146&action=view)
Fix and two test cases for the latest regressions

I post this now, as a prelude to submitting the patch in the next 24 hours. 
Before doing so, I want to check that all the derived type symbols get cleaned
up and to try a last ditch attemt to identify the references that cause these
regressions.

The patch regtests on Cygwin_NT/PIV and Martin Reinecke confirms that it
compiles his "real-life" code correctly.

Paul


-- 


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



[Bug fortran/28788] [gfortran: 4.1, 4.2 regression] ICE on valid code

2006-08-23 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-08-23 
13:20 ---
Created an attachment (id=12117)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12117&action=view)
Fix for this and Martin Tee's submission to the list

Martin,

I would be very grateful if you would test this patch to see if it fixes your
problem "in the flesh".  It is just now regression testing and I will run the
tonto and Polyhedron testsuites before submitting it.

Thanks for coming back with the problem so quickly.  Whilst I was willing to be
surprised, I did expect some fall-out from the derived type reform.

Sorry for any inconvenience.

Paul


-- 


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



[Bug fortran/28660] Spurious warning: 'ubound.6' is used uninitialized in this function

2006-08-11 Thread paul dot richard dot thomas at cea dot fr


--- Comment #6 from paul dot richard dot thomas at cea dot fr  2006-08-11 
14:08 ---
Created an attachment (id=12066)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12066&action=view)
Prototype fix

The attached runs the testcase below correctly and regtests, except for 
gfortran.fortran-torture/execute/entry_5.f90, on Cygwin_NT/PIV.

I have not had enough time to really check with it is necessary and sufficient,
to fix this one regression nor have I had time to track down the cause of an
irritating but apparently harmless wrinkle - the declaration char z[1:.z]
appears twice; the first time with an incorrect .z and the second with the
correct value for .z.  Fortunately, it is the second declaration that is seen
in the scope of the executable code.

As of tomorrow, I am back on the road again until the end of next week.  If you
want to run with this, please do.  Otherwise, I will complete the job upon my
return.

All the best

Paul

PS I have made some progress on allocatable component derived type
constructors.

PPS This works with the patch:

program runoptf90
implicit none
real :: x(10)
call simulated_annealing1 (x)
call simulated_annealing2 (x)
call simulated_annealing3 (x)
contains
subroutine simulated_annealing1 (xmin)
real, intent(inout) :: xmin(:)
real :: x(size(xmin)+1)
real :: r(size(x)-2)
xmin = r
print *, "#1 ", size(r), size(x)
end subroutine simulated_annealing1
subroutine simulated_annealing2 (xmin)
real, intent(inout) :: xmin(:)
real :: x(size(xmin)+3)
real :: zr(size(x)-6)
xmin = zr
print *, "#2 ", size(zr), size(x)
end subroutine simulated_annealing2
subroutine simulated_annealing3 (xmin)
real, intent(inout) :: xmin(:)
character(size(x)+2) :: y ! host associated x
character(len(y)+3) :: z
real :: r(len(z)-10)
xmin = r
print *, "#3 ", size(r), len(z)
end subroutine simulated_annealing3
end program runoptf90


-- 


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



[Bug fortran/28660] Spurious warning: 'ubound.6' is used uninitialized in this function

2006-08-11 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-08-11 
08:06 ---
Try this one!  No matter what you rename 'r' as, the order of execution is
wrong.

program runoptf90

implicit none
real :: x(10)

call simulated_annealing (x)

contains

subroutine simulated_annealing (zzxmin)
real, intent(inout) :: zzxmin(:)
character(LEN = 5+size(zzxmin)) :: x
real :: r(len(x)-2)

zzxmin = r
print *, "here", len(x), size(r)
end subroutine simulated_annealing

end program runoptf90


-- 


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



[Bug fortran/26106] [meta-bug] Gfortran can't compile tonto correctly

2006-08-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #24 from paul dot richard dot thomas at cea dot fr  2006-08-10 
12:11 ---
(In reply to comment #23)
> Tonto failed to build again.

HJ

Can we close this again?  Steve's patch fixed the problem, as far as I know.

Regards

Paul Thomas


-- 


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



[Bug fortran/28496] Error during array initialization

2006-08-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-08-10 
07:52 ---
Created an attachment (id=12054)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12054&action=view)
Patch to fix the PR and a testcase

This seems to do the trick.  I will regtest and submit to the list this
evening.

Paul


-- 


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



[Bug fortran/28600] [4.2 regression] ICE on character pointer assignment

2006-08-08 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-08-08 
14:15 ---
(In reply to comment #2)
> I wonder if this was caused by Jakub's patches for openmp.

Or Richard Sandiford's patches. The above produces:
gee ()
{
  int4 .s;

  __builtin_memmove (&(*(char[0:][1:3] *) m.data)[NON_LVALUE_EXPR
 + m.offset], s, 3);
}


bar (s, n, _s)
{
  struct array1_unknown m;
  bit_size_type D.914;
   D.915;
  static void gee (void);

  .s = *n;
  D.914 = (bit_size_type) () .s * 8;
  D.915 = () .s;
  m.data = 0B;
}
so that .s is declared in gee but used in bar.

This:

subroutine bar(s, n)
 integer n
 character s*(*)
 character*3, dimension(:), pointer :: m
contains
 subroutine gee
m(1) = s(1:3)
 end subroutine gee
end subroutine bar

compiles correctly and outputs this code:

gee ()
{
  __builtin_memmove (&(*(char[0:][1:3] *) m.data)[NON_LVALUE_EXPR
 + m.offset], s, 3);


bar (s, n, _s)
{
  struct array1_unknown m;
  bit_size_type D.913;
   D.914;
  static void gee (void);

  D.913 = (bit_size_type) () _s * 8;
  D.914 = () _s;
  m.data = 0B;
}

where _s is used directly.

The declaration for .s needs to be boosted to the correct context.

Paul


-- 


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



[Bug fortran/28630] New: ICE due to a module function returning a derived type

2006-08-07 Thread paul dot richard dot thomas at cea dot fr
This was reported by Mark Hesselink
http://gcc.gnu.org/ml/fortran/2006-08/msg00124.html

This:

MODULE types
   TYPE :: t
  INTEGER :: i
   END TYPE
END MODULE types

MODULE foo
   USE types
CONTAINS
   FUNCTION bar (x) RESULT(r)
  USE types
  REAL, INTENT(IN) :: x
  TYPE(t) :: r
  r = t(0)
   END FUNCTION bar
END MODULE

LOGICAL FUNCTION foobar (x)
   USE foo
   REAL :: x
   TYPE(t) :: c
   foobar = .FALSE.
   c = bar (x)
END FUNCTION foobar

produces:

$ /irun/bin/gfortran mark.f90
mark.f90: In function 'foobar':
mark.f90:22: internal compiler error: in fold_convert, at fold-const.c:2098
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html> for instructions.

This is essentially the same as PR25391 except that it is a function that is
picking up the wrong derived type definition (look at foo.mod).

I already have a very kludgy fix working.

Paul


-- 
   Summary: ICE due to a module function returning a derived type
   Product: gcc
   Version: 4.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
    ReportedBy: paul dot richard dot thomas at cea dot fr


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



[Bug fortran/28548] [4.2 Regression]: Optional argument failed

2006-08-04 Thread paul dot richard dot thomas at cea dot fr


--- Comment #12 from paul dot richard dot thomas at cea dot fr  2006-08-04 
09:53 ---
Created an attachment (id=12016)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12016&action=view)
A modified fix to take account of comments

I have taken Steve's patch and changed the error to a warning.  This requires
that the text of the warning be modified.  Also elemental_optional_args_1.f90
needs the dg-error's to be changed to dg-warning's.

With this modification, Steve's patch is OK for committing.

Paul


-- 


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



[Bug fortran/28590] A SEQUENCEd defined type which refers to another defined type generates a spurious complaint about the lack of SEQUENCE attribute in the latter

2006-08-04 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-08-04 
09:44 ---
Created an attachment (id=12015)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=12015&action=view)
Fix and testcase for this PR

The check that sequence type components are themselves sequence types was being
done in parse.c.  This is too early for pointer components, since there is no
requirement that they be already defined.  This is cured by moving the test to
resolve.c.  The testcase is Chris's submission with a bit of DejaGnuery and a
comment.

Paul


-- 


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



[Bug fortran/28548] [4.2 Regression]: Optional argument failed

2006-08-04 Thread paul dot richard dot thomas at cea dot fr


--- Comment #11 from paul dot richard dot thomas at cea dot fr  2006-08-04 
08:14 ---
Steve and Martin,

> > Hmm, but my point was that even if gfortran thinks that the __convert_*
> > routines are elemental (as was mentioned in an earlier comment), it should
> > still compile the code without problems, because it is proven that the
> > optional argument actually exists when the __convert_* call is made.

I think that you are right - I screwed up by nor reading the first sentence
carefully enough.

> It's more complicated than just optional and elemental.
> The patch, AFAICT, is correct.

Yes, I think that it is in that it excludes procedures marked as elemental that
are not, in fact, elemental.

I have taken a brief look at making a runtime version of this error and have
recoiled in horror; the combination of simplification and separate translation
of intrinsic procedures leads me to believe that the best course of action
would be to accept Steve's patch and change the error to a warning.

Paul


-- 


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



[Bug fortran/28443] gfortran does not implement the present intrinsic procedure correctly for optional character strings

2006-08-04 Thread paul dot richard dot thomas at cea dot fr


--- Comment #7 from paul dot richard dot thomas at cea dot fr  2006-08-04 
07:50 ---
Just to reinforce the above, I should remark that an explicit interface in the
main program makes the code behave correctly (see below).

The standard requires that references to a procedure with an implicit interface
have the same number of actual arguments with the same type characteristics.

As Andrew says, gfortran does not check implicitly defined procedure arguments;
either for consistency of references within one scope or for a formal interface
generated by the procedure happening to be in the same file.

Paul

program test_string_present
interface
  subroutine test_present(a, b)
integer :: a
character*(*), optional :: b
  end subroutine test_present
end interface

call test_present(1, "foo")
call test_present(2)

end program

subroutine test_present(a, b)
integer :: a
character*(*), optional :: b

if (present(b)) then
write (0,*) "b is present."
else
write (0,*) "b is not present."
end if

end subroutine test_present


-- 


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



[Bug fortran/28416] ICE on allocatable codes

2006-07-18 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-07-18 
14:38 ---
The fix, as described on the list, is to be found in the latest patch to
PR20541 - the TR15581 story.  It includes the corrections to the
going-out-of-scope cleanup, as well.

I am sorry that I cannot deal with it; I hope that Erik is in a position to do
so.

Paul


-- 


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



[Bug fortran/20541] TR 15581: ALLOCATABLE components

2006-07-18 Thread paul dot richard dot thomas at cea dot fr


--- Comment #12 from paul dot richard dot thomas at cea dot fr  2006-07-18 
14:35 ---
Created an attachment (id=11910)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11910&action=view)
The latest version of the patch

This patch is the last version that I will post until after I return from
vacation.  As well as allocatable components, it fixes the two issues raised by
Salvatore Filippone on the gfortran list.  It also includes a test version of
move_alloc that runs the following correctly:

  integer, allocatable :: x(:), y(:), temp(:)
  character(4), allocatable :: a(:), b(:)
  allocate (x(2))
  allocate (a(2))

  x = (/42, 77/)

  print *, allocated(x), allocated(y)
  if (allocated (x)) print *, x
  call move_alloc (x, y)
  print *, allocated(x), allocated(y)
  if (allocated (y)) print *, y


  a = (/"abcd", "efgh"/)
  print *, allocated(a), allocated(b)
  if (allocated (a)) print *, a
  call move_alloc (a, b)
  print *, allocated(a), allocated(b)
  if (allocated (b)) print *, b

! Now one of the intended applications of move_alloc; resizing

  call move_alloc (to = temp, from = y)
  allocate (y(6))
  y(1:2) = temp
  y(3:) = 99
  print *, y
end


Paul 


-- 


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



[Bug fortran/20541] TR 15581: ALLOCATABLE components

2006-07-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #10 from paul dot richard dot thomas at cea dot fr  2006-07-12 
14:23 ---
Bother! Forget the last test - it is an old, incorrect version.  I will post
the right one tonight.

Paul


-- 


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



[Bug fortran/20541] TR 15581: ALLOCATABLE components

2006-07-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #9 from paul dot richard dot thomas at cea dot fr  2006-07-12 
14:20 ---
Created an attachment (id=11867)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11867&action=view)
For discussion, perusal and testing: a beta-release of the TR15581 patch

This patch represents some months of work by Erik and myself.  It is still not
complete and has at least one residual source of memory leakage (derived type
constructors with function array-valued actuals). That withstanding, it does
most of the memory management required by the standard, it does assignments
correctly and handless allocatable components in contructors.  There is still a
way to go before it is submittable but it's getting there!

What does it do?

(i) It runs most of the iso_varying_string testsuite (vst16.f95 fails in io,
vst28.f95, vst30.f95 and vst31.f95 need modification to catch zero length
strings).

(ii) This tests the basic functionality:

! { dg-do run}
! { dg-options "-O2 -fdump-tree-original" }
!
! Check some basic functionality of allocatable components, including that they
! are nullified when created and automatically deallocated when
! 1. A variable goes out of scope
! 2. INTENT(OUT) dummies
! 3. Function results
!
module alloc_m

implicit none

type :: alloc1
real, allocatable :: x(:)
end type alloc1

end module alloc_m


program alloc

use alloc_m

implicit none

type :: alloc2
type(alloc1), allocatable :: a1(:)
integer, allocatable :: a2(:)
end type alloc2

type(alloc2) :: b
integer :: i
type(alloc2), allocatable :: c(:)

if (allocated(b%a2) .OR. allocated(b%a1)) then
write (0, *) 'main - 1'
call abort()
end if

! 3 calls to _gfortran_deallocate (INTENT(OUT) dummy)
call allocate_alloc2(b)
call check_alloc2(b)

do i = 1, size(b%a1)
! 1 call to _gfortran_deallocate
deallocate(b%a1(i)%x)
end do

! 3 calls to _gfortran_deallocate (INTENT(OUT) dummy)
call allocate_alloc2(b)

call check_alloc2(return_alloc2())
! 3 calls to _gfortran_deallocate (function result)

allocate(c(1))
! 3 calls to _gfortran_deallocate (INTENT(OUT) dummy)
call allocate_alloc2(c(1))
! 4 calls to _gfortran_deallocate
deallocate(c)

! 7 calls to _gfortran_deallocate (b (3) and c(4) goes aout of scope)

contains

subroutine allocate_alloc2(b)
type(alloc2), intent(out) :: b
integer :: i

if (allocated(b%a2) .OR. allocated(b%a1)) then
write (0, *) 'allocate_alloc2 - 1'
call abort()
end if

allocate (b%a2(3))
b%a2 = [ 1, 2, 3 ]

allocate (b%a1(3))

do i = 1, 3
if (allocated(b%a1(i)%x)) then
write (0, *) 'allocate_alloc2 - 2', i
call abort()
end if
allocate (b%a1(i)%x(3))
b%a1(i)%x = i + [ 1.0, 2.0, 3.0 ]
end do

end subroutine allocate_alloc2


type(alloc2) function return_alloc2() result(b)
if (allocated(b%a2) .OR. allocated(b%a1)) then
write (0, *) 'return_alloc2 - 1'
call abort()
end if

allocate (b%a2(3))
b%a2 = [ 1, 2, 3 ]

allocate (b%a1(3))

do i = 1, 3
if (allocated(b%a1(i)%x)) then
write (0, *) 'return_alloc2 - 2', i
call abort()
end if
allocate (b%a1(i)%x(3))
b%a1(i)%x = i + [ 1.0, 2.0, 3.0 ]
end do
end function return_alloc2


subroutine check_alloc2(b)
type(alloc2), intent(in) :: b

if (.NOT.(allocated(b%a2) .AND. allocated(b%a1))) then
write (0, *) 'check_alloc2 - 1'
call abort()
end if
if (any(b%a2 /= [ 1, 2, 3 ])) then
write (0, *) 'check_alloc2 - 2'
call abort()
end if
do i = 1, 3
if (.NOT.allocated(b%a1(i)%x)) then
write (0, *) 'check_alloc2 - 3', i
call abort()
end if
if (any(b%a1(i)%x /= i + [ 1.0, 2.0, 3.0 ])) then
write (0, *) 'check_alloc2 - 4', i
call abort()
end if
end do
end subroutine check_alloc2

end program alloc
! { dg-final { scan-tree-dump-times "deallocate" 24 "original" } }
! { dg-final { cleanup-tree-dump "original" } }


(iii) The following tests constructors:
program
  type :: mytype
integer, allocatable :: a(:, :)
  end type mytype
  type (mytype) :: x
  integer :: y(0:1, -1:0) = reshape ((/42, 99, 55, 77/), (/2,2/))
  x = mytype (y)
  call foo (x, y)
  x = mytype (reshape ((/42, 99, 55, 77/), (/2,2/)))
  call foo (x, reshape ((/42, 99, 55, 77/), (/2,2/)))
  x = mytype (bar (y))
  call foo (x, y**3)
contains
  subroutine foo (x, y)
 

[Bug fortran/28353] ICE: Segmentation fault

2006-07-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-07-12 
11:54 ---
Tobias,

I am so glad to see that somebody is passing components of derived type arrays;
I bust myself to make that work!  Anyway, I partially broke it with a recent
patch - sorry.

Reduced testcase:

SUBROUTINE mpi_bc_all(lda_u, ntypd)
  TYPE t_utype
INTEGER l
  END TYPE t_utype
  TYPE (t_utype), INTENT (INOUT) :: lda_u(ntypd)
  EXTERNAL MPI_BCAST
  CALL MPI_BCAST(lda_u(:)%l) ! No explicit interface -> no fsym -> segfault
END SUBROUTINE mpi_bc_all

A work around is to add an interface:

  interface
subroutine MPI_BCAST (i)
  integer, dimension (:) :: i
end subroutine MPI_BCAST
  end interface

Here is a patch that works.  It is not regtested but I am sure that it is
bombproof.  I will do all the regtesting tonight and commit it as "obvious"
tomorrow morning.

Patch:

Index: gcc/fortran/trans-expr.c
===
--- gcc/fortran/trans-expr.c(r├®vision 115306)
+++ gcc/fortran/trans-expr.c(copie de travail)
@@ -1980,7 +1980,8 @@
   array of derived types.  In this case, the argument
   is converted to a temporary, which is passed and then
   written back after the procedure call.  */
-   gfc_conv_aliased_arg (&parmse, e, f, fsym->attr.intent);
+   gfc_conv_aliased_arg (&parmse, e, f,
+ fsym ? fsym->attr.intent : INTENT_INOUT);
  else
gfc_conv_array_parameter (&parmse, e, argss, f);

Paul 


-- 


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



[Bug fortran/28237] print call()

2006-07-05 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-07-05 
09:47 ---
Created an attachment (id=11825)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11825&action=view)
Fix for PR28237 and the last bit of PR2320.

I have not had time to do a full regtest; just gfortran.dg/print*, which
includes the following testcase (print_fmt_5.f90):

Paul

! { dg-do compile }
! print_fmt_5.f90
! Test of fix for PR28237 and the last bit of PR2320.  See
! below for the description of the problem.
!
program r
  character(12) :: for = '(i5)', left = '(i', right = ')'
  integer :: i, j
  integer :: h(4) &
= (/1h(, 1hi, 1h5, 1h)/)! { dg-warning "HOLLERITH|Hollerith" }
  namelist /mynml/ i
  i = fact ()
!
! All these are "legal" things to do; note however the warnings
! for extensions or obsolete features!
!
  print *, fact()
  print 100, fact()
  print '(i5)', fact()
  print mynml  ! { dg-warning "is an extension" }
  do i = 1, 5
print trim(left)//char(iachar('0') + i)//trim(right), i
  end do
  assign 100 to i  ! { dg-warning "ASSIGN statement" }
  print i, fact()  ! { dg-warning "ASSIGNED variable" }
  print h, fact () ! { dg-warning "Non-character in FORMAT" }
!
! These are not and caused a segfault in trans-io:560
!
! PR28237
  print fact() ! { dg-error "not an ASSIGNED variable" }
! original PR23420
  print precision(1.2_8) ! { dg-error "type default CHARACTER" }
! PR23420 points 4 and 5
  print j + j  ! { dg-error "not an ASSIGNED variable" }
! An extension of the above, encountered in writing the fix
  write (*, fact())! { dg-error "not an ASSIGNED variable" }
 100 format (i5)
contains
  function fact()
integer :: fact
fact = 1
  end function fact
end


-- 


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



[Bug fortran/27998] character arrays: warn if erray constructor values have different lengths

2006-06-30 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-06-30 
12:40 ---
Created an attachment (id=11784)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11784&action=view)
The beginnings of a fix for the PR

Thee attached is simple, only gives warnings but is way too verbose, as the
following demonstrates:

program test
  character(10) :: a(3)
  character(10) :: b(3)= (/ 'Takata ', 'Tanaka', 'Hayashi' /)
  character(4) :: c = "abcde"
  a =  (/ 'Takata', 'Tanaka ', 'Hayashi' /)
  a =  (/ 'Takata ', 'Tanaka ', 'Hayashi' /)
  b = "abc"
  c = "abcdefg"
end program test

More work needed!

Paul


-- 


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



[Bug fortran/28167] ICE: in fold_binary, at fold-const.c:8239 (temporary character array?)

2006-06-27 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-06-27 
14:17 ---
I believe that a frontend problem is involved, even if it is only part of the
story.  This exhibits the same symptoms as Harald's testcase:

  call foo ( (/( 'a',i=1,2 )/) )
end

but this works fine:

  call foo ( (/'a', 'b'/) )
end

Both expand the constructor just fine.  However the second makes just one call
to resolve_expr and leaves with a value for the string length. The first calls
resolve_expr twice and has lost the string length between the first and second
calls.  I am blowed if I can see where this happens for the moment but I am
looking furiously!

Paul 


-- 


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



[Bug fortran/22571] Reject derived types for dummy arguments declared in the subroutine unless they are SEQUENCE

2006-06-23 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-06-23 
07:04 ---
It should be noted that encasing the two subroutines in a module produces the
correct error

 In file pr22571.f90:15

call a(q)
  1
Error: Type/rank mismatch in argument 'p' at (1)

The problem lies in the absence of global actual/formal argument checking;
where there is an explicit interface, all works correctly.

Paul


-- 


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



[Bug fortran/25073] CASEs overlap

2006-06-22 Thread paul dot richard dot thomas at cea dot fr


--- Comment #9 from paul dot richard dot thomas at cea dot fr  2006-06-22 
14:31 ---

> A straightforward fix in resolve.c (resolve_select).

In checking the attachment, I have just seen that the if condition can be
simplified to

  if (cp->low->value.logical & seen_logical)
{
  gfc_error ("constant logical value in CASE statement "
 "is repeated at %L",
 &cp->low->where);
  t = FAILURE;
  break;
}
  seen_logical |= cp->low->value.logical == 0 ? 2 : 1;

Paul


-- 


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



[Bug fortran/25073] CASEs overlap

2006-06-22 Thread paul dot richard dot thomas at cea dot fr


--- Comment #8 from paul dot richard dot thomas at cea dot fr  2006-06-22 
14:25 ---
Created an attachment (id=11728)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11728&action=view)
A patch to fix the PR.

A straightforward fix in resolve.c (resolve_select).

Paul


-- 


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



[Bug fortran/25056] non-PURE function should not be a valid argument

2006-06-22 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-06-22 
14:24 ---
Created an attachment (id=11727)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11727&action=view)
Patch to fix the PR

A straightforward check in interface.c (compare_actual_formal) was all that was
required.

Paul


-- 


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



[Bug fortran/28118] ICE calling subroutine defined via explicit interface

2006-06-21 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-06-21 
10:24 ---
This reduced version produces the same error

  character(12) :: a(2)
  call foo (a(:)(7:11))
end

(gdb) run PR28118.f90
Starting program: /irun/libexec/gcc/i686-pc-cygwin/4.2.0/f951.exe PR28118.f90
 MAIN__
Program received signal SIGSEGV, Segmentation fault.
0x0048a297 in gfc_conv_expr_descriptor (se=0x22eb70, expr=0x101ff150,
ss=0x1020f730) at ../../trunk/gcc/fortran/trans-array.c:4203
4203  loop.temp_ss->string_length = expr->ts.cl->backend_decl;
(gdb) backtrace
#0  0x0048a297 in gfc_conv_expr_descriptor (se=0x22eb70, expr=0x101ff150,
ss=0x1020f730) at ../../trunk/gcc/fortran/trans-array.c:4203
#1  0x0048a682 in gfc_conv_array_parameter (se=0x22eb70, expr=0x101ff150,
ss=0x1020f730, g77=1) at ../../trunk/gcc/fortran/trans-array.c:4485
#2  0x0049924a in gfc_conv_function_call (se=0x22ed20, sym=0x101ff018,
arg=0x101ff0b8) at ../../trunk/gcc/fortran/trans-expr.c:1953
#3  0x004ad94c in gfc_trans_call (code=0x101ff418, dependency_check=0 '\0')
at ../../trunk/gcc/fortran/trans-stmt.c:336
#4  0x00480d05 in gfc_trans_code (code=0x101ff418)
at ../../trunk/gcc/fortran/trans.c:509
#5  0x004954f6 in gfc_generate_function_code (ns=0x101feb40)
at ../../trunk/gcc/fortran/trans-decl.c:2990
#6  0x00451cfd in gfc_parse_file () at ../../trunk/gcc/fortran/parse.c:3206
#7  0x00474530 in gfc_be_parse_file (set_yydebug=0)
at ../../trunk/gcc/fortran/f95-lang.c:303
#8  0x0051eab0 in compile_file () at ../../trunk/gcc/toplev.c:999
#9  0x00520b8b in do_compile () at ../../trunk/gcc/toplev.c:1970
#10 0x00520c15 in toplev_main (argc=2, argv=0x10102068)
at ../../trunk/gcc/toplev.c:2002
#11 0x004b7637 in main (argc=2, argv=0x10102068) at ../../trunk/gcc/main.c:35

I will confirm it tonight.

Paul


-- 


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



[Bug fortran/28119] New: forall_stmt ; stmt gives an internal error

2006-06-21 Thread paul dot richard dot thomas at cea dot fr
In the course of understanding pr25072, I came across this beauty.

$ cat test.f90
   real a(2)
   forall (i = 1:2) a(i) = i ; a = 2.0 * a
end

[EMAIL PROTECTED] /cygdrive/d/svn/prs
$ /snap/bin/gfortran test.f90
 In file test.f90:2

   forall (i = 1:2) a(i) = i ; a = 2.0 * a
  1
 Internal Error at (1):
 free_expr0(): Bad expr type

Paul


-- 
   Summary: forall_stmt ; stmt gives an internal error
   Product: gcc
   Version: 4.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
ReportedBy: paul dot richard dot thomas at cea dot fr


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



[Bug fortran/24518] Intrinsic MOD incorrect for large arg1/arg2 and slow.

2006-06-21 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-06-21 
07:19 ---
Subject: RE:  Intrinsic MOD incorrect for large arg1/arg2 and slow.

FX,

I do not have the slightest idea!  I wrote various versions using
BUILT_IN_FMOD and got bogged down in a discussion about the use of
built-in fast-math versions.  These seem to me to have more useful
arithmetical properties, as well as being faster.  I lost interest
after that.

I am stuck with a build problem that is causing me to scratch my
head.  PRECISION and RANGE do not seem to be known to the build
any more and, in consequence it goes down in flames at
selected_int/real_kind.f90.  This is with a completely clean build.

I cannot see any obvious culprit yet but we will see!

Paul

> -Message d'origine-
> De : fxcoudert at gcc dot gnu dot org 
> [mailto:[EMAIL PROTECTED]
> Envoyé : mardi 20 juin 2006 14:23
> À : THOMAS Paul Richard 169137
> Objet : [Bug fortran/24518] Intrinsic MOD incorrect for large 
> arg1/arg2
> and slow.
> 
> 
> 
> 
> --- Comment #2 from fxcoudert at gcc dot gnu dot org  
> 2006-06-20 12:22 ---
> Why exactly aren't we using BUILT_IN_FMOD{F,,L}?
> 
> $ cat a.f90   
>   real*8 :: x = 10.0e9
>   do i = 10, 22
> x = 10d0 * x
> print '(a,i2,a,g14.8," = ",g14.8)', "mod (10**",i,", 1.7_8) = ", &
> fmod (x, 1.7_8), mod 
> (x, 1.7_8);
>   end do
> end
> $ cat a.c
> #include 
> double fmod_ (double *x, double *y)
> { return fmod(*x,*y); }
> $ gfortran a.f90 a.c && ./a.out
> mod (10**10, 1.7_8) =  1.326 =  1.326
> mod (10**11, 1.7_8) =  1.1000261 =  1.1000261
> mod (10**12, 1.7_8) = 0.80026120 = 0.80026150
> mod (10**13, 1.7_8) =  1.2026123 =  1.2026138
> mod (10**14, 1.7_8) = 0.12612289 = 0.12609863
> mod (10**15, 1.7_8) =  1.2612289 =  1.2607422
> mod (10**16, 1.7_8) = 0.71228945 =  5.8125000
> mod (10**17, 1.7_8) = 0.32289469 = -50.687500
> mod (10**18, 1.7_8) =  1.5289470 =  364.0
> mod (10**19, 1.7_8) =  1.6894697 = -.7000E+20
> mod (10**20, 1.7_8) =  1.5946971 = -.7000E+21
> mod (10**21, 1.7_8) = 0.64697063 = -.7000E+22
> mod (10**22, 1.7_8) = 0.86970627 = -.7000E+23
> 
> It's actually slower: 55% slower at -O0 and 230% slower at 
> -O2, on a loop with
> real(kind=8) variables modulo. But then, we're already 
> testing whether the
> division can be represented by an integer, we could call fmod 
> only in the case
> where it's not possible. Opinions?
> 
> 
> -- 
> 
> fxcoudert at gcc dot gnu dot org changed:
> 
>What|Removed |Added
> --
> --
>  CC||fxcoudert at 
> gcc dot gnu dot
>||org
>Last reconfirmed|2006-01-24 04:26:11 |2006-06-20 12:22:57
>date||
> 
> 
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=24518
> 
> --- You are receiving this mail because: ---
> You reported the bug, or are watching the reporter.
> 


-- 


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



[Bug fortran/25072] non PURE function used in For-All

2006-06-20 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-06-20 
13:49 ---
This fixes the problem:

Index: gcc/fortran/primary.c
===
--- gcc/fortran/primary.c   (révision 114599)
+++ gcc/fortran/primary.c   (copie de travail)
@@ -1926,6 +1926,18 @@
 return MATCH_ERROR;

   sym = symtree->n.sym;
+
+  /* Hope that this is a function that has not yet been
+ declared; the need for this comes from the occasional
+ return from gfc_get_ha_sym_tree of spurious values
+ for sym->attr.flavor.  */
+  if (sym->new && sym->refs == 1 && !sym->attr.dimension)
+{
+  gfc_gobble_whitespace ();
+  if (gfc_peek_char () == '(')
+   sym->attr.flavor = FL_UNKNOWN;
+}
+
   e = NULL;
   where = gfc_current_locus;

I do not understand why spurious values are returning from gfc_get_ha_sym_tree,
however.  I put diagnostics on the return value and the result; the value just
changes!  The above, however, will not do any harm and certainly allows the
following to run correctly.

Paul

module foo
  integer, parameter :: n = 4
contains
  logical function foot (i)
integer, intent(in) :: i
foot = (i == 2) .or. (i == 3)
  end function foot
end module foo

  use foo
  integer :: i, a(n)
  logical :: s(n)
  s = (/(foot (i), i=1, n)/)

! Check that non-mask case is still OK
  a = 0
  forall (i=1:n) a(i) = i
  if (any (a .ne. (/1,2,3,4/))) call abort ()

! Now a mask using a function with an explicit interface
! via use association.
  a = 0
  forall (i=1:n, foot (i)) a(i) = i
  if (any (a .ne. (/0,2,3,0/))) call abort ()

! Now an array variable mask
  a = 0
  forall (i=1:n, .not. s(i)) a(i) = i
  if (any (a .ne. (/1,0,0,4/))) call abort ()

! This was the PR - an internal function mask
  a = 0
  forall (i=1:n, t (i)) a(i) = i
  if (any (a .ne. (/0,2,0,4/))) call abort ()

! Check that an expression is OK
  a = 0
  forall (i=1:n, t (i) .eqv. .false.) a(i) = i
  if (any (a .ne. (/1,0,3,0/))) call abort ()

! And that an expression that used to work is OK
  a = 0
  forall (i=1:n, s (i) .or. t(i)) a(i) = i
  if (any (a .ne. (/0,2,3,4/))) call abort ()

contains
  logical function t(i)
integer, intent(in) :: i
t = (mod (i, 2) == 0)
  end function t
end


-- 


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



[Bug fortran/20867] statement function args not given implicit type early enough

2006-06-19 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-06-19 
13:00 ---
Created an attachment (id=11702)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11702&action=view)
Patch to fix this PR

Will submit tonight.

Paul


-- 


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



[Bug fortran/20874] elemental function ought to be scalar

2006-06-19 Thread paul dot richard dot thomas at cea dot fr


--- Comment #1 from paul dot richard dot thomas at cea dot fr  2006-06-19 
09:25 ---
Created an attachment (id=11695)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11695&action=view)
Patch to fix PR

I will submit this tonight.

Paul


-- 


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



[Bug fortran/20876] Subroutine call in FORALL block not PURE

2006-06-19 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-06-19 
08:11 ---
Created an attachment (id=11694)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11694&action=view)
Patch to fix PR

The reason for the segfault is that the locus for the assign statement was
never set.

Will commit tonight under the obvious rule.

Paul


-- 


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



[Bug fortran/27998] character arrays: warn if erray constructor values have different lengths

2006-06-14 Thread paul dot richard dot thomas at cea dot fr


--- Comment #1 from paul dot richard dot thomas at cea dot fr  2006-06-15 
06:33 ---
(In reply to comment #0)
According to section 4.5 of the Fortran95 standard:

"If the ac-value expressions are of type character, each ac-value expression in
the array-constructor shall have the same character length parameter."

.so, an error is definitely in order.

Paul


-- 


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



[Bug fortran/28005] gfortran: mathmul produces wrong result

2006-06-14 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-06-14 
10:28 ---
Created an attachment (id=11668)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11668&action=view)
Development fix to the PR

Tobias,

I have fixed the problem for integer_4; I do not have the time to regenerate
the library today but will do so in the next 24 hours, so that the general case
is fixed. I will submit the patch asap afterwards.

The testcase that will be submitted is attached below.

Thanks again

Paul

! { dg-do run }
! Check the fix for PR28005, in which the mechanism for dealing
! with matmul (transpose (a), b) would cause wrong results for
! matmul (a(i, 1:n), b(1:n, 1:n)).
!
! Based on the original testcase contributed by
! Tobias Burnus  <[EMAIL PROTECTED]>
!   
   implicit none
   integer, parameter ::  nmax = 3
   integer::  i, n = 2
   integer, dimension(nmax,nmax) ::  iB=0 , iC=1
   integer, dimension(nmax,nmax) ::  iX1=99, iX2=99, iChk
   iChk = reshape((/30,66,102,36,81,126,42,96,150/),(/3,3/))

! This would give 3, 3, 99
   iB = reshape((/1 ,3 ,0 ,2 ,5 ,0 ,0 ,0 ,0 /),(/3,3/))
   iX1(1:n,1) = matmul( iB(2,1:n),iC(1:n,1:n) )

! This would give 4, 4, 99
   ib(3,1) = 1
   iX2(1:n,1) = matmul( iB(2,1:n),iC(1:n,1:n) )

! Whereas, we should have 8, 8, 99
   if (any (iX1(1:n,1) .ne. (/8, 8, 99/))) call abort ()
   if (any (iX1 .ne. iX2)) call abort ()

! Make sure that the fix does not break transpose temporaries.
   iB = reshape((/(i, i = 1, 9)/),(/3,3/))
   ic = transpose (iB)
   iX1 = transpose (iB)
   iX1 = matmul (iX1, iC)
   iX2 = matmul (transpose (iB), iC)
   if (any (iX1 .ne. iX2)) call abort ()
   if (any (iX1 .ne. iChk)) call abort ()
end


-- 


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



[Bug fortran/16206] rejects valid array initialization expression

2006-06-09 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-06-09 
15:19 ---
Created an attachment (id=11647)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11647&action=view)
An experimental fix for the PR

This was to have been the second of the two approaches, described above.  It
works, in that it fixes the bug but its limitations become obvious, very
quickly; try some arithmetic with an arrya_section, for example.

However, all is not lost!  You will note the heavy use of gmp to do the
arithmetic - that was in preparation for a tactical retreat to approach (i).  I
have done all the tests to understand what happens in expr.c and am confident
that I will have a proper fix in about 1 week.

Paul


-- 


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



[Bug middle-end/27889] [4.1/4.2 Regression] ICE on complex assignment in nested function

2006-06-09 Thread paul dot richard dot thomas at cea dot fr


--- Comment #12 from paul dot richard dot thomas at cea dot fr  2006-06-09 
08:50 ---
(In reply to comment #11)
> (In reply to comment #10)
> >   implicit COMPLEX (a-z)
> Does that actually declare the variables in MAIN or just say after the first
> use, they are declared in that function as complex?
> (this should be noted as a seperate bug if it really should declared the
> variables in the "program" instead of the function).

They are declared in MAIN and the type information should be host associated to
the variables in the function.

According to the gfortran parse tree, this is happening correctly:

$ /irun/bin/gfortran  -fdump-parse-tree pr27889.f90

Namespace: A-H: (REAL 4) I-N: (INTEGER 4) O-Z: (REAL 4)
procedure name = MAIN__
symtree: t  Ambig 0
symbol t (COMPLEX 4)(VARIABLE UNKNOWN-INTENT UNKNOWN-ACCESS
UNKNOWN-PROC
)

symtree: foo  Ambig 0
symbol foo (UNKNOWN 0)(PROCEDURE UNKNOWN-INTENT UNKNOWN-ACCESS
INTERNAL-
PROC SUBROUTINE)

symtree: MAIN__  Ambig 0
symbol MAIN__ (UNKNOWN 0)(PROCEDURE UNKNOWN-INTENT PUBLIC UNKNOWN-PROC
S
UBROUTINE)

symtree: s  Ambig 0
symbol s (COMPLEX 4)(VARIABLE UNKNOWN-INTENT UNKNOWN-ACCESS
UNKNOWN-PROC
)


  CALL foo ()

CONTAINS

  Namespace: A-H: (REAL 4) I-N: (INTEGER 4) O-Z: (REAL 4)
  procedure name = foo
  symtree: foo  Ambig 0 from namespace MAIN__

  ASSIGN MAIN__:t (+ MAIN__:s MAIN__:s)


pr27889.f90: In function 'foo':
pr27889.f90:2: error: invalid operand to binary operator
D.907

pr27889.f90:2: internal compiler error: verify_stmts failed
Please submit a full bug report,
with preprocessed source if appropriate.
See http://gcc.gnu.org/bugs.html> for instructions.


This is rather like that parameter bug, isn't it, Andrew? ie. type information
is not getting correctly broadcast to enclosed procedure blocks.

Paul


-- 


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



[Bug fortran/22210] gfc_conv_array_initializer weirdness

2006-06-07 Thread paul dot richard dot thomas at cea dot fr


--- Comment #7 from paul dot richard dot thomas at cea dot fr  2006-06-08 
06:54 ---
Where did this one go to? Can we close it?

Paul


-- 


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



[Bug fortran/23091] ICE in gfc_trans_auto_array_allocation

2006-06-06 Thread paul dot richard dot thomas at cea dot fr


--- Comment #9 from paul dot richard dot thomas at cea dot fr  2006-06-06 
14:06 ---
Created an attachment (id=11608)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11608&action=view)
Patch for this and PR27583

This needs cleaning up and a testcase writing but it is nearly there.

Paul 


-- 


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



[Bug fortran/16206] rejects valid array initialization expression

2006-06-06 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-06-06 
11:46 ---
(In reply to comment #3)
> This bug report is approaching its second anniversary.
> Does anybody still watch it or take care?

Yes, Harald.  I have been looking these last days at a number of array
initializer problems.

I have not entirely decided how to do this one yet:
(i) Blasting through and expanding the array setion is one way; or
(ii) Doing as Erik Edelmann suggested in another PR; use a normal assignment
for the initialization and a static flag to make sure that it only is done
once.

The first is consistent with the existing structure and the second can be used
to simplify a lot but will be much more work.  This is why I am looking at
initializer PRs as a package.

Paul


-- 


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



[Bug fortran/24168] Problems with SPREAD and/or scalarization

2006-06-06 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-06-06 
10:26 ---
Created an attachment (id=11607)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11607&action=view)
Patch and testcase for the PR

The problem lay in simplification of the binary expression because the rank of
the operands was not transferred.

I will submit tonight.

Paul


-- 


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



[Bug middle-end/27889] [4.1/4.2 Regression] ICE on complex assignment in nested function

2006-06-05 Thread paul dot richard dot thomas at cea dot fr


--- Comment #10 from paul dot richard dot thomas at cea dot fr  2006-06-06 
06:47 ---
Noting the non-fortran tilt on this, it is interesting that

  implicit COMPLEX (a-z)
  CALL foo
CONTAINS
  SUBROUTINE foo
t = s + s
  END SUBROUTINE foo
END

is OK and produces declarations for s and t in foo.  Alternatively, declaring s
and t in foo also works.

However,

  COMPLEX s, t
  CALL foo
CONTAINS
  SUBROUTINE foo
t = s + s
  END SUBROUTINE foo
END

puts the declarations in MAIN__, thusly:

foo ()
{
  t = s + s;


MAIN__ ()
{
  complex4 s;
  complex4 t;
  static void foo (void);

  _gfortran_set_std (70, 127, 0);
  foo ();
}

and triggers the ICE for any optimization level.  In fortran parlance, it is
host or use association of the complex type that is broken.

Paul


-- 


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



[Bug middle-end/27889] [4.1/4.2 Regression] ICE on complex assignment in nested function

2006-06-05 Thread paul dot richard dot thomas at cea dot fr


--- Comment #9 from paul dot richard dot thomas at cea dot fr  2006-06-06 
06:18 ---
Subject: RE:  [4.1/4.2 Regression] ICE on complex assignment in nested function

Andrew,

Thanks, I just went at the mail in the wrong order.  I discovered that it is
not fortran by peaking at the PR.  

Who knows, maybe I can fix a C bug too?

Paul


-- 


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



[Bug middle-end/27889] [4.1/4.2 Regression] ICE on complex assignment in nested function

2006-06-05 Thread paul dot richard dot thomas at cea dot fr


--- Comment #7 from paul dot richard dot thomas at cea dot fr  2006-06-06 
06:13 ---
Subject: RE:  ICE on complex assignment

FX,


> Paul, I'm adding you to the CC list since this looks fully 
> module-related.
>

Oh Gee, thanks - that's all I need!..

I'll take a look at it this morning.

Paul


-- 


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



[Bug fortran/13615] g77 -Wuninitialized doesn't produce warning on characters

2006-06-01 Thread paul dot richard dot thomas at cea dot fr


--- Comment #7 from paul dot richard dot thomas at cea dot fr  2006-06-01 
08:17 ---
This is still the case; Is this a gfortran issue or a gcc one?

If I give the characters length, using any format, even the anonymous warning
goes away.  In fact, any array expression that I have tried is the same; eg.

  real d(8), c(8) 
  d = c 

is ignored.

Paul


-- 


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



[Bug fortran/5900] [g77 & gfortran] Lapack regressions since g77 2.95.2

2006-06-01 Thread paul dot richard dot thomas at cea dot fr


--- Comment #56 from paul dot richard dot thomas at cea dot fr  2006-06-01 
07:31 ---
Jerry,

Where are we with this one?  Did you have time yet to automatize the testing?

It would be real nice to close it!

Paul


-- 


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



[Bug fortran/25090] Bad automatic character length

2006-05-18 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-05-18 
15:43 ---
Created an attachment (id=11486)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11486&action=view)
A patch to the patch

This fixes the problem with the patch, applied to trunk, that was reported by
Grigory Zagorodnev at http://gcc.gnu.org/ml/fortran/2006-05/msg00233.html

It needs tidying up before submission but seems to do what is needed.  It also
cures pr25058.

Thanks, Grigory.

Paul


-- 


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



[Bug fortran/27613] compile fails with "Unclassifiable statement" error message

2006-05-18 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-05-18 
15:31 ---
(In reply to comment #4)
> Paul, I've looked at the patch and it looks ok.  You don't seem to have posted
> it, at least it's not in the patch tracker.  Did you find any problems
> associated with it?

I think that it is OK.  I prepared the submission, whereupon Grigory came up
with the problem with the fix for PR25090.  I dropped everything to fix the
fix!

I have also been bogged down with the problem with TRANSFER on 64bit machines.
It is not too easy to fix when you do not have a 64bit machine!

I will submit the patch in the next 24hours - promise!

Many thanks

Paul 


-- 


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



[Bug fortran/27613] compile fails with "Unclassifiable statement" error message

2006-05-15 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-05-15 
13:59 ---
Created an attachment (id=11471)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11471&action=view)
Patch for the problem

The attachment is a patch for the problem. The testcase is below.
Regtesting right now on Cygwin_NT/PIV
It will be submitted if all is well.

Paul

! { dg-do compile }
! Tests the patch for PR27613, in which directly recursive, scalar
! functions were generating an "unclassifiable statement" error
! for the recursive statement(s).
!
! Based on PR testcase by Nicolas Bock  <[EMAIL PROTECTED]>
!
program test
  if (original_stuff(1) .ne. 5) call abort ()
  if (scalar_stuff(-4) .ne. 10) call abort ()
  if (any (array_stuff((/-19,-30/)) .ne. (/25,25/))) call abort ()
contains
  recursive function original_stuff(n)
integer :: original_stuff
integer :: n
original_stuff = 1
if(n < 5) then
  original_stuff = original_stuff + original_stuff (n+1)
endif
  end function original_stuff

  recursive function scalar_stuff(n) result (tmp)
integer :: tmp
integer :: n
tmp = 1
if(n < 5) then
  tmp = tmp + scalar_stuff (n+1)
endif
  end function scalar_stuff

  recursive function array_stuff(n) result (tmp)
integer :: tmp (2)
integer :: n (2)
tmp = 1
if(maxval (n) < 5) then
  tmp = tmp + array_stuff (n+1)
endif
  end function array_stuff

  recursive function bad_stuff(n)
integer :: bad_stuff (2)
integer :: n(2)
bad_stuff = 1
if(maxval (n) < 5) then
  bad_stuff = bad_stuff + bad_stuff (n+1) ! { dg-error "RESULT must be
specified" }
endif
  end function bad_stuff
end program test


-- 


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



[Bug fortran/27613] compile fails with "Unclassifiable statement" error message

2006-05-14 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-05-15 
06:42 ---
A temporary workaround is:

program test
  integer :: stuff

  write(*, *) "called stuff ", stuff(1), " times"

end program test

recursive function stuff(n) result (tmp)
  integer :: tmp
  integer :: n

  tmp = 1
  if(n < 5) then
tmp = tmp+stuff(n+1)
  endif

end function stuff


-- 


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



[Bug fortran/27155] Transfer of character to integer array and vice versa still doesn't work

2006-05-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-05-12 
14:50 ---
Created an attachment (id=11445)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11445&action=view)
Patch for bug (not regtested)

The problem turned out to be less severe than I imagined.  The attached patch
runs your program and the existing testcases correctly.  I do not ever seem to
have tested the case of a character scalar with anything other than len=4. The
code is such that it only produces a value of 4 for any length of string -
blush, blush!

I will endeavour to go through this with a fine toothcomb and, maybe, to fix
PR27449 before submitting.

Once again, "takk"

Paul 


-- 


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



[Bug fortran/19015] shape / rank mismatch in maxloc / minloc could be caught at compile time

2006-05-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-05-12 
13:45 ---
Created an attachment (id=11444)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11444&action=view)
Corrected version of patch

This version of the patch survives regtesting!


-- 

paul dot richard dot thomas at cea dot fr changed:

   What|Removed |Added

  Attachment #11442|0   |1
is obsolete||


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



[Bug fortran/19015] shape / rank mismatch in maxloc / minloc could be caught at compile time

2006-05-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-05-12 
11:42 ---
Created an attachment (id=11442)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11442&action=view)
Patch to effect compile time checking

Thomas,

The attached patch corrects the problem and is presently regtesting.  Of
course, it can only deal with constant values of dim so the runtime checking
should remain in place.

Gruesse

Paul


-- 


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



[Bug fortran/24168] Problems with SPREAD and/or scalarization

2006-05-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #1 from paul dot richard dot thomas at cea dot fr  2006-05-12 
09:23 ---
I find this to be "surprising":

$ cat pr24168.f90;rm a.exe;/irun/bin/gfortran -fdump-tree-original pr24168.f90;
./a
program bug
 implicit none
 integer, parameter :: nx=2,ny=2
 real, dimension(nx,ny) :: f
 real, dimension(nx) :: x
 integer, dimension(nx) :: p
 integer :: i
 x = real ((/ (i, i = 1, nx) /))
 print '(A,2F4.1)', "x = ", x
 print '(A,2F4.1)', "cshift( x, nx/2) * 2 = ",cshift( x, nx/2) * 2
 print '(A,4F4.1)', "spread(cshift( x, nx/2) * 2, 2, ny) = ", spread(cshift( x,
nx/2) * 2, 2, ny)
end program bug

x =  1.0 2.0
cshift( x, nx/2) * 2 =  4.0 2.0
spread(cshift( x, nx/2) * 2, 2, ny) =  4.0 4.0 4.0 4.0

Paul


-- 


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



[Bug fortran/18315] missing error for incompatible array assignment involving lbound

2006-05-11 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-05-11 
15:54 ---

> I think what is happening is that lbound's type is becoming a scalar and not 
> > an array with size of 1.

I believe that I fixed this with either the bounds scalarization patch or some
of the work on conformance or both.  Will close tonight.

Paul

Note the following:

[EMAIL PROTECTED] /cygdrive/d/svn/prs
$ cat pr18315.f90;rm a.exe;/irun/bin/gfortran pr18315.f90;./a
program main
  implicit none
  real :: a(0:9)
  integer :: bn(10)
  bn(1:1) = lbound(a)
  print *, bn(1)
end program main
   0

[EMAIL PROTECTED] /cygdrive/d/svn/prs
$ cat pr18315.f90;rm a.exe;/irun/bin/gfortran pr18315.f90;./a
program main
  implicit none
  real :: a(0:9)
  integer :: bn(10)
  bn = lbound(a)
  print *, bn(1)
end program main
 In file pr18315.f90:5

  bn = lbound(a)
   1
Error: different shape for Array assignment at (1) on dimension 1 (10/1)
bash: ./a: No such file or directory

[EMAIL PROTECTED] /cygdrive/d/svn/prs
$ cat pr18315.f90;rm a.exe;/irun/bin/gfortran pr18315.f90;./a
program main
  implicit none
  real :: a(0:9)
  integer :: bn(10)
  bn(1) = lbound(a)
  print *, bn(1)
end program main
rm: cannot remove `a.exe': No such file or directory
 In file pr18315.f90:5

  bn(1) = lbound(a)
   1
Error: Incompatible ranks 0 and 1 in assignment at (1)
bash: ./a: No such file or directory


-- 

paul dot richard dot thomas at cea dot fr changed:

   What|Removed |Added

 CC|            |paul dot richard dot thomas
   |                |at cea dot fr


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



[Bug fortran/25082] Subroutine with RETURN value, ICE in gfc_conv_scalarized_array_ref

2006-05-11 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-05-11 
14:02 ---
The patch is simple:

12.5.2.6 RETURN statement
R1226 return-stmt is RETURN [ scalar-int-expr ]

The int-expr part is implemented in resolve.c(resolve_code); a further
condition has been imposed to implement scalar-int-expr.

Paul

Index: gcc/fortran/resolve.c
===
--- gcc/fortran/resolve.c   (r├®vision 113694)
+++ gcc/fortran/resolve.c   (copie de travail)
@@ -4345,9 +4345,10 @@
  break;

case EXEC_RETURN:
- if (code->expr != NULL && code->expr->ts.type != BT_INTEGER)
-   gfc_error ("Alternate RETURN statement at %L requires an INTEGER "
-  "return specifier", &code->expr->where);
+ if (code->expr != NULL
+   && (code->expr->ts.type != BT_INTEGER || code->expr->rank))
+   gfc_error ("Alternate RETURN statement at %L requires an SCALAR-"
+  "INTEGER return specifier", &code->expr->where);
  break;

case EXEC_ASSIGN:


-- 


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



[Bug fortran/25090] Bad automatic character length

2006-05-11 Thread paul dot richard dot thomas at cea dot fr


--- Comment #1 from paul dot richard dot thomas at cea dot fr  2006-05-11 
10:22 ---
The following patch fixes this bug.  It makes use of existing calls to
gfc_resolve_expr, whilst resolving specification expressions, to check that
variables used are parameters of each and every entry.  Since existing code is
recycled and the test in gfc_resolve_epr is pretty exclusive, the load on
resolution is negligible.

I will submit asap.

Paul

Index: gcc/fortran/resolve.c
===
--- gcc/fortran/resolve.c   (révision 113111)
+++ gcc/fortran/resolve.c   (copie de travail)
@@ -60,6 +60,9 @@
resets the flag each time that it is read.  */
 static int formal_arg_flag = 0;

+/* True if we are resolving a specification expression.  */
+static int resolving_index_expr = 0;
+
 int
 gfc_is_formal_arg (void)
 {
@@ -2623,6 +2639,50 @@
 }


+/* Emits an error if the expression is a variable that is
+   not a parameter in all entry formal argument lists for
+   the namespace.  */
+
+static void
+entry_parameter (gfc_expr *e)
+{
+  gfc_symbol *sym, *esym;
+  gfc_entry_list *entry;
+  gfc_formal_arglist *f;
+  bool p;
+
+  if (e->expr_type != EXPR_VARIABLE)
+return;
+
+  sym = e->symtree->n.sym;
+  if (sym->ns->entries
+   && !sym->attr.use_assoc
+   && sym->attr.dummy
+   && sym->ns == gfc_current_ns)
+{
+  entry = sym->ns->entries;
+  for (; entry; entry = entry->next)
+   {
+ esym = entry->sym;
+ p = false;
+ f = esym->formal;
+ for (; f && !p; f = f->next)
+   {
+ if (f->sym && f->sym->name
+   && sym->name == f->sym->name)
+   {
+ p = true;
+   }
+   }
+ if (!p)
+   gfc_error ("%s at %L must be a parameter of the entry at %L",
+  sym->name, &e->where, &esym->declared_at);
+   }
+}
+  return;
+}
+
+
 /* Resolve an expression.  That is, make sure that types of operands agree
with their operators, intrinsic operators are converted to function calls
for overloaded types and unresolved function references are resolved.  */
@@ -2647,6 +2707,10 @@

 case EXPR_VARIABLE:
   t = resolve_variable (e);
+
+  if (gfc_current_ns->entries && resolving_index_expr)
+   entry_parameter (e);
+
   if (t == SUCCESS)
expression_rank (e);
   break;
@@ -4597,7 +4661,6 @@
 static try
 resolve_index_expr (gfc_expr * e)
 {
-
   if (gfc_resolve_expr (e) == FAILURE)
 return FAILURE;

@@ -4620,9 +4683,12 @@

   cl->resolved = 1;

+  resolving_index_expr = 1;
+
   if (resolve_index_expr (cl->length) == FAILURE)
 return FAILURE;

+  resolving_index_expr = 0;
   return SUCCESS;
 }

@@ -4709,20 +4775,29 @@
   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
 return FAILURE;

-  /* The shape of a main program or module array needs to be constant.  */
-  if (sym->ns->proc_name
-   && (sym->ns->proc_name->attr.flavor == FL_MODULE
-|| sym->ns->proc_name->attr.is_main_program)
-   && !sym->attr.use_assoc
+  /* Set this flag to check that variables are parameters of all entries.
+ This check is effected by the call to gfc_resolve_expr through
+ is_non_contant_shape_array.  */
+  resolving_index_expr = 1;
+
+  if (!sym->attr.use_assoc
&& !sym->attr.allocatable
&& !sym->attr.pointer
&& is_non_constant_shape_array (sym))
 {
-   gfc_error ("The module or main program array '%s' at %L must "
-"have constant shape", sym->name, &sym->declared_at);
- return FAILURE;
+   /* The shape of a main program or module array needs to be constant. 
*/
+   if (sym->ns->proc_name
+ && (sym->ns->proc_name->attr.flavor == FL_MODULE
+   || sym->ns->proc_name->attr.is_main_program))
+ {
+   gfc_error ("The module or main program array '%s' at %L must "
+  "have constant shape", sym->name, &sym->declared_at);
+   return FAILURE;
+ }
 }

+  resolving_index_expr = 0;
+
   if (sym->ts.type == BT_CHARACTER)
 {
   /* Make sure that character string variables with assumed length are


-- 


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



[Bug fortran/27229] char_transpose_1.f90 fails with ICE in gfc_conv_array_transpose

2006-05-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-05-10 
14:58 ---
(In reply to comment #2)
> Very odd; I do nightly builds of mainline on two different systems.  On one of
> them this failure stopped on 20060430 and on the other it stopped on 20060503,
> but failed on 20060502.

Can this now be closed?

Paul Thomas


-- 


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



[Bug fortran/17741] ICE in gfc_free_namespace, at fortran/symbol.c:2208

2006-05-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-05-10 
12:59 ---
I think that it is not correct to emit an ICE on this one.  The patch below
emits an error and bails out.

I will submit in the next 24hours.

Paul

Index: gcc/fortran/symbol.c
===
--- gcc/fortran/symbol.c(r├®vision 113111)
+++ gcc/fortran/symbol.c(copie de travail)
@@ -2490,8 +2490,15 @@
   ns->refs--;
   if (ns->refs > 0)
 return;
-  gcc_assert (ns->refs == 0);

+  if (ns->refs != 0)
+{
+  gfc_error_now ("namespace %s has %d references on being freed",
+ns->proc_name->name ? ns->proc_name->name : "MAIN",
+ns->refs + 1);
+  return;
+}
+
   gfc_free_statements (ns->code);

   free_sym_tree (ns->sym_root);


-- 

paul dot richard dot thomas at cea dot fr changed:

   What|Removed |Added
----
             CC||paul dot richard dot thomas
       ||at cea dot fr


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



[Bug fortran/26106] [meta-bug] Gfortran can't compile tonto

2006-04-13 Thread paul dot richard dot thomas at cea dot fr


--- Comment #15 from paul dot richard dot thomas at cea dot fr  2006-04-13 
13:36 ---
I can now compile tonto-1.0 without any kludges or tricks.  That said, it
segfaults immediately after reading the input data.  I will endeavour to find
the cause.

tonto-2.x is blocked by complex(ie. complicated) constructors, which in the
words of "Hitch-hikers Guide to the Galaxy", "will take a little while";
although I hope to improve on the 4 million years of the story

Paul


-- 


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



[Bug fortran/26822] Scalarization of non-elemental intrinsic: __logical_4_l4

2006-04-13 Thread paul dot richard dot thomas at cea dot fr


--- Comment #6 from paul dot richard dot thomas at cea dot fr  2006-04-13 
13:04 ---
Created an attachment (id=11256)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11256&action=view)
Patch to fix P26822

This took a depressingly long time to get to the bottom of - particularly since
the patch changes one character!  Fortunately, it was a few minutes here and
there.

The problem came about because LOGICAL was not marked as elemental in
intrinsic.c(add_functions), which put it in the wrong place in
trans_intrinsic.c and caused the observed consequences.

I will regtest and submit tonight but I am sure that this is the right fix.

Paul


-- 


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



[Bug fortran/26787] Assigning to function causes ice in gfortran

2006-04-13 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-04-13 
12:08 ---
(From update of attachment 11254)
This was the testcase, of course.


-- 

paul dot richard dot thomas at cea dot fr changed:

   What|Removed |Added

  Attachment #11254|Patch for PR26787   |Testcase for PR26787
description||
  Attachment #11254|1   |0
   is patch||
  Attachment #11254|1   |0
is obsolete||


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



[Bug fortran/26787] Assigning to function causes ice in gfortran

2006-04-13 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-04-13 
12:07 ---
Created an attachment (id=11255)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11255&action=view)
Patch for PR26787

Sorry, this is the patch that was regtested on Cygwin_NT/PIV and will be
submitted tonight.

Paul


-- 

paul dot richard dot thomas at cea dot fr changed:

   What|Removed |Added

  Attachment #11254|0   |1
is obsolete||


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



[Bug fortran/26787] Assigning to function causes ice in gfortran

2006-04-13 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-04-13 
12:04 ---
Created an attachment (id=11254)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11254&action=view)
Patch for PR26787

This has been regtested on Cygwin_NT/PIV and will be submitted tonight.

The testcase follows.

Paul


-- 


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



[Bug fortran/27124] Incorrect dependency for assignment from function with array section actual arg.

2006-04-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-04-12 
14:34 ---
I have a fix for it, which is regtesting right now.  Even if it fails in this
form, it is along the right lines and there will be a version that is pukkah. I
hope to submit the patch tonight.

Quite simply, the fix consists of gathering up all the argument post_blocks,
which contain the unpacking and freeing of argument temporaries, and putting
them into a separate block.  Once the function call is translated, it either
goes in the se->pre block or becomes the se expression, depending on how the
value is returned.  Depending on this same choice, we now add the argument post
block to se->pre or to se->post.  This ensures that the results of byref calls
that produce temporaries are transferred to the destination array AFTER the
unpacking of the argument.  The reduced testcase below now runs correctly.

The patch and testcase appear below.

Paul

Index: gcc/fortran/trans-expr.c
===
--- gcc/fortran/trans-expr.c(révision 112853)
+++ gcc/fortran/trans-expr.c(copie de travail)
@@ -1832,6 +1832,7 @@
   gfc_charlen cl;
   gfc_expr *e;
   gfc_symbol *fsym;
+  stmtblock_t post;

   arglist = NULL_TREE;
   retargs = NULL_TREE;
@@ -1861,6 +1862,7 @@
   else
 info = NULL;

+  gfc_init_block (&post);
   gfc_init_interface_mapping (&mapping);
   need_interface_mapping = ((sym->ts.type == BT_CHARACTER
  && sym->ts.cl->length
@@ -1970,7 +1972,7 @@
gfc_add_interface_mapping (&mapping, fsym, &parmse);

   gfc_add_block_to_block (&se->pre, &parmse.pre);
-  gfc_add_block_to_block (&se->post, &parmse.post);
+  gfc_add_block_to_block (&post, &parmse.post);

   /* Character strings are passed as two parameters, a length and a
  pointer.  */
@@ -2177,6 +2179,11 @@
}
 }

+  if (byref)
+gfc_add_block_to_block (&se->pre, &post);
+  else
+gfc_add_block_to_block (&se->post, &post);
+
   return has_alternate_specifier;
 }

! { dg-do run }
! Tests the fix for PR27124 in which the unpacking of argument
! temporaries and of array result temporaries occurred in the
! incorrect order.
! 
! Test is based on the original example, provided by
! Philippe Schaffnit <[EMAIL PROTECTED]>
!
  PROGRAM Test
INTEGER :: Array(2, 3) = reshape ((/1,4,2,5,3,6/),(/2,3/))
integer :: Brray(2, 3) = 0
Brray(1,:) = Function_Test (Array(1,:))
if (any(reshape (Brray, (/6/)) .ne. (/11, 0, 12, 0, 13, 0/))) call abort ()
Array(1,:) = Function_Test (Array(1,:))
if (any(reshape (Array, (/6/)) .ne. (/11, 4, 12, 5, 13, 6/))) call abort ()

  contains
  FUNCTION Function_Test (Input)
  INTEGER, INTENT(IN) :: Input(1:3)
  INTEGER :: Function_Test(1:3)
  Function_Test = Input + 10
  END FUNCTION Function_Test
  END PROGRAM Test




-- 


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



[Bug fortran/26834] gfc_todo: Not Implemented: Unable to determine rank of expression

2006-04-12 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-04-12 
14:32 ---
(In reply to comment #1)
> Confirmed, PR 25669 and bug 18003 are very closely related (it might turn out
> this is a dup of one of them).

They are indeed the same.  Attached below is a patch that fixes all three and a
testcase that demonstrates that this is so.  The patch is still testing but I
am pretty sure it is OK (ie. this is a path that ICEd previously).  I will
submit tonight, if all is well.

Paul

Index: gcc/fortran/trans-array.c
===
--- gcc/fortran/trans-array.c   (révision 112853)
+++ gcc/fortran/trans-array.c   (copie de travail)
@@ -2393,6 +2393,19 @@
  loop->dimen = ss->data.info.dimen;
  break;

+   /* Cope with the likes of PRINT *, lbound (a), where nothing
+  better is available.  */
+   case GFC_SS_INTRINSIC:
+ switch (ss->expr->value.function.isym->generic_id)
+   {
+   case GFC_ISYM_LBOUND:
+   case GFC_ISYM_UBOUND:
+ loop->dimen = ss->data.info.dimen;
+
+   default:
+ break;
+   }
+
default:
  break;
}
@@ -2418,6 +2431,15 @@
gfc_conv_section_startstride (loop, ss, n);
  break;

+   case GFC_SS_INTRINSIC:
+ switch (ss->expr->value.function.isym->generic_id)
+   {
+   case GFC_ISYM_LBOUND:
+   case GFC_ISYM_UBOUND:
+ break;
+   default:
+ continue;
+   }
case GFC_SS_CONSTRUCTOR:
case GFC_SS_FUNCTION:
  for (n = 0; n < ss->data.info.dimen; n++)
Index: gcc/fortran/trans-intrinsic.c
===
--- gcc/fortran/trans-intrinsic.c   (révision 112853)
+++ gcc/fortran/trans-intrinsic.c   (copie de travail)
@@ -3710,6 +3710,7 @@
   newss->type = GFC_SS_INTRINSIC;
   newss->expr = expr;
   newss->next = ss;
+  newss->data.info.dimen = 1;

   return newss;
 }

! { dg-do compile }
! This tests the fix for PRs 26834, 25669 and 18803, in which
! shape information for the lbound and ubound intrinsics was not
! transferred to the scalarizer.  For this reason, an ICE would
! ensue, whenever these functions were used in temporaries.
!
! The tests are lifted from the PRs and some further checks are
! done to make sure that nothing is broken.
!
! This is PR26834
subroutine gfcbug34 ()
  implicit none
  type t
 integer, pointer :: i (:) => NULL ()
  end type t
  type(t), save :: gf
  allocate (gf%i(20))
  write(*,*) 'ubound:', ubound (gf% i)
  write(*,*) 'lbound:', lbound (gf% i)
end subroutine gfcbug34

! This is PR25669
subroutine foo (a)
  real a(*)
  call bar (a, LBOUND(a),2)
end subroutine foo
subroutine bar (b, i, j)
  real b(i:j)
  print *, i, j
  print *, b(i:j)
end subroutine bar

! This is PR18003
subroutine io_bug()
  integer :: a(10)
  print *, ubound(a)
end subroutine io_bug

! This checks that lbound and ubound are OK in  temporary
! expressions.
subroutine io_bug_plus()
  integer :: a(10, 10), b(2)
  print *, ubound(a)*(/1,2/)
  print *, (/1,2/)*ubound(a)
end subroutine io_bug_plus

  character(4) :: ch(2), ech(2) = (/'ABCD', 'EFGH'/)
  real(4) :: a(2)
  equivalence (ech,a)
  integer(1) :: i(8) = (/(j, j = 1,8)/)

! Check that the bugs have gone
  call io_bug ()
  call io_bug_plus ()
  call foo ((/1.0,2.0,3.0/))
  call gfcbug34 ()

! Check that we have not broken other intrinsics.
  print *, cos ((/1.0,2.0/))
  print *, transfer (a, ch)
  print *, i(1:4) * transfer (a, i, 4) * 2
end


-- 


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



[Bug fortran/27112] Rejects to call a generic procedure by argument keywords.

2006-04-11 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-04-11 
08:59 ---
Iguchi-san,

You are correct. The reference to foo with an integer argument is disambiguated
by the use of the keyword.

The only compiler that I have found that handles this correctly is DF5.0/6.0.

Domo arigato gozaimasu


-- 


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



[Bug fortran/26106] [meta-bug] Gfortran can't compile tonto

2006-04-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #14 from paul dot richard dot thomas at cea dot fr  2006-04-10 
15:07 ---
(In reply to comment #13)
> PR23634 does not affect this PR.  So only two bugs left.  I checked by
> commenting out the lines effecting compiling.

I have submitted 2 PRs for tonto-2.2; PR25597 and PR27096.

The first I have submitted a patch for and the patch for the second will be
submitted tonight.

Paul


-- 


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



[Bug fortran/27096] Automatic charlen pointer array result produces and ICE

2006-04-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-04-10 
14:48 ---
A patch (not regtested yet, nor tested on tonto) and testcase for this and
PR25597:

Index: gcc/fortran/trans-decl.c
===
--- gcc/fortran/trans-decl.c(révision 112529)
+++ gcc/fortran/trans-decl.c(copie de travail)
@@ -2536,6 +2536,12 @@
{
  tree result = TREE_VALUE (current_fake_result_decl);
  fnbody = gfc_trans_dummy_array_bias (proc_sym, result, fnbody);
+
+ /* An automatic character length, pointer array result.  */
+ if (proc_sym->ts.type == BT_CHARACTER
+   && TREE_CODE (proc_sym->ts.cl->backend_decl) == VAR_DECL)
+   fnbody = gfc_trans_dummy_character (proc_sym, proc_sym->ts.cl,
+   fnbody);
}
   else if (proc_sym->ts.type == BT_CHARACTER)
{
Index: gcc/fortran/trans-array.c
===
--- gcc/fortran/trans-array.c   (révision 112529)
+++ gcc/fortran/trans-array.c   (copie de travail)
@@ -4385,7 +4385,14 @@

   /* Get the descriptor type.  */
   type = TREE_TYPE (sym->backend_decl);
-  gcc_assert (GFC_DESCRIPTOR_TYPE_P (type));
+  if (!GFC_DESCRIPTOR_TYPE_P (type))
+{
+  /* If the backend_decl is not a descriptor, we must have a pointer
+to one.  */
+  descriptor = build_fold_indirect_ref (sym->backend_decl);
+  type = TREE_TYPE (descriptor);
+  gcc_assert (GFC_DESCRIPTOR_TYPE_P (type));
+}

   /* NULLIFY the data pointer.  */
   gfc_conv_descriptor_data_set (&fnblock, descriptor, null_pointer_node);


! { dg-do run }
! Tests the fixes for PR25597 and PR27096.
!
! This test combines the PR testcases.
!
  character(10), dimension (2) :: implicit_result
  character(10), dimension (2) :: explicit_result
  character(10), dimension (2) :: source
  source = "abcdefghij"
  explicit_result = join_1(source)
  if (any (explicit_result .ne. source)) call abort () 

  implicit_result = reallocate_hnv (source, size(source, 1), LEN (source))
  if (any (implicit_result .ne. source)) call abort () 

contains

! This function would cause an ICE in gfc_trans_deferred_array.
  function join_1(self) result(res)
character(len=*), dimension(:) :: self
character(len=len(self)), dimension(:), pointer :: res
allocate (res(2))
res = self
  end function

! This function originally ICEd and latterly caused a runtime error.
  FUNCTION reallocate_hnv(p, n, LEN)
CHARACTER(LEN=LEN), DIMENSION(:), POINTER :: reallocate_hnv
character(*), dimension(:) :: p
ALLOCATE (reallocate_hnv(n))
reallocate_hnv = p
  END FUNCTION reallocate_hnv

end


Paul


-- 


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



[Bug fortran/25597] ICE with allocate on the return value of a function, character array with a len of an argument

2006-04-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #6 from paul dot richard dot thomas at cea dot fr  2006-04-10 
14:35 ---
(In reply to comment #5)
> (In reply to comment #4)
> > A little further reduced:
> Actually that is a different bug.
> Anyways the reduced testcase looks like:
>   FUNCTION reallocate_hnv(p,n,LEN)
> CHARACTER(LEN=LEN), DIMENSION(:), POINTER :: reallocate_hnv
> ALLOCATE(reallocate_hnv(n))
>   END FUNCTION reallocate_hnv

This no longer ICEs but does bomn out in runtime, as described in PR27096

Paul


-- 


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



[Bug fortran/27096] Automatic charlen pointer array result produces and ICE

2006-04-10 Thread paul dot richard dot thomas at cea dot fr


--- Comment #2 from paul dot richard dot thomas at cea dot fr  2006-04-10 
14:19 ---
The peculiar code turns out to be a result of the way in which I kludged my way
past the ICE.  In sorting the out, I found that there is a double fault:

The implicit result version of the above

  character(10), dimension (2) :: inp
  inp = "abcdefghij"
  inp = join_1(inp)
  print *, inp
contains
  function join_1(self)
character(len=*), dimension(:) :: self
character(len=len(self)), dimension(:), pointer :: join_1
allocate (join_1(2))
join_1 = self
  end function
end

compiles but hits the runtime error:

Fortran runtime error: Attempt to allocate negative amount of memory.  Possible
integer overflow.

I must check that this is not an existing PR.

A double patch is on its way.

Paul


-- 


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



[Bug fortran/25746] Elemental assignment gives wrong result

2006-04-07 Thread paul dot richard dot thomas at cea dot fr


--- Comment #4 from paul dot richard dot thomas at cea dot fr  2006-04-07 
10:16 ---
> Patch to fix elemental subroutine dependences.
This is still a little bit ragged insofar as it produces and excess of
temporaries and that it still gets one case wrong:

x(1:2) = x(2:3) is broken.
However, the bulk of the work is done and the submission is a few days away.  I
will add the conformance checks too.

Cheers

Paul 


-- 


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



[Bug fortran/25746] Elemental assignment gives wrong result

2006-04-07 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-04-07 
10:13 ---
Created an attachment (id=11220)
 --> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=11220&action=view)
Patch to fix elemental subroutine dependences.


-- 


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



[Bug fortran/27035] present doesn't work on array

2006-04-05 Thread paul dot richard dot thomas at cea dot fr


--- Comment #11 from paul dot richard dot thomas at cea dot fr  2006-04-05 
07:17 ---
(In reply to comment #7)
> I don't think this is defined code:
> if (present (a)) call abort ()
> call foo_ (a)
> If a is not present, you should not be able to use a in any way.

Not quite; as I recorded in PR26891 (fixed in trunk and to be fixed in 4.1
tomorrow)

12.4.1.5 Restriction on dummy arguments not present.
. snip .
Except as noted in the list above, it may be supplied as an actual argument
corresponding to an optional dummy argument, which is also considered not to be
associated with an actual argument.

The code below works correctly (and in the same way as DF6.0 and ifort).

I cannot see a bug in this PR.

Paul

module mod
implicit none

private

public bar_
interface bar_
module procedure bar
end interface

public foo_
interface foo_
module procedure foo
end interface

contains

  subroutine bar (a)
real(kind=kind(1.0d0)), dimension(:,:), optional :: a
if (present(a)) then
  print *, "present in BAR"
else
  print *, "not present in BAR"
ENDIF
call foo_ (a) ! Optional dummy and optional actual => Acceptable
  end subroutine bar

  subroutine foo(a)
real(kind=kind(1.0d0)), dimension(:,:), optional :: a
if (present(a)) then
  print *, "present in FOO"
else
  print *, "not present in FOO"
ENDIF
  end subroutine foo

end

program main
 use mod
 real(kind=kind(1.0d0)), dimension(1,1) :: a
 call bar_ ()
 call bar_ (a)
end program main


-- 


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



[Bug fortran/27035] present doesn't work on array

2006-04-05 Thread paul dot richard dot thomas at cea dot fr


--- Comment #10 from paul dot richard dot thomas at cea dot fr  2006-04-05 
07:02 ---
> program main
>   call foo (5)
> end program main
> subroutine foo(n, a)
>   integer :: n
>   integer, dimension(5), optional :: a
>   print *, n
>   if (present (a)) call abort ()
> end subroutine foo

Andrew is right about this; gfortran does not communicate the "interface"
(that's the word that you were looking for, Andrew) between same file but
separate procedures.  Thus, MAIN does not "know" that the second argument is
optional. 


-- 


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



[Bug fortran/24406] EQUIVALENCE broken in 32-bit code with optimization -O2

2006-03-23 Thread paul dot richard dot thomas at cea dot fr


--- Comment #15 from paul dot richard dot thomas at cea dot fr  2006-03-23 
08:06 ---
Subject: RE:  EQUIVALENCE broken in 32-bit code with optimization -O2

I thought to take a look at the patch tonight; does it look OK to you?

Paul

> -Message d'origine-
> De : pinskia at gcc dot gnu dot org [mailto:[EMAIL PROTECTED]
> Envoyé : jeudi 23 mars 2006 02:06
> À : THOMAS Paul Richard 169137
> Objet : [Bug fortran/24406] EQUIVALENCE broken in 32-bit code with
> optimization -O2
> 
> 
> 
> 
> --- Comment #14 from pinskia at gcc dot gnu dot org  
> 2006-03-23 01:06 ---
> Jakub posted a patch:
> http://gcc.gnu.org/ml/gcc-patches/2006-03/msg01419.html
> 
> So this is no longer mine.
> 
> 
> -- 
> 
> pinskia at gcc dot gnu dot org changed:
> 
>What|Removed |Added
> --
> --
>  AssignedTo|pinskia at gcc dot gnu dot  |unassigned 
> at gcc dot gnu
>|org |dot org
> URL|
> |http://gcc.gnu.org/ml/gcc-
>||patches/2006-
>||03/msg01419.html
>  Status|ASSIGNED|NEW
>Keywords||patch
> 
> 
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=24406
> 
> --- You are receiving this mail because: ---
> You are on the CC list for the bug, or are watching someone who is.
> 


-- 


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



[Bug fortran/26779] New: Internal module procedure may not have private type dummy arguments

2006-03-21 Thread paul dot richard dot thomas at cea dot fr
This error is generated by the example, given at the end of Metcalf, Reid and
Cohen; pointer.f90.  The following reduced testcase, illustartes it:

module test
  public sub
  type, private :: t
!  type :: t
integer :: i
  end type t
contains
  subroutine sub (arg)
integer arg
type(t) :: root
call init(root, arg)
  contains
subroutine init(ir, i)
  integer i
  type(t) :: ir
  ir%i = i
end subroutine init
  end subroutine sub
end module test

In file private.f90:11

call init(root, arg)
1
Error: 'ir' is of a PRIVATE type and cannot be a dummy argument of 'init',
which
 is PUBLIC at (1)

Being an internal procedure, init is NOT public by 2.2.3.3 of the F95 standard.
It should have access to all the symbols of the host, therefore this error is
wrong on both levels; ir cannot be private to it, nor is init public!

Needless to say, a patch is on its way!

Paul


-- 
   Summary: Internal module procedure may not have private type
dummy arguments
   Product: gcc
   Version: 4.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
AssignedTo: unassigned at gcc dot gnu dot org
    ReportedBy: paul dot richard dot thomas at cea dot fr


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



[Bug fortran/25034] allows passing of contained subprograms as actual argument

2006-03-20 Thread paul dot richard dot thomas at cea dot fr


--- Comment #3 from paul dot richard dot thomas at cea dot fr  2006-03-20 
12:49 ---
(In reply to comment #2)
> Isn't this just a dup of bug 20861?

... and, in fact, was fixed by the patch for 20861.

I will set this one as resolved tonight.

Paul


-- 


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



[Bug fortran/24520] Temporary constant array descriptors being declared at wrong binding level.

2006-03-16 Thread paul dot richard dot thomas at cea dot fr


--- Comment #5 from paul dot richard dot thomas at cea dot fr  2006-03-16 
08:38 ---
Yes, it is not quite as spectacular as before but present nonetheless.  By
comparing pointer and non-pointer cases, I measure an overhead of 12 +/- 7 ns
on a 2.4Ghz PIV.  I have no idea why the error is so large but it bobs around,
according to the size of the array; eg. for array size N = 1, it is 19ns, for N
= 16 is 16ns, whilst n = 4 is only hit for 6ns.

In preparing the array TRANSFER intrinsic, I have learned more about parameter
passing than I like to think about. *sigh*  I think it might be an easy matter
to promote the case of a constant descriptor up to the procedure scope.  I t
has been pushed onto the TODO stack.

Paul 


-- 


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



  1   2   >