aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bootstrap/src/Fpm.hs73
-rw-r--r--bootstrap/test/Spec.hs15
-rwxr-xr-xci/run_tests.bat13
-rwxr-xr-xci/run_tests.sh6
-rw-r--r--example_packages/README.md1
-rw-r--r--example_packages/with_examples/.gitignore1
-rw-r--r--example_packages/with_examples/demo/prog.f903
-rw-r--r--example_packages/with_examples/fpm.toml7
-rw-r--r--fpm/src/fpm.f9036
-rw-r--r--fpm/src/fpm/dependency.f9010
-rw-r--r--fpm/src/fpm/manifest.f9031
-rw-r--r--fpm/src/fpm/manifest/build.f9015
-rw-r--r--fpm/src/fpm/manifest/example.f90175
-rw-r--r--fpm/src/fpm/manifest/package.f9079
-rw-r--r--fpm/src/fpm_command_line.f9020
-rw-r--r--fpm/src/fpm_model.f903
-rw-r--r--fpm/src/fpm_targets.f908
-rw-r--r--fpm/test/fpm_test/test_manifest.f9054
-rw-r--r--manifest-reference.md42
19 files changed, 558 insertions, 34 deletions
diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs
index 9fc1c91..bec7706 100644
--- a/bootstrap/src/Fpm.hs
+++ b/bootstrap/src/Fpm.hs
@@ -92,6 +92,7 @@ data Arguments =
}
| Run
{ runRelease :: Bool
+ , runExample :: Bool
, runCompiler :: FilePath
, runFlags :: [String]
, runRunner :: Maybe String
@@ -111,6 +112,7 @@ data TomlSettings = TomlSettings {
tomlSettingsProjectName :: String
, tomlSettingsLibrary :: (Maybe Library)
, tomlSettingsExecutables :: [Executable]
+ , tomlSettingsExamples :: [Executable]
, tomlSettingsTests :: [Executable]
, tomlSettingsDependencies :: (Map.Map String Version)
, tomlSettingsDevDependencies :: (Map.Map String Version)
@@ -122,6 +124,7 @@ data AppSettings = AppSettings {
, appSettingsBuildPrefix :: String
, appSettingsLibrary :: (Maybe Library)
, appSettingsExecutables :: [Executable]
+ , appSettingsExamples :: [Executable]
, appSettingsTests :: [Executable]
, appSettingsDependencies :: (Map.Map String Version)
, appSettingsDevDependencies :: (Map.Map String Version)
@@ -168,15 +171,23 @@ start args = case args of
app :: Arguments -> AppSettings -> IO ()
app args settings = case args of
Build{} -> build settings
- Run { runTarget = whichOne, runArgs = runArgs, runRunner = runner } -> do
+ Run { runTarget = whichOne, runArgs = runArgs, runRunner = runner, runExample = runExample } -> do
build settings
let buildPrefix = appSettingsBuildPrefix settings
let
- executableNames = map
- (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } ->
- sourceDir </> name
- )
- (appSettingsExecutables settings)
+ executableNames = if runExample
+ then
+ map
+ (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } ->
+ sourceDir </> name
+ )
+ (appSettingsExamples settings)
+ else
+ map
+ (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name } ->
+ sourceDir </> name
+ )
+ (appSettingsExecutables settings)
let executables =
map (buildPrefix </>) $ map (flip (<.>) exe) executableNames
canonicalExecutables <- mapM makeAbsolute executables
@@ -265,6 +276,7 @@ build settings = do
let projectName = appSettingsProjectName settings
let buildPrefix = appSettingsBuildPrefix settings
let executables = appSettingsExecutables settings
+ let examples = appSettingsExamples settings
let tests = appSettingsTests settings
mainDependencyTrees <- fetchDependencies (appSettingsDependencies settings)
builtDependencies <- buildDependencies buildPrefix
@@ -341,6 +353,29 @@ build settings = do
++ (map snd localDependencies)
)
)
+ examples
+ mapM_
+ (\Executable { executableSourceDir = sourceDir, executableMainFile = mainFile, executableName = name, executableDependencies = dependencies } ->
+ do
+ localDependencies <-
+ fetchExecutableDependencies maybeTree dependencies
+ >>= buildDependencies buildPrefix compilerSettings
+ buildProgram
+ sourceDir
+ ( (map fst executableDepends)
+ ++ (map fst devDependencies)
+ ++ (map fst localDependencies)
+ )
+ [".f90", ".f", ".F", ".F90", ".f95", ".f03"]
+ (buildPrefix </> sourceDir)
+ compilerSettings
+ name
+ mainFile
+ ( (map snd executableDepends)
+ ++ (map snd devDependencies)
+ ++ (map snd localDependencies)
+ )
+ )
tests
getArguments :: IO Arguments
@@ -410,6 +445,10 @@ runArguments =
( long "release"
<> help "Build with optimizations instead of debugging"
)
+ <*> switch
+ ( long "example"
+ <> help "Run example programs instead of applications"
+ )
<*> strOption
( long "compiler"
<> metavar "COMPILER"
@@ -503,6 +542,8 @@ settingsCodec =
.= tomlSettingsLibrary
<*> Toml.list executableCodec "executable"
.= tomlSettingsExecutables
+ <*> Toml.list executableCodec "example"
+ .= tomlSettingsExamples
<*> Toml.list executableCodec "test"
.= tomlSettingsTests
<*> Toml.tableMap Toml._KeyString versionCodec "dependencies"
@@ -608,6 +649,7 @@ toml2AppSettings tomlSettings args = do
executableSettings <- getExecutableSettings
(tomlSettingsExecutables tomlSettings)
projectName
+ exampleSettings <- getExampleSettings $ tomlSettingsExamples tomlSettings
testSettings <- getTestSettings $ tomlSettingsTests tomlSettings
compilerSettings <- defineCompilerSettings specifiedFlags compiler release
buildPrefix <- makeBuildPrefix (compilerSettingsCompiler compilerSettings)
@@ -619,6 +661,7 @@ toml2AppSettings tomlSettings args = do
, appSettingsBuildPrefix = buildPrefix
, appSettingsLibrary = librarySettings
, appSettingsExecutables = executableSettings
+ , appSettingsExamples = exampleSettings
, appSettingsTests = testSettings
, appSettingsDependencies = dependencies
, appSettingsDevDependencies = devDependencies
@@ -725,6 +768,24 @@ getExecutableSettings [] projectName = do
else return []
getExecutableSettings executables _ = return executables
+getExampleSettings :: [Executable] -> IO [Executable]
+getExampleSettings [] = do
+ defaultDirectoryExists <- doesDirectoryExist "example"
+ if defaultDirectoryExists
+ then do
+ defaultMainExists <- doesFileExist ("example" </> "main.f90")
+ if defaultMainExists
+ then return
+ [ Executable { executableSourceDir = "example"
+ , executableMainFile = "main.f90"
+ , executableName = "demo"
+ , executableDependencies = Map.empty
+ }
+ ]
+ else return []
+ else return []
+getExampleSettings examples = return examples
+
getTestSettings :: [Executable] -> IO [Executable]
getTestSettings [] = do
defaultDirectoryExists <- doesDirectoryExist "test"
diff --git a/bootstrap/test/Spec.hs b/bootstrap/test/Spec.hs
index 215024d..6e9daa2 100644
--- a/bootstrap/test/Spec.hs
+++ b/bootstrap/test/Spec.hs
@@ -20,6 +20,7 @@ testHelloWorld :: IO ()
testHelloWorld =
withCurrentDirectory (example_path </> "hello_world") $ start $ Run
{ runRelease = False
+ , runExample = False
, runCompiler = "gfortran"
, runFlags = []
, runRunner = Nothing
@@ -42,6 +43,19 @@ testHelloFpm :: IO ()
testHelloFpm =
withCurrentDirectory (example_path </> "hello_fpm") $ start $ Run
{ runRelease = False
+ , runExample = False
+ , runCompiler = "gfortran"
+ , runFlags = []
+ , runRunner = Nothing
+ , runTarget = Nothing
+ , runArgs = Nothing
+ }
+
+testWithExamples :: IO ()
+testWithExamples =
+ withCurrentDirectory (example_path </> "with_examples") $ start $ Run
+ { runRelease = False
+ , runExample = True
, runCompiler = "gfortran"
, runFlags = []
, runRunner = Nothing
@@ -72,6 +86,7 @@ testMakefileComplex :: IO ()
testMakefileComplex =
withCurrentDirectory (example_path </> "makefile_complex") $ start $ Run
{ runRelease = False
+ , runExample = False
, runCompiler = "gfortran"
, runFlags = []
, runRunner = Nothing
diff --git a/ci/run_tests.bat b/ci/run_tests.bat
index 22be2db..42f391c 100755
--- a/ci/run_tests.bat
+++ b/ci/run_tests.bat
@@ -109,6 +109,17 @@ if errorlevel 1 exit 1
.\build\gfortran_debug\test\farewell_test
+cd ..\with_examples
+if errorlevel 1 exit 1
+
+del /q /f build
+%fpm_path% build
+if errorlevel 1 exit 1
+
+.\build\gfortran_debug\app\demo-prog
+if errorlevel 1 exit 1
+
+
cd ..\auto_discovery_off
if errorlevel 1 exit 1
@@ -167,4 +178,4 @@ if errorlevel 1 exit 1
.\build\gfortran_debug\app\gomp_test
if errorlevel 1 exit 1
-cd ..\.. \ No newline at end of file
+cd ..\..
diff --git a/ci/run_tests.sh b/ci/run_tests.sh
index 85484e5..7412fba 100755
--- a/ci/run_tests.sh
+++ b/ci/run_tests.sh
@@ -50,6 +50,10 @@ cd ../hello_complex_2
./build/gfortran_debug/test/greet_test
./build/gfortran_debug/test/farewell_test
+cd ../with_examples
+"${f_fpm_path}" build
+./build/gfortran_debug/app/demo-prog
+
cd ../auto_discovery_off
"${f_fpm_path}" build
./build/gfortran_debug/app/auto_discovery_off
@@ -77,4 +81,4 @@ cd ../link_executable
./build/gfortran_debug/app/gomp_test
# Cleanup
-rm -rf ./*/build \ No newline at end of file
+rm -rf ./*/build
diff --git a/example_packages/README.md b/example_packages/README.md
index 0eb0653..667b9a3 100644
--- a/example_packages/README.md
+++ b/example_packages/README.md
@@ -13,6 +13,7 @@ the features demonstrated in each package and which versions of fpm are supporte
| hello_complex_2 | Auto-discovery of tests and executables with modules | N | Y |
| hello_fpm | App-only; local path dependency | Y | Y |
| hello_world | App-only | Y | Y |
+| with_examples | Example-only | Y | Y |
| makefile_complex | External build command (makefile); local path dependency | Y | N |
| program_with_module | App-only; module+program in single source file | Y | Y |
| submodules | Lib-only; submodules (3 levels) | N | Y |
diff --git a/example_packages/with_examples/.gitignore b/example_packages/with_examples/.gitignore
new file mode 100644
index 0000000..d9b4f01
--- /dev/null
+++ b/example_packages/with_examples/.gitignore
@@ -0,0 +1 @@
+/build/*
diff --git a/example_packages/with_examples/demo/prog.f90 b/example_packages/with_examples/demo/prog.f90
new file mode 100644
index 0000000..8b3d882
--- /dev/null
+++ b/example_packages/with_examples/demo/prog.f90
@@ -0,0 +1,3 @@
+program demo
+ write(*, '(a)') "This is a simple demo program, but not a real application"
+end program demo
diff --git a/example_packages/with_examples/fpm.toml b/example_packages/with_examples/fpm.toml
new file mode 100644
index 0000000..d7d2926
--- /dev/null
+++ b/example_packages/with_examples/fpm.toml
@@ -0,0 +1,7 @@
+name = "with_examples"
+build.auto-examples = false
+
+[[example]]
+name = "demo-prog"
+source-dir = "demo"
+main = "prog.f90"
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index f23e119..1b32cb6 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -7,8 +7,8 @@ use fpm_dependency, only : new_dependency_tree
use fpm_environment, only: run
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, &
- FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
- FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
+ FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
+ FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
use fpm_compiler, only: add_compile_flag_defaults
@@ -86,6 +86,15 @@ subroutine build_model(model, settings, package, error)
end if
end if
+ if (is_dir('example') .and. package%build%auto_examples) then
+ call add_sources_from_dir(model%sources,'example', FPM_SCOPE_EXAMPLE, &
+ with_executables=.true., error=error)
+
+ if (allocated(error)) then
+ return
+ end if
+
+ end if
if (is_dir('test') .and. package%build%auto_tests) then
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
with_executables=.true., error=error)
@@ -105,6 +114,16 @@ subroutine build_model(model, settings, package, error)
end if
end if
+ if (allocated(package%example)) then
+ call add_executable_sources(model%sources, package%example, FPM_SCOPE_EXAMPLE, &
+ auto_discover=package%build%auto_examples, &
+ 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%auto_tests, &
@@ -205,6 +224,7 @@ subroutine cmd_run(settings,test)
type(string_t), allocatable :: executables(:)
type(build_target_t), pointer :: exe_target
type(srcfile_t), pointer :: exe_source
+ integer :: run_scope
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
@@ -218,6 +238,12 @@ subroutine cmd_run(settings,test)
error stop 1
end if
+ if (test) then
+ run_scope = FPM_SCOPE_TEST
+ else
+ run_scope = merge(FPM_SCOPE_EXAMPLE, FPM_SCOPE_APP, settings%example)
+ end if
+
! Enumerate executable targets to run
col_width = -1
found(:) = .false.
@@ -231,8 +257,7 @@ subroutine cmd_run(settings,test)
exe_source => exe_target%dependencies(1)%ptr%source
- if (exe_source%unit_scope == &
- merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
+ if (exe_source%unit_scope == run_scope) then
col_width = max(col_width,len(basename(exe_target%output_file))+2)
@@ -295,8 +320,7 @@ subroutine cmd_run(settings,test)
exe_source => exe_target%dependencies(1)%ptr%source
- if (exe_source%unit_scope == &
- merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
+ if (exe_source%unit_scope == run_scope) then
write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
& [character(len=col_width) :: basename(exe_target%output_file)]
diff --git a/fpm/src/fpm/dependency.f90 b/fpm/src/fpm/dependency.f90
index e5e18ae..144ffbe 100644
--- a/fpm/src/fpm/dependency.f90
+++ b/fpm/src/fpm/dependency.f90
@@ -310,6 +310,16 @@ contains
if (allocated(error)) return
end if
+ if (allocated(package%example)) then
+ do ii = 1, size(package%example)
+ if (allocated(package%example(ii)%dependency)) then
+ call self%add(package%example(ii)%dependency, error)
+ if (allocated(error)) exit
+ end if
+ end do
+ if (allocated(error)) return
+ end if
+
if (allocated(package%test)) then
do ii = 1, size(package%test)
if (allocated(package%test(ii)%dependency)) then
diff --git a/fpm/src/fpm/manifest.f90 b/fpm/src/fpm/manifest.f90
index 2398d79..7e80b29 100644
--- a/fpm/src/fpm/manifest.f90
+++ b/fpm/src/fpm/manifest.f90
@@ -8,6 +8,7 @@
!> to hide the actual implementation details.
module fpm_manifest
use fpm_manifest_build, only: build_config_t
+ use fpm_manifest_example, only : example_config_t
use fpm_manifest_executable, only : executable_config_t
use fpm_manifest_dependency, only : dependency_config_t
use fpm_manifest_library, only : library_config_t
@@ -20,6 +21,7 @@ module fpm_manifest
private
public :: get_package_data, default_executable, default_library, default_test
+ public :: default_example
public :: package_config_t, dependency_config_t
@@ -52,6 +54,21 @@ contains
end subroutine default_executable
+ !> Populate test in case we find the default example/ directory
+ subroutine default_example(self, name)
+
+ !> Instance of the executable meta data
+ type(example_config_t), intent(out) :: self
+
+ !> Name of the package
+ character(len=*), intent(in) :: name
+
+ self%name = name // "-demo"
+ self%source_dir = "example"
+ self%main = "main.f90"
+
+ end subroutine default_example
+
!> Populate test in case we find the default test/ directory
subroutine default_test(self, name)
@@ -61,7 +78,7 @@ contains
!> Name of the package
character(len=*), intent(in) :: name
- self%name = name
+ self%name = name // "-test"
self%source_dir = "test"
self%main = "main.f90"
@@ -135,6 +152,13 @@ contains
call default_executable(package%executable(1), package%name)
end if
+ ! Populate example in case we find the default example directory
+ if (.not.allocated(package%example) .and. &
+ exists(join_path("example","main.f90"))) then
+ allocate(package%example(1))
+ call default_example(package%example(1), package%name)
+ endif
+
! Populate test in case we find the default test directory
if (.not.allocated(package%test) .and. &
& exists(join_path(root, "test", "main.f90"))) then
@@ -142,7 +166,10 @@ contains
call default_test(package%test(1), package%name)
endif
- if (.not.(allocated(package%library) .or. allocated(package%executable))) then
+ if (.not.(allocated(package%library) &
+ & .or. allocated(package%executable) &
+ & .or. allocated(package%example) &
+ & .or. allocated(package%test))) then
call fatal_error(error, "Neither library nor executable found, there is nothing to do")
return
end if
diff --git a/fpm/src/fpm/manifest/build.f90 b/fpm/src/fpm/manifest/build.f90
index 85fd2c7..d96974f 100644
--- a/fpm/src/fpm/manifest/build.f90
+++ b/fpm/src/fpm/manifest/build.f90
@@ -5,6 +5,7 @@
!>```toml
!>[build]
!>auto-executables = bool
+!>auto-examples = bool
!>auto-tests = bool
!>link = ["lib"]
!>```
@@ -24,6 +25,9 @@ module fpm_manifest_build
!> Automatic discovery of executables
logical :: auto_executables
+ !> Automatic discovery of examples
+ logical :: auto_examples
+
!> Automatic discovery of tests
logical :: auto_tests
@@ -72,6 +76,14 @@ contains
return
end if
+ call get_value(table, "auto-examples", self%auto_examples, .true., stat=stat)
+
+ if (stat /= toml_stat%success) then
+ call fatal_error(error,"Error while reading value for 'auto-examples' in fpm.toml, expecting logical")
+ return
+ end if
+
+
call get_value(table, "link", self%link, error)
if (allocated(error)) return
@@ -98,7 +110,7 @@ contains
do ikey = 1, size(list)
select case(list(ikey)%key)
- case("auto-executables", "auto-tests", "link")
+ case("auto-executables", "auto-examples", "auto-tests", "link")
continue
case default
@@ -136,6 +148,7 @@ contains
write(unit, fmt) "Build configuration"
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
+ write(unit, fmt) " - auto-discovery (examples) ", merge("enabled ", "disabled", self%auto_examples)
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
if (allocated(self%link)) then
write(unit, fmt) " - link against"
diff --git a/fpm/src/fpm/manifest/example.f90 b/fpm/src/fpm/manifest/example.f90
new file mode 100644
index 0000000..fc2a0af
--- /dev/null
+++ b/fpm/src/fpm/manifest/example.f90
@@ -0,0 +1,175 @@
+!> Implementation of the meta data for an example.
+!>
+!> The example data structure is effectively a decorated version of an executable
+!> and shares most of its properties, except for the defaults and can be
+!> handled under most circumstances just like any other executable.
+!>
+!> A example table can currently have the following fields
+!>
+!>```toml
+!>[[ example ]]
+!>name = "string"
+!>source-dir = "path"
+!>main = "file"
+!>link = ["lib"]
+!>[example.dependencies]
+!>```
+module fpm_manifest_example
+ use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
+ use fpm_manifest_executable, only : executable_config_t
+ use fpm_error, only : error_t, syntax_error
+ use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
+ implicit none
+ private
+
+ public :: example_config_t, new_example
+
+
+ !> Configuation meta data for an example
+ type, extends(executable_config_t) :: example_config_t
+
+ contains
+
+ !> Print information on this instance
+ procedure :: info
+
+ end type example_config_t
+
+
+contains
+
+
+ !> Construct a new example configuration from a TOML data structure
+ subroutine new_example(self, table, error)
+
+ !> Instance of the example configuration
+ type(example_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
+
+ type(toml_table), pointer :: child
+
+ call check(table, error)
+ if (allocated(error)) return
+
+ call get_value(table, "name", self%name)
+ if (.not.allocated(self%name)) then
+ call syntax_error(error, "Could not retrieve example name")
+ return
+ end if
+ call get_value(table, "source-dir", self%source_dir, "example")
+ call get_value(table, "main", self%main, "main.f90")
+
+ call get_value(table, "dependencies", child, requested=.false.)
+ if (associated(child)) then
+ call new_dependencies(self%dependency, child, error)
+ if (allocated(error)) return
+ end if
+
+ call get_value(table, "link", self%link, error)
+ if (allocated(error)) return
+
+ end subroutine new_example
+
+
+ !> 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(:)
+ logical :: name_present
+ integer :: ikey
+
+ name_present = .false.
+
+ call table%get_keys(list)
+
+ if (size(list) < 1) then
+ call syntax_error(error, "Example section does not provide sufficient entries")
+ return
+ end if
+
+ do ikey = 1, size(list)
+ select case(list(ikey)%key)
+ case default
+ call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in example entry")
+ exit
+
+ case("name")
+ name_present = .true.
+
+ case("source-dir", "main", "dependencies", "link")
+ continue
+
+ end select
+ end do
+ if (allocated(error)) return
+
+ if (.not.name_present) then
+ call syntax_error(error, "Example name is not provided, please add a name entry")
+ end if
+
+ end subroutine check
+
+
+ !> Write information on instance
+ subroutine info(self, unit, verbosity)
+
+ !> Instance of the example configuration
+ class(example_config_t), intent(in) :: self
+
+ !> Unit for IO
+ integer, intent(in) :: unit
+
+ !> Verbosity of the printout
+ integer, intent(in), optional :: verbosity
+
+ integer :: pr, ii
+ character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)', &
+ & fmti = '("#", 1x, a, t30, i0)'
+
+ if (present(verbosity)) then
+ pr = verbosity
+ else
+ pr = 1
+ end if
+
+ if (pr < 1) return
+
+ write(unit, fmt) "Example target"
+ if (allocated(self%name)) then
+ write(unit, fmt) "- name", self%name
+ end if
+ if (allocated(self%source_dir)) then
+ if (self%source_dir /= "example" .or. pr > 2) then
+ write(unit, fmt) "- source directory", self%source_dir
+ end if
+ end if
+ if (allocated(self%main)) then
+ if (self%main /= "main.f90" .or. pr > 2) then
+ write(unit, fmt) "- example source", self%main
+ end if
+ end if
+
+ if (allocated(self%dependency)) then
+ if (size(self%dependency) > 1 .or. pr > 2) then
+ write(unit, fmti) "- dependencies", size(self%dependency)
+ end if
+ do ii = 1, size(self%dependency)
+ call self%dependency(ii)%info(unit, pr - 1)
+ end do
+ end if
+
+ end subroutine info
+
+
+end module fpm_manifest_example
diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90
index 987f2d1..9c759a5 100644
--- a/fpm/src/fpm/manifest/package.f90
+++ b/fpm/src/fpm/manifest/package.f90
@@ -25,11 +25,13 @@
!>[dependencies]
!>[dev-dependencies]
!>[[ executable ]]
+!>[[ example ]]
!>[[ test ]]
!>```
module fpm_manifest_package
use fpm_manifest_build, only: build_config_t, new_build_config
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
+ use fpm_manifest_example, only : example_config_t, new_example
use fpm_manifest_executable, only : executable_config_t, new_executable
use fpm_manifest_library, only : library_config_t, new_library
use fpm_manifest_test, only : test_config_t, new_test
@@ -43,6 +45,12 @@ module fpm_manifest_package
public :: package_config_t, new_package
+ interface unique_programs
+ module procedure :: unique_programs1
+ module procedure :: unique_programs2
+ end interface unique_programs
+
+
!> Package meta data
type :: package_config_t
@@ -67,6 +75,9 @@ module fpm_manifest_package
!> Development dependency meta data
type(dependency_config_t), allocatable :: dev_dependency(:)
+ !> Example meta data
+ type(example_config_t), allocatable :: example(:)
+
!> Test meta data
type(test_config_t), allocatable :: test(:)
@@ -174,6 +185,30 @@ contains
if (allocated(error)) return
end if
+ call get_value(table, "example", children, requested=.false.)
+ if (associated(children)) then
+ nn = len(children)
+ allocate(self%example(nn))
+ do ii = 1, nn
+ call get_value(children, ii, node, stat=stat)
+ if (stat /= toml_stat%success) then
+ call fatal_error(error, "Could not retrieve example from array entry")
+ exit
+ end if
+ call new_example(self%example(ii), node, error)
+ if (allocated(error)) exit
+ end do
+ if (allocated(error)) return
+
+ call unique_programs(self%example, error)
+ if (allocated(error)) return
+
+ if (allocated(self%executable)) then
+ call unique_programs(self%executable, self%example, error)
+ if (allocated(error)) return
+ end if
+ end if
+
call get_value(table, "test", children, requested=.false.)
if (associated(children)) then
nn = len(children)
@@ -230,7 +265,7 @@ contains
case("version", "license", "author", "maintainer", "copyright", &
& "description", "keywords", "categories", "homepage", "build", &
& "dependencies", "dev-dependencies", "test", "executable", &
- & "library")
+ & "example", "library")
continue
end select
@@ -298,6 +333,15 @@ contains
end do
end if
+ if (allocated(self%example)) then
+ if (size(self%example) > 1 .or. pr > 2) then
+ write(unit, fmti) "- examples", size(self%example)
+ end if
+ do ii = 1, size(self%example)
+ call self%example(ii)%info(unit, pr - 1)
+ end do
+ end if
+
if (allocated(self%test)) then
if (size(self%test) > 1 .or. pr > 2) then
write(unit, fmti) "- tests", size(self%test)
@@ -320,7 +364,7 @@ contains
!> Check whether or not the names in a set of executables are unique
- subroutine unique_programs(executable, error)
+ subroutine unique_programs1(executable, error)
!> Array of executables
class(executable_config_t), intent(in) :: executable(:)
@@ -342,7 +386,36 @@ contains
end do
if (allocated(error)) return
- end subroutine unique_programs
+ end subroutine unique_programs1
+
+
+ !> Check whether or not the names in a set of executables are unique
+ subroutine unique_programs2(executable_i, executable_j, error)
+
+ !> Array of executables
+ class(executable_config_t), intent(in) :: executable_i(:)
+
+ !> Array of executables
+ class(executable_config_t), intent(in) :: executable_j(:)
+
+ !> Error handling
+ type(error_t), allocatable, intent(out) :: error
+
+ integer :: i, j
+
+ do i = 1, size(executable_i)
+ do j = 1, size(executable_j)
+ if (executable_i(i)%name == executable_j(j)%name) then
+ call fatal_error(error, "The program named '"//&
+ executable_j(j)%name//"' is duplicated. "//&
+ "Unique program names are required.")
+ exit
+ end if
+ end do
+ end do
+ if (allocated(error)) return
+
+ end subroutine unique_programs2
end module fpm_manifest_package
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index ca15916..96a335f 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -67,6 +67,7 @@ type, extends(fpm_build_settings) :: fpm_run_settings
character(len=ibug),allocatable :: name(:)
character(len=:),allocatable :: args
character(len=:),allocatable :: runner
+ logical :: example
end type
type, extends(fpm_run_settings) :: fpm_test_settings
@@ -142,6 +143,7 @@ contains
& --target " " &
& --list F &
& --release F&
+ & --example F&
& --runner " " &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
& --verbose F&
@@ -166,6 +168,7 @@ contains
& args=remaining,&
& build_name=val_build,&
& compiler=val_compiler, &
+ & example=lget('example'), &
& list=lget('list'),&
& name=names,&
& runner=val_runner,&
@@ -334,6 +337,7 @@ contains
& args=remaining, &
& build_name=val_build, &
& compiler=val_compiler, &
+ & example=.false., &
& list=lget('list'), &
& name=names, &
& runner=val_runner, &
@@ -359,7 +363,7 @@ contains
call set_args('&
& --list F&
& --verbose F&
- ', help_fpm, version_text)
+ &', help_fpm, version_text)
! Note: will not get here if --version or --usage or --help
! is present on commandline
help_text=help_usage
@@ -451,7 +455,7 @@ contains
' new NAME [--lib|--src] [--app] [--test] [--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
' list [--list] ', &
- ' run [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', &
+ ' run [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] [--example] ', &
' [--compiler COMPILER_NAME] [-- ARGS] ', &
' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', &
' [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -629,17 +633,21 @@ contains
' ', &
'SYNOPSIS ', &
' fpm run [[--target] NAME(s)][--release][--compiler COMPILER_NAME] ', &
- ' [--runner "CMD"] [--list][-- ARGS] ', &
+ ' [--runner "CMD"] [--example] [--list][-- ARGS] ', &
' ', &
' fpm run --help|--version ', &
' ', &
'DESCRIPTION ', &
' Run applications you have built in your fpm(1) project. ', &
+ ' By default applications specified in as "executable" in your package ', &
+ ' manifest are used, alternatively also demonstration programs under ', &
+ ' "example" can be used with this subcommand. ', &
' ', &
'OPTIONS ', &
' --target NAME(s) optional list of specific names to execute. ', &
' The default is to run all the applications in app/ ', &
' or the programs listed in the "fpm.toml" file. ', &
+ ' --example run example programs instead of applications ', &
' --release selects the optimized build instead of the debug ', &
' build. ', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
@@ -657,11 +665,15 @@ contains
' ', &
' # run default programs in /app or as specified in "fpm.toml" ', &
' fpm run ', &
-
+ ' ', &
' # run default programs in /app or as specified in "fpm.toml" ', &
' # using the compiler command "f90". ', &
' fpm run --compiler f90 ', &
' ', &
+ ' # run example and demonstration programs instead of the default ', &
+ ' # application programs (specified in "fpm.toml") ', &
+ ' fpm run --example ', &
+ ' ', &
' # run a specific program and pass arguments to the command ', &
' fpm run mytest -- -x 10 -y 20 --title "my title line" ', &
' ', &
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index a40aef0..b7d97db 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -36,7 +36,7 @@ public :: fpm_model_t, srcfile_t, build_target_t, build_target_ptr
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
- FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
+ FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, &
FPM_TARGET_OBJECT
@@ -66,6 +66,7 @@ integer, parameter :: FPM_SCOPE_DEP = 2
integer, parameter :: FPM_SCOPE_APP = 3
!> Module-use scope is library/dependency and test modules
integer, parameter :: FPM_SCOPE_TEST = 4
+integer, parameter :: FPM_SCOPE_EXAMPLE = 5
!> Target type is unknown (ignored)
diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90
index fd810f4..fb5a8ac 100644
--- a/fpm/src/fpm_targets.f90
+++ b/fpm/src/fpm_targets.f90
@@ -99,7 +99,7 @@ subroutine targets_from_sources(model,sources)
source = sources(i) &
)
- if (sources(i)%unit_scope == FPM_SCOPE_APP) then
+ if (any(sources(i)%unit_scope == [FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE])) then
call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
link_libraries = sources(i)%link_libraries, &
output_file = join_path(model%output_directory,'app', &
@@ -151,7 +151,7 @@ subroutine targets_from_sources(model,sources)
select case(source%unit_scope)
- case (FPM_SCOPE_APP)
+ case (FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE)
object_file = join_path(model%output_directory,'app',object_file)//'.o'
case (FPM_SCOPE_TEST)
@@ -258,8 +258,8 @@ subroutine resolve_module_dependencies(targets,error)
cycle
end if
- if (targets(i)%ptr%source%unit_scope == FPM_SCOPE_APP .OR. &
- targets(i)%ptr%source%unit_scope == FPM_SCOPE_TEST ) then
+ if (any(targets(i)%ptr%source%unit_scope == &
+ [FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
dep%ptr => &
find_module_dependency(targets,targets(i)%ptr%source%modules_used(j)%s, &
include_dir = dirname(targets(i)%ptr%source%file_name))
diff --git a/fpm/test/fpm_test/test_manifest.f90 b/fpm/test/fpm_test/test_manifest.f90
index 1c2cfb7..d8adf50 100644
--- a/fpm/test/fpm_test/test_manifest.f90
+++ b/fpm/test/fpm_test/test_manifest.f90
@@ -53,9 +53,11 @@ contains
& new_unittest("test-typeerror", test_test_typeerror, should_fail=.true.), &
& new_unittest("test-noname", test_test_noname, should_fail=.true.), &
& new_unittest("test-wrongkey", test_test_wrongkey, should_fail=.true.), &
- & new_unittest("test-link-string", test_link_string), &
- & new_unittest("test-link-array", test_link_array), &
- & new_unittest("test-link-error", test_invalid_link, should_fail=.true.)]
+ & new_unittest("link-string", test_link_string), &
+ & new_unittest("link-array", test_link_array), &
+ & new_unittest("link-error", test_invalid_link, should_fail=.true.), &
+ & new_unittest("example-simple", test_example_simple), &
+ & new_unittest("example-empty", test_example_empty, should_fail=.true.)]
end subroutine collect_manifest
@@ -881,6 +883,52 @@ contains
end subroutine test_test_wrongkey
+ !> Create a simple example entry
+ subroutine test_example_simple(error)
+ use fpm_manifest_example
+ use fpm_toml, only : new_table, set_value, add_table, toml_table
+
+ !> Error handling
+ type(error_t), allocatable, intent(out) :: error
+
+ type(toml_table) :: table
+ type(toml_table), pointer :: child
+ integer :: stat
+ type(example_config_t) :: example
+
+ call new_table(table)
+ call set_value(table, 'name', '"example"', stat)
+ call set_value(table, 'source-dir', '"demos"', stat)
+ call set_value(table, 'main', '"demo.f90"', stat)
+ call add_table(table, 'dependencies', child, stat)
+
+ call new_example(example, table, error)
+ if (allocated(error)) return
+
+ call check_string(error, example%main, "demo.f90", "Example main")
+ if (allocated(error)) return
+
+ end subroutine test_example_simple
+
+
+ !> Examples cannot be created from empty tables
+ subroutine test_example_empty(error)
+ use fpm_manifest_example
+ use fpm_toml, only : new_table, toml_table
+
+ !> Error handling
+ type(error_t), allocatable, intent(out) :: error
+
+ type(toml_table) :: table
+ type(example_config_t) :: example
+
+ call new_table(table)
+
+ call new_example(example, table, error)
+
+ end subroutine test_example_empty
+
+
!> Test link options
subroutine test_link_string(error)
use fpm_manifest_build
diff --git a/manifest-reference.md b/manifest-reference.md
index f1394cb..45b4827 100644
--- a/manifest-reference.md
+++ b/manifest-reference.md
@@ -27,6 +27,8 @@ Every manifest file consists of the following sections:
- Build configuration:
- [*auto-tests*](#automatic-target-discovery):
Toggle automatic discovery of test executables
+ - [*auto-examples*](#automatic-target-discovery):
+ Toggle automatic discovery of example programs
- [*auto-executables*](#automatic-target-discovery):
Toggle automatic discovery of executables
- [*link*](#link-external-libraries):
@@ -260,6 +262,41 @@ executable = [
```
+### Example targets
+
+Example applications for a project are defined as *example* sections.
+If no example section is specified the ``example`` directory is searched for program definitions.
+For explicitly specified examples the *name* entry must always be specified.
+The source directory for each example can be adjusted in the *source-dir* entry.
+Paths for the source directory are given relative to the project root and use ``/`` as path separator on all platforms.
+The source file containing the program body can be specified in the *main* entry.
+
+Examples can have their own dependencies.
+See [specifying dependencies](#specifying-dependencies) for more details.
+
+> Dependencies supported in Bootstrap fpm only
+
+Examples can also specify their own external library dependencies.
+See [external libraries](#link-external-libraries) for more details.
+
+> Linking against libraries is supported in Fortran fpm only
+
+*Example:*
+
+```toml
+[[ example ]]
+name = "demo-app"
+source-dir = "demo"
+main = "program.f90"
+
+[[ example ]]
+name = "example-tool"
+link = "z"
+[example.dependencies]
+helloff = { git = "https://gitlab.com/everythingfunctional/helloff.git" }
+```
+
+
### Test targets
Test targets are Fortran programs defined as *test* sections.
@@ -328,14 +365,15 @@ link = ["blas", "lapack"]
> Supported in Fortran fpm only
Executables and test can be discovered automatically in their default directories.
-The automatic discovery recursively searches the ``app`` and ``test`` directories for ``program`` definitions and declares them as executable and test targets, respectively.
+The automatic discovery recursively searches the ``app``, ``example``, and ``test`` directories for ``program`` definitions and declares them as executable, example, and test targets, respectively.
The automatic discovery is enabled by default.
-To disable the automatic discovery of targets set the *auto-executables* and *auto-tests* entry to *false*.
+To disable the automatic discovery of targets set the *auto-executables*, *auto-examples*, and *auto-tests* entry to *false*.
```toml
[build]
auto-executables = false
+auto-examples = false
auto-tests = false
```