cmd_install Subroutine

public subroutine cmd_install(settings)

Entry point for the fpm-install subcommand

Arguments

Type IntentOptional Attributes Name
type(fpm_install_settings), intent(inout) :: settings

Representation of the command line settings


Source Code

  subroutine cmd_install(settings)
    !> Representation of the command line settings
    type(fpm_install_settings), intent(inout) :: settings
    type(package_config_t) :: package
    type(error_t), allocatable :: error
    type(fpm_model_t) :: model
    type(build_target_ptr), allocatable :: targets(:)
    type(installer_t) :: installer
    type(string_t), allocatable :: list(:)
    logical :: installable

    call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
    call handle_error(error)

    call build_model(model, settings, package, error)
    call handle_error(error)

    call targets_from_sources(targets, model, settings%prune, error)
    call handle_error(error)

    installable = (allocated(package%library) .and. package%install%library) &
      .or. allocated(package%executable)
    if (.not.installable) then
      call fatal_error(error, "Project does not contain any installable targets")
      call handle_error(error)
    end if

    if (settings%list) then
      call install_info(output_unit, targets)
      return
    end if

    if (.not.settings%no_rebuild) then
      call build_package(targets,model,verbose=settings%verbose)
    end if

    call new_installer(installer, prefix=settings%prefix, &
      bindir=settings%bindir, libdir=settings%libdir, &
      includedir=settings%includedir, &
      verbosity=merge(2, 1, settings%verbose))

    if (allocated(package%library) .and. package%install%library) then
      call filter_library_targets(targets, list)

      if (size(list) > 0) then
        call installer%install_library(list(1)%s, error)
        call handle_error(error)

        call install_module_files(installer, targets, error)
        call handle_error(error)
      end if
    end if

    if (allocated(package%executable)) then
      call install_executables(installer, targets, error)
      call handle_error(error)
    end if

  end subroutine cmd_install