Skip to content

Commit 4d14f5c

Browse files
committed
Allow constructing string_type instances from integer/logical scalars
1 parent afe299c commit 4d14f5c

File tree

5 files changed

+160
-8
lines changed

5 files changed

+160
-8
lines changed

doc/specs/stdlib_string_type.md

Lines changed: 85 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -123,6 +123,90 @@ end program demo
123123
```
124124

125125

126+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
127+
### Constructor from integer scalar
128+
129+
#### Description
130+
131+
The module defines a constructor to create a string type from an integer scalar.
132+
133+
#### Syntax
134+
135+
`res = [[stdlib_string_type(module):string_type(interface)]] (string)`
136+
137+
#### Status
138+
139+
Experimental
140+
141+
#### Class
142+
143+
Elemental function.
144+
145+
#### Argument
146+
147+
`val`: shall be a scalar integer value. It is an `intent(in)` argument.
148+
149+
#### Result value
150+
151+
The result is an instance of `string_type`.
152+
153+
#### Example
154+
155+
```fortran
156+
program demo
157+
use stdlib_string_type
158+
implicit none
159+
type(string_type) :: string
160+
string = string_type(42)
161+
! len(string) == 2
162+
string = string_type(-289)
163+
! len(string) == 4
164+
end program demo
165+
```
166+
167+
168+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
169+
### Constructor from logical scalar
170+
171+
#### Description
172+
173+
The module defines a constructor to create a string type from a logical scalar.
174+
175+
#### Syntax
176+
177+
`res = [[stdlib_string_type(module):string_type(interface)]] (string)`
178+
179+
#### Status
180+
181+
Experimental
182+
183+
#### Class
184+
185+
Elemental function.
186+
187+
#### Argument
188+
189+
`val`: shall be a scalar logical value. It is an `intent(in)` argument.
190+
191+
#### Result value
192+
193+
The result is an instance of `string_type`.
194+
195+
#### Example
196+
197+
```fortran
198+
program demo
199+
use stdlib_string_type
200+
implicit none
201+
type(string_type) :: string
202+
string = string_type(.true.)
203+
! len(string) == 1
204+
string = string_type(.false.)
205+
! len(string) == 1
206+
end program demo
207+
```
208+
209+
126210
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
127211
### Assignment of character scalar
128212

@@ -143,7 +227,7 @@ Experimental
143227

144228
#### Class
145229

146-
Elemntal subroutine, `assignment(=)`.
230+
Elemental subroutine, `assignment(=)`.
147231

148232
#### Example
149233

src/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ set(fppFiles
2323
stdlib_quadrature_trapz.fypp
2424
stdlib_quadrature_simps.fypp
2525
stdlib_stats_distribution_PRNG.fypp
26+
stdlib_string_type.fypp
2627
)
2728

2829

@@ -41,7 +42,6 @@ set(SRC
4142
stdlib_error.f90
4243
stdlib_kinds.f90
4344
stdlib_logger.f90
44-
stdlib_string_type.f90
4545
stdlib_system.F90
4646
${outFiles}
4747
)

src/Makefile.manual

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -19,13 +19,13 @@ SRCFYPP =\
1919
stdlib_stats_moment_mask.fypp \
2020
stdlib_stats_moment_scalar.fypp \
2121
stdlib_stats_var.fypp \
22-
stdlib_stats_distribution_PRNG.fypp
22+
stdlib_stats_distribution_PRNG.fypp \
23+
stdlib_string_type.fypp
2324

2425
SRC = f18estop.f90 \
2526
stdlib_error.f90 \
2627
stdlib_kinds.f90 \
2728
stdlib_logger.f90 \
28-
stdlib_string_type.f90 \
2929
$(SRCGEN)
3030

3131
LIB = libstdlib.a
@@ -109,4 +109,4 @@ stdlib_stats_var.o: \
109109
stdlib_stats_distribution_PRNG.o: \
110110
stdlib_kinds.o \
111111
stdlib_error.o
112-
stdlib_string_type.o: stdlib_ascii.o
112+
stdlib_string_type.o: stdlib_ascii.o stdlib_kinds.o

src/stdlib_string_type.f90 renamed to src/stdlib_string_type.fypp

Lines changed: 25 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
! SPDX-Identifier: MIT
2+
#:include "common.fypp"
23

34
!> Implementation of a string type to hold an arbitrary sequence of characters.
45
!>
@@ -13,8 +14,8 @@
1314
!> The specification of this module is available [here](../page/specs/stdlib_string_type.html).
1415
module stdlib_string_type
1516
use stdlib_ascii, only: to_lower_ => to_lower, to_upper_ => to_upper, &
16-
to_title_ => to_title, reverse_ => reverse
17-
17+
& to_title_ => to_title, reverse_ => reverse, to_char
18+
use stdlib_kinds, only : int8, int16, int32, int64
1819
implicit none
1920
private
2021

@@ -44,6 +45,10 @@ module stdlib_string_type
4445
!> Constructor for new string instances
4546
interface string_type
4647
module procedure :: new_string
48+
#:for kind in INT_KINDS
49+
module procedure :: new_string_from_integer_${kind}$
50+
module procedure :: new_string_from_logical_${kind}$
51+
#:endfor
4752
end interface string_type
4853

4954

@@ -351,6 +356,24 @@ elemental function new_string(string) result(new)
351356
end if
352357
end function new_string
353358

359+
#:for kind in INT_KINDS
360+
!> Constructor for new string instances from an integer of kind ${kind}$.
361+
elemental function new_string_from_integer_${kind}$(val) result(new)
362+
integer(${kind}$), intent(in) :: val
363+
type(string_type) :: new
364+
new%raw = to_char(val)
365+
end function new_string_from_integer_${kind}$
366+
#:endfor
367+
368+
#:for kind in INT_KINDS
369+
!> Constructor for new string instances from a logical of kind ${kind}$.
370+
elemental function new_string_from_logical_${kind}$(val) result(new)
371+
logical(${kind}$), intent(in) :: val
372+
type(string_type) :: new
373+
new%raw = to_char(val)
374+
end function new_string_from_logical_${kind}$
375+
#:endfor
376+
354377

355378
!> Assign a character sequence to a string.
356379
elemental subroutine assign_string_char(lhs, rhs)

src/tests/string/test_string_assignment.f90

Lines changed: 46 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
! SPDX-Identifier: MIT
22
module test_string_assignment
33
use stdlib_error, only : check
4-
use stdlib_string_type, only : string_type, assignment(=), len
4+
use stdlib_kinds, only : int8, int16, int32, int64
5+
use stdlib_string_type, only : string_type, assignment(=), operator(==), len
56
implicit none
67

78
contains
@@ -15,13 +16,57 @@ subroutine test_assignment
1516
call check(len(string) == 8)
1617
end subroutine test_assignment
1718

19+
subroutine test_char_value
20+
character(len=128) :: flc
21+
22+
write(flc, '(g0)') -1026191
23+
call check(string_type(-1026191) == trim(flc))
24+
25+
write(flc, '(g0)') 124787
26+
call check(string_type(124787) == trim(flc))
27+
28+
write(flc, '(g0)') -2_int8
29+
call check(string_type(-2_int8) == trim(flc))
30+
31+
write(flc, '(g0)') 5_int8
32+
call check(string_type(5_int8) == trim(flc))
33+
34+
write(flc, '(g0)') -72_int16
35+
call check(string_type(-72_int16) == trim(flc))
36+
37+
write(flc, '(g0)') -8924889_int32
38+
call check(string_type(-8924889_int32) == trim(flc))
39+
40+
write(flc, '(g0)') 2378405_int32
41+
call check(string_type(2378405_int32) == trim(flc))
42+
43+
write(flc, '(g0)') 921092378411_int64
44+
call check(string_type(921092378411_int64) == trim(flc))
45+
46+
write(flc, '(g0)') -1272835761_int64
47+
call check(string_type(-1272835761_int64) == trim(flc))
48+
49+
write(flc, '(g0)') .true.
50+
call check(string_type(.true.) == trim(flc))
51+
52+
write(flc, '(g0)') .false.
53+
call check(string_type(.false.) == trim(flc))
54+
55+
write(flc, '(g0)') .false._int8
56+
call check(string_type(.false._int8) == trim(flc))
57+
58+
write(flc, '(g0)') .true._int64
59+
call check(string_type(.true._int64) == trim(flc))
60+
end subroutine test_char_value
61+
1862
end module test_string_assignment
1963

2064
program tester
2165
use test_string_assignment
2266
implicit none
2367

2468
call test_assignment
69+
call test_char_value
2570

2671
end program tester
2772

0 commit comments

Comments
 (0)