Skip to content

Commit 170070b

Browse files
committed
deploy fpm export
1 parent 2990bc7 commit 170070b

File tree

5 files changed

+134
-5
lines changed

5 files changed

+134
-5
lines changed

app/main.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ program main
44
fpm_cmd_settings, &
55
fpm_new_settings, &
66
fpm_build_settings, &
7+
fpm_export_settings, &
78
fpm_run_settings, &
89
fpm_test_settings, &
910
fpm_install_settings, &
@@ -15,6 +16,7 @@ program main
1516
use fpm_filesystem, only: exists, parent_dir, join_path
1617
use fpm, only: cmd_build, cmd_run, cmd_clean
1718
use fpm_cmd_install, only: cmd_install
19+
use fpm_cmd_export, only: cmd_export
1820
use fpm_cmd_new, only: cmd_new
1921
use fpm_cmd_update, only : cmd_update
2022
use fpm_cmd_publish, only: cmd_publish
@@ -76,6 +78,8 @@ program main
7678
call cmd_run(settings,test=.false.)
7779
type is (fpm_test_settings)
7880
call cmd_run(settings,test=.true.)
81+
type is (fpm_export_settings)
82+
call cmd_export(settings)
7983
type is (fpm_install_settings)
8084
call cmd_install(settings)
8185
type is (fpm_update_settings)

src/fpm/cmd/export.f90

Lines changed: 83 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,83 @@
1+
module fpm_cmd_export
2+
use fpm_command_line, only : fpm_export_settings
3+
use fpm_dependency, only : dependency_tree_t, new_dependency_tree
4+
use fpm_error, only : error_t, fpm_stop
5+
use fpm_filesystem, only : join_path
6+
use fpm_manifest, only : package_config_t, get_package_data
7+
use fpm_toml, only: name_is_json
8+
use fpm_model, only: fpm_model_t
9+
use fpm, only: build_model
10+
implicit none
11+
private
12+
public :: cmd_export
13+
14+
contains
15+
16+
!> Entry point for the export subcommand
17+
subroutine cmd_export(settings)
18+
!> Representation of the command line arguments
19+
type(fpm_export_settings), intent(in) :: settings
20+
type(package_config_t) :: package
21+
type(dependency_tree_t) :: deps
22+
type(fpm_model_t) :: model
23+
type(error_t), allocatable :: error
24+
25+
integer :: ii
26+
character(len=:), allocatable :: filename
27+
28+
if (len_trim(settings%dump_manifest)<=0 .and. &
29+
len_trim(settings%dump_model)<=0 .and. &
30+
len_trim(settings%dump_dependencies)<=0) then
31+
call fpm_stop(0,'*cmd_export* exiting: no manifest/model/dependencies keyword provided')
32+
end if
33+
34+
!> Read in manifest
35+
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
36+
call handle_error(error)
37+
38+
!> Export manifest
39+
if (len_trim(settings%dump_manifest)>0) then
40+
filename = trim(settings%dump_manifest)
41+
call package%dump(filename, error, json=name_is_json(filename))
42+
end if
43+
44+
!> Export dependency tree
45+
if (len_trim(settings%dump_dependencies)>0) then
46+
47+
!> Generate dependency tree
48+
filename = join_path("build", "cache.toml")
49+
call new_dependency_tree(deps, cache=filename, verbosity=merge(2, 1, settings%verbose))
50+
call deps%add(package, error)
51+
call handle_error(error)
52+
53+
!> Export dependency tree
54+
filename = settings%dump_dependencies
55+
call deps%dump(filename, error, json=name_is_json(filename))
56+
call handle_error(error)
57+
end if
58+
59+
!> Export full model
60+
if (len_trim(settings%dump_model)>0) then
61+
62+
call build_model(model, settings%fpm_build_settings, package, error)
63+
if (allocated(error)) then
64+
call fpm_stop(1,'*cmd_export* Model error: '//error%message)
65+
end if
66+
67+
filename = settings%dump_model
68+
call model%dump(filename, error, json=name_is_json(filename))
69+
call handle_error(error)
70+
end if
71+
72+
end subroutine cmd_export
73+
74+
!> Error handling for this command
75+
subroutine handle_error(error)
76+
!> Potential error
77+
type(error_t), intent(in), optional :: error
78+
if (present(error)) then
79+
call fpm_stop(1, '*cmd_export* error: '//error%message)
80+
end if
81+
end subroutine handle_error
82+
83+
end module fpm_cmd_export

src/fpm/cmd/update.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,10 +15,10 @@ module fpm_cmd_update
1515
subroutine cmd_update(settings)
1616
!> Representation of the command line arguments
1717
type(fpm_update_settings), intent(in) :: settings
18+
1819
type(package_config_t) :: package
1920
type(dependency_tree_t) :: deps
2021
type(error_t), allocatable :: error
21-
2222
integer :: ii
2323
character(len=:), allocatable :: cache
2424

src/fpm/manifest/package.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -743,7 +743,7 @@ subroutine dump_to_toml(self, table, error)
743743

744744
!> Duplicate profile names are possible, as multiple profiles are possible with the
745745
!> same name, same compiler, etc. So, use a unique name here
746-
write(profile_name,1) 'PROFILE',ii
746+
write(profile_name,2) ii
747747
call add_table(ptr_pkg, trim(profile_name), ptr, error, class_name//'(profiles)')
748748
if (allocated(error)) return
749749
call pkg%dump_to_toml(ptr, error)
@@ -842,6 +842,7 @@ subroutine dump_to_toml(self, table, error)
842842
end if
843843

844844
1 format('UNNAMED_',a,'_',i0)
845+
2 format('PROFILE_',i0)
845846

846847
end subroutine dump_to_toml
847848

src/fpm_command_line.f90

Lines changed: 44 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ module fpm_command_line
4444
public :: fpm_cmd_settings, &
4545
fpm_build_settings, &
4646
fpm_install_settings, &
47+
fpm_export_settings, &
4748
fpm_new_settings, &
4849
fpm_run_settings, &
4950
fpm_test_settings, &
@@ -108,9 +109,16 @@ module fpm_command_line
108109
!> Settings for interacting and updating with project dependencies
109110
type, extends(fpm_cmd_settings) :: fpm_update_settings
110111
character(len=ibug),allocatable :: name(:)
111-
character(len=:),allocatable :: dump
112-
logical :: fetch_only
113-
logical :: clean
112+
character(len=:),allocatable :: dump
113+
logical :: fetch_only
114+
logical :: clean
115+
end type
116+
117+
!> Settings for exporting model data
118+
type, extends(fpm_build_settings) :: fpm_export_settings
119+
character(len=:),allocatable :: dump_manifest
120+
character(len=:),allocatable :: dump_dependencies
121+
character(len=:),allocatable :: dump_model
114122
end type
115123

116124
type, extends(fpm_cmd_settings) :: fpm_clean_settings
@@ -221,6 +229,7 @@ subroutine get_command_line_settings(cmd_settings)
221229
logical :: is_unix
222230
type(fpm_install_settings), allocatable :: install_settings
223231
type(fpm_publish_settings), allocatable :: publish_settings
232+
type(fpm_export_settings) , allocatable :: export_settings
224233
type(version_t) :: version
225234
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
226235
& c_compiler, cxx_compiler, archiver, version_s
@@ -606,6 +615,38 @@ subroutine get_command_line_settings(cmd_settings)
606615
fetch_only=lget('fetch-only'), verbose=lget('verbose'), &
607616
clean=lget('clean'))
608617

618+
case('export')
619+
620+
call set_args(common_args // compiler_args // '&
621+
& --manifest "filename" &
622+
& --model "filename" &
623+
& --dependencies "filename" ', &
624+
help_build, version_text)
625+
626+
call check_build_vals()
627+
628+
c_compiler = sget('c-compiler')
629+
cxx_compiler = sget('cxx-compiler')
630+
archiver = sget('archiver')
631+
allocate(export_settings, source=fpm_export_settings(&
632+
profile=val_profile,&
633+
prune=.not.lget('no-prune'), &
634+
compiler=val_compiler, &
635+
c_compiler=c_compiler, &
636+
cxx_compiler=cxx_compiler, &
637+
archiver=archiver, &
638+
flag=val_flag, &
639+
cflag=val_cflag, &
640+
show_model=.true., &
641+
cxxflag=val_cxxflag, &
642+
ldflag=val_ldflag, &
643+
verbose=lget('verbose')))
644+
call get_char_arg(export_settings%dump_model, 'model')
645+
call get_char_arg(export_settings%dump_manifest, 'manifest')
646+
call get_char_arg(export_settings%dump_dependencies, 'dependencies')
647+
call move_alloc(export_settings, cmd_settings)
648+
649+
609650
case('clean')
610651
call set_args(common_args // &
611652
& ' --skip' // &

0 commit comments

Comments
 (0)