Skip to content

Commit

Permalink
Merge pull request #879 from perazz/serialize_fpm_model
Browse files Browse the repository at this point in the history
export fpm model to TOML and JSON
  • Loading branch information
henilp105 committed Feb 25, 2024
2 parents bc0927f + 8dc7015 commit 9a2849d
Show file tree
Hide file tree
Showing 27 changed files with 5,134 additions and 186 deletions.
18 changes: 9 additions & 9 deletions .github/workflows/meta.yml
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ jobs:
Remove-Item "oneAPI" -Force -Recurse
- name: (Ubuntu) Install gfortran
if: contains(matrix.os,'ubuntu') && (!contains(matrix.mpi,'intel'))
if: contains(matrix.os,'ubuntu')
run: |
sudo update-alternatives --install /usr/bin/gcc gcc /usr/bin/gcc-${GCC_V} 100 \
--slave /usr/bin/gfortran gfortran /usr/bin/gfortran-${GCC_V} \
Expand Down Expand Up @@ -209,14 +209,6 @@ jobs:
mv $(which fpm) fpm-bootstrap${{ matrix.exe }}
echo "BOOTSTRAP=$PWD/fpm-bootstrap" >> $GITHUB_ENV
- name: Use Intel compiler for the metapackage tests
if: contains(matrix.mpi,'intel')
shell: bash
run: |
echo "FPM_FC=ifx" >> $GITHUB_ENV
echo "FPM_CC=icx" >> $GITHUB_ENV
echo "FPM_CXX=icpx" >> $GITHUB_ENV
- name: (macOS) Use gcc/g++ instead of Clang for C/C++
if: contains(matrix.os,'macOS')
shell: bash
Expand Down Expand Up @@ -300,6 +292,14 @@ jobs:
env:
EXE: fpm-${{ env.VERSION }}-${{ matrix.os-arch }}${{ matrix.exe }}

- name: Use Intel compiler for the metapackage tests
if: contains(matrix.mpi,'intel')
shell: bash
run: |
echo "FPM_FC=ifx" >> $GITHUB_ENV
echo "FPM_CC=icx" >> $GITHUB_ENV
echo "FPM_CXX=icpx" >> $GITHUB_ENV
- name: Run metapackage tests using the release version
shell: bash
run: |
Expand Down
4 changes: 4 additions & 0 deletions app/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ program main
fpm_cmd_settings, &
fpm_new_settings, &
fpm_build_settings, &
fpm_export_settings, &
fpm_run_settings, &
fpm_test_settings, &
fpm_install_settings, &
Expand All @@ -15,6 +16,7 @@ program main
use fpm_filesystem, only: exists, parent_dir, join_path
use fpm, only: cmd_build, cmd_run, cmd_clean
use fpm_cmd_install, only: cmd_install
use fpm_cmd_export, only: cmd_export
use fpm_cmd_new, only: cmd_new
use fpm_cmd_update, only : cmd_update
use fpm_cmd_publish, only: cmd_publish
Expand Down Expand Up @@ -76,6 +78,8 @@ program main
call cmd_run(settings,test=.false.)
type is (fpm_test_settings)
call cmd_run(settings,test=.true.)
type is (fpm_export_settings)
call cmd_export(settings)
type is (fpm_install_settings)
call cmd_install(settings)
type is (fpm_update_settings)
Expand Down
7 changes: 7 additions & 0 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ module fpm
use fpm_manifest, only : get_package_data, package_config_t
use fpm_meta, only : resolve_metapackages
use fpm_error, only : error_t, fatal_error, fpm_stop
use fpm_toml, only: name_is_json
use, intrinsic :: iso_fortran_env, only : stdin => input_unit, &
& stdout => output_unit, &
& stderr => error_unit
Expand Down Expand Up @@ -449,6 +450,12 @@ subroutine cmd_build(settings)
call fpm_stop(1,'*cmd_build* Target error: '//error%message)
end if

!> Dump model to file
if (len_trim(settings%dump)>0) then
call model%dump(trim(settings%dump),error,json=name_is_json(trim(settings%dump)))
if (allocated(error)) call fpm_stop(1,'*cmd_build* Model dump error: '//error%message)
endif

if(settings%list)then
do i=1,size(targets)
write(stderr,*) targets(i)%ptr%output_file
Expand Down
83 changes: 83 additions & 0 deletions src/fpm/cmd/export.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,83 @@
module fpm_cmd_export
use fpm_command_line, only : fpm_export_settings
use fpm_dependency, only : dependency_tree_t, new_dependency_tree
use fpm_error, only : error_t, fpm_stop
use fpm_filesystem, only : join_path
use fpm_manifest, only : package_config_t, get_package_data
use fpm_toml, only: name_is_json
use fpm_model, only: fpm_model_t
use fpm, only: build_model
implicit none
private
public :: cmd_export

contains

!> Entry point for the export subcommand
subroutine cmd_export(settings)
!> Representation of the command line arguments
type(fpm_export_settings), intent(inout) :: settings
type(package_config_t) :: package
type(dependency_tree_t) :: deps
type(fpm_model_t) :: model
type(error_t), allocatable :: error

integer :: ii
character(len=:), allocatable :: filename

if (len_trim(settings%dump_manifest)<=0 .and. &
len_trim(settings%dump_model)<=0 .and. &
len_trim(settings%dump_dependencies)<=0) then
call fpm_stop(0,'*cmd_export* exiting: no manifest/model/dependencies keyword provided')
end if

!> Read in manifest
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
call handle_error(error)

!> Export manifest
if (len_trim(settings%dump_manifest)>0) then
filename = trim(settings%dump_manifest)
call package%dump(filename, error, json=name_is_json(filename))
end if

!> Export dependency tree
if (len_trim(settings%dump_dependencies)>0) then

!> Generate dependency tree
filename = join_path("build", "cache.toml")
call new_dependency_tree(deps, cache=filename, verbosity=merge(2, 1, settings%verbose))
call deps%add(package, error)
call handle_error(error)

!> Export dependency tree
filename = settings%dump_dependencies
call deps%dump(filename, error, json=name_is_json(filename))
call handle_error(error)
end if

!> Export full model
if (len_trim(settings%dump_model)>0) then

call build_model(model, settings%fpm_build_settings, package, error)
if (allocated(error)) then
call fpm_stop(1,'*cmd_export* Model error: '//error%message)
end if

filename = settings%dump_model
call model%dump(filename, error, json=name_is_json(filename))
call handle_error(error)
end if

end subroutine cmd_export

!> Error handling for this command
subroutine handle_error(error)
!> Potential error
type(error_t), intent(in), optional :: error
if (present(error)) then
call fpm_stop(1, '*cmd_export* error: '//error%message)
end if
end subroutine handle_error

end module fpm_cmd_export
10 changes: 8 additions & 2 deletions src/fpm/cmd/update.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module fpm_cmd_update
use fpm_error, only : error_t, fpm_stop
use fpm_filesystem, only : exists, mkdir, join_path, delete_file, filewrite
use fpm_manifest, only : package_config_t, get_package_data
use fpm_toml, only: name_is_json
implicit none
private
public :: cmd_update
Expand All @@ -14,10 +15,10 @@ module fpm_cmd_update
subroutine cmd_update(settings)
!> Representation of the command line arguments
type(fpm_update_settings), intent(in) :: settings

type(package_config_t) :: package
type(dependency_tree_t) :: deps
type(error_t), allocatable :: error

integer :: ii
character(len=:), allocatable :: cache

Expand Down Expand Up @@ -57,14 +58,19 @@ subroutine cmd_update(settings)
end do
end if

if (len_trim(settings%dump)>0) then
call deps%dump(trim(settings%dump), error, json=name_is_json(trim(settings%dump)))
call handle_error(error)
end if

end subroutine cmd_update

!> Error handling for this command
subroutine handle_error(error)
!> Potential error
type(error_t), intent(in), optional :: error
if (present(error)) then
call fpm_stop(1, error%message)
call fpm_stop(1, '*cmd_update* error: '//error%message)
end if
end subroutine handle_error

Expand Down
Loading

0 comments on commit 9a2849d

Please sign in to comment.