forked from fortran-lang/stdlib
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathtest_optval.f90
151 lines (108 loc) · 3.46 KB
/
test_optval.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
program test_optval
use, intrinsic :: iso_fortran_env, only: &
sp => real32, dp => real64, qp => real128, &
int8, int16, int32, int64
use stdlib_experimental_error, only: assert
use stdlib_experimental_optval, only: optval
implicit none
call test_optval_sp
call test_optval_dp
call test_optval_qp
call test_optval_int8
call test_optval_int16
call test_optval_int32
call test_optval_int64
call test_optval_logical
call test_optval_character
contains
subroutine test_optval_sp
print *, "test_optval_sp"
call assert(foo_sp(1.0_sp) == 1.0_sp)
call assert(foo_sp() == 2.0_sp)
end subroutine test_optval_sp
function foo_sp(x) result(z)
real(sp), intent(in), optional :: x
real(sp) :: z
z = optval(x, 2.0_sp)
endfunction foo_sp
subroutine test_optval_dp
print *, "test_optval_dp"
call assert(foo_dp(1.0_dp) == 1.0_dp)
call assert(foo_dp() == 2.0_dp)
end subroutine test_optval_dp
function foo_dp(x) result(z)
real(dp), intent(in), optional :: x
real(dp) :: z
z = optval(x, 2.0_dp)
endfunction foo_dp
subroutine test_optval_qp
print *, "test_optval_qp"
call assert(foo_qp(1.0_qp) == 1.0_qp)
call assert(foo_qp() == 2.0_qp)
end subroutine test_optval_qp
function foo_qp(x) result(z)
real(qp), intent(in), optional :: x
real(qp) :: z
z = optval(x, 2.0_qp)
endfunction foo_qp
subroutine test_optval_int8
print *, "test_optval_int8"
call assert(foo_int8(1_int8) == 1_int8)
call assert(foo_int8() == 2_int8)
end subroutine test_optval_int8
function foo_int8(x) result(z)
integer(int8), intent(in), optional :: x
integer(int8) :: z
z = optval(x, 2_int8)
endfunction foo_int8
subroutine test_optval_int16
print *, "test_optval_int16"
call assert(foo_int16(1_int16) == 1_int16)
call assert(foo_int16() == 2_int16)
end subroutine test_optval_int16
function foo_int16(x) result(z)
integer(int16), intent(in), optional :: x
integer(int16) :: z
z = optval(x, 2_int16)
endfunction foo_int16
subroutine test_optval_int32
print *, "test_optval_int32"
call assert(foo_int32(1_int32) == 1_int32)
call assert(foo_int32() == 2_int32)
end subroutine test_optval_int32
function foo_int32(x) result(z)
integer(int32), intent(in), optional :: x
integer(int32) :: z
z = optval(x, 2_int32)
endfunction foo_int32
subroutine test_optval_int64
print *, "test_optval_int64"
call assert(foo_int64(1_int64) == 1_int64)
call assert(foo_int64() == 2_int64)
end subroutine test_optval_int64
function foo_int64(x) result(z)
integer(int64), intent(in), optional :: x
integer(int64) :: z
z = optval(x, 2_int64)
endfunction foo_int64
subroutine test_optval_logical
print *, "test_optval_logical"
call assert(foo_logical(.true.))
call assert(.not.foo_logical())
end subroutine test_optval_logical
function foo_logical(x) result(z)
logical, intent(in), optional :: x
logical :: z
z = optval(x, .false.)
endfunction foo_logical
subroutine test_optval_character
print *, "test_optval_character"
call assert(foo_character("x") == "x")
call assert(foo_character() == "y")
end subroutine test_optval_character
function foo_character(x) result(z)
character(len=*), intent(in), optional :: x
character(len=:), allocatable :: z
z = optval(x, "y")
endfunction foo_character
end program test_optval