Skip to content

Commit

Permalink
Merge branch 'main' into add-dry-run-http-request
Browse files Browse the repository at this point in the history
# Conflicts:
#	src/fpm/cmd/publish.f90
  • Loading branch information
minhqdao committed Jun 25, 2023
2 parents 613bf83 + ee397ac commit 94d1438
Show file tree
Hide file tree
Showing 16 changed files with 309 additions and 199 deletions.
13 changes: 7 additions & 6 deletions .github/workflows/meta.yml
Original file line number Diff line number Diff line change
Expand Up @@ -14,11 +14,12 @@ on:

env:
CI: "ON" # We can detect this in the build system and other vendors implement it
HOMEBREW_NO_ANALYTICS: "ON" # Make Homebrew installation a little quicker
HOMEBREW_NO_AUTO_UPDATE: "ON"
HOMEBREW_NO_BOTTLE_SOURCE_FALLBACK: "ON"
HOMEBREW_NO_GITHUB_API: "ON"
HOMEBREW_NO_INSTALL_CLEANUP: "ON"
HOMEBREW_NO_ANALYTICS: 1 # Make Homebrew installation a little quicker
HOMEBREW_NO_AUTO_UPDATE: 1
HOMEBREW_NO_BOTTLE_SOURCE_FALLBACK: 1
HOMEBREW_NO_GITHUB_API: 1
HOMEBREW_NO_INSTALL_CLEANUP: 1
HOMEBREW_NO_INSTALLED_DEPENDENTS_CHECK: 1

jobs:

Expand Down Expand Up @@ -198,7 +199,7 @@ jobs:
- name: (macOS) Install homebrew OpenMPI
if: contains(matrix.mpi,'openmpi') && contains(matrix.os,'macos')
run: |
brew install --cc=gcc-${{ env.GCC_V }} openmpi
brew install openmpi #--cc=gcc-${{ env.GCC_V }} openmpi
# Phase 1: Bootstrap fpm with existing version
- name: Install fpm
Expand Down
2 changes: 1 addition & 1 deletion fpm.toml
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ M_CLI2.rev = "7264878cdb1baff7323cc48596d829ccfe7751b8"
fortran-regex.git = "https://github.com/perazz/fortran-regex"
fortran-regex.tag = "1.1.2"
jonquil.git = "https://github.com/toml-f/jonquil"
jonquil.rev = "4c27c8c1e411fa8790dffcf8c3fa7a27b6322273"
jonquil.rev = "4fbd4cf34d577c0fd25e32667ee9e41bf231ece8"

[[test]]
name = "cli-test"
Expand Down
70 changes: 36 additions & 34 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,10 +21,12 @@ 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,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
use, intrinsic :: iso_fortran_env, only : stdin => input_unit, &
& stdout => output_unit, &
& stderr => error_unit
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
use fpm_environment, only: os_is_unix

implicit none
private
public :: cmd_build, cmd_run, cmd_clean
Expand All @@ -42,7 +44,6 @@ subroutine build_model(model, settings, package, error)
integer :: i, j
type(package_config_t) :: dependency
character(len=:), allocatable :: manifest, lib_dir
character(len=:), allocatable :: version
logical :: has_cpp
logical :: duplicates_found
type(string_t) :: include_dir
Expand Down Expand Up @@ -324,7 +325,7 @@ end subroutine check_modules_for_duplicates
subroutine check_module_names(model, error)
type(fpm_model_t), intent(in) :: model
type(error_t), allocatable, intent(out) :: error
integer :: i,j,k,l,m
integer :: k,l,m
logical :: valid,errors_found,enforce_this_file
type(string_t) :: package_name,module_name,package_prefix

Expand Down Expand Up @@ -617,29 +618,29 @@ subroutine cmd_run(settings,test)
call fpm_stop(stat(firsterror),'*cmd_run*:stopping due to failed executions')
end if

endif
end if

contains

subroutine compact_list_all()
integer, parameter :: LINE_WIDTH = 80
integer :: i, j, nCol
j = 1
integer :: ii, jj, nCol
jj = 1
nCol = LINE_WIDTH/col_width
write(stderr,*) 'Available names:'
do i=1,size(targets)
do ii=1,size(targets)

exe_target => targets(i)%ptr
exe_target => targets(ii)%ptr

if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
allocated(exe_target%dependencies)) then

exe_source => exe_target%dependencies(1)%ptr%source

if (exe_source%unit_scope == run_scope) then

write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
write(stderr,'(A)',advance=(merge("yes","no ",modulo(jj,nCol)==0))) &
& [character(len=col_width) :: basename(exe_target%output_file, suffix=.false.)]
j = j + 1

jj = jj + 1
end if
end if
end do
Expand All @@ -648,15 +649,15 @@ end subroutine compact_list_all

subroutine compact_list()
integer, parameter :: LINE_WIDTH = 80
integer :: i, j, nCol
j = 1
integer :: ii, jj, nCol
jj = 1
nCol = LINE_WIDTH/col_width
write(stderr,*) 'Matched names:'
do i=1,size(executables)
write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
& [character(len=col_width) :: basename(executables(i)%s, suffix=.false.)]
j = j + 1
enddo
do ii=1,size(executables)
write(stderr,'(A)',advance=(merge("yes","no ",modulo(jj,nCol)==0))) &
& [character(len=col_width) :: basename(executables(ii)%s, suffix=.false.)]
jj = jj + 1
end do
write(stderr,*)
end subroutine compact_list

Expand All @@ -677,27 +678,28 @@ subroutine delete_skip(is_unix)
end do
end subroutine delete_skip

!> Delete the build directory including or excluding dependencies.
subroutine cmd_clean(settings)
!> fpm clean called
!> Settings for the clean command.
class(fpm_clean_settings), intent(in) :: settings
! character(len=:), allocatable :: dir
! type(string_t), allocatable :: files(:)
character(len=1) :: response

character :: user_response

if (is_dir('build')) then
! remove the entire build directory
! Remove the entire build directory
if (settings%clean_call) then
call os_delete_dir(settings%is_unix, 'build')
return
call os_delete_dir(os_is_unix(), 'build'); return
end if
! remove the build directory but skip dependencies

! Remove the build directory but skip dependencies
if (settings%clean_skip) then
call delete_skip(settings%is_unix)
return
call delete_skip(os_is_unix()); return
end if
! prompt to remove the build directory but skip dependencies

! Prompt to remove the build directory but skip dependencies
write(stdout, '(A)', advance='no') "Delete build, excluding dependencies (y/n)? "
read(stdin, '(A1)') response
if (lower(response) == 'y') call delete_skip(settings%is_unix)
read(stdin, '(A1)') user_response
if (lower(user_response) == 'y') call delete_skip(os_is_unix())
else
write (stdout, '(A)') "fpm: No build directory found."
end if
Expand Down
6 changes: 3 additions & 3 deletions src/fpm/cmd/publish.f90
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,7 @@ subroutine cmd_publish(settings)
end do

tmp_file = get_temp_filename()
call git_archive('.', tmp_file, error)
call git_archive('.', tmp_file, 'HEAD', settings%verbose, error)
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Archive error: '//error%message)

upload_data = [ &
Expand Down Expand Up @@ -97,16 +97,16 @@ subroutine cmd_publish(settings)
end if

if (settings%verbose) then
print *, ''
call print_upload_data(upload_data)
print *, ''
end if

call downloader%upload_form(official_registry_base_url//'/packages', upload_data, error)
call downloader%upload_form(official_registry_base_url//'/packages', upload_data, settings%verbose, error)
if (allocated(error)) then
call delete_file(tmp_file); call fpm_stop(1, '*cmd_publish* Upload error: '//error%message)
end if

call downloader%upload_form(official_registry_base_url//'/packages', upload_data, settings%verbose, error)
if (settings%is_dry_run) then
print *, 'Generated tarball: ', tmp_file
else
Expand Down
6 changes: 2 additions & 4 deletions src/fpm/cmd/update.f90
Original file line number Diff line number Diff line change
Expand Up @@ -24,15 +24,13 @@ subroutine cmd_update(settings)
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
call handle_error(error)

if (.not.exists("build")) then
if (.not. exists("build")) then
call mkdir("build")
call filewrite(join_path("build", ".gitignore"),["*"])
end if

cache = join_path("build", "cache.toml")
if (settings%clean) then
call delete_file(cache)
end if
if (settings%clean) call delete_file(cache)

call new_dependency_tree(deps, cache=cache, &
verbosity=merge(2, 1, settings%verbose))
Expand Down
56 changes: 27 additions & 29 deletions src/fpm/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,9 @@ module fpm_dependency
type(dependency_node_t), allocatable :: dep(:)
!> Cache file
character(len=:), allocatable :: cache

contains

!> Overload procedure to add new dependencies to the tree
generic :: add => add_project, add_project_dependencies, add_dependencies, &
add_dependency, add_dependency_node
Expand Down Expand Up @@ -194,13 +196,9 @@ subroutine new_dependency_tree(self, verbosity, cache)
call resize(self%dep)
self%dep_dir = join_path("build", "dependencies")

if (present(verbosity)) then
self%verbosity = verbosity
end if
if (present(verbosity)) self%verbosity = verbosity

if (present(cache)) then
self%cache = cache
end if
if (present(cache)) self%cache = cache

end subroutine new_dependency_tree

Expand Down Expand Up @@ -311,15 +309,15 @@ subroutine add_project(self, package, error)

! After resolving all dependencies, check if we have cached ones to avoid updates
if (allocated(self%cache)) then
call new_dependency_tree(cached, verbosity=self%verbosity,cache=self%cache)
call new_dependency_tree(cached, verbosity=self%verbosity, cache=self%cache)
call cached%load(self%cache, error)
if (allocated(error)) return

! Skip root node
do id=2,cached%ndep
cached%dep(id)%cached = .true.
call self%add(cached%dep(id), error)
if (allocated(error)) return
do id = 2, cached%ndep
cached%dep(id)%cached = .true.
call self%add(cached%dep(id), error)
if (allocated(error)) return
end do
end if

Expand Down Expand Up @@ -443,13 +441,13 @@ subroutine add_dependency_node(self, dependency, error)
! the manifest has priority
if (dependency%cached) then
if (dependency_has_changed(dependency, self%dep(id), self%verbosity, self%unit)) then
if (self%verbosity>0) write (self%unit, out_fmt) "Dependency change detected:", dependency%name
self%dep(id)%update = .true.
if (self%verbosity > 0) write (self%unit, out_fmt) "Dependency change detected:", dependency%name
self%dep(id)%update = .true.
else
! Store the cached one
self%dep(id) = dependency
self%dep(id)%update = .false.
endif
! Store the cached one
self%dep(id) = dependency
self%dep(id)%update = .false.
end if
end if
else
! New dependency: add from scratch
Expand Down Expand Up @@ -498,7 +496,7 @@ subroutine update_dependency(self, name, error)

associate (dep => self%dep(id))
if (allocated(dep%git) .and. dep%update) then
if (self%verbosity>0) write (self%unit, out_fmt) "Update:", dep%name
if (self%verbosity > 0) write (self%unit, out_fmt) "Update:", dep%name
proj_dir = join_path(self%dep_dir, dep%name)
call dep%git%checkout(proj_dir, error)
if (allocated(error)) return
Expand Down Expand Up @@ -722,7 +720,7 @@ subroutine check_and_read_pkg_data(json, node, download_url, version, error)
character(:), allocatable :: version_key, version_str, error_message, namespace, name

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

Expand Down Expand Up @@ -1199,27 +1197,27 @@ logical function dependency_has_changed(cached, manifest, verbosity, iunit) resu
!> may not have it
if (allocated(cached%version) .and. allocated(manifest%version)) then
if (cached%version /= manifest%version) then
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed: "//cached%version%s()//" vs. "//manifest%version%s()
return
endif
if (verbosity > 1) write (iunit, out_fmt) "VERSION has changed: "//cached%version%s()//" vs. "//manifest%version%s()
return
end if
else
if (verbosity>1) write(iunit,out_fmt) "VERSION has changed presence "
if (verbosity > 1) write (iunit, out_fmt) "VERSION has changed presence "
end if
if (allocated(cached%revision) .and. allocated(manifest%revision)) then
if (cached%revision /= manifest%revision) then
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
if (verbosity > 1) write (iunit, out_fmt) "REVISION has changed: "//cached%revision//" vs. "//manifest%revision
return
endif
end if
else
if (verbosity>1) write(iunit,out_fmt) "REVISION has changed presence "
if (verbosity > 1) write (iunit, out_fmt) "REVISION has changed presence "
end if
if (allocated(cached%proj_dir) .and. allocated(manifest%proj_dir)) then
if (cached%proj_dir /= manifest%proj_dir) then
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed: "//cached%proj_dir//" vs. "//manifest%proj_dir
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed: "//cached%proj_dir//" vs. "//manifest%proj_dir
return
endif
end if
else
if (verbosity>1) write(iunit,out_fmt) "PROJECT DIR has changed presence "
if (verbosity > 1) write (iunit, out_fmt) "PROJECT DIR has changed presence "
end if

!> All checks passed: the two dependencies have no differences
Expand Down
16 changes: 12 additions & 4 deletions src/fpm/downloader.f90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module fpm_downloader
use fpm_error, only: error_t, fatal_error
use fpm_filesystem, only: which
use fpm_filesystem, only: which, run
use fpm_versioning, only: version_t
use jonquil, only: json_object, json_value, json_error, json_load, cast_to_object
use fpm_strings, only: string_t
Expand Down Expand Up @@ -76,9 +76,14 @@ subroutine get_file(url, tmp_pkg_file, error)
end

!> Perform an http post request with form data.
subroutine upload_form(endpoint, form_data, error)
subroutine upload_form(endpoint, form_data, verbose, error)
!> Endpoint to upload to.
character(len=*), intent(in) :: endpoint
!> Form data to upload.
type(string_t), intent(in) :: form_data(:)
!> Print additional information if true.
logical, intent(in) :: verbose
!> Error handling.
type(error_t), allocatable, intent(out) :: error

integer :: stat, i
Expand All @@ -91,8 +96,8 @@ subroutine upload_form(endpoint, form_data, error)

if (which('curl') /= '') then
print *, 'Uploading package ...'
call execute_command_line('curl -X POST -H "Content-Type: multipart/form-data" ' &
& //form_data_str//endpoint, exitstat=stat)
call run('curl -X POST -H "Content-Type: multipart/form-data" '// &
& form_data_str//endpoint, exitstat=stat, echo=verbose)
else
call fatal_error(error, "'curl' not installed."); return
end if
Expand All @@ -104,8 +109,11 @@ subroutine upload_form(endpoint, form_data, error)

!> Unpack a tarball to a destination.
subroutine unpack(tmp_pkg_file, destination, error)
!> Path to tarball.
character(*), intent(in) :: tmp_pkg_file
!> Destination to unpack to.
character(*), intent(in) :: destination
!> Error handling.
type(error_t), allocatable, intent(out) :: error

integer :: stat
Expand Down
Loading

0 comments on commit 94d1438

Please sign in to comment.