Skip to content

Commit 49de89e

Browse files
authored
Merge pull request #203 from urbanjost/urbanjs
refactor fpm.f90 to separate subcommand new into fpm_new_subcommand.f90
2 parents d3a65e3 + 9d16e5d commit 49de89e

File tree

5 files changed

+175
-164
lines changed

5 files changed

+175
-164
lines changed

fpm/app/main.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,8 @@ program main
77
fpm_test_settings, &
88
fpm_install_settings, &
99
get_command_line_settings
10-
use fpm, only: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
10+
use fpm, only: cmd_build, cmd_install, cmd_run, cmd_test
11+
use fpm_cmd_new, only: cmd_new
1112

1213
implicit none
1314

fpm/src/fpm.f90

Lines changed: 4 additions & 160 deletions
Original file line numberDiff line numberDiff line change
@@ -4,8 +4,8 @@ module fpm
44
use fpm_backend, only: build_package
55
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
66
fpm_run_settings, fpm_install_settings, fpm_test_settings
7-
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
8-
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename, mkdir
7+
use fpm_environment, only: run
8+
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
99
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
1010
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
1111
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
@@ -16,12 +16,10 @@ module fpm
1616
default_library, package_t, default_test
1717
use fpm_error, only : error_t
1818
use fpm_manifest_test, only : test_t
19-
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
20-
& stdout=>output_unit, &
21-
& stderr=>error_unit
19+
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
2220
implicit none
2321
private
24-
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
22+
public :: cmd_build, cmd_install, cmd_run, cmd_test
2523

2624
contains
2725

@@ -168,160 +166,6 @@ subroutine cmd_install(settings)
168166
error stop 8
169167
end subroutine cmd_install
170168

171-
172-
subroutine cmd_new(settings) ! --with-executable F --with-test F '
173-
type(fpm_new_settings), intent(in) :: settings
174-
integer :: ierr
175-
character(len=:),allocatable :: bname ! baeename of NAME
176-
character(len=:),allocatable :: message(:)
177-
character(len=:),allocatable :: littlefile(:)
178-
179-
call mkdir(settings%name) ! make new directory
180-
call run('cd '//settings%name) ! change to new directory as a test. New OS routines to improve this; system dependent potentially
181-
!! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd().
182-
bname=basename(settings%name)
183-
184-
!! weird gfortran bug?? lines truncated to concatenated string length, not 80
185-
!! hit some weird gfortran bug when littlefile data was an argument to warnwrite(3f), ok when a variable
186-
187-
call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) ! create NAME/.gitignore file
188-
189-
littlefile=[character(len=80) :: '# '//bname, 'My cool new project!']
190-
191-
call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md
192-
193-
message=[character(len=80) :: & ! start building NAME/fpm.toml
194-
&'name = "'//bname//'" ', &
195-
&'version = "0.1.0" ', &
196-
&'license = "license" ', &
197-
&'author = "Jane Doe" ', &
198-
&'maintainer = "[email protected]" ', &
199-
&'copyright = "2020 Jane Doe" ', &
200-
&' ', &
201-
&'']
202-
203-
if(settings%with_lib)then
204-
call mkdir(join_path(settings%name,'src') )
205-
message=[character(len=80) :: message, & ! create next section of fpm.toml
206-
&'[library] ', &
207-
&'source-dir="src" ', &
208-
&'']
209-
littlefile=[character(len=80) :: & ! create placeholder module src/bname.f90
210-
&'module '//bname, &
211-
&' implicit none', &
212-
&' private', &
213-
&'', &
214-
&' public :: say_hello', &
215-
&'contains', &
216-
&' subroutine say_hello', &
217-
&' print *, "Hello, '//bname//'!"', &
218-
&' end subroutine say_hello', &
219-
&'end module '//bname]
220-
! a proposed alternative default
221-
call warnwrite(join_path(settings%name, 'src', bname//'.f90'), littlefile) ! create NAME/src/NAME.f90
222-
endif
223-
224-
if(settings%with_test)then
225-
call mkdir(join_path(settings%name, 'test')) ! create NAME/test or stop
226-
message=[character(len=80) :: message, & ! create next section of fpm.toml
227-
&'[[test]] ', &
228-
&'name="runTests" ', &
229-
&'source-dir="test" ', &
230-
&'main="main.f90" ', &
231-
&'']
232-
233-
littlefile=[character(len=80) :: &
234-
&'program main', &
235-
&'implicit none', &
236-
&'', &
237-
&'print *, "Put some tests in here!"', &
238-
&'end program main']
239-
! a proposed alternative default a little more substantive
240-
call warnwrite(join_path(settings%name, 'test/main.f90'), littlefile) ! create NAME/test/main.f90
241-
endif
242-
243-
if(settings%with_executable)then
244-
call mkdir(join_path(settings%name, 'app')) ! create NAME/app or stop
245-
message=[character(len=80) :: message, & ! create next section of fpm.toml
246-
&'[[executable]] ', &
247-
&'name="'//bname//'" ', &
248-
&'source-dir="app" ', &
249-
&'main="main.f90" ', &
250-
&'']
251-
252-
littlefile=[character(len=80) :: &
253-
&'program main', &
254-
&' use '//bname//', only: say_hello', &
255-
&'', &
256-
&' implicit none', &
257-
&'', &
258-
&' call say_hello', &
259-
&'end program main']
260-
call warnwrite(join_path(settings%name, 'app/main.f90'), littlefile)
261-
endif
262-
263-
call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml
264-
265-
call run('cd ' // settings%name // ';git init') ! assumes these commands work on all systems and git(1) is installed
266-
contains
267-
268-
subroutine warnwrite(fname,data)
269-
character(len=*),intent(in) :: fname
270-
character(len=*),intent(in) :: data(:)
271-
272-
if(.not.exists(fname))then
273-
call filewrite(fname,data)
274-
else
275-
write(stderr,'(*(g0,1x))')'fpm::new<WARNING>',fname,'already exists. Not overwriting'
276-
endif
277-
278-
end subroutine warnwrite
279-
280-
subroutine filewrite(filename,filedata)
281-
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
282-
! write filedata to file filename
283-
character(len=*),intent(in) :: filename
284-
character(len=*),intent(in) :: filedata(:)
285-
integer :: lun, i, ios
286-
character(len=256) :: message
287-
288-
message=' '
289-
ios=0
290-
if(filename.ne.' ')then
291-
open(file=filename, &
292-
& newunit=lun, &
293-
& form='formatted', & ! FORM = FORMATTED | UNFORMATTED
294-
& access='sequential', & ! ACCESS = SEQUENTIAL | DIRECT | STREAM
295-
& action='write', & ! ACTION = READ|WRITE | READWRITE
296-
& position='rewind', & ! POSITION = ASIS | REWIND | APPEND
297-
& status='new', & ! STATUS = NEW | REPLACE | OLD | SCRATCH | UNKNOWN
298-
& iostat=ios, &
299-
& iomsg=message)
300-
else
301-
lun=stdout
302-
ios=0
303-
endif
304-
if(ios.ne.0)then
305-
write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message)
306-
error stop 1
307-
endif
308-
do i=1,size(filedata) ! write file
309-
write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i))
310-
if(ios.ne.0)then
311-
write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message)
312-
error stop 4
313-
endif
314-
enddo
315-
close(unit=lun,iostat=ios,iomsg=message) ! close file
316-
if(ios.ne.0)then
317-
write(stderr,'(*(a:,1x))')'*filewrite* error:',trim(message)
318-
error stop 2
319-
endif
320-
end subroutine filewrite
321-
322-
end subroutine cmd_new
323-
324-
325169
subroutine cmd_run(settings)
326170
type(fpm_run_settings), intent(in) :: settings
327171
character(len=:),allocatable :: release_name, cmd, fname

fpm/src/fpm/cmd/new.f90

Lines changed: 164 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,164 @@
1+
module fpm_cmd_new
2+
3+
use fpm_command_line, only : fpm_new_settings
4+
use fpm_environment, only : run, OS_LINUX, OS_MACOS, OS_WINDOWS
5+
use fpm_filesystem, only : join_path, exists, basename, mkdir
6+
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
7+
implicit none
8+
private
9+
public :: cmd_new
10+
11+
contains
12+
13+
subroutine cmd_new(settings) ! --with-executable F --with-test F '
14+
type(fpm_new_settings), intent(in) :: settings
15+
character(len=:),allocatable :: bname ! baeename of NAME
16+
character(len=:),allocatable :: message(:)
17+
character(len=:),allocatable :: littlefile(:)
18+
19+
call mkdir(settings%name) ! make new directory
20+
call run('cd '//settings%name) ! change to new directory as a test. System dependent potentially
21+
!! NOTE: need some system routines to handle filenames like "." like realpath() or getcwd().
22+
bname=basename(settings%name)
23+
24+
!! weird gfortran bug?? lines truncated to concatenated string length, not 80
25+
!! hit some weird gfortran bug when littlefile data was an argument to warnwrite(3f), ok when a variable
26+
27+
call warnwrite(join_path(settings%name, '.gitignore'), ['build/*']) ! create NAME/.gitignore file
28+
29+
littlefile=[character(len=80) :: '# '//bname, 'My cool new project!']
30+
31+
call warnwrite(join_path(settings%name, 'README.md'), littlefile) ! create NAME/README.md
32+
33+
message=[character(len=80) :: & ! start building NAME/fpm.toml
34+
&'name = "'//bname//'" ', &
35+
&'version = "0.1.0" ', &
36+
&'license = "license" ', &
37+
&'author = "Jane Doe" ', &
38+
&'maintainer = "[email protected]" ', &
39+
&'copyright = "2020 Jane Doe" ', &
40+
&' ', &
41+
&'']
42+
43+
if(settings%with_lib)then
44+
call mkdir(join_path(settings%name,'src') )
45+
message=[character(len=80) :: message, & ! create next section of fpm.toml
46+
&'[library] ', &
47+
&'source-dir="src" ', &
48+
&'']
49+
littlefile=[character(len=80) :: & ! create placeholder module src/bname.f90
50+
&'module '//bname, &
51+
&' implicit none', &
52+
&' private', &
53+
&'', &
54+
&' public :: say_hello', &
55+
&'contains', &
56+
&' subroutine say_hello', &
57+
&' print *, "Hello, '//bname//'!"', &
58+
&' end subroutine say_hello', &
59+
&'end module '//bname]
60+
! a proposed alternative default
61+
call warnwrite(join_path(settings%name, 'src', bname//'.f90'), littlefile) ! create NAME/src/NAME.f90
62+
endif
63+
64+
if(settings%with_test)then
65+
call mkdir(join_path(settings%name, 'test')) ! create NAME/test or stop
66+
message=[character(len=80) :: message, & ! create next section of fpm.toml
67+
&'[[test]] ', &
68+
&'name="runTests" ', &
69+
&'source-dir="test" ', &
70+
&'main="main.f90" ', &
71+
&'']
72+
73+
littlefile=[character(len=80) :: &
74+
&'program main', &
75+
&'implicit none', &
76+
&'', &
77+
&'print *, "Put some tests in here!"', &
78+
&'end program main']
79+
! a proposed alternative default a little more substantive
80+
call warnwrite(join_path(settings%name, 'test/main.f90'), littlefile) ! create NAME/test/main.f90
81+
endif
82+
83+
if(settings%with_executable)then
84+
call mkdir(join_path(settings%name, 'app')) ! create NAME/app or stop
85+
message=[character(len=80) :: message, & ! create next section of fpm.toml
86+
&'[[executable]] ', &
87+
&'name="'//bname//'" ', &
88+
&'source-dir="app" ', &
89+
&'main="main.f90" ', &
90+
&'']
91+
92+
littlefile=[character(len=80) :: &
93+
&'program main', &
94+
&' use '//bname//', only: say_hello', &
95+
&'', &
96+
&' implicit none', &
97+
&'', &
98+
&' call say_hello', &
99+
&'end program main']
100+
call warnwrite(join_path(settings%name, 'app/main.f90'), littlefile)
101+
endif
102+
103+
call warnwrite(join_path(settings%name, 'fpm.toml'), message) ! now that built it write NAME/fpm.toml
104+
105+
call run('cd ' // settings%name // '&&git init') ! assumes these commands work on all systems and git(1) is installed
106+
contains
107+
108+
subroutine warnwrite(fname,data)
109+
character(len=*),intent(in) :: fname
110+
character(len=*),intent(in) :: data(:)
111+
112+
if(.not.exists(fname))then
113+
call filewrite(fname,data)
114+
else
115+
write(stderr,'(*(g0,1x))')'fpm::new<WARNING>',fname,'already exists. Not overwriting'
116+
endif
117+
118+
end subroutine warnwrite
119+
120+
subroutine filewrite(filename,filedata)
121+
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
122+
! write filedata to file filename
123+
character(len=*),intent(in) :: filename
124+
character(len=*),intent(in) :: filedata(:)
125+
integer :: lun, i, ios
126+
character(len=256) :: message
127+
128+
message=' '
129+
ios=0
130+
if(filename.ne.' ')then
131+
open(file=filename, &
132+
& newunit=lun, &
133+
& form='formatted', & ! FORM = FORMATTED | UNFORMATTED
134+
& access='sequential', & ! ACCESS = SEQUENTIAL | DIRECT | STREAM
135+
& action='write', & ! ACTION = READ|WRITE | READWRITE
136+
& position='rewind', & ! POSITION = ASIS | REWIND | APPEND
137+
& status='new', & ! STATUS = NEW | REPLACE | OLD | SCRATCH | UNKNOWN
138+
& iostat=ios, &
139+
& iomsg=message)
140+
else
141+
lun=stdout
142+
ios=0
143+
endif
144+
if(ios.ne.0)then
145+
write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message)
146+
error stop 1
147+
endif
148+
do i=1,size(filedata) ! write file
149+
write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i))
150+
if(ios.ne.0)then
151+
write(stderr,'(*(a:,1x))')'*filewrite* error:',filename,trim(message)
152+
error stop 4
153+
endif
154+
enddo
155+
close(unit=lun,iostat=ios,iomsg=message) ! close file
156+
if(ios.ne.0)then
157+
write(stderr,'(*(a:,1x))')'*filewrite* error:',trim(message)
158+
error stop 2
159+
endif
160+
end subroutine filewrite
161+
162+
end subroutine cmd_new
163+
164+
end module fpm_cmd_new

fpm/src/fpm_command_line.f90

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -416,8 +416,9 @@ subroutine set_help()
416416
' ', &
417417
' The "new" subcommand creates a directory and runs the command ', &
418418
' "git init" in that directory and makes an example "fpm.toml" ', &
419-
' file, a src/ directory, and optionally a test/ and app/ ', &
420-
' directory with trivial example Fortran source files. ', &
419+
' file. and src/ directory and a sample module file. It ', &
420+
' optionally also creates a test/ and app/ directory with ', &
421+
' trivial example Fortran program sources. ', &
421422
' ', &
422423
' Remember to update the information in the sample "fpm.toml" ', &
423424
' file with such information as your name and e-mail address. ', &

fpm/test/cli_test/cli_test.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -193,7 +193,8 @@ subroutine parse()
193193
fpm_test_settings, &
194194
fpm_install_settings, &
195195
get_command_line_settings
196-
use fpm, only: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
196+
use fpm, only: cmd_build, cmd_install, cmd_run, cmd_test
197+
use fpm_cmd_new, only: cmd_new
197198
class(fpm_cmd_settings), allocatable :: cmd_settings
198199
! duplicates the calls as seen in the main program for fpm
199200
call get_command_line_settings(cmd_settings)

0 commit comments

Comments
 (0)