Skip to content

Commit

Permalink
clean
Browse files Browse the repository at this point in the history
  • Loading branch information
henilp105 committed Jun 9, 2024
1 parent aa1112b commit 8496b5c
Showing 1 changed file with 28 additions and 23 deletions.
51 changes: 28 additions & 23 deletions src/fpm/cmd/search.f90
Original file line number Diff line number Diff line change
Expand Up @@ -83,14 +83,17 @@ subroutine cmd_search(settings)
if (allocated(error)) then
call fpm_stop(1, "Error retrieving package data from registry: "//settings%registry); return
end if

print *
print *, "Searching packages in Local Registry:"
print *
call search_package(settings%query, settings%namespace, settings%package, settings%version)
if (json%has_key("packages")) then
!> Shift to better method to display the package data
call get_value(json, 'packages', array)
print *
print '(A,I0,A)', ' Found ', len(array), ' packages in fpm - registry:'
print *
! call print_packages(array)
do ii=1, len(array)
call get_value(array, ii, p)
call get_value(p, 'name', name)
Expand Down Expand Up @@ -124,27 +127,8 @@ subroutine search_package(query,namespace,package,version)
call fpm_stop(1, "Error retrieving global settings"); return
end if

path = global_settings%registry_settings%cache_path

if (namespace /= "") then
wild = path//"/"//namespace
else
wild = path//"/*"
end if
if (package /= "") then
wild = wild//"/"//package
else
wild = wild//"/*"
end if
if (version /= "") then
wild = wild//"/"//version
else
wild = wild//"/?.?.?"
end if
wild = wild//"/fpm.toml"
print *
print *, "Searching packages in Local Registry:"
print *
path = global_settings%registry_settings%cache_path
wild = package_search_wild(path,namespace,package,version)

! Scan directory for packages
call list_files(path, file_names,recurse=.true.)
Expand Down Expand Up @@ -187,10 +171,31 @@ subroutine search_package(query,namespace,package,version)
call fpm_stop(1, "Error Searching for the query"); return
end if
end if

end if
end if
end do
end subroutine search_package

function package_search_wild(path,namespace,package,version) result(wild)
character(:), allocatable, intent(in) :: namespace, package, version, path
character(:), allocatable :: wild
character(:), allocatable :: array(:)
if (namespace /= "") then
wild = path//"/"//namespace
else
wild = path//"/*"
end if
if (package /= "") then
wild = wild//"/"//package
else
wild = wild//"/*"
end if
if (version /= "") then
wild = wild//"/"//version
else
wild = wild//"/?.?.?"
end if
wild = wild//"/fpm.toml"
end function package_search_wild
end

0 comments on commit 8496b5c

Please sign in to comment.