Skip to content

Commit 1993d62

Browse files
committed
add bitset support
1 parent 6a30b2f commit 1993d62

File tree

4 files changed

+68
-4
lines changed

4 files changed

+68
-4
lines changed

doc/specs/stdlib_math.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -82,8 +82,8 @@ Elemental subroutine.
8282

8383
#### Argument(s)
8484

85-
`lhs`: scalar or array of any of the intrinsic types `integer`, `real`, `complex`, `logical`, `character`, `string_type` type. This argument is `intent(inout)`.
86-
`rhs`: scalar or array of any of the intrinsic types `integer`, `real`, `complex`, `logical`, `character`, `string_type` type. This argument is `intent(inout)`.
85+
`lhs`: scalar or array of any of the intrinsic types `integer`, `real`, `complex`, `logical`, `character`, `string_type`, `bitset` type. This argument is `intent(inout)`.
86+
`rhs`: scalar or array of any of the intrinsic types `integer`, `real`, `complex`, `logical`, `character`, `string_type`, `bitset` type. This argument is `intent(inout)`.
8787

8888
Note: All arguments must have same `type` and same `kind`.
8989

example/math/example_math_swap.f90

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,4 +38,12 @@ program example_math_swap
3838
call swap(x,y)
3939
end block
4040

41+
block
42+
use stdlib_bitsets
43+
type(bitset_64) :: x, y
44+
call x%from_string('0000')
45+
call y%from_string('1111')
46+
call swap(x,y)
47+
end block
48+
4149
end program example_math_swap

src/stdlib_math.fypp

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
#:include "common.fypp"
22
#:set IR_KINDS_TYPES = INT_KINDS_TYPES + REAL_KINDS_TYPES
33
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
4-
4+
#:set BITSET_KINDS_TYPES = list(zip(BITSET_KINDS, BITSET_TYPES))
55
module stdlib_math
66
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
77
use stdlib_optval, only: optval
@@ -47,7 +47,7 @@ module stdlib_math
4747
!>
4848
!> Version: experimental
4949
interface swap
50-
#:for k1, t1 in INT_KINDS_TYPES + REAL_KINDS_TYPES
50+
#:for k1, t1 in INT_KINDS_TYPES + REAL_KINDS_TYPES + BITSET_KINDS_TYPES
5151
module procedure :: swap_${k1}$
5252
#:endfor
5353
#:for k1, t1 in CMPLX_KINDS_TYPES
@@ -562,5 +562,15 @@ contains
562562
type(string_type) :: temp
563563
temp = lhs ; lhs = rhs ; rhs = temp
564564
end subroutine
565+
566+
#:for k1, t1 in BITSET_KINDS_TYPES
567+
elemental subroutine swap_${k1}$(lhs,rhs)
568+
use stdlib_bitsets
569+
${t1}$, intent(inout) :: lhs, rhs
570+
${t1}$ :: temp
571+
temp = lhs ; lhs = rhs ; rhs = temp
572+
end subroutine
573+
574+
#:endfor
565575

566576
end module stdlib_math

test/math/test_stdlib_math.fypp

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -345,6 +345,52 @@ contains
345345
if (allocated(error)) return
346346
end subroutine test_swap_stt
347347

348+
subroutine test_swap_bitset_64(error)
349+
use stdlib_bitsets
350+
type(error_type), allocatable, intent(out) :: error
351+
type(bitset_64) :: x, y, u, v
352+
353+
x = [.true.,.false.,.true.,.false.]
354+
u = x
355+
y = [.false.,.true.,.false.,.true.]
356+
v = y
357+
call swap(x,y)
358+
359+
call check(error, x == v )
360+
if (allocated(error)) return
361+
call check(error, y == u )
362+
if (allocated(error)) return
363+
364+
! check self swap
365+
call swap(x,x)
366+
367+
call check(error, x == v )
368+
if (allocated(error)) return
369+
end subroutine test_swap_bitset_64
370+
371+
subroutine test_swap_bitset_large(error)
372+
use stdlib_bitsets
373+
type(error_type), allocatable, intent(out) :: error
374+
type(bitset_large) :: x, y, u, v
375+
376+
x = [.true.,.false.,.true.,.false.]
377+
u = x
378+
y = [.false.,.true.,.false.,.true.]
379+
v = y
380+
call swap(x,y)
381+
382+
call check(error, x == v )
383+
if (allocated(error)) return
384+
call check(error, y == u )
385+
if (allocated(error)) return
386+
387+
! check self swap
388+
call swap(x,x)
389+
390+
call check(error, x == v )
391+
if (allocated(error)) return
392+
end subroutine test_swap_bitset_large
393+
348394
#:for k1 in CMPLX_KINDS
349395
subroutine test_arg_${k1}$(error)
350396
type(error_type), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)