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


XL High Performance Fortran for AIX, Version 01.01.0000.0000 --- two_triples.f 12/31/96 19:28:34
 
>>>>> 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 <<<<< ** TWO_TRIPLES="=End" 1="=" OF COMPILATION>>>>> PARALLELIZATION AND LOOP TRANSFORMATION SECTION <<<<< PARALLELIZATION A1 1585-102 PROGRAM REPORT TWO_TRIPLES HPF POINTER !="" INTEGER*4 TWO_TRIPLES() :: ***> a1_45
         real*4 :: a1_45(:,:)
       pointer :: a2    ! => a2_46
         real*4 :: a2_46(:,:)
       pointer :: b1    ! => b1_47
         real*4 :: b1_47(:,:)
       pointer :: b2    ! => b2_48
         real*4 :: b2_48(:,:)
       integer*4 :: #ALLOCATEMP
       integer*4 :: SSA_STACK_1
       integer*4 :: i_5
       integer*4 :: i_6
       integer*4 :: i_7
       integer*4 :: i_8
       integer*4 :: i_9
       save, integer*4 :: PGB_10(1:2)
       save, integer*4 :: PID_11(1:2)
       save, integer*4 :: PG_12
       integer*4 :: B_13(1:4)
       save, integer*4 :: D_14(1:4)
       integer*4 :: iown_l_15
       integer*4 :: iown_u_16
       integer*4 :: iown_l_17
       integer*4 :: iown_u_18
       integer*4 :: Ax_19(1:2)
       integer*4 :: A_20(1:6)
       save, integer*4 :: init_flag_21
       integer*4 :: SSA_STACK_22
       integer*4 :: SSA_STACK_23
       integer*4 :: msg_24
       integer*4 :: PS_RAS_29(1:2)
       integer*4 :: DS_SAS_30(1:90)
       integer*4 :: PS_SAS_31(1:2)
       integer*4 :: DS_RAS_32(1:90)
       integer*4 :: PS_RAS_33(1:2)
       integer*4 :: DS_SAS_34(1:90)
       integer*4 :: PS_SAS_35(1:2)
       integer*4 :: DS_RAS_36(1:90)
       integer*4 :: PS_RAS_37(1:2)
       integer*4 :: DS_SAS_38(1:90)
       integer*4 :: PS_SAS_39(1:2)
       integer*4 :: DS_RAS_40(1:90)
       integer*4 :: PS_RAS_41(1:2)
       integer*4 :: DS_SAS_42(1:90)
       integer*4 :: PS_SAS_43(1:2)
       integer*4 :: DS_RAS_44(1:90)
       external :: two_triples
         integer*4 :: two_triples
       external :: __trap
       external :: init
       external :: use
       external :: _xlhpfExit
       external :: TRAP
       external, integer*4 :: _xlhpf_get_pe_bounds_index
       external :: _xlhpf_allocate
       external :: _xlhpf_deallocate
       external, integer*4 :: MIN0
       external, integer*4 :: MAX0
       external :: _xlhpf_send_section
       external :: _xlhpf_nbreceive_section
       external :: _xlhpf_waitforall
       #ALLOCATEMP = 0
       if ((init_flag_21 .eq. 0) .ne. 0) then
         PG_12 = _xlhpf_get_pe_bounds_index(2,PGB_10,PID_11)
         D_14(3) = ((40 + PGB_10(2)) - 1) / PGB_10(2)
         D_14(4) = 0
         D_14(1) = ((30 + PGB_10(1)) - 1) / PGB_10(1)
         D_14(2) = 0
         init_flag_21 = 1
       end if
       B_13(3) = 1
       B_13(4) = 40
       B_13(1) = 1
       B_13(2) = 30
       iown_l_15 = 1 + ((40 + PGB_10(2)) - 1) / PGB_10(2) * PID_11(2)
       iown_u_16 = (((40 + PGB_10(2)) - 1) / PGB_10(2) + iown_l_15) - 1
       iown_l_17 = 1 + ((30 + PGB_10(1)) - 1) / PGB_10(1) * PID_11(1)
       iown_u_18 = (((30 + PGB_10(1)) - 1) / PGB_10(1) + iown_l_17) - 1
       Ax_19(2) = 1
       Ax_19(1) = 0
       call _xlhpf_allocate(a1,4,2,9,PG_12,B_13,D_14,%val(0),Ax_19,2)
       A_20(4) = 1
       A_20(5) = 1
       A_20(1) = 1
       A_20(2) = 1
       call _xlhpf_allocate(a2,4,2,9,PG_12,B_13,D_14,A_20,Ax_19,2)
       call _xlhpf_allocate(b1,4,2,9,PG_12,B_13,D_14,A_20,Ax_19,2)
       call _xlhpf_allocate(b2,4,2,9,PG_12,B_13,D_14,A_20,Ax_19,2)
       call init(a1,b1)
C 1585-501  Original Source Line 9
       if ((PID_11(2) .lt. PGB_10(2) - 1) .ne. 0) then
         PS_SAS_31(1) = PID_11(1)
         PS_SAS_31(2) = PID_11(2) - (-1)
         DS_RAS_32(1) = MAX0(1,D_14(1) * PID_11(1) + 1)
         DS_RAS_32(2) = MIN0(MIN0(((1 + D_14(1) * PS_SAS_31(1) + D_14(1)
     &) - 1) - 1,29),MIN0(iown_u_18,29)) + 1
         DS_RAS_32(3) = 1
         DS_RAS_32(4) = MAX0(MAX0((1 + D_14(3) * PS_SAS_31(2)) - 1,1),io
     &wn_l_15) + 1
         DS_RAS_32(5) = MIN0(MIN0(((1 + D_14(3) * PS_SAS_31(2) + D_14(3)
     &) - 1) - 1,39),MIN0(iown_u_16,39)) + 1
         DS_RAS_32(6) = 1
         call _xlhpf_nbreceive_section(a1,2,%val(0),DS_RAS_32,PG_12,PS_S
     &AS_31,msg_24)
       end if
C 1585-501  Original Source Line 9
       if ((PID_11(2) .gt. 0) .ne. 0) then
         PS_RAS_29(1) = PID_11(1)
         PS_RAS_29(2) = PID_11(2) + (-1)
         DS_SAS_30(1) = MAX0(1,D_14(1) * PID_11(1) + 1)
         DS_SAS_30(2) = MIN0(MIN0(iown_u_18 - 1,29),MIN0((1 + D_14(1) * 
     &PS_RAS_29(1) + D_14(1)) - 1,29)) + 1
         DS_SAS_30(3) = 1
         DS_SAS_30(4) = MAX0(MAX0(iown_l_15 - 1,1),1 + D_14(3) * PS_RAS_
     &29(2)) + 1
         DS_SAS_30(5) = MIN0(MIN0(iown_u_16 - 1,39),MIN0((1 + D_14(3) * 
     &PS_RAS_29(2) + D_14(3)) - 1,39)) + 1
         DS_SAS_30(6) = 1
         call _xlhpf_send_section(a1,DS_SAS_30,PG_12,PS_RAS_29,a1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 9
       if ((PID_11(1) .lt. PGB_10(1) - 1) .ne. 0) then
         PS_SAS_35(1) = PID_11(1) - (-1)
         PS_SAS_35(2) = PID_11(2)
         DS_RAS_36(1) = MAX0(MAX0((1 + D_14(1) * PS_SAS_35(1)) - 1,1),io
     &wn_l_17) + 1
         DS_RAS_36(2) = MIN0(MIN0(((1 + D_14(1) * PS_SAS_35(1) + D_14(1)
     &) - 1) - 1,29),MIN0(iown_u_18,29)) + 1
         DS_RAS_36(3) = 1
         DS_RAS_36(4) = MAX0(1,D_14(3) * PID_11(2) + 1)
         DS_RAS_36(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &)) + 2
         DS_RAS_36(6) = 1
         call _xlhpf_nbreceive_section(a1,2,%val(0),DS_RAS_36,PG_12,PS_S
     &AS_35,msg_24)
       end if
C 1585-501  Original Source Line 9
       if ((PID_11(1) .gt. 0) .ne. 0) then
         PS_RAS_33(1) = PID_11(1) + (-1)
         PS_RAS_33(2) = PID_11(2)
         DS_SAS_34(1) = MAX0(MAX0(iown_l_17 - 1,1),1 + D_14(1) * PS_RAS_
     &33(1)) + 1
         DS_SAS_34(2) = MIN0(MIN0(iown_u_18 - 1,29),MIN0((1 + D_14(1) * 
     &PS_RAS_33(1) + D_14(1)) - 1,29)) + 1
         DS_SAS_34(3) = 1
         DS_SAS_34(4) = MAX0(1,D_14(3) * PID_11(2) + 1)
         DS_SAS_34(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &)) + 2
         DS_SAS_34(6) = 1
         call _xlhpf_send_section(a1,DS_SAS_34,PG_12,PS_RAS_33,a1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 9
       do i_5=iown_l_15,MIN0(iown_u_16,39),1
C 1585-501  Original Source Line 9
         do i_6=iown_l_17,MIN0(iown_u_18,29),1
           a2_46(i_6,i_5) = a1_45(i_6 + 1,i_5 + 1)
         end do
       end do
C 1585-501  Original Source Line 10
       if ((PID_11(2) .gt. 0) .ne. 0) then
         PS_SAS_39(1) = PID_11(1)
         PS_SAS_39(2) = PID_11(2) - 1
         DS_RAS_40(1) = MAX0(1 + D_14(1) * PS_SAS_39(1),MAX0(iown_l_17 -
     & 1,1))
         DS_RAS_40(2) = MIN0(30,D_14(1) * PID_11(1) + ((1 + D_14(1)) - 1
     &))
         DS_RAS_40(3) = 1
         DS_RAS_40(4) = MAX0(1 + D_14(3) * PS_SAS_39(2),MAX0(iown_l_15 -
     & 1,1))
         DS_RAS_40(5) = MIN0(MIN0((1 + D_14(3) * PS_SAS_39(2) + D_14(3))
     & - 1,39),MIN0(iown_u_16 - 1,39))
         DS_RAS_40(6) = 1
         call _xlhpf_nbreceive_section(b1,2,%val(0),DS_RAS_40,PG_12,PS_S
     &AS_39,msg_24)
       end if
C 1585-501  Original Source Line 10
       if ((PID_11(2) .lt. PGB_10(2) - 1) .ne. 0) then
         PS_RAS_37(1) = PID_11(1)
         PS_RAS_37(2) = PID_11(2) + 1
         DS_SAS_38(1) = MAX0(iown_l_17,MAX0((1 + D_14(1) * PS_RAS_37(1))
     & - 1,1))
         DS_SAS_38(2) = MIN0(30,D_14(1) * PID_11(1) + ((1 + D_14(1)) - 1
     &))
         DS_SAS_38(3) = 1
         DS_SAS_38(4) = MAX0(iown_l_15,MAX0((1 + D_14(3) * PS_RAS_37(2))
     & - 1,1))
         DS_SAS_38(5) = MIN0(MIN0(iown_u_16,39),MIN0(((1 + D_14(3) * PS_
     &RAS_37(2) + D_14(3)) - 1) - 1,39))
         DS_SAS_38(6) = 1
         call _xlhpf_send_section(b1,DS_SAS_38,PG_12,PS_RAS_37,b1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 10
       if ((PID_11(1) .gt. 0) .ne. 0) then
         PS_SAS_43(1) = PID_11(1) - 1
         PS_SAS_43(2) = PID_11(2)
         DS_RAS_44(1) = MAX0(1 + D_14(1) * PS_SAS_43(1),MAX0(iown_l_17 -
     & 1,1))
         DS_RAS_44(2) = MIN0(MIN0((1 + D_14(1) * PS_SAS_43(1) + D_14(1))
     & - 1,29),MIN0(iown_u_18 - 1,29))
         DS_RAS_44(3) = 1
         DS_RAS_44(4) = MAX0(1,D_14(3) * PID_11(2) + 1) - 2
         DS_RAS_44(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &))
         DS_RAS_44(6) = 1
         call _xlhpf_nbreceive_section(b1,2,%val(0),DS_RAS_44,PG_12,PS_S
     &AS_43,msg_24)
       end if
C 1585-501  Original Source Line 10
       if ((PID_11(1) .lt. PGB_10(1) - 1) .ne. 0) then
         PS_RAS_41(1) = PID_11(1) + 1
         PS_RAS_41(2) = PID_11(2)
         DS_SAS_42(1) = MAX0(iown_l_17,MAX0((1 + D_14(1) * PS_RAS_41(1))
     & - 1,1))
         DS_SAS_42(2) = MIN0(MIN0(iown_u_18,29),MIN0(((1 + D_14(1) * PS_
     &RAS_41(1) + D_14(1)) - 1) - 1,29))
         DS_SAS_42(3) = 1
         DS_SAS_42(4) = MAX0(1,D_14(3) * PID_11(2) + 1) - 2
         DS_SAS_42(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &))
         DS_SAS_42(6) = 1
         call _xlhpf_send_section(b1,DS_SAS_42,PG_12,PS_RAS_41,b1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 10
       do i_5=MAX0(iown_l_15 - 1,1),MIN0(iown_u_16 - 1,39),1
C 1585-501  Original Source Line 10
         do i_6=MAX0(iown_l_17 - 1,1),MIN0(iown_u_18 - 1,29),1
           b2_48(i_6 + 1,i_5 + 1) = b1_47(i_6,i_5)
         end do
       end do
       call use(a2,b2)
       call _xlhpfExit(%val(0))
       TRAP(3)
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       call _xlhpf_deallocate(b1)
       call _xlhpf_deallocate(b2)
       return
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       call _xlhpf_deallocate(b1)
       call _xlhpf_deallocate(b2)
       end

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

       program two_triples()
       integer*4 :: two_triples
       pointer :: a1    ! => a1_45
         real*4 :: a1_45(:,:)
       pointer :: a2    ! => a2_46
         real*4 :: a2_46(:,:)
       pointer :: b1    ! => b1_47
         real*4 :: b1_47(:,:)
       pointer :: b2    ! => b2_48
         real*4 :: b2_48(:,:)
       integer*4 :: #ALLOCATEMP
       integer*4 :: SSA_STACK_1
       integer*4 :: i_5
       integer*4 :: i_6
       integer*4 :: i_7
       integer*4 :: i_8
       integer*4 :: i_9
       save, integer*4 :: PGB_10(1:2)
       save, integer*4 :: PID_11(1:2)
       save, integer*4 :: PG_12
       integer*4 :: B_13(1:4)
       save, integer*4 :: D_14(1:4)
       integer*4 :: iown_l_15
       integer*4 :: iown_u_16
       integer*4 :: iown_l_17
       integer*4 :: iown_u_18
       integer*4 :: Ax_19(1:2)
       integer*4 :: A_20(1:6)
       save, integer*4 :: init_flag_21
       integer*4 :: SSA_STACK_22
       integer*4 :: SSA_STACK_23
       integer*4 :: msg_24
       integer*4 :: PS_RAS_29(1:2)
       integer*4 :: DS_SAS_30(1:90)
       integer*4 :: PS_SAS_31(1:2)
       integer*4 :: DS_RAS_32(1:90)
       integer*4 :: PS_RAS_33(1:2)
       integer*4 :: DS_SAS_34(1:90)
       integer*4 :: PS_SAS_35(1:2)
       integer*4 :: DS_RAS_36(1:90)
       integer*4 :: PS_RAS_37(1:2)
       integer*4 :: DS_SAS_38(1:90)
       integer*4 :: PS_SAS_39(1:2)
       integer*4 :: DS_RAS_40(1:90)
       integer*4 :: PS_RAS_41(1:2)
       integer*4 :: DS_SAS_42(1:90)
       integer*4 :: PS_SAS_43(1:2)
       integer*4 :: DS_RAS_44(1:90)
       integer*4 :: SSA_STACK_49
       external :: two_triples
         integer*4 :: two_triples
       external :: __trap
       external :: init
       external :: use
       external :: _xlhpfExit
       external :: TRAP
       external, integer*4 :: _xlhpf_get_pe_bounds_index
       external :: _xlhpf_allocate
       external :: _xlhpf_deallocate
       external, integer*4 :: MIN0
       external, integer*4 :: MAX0
       external :: _xlhpf_send_section
       external :: _xlhpf_nbreceive_section
       external :: _xlhpf_waitforall
       #ALLOCATEMP = 0
       if ((init_flag_21 .eq. 0) .ne. 0) then
         PG_12 = _xlhpf_get_pe_bounds_index(2,PGB_10,PID_11)
         D_14(3) = ((40 + PGB_10(2)) - 1) / PGB_10(2)
         D_14(4) = 0
         D_14(1) = ((30 + PGB_10(1)) - 1) / PGB_10(1)
         D_14(2) = 0
         init_flag_21 = 1
       end if
       B_13(3) = 1
       B_13(4) = 40
       B_13(1) = 1
       B_13(2) = 30
       iown_l_15 = 1 + ((40 + PGB_10(2)) - 1) / PGB_10(2) * PID_11(2)
       iown_u_16 = (((40 + PGB_10(2)) - 1) / PGB_10(2) + iown_l_15) - 1
       iown_l_17 = 1 + ((30 + PGB_10(1)) - 1) / PGB_10(1) * PID_11(1)
       iown_u_18 = (((30 + PGB_10(1)) - 1) / PGB_10(1) + iown_l_17) - 1
       Ax_19(2) = 1
       Ax_19(1) = 0
       call _xlhpf_allocate(a1,4,2,9,PG_12,B_13,D_14,%val(0),Ax_19,2)
       A_20(4) = 1
       A_20(5) = 1
       A_20(1) = 1
       A_20(2) = 1
       call _xlhpf_allocate(a2,4,2,9,PG_12,B_13,D_14,A_20,Ax_19,2)
       call _xlhpf_allocate(b1,4,2,9,PG_12,B_13,D_14,A_20,Ax_19,2)
       call _xlhpf_allocate(b2,4,2,9,PG_12,B_13,D_14,A_20,Ax_19,2)
       call init(a1,b1)


C 1585-501  Original Source Line 9
       if ((PID_11(2) .lt. PGB_10(2) - 1) .ne. 0) then
         PS_SAS_31(1) = PID_11(1)
         PS_SAS_31(2) = PID_11(2) - (-1)
         DS_RAS_32(1) = MAX0(1,D_14(1) * PID_11(1) + 1)
         DS_RAS_32(2) = MIN0(MIN0(((1 + D_14(1) * PS_SAS_31(1) + D_14(1)
     &) - 1) - 1,29),MIN0(iown_u_18,29)) + 1
         DS_RAS_32(3) = 1
         DS_RAS_32(4) = MAX0(MAX0((1 + D_14(3) * PS_SAS_31(2)) - 1,1),io
     &wn_l_15) + 1
         DS_RAS_32(5) = MIN0(MIN0(((1 + D_14(3) * PS_SAS_31(2) + D_14(3)
     &) - 1) - 1,39),MIN0(iown_u_16,39)) + 1
         DS_RAS_32(6) = 1
         call _xlhpf_nbreceive_section(a1,2,%val(0),DS_RAS_32,PG_12,PS_S
     &AS_31,msg_24)
       end if
C 1585-501  Original Source Line 9
       if ((PID_11(2) .gt. 0) .ne. 0) then
         PS_RAS_29(1) = PID_11(1)
         PS_RAS_29(2) = PID_11(2) + (-1)
         DS_SAS_30(1) = MAX0(1,D_14(1) * PID_11(1) + 1)
         DS_SAS_30(2) = MIN0(MIN0(iown_u_18 - 1,29),MIN0((1 + D_14(1) * 
     &PS_RAS_29(1) + D_14(1)) - 1,29)) + 1
         DS_SAS_30(3) = 1
         DS_SAS_30(4) = MAX0(MAX0(iown_l_15 - 1,1),1 + D_14(3) * PS_RAS_
     &29(2)) + 1
         DS_SAS_30(5) = MIN0(MIN0(iown_u_16 - 1,39),MIN0((1 + D_14(3) * 
     &PS_RAS_29(2) + D_14(3)) - 1,39)) + 1
         DS_SAS_30(6) = 1
         call _xlhpf_send_section(a1,DS_SAS_30,PG_12,PS_RAS_29,a1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 9
       if ((PID_11(1) .lt. PGB_10(1) - 1) .ne. 0) then
         PS_SAS_35(1) = PID_11(1) - (-1)
         PS_SAS_35(2) = PID_11(2)
         DS_RAS_36(1) = MAX0(MAX0((1 + D_14(1) * PS_SAS_35(1)) - 1,1),io
     &wn_l_17) + 1
         DS_RAS_36(2) = MIN0(MIN0(((1 + D_14(1) * PS_SAS_35(1) + D_14(1)
     &) - 1) - 1,29),MIN0(iown_u_18,29)) + 1
         DS_RAS_36(3) = 1
         DS_RAS_36(4) = MAX0(1,D_14(3) * PID_11(2) + 1)
         DS_RAS_36(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &)) + 2
         DS_RAS_36(6) = 1
         call _xlhpf_nbreceive_section(a1,2,%val(0),DS_RAS_36,PG_12,PS_S
     &AS_35,msg_24)
       end if
C 1585-501  Original Source Line 9
       if ((PID_11(1) .gt. 0) .ne. 0) then
         PS_RAS_33(1) = PID_11(1) + (-1)
         PS_RAS_33(2) = PID_11(2)
         DS_SAS_34(1) = MAX0(MAX0(iown_l_17 - 1,1),1 + D_14(1) * PS_RAS_
     &33(1)) + 1
         DS_SAS_34(2) = MIN0(MIN0(iown_u_18 - 1,29),MIN0((1 + D_14(1) * 
     &PS_RAS_33(1) + D_14(1)) - 1,29)) + 1
         DS_SAS_34(3) = 1
         DS_SAS_34(4) = MAX0(1,D_14(3) * PID_11(2) + 1)
         DS_SAS_34(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &)) + 2
         DS_SAS_34(6) = 1
         call _xlhpf_send_section(a1,DS_SAS_34,PG_12,PS_RAS_33,a1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 9
       do i_5=iown_l_15,MIN0(iown_u_16,39),1
C 1585-501  Original Source Line 9
         do i_6=iown_l_17,MIN0(iown_u_18,29),1
           a2_46(i_6,i_5) = a1_45(i_6 + 1,i_5 + 1)
         end do
       end do
C 1585-501  Original Source Line 10
       if ((PID_11(2) .gt. 0) .ne. 0) then
         PS_SAS_39(1) = PID_11(1)
         PS_SAS_39(2) = PID_11(2) - 1
         DS_RAS_40(1) = MAX0(1 + D_14(1) * PS_SAS_39(1),MAX0(iown_l_17 -
     & 1,1))
         DS_RAS_40(2) = MIN0(30,D_14(1) * PID_11(1) + ((1 + D_14(1)) - 1
     &))
         DS_RAS_40(3) = 1
         DS_RAS_40(4) = MAX0(1 + D_14(3) * PS_SAS_39(2),MAX0(iown_l_15 -
     & 1,1))
         DS_RAS_40(5) = MIN0(MIN0((1 + D_14(3) * PS_SAS_39(2) + D_14(3))
     & - 1,39),MIN0(iown_u_16 - 1,39))
         DS_RAS_40(6) = 1
         call _xlhpf_nbreceive_section(b1,2,%val(0),DS_RAS_40,PG_12,PS_S
     &AS_39,msg_24)
       end if
C 1585-501  Original Source Line 10
       if ((PID_11(2) .lt. PGB_10(2) - 1) .ne. 0) then
         PS_RAS_37(1) = PID_11(1)
         PS_RAS_37(2) = PID_11(2) + 1
         DS_SAS_38(1) = MAX0(iown_l_17,MAX0((1 + D_14(1) * PS_RAS_37(1))
     & - 1,1))
         DS_SAS_38(2) = MIN0(30,D_14(1) * PID_11(1) + ((1 + D_14(1)) - 1
     &))
         DS_SAS_38(3) = 1
         DS_SAS_38(4) = MAX0(iown_l_15,MAX0((1 + D_14(3) * PS_RAS_37(2))
     & - 1,1))
         DS_SAS_38(5) = MIN0(MIN0(iown_u_16,39),MIN0(((1 + D_14(3) * PS_
     &RAS_37(2) + D_14(3)) - 1) - 1,39))
         DS_SAS_38(6) = 1
         call _xlhpf_send_section(b1,DS_SAS_38,PG_12,PS_RAS_37,b1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 10
       if ((PID_11(1) .gt. 0) .ne. 0) then
         PS_SAS_43(1) = PID_11(1) - 1
         PS_SAS_43(2) = PID_11(2)
         DS_RAS_44(1) = MAX0(1 + D_14(1) * PS_SAS_43(1),MAX0(iown_l_17 -
     & 1,1))
         DS_RAS_44(2) = MIN0(MIN0((1 + D_14(1) * PS_SAS_43(1) + D_14(1))
     & - 1,29),MIN0(iown_u_18 - 1,29))
         DS_RAS_44(3) = 1
         DS_RAS_44(4) = MAX0(1,D_14(3) * PID_11(2) + 1) - 2
         DS_RAS_44(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &))
         DS_RAS_44(6) = 1
         call _xlhpf_nbreceive_section(b1,2,%val(0),DS_RAS_44,PG_12,PS_S
     &AS_43,msg_24)
       end if
C 1585-501  Original Source Line 10
       if ((PID_11(1) .lt. PGB_10(1) - 1) .ne. 0) then
         PS_RAS_41(1) = PID_11(1) + 1
         PS_RAS_41(2) = PID_11(2)
         DS_SAS_42(1) = MAX0(iown_l_17,MAX0((1 + D_14(1) * PS_RAS_41(1))
     & - 1,1))
         DS_SAS_42(2) = MIN0(MIN0(iown_u_18,29),MIN0(((1 + D_14(1) * PS_
     &RAS_41(1) + D_14(1)) - 1) - 1,29))
         DS_SAS_42(3) = 1
         DS_SAS_42(4) = MAX0(1,D_14(3) * PID_11(2) + 1) - 2
         DS_SAS_42(5) = MIN0(40,D_14(3) * PID_11(2) + ((1 + D_14(3)) - 1
     &))
         DS_SAS_42(6) = 1
         call _xlhpf_send_section(b1,DS_SAS_42,PG_12,PS_RAS_41,b1)
       end if
       call _xlhpf_waitforall(1)
C 1585-501  Original Source Line 10
       do i_5=MAX0(iown_l_15 - 1,1),MIN0(iown_u_16 - 1,39),1
C 1585-501  Original Source Line 10
         do i_6=MAX0(iown_l_17 - 1,1),MIN0(iown_u_18 - 1,29),1
           b2_48(i_6 + 1,i_5 + 1) = b1_47(i_6,i_5)
         end do
       end do

       call use(a2,b2)
       call _xlhpfExit(%val(0))
       TRAP(3)
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       call _xlhpf_deallocate(b1)
       call _xlhpf_deallocate(b2)
       return
       call _xlhpf_deallocate(a1)
       call _xlhpf_deallocate(a2)
       call _xlhpf_deallocate(b1)
       call _xlhpf_deallocate(b2)
       end

 
 
>>>>> FILE TABLE SECTION <<<<< TIME TWO_TRIPLES.F FROM 08/16/96 NO DATE FILE FILENAME 14:41:24 LINE 0 CREATION>>>>> COMPILATION EPILOGUE SECTION <<<<< TOTAL (S) 14 (U) FOR (W) UNRECOVERABLE DIAGNOSED 1501-543 RECORDS INFORMATIONAL CONDITIONS FORTRAN 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