diff --git a/CMakeLists.txt b/CMakeLists.txt index b10e1f73d..a5e9a4550 100644 --- a/CMakeLists.txt +++ b/CMakeLists.txt @@ -65,6 +65,7 @@ list( "-DPROJECT_VERSION_MAJOR=${PROJECT_VERSION_MAJOR}" "-DPROJECT_VERSION_MINOR=${PROJECT_VERSION_MINOR}" "-DPROJECT_VERSION_PATCH=${PROJECT_VERSION_PATCH}" + "-DOS=\\\"${CMAKE_SYSTEM_NAME}\\\"" "-I${PROJECT_SOURCE_DIR}/include" ) diff --git a/config/fypp_deployment.py b/config/fypp_deployment.py index 9f3549e4f..77923d004 100644 --- a/config/fypp_deployment.py +++ b/config/fypp_deployment.py @@ -1,4 +1,5 @@ import os +import platform import fypp import argparse from joblib import Parallel, delayed @@ -42,6 +43,7 @@ def pre_process_fypp(args): kwd.append("-DWITH_QP=True") if args.with_xdp: kwd.append("-DWITH_XDP=True") + kwd.append("-DOS=\"{}\"".format(platform.system())) optparser = fypp.get_option_parser() options, leftover = optparser.parse_args(args=kwd) diff --git a/doc/specs/index.md b/doc/specs/index.md index de3eb8f38..b965b006f 100644 --- a/doc/specs/index.md +++ b/doc/specs/index.md @@ -17,6 +17,7 @@ This is an index/directory of the specifications (specs) for each new module/fea - [constants](./stdlib_constants.html) - Constants - [bitsets](./stdlib_bitsets.html) - Bitset data types and procedures - [error](./stdlib_error.html) - Catching and handling errors + - [filesystem](./stdlib_filesystem.html) - Filesystem interactions - [hash](./stdlib_hash_procedures.html) - Hashing integer vectors or character strings - [hashmaps](./stdlib_hashmaps.html) - Hash maps/tables diff --git a/doc/specs/stdlib_filesystem.md b/doc/specs/stdlib_filesystem.md new file mode 100644 index 000000000..90b48eeed --- /dev/null +++ b/doc/specs/stdlib_filesystem.md @@ -0,0 +1,131 @@ +--- +title: filesystem +--- + +# The `stdlib_filesystem` module + +[TOC] + +## Introduction + +Module for filesystem interactions. + +## Constants + +### `is_windows`` + +Boolean constant indicating whether the current platform is Windows. + +### `path_separator`` + +Character constant representing the path separator for the current platform. On Windows, it is `\`. On other platforms, it is `/`. + +## Procedures + +### `exists` + +#### Status + +Experimental + +#### Description + +Determines if a file or directory exists at the given path by returning a logical value. + +#### Syntax + +`exists = ` [[stdlib_filesystem(module):exists(function)]] `(path)` + +#### Arguments + +`path`: Shall be a character expression containing the path to a file or directory to check for existence. + +#### Return value + +A logical value indicating whether a file or directory exists at the given path. + +### `list_dir` + +#### Status + +Experimental + +#### Description + +Lists the contents of a directory. + +#### Syntax + +`call ` [[stdlib_filesystem(module):list_dir(subroutine)]] `(dir, files[, iostat][, iomsg])` + +#### Arguments + +`dir`: Shall be a character expression containing the path to the directory to list. + +`files`: Shall be an allocatable rank-1 array of type `string_type` that will contain the names of the files and directories in the directory. + +`iostat`: Shall be a scalar of type `integer` that receives the error status of `list_dir`. Optional argument. + +`iomsg`: Shall be a deferred length character variable that receives the error message of `list_dir`. Optional argument. + +### `mkdir` + +#### Status + +Experimental + +#### Description + +Creates a new directory. + +#### Syntax + +`call ` [[stdlib_filesystem(module):mkdir(subroutine)]] `(dir[, iostat][, iomsg])` + +#### Arguments + +`dir`: Shall be a character expression containing the path to the directory to create. + +`iostat`: Shall be a scalar of type `integer` that receives the error status of `mkdir`. Optional argument. + +`iomsg`: Shall be a deferred length character variable that receives the error message of `mkdir`. Optional argument. + +### `rmdir` + +#### Status + +Experimental + +#### Description + +Removes a directory. + +#### Syntax + +`call ` [[stdlib_filesystem(module):rmdir(subroutine)]] `(dir)` + +#### Arguments + +`dir`: Shall be a character expression containing the path to the directory to remove. + +### `run` + +#### Status + +Experimental + +#### Description + +Runs a command in the shell. + +#### Syntax + +`call ` [[stdlib_filesystem(module):run(subroutine)]] `(command[, iostat][, iomsg])` + +#### Arguments + +`command`: Shall be a character expression containing the command to run in the shell. + +`iostat`: Shall be a scalar of type `integer` that receives the error status of `run`. Optional argument. + +`iomsg`: Shall be a deferred length character variable that receives the error message of `run`. Optional argument. diff --git a/src/CMakeLists.txt b/src/CMakeLists.txt index ef11b642e..9e1723c92 100644 --- a/src/CMakeLists.txt +++ b/src/CMakeLists.txt @@ -8,6 +8,7 @@ set(fppFiles stdlib_bitsets_large.fypp stdlib_codata_type.fypp stdlib_constants.fypp + stdlib_filesystem.fypp stdlib_hash_32bit.fypp stdlib_hash_32bit_fnv.fypp stdlib_hash_32bit_nm.fypp diff --git a/src/stdlib_filesystem.fypp b/src/stdlib_filesystem.fypp new file mode 100644 index 000000000..9d022baa0 --- /dev/null +++ b/src/stdlib_filesystem.fypp @@ -0,0 +1,159 @@ +! SPDX-Identifier: MIT + +!> Interaction with the filesystem. +module stdlib_filesystem + use stdlib_string_type, only: string_type + implicit none + private + + public :: temp_dir, is_windows, exists, path_separator, list_dir, mkdir, rmdir, run + +#: if OS == 'Windows' + !> Whether the operating system is Windows. + logical, parameter :: is_windows = .true. + !> Path separator for Windows. + character, parameter :: path_separator = '\' +#: else + !> Whether the operating system is Windows. + logical, parameter :: is_windows = .false. + !> Path separator for filesystems on non-Windows operating systems. + character, parameter :: path_separator = '/' +#: endif + + character(*), parameter :: temp_dir = 'temp' + +contains + !> Version: experimental + !> + !> Whether a file or directory exists at the given path. + !> [Specification](../page/specs/stdlib_filesystem.html#exists) + logical function exists(path) + !> Path to a file or directory. + character(len=*), intent(in) :: path + + inquire(file=path, exist=exists) + +#if defined(__INTEL_COMPILER) + if (.not. exists) inquire(directory=path, exist=exists) +#endif + end function + + !> Version: experimental + !> + !> List files and directories of a directory. Does not list hidden files. + !> [Specification](../page/specs/stdlib_filesystem.html#list_dir) + subroutine list_dir(dir, files, iostat, iomsg) + !> Directory to list. + character(len=*), intent(in) :: dir + !> List of files and directories. + type(string_type), allocatable, intent(out) :: files(:) + !> Status of listing. + integer, optional, intent(out) :: iostat + !> Error message. + character(len=:), allocatable, optional, intent(out) :: iomsg + + integer :: unit, stat + character(len=256) :: line + character(:), allocatable :: listed_contents + + stat = 0 + + if (.not. exists(temp_dir)) then + call mkdir(temp_dir, stat) + if (stat /= 0) then + if (present(iostat)) iostat = stat + if (present(iomsg)) iomsg = "Failed to create temporary directory '"//temp_dir//"'." + return + end if + end if + + listed_contents = temp_dir//path_separator//'listed_contents.txt' + + if (is_windows) then + call run('dir /b '//dir//' > '//listed_contents, stat) + else + call run('ls '//dir//' > '//listed_contents, stat) + end if + if (stat /= 0) then + if (present(iostat)) iostat = stat + if (present(iomsg)) iomsg = "Failed to list files in directory '"//dir//"'." + return + end if + + open(newunit=unit, file=listed_contents, status='old', action='read', iostat=stat) + if (stat /= 0) then + if (present(iostat)) iostat = stat + if (present(iomsg)) iomsg = "Failed to open file '"//listed_contents//"'." + return + end if + + allocate(files(0)) + do + read(unit, '(A)', iostat=stat) line + if (stat /= 0) exit + files = [files, string_type(line)] + end do + close(unit, status="delete") + end subroutine + + !> Version: experimental + !> + !> Create a directory. + !> [Specification](../page/specs/stdlib_filesystem.html#mkdir) + subroutine mkdir(dir, iostat, iomsg) + character(len=*), intent(in) :: dir + integer, optional, intent(out) :: iostat + character(len=:), allocatable, optional, intent(out) :: iomsg + + if (is_windows) then + call run('mkdir '//dir, iostat, iomsg) + else + call run('mkdir -p '//dir, iostat, iomsg) + end if + end subroutine + + !> Version: experimental + !> + !> Remove a directory including its contents. + !> [Specification](../page/specs/stdlib_filesystem.html#rmdir) + subroutine rmdir(dir) + character(len=*), intent(in) :: dir + + if (is_windows) then + call run('rmdir /s/q '//dir) + else + call run('rm -rf '//dir) + end if + end subroutine + + !> Version: experimental + !> + !> Run a command in the shell. + !> [Specification](../page/specs/stdlib_filesystem.html#run) + subroutine run(command, iostat, iomsg) + !> Command to run. + character(len=*), intent(in) :: command + !> Status of the operation. + integer, intent(out), optional :: iostat + !> Error message. + character(len=:), allocatable, intent(out), optional :: iomsg + + integer :: exitstat, cmdstat + character(len=256) :: cmdmsg + + if (present(iostat)) iostat = 0 + exitstat = 0; cmdstat = 0 + + call execute_command_line(command, exitstat=exitstat, cmdstat=cmdstat, cmdmsg=cmdmsg) + if (exitstat /= 0 .or. cmdstat /= 0) then + if (present(iostat)) then + if (exitstat /= 0) then + iostat = exitstat + else + iostat = cmdstat + end if + end if + if (present(iomsg) .and. trim(adjustl(cmdmsg)) /= '') iomsg = cmdmsg + end if + end subroutine +end module diff --git a/test/CMakeLists.txt b/test/CMakeLists.txt index 4d83548db..737938a64 100644 --- a/test/CMakeLists.txt +++ b/test/CMakeLists.txt @@ -14,6 +14,7 @@ add_subdirectory(array) add_subdirectory(ascii) add_subdirectory(bitsets) add_subdirectory(constants) +add_subdirectory(filesystem) add_subdirectory(hash_functions) add_subdirectory(hash_functions_perf) add_subdirectory(hashmaps) diff --git a/test/filesystem/CMakeLists.txt b/test/filesystem/CMakeLists.txt new file mode 100644 index 000000000..48d7eb893 --- /dev/null +++ b/test/filesystem/CMakeLists.txt @@ -0,0 +1 @@ +ADDTEST(filesystem) diff --git a/test/filesystem/test_filesystem.f90 b/test/filesystem/test_filesystem.f90 new file mode 100644 index 000000000..44588519b --- /dev/null +++ b/test/filesystem/test_filesystem.f90 @@ -0,0 +1,308 @@ +module test_filesystem + use stdlib_filesystem + use stdlib_string_type, only: char, string_type + use testdrive, only: new_unittest, unittest_type, error_type, check, test_failed + implicit none + private + + public :: collect_filesystem + + character(*), parameter :: temp_list_dir = 'temp_list_dir' + +contains + + !> Collect all exported unit tests + subroutine collect_filesystem(testsuite) + !> Collection of tests + type(unittest_type), allocatable, intent(out) :: testsuite(:) + + testsuite = [ & + new_unittest("fs_is_windows", fs_is_windows), & + new_unittest("fs_path_separator", fs_path_separator), & + new_unittest("fs_file_not_exists", fs_file_not_exists, should_fail=.true.), & + new_unittest("fs_file_exists", fs_file_exists), & + new_unittest("fs_current_dir_exists", fs_current_dir_exists), & + new_unittest("fs_use_path_separator", fs_use_path_separator), & + new_unittest("fs_run_invalid_command", fs_run_invalid_command, should_fail=.true.), & + new_unittest("fs_run_with_invalid_option", fs_run_with_invalid_option, should_fail=.true.), & + new_unittest("fs_run_valid_command", fs_run_valid_command), & + new_unittest("fs_list_dir_empty", fs_list_dir_empty), & + new_unittest("fs_list_dir_one_file", fs_list_dir_one_file), & + new_unittest("fs_list_dir_two_files", fs_list_dir_two_files), & + new_unittest("fs_list_dir_one_file_one_dir", fs_list_dir_one_file_one_dir), & + new_unittest("fs_rmdir_empty", fs_rmdir_empty), & + new_unittest("fs_rmdir_with_contents", fs_rmdir_with_contents) & + ] + end subroutine + + subroutine fs_is_windows(error) + type(error_type), allocatable, intent(out) :: error + + character(len=255) :: value + integer :: length, stat + + call get_environment_variable('HOMEDRIVE', value, length, stat) + if (is_windows) then + call check(error, stat == 0 .and. length > 0, "Windows should be detected.") + else + call check(error, stat /= 0 .and. length == 0, "Windows should not be detected.") + end if + end subroutine + + subroutine fs_path_separator(error) + type(error_type), allocatable, intent(out) :: error + + character(len=255) :: value + integer :: length, stat + + call get_environment_variable('HOMEDRIVE', value, length, stat) + if (stat == 0 .and. length > 0) then + call check(error, path_separator == '\', "Path separator should be set for Windows.") + else + call check(error, path_separator == '/', "Path separator should not be set for non-Windows.") + end if + end subroutine + + subroutine fs_file_not_exists(error) + type(error_type), allocatable, intent(out) :: error + + logical :: is_existing + + is_existing = exists("nonexistent") + call check(error, is_existing, "Non-existent file should fail.") + end subroutine + + subroutine fs_file_exists(error) + type(error_type), allocatable, intent(out) :: error + + logical :: is_existing + character(*), parameter :: filename = "file.tmp" + + call create_file(filename) + is_existing = exists(filename) + call check(error, is_existing, "An existing file should not fail.") + call delete_file(filename) + end subroutine + + subroutine fs_current_dir_exists(error) + type(error_type), allocatable, intent(out) :: error + + logical :: is_existing + + is_existing = exists(".") + call check(error, is_existing, "Current directory should not fail.") + end subroutine + + subroutine fs_use_path_separator(error) + type(error_type), allocatable, intent(out) :: error + + character(*), parameter :: outer_dir = "path_separator_outer" + character(*), parameter :: inner_dir = "path_separator_inner" + + call rmdir(outer_dir) + call check(error, .not. exists(outer_dir), "Directory should not exist.") + call mkdir(outer_dir) + call check(error, exists(outer_dir), "Outer directory should now exist.") + call mkdir(outer_dir//path_separator//inner_dir) + call check(error, exists(outer_dir//path_separator//inner_dir), "Inner directory should now exist.") + call rmdir(outer_dir) + end subroutine + + subroutine fs_run_invalid_command(error) + type(error_type), allocatable, intent(out) :: error + + integer :: stat + + call run("invalid_command", iostat=stat) + call check(error, stat, "Running an invalid command should fail.") + end subroutine + + subroutine fs_run_with_invalid_option(error) + type(error_type), allocatable, intent(out) :: error + + integer :: stat + + call run("whoami -X", iostat=stat) + call check(error, stat, "Running a valid command with an invalid option should fail.") + end subroutine + + subroutine fs_run_valid_command(error) + type(error_type), allocatable, intent(out) :: error + + integer :: stat + + call run("whoami", iostat=stat) + call check(error, stat, "Running a valid command should not fail.") + end subroutine + + subroutine fs_list_dir_empty(error) + type(error_type), allocatable, intent(out) :: error + + integer :: stat + type(string_type), allocatable :: files(:) + + call rmdir(temp_list_dir) + call mkdir(temp_list_dir, stat) + if (stat /= 0) then + call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return + end if + + call list_dir(temp_list_dir, files, stat) + call check(error, stat, "Listing the contents of an empty directory shouldn't fail.") + call check(error, size(files) == 0, "The directory should be empty.") + + call rmdir(temp_list_dir) + end subroutine + + subroutine fs_list_dir_one_file(error) + type(error_type), allocatable, intent(out) :: error + + integer :: stat + + type(string_type), allocatable :: files(:) + character(*), parameter :: filename = 'abc.txt' + + call rmdir(temp_list_dir) + call mkdir(temp_list_dir, stat) + if (stat /= 0) then + call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return + end if + + call create_file(temp_list_dir//path_separator//filename) + + call list_dir(temp_list_dir, files, stat) + call check(error, stat, "Listing the contents of an empty directory shouldn't fail.") + call check(error, size(files) == 1, "The directory should contain one file.") + call check(error, char(files(1)) == filename, "The file should be '"//filename//"'.") + + call rmdir(temp_list_dir) + end subroutine + + subroutine fs_list_dir_two_files(error) + type(error_type), allocatable, intent(out) :: error + + integer :: stat + + type(string_type), allocatable :: files(:) + character(*), parameter :: filename1 = 'abc.txt' + character(*), parameter :: filename2 = 'xyz' + + call rmdir(temp_list_dir) + call mkdir(temp_list_dir, stat) + if (stat /= 0) then + call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return + end if + + call create_file(temp_list_dir//path_separator//filename1) + call create_file(temp_list_dir//path_separator//filename2) + + call list_dir(temp_list_dir, files, stat) + call check(error, stat, "Listing the contents of an empty directory shouldn't fail.") + call check(error, size(files) == 2, "The directory should contain two files.") + call check(error, char(files(1)) == filename1, "The file should be '"//filename1//"'.") + call check(error, char(files(2)) == filename2, "The file should be '"//filename2//"'.") + + call rmdir(temp_list_dir) + end subroutine + + subroutine fs_list_dir_one_file_one_dir(error) + type(error_type), allocatable, intent(out) :: error + + integer :: stat + + type(string_type), allocatable :: contents(:) + character(*), parameter :: filename = 'abc.txt' + character(*), parameter :: dir = 'xyz' + + call rmdir(temp_list_dir) + call mkdir(temp_list_dir, stat) + if (stat /= 0) then + call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return + end if + + call create_file(temp_list_dir//path_separator//filename) + call mkdir(temp_list_dir//path_separator//dir, stat) + if (stat /= 0) then + call test_failed(error, "Creating dir in directory '"//temp_list_dir//"' failed."); return + end if + + call list_dir(temp_list_dir, contents, stat) + call check(error, stat, "Listing the contents of an empty directory shouldn't fail.") + call check(error, size(contents) == 2, "The directory should contain two files.") + call check(error, char(contents(1)) == filename, "The file should be '"//filename//"'.") + call check(error, char(contents(2)) == dir, "The file should be '"//dir//"'.") + + call rmdir(temp_list_dir) + end subroutine + + subroutine fs_rmdir_empty(error) + type(error_type), allocatable, intent(out) :: error + + character(*), parameter :: dir = "empty_dir_to_remove" + + call rmdir(dir) + call check(error, .not. exists(dir), "Directory should not exist.") + call mkdir(dir) + call check(error, exists(dir), "Directory should exist.") + call rmdir(dir) + call check(error, .not. exists(dir), "Directory should not exist.") + end subroutine + + subroutine fs_rmdir_with_contents(error) + type(error_type), allocatable, intent(out) :: error + + character(*), parameter :: dir = "dir_with_contents_to_remove" + + call rmdir(dir) + call check(error, .not. exists(dir), "Directory should not exist.") + call mkdir(dir) + call check(error, exists(dir), "Directory should exist.") + call mkdir(dir//path_separator//'another_dir') + call rmdir(dir) + call check(error, .not. exists(dir), "Directory should not exist.") + end subroutine + + subroutine create_file(filename) + character(len=*), intent(in) :: filename + + integer :: io + + open(newunit=io, file=filename) + close(io) + end subroutine + + subroutine delete_file(filename) + character(len=*), intent(in) :: filename + + integer :: io + + open(newunit=io, file=filename) + close(io, status="delete") + end subroutine +end module + +program tester + use, intrinsic :: iso_fortran_env, only : error_unit + use testdrive, only : run_testsuite, new_testsuite, testsuite_type + use test_filesystem, only : collect_filesystem + implicit none + integer :: stat, is + type(testsuite_type), allocatable :: testsuites(:) + character(len=*), parameter :: fmt = '("#", *(1x, a))' + + stat = 0 + + testsuites = [ & + new_testsuite("filesystem", collect_filesystem) & + ] + + do is = 1, size(testsuites) + write(error_unit, fmt) "Testing:", testsuites(is)%name + call run_testsuite(testsuites(is)%collect, error_unit, stat) + end do + + if (stat > 0) then + write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!" + error stop + end if +end program