Skip to content

Commit 6720abd

Browse files
committed
Extend stdlib_ascii module for handling character variables
- extend to_lower function to work on character strings - extend to_upper function to work on character strings - implement to_title function - implement reverse function
1 parent 9117db8 commit 6720abd

File tree

4 files changed

+294
-15
lines changed

4 files changed

+294
-15
lines changed

doc/specs/index.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ This is and index/directory of the specifications (specs) for each new module/fe
1111

1212
## Experimental Features & Modules
1313

14+
- [ascii](./stdlib_ascii.html) - Procedures for handling ASCII characters
1415
- [bitsets](./stdlib_bitsets.html) - Bitset data types and procedures
1516
- [error](./stdlib_error.html) - Catching and handling errors
1617
- [IO](./stdlib_io.html) - Input/output helper & convenience
@@ -22,7 +23,6 @@ This is and index/directory of the specifications (specs) for each new module/fe
2223

2324
## Missing specs
2425

25-
- [ascii](https://github.com/fortran-lang/stdlib/blob/master/src/stdlib_ascii.f90)
2626
- [kinds](https://github.com/fortran-lang/stdlib/blob/master/src/stdlib_kinds.f90)
2727

2828
## Released/Stable Features & Modules

doc/specs/stdlib_ascii.md

Lines changed: 149 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,149 @@
1+
---
2+
title: ASCII
3+
---
4+
5+
# The `stdlib_ascii` module
6+
7+
[TOC]
8+
9+
## Introduction
10+
11+
The `stdlib_ascii` module provides procedures for handling and manipulating
12+
intrinsic character variables and constants.
13+
14+
15+
## Constants provided by `stdlib_ascii`
16+
17+
@note Specification of constants is currently incomplete.
18+
19+
20+
## Specification of the `stdlib_ascii` procedures
21+
22+
@note Specification of procedures is currently incomplete.
23+
24+
25+
### `to_lower`
26+
27+
#### Status
28+
29+
Experimental
30+
31+
#### Description
32+
33+
Converts input character variable to all lowercase.
34+
35+
#### Syntax
36+
37+
```f90
38+
res = to_lower("HELLO!")
39+
! res == "hello!"
40+
```
41+
42+
#### Class
43+
44+
Pure function.
45+
46+
#### Argument
47+
48+
`string`: shall be an intrinsic character type. It is an `intent(in)` argument.
49+
50+
#### Result value
51+
52+
The result is an intrinsic character type of the same length as `string`.
53+
54+
55+
### `to_upper`
56+
57+
#### Status
58+
59+
Experimental
60+
61+
#### Description
62+
63+
Converts input character variable to all uppercase.
64+
65+
#### Syntax
66+
67+
```
68+
res = to_upper("hello!")
69+
! res == "HELLO!"
70+
```
71+
72+
#### Class
73+
74+
Pure function.
75+
76+
#### Argument
77+
78+
`string`: shall be an intrinsic character type. It is an `intent(in)` argument.
79+
80+
#### Result value
81+
82+
The result is an intrinsic character type of the same length as `string`.
83+
84+
85+
### `to_title`
86+
87+
#### Status
88+
89+
Experimental
90+
91+
#### Description
92+
93+
Returns capitalized version of input character variable.
94+
The first alphanumeric character is capitalized.
95+
96+
#### Syntax
97+
98+
```
99+
res = to_title("hello!")
100+
! res == "Hello!"
101+
res = to_title("'enquoted'")
102+
! res == "'Enquoted'"
103+
res = to_title("1st")
104+
! res == "1st"
105+
```
106+
107+
#### Class
108+
109+
Pure function.
110+
111+
#### Argument
112+
113+
`string`: shall be an intrinsic character type. It is an `intent(in)` argument.
114+
115+
#### Result value
116+
117+
The result is an intrinsic character type of the same length as `string`.
118+
119+
120+
### `reverse`
121+
122+
#### Status
123+
124+
Experimental
125+
126+
#### Description
127+
128+
Reverses the order of all characters in the input character type.
129+
130+
#### Syntax
131+
132+
```f90
133+
res = reverse("Hello, World!")
134+
! res == "!dlroW ,olleH"
135+
res = reverse(res)
136+
! res == "Hello, World!"
137+
```
138+
139+
#### Class
140+
141+
Pure function.
142+
143+
#### Argument
144+
145+
`string`: shall be an intrinsic character type. It is an `intent(in)` argument.
146+
147+
#### Result value
148+
149+
The result is an intrinsic character type of the same length as `string`.

src/stdlib_ascii.f90

Lines changed: 70 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module stdlib_ascii
1212
public :: is_lower, is_upper
1313

1414
! Character conversion functions
15-
public :: to_lower, to_upper
15+
public :: to_lower, to_upper, to_title, reverse
1616

1717
! All control characters in the ASCII table (see www.asciitable.com).
1818
character(len=1), public, parameter :: NUL = achar(int(z'00')) !! Null
@@ -60,9 +60,6 @@ module stdlib_ascii
6060
character(len=*), public, parameter :: lowercase = letters(27:) !! a .. z
6161
character(len=*), public, parameter :: whitespace = " "//TAB//VT//CR//LF//FF !! ASCII _whitespace
6262

63-
character(len=26), parameter, private :: lower_case = 'abcdefghijklmnopqrstuvwxyz'
64-
character(len=26), parameter, private :: upper_case = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
65-
6663
contains
6764

6865
!> Checks whether `c` is an ASCII letter (A .. Z, a .. z).
@@ -179,34 +176,94 @@ pure logical function is_blank(c)
179176

180177
!> Returns the corresponding lowercase letter, if `c` is an uppercase
181178
! ASCII character, otherwise `c` itself.
182-
pure function to_lower(c) result(t)
179+
pure function char_to_lower(c) result(t)
183180
character(len=1), intent(in) :: c !! A character.
184181
character(len=1) :: t
185182
integer :: k
186183

187-
k = index( upper_case, c )
184+
k = index( uppercase, c )
188185

189186
if ( k > 0 ) then
190-
t = lower_case(k:k)
187+
t = lowercase(k:k)
191188
else
192189
t = c
193190
endif
194-
end function
191+
end function char_to_lower
195192

196193
!> Returns the corresponding uppercase letter, if `c` is a lowercase
197194
! ASCII character, otherwise `c` itself.
198-
pure function to_upper(c) result(t)
195+
pure function char_to_upper(c) result(t)
199196
character(len=1), intent(in) :: c !! A character.
200197
character(len=1) :: t
201198
integer :: k
202199

203-
k = index( lower_case, c )
200+
k = index( lowercase, c )
204201

205202
if ( k > 0 ) then
206-
t = upper_case(k:k)
203+
t = uppercase(k:k)
207204
else
208205
t = c
209206
endif
210-
end function
207+
end function char_to_upper
208+
209+
!> Convert character variable to lower case
210+
pure function to_lower(string) result(lower_string)
211+
character(len=*), intent(in) :: string
212+
character(len=len(string)) :: lower_string
213+
integer :: i
214+
215+
do i = 1, len(string)
216+
lower_string(i:i) = char_to_lower(string(i:i))
217+
end do
218+
219+
end function to_lower
220+
221+
!> Convert character variable to upper case
222+
pure function to_upper(string) result(upper_string)
223+
character(len=*), intent(in) :: string
224+
character(len=len(string)) :: upper_string
225+
integer :: i
226+
227+
do i = 1, len(string)
228+
upper_string(i:i) = char_to_upper(string(i:i))
229+
end do
230+
231+
end function to_upper
232+
233+
!> Convert character variable to title case
234+
pure function to_title(string) result(title_string)
235+
character(len=*), intent(in) :: string
236+
character(len=len(string)) :: title_string
237+
integer :: i, n
238+
239+
n = len(string)
240+
do i = 1, len(string)
241+
if (is_alphanum(string(i:i))) then
242+
title_string(i:i) = char_to_upper(string(i:i))
243+
n = i
244+
exit
245+
else
246+
title_string(i:i) = string(i:i)
247+
end if
248+
end do
249+
250+
do i = n + 1, len(string)
251+
title_string(i:i) = char_to_lower(string(i:i))
252+
end do
253+
254+
end function to_title
255+
256+
!> Reverse the character order in the input character variable
257+
pure function reverse(string) result(reverse_string)
258+
character(len=*), intent(in) :: string
259+
character(len=len(string)) :: reverse_string
260+
integer :: i, n
261+
262+
n = len(string)
263+
do i = 1, n
264+
reverse_string(n-i+1:n-i+1) = string(i:i)
265+
end do
266+
267+
end function reverse
211268

212-
end module
269+
end module stdlib_ascii

src/tests/ascii/test_ascii.f90

Lines changed: 74 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ program test_ascii
66
whitespace, letters, is_alphanum, is_alpha, is_lower, is_upper, &
77
is_digit, is_octal_digit, is_hex_digit, is_white, is_blank, &
88
is_control, is_punctuation, is_graphical, is_printable, is_ascii, &
9-
to_lower, to_upper, LF, TAB, NUL, DEL
9+
to_lower, to_upper, to_title, reverse, LF, TAB, NUL, DEL
1010

1111
implicit none
1212

@@ -68,6 +68,11 @@ program test_ascii
6868

6969
! call test_ascii_table
7070

71+
call test_to_upper_string
72+
call test_to_lower_string
73+
call test_to_title_string
74+
call test_reverse_string
75+
7176
contains
7277

7378
subroutine test_is_alphanum_short
@@ -540,4 +545,72 @@ pure logical function validation_func_interface(c)
540545
write(*,'(5X,12(I4))') (count(table(:,i)),i=1,12)
541546
end subroutine test_ascii_table
542547

548+
subroutine test_to_lower_string
549+
character(len=:), allocatable :: dlc
550+
character(len=32), parameter :: input = "UPPERCASE"
551+
552+
dlc = to_lower("UPPERCASE")
553+
call check(dlc == "uppercase")
554+
555+
dlc = to_lower(input)
556+
call check(len(dlc) == 32)
557+
call check(len_trim(dlc) == 9)
558+
call check(trim(dlc) == "uppercase")
559+
560+
dlc = to_lower("0123456789ABCDE")
561+
call check(dlc == "0123456789abcde")
562+
end subroutine test_to_lower_string
563+
564+
subroutine test_to_upper_string
565+
character(len=:), allocatable :: dlc
566+
character(len=32), parameter :: input = "lowercase"
567+
568+
dlc = to_upper("lowercase")
569+
call check(dlc == "LOWERCASE")
570+
571+
dlc = to_upper(input)
572+
call check(len(dlc) == 32)
573+
call check(len_trim(dlc) == 9)
574+
call check(trim(dlc) == "LOWERCASE")
575+
576+
dlc = to_upper("0123456789abcde")
577+
call check(dlc == "0123456789ABCDE")
578+
end subroutine test_to_upper_string
579+
580+
subroutine test_to_title_string
581+
character(len=:), allocatable :: dlc
582+
character(len=32), parameter :: input = "tiTLe"
583+
584+
dlc = to_title("tiTLe")
585+
call check(dlc == "Title")
586+
587+
dlc = to_title(input)
588+
call check(len(dlc) == 32)
589+
call check(len_trim(dlc) == 5)
590+
call check(trim(dlc) == "Title")
591+
592+
dlc = to_title(" s P a C e D !")
593+
call check(dlc == " S p a c e d !")
594+
595+
dlc = to_title("1st, 2nd, 3rd")
596+
call check(dlc == "1st, 2nd, 3rd")
597+
598+
dlc = to_title("""quOTed""")
599+
call check(dlc == """Quoted""")
600+
end subroutine test_to_title_string
601+
602+
subroutine test_reverse_string
603+
character(len=:), allocatable :: dlc
604+
character(len=32), parameter :: input = "reversed"
605+
606+
dlc = reverse("reversed")
607+
call check(dlc == "desrever")
608+
609+
dlc = reverse(input)
610+
call check(len(dlc) == 32)
611+
call check(len_trim(dlc) == 32)
612+
call check(trim(dlc) == " desrever")
613+
call check(trim(adjustl(dlc)) == "desrever")
614+
end subroutine test_reverse_string
615+
543616
end program test_ascii

0 commit comments

Comments
 (0)