Skip to content

Commit 7704c00

Browse files
authored
Merge pull request #468 from ibara/openbsd
Identify OpenBSD.
2 parents 7b53e5a + bd347aa commit 7704c00

File tree

5 files changed

+20
-11
lines changed

5 files changed

+20
-11
lines changed

src/fpm_command_line.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@
2525
module fpm_command_line
2626
use fpm_environment, only : get_os_type, get_env, &
2727
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
28-
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
28+
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030
use fpm_strings, only : lower, split, fnv_1a
3131
use fpm_filesystem, only : basename, canon_path, to_fortran_name
@@ -129,6 +129,7 @@ subroutine get_command_line_settings(cmd_settings)
129129
case (OS_CYGWIN); os_type = "OS Type: Cygwin"
130130
case (OS_SOLARIS); os_type = "OS Type: Solaris"
131131
case (OS_FREEBSD); os_type = "OS Type: FreeBSD"
132+
case (OS_OPENBSD); os_type = "OS Type: OpenBSD"
132133
case (OS_UNKNOWN); os_type = "OS Type: Unknown"
133134
case default ; os_type = "OS Type: UNKNOWN"
134135
end select

src/fpm_compiler.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,8 @@ module fpm_compiler
3535
OS_WINDOWS, &
3636
OS_CYGWIN, &
3737
OS_SOLARIS, &
38-
OS_FREEBSD
38+
OS_FREEBSD, &
39+
OS_OPENBSD
3940
implicit none
4041
public :: is_unknown_compiler
4142
public :: get_module_flags

src/fpm_environment.f90

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,12 +18,13 @@ module fpm_environment
1818
integer, parameter, public :: OS_CYGWIN = 4
1919
integer, parameter, public :: OS_SOLARIS = 5
2020
integer, parameter, public :: OS_FREEBSD = 6
21+
integer, parameter, public :: OS_OPENBSD = 7
2122
contains
2223
!> Determine the OS type
2324
integer function get_os_type() result(r)
2425
!!
2526
!! Returns one of OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, OS_CYGWIN,
26-
!! OS_SOLARIS, OS_FREEBSD.
27+
!! OS_SOLARIS, OS_FREEBSD, OS_OPENBSD.
2728
!!
2829
!! At first, the environment variable `OS` is checked, which is usually
2930
!! found on Windows. Then, `OSTYPE` is read in and compared with common
@@ -84,6 +85,12 @@ integer function get_os_type() result(r)
8485
r = OS_FREEBSD
8586
return
8687
end if
88+
89+
! OpenBSD
90+
if (index(val, 'OpenBSD') > 0 .or. index(val, 'openbsd') > 0) then
91+
r = OS_OPENBSD
92+
return
93+
end if
8794
end if
8895

8996
! Linux

src/fpm_filesystem.f90

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module fpm_filesystem
44
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
55
use fpm_environment, only: get_os_type, &
66
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
7-
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
7+
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
88
use fpm_strings, only: f_string, replace, string_t, split
99
implicit none
1010
private
@@ -192,7 +192,7 @@ logical function is_dir(dir)
192192

193193
select case (get_os_type())
194194

195-
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
195+
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
196196
call execute_command_line("test -d " // dir , exitstat=stat)
197197

198198
case (OS_WINDOWS)
@@ -214,7 +214,7 @@ function join_path(a1,a2,a3,a4,a5) result(path)
214214
character(len=1) :: filesep
215215

216216
select case (get_os_type())
217-
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
217+
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
218218
filesep = '/'
219219
case (OS_WINDOWS)
220220
filesep = '\'
@@ -283,7 +283,7 @@ subroutine mkdir(dir)
283283
if (is_dir(dir)) return
284284

285285
select case (get_os_type())
286-
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
286+
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
287287
call execute_command_line('mkdir -p ' // dir, exitstat=stat)
288288
write (*, '(" + ",2a)') 'mkdir -p ' // dir
289289

@@ -322,7 +322,7 @@ recursive subroutine list_files(dir, files, recurse)
322322
allocate (temp_file, source=get_temp_filename())
323323

324324
select case (get_os_type())
325-
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
325+
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
326326
call execute_command_line('ls -A ' // dir // ' > ' // temp_file, &
327327
exitstat=stat)
328328
case (OS_WINDOWS)

test/new_test/new_test.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ program new_test
44
dirname
55
use fpm_strings, only : string_t, operator(.in.)
66
use fpm_environment, only : run, get_os_type
7-
use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS
7+
use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD, OS_WINDOWS
88
implicit none
99
type(string_t), allocatable :: file_names(:)
1010
integer :: i, j, k
@@ -49,7 +49,7 @@ program new_test
4949
!! o DOS versus POSIX filenames
5050
is_os_windows=.false.
5151
select case (get_os_type())
52-
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
52+
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
5353
call execute_command_line('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message)
5454
path=cmdpath
5555
case (OS_WINDOWS)
@@ -145,7 +145,7 @@ program new_test
145145

146146
! clean up scratch files; might want an option to leave them for inspection
147147
select case (get_os_type())
148-
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
148+
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
149149
call execute_command_line('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message)
150150
case (OS_WINDOWS)
151151
call execute_command_line('rmdir fpm_scratch_* /s /q',exitstat=estat,cmdstat=cstat,cmdmsg=message)

0 commit comments

Comments
 (0)