aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/fpm_command_line.f903
-rw-r--r--src/fpm_compiler.f903
-rw-r--r--src/fpm_environment.f909
-rw-r--r--src/fpm_filesystem.f9010
4 files changed, 17 insertions, 8 deletions
diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90
index 9e9a572..2a2ecf5 100644
--- a/src/fpm_command_line.f90
+++ b/src/fpm_command_line.f90
@@ -25,7 +25,7 @@
module fpm_command_line
use fpm_environment, only : get_os_type, get_env, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
- OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
+ OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
use fpm_strings, only : lower, split, fnv_1a
use fpm_filesystem, only : basename, canon_path, to_fortran_name
@@ -129,6 +129,7 @@ contains
case (OS_CYGWIN); os_type = "OS Type: Cygwin"
case (OS_SOLARIS); os_type = "OS Type: Solaris"
case (OS_FREEBSD); os_type = "OS Type: FreeBSD"
+ case (OS_OPENBSD); os_type = "OS Type: OpenBSD"
case (OS_UNKNOWN); os_type = "OS Type: Unknown"
case default ; os_type = "OS Type: UNKNOWN"
end select
diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90
index ca0f4d7..ff311f7 100644
--- a/src/fpm_compiler.f90
+++ b/src/fpm_compiler.f90
@@ -35,7 +35,8 @@ use fpm_environment, only: &
OS_WINDOWS, &
OS_CYGWIN, &
OS_SOLARIS, &
- OS_FREEBSD
+ OS_FREEBSD, &
+ OS_OPENBSD
implicit none
public :: is_unknown_compiler
public :: get_module_flags
diff --git a/src/fpm_environment.f90 b/src/fpm_environment.f90
index cde1780..345f6ab 100644
--- a/src/fpm_environment.f90
+++ b/src/fpm_environment.f90
@@ -18,12 +18,13 @@ module fpm_environment
integer, parameter, public :: OS_CYGWIN = 4
integer, parameter, public :: OS_SOLARIS = 5
integer, parameter, public :: OS_FREEBSD = 6
+ integer, parameter, public :: OS_OPENBSD = 7
contains
!> Determine the OS type
integer function get_os_type() result(r)
!!
!! Returns one of OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, OS_CYGWIN,
- !! OS_SOLARIS, OS_FREEBSD.
+ !! OS_SOLARIS, OS_FREEBSD, OS_OPENBSD.
!!
!! At first, the environment variable `OS` is checked, which is usually
!! found on Windows. Then, `OSTYPE` is read in and compared with common
@@ -84,6 +85,12 @@ contains
r = OS_FREEBSD
return
end if
+
+ ! OpenBSD
+ if (index(val, 'OpenBSD') > 0 .or. index(val, 'openbsd') > 0) then
+ r = OS_OPENBSD
+ return
+ end if
end if
! Linux
diff --git a/src/fpm_filesystem.f90 b/src/fpm_filesystem.f90
index 6acd383..28c3b33 100644
--- a/src/fpm_filesystem.f90
+++ b/src/fpm_filesystem.f90
@@ -4,7 +4,7 @@ module fpm_filesystem
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
use fpm_environment, only: get_os_type, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
- OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
+ OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
use fpm_strings, only: f_string, replace, string_t, split
implicit none
private
@@ -192,7 +192,7 @@ logical function is_dir(dir)
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line("test -d " // dir , exitstat=stat)
case (OS_WINDOWS)
@@ -214,7 +214,7 @@ function join_path(a1,a2,a3,a4,a5) result(path)
character(len=1) :: filesep
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
filesep = '/'
case (OS_WINDOWS)
filesep = '\'
@@ -283,7 +283,7 @@ subroutine mkdir(dir)
if (is_dir(dir)) return
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line('mkdir -p ' // dir, exitstat=stat)
write (*, '(" + ",2a)') 'mkdir -p ' // dir
@@ -322,7 +322,7 @@ recursive subroutine list_files(dir, files, recurse)
allocate (temp_file, source=get_temp_filename())
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line('ls -A ' // dir // ' > ' // temp_file, &
exitstat=stat)
case (OS_WINDOWS)