@@ -2,15 +2,19 @@ module fpm
2
2
3
3
use fpm_strings, only: string_t, str_ends_with
4
4
use fpm_backend, only: build_package
5
- use fpm_command_line, only: fpm_build_settings
5
+ use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
6
+ fpm_run_settings, fpm_install_settings, fpm_test_settings
6
7
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_filesystem, only: join_path, number_of_rows, list_files, exists, basename
8
9
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
9
10
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
10
11
resolve_module_dependencies
11
12
use fpm_manifest, only : get_package_data, default_executable, &
12
13
default_library, package_t
13
14
use fpm_error, only : error_t
15
+ use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, &
16
+ & stdout= >output_unit, &
17
+ & stderr= >error_unit
14
18
implicit none
15
19
private
16
20
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
@@ -30,18 +34,31 @@ subroutine build_model(model, settings, package, error)
30
34
31
35
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
32
36
model% fortran_compiler = ' gfortran'
33
- model% output_directory = ' build/gfortran_debug'
34
- model% fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g ' // &
35
- ' -fbounds-check -fcheck-array-temporaries -fbacktrace ' // &
36
- ' -J' // join_path(model% output_directory,model% package_name)
37
+
38
+ if (settings% release)then
39
+ model% output_directory = ' build/gfortran_release'
40
+ model% fortran_compile_flags= ' &
41
+ & -O3 &
42
+ & -Wimplicit-interface &
43
+ & -fPIC &
44
+ & -fmax-errors=1 &
45
+ & -ffast-math &
46
+ & -funroll-loops ' // &
47
+ & ' -J' // join_path(model% output_directory,model% package_name)
48
+ else
49
+ model% output_directory = ' build/gfortran_debug'
50
+ model% fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g ' // &
51
+ ' -fbounds-check -fcheck-array-temporaries -fbacktrace ' // &
52
+ ' -J' // join_path(model% output_directory,model% package_name)
53
+ endif
37
54
model% link_flags = ' '
38
55
39
56
! Add sources from executable directories
40
57
if (allocated (package% executable)) then
41
58
42
59
call add_executable_sources(model% sources, package% executable, &
43
60
is_test= .false. , error= error)
44
-
61
+
45
62
if (allocated (error)) then
46
63
return
47
64
end if
@@ -111,24 +128,91 @@ subroutine cmd_build(settings)
111
128
112
129
end subroutine
113
130
114
- subroutine cmd_install ()
131
+ subroutine cmd_install (settings )
132
+ type (fpm_install_settings), intent (in ) :: settings
115
133
print * , " fpm error: 'fpm install' not implemented."
116
134
error stop 1
117
- end subroutine
118
-
119
- subroutine cmd_new ()
120
- print * , " fpm error: 'fpm new' not implemented."
121
- error stop 1
122
- end subroutine
135
+ end subroutine cmd_install
136
+
137
+ subroutine cmd_new (settings ) ! --with-executable F --with-test F '
138
+ type (fpm_new_settings), intent (in ) :: settings
139
+ character (len= :),allocatable :: message(:)
140
+ character (len= :),allocatable :: bname
141
+ bname= basename(settings% name) ! ! new basename(dirname) if full paths are allowed ???
142
+
143
+ message= [character (len= 80 ) :: & ! create fpm.toml
144
+ &' name = "' // bname// ' " ' , &
145
+ &' version = "0.1.0" ' , &
146
+ &' license = "license" ' , &
147
+ &' author = "Jane Doe" ' , &
148
+ &
' maintainer = "[email protected] " ' , &
149
+ &' copyright = "2020 Jane Doe" ' , &
150
+ &' ' , &
151
+ &' [library] ' , &
152
+ &' source-dir="src" ' , &
153
+ &' ' ]
154
+
155
+ if (settings% with_test)then
156
+ message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
157
+ &' [[test]] ' , &
158
+ &' name="runTests" ' , &
159
+ &' source-dir="test" ' , &
160
+ &' main="main.f90" ' , &
161
+ &' ' ]
162
+ endif
163
+
164
+ if (settings% with_executable)then
165
+ message= [character (len= 80 ) :: message, & ! create next section of fpm.toml
166
+ &' [[executable]] ' , &
167
+ &' name="' // bname// ' " ' , &
168
+ &' source-dir="app" ' , &
169
+ &' main="main.f90" ' , &
170
+ &' ' ]
171
+ endif
172
+
173
+ write (* ,' (a)' )message
174
+ print * , " fpm error: 'fpm new' not implemented."
175
+ error stop 1
176
+ end subroutine cmd_new
177
+
178
+ subroutine cmd_run (settings )
179
+ type (fpm_run_settings), intent (in ) :: settings
180
+ integer :: i
181
+
182
+ write (* ,* )' RELEASE=' ,settings% release
183
+ if (size (settings% name).eq. 0 )then
184
+ write (* ,* )' RUN DEFAULTS with arguments [' // settings% args// ' ]'
185
+ else
186
+ do i= 1 ,size (settings% name)
187
+ write (* ,* )' RUN:' // trim (settings% name (i))// ' with arguments [' // settings% args// ' ]'
188
+ enddo
189
+ endif
123
190
124
- subroutine cmd_run ()
125
191
print * , " fpm error: 'fpm run' not implemented."
126
192
error stop 1
127
- end subroutine
128
193
129
- subroutine cmd_test ()
194
+ end subroutine cmd_run
195
+
196
+ subroutine cmd_test (settings )
197
+ type (fpm_test_settings), intent (in ) :: settings
198
+ character (len= :),allocatable :: release_name
199
+ integer :: i
200
+
201
+ ! ! looks like would get this from model when cmd_test is implimented
202
+ release_name= trim (merge (' gfortran_release' ,' gfortran_debug ' ,settings% release))
203
+
204
+ write (* ,* )' RELEASE=' ,settings% release,' RELEASE_NAME=' ,release_name,' ARGS=' ,settings% args
205
+ if ( size (settings% name) .gt. 0 )then
206
+ write (* ,* )' RUN THESE:'
207
+ do i= 1 ,size (settings% name)
208
+ write (* ,* )' RUN:' // trim (settings% name (i))// ' with arguments [' // settings% args// ' ]'
209
+ enddo
210
+ else
211
+ write (* ,* )' RUN DEFAULTS: with arguments [' // settings% args// ' ]'
212
+ endif
213
+
130
214
print * , " fpm error: 'fpm test' not implemented."
131
215
error stop 1
132
- end subroutine
216
+ end subroutine cmd_test
133
217
134
218
end module fpm
0 commit comments