Skip to content

Commit 9a2849d

Browse files
authored
Merge pull request #879 from perazz/serialize_fpm_model
export fpm model to TOML and JSON
2 parents bc0927f + 8dc7015 commit 9a2849d

27 files changed

+5134
-186
lines changed

.github/workflows/meta.yml

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ jobs:
8484
Remove-Item "oneAPI" -Force -Recurse
8585
8686
- name: (Ubuntu) Install gfortran
87-
if: contains(matrix.os,'ubuntu') && (!contains(matrix.mpi,'intel'))
87+
if: contains(matrix.os,'ubuntu')
8888
run: |
8989
sudo update-alternatives --install /usr/bin/gcc gcc /usr/bin/gcc-${GCC_V} 100 \
9090
--slave /usr/bin/gfortran gfortran /usr/bin/gfortran-${GCC_V} \
@@ -209,14 +209,6 @@ jobs:
209209
mv $(which fpm) fpm-bootstrap${{ matrix.exe }}
210210
echo "BOOTSTRAP=$PWD/fpm-bootstrap" >> $GITHUB_ENV
211211
212-
- name: Use Intel compiler for the metapackage tests
213-
if: contains(matrix.mpi,'intel')
214-
shell: bash
215-
run: |
216-
echo "FPM_FC=ifx" >> $GITHUB_ENV
217-
echo "FPM_CC=icx" >> $GITHUB_ENV
218-
echo "FPM_CXX=icpx" >> $GITHUB_ENV
219-
220212
- name: (macOS) Use gcc/g++ instead of Clang for C/C++
221213
if: contains(matrix.os,'macOS')
222214
shell: bash
@@ -300,6 +292,14 @@ jobs:
300292
env:
301293
EXE: fpm-${{ env.VERSION }}-${{ matrix.os-arch }}${{ matrix.exe }}
302294

295+
- name: Use Intel compiler for the metapackage tests
296+
if: contains(matrix.mpi,'intel')
297+
shell: bash
298+
run: |
299+
echo "FPM_FC=ifx" >> $GITHUB_ENV
300+
echo "FPM_CC=icx" >> $GITHUB_ENV
301+
echo "FPM_CXX=icpx" >> $GITHUB_ENV
302+
303303
- name: Run metapackage tests using the release version
304304
shell: bash
305305
run: |

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.f90

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ module fpm
2121
use fpm_manifest, only : get_package_data, package_config_t
2222
use fpm_meta, only : resolve_metapackages
2323
use fpm_error, only : error_t, fatal_error, fpm_stop
24+
use fpm_toml, only: name_is_json
2425
use, intrinsic :: iso_fortran_env, only : stdin => input_unit, &
2526
& stdout => output_unit, &
2627
& stderr => error_unit
@@ -449,6 +450,12 @@ subroutine cmd_build(settings)
449450
call fpm_stop(1,'*cmd_build* Target error: '//error%message)
450451
end if
451452

453+
!> Dump model to file
454+
if (len_trim(settings%dump)>0) then
455+
call model%dump(trim(settings%dump),error,json=name_is_json(trim(settings%dump)))
456+
if (allocated(error)) call fpm_stop(1,'*cmd_build* Model dump error: '//error%message)
457+
endif
458+
452459
if(settings%list)then
453460
do i=1,size(targets)
454461
write(stderr,*) targets(i)%ptr%output_file

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(inout) :: 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: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ module fpm_cmd_update
44
use fpm_error, only : error_t, fpm_stop
55
use fpm_filesystem, only : exists, mkdir, join_path, delete_file, filewrite
66
use fpm_manifest, only : package_config_t, get_package_data
7+
use fpm_toml, only: name_is_json
78
implicit none
89
private
910
public :: cmd_update
@@ -14,10 +15,10 @@ module fpm_cmd_update
1415
subroutine cmd_update(settings)
1516
!> Representation of the command line arguments
1617
type(fpm_update_settings), intent(in) :: settings
18+
1719
type(package_config_t) :: package
1820
type(dependency_tree_t) :: deps
1921
type(error_t), allocatable :: error
20-
2122
integer :: ii
2223
character(len=:), allocatable :: cache
2324

@@ -57,14 +58,19 @@ subroutine cmd_update(settings)
5758
end do
5859
end if
5960

61+
if (len_trim(settings%dump)>0) then
62+
call deps%dump(trim(settings%dump), error, json=name_is_json(trim(settings%dump)))
63+
call handle_error(error)
64+
end if
65+
6066
end subroutine cmd_update
6167

6268
!> Error handling for this command
6369
subroutine handle_error(error)
6470
!> Potential error
6571
type(error_t), intent(in), optional :: error
6672
if (present(error)) then
67-
call fpm_stop(1, error%message)
73+
call fpm_stop(1, '*cmd_update* error: '//error%message)
6874
end if
6975
end subroutine handle_error
7076

0 commit comments

Comments
 (0)