Skip to content

Commit 5a75fa3

Browse files
committed
add swap for stdlib string_type
1 parent 0daa4d8 commit 5a75fa3

File tree

4 files changed

+41
-2
lines changed

4 files changed

+41
-2
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 function.
8282

8383
#### Argument(s)
8484

85-
`lhs`: scalar or array of any of the intrinsic types `integer`, `real`, `complex`, `logical`, `character` type. This argument is `intent(inout)`.
86-
`rhs`: scalar or array of any of the intrinsic types `integer`, `real`, `complex`, `logical`, `character` type. This argument is `intent(inout)`.
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)`.
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
@@ -30,4 +30,12 @@ program example_math_swap
3030
call swap(x,y)
3131
end block
3232

33+
block
34+
use stdlib_string_type
35+
type(string_type) :: x, y
36+
x = 'abcde'
37+
y = 'fghij'
38+
call swap(x,y)
39+
end block
40+
3341
end program example_math_swap

src/stdlib_math.fypp

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@ module stdlib_math
5151
#:endfor
5252
module procedure :: swap_bool
5353
module procedure :: swap_str
54+
module procedure :: swap_stt
5455
end interface
5556

5657
!> Returns the greatest common divisor of two integers
@@ -550,5 +551,12 @@ contains
550551
character(len=max(len(lhs),len(rhs))) :: temp
551552
temp = lhs ; lhs = rhs ; rhs = temp
552553
end subroutine
554+
555+
elemental subroutine swap_stt(lhs,rhs)
556+
use stdlib_string_type
557+
type(string_type), intent(inout) :: lhs, rhs
558+
type(string_type) :: temp
559+
temp = lhs ; lhs = rhs ; rhs = temp
560+
end subroutine
553561

554562
end module stdlib_math

test/math/test_stdlib_math.fypp

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ contains
4646
, new_unittest("swap_c${k1}$", test_swap_c${k1}$) &
4747
#:endfor
4848
, new_unittest("swap_str", test_swap_str) &
49+
, new_unittest("swap_stt", test_swap_stt) &
4950

5051
!> Tests for arg/argd/argpi
5152
#:for k1 in CMPLX_KINDS
@@ -322,6 +323,28 @@ contains
322323
if (allocated(error)) return
323324
end subroutine test_swap_str
324325

326+
subroutine test_swap_stt(error)
327+
use stdlib_string_type
328+
type(error_type), allocatable, intent(out) :: error
329+
type(string_type) :: x(2), y(2)
330+
331+
x = ['abcde','fghij']
332+
y = ['fghij','abcde']
333+
334+
call swap(x,y)
335+
336+
call check(error, all( x == ['fghij','abcde'] ) )
337+
if (allocated(error)) return
338+
call check(error, all( y == ['abcde','fghij'] ) )
339+
if (allocated(error)) return
340+
341+
! check self swap
342+
call swap(x,x)
343+
344+
call check(error, all( x == ['fghij','abcde'] ) )
345+
if (allocated(error)) return
346+
end subroutine test_swap_stt
347+
325348
#:for k1 in CMPLX_KINDS
326349
subroutine test_arg_${k1}$(error)
327350
type(error_type), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)