Skip to content

Commit

Permalink
Merge branch 'metapackages' of https://github.com/perazz/fpm into met…
Browse files Browse the repository at this point in the history
…apackages
  • Loading branch information
perazz committed May 25, 2023
2 parents 6d6411c + f3f4d41 commit 24bdea2
Show file tree
Hide file tree
Showing 20 changed files with 208 additions and 156 deletions.
4 changes: 2 additions & 2 deletions fpm.toml
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
name = "fpm"
version = "0.8.1"
version = "0.8.2"
license = "MIT"
author = "fpm maintainers"
maintainer = ""
copyright = "2020 fpm contributors"
copyright = "2020-2023 fpm contributors"

[preprocess]
[preprocess.cpp]
Expand Down
4 changes: 2 additions & 2 deletions install.sh
Original file line number Diff line number Diff line change
Expand Up @@ -73,9 +73,9 @@ fi

LATEST_RELEASE=$(get_latest_release "fortran-lang/fpm" "$FETCH")

# Fallback to a latest known release if network timeout
if [ -z "$LATEST_RELEASE" ]; then
echo "Could not fetch the latest release from GitHub. Install curl or wget, and ensure network connectivity."
exit 3
LATEST_RELEASE="0.8.0"
fi

SOURCE_URL="https://github.com/fortran-lang/fpm/releases/download/v${LATEST_RELEASE}/fpm-${LATEST_RELEASE}.F90"
Expand Down
13 changes: 6 additions & 7 deletions src/fpm/cmd/publish.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,8 @@ module fpm_cmd_publish
use fpm_model, only: fpm_model_t
use fpm_error, only: error_t, fpm_stop
use fpm_versioning, only: version_t
use fpm_filesystem, only: exists, join_path, get_tmp_directory
use fpm_git, only: git_archive, compressed_package_name
use fpm_filesystem, only: exists, join_path, get_temp_filename
use fpm_git, only: git_archive
use fpm_downloader, only: downloader_t
use fpm_strings, only: string_t
use fpm_settings, only: official_registry_base_url
Expand All @@ -31,7 +31,7 @@ subroutine cmd_publish(settings)
type(error_t), allocatable :: error
type(version_t), allocatable :: version
type(string_t), allocatable :: form_data(:)
character(len=:), allocatable :: tmpdir
character(len=:), allocatable :: tmp_file
type(downloader_t) :: downloader
integer :: i

Expand Down Expand Up @@ -69,11 +69,10 @@ subroutine cmd_publish(settings)

if (allocated(settings%token)) form_data = [form_data, string_t('upload_token="'//settings%token//'"')]

call get_tmp_directory(tmpdir, error)
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Tmp directory error: '//error%message)
call git_archive('.', tmpdir, error)
tmp_file = get_temp_filename()
call git_archive('.', tmp_file, error)
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Pack error: '//error%message)
form_data = [form_data, string_t('tarball=@"'//join_path(tmpdir, compressed_package_name)//'"')]
form_data = [form_data, string_t('tarball=@"'//tmp_file//'"')]

if (settings%show_form_data) then
do i = 1, size(form_data)
Expand Down
35 changes: 20 additions & 15 deletions src/fpm/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -719,40 +719,45 @@ subroutine check_and_read_pkg_data(json, node, download_url, version, error)

integer :: code, stat
type(json_object), pointer :: p, q
character(:), allocatable :: version_key, version_str, error_message
character(:), allocatable :: version_key, version_str, error_message, namespace, name

namespace = ""
name = "UNNAMED_NODE"
if (allocated(node%namespace)) namespace = node%namespace
if (allocated(node%name)) name = node%name

if (.not. json%has_key('code')) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': No status code."); return
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': No status code."); return
end if

call get_value(json, 'code', code, stat=stat)
if (stat /= 0) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': "// &
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': "// &
& "Failed to read status code."); return
end if

if (code /= 200) then
if (.not. json%has_key('message')) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': No error message."); return
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': No error message."); return
end if

call get_value(json, 'message', error_message, stat=stat)
if (stat /= 0) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': "// &
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': "// &
& "Failed to read error message."); return
end if

call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"'. Status code: '"// &
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"'. Status code: '"// &
& str(code)//"'. Error message: '"//error_message//"'."); return
end if

if (.not. json%has_key('data')) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': No data."); return
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': No data."); return
end if

call get_value(json, 'data', p, stat=stat)
if (stat /= 0) then
call fatal_error(error, "Failed to read package data for '"//join_path(node%namespace, node%name)//"'."); return
call fatal_error(error, "Failed to read package data for '"//join_path(namespace, name)//"'."); return
end if

if (allocated(node%requested_version)) then
Expand All @@ -762,38 +767,38 @@ subroutine check_and_read_pkg_data(json, node, download_url, version, error)
end if

if (.not. p%has_key(version_key)) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': No version data."); return
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': No version data."); return
end if

call get_value(p, version_key, q, stat=stat)
if (stat /= 0) then
call fatal_error(error, "Failed to retrieve version data for '"//join_path(node%namespace, node%name)//"'."); return
call fatal_error(error, "Failed to retrieve version data for '"//join_path(namespace, name)//"'."); return
end if

if (.not. q%has_key('download_url')) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': No download url."); return
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': No download url."); return
end if

call get_value(q, 'download_url', download_url, stat=stat)
if (stat /= 0) then
call fatal_error(error, "Failed to read download url for '"//join_path(node%namespace, node%name)//"'."); return
call fatal_error(error, "Failed to read download url for '"//join_path(namespace, name)//"'."); return
end if

download_url = official_registry_base_url//download_url

if (.not. q%has_key('version')) then
call fatal_error(error, "Failed to download '"//join_path(node%namespace, node%name)//"': No version found."); return
call fatal_error(error, "Failed to download '"//join_path(namespace, name)//"': No version found."); return
end if

call get_value(q, 'version', version_str, stat=stat)
if (stat /= 0) then
call fatal_error(error, "Failed to read version data for '"//join_path(node%namespace, node%name)//"'."); return
call fatal_error(error, "Failed to read version data for '"//join_path(namespace, name)//"'."); return
end if

call new_version(version, version_str, error)
if (allocated(error)) then
call fatal_error(error, "'"//version_str//"' is not a valid version for '"// &
& join_path(node%namespace, node%name)//"'."); return
& join_path(namespace, name)//"'."); return
end if
end subroutine

Expand Down
File renamed without changes.
7 changes: 4 additions & 3 deletions src/fpm/git.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module fpm_git

public :: git_target_t, git_target_default, git_target_branch, git_target_tag, git_target_revision, git_revision, &
& git_archive, git_matches_manifest, operator(==), compressed_package_name

!> Name of the compressed package that is generated temporarily.
character(len=*), parameter :: compressed_package_name = 'compressed_package'

Expand Down Expand Up @@ -165,6 +165,8 @@ logical function git_matches_manifest(cached,manifest,verbosity,iunit)
!> while the cached dependency always stores a commit hash because it's built
!> after the repo is available (saved as git_descriptor%revision==revision).
!> So, comparing against the descriptor is not reliable
git_matches_manifest = allocated(cached%object) .eqv. allocated(manifest%object)
if (git_matches_manifest .and. allocated(cached%object)) &
git_matches_manifest = cached%object == manifest%object
if (.not.git_matches_manifest) then
if (verbosity>1) write(iunit,out_fmt) "GIT OBJECT has changed: ",cached%object," vs. ", manifest%object
Expand Down Expand Up @@ -326,8 +328,7 @@ subroutine git_archive(source, destination, error)
call fatal_error(error, "Cannot find a suitable archive format for 'git archive'."); return
end if

call execute_command_line('git archive HEAD --format='//archive_format//' -o '// &
& join_path(destination, compressed_package_name), exitstat=stat)
call execute_command_line('git archive HEAD --format='//archive_format//' -o '// destination, exitstat=stat)
if (stat /= 0) then
call fatal_error(error, "Error packing '"//source//"'."); return
end if
Expand Down
4 changes: 2 additions & 2 deletions src/fpm/manifest/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ module fpm_manifest_dependency
use fpm_git, only: git_target_t, git_target_tag, git_target_branch, &
& git_target_revision, git_target_default, operator(==), git_matches_manifest
use fpm_toml, only: toml_table, toml_key, toml_stat, get_value, check_keys
use fpm_filesystem, only: windows_path
use fpm_filesystem, only: windows_path, join_path
use fpm_environment, only: get_os_type, OS_WINDOWS
use fpm_manifest_metapackages, only: metapackage_config_t, is_meta_package, new_meta_config
use fpm_versioning, only: version_t, new_version
Expand Down Expand Up @@ -95,7 +95,7 @@ subroutine new_dependency(self, table, root, error)
call get_value(table, "path", uri)
if (allocated(uri)) then
if (get_os_type() == OS_WINDOWS) uri = windows_path(uri)
if (present(root)) uri = root//uri ! Relative to the fpm.toml it’s written in
if (present(root)) uri = join_path(root,uri) ! Relative to the fpm.toml it’s written in
call move_alloc(uri, self%path)
return
end if
Expand Down
Loading

0 comments on commit 24bdea2

Please sign in to comment.