Skip to content

Commit 124e627

Browse files
committed
Deploying to stdlib-fpm from @ 82f8c8d 🚀
1 parent bf283ac commit 124e627

11 files changed

+417
-456
lines changed

src/stdlib_bitsets.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module stdlib_bitsets
1212
int16, &
1313
int32, &
1414
int64
15+
use stdlib_optval, only : optval
1516

1617
use, intrinsic :: &
1718
iso_fortran_env, only: &

src/stdlib_bitsets_64.f90

Lines changed: 13 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -935,23 +935,13 @@ module subroutine read_bitset_unit_64(self, unit, advance, status)
935935
end if
936936
end do
937937

938-
if ( present(advance) ) then
939-
read( unit, &
940-
advance=advance, &
941-
FMT='(A1)', &
942-
err=997, &
943-
end=998, &
944-
iostat=ierr, &
945-
iomsg=message ) char
946-
else
947-
read( unit, &
948-
advance='YES', &
949-
FMT='(A1)', &
950-
err=997, &
951-
end=998, &
952-
iostat=ierr, &
953-
iomsg=message ) char
954-
end if
938+
read( unit, &
939+
advance=optval(advance, 'YES'), &
940+
FMT='(A1)', &
941+
err=997, &
942+
end=998, &
943+
iostat=ierr, &
944+
iomsg=message ) char
955945
if ( char == '0' ) then
956946
call self % clear( bits-bit )
957947
else if ( char == '1' ) then
@@ -1203,21 +1193,12 @@ module subroutine write_bitset_unit_64(self, unit, advance, status)
12031193
end if
12041194

12051195

1206-
if ( present( advance ) ) then
1207-
write( unit, &
1208-
FMT='(A)', &
1209-
advance=advance, &
1210-
iostat=ierr, &
1211-
iomsg=message ) &
1212-
string
1213-
else
1214-
write( unit, &
1215-
FMT='(A)', &
1216-
advance='YES', &
1217-
iostat=ierr, &
1218-
iomsg=message ) &
1219-
string
1220-
end if
1196+
write( unit, &
1197+
FMT='(A)', &
1198+
advance=optval(advance, 'YES'), &
1199+
iostat=ierr, &
1200+
iomsg=message ) &
1201+
string
12211202
if (ierr /= 0) then
12221203
call error_handler( 'Failure on a WRITE statement for UNIT.', &
12231204
write_failure, status, module_name, procedure )

src/stdlib_bitsets_large.f90

Lines changed: 13 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1129,23 +1129,13 @@ module subroutine read_bitset_unit_large(self, unit, advance, status)
11291129
end if
11301130
end do
11311131

1132-
if ( present(advance) ) then
1133-
read( unit, &
1134-
advance=advance, &
1135-
FMT='(A1)', &
1136-
err=997, &
1137-
end=998, &
1138-
iostat=ierr, &
1139-
iomsg=message ) char
1140-
else
1141-
read( unit, &
1142-
advance='YES', &
1143-
FMT='(A1)', &
1144-
err=997, &
1145-
end=998, &
1146-
iostat=ierr, &
1147-
iomsg=message ) char
1148-
end if
1132+
read( unit, &
1133+
advance=optval(advance, 'YES'), &
1134+
FMT='(A1)', &
1135+
err=997, &
1136+
end=998, &
1137+
iostat=ierr, &
1138+
iomsg=message ) char
11491139

11501140
if ( char == '0' ) then
11511141
call self % clear( bits-bit )
@@ -1434,21 +1424,12 @@ module subroutine write_bitset_unit_large(self, unit, advance, status)
14341424
end if
14351425

14361426

1437-
if ( present( advance ) ) then
1438-
write( unit, &
1439-
FMT='(A)', &
1440-
advance=advance, &
1441-
iostat=ierr, &
1442-
iomsg=message ) &
1443-
string
1444-
else
1445-
write( unit, &
1446-
FMT='(A)', &
1447-
advance='YES', &
1448-
iostat=ierr, &
1449-
iomsg=message ) &
1450-
string
1451-
end if
1427+
write( unit, &
1428+
FMT='(A)', &
1429+
advance=optval(advance, 'YES'), &
1430+
iostat=ierr, &
1431+
iomsg=message ) &
1432+
string
14521433
if (ierr /= 0) then
14531434
call error_handler( 'Failure on a WRITE statement for UNIT.', &
14541435
write_failure, status, module_name, procedure )

src/stdlib_logger.f90

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1147,11 +1147,8 @@ subroutine log_message( self, message, module, procedure, prefix )
11471147
character(:), allocatable :: d_and_t, m_and_p, pref
11481148
character(:), allocatable :: buffer
11491149

1150-
if ( present(prefix) ) then
1151-
pref = prefix // ': '
1152-
else
1153-
pref = ''
1154-
end if
1150+
pref = optval(prefix, '')
1151+
if ( len(pref) > 0 ) pref = pref // ': '
11551152

11561153
if ( self % time_stamp ) then
11571154
d_and_t = time_stamp() // ': '

src/stdlib_sorting.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -114,6 +114,8 @@ module stdlib_sorting
114114
dp, &
115115
qp
116116

117+
use stdlib_optval, only: optval
118+
117119
use stdlib_string_type, only: string_type, assignment(=), operator(>), &
118120
operator(>=), operator(<), operator(<=)
119121

src/stdlib_sorting_ord_sort.f90

Lines changed: 9 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -61,12 +61,7 @@ module subroutine int8_ord_sort( array, work, reverse )
6161
integer(int8), intent(out), optional :: work(0:)
6262
logical, intent(in), optional :: reverse
6363

64-
logical :: reverse_
65-
66-
reverse_ = .false.
67-
if(present(reverse)) reverse_ = reverse
68-
69-
if (reverse_) then
64+
if (optval(reverse, .false.)) then
7065
call int8_decrease_ord_sort(array, work)
7166
else
7267
call int8_increase_ord_sort(array, work)
@@ -78,12 +73,7 @@ module subroutine int16_ord_sort( array, work, reverse )
7873
integer(int16), intent(out), optional :: work(0:)
7974
logical, intent(in), optional :: reverse
8075

81-
logical :: reverse_
82-
83-
reverse_ = .false.
84-
if(present(reverse)) reverse_ = reverse
85-
86-
if (reverse_) then
76+
if (optval(reverse, .false.)) then
8777
call int16_decrease_ord_sort(array, work)
8878
else
8979
call int16_increase_ord_sort(array, work)
@@ -95,12 +85,7 @@ module subroutine int32_ord_sort( array, work, reverse )
9585
integer(int32), intent(out), optional :: work(0:)
9686
logical, intent(in), optional :: reverse
9787

98-
logical :: reverse_
99-
100-
reverse_ = .false.
101-
if(present(reverse)) reverse_ = reverse
102-
103-
if (reverse_) then
88+
if (optval(reverse, .false.)) then
10489
call int32_decrease_ord_sort(array, work)
10590
else
10691
call int32_increase_ord_sort(array, work)
@@ -112,12 +97,7 @@ module subroutine int64_ord_sort( array, work, reverse )
11297
integer(int64), intent(out), optional :: work(0:)
11398
logical, intent(in), optional :: reverse
11499

115-
logical :: reverse_
116-
117-
reverse_ = .false.
118-
if(present(reverse)) reverse_ = reverse
119-
120-
if (reverse_) then
100+
if (optval(reverse, .false.)) then
121101
call int64_decrease_ord_sort(array, work)
122102
else
123103
call int64_increase_ord_sort(array, work)
@@ -129,12 +109,7 @@ module subroutine sp_ord_sort( array, work, reverse )
129109
real(sp), intent(out), optional :: work(0:)
130110
logical, intent(in), optional :: reverse
131111

132-
logical :: reverse_
133-
134-
reverse_ = .false.
135-
if(present(reverse)) reverse_ = reverse
136-
137-
if (reverse_) then
112+
if (optval(reverse, .false.)) then
138113
call sp_decrease_ord_sort(array, work)
139114
else
140115
call sp_increase_ord_sort(array, work)
@@ -146,12 +121,7 @@ module subroutine dp_ord_sort( array, work, reverse )
146121
real(dp), intent(out), optional :: work(0:)
147122
logical, intent(in), optional :: reverse
148123

149-
logical :: reverse_
150-
151-
reverse_ = .false.
152-
if(present(reverse)) reverse_ = reverse
153-
154-
if (reverse_) then
124+
if (optval(reverse, .false.)) then
155125
call dp_decrease_ord_sort(array, work)
156126
else
157127
call dp_increase_ord_sort(array, work)
@@ -163,12 +133,7 @@ module subroutine qp_ord_sort( array, work, reverse )
163133
real(qp), intent(out), optional :: work(0:)
164134
logical, intent(in), optional :: reverse
165135

166-
logical :: reverse_
167-
168-
reverse_ = .false.
169-
if(present(reverse)) reverse_ = reverse
170-
171-
if (reverse_) then
136+
if (optval(reverse, .false.)) then
172137
call qp_decrease_ord_sort(array, work)
173138
else
174139
call qp_increase_ord_sort(array, work)
@@ -180,12 +145,7 @@ module subroutine string_type_ord_sort( array, work, reverse )
180145
type(string_type), intent(out), optional :: work(0:)
181146
logical, intent(in), optional :: reverse
182147

183-
logical :: reverse_
184-
185-
reverse_ = .false.
186-
if(present(reverse)) reverse_ = reverse
187-
188-
if (reverse_) then
148+
if (optval(reverse, .false.)) then
189149
call string_type_decrease_ord_sort(array, work)
190150
else
191151
call string_type_increase_ord_sort(array, work)
@@ -197,12 +157,7 @@ module subroutine char_ord_sort( array, work, reverse )
197157
character(len=len(array)), intent(out), optional :: work(0:)
198158
logical, intent(in), optional :: reverse
199159

200-
logical :: reverse_
201-
202-
reverse_ = .false.
203-
if(present(reverse)) reverse_ = reverse
204-
205-
if (reverse_) then
160+
if (optval(reverse, .false.)) then
206161
call char_decrease_ord_sort(array, work)
207162
else
208163
call char_increase_ord_sort(array, work)

0 commit comments

Comments
 (0)