public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/29660]  New: get 'internal compiler error' when building numerical recipes
@ 2006-10-31  1:45 karlglazebrook at mac dot com
  2006-10-31  1:51 ` [Bug target/29660] " pinskia at gcc dot gnu dot org
                   ` (5 more replies)
  0 siblings, 6 replies; 7+ messages in thread
From: karlglazebrook at mac dot com @ 2006-10-31  1:45 UTC (permalink / raw)
  To: gcc-bugs

I get the following error when trying to compile a subroutine from the famed 
numerical recipes in fortran lib

 gfortran -O cisi.f

cisi.f: In function 'cisi':
cisi.f:1: internal compiler error: Bus error
Please submit a full bug report,

Code attached. Error goes away when I leave out the -O flag.

frenel.f has the same issue. Older g77 has no issue.

     SUBROUTINE cisi(x,ci,si)
      INTEGER MAXIT
      REAL ci,si,x,EPS,EULER,PIBY2,FPMIN,TMIN
      PARAMETER (EPS=6.e-8,EULER=.57721566,MAXIT=100,PIBY2=1.5707963,
     *FPMIN=1.e-30,TMIN=2.)
      INTEGER i,k
      REAL a,err,fact,sign,sum,sumc,sums,t,term,absc
      COMPLEX h,b,c,d,del
      LOGICAL odd
      absc(h)=abs(real(h))+abs(aimag(h))
      t=abs(x)
      if(t.eq.0.)then
        si=0.
        ci=-1./FPMIN
        return
      endif
      if(t.gt.TMIN)then
        b=cmplx(1.,t)
        c=1./FPMIN
        d=1./b
        h=d
        do 11 i=2,MAXIT
          a=-(i-1)**2
          b=b+2.
          d=1./(a*d+b)
          c=b+a/c
          del=c*d
          h=h*del
          if(absc(del-1.).lt.EPS)goto 1
11      continue
        pause 'cf failed in cisi'
1       continue
        h=cmplx(cos(t),-sin(t))*h
        ci=-real(h)
        si=PIBY2+aimag(h)
      else
        if(t.lt.sqrt(FPMIN))then
          sumc=0.
          sums=t
        else
          sum=0.
          sums=0.
          sumc=0.
          sign=1.
          fact=1.
          odd=.true.
          do 12 k=1,MAXIT
            fact=fact*t/k
            term=fact/k
            sum=sum+sign*term
            err=term/abs(sum)
            if(odd)then
              sign=-sign
              sums=sum
              sum=sumc
            else
              sumc=sum
              sum=sums
            endif
            if(err.lt.EPS)goto 2
            odd=.not.odd
12        continue
          pause 'maxits exceeded in cisi'
        endif
2       si=sums
        ci=sumc+log(t)+EULER
      endif
      if(x.lt.0.)si=-si
      return
      END


-- 
           Summary: get 'internal compiler error' when building numerical
                    recipes
           Product: gcc
           Version: 4.0.1
            Status: UNCONFIRMED
          Severity: major
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: karlglazebrook at mac dot com
GCC target triplet: i686-apple-darwin8


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


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

* [Bug target/29660] get 'internal compiler error' when building numerical recipes
  2006-10-31  1:45 [Bug fortran/29660] New: get 'internal compiler error' when building numerical recipes karlglazebrook at mac dot com
@ 2006-10-31  1:51 ` pinskia at gcc dot gnu dot org
  2006-10-31  4:46 ` kargl at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2006-10-31  1:51 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pinskia at gcc dot gnu dot org  2006-10-31 01:51 -------
This works just fine on i686-linux so this is a darwin specific bug.  Can you
try a build of 4.2.0 for i686-darwin? Any build of GCC for darwin before 4.2.0
does not support Darwin that well.


-- 

pinskia at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|major                       |normal
          Component|fortran                     |target


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


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

* [Bug target/29660] get 'internal compiler error' when building numerical recipes
  2006-10-31  1:45 [Bug fortran/29660] New: get 'internal compiler error' when building numerical recipes karlglazebrook at mac dot com
  2006-10-31  1:51 ` [Bug target/29660] " pinskia at gcc dot gnu dot org
@ 2006-10-31  4:46 ` kargl at gcc dot gnu dot org
  2006-10-31  5:49 ` karlglazebrook at mac dot com
                   ` (3 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: kargl at gcc dot gnu dot org @ 2006-10-31  4:46 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from kargl at gcc dot gnu dot org  2006-10-31 04:46 -------
See Andrew's comment.  Using gfortran 4.0.1 is guaranteed
not to compile NR.


-- 


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


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

* [Bug target/29660] get 'internal compiler error' when building numerical recipes
  2006-10-31  1:45 [Bug fortran/29660] New: get 'internal compiler error' when building numerical recipes karlglazebrook at mac dot com
  2006-10-31  1:51 ` [Bug target/29660] " pinskia at gcc dot gnu dot org
  2006-10-31  4:46 ` kargl at gcc dot gnu dot org
@ 2006-10-31  5:49 ` karlglazebrook at mac dot com
  2007-01-09 16:05 ` fxcoudert at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  5 siblings, 0 replies; 7+ messages in thread
From: karlglazebrook at mac dot com @ 2006-10-31  5:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from karlglazebrook at mac dot com  2006-10-31 05:49 -------
Subject: Re:  get 'internal compiler error' when building numerical recipes

I'm happy to give 4.2.0 a try

Is it binary compatible with 4.0.1 or will I have to rebuild  
everything with a libgfortran dependence?

Karl

On 31/10/2006, at 3:46 PM, kargl at gcc dot gnu dot org wrote:

>
>
> ------- Comment #2 from kargl at gcc dot gnu dot org  2006-10-31  
> 04:46 -------
> See Andrew's comment.  Using gfortran 4.0.1 is guaranteed
> not to compile NR.
>
>
> -- 
>
>
> http://gcc.gnu.org/bugzilla/show_bug.cgi?id=29660
>
> ------- You are receiving this mail because: -------
> You reported the bug, or are watching the reporter.


-- 


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


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

* [Bug target/29660] get 'internal compiler error' when building numerical recipes
  2006-10-31  1:45 [Bug fortran/29660] New: get 'internal compiler error' when building numerical recipes karlglazebrook at mac dot com
                   ` (2 preceding siblings ...)
  2006-10-31  5:49 ` karlglazebrook at mac dot com
@ 2007-01-09 16:05 ` fxcoudert at gcc dot gnu dot org
  2007-01-24 12:05 ` fxcoudert at gcc dot gnu dot org
  2008-02-21 18:45 ` fxcoudert at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2007-01-09 16:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from fxcoudert at gcc dot gnu dot org  2007-01-09 16:05 -------
Works for me on i386-darwin with gfortran 4.3.0 20070109 (experimental).


-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
      Known to work|                            |4.3.0


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


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

* [Bug target/29660] get 'internal compiler error' when building numerical recipes
  2006-10-31  1:45 [Bug fortran/29660] New: get 'internal compiler error' when building numerical recipes karlglazebrook at mac dot com
                   ` (3 preceding siblings ...)
  2007-01-09 16:05 ` fxcoudert at gcc dot gnu dot org
@ 2007-01-24 12:05 ` fxcoudert at gcc dot gnu dot org
  2008-02-21 18:45 ` fxcoudert at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2007-01-24 12:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from fxcoudert at gcc dot gnu dot org  2007-01-24 12:05 -------
(In reply to comment #3)
> Is it binary compatible with 4.0.1 or will I have to rebuild  
> everything with a libgfortran dependence?

I see noone answered this question, so here I go: there is no binary
compatibility for libgfortran between GCC branches (4.0, 4.1, 4.2, 4.3). The
library versions are different each time, so you should be able to have
different libraries linked to different libgfortrans (I use that on a regular
basis).


-- 


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


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

* [Bug target/29660] get 'internal compiler error' when building numerical recipes
  2006-10-31  1:45 [Bug fortran/29660] New: get 'internal compiler error' when building numerical recipes karlglazebrook at mac dot com
                   ` (4 preceding siblings ...)
  2007-01-24 12:05 ` fxcoudert at gcc dot gnu dot org
@ 2008-02-21 18:45 ` fxcoudert at gcc dot gnu dot org
  5 siblings, 0 replies; 7+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2008-02-21 18:45 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from fxcoudert at gcc dot gnu dot org  2008-02-21 18:44 -------
gfortran-4.0.1 is really old, this code works fine for 4.3.0 so I suggest we
close it as WONTFIX. Please reopen if you can reproduce this with a more recent
compiler.

Thanks for the bug report.


-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |fxcoudert at gcc dot gnu dot
                   |                            |org
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |WONTFIX
   Target Milestone|---                         |4.3.0


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


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

end of thread, other threads:[~2008-02-21 18:45 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2006-10-31  1:45 [Bug fortran/29660] New: get 'internal compiler error' when building numerical recipes karlglazebrook at mac dot com
2006-10-31  1:51 ` [Bug target/29660] " pinskia at gcc dot gnu dot org
2006-10-31  4:46 ` kargl at gcc dot gnu dot org
2006-10-31  5:49 ` karlglazebrook at mac dot com
2007-01-09 16:05 ` fxcoudert at gcc dot gnu dot org
2007-01-24 12:05 ` fxcoudert at gcc dot gnu dot org
2008-02-21 18:45 ` fxcoudert at gcc dot gnu dot org

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