Skip to content

Commit 482a52b

Browse files
authored
Merge pull request #378 from urbanjost/ford-ify
Add ford-compatible documentation to fpm_strings.f90
2 parents 79d7fb6 + 6c03afd commit 482a52b

File tree

5 files changed

+182
-130
lines changed

5 files changed

+182
-130
lines changed

fpm/src/fpm_command_line.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@
1515
!> wanted command line and the expected default values.
1616
!> Some of the following points also apply if you add a new option or argument
1717
!> to an existing *fpm* subcommand.
18-
!> Add this point you should create a help page for the new command in a simple
18+
!> At this point you should create a help page for the new command in a simple
1919
!> catman-like format as well in the ``set_help`` procedure.
2020
!> Make sure to register new subcommands in the ``fpm-manual`` command by adding
2121
!> them to the manual character array and in the help/manual case as well.

fpm/src/fpm_compiler.f90

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,18 @@
1+
!># Define compiler command options
2+
!!
3+
!! This module defines compiler options to use for the debug and release builds.
14
module fpm_compiler
25
use fpm_model, only: fpm_model_t
36
use fpm_filesystem, only: join_path
47
public add_compile_flag_defaults
58

69
contains
10+
!> Choose compile flags based on cli settings & manifest inputs
711
subroutine add_compile_flag_defaults(build_name,compiler,model)
8-
! Choose compile flags based on cli settings & manifest inputs
9-
character(len=*),intent(in) :: build_name, compiler
12+
character(len=*),intent(in) :: build_name !! select build from {release,debug}
13+
character(len=*),intent(in) :: compiler !! compiler name
14+
type(fpm_model_t), intent(inout) :: model !! model to add compiler options to
1015

11-
type(fpm_model_t), intent(inout) :: model
1216
! could just be a function to return a string instead of passing model
1317
! but likely to change other components like matching C compiler
1418

fpm/src/fpm_environment.f90

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,7 @@
1+
!> This module contains procedures that interact with the programming environment.
2+
!!
3+
!! * [get_os_type] -- Determine the OS type
4+
!! * [get_env] -- return the value of an environment variable
15
module fpm_environment
26
implicit none
37
private
@@ -14,8 +18,8 @@ module fpm_environment
1418
integer, parameter, public :: OS_SOLARIS = 5
1519
integer, parameter, public :: OS_FREEBSD = 6
1620
contains
21+
!> Determine the OS type
1722
integer function get_os_type() result(r)
18-
!! Determine the OS type
1923
!!
2024
!! Returns one of OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, OS_CYGWIN,
2125
!! OS_SOLARIS, OS_FREEBSD.
@@ -106,6 +110,9 @@ integer function get_os_type() result(r)
106110
end if
107111
end function get_os_type
108112

113+
!> Compare the output of [[get_os_type]] or the optional
114+
!! passed INTEGER value to the value for OS_WINDOWS
115+
!! and return .TRUE. if they match and .FALSE. otherwise
109116
logical function os_is_unix(os) result(unix)
110117
integer, intent(in), optional :: os
111118
integer :: build_os
@@ -117,6 +124,7 @@ logical function os_is_unix(os) result(unix)
117124
unix = os /= OS_WINDOWS
118125
end function os_is_unix
119126

127+
!> echo command string and pass it to the system for execution
120128
subroutine run(cmd,echo)
121129
character(len=*), intent(in) :: cmd
122130
logical,intent(in),optional :: echo
@@ -137,10 +145,15 @@ subroutine run(cmd,echo)
137145
end if
138146
end subroutine run
139147

148+
!> get named environment variable value. It it is blank or
149+
!! not set return the optional default value
140150
function get_env(NAME,DEFAULT) result(VALUE)
141151
implicit none
142-
character(len=*),intent(in) :: NAME
152+
!> name of environment variable to get the value of
153+
character(len=*),intent(in) :: NAME
154+
!> default value to return if the requested value is undefined or blank
143155
character(len=*),intent(in),optional :: DEFAULT
156+
!> the returned value
144157
character(len=:),allocatable :: VALUE
145158
integer :: howbig
146159
integer :: stat

fpm/src/fpm_filesystem.f90

Lines changed: 42 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
!> This module contains general routines for interacting with the file system
2+
!!
13
module fpm_filesystem
24
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
35
use fpm_environment, only: get_os_type, &
@@ -15,6 +17,7 @@ module fpm_filesystem
1517
contains
1618

1719

20+
!> return value of environment variable
1821
subroutine env_variable(var, name)
1922
character(len=:), allocatable, intent(out) :: var
2023
character(len=*), intent(in) :: name
@@ -36,9 +39,9 @@ subroutine env_variable(var, name)
3639
end subroutine env_variable
3740

3841

42+
!> Extract filename from path with/without suffix
3943
function basename(path,suffix) result (base)
40-
! Extract filename from path with/without suffix
41-
!
44+
4245
character(*), intent(In) :: path
4346
logical, intent(in), optional :: suffix
4447
character(:), allocatable :: base
@@ -71,13 +74,13 @@ function basename(path,suffix) result (base)
7174
end function basename
7275

7376

77+
!> Canonicalize path for comparison
78+
!! * Handles path string redundancies
79+
!! * Does not test existence of path
80+
!!
81+
!! To be replaced by realpath/_fullname in stdlib_os
82+
!!
7483
function canon_path(path) result(canon)
75-
! Canonicalize path for comparison
76-
! Handles path string redundancies
77-
! Does not test existence of path
78-
!
79-
! To be replaced by realpath/_fullname in stdlib_os
80-
!
8184
character(*), intent(in) :: path
8285
character(:), allocatable :: canon
8386

@@ -141,9 +144,8 @@ function canon_path(path) result(canon)
141144
end function canon_path
142145

143146

147+
!> Extract dirname from path
144148
function dirname(path) result (dir)
145-
! Extract dirname from path
146-
!
147149
character(*), intent(in) :: path
148150
character(:), allocatable :: dir
149151

@@ -152,6 +154,7 @@ function dirname(path) result (dir)
152154
end function dirname
153155

154156

157+
!> test if a name matches an existing directory path
155158
logical function is_dir(dir)
156159
character(*), intent(in) :: dir
157160
integer :: stat
@@ -171,9 +174,9 @@ logical function is_dir(dir)
171174
end function is_dir
172175

173176

177+
!> Construct path by joining strings with os file separator
174178
function join_path(a1,a2,a3,a4,a5) result(path)
175-
! Construct path by joining strings with os file separator
176-
!
179+
177180
character(len=*), intent(in) :: a1, a2
178181
character(len=*), intent(in), optional :: a3, a4, a5
179182
character(len=:), allocatable :: path
@@ -209,8 +212,8 @@ function join_path(a1,a2,a3,a4,a5) result(path)
209212
end function join_path
210213

211214

215+
!> Determine number or rows in a file given a LUN
212216
integer function number_of_rows(s) result(nrows)
213-
! determine number or rows
214217
integer,intent(in)::s
215218
integer :: ios
216219
character(len=100) :: r
@@ -225,6 +228,7 @@ integer function number_of_rows(s) result(nrows)
225228
end function number_of_rows
226229

227230

231+
!> read lines into an array of TYPE(STRING_T) variables
228232
function read_lines(fh) result(lines)
229233
integer, intent(in) :: fh
230234
type(string_t), allocatable :: lines(:)
@@ -240,6 +244,7 @@ function read_lines(fh) result(lines)
240244

241245
end function read_lines
242246

247+
!> Create a directory. Create subdirectories as needed
243248
subroutine mkdir(dir)
244249
character(len=*), intent(in) :: dir
245250
integer :: stat
@@ -263,12 +268,12 @@ subroutine mkdir(dir)
263268
end subroutine mkdir
264269

265270

271+
!> Get file & directory names in directory `dir`.
272+
!!
273+
!! - File/directory names return are relative to cwd, ie. preprended with `dir`
274+
!! - Includes files starting with `.` except current directory and parent directory
275+
!!
266276
recursive subroutine list_files(dir, files, recurse)
267-
! Get file & directory names in directory `dir`.
268-
!
269-
! - File/directory names return are relative to cwd, ie. preprended with `dir`
270-
! - Includes files starting with `.` except current directory and parent directory
271-
!
272277
character(len=*), intent(in) :: dir
273278
type(string_t), allocatable, intent(out) :: files(:)
274279
logical, intent(in), optional :: recurse
@@ -329,18 +334,19 @@ recursive subroutine list_files(dir, files, recurse)
329334
end subroutine list_files
330335

331336

337+
!> test if pathname already exists
332338
logical function exists(filename) result(r)
333339
character(len=*), intent(in) :: filename
334340
inquire(file=filename, exist=r)
335341
end function
336342

337343

344+
!> Get a unused temporary filename
345+
!! Calls posix 'tempnam' - not recommended, but
346+
!! we have no security concerns for this application
347+
!! and use here is temporary.
348+
!! Works with MinGW
338349
function get_temp_filename() result(tempfile)
339-
! Get a unused temporary filename
340-
! Calls posix 'tempnam' - not recommended, but
341-
! we have no security concerns for this application
342-
! and use here is temporary.
343-
! Works with MinGW
344350
!
345351
use iso_c_binding, only: c_ptr, C_NULL_PTR, c_f_pointer
346352
character(:), allocatable :: tempfile
@@ -374,9 +380,9 @@ end subroutine c_free
374380
end function get_temp_filename
375381

376382

383+
!> Replace file system separators for windows
377384
function windows_path(path) result(winpath)
378-
! Replace file system separators for windows
379-
!
385+
380386
character(*), intent(in) :: path
381387
character(:), allocatable :: winpath
382388

@@ -393,9 +399,9 @@ function windows_path(path) result(winpath)
393399
end function windows_path
394400

395401

402+
!> Replace file system separators for unix
396403
function unix_path(path) result(nixpath)
397-
! Replace file system separators for unix
398-
!
404+
399405
character(*), intent(in) :: path
400406
character(:), allocatable :: nixpath
401407

@@ -412,6 +418,7 @@ function unix_path(path) result(nixpath)
412418
end function unix_path
413419

414420

421+
!> read a line of arbitrary length into a CHARACTER variable from the specified LUN
415422
subroutine getline(unit, line, iostat, iomsg)
416423

417424
!> Formatted IO unit
@@ -453,6 +460,7 @@ subroutine getline(unit, line, iostat, iomsg)
453460
end subroutine getline
454461

455462

463+
!> delete a file by filename
456464
subroutine delete_file(file)
457465
character(len=*), intent(in) :: file
458466
logical :: exist
@@ -464,8 +472,8 @@ subroutine delete_file(file)
464472
end if
465473
end subroutine delete_file
466474

467-
subroutine warnwrite(fname,data)
468475
!> write trimmed character data to a file if it does not exist
476+
subroutine warnwrite(fname,data)
469477
character(len=*),intent(in) :: fname
470478
character(len=*),intent(in) :: data(:)
471479

@@ -478,8 +486,8 @@ subroutine warnwrite(fname,data)
478486

479487
end subroutine warnwrite
480488

489+
!> procedure to open filename as a sequential "text" file
481490
subroutine fileopen(filename,lun,ier)
482-
! procedure to open filename as a sequential "text" file
483491

484492
character(len=*),intent(in) :: filename
485493
integer,intent(out) :: lun
@@ -516,8 +524,8 @@ subroutine fileopen(filename,lun,ier)
516524

517525
end subroutine fileopen
518526

527+
!> simple close of a LUN. On error show message and stop (by default)
519528
subroutine fileclose(lun,ier)
520-
! simple close of a LUN. On error show message and stop (by default)
521529
integer,intent(in) :: lun
522530
integer,intent(out),optional :: ier
523531
character(len=256) :: message
@@ -535,8 +543,8 @@ subroutine fileclose(lun,ier)
535543
endif
536544
end subroutine fileclose
537545

546+
!> procedure to write filedata to file filename
538547
subroutine filewrite(filename,filedata)
539-
! procedure to write filedata to file filename
540548

541549
character(len=*),intent(in) :: filename
542550
character(len=*),intent(in) :: filedata(:)
@@ -560,10 +568,10 @@ subroutine filewrite(filename,filedata)
560568

561569
end subroutine filewrite
562570

571+
!> Returns string with special characters replaced with an underscore.
572+
!! For now, only a hyphen is treated as a special character, but this can be
573+
!! expanded to other characters if needed.
563574
pure function to_fortran_name(string) result(res)
564-
! Returns string with special characters replaced with an underscore.
565-
! For now, only a hyphen is treated as a special character, but this can be
566-
! expanded to other characters if needed.
567575
character(*), intent(in) :: string
568576
character(len(string)) :: res
569577
character, parameter :: SPECIAL_CHARACTERS(*) = ['-']

0 commit comments

Comments
 (0)