Skip to content

Commit

Permalink
ssids hwloc bug squashed
Browse files Browse the repository at this point in the history
  • Loading branch information
dalekopera committed Jan 7, 2025
1 parent 7019145 commit 13443f2
Show file tree
Hide file tree
Showing 3 changed files with 0 additions and 13 deletions.
9 changes: 0 additions & 9 deletions src/sls/sls.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2852,7 +2852,6 @@ SUBROUTINE SLS_analyse( matrix, data, control, inform, PERM )
inform%alloc_status )
IF ( inform%status /= GALAHAD_ok ) THEN
inform%bad_alloc = 'sls: data%matrix%VAL' ; GO TO 900 ; END IF
write(6,*) 8, inform%status

DO i = 1, matrix%n
l = data%matrix%PTR( i )
Expand Down Expand Up @@ -3664,15 +3663,11 @@ SUBROUTINE SLS_analyse( matrix, data, control, inform, PERM )
CALL CPU_time( time ) ; CALL CLOCK_time( clock )
IF ( mc6168_ordering ) THEN
data%ssids_options%ordering = 0
write(6,*) 'order', data%ORDER
write(6,*) 'into ssids_analyse'
CALL SSIDS_analyse( .FALSE., data%matrix%n, &
data%matrix%PTR, data%matrix%COL, &
data%ssids_akeep, &
data%ssids_options, data%ssids_inform, &
order = data%ORDER )
write(6,*) 'out of ssids_analyse'
write(6,*) ' ssids_inform = ', data%ssids_inform
ELSE
IF ( PRESENT( PERM ) ) THEN
data%ssids_options%ordering = 0
Expand All @@ -3690,7 +3685,6 @@ SUBROUTINE SLS_analyse( matrix, data, control, inform, PERM )
order = data%ORDER )
END IF
END IF
write(6,*) ' ssids_inform%stat = ', data%ssids_inform%stat
CALL SLS_copy_inform_from_ssids( inform, data%ssids_inform )
IF ( inform%status /= GALAHAD_ok ) GO TO 800
CALL SPACE_resize_array( matrix%n, data%LFLAG, &
Expand Down Expand Up @@ -4219,8 +4213,6 @@ SUBROUTINE SLS_analyse( matrix, data, control, inform, PERM )
CALL CPU_time( time_now ) ; CALL CLOCK_time( clock_now )
inform%time%analyse_external = time_now - time
inform%time%clock_analyse_external = clock_now - clock
write(6,*) 20, inform%status


! record total time

Expand All @@ -4232,7 +4224,6 @@ SUBROUTINE SLS_analyse( matrix, data, control, inform, PERM )
inform%time%total = inform%time%total + time_now - time_start
inform%time%clock_total = &
inform%time%clock_total + clock_now - clock_start
write(6,*) 21, inform%status
RETURN

! End of SLS_analyse
Expand Down
3 changes: 0 additions & 3 deletions src/spral/hw_topology.F90
Original file line number Diff line number Diff line change
Expand Up @@ -72,18 +72,15 @@ subroutine guess_topology(regions, st)

! Get regions from C
call spral_hw_topology_guess(nregions, c_regions)
write(6,*) 'regions = ', nregions
if (c_associated(c_regions)) then
call c_f_pointer(c_regions, f_regions, shape=(/ nregions /))

! Copy to allocatable array
allocate(regions(nregions), stat=st)
if(st/=0) write(6,*) nregions, ' regions st = ', st
if (st .ne. 0) return
do i = 1, nregions
regions(i)%nproc = f_regions(i)%nproc
allocate(regions(i)%gpus(f_regions(i)%ngpu), stat=st)
if(st/=0) write(6,*) i, ' regionsi st = ', st
if (st .ne. 0) return
if (f_regions(i)%ngpu .gt. 0) then
call c_f_pointer(f_regions(i)%gpus, f_gpus, &
Expand Down
1 change: 0 additions & 1 deletion src/ssids/ssids.F90
Original file line number Diff line number Diff line change
Expand Up @@ -373,7 +373,6 @@ subroutine analyse_precision(check, n, ptr, row, akeep, options, inform, &
else
! Guess it
call guess_topology(akeep%topology, st)
if (st .ne. 0) write(6,*) 'error return from guess_topology, st = ', st
if (st .ne. 0) goto 490
end if
call squash_topology(akeep%topology, options, st)
Expand Down

0 comments on commit 13443f2

Please sign in to comment.