OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [graphite/] [pr45758.f90] - Blame information for rev 801

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-options "-O3 -floop-block" }
2
 
3
MODULE util
4
  INTEGER, PARAMETER :: int_4=4
5
  INTERFACE sort
6
     MODULE PROCEDURE sort_int_4v
7
  END INTERFACE
8
CONTAINS
9
  SUBROUTINE sort_int_4v ( arr, n, index )
10
    INTEGER(KIND=int_4), INTENT(INOUT)       :: arr(1:n)
11
    INTEGER, INTENT(OUT)                     :: INDEX(1:n)
12
    DO i = 1, n
13
       INDEX(i) = i
14
    END DO
15
1   IF (ir-l
16
       DO j = l + 1, ir
17
          DO i = j - 1, 1, -1
18
             IF (arr(i)<=a) GO TO 2
19
             arr(i+1) = arr(i)
20
             INDEX(i+1) = INDEX(i)
21
          END DO
22
2         arr(i+1) = a
23
       END DO
24
    END IF
25
  END SUBROUTINE sort_int_4v
26
  SUBROUTINE create_destination_list(list)
27
    INTEGER, DIMENSION(:, :, :), POINTER     :: list
28
    INTEGER                                  ::  icpu, ncpu, stat, ultimate_max
29
    INTEGER, ALLOCATABLE, DIMENSION(:)       :: index, sublist
30
    ultimate_max=7
31
    ALLOCATE(INDEX(ultimate_max),STAT=stat)
32
    CALL t(stat==0)
33
    ALLOCATE(sublist(ultimate_max),STAT=stat)
34
    DO icpu=0,ncpu-1
35
       CALL sort(sublist,ultimate_max,index)
36
       list(1,:,icpu)=sublist
37
       list(2,:,icpu)=0
38
    ENDDO
39
  END SUBROUTINE create_destination_list
40
END MODULE
41
! { dg-final { cleanup-modules "util" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.