Skip to content

Commit

Permalink
Merge pull request #1654 from ExtremeFLOW/fix/neko_job_info
Browse files Browse the repository at this point in the history
Move job info to an own subroutine
  • Loading branch information
njansson authored Jan 6, 2025
2 parents 6a89a72 + ce5bc42 commit 6e1ab93
Showing 1 changed file with 113 additions and 101 deletions.
214 changes: 113 additions & 101 deletions src/neko.f90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
! Copyright (c) 2019-2024, The Neko Authors
! Copyright (c) 2019-2025, The Neko Authors
! All rights reserved.
!
! Redistribution and use in source and binary forms, with or without
Expand Down Expand Up @@ -126,14 +126,15 @@ module neko

contains

!> Initialise Neko
subroutine neko_init(C)
type(case_t), target, intent(inout), optional :: C
character(len=NEKO_FNAME_LEN) :: case_file, args
character(len=LOG_SIZE) :: log_buf
character(len=10) :: suffix
character(10) :: time
character(8) :: date
integer :: argc, nthrds, rw, sw, i
integer :: argc, i

call date_and_time(time = time, date = date)

Expand Down Expand Up @@ -171,14 +172,6 @@ subroutine neko_init(C)
end if
end if

!
! Job information
!
call neko_log%section("Job Information")
write(log_buf, '(A,A,A,A,1x,A,1x,A,A,A,A,A)') 'Start time: ',&
time(1:2), ':', time(3:4), &
'/', date(1:4), '-', date(5:6), '-', date(7:8)
call neko_log%message(log_buf, NEKO_LOG_QUIET)
if (argc .gt. 1) then
write(log_buf, '(a)') 'Running with command line arguments: '
call neko_log%message(log_buf, NEKO_LOG_QUIET)
Expand All @@ -187,97 +180,10 @@ subroutine neko_init(C)
call neko_log%message(args, NEKO_LOG_QUIET)
end do
end if
write(log_buf, '(a)') 'Running on: '
sw = 10
if (pe_size .lt. 1e1) then
write(log_buf(13:), '(i1,a)') pe_size, ' MPI '
if (pe_size .eq. 1) then
write(log_buf(19:), '(a)') 'rank'
sw = 9
else
write(log_buf(19:), '(a)') 'ranks'
end if
rw = 1
else if (pe_size .lt. 1e2) then
write(log_buf(13:), '(i2,a)') pe_size, ' MPI ranks'
rw = 2
else if (pe_size .lt. 1e3) then
write(log_buf(13:), '(i3,a)') pe_size, ' MPI ranks'
rw = 3
else if (pe_size .lt. 1e4) then
write(log_buf(13:), '(i4,a)') pe_size, ' MPI ranks'
rw = 4
else if (pe_size .lt. 1e5) then
write(log_buf(13:), '(i5,a)') pe_size, ' MPI ranks'
rw = 5
else
write(log_buf(13:), '(i6,a)') pe_size, ' MPI ranks'
rw = 6
end if

nthrds = 1
!$omp parallel
!$omp master
!$ nthrds = omp_get_num_threads()
!$omp end master
!$omp end parallel

if (nthrds .gt. 1) then
if (nthrds .lt. 1e1) then
write(log_buf(13 + rw + sw:), '(a,i1,a)') ', using ', &
nthrds, ' thrds each'
else if (nthrds .lt. 1e2) then
write(log_buf(13 + rw + sw:), '(a,i2,a)') ', using ', &
nthrds, ' thrds each'
else if (nthrds .lt. 1e3) then
write(log_buf(13 + rw + sw:), '(a,i3,a)') ', using ', &
nthrds, ' thrds each'
else if (nthrds .lt. 1e4) then
write(log_buf(13 + rw + sw:), '(a,i4,a)') ', using ', &
nthrds, ' thrds each'
end if
end if
call neko_log%message(log_buf, NEKO_LOG_QUIET)

write(log_buf, '(a)') 'CPU type : '
call system_cpu_name(log_buf(13:))
call neko_log%message(log_buf, NEKO_LOG_QUIET)

write(log_buf, '(a)') 'Bcknd type: '
if (NEKO_BCKND_SX .eq. 1) then
write(log_buf(13:), '(a)') 'SX-Aurora'
else if (NEKO_BCKND_XSMM .eq. 1) then
write(log_buf(13:), '(a)') 'CPU (libxsmm)'
else if (NEKO_BCKND_CUDA .eq. 1) then
write(log_buf(13:), '(a)') 'Accelerator (CUDA)'
else if (NEKO_BCKND_HIP .eq. 1) then
write(log_buf(13:), '(a)') 'Accelerator (HIP)'
else if (NEKO_BCKND_OPENCL .eq. 1) then
write(log_buf(13:), '(a)') 'Accelerator (OpenCL)'
else
write(log_buf(13:), '(a)') 'CPU'
end if
call neko_log%message(log_buf, NEKO_LOG_QUIET)

if (NEKO_BCKND_HIP .eq. 1 .or. NEKO_BCKND_CUDA .eq. 1 .or. &
NEKO_BCKND_OPENCL .eq. 1) then
write(log_buf, '(a)') 'Dev. name : '
call device_name(log_buf(13:))
call neko_log%message(log_buf, NEKO_LOG_QUIET)
end if

write(log_buf, '(a)') 'Real type : '
select case (rp)
case (real32)
write(log_buf(13:), '(a)') 'single precision'
case (real64)
write(log_buf(13:), '(a)') 'double precision'
case (real128)
write(log_buf(13:), '(a)') 'quad precision'
end select
call neko_log%message(log_buf, NEKO_LOG_QUIET)

call neko_log%end()
!
! Job information
!
call neko_job_info(date, time)

!
! Create case
Expand All @@ -299,6 +205,7 @@ subroutine neko_init(C)

end subroutine neko_init

!> Finalize Neko
subroutine neko_finalize(C)
type(case_t), intent(inout), optional :: C

Expand All @@ -317,4 +224,109 @@ subroutine neko_finalize(C)
call comm_free
end subroutine neko_finalize


!> Display job information, number of MPI ranks,
!! CPU type and selected hardware backend
subroutine neko_job_info(date, time)
character(10), optional, intent(in) :: time
character(8), optional, intent(in) :: date
character(len=LOG_SIZE) :: log_buf
integer :: nthrds, rw, sw

call neko_log%section("Job Information")

if (present(time) .and. present(date)) then
write(log_buf, '(A,A,A,A,1x,A,1x,A,A,A,A,A)') 'Start time: ', &
time(1:2), ':', time(3:4), &
'/', date(1:4), '-', date(5:6), '-', date(7:8)
call neko_log%message(log_buf, NEKO_LOG_QUIET)
end if
write(log_buf, '(a)') 'Running on: '
sw = 10
if (pe_size .lt. 1e1) then
write(log_buf(13:), '(i1,a)') pe_size, ' MPI '
if (pe_size .eq. 1) then
write(log_buf(19:), '(a)') 'rank'
sw = 9
else
write(log_buf(19:), '(a)') 'ranks'
end if
rw = 1
else if (pe_size .lt. 1e2) then
write(log_buf(13:), '(i2,a)') pe_size, ' MPI ranks'
rw = 2
else if (pe_size .lt. 1e3) then
write(log_buf(13:), '(i3,a)') pe_size, ' MPI ranks'
rw = 3
else if (pe_size .lt. 1e4) then
write(log_buf(13:), '(i4,a)') pe_size, ' MPI ranks'
rw = 4
else if (pe_size .lt. 1e5) then
write(log_buf(13:), '(i5,a)') pe_size, ' MPI ranks'
rw = 5
else
write(log_buf(13:), '(i6,a)') pe_size, ' MPI ranks'
rw = 6
end if
nthrds = 1
!$omp parallel
!$omp master
!$ nthrds = omp_get_num_threads()
!$omp end master
!$omp end parallel
if (nthrds .gt. 1) then
if (nthrds .lt. 1e1) then
write(log_buf(13 + rw + sw:), '(a,i1,a)') ', using ', &
nthrds, ' thrds each'
else if (nthrds .lt. 1e2) then
write(log_buf(13 + rw + sw:), '(a,i2,a)') ', using ', &
nthrds, ' thrds each'
else if (nthrds .lt. 1e3) then
write(log_buf(13 + rw + sw:), '(a,i3,a)') ', using ', &
nthrds, ' thrds each'
else if (nthrds .lt. 1e4) then
write(log_buf(13 + rw + sw:), '(a,i4,a)') ', using ', &
nthrds, ' thrds each'
end if
end if
call neko_log%message(log_buf, NEKO_LOG_QUIET)

write(log_buf, '(a)') 'CPU type : '
call system_cpu_name(log_buf(13:))
call neko_log%message(log_buf, NEKO_LOG_QUIET)

write(log_buf, '(a)') 'Bcknd type: '
if (NEKO_BCKND_SX .eq. 1) then
write(log_buf(13:), '(a)') 'SX-Aurora'
else if (NEKO_BCKND_XSMM .eq. 1) then
write(log_buf(13:), '(a)') 'CPU (libxsmm)'
else if (NEKO_BCKND_CUDA .eq. 1) then
write(log_buf(13:), '(a)') 'Accelerator (CUDA)'
else if (NEKO_BCKND_HIP .eq. 1) then
write(log_buf(13:), '(a)') 'Accelerator (HIP)'
else if (NEKO_BCKND_OPENCL .eq. 1) then
write(log_buf(13:), '(a)') 'Accelerator (OpenCL)'
else
write(log_buf(13:), '(a)') 'CPU'
end if
call neko_log%message(log_buf, NEKO_LOG_QUIET)

if (NEKO_BCKND_HIP .eq. 1 .or. NEKO_BCKND_CUDA .eq. 1 .or. &
NEKO_BCKND_OPENCL .eq. 1) then
write(log_buf, '(a)') 'Dev. name : '
call device_name(log_buf(13:))
call neko_log%message(log_buf, NEKO_LOG_QUIET)
end if
write(log_buf, '(a)') 'Real type : '
select case (rp)
case (real32)
write(log_buf(13:), '(a)') 'single precision'
case (real64)
write(log_buf(13:), '(a)') 'double precision'
case (real128)
write(log_buf(13:), '(a)') 'quad precision'
end select
call neko_log%message(log_buf, NEKO_LOG_QUIET)
call neko_log%end()
end subroutine neko_job_info
end module neko

0 comments on commit 6e1ab93

Please sign in to comment.