With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
IMPLICIT NONE
CONTAINS
SUBROUTINE S1(F1)
INTERFACE
FUNCTION F1()
END FUNCTION F1
END INTERFACE
END SUBROUTINE S1
END MODULE
END
--
Summary: incorrect error message
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
SUBROUTINE S1(a)
INTEGER :: a(*)
IF(SIZE(a(1:10),1).NE.10) CALL ABORT()
END SUBROUTINE S1
INTEGER :: a(10)
CALL S1(a)
END
--
Summary: incorrect error message for valid code
Product
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
INTEGER, PARAMETER :: K=1
INTEGER :: I
I=TRANSFER(.TRUE.,K)
SELECT CASE(I)
CASE(TRANSFER(.TRUE.,K))
CASE(TRANSFER(.FALSE.,K))
CALL ABORT()
CASE DEFAULT
CALL ABORT()
END SELECT
I=TRANSFER(.FALSE.,K)
SELECT
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
TYPE T1
INTEGER :: i=7
END TYPE T1
CONTAINS
FUNCTION F1(d1) RESULT(res)
INTEGER :: res
TYPE(T1), INTENT(OUT) :: d1
TYPE(T1), INTENT(INOUT) :: d2
res=d1%i
d1%i=0
RETURN
ENTRY E1
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
TYPE T1
INTEGER :: I
END TYPE T1
TYPE(T1), PARAMETER :: D1=T1(2)
INTEGER :: a(2)
DATA (a(i),i=1,D1%I) /D1%I*D1%I/
END
--
Summary: incorrect error message for valid code
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
CONTAINS
INTEGER FUNCTION F1()
NAMELIST /NML/ F1
F1=1
END FUNCTION
INTEGER FUNCTION F2()
F2=1
END FUNCTION
END MODULE
END
--
Summary: incorrect error me
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
INTERFACE OPERATOR(*)
MODULE PROCEDURE F1
END INTERFACE
CONTAINS
FUNCTION F1(a,b) RESULT (c)
COMPLEX, dimension(2,2), INTENT(IN) :: a
COMPLEX, dimension(2), INTENT(IN) :: b
COMPLEX, di
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
CONTAINS
FUNCTION correct_input(i)
INTEGER :: i,correct_input(5)
IF (i<1) correct_input=test(1)
IF (i>5) correct_input=test(5)
END FUNCTION correct_input
RECURSIVE FUNCTION test(i)
I
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
TYPE T1
sequence
integer :: i=1
END TYPE T1
TYPE T2
sequence
integer :: i=1
END TYPE T2
TYPE(T1) :: a1
TYPE(T2) :: a2
EQUIVALENCE(a1,a2)
write(6,*) a1,a2
END
--
Summary: incorrect error mes
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
program forall_9
real, dimension (5, 5, 5, 5) :: a, b, c, d
a (:, :, :, :) = 4
forall (i = 1:5)
a (i, i, 6 - i, i) = 7
end forall
forall (i = 1:5)
a (i, 6 - i, i, i) = 7
end forall
for
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE M1
CONTAINS
FUNCTION F2(K)
INTEGER :: F2,K
F2=E1(K)
END FUNCTION F2
RECURSIVE FUNCTION F1(I)
INTEGER :: F1,I,E1
F1=F2(I)
RETURN
ENTRY E1(I)
E1=-I
RETURN
END FUNCTION F1
END MODULE M1
USE M1
I
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE MOD1
IMPLICIT NONE
INTEGER, PARAMETER :: dp=KIND(0.0D0)
CONTAINS
SUBROUTINE pw_compose_stripe(weights,in_val,in_val_first,in_val_last,&
out_val,n_el)
REAL(kind=dp), DIMENSION(0:2), &
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
TYPE data
CHARACTER(LEN=3) :: A
END TYPE
TYPE(data), DIMENSION(10), TARGET :: Z
CHARACTER(LEN=1), DIMENSION(:), POINTER :: ptr
Z(:)%A="123"
ptr=>Z(:)%A(2:2)
write(6,*) ptr
END
--
Summary: inco
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE TEST
INTERFACE xx
MODULE PROCEDURE xx
END INTERFACE
public :: xx
CONTAINS
SUBROUTINE xx(i)
INTEGER :: I
I=7
END SUBROUTINE
END
MODULE TOO
CONTAINS
SUBROUTINE SUB(xx,I)
INTERFACE
SUB
With recent trunk, gfortran incorrectly generates an error for the following
standard code:
INTEGER, POINTER :: i
ALLOCATE(i)
DO i=1,10
ENDDO
DEALLOCATE(i)
END
--
Summary: incorrect error message for valid code
Product: gcc
Version: 4.3.0
Status: UNC
--- Comment #2 from pinskia at gcc dot gnu dot org 2007-02-20 06:38 ---
Is this a precompiled GCC? If so are you sure that the program is compiled for
the OS version you are using as it looks like it is not.
--
pinskia at gcc dot gnu dot org changed:
What|Removed
--- Comment #1 from r dot ford at cox dot net 2007-02-20 06:13 ---
HP-UX hpux B.11.11 U 9000/785 2011004178
--
r dot ford at cox dot net changed:
What|Removed |Added
# gcc -o main.out main.c
/usr/lib/dld.sl: Unresolved symbol: pthread_mutex_lock (code) from
/usr/local/libexec/gcc/hppa2.0w-hp-hpux11.11/4.1.1/cc1
gcc: Internal error: Aborted (program cc1)
Please submit a full bug report.
See http://gcc.gnu.org/bugs.html> for instructions.
# cc -o main.out main.c
--- Comment #10 from christoph dot mallon at gmx dot de 2007-02-20 06:02
---
(In reply to comment #9)
> Note SSA CCP usually (this is how it is done in the papers and almost always
> done in all comericial compilers too) does PHI<1, UNDEFINED> as just being 1.
>
> This is still a dup b
--- Comment #1 from pinskia at gcc dot gnu dot org 2007-02-20 05:54 ---
You should note that __DATE__ and __TIME__ are actually part of the C89 (ANSI)
and C90 (ISO) standards.
> This is probably a question for the steering committee
Really if you up to implementing it, I would say go a
--
pault at gcc dot gnu dot org changed:
What|Removed |Added
Status|UNCONFIRMED |NEW
Ever Confirmed|0 |1
Last reconfirm
--- Comment #1 from pault at gcc dot gnu dot org 2007-02-20 05:34 ---
Confirmed:
The first call to checkv produces
checkv (&ires, &parm.10, 0B);
With prototype: checkv (ires, a1, opt1), the call to size1 is
*ires = _gfortran_size1 (&parm.6, *opt1);
with the obvious consequences.
--- Comment #3 from rizzolo at gmail dot com 2007-02-20 03:25 ---
Subject: Re: invalid "Can't find method" error
Ya gotta do what ya gotta do.
Thanks,
- Nick
On 20 Feb 2007 02:16:12 -, tromey at gcc dot gnu dot org
<[EMAIL PROTECTED]> wrote:
>
>
> --- Comment #2 from tromey
--- Comment #2 from tromey at gcc dot gnu dot org 2007-02-20 02:16 ---
FWIW we've basically stopped fixing bugs in the older gcj front end
and instead we've switched to using ecj.
I would close this as "wontfix" but that seems a bit harsh to do
unannounced... so with your permission I'd
Several times now in different jobs, I have come across the need for a better
__DATE__ and __TIME__, and always had to use a function such as that listed
below.
This is probably a question for the steering committee, but can I suggest the
following.
In particular, some formats which are sortable
--- Comment #14 from amodra at bigpond dot net dot au 2007-02-20 01:29
---
Patch applied
--
amodra at bigpond dot net dot au changed:
What|Removed |Added
Sta
--
amodra at bigpond dot net dot au changed:
What|Removed |Added
AssignedTo|unassigned at gcc dot gnu |amodra at bigpond dot net
|dot org
--- Comment #13 from amodra at gcc dot gnu dot org 2007-02-20 01:28 ---
Subject: Bug 29943
Author: amodra
Date: Tue Feb 20 01:28:01 2007
New Revision: 122149
URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=122149
Log:
PR target/29943
* varasm.c (use_blocks_for_dec
--- Comment #12 from amodra at gcc dot gnu dot org 2007-02-20 01:25 ---
Subject: Bug 29943
Author: amodra
Date: Tue Feb 20 01:25:41 2007
New Revision: 122148
URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=122148
Log:
PR target/29943
* varasm.c (use_blocks_for_dec
--- Comment #10 from rth at gcc dot gnu dot org 2007-02-19 23:45 ---
Fixed.
--
rth at gcc dot gnu dot org changed:
What|Removed |Added
Status|ASSIGNED
--- Comment #21 from dberlin at gcc dot gnu dot org 2007-02-19 23:41
---
(In reply to comment #20)
> Is there a backport of the mainline patch that I could review, or ask another
> maintainer to review for inclusion in 4.2?
>
> Thanks,
>
> -- Mark
>
The attached patch named "access_
--- Comment #20 from mmitchel at gcc dot gnu dot org 2007-02-19 23:33
---
Is there a backport of the mainline patch that I could review, or ask another
maintainer to review for inclusion in 4.2?
Thanks,
-- Mark
--
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=28544
--- Comment #8 from moshevds at gmail dot com 2007-02-19 22:58 ---
I'll update my gcc and try sometime this week.
--
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29718
--- Comment #2 from martin at mpa-garching dot mpg dot de 2007-02-19 22:39
---
Created an attachment (id=13071)
--> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=13071&action=view)
preprocessed, unreduced test case
--
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30866
--- Comment #1 from martin at mpa-garching dot mpg dot de 2007-02-19 22:32
---
Sorry, I meant PR25874.
--
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30866
ran --enable-checking=release
Thread model: posix
gcc version 4.3.0 20070219 (experimental)
/home/martin/software/ugcc/libexec/gcc/x86_64-unknown-linux-gnu/4.3.0/cc1plus
-fpreprocessed bug.ii -quiet -dumpbase bug.ii -mtune=generic -auxbase bug -O
-version -o /tmp/ccpih7d1.s
GNU C++ version 4.
--- Comment #3 from joseph at codesourcery dot com 2007-02-19 22:20 ---
Subject: Re: [4.1/4.2/4.3 Regression] Internal
compiler error when using "x##,##__VA_ARGS__" in macro
The order of evaluation of ## operators is unspecified.
If the left ## is evaluated first, it tries to concate
The following is legal (see
<[EMAIL PROTECTED]>), but we segfault
on execution:
$ cat size.f90
module foo
contains
subroutine checkv(ires,a1,opt1)
integer :: a1(:,:)
integer, optional :: opt1
ires = size (a1, dim=opt1)
end subroutine checkv
end module foo
program main
use foo
--- Comment #8 from sgk at troutmask dot apl dot washington dot edu
2007-02-19 21:49 ---
Subject: Re: ICE with kind=8 exponentiaton
On Mon, Feb 19, 2007 at 09:11:45PM -, tkoenig at gcc dot gnu dot org wrote:
>
> >Feel free to create a gfc_extract_long_long and document that
> > e
Jarl Friis wrote:
Can anyone here tell me who is (and the email of) the GCC bugzilla
administrator
gcc-bugs is mainly a list for output from our bug database. Posting
here isn't very useful. Better to file a bug report, or send email to
the gcc list.
If you really need to reach an admini
--- Comment #4 from tkoenig at gcc dot gnu dot org 2007-02-19 21:44 ---
The file generation issue still needs to be fixed on 4.2.
--
tkoenig at gcc dot gnu dot org changed:
What|Removed |Added
---
--
ebotcazou at gcc dot gnu dot org changed:
What|Removed |Added
Summary|[4.2 regression] boostrap |[4.1 regression] boostrap
|failed with undefined
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30852
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P4
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30851
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P4
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30849
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30848
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30847
--- Comment #7 from tkoenig at gcc dot gnu dot org 2007-02-19 21:11 ---
(In reply to comment #6)
>Feel free to create a gfc_extract_long_long and document that
> e is constrained to be within [LONG_LONG_MIN, LONG_LONG_MAX].
Suppose we don't simplify if gfc_extract_int fails. Would tha
--- Comment #2 from mmitchel at gcc dot gnu dot org 2007-02-19 21:09
---
Joseph --
Is this valid code?
Thanks,
-- Mark
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
-
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30786
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30762
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30761
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30759
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30744
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30729
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30704
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30700
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P5
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30684
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30675
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P5
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30660
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P4
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30535
--- Comment #3 from mmitchel at gcc dot gnu dot org 2007-02-19 21:01
---
Jan --
Would you please comment as to whether or not the error message is valid?
Thanks,
-- Mark
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
--
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30328
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P4
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30303
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P4
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30299
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P4
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30298
--- Comment #6 from mmitchel at gcc dot gnu dot org 2007-02-19 20:57
---
This is not a bug. The C++ standard says:
[expr.post.incr]
the value of the object is modified by adding 1 to it, unless the object is of
type bool, in which case it is set to true
--
mmitchel at gcc dot gnu
--- Comment #6 from mmitchel at gcc dot gnu dot org 2007-02-19 20:52
---
Before we can prioritize this problem, we need to establish that it doesn't
violate the aliasing rules. As Andrew says in Comment #2, this looks likely to
be a problem in the input program.
--
mmitchel at gcc
--- Comment #2 from pinskia at gcc dot gnu dot org 2007-02-19 20:50 ---
Reducing ...
--
pinskia at gcc dot gnu dot org changed:
What|Removed |Added
CC|
--- Comment #8 from manu at gcc dot gnu dot org 2007-02-19 20:50 ---
(In reply to comment #6)
> there is an implicit value conversion, boolean "false" to address "0". I think
> that is the definition of -Wconversion, no?
>
> anyway, I'll work on a patch.
>
Take a look at http://gcc.g
--- Comment #3 from tkoenig at gcc dot gnu dot org 2007-02-19 20:49 ---
Subject: Bug 30765
Author: tkoenig
Date: Mon Feb 19 20:49:10 2007
New Revision: 122137
URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=122137
Log:
2007-02-19 Thomas Koenig <[EMAIL PROTECTED]>
PR li
--- Comment #11 from tkoenig at gcc dot gnu dot org 2007-02-19 20:49
---
Subject: Bug 30533
Author: tkoenig
Date: Mon Feb 19 20:49:10 2007
New Revision: 122137
URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=122137
Log:
2007-02-19 Thomas Koenig <[EMAIL PROTECTED]>
PR
--- Comment #7 from gdr at cs dot tamu dot edu 2007-02-19 20:49 ---
Subject: Re: Should warn about boolean constant false used in pointer context
"mueller at gcc dot gnu dot org" <[EMAIL PROTECTED]> writes:
| there is an implicit value conversion, boolean "false" to address "0". I
thi
--- Comment #11 from mmitchel at gcc dot gnu dot org 2007-02-19 20:49
---
Jakub --
This patch is OK for 4.2 if tested there.
Thanks,
-- Mark
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
---
--- Comment #1 from dcb314 at hotmail dot com 2007-02-19 20:45 ---
Created an attachment (id=13070)
--> (http://gcc.gnu.org/bugzilla/attachment.cgi?id=13070&action=view)
gzipped C++ source code
--
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=30864
--- Comment #11 from mmitchel at gcc dot gnu dot org 2007-02-19 20:45
---
Alan --
This patch is OK. Would you please apply to 4.2 and mainline?
Thanks,
-- Mark
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
---
I just tried to compile Suse Linux package vym-1.8.1-39
with the GNU C++ compiler version 4.3 snapshot 20070216.
The compiler said
main.cpp: In function 'void __tcf_8(void*)':
main.cpp:123: internal compiler error: in alloc_aux_for_block, at cfg.c:665
Please submit a full bug report,
with preproc
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29902
--- Comment #9 from mmitchel at gcc dot gnu dot org 2007-02-19 20:43
---
Zdenek --
Can this patch be backported to 4.2?
Thanks,
-- Mark
--
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29902
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29841
--
pinskia at gcc dot gnu dot org changed:
What|Removed |Added
Severity|blocker |normal
Component|other |libgcj
http:
--- Comment #7 from mmitchel at gcc dot gnu dot org 2007-02-19 20:40
---
Moshe --
Do you still see the failure? Richard Guenther believes it to be fixed.
-- Mark
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
--
--- Comment #1 from pinskia at gcc dot gnu dot org 2007-02-19 20:39 ---
Confirmed.
--
pinskia at gcc dot gnu dot org changed:
What|Removed |Added
Status|UNCON
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P2
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29614
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29585
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P4
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29571
--- Comment #9 from mmitchel at gcc dot gnu dot org 2007-02-19 20:34
---
RTH --
You checked in a patch for this on the 4.2 branch; should this issue be closed
now?
Thanks,
-- Mark
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P5
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29524
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P1
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29255
--
mmitchel at gcc dot gnu dot org changed:
What|Removed |Added
Priority|P3 |P5
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29206
test.cc:
#include
template
struct s {
s() {
printf("Print me, please!\n");
}
};
int main(){
s x;
unsigned s y;
}
% g++ -Wall test.cc -o test &&./test
test.cc: In function 'int main()':
test.cc:12: warning: unused variable 'y'
Print me, please!
--- Comment #6 from mueller at gcc dot gnu dot org 2007-02-19 20:23 ---
there is an implicit value conversion, boolean "false" to address "0". I think
that is the definition of -Wconversion, no?
anyway, I'll work on a patch.
--
mueller at gcc dot gnu dot org changed:
Wh
--
mueller at gcc dot gnu dot org changed:
What|Removed |Added
Status|UNCONFIRMED |NEW
Ever Confirmed|0 |1
Last reconfi
After correct bootstrapping of the compiler (C, C++ and Java), make install
gives the following error, leaving the Java installation in a broken state:
Making install in midi-alsa
make[6]: Entering directory
`/root/gccbuild/i686-pc-linux-gnu/libjava/classpath/native/jni/midi-alsa'
make[7]: Enterin
--- Comment #5 from gdr at cs dot tamu dot edu 2007-02-19 19:59 ---
Subject: Re: Should warn about boolean constant false used in pointer context
"manu at gcc dot gnu dot org" <[EMAIL PROTECTED]> writes:
| No, it is not. And I don't think it should be warned by -Wconversion. After
| a
--- Comment #2 from patchapp at dberlin dot org 2007-02-19 19:55 ---
Subject: Bug number PR 30824
A patch for this bug has been added to the patch tracker.
The mailing list url for the patch is
http://gcc.gnu.org/ml/gcc-patches/2007-02/msg01640.html
--
http://gcc.gnu.org/bugzilla/s
--- Comment #72 from jv244 at cam dot ac dot uk 2007-02-19 19:51 ---
I checked that gfortran yields correct results for the CP2K testsuite with the
options:
-O0 -g -fbounds-check
and
-O3 -ffast-math -funroll-loops -ftree-vectorize -fomit-frame-pointer -msse2
-march=native
I've added the
--- Comment #4 from gdr at cs dot tamu dot edu 2007-02-19 19:48 ---
Subject: Re: Should warn about boolean constant false used in pointer context
"pinskia at gcc dot gnu dot org" <[EMAIL PROTECTED]> writes:
| I don't see why we should warn about a very valid and well defined and will
--- Comment #7 from dberlin at gcc dot gnu dot org 2007-02-19 19:34 ---
Sorry, the fix was committed before the bug report was filed (IE ~5 minutes
before).
I forgot to mark this one closed.
--
dberlin at gcc dot gnu dot org changed:
What|Removed |
--- Comment #3 from manu at gcc dot gnu dot org 2007-02-19 19:14 ---
(In reply to comment #1)
> manu, is this something already covered by your pending -Wconversion fixes?
>
No, it is not. And I don't think it should be warned by -Wconversion. After
all, no value is changed during the
1 - 100 of 150 matches
Mail list logo