diff --git a/src/fpm.f90 b/src/fpm.f90
index 41dac941ba..2075c02f52 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -78,7 +78,8 @@ subroutine build_model(model, settings, package, error)
     if (allocated(error)) return
 
     ! Create dependencies
-    call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
+    call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"), &
+    & path_to_config=settings%path_to_config)
 
     ! Build and resolve model dependencies
     call model%deps%add(package, error)
diff --git a/src/fpm/cmd/update.f90 b/src/fpm/cmd/update.f90
index c1f09e07c6..a78473b3a9 100644
--- a/src/fpm/cmd/update.f90
+++ b/src/fpm/cmd/update.f90
@@ -33,8 +33,8 @@ subroutine cmd_update(settings)
     cache = join_path("build", "cache.toml")
     if (settings%clean) call delete_file(cache)
 
-    call new_dependency_tree(deps, cache=cache, &
-      verbosity=merge(2, 1, settings%verbose))
+    call new_dependency_tree(deps, cache=cache, verbosity=merge(2, 1, settings%verbose), &
+    & path_to_config=settings%path_to_config)
 
     call deps%add(package, error)
     call handle_error(error)
diff --git a/src/fpm/dependency.f90 b/src/fpm/dependency.f90
index a7b3e51522..8929ea7c79 100644
--- a/src/fpm/dependency.f90
+++ b/src/fpm/dependency.f90
@@ -59,7 +59,7 @@ module fpm_dependency
   use fpm_environment, only: get_os_type, OS_WINDOWS, os_is_unix
   use fpm_error, only: error_t, fatal_error
   use fpm_filesystem, only: exists, join_path, mkdir, canon_path, windows_path, list_files, is_dir, basename, &
-                            os_delete_dir, get_temp_filename
+                            os_delete_dir, get_temp_filename, parent_dir
   use fpm_git, only: git_target_revision, git_target_default, git_revision, serializable_t
   use fpm_manifest, only: package_config_t, dependency_config_t, get_package_data
   use fpm_manifest_dependency, only: manifest_has_changed, dependency_destroy
@@ -130,6 +130,8 @@ module fpm_dependency
     type(dependency_node_t), allocatable :: dep(:)
     !> Cache file
     character(len=:), allocatable :: cache
+    !> Custom path to the global config file
+    character(len=:), allocatable :: path_to_config
 
   contains
 
@@ -198,13 +200,15 @@ module fpm_dependency
 contains
 
   !> Create a new dependency tree
-  subroutine new_dependency_tree(self, verbosity, cache)
+  subroutine new_dependency_tree(self, verbosity, cache, path_to_config)
     !> Instance of the dependency tree
     type(dependency_tree_t), intent(out) :: self
     !> Verbosity of printout
     integer, intent(in), optional :: verbosity
     !> Name of the cache file
     character(len=*), intent(in), optional :: cache
+    !> Path to the global config file.
+    character(len=*), intent(in), optional :: path_to_config
 
     call resize(self%dep)
     self%dep_dir = join_path("build", "dependencies")
@@ -213,6 +217,8 @@ subroutine new_dependency_tree(self, verbosity, cache)
 
     if (present(cache)) self%cache = cache
 
+    if (present(path_to_config)) self%path_to_config = path_to_config
+
   end subroutine new_dependency_tree
 
   !> Create a new dependency node from a configuration
@@ -566,8 +572,24 @@ subroutine resolve_dependencies(self, root, error)
     type(error_t), allocatable, intent(out) :: error
 
     type(fpm_global_settings) :: global_settings
+    character(:), allocatable :: parent_directory
     integer :: ii
 
+    ! Register path to global config file if it was entered via the command line.
+    if (allocated(self%path_to_config)) then
+      if (len_trim(self%path_to_config) > 0) then
+        parent_directory = parent_dir(self%path_to_config)
+
+        if (len_trim(parent_directory) == 0) then
+          global_settings%path_to_config_folder = "."
+        else
+          global_settings%path_to_config_folder = parent_directory
+        end if
+
+        global_settings%config_file_name = basename(self%path_to_config)
+      end if
+    end if
+
     call get_global_settings(global_settings, error)
     if (allocated(error)) return
 
@@ -695,7 +717,7 @@ subroutine get_from_registry(self, target_dir, global_settings, error, downloade
     end if
 
     ! Include namespace and package name in the target url and download package data.
-    target_url = global_settings%registry_settings%url//'packages/'//self%namespace//'/'//self%name
+    target_url = global_settings%registry_settings%url//'/packages/'//self%namespace//'/'//self%name
     call downloader%get_pkg_data(target_url, self%requested_version, tmp_file, json, error)
     close (unit, status='delete')
     if (allocated(error)) return
diff --git a/src/fpm/downloader.f90 b/src/fpm/downloader.f90
index 39a3314ccf..4c19bf9f29 100644
--- a/src/fpm/downloader.f90
+++ b/src/fpm/downloader.f90
@@ -18,7 +18,7 @@ module fpm_downloader
 
 contains
 
-  !> Perform an http get request, save output to file, and parse json.
+  !> Perform an http get request, save output to file, and parse json. 
   subroutine get_pkg_data(url, version, tmp_pkg_file, json, error)
     character(*), intent(in) :: url
     type(version_t), allocatable, intent(in) :: version
diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90
index a64a708103..ffb5a5b617 100644
--- a/src/fpm_command_line.f90
+++ b/src/fpm_command_line.f90
@@ -57,6 +57,7 @@ module fpm_command_line
 
 type, abstract :: fpm_cmd_settings
     character(len=:), allocatable :: working_dir
+    character(len=:), allocatable :: path_to_config
     logical                       :: verbose=.true.
 end type
 
@@ -240,7 +241,7 @@ subroutine get_command_line_settings(cmd_settings)
         type(fpm_export_settings) , allocatable :: export_settings
         type(version_t) :: version
         character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
-            & c_compiler, cxx_compiler, archiver, version_s, token_s
+            & c_compiler, cxx_compiler, archiver, version_s, token_s, config_file
 
         character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", &
             & fflags_env = "FFLAGS", cflags_env = "CFLAGS", cxxflags_env = "CXXFLAGS", ldflags_env = "LDFLAGS", &
@@ -308,7 +309,8 @@ subroutine get_command_line_settings(cmd_settings)
         case('run')
             call set_args(common_args // compiler_args // run_args //'&
             & --all F &
-            & --example F&
+            & --example F &
+            & --config-file " " &
             & --',help_run,version_text)
 
             call check_build_vals()
@@ -319,7 +321,6 @@ subroutine get_command_line_settings(cmd_settings)
                 names=[character(len=len(names)) :: ]
             endif
 
-
             if(specified('target') )then
                call split(sget('target'),tnames,delimiters=' ,:')
                names=[character(len=max(len(names),len(tnames))) :: names,tnames]
@@ -344,6 +345,7 @@ subroutine get_command_line_settings(cmd_settings)
             c_compiler = sget('c-compiler')
             cxx_compiler = sget('cxx-compiler')
             archiver = sget('archiver')
+            config_file = sget('config-file')
             allocate(fpm_run_settings :: cmd_settings)
             val_runner=sget('runner')
             if(specified('runner') .and. val_runner=='')val_runner='echo'
@@ -356,6 +358,7 @@ subroutine get_command_line_settings(cmd_settings)
             & c_compiler=c_compiler, &
             & cxx_compiler=cxx_compiler, &
             & archiver=archiver, &
+            & path_to_config=config_file, &
             & flag=val_flag, &
             & cflag=val_cflag, &
             & cxxflag=val_cxxflag, &
@@ -374,6 +377,7 @@ subroutine get_command_line_settings(cmd_settings)
             & --show-model F &
             & --dump " " &
             & --tests F &
+            & --config-file " " &
             & --',help_build,version_text)
 
             call check_build_vals()
@@ -381,7 +385,7 @@ subroutine get_command_line_settings(cmd_settings)
             c_compiler = sget('c-compiler')
             cxx_compiler = sget('cxx-compiler')
             archiver = sget('archiver')
-
+            config_file = sget('config-file')
             val_dump = sget('dump')
             if (specified('dump') .and. val_dump=='')val_dump='fpm_model.toml'
 
@@ -394,6 +398,7 @@ subroutine get_command_line_settings(cmd_settings)
             & c_compiler=c_compiler, &
             & cxx_compiler=cxx_compiler, &
             & archiver=archiver, &
+            & path_to_config=config_file, &
             & flag=val_flag, &
             & cflag=val_cflag, &
             & cxxflag=val_cxxflag, &
@@ -412,8 +417,8 @@ subroutine get_command_line_settings(cmd_settings)
             & --example F &
             & --backfill F &
             & --full F &
-            & --bare F', &
-            & help_new, version_text)
+            & --bare F &
+            &', help_new, version_text)
             select case(size(unnamed))
             case(1)
                 if(lget('backfill'))then
@@ -446,7 +451,6 @@ subroutine get_command_line_settings(cmd_settings)
                 call fpm_stop(4,' ')
             endif
 
-
             allocate(fpm_new_settings :: cmd_settings)
             if (any( specified([character(len=10) :: 'src','lib','app','test','example','bare'])) &
             & .and.lget('full') )then
@@ -482,7 +486,7 @@ subroutine get_command_line_settings(cmd_settings)
                  & verbose=lget('verbose') )
             endif
 
-        case('help','manual')
+        case('help', 'manual')
             call set_args(common_args, help_help,version_text)
             if(size(unnamed)<2)then
                 if(unnamed(1)=='help')then
@@ -533,16 +537,23 @@ subroutine get_command_line_settings(cmd_settings)
 
         case('install')
             call set_args(common_args // compiler_args // '&
-                & --no-rebuild F --prefix " " &
-                & --list F --test F &
-                & --libdir "lib" --bindir "bin" --testdir "test" --includedir "include"', &
-                help_install, version_text)
+                & --no-rebuild F &
+                & --prefix " " &
+                & --list F &
+                & --test F &
+                & --libdir "lib" &
+                & --bindir "bin" &
+                & --testdir "test" &
+                & --includedir "include" &
+                & --config-file " " &
+                &', help_install, version_text)
 
             call check_build_vals()
 
             c_compiler = sget('c-compiler')
             cxx_compiler = sget('cxx-compiler')
             archiver = sget('archiver')
+            config_file = sget('config-file')
             allocate(install_settings, source=fpm_install_settings(&
                 list=lget('list'), &
                 build_tests=lget('test'), &
@@ -552,6 +563,7 @@ subroutine get_command_line_settings(cmd_settings)
                 c_compiler=c_compiler, &
                 cxx_compiler=cxx_compiler, &
                 archiver=archiver, &
+                path_to_config=config_file, &
                 flag=val_flag, &
                 cflag=val_cflag, &
                 cxxflag=val_cxxflag, &
@@ -567,7 +579,7 @@ subroutine get_command_line_settings(cmd_settings)
 
         case('list')
             call set_args(common_args // '&
-            & --list F&
+            & --list F &
             &', help_list, version_text)
             if(lget('list'))then
                 help_text = [character(widest) :: help_list_nodash, help_list_dash]
@@ -577,8 +589,9 @@ subroutine get_command_line_settings(cmd_settings)
             call printhelp(help_text)
 
         case('test')
-            call set_args(common_args // compiler_args // run_args // ' --', &
-              help_test,version_text)
+            call set_args(common_args // compiler_args // run_args // '&
+            & --config-file " " &
+            & -- ', help_test,version_text)
 
             call check_build_vals()
 
@@ -607,6 +620,8 @@ subroutine get_command_line_settings(cmd_settings)
             c_compiler = sget('c-compiler')
             cxx_compiler = sget('cxx-compiler')
             archiver = sget('archiver')
+            config_file = sget('config-file')
+
             allocate(fpm_test_settings :: cmd_settings)
             val_runner=sget('runner')
             if(specified('runner') .and. val_runner=='')val_runner='echo'
@@ -619,6 +634,7 @@ subroutine get_command_line_settings(cmd_settings)
             & c_compiler=c_compiler, &
             & cxx_compiler=cxx_compiler, &
             & archiver=archiver, &
+            & path_to_config=config_file, &
             & flag=val_flag, &
             & cflag=val_cflag, &
             & cxxflag=val_cxxflag, &
@@ -632,8 +648,12 @@ subroutine get_command_line_settings(cmd_settings)
             & verbose=lget('verbose'))
 
         case('update')
-            call set_args(common_args // ' --fetch-only F --clean F --dump " " ', &
-                help_update, version_text)
+            call set_args(common_args // '&
+            & --fetch-only F &
+            & --clean F &
+            & --dump " " &
+            & --config-file " " &
+            &', help_update, version_text)
 
             if( size(unnamed) > 1 )then
                 names=unnamed(2:)
@@ -641,13 +661,19 @@ subroutine get_command_line_settings(cmd_settings)
                 names=[character(len=len(names)) :: ]
             endif
 
+
+            config_file = sget('config-file')
             val_dump = sget('dump')
             if (specified('dump') .and. val_dump=='')val_dump='fpm_dependencies.toml'
 
+
             allocate(fpm_update_settings :: cmd_settings)
-            cmd_settings=fpm_update_settings(name=names, dump=val_dump, &
-                fetch_only=lget('fetch-only'), verbose=lget('verbose'), &
-                clean=lget('clean'))
+            cmd_settings=fpm_update_settings(name=names, &
+            & fetch_only=lget('fetch-only'), &
+            & dump=val_dump, &
+            & verbose=lget('verbose'), &
+            & path_to_config=config_file, &
+            & clean=lget('clean'))
 
         case('export')
 
@@ -685,24 +711,28 @@ subroutine get_command_line_settings(cmd_settings)
             call set_args(common_args // &
             &   ' --registry-cache'   // &
             &   ' --skip'             // &
-            &   ' --all',                &
-                help_clean, version_text)
+            &   ' --all'              // &
+            &   ' --config-file ""', help_clean, version_text)
 
             block
                 logical :: skip, clean_all
 
                 skip = lget('skip')
                 clean_all = lget('all')
+                config_file = sget('config-file')
 
                 if (all([skip, clean_all])) then
                     call fpm_stop(6, 'Do not specify both --skip and --all options on the clean subcommand.')
                 end if
 
                 allocate(fpm_clean_settings :: cmd_settings)
+                call get_current_directory(working_dir, error)
                 cmd_settings = fpm_clean_settings( &
-                &   registry_cache=lget('registry-cache'), &
+                &   working_dir=working_dir, &
                 &   clean_skip=skip, &
-                &   clean_all=clean_all)
+                &   registry_cache=lget('registry-cache'), &
+                &   clean_all=clean_all, &
+                &   path_to_config=config_file)
             end block
 
         case('publish')
@@ -714,6 +744,7 @@ subroutine get_command_line_settings(cmd_settings)
             & --list F &
             & --show-model F &
             & --tests F &
+            & --config-file " " &
             & --', help_publish, version_text)
 
             call check_build_vals()
@@ -721,6 +752,7 @@ subroutine get_command_line_settings(cmd_settings)
             c_compiler = sget('c-compiler')
             cxx_compiler = sget('cxx-compiler')
             archiver = sget('archiver')
+            config_file = sget('config-file')
             token_s = sget('token')
 
             allocate(fpm_publish_settings :: cmd_settings)
@@ -741,6 +773,7 @@ subroutine get_command_line_settings(cmd_settings)
             & list=lget('list'),&
             & show_model=lget('show-model'),&
             & build_tests=lget('tests'),&
+            & path_to_config=config_file, &
             & verbose=lget('verbose'),&
             & token=token_s)
 
@@ -784,7 +817,7 @@ subroutine check_build_vals()
 
         val_flag = " " // sget('flag')
         val_cflag = " " // sget('c-flag')
-        val_cxxflag = " "// sget('cxx-flag')
+        val_cxxflag = " " // sget('cxx-flag')
         val_ldflag = " " // sget('link-flag')
         val_profile = sget('profile')
 
@@ -831,7 +864,7 @@ subroutine set_help()
    help_list_dash = [character(len=80) :: &
    '                                                                                ', &
    ' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list]     ', &
-   '       [--tests] [--no-prune] [--dump [FILENAME]]                               ', &
+   '       [--tests] [--no-prune] [--dump [FILENAME]] [--config-file PATH]          ', &
    ' help [NAME(s)]                                                                 ', &
    ' new NAME [[--lib|--src] [--app] [--test] [--example]]|                         ', &
    '          [--full|--bare][--backfill]                                           ', &
@@ -839,13 +872,14 @@ subroutine set_help()
    ' list [--list]                                                                  ', &
    ' run  [[--target] NAME(s) [--example] [--profile PROF] [--flag FFLAGS] [--all]  ', &
    '      [--runner "CMD"] [--compiler COMPILER_NAME] [--list] [-- ARGS]            ', &
+   '      [--config-file PATH]                                                      ', &
    ' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--runner "CMD"]    ', &
-   '      [--list] [--compiler COMPILER_NAME] [-- ARGS]                             ', &
+   '      [--list] [--compiler COMPILER_NAME] [--config-file PATH] [-- ARGS]        ', &
    ' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH]        ', &
-   '         [options]                                                              ', &
-   ' clean [--skip] [--all] [--registry-cache]                                      ', &
+   '         [--config-file PATH] [--registry-cache] [options]                      ', &
+   ' clean [--skip] [--all] [--config-file PATH] [--registry-cache]                 ', &
    ' publish [--token TOKEN] [--show-package-version] [--show-upload-data]          ', &
-   '         [--dry-run] [--verbose]                                                ', &
+   '         [--dry-run] [--verbose] [--config-file PATH]                           ', &
    ' ']
     help_usage=[character(len=80) :: &
     '' ]
@@ -867,7 +901,7 @@ subroutine set_help()
    '   from platform to platform or require independent installation.               ', &
    '                                                                                ', &
    'OPTION                                                                          ', &
-   ' --runner ''CMD''  quoted command used to launch the fpm(1) executables.          ', &
+   ' --runner ''CMD''  quoted command used to launch the fpm(1) executables.        ', &
    '               Available for both the "run" and "test" subcommands.             ', &
    '               If the keyword is specified without a value the default command  ', &
    '               is "echo".                                                       ', &
@@ -877,7 +911,7 @@ subroutine set_help()
    '                    file names with. These options are passed as command-line   ', &
    '                    arguments to the app.                                       ', &
    'EXAMPLES                                                                        ', &
-   '   Use cases for ''fpm run|test --runner "CMD"'' include employing                ', &
+   '   Use cases for ''fpm run|test --runner "CMD"'' include employing              ', &
    '   the following common GNU/Linux and Unix commands:                            ', &
    '                                                                                ', &
    ' INTERROGATE                                                                    ', &
@@ -907,7 +941,7 @@ subroutine set_help()
    '  fpm run --runner "mpiexec" --runner-args "-np 12"                             ', &
    '  fpm run --runner ldd                                                          ', &
    '  fpm run --runner strip                                                        ', &
-   '  fpm run --runner ''cp -t /usr/local/bin''                                       ', &
+   '  fpm run --runner ''cp -t /usr/local/bin''                                     ', &
    '                                                                                ', &
    '  # options after executable name can be specified after the -- option          ', &
    '  fpm --runner cp run -- /usr/local/bin/                                        ', &
@@ -959,22 +993,23 @@ subroutine set_help()
     '  Their syntax is                                                      ', &
     '                                                                                ', &
     '    build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME]  ', &
-    '          [--tests] [--no-prune] [--dump [FILENAME]]                            ', &
+    '          [--tests] [--no-prune] [--config-file PATH] [--dump [FILENAME]]       ', &
     '    new NAME [[--lib|--src] [--app] [--test] [--example]]|                      ', &
     '             [--full|--bare][--backfill]                                        ', &
-    '    update [NAME(s)] [--fetch-only] [--clean] [--dump [FILENAME]]               ', &
+    '    update [NAME(s)] [--fetch-only] [--clean] [--config-file PATH] [--dump [FILENAME]]', &
     '    run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] [--all]  ', &
     '        [--example] [--runner "CMD"] [--compiler COMPILER_NAME]                 ', &
-    '        [--no-prune] [-- ARGS]                                                  ', &
+    '        [--no-prune] [-- ARGS] [--config-file PATH]                             ', &
     '    test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list]         ', &
     '         [--runner "CMD"] [--compiler COMPILER_NAME] [--no-prune] [-- ARGS]     ', &
+    '         [--config-file PATH]                                                   ', &
     '    help [NAME(s)]                                                              ', &
     '    list [--list]                                                               ', &
     '    install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH]     ', &
-    '            [options]                                                           ', &
-    '    clean [--skip] [--all] [--registry-cache]                                   ', &
+    '            [options] [--config-file PATH] [--registry-cache]                    ', &
+    '    clean [--skip] [--all] [--config-file PATH] [--registry-cache]               ', &
     '    publish [--token TOKEN] [--show-package-version] [--show-upload-data]       ', &
-    '            [--dry-run] [--verbose]                                             ', &
+    '            [--dry-run] [--verbose] [--config-file PATH]                        ', &
     '                                                                                ', &
     'SUBCOMMAND OPTIONS                                                              ', &
     ' -C, --directory PATH', &
@@ -1079,9 +1114,9 @@ subroutine set_help()
     ' run(1) - the fpm(1) subcommand to run project applications            ', &
     '                                                                       ', &
     'SYNOPSIS                                                               ', &
-    ' fpm run [[--target] NAME(s) [--profile PROF] [--flag FFLAGS]', &
+    ' fpm run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS]', &
     '         [--compiler COMPILER_NAME] [--runner "CMD"] [--example]', &
-    '         [--list] [--all] [-- ARGS]', &
+    '         [--list] [--all] [--config-file PATH] [-- ARGS]', &
     '                                                                       ', &
     ' fpm run --help|--version                                              ', &
     '                                                                       ', &
@@ -1103,8 +1138,9 @@ subroutine set_help()
     '                   any single character and "*" represents any string. ', &
     '                   Note The glob string normally needs quoted to       ', &
     '                   the special characters from shell expansion.        ', &
-    ' --all   Run all examples or applications. An alias for --target ''*''.  ', &
+    ' --all  Run all examples or applications. An alias for --target ''*''. ', &
     ' --example  Run example programs instead of applications.              ', &
+    ' --config-file PATH  Custom location of the global config file.        ', &
     help_text_build_common, &
     help_text_compiler, &
     help_text_flag, &
@@ -1150,7 +1186,7 @@ subroutine set_help()
     '                                                                       ', &
     'SYNOPSIS                                                               ', &
     ' fpm build [--profile PROF] [--flag FFLAGS] [--compiler COMPILER_NAME] ', &
-    '           [--list] [--tests] [--dump [FILENAME]]                      ', &
+    '           [--list] [--tests] [--config-file PATH] [--dump [FILENAME]] ', &
     '                                                                       ', &
     ' fpm build --help|--version                                            ', &
     '                                                                       ', &
@@ -1185,6 +1221,7 @@ subroutine set_help()
     '                   (default file name: model.toml)                     ', &
     ' --help        print this help and exit                                ', &
     ' --version     print program version information and exit              ', &
+    ' --config-file PATH  custom location of the global config file         ', &    
     '                                                                       ', &
     help_text_environment, &
     '                                                                       ', &
@@ -1335,8 +1372,9 @@ subroutine set_help()
     ' test(1) - the fpm(1) subcommand to run project tests                  ', &
     '                                                                       ', &
     'SYNOPSIS                                                               ', &
-    ' fpm test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS]', &
-    '          [--compiler COMPILER_NAME ] [--runner "CMD"] [--list][-- ARGS]', &
+    ' fpm test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS]        ', &
+    '          [--compiler COMPILER_NAME ] [--runner "CMD"] [--list]        ', &
+    '          [-- ARGS] [--config-file PATH]                               ', &
     '                                                                       ', &
     ' fpm test --help|--version                                             ', &
     '                                                                       ', &
@@ -1359,6 +1397,7 @@ subroutine set_help()
     '               see "fpm help runner" for further details.              ', &
     ' --list     list candidate basenames instead of running them. Note they', &
     ' --list     will still be built if not currently up to date.           ', &
+    ' --config-file PATH  Custom location of the global config file.        ', &
     ' -- ARGS    optional arguments to pass to the test program(s).         ', &
     '            The same arguments are passed to all test names            ', &
     '            specified.                                                 ', &
@@ -1385,18 +1424,20 @@ subroutine set_help()
     '', &
     'SYNOPSIS', &
     ' fpm update [--fetch-only] [--clean] [--verbose] [--dump [FILENAME]] [NAME(s)]', &
+    '            [--config-file PATH] ', &
     '', &
     'DESCRIPTION', &
     ' Manage and update project dependencies. If no dependency names are', &
     ' provided all the dependencies are updated automatically.', &
     '', &
     'OPTIONS', &
-    ' --fetch-only  Only fetch dependencies, do not update existing projects', &
-    ' --clean       Do not use previous dependency cache', &
-    ' --verbose     Show additional printout', &
-    ' --dump [FILENAME] Dump updated dependency tree to file. use JSON format  ', &
-    '                   if file name is *.json; use TOML format otherwise      ', &
-    '                   (default file name: fpm_dependencies.toml)             ', &
+    ' --fetch-only        Only fetch dependencies, do not update existing projects', &
+    ' --clean             Do not use previous dependency cache', &
+    ' --config-file PATH  Custom location of the global config file', &
+    ' --verbose           Show additional printout', &
+    ' --dump [FILENAME]   Dump updated dependency tree to file. use JSON format  ', &
+    '                     if file name is *.json; use TOML format otherwise      ', &
+    '                     (default file name: fpm_dependencies.toml)             ', &
     '', &
     'SEE ALSO', &
     ' The fpm(1) home page at https://github.com/fortran-lang/fpm', &
@@ -1408,7 +1449,7 @@ subroutine set_help()
     'SYNOPSIS', &
     ' fpm install [--profile PROF] [--flag FFLAGS] [--list] [--no-rebuild]', &
     '             [--prefix DIR] [--bindir DIR] [--libdir DIR] [--includedir DIR]', &
-    '             [--verbose]', &
+    '             [--verbose] [--config-file PATH]', &
     '', &
     'DESCRIPTION', &
     ' Subcommand to install fpm projects. Running install will export the', &
@@ -1422,18 +1463,19 @@ subroutine set_help()
     '                   but do not install any of them', &
     help_text_build_common,&
     help_text_flag, &
-    ' --no-rebuild      do not rebuild project before installation', &
-    ' --test            also install test programs', &
-    ' --prefix DIR      path to installation directory (requires write access),', &
-    '                   the default prefix on Unix systems is $HOME/.local', &
-    '                   and %APPDATA%\local on Windows', &
-    ' --bindir DIR      subdirectory to place executables in (default: bin)', &
-    ' --libdir DIR      subdirectory to place libraries and archives in', &
-    '                   (default: lib)', &
-    ' --includedir DIR  subdirectory to place headers and module files in', &
-    '                   (default: include)', &
-    ' --testdir DIR     subdirectory to place test programs in (default: test)', & 
-    ' --verbose         print more information', &
+    ' --no-rebuild        do not rebuild project before installation', &
+    ' --test              also install test programs', &    
+    ' --prefix DIR        path to installation directory (requires write access),', &
+    '                     the default prefix on Unix systems is $HOME/.local', &
+    '                     and %APPDATA%\local on Windows', &
+    ' --bindir DIR        subdirectory to place executables in (default: bin)', &
+    ' --libdir DIR        subdirectory to place libraries and archives in', &
+    '                     (default: lib)', &
+    ' --includedir DIR    subdirectory to place headers and module files in', &
+    '                     (default: include)', &
+    ' --testdir DIR       subdirectory to place test programs in (default: test)', &     
+    ' --config-file PATH  custom location of the global config file', &
+    ' --verbose           print more information', &
     '', &
     help_text_environment, &
     '', &
@@ -1466,9 +1508,10 @@ subroutine set_help()
     ' Use the --registry-cache option to delete the registry cache.', &
     '', &
     'OPTIONS', &
-    ' --skip            Delete the build without prompting but skip dependencies.', &
-    ' --all             Delete the build without prompting including dependencies.', &
-    ' --registry-cache  Delete registry cache.', &
+    ' --skip              Delete the build without prompting but skip dependencies.', &
+    ' --all               Delete the build without prompting including dependencies.', &
+    ' --config-file PATH  Custom location of the global config file.', &
+    ' --registry-cache    Delete registry cache.', &
     '' ]
     help_publish=[character(len=80) :: &
     'NAME', &
@@ -1476,7 +1519,7 @@ subroutine set_help()
     '', &
     'SYNOPSIS', &
     ' fpm publish [--token TOKEN] [--show-package-version] [--show-upload-data]', &
-    '             [--dry-run] [--verbose]                                      ', &
+    '             [--dry-run] [--verbose] [--config-file PATH]', &
     '', &
     ' fpm publish --help|--version', &
     '', &
@@ -1508,6 +1551,7 @@ subroutine set_help()
     ' --dry-run                perform dry run without publishing', &
     ' --help                   print this help and exit', &
     ' --version                print program version information and exit', &
+    ' --config-file PATH       custom location of the global config file', &
     ' --verbose                print more information', &
     '', &
     'EXAMPLES', &