Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
40 changes: 40 additions & 0 deletions doc/specs/stdlib_system.md
Original file line number Diff line number Diff line change
Expand Up @@ -720,6 +720,46 @@ Subroutine

---

## `get_file_size` - Gets the size (in bytes) of a file.
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

We have not used get_* patterns anywhere else so, this function may perhaps just be file_size? The fact that it is a function already means we're get_ting stuff.


### Status

Experimental

### Description

This function gets the size (in bytes) of a file in the filesystem.
It follows symbolic links, returns an error if the symbolic link or the `path` points to a directory instead.
It is designed to work across multiple platforms. On Windows, paths with both forward `/` and backward `\` slashes are accepted.

### Syntax

`res = [[stdlib_system(module):get_file_size(function)]] (path [, err])`

### Class

Function

### Arguments

`path`: Shall be a character string containing the path of the file. It is an `intent(in)` argument.

`err`(optional): Shall be of type `state_type`, and is used for error handling. It is an `intent(out)` argument.

### Return values

`res`: it is the size (in bytes). It is of type `integer(kind=int64)`.

`err`: it is an optional state return flag. On error if not requested, an `FS_ERROR` will trigger an error stop.

### Example

```fortran
{!example/system/example_get_file_size.f90!}
```

---

## `null_device` - Return the null device file path

### Status
Expand Down
1 change: 1 addition & 0 deletions example/system/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -19,3 +19,4 @@ ADD_EXAMPLE(path_dir_name)
ADD_EXAMPLE(make_directory)
ADD_EXAMPLE(remove_directory)
ADD_EXAMPLE(cwd)
ADD_EXAMPLE(get_file_size)
21 changes: 21 additions & 0 deletions example/system/example_get_file_size.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
program example_get_file_size
use, intrinsic :: iso_fortran_env, only: int64
use stdlib_system, only: get_file_size
use stdlib_error, only: state_type
implicit none

type(state_type) :: err
integer(int64) :: size

character(*), parameter :: path = "path/to/check"

size = get_file_size(path, err)

if (err%ok()) then
print *, "Size in bytes = ", size
else
print *, "Error!: ", err%print()
end if

end program example_get_file_size

48 changes: 48 additions & 0 deletions src/stdlib_system.F90
Original file line number Diff line number Diff line change
Expand Up @@ -182,6 +182,21 @@ module stdlib_system
!!
public :: set_cwd

!! version: experimental
!!
!! Gets the size (in bytes) of a file.
!! ([Specification](../page/specs/stdlib_system.html#get_file_size))
!!
!! ### Summary
!! Gets the size (in bytes) of a file.
!!
!! ### Description
!! This function gets the size (in bytes) of a file in the filesystem.
!! It follows symbolic links, gives an error if the symbolic link or the `path` points to a directory instead.
!! It is designed to work across multiple platforms. On Windows, paths with both forward `/` and backward `\` slashes are accepted.
!!
public :: get_file_size

!! version: experimental
!!
!! Deletes a specified file from the filesystem.
Expand Down Expand Up @@ -1112,6 +1127,39 @@ end function stdlib_set_cwd
end if
end subroutine set_cwd

integer(int64) function get_file_size(path, err) result(size)
character(*), intent(in) :: path
type(state_type), optional, intent(out) :: err

interface
integer function stdlib_get_file_size(path, size) bind(C)
import c_char, c_int64_t
character(kind=c_char), intent(in) :: path(*)
integer(c_int64_t), intent(out) :: size
end function stdlib_get_file_size
end interface

type(state_type) :: err0
integer :: code
integer(c_int64_t) :: c_size

if (is_directory(path)) then
err0 = FS_ERROR("Is a directory!")
call err0%handle(err)
return
end if

code = stdlib_get_file_size(to_c_char(trim(path)), c_size)

if (code /= 0) then
err0 = FS_ERROR_CODE(code, c_get_strerror())
call err0%handle(err)
return
end if
Comment on lines +1142 to +1158
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This functionality can be achieved by Fortran intrinsics only. Perhaps that would be a good way to avoid cross-platform CI issues and avoid the C backend calls?

Suggested change
type(state_type) :: err0
integer :: code
integer(c_int64_t) :: c_size
if (is_directory(path)) then
err0 = FS_ERROR("Is a directory!")
call err0%handle(err)
return
end if
code = stdlib_get_file_size(to_c_char(trim(path)), c_size)
if (code /= 0) then
err0 = FS_ERROR_CODE(code, c_get_strerror())
call err0%handle(err)
return
end if
type(state_type) :: err0
integer :: code
character(len=256) :: iomsg
integer(c_int64_t) :: c_size
if (is_directory(path)) then
err0 = FS_ERROR("Is a directory!")
call err0%handle(err)
return
end if
inquire(file=path, size=c_size, iostat=code, iomsg=iomsg)
if (code /= 0) then
err0 = FS_ERROR_CODE(code, iomsg)
call err0%handle(err)
return
end if


size = c_size
end function get_file_size

!> Returns the file path of the null device for the current operating system.
!>
!> Version: Helper function.
Expand Down
24 changes: 24 additions & 0 deletions src/stdlib_system.c
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
#include <sys/types.h>
#include <string.h>
#include <errno.h>
#include <stdint.h>
#ifdef _WIN32
#include <direct.h>
#else
Expand Down Expand Up @@ -91,3 +92,26 @@ int stdlib_set_cwd(char* path) {

return (code == -1) ? errno : 0;
}

int stdlib_get_file_size(char* path, int64_t* size){
int code;
*size = 0;
#ifdef _WIN32
struct _stati64 buf = {0};

code = _stati64(path, &buf);

if (code == -1) return errno;

*size = (int64_t) buf.st_size;
#else
struct stat buf = {0};
code = stat(path, &buf);

if (code == -1) return errno;

*size = (int64_t) buf.st_size;
#endif /* ifdef _WIN32 */

return 0;
}
82 changes: 80 additions & 2 deletions test/system/test_filesystem.f90
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
module test_filesystem
use, intrinsic :: iso_fortran_env, only: int64
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
use stdlib_system, only: is_directory, delete_file, FS_ERROR, FS_ERROR_CODE, &
make_directory, remove_directory, make_directory_all, is_windows, OS_TYPE, &
OS_WINDOWS, get_cwd, set_cwd, operator(/)
OS_WINDOWS, get_cwd, set_cwd, operator(/), get_file_size
use stdlib_error, only: state_type, STDLIB_FS_ERROR
use stdlib_strings, only: to_string

implicit none

Expand All @@ -26,7 +28,9 @@ subroutine collect_suite(testsuite)
new_unittest("fs_make_dir_all", test_make_directory_all), &
new_unittest("fs_remove_dir", test_remove_directory), &
new_unittest("fs_remove_dir_non_existent", test_remove_directory_nonexistent), &
new_unittest("fs_cwd", test_cwd) &
new_unittest("fs_cwd", test_cwd), &
new_unittest("fs_get_file_size_dir", test_get_file_size_dir), &
new_unittest("fs_get_file_size_file", test_get_file_size_file) &
]
end subroutine collect_suite

Expand Down Expand Up @@ -330,6 +334,80 @@ subroutine test_cwd(error)
if (allocated(error)) return
end subroutine test_cwd

subroutine test_get_file_size_dir(error)
type(error_type), allocatable, intent(out) :: error
type(state_type) :: err
character(len=256) :: dir_name
integer :: ios,iocmd
character(len=512) :: msg
integer(int64) :: size

! create a temporary directory
dir_name = "test_directory"

call execute_command_line('mkdir ' // dir_name, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
call check(error, ios==0 .and. iocmd==0, 'Cannot init get_file_size test: '//trim(msg))
if (allocated(error)) return

size = get_file_size(dir_name, err)

call check(error, err%error(), 'get_file_size did not error out with a directory argument!')

if (allocated(error)) then
! cleanup: remove the empty directory
call execute_command_line('rmdir ' // dir_name, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
call check(error, ios==0 .and. iocmd==0, err%message // &
' and cannot cleanup get_file_size test, cannot remove empty dir: '//trim(msg))
return
end if

! cleanup: remove the empty directory
call execute_command_line('rmdir ' // dir_name, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
call check(error, ios==0 .and. iocmd==0, 'Cannot cleanup cwd test, cannot remove empty dir: '//trim(msg))
if (allocated(error)) return
end subroutine test_get_file_size_dir

subroutine test_get_file_size_file(error)
type(error_type), allocatable, intent(out) :: error
character(len=256) :: filename
integer :: ios, iunit, iocmd
character(len=512) :: msg
character(len=20) :: text

integer(int64) :: size
type(state_type) :: err

filename = "test_file.txt"

! Create a file and open it in `stream` access
open(newunit=iunit, file=filename, status="replace", action='write', access='stream', iostat=ios, iomsg=msg)
call check(error, ios == 0, "Cannot create test file: " // trim(msg))
if (allocated(error)) return

! get the size of an empty file => should be zero
size = get_file_size(filename, err)
call check(error, size == 0 .and. err%ok(), "Empty file has a non-zero size!: " // to_string(size))

text = "Hello, World!"
write(iunit, iostat=ios, iomsg=msg) text ! no newlines or additional bytes
call check(error, ios == 0, "Cannot write to test file: " // trim(msg))

! close the file to flush the previous write
! `flush` doesn't seem to work on windows
close(iunit,iostat=ios,iomsg=msg)
call check(error, ios == 0, "Cannot close test file: " // trim(msg))

! get the size of the file => should be len(text)
size = get_file_size(filename, err)
call check(error, size == len(text) .and. err%ok(), "file has an unexpected size!, Expected: " &
// to_string(len(text)) // " ,Got: " // to_string(size))

! Clean up: remove the file
call execute_command_line("rm " // filename, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
call check(error, ios == 0 .and. iocmd == 0, "Cannot remove test file: " // trim(msg))
if (allocated(error)) return
end subroutine test_get_file_size_file

end module test_filesystem

program tester
Expand Down
Loading