public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage
@ 2012-07-04 11:19 Joost.VandeVondele at mat dot ethz.ch
  2012-07-04 11:54 ` [Bug middle-end/53852] " rguenth at gcc dot gnu.org
                   ` (21 more replies)
  0 siblings, 22 replies; 23+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2012-07-04 11:19 UTC (permalink / raw)
  To: gcc-bugs

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

             Bug #: 53852
           Summary: -ftree-loop-linear: large compile time / memory usage
    Classification: Unclassified
           Product: gcc
           Version: 4.8.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: middle-end
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: Joost.VandeVondele@mat.ethz.ch


Current trunk (189233) has >X Gb of memory usage (before I have to kill the
compilation) on the following testcase with:

gfortran -O2 -ftree-loop-linear test.f90

  SUBROUTINE  build_d_tensor_gks(d1f, d2f, d3f, d4f, d5f, v, d1, d2, d3, d4,
d5)
    INTEGER, PARAMETER :: dp=8
    REAL(KIND=dp), DIMENSION(3), INTENT(OUT) :: d1f
    REAL(KIND=dp), DIMENSION(3, 3), &
      INTENT(OUT)                            :: d2f
    REAL(KIND=dp), DIMENSION(3, 3, 3), &
      INTENT(OUT)                            :: d3f
    REAL(KIND=dp), DIMENSION(3, 3, 3, 3), &
      INTENT(OUT)                            :: d4f
    REAL(KIND=dp), &
      DIMENSION(3, 3, 3, 3, 3), &
      INTENT(OUT), OPTIONAL                  :: d5f
    REAL(KIND=dp), DIMENSION(3), INTENT(IN)  :: v
    REAL(KIND=dp), INTENT(IN)                :: d1, d2, d3, d4
    REAL(KIND=dp), INTENT(IN), OPTIONAL      :: d5

    INTEGER                                  :: k1, k2, k3, k4, k5
    REAL(KIND=dp)                            :: w

    d1f = 0.0_dp
    d2f = 0.0_dp
    d3f = 0.0_dp
    d4f = 0.0_dp
    DO k1=1,3
       d1f(k1)=d1f(k1)+v(k1)*d1
    ENDDO
    DO k1=1,3
       DO k2=1,3
          d2f(k2,k1)=d2f(k2,k1)+v(k1)*v(k2)*d2
       ENDDO
       d2f(k1,k1)=d2f(k1,k1)+ d1
    ENDDO
    DO k1=1,3
       DO k2=1,3
          DO k3=1,3
             d3f(k3,k2,k1)=d3f(k3,k2,k1)+v(k1)*v(k2)*v(k3)*d3
          ENDDO
          w=v(k1)*d2
          d3f(k1,k2,k2)=d3f(k1,k2,k2)+w
          d3f(k2,k1,k2)=d3f(k2,k1,k2)+w
          d3f(k2,k2,k1)=d3f(k2,k2,k1)+w
       ENDDO
    ENDDO
    DO k1=1,3
       DO k2=1,3
          DO k3=1,3
             DO k4=1,3
                d4f(k4,k3,k2,k1)=d4f(k4,k3,k2,k1)+ &
                        v(k1)*v(k2)*v(k3)*v(k4)*d4
             ENDDO
             w=v(k1)*v(k2)*d3
             d4f(k1,k2,k3,k3)=d4f(k1,k2,k3,k3)+w
             d4f(k1,k3,k2,k3)=d4f(k1,k3,k2,k3)+w
             d4f(k3,k1,k2,k3)=d4f(k3,k1,k2,k3)+w
             d4f(k1,k3,k3,k2)=d4f(k1,k3,k3,k2)+w
             d4f(k3,k1,k3,k2)=d4f(k3,k1,k3,k2)+w
             d4f(k3,k3,k1,k2)=d4f(k3,k3,k1,k2)+w
          ENDDO
          d4f(k1,k1,k2,k2)=d4f(k1,k1,k2,k2)+d2
          d4f(k1,k2,k1,k2)=d4f(k1,k2,k1,k2)+d2
          d4f(k1,k2,k2,k1)=d4f(k1,k2,k2,k1)+d2
       ENDDO
    ENDDO
    IF (PRESENT(d5f).AND.PRESENT(d5)) THEN
       d5f = 0.0_dp

       DO k1=1,3
          DO k2=1,3
             DO k3=1,3
                DO k4=1,3
                   DO k5=1,3
                      d5f(k5,k4,k3,k2,k1)=d5f(k5,k4,k3,k2,k1)+ &
                             v(k1)*v(k2)*v(k3)*v(k4)*v(k5)*d5
                   ENDDO
                   w=v(k1)*v(k2)*v(k3)*d4
                   d5f(k1,k2,k3,k4,k4)=d5f(k1,k2,k3,k4,k4)+w
                   d5f(k1,k2,k4,k3,k4)=d5f(k1,k2,k4,k3,k4)+w
                   d5f(k1,k4,k2,k3,k4)=d5f(k1,k4,k2,k3,k4)+w
                   d5f(k4,k1,k2,k3,k4)=d5f(k4,k1,k2,k3,k4)+w
                   d5f(k1,k2,k4,k4,k3)=d5f(k1,k2,k4,k4,k3)+w
                   d5f(k1,k4,k2,k4,k3)=d5f(k1,k4,k2,k4,k3)+w
                   d5f(k4,k1,k2,k4,k3)=d5f(k4,k1,k2,k4,k3)+w
                   d5f(k1,k4,k4,k2,k3)=d5f(k1,k4,k4,k2,k3)+w
                   d5f(k4,k1,k4,k2,k3)=d5f(k4,k1,k4,k2,k3)+w
                   d5f(k4,k4,k1,k2,k3)=d5f(k4,k4,k1,k2,k3)+w
                ENDDO
                w=v(k1)*d3
                d5f(k1,k2,k2,k3,k3)=d5f(k1,k2,k2,k3,k3)+w
                d5f(k1,k2,k3,k2,k3)=d5f(k1,k2,k3,k2,k3)+w
                d5f(k1,k2,k3,k3,k2)=d5f(k1,k2,k3,k3,k2)+w
                d5f(k2,k1,k2,k3,k3)=d5f(k2,k1,k2,k3,k3)+w
                d5f(k2,k1,k3,k2,k3)=d5f(k2,k1,k3,k2,k3)+w
                d5f(k2,k1,k3,k3,k2)=d5f(k2,k1,k3,k3,k2)+w
                d5f(k2,k2,k1,k3,k3)=d5f(k2,k2,k1,k3,k3)+w
                d5f(k2,k3,k1,k2,k3)=d5f(k2,k3,k1,k2,k3)+w
                d5f(k2,k3,k1,k3,k2)=d5f(k2,k3,k1,k3,k2)+w
                d5f(k2,k2,k3,k1,k3)=d5f(k2,k2,k3,k1,k3)+w
                d5f(k2,k3,k2,k1,k3)=d5f(k2,k3,k2,k1,k3)+w
                d5f(k2,k3,k3,k1,k2)=d5f(k2,k3,k3,k1,k2)+w
                d5f(k2,k2,k3,k3,k1)=d5f(k2,k2,k3,k3,k1)+w
                d5f(k2,k3,k2,k3,k1)=d5f(k2,k3,k2,k3,k1)+w
                d5f(k2,k3,k3,k2,k1)=d5f(k2,k3,k3,k2,k1)+w
             ENDDO
          ENDDO
       ENDDO
    END IF
  END SUBROUTINE build_d_tensor_gks


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

* [Bug middle-end/53852] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
@ 2012-07-04 11:54 ` rguenth at gcc dot gnu.org
  2012-07-04 12:11 ` matz at gcc dot gnu.org
                   ` (20 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu.org @ 2012-07-04 11:54 UTC (permalink / raw)
  To: gcc-bugs

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

Richard Guenther <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|                            |compile-time-hog,
                   |                            |memory-hog
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2012-07-04
                 CC|                            |matz at gcc dot gnu.org,
                   |                            |rguenth at gcc dot gnu.org
     Ever Confirmed|0                           |1

--- Comment #1 from Richard Guenther <rguenth at gcc dot gnu.org> 2012-07-04 11:54:42 UTC ---
From

#20 0x00000000012171c0 in compute_deps (scop=0x1f16e50, pbbs=0x1fa6d70, 
    must_raw=0x1f16e90, may_raw=0x1f16e98, must_raw_no_source=0x1f16ea0, 
    may_raw_no_source=0x1f16ea8, must_war=0x1f16eb0, may_war=0x1f16eb8, 
    must_war_no_source=0x1f16ec0, may_war_no_source=0x1f16ec8, 
    must_waw=0x1f16ed0, may_waw=0x1f16ed8, must_waw_no_source=0x1f16ee0, 
    may_waw_no_source=0x1f16ee8)
    at /space/rguenther/src/svn/trunk/gcc/graphite-dependences.c:471
471       res = isl_union_map_compute_flow (isl_union_map_copy (reads),

we do not finish without allocating much much memory.

from inside ISL it's compute_val_based_dependences that takes that much
memory and compile-time.


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

* [Bug middle-end/53852] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
  2012-07-04 11:54 ` [Bug middle-end/53852] " rguenth at gcc dot gnu.org
@ 2012-07-04 12:11 ` matz at gcc dot gnu.org
  2012-07-04 12:18 ` Joost.VandeVondele at mat dot ethz.ch
                   ` (19 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: matz at gcc dot gnu.org @ 2012-07-04 12:11 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Michael Matz <matz at gcc dot gnu.org> 2012-07-04 12:11:10 UTC ---
ISL generally has speed problems.  For instance graphite/interchange-8.c
needs quite long to compile (well, several seconds), and _all_ of the runtime
is basically in malloc/free/copy activity of isl_int's.  It does 10 million
calls to malloc/free, 51 million to gmpz_set, 15 million to gmpz_addmul,
9 million to gmpz_mul, 51 million gmpn_copi, and so on.

Huge causes for this excessive gmp activity is compute_deps ->
isl_union_map_compute_flow.  Three calls of the latter are responsible
for 76% compile time, and it's all in gmp activity.  It's then
doing 16x isl_access_info_compute_flow, 210x isl_map_partial_lexmax,
307x isl_map_apply_range and isl_map_intersect, which do 10000x 
isl_basic_map_intersect and 7400x isl_basic_map_apply_range.  That causes
25000x isl_basic_map_simplify and 61000x isl_basic_map_alloc_space.
That results in 82000x isl_blk_alloc, which ultimately does the excessive
number of malloc and gmp_init calls.  And it results in several million
calls to the simplify primitives
(isl_seq_elim->isl_seq_combine->gmp_addmul/mul/set, isl_seq_copy, and
isl_seq_abs_min_non_zero).


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

* [Bug middle-end/53852] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
  2012-07-04 11:54 ` [Bug middle-end/53852] " rguenth at gcc dot gnu.org
  2012-07-04 12:11 ` matz at gcc dot gnu.org
@ 2012-07-04 12:18 ` Joost.VandeVondele at mat dot ethz.ch
  2012-07-04 12:44 ` [Bug tree-optimization/53852] [4.8 Regression] " rguenth at gcc dot gnu.org
                   ` (18 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2012-07-04 12:18 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> 2012-07-04 12:17:47 UTC ---
To fill in the X, 130 Gb is not sufficient for this testcase.


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

* [Bug tree-optimization/53852] [4.8 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (2 preceding siblings ...)
  2012-07-04 12:18 ` Joost.VandeVondele at mat dot ethz.ch
@ 2012-07-04 12:44 ` rguenth at gcc dot gnu.org
  2012-08-22 11:58 ` Joost.VandeVondele at mat dot ethz.ch
                   ` (17 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu.org @ 2012-07-04 12:44 UTC (permalink / raw)
  To: gcc-bugs

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

Richard Guenther <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
          Component|middle-end                  |tree-optimization
      Known to work|                            |4.7.1
   Target Milestone|---                         |4.8.0
            Summary|-ftree-loop-linear: large   |[4.8 Regression]
                   |compile time / memory usage |-ftree-loop-linear: large
                   |                            |compile time / memory usage

--- Comment #4 from Richard Guenther <rguenth at gcc dot gnu.org> 2012-07-04 12:43:48 UTC ---
4.7 compiles this quickly and without too much memory.


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

* [Bug tree-optimization/53852] [4.8 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (3 preceding siblings ...)
  2012-07-04 12:44 ` [Bug tree-optimization/53852] [4.8 Regression] " rguenth at gcc dot gnu.org
@ 2012-08-22 11:58 ` Joost.VandeVondele at mat dot ethz.ch
  2012-12-06 16:25 ` rguenth at gcc dot gnu.org
                   ` (16 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2012-08-22 11:58 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> 2012-08-22 11:58:00 UTC ---
simplified testcase and some analysis:

SUBROUTINE  build_d_tensor_gks(d5f,v,d5)
    INTEGER, PARAMETER :: dp=8
    REAL(KIND=dp),  DIMENSION(3, 3, 3, 3, 3), &
      INTENT(OUT) :: d5f
    REAL(KIND=dp), DIMENSION(3), INTENT(IN)  :: v
    REAL(KIND=dp), INTENT(IN) :: d5
    INTEGER       :: k1, k2, k3, k4, k5
    REAL(KIND=dp) :: w

    d5f = 0.0_dp
    DO k1=1,3
       DO k2=1,3
          DO k3=1,3
             DO k4=1,3
                DO k5=1,3
                   d5f(k5,k4,k3,k2,k1)=d5f(k5,k4,k3,k2,k1)+ &
                          v(k1)*v(k2)*v(k3)*v(k4)*v(k5)*d5
                ENDDO
                w=v(k1)*v(k2)*v(k3)*d4
                d5f(k1,k2,k3,k4,k4)=d5f(k1,k2,k3,k4,k4)+w
                d5f(k1,k2,k4,k3,k4)=d5f(k1,k2,k4,k3,k4)+w
                d5f(k1,k4,k2,k3,k4)=d5f(k1,k4,k2,k3,k4)+w
                d5f(k4,k1,k2,k3,k4)=d5f(k4,k1,k2,k3,k4)+w
                d5f(k1,k2,k4,k4,k3)=d5f(k1,k2,k4,k4,k3)+w
             !  d5f(k1,k4,k2,k4,k3)=d5f(k1,k4,k2,k4,k3)+w
             !  d5f(k4,k1,k2,k4,k3)=d5f(k4,k1,k2,k4,k3)+w
             !  d5f(k1,k4,k4,k2,k3)=d5f(k1,k4,k4,k2,k3)+w
             !  d5f(k4,k1,k4,k2,k3)=d5f(k4,k1,k4,k2,k3)+w
             !  d5f(k4,k4,k1,k2,k3)=d5f(k4,k4,k1,k2,k3)+w
             ENDDO
          ENDDO
       ENDDO
    ENDDO
  END SUBROUTINE build_d_tensor_gks


the issue is that the compile time grows exponentially in the number of
uncommented lines of the d5f=d5f+w type:

1 0m1.112s
2 0m4.448s
3 0m11.513s
4 0m21.514s
5 0m35.529s


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

* [Bug tree-optimization/53852] [4.8 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (4 preceding siblings ...)
  2012-08-22 11:58 ` Joost.VandeVondele at mat dot ethz.ch
@ 2012-12-06 16:25 ` rguenth at gcc dot gnu.org
  2012-12-13 13:00 ` rguenth at gcc dot gnu.org
                   ` (15 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu.org @ 2012-12-06 16:25 UTC (permalink / raw)
  To: gcc-bugs


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

Richard Biener <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P3                          |P1


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

* [Bug tree-optimization/53852] [4.8 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (5 preceding siblings ...)
  2012-12-06 16:25 ` rguenth at gcc dot gnu.org
@ 2012-12-13 13:00 ` rguenth at gcc dot gnu.org
  2013-02-07  9:05 ` Joost.VandeVondele at mat dot ethz.ch
                   ` (14 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu.org @ 2012-12-13 13:00 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #6 from Richard Biener <rguenth at gcc dot gnu.org> 2012-12-13 12:59:45 UTC ---
Sven suggests sth like:

Index: gcc/graphite-dependences.c
===================================================================
--- gcc/graphite-dependences.c  (revision 194472)
+++ gcc/graphite-dependences.c  (working copy)
@@ -461,13 +461,16 @@ compute_deps (scop_p scop, vec<poly_bb_p
   isl_union_map *reads = scop_get_reads (scop, pbbs);
   isl_union_map *must_writes = scop_get_must_writes (scop, pbbs);
   isl_union_map *may_writes = scop_get_may_writes (scop, pbbs);
-  isl_union_map *all_writes = isl_union_map_union
-    (isl_union_map_copy (must_writes), isl_union_map_copy (may_writes));
-  isl_space *space = isl_union_map_get_space (all_writes);
-  isl_union_map *empty = isl_union_map_empty (space);
   isl_union_map *original = scop_get_original_schedule (scop, pbbs);
   int res;

+  reads = isl_union_map_coalesce (reads);
+  must_writes = isl_union_map_coalesce (must_writes);
+  may_writes = isl_union_map_coalesce (may_writes);
+  isl_union_map *all_writes = isl_union_map_union
+    (isl_union_map_copy (must_writes), isl_union_map_copy (may_writes));
+  all_writes = isl_union_map_coalesce (all_writes);
+  original = isl_union_map_coalesce (original);
   res = isl_union_map_compute_flow (isl_union_map_copy (reads),
                                    isl_union_map_copy (must_writes),
                                    isl_union_map_copy (may_writes),
@@ -475,6 +478,8 @@ compute_deps (scop_p scop, vec<poly_bb_p
                                    must_raw, may_raw, must_raw_no_source,
                                    may_raw_no_source);
   gcc_assert (res == 0);
+  isl_space *space = isl_union_map_get_space (all_writes);
+  isl_union_map *empty = isl_union_map_empty (space);
   res = isl_union_map_compute_flow (isl_union_map_copy (all_writes),
                                    reads, empty,
                                    isl_union_map_copy (original),

which for me only shaves a small bit of compile-time from the reduced testcase
(around 10%).


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

* [Bug tree-optimization/53852] [4.8 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (6 preceding siblings ...)
  2012-12-13 13:00 ` rguenth at gcc dot gnu.org
@ 2013-02-07  9:05 ` Joost.VandeVondele at mat dot ethz.ch
  2013-02-19 20:48 ` law at redhat dot com
                   ` (13 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2013-02-07  9:05 UTC (permalink / raw)
  To: gcc-bugs


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

Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |grosser at gcc dot gnu.org

--- Comment #7 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> 2013-02-07 09:04:36 UTC ---
I assume this PR is also a result of the PPL to ISL change ? 

Is there anything in place that could be used to avoid this exponential
complexity ? The pattern in comment #5 seems not too exotic.


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

* [Bug tree-optimization/53852] [4.8 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (7 preceding siblings ...)
  2013-02-07  9:05 ` Joost.VandeVondele at mat dot ethz.ch
@ 2013-02-19 20:48 ` law at redhat dot com
  2013-03-22 14:43 ` [Bug tree-optimization/53852] [4.8/4.9 " jakub at gcc dot gnu.org
                   ` (12 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: law at redhat dot com @ 2013-02-19 20:48 UTC (permalink / raw)
  To: gcc-bugs


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

Jeffrey A. Law <law at redhat dot com> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P1                          |P2
                 CC|                            |law at redhat dot com

--- Comment #8 from Jeffrey A. Law <law at redhat dot com> 2013-02-19 20:47:03 UTC ---
I'm downgrading this to a P2.  Graphite is an optional component and with
somewhat dubious value.  While I hate to see compile-time and memory
consumption problems of this nature, I can't support this PR as being important
enough to be a release blocker.

I took a look to see if there was some reasonable way to throttle the
compile-time and memory consumption, but from what I can tell (with minimal
graphite/ISL knowledge), the sizes of the maps we're passing down to the ISL
code aren't terribly big.  Yet something in the ISL code just goes bananas.


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

* [Bug tree-optimization/53852] [4.8/4.9 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (8 preceding siblings ...)
  2013-02-19 20:48 ` law at redhat dot com
@ 2013-03-22 14:43 ` jakub at gcc dot gnu.org
  2013-05-31 10:58 ` jakub at gcc dot gnu.org
                   ` (11 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-03-22 14:43 UTC (permalink / raw)
  To: gcc-bugs


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

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.8.0                       |4.8.1

--- Comment #9 from Jakub Jelinek <jakub at gcc dot gnu.org> 2013-03-22 14:42:53 UTC ---
GCC 4.8.0 is being released, adjusting target milestone.


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

* [Bug tree-optimization/53852] [4.8/4.9 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (9 preceding siblings ...)
  2013-03-22 14:43 ` [Bug tree-optimization/53852] [4.8/4.9 " jakub at gcc dot gnu.org
@ 2013-05-31 10:58 ` jakub at gcc dot gnu.org
  2013-10-16  9:51 ` jakub at gcc dot gnu.org
                   ` (10 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-05-31 10:58 UTC (permalink / raw)
  To: gcc-bugs

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

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.8.1                       |4.8.2

--- Comment #10 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
GCC 4.8.1 has been released.


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

* [Bug tree-optimization/53852] [4.8/4.9 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (10 preceding siblings ...)
  2013-05-31 10:58 ` jakub at gcc dot gnu.org
@ 2013-10-16  9:51 ` jakub at gcc dot gnu.org
  2014-01-23  7:30 ` law at redhat dot com
                   ` (9 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-10-16  9:51 UTC (permalink / raw)
  To: gcc-bugs

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

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.8.2                       |4.8.3

--- Comment #11 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
GCC 4.8.2 has been released.


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

* [Bug tree-optimization/53852] [4.8/4.9 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (11 preceding siblings ...)
  2013-10-16  9:51 ` jakub at gcc dot gnu.org
@ 2014-01-23  7:30 ` law at redhat dot com
  2014-05-22  9:02 ` [Bug tree-optimization/53852] [4.8/4.9/4.10 " rguenth at gcc dot gnu.org
                   ` (8 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: law at redhat dot com @ 2014-01-23  7:30 UTC (permalink / raw)
  To: gcc-bugs

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

Jeffrey A. Law <law at redhat dot com> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P2                          |P4

--- Comment #12 from Jeffrey A. Law <law at redhat dot com> ---
Pushing this out to P4 as the graphite infrastructure is, effectively,
unmaintained.


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

* [Bug tree-optimization/53852] [4.8/4.9/4.10 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (12 preceding siblings ...)
  2014-01-23  7:30 ` law at redhat dot com
@ 2014-05-22  9:02 ` rguenth at gcc dot gnu.org
  2014-12-19 13:41 ` [Bug tree-optimization/53852] [4.8/4.9/5 " jakub at gcc dot gnu.org
                   ` (7 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu.org @ 2014-05-22  9:02 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

Richard Biener <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.8.3                       |4.8.4

--- Comment #13 from Richard Biener <rguenth at gcc dot gnu.org> ---
GCC 4.8.3 is being released, adjusting target milestone.


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

* [Bug tree-optimization/53852] [4.8/4.9/5 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (13 preceding siblings ...)
  2014-05-22  9:02 ` [Bug tree-optimization/53852] [4.8/4.9/4.10 " rguenth at gcc dot gnu.org
@ 2014-12-19 13:41 ` jakub at gcc dot gnu.org
  2015-06-23  8:23 ` [Bug tree-optimization/53852] [4.8/4.9/5/6 " rguenth at gcc dot gnu.org
                   ` (6 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: jakub at gcc dot gnu.org @ 2014-12-19 13:41 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.8.4                       |4.8.5

--- Comment #14 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
GCC 4.8.4 has been released.


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

* [Bug tree-optimization/53852] [4.8/4.9/5/6 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (14 preceding siblings ...)
  2014-12-19 13:41 ` [Bug tree-optimization/53852] [4.8/4.9/5 " jakub at gcc dot gnu.org
@ 2015-06-23  8:23 ` rguenth at gcc dot gnu.org
  2015-06-26 20:13 ` [Bug tree-optimization/53852] [4.9/5/6 " jakub at gcc dot gnu.org
                   ` (5 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: rguenth at gcc dot gnu.org @ 2015-06-23  8:23 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

Richard Biener <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.8.5                       |4.9.3

--- Comment #15 from Richard Biener <rguenth at gcc dot gnu.org> ---
The gcc-4_8-branch is being closed, re-targeting regressions to 4.9.3.


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

* [Bug tree-optimization/53852] [4.9/5/6 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (15 preceding siblings ...)
  2015-06-23  8:23 ` [Bug tree-optimization/53852] [4.8/4.9/5/6 " rguenth at gcc dot gnu.org
@ 2015-06-26 20:13 ` jakub at gcc dot gnu.org
  2015-06-26 20:37 ` jakub at gcc dot gnu.org
                   ` (4 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: jakub at gcc dot gnu.org @ 2015-06-26 20:13 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

--- Comment #16 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
GCC 4.9.3 has been released.


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

* [Bug tree-optimization/53852] [4.9/5/6 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (16 preceding siblings ...)
  2015-06-26 20:13 ` [Bug tree-optimization/53852] [4.9/5/6 " jakub at gcc dot gnu.org
@ 2015-06-26 20:37 ` jakub at gcc dot gnu.org
  2015-08-28  4:28 ` Joost.VandeVondele at mat dot ethz.ch
                   ` (3 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: jakub at gcc dot gnu.org @ 2015-06-26 20:37 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|4.9.3                       |4.9.4


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

* [Bug tree-optimization/53852] [4.9/5/6 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (17 preceding siblings ...)
  2015-06-26 20:37 ` jakub at gcc dot gnu.org
@ 2015-08-28  4:28 ` Joost.VandeVondele at mat dot ethz.ch
  2015-08-28 14:29 ` spop at gcc dot gnu.org
                   ` (2 subsequent siblings)
  21 siblings, 0 replies; 23+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2015-08-28  4:28 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Last reconfirmed|2013-02-03 00:00:00         |2015-8-28
                 CC|                            |spop at gcc dot gnu.org
      Known to fail|                            |6.0

--- Comment #17 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> ---
since today on trunk this also triggers for options such as -floop-block, which
didn't trigger this before.


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

* [Bug tree-optimization/53852] [4.9/5/6 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (18 preceding siblings ...)
  2015-08-28  4:28 ` Joost.VandeVondele at mat dot ethz.ch
@ 2015-08-28 14:29 ` spop at gcc dot gnu.org
  2015-09-02 22:38 ` spop at gcc dot gnu.org
  2015-09-09  4:23 ` spop at gcc dot gnu.org
  21 siblings, 0 replies; 23+ messages in thread
From: spop at gcc dot gnu.org @ 2015-08-28 14:29 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

--- Comment #18 from Sebastian Pop <spop at gcc dot gnu.org> ---
(In reply to Joost VandeVondele from comment #17)
> since today on trunk this also triggers for options such as -floop-block,
> which didn't trigger this before.

Because as of yesterday both -ftree-loop-linear and -floop-block are aliases of
-floop-nest-optimize, that triggers the ISL scheduler.
I will have a look at the compile time and memory usage of this testcase.
Thanks for the heads'up.


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

* [Bug tree-optimization/53852] [4.9/5/6 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (19 preceding siblings ...)
  2015-08-28 14:29 ` spop at gcc dot gnu.org
@ 2015-09-02 22:38 ` spop at gcc dot gnu.org
  2015-09-09  4:23 ` spop at gcc dot gnu.org
  21 siblings, 0 replies; 23+ messages in thread
From: spop at gcc dot gnu.org @ 2015-09-02 22:38 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

--- Comment #19 from Sebastian Pop <spop at gcc dot gnu.org> ---
Patch fixing the compile time problem with at least isl-0.15:
https://gcc.gnu.org/ml/gcc-patches/2015-09/msg00198.html

isl-0.12 does not support the compute-out mechanism.


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

* [Bug tree-optimization/53852] [4.9/5/6 Regression] -ftree-loop-linear: large compile time / memory usage
  2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
                   ` (20 preceding siblings ...)
  2015-09-02 22:38 ` spop at gcc dot gnu.org
@ 2015-09-09  4:23 ` spop at gcc dot gnu.org
  21 siblings, 0 replies; 23+ messages in thread
From: spop at gcc dot gnu.org @ 2015-09-09  4:23 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=53852

Sebastian Pop <spop at gcc dot gnu.org> changed:

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

--- Comment #20 from Sebastian Pop <spop at gcc dot gnu.org> ---
Fixed in r227572.


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

end of thread, other threads:[~2015-09-09  4:23 UTC | newest]

Thread overview: 23+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2012-07-04 11:19 [Bug middle-end/53852] New: -ftree-loop-linear: large compile time / memory usage Joost.VandeVondele at mat dot ethz.ch
2012-07-04 11:54 ` [Bug middle-end/53852] " rguenth at gcc dot gnu.org
2012-07-04 12:11 ` matz at gcc dot gnu.org
2012-07-04 12:18 ` Joost.VandeVondele at mat dot ethz.ch
2012-07-04 12:44 ` [Bug tree-optimization/53852] [4.8 Regression] " rguenth at gcc dot gnu.org
2012-08-22 11:58 ` Joost.VandeVondele at mat dot ethz.ch
2012-12-06 16:25 ` rguenth at gcc dot gnu.org
2012-12-13 13:00 ` rguenth at gcc dot gnu.org
2013-02-07  9:05 ` Joost.VandeVondele at mat dot ethz.ch
2013-02-19 20:48 ` law at redhat dot com
2013-03-22 14:43 ` [Bug tree-optimization/53852] [4.8/4.9 " jakub at gcc dot gnu.org
2013-05-31 10:58 ` jakub at gcc dot gnu.org
2013-10-16  9:51 ` jakub at gcc dot gnu.org
2014-01-23  7:30 ` law at redhat dot com
2014-05-22  9:02 ` [Bug tree-optimization/53852] [4.8/4.9/4.10 " rguenth at gcc dot gnu.org
2014-12-19 13:41 ` [Bug tree-optimization/53852] [4.8/4.9/5 " jakub at gcc dot gnu.org
2015-06-23  8:23 ` [Bug tree-optimization/53852] [4.8/4.9/5/6 " rguenth at gcc dot gnu.org
2015-06-26 20:13 ` [Bug tree-optimization/53852] [4.9/5/6 " jakub at gcc dot gnu.org
2015-06-26 20:37 ` jakub at gcc dot gnu.org
2015-08-28  4:28 ` Joost.VandeVondele at mat dot ethz.ch
2015-08-28 14:29 ` spop at gcc dot gnu.org
2015-09-02 22:38 ` spop at gcc dot gnu.org
2015-09-09  4:23 ` spop at gcc dot gnu.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).