Skip to content

Commit c616095

Browse files
committed
Merge branch 'master' of https://github.com/jalvesz/stdlib
2 parents b8dd3b4 + a2aad14 commit c616095

File tree

7 files changed

+47
-26
lines changed

7 files changed

+47
-26
lines changed

.github/workflows/CI.yml

+1-1
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ jobs:
2020
fail-fast: false
2121
matrix:
2222
os: [ubuntu-latest, macos-latest]
23-
gcc_v: [10, 11, 12] # Version of GFortran we want to use.
23+
gcc_v: [10, 11, 12, 13] # Version of GFortran we want to use.
2424
build: [cmake]
2525
include:
2626
- os: ubuntu-latest

README.md

+2-2
Original file line numberDiff line numberDiff line change
@@ -87,8 +87,8 @@ The following combinations are tested on the default branch of stdlib:
8787

8888
Name | Version | Platform | Architecture
8989
--- | --- | --- | ---
90-
GCC Fortran | 10, 11, 12 | Ubuntu 22.04.2 LTS | x86_64
91-
GCC Fortran | 10, 11, 12 | macOS 12.6.3 (21G419) | x86_64
90+
GCC Fortran | 10, 11, 12, 13 | Ubuntu 22.04.2 LTS | x86_64
91+
GCC Fortran | 10, 11, 12, 13 | macOS 12.6.3 (21G419) | x86_64
9292
GCC Fortran (MSYS) | 10 | Windows Server 2022 (10.0.20348 Build 1547) | x86_64
9393
GCC Fortran (MinGW) | 10 | Windows Server 2022 (10.0.20348 Build 1547) | x86_64, i686
9494
Intel oneAPI classic | 2021.1 | Ubuntu 22.04.2 LTS | x86_64

doc/specs/stdlib_string_type.md

+3-1
Original file line numberDiff line numberDiff line change
@@ -1523,6 +1523,7 @@ Experimental
15231523
Moves the allocation from `from` to `to`, consequently deallocating `from` in this process.
15241524
If `from` is not allocated before execution, `to` gets deallocated by the process.
15251525
An unallocated `string_type` instance is equivalent to an empty string.
1526+
If `from` and `to` are the same variable, then `from` remains unchanged.
15261527

15271528
#### Syntax
15281529

@@ -1537,7 +1538,8 @@ Pure subroutine (Elemental subroutine, only when both `from` and `to` are `type(
15371538
- `from`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
15381539
This argument is `intent(inout)`.
15391540
- `to`: Character scalar or [[stdlib_string_type(module):string_type(type)]].
1540-
This argument is `intent(out)`.
1541+
This argument is `intent(inout)` when both `from` and `to` are `type(string_type)`,
1542+
otherwise `intent(out)`.
15411543

15421544
#### Example
15431545

src/stdlib_specialfunctions_gamma.fypp

+4-4
Original file line numberDiff line numberDiff line change
@@ -298,14 +298,14 @@ contains
298298

299299
end if
300300

301-
if(z % re > zero_k1) then
301+
if(z % re < zero_k1) then
302302

303-
y = z - one
303+
x = cmplx(abs(z % re), - z % im, kind = ${k1}$)
304+
y = x - one
304305

305306
else
306307

307-
x = cmplx(abs(z % re), - z % im, kind = ${k1}$)
308-
y = x - one
308+
y = z - one
309309

310310
end if
311311

src/stdlib_string_type.fypp

+4-2
Original file line numberDiff line numberDiff line change
@@ -680,9 +680,11 @@ contains
680680
!> No output
681681
elemental subroutine move_string_string(from, to)
682682
type(string_type), intent(inout) :: from
683-
type(string_type), intent(out) :: to
683+
type(string_type), intent(inout) :: to
684+
character(:), allocatable :: tmp
684685

685-
call move_alloc(from%raw, to%raw)
686+
call move_alloc(from%raw, tmp)
687+
call move_alloc(tmp, to%raw)
686688

687689
end subroutine move_string_string
688690

test/specialfunctions/test_specialfunctions_gamma.fypp

+18-14
Original file line numberDiff line numberDiff line change
@@ -96,21 +96,21 @@ contains
9696
4.78749174, 3.63739376e2]
9797

9898
#:elif k1 == "int16"
99-
99+
100100
${t1}$, parameter :: x(n) = [0_${k1}$, 1_${k1}$, 2_${k1}$, 4_${k1}$, &
101101
7_${k1}$, 500_${k1}$]
102102
real(sp), parameter :: ans(n) = [0.0, 0.0, 0.693147180, 3.17805383, &
103103
8.52516136, 2.61133046e3]
104104

105105
#:elif k1 == "int32"
106-
106+
107107
${t1}$, parameter :: x(n) = [0_${k1}$, 1_${k1}$, 2_${k1}$, 4_${k1}$, &
108108
12_${k1}$, 7000_${k1}$]
109109
real(sp), parameter :: ans(n) = [0.0, 0.0, 0.693147180, 3.17805383, &
110110
1.99872145e1, 5.49810038e4]
111111

112112
#:elif k1 == "int64"
113-
113+
114114
${t1}$, parameter :: x(n) = [0_${k1}$, 1_${k1}$, 2_${k1}$, 4_${k1}$, &
115115
20_${k1}$, 90000_${k1}$]
116116
real(sp), parameter :: ans(n) = [0.0, 0.0, 0.693147180, 3.17805383, &
@@ -134,42 +134,46 @@ contains
134134

135135
subroutine test_gamma_${t1[0]}$${k1}$(error)
136136
type(error_type), allocatable, intent(out) :: error
137-
integer, parameter :: n = 4
137+
integer, parameter :: n = 5
138138
integer :: i
139139

140140
#:if k1 == "int8"
141141

142-
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 6_${k1}$]
143-
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, 120_${k1}$]
142+
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 5_${k1}$, 6_${k1}$]
143+
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, 24_${k1}$, 120_${k1}$]
144144

145145
#:elif k1 == "int16"
146146

147-
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 8_${k1}$]
148-
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, 5040_${k1}$]
147+
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 5_${k1}$, 8_${k1}$]
148+
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, 24_${k1}$, 5040_${k1}$]
149149

150150
#:elif k1 == "int32"
151151

152-
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 13_${k1}$]
153-
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, &
152+
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 8_${k1}$, 13_${k1}$]
153+
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, 5040_${k1}$, &
154154
479001600_${k1}$]
155155

156156
#:elif k1 == "int64"
157157

158-
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 21_${k1}$]
159-
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, &
158+
${t1}$, parameter :: x(n) = [1_${k1}$, 2_${k1}$, 4_${k1}$, 13_${k1}$, 21_${k1}$]
159+
${t1}$, parameter :: ans(n) = [1_${k1}$, 1_${k1}$, 6_${k1}$, 479001600_${k1}$, &
160160
2432902008176640000_${k1}$]
161161
#:elif t1[0] == "c"
162162

163163
${t1}$, parameter :: x(n) = [(0.25_${k1}$, 0.25_${k1}$), &
164164
(0.5_${k1}$, -0.5_${k1}$), &
165165
(1.0_${k1}$, 1.0_${k1}$), &
166-
(-1.254e1_${k1}$, -9.87_${k1}$)]
166+
(-1.254e1_${k1}$, -9.87_${k1}$), &
167+
(0.0_${k1}$, 1.0_${k1}$) &
168+
]
167169

168170
${t1}$, parameter :: ans(n) = &
169171
[(1.6511332803889208_${k1}$, -1.8378758749947890_${k1}$), &
170172
(0.81816399954174739_${k1}$, 0.76331382871398262_${k1}$),&
171173
(0.49801566811835604_${k1}$, -0.15494982830181069_${k1}$),&
172-
(-2.18767396709283064e-21_${k1}$, 2.77577940846953455e-21_${k1}$)]
174+
(-2.18767396709283064e-21_${k1}$, 2.77577940846953455e-21_${k1}$),&
175+
(-0.15494982830181067_${k1}$, -0.49801566811835607_${k1}$) &
176+
]
173177
#:endif
174178

175179

test/string/test_string_intrinsic.f90

+15-2
Original file line numberDiff line numberDiff line change
@@ -667,6 +667,7 @@ subroutine test_move(error)
667667
!> Error handling
668668
type(error_type), allocatable, intent(out) :: error
669669
type(string_type) :: from_string, to_string
670+
type(string_type) :: from_string_not
670671
type(string_type) :: from_strings(2), to_strings(2)
671672
character(len=:), allocatable :: from_char, to_char
672673

@@ -706,20 +707,32 @@ subroutine test_move(error)
706707
call check(error, .not. allocated(from_char) .and. from_string == "new char", "move: test_case 6")
707708
if (allocated(error)) return
708709

709-
! character (unallocated) --> string_type (allocated)
710+
! character (not allocated) --> string_type (allocated)
710711
call move(from_char, from_string)
711712
call check(error, from_string == "", "move: test_case 7")
712713
if (allocated(error)) return
713714

714715
from_string = "moving to self"
715716
! string_type (allocated) --> string_type (allocated)
716717
call move(from_string, from_string)
717-
call check(error, from_string == "", "move: test_case 8")
718+
call check(error, from_string == "moving to self", "move: test_case 8")
718719
if (allocated(error)) return
719720

720721
! elemental: string_type (allocated) --> string_type (not allocated)
721722
call move(from_strings, to_strings)
722723
call check(error, all(from_strings(:) == "") .and. all(to_strings(:) == "Move This String"), "move: test_case 9")
724+
725+
! string_type (not allocated) --> string_type (not allocated)
726+
call move(from_string_not, to_string)
727+
call check(error, from_string_not == "" .and. to_string == "", "move: test_case 10")
728+
if (allocated(error)) return
729+
730+
! string_type (not allocated) --> string_type (not allocated)
731+
to_string = "to be deallocated"
732+
call move(from_string_not, to_string)
733+
call check(error, from_string_not == "" .and. to_string == "", "move: test_case 11")
734+
if (allocated(error)) return
735+
723736
end subroutine test_move
724737

725738
end module test_string_intrinsic

0 commit comments

Comments
 (0)