Skip to content

Commit 73e3171

Browse files
committed
a little more documentation
1 parent 58d64b5 commit 73e3171

File tree

4 files changed

+22
-6
lines changed

4 files changed

+22
-6
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: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,8 +14,8 @@ module fpm_environment
1414
integer, parameter, public :: OS_SOLARIS = 5
1515
integer, parameter, public :: OS_FREEBSD = 6
1616
contains
17+
!> Determine the OS type
1718
integer function get_os_type() result(r)
18-
!! Determine the OS type
1919
!!
2020
!! Returns one of OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, OS_CYGWIN,
2121
!! OS_SOLARIS, OS_FREEBSD.
@@ -106,6 +106,9 @@ integer function get_os_type() result(r)
106106
end if
107107
end function get_os_type
108108

109+
!> Compare the output of [[get_os_type]] or the optional
110+
!! passed INTEGER value to the value for OS_WINDOWS
111+
!! and return .TRUE. if they match and .FALSE. otherwise
109112
logical function os_is_unix(os) result(unix)
110113
integer, intent(in), optional :: os
111114
integer :: build_os
@@ -117,6 +120,7 @@ logical function os_is_unix(os) result(unix)
117120
unix = os /= OS_WINDOWS
118121
end function os_is_unix
119122

123+
!> echo command string and pass it to the system for execution
120124
subroutine run(cmd,echo)
121125
character(len=*), intent(in) :: cmd
122126
logical,intent(in),optional :: echo
@@ -137,10 +141,15 @@ subroutine run(cmd,echo)
137141
end if
138142
end subroutine run
139143

144+
!> get named environment variable value. It it is blank or
145+
!! not set return the optional default value
140146
function get_env(NAME,DEFAULT) result(VALUE)
141147
implicit none
142-
character(len=*),intent(in) :: NAME
148+
!> name of environment variable to get the value of
149+
character(len=*),intent(in) :: NAME
150+
!> default value to return if the requested value is undefined or blank
143151
character(len=*),intent(in),optional :: DEFAULT
152+
!> the returned value
144153
character(len=:),allocatable :: VALUE
145154
integer :: howbig
146155
integer :: stat

fpm/src/fpm_strings.f90

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
!> This module defines general procedures for **string operations** for both CHARACTER and
2+
!! TYPE(STRING_T) variables
3+
!
14
!>## general routines for performing __string operations__
25
!!
36
!!### Types

0 commit comments

Comments
 (0)