aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
authorBrad Richardson <everythingfunctional@protonmail.com>2020-10-14 09:24:55 -0500
committerBrad Richardson <everythingfunctional@protonmail.com>2020-10-14 09:24:55 -0500
commitb5b16cf826d468e79b4087500192a4a9e07c140f (patch)
tree1f615ee9ed6500bb1f6964ef2af0478b2fe51e4e /test
parentd3a65e36b28808c2c51ae41fc107f1179e27a08c (diff)
downloadfpm-b5b16cf826d468e79b4087500192a4a9e07c140f.tar.gz
fpm-b5b16cf826d468e79b4087500192a4a9e07c140f.zip
Better organize example packages and bootstrap tests
Diffstat (limited to 'test')
-rw-r--r--test/Spec.hs41
-rw-r--r--test/example_packages/README.md20
-rw-r--r--test/example_packages/auto_discovery_off/app/main.f906
-rw-r--r--test/example_packages/auto_discovery_off/app/unused.f906
-rw-r--r--test/example_packages/auto_discovery_off/fpm.toml12
-rw-r--r--test/example_packages/auto_discovery_off/test/my_test.f906
-rw-r--r--test/example_packages/auto_discovery_off/test/unused_test.f907
-rw-r--r--test/example_packages/circular_example/.gitignore1
-rw-r--r--test/example_packages/circular_example/fpm.toml4
-rw-r--r--test/example_packages/circular_example/src/greet_m.f9013
-rw-r--r--test/example_packages/circular_example/test/main.f907
-rw-r--r--test/example_packages/circular_test/.gitignore1
-rw-r--r--test/example_packages/circular_test/fpm.toml4
-rw-r--r--test/example_packages/circular_test/src/hello_test.f9012
-rw-r--r--test/example_packages/hello_complex/.gitignore1
-rw-r--r--test/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f907
-rw-r--r--test/example_packages/hello_complex/apps/say_hello/say_Hello.f907
-rw-r--r--test/example_packages/hello_complex/fpm.toml24
-rw-r--r--test/example_packages/hello_complex/source/farewell_m.f9014
-rw-r--r--test/example_packages/hello_complex/source/greet_m.f9014
-rw-r--r--test/example_packages/hello_complex/source/subdir/constants.f907
-rw-r--r--test/example_packages/hello_complex/tests/farewell/farewell_test.f9018
-rw-r--r--test/example_packages/hello_complex/tests/greet/greet_test.f9018
-rw-r--r--test/example_packages/hello_complex_2/.gitignore1
-rw-r--r--test/example_packages/hello_complex_2/app/app_mod.f905
-rw-r--r--test/example_packages/hello_complex_2/app/say_goodbye.f908
-rw-r--r--test/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f904
-rw-r--r--test/example_packages/hello_complex_2/app/say_hello/say_Hello.f908
-rw-r--r--test/example_packages/hello_complex_2/fpm.toml6
-rw-r--r--test/example_packages/hello_complex_2/src/farewell_m.f9013
-rw-r--r--test/example_packages/hello_complex_2/src/greet_m.f9013
-rw-r--r--test/example_packages/hello_complex_2/test/farewell_test.f9019
-rw-r--r--test/example_packages/hello_complex_2/test/greet_test.f9019
-rw-r--r--test/example_packages/hello_complex_2/test/test_mod.f905
-rw-r--r--test/example_packages/hello_fpm/.gitignore1
-rw-r--r--test/example_packages/hello_fpm/app/main.f909
-rw-r--r--test/example_packages/hello_fpm/fpm.toml4
-rw-r--r--test/example_packages/hello_world/.gitignore1
-rw-r--r--test/example_packages/hello_world/app/main.f903
-rw-r--r--test/example_packages/hello_world/fpm.toml1
-rw-r--r--test/example_packages/makefile_complex/.gitignore1
-rw-r--r--test/example_packages/makefile_complex/Makefile9
-rw-r--r--test/example_packages/makefile_complex/app/main.f907
-rw-r--r--test/example_packages/makefile_complex/fpm.toml8
-rw-r--r--test/example_packages/makefile_complex/src/wrapper_mod.f9012
-rw-r--r--test/example_packages/program_with_module/app/main.f9010
-rw-r--r--test/example_packages/program_with_module/fpm.toml1
-rw-r--r--test/example_packages/submodules/fpm.toml1
-rw-r--r--test/example_packages/submodules/src/child1.f9016
-rw-r--r--test/example_packages/submodules/src/child2.f9010
-rw-r--r--test/example_packages/submodules/src/grandchild.f9010
-rw-r--r--test/example_packages/submodules/src/parent.f9015
-rw-r--r--test/example_packages/with_c/app/main.f9010
-rw-r--r--test/example_packages/with_c/fpm.toml1
-rw-r--r--test/example_packages/with_c/src/c_code.c10
-rw-r--r--test/example_packages/with_c/src/with_c.f9026
-rw-r--r--test/example_packages/with_makefile/.gitignore1
-rw-r--r--test/example_packages/with_makefile/Makefile9
-rw-r--r--test/example_packages/with_makefile/fpm.toml5
-rw-r--r--test/example_packages/with_makefile/src/hello_makefile.f9010
60 files changed, 0 insertions, 542 deletions
diff --git a/test/Spec.hs b/test/Spec.hs
deleted file mode 100644
index 6fb4006..0000000
--- a/test/Spec.hs
+++ /dev/null
@@ -1,41 +0,0 @@
-import Development.Shake.FilePath ( (</>) )
-import Fpm ( Arguments(..)
- , Command(..)
- , start
- )
-import System.Directory ( withCurrentDirectory )
-
-example_path = "test" </> "example_packages"
-
-main :: IO ()
-main = do
- testHelloWorld
- testHelloComplex
- testHelloFpm
- testCircular
- testWithMakefile
- testMakefileComplex
-
-testHelloWorld :: IO ()
-testHelloWorld =
- withCurrentDirectory (example_path </> "hello_world") $ start $ Arguments (Run "") False ""
-
-testHelloComplex :: IO ()
-testHelloComplex =
- withCurrentDirectory (example_path </> "hello_complex") $ start $ Arguments (Test "") False ""
-
-testHelloFpm :: IO ()
-testHelloFpm =
- withCurrentDirectory (example_path </> "hello_fpm") $ start $ Arguments (Run "") False ""
-
-testCircular :: IO ()
-testCircular =
- withCurrentDirectory (example_path </> "circular_example") $ start $ Arguments (Test "") False ""
-
-testWithMakefile :: IO ()
-testWithMakefile =
- withCurrentDirectory (example_path </> "with_makefile") $ start $ Arguments (Build) False ""
-
-testMakefileComplex :: IO ()
-testMakefileComplex =
- withCurrentDirectory (example_path </> "makefile_complex") $ start $ Arguments (Run "") False ""
diff --git a/test/example_packages/README.md b/test/example_packages/README.md
deleted file mode 100644
index 79fadb1..0000000
--- a/test/example_packages/README.md
+++ /dev/null
@@ -1,20 +0,0 @@
-# Example packages
-
-See the table below for a list of the example packages provided in this directory including
-the features demonstrated in each package and which versions of fpm are supported.
-
-
-| Name | Features | Bootstrap (Haskell) fpm | fpm |
-|---------------------|---------------------------------------------------------------|:-----------------------:|:---:|
-| auto_discovery_off | Default layout with auto-discovery disabled | N | Y |
-| circular_example | Local path dependency; circular dependency | Y | N |
-| circular_test | Local path dependency; circular dependency | Y | N |
-| hello_complex | Non-standard directory layout; multiple tests and executables | Y | Y |
-| hello_complex_2 | Auto-discovery of tests and executables with modules | N | Y |
-| hello_fpm | App-only; local path dependency | Y | N |
-| hello_world | App-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 |
-| with_c | Compile with `c` source files | N | Y |
-| with_makefile | External build command (makefile) | Y | N | \ No newline at end of file
diff --git a/test/example_packages/auto_discovery_off/app/main.f90 b/test/example_packages/auto_discovery_off/app/main.f90
deleted file mode 100644
index 8902dc6..0000000
--- a/test/example_packages/auto_discovery_off/app/main.f90
+++ /dev/null
@@ -1,6 +0,0 @@
-program main
-implicit none
-
-print *, "This program should run."
-
-end program main
diff --git a/test/example_packages/auto_discovery_off/app/unused.f90 b/test/example_packages/auto_discovery_off/app/unused.f90
deleted file mode 100644
index 57d8153..0000000
--- a/test/example_packages/auto_discovery_off/app/unused.f90
+++ /dev/null
@@ -1,6 +0,0 @@
-program unused
-implicit none
-
-print *, "This program should NOT run."
-
-end program unused
diff --git a/test/example_packages/auto_discovery_off/fpm.toml b/test/example_packages/auto_discovery_off/fpm.toml
deleted file mode 100644
index 9a852df..0000000
--- a/test/example_packages/auto_discovery_off/fpm.toml
+++ /dev/null
@@ -1,12 +0,0 @@
-name = "auto_discovery_off"
-
-[build]
-auto-executables = false
-auto-tests = false
-
-
-[[test]]
-name = "my_test"
-source-dir="test"
-main="my_test.f90"
-
diff --git a/test/example_packages/auto_discovery_off/test/my_test.f90 b/test/example_packages/auto_discovery_off/test/my_test.f90
deleted file mode 100644
index fd59f9f..0000000
--- a/test/example_packages/auto_discovery_off/test/my_test.f90
+++ /dev/null
@@ -1,6 +0,0 @@
-program my_test
-implicit none
-
-print *, "Test passed! That was easy!"
-
-end program my_test
diff --git a/test/example_packages/auto_discovery_off/test/unused_test.f90 b/test/example_packages/auto_discovery_off/test/unused_test.f90
deleted file mode 100644
index 5c42611..0000000
--- a/test/example_packages/auto_discovery_off/test/unused_test.f90
+++ /dev/null
@@ -1,7 +0,0 @@
-program unused_test
-implicit none
-
-print *, "This program should NOT run."
-
-end program unused_test
-
diff --git a/test/example_packages/circular_example/.gitignore b/test/example_packages/circular_example/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/circular_example/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/circular_example/fpm.toml b/test/example_packages/circular_example/fpm.toml
deleted file mode 100644
index c524ce5..0000000
--- a/test/example_packages/circular_example/fpm.toml
+++ /dev/null
@@ -1,4 +0,0 @@
-name = "circular_example"
-
-[dev-dependencies]
-circular_test = { path = "../circular_test" }
diff --git a/test/example_packages/circular_example/src/greet_m.f90 b/test/example_packages/circular_example/src/greet_m.f90
deleted file mode 100644
index 2372f9a..0000000
--- a/test/example_packages/circular_example/src/greet_m.f90
+++ /dev/null
@@ -1,13 +0,0 @@
-module greet_m
- implicit none
- private
-
- public :: make_greeting
-contains
- function make_greeting(name) result(greeting)
- character(len=*), intent(in) :: name
- character(len=:), allocatable :: greeting
-
- greeting = "Hello, " // name // "!"
- end function make_greeting
-end module greet_m
diff --git a/test/example_packages/circular_example/test/main.f90 b/test/example_packages/circular_example/test/main.f90
deleted file mode 100644
index 5b7d803..0000000
--- a/test/example_packages/circular_example/test/main.f90
+++ /dev/null
@@ -1,7 +0,0 @@
-program run_tests
- use hello_test, only: run_test
-
- implicit none
-
- call run_test
-end program run_tests
diff --git a/test/example_packages/circular_test/.gitignore b/test/example_packages/circular_test/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/circular_test/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/circular_test/fpm.toml b/test/example_packages/circular_test/fpm.toml
deleted file mode 100644
index 56cfa2e..0000000
--- a/test/example_packages/circular_test/fpm.toml
+++ /dev/null
@@ -1,4 +0,0 @@
-name = "circular_test"
-
-[dependencies]
-circular_example = { path = "../circular_example"}
diff --git a/test/example_packages/circular_test/src/hello_test.f90 b/test/example_packages/circular_test/src/hello_test.f90
deleted file mode 100644
index 5a591c6..0000000
--- a/test/example_packages/circular_test/src/hello_test.f90
+++ /dev/null
@@ -1,12 +0,0 @@
-module hello_test
- use greet_m, only: make_greeting
-
- implicit none
- private
-
- public :: run_test
-contains
- subroutine run_test
- print *, make_greeting("from test")
- end subroutine run_test
-end module hello_test
diff --git a/test/example_packages/hello_complex/.gitignore b/test/example_packages/hello_complex/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/hello_complex/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90 b/test/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90
deleted file mode 100644
index 6966e79..0000000
--- a/test/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90
+++ /dev/null
@@ -1,7 +0,0 @@
-program say_goodbye
- use farewell_m, only: make_farewell
-
- implicit none
-
- print *, make_farewell("World")
-end program say_goodbye
diff --git a/test/example_packages/hello_complex/apps/say_hello/say_Hello.f90 b/test/example_packages/hello_complex/apps/say_hello/say_Hello.f90
deleted file mode 100644
index cf4a742..0000000
--- a/test/example_packages/hello_complex/apps/say_hello/say_Hello.f90
+++ /dev/null
@@ -1,7 +0,0 @@
-program say_Hello
- use greet_m, only: make_greeting
-
- implicit none
-
- print *, make_greeting("World")
-end program say_Hello
diff --git a/test/example_packages/hello_complex/fpm.toml b/test/example_packages/hello_complex/fpm.toml
deleted file mode 100644
index 30ed293..0000000
--- a/test/example_packages/hello_complex/fpm.toml
+++ /dev/null
@@ -1,24 +0,0 @@
-name = "hello_complex"
-
-[library]
-source-dir="source"
-
-[[executable]]
-name="say_Hello"
-source-dir="apps/say_hello"
-main="say_Hello.f90"
-
-[[executable]]
-name="say_goodbye"
-source-dir="apps/say_goodbye"
-main="say_goodbye.f90"
-
-[[test]]
-name="greet_test"
-source-dir="tests/greet"
-main="greet_test.f90"
-
-[[test]]
-name="farewell_test"
-source-dir="tests/farewell"
-main="farewell_test.f90"
diff --git a/test/example_packages/hello_complex/source/farewell_m.f90 b/test/example_packages/hello_complex/source/farewell_m.f90
deleted file mode 100644
index fbc45ed..0000000
--- a/test/example_packages/hello_complex/source/farewell_m.f90
+++ /dev/null
@@ -1,14 +0,0 @@
-module farewell_m
- use subdir_constants, only: FAREWELL_STR
- implicit none
- private
-
- public :: make_farewell
-contains
- function make_farewell(name) result(greeting)
- character(len=*), intent(in) :: name
- character(len=:), allocatable :: greeting
-
- greeting = FAREWELL_STR // name // "!"
- end function make_farewell
-end module farewell_m
diff --git a/test/example_packages/hello_complex/source/greet_m.f90 b/test/example_packages/hello_complex/source/greet_m.f90
deleted file mode 100644
index 38afd08..0000000
--- a/test/example_packages/hello_complex/source/greet_m.f90
+++ /dev/null
@@ -1,14 +0,0 @@
-module greet_m
- use subdir_constants, only: GREET_STR
- implicit none
- private
-
- public :: make_greeting
-contains
- function make_greeting(name) result(greeting)
- character(len=*), intent(in) :: name
- character(len=:), allocatable :: greeting
-
- greeting = GREET_STR // name // "!"
- end function make_greeting
-end module greet_m
diff --git a/test/example_packages/hello_complex/source/subdir/constants.f90 b/test/example_packages/hello_complex/source/subdir/constants.f90
deleted file mode 100644
index 59d6e5f..0000000
--- a/test/example_packages/hello_complex/source/subdir/constants.f90
+++ /dev/null
@@ -1,7 +0,0 @@
-module subdir_constants
-implicit none
-
-character(*), parameter :: GREET_STR = 'Hello, '
-character(*), parameter :: FAREWELL_STR = 'Goodbye, '
-
-end module subdir_constants
diff --git a/test/example_packages/hello_complex/tests/farewell/farewell_test.f90 b/test/example_packages/hello_complex/tests/farewell/farewell_test.f90
deleted file mode 100644
index 0f21b18..0000000
--- a/test/example_packages/hello_complex/tests/farewell/farewell_test.f90
+++ /dev/null
@@ -1,18 +0,0 @@
-program farewell_test
- use farewell_m, only: make_farewell
- use iso_fortran_env, only: error_unit, output_unit
-
- implicit none
-
- character(len=:), allocatable :: farewell
-
- allocate(character(len=0) :: farewell)
- farewell = make_farewell("World")
-
- if (farewell == "Goodbye, World!") then
- write(output_unit, *) "Passed"
- else
- write(error_unit, *) "Failed"
- call exit(1)
- end if
-end program farewell_test
diff --git a/test/example_packages/hello_complex/tests/greet/greet_test.f90 b/test/example_packages/hello_complex/tests/greet/greet_test.f90
deleted file mode 100644
index 41fa508..0000000
--- a/test/example_packages/hello_complex/tests/greet/greet_test.f90
+++ /dev/null
@@ -1,18 +0,0 @@
-program greet_test
- use greet_m, only: make_greeting
- use iso_fortran_env, only: error_unit, output_unit
-
- implicit none
-
- character(len=:), allocatable :: greeting
-
- allocate(character(len=0) :: greeting)
- greeting = make_greeting("World")
-
- if (greeting == "Hello, World!") then
- write(output_unit, *) "Passed"
- else
- write(error_unit, *) "Failed"
- call exit(1)
- end if
-end program greet_test
diff --git a/test/example_packages/hello_complex_2/.gitignore b/test/example_packages/hello_complex_2/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/hello_complex_2/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/hello_complex_2/app/app_mod.f90 b/test/example_packages/hello_complex_2/app/app_mod.f90
deleted file mode 100644
index d69a228..0000000
--- a/test/example_packages/hello_complex_2/app/app_mod.f90
+++ /dev/null
@@ -1,5 +0,0 @@
-module app_mod
-implicit none
-
-
-end module app_mod
diff --git a/test/example_packages/hello_complex_2/app/say_goodbye.f90 b/test/example_packages/hello_complex_2/app/say_goodbye.f90
deleted file mode 100644
index db12cbf..0000000
--- a/test/example_packages/hello_complex_2/app/say_goodbye.f90
+++ /dev/null
@@ -1,8 +0,0 @@
-program say_goodbye
- use farewell_m, only: make_farewell
- use app_mod
-
- implicit none
-
- print *, make_farewell("World")
-end program say_goodbye
diff --git a/test/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90 b/test/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90
deleted file mode 100644
index 5c426c8..0000000
--- a/test/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90
+++ /dev/null
@@ -1,4 +0,0 @@
-module app_hello_mod
-implicit none
-
-end module app_hello_mod
diff --git a/test/example_packages/hello_complex_2/app/say_hello/say_Hello.f90 b/test/example_packages/hello_complex_2/app/say_hello/say_Hello.f90
deleted file mode 100644
index 3b69ba7..0000000
--- a/test/example_packages/hello_complex_2/app/say_hello/say_Hello.f90
+++ /dev/null
@@ -1,8 +0,0 @@
-program say_Hello
- use greet_m, only: make_greeting
- use app_hello_mod
-
- implicit none
-
- print *, make_greeting("World")
-end program say_Hello
diff --git a/test/example_packages/hello_complex_2/fpm.toml b/test/example_packages/hello_complex_2/fpm.toml
deleted file mode 100644
index 28c91d8..0000000
--- a/test/example_packages/hello_complex_2/fpm.toml
+++ /dev/null
@@ -1,6 +0,0 @@
-name = "hello_complex"
-
-[[executable]]
-name="say_hello_world"
-source-dir="app/say_hello"
-main="say_Hello.f90"
diff --git a/test/example_packages/hello_complex_2/src/farewell_m.f90 b/test/example_packages/hello_complex_2/src/farewell_m.f90
deleted file mode 100644
index 9fc75b9..0000000
--- a/test/example_packages/hello_complex_2/src/farewell_m.f90
+++ /dev/null
@@ -1,13 +0,0 @@
-module farewell_m
- implicit none
- private
-
- public :: make_farewell
-contains
- function make_farewell(name) result(greeting)
- character(len=*), intent(in) :: name
- character(len=:), allocatable :: greeting
-
- greeting = "Goodbye, " // name // "!"
- end function make_farewell
-end module farewell_m
diff --git a/test/example_packages/hello_complex_2/src/greet_m.f90 b/test/example_packages/hello_complex_2/src/greet_m.f90
deleted file mode 100644
index 2372f9a..0000000
--- a/test/example_packages/hello_complex_2/src/greet_m.f90
+++ /dev/null
@@ -1,13 +0,0 @@
-module greet_m
- implicit none
- private
-
- public :: make_greeting
-contains
- function make_greeting(name) result(greeting)
- character(len=*), intent(in) :: name
- character(len=:), allocatable :: greeting
-
- greeting = "Hello, " // name // "!"
- end function make_greeting
-end module greet_m
diff --git a/test/example_packages/hello_complex_2/test/farewell_test.f90 b/test/example_packages/hello_complex_2/test/farewell_test.f90
deleted file mode 100644
index dbe98d6..0000000
--- a/test/example_packages/hello_complex_2/test/farewell_test.f90
+++ /dev/null
@@ -1,19 +0,0 @@
-program farewell_test
- use farewell_m, only: make_farewell
- use test_mod
- use iso_fortran_env, only: error_unit, output_unit
-
- implicit none
-
- character(len=:), allocatable :: farewell
-
- allocate(character(len=0) :: farewell)
- farewell = make_farewell("World")
-
- if (farewell == "Goodbye, World!") then
- write(output_unit, *) "Passed"
- else
- write(error_unit, *) "Failed"
- call exit(1)
- end if
-end program farewell_test
diff --git a/test/example_packages/hello_complex_2/test/greet_test.f90 b/test/example_packages/hello_complex_2/test/greet_test.f90
deleted file mode 100644
index 38e9be0..0000000
--- a/test/example_packages/hello_complex_2/test/greet_test.f90
+++ /dev/null
@@ -1,19 +0,0 @@
-program greet_test
- use greet_m, only: make_greeting
- use test_mod
- use iso_fortran_env, only: error_unit, output_unit
-
- implicit none
-
- character(len=:), allocatable :: greeting
-
- allocate(character(len=0) :: greeting)
- greeting = make_greeting("World")
-
- if (greeting == "Hello, World!") then
- write(output_unit, *) "Passed"
- else
- write(error_unit, *) "Failed"
- call exit(1)
- end if
-end program greet_test
diff --git a/test/example_packages/hello_complex_2/test/test_mod.f90 b/test/example_packages/hello_complex_2/test/test_mod.f90
deleted file mode 100644
index edb2626..0000000
--- a/test/example_packages/hello_complex_2/test/test_mod.f90
+++ /dev/null
@@ -1,5 +0,0 @@
-module test_mod
-implicit none
-
-
-end module test_mod
diff --git a/test/example_packages/hello_fpm/.gitignore b/test/example_packages/hello_fpm/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/hello_fpm/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/hello_fpm/app/main.f90 b/test/example_packages/hello_fpm/app/main.f90
deleted file mode 100644
index 5df6d64..0000000
--- a/test/example_packages/hello_fpm/app/main.f90
+++ /dev/null
@@ -1,9 +0,0 @@
-program hello_fpm
- use farewell_m, only: make_farewell
- use greet_m, only: make_greeting
-
- implicit none
-
- print *, make_greeting("fpm")
- print *, make_farewell("fpm")
-end program hello_fpm
diff --git a/test/example_packages/hello_fpm/fpm.toml b/test/example_packages/hello_fpm/fpm.toml
deleted file mode 100644
index d94d904..0000000
--- a/test/example_packages/hello_fpm/fpm.toml
+++ /dev/null
@@ -1,4 +0,0 @@
-name = "hello_fpm"
-
-[dependencies]
-hello_complex = { path = "../hello_complex" }
diff --git a/test/example_packages/hello_world/.gitignore b/test/example_packages/hello_world/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/hello_world/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/hello_world/app/main.f90 b/test/example_packages/hello_world/app/main.f90
deleted file mode 100644
index d16022b..0000000
--- a/test/example_packages/hello_world/app/main.f90
+++ /dev/null
@@ -1,3 +0,0 @@
-program hello_world
- print *, "Hello, World!"
-end program hello_world
diff --git a/test/example_packages/hello_world/fpm.toml b/test/example_packages/hello_world/fpm.toml
deleted file mode 100644
index b80e8d1..0000000
--- a/test/example_packages/hello_world/fpm.toml
+++ /dev/null
@@ -1 +0,0 @@
-name = "hello_world"
diff --git a/test/example_packages/makefile_complex/.gitignore b/test/example_packages/makefile_complex/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/makefile_complex/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/makefile_complex/Makefile b/test/example_packages/makefile_complex/Makefile
deleted file mode 100644
index 497c6b2..0000000
--- a/test/example_packages/makefile_complex/Makefile
+++ /dev/null
@@ -1,9 +0,0 @@
-INCLUDE_FLAGS = $(addprefix -I,$(INCLUDE_DIRS))
-
-$(BUILD_DIR)/libmakefile_complex.a: $(BUILD_DIR)/wrapper_mod.o
- ar rs $(@) $(^)
-
-$(BUILD_DIR)/wrapper_mod.mod: src/wrapper_mod.f90
-
-$(BUILD_DIR)/wrapper_mod.o: src/wrapper_mod.f90
- $(FC) -c -J$(BUILD_DIR) $(INCLUDE_FLAGS) $(FFLAGS) -o $(@) $(<)
diff --git a/test/example_packages/makefile_complex/app/main.f90 b/test/example_packages/makefile_complex/app/main.f90
deleted file mode 100644
index ac9ed51..0000000
--- a/test/example_packages/makefile_complex/app/main.f90
+++ /dev/null
@@ -1,7 +0,0 @@
-program makefile_complex
- use wrapper_mod, only: do_stuff
-
- implicit none
-
- call do_stuff
-end program makefile_complex
diff --git a/test/example_packages/makefile_complex/fpm.toml b/test/example_packages/makefile_complex/fpm.toml
deleted file mode 100644
index 3282cbe..0000000
--- a/test/example_packages/makefile_complex/fpm.toml
+++ /dev/null
@@ -1,8 +0,0 @@
-name = "makefile_complex"
-
-[dependencies]
-with_makefile = { path = "../with_makefile" }
-
-[library]
-source-dir = "src"
-build-script = "Makefile"
diff --git a/test/example_packages/makefile_complex/src/wrapper_mod.f90 b/test/example_packages/makefile_complex/src/wrapper_mod.f90
deleted file mode 100644
index e8028b5..0000000
--- a/test/example_packages/makefile_complex/src/wrapper_mod.f90
+++ /dev/null
@@ -1,12 +0,0 @@
-module wrapper_mod
- use hello_makefile, only: say_hello_from_makefile
-
- implicit none
- private
-
- public :: do_stuff
-contains
- subroutine do_stuff
- call say_hello_from_makefile
- end subroutine do_stuff
-end module wrapper_mod
diff --git a/test/example_packages/program_with_module/app/main.f90 b/test/example_packages/program_with_module/app/main.f90
deleted file mode 100644
index 59441f0..0000000
--- a/test/example_packages/program_with_module/app/main.f90
+++ /dev/null
@@ -1,10 +0,0 @@
-module greet_m
- implicit none
- character(*), parameter :: greeting = 'Hello, fpm!'
-end module greet_m
-
-program program_with_module
- use greet_m, only: greeting
- implicit none
- print *, greeting
-end program program_with_module
diff --git a/test/example_packages/program_with_module/fpm.toml b/test/example_packages/program_with_module/fpm.toml
deleted file mode 100644
index bce6aa2..0000000
--- a/test/example_packages/program_with_module/fpm.toml
+++ /dev/null
@@ -1 +0,0 @@
-name = "Program_with_module"
diff --git a/test/example_packages/submodules/fpm.toml b/test/example_packages/submodules/fpm.toml
deleted file mode 100644
index cfc3d61..0000000
--- a/test/example_packages/submodules/fpm.toml
+++ /dev/null
@@ -1 +0,0 @@
-name = "submodules"
diff --git a/test/example_packages/submodules/src/child1.f90 b/test/example_packages/submodules/src/child1.f90
deleted file mode 100644
index dbd0fa5..0000000
--- a/test/example_packages/submodules/src/child1.f90
+++ /dev/null
@@ -1,16 +0,0 @@
-submodule(parent) child1
-implicit none
-
-interface
- module function my_fun() result (b)
- integer :: b
- end function my_fun
-end interface
-
-contains
-
-module procedure my_sub1
- a = 1
-end procedure my_sub1
-
-end submodule child1 \ No newline at end of file
diff --git a/test/example_packages/submodules/src/child2.f90 b/test/example_packages/submodules/src/child2.f90
deleted file mode 100644
index 179cc32..0000000
--- a/test/example_packages/submodules/src/child2.f90
+++ /dev/null
@@ -1,10 +0,0 @@
-submodule(parent) child2
-implicit none
-
-contains
-
-module procedure my_sub2
- a = 2
-end procedure my_sub2
-
-end submodule child2 \ No newline at end of file
diff --git a/test/example_packages/submodules/src/grandchild.f90 b/test/example_packages/submodules/src/grandchild.f90
deleted file mode 100644
index 8c5aa17..0000000
--- a/test/example_packages/submodules/src/grandchild.f90
+++ /dev/null
@@ -1,10 +0,0 @@
-submodule(parent:child1) grandchild
-implicit none
-
-contains
-
-module procedure my_fun
- b = 2
-end procedure my_fun
-
-end submodule grandchild \ No newline at end of file
diff --git a/test/example_packages/submodules/src/parent.f90 b/test/example_packages/submodules/src/parent.f90
deleted file mode 100644
index 570827c..0000000
--- a/test/example_packages/submodules/src/parent.f90
+++ /dev/null
@@ -1,15 +0,0 @@
-module parent
-implicit none
-
-interface
-
- module subroutine my_sub1(a)
- integer, intent(out) :: a
- end subroutine my_sub1
-
- module subroutine my_sub2(a)
- integer, intent(out) :: a
- end subroutine my_sub2
-end interface
-
-end module parent \ No newline at end of file
diff --git a/test/example_packages/with_c/app/main.f90 b/test/example_packages/with_c/app/main.f90
deleted file mode 100644
index 4d3174b..0000000
--- a/test/example_packages/with_c/app/main.f90
+++ /dev/null
@@ -1,10 +0,0 @@
-program with_c_app
-use with_c
-implicit none
-
-write(*,*) "isdir('app') = ", system_isdir('app')
-write(*,*) "isdir('src') = ", system_isdir('src')
-write(*,*) "isdir('test') = ", system_isdir('test')
-write(*,*) "isdir('bench') = ", system_isdir('bench')
-
-end program with_c_app \ No newline at end of file
diff --git a/test/example_packages/with_c/fpm.toml b/test/example_packages/with_c/fpm.toml
deleted file mode 100644
index 97e3110..0000000
--- a/test/example_packages/with_c/fpm.toml
+++ /dev/null
@@ -1 +0,0 @@
-name = "with_c"
diff --git a/test/example_packages/with_c/src/c_code.c b/test/example_packages/with_c/src/c_code.c
deleted file mode 100644
index 44604f0..0000000
--- a/test/example_packages/with_c/src/c_code.c
+++ /dev/null
@@ -1,10 +0,0 @@
-#include <sys/stat.h>
-/*
- * Decides whether a given file name is a directory.
- * return 1 if file exists and is a directory
- * Source (Public domain): https://github.com/urbanjost/M_system
- */
-int my_isdir (const char *path) {
- struct stat sb;
- return stat(path, &sb) == 0 && S_ISDIR (sb.st_mode);
-} \ No newline at end of file
diff --git a/test/example_packages/with_c/src/with_c.f90 b/test/example_packages/with_c/src/with_c.f90
deleted file mode 100644
index edd839e..0000000
--- a/test/example_packages/with_c/src/with_c.f90
+++ /dev/null
@@ -1,26 +0,0 @@
-module with_c
- use iso_c_binding, only: c_char, c_int, c_null_char
- implicit none
-
-contains
-
- function system_isdir(dirname)
- ! Source (Public domain): https://github.com/urbanjost/M_system
- !
- implicit none
- character(len=*),intent(in) :: dirname
- logical :: system_isdir
-
- interface
- function c_isdir(dirname) bind (C,name="my_isdir") result (c_ierr)
- import c_char,c_int
- character(kind=c_char,len=1),intent(in) :: dirname(*)
- integer(kind=c_int) :: c_ierr
- end function c_isdir
- end interface
-
- system_isdir= c_isdir(trim(dirname)//c_null_char) == 1
-
- end function system_isdir
-
-end module with_c \ No newline at end of file
diff --git a/test/example_packages/with_makefile/.gitignore b/test/example_packages/with_makefile/.gitignore
deleted file mode 100644
index a007fea..0000000
--- a/test/example_packages/with_makefile/.gitignore
+++ /dev/null
@@ -1 +0,0 @@
-build/*
diff --git a/test/example_packages/with_makefile/Makefile b/test/example_packages/with_makefile/Makefile
deleted file mode 100644
index 51e72d4..0000000
--- a/test/example_packages/with_makefile/Makefile
+++ /dev/null
@@ -1,9 +0,0 @@
-INCLUDE_FLAGS = $(addprefix -I,$(INCLUDE_DIRS))
-
-$(BUILD_DIR)/libwith_makefile.a: $(BUILD_DIR)/hello_makefile.o
- ar rs $(@) $(^)
-
-$(BUILD_DIR)/hello_makefile.mod: src/hello_makefile.f90
-
-$(BUILD_DIR)/hello_makefile.o: src/hello_makefile.f90
- $(FC) -c -J$(BUILD_DIR) $(INCLUDE_FLAGS) $(FFLAGS) -o $(@) $(<)
diff --git a/test/example_packages/with_makefile/fpm.toml b/test/example_packages/with_makefile/fpm.toml
deleted file mode 100644
index 81dd02a..0000000
--- a/test/example_packages/with_makefile/fpm.toml
+++ /dev/null
@@ -1,5 +0,0 @@
-name = "with_makefile"
-
-[library]
-source-dir = "src"
-build-script = "Makefile"
diff --git a/test/example_packages/with_makefile/src/hello_makefile.f90 b/test/example_packages/with_makefile/src/hello_makefile.f90
deleted file mode 100644
index 2d4d1a2..0000000
--- a/test/example_packages/with_makefile/src/hello_makefile.f90
+++ /dev/null
@@ -1,10 +0,0 @@
-module hello_makefile
- implicit none
- private
-
- public :: say_hello_from_makefile
-contains
- subroutine say_hello_from_makefile()
- print *, "Hello from Makefile library!"
- end subroutine say_hello_from_makefile
-end module hello_makefile