Skip to content
Merged
Show file tree
Hide file tree
Changes from all 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
17 changes: 9 additions & 8 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module fpm
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
use fpm_dependency, only : new_dependency_tree
use fpm_environment, only: run, get_env
use fpm_environment, only: run, get_env, get_archiver
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
Expand Down Expand Up @@ -63,6 +63,7 @@ subroutine build_model(model, settings, package, error)
model%fortran_compiler = settings%compiler
endif

model%archiver = get_archiver()
call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)

Expand Down Expand Up @@ -151,7 +152,7 @@ subroutine build_model(model, settings, package, error)
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))

if (allocated(dependency%library)) then

if (allocated(dependency%library%source_dir)) then
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
if (is_dir(lib_dir)) then
Expand All @@ -169,7 +170,7 @@ subroutine build_model(model, settings, package, error)
end if
end do
end if

end if

if (allocated(dependency%build%link)) then
Expand All @@ -187,8 +188,8 @@ subroutine build_model(model, settings, package, error)
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
write(*,*)'<INFO> COMPILER: ',settings%compiler
write(*,*)'<INFO> C COMPILER: ',model%c_compiler
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
end if

! Check for duplicate modules
Expand All @@ -199,7 +200,7 @@ subroutine build_model(model, settings, package, error)
end subroutine build_model

! Check for duplicate modules
subroutine check_modules_for_duplicates(model, duplicates_found)
subroutine check_modules_for_duplicates(model, duplicates_found)
type(fpm_model_t), intent(in) :: model
integer :: maxsize
integer :: i,j,k,l,m,modi
Expand Down Expand Up @@ -379,7 +380,7 @@ subroutine cmd_run(settings,test)

! Check all names are valid
! or no name and found more than one file
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
if ( any(.not.found) &
& .or. &
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
Expand Down Expand Up @@ -429,7 +430,7 @@ subroutine cmd_run(settings,test)
end if
end do
endif
contains
contains
subroutine compact_list_all()
integer, parameter :: LINE_WIDTH = 80
integer :: i, j, nCol
Expand Down
35 changes: 17 additions & 18 deletions src/fpm_backend.f90
Original file line number Diff line number Diff line change
@@ -1,28 +1,28 @@
!># Build backend
!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
!> to schedule and execute the compilation and linking of package targets.
!>
!>
!> The package build process (`[[build_package]]`) comprises three steps:
!>
!> 1. __Target sorting:__ topological sort of the target dependency graph (`[[sort_target]]`)
!> 2. __Target scheduling:__ group targets into schedule regions based on the sorting (`[[schedule_targets]]`)
!> 3. __Target building:__ generate targets by compilation or linking
!>
!>
!> @note If compiled with OpenMP, targets will be build in parallel where possible.
!>
!>### Incremental compilation
!> The backend process supports *incremental* compilation whereby targets are not
!> The backend process supports *incremental* compilation whereby targets are not
!> re-compiled if their corresponding dependencies have not been modified.
!>
!>
!> - Source-based targets (*i.e.* objects) are not re-compiled if the corresponding source
!> file is unmodified AND all of the target dependencies are not marked for re-compilation
!>
!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
!> target output file already exists AND all of the target dependencies are not marked for
!> re-compilation
!>
!> Source file modification is determined by a file digest (hash) which is calculated during
!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
!> successfully generated.
!>
module fpm_backend
Expand All @@ -32,7 +32,6 @@ module fpm_backend
use fpm_model, only: fpm_model_t
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE

use fpm_strings, only: string_cat

implicit none
Expand All @@ -58,9 +57,9 @@ subroutine build_package(targets,model)

! Perform depth-first topological sort of targets
do i=1,size(targets)

call sort_target(targets(i)%ptr)

end do

! Construct build schedule queue
Expand All @@ -78,20 +77,20 @@ subroutine build_package(targets,model)
end do

end do

end subroutine build_package


!> Topologically sort a target for scheduling by
!> Topologically sort a target for scheduling by
!> recursing over its dependencies.
!>
!>
!> Checks disk-cached source hashes to determine if objects are
!> up-to-date. Up-to-date sources are tagged as skipped.
!>
!> On completion, `target` should either be marked as
!> On completion, `target` should either be marked as
!> sorted (`target%sorted=.true.`) or skipped (`target%skip=.true.`)
!>
!> If `target` is marked as sorted, `target%schedule` should be an
!> If `target` is marked as sorted, `target%schedule` should be an
!> integer greater than zero indicating the region for scheduling
!>
recursive subroutine sort_target(target)
Expand Down Expand Up @@ -162,7 +161,7 @@ recursive subroutine sort_target(target)
end if

end do

! Mark flag as processed: either sorted or skipped
target%sorted = .not.target%skip

Expand Down Expand Up @@ -246,12 +245,12 @@ subroutine build_target(model,target)
// " -o " // target%output_file)

case (FPM_TARGET_EXECUTABLE)

call run(model%fortran_compiler// " " // target%compile_flags &
//" "//target%link_flags// " -o " // target%output_file)

case (FPM_TARGET_ARCHIVE)
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))

end select

Expand Down
27 changes: 24 additions & 3 deletions src/fpm_environment.f90
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!> This module contains procedures that interact with the programming environment.
!!
!!
!! * [get_os_type] -- Determine the OS type
!! * [get_env] -- return the value of an environment variable
module fpm_environment
Expand All @@ -9,6 +9,7 @@ module fpm_environment
public :: os_is_unix
public :: run
public :: get_env
public :: get_archiver

integer, parameter, public :: OS_UNKNOWN = 0
integer, parameter, public :: OS_LINUX = 1
Expand Down Expand Up @@ -110,7 +111,7 @@ integer function get_os_type() result(r)
end if
end function get_os_type

!> Compare the output of [[get_os_type]] or the optional
!> Compare the output of [[get_os_type]] or the optional
!! passed INTEGER value to the value for OS_WINDOWS
!! and return .TRUE. if they match and .FALSE. otherwise
logical function os_is_unix(os) result(unix)
Expand Down Expand Up @@ -150,7 +151,7 @@ end subroutine run
function get_env(NAME,DEFAULT) result(VALUE)
implicit none
!> name of environment variable to get the value of
character(len=*),intent(in) :: NAME
character(len=*),intent(in) :: NAME
!> default value to return if the requested value is undefined or blank
character(len=*),intent(in),optional :: DEFAULT
!> the returned value
Expand Down Expand Up @@ -182,4 +183,24 @@ function get_env(NAME,DEFAULT) result(VALUE)
if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
end function get_env

function get_archiver() result(archiver)
character(:), allocatable :: archiver

associate(os_type => get_os_type())
if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
archiver = "ar -rs "
else
block
integer :: estat

call execute_command_line("ar --version", exitstat=estat)
if (estat /= 0) then
archiver = "lib /OUT:"
else
archiver = "ar -rs "
end if
end block
end if
end associate
end function
end module fpm_environment
7 changes: 5 additions & 2 deletions src/fpm_model.f90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
!># The fpm package model
!>
!> Defines the fpm model data types which encapsulate all information
!> Defines the fpm model data types which encapsulate all information
!> required to correctly build a package and its dependencies.
!>
!> The process (see `[[build_model(subroutine)]]`) for generating a valid `[[fpm_model]]` involves
Expand Down Expand Up @@ -117,6 +117,9 @@ module fpm_model
!> Command line name to invoke fortran compiler
character(:), allocatable :: fortran_compiler

!> Command line to invoke for creating static library
character(:), allocatable :: archiver

!> Command line name to invoke c compiler
character(:), allocatable :: c_compiler

Expand All @@ -131,7 +134,7 @@ module fpm_model

!> Native libraries to link against
type(string_t), allocatable :: link_libraries(:)

!> External modules used
type(string_t), allocatable :: external_modules(:)

Expand Down