Skip to content

Commit f39c35e

Browse files
committed
rename default -> optval
1 parent 486be15 commit f39c35e

File tree

4 files changed

+155
-158
lines changed

4 files changed

+155
-158
lines changed

src/CMakeLists.txt

+1-1
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ set(SRC
22
stdlib_experimental_ascii.f90
33
stdlib_experimental_io.f90
44
stdlib_experimental_error.f90
5-
stdlib_experimental_default.f90
5+
stdlib_experimental_optval.f90
66
)
77

88
add_library(fortran_stdlib ${SRC})

src/Makefile.manual

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
SRC = stdlib_experimental_ascii.f90 \
22
stdlib_experimental_error.f90 \
33
stdlib_experimental_io.f90 \
4-
stdlib_experimental_default.f90 \
4+
stdlib_experimental_optval.f90 \
55
f18estop.f90
66

77
LIB = libstdlib.a

src/stdlib_experimental_default.f90

-156
This file was deleted.

src/stdlib_experimental_optval.f90

+153
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,153 @@
1+
module stdlib_experimental_optval
2+
!!
3+
!! Provides a generic function `optval`, which can be used to
4+
!! conveniently implement fallback values for optional arguments
5+
!! to subprograms. If `x` is an `optional` parameter of a
6+
!! subprogram, then the expression `optval(x, default)` inside that
7+
!! subprogram evaluates to `x` if it is present, otherwise `default`.
8+
!!
9+
!! It is an error to call `optval` with a single actual argument.
10+
!!
11+
use iso_fortran_env, only: sp => real32, dp => real64, qp => real128, int8, int16, int32, int64
12+
implicit none
13+
14+
15+
private
16+
public :: optval
17+
18+
19+
interface optval
20+
module procedure optval_sp
21+
module procedure optval_dp
22+
module procedure optval_qp
23+
module procedure optval_int8
24+
module procedure optval_int16
25+
module procedure optval_int32
26+
module procedure optval_int64
27+
module procedure optval_logical
28+
module procedure optval_character
29+
! TODO: complex kinds
30+
! TODO: differentiate ascii & ucs char kinds
31+
end interface optval
32+
33+
34+
contains
35+
36+
37+
function optval_sp(x, default) result(y)
38+
real(sp), intent(in), optional :: x
39+
real(sp), intent(in) :: default
40+
real(sp) :: y
41+
42+
if (present(x)) then
43+
y = x
44+
else
45+
y = default
46+
end if
47+
end function optval_sp
48+
49+
50+
function optval_dp(x, default) result(y)
51+
real(dp), intent(in), optional :: x
52+
real(dp), intent(in) :: default
53+
real(dp) :: y
54+
55+
if (present(x)) then
56+
y = x
57+
else
58+
y = default
59+
end if
60+
end function optval_dp
61+
62+
63+
function optval_qp(x, default) result(y)
64+
real(qp), intent(in), optional :: x
65+
real(qp), intent(in) :: default
66+
real(qp) :: y
67+
68+
if (present(x)) then
69+
y = x
70+
else
71+
y = default
72+
end if
73+
end function optval_qp
74+
75+
76+
function optval_int8(x, default) result(y)
77+
integer(int8), intent(in), optional :: x
78+
integer(int8), intent(in) :: default
79+
integer(int8) :: y
80+
81+
if (present(x)) then
82+
y = x
83+
else
84+
y = default
85+
end if
86+
end function optval_int8
87+
88+
89+
function optval_int16(x, default) result(y)
90+
integer(int16), intent(in), optional :: x
91+
integer(int16), intent(in) :: default
92+
integer(int16) :: y
93+
94+
if (present(x)) then
95+
y = x
96+
else
97+
y = default
98+
end if
99+
end function optval_int16
100+
101+
102+
function optval_int32(x, default) result(y)
103+
integer(int32), intent(in), optional :: x
104+
integer(int32), intent(in) :: default
105+
integer(int32) :: y
106+
107+
if (present(x)) then
108+
y = x
109+
else
110+
y = default
111+
end if
112+
end function optval_int32
113+
114+
115+
function optval_int64(x, default) result(y)
116+
integer(int64), intent(in), optional :: x
117+
integer(int64), intent(in) :: default
118+
integer(int64) :: y
119+
120+
if (present(x)) then
121+
y = x
122+
else
123+
y = default
124+
end if
125+
end function optval_int64
126+
127+
128+
function optval_logical(x, default) result(y)
129+
logical, intent(in), optional :: x
130+
logical, intent(in) :: default
131+
logical :: y
132+
133+
if (present(x)) then
134+
y = x
135+
else
136+
y = default
137+
end if
138+
end function optval_logical
139+
140+
141+
function optval_character(x, default) result(y)
142+
character(len=*), intent(in), optional :: x
143+
character(len=*), intent(in) :: default
144+
character(len=:), allocatable :: y
145+
146+
if (present(x)) then
147+
y = x
148+
else
149+
y = default
150+
end if
151+
end function optval_character
152+
153+
end module stdlib_experimental_optval

0 commit comments

Comments
 (0)