Skip to content

Commit 5e93fa5

Browse files
authored
Merge branch 'master' into system_is_dir
2 parents 8dfaac7 + 954a84b commit 5e93fa5

File tree

7 files changed

+141
-36
lines changed

7 files changed

+141
-36
lines changed

doc/specs/stdlib_system.md

+42-2
Original file line numberDiff line numberDiff line change
@@ -410,14 +410,14 @@ None.
410410

411411
Returns one of the `integer` `OS_*` parameters representing the OS type, from the `stdlib_system` module, or `OS_UNKNOWN` if undetermined.
412412

413-
---
414-
415413
### Example
416414

417415
```fortran
418416
{!example/system/example_os_type.f90!}
419417
```
420418

419+
---
420+
421421
## `is_directory` - Test if a path is a directory
422422

423423
### Status
@@ -434,6 +434,7 @@ It is designed to work across multiple platforms. On Windows, paths with both fo
434434
`result = [[stdlib_io(module):is_directory(function)]] (path)`
435435

436436
### Class
437+
437438
Function
438439

439440
### Arguments
@@ -452,3 +453,42 @@ The function returns a `logical` value:
452453
```fortran
453454
{!example/system/example_is_directory.f90!}
454455
```
456+
457+
---
458+
459+
## `null_device` - Return the null device file path
460+
461+
### Status
462+
463+
Experimental
464+
465+
### Description
466+
467+
This function returns the file path of the null device, which is a special file used to discard any data written to it.
468+
It reads as an empty file. The null device's path varies by operating system:
469+
- On Windows, the null device is represented as `NUL`.
470+
- On UNIX-like systems (Linux, macOS), the null device is represented as `/dev/null`.
471+
472+
### Syntax
473+
474+
`path = [[stdlib_system(module):null_device(function)]]()`
475+
476+
### Class
477+
478+
Function
479+
480+
### Arguments
481+
482+
None.
483+
484+
### Return Value
485+
486+
- **Type:** `character(:), allocatable`
487+
- Returns the null device file path as a character string, appropriate for the operating system.
488+
489+
### Example
490+
491+
```fortran
492+
{!example/system/example_null_device.f90!}
493+
```
494+

example/system/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
ADD_EXAMPLE(get_runtime_os)
22
ADD_EXAMPLE(is_directory)
3+
ADD_EXAMPLE(null_device)
34
ADD_EXAMPLE(os_type)
45
ADD_EXAMPLE(process_1)
56
ADD_EXAMPLE(process_2)
+20
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
! Showcase usage of the null device
2+
program example_null_device
3+
use stdlib_system, only: null_device
4+
use iso_fortran_env, only: output_unit
5+
implicit none
6+
integer :: unit
7+
logical :: screen_output = .false.
8+
9+
if (screen_output) then
10+
unit = output_unit
11+
else
12+
! Write to the null device if no screen output is wanted
13+
open(newunit=unit,file=null_device())
14+
endif
15+
16+
write(unit,*) "Hello, world!"
17+
18+
if (.not.screen_output) close(unit)
19+
20+
end program example_null_device

src/stdlib_system.F90

+54-1
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
module stdlib_system
2-
use, intrinsic :: iso_c_binding, only : c_int, c_long, c_null_ptr, c_int64_t
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
34
use stdlib_kinds, only: int64, dp, c_bool, c_char
45
use stdlib_strings, only: to_c_char
56
implicit none
@@ -97,6 +98,23 @@ module stdlib_system
9798
!! Windows, and various UNIX-like environments. On unsupported operating systems, the function will return `.false.`.
9899
!!
99100
public :: is_directory
101+
102+
!! version: experimental
103+
!!
104+
!! Returns the file path of the null device, which discards all data written to it.
105+
!! ([Specification](../page/specs/stdlib_system.html#null_device-return-the-null-device-file-path))
106+
!!
107+
!! ### Summary
108+
!! Function that provides the file path of the null device appropriate for the current operating system.
109+
!!
110+
!! ### Description
111+
!!
112+
!! The null device is a special file that discards all data written to it and always reads as
113+
!! an empty file. This function returns the null device path, adapted for the operating system in use.
114+
!!
115+
!! On Windows, this is `NUL`. On UNIX-like systems, this is `/dev/null`.
116+
!!
117+
public :: null_device
100118

101119
! CPU clock ticks storage
102120
integer, parameter, private :: TICKS = int64
@@ -654,4 +672,39 @@ end function stdlib_is_directory
654672

655673
end function is_directory
656674

675+
!> Returns the file path of the null device for the current operating system.
676+
!>
677+
!> Version: Helper function.
678+
function null_device() result(path)
679+
!> File path of the null device
680+
character(:), allocatable :: path
681+
682+
interface
683+
684+
! No-overhead return path to the null device
685+
type(c_ptr) function process_null_device(len) bind(C,name='process_null_device')
686+
import c_ptr, c_size_t
687+
implicit none
688+
integer(c_size_t), intent(out) :: len
689+
end function process_null_device
690+
691+
end interface
692+
693+
integer(c_size_t) :: i, len
694+
type(c_ptr) :: c_path_ptr
695+
character(kind=c_char), pointer :: c_path(:)
696+
697+
! Call the C function to get the null device path and its length
698+
c_path_ptr = process_null_device(len)
699+
call c_f_pointer(c_path_ptr,c_path,[len])
700+
701+
! Allocate the Fortran string with the length returned from C
702+
allocate(character(len=len) :: path)
703+
704+
do concurrent (i=1:len)
705+
path(i:i) = c_path(i)
706+
end do
707+
708+
end function null_device
709+
657710
end module stdlib_system

src/stdlib_system_subprocess.F90

-30
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

+1-1
Original file line numberDiff line numberDiff line change
@@ -400,7 +400,7 @@ void process_wait(float seconds)
400400
}
401401

402402
// Returns the cross-platform file path of the null device for the current operating system.
403-
const char* process_null_device(int* len)
403+
const char* process_null_device(size_t* len)
404404
{
405405
#ifdef _WIN32
406406
(*len) = strlen("NUL");

test/system/test_os.f90

+23-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
module test_os
22
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3-
use stdlib_system, only: get_runtime_os, OS_WINDOWS, OS_UNKNOWN, OS_TYPE, is_windows
3+
use stdlib_system, only: get_runtime_os, OS_WINDOWS, OS_UNKNOWN, OS_TYPE, is_windows, null_device
44

55
implicit none
66

@@ -13,7 +13,8 @@ subroutine collect_suite(testsuite)
1313

1414
testsuite = [ &
1515
new_unittest('test_get_runtime_os', test_get_runtime_os), &
16-
new_unittest('test_is_windows', test_is_windows) &
16+
new_unittest('test_is_windows', test_is_windows), &
17+
new_unittest('test_null_device', test_null_device) &
1718
]
1819
end subroutine collect_suite
1920

@@ -38,6 +39,26 @@ subroutine test_is_windows(error)
3839

3940
end subroutine test_is_windows
4041

42+
!> Test that the null_device is valid by writing something to it
43+
subroutine test_null_device(error)
44+
type(error_type), allocatable, intent(out) :: error
45+
integer :: unit, ios
46+
character(len=512) :: iomsg
47+
48+
! Try opening the null device for writing
49+
open(newunit=unit, file=null_device(), status='old', action='write', iostat=ios, iomsg=iomsg)
50+
call check(error, ios==0, 'Cannot open null_device unit: '//trim(iomsg))
51+
if (allocated(error)) return
52+
53+
write(unit, *, iostat=ios, iomsg=iomsg) 'Hello, World!'
54+
call check(error, ios==0, 'Cannot write to null_device unit: '//trim(iomsg))
55+
if (allocated(error)) return
56+
57+
close(unit, iostat=ios, iomsg=iomsg)
58+
call check(error, ios==0, 'Cannot close null_device unit: '//trim(iomsg))
59+
if (allocated(error)) return
60+
61+
end subroutine test_null_device
4162

4263
end module test_os
4364

0 commit comments

Comments
 (0)