fpm_filesystem Module

This module contains general routines for interacting with the file system

Directories are not files for the Intel compilers. If so, also use this compiler-dependent extension



Functions

public function basename(path, suffix) result(base)

Extract filename from path with/without suffix

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path
logical, intent(in), optional :: suffix

Return Value character(len=:), allocatable

public function canon_path(path)

Canonicalize path for comparison * Handles path string redundancies * Does not test existence of path

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path

Return Value character(len=:), allocatable

public function dirname(path) result(dir)

Extract dirname from path

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path

Return Value character(len=:), allocatable

public function exists(filename) result(r)

test if pathname already exists

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename

Return Value logical

public function get_dos_path(path, error)

Ensure a windows path is converted to an 8.3 DOS path if it contains spaces No need to convert if there are no spaces

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path
type(error_t), intent(out), allocatable :: error

Return Value character(len=:), allocatable

public function get_local_prefix(os) result(prefix)

Determine the path prefix to the local folder. Used for installation, registry etc.

Arguments

Type IntentOptional Attributes Name
integer, intent(in), optional :: os

Platform identifier

Return Value character(len=:), allocatable

Installation prefix

public function get_temp_filename() result(tempfile)

Get a unused temporary filename Calls posix ‘tempnam’ - not recommended, but we have no security concerns for this application and use here is temporary. Works with MinGW

Arguments

None

Return Value character(len=:), allocatable

public function is_absolute_path(path, is_unix)

Returns .true. if provided path is absolute.

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path
logical, intent(in), optional :: is_unix

Return Value logical

public function is_dir(dir)

test if a name matches an existing directory path

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: dir

Return Value logical

public function is_hidden_file(file_basename) result(r)

test if a file is hidden

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: file_basename

Return Value logical

public function join_path(a1, a2, a3, a4, a5) result(path)

Construct path by joining strings with os file separator

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: a1
character(len=*), intent(in) :: a2
character(len=*), intent(in), optional :: a3
character(len=*), intent(in), optional :: a4
character(len=*), intent(in), optional :: a5

Return Value character(len=:), allocatable

public function number_of_rows(s) result(nrows)

Determine number or rows in a file given a LUN

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: s

Return Value integer

public function parent_dir(path) result(dir)

Extract dirname from path

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path

Return Value character(len=:), allocatable

public function read_lines(filename) result(lines)

read lines into an array of TYPE(STRING_T) variables

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename

Return Value type(string_t), allocatable, (:)

public function read_lines_expanded(filename) result(lines)

read lines into an array of TYPE(STRING_T) variables expanding tabs

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename

Return Value type(string_t), allocatable, (:)

public function unix_path(path) result(nixpath)

Replace file system separators for unix

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path

Return Value character(len=:), allocatable

public function which(command) result(pathname)

Author
John S. Urban
License
Public Domain

function which(command) result(pathname)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: command

Return Value character(len=:), allocatable

public function windows_path(path) result(winpath)

Replace file system separators for windows

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: path

Return Value character(len=:), allocatable


Subroutines

public subroutine delete_file(file)

delete a file by filename

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: file

public subroutine execute_and_read_output(cmd, output, error, verbose)

Execute command line and return output as a string.

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: cmd

Command to execute.

character(len=:), intent(out), allocatable :: output

Command line output.

type(error_t), intent(out), allocatable :: error

Error to handle.

logical, intent(in), optional :: verbose

Print additional information if true.

public subroutine fileclose(lun, ier)

simple close of a LUN. On error show message and stop (by default)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: lun
integer, intent(out), optional :: ier

public subroutine fileopen(filename, lun, ier)

procedure to open filename as a sequential “text” file

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
integer, intent(out) :: lun
integer, intent(out), optional :: ier

public subroutine filewrite(filename, filedata)

procedure to write filedata to file filename

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
character(len=*), intent(in) :: filedata(:)

public subroutine get_home(home, error)

Get the HOME directory on Unix and the %USERPROFILE% directory on Windows.

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(out), allocatable :: home
type(error_t), intent(out), allocatable :: error

public subroutine getline(unit, line, iostat, iomsg)

Author
fpm(1) contributors
License
MIT

subroutine getline(unit,line,iostat,iomsg)

Read more…

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: unit

Formatted IO unit

character(len=:), intent(out), allocatable :: line

Line to read

integer, intent(out) :: iostat

Status of operation

character(len=:), optional, allocatable :: iomsg

Error message

public recursive subroutine list_files(dir, files, recurse)

Get file & directory names in directory dir using iso_c_binding.

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: dir
type(string_t), intent(out), allocatable :: files(:)
logical, intent(in), optional :: recurse

public subroutine mkdir(dir, echo)

Create a directory. Create subdirectories as needed

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: dir
logical, intent(in), optional :: echo

public subroutine os_delete_dir(is_unix, dir, echo)

Delete directory using system OS remove directory commands

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: is_unix
character(len=*), intent(in) :: dir
logical, intent(in), optional :: echo

public subroutine run(cmd, echo, exitstat, verbose, redirect)

Author
fpm(1) contributors
License
MIT

Execute the specified system command. Optionally

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: cmd
logical, intent(in), optional :: echo
integer, intent(out), optional :: exitstat
logical, intent(in), optional :: verbose
character(len=*), intent(in), optional :: redirect

public subroutine warnwrite(fname, data)

write trimmed character data to a file if it does not exist

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fname
character(len=*), intent(in) :: data(:)