Skip to content

Commit 4a4c135

Browse files
committed
use no-overhead C function
1 parent 103cf9b commit 4a4c135

File tree

3 files changed

+32
-39
lines changed

3 files changed

+32
-39
lines changed

src/stdlib_system.F90

Lines changed: 31 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module stdlib_system
2-
use, intrinsic :: iso_c_binding, only : c_int, c_long, c_null_ptr, c_int64_t
3-
use stdlib_kinds, only: int64, dp
2+
use, intrinsic :: iso_c_binding, only : c_int, c_long, c_ptr, c_null_ptr, c_int64_t, c_size_t, &
3+
c_f_pointer
4+
use stdlib_kinds, only: int64, dp, c_char
45
implicit none
56
private
67
public :: sleep
@@ -635,17 +636,39 @@ pure function OS_NAME(os)
635636
end select
636637
end function OS_NAME
637638

638-
!> Return the file path of the null device for the current operating system.
639+
!> Returns the file path of the null device for the current operating system.
640+
!>
641+
!> Version: Helper function.
639642
function null_device() result(path)
640643
!> File path of the null device
641644
character(:), allocatable :: path
642645

643-
if (OS_TYPE()==OS_WINDOWS) then
644-
path = 'NUL'
645-
else
646-
path = '/dev/null'
647-
end if
646+
interface
647+
648+
! No-overhead return path to the null device
649+
type(c_ptr) function process_null_device(len) bind(C,name='process_null_device')
650+
import c_ptr, c_size_t
651+
implicit none
652+
integer(c_size_t), intent(out) :: len
653+
end function process_null_device
654+
655+
end interface
648656

657+
integer(c_size_t) :: i, len
658+
type(c_ptr) :: c_path_ptr
659+
character(kind=c_char), pointer :: c_path(:)
660+
661+
! Call the C function to get the null device path and its length
662+
c_path_ptr = process_null_device(len)
663+
call c_f_pointer(c_path_ptr,c_path,[len])
664+
665+
! Allocate the Fortran string with the length returned from C
666+
allocate(character(len=len) :: path)
667+
668+
do concurrent (i=1:len)
669+
path(i:i) = c_path(i)
670+
end do
671+
649672
end function null_device
650673

651674
end module stdlib_system

src/stdlib_system_subprocess.F90

Lines changed: 0 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -51,13 +51,6 @@ subroutine process_wait(seconds) bind(C,name='process_wait')
5151
real(c_float), intent(in), value :: seconds
5252
end subroutine process_wait
5353

54-
! Return path to the null device
55-
type(c_ptr) function process_null_device(len) bind(C,name='process_null_device')
56-
import c_ptr, c_int
57-
implicit none
58-
integer(c_int), intent(out) :: len
59-
end function process_null_device
60-
6154
! Utility: check if _WIN32 is defined in the C compiler
6255
logical(c_bool) function process_is_windows() bind(C,name='process_is_windows')
6356
import c_bool
@@ -604,29 +597,6 @@ function assemble_cmd(args, stdin, stdout, stderr) result(cmd)
604597

605598
end function assemble_cmd
606599

607-
!> Returns the file path of the null device for the current operating system.
608-
!>
609-
!> Version: Helper function.
610-
function null_device()
611-
character(:), allocatable :: null_device
612-
613-
integer(c_int) :: i, len
614-
type(c_ptr) :: c_path_ptr
615-
character(kind=c_char), pointer :: c_path(:)
616-
617-
! Call the C function to get the null device path and its length
618-
c_path_ptr = process_null_device(len)
619-
call c_f_pointer(c_path_ptr,c_path,[len])
620-
621-
! Allocate the Fortran string with the length returned from C
622-
allocate(character(len=len) :: null_device)
623-
624-
do concurrent (i=1:len)
625-
null_device(i:i) = c_path(i)
626-
end do
627-
628-
end function null_device
629-
630600
!> Returns the file path of the null device for the current operating system.
631601
!>
632602
!> Version: Helper function.

src/stdlib_system_subprocess.c

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -376,7 +376,7 @@ void process_wait(float seconds)
376376
}
377377

378378
// Returns the cross-platform file path of the null device for the current operating system.
379-
const char* process_null_device(int* len)
379+
const char* process_null_device(size_t* len)
380380
{
381381
#ifdef _WIN32
382382
(*len) = strlen("NUL");

0 commit comments

Comments
 (0)