Skip to content
Merged
Show file tree
Hide file tree
Changes from 11 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
18 changes: 18 additions & 0 deletions ci/run_tests.bat
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,24 @@ if errorlevel 1 exit 1
if errorlevel 1 exit 1


cd ..\hello_complex_2
if errorlevel 1 exit 1

..\..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1

.\build\gfortran_debug\app\say_hello_world
if errorlevel 1 exit 1

.\build\gfortran_debug\app\say_goodbye
if errorlevel 1 exit 1

.\build\gfortran_debug\test\greet_test
if errorlevel 1 exit 1

.\build\gfortran_debug\test\farewell_test


cd ..\with_c
if errorlevel 1 exit 1

Expand Down
9 changes: 8 additions & 1 deletion ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,13 @@ cd ../hello_complex
./build/gfortran_debug/test/greet_test
./build/gfortran_debug/test/farewell_test

cd ../hello_complex_2
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/say_hello_world
./build/gfortran_debug/app/say_goodbye
./build/gfortran_debug/test/greet_test
./build/gfortran_debug/test/farewell_test

cd ../with_c
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/with_c
Expand All @@ -28,4 +35,4 @@ cd ../submodules

cd ../program_with_module
../../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/Program_with_module
./build/gfortran_debug/app/Program_with_module
59 changes: 44 additions & 15 deletions fpm/src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,12 +5,15 @@ module fpm
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
use fpm_filesystem, only: join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST

use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
resolve_module_dependencies
use fpm_manifest, only : get_package_data, default_executable, &
default_library, package_t
default_library, default_build_config, package_t
use fpm_error, only : error_t
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
Expand Down Expand Up @@ -54,20 +57,38 @@ subroutine build_model(model, settings, package, error)
model%link_flags = ''

! Add sources from executable directories
if (allocated(package%executable)) then
if (is_dir('app') .and. package%build_config%auto_executables) then
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
with_executables=.true., error=error)

if (allocated(error)) then
return
end if

call add_executable_sources(model%sources, package%executable, &
is_test=.false., error=error)
end if
if (is_dir('test') .and. package%build_config%auto_tests) then
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
with_executables=.true., error=error)

if (allocated(error)) then
return
end if

end if
if (allocated(package%test)) then
if (allocated(package%executable)) then
call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, &
auto_discover=package%build_config%auto_executables, &
error=error)

call add_executable_sources(model%sources, package%test, &
is_test=.true., error=error)
if (allocated(error)) then
return
end if

end if
if (allocated(package%test)) then
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
auto_discover=package%build_config%auto_tests, &
error=error)

if (allocated(error)) then
return
Expand All @@ -76,17 +97,16 @@ subroutine build_model(model, settings, package, error)
end if

if (allocated(package%library)) then

call add_sources_from_dir(model%sources,package%library%source_dir, &
error=error)
call add_sources_from_dir(model%sources, package%library%source_dir, &
FPM_SCOPE_LIB, error=error)

if (allocated(error)) then
return
end if

end if

call resolve_module_dependencies(model%sources)
call resolve_module_dependencies(model%sources,error)

end subroutine build_model

Expand All @@ -101,14 +121,23 @@ subroutine cmd_build(settings)
error stop 1
end if

call package%info(stdout,10)

! Populate default build configuration if not included
if (.not.allocated(package%build_config)) then
allocate(package%build_config)
call default_build_config(package%build_config)
end if

! Populate library in case we find the default src directory
if (.not.allocated(package%library) .and. exists("src")) then
allocate(package%library)
call default_library(package%library)
end if

! Populate executable in case we find the default app directory
if (.not.allocated(package%executable) .and. exists("app")) then
! Populate executable in case we find the default app
if (.not.allocated(package%executable) .and. &
exists(join_path('app',"main.f90"))) then
allocate(package%executable(1))
call default_executable(package%executable(1), package%name)
end if
Expand Down
14 changes: 14 additions & 0 deletions fpm/src/fpm/manifest.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
! Additionally, the required data types for users of this module are reexported
! to hide the actual implementation details.
module fpm_manifest
use fpm_manifest_build_config, only: build_config_t
use fpm_manifest_executable, only : executable_t
use fpm_manifest_library, only : library_t
use fpm_manifest_package, only : package_t, new_package
Expand All @@ -16,12 +17,25 @@ module fpm_manifest
private

public :: get_package_data, default_executable, default_library
public :: default_build_config
public :: package_t


contains


!> Populate build configuration with defaults
subroutine default_build_config(self)

!> Instance of the build configuration data
type(build_config_t), intent(out) :: self

self%auto_executables = .true.
self%auto_tests = .true.

end subroutine default_build_config


!> Populate library in case we find the default src directory
subroutine default_library(self)

Expand Down
140 changes: 140 additions & 0 deletions fpm/src/fpm/manifest/build_config.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,140 @@
!> Implementation of the build configuration data.
!
! A build table can currently have the following fields
!
! ```toml
! [build]
! auto-executables = <bool>
! auto-tests = <bool>
! ```
module fpm_manifest_build_config
use fpm_error, only : error_t, syntax_error, fatal_error
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
implicit none
private

public :: build_config_t, new_build_config


!> Configuration data for build
type :: build_config_t

!> Automatic discovery of executables
logical :: auto_executables

!> Automatic discovery of tests
logical :: auto_tests

contains

!> Print information on this instance
procedure :: info

end type build_config_t


contains


!> Construct a new build configuration from a TOML data structure
subroutine new_build_config(self, table, error)

!> Instance of the build configuration
type(build_config_t), intent(out) :: self

!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table

!> Error handling
type(error_t), allocatable, intent(out) :: error

!> Status
integer :: stat

call check(table, error)
if (allocated(error)) return

call get_value(table, "auto-executables", self%auto_executables, .true., stat=stat)

if (stat /= toml_stat%success) then
call fatal_error(error,"Error while reading value for 'auto-executables' in fpm.toml, expecting logical")
return
end if

call get_value(table, "auto-tests", self%auto_tests, .true., stat=stat)

if (stat /= toml_stat%success) then
call fatal_error(error,"Error while reading value for 'auto-tests' in fpm.toml, expecting logical")
return
end if

end subroutine new_build_config


!> Check local schema for allowed entries
subroutine check(table, error)

!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table

!> Error handling
type(error_t), allocatable, intent(out) :: error

type(toml_key), allocatable :: list(:)
integer :: ikey

call table%get_keys(list)

! table can be empty
if (size(list) < 1) return

do ikey = 1, size(list)
select case(list(ikey)%key)

case("auto-executables", "auto-tests")
continue

case default
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in [build]")
exit

end select
end do

end subroutine check


!> Write information on build configuration instance
subroutine info(self, unit, verbosity)

!> Instance of the build configuration
class(build_config_t), intent(in) :: self

!> Unit for IO
integer, intent(in) :: unit

!> Verbosity of the printout
integer, intent(in), optional :: verbosity

integer :: pr
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'

if (present(verbosity)) then
pr = verbosity
else
pr = 1
end if

if (pr < 1) return

write(unit, fmt) "Build configuration"
! if (allocated(self%auto_executables)) then
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
! end if
! if (allocated(self%auto_tests)) then
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
! end if

end subroutine info

end module fpm_manifest_build_config
18 changes: 17 additions & 1 deletion fpm/src/fpm/manifest/package.f90
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@
! [[test]]
! ```
module fpm_manifest_package
use fpm_manifest_build_config, only: build_config_t, new_build_config
use fpm_manifest_dependency, only : dependency_t, new_dependencies
use fpm_manifest_executable, only : executable_t, new_executable
use fpm_manifest_library, only : library_t, new_library
Expand All @@ -47,6 +48,9 @@ module fpm_manifest_package
!> Name of the package
character(len=:), allocatable :: name

!> Build configuration data
type(build_config_t), allocatable :: build_config

!> Library meta data
type(library_t), allocatable :: library

Expand Down Expand Up @@ -98,6 +102,13 @@ subroutine new_package(self, table, error)
return
end if

call get_value(table, "build", child, requested=.false.)
if (associated(child)) then
allocate(self%build_config)
call new_build_config(self%build_config, child, error)
if (allocated(error)) return
end if

call get_value(table, "dependencies", child, requested=.false.)
if (associated(child)) then
call new_dependencies(self%dependency, child, error)
Expand Down Expand Up @@ -184,7 +195,7 @@ subroutine check(table, error)
name_present = .true.

case("version", "license", "author", "maintainer", "copyright", &
& "description", "keywords", "categories", "homepage", &
& "description", "keywords", "categories", "homepage", "build", &
& "dependencies", "dev-dependencies", "test", "executable", &
& "library")
continue
Expand Down Expand Up @@ -229,6 +240,11 @@ subroutine info(self, unit, verbosity)
write(unit, fmt) "- name", self%name
end if

if (allocated(self%build_config)) then
write(unit, fmt) "- build configuration", ""
call self%build_config%info(unit, pr - 1)
end if

if (allocated(self%library)) then
write(unit, fmt) "- target", "archive"
call self%library%info(unit, pr - 1)
Expand Down
Loading