1
1
module fpm
2
- use environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
3
- use fpm_manifest, only : get_package_data, default_executable, default_library, &
4
- & package_t
2
+
3
+ use fpm_strings, only: string_t, str_ends_with
4
+ use fpm_backend, only: build_package
5
+ use fpm_command_line, only: fpm_build_settings
6
+ use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
7
+ use fpm_filesystem, only: join_path, number_of_rows, list_files, exists
8
+ use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
9
+ use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
10
+ resolve_module_dependencies
11
+ use fpm_manifest, only : get_package_data, default_executable, &
12
+ default_library, package_t
5
13
use fpm_error, only : error_t
6
14
implicit none
7
15
private
8
16
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
9
17
10
- type string_t
11
- character (len= :), allocatable :: s
12
- end type
13
18
14
19
contains
15
20
16
- integer function number_of_rows (s ) result(nrows)
17
- ! determine number or rows
18
- integer ,intent (in ):: s
19
- integer :: ios
20
- character (len= 100 ) :: r
21
- rewind(s)
22
- nrows = 0
23
- do
24
- read (s, * , iostat= ios) r
25
- if (ios /= 0 ) exit
26
- nrows = nrows + 1
27
- end do
28
- rewind(s)
29
- end function
30
-
31
-
32
- subroutine list_files (dir , files )
33
- character (len=* ), intent (in ) :: dir
34
- type (string_t), allocatable , intent (out ) :: files(:)
35
- character (len= 100 ) :: filename
36
- integer :: stat, u, i
37
- ! Using `inquire` / exists on directories works with gfortran, but not ifort
38
- if (.not. exists(dir)) then
39
- allocate (files(0 ))
40
- return
41
- end if
42
- select case (get_os_type())
43
- case (OS_LINUX)
44
- call execute_command_line(" ls " // dir // " > fpm_ls.out" , exitstat= stat)
45
- case (OS_MACOS)
46
- call execute_command_line(" ls " // dir // " > fpm_ls.out" , exitstat= stat)
47
- case (OS_WINDOWS)
48
- call execute_command_line(" dir /b " // dir // " > fpm_ls.out" , exitstat= stat)
49
- end select
50
- if (stat /= 0 ) then
51
- print * , " execute_command_line() failed"
52
- error stop
53
- end if
54
- open (newunit= u, file= " fpm_ls.out" , status= " old" )
55
- allocate (files(number_of_rows(u)))
56
- do i = 1 , size (files)
57
- read (u, * ) filename
58
- files(i)% s = trim (filename)
59
- end do
60
- close (u)
61
- end subroutine
62
-
63
- subroutine run (cmd )
64
- character (len=* ), intent (in ) :: cmd
65
- integer :: stat
66
- print * , " + " , cmd
67
- call execute_command_line(cmd, exitstat= stat)
68
- if (stat /= 0 ) then
69
- print * , " Command failed"
70
- error stop
71
- end if
72
- end subroutine
73
-
74
- logical function exists (filename ) result(r)
75
- character (len=* ), intent (in ) :: filename
76
- inquire (file= filename, exist= r)
77
- end function
78
-
79
- logical function str_ends_with (s , e ) result(r)
80
- character (* ), intent (in ) :: s, e
81
- integer :: n1, n2
82
- n1 = len (s)- len (e)+ 1
83
- n2 = len (s)
84
- if (n1 < 1 ) then
85
- r = .false.
86
- else
87
- r = (s(n1:n2) == e)
88
- end if
89
- end function
90
-
91
- subroutine cmd_build ()
21
+ subroutine build_model (model , settings , package )
22
+ ! Constructs a valid fpm model from command line settings and toml manifest
23
+ !
24
+ type (fpm_model_t), intent (out ) :: model
25
+ type (fpm_build_settings), intent (in ) :: settings
26
+ type (package_t), intent (in ) :: package
27
+
28
+ model% package_name = package% name
29
+
30
+ ! #TODO: Choose flags and output directory based on cli settings & manifest inputs
31
+ model% fortran_compiler = ' gfortran'
32
+ model% output_directory = ' build/gfortran_debug'
33
+ model% fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g ' // &
34
+ ' -fbounds-check -fcheck-array-temporaries -fbacktrace ' // &
35
+ ' -J' // join_path(model% output_directory,model% package_name)
36
+ model% link_flags = ' '
37
+
38
+ ! Add sources from executable directories
39
+ if (allocated (package% executable)) then
40
+ call add_executable_sources(model% sources, package% executable,is_test= .false. )
41
+ end if
42
+ if (allocated (package% test)) then
43
+ call add_executable_sources(model% sources, package% test,is_test= .true. )
44
+ end if
45
+
46
+ if (allocated (package% library)) then
47
+ call add_sources_from_dir(model% sources,package% library% source_dir)
48
+ end if
49
+
50
+ call resolve_module_dependencies(model% sources)
51
+
52
+ end subroutine build_model
53
+
54
+ subroutine cmd_build (settings )
55
+ type (fpm_build_settings), intent (in ) :: settings
92
56
type (package_t) :: package
57
+ type (fpm_model_t) :: model
93
58
type (error_t), allocatable :: error
94
- type (string_t), allocatable :: files(:)
95
- character (:), allocatable :: basename, linking
96
- integer :: i, n
97
59
call get_package_data(package, " fpm.toml" , error)
98
60
if (allocated (error)) then
99
61
print ' (a)' , error% message
@@ -102,6 +64,7 @@ subroutine cmd_build()
102
64
103
65
! Populate library in case we find the default src directory
104
66
if (.not. allocated (package% library) .and. exists(" src" )) then
67
+ allocate (package% library)
105
68
call default_library(package% library)
106
69
end if
107
70
@@ -116,27 +79,10 @@ subroutine cmd_build()
116
79
error stop 1
117
80
end if
118
81
119
- linking = " "
120
- if (allocated (package% library)) then
121
- call list_files(package% library% source_dir, files)
122
- do i = 1 , size (files)
123
- if (str_ends_with(files(i)% s, " .f90" )) then
124
- n = len (files(i)% s)
125
- basename = files(i)% s
126
- call run(" gfortran -c " // package% library% source_dir // " /" // &
127
- & basename // " -o " // basename // " .o" )
128
- linking = linking // " " // basename // " .o"
129
- end if
130
- end do
131
- end if
82
+ call build_model(model, settings, package)
83
+
84
+ call build_package(model)
132
85
133
- do i = 1 , size (package% executable)
134
- basename = package% executable(i)% main
135
- call run(" gfortran -c " // package% executable(i)% source_dir // " /" // &
136
- & basename // " -o " // basename // " .o" )
137
- call run(" gfortran " // basename // " .o " // linking // " -o " // &
138
- & package% executable(i)% name)
139
- end do
140
86
end subroutine
141
87
142
88
subroutine cmd_install ()
0 commit comments