From f28ac3e31cb0e5c558a4fdb4ce5f461ce1c83ea4 Mon Sep 17 00:00:00 2001 From: LKedward Date: Thu, 8 Apr 2021 15:26:29 +0100 Subject: Separate target type for c objects --- src/fpm_backend.f90 | 8 ++++++-- src/fpm_targets.f90 | 9 ++++++--- 2 files changed, 12 insertions(+), 5 deletions(-) diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90 index 74cef61..be4c4c9 100644 --- a/src/fpm_backend.f90 +++ b/src/fpm_backend.f90 @@ -30,8 +30,8 @@ module fpm_backend use fpm_environment, only: run use fpm_filesystem, only: dirname, join_path, exists, mkdir use fpm_model, only: fpm_model_t -use fpm_targets, only: build_target_t, build_target_ptr, & - FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE +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 @@ -241,6 +241,10 @@ subroutine build_target(model,target) call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags & // " -o " // target%output_file) + case (FPM_TARGET_C_OBJECT) + call run(model%c_compiler//" -c " // target%source%file_name & + // " -o " // target%output_file) + case (FPM_TARGET_EXECUTABLE) call run(model%fortran_compiler// " " // target%compile_flags & diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90 index 02bb600..6d4d8f0 100644 --- a/src/fpm_targets.f90 +++ b/src/fpm_targets.f90 @@ -35,7 +35,8 @@ implicit none private public FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, & - FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT + FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT, & + FPM_TARGET_C_OBJECT public build_target_t, build_target_ptr public targets_from_sources, resolve_module_dependencies public resolve_target_linking, add_target, add_dependency @@ -50,7 +51,8 @@ integer, parameter :: FPM_TARGET_EXECUTABLE = 1 integer, parameter :: FPM_TARGET_ARCHIVE = 2 !> Target type is compiled object integer, parameter :: FPM_TARGET_OBJECT = 3 - +!> Target type is c compiled object +integer, parameter :: FPM_TARGET_C_OBJECT = 4 !> Wrapper type for constructing arrays of `[[build_target_t]]` pointers type build_target_ptr @@ -194,7 +196,8 @@ subroutine build_target_list(targets,model) case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE) call add_target(targets,source = sources(i), & - type = FPM_TARGET_OBJECT,& + type = merge(FPM_TARGET_C_OBJECT,FPM_TARGET_OBJECT,& + sources(i)%unit_type==FPM_UNIT_CSOURCE), & output_file = get_object_name(sources(i))) if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then -- cgit v1.2.3 From c957b27d275ebd575b5d49599c14e7252765f3ce Mon Sep 17 00:00:00 2001 From: LKedward Date: Thu, 8 Apr 2021 15:27:07 +0100 Subject: Select c compiler based on fortran compiler id --- src/fpm.f90 | 5 ++++- src/fpm_compiler.f90 | 27 +++++++++++++++++++++++++++ src/fpm_model.f90 | 3 +++ 3 files changed, 34 insertions(+), 1 deletion(-) diff --git a/src/fpm.f90 b/src/fpm.f90 index 31b68ff..653f8be 100644 --- a/src/fpm.f90 +++ b/src/fpm.f90 @@ -9,7 +9,7 @@ use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, use fpm_model, only: fpm_model_t, srcfile_t, show_model, & FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, & FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST -use fpm_compiler, only: get_module_flags, is_unknown_compiler +use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler use fpm_sources, only: add_executable_sources, add_sources_from_dir @@ -62,6 +62,8 @@ subroutine build_model(model, settings, package, error) model%fortran_compiler = settings%compiler endif + call get_default_c_compiler(model%fortran_compiler, model%c_compiler) + if (is_unknown_compiler(model%fortran_compiler)) then write(*, '(*(a:,1x))') & "", "Unknown compiler", model%fortran_compiler, "requested!", & @@ -178,6 +180,7 @@ subroutine build_model(model, settings, package, error) if (settings%verbose) then write(*,*)' BUILD_NAME: ',settings%build_name write(*,*)' COMPILER: ',settings%compiler + write(*,*)' C COMPILER: ',model%c_compiler write(*,*)' COMPILER OPTIONS: ', model%fortran_compile_flags write(*,*)' INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']' end if diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90 index 36041bf..76aedcc 100644 --- a/src/fpm_compiler.f90 +++ b/src/fpm_compiler.f90 @@ -336,6 +336,33 @@ subroutine get_module_flags(compiler, modpath, flags) end subroutine get_module_flags +subroutine get_default_c_compiler(f_compiler, c_compiler) + character(len=*), intent(in) :: f_compiler + character(len=:), allocatable, intent(out) :: c_compiler + integer(compiler_enum) :: id + + id = get_compiler_id(f_compiler) + + select case(id) + case default + c_compiler = 'gcc' + + case(id_intel_classic) + c_compiler = 'icc' + + case(id_intel_llvm) + c_compiler = 'icx' + + case(id_flang) + c_compiler='clang' + + case(id_ibmxl) + c_compiler='xlc' + + end select + +end subroutine get_default_c_compiler + function get_compiler_id(compiler) result(id) character(len=*), intent(in) :: compiler integer(kind=compiler_enum) :: id diff --git a/src/fpm_model.f90 b/src/fpm_model.f90 index bfb0115..5c575fc 100644 --- a/src/fpm_model.f90 +++ b/src/fpm_model.f90 @@ -117,6 +117,9 @@ type :: fpm_model_t !> Command line name to invoke fortran compiler character(:), allocatable :: fortran_compiler + !> Command line name to invoke c compiler + character(:), allocatable :: c_compiler + !> Command line flags passed to fortran for compilation character(:), allocatable :: fortran_compile_flags -- cgit v1.2.3 From f85a458f7ab35ee53ab188b3679e05fae5e5819c Mon Sep 17 00:00:00 2001 From: LKedward Date: Thu, 8 Apr 2021 15:40:33 +0100 Subject: Fix include flags for c objects --- src/fpm_backend.f90 | 2 +- src/fpm_targets.f90 | 13 ++++++++----- 2 files changed, 9 insertions(+), 6 deletions(-) diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90 index be4c4c9..8c4cf40 100644 --- a/src/fpm_backend.f90 +++ b/src/fpm_backend.f90 @@ -242,7 +242,7 @@ subroutine build_target(model,target) // " -o " // target%output_file) case (FPM_TARGET_C_OBJECT) - call run(model%c_compiler//" -c " // target%source%file_name & + call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags & // " -o " // target%output_file) case (FPM_TARGET_EXECUTABLE) diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90 index 6d4d8f0..7a06877 100644 --- a/src/fpm_targets.f90 +++ b/src/fpm_targets.f90 @@ -445,7 +445,7 @@ subroutine resolve_target_linking(targets, model) integer :: i character(:), allocatable :: global_link_flags - character(:), allocatable :: global_compile_flags + character(:), allocatable :: global_include_flags if (size(targets) == 0) return @@ -455,17 +455,16 @@ subroutine resolve_target_linking(targets, model) allocate(character(0) :: global_link_flags) end if - global_compile_flags = model%fortran_compile_flags - if (allocated(model%link_libraries)) then if (size(model%link_libraries) > 0) then global_link_flags = global_link_flags // " -l" // string_cat(model%link_libraries," -l") end if end if + allocate(character(0) :: global_include_flags) if (allocated(model%include_dirs)) then if (size(model%include_dirs) > 0) then - global_compile_flags = global_compile_flags // & + global_include_flags = global_include_flags // & & " -I" // string_cat(model%include_dirs," -I") end if end if @@ -474,7 +473,11 @@ subroutine resolve_target_linking(targets, model) associate(target => targets(i)%ptr) - target%compile_flags = global_compile_flags + if (target%target_type /= FPM_TARGET_C_OBJECT) then + target%compile_flags = model%fortran_compile_flags//" "//global_include_flags + else + target%compile_flags = global_include_flags + end if allocate(target%link_objects(0)) -- cgit v1.2.3 From 836a652f85b505493673ef2b3adc4703060ef10b Mon Sep 17 00:00:00 2001 From: LKedward Date: Fri, 9 Apr 2021 14:30:46 +0100 Subject: Change fallback C compiler equal to Fortran compiler --- src/fpm_compiler.f90 | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90 index 76aedcc..dcfd101 100644 --- a/src/fpm_compiler.f90 +++ b/src/fpm_compiler.f90 @@ -344,8 +344,6 @@ subroutine get_default_c_compiler(f_compiler, c_compiler) id = get_compiler_id(f_compiler) select case(id) - case default - c_compiler = 'gcc' case(id_intel_classic) c_compiler = 'icc' @@ -359,6 +357,9 @@ subroutine get_default_c_compiler(f_compiler, c_compiler) case(id_ibmxl) c_compiler='xlc' + case default + ! Fall-back to using Fortran compiler + c_compiler = f_compiler end select end subroutine get_default_c_compiler -- cgit v1.2.3 From 8c5763bdabe2374b83c83b8285bdc9c28730ae54 Mon Sep 17 00:00:00 2001 From: LKedward Date: Fri, 9 Apr 2021 14:32:57 +0100 Subject: Allow specifying C compiler with environment variable FPM_C_COMPILER --- src/fpm.f90 | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/fpm.f90 b/src/fpm.f90 index 653f8be..805132c 100644 --- a/src/fpm.f90 +++ b/src/fpm.f90 @@ -4,7 +4,7 @@ use fpm_backend, only: build_package 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 +use fpm_environment, only: run, get_env 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, & @@ -63,6 +63,7 @@ subroutine build_model(model, settings, package, error) endif call get_default_c_compiler(model%fortran_compiler, model%c_compiler) + model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler) if (is_unknown_compiler(model%fortran_compiler)) then write(*, '(*(a:,1x))') & -- cgit v1.2.3 From 079e7da06181a6dc9cee6f8f3b1b1c4ebde9e573 Mon Sep 17 00:00:00 2001 From: Laurence Kedward Date: Fri, 9 Apr 2021 14:48:03 +0100 Subject: Update compiler ids from rebase. --- src/fpm_compiler.f90 | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90 index dcfd101..75bd3be 100644 --- a/src/fpm_compiler.f90 +++ b/src/fpm_compiler.f90 @@ -345,10 +345,10 @@ subroutine get_default_c_compiler(f_compiler, c_compiler) select case(id) - case(id_intel_classic) + case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows, id_intel_classic_unknown) c_compiler = 'icc' - case(id_intel_llvm) + case(id_intel_llvm_nix,id_intel_llvm_windows, id_intel_llvm_unknown) c_compiler = 'icx' case(id_flang) -- cgit v1.2.3 From a49b0177f8d7ca74b3bfaa325fd37ee614975367 Mon Sep 17 00:00:00 2001 From: LKedward Date: Mon, 12 Apr 2021 16:39:29 +0100 Subject: Add: external-modules key to build table for non-fpm modules --- src/fpm.f90 | 5 +++++ src/fpm/manifest/build.f90 | 16 ++++++++++++++-- src/fpm_model.f90 | 10 ++++++++++ src/fpm_targets.f90 | 10 ++++++++-- test/fpm_test/test_module_dependencies.f90 | 9 +++++++++ 5 files changed, 46 insertions(+), 4 deletions(-) diff --git a/src/fpm.f90 b/src/fpm.f90 index 31b68ff..a62ffe0 100644 --- a/src/fpm.f90 +++ b/src/fpm.f90 @@ -51,6 +51,7 @@ subroutine build_model(model, settings, package, error) allocate(model%include_dirs(0)) allocate(model%link_libraries(0)) + allocate(model%external_modules(0)) call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml")) call model%deps%add(package, error) @@ -171,6 +172,10 @@ subroutine build_model(model, settings, package, error) if (allocated(dependency%build%link)) then model%link_libraries = [model%link_libraries, dependency%build%link] end if + + if (allocated(dependency%build%external_modules)) then + model%external_modules = [model%external_modules, dependency%build%external_modules] + end if end associate end do if (allocated(error)) return diff --git a/src/fpm/manifest/build.f90 b/src/fpm/manifest/build.f90 index d96974f..c9b3f44 100644 --- a/src/fpm/manifest/build.f90 +++ b/src/fpm/manifest/build.f90 @@ -34,6 +34,9 @@ module fpm_manifest_build !> Libraries to link against type(string_t), allocatable :: link(:) + !> External modules to use + type(string_t), allocatable :: external_modules(:) + contains !> Print information on this instance @@ -87,6 +90,9 @@ contains call get_value(table, "link", self%link, error) if (allocated(error)) return + call get_value(table, "external-modules", self%external_modules, error) + if (allocated(error)) return + end subroutine new_build_config @@ -110,7 +116,7 @@ contains do ikey = 1, size(list) select case(list(ikey)%key) - case("auto-executables", "auto-examples", "auto-tests", "link") + case("auto-executables", "auto-examples", "auto-tests", "link", "external-modules") continue case default @@ -135,7 +141,7 @@ contains !> Verbosity of the printout integer, intent(in), optional :: verbosity - integer :: pr, ilink + integer :: pr, ilink, imod character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)' if (present(verbosity)) then @@ -156,6 +162,12 @@ contains write(unit, fmt) " - " // self%link(ilink)%s end do end if + if (allocated(self%external_modules)) then + write(unit, fmt) " - external modules" + do imod = 1, size(self%external_modules) + write(unit, fmt) " - " // self%external_modules(imod)%s + end do + end if end subroutine info diff --git a/src/fpm_model.f90 b/src/fpm_model.f90 index bfb0115..ec366d6 100644 --- a/src/fpm_model.f90 +++ b/src/fpm_model.f90 @@ -129,6 +129,9 @@ type :: fpm_model_t !> Native libraries to link against type(string_t), allocatable :: link_libraries(:) + !> External modules used + type(string_t), allocatable :: external_modules(:) + !> Project dependencies type(dependency_tree_t) :: deps @@ -276,6 +279,13 @@ function info_model(model) result(s) if (i < size(model%link_libraries)) s = s // ", " end do s = s // "]" + ! type(string_t), allocatable :: external_modules(:) + s = s // ", external_modules=[" + do i = 1, size(model%external_modules) + s = s // '"' // model%external_modules(i)%s // '"' + if (i < size(model%external_modules)) s = s // ", " + end do + s = s // "]" ! type(dependency_tree_t) :: deps ! TODO: print `dependency_tree_t` properly, which should become part of the ! model, not imported from another file diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90 index 02bb600..671145d 100644 --- a/src/fpm_targets.f90 +++ b/src/fpm_targets.f90 @@ -121,7 +121,7 @@ subroutine targets_from_sources(targets,model,error) call build_target_list(targets,model) - call resolve_module_dependencies(targets,error) + call resolve_module_dependencies(targets,model%external_modules,error) if (allocated(error)) return call resolve_target_linking(targets,model) @@ -345,8 +345,9 @@ end subroutine add_dependency !> a source file in the package of the correct scope, then a __fatal error__ !> is returned by the procedure and model construction fails. !> -subroutine resolve_module_dependencies(targets,error) +subroutine resolve_module_dependencies(targets,external_modules,error) type(build_target_ptr), intent(inout), target :: targets(:) + type(string_t), intent(in) :: external_modules(:) type(error_t), allocatable, intent(out) :: error type(build_target_ptr) :: dep @@ -364,6 +365,11 @@ subroutine resolve_module_dependencies(targets,error) cycle end if + if (targets(i)%ptr%source%modules_used(j)%s .in. external_modules) then + ! Dependency satisfied in system-installed module + cycle + end if + if (any(targets(i)%ptr%source%unit_scope == & [FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then dep%ptr => & diff --git a/test/fpm_test/test_module_dependencies.f90 b/test/fpm_test/test_module_dependencies.f90 index f193646..992f227 100644 --- a/test/fpm_test/test_module_dependencies.f90 +++ b/test/fpm_test/test_module_dependencies.f90 @@ -67,6 +67,7 @@ contains type(build_target_ptr), allocatable :: targets(:) model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) @@ -137,6 +138,7 @@ contains character(:), allocatable :: scope_str model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) @@ -196,6 +198,7 @@ contains type(build_target_ptr), allocatable :: targets(:) model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(1)) @@ -249,6 +252,7 @@ contains character(:), allocatable :: scope_str model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(3)) @@ -308,6 +312,7 @@ contains type(build_target_ptr), allocatable :: targets(:) model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) @@ -335,6 +340,7 @@ contains type(build_target_ptr), allocatable :: targets(:) model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) @@ -361,6 +367,7 @@ contains type(build_target_ptr), allocatable :: targets(:) model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) @@ -388,6 +395,7 @@ contains type(build_target_ptr), allocatable :: targets(:) model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) @@ -507,6 +515,7 @@ contains type(build_target_ptr), allocatable :: targets(:) model%output_directory = '' + allocate(model%external_modules(0)) allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) -- cgit v1.2.3 From 2c0975b729e173042bec227e10fb6bf40a1609dd Mon Sep 17 00:00:00 2001 From: LKedward Date: Mon, 12 Apr 2021 16:54:35 +0100 Subject: Update: manifest-reference with new external-modules key --- manifest-reference.md | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/manifest-reference.md b/manifest-reference.md index 1a33dc1..89bf1db 100644 --- a/manifest-reference.md +++ b/manifest-reference.md @@ -33,6 +33,8 @@ Every manifest file consists of the following sections: Toggle automatic discovery of executables - [*link*](#link-external-libraries): Link with external dependencies + - [*external-modules*](#use-system-installed-modules): + Specify modules used that are not within your fpm package - Target sections: - [*library*](#library-configuration) Configuration of the library target @@ -353,6 +355,26 @@ In this case the order of the libraries matters: link = ["blas", "lapack"] ``` +## Use system-installed modules + +To use modules that are not defined within your fpm package or its dependencies, +specify the module name using the *external-modules* key in the *build* table. + +*Example:* + +```toml +[build] +external-modules = "netcdff" +``` + +Multiple external modules can be specified as a list. + +*Example:* + +```toml +[build] +external-modules = ["netcdff","h5lt"] +``` ## Automatic target discovery -- cgit v1.2.3 From d407ee0b992dbcde8663c62c06e72f57ea0691a9 Mon Sep 17 00:00:00 2001 From: Laurence Kedward Date: Wed, 14 Apr 2021 17:46:34 +0100 Subject: Update manifest-reference.md Co-authored-by: Milan Curcic --- manifest-reference.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/manifest-reference.md b/manifest-reference.md index 89bf1db..e8998a9 100644 --- a/manifest-reference.md +++ b/manifest-reference.md @@ -364,7 +364,7 @@ specify the module name using the *external-modules* key in the *build* table. ```toml [build] -external-modules = "netcdff" +external-modules = "netcdf" ``` Multiple external modules can be specified as a list. -- cgit v1.2.3 From d97abb90435501bd392ff3269633a409cfea1cb0 Mon Sep 17 00:00:00 2001 From: Laurence Kedward Date: Wed, 14 Apr 2021 18:52:25 +0100 Subject: Update manifest-reference.md Co-authored-by: Milan Curcic --- manifest-reference.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/manifest-reference.md b/manifest-reference.md index e8998a9..7b85708 100644 --- a/manifest-reference.md +++ b/manifest-reference.md @@ -373,7 +373,7 @@ Multiple external modules can be specified as a list. ```toml [build] -external-modules = ["netcdff","h5lt"] +external-modules = ["netcdf", "h5lt"] ``` ## Automatic target discovery -- cgit v1.2.3 From 5eb1ee4c21426db55400752bffca5beda47e8c39 Mon Sep 17 00:00:00 2001 From: LKedward Date: Thu, 15 Apr 2021 14:52:35 +0100 Subject: Update: manifest reference with note about external module directories --- manifest-reference.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/manifest-reference.md b/manifest-reference.md index 89bf1db..a77c2d2 100644 --- a/manifest-reference.md +++ b/manifest-reference.md @@ -360,6 +360,10 @@ link = ["blas", "lapack"] To use modules that are not defined within your fpm package or its dependencies, specify the module name using the *external-modules* key in the *build* table. +> __Important:__ *fpm* cannot automatically locate external module files; it is the responsibility +> of the user to specify the necessary include directories using compiler flags such that +> the compiler can locate external module files during compilation. + *Example:* ```toml -- cgit v1.2.3 From a540c83d9e303acd6fece95927c49fa8d2565366 Mon Sep 17 00:00:00 2001 From: gareth-nx <82561769+gareth-nx@users.noreply.github.com> Date: Fri, 16 Apr 2021 03:30:43 +1000 Subject: Minor edits to README.md (#440) Make clear that this snippet must be run in the fpm directory to work. Otherwise it fails, because it needs to find the fpm.toml file. --- README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index d4e9002..290b586 100644 --- a/README.md +++ b/README.md @@ -101,7 +101,7 @@ This guide explains the process of building *fpm* on a platform for the first ti To build *fpm* without a prior *fpm* version a single source file version is available at each release. -To build manually using the single source distribution use +To build manually using the single source distribution, run the following code (from within the current directory) ``` mkdir _tmp -- cgit v1.2.3