Skip to content

Commit 6f11ee9

Browse files
committed
Always replace when download
1 parent 3c03802 commit 6f11ee9

File tree

2 files changed

+66
-7
lines changed

2 files changed

+66
-7
lines changed

src/fpm/dependency.f90

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -56,9 +56,9 @@
5656
!> Currenly ignored. First come, first serve.
5757
module fpm_dependency
5858
use, intrinsic :: iso_fortran_env, only: output_unit
59-
use fpm_environment, only: get_os_type, OS_WINDOWS
59+
use fpm_environment, only: get_os_type, OS_WINDOWS, os_is_unix
6060
use fpm_error, only: error_t, fatal_error
61-
use fpm_filesystem, only: exists, join_path, mkdir, canon_path, windows_path, list_files, is_dir, basename
61+
use fpm_filesystem, only: exists, join_path, mkdir, canon_path, windows_path, list_files, is_dir, basename, os_delete_dir
6262
use fpm_git, only: git_target_revision, git_target_default, git_revision
6363
use fpm_manifest, only: package_config_t, dependency_config_t, &
6464
get_package_data
@@ -562,10 +562,11 @@ subroutine get_from_registry(self, target_dir, global_settings, error, downloade
562562
call fatal_error(error, "Error creating temporary file for downloading package '"//self%name//"'."); return
563563
end if
564564

565-
! Include version number in the cache path. In no cached version exists, download it.
565+
! Include version number in the cache path. If no cached version exists, download it.
566566
cache_path = join_path(cache_path, version%s())
567567
if (.not. exists(join_path(cache_path, 'fpm.toml'))) then
568-
if (.not. exists(cache_path)) call mkdir(cache_path)
568+
if (is_dir(cache_path)) call os_delete_dir(os_is_unix(), cache_path)
569+
call mkdir(cache_path)
569570

570571
print *, "Downloading '"//join_path(self%namespace, self%name, version%s())//"' ..."
571572
call downloader%get_file(target_url, tmp_file, error)

test/fpm_test/test_package_dependencies.f90

Lines changed: 61 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -55,9 +55,10 @@ subroutine collect_package_dependencies(tests)
5555
& new_unittest("local-registry-unspecified-has-manifest", local_registry_unspecified_has_manifest), &
5656
& new_unittest("cache-specified-version-found", cache_specified_version_found), &
5757
& new_unittest("specified-version-not-found-in-cache", registry_specified_version_not_found_in_cache), &
58-
& new_unittest("registry-specified-version-not-exists-anywhere", registry_specified_version_not_exists_anywhere, should_fail=.true.), &
58+
& new_unittest("registry-specified-version-not-exists", registry_specified_version_not_exists, should_fail=.true.), &
5959
& new_unittest("registry-specified-version-other-versions-exist", registry_specified_version_other_versions_exist), &
6060
& new_unittest("registry-unspecified-version", registry_unspecified_version), &
61+
& new_unittest("registry-unspecified-version_exists_in_cache", registry_unspecified_version_exists_in_cache), &
6162
& new_unittest("pkg-data-no-code", pkg_data_no_code, should_fail=.true.), &
6263
& new_unittest("pkg-data-corrupt-code", pkg_data_corrupt_code, should_fail=.true.), &
6364
& new_unittest("pkg-data-missing-error-message", pkg_data_missing_error_msg, should_fail=.true.), &
@@ -795,7 +796,7 @@ subroutine registry_specified_version_not_found_in_cache(error)
795796
end subroutine registry_specified_version_not_found_in_cache
796797

797798
!> Version specified in manifest, but not found in cache or registry.
798-
subroutine registry_specified_version_not_exists_anywhere(error)
799+
subroutine registry_specified_version_not_exists(error)
799800
type(error_t), allocatable, intent(out) :: error
800801

801802
type(toml_table) :: table
@@ -836,7 +837,7 @@ subroutine registry_specified_version_not_exists_anywhere(error)
836837

837838
call delete_tmp_folder
838839

839-
end subroutine registry_specified_version_not_exists_anywhere
840+
end subroutine registry_specified_version_not_exists
840841

841842
subroutine registry_specified_version_other_versions_exist(error)
842843
type(error_t), allocatable, intent(out) :: error
@@ -935,6 +936,63 @@ subroutine registry_unspecified_version(error)
935936

936937
end subroutine registry_unspecified_version
937938

939+
!> No version specified, therefore load package data from the registry. Find out that there is a cached version of
940+
!> the latest package.
941+
subroutine registry_unspecified_version_exists_in_cache(error)
942+
type(error_t), allocatable, intent(out) :: error
943+
944+
type(toml_table) :: table
945+
type(dependency_node_t) :: node
946+
type(fpm_global_settings) :: global_settings
947+
character(len=:), allocatable :: target_dir, cwd
948+
type(toml_table), pointer :: child
949+
type(mock_downloader_t) :: mock_downloader
950+
951+
call new_table(table)
952+
table%key = 'test-dep'
953+
call set_value(table, 'namespace', 'test-org')
954+
955+
call new_dependency(node%dependency_config_t, table, error=error)
956+
if (allocated(error)) return
957+
958+
call delete_tmp_folder
959+
call mkdir(join_path(tmp_folder, 'cache', 'test-org', 'test-dep', '0.0.0'))
960+
call mkdir(join_path(tmp_folder, 'cache', 'test-org', 'test-dep', '0.1.0'))
961+
call filewrite(join_path(join_path(tmp_folder, 'cache', 'test-org', 'test-dep', '0.1.0'), 'fpm.toml'), [''])
962+
call mkdir(join_path(tmp_folder, 'cache', 'test-org', 'test-dep', '1.2.1'))
963+
964+
call new_table(table)
965+
call add_table(table, 'registry', child)
966+
967+
call setup_global_settings(global_settings, error)
968+
if (allocated(error)) then
969+
call delete_tmp_folder; return
970+
end if
971+
972+
call get_registry_settings(child, global_settings, error)
973+
if (allocated(error)) then
974+
call delete_tmp_folder; return
975+
end if
976+
977+
call node%get_from_registry(target_dir, global_settings, error, mock_downloader)
978+
if (allocated(error)) then
979+
call delete_tmp_folder; return
980+
end if
981+
982+
call get_current_directory(cwd, error)
983+
if (allocated(error)) then
984+
call delete_tmp_folder; return
985+
end if
986+
987+
if (target_dir /= join_path(cwd, join_path(tmp_folder, 'dependencies', 'test-org', 'test-dep', '0.1.0'))) then
988+
call test_failed(error, "Target directory not set correctly: '"//target_dir//"'")
989+
call delete_tmp_folder; return
990+
end if
991+
992+
call delete_tmp_folder
993+
994+
end subroutine registry_unspecified_version_exists_in_cache
995+
938996
!> Package data returned from the registry does not contain a code field.
939997
subroutine pkg_data_no_code(error)
940998
type(error_t), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)