diff options
author | LKedward <laurence.kedward@bristol.ac.uk> | 2021-07-16 15:24:25 +0100 |
---|---|---|
committer | LKedward <laurence.kedward@bristol.ac.uk> | 2021-07-16 15:24:25 +0100 |
commit | f884bfd38a546dba12ccabcce8581e7bab29e51f (patch) | |
tree | 9c0f3822b59741f18cfb8feef02db7d27caf712d /src/fpm_filesystem.F90 | |
parent | 53027990c205eb905ff534544f4752ea92e747d7 (diff) | |
parent | 68937a4eae6a71b74edbf762c574cc2dc22bb2d6 (diff) | |
download | fpm-f884bfd38a546dba12ccabcce8581e7bab29e51f.tar.gz fpm-f884bfd38a546dba12ccabcce8581e7bab29e51f.zip |
Merge branch 'upstream_master' into file-listing
Diffstat (limited to 'src/fpm_filesystem.F90')
-rw-r--r-- | src/fpm_filesystem.F90 | 32 |
1 files changed, 8 insertions, 24 deletions
diff --git a/src/fpm_filesystem.F90 b/src/fpm_filesystem.F90 index 2851bfd..e5cfa9d 100644 --- a/src/fpm_filesystem.F90 +++ b/src/fpm_filesystem.F90 @@ -1,17 +1,18 @@ !> This module contains general routines for interacting with the file system !! module fpm_filesystem -use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit + use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit use fpm_environment, only: get_os_type, & OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, & OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD use fpm_environment, only: separator, get_env use fpm_strings, only: f_string, replace, string_t, split use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer + use fpm_error, only : fpm_stop implicit none private public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, & - mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, to_fortran_name + mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file public :: fileopen, fileclose, filewrite, warnwrite, parent_dir public :: which @@ -340,8 +341,7 @@ subroutine mkdir(dir) end select if (stat /= 0) then - print *, 'execute_command_line() failed' - error stop + call fpm_stop(1, '*mkdir*:directory creation failed') end if end subroutine mkdir @@ -478,8 +478,7 @@ recursive subroutine list_files(dir, files, recurse) end select if (stat /= 0) then - print *, 'execute_command_line() failed' - error stop + call fpm_stop(2,'*list_files*:directory listing failed') end if open (newunit=fh, file=temp_file, status='old') @@ -692,13 +691,11 @@ character(len=256) :: message ios=0 endif if(ios.ne.0)then - write(stderr,'(*(a:,1x))')& - & '<ERROR> *filewrite*:',filename,trim(message) lun=-1 if(present(ier))then ier=ios else - stop 1 + call fpm_stop(3,'*fileopen*:'//filename//':'//trim(message)) endif endif @@ -713,11 +710,10 @@ integer :: ios if(lun.ne.-1)then close(unit=lun,iostat=ios,iomsg=message) if(ios.ne.0)then - write(stderr,'(*(a:,1x))')'<ERROR> *filewrite*:',trim(message) if(present(ier))then ier=ios else - stop 2 + call fpm_stop(4,'*fileclose*:'//trim(message)) endif endif endif @@ -737,9 +733,7 @@ character(len=256) :: message do i=1,size(filedata) write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i)) if(ios.ne.0)then - write(stderr,'(*(a:,1x))')& - & '<ERROR> *filewrite*:',filename,trim(message) - stop 4 + call fpm_stop(5,'*filewrite*:'//filename//':'//trim(message)) endif enddo endif @@ -748,16 +742,6 @@ character(len=256) :: message end subroutine filewrite -!> Returns string with special characters replaced with an underscore. -!! For now, only a hyphen is treated as a special character, but this can be -!! expanded to other characters if needed. -pure function to_fortran_name(string) result(res) - character(*), intent(in) :: string - character(len(string)) :: res - character, parameter :: SPECIAL_CHARACTERS(*) = ['-'] - res = replace(string, SPECIAL_CHARACTERS, '_') -end function to_fortran_name - function which(command) result(pathname) !> !!##NAME |