| <- HREF="index.html" PREV | Index | Next -> |
NHSE ReviewTM: Comments · Archive · Search


XL High Performance Fortran for AIX, Version 01.01.0000.0000 --- sum_prog_2.f 12/31/96 19:47:31
 
>>>>> OPTIONS SECTION <<<<< HPF(PURECOMM,COMMONINIT) TYPE="=" FREE(F90) REALSIZE(4) SPILLSIZE(512)="=" INTSIZE(4) OPTIONS AUTODBL(NONE) CHARACTER HALT(S) INTEGER FLAG(L,L) ALIAS(STD,NOINTPTR) MAXMEM(-1) REPORT(HOTLIST,HPFLIST) OFF ZEROSIZE="=" HOT() I4 XFLAG() XLF77(LEADZERO,BLANKPAD) NOSAVE EFFECT / IEEE(NEAR) ESCAPE FLOAT(MAF,FOLD,RSQRT,FLTINT) DIRECTIVE(IBM*) OF OPTIMIZE(3) NOSTRICT IN OBJECT LANGLVL(90EXT) ON ***="=">>>>> SOURCE SECTION <<<<< ** SUM_PROG="=End" 1="=" OF COMPILATION>>>>> PARALLELIZATION AND LOOP TRANSFORMATION SECTION <<<<< PARALLELIZATION A1 1585-102 PROGRAM REPORT HPF POINTER !="" INTEGER*4 SUM_PROG :: SUM_PROG() ***> a1_35
         real*4 :: a1_35(:,:)
       pointer :: a2    ! => a2_36
         real*4 :: a2_36(:,:)
       real*4 :: s
       integer*4 :: #ALLOCATEMP
       integer*4 :: SSA_STACK_5
       integer*4 :: i_9
       integer*4 :: i_10
       integer*4 :: i_11
       integer*4 :: i_12
       integer*4 :: i_13
       save, integer*4 :: PGB_14(1:2)
       save, integer*4 :: PID_15(1:2)
       save, integer*4 :: PG_16
       integer*4 :: B_17(1:4)
       save, integer*4 :: D_18(1:4)
       integer*4 :: iown_l_19
       integer*4 :: iown_u_20
       integer*4 :: iown_l_21
       integer*4 :: iown_u_22
       integer*4 :: Ax_23(1:2)
       integer*4 :: A_24(1:6)
       save, integer*4 :: init_flag_25
       integer*4 :: SSA_STACK_26
       integer*4 :: SSA_STACK_27
       integer*4 :: msg_28
       real*4 :: SCALAR_29
       integer*4 :: Recv_index_32(1:2)
       integer*4 :: Send_index_33(1:2)
       integer*4 :: DS_SAS_34(1:90)
       external :: sum_prog
         integer*4 :: sum_prog
       external :: __sum
         real*4 :: __sum
       external :: __ldatemp
         integer*4 :: __ldatemp
       external :: __supplyoptarg
         integer*4 :: __supplyoptarg
       external :: __trap
       external :: use_it
       external :: _xlhpfExit
       external :: SUM
       external :: SUPPLY_OPT_ARG
       external :: TRAP
       external, integer*4 :: _xlhpf_get_pe_bounds_index
       external :: _xlhpf_allocate
       external :: _xlhpf_deallocate
       external, integer*4 :: MIN0
       external :: _xlhpf_reduce_sum
       #ALLOCATEMP = 0
       if ((init_flag_25 .eq. 0) .ne. 0) then
         PG_16 = _xlhpf_get_pe_bounds_index(2,PGB_14,PID_15)
         D_18(3) = ((40 + PGB_14(2)) - 1) / PGB_14(2)
         D_18(4) = 0
         D_18(1) = ((30 + PGB_14(1)) - 1) / PGB_14(1)
         D_18(2) = 0
         init_flag_25 = 1
       end if
       B_17(3) = 1
       B_17(4) = 40
       B_17(1) = 1
       B_17(2) = 30
       iown_l_19 = 1 + ((40 + PGB_14(2)) - 1) / PGB_14(2) * PID_15(2)
       iown_u_20 = (((40 + PGB_14(2)) - 1) / PGB_14(2) + iown_l_19) - 1
       iown_l_21 = 1 + ((30 + PGB_14(1)) - 1) / PGB_14(1) * PID_15(1)
       iown_u_22 = (((30 + PGB_14(1)) - 1) / PGB_14(1) + iown_l_21) - 1
       Ax_23(2) = 1
       Ax_23(1) = 0
       call _xlhpf_allocate(a1,4,2,9,PG_16,B_17,D_18,%val(0),Ax_23,2)
       A_24(4) = 1
       A_24(5) = 1
       A_24(1) = 1
       A_24(2) = 1
       call _xlhpf_allocate(a2,4,2,9,PG_16,B_17,D_18,A_24,Ax_23,2)
       s = 0.
       SCALAR_29 = 0.
C 1585-501  Original Source Line 6
       do i_9=iown_l_19,MIN0(iown_u_20,40),1
C 1585-501  Original Source Line 6
         do i_10=iown_l_21,MIN0(iown_u_22,30),1
           SCALAR_29 = SCALAR_29 + (a1_35(i_10,i_9) + a2_36(i_10,i_9))
         end do
       end do
C 1585-501  Original Source Line 6
       if ((.true. .and. (1)) .ne. 0) then
         Recv_index_32(1) = (-2)
         Recv_index_32(2) = (-2)
         Send_index_33(1) = 0
         Send_index_33(2) = 1
         DS_SAS_34(1) = 0
         DS_SAS_34(2) = MIN0(29 / D_18(1),PGB_14(1) - 1)
         DS_SAS_34(3) = 1
         DS_SAS_34(4) = 0
         DS_SAS_34(5) = MIN0(39 / D_18(3),PGB_14(2) - 1)
         DS_SAS_34(6) = 1
         call _xlhpf_reduce_sum(9,SCALAR_29,s,PG_16,2,Send_index_33,DS_S
     &AS_34,Recv_index_32)
       end if
       call use_it(s)
       call _xlhpfExit(%val(0))
       TRAP(3)
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       return
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       end

1585-103  *** Loop Transformation Report ***

       program sum_prog()
       integer*4 :: sum_prog
       pointer :: a1    ! => a1_35
         real*4 :: a1_35(:,:)
       pointer :: a2    ! => a2_36
         real*4 :: a2_36(:,:)
       real*4 :: s
       integer*4 :: #ALLOCATEMP
       integer*4 :: SSA_STACK_5
       integer*4 :: i_9
       integer*4 :: i_10
       integer*4 :: i_11
       integer*4 :: i_12
       integer*4 :: i_13
       save, integer*4 :: PGB_14(1:2)
       save, integer*4 :: PID_15(1:2)
       save, integer*4 :: PG_16
       integer*4 :: B_17(1:4)
       save, integer*4 :: D_18(1:4)
       integer*4 :: iown_l_19
       integer*4 :: iown_u_20
       integer*4 :: iown_l_21
       integer*4 :: iown_u_22
       integer*4 :: Ax_23(1:2)
       integer*4 :: A_24(1:6)
       save, integer*4 :: init_flag_25
       integer*4 :: SSA_STACK_26
       integer*4 :: SSA_STACK_27
       integer*4 :: msg_28
       real*4 :: SCALAR_29
       integer*4 :: Recv_index_32(1:2)
       integer*4 :: Send_index_33(1:2)
       integer*4 :: DS_SAS_34(1:90)
       integer*4 :: SSA_STACK_37
       integer*4 :: SSA_STACK_38
       integer*4 :: SSA_STACK_39
       real*8 :: ScRed_40
       real*8 :: ScRed_41
       real*8 :: ScRed_42
       real*8 :: ScRed_43
       external :: sum_prog
         integer*4 :: sum_prog
       external :: __sum
         real*4 :: __sum
       external :: __ldatemp
         integer*4 :: __ldatemp
       external :: __supplyoptarg
         integer*4 :: __supplyoptarg
       external :: __trap
       external :: use_it
       external :: _xlhpfExit
       external :: SUM
       external :: SUPPLY_OPT_ARG
       external :: TRAP
       external, integer*4 :: _xlhpf_get_pe_bounds_index
       external :: _xlhpf_allocate
       external :: _xlhpf_deallocate
       external, integer*4 :: MIN0
       external :: _xlhpf_reduce_sum
       #ALLOCATEMP = 0
       if ((init_flag_25 .eq. 0) .ne. 0) then
         PG_16 = _xlhpf_get_pe_bounds_index(2,PGB_14,PID_15)
         D_18(3) = ((40 + PGB_14(2)) - 1) / PGB_14(2)
         D_18(4) = 0
         D_18(1) = ((30 + PGB_14(1)) - 1) / PGB_14(1)
         D_18(2) = 0
         init_flag_25 = 1
       end if
       B_17(3) = 1
       B_17(4) = 40
       B_17(1) = 1
       B_17(2) = 30

       iown_l_19 = 1 + ((40 + PGB_14(2)) - 1) / PGB_14(2) * PID_15(2)
       iown_u_20 = (((40 + PGB_14(2)) - 1) / PGB_14(2) + iown_l_19) - 1
       iown_l_21 = 1 + ((30 + PGB_14(1)) - 1) / PGB_14(1) * PID_15(1)
       iown_u_22 = (((30 + PGB_14(1)) - 1) / PGB_14(1) + iown_l_21) - 1
       Ax_23(2) = 1
       Ax_23(1) = 0
       call _xlhpf_allocate(a1,4,2,9,PG_16,B_17,D_18,%val(0),Ax_23,2)
       A_24(4) = 1
       A_24(5) = 1
       A_24(1) = 1
       A_24(2) = 1
       call _xlhpf_allocate(a2,4,2,9,PG_16,B_17,D_18,A_24,Ax_23,2)

       s = 0.
       SCALAR_29 = 0.
       ScRed_40 = dble(SCALAR_29)
       ScRed_41 = dble(0)
       ScRed_42 = dble(0)
       ScRed_43 = dble(0)
C 1585-501  Original Source Line 6
       do i_9=iown_l_19,MIN0(iown_u_20,40),1
C 1585-501  Original Source Line 6
         do i_10=iown_l_21,MIN0(iown_u_22,30) - 3,4
           ScRed_40 = ScRed_40 + dble(a1_35(i_10,i_9) + a2_36(i_10,i_9))
     &
           ScRed_41 = ScRed_41 + dble(a1_35(i_10 + 1,i_9) + a2_36(i_10 +
     & 1,i_9))
           ScRed_42 = ScRed_42 + dble(a1_35(i_10 + 2,i_9) + a2_36(i_10 +
     & 2,i_9))
           ScRed_43 = ScRed_43 + dble(a1_35(i_10 + 3,i_9) + a2_36(i_10 +
     & 3,i_9))
         end do
C 1585-501  Original Source Line 6
         do i_10=i_10,MIN0(iown_u_22,30),1
           ScRed_40 = ScRed_40 + dble(a1_35(i_10,i_9) + a2_36(i_10,i_9))
     &
         end do
       end do
       SCALAR_29 = real(ScRed_40 + ScRed_41 + ScRed_42 + ScRed_43)
       Recv_index_32(1) = (-2)
       Recv_index_32(2) = (-2)
       Send_index_33(1) = 0
       Send_index_33(2) = 1
       DS_SAS_34(1) = 0
       DS_SAS_34(2) = MIN0(29 / D_18(1),PGB_14(1) - 1)
       DS_SAS_34(3) = 1
       DS_SAS_34(4) = 0
       DS_SAS_34(5) = MIN0(39 / D_18(3),PGB_14(2) - 1)
       DS_SAS_34(6) = 1
       call _xlhpf_reduce_sum(9,SCALAR_29,s,PG_16,2,Send_index_33,DS_SAS
     &_34,Recv_index_32)

       call use_it(s)
       call _xlhpfExit(%val(0))
       TRAP(3)
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       return
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       end


 
>>>>> FILE TABLE SECTION <<<<< TIME SUM_PROG_2.F FROM 12/31/96 NO DATE FILE FILENAME LINE 19:36:53 0 CREATION>>>>> COMPILATION EPILOGUE SECTION <<<<< 10 TOTAL (S) (U) FOR (W) UNRECOVERABLE DIAGNOSED 1501-543 RECORDS INFORMATIONAL CONDITIONS FORTRAN SUM_PROG_2.F. SUCCESSFUL FILE CREATED. SEVERE ERROR 1501-510 SUMMARY 0 SOURCE 

| <- HREF="index.html" PREV | Index | Next -> |
NHSE ReviewTM: Comments · Archive · Search


presberg@tc.cornell.edu
Last modified: Fri Jan 31 1997