aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorMilan Curcic <caomaco@gmail.com>2020-09-03 11:15:43 -0400
committerMilan Curcic <caomaco@gmail.com>2020-09-03 11:15:43 -0400
commit07c5828c9843e6e64aab50b7407bec05e38e27b3 (patch)
treea42690ee13b42998ec0b8b70b124047d2fb2beca
parentf85f291ba5ebd66bbb258e2dc859f4dcc95017c5 (diff)
downloadfpm-07c5828c9843e6e64aab50b7407bec05e38e27b3.tar.gz
fpm-07c5828c9843e6e64aab50b7407bec05e38e27b3.zip
explicit imports throughout; reorder imports alphabetically; explicitly declare public names
-rw-r--r--fpm/src/fpm.f9012
-rw-r--r--fpm/src/fpm_backend.f9017
-rw-r--r--fpm/src/fpm_command_line.f9021
-rw-r--r--fpm/src/fpm_environment.f909
-rw-r--r--fpm/src/fpm_filesystem.f9018
-rw-r--r--fpm/src/fpm_model.f9021
-rw-r--r--fpm/src/fpm_sources.f9029
-rw-r--r--fpm/src/fpm_strings.f905
8 files changed, 79 insertions, 53 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 4fb6bd4..5e27701 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -1,12 +1,12 @@
module fpm
-use fpm_strings
-use fpm_command_line
-use fpm_manifest
-use fpm_model
+
+use fpm_backend, only: build_package
+use fpm_command_line, only: fpm_build_settings
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
use fpm_filesystem, only: number_of_rows, list_files, exists
-use fpm_sources
-use fpm_backend
+use fpm_manifest, only: fpm_manifest_t
+use fpm_model, only: build_model, fpm_model_t
+
implicit none
private
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 475dcdd..07cd646 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -1,11 +1,14 @@
module fpm_backend
+
! Implements the native fpm build backend
-!
-use fpm_strings
-use fpm_environment
-use fpm_sources
-use fpm_model
-use fpm_filesystem
+
+use fpm_environment, only: run
+use fpm_filesystem, only: exists, mkdir
+use fpm_model, only: fpm_model_t
+use fpm_sources, only: srcfile_t, FPM_UNIT_MODULE, FPM_UNIT_SUBMODULE, &
+ FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM
+use fpm_strings, only: split
+
implicit none
private
@@ -102,4 +105,4 @@ recursive subroutine build_source(model,source_file,linking)
end subroutine build_source
-end module fpm_backend \ No newline at end of file
+end module fpm_backend
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index 9902110..5e9daee 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -2,27 +2,34 @@ module fpm_command_line
use fpm_environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
implicit none
+
private
+ public :: fpm_cmd_settings, &
+ fpm_build_settings, &
+ fpm_install_settings, &
+ fpm_new_settings, &
+ fpm_run_settings, &
+ fpm_test_settings, &
+ get_command_line_settings
- type, public, abstract :: fpm_cmd_settings
+ type, abstract :: fpm_cmd_settings
end type
- type, public, extends(fpm_cmd_settings) :: fpm_new_settings
+ type, extends(fpm_cmd_settings) :: fpm_new_settings
end type
- type, public, extends(fpm_cmd_settings) :: fpm_build_settings
+ type, extends(fpm_cmd_settings) :: fpm_build_settings
end type
- type, public, extends(fpm_cmd_settings) :: fpm_run_settings
+ type, extends(fpm_cmd_settings) :: fpm_run_settings
end type
- type, public, extends(fpm_cmd_settings) :: fpm_test_settings
+ type, extends(fpm_cmd_settings) :: fpm_test_settings
end type
- type, public, extends(fpm_cmd_settings) :: fpm_install_settings
+ type, extends(fpm_cmd_settings) :: fpm_install_settings
end type
- public :: get_command_line_settings
contains
subroutine get_command_line_settings(cmd_settings)
class(fpm_cmd_settings), allocatable, intent(out) :: cmd_settings
diff --git a/fpm/src/fpm_environment.f90 b/fpm/src/fpm_environment.f90
index 5ef7e18..9ac42ac 100644
--- a/fpm/src/fpm_environment.f90
+++ b/fpm/src/fpm_environment.f90
@@ -1,12 +1,13 @@
module fpm_environment
implicit none
private
+ public :: get_os_type, run
+ public :: OS_LINUX, OS_MACOS, OS_WINDOWS
- integer, parameter, public :: OS_LINUX = 1
- integer, parameter, public :: OS_MACOS = 2
- integer, parameter, public :: OS_WINDOWS = 3
+ integer, parameter :: OS_LINUX = 1
+ integer, parameter :: OS_MACOS = 2
+ integer, parameter :: OS_WINDOWS = 3
- public :: get_os_type, run
contains
integer function get_os_type() result(r)
! Determine the OS type
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index c531e84..a86e813 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -1,10 +1,11 @@
module fpm_filesystem
-use fpm_strings
use fpm_environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
+use fpm_strings, only: f_string, string_t
implicit none
private
-public :: number_of_rows, read_lines, list_files, mkdir, exists, get_temp_filename
+public :: number_of_rows, read_lines, list_files, mkdir, exists, &
+ get_temp_filename
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -79,11 +80,14 @@ subroutine list_files(dir, files)
select case (get_os_type())
case (OS_LINUX)
- call execute_command_line("ls " // dir // " > "//temp_file, exitstat=stat)
+ call execute_command_line("ls " // dir // " > "//temp_file, &
+ exitstat=stat)
case (OS_MACOS)
- call execute_command_line("ls " // dir // " > "//temp_file, exitstat=stat)
+ call execute_command_line("ls " // dir // " > "//temp_file, &
+ exitstat=stat)
case (OS_WINDOWS)
- call execute_command_line("dir /b " // dir // " > "//temp_file, exitstat=stat)
+ call execute_command_line("dir /b " // dir // " > "//temp_file, &
+ exitstat=stat)
end select
if (stat /= 0) then
print *, "execute_command_line() failed"
@@ -118,7 +122,7 @@ function get_temp_filename() result(tempfile)
interface
- function c_tempnam(dir,pfx) result(tmp) BIND(C,name="tempnam")
+ function c_tempnam(dir,pfx) result(tmp) bind(c,name="tempnam")
import
type(c_ptr), intent(in), value :: dir
type(c_ptr), intent(in), value :: pfx
@@ -142,4 +146,4 @@ function get_temp_filename() result(tempfile)
end function get_temp_filename
-end module fpm_filesystem \ No newline at end of file
+end module fpm_filesystem
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index c1489cf..b519c87 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -1,14 +1,19 @@
module fpm_model
+
! Definition and validation of the backend model
-!
-use fpm_strings
-use fpm_sources
-use fpm_command_line
-use fpm_filesystem
-use fpm_manifest
+
+use fpm_command_line, only: fpm_build_settings
+use fpm_filesystem, only: exists
+use fpm_manifest, only: fpm_manifest_t
+use fpm_sources, only: resolve_dependencies, scan_sources, srcfile_t
+use fpm_strings, only: string_t
+
implicit none
-type fpm_model_t
+private
+public :: build_model, fpm_model_t
+
+type :: fpm_model_t
character(:), allocatable :: package_name
! Name of package
type(srcfile_t), allocatable :: sources(:)
@@ -52,4 +57,4 @@ subroutine build_model(model, settings, manifest)
end subroutine build_model
-end module fpm_model \ No newline at end of file
+end module fpm_model
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index 2960339..ab0f68a 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -1,19 +1,22 @@
module fpm_sources
-use fpm_strings
use fpm_filesystem, only: read_lines, list_files
+use fpm_strings, only: lower, split, str_ends_with, string_t
implicit none
private
-public srcfile_ptr, srcfile_t
-public scan_sources, resolve_dependencies
-
-integer, parameter, public :: FPM_UNIT_UNKNOWN = -1
-integer, parameter, public :: FPM_UNIT_PROGRAM = 1
-integer, parameter, public :: FPM_UNIT_MODULE = 2
-integer, parameter, public :: FPM_UNIT_SUBMODULE = 3
-integer, parameter, public :: FPM_UNIT_SUBPROGRAM = 4
-integer, parameter, public :: FPM_UNIT_CSOURCE = 5
-integer, parameter, public :: FPM_UNIT_CHEADER = 6
+public :: srcfile_ptr, srcfile_t
+public :: scan_sources, resolve_dependencies
+public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
+ FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
+ FPM_UNIT_CHEADER
+
+integer, parameter :: FPM_UNIT_UNKNOWN = -1
+integer, parameter :: FPM_UNIT_PROGRAM = 1
+integer, parameter :: FPM_UNIT_MODULE = 2
+integer, parameter :: FPM_UNIT_SUBMODULE = 3
+integer, parameter :: FPM_UNIT_SUBPROGRAM = 4
+integer, parameter :: FPM_UNIT_CSOURCE = 5
+integer, parameter :: FPM_UNIT_CHEADER = 6
character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
['iso_c_binding ', &
@@ -21,7 +24,7 @@ character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
type srcfile_ptr
! For constructing arrays of src_file pointers
- type(srcfile_t), pointer :: ptr => NULL()
+ type(srcfile_t), pointer :: ptr => null()
end type srcfile_ptr
type srcfile_t
@@ -415,4 +418,4 @@ function find_module_dependency(sources,module_name) result(src_ptr)
end function find_module_dependency
-end module fpm_sources \ No newline at end of file
+end module fpm_sources
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
index 09fa3c0..dd18f09 100644
--- a/fpm/src/fpm_strings.f90
+++ b/fpm/src/fpm_strings.f90
@@ -1,6 +1,9 @@
module fpm_strings
implicit none
+private
+public :: f_string, lower, split, str_ends_with, string_t
+
type string_t
character(len=:), allocatable :: s
end type
@@ -192,4 +195,4 @@ subroutine split(input_line,array,delimiters,order,nulls)
end subroutine split
-end module fpm_strings \ No newline at end of file
+end module fpm_strings