-
Notifications
You must be signed in to change notification settings - Fork 108
/
Copy pathsearch.f90
151 lines (128 loc) · 6.23 KB
/
search.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
!> Search a package from both local and remote registry using the `search` command.
!>
!> The package can be searched by packagename, namespace, query (description and README.md), and license from the registries (local and remote).
!> the remote registry URL can also be specified by the paramter --registry.
!> It can be used as `fpm search --query fortran --page 2 --name fortran --namespace fortran --license MIT --registry URL`.
module fpm_cmd_search
use fpm_command_line, only: fpm_search_settings
use fpm_manifest, only: package_config_t, get_package_data
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_temp_filename, delete_file, basename, &
canon_path, dirname, list_files, is_hidden_file
use fpm_git, only: git_archive
use fpm_downloader, only: downloader_t
use fpm_strings, only: string_t, string_array_contains, split, str
use fpm, only: build_model
use fpm_error, only : error_t, fatal_error, fpm_stop
use jonquil, only : json_object
use tomlf, only : toml_array, get_value, len, toml_key
use fpm_settings, only: fpm_global_settings, get_global_settings, official_registry_base_url
implicit none
private
public :: cmd_search
contains
!> Search the fpm registry for a package
subroutine cmd_search(settings)
!> Settings for the search command.
class(fpm_search_settings), intent(in) :: settings
type(fpm_global_settings) :: global_settings
character(:), allocatable :: tmp_file, name, namespace, description, query_url
type(toml_key), allocatable :: list(:)
integer :: stat, unit, ii
type(json_object) :: json
type(json_object), pointer :: p
!> Error handling.
type(error_t), allocatable :: error
type(toml_array), pointer :: array
type(version_t), allocatable :: version
!> Downloader instance.
class(downloader_t), allocatable :: downloader
allocate (downloader)
call get_global_settings(global_settings, error)
if (allocated(error)) then
call fpm_stop(1, "Error retrieving global settings"); return
end if
print *,global_settings%registry_settings%cache_path
! print *,global_settings%registry_settings%path
! print *,global_settings%registry_settings%url
! print *,global_settings%path_to_config_folder
! new function to search package names, namespace.
! query general term for description (both toml and readme)
! search by namespace, package, license
! search by namespace , package.
! from fpm.toml -> description and license
! README.md -> description
!> Generate a temporary file to store the downloaded package search data
tmp_file = get_temp_filename()
open (newunit=unit, file=tmp_file, action='readwrite', iostat=stat)
if (stat /= 0) then
call fatal_error(error, "Error creating temporary file for downloading package."); return
end if
query_url = settings%registry//'/packages?query='//settings%query//'&page='//settings%page
!> Get the package data from the registry
call downloader%get_pkg_data(query_url, version, tmp_file, json, error)
close (unit)
if (allocated(error)) then
call fpm_stop(1, "Error retrieving package data from registry: "//settings%registry); return
end if
call search_namespace(settings%namespace)
if (.not.json%has_key("packages")) then
call get_value(json, 'packages', array)
print '(A,I0,A)', ' Found ', len(array), ' packages:'
do ii=1, len(array)
call get_value(array, ii, p)
call get_value(p, 'name', name)
call get_value(p, 'namespace', namespace)
call get_value(p, 'description', description)
print *, "Name: ", name
print *, "namespace: ", namespace
print *, "Description: ", description
print *, ""
end do
else
call fpm_stop(1, "Invalid package data returned"); return
end if
end subroutine cmd_search
subroutine search_namespace(namespace)
type(fpm_global_settings) :: global_settings
type(error_t), allocatable :: error
character(:), allocatable, intent(in) :: namespace
character(:), allocatable :: path
character(:), allocatable :: array(:)
type(string_t), allocatable :: file_names(:)
integer :: i,j
call get_global_settings(global_settings, error)
if (allocated(error)) then
call fpm_stop(1, "Error retrieving global settings"); return
end if
! print *,global_settings%registry_settings%cache_path
print *, "Searching for namespace: ", namespace
if (exists(join_path(global_settings%registry_settings%cache_path, namespace))) then
! print *, "Namespace: ", namespace
path = join_path(global_settings%registry_settings%cache_path, namespace)
! Scan directory for sources
call list_files(path, file_names,recurse=.false.)
print *, "Found "//str(size(file_names))//" package(s) in namespace in the local registry."
do i=1,size(file_names)
if (.not.is_hidden_file(file_names(i)%s)) then
call split(file_names(i)%s,array,'/')
print *,"Package: ", array(size(array))
print *, "Add as Dependency: "
print *, array(size(array)), " = { namespace = '", namespace, "' }"
end if
end do
else
print *, "Namespace not found in local registry. Searching remote registry."
end if
end subroutine search_namespace
! subroutine print_upload_data(upload_data)
! type(string_t), intent(in) :: upload_data(:)
! integer :: i
! print *, 'Upload data:'
! do i = 1, size(upload_data)
! print *, upload_data(i)%s
! end do
! end
end