Skip to content

Commit

Permalink
Merge pull request #468 from ibara/openbsd
Browse files Browse the repository at this point in the history
Identify OpenBSD.
  • Loading branch information
milancurcic committed Apr 30, 2021
2 parents 7b53e5a + bd347aa commit 7704c00
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 11 deletions.
3 changes: 2 additions & 1 deletion src/fpm_command_line.f90
Expand Up @@ -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
Expand Down Expand Up @@ -129,6 +129,7 @@ subroutine get_command_line_settings(cmd_settings)
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
Expand Down
3 changes: 2 additions & 1 deletion src/fpm_compiler.f90
Expand Up @@ -35,7 +35,8 @@ module fpm_compiler
OS_WINDOWS, &
OS_CYGWIN, &
OS_SOLARIS, &
OS_FREEBSD
OS_FREEBSD, &
OS_OPENBSD
implicit none
public :: is_unknown_compiler
public :: get_module_flags
Expand Down
9 changes: 8 additions & 1 deletion src/fpm_environment.f90
Expand Up @@ -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
Expand Down Expand Up @@ -84,6 +85,12 @@ integer function get_os_type() result(r)
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
Expand Down
10 changes: 5 additions & 5 deletions src/fpm_filesystem.f90
Expand Up @@ -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
Expand Down Expand Up @@ -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)
Expand All @@ -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 = '\'
Expand Down Expand Up @@ -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

Expand Down Expand Up @@ -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)
Expand Down
6 changes: 3 additions & 3 deletions test/new_test/new_test.f90
Expand Up @@ -4,7 +4,7 @@ program new_test
dirname
use fpm_strings, only : string_t, operator(.in.)
use fpm_environment, only : run, get_os_type
use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS
use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD, OS_WINDOWS
implicit none
type(string_t), allocatable :: file_names(:)
integer :: i, j, k
Expand Down Expand Up @@ -49,7 +49,7 @@ program new_test
!! o DOS versus POSIX filenames
is_os_windows=.false.
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('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message)
path=cmdpath
case (OS_WINDOWS)
Expand Down Expand Up @@ -145,7 +145,7 @@ program new_test

! clean up scratch files; might want an option to leave them for inspection
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('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message)
case (OS_WINDOWS)
call execute_command_line('rmdir fpm_scratch_* /s /q',exitstat=estat,cmdstat=cstat,cmdmsg=message)
Expand Down

0 comments on commit 7704c00

Please sign in to comment.