Skip to content

Commit 90ddc6f

Browse files
Merge pull request #182 from urbanjost/CLI
CLI interface to further development of subcommands
2 parents 1a394d7 + d653c11 commit 90ddc6f

File tree

12 files changed

+668
-83
lines changed

12 files changed

+668
-83
lines changed

bootstrap/src/Build.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -259,7 +259,7 @@ createSourceToObjectMap buildDirectory libraryDirectory sourceFile =
259259

260260
sourceFileToObjectFile :: FilePath -> FilePath -> FilePath -> FilePath
261261
sourceFileToObjectFile buildDirectory libraryDirectory sourceFile =
262-
buildDirectory
262+
(foldl (</>) "" $ splitDirectories buildDirectory)
263263
</> map
264264
toLower
265265
(pathSeparatorsToUnderscores

fpm/.gitignore

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1 +1,2 @@
11
build/*
2+
*/FODDER/*

fpm/app/main.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -17,15 +17,15 @@ program main
1717

1818
select type(settings=>cmd_settings)
1919
type is (fpm_new_settings)
20-
call cmd_new()
20+
call cmd_new(settings)
2121
type is (fpm_build_settings)
2222
call cmd_build(settings)
2323
type is (fpm_run_settings)
24-
call cmd_run()
24+
call cmd_run(settings)
2525
type is (fpm_test_settings)
26-
call cmd_test()
26+
call cmd_test(settings)
2727
type is (fpm_install_settings)
28-
call cmd_install()
28+
call cmd_install(settings)
2929
end select
3030

3131
end program main

fpm/fpm.toml

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,18 @@ copyright = "2020 fpm contributors"
1010
git = "https://github.com/toml-f/toml-f"
1111
tag = "v0.2"
1212

13+
[dependencies.M_CLI2]
14+
git = "https://github.com/urbanjost/M_CLI2.git"
15+
rev = "5c7df1267c918ec2b1b8e2c6a0ac000367b562cf"
16+
17+
[[test]]
18+
name = "cli-test"
19+
source-dir = "test/cli_test"
20+
main = "cli_test.f90"
21+
1322
[[test]]
1423
name = "fpm-test"
15-
source-dir = "test"
24+
source-dir = "test/fpm_test"
1625
main = "main.f90"
26+
27+

fpm/src/fpm.f90

Lines changed: 102 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -2,15 +2,19 @@ module fpm
22

33
use fpm_strings, only: string_t, str_ends_with
44
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
67
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
89
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
910
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
1011
resolve_module_dependencies
1112
use fpm_manifest, only : get_package_data, default_executable, &
1213
default_library, package_t
1314
use fpm_error, only : error_t
15+
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
16+
& stdout=>output_unit, &
17+
& stderr=>error_unit
1418
implicit none
1519
private
1620
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
@@ -30,18 +34,31 @@ subroutine build_model(model, settings, package, error)
3034

3135
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
3236
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
3754
model%link_flags = ''
3855

3956
! Add sources from executable directories
4057
if (allocated(package%executable)) then
4158

4259
call add_executable_sources(model%sources, package%executable, &
4360
is_test=.false., error=error)
44-
61+
4562
if (allocated(error)) then
4663
return
4764
end if
@@ -111,24 +128,91 @@ subroutine cmd_build(settings)
111128

112129
end subroutine
113130

114-
subroutine cmd_install()
131+
subroutine cmd_install(settings)
132+
type(fpm_install_settings), intent(in) :: settings
115133
print *, "fpm error: 'fpm install' not implemented."
116134
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
123190

124-
subroutine cmd_run()
125191
print *, "fpm error: 'fpm run' not implemented."
126192
error stop 1
127-
end subroutine
128193

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+
130214
print *, "fpm error: 'fpm test' not implemented."
131215
error stop 1
132-
end subroutine
216+
end subroutine cmd_test
133217

134218
end module fpm

0 commit comments

Comments
 (0)