Skip to content

Commit 36edb6c

Browse files
authored
Enforce module naming (#828)
1 parent 4ebb18e commit 36edb6c

File tree

8 files changed

+698
-27
lines changed

8 files changed

+698
-27
lines changed

.gitignore

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,4 +4,5 @@ build/*
44
.vscode/
55

66
# CodeBlocks
7-
project/*
7+
project/
8+

src/fpm.f90

Lines changed: 108 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module fpm
22
use fpm_strings, only: string_t, operator(.in.), glob, join, string_cat, &
3-
lower, str_ends_with
3+
lower, str_ends_with, is_fortran_name, str_begins_with_str, &
4+
is_valid_module_name, len_trim
45
use fpm_backend, only: build_package
56
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
67
fpm_run_settings, fpm_install_settings, fpm_test_settings, &
@@ -92,6 +93,8 @@ subroutine build_model(model, settings, package, error)
9293
model%build_prefix = join_path("build", basename(model%compiler%fc))
9394

9495
model%include_tests = settings%build_tests
96+
model%enforce_module_names = package%build%module_naming
97+
model%module_prefix = package%build%module_prefix
9598

9699
allocate(model%packages(model%deps%ndep))
97100

@@ -107,7 +110,7 @@ subroutine build_model(model, settings, package, error)
107110
model%packages(i)%name = dependency%name
108111
call package%version%to_string(version)
109112
model%packages(i)%version = version
110-
113+
111114
if (allocated(dependency%preprocess)) then
112115
do j = 1, size(dependency%preprocess)
113116
if (dependency%preprocess(j)%name == "cpp") then
@@ -153,6 +156,11 @@ subroutine build_model(model, settings, package, error)
153156
if (allocated(dependency%build%external_modules)) then
154157
model%external_modules = [model%external_modules, dependency%build%external_modules]
155158
end if
159+
160+
! Copy naming conventions from this dependency's manifest
161+
model%packages(i)%enforce_module_names = dependency%build%module_naming
162+
model%packages(i)%module_prefix = dependency%build%module_prefix
163+
156164
end associate
157165
end do
158166
if (allocated(error)) return
@@ -233,7 +241,11 @@ subroutine build_model(model, settings, package, error)
233241
write(*,*)'<INFO> CXX COMPILER OPTIONS: ', model%cxx_compile_flags
234242
write(*,*)'<INFO> LINKER OPTIONS: ', model%link_flags
235243
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
236-
end if
244+
end if
245+
246+
! Check for invalid module names
247+
call check_module_names(model, error)
248+
if (allocated(error)) return
237249

238250
! Check for duplicate modules
239251
call check_modules_for_duplicates(model, duplicates_found)
@@ -286,6 +298,99 @@ subroutine check_modules_for_duplicates(model, duplicates_found)
286298
end do
287299
end subroutine check_modules_for_duplicates
288300

301+
! Check names of all modules in this package and its dependencies
302+
subroutine check_module_names(model, error)
303+
type(fpm_model_t), intent(in) :: model
304+
type(error_t), allocatable, intent(out) :: error
305+
integer :: i,j,k,l,m
306+
logical :: valid,errors_found,enforce_this_file
307+
type(string_t) :: package_name,module_name,package_prefix
308+
309+
errors_found = .false.
310+
311+
! Loop through modules provided by each source file of every package
312+
! Add it to the array if it is not already there
313+
! Otherwise print out warning about duplicates
314+
do k=1,size(model%packages)
315+
316+
package_name = string_t(model%packages(k)%name)
317+
318+
! Custom prefix is taken from each dependency's manifest
319+
if (model%packages(k)%enforce_module_names) then
320+
package_prefix = model%packages(k)%module_prefix
321+
else
322+
package_prefix = string_t("")
323+
end if
324+
325+
! Warn the user if some of the dependencies have loose naming
326+
if (model%enforce_module_names .and. .not.model%packages(k)%enforce_module_names) then
327+
write(stderr, *) "Warning: Dependency ",package_name%s // &
328+
" does not enforce module naming, but project does. "
329+
end if
330+
331+
do l=1,size(model%packages(k)%sources)
332+
333+
! Module naming is not enforced in test modules
334+
enforce_this_file = model%enforce_module_names .and. &
335+
model%packages(k)%sources(l)%unit_scope/=FPM_SCOPE_TEST
336+
337+
if (allocated(model%packages(k)%sources(l)%modules_provided)) then
338+
339+
do m=1,size(model%packages(k)%sources(l)%modules_provided)
340+
341+
module_name = model%packages(k)%sources(l)%modules_provided(m)
342+
343+
valid = is_valid_module_name(module_name, &
344+
package_name, &
345+
package_prefix, &
346+
enforce_this_file)
347+
348+
if (.not.valid) then
349+
350+
if (enforce_this_file) then
351+
352+
if (len_trim(package_prefix)>0) then
353+
354+
write(stderr, *) "ERROR: Module ",module_name%s, &
355+
" in ",model%packages(k)%sources(l)%file_name, &
356+
" does not match its package name ("//package_name%s// &
357+
") or custom prefix ("//package_prefix%s//")."
358+
else
359+
360+
write(stderr, *) "ERROR: Module ",module_name%s, &
361+
" in ",model%packages(k)%sources(l)%file_name, &
362+
" does not match its package name ("//package_name%s//")."
363+
364+
endif
365+
366+
else
367+
368+
write(stderr, *) "ERROR: Module ",module_name%s, &
369+
" in ",model%packages(k)%sources(l)%file_name, &
370+
" has an invalid Fortran name. "
371+
372+
end if
373+
374+
errors_found = .true.
375+
376+
end if
377+
end do
378+
end if
379+
end do
380+
end do
381+
382+
if (errors_found) then
383+
384+
if (model%enforce_module_names) &
385+
write(stderr, *) " Hint: Try disabling module naming in the manifest: [build] module-naming=false . "
386+
387+
call fatal_error(error,"The package contains invalid module names. "// &
388+
"Naming conventions "//merge('are','not',model%enforce_module_names)// &
389+
" being requested.")
390+
end if
391+
392+
end subroutine check_module_names
393+
289394
subroutine cmd_build(settings)
290395
type(fpm_build_settings), intent(in) :: settings
291396
type(package_config_t) :: package

src/fpm/manifest/build.f90

Lines changed: 38 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,14 +11,13 @@
1111
!>```
1212
module fpm_manifest_build
1313
use fpm_error, only : error_t, syntax_error, fatal_error
14-
use fpm_strings, only : string_t
14+
use fpm_strings, only : string_t, len_trim, is_valid_module_prefix
1515
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
1616
implicit none
1717
private
1818

1919
public :: build_config_t, new_build_config
2020

21-
2221
!> Configuration data for build
2322
type :: build_config_t
2423

@@ -31,6 +30,10 @@ module fpm_manifest_build
3130
!> Automatic discovery of tests
3231
logical :: auto_tests
3332

33+
!> Enforcing of package module names
34+
logical :: module_naming = .false.
35+
type(string_t) :: module_prefix
36+
3437
!> Libraries to link against
3538
type(string_t), allocatable :: link(:)
3639

@@ -86,6 +89,35 @@ subroutine new_build_config(self, table, error)
8689
return
8790
end if
8891

92+
!> Module naming: fist, attempt boolean value first
93+
call get_value(table, "module-naming", self%module_naming, .false., stat=stat)
94+
95+
if (stat == toml_stat%success) then
96+
97+
! Boolean value found. Set no custom prefix. This also falls back to
98+
! key not provided
99+
self%module_prefix = string_t("")
100+
101+
else
102+
103+
!> Value found, but not a boolean. Attempt to read a prefix string
104+
call get_value(table, "module-naming", self%module_prefix%s)
105+
106+
if (.not.allocated(self%module_prefix%s)) then
107+
call syntax_error(error,"Could not read value for 'module-naming' in fpm.toml, expecting logical or a string")
108+
return
109+
end if
110+
111+
if (.not.is_valid_module_prefix(self%module_prefix)) then
112+
call syntax_error(error,"Invalid custom module name prefix for in fpm.toml: <"//self%module_prefix%s// &
113+
">, expecting a valid alphanumeric string")
114+
return
115+
end if
116+
117+
! Set module naming to ON
118+
self%module_naming = .true.
119+
120+
end if
89121

90122
call get_list(table, "link", self%link, error)
91123
if (allocated(error)) return
@@ -95,7 +127,6 @@ subroutine new_build_config(self, table, error)
95127

96128
end subroutine new_build_config
97129

98-
99130
!> Check local schema for allowed entries
100131
subroutine check(table, error)
101132

@@ -119,6 +150,9 @@ subroutine check(table, error)
119150
case("auto-executables", "auto-examples", "auto-tests", "link", "external-modules")
120151
continue
121152

153+
case ("module-naming")
154+
continue
155+
122156
case default
123157
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in [build]")
124158
exit
@@ -156,6 +190,7 @@ subroutine info(self, unit, verbosity)
156190
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
157191
write(unit, fmt) " - auto-discovery (examples) ", merge("enabled ", "disabled", self%auto_examples)
158192
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
193+
write(unit, fmt) " - enforce module naming ", merge("enabled ", "disabled", self%module_naming)
159194
if (allocated(self%link)) then
160195
write(unit, fmt) " - link against"
161196
do ilink = 1, size(self%link)

src/fpm_model.f90

Lines changed: 25 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ module fpm_model
3838
use iso_fortran_env, only: int64
3939
use fpm_compiler, only: compiler_t, archiver_t, debug
4040
use fpm_dependency, only: dependency_tree_t
41-
use fpm_strings, only: string_t, str
41+
use fpm_strings, only: string_t, str, len_trim
4242
implicit none
4343

4444
private
@@ -130,6 +130,10 @@ module fpm_model
130130
!> Package version number.
131131
character(:), allocatable :: version
132132

133+
!> Module naming conventions
134+
logical :: enforce_module_names
135+
type(string_t) :: module_prefix
136+
133137
end type package_t
134138

135139

@@ -179,6 +183,10 @@ module fpm_model
179183
!> Whether tests should be added to the build list
180184
logical :: include_tests = .true.
181185

186+
!> Whether module names should be prefixed with the package name
187+
logical :: enforce_module_names = .false.
188+
type(string_t) :: module_prefix
189+
182190
end type fpm_model_t
183191

184192
contains
@@ -199,6 +207,14 @@ function info_package(p) result(s)
199207
if (i < size(p%sources)) s = s // ", "
200208
end do
201209
s = s // "]"
210+
211+
! Print module naming convention
212+
s = s // ', enforce_module_names="' // merge('T','F',p%enforce_module_names) // '"'
213+
214+
! Print custom prefix
215+
if (p%enforce_module_names .and. len_trim(p%module_prefix)>0) &
216+
s = s // ', custom_prefix="' // p%module_prefix%s // '"'
217+
202218
s = s // ")"
203219

204220
end function info_package
@@ -343,6 +359,14 @@ function info_model(model) result(s)
343359
! TODO: print `dependency_tree_t` properly, which should become part of the
344360
! model, not imported from another file
345361
s = s // ", deps=dependency_tree_t(...)"
362+
363+
! Print module naming convention
364+
s = s // ', enforce_module_names="' // merge('T','F',model%enforce_module_names) // '"'
365+
366+
! Print custom prefix
367+
if (model%enforce_module_names .and. len_trim(model%module_prefix)>0) &
368+
s = s // ', custom_prefix="' // model%module_prefix%s // '"'
369+
346370
!end type fpm_model_t
347371
s = s // ")"
348372
end function info_model

0 commit comments

Comments
 (0)