aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rwxr-xr-xci/run_tests.bat21
-rwxr-xr-xci/run_tests.sh10
-rw-r--r--fpm/app/main.f906
-rw-r--r--fpm/src/fpm.f90156
-rw-r--r--fpm/src/fpm_backend.f90123
-rw-r--r--fpm/src/fpm_command_line.f90 (renamed from fpm/src/command_line.f90)27
-rw-r--r--fpm/src/fpm_environment.f90 (renamed from fpm/src/environment.f90)25
-rw-r--r--fpm/src/fpm_filesystem.f90234
-rw-r--r--fpm/src/fpm_model.f9065
-rw-r--r--fpm/src/fpm_sources.f90468
-rw-r--r--fpm/src/fpm_strings.f90217
11 files changed, 1226 insertions, 126 deletions
diff --git a/ci/run_tests.bat b/ci/run_tests.bat
index 33d7071..9435e0d 100755
--- a/ci/run_tests.bat
+++ b/ci/run_tests.bat
@@ -21,5 +21,24 @@ if errorlevel 1 exit 1
..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
-.\hello_world
+.\build\gfortran_debug\app\hello_world
if errorlevel 1 exit 1
+
+
+cd ..\hello_complex
+if errorlevel 1 exit 1
+
+..\..\..\fpm\build\gfortran_debug\app\fpm build
+if errorlevel 1 exit 1
+
+.\build\gfortran_debug\app\say_Hello
+if errorlevel 1 exit 1
+
+.\build\gfortran_debug\app\say_goodbye
+if errorlevel 1 exit 1
+
+.\build\gfortran_debug\test\greet_test
+if errorlevel 1 exit 1
+
+.\build\gfortran_debug\test\farewell_test
+if errorlevel 1 exit 1 \ No newline at end of file
diff --git a/ci/run_tests.sh b/ci/run_tests.sh
index c740cd8..3033c2a 100755
--- a/ci/run_tests.sh
+++ b/ci/run_tests.sh
@@ -7,6 +7,14 @@ fpm build
fpm run
fpm test
build/gfortran_debug/app/fpm
+
cd ../test/example_packages/hello_world
../../../fpm/build/gfortran_debug/app/fpm build
-./hello_world
+./build/gfortran_debug/app/hello_world
+
+cd ../hello_complex
+../../../fpm/build/gfortran_debug/app/fpm build
+./build/gfortran_debug/app/say_Hello
+./build/gfortran_debug/app/say_goodbye
+./build/gfortran_debug/test/greet_test
+./build/gfortran_debug/test/farewell_test \ No newline at end of file
diff --git a/fpm/app/main.f90 b/fpm/app/main.f90
index 30abf5b..c7f9786 100644
--- a/fpm/app/main.f90
+++ b/fpm/app/main.f90
@@ -1,5 +1,5 @@
program main
-use command_line, only: &
+use fpm_command_line, only: &
fpm_cmd_settings, &
fpm_new_settings, &
fpm_build_settings, &
@@ -15,11 +15,11 @@ class(fpm_cmd_settings), allocatable :: cmd_settings
call get_command_line_settings(cmd_settings)
-select type(cmd_settings)
+select type(settings=>cmd_settings)
type is (fpm_new_settings)
call cmd_new()
type is (fpm_build_settings)
- call cmd_build()
+ call cmd_build(settings)
type is (fpm_run_settings)
call cmd_run()
type is (fpm_test_settings)
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 9c8918b..29d663c 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -1,99 +1,61 @@
module fpm
-use environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
-use fpm_manifest, only : get_package_data, default_executable, default_library, &
- & package_t
+
+use fpm_strings, only: string_t, str_ends_with
+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: join_path, number_of_rows, list_files, exists
+use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
+use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
+ resolve_module_dependencies
+use fpm_manifest, only : get_package_data, default_executable, &
+ default_library, package_t
use fpm_error, only : error_t
implicit none
private
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
-type string_t
- character(len=:), allocatable :: s
-end type
contains
-integer function number_of_rows(s) result(nrows)
-! determine number or rows
-integer,intent(in)::s
-integer :: ios
-character(len=100) :: r
-rewind(s)
-nrows = 0
-do
- read(s, *, iostat=ios) r
- if (ios /= 0) exit
- nrows = nrows + 1
-end do
-rewind(s)
-end function
-
-
-subroutine list_files(dir, files)
-character(len=*), intent(in) :: dir
-type(string_t), allocatable, intent(out) :: files(:)
-character(len=100) :: filename
-integer :: stat, u, i
-! Using `inquire` / exists on directories works with gfortran, but not ifort
-if (.not. exists(dir)) then
- allocate(files(0))
- return
-end if
-select case (get_os_type())
- case (OS_LINUX)
- call execute_command_line("ls " // dir // " > fpm_ls.out", exitstat=stat)
- case (OS_MACOS)
- call execute_command_line("ls " // dir // " > fpm_ls.out", exitstat=stat)
- case (OS_WINDOWS)
- call execute_command_line("dir /b " // dir // " > fpm_ls.out", exitstat=stat)
-end select
-if (stat /= 0) then
- print *, "execute_command_line() failed"
- error stop
-end if
-open(newunit=u, file="fpm_ls.out", status="old")
-allocate(files(number_of_rows(u)))
-do i = 1, size(files)
- read(u, *) filename
- files(i)%s = trim(filename)
-end do
-close(u)
-end subroutine
-
-subroutine run(cmd)
-character(len=*), intent(in) :: cmd
-integer :: stat
-print *, "+ ", cmd
-call execute_command_line(cmd, exitstat=stat)
-if (stat /= 0) then
- print *, "Command failed"
- error stop
-end if
-end subroutine
-
-logical function exists(filename) result(r)
-character(len=*), intent(in) :: filename
-inquire(file=filename, exist=r)
-end function
-
-logical function str_ends_with(s, e) result(r)
-character(*), intent(in) :: s, e
-integer :: n1, n2
-n1 = len(s)-len(e)+1
-n2 = len(s)
-if (n1 < 1) then
- r = .false.
-else
- r = (s(n1:n2) == e)
-end if
-end function
-
-subroutine cmd_build()
+subroutine build_model(model, settings, package)
+ ! Constructs a valid fpm model from command line settings and toml manifest
+ !
+ type(fpm_model_t), intent(out) :: model
+ type(fpm_build_settings), intent(in) :: settings
+ type(package_t), intent(in) :: package
+
+ model%package_name = package%name
+
+ ! #TODO: Choose flags and output directory based on cli settings & manifest inputs
+ model%fortran_compiler = 'gfortran'
+ model%output_directory = 'build/gfortran_debug'
+ model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
+ '-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
+ '-J'//join_path(model%output_directory,model%package_name)
+ model%link_flags = ''
+
+ ! Add sources from executable directories
+ if (allocated(package%executable)) then
+ call add_executable_sources(model%sources, package%executable,is_test=.false.)
+ end if
+ if (allocated(package%test)) then
+ call add_executable_sources(model%sources, package%test,is_test=.true.)
+ end if
+
+ if (allocated(package%library)) then
+ call add_sources_from_dir(model%sources,package%library%source_dir)
+ end if
+
+ call resolve_module_dependencies(model%sources)
+
+end subroutine build_model
+
+subroutine cmd_build(settings)
+type(fpm_build_settings), intent(in) :: settings
type(package_t) :: package
+type(fpm_model_t) :: model
type(error_t), allocatable :: error
-type(string_t), allocatable :: files(:)
-character(:), allocatable :: basename, linking
-integer :: i, n
call get_package_data(package, "fpm.toml", error)
if (allocated(error)) then
print '(a)', error%message
@@ -102,6 +64,7 @@ end if
! Populate library in case we find the default src directory
if (.not.allocated(package%library) .and. exists("src")) then
+ allocate(package%library)
call default_library(package%library)
end if
@@ -116,27 +79,10 @@ if (.not.(allocated(package%library) .or. allocated(package%executable))) then
error stop 1
end if
-linking = ""
-if (allocated(package%library)) then
- call list_files(package%library%source_dir, files)
- do i = 1, size(files)
- if (str_ends_with(files(i)%s, ".f90")) then
- n = len(files(i)%s)
- basename = files(i)%s
- call run("gfortran -c " // package%library%source_dir // "/" // &
- & basename // " -o " // basename // ".o")
- linking = linking // " " // basename // ".o"
- end if
- end do
-end if
+call build_model(model, settings, package)
+
+call build_package(model)
-do i = 1, size(package%executable)
- basename = package%executable(i)%main
- call run("gfortran -c " // package%executable(i)%source_dir // "/" // &
- & basename // " -o " // basename // ".o")
- call run("gfortran " // basename // ".o " // linking // " -o " // &
- & package%executable(i)%name)
-end do
end subroutine
subroutine cmd_install()
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
new file mode 100644
index 0000000..62fd242
--- /dev/null
+++ b/fpm/src/fpm_backend.f90
@@ -0,0 +1,123 @@
+module fpm_backend
+
+! Implements the native fpm build backend
+
+use fpm_environment, only: run
+use fpm_filesystem, only: basename, join_path, exists, mkdir
+use fpm_model, only: fpm_model_t, 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
+public :: build_package
+
+contains
+
+
+subroutine build_package(model)
+ type(fpm_model_t), intent(inout) :: model
+
+ integer :: i
+ character(:), allocatable :: base, linking, subdir
+
+ if (.not.exists(model%output_directory)) then
+ call mkdir(model%output_directory)
+ end if
+ if (.not.exists(join_path(model%output_directory,model%package_name))) then
+ call mkdir(join_path(model%output_directory,model%package_name))
+ end if
+
+ linking = ""
+ do i=1,size(model%sources)
+
+ if (model%sources(i)%unit_type == FPM_UNIT_MODULE .or. &
+ model%sources(i)%unit_type == FPM_UNIT_SUBMODULE .or. &
+ model%sources(i)%unit_type == FPM_UNIT_SUBPROGRAM .or. &
+ model%sources(i)%unit_type == FPM_UNIT_CSOURCE) then
+
+ call build_source(model,model%sources(i),linking)
+
+ end if
+
+ end do
+
+ if (any([(model%sources(i)%unit_type == FPM_UNIT_PROGRAM,i=1,size(model%sources))])) then
+ if (.not.exists(join_path(model%output_directory,'test'))) then
+ call mkdir(join_path(model%output_directory,'test'))
+ end if
+ if (.not.exists(join_path(model%output_directory,'app'))) then
+ call mkdir(join_path(model%output_directory,'app'))
+ end if
+ end if
+
+ do i=1,size(model%sources)
+
+ if (model%sources(i)%unit_type == FPM_UNIT_PROGRAM) then
+
+ base = basename(model%sources(i)%file_name,suffix=.false.)
+
+ if (model%sources(i)%is_test) then
+ subdir = 'test'
+ else
+ subdir = 'app'
+ end if
+
+ call run("gfortran -c " // model%sources(i)%file_name // ' '//model%fortran_compile_flags &
+ // " -o " // join_path(model%output_directory,subdir,base) // ".o")
+
+ call run("gfortran " // join_path(model%output_directory, subdir, base) // ".o "// &
+ linking //" " //model%link_flags // " -o " // &
+ join_path(model%output_directory,subdir,model%sources(i)%exe_name) )
+
+ end if
+
+ end do
+
+end subroutine build_package
+
+
+
+recursive subroutine build_source(model,source_file,linking)
+ ! Compile Fortran source, called recursively on it dependents
+ !
+ type(fpm_model_t), intent(in) :: model
+ type(srcfile_t), intent(inout) :: source_file
+ character(:), allocatable, intent(inout) :: linking
+
+ integer :: i
+ character(:), allocatable :: object_file
+
+ if (source_file%built) then
+ return
+ end if
+
+ if (source_file%touched) then
+ write(*,*) '(!) Circular dependency found with: ',source_file%file_name
+ stop
+ else
+ source_file%touched = .true.
+ end if
+
+ do i=1,size(source_file%file_dependencies)
+
+ if (associated(source_file%file_dependencies(i)%ptr)) then
+ call build_source(model,source_file%file_dependencies(i)%ptr,linking)
+ end if
+
+ end do
+
+ object_file = join_path(model%output_directory, model%package_name, &
+ basename(source_file%file_name,suffix=.false.)//'.o')
+
+ call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
+ // " -o " // object_file)
+ linking = linking // " " // object_file
+
+ source_file%built = .true.
+
+end subroutine build_source
+
+end module fpm_backend
diff --git a/fpm/src/command_line.f90 b/fpm/src/fpm_command_line.f90
index cd78904..5e9daee 100644
--- a/fpm/src/command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -1,28 +1,35 @@
-module command_line
- use environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
+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
@@ -75,4 +82,4 @@ contains
print *, " run Run a binary of the local package (not implemented)"
print *, " test Run the tests (not implemented)"
end subroutine
-end module command_line
+end module fpm_command_line
diff --git a/fpm/src/environment.f90 b/fpm/src/fpm_environment.f90
index 9190eb6..9ac42ac 100644
--- a/fpm/src/environment.f90
+++ b/fpm/src/fpm_environment.f90
@@ -1,12 +1,13 @@
-module environment
+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
contains
integer function get_os_type() result(r)
! Determine the OS type
@@ -51,4 +52,16 @@ contains
r = OS_LINUX
end if
end function
-end module
+
+ subroutine run(cmd)
+ character(len=*), intent(in) :: cmd
+ integer :: stat
+ print *, "+ ", cmd
+ call execute_command_line(cmd, exitstat=stat)
+ if (stat /= 0) then
+ print *, "Command failed"
+ error stop
+ end if
+ end subroutine run
+
+end module fpm_environment
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
new file mode 100644
index 0000000..d5c8e67
--- /dev/null
+++ b/fpm/src/fpm_filesystem.f90
@@ -0,0 +1,234 @@
+module fpm_filesystem
+use fpm_environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
+use fpm_strings, only: f_string, string_t, split
+implicit none
+
+private
+public :: basename, join_path, number_of_rows, read_lines, list_files,&
+ mkdir, exists, get_temp_filename, windows_path
+
+integer, parameter :: LINE_BUFFER_LEN = 1000
+
+contains
+
+
+function basename(path,suffix) result (base)
+ ! Extract filename from path with/without suffix
+ !
+ character(*), intent(In) :: path
+ logical, intent(in), optional :: suffix
+ character(:), allocatable :: base
+
+ character(:), allocatable :: file_parts(:)
+ logical :: with_suffix
+
+ if (.not.present(suffix)) then
+ with_suffix = .true.
+ else
+ with_suffix = suffix
+ end if
+
+ if (with_suffix) then
+ call split(path,file_parts,delimiters='\/')
+ base = trim(file_parts(size(file_parts)))
+ else
+ call split(path,file_parts,delimiters='\/.')
+ base = trim(file_parts(size(file_parts)-1))
+ end if
+
+end function basename
+
+
+function join_path(a1,a2,a3,a4,a5) result(path)
+ ! Construct path by joining strings with os file separator
+ !
+ character(*), intent(in) :: a1, a2
+ character(*), intent(in), optional :: a3,a4,a5
+ character(:), allocatable :: path
+
+ character(1) :: filesep
+
+ select case (get_os_type())
+ case (OS_LINUX,OS_MACOS)
+ filesep = '/'
+ case (OS_WINDOWS)
+ filesep = '\'
+ end select
+
+ path = a1 // filesep // a2
+
+ if (present(a3)) then
+ path = path // filesep // a3
+ else
+ return
+ end if
+
+ if (present(a4)) then
+ path = path // filesep // a4
+ else
+ return
+ end if
+
+ if (present(a5)) then
+ path = path // filesep // a5
+ else
+ return
+ end if
+
+end function join_path
+
+
+integer function number_of_rows(s) result(nrows)
+ ! determine number or rows
+ integer,intent(in)::s
+ integer :: ios
+ character(len=100) :: r
+ rewind(s)
+ nrows = 0
+ do
+ read(s, '(A)', iostat=ios) r
+ if (ios /= 0) exit
+ nrows = nrows + 1
+ end do
+ rewind(s)
+end function number_of_rows
+
+
+function read_lines(fh) result(lines)
+ integer, intent(in) :: fh
+ type(string_t), allocatable :: lines(:)
+
+ integer :: i
+ character(LINE_BUFFER_LEN) :: line_buffer
+
+ allocate(lines(number_of_rows(fh)))
+ do i = 1, size(lines)
+ read(fh, '(A)') line_buffer
+ lines(i)%s = trim(line_buffer)
+ end do
+
+end function read_lines
+
+subroutine mkdir(dir)
+ character(*), intent(in) :: dir
+
+ integer :: stat
+
+ select case (get_os_type())
+ case (OS_LINUX,OS_MACOS)
+ call execute_command_line("mkdir -p " // dir , exitstat=stat)
+ write(*,*) "mkdir -p " // dir
+ case (OS_WINDOWS)
+ call execute_command_line("mkdir " // windows_path(dir), exitstat=stat)
+ write(*,*) "mkdir " // windows_path(dir)
+ end select
+ if (stat /= 0) then
+ print *, "execute_command_line() failed"
+ error stop
+ end if
+
+end subroutine mkdir
+
+
+subroutine list_files(dir, files)
+ character(len=*), intent(in) :: dir
+ type(string_t), allocatable, intent(out) :: files(:)
+
+ integer :: stat, fh
+ character(:), allocatable :: temp_file
+
+ ! Using `inquire` / exists on directories works with gfortran, but not ifort
+ if (.not. exists(dir)) then
+ allocate(files(0))
+ return
+ end if
+
+ allocate(temp_file, source = get_temp_filename() )
+
+ select case (get_os_type())
+ case (OS_LINUX)
+ call execute_command_line("ls " // dir // " > "//temp_file, &
+ exitstat=stat)
+ case (OS_MACOS)
+ call execute_command_line("ls " // dir // " > "//temp_file, &
+ exitstat=stat)
+ case (OS_WINDOWS)
+ call execute_command_line("dir /b " // windows_path(dir) // " > "//temp_file, &
+ exitstat=stat)
+ end select
+ if (stat /= 0) then
+ print *, "execute_command_line() failed"
+ error stop
+ end if
+
+ open(newunit=fh, file=temp_file, status="old")
+ files = read_lines(fh)
+ close(fh,status="delete")
+
+end subroutine list_files
+
+
+logical function exists(filename) result(r)
+ character(len=*), intent(in) :: filename
+ inquire(file=filename, exist=r)
+end function
+
+
+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
+ !
+ use iso_c_binding, only: c_ptr, C_NULL_PTR, c_f_pointer
+ character(:), allocatable :: tempfile
+
+ type(c_ptr) :: c_tempfile_ptr
+ character(len=1), pointer :: c_tempfile(:)
+
+ interface
+
+ 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
+ type(c_ptr) :: tmp
+ end function c_tempnam
+
+ subroutine c_free(ptr) BIND(C,name="free")
+ import
+ type(c_ptr), value :: ptr
+ end subroutine c_free
+
+ end interface
+
+ c_tempfile_ptr = c_tempnam(C_NULL_PTR, C_NULL_PTR)
+ call c_f_pointer(c_tempfile_ptr,c_tempfile,[LINE_BUFFER_LEN])
+
+ tempfile = f_string(c_tempfile)
+
+ call c_free(c_tempfile_ptr)
+
+end function get_temp_filename
+
+
+function windows_path(path) result(winpath)
+ ! Replace file system separators for windows
+ !
+ character(*), intent(in) :: path
+ character(:), allocatable :: winpath
+
+ integer :: idx
+
+ winpath = path
+
+ idx = index(winpath,'/')
+ do while(idx > 0)
+ winpath(idx:idx) = '\'
+ idx = index(winpath,'/')
+ end do
+
+end function windows_path
+
+end module fpm_filesystem
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
new file mode 100644
index 0000000..702ba6f
--- /dev/null
+++ b/fpm/src/fpm_model.f90
@@ -0,0 +1,65 @@
+module fpm_model
+! Definition and validation of the backend model
+use fpm_strings, only: string_t
+implicit none
+
+private
+public :: srcfile_ptr, srcfile_t, fpm_model_t
+
+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
+
+type srcfile_ptr
+ ! For constructing arrays of src_file pointers
+ type(srcfile_t), pointer :: ptr => null()
+end type srcfile_ptr
+
+type srcfile_t
+ ! Type for encapsulating a source file
+ ! and it's metadata
+ character(:), allocatable :: file_name
+ ! File path relative to cwd
+ character(:), allocatable :: exe_name
+ ! Name of executable for FPM_UNIT_PROGRAM
+ logical :: is_test = .false.
+ ! Is executable a test?
+ type(string_t), allocatable :: modules_provided(:)
+ ! Modules provided by this source file (lowerstring)
+ integer :: unit_type = FPM_UNIT_UNKNOWN
+ ! Type of program unit
+ type(string_t), allocatable :: modules_used(:)
+ ! Modules USEd by this source file (lowerstring)
+ type(string_t), allocatable :: include_dependencies(:)
+ ! Files INCLUDEd by this source file
+ type(srcfile_ptr), allocatable :: file_dependencies(:)
+ ! Resolved source file dependencies
+
+ logical :: built = .false.
+ logical :: touched = .false.
+end type srcfile_t
+
+type :: fpm_model_t
+ character(:), allocatable :: package_name
+ ! Name of package
+ type(srcfile_t), allocatable :: sources(:)
+ ! Array of sources with module-dependencies resolved
+ character(:), allocatable :: fortran_compiler
+ ! Command line name to invoke fortran compiler
+ character(:), allocatable :: fortran_compile_flags
+ ! Command line flags passed to fortran for compilation
+ character(:), allocatable :: link_flags
+ ! Command line flags pass for linking
+ character(:), allocatable :: output_directory
+ ! Base directory for build
+end type fpm_model_t
+
+end module fpm_model
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
new file mode 100644
index 0000000..f2418b5
--- /dev/null
+++ b/fpm/src/fpm_sources.f90
@@ -0,0 +1,468 @@
+module fpm_sources
+use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
+ FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
+ FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
+ FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER
+use fpm_filesystem, only: basename, read_lines, list_files
+use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.)
+use fpm_manifest_executable, only: executable_t
+implicit none
+
+private
+public :: add_sources_from_dir, add_executable_sources, resolve_module_dependencies
+
+character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
+ ['iso_c_binding ', &
+ 'iso_fortran_env', &
+ 'ieee_arithmetic', &
+ 'ieee_exceptions', &
+ 'ieee_features ']
+
+contains
+
+subroutine add_sources_from_dir(sources,directory,with_executables)
+ ! Enumerate sources in a directory
+ !
+ type(srcfile_t), allocatable, intent(inout), target :: sources(:)
+ character(*), intent(in) :: directory
+ logical, intent(in), optional :: with_executables
+
+ integer :: i, j
+ logical, allocatable :: is_source(:), exclude_source(:)
+ type(string_t), allocatable :: file_names(:)
+ type(string_t), allocatable :: src_file_names(:)
+ type(srcfile_t), allocatable :: dir_sources(:)
+
+ ! Scan directory for sources
+ call list_files(directory, file_names)
+ file_names = [(string_t(directory//'/'//file_names(j)%s),j=1,size(file_names))]
+
+ is_source = [(str_ends_with(lower(file_names(i)%s), ".f90") .or. &
+ str_ends_with(lower(file_names(i)%s), ".c") .or. &
+ str_ends_with(lower(file_names(i)%s), ".h"),i=1,size(file_names))]
+ src_file_names = pack(file_names,is_source)
+
+ allocate(dir_sources(size(src_file_names)))
+ allocate(exclude_source(size(src_file_names)))
+
+ do i = 1, size(src_file_names)
+
+ if (str_ends_with(lower(src_file_names(i)%s), ".f90")) then
+ dir_sources(i) = parse_f_source(src_file_names(i)%s)
+ end if
+
+ if (str_ends_with(lower(src_file_names(i)%s), ".c") .or. &
+ str_ends_with(lower(src_file_names(i)%s), ".h")) then
+ dir_sources(i) = parse_c_source(src_file_names(i)%s)
+ end if
+
+ ! Exclude executables unless specified otherwise
+ exclude_source(i) = (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM)
+ if (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM .and. &
+ & present(with_executables)) then
+ if (with_executables) then
+
+ exclude_source(i) = .false.
+ dir_sources(i)%exe_name = basename(src_file_names(i)%s,suffix=.false.)
+
+ end if
+ end if
+
+ end do
+
+ if (.not.allocated(sources)) then
+ sources = pack(dir_sources,.not.exclude_source)
+ else
+ sources = [sources, pack(dir_sources,.not.exclude_source)]
+ end if
+
+end subroutine add_sources_from_dir
+
+
+subroutine add_executable_sources(sources,executables,is_test)
+ ! Add sources from executable directories specified in manifest
+ ! Only allow executables that are explicitly specified in manifest
+ !
+ type(srcfile_t), allocatable, intent(inout), target :: sources(:)
+ class(executable_t), intent(in) :: executables(:)
+ logical, intent(in) :: is_test
+
+ integer :: i, j
+
+ type(string_t), allocatable :: exe_dirs(:)
+ logical, allocatable :: exclude_source(:)
+ type(srcfile_t), allocatable :: dir_sources(:)
+
+ call get_executable_source_dirs(exe_dirs,executables)
+
+ do i=1,size(exe_dirs)
+ call add_sources_from_dir(dir_sources,exe_dirs(i)%s, &
+ with_executables=.true.)
+ end do
+
+ allocate(exclude_source(size(dir_sources)))
+
+ do i = 1, size(dir_sources)
+
+ ! Only allow executables in 'executables' list
+ exclude_source(i) = (dir_sources(i)%unit_type == FPM_UNIT_PROGRAM)
+
+ do j=1,size(executables)
+ if (basename(dir_sources(i)%file_name,suffix=.true.) == &
+ executables(j)%main) then
+ exclude_source(i) = .false.
+ dir_sources(i)%exe_name = executables(j)%name
+ dir_sources(i)%is_test = is_test
+ exit
+ end if
+ end do
+
+ end do
+
+ if (.not.allocated(sources)) then
+ sources = pack(dir_sources,.not.exclude_source)
+ else
+ sources = [sources, pack(dir_sources,.not.exclude_source)]
+ end if
+
+end subroutine add_executable_sources
+
+
+subroutine get_executable_source_dirs(exe_dirs,executables)
+ ! Build a list of unique source directories
+ ! from executables specified in manifest
+ type(string_t), allocatable, intent(inout) :: exe_dirs(:)
+ class(executable_t), intent(in) :: executables(:)
+
+ type(string_t) :: dirs_temp(size(executables))
+
+ integer :: i, n
+
+ n = 0
+ do i=1,size(executables)
+ if (.not.(executables(i)%source_dir .in. dirs_temp)) then
+
+ n = n + 1
+ dirs_temp(n)%s = executables(i)%source_dir
+
+ end if
+ end do
+
+ if (.not.allocated(exe_dirs)) then
+ exe_dirs = dirs_temp(1:n)
+ else
+ exe_dirs = [exe_dirs,dirs_temp(1:n)]
+ end if
+
+end subroutine get_executable_source_dirs
+
+
+function parse_f_source(f_filename) result(f_source)
+ ! Rudimentary scan of Fortran source file and
+ ! extract program unit name and use/include dependencies
+ !
+ character(*), intent(in) :: f_filename
+ type(srcfile_t) :: f_source
+
+ integer :: fh, n_use, n_include, n_mod, i, j, ic, pass
+ type(string_t), allocatable :: file_lines(:)
+ character(:), allocatable :: line_parts(:)
+ character(:), allocatable :: temp_string, mod_name
+
+ f_source%file_name = f_filename
+
+ open(newunit=fh,file=f_filename,status='old')
+ file_lines = read_lines(fh)
+ close(fh)
+
+ do pass = 1,2
+ n_use = 0
+ n_include = 0
+ n_mod = 0
+ file_loop: do i=1,size(file_lines)
+
+ ! Skip lines that are continued: not statements
+ if (i > 1) then
+ ic = index(file_lines(i-1)%s,'!')
+ if (ic < 1) then
+ ic = len(file_lines(i-1)%s)
+ end if
+ temp_string = trim(file_lines(i-1)%s(1:ic))
+ if (len(temp_string) > 0 .and. index(temp_string,'&') == len(temp_string)) then
+ cycle
+ end if
+ end if
+
+ ! Process 'USE' statements
+ if (index(adjustl(lower(file_lines(i)%s)),'use ') == 1 .or. &
+ index(adjustl(lower(file_lines(i)%s)),'use::') == 1) then
+
+ if (index(file_lines(i)%s,'::') > 0) then
+
+ call split(file_lines(i)%s,line_parts,delimiters=':')
+ temp_string = trim(line_parts(2))
+ call split(temp_string,line_parts,delimiters=' ,')
+ mod_name = trim(lower(line_parts(1)))
+
+ else
+
+ call split(file_lines(i)%s,line_parts,delimiters=' ,')
+ mod_name = trim(lower(line_parts(2)))
+
+ end if
+
+ if (.not.validate_name(mod_name)) then
+ cycle
+ end if
+
+ if (any([(index(mod_name,trim(INTRINSIC_MODULE_NAMES(j)))>0, &
+ j=1,size(INTRINSIC_MODULE_NAMES))])) then
+ cycle
+ end if
+
+ n_use = n_use + 1
+
+ if (pass == 2) then
+
+ f_source%modules_used(n_use)%s = mod_name
+
+ end if
+
+ end if
+
+ ! Process 'INCLUDE' statements
+ if (index(adjustl(lower(file_lines(i)%s)),'include') == 1) then
+
+ n_include = n_include + 1
+
+ if (pass == 2) then
+ call split(file_lines(i)%s,line_parts,delimiters="'"//'"')
+ f_source%include_dependencies(n_include)%s = trim(line_parts(2))
+ end if
+
+ end if
+
+ ! Extract name of module if is module
+ if (index(adjustl(lower(file_lines(i)%s)),'module ') == 1) then
+
+ call split(file_lines(i)%s,line_parts,delimiters=' ')
+
+ mod_name = adjustl(trim(lower(line_parts(2))))
+
+ if (.not.validate_name(mod_name)) then
+ cycle
+ end if
+
+ n_mod = n_mod + 1
+
+ if (pass == 2) then
+ f_source%modules_provided(n_mod) = string_t(mod_name)
+ end if
+
+ f_source%unit_type = FPM_UNIT_MODULE
+
+ end if
+
+ ! Extract name of submodule if is submodule
+ if (index(adjustl(lower(file_lines(i)%s)),'submodule') == 1) then
+
+ call split(file_lines(i)%s,line_parts,delimiters=' ()')
+
+ f_source%unit_type = FPM_UNIT_SUBMODULE
+
+ n_use = n_use + 1
+
+ if (pass == 2) then
+
+ if (index(line_parts(2),':') > 0) then
+
+ line_parts(2) = line_parts(2)(index(line_parts(2),':')+1:)
+
+ end if
+
+ f_source%modules_used(n_use)%s = adjustl(trim(lower(line_parts(2))))
+
+ end if
+
+ end if
+
+ ! Detect if is program
+ if (f_source%unit_type == FPM_UNIT_UNKNOWN .and. &
+ index(adjustl(lower(file_lines(i)%s)),'program') == 1) then
+
+ f_source%unit_type = FPM_UNIT_PROGRAM
+
+ end if
+
+ end do file_loop
+
+ ! Default to subprogram unit type
+ if (f_source%unit_type == FPM_UNIT_UNKNOWN) then
+ f_source%unit_type = FPM_UNIT_SUBPROGRAM
+ end if
+
+ if (pass == 1) then
+ allocate(f_source%modules_used(n_use))
+ allocate(f_source%include_dependencies(n_include))
+ allocate(f_source%modules_provided(n_mod))
+ end if
+
+ end do
+
+ contains
+
+ function validate_name(name) result(valid)
+ character(*), intent(in) :: name
+ logical :: valid
+
+ integer :: i
+
+ if (trim(lower(name)) == 'procedure' .or. &
+ trim(lower(name)) == 'subroutine' .or. &
+ trim(lower(name)) == 'function') then
+
+ valid = .false.
+ return
+ end if
+
+ if (lower(name(1:1)) < 'a' .or. &
+ lower(name(1:1)) > 'z') then
+
+ valid = .false.
+ return
+ end if
+
+ do i=1,len(name)
+
+ if (.not.( &
+ (name(i:i) >= '0' .and. name(i:i) <= '9').or. &
+ (lower(name(i:i)) >= 'a' .and. lower(name(i:i)) <= 'z').or. &
+ name(i:i) == '_') ) then
+
+ valid = .false.
+ return
+ end if
+
+ end do
+
+ valid = .true.
+ return
+
+ end function validate_name
+
+end function parse_f_source
+
+
+function parse_c_source(c_filename) result(c_source)
+ ! Rudimentary scan of c source file and
+ ! extract include dependencies
+ !
+ character(*), intent(in) :: c_filename
+ type(srcfile_t) :: c_source
+
+ integer :: fh, n_include, i, pass
+ type(string_t), allocatable :: file_lines(:)
+ character(:), allocatable :: line_parts(:)
+
+ c_source%file_name = c_filename
+
+ if (str_ends_with(lower(c_filename), ".c")) then
+
+ c_source%unit_type = FPM_UNIT_CSOURCE
+
+ elseif (str_ends_with(lower(c_filename), ".h")) then
+
+ c_source%unit_type = FPM_UNIT_CHEADER
+
+ end if
+
+ allocate(c_source%modules_used(0))
+ allocate(c_source%modules_provided(0))
+
+ open(newunit=fh,file=c_filename,status='old')
+ file_lines = read_lines(fh)
+ close(fh)
+
+ do pass = 1,2
+ n_include = 0
+ file_loop: do i=1,size(file_lines)
+
+ ! Process 'INCLUDE' statements
+ if (index(adjustl(lower(file_lines(i)%s)),'#include') == 1 .and. &
+ index(file_lines(i)%s,'"') > 0) then
+
+ n_include = n_include + 1
+
+ if (pass == 2) then
+ call split(file_lines(i)%s,line_parts,delimiters='"')
+ c_source%include_dependencies(n_include)%s = trim(line_parts(2))
+ end if
+
+ end if
+
+ end do file_loop
+
+ if (pass == 1) then
+ allocate(c_source%include_dependencies(n_include))
+ end if
+
+ end do
+
+end function parse_c_source
+
+
+subroutine resolve_module_dependencies(sources)
+ ! After enumerating all source files: resolve file dependencies
+ ! by searching on module names
+ !
+ type(srcfile_t), intent(inout), target :: sources(:)
+
+ integer :: n_depend, i, j
+
+ do i=1,size(sources)
+
+ n_depend = size(sources(i)%modules_used)
+
+ allocate(sources(i)%file_dependencies(n_depend))
+
+ do j=1,n_depend
+
+ sources(i)%file_dependencies(j)%ptr => &
+ find_module_dependency(sources,sources(i)%modules_used(j)%s)
+
+ if (.not.associated(sources(i)%file_dependencies(j)%ptr)) then
+ write(*,*) '(!) Unable to find source for module dependency: ',sources(i)%modules_used(j)%s
+ ! stop
+ end if
+
+ end do
+
+ end do
+
+end subroutine resolve_module_dependencies
+
+function find_module_dependency(sources,module_name) result(src_ptr)
+ type(srcfile_t), intent(in), target :: sources(:)
+ character(*), intent(in) :: module_name
+ type(srcfile_t), pointer :: src_ptr
+
+ integer :: k, l
+
+ src_ptr => NULL()
+
+ do k=1,size(sources)
+
+ do l=1,size(sources(k)%modules_provided)
+
+ if (module_name == sources(k)%modules_provided(l)%s) then
+ src_ptr => sources(k)
+ exit
+ end if
+
+ end do
+
+ end do
+
+end function find_module_dependency
+
+end module fpm_sources
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
new file mode 100644
index 0000000..a6511c9
--- /dev/null
+++ b/fpm/src/fpm_strings.f90
@@ -0,0 +1,217 @@
+module fpm_strings
+implicit none
+
+private
+public :: f_string, lower, split, str_ends_with, string_t
+public :: string_array_contains, operator(.in.)
+
+type string_t
+ character(len=:), allocatable :: s
+end type
+
+interface operator(.in.)
+ module procedure string_array_contains
+end interface
+
+contains
+
+logical function str_ends_with(s, e) result(r)
+ character(*), intent(in) :: s, e
+ integer :: n1, n2
+ n1 = len(s)-len(e)+1
+ n2 = len(s)
+ if (n1 < 1) then
+ r = .false.
+ else
+ r = (s(n1:n2) == e)
+ end if
+end function str_ends_with
+
+function f_string(c_string)
+ use iso_c_binding
+ character(len=1), intent(in) :: c_string(:)
+ character(:), allocatable :: f_string
+
+ integer :: i, n
+
+ i = 0
+ do while(c_string(i+1) /= C_NULL_CHAR)
+ i = i + 1
+ end do
+ n = i
+
+ allocate(character(n) :: f_string)
+ do i=1,n
+ f_string(i:i) = c_string(i)
+ end do
+
+end function f_string
+
+
+elemental pure function lower(str,begin,end) result (string)
+ ! Changes a string to lowercase over specified range
+ ! Author: John S. Urban
+ ! License: Public Domain
+
+ character(*), intent(In) :: str
+ character(len(str)) :: string
+ integer,intent(in),optional :: begin, end
+ integer :: i
+ integer :: ibegin, iend
+ string = str
+
+ ibegin = 1
+ if (present(begin))then
+ ibegin = max(ibegin,begin)
+ endif
+
+ iend = len_trim(str)
+ if (present(end))then
+ iend= min(iend,end)
+ endif
+
+ do i = ibegin, iend ! step thru each letter in the string in specified range
+ select case (str(i:i))
+ case ('A':'Z')
+ string(i:i) = char(iachar(str(i:i))+32) ! change letter to miniscule
+ case default
+ end select
+ end do
+
+end function lower
+
+
+logical function string_array_contains(search_string,array)
+ ! Check if array of string_t contains a particular string
+ !
+ character(*), intent(in) :: search_string
+ type(string_t), intent(in) :: array(:)
+
+ integer :: i
+
+ string_array_contains = any([(array(i)%s==search_string, &
+ i=1,size(array))])
+
+end function string_array_contains
+
+
+subroutine split(input_line,array,delimiters,order,nulls)
+ ! parse string on delimiter characters and store tokens into an allocatable array"
+ ! Author: John S. Urban
+ ! License: Public Domain
+
+
+ ! given a line of structure " par1 par2 par3 ... parn " store each par(n) into a separate variable in array.
+ ! o by default adjacent delimiters in the input string do not create an empty string in the output array
+ ! o no quoting of delimiters is supported
+ character(len=*),intent(in) :: input_line ! input string to tokenize
+ character(len=*),optional,intent(in) :: delimiters ! list of delimiter characters
+ character(len=*),optional,intent(in) :: order ! order of output array sequential|[reverse|right]
+ character(len=*),optional,intent(in) :: nulls ! return strings composed of delimiters or not ignore|return|ignoreend
+ character(len=:),allocatable,intent(out) :: array(:) ! output array of tokens
+
+ integer :: n ! max number of strings INPUT_LINE could split into if all delimiter
+ integer,allocatable :: ibegin(:) ! positions in input string where tokens start
+ integer,allocatable :: iterm(:) ! positions in input string where tokens end
+ character(len=:),allocatable :: dlim ! string containing delimiter characters
+ character(len=:),allocatable :: ordr ! string containing order keyword
+ character(len=:),allocatable :: nlls ! string containing nulls keyword
+ integer :: ii,iiii ! loop parameters used to control print order
+ integer :: icount ! number of tokens found
+ integer :: ilen ! length of input string with trailing spaces trimmed
+ integer :: i10,i20,i30 ! loop counters
+ integer :: icol ! pointer into input string as it is being parsed
+ integer :: idlim ! number of delimiter characters
+ integer :: ifound ! where next delimiter character is found in remaining input string data
+ integer :: inotnull ! count strings not composed of delimiters
+ integer :: ireturn ! number of tokens returned
+ integer :: imax ! length of longest token
+
+ ! decide on value for optional DELIMITERS parameter
+ if (present(delimiters)) then ! optional delimiter list was present
+ if(delimiters.ne.'')then ! if DELIMITERS was specified and not null use it
+ dlim=delimiters
+ else ! DELIMITERS was specified on call as empty string
+ dlim=' '//char(9)//char(10)//char(11)//char(12)//char(13)//char(0) ! use default delimiter when not specified
+ endif
+ else ! no delimiter value was specified
+ dlim=' '//char(9)//char(10)//char(11)//char(12)//char(13)//char(0) ! use default delimiter when not specified
+ endif
+ idlim=len(dlim) ! dlim a lot of blanks on some machines if dlim is a big string
+
+ if(present(order))then; ordr=lower(adjustl(order)); else; ordr='sequential'; endif ! decide on value for optional ORDER parameter
+ if(present(nulls))then; nlls=lower(adjustl(nulls)); else; nlls='ignore' ; endif ! optional parameter
+
+ n=len(input_line)+1 ! max number of strings INPUT_LINE could split into if all delimiter
+ allocate(ibegin(n)) ! allocate enough space to hold starting location of tokens if string all tokens
+ allocate(iterm(n)) ! allocate enough space to hold ending location of tokens if string all tokens
+ ibegin(:)=1
+ iterm(:)=1
+
+ ilen=len(input_line) ! ILEN is the column position of the last non-blank character
+ icount=0 ! how many tokens found
+ inotnull=0 ! how many tokens found not composed of delimiters
+ imax=0 ! length of longest token found
+
+ select case (ilen)
+
+ case (:0) ! command was totally blank
+
+ case default ! there is at least one non-delimiter in INPUT_LINE if get here
+ icol=1 ! initialize pointer into input line
+ INFINITE: do i30=1,ilen,1 ! store into each array element
+ ibegin(i30)=icol ! assume start new token on the character
+ if(index(dlim(1:idlim),input_line(icol:icol)).eq.0)then ! if current character is not a delimiter
+ iterm(i30)=ilen ! initially assume no more tokens
+ do i10=1,idlim ! search for next delimiter
+ ifound=index(input_line(ibegin(i30):ilen),dlim(i10:i10))
+ IF(ifound.gt.0)then
+ iterm(i30)=min(iterm(i30),ifound+ibegin(i30)-2)
+ endif
+ enddo
+ icol=iterm(i30)+2 ! next place to look as found end of this token
+ inotnull=inotnull+1 ! increment count of number of tokens not composed of delimiters
+ else ! character is a delimiter for a null string
+ iterm(i30)=icol-1 ! record assumed end of string. Will be less than beginning
+ icol=icol+1 ! advance pointer into input string
+ endif
+ imax=max(imax,iterm(i30)-ibegin(i30)+1)
+ icount=i30 ! increment count of number of tokens found
+ if(icol.gt.ilen)then ! no text left
+ exit INFINITE
+ endif
+ enddo INFINITE
+
+ end select
+
+ select case (trim(adjustl(nlls)))
+ case ('ignore','','ignoreend')
+ ireturn=inotnull
+ case default
+ ireturn=icount
+ end select
+ allocate(character(len=imax) :: array(ireturn)) ! allocate the array to return
+ !allocate(array(ireturn)) ! allocate the array to turn
+
+ select case (trim(adjustl(ordr))) ! decide which order to store tokens
+ case ('reverse','right') ; ii=ireturn ; iiii=-1 ! last to first
+ case default ; ii=1 ; iiii=1 ! first to last
+ end select
+
+ do i20=1,icount ! fill the array with the tokens that were found
+ if(iterm(i20).lt.ibegin(i20))then
+ select case (trim(adjustl(nlls)))
+ case ('ignore','','ignoreend')
+ case default
+ array(ii)=' '
+ ii=ii+iiii
+ end select
+ else
+ array(ii)=input_line(ibegin(i20):iterm(i20))
+ ii=ii+iiii
+ endif
+ enddo
+end subroutine split
+
+
+end module fpm_strings