Skip to content
Merged
Show file tree
Hide file tree
Changes from 6 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion doc/specs/index.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ This is and index/directory of the specifications (specs) for each new module/fe

## Experimental Features & Modules

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

## Missing specs

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

## Released/Stable Features & Modules
Expand Down
171 changes: 171 additions & 0 deletions doc/specs/stdlib_ascii.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,171 @@
---
title: ASCII
---

# The `stdlib_ascii` module

[TOC]

## Introduction

The `stdlib_ascii` module provides procedures for handling and manipulating
intrinsic character variables and constants.


## Constants provided by `stdlib_ascii`

@note Specification of constants is currently incomplete.


## Specification of the `stdlib_ascii` procedures

@note Specification of procedures is currently incomplete.


### `to_lower`

#### Status

Experimental

#### Description

Converts input character variable to all lowercase.

#### Syntax

`res = [[stdlib_asciii(module):to_lower(function)]] (string)`

#### Class

Elemental function.

#### Argument

`string`: shall be an intrinsic character type. It is an `intent(in)` argument.

#### Result value

The result is an intrinsic character type of the same length as `string`.

#### Example

```fortran
program demo_to_lower
use stdlib_ascii, only : to_lower
implicit none
print'(a)', to_lower("HELLo!") ! returns "hello!"
end program demo_to_lower
```

### `to_upper`

#### Status

Experimental

#### Description

Converts input character variable to all uppercase.

#### Syntax

`res = [[stdlib_ascii(module):to_upper(function)]] (string)`

#### Class

Elemental function.

#### Argument

`string`: shall be an intrinsic character type. It is an `intent(in)` argument.

#### Result value

The result is an intrinsic character type of the same length as `string`.

#### Example

```fortran
program demo_to_upper
use stdlib_ascii, only : to_upper
implicit none
print'(a)', to_upper("hello!") ! returns "HELLO!"
end program demo_to_upper
```

### `to_title`

#### Status

Experimental

#### Description

Returns a capitalized version of an input character variable.
The first alphabetical character is transformed to uppercase unless it follows a numeral.
The rest of the character sequence is transformed to lowercase.

#### Syntax

`res = [[stdlib_ascii(module):to_title(interface)]] (string)`

#### Class

Elemental function.

#### Argument

`string`: shall be an intrinsic character type. It is an `intent(in)` argument.

#### Result value

The result is an intrinsic character type of the same length as `string`.

#### Example

```fortran
program demo_to_title
use stdlib_ascii, only : to_title
implicit none
print*, to_title("hello!") ! returns "Hello!"
print*, to_title("'enquoted'") ! returns "'Enquoted'"
print*, to_title("1st") ! returns "1st"
end program demo_to_title
```

### `reverse`

#### Status

Experimental

#### Description

Reverses the order of all characters in the input character type.

#### Syntax

`res = [[stdlib_ascii(module):reverse(function)]] (string)`

#### Class

Elemental function.

#### Argument

`string`: shall be an intrinsic character type. It is an `intent(in)` argument.

#### Result value

The result is an intrinsic character type of the same length as `string`.

#### Example

```fortran
program demo_reverse
use stdlib_ascii, only : reverse
implicit none
print'(a)', reverse("Hello, World!") ! returns "!dlroW ,olleH"
end program demo_reverse
```
115 changes: 92 additions & 23 deletions src/stdlib_ascii.f90
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
!> The `stdlib_ascii` module provides procedures for handling and manipulating
!> intrinsic character variables and constants.
!>
!> The specification of this module is available [here](../page/specs/stdlib_ascii.html).
module stdlib_ascii

implicit none
Expand All @@ -12,7 +16,7 @@ module stdlib_ascii
public :: is_lower, is_upper

! Character conversion functions
public :: to_lower, to_upper
public :: to_lower, to_upper, to_title, reverse

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

character(len=26), parameter, private :: lower_case = 'abcdefghijklmnopqrstuvwxyz'
character(len=26), parameter, private :: upper_case = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'

contains

!> Checks whether `c` is an ASCII letter (A .. Z, a .. z).
Expand All @@ -79,7 +80,7 @@ pure logical function is_alphanum(c)
end function

!> Checks whether or not `c` is in the ASCII character set -
! i.e. in the range 0 .. 0x7F.
!> i.e. in the range 0 .. 0x7F.
pure logical function is_ascii(c)
character(len=1), intent(in) :: c !! The character to test.
is_ascii = iachar(c) <= int(z'7F')
Expand Down Expand Up @@ -113,8 +114,8 @@ pure logical function is_hex_digit(c)
end function

!> Checks whether or not `c` is a punctuation character. That includes
! all ASCII characters which are not control characters, letters,
! digits, or whitespace.
!> all ASCII characters which are not control characters, letters,
!> digits, or whitespace.
pure logical function is_punctuation(c)
character(len=1), intent(in) :: c !! The character to test.
integer :: ic
Expand All @@ -124,7 +125,7 @@ pure logical function is_punctuation(c)
end function

!> Checks whether or not `c` is a printable character other than the
! space character.
!> space character.
pure logical function is_graphical(c)
character(len=1), intent(in) :: c !! The character to test.
integer :: ic
Expand All @@ -135,7 +136,7 @@ pure logical function is_graphical(c)
end function

!> Checks whether or not `c` is a printable character - including the
! space character.
!> space character.
pure logical function is_printable(c)
character(len=1), intent(in) :: c !! The character to test.
integer :: ic
Expand All @@ -159,8 +160,8 @@ pure logical function is_upper(c)
end function

!> Checks whether or not `c` is a whitespace character. That includes the
! space, tab, vertical tab, form feed, carriage return, and linefeed
! characters.
!> space, tab, vertical tab, form feed, carriage return, and linefeed
!> characters.
pure logical function is_white(c)
character(len=1), intent(in) :: c !! The character to test.
integer :: ic
Expand All @@ -169,7 +170,7 @@ pure logical function is_white(c)
end function

!> Checks whether or not `c` is a blank character. That includes the
! only the space and tab characters
!> only the space and tab characters
pure logical function is_blank(c)
character(len=1), intent(in) :: c !! The character to test.
integer :: ic
Expand All @@ -178,35 +179,103 @@ pure logical function is_blank(c)
end function

!> Returns the corresponding lowercase letter, if `c` is an uppercase
! ASCII character, otherwise `c` itself.
pure function to_lower(c) result(t)
!> ASCII character, otherwise `c` itself.
pure function char_to_lower(c) result(t)
character(len=1), intent(in) :: c !! A character.
character(len=1) :: t
integer :: k

k = index( upper_case, c )
k = index( uppercase, c )

if ( k > 0 ) then
t = lower_case(k:k)
t = lowercase(k:k)
else
t = c
endif
end function
end function char_to_lower

!> Returns the corresponding uppercase letter, if `c` is a lowercase
! ASCII character, otherwise `c` itself.
pure function to_upper(c) result(t)
!> ASCII character, otherwise `c` itself.
pure function char_to_upper(c) result(t)
character(len=1), intent(in) :: c !! A character.
character(len=1) :: t
integer :: k

k = index( lower_case, c )
k = index( lowercase, c )

if ( k > 0 ) then
t = upper_case(k:k)
t = uppercase(k:k)
else
t = c
endif
end function
end function char_to_upper

!> Convert character variable to lower case
!>
!> Version: experimental
elemental function to_lower(string) result(lower_string)
character(len=*), intent(in) :: string
character(len=len(string)) :: lower_string
integer :: i

do i = 1, len(string)
lower_string(i:i) = char_to_lower(string(i:i))
end do

end function to_lower

!> Convert character variable to upper case
!>
!> Version: experimental
elemental function to_upper(string) result(upper_string)
character(len=*), intent(in) :: string
character(len=len(string)) :: upper_string
integer :: i

do i = 1, len(string)
upper_string(i:i) = char_to_upper(string(i:i))
end do

end function to_upper

!> Convert character variable to title case
!>
!> Version: experimental
elemental function to_title(string) result(title_string)
character(len=*), intent(in) :: string
character(len=len(string)) :: title_string
integer :: i, n

n = len(string)
do i = 1, len(string)
if (is_alphanum(string(i:i))) then
title_string(i:i) = char_to_upper(string(i:i))
n = i
exit
else
title_string(i:i) = string(i:i)
end if
end do

do i = n + 1, len(string)
title_string(i:i) = char_to_lower(string(i:i))
end do

end function to_title

!> Reverse the character order in the input character variable
!>
!> Version: experimental
elemental function reverse(string) result(reverse_string)
character(len=*), intent(in) :: string
character(len=len(string)) :: reverse_string
integer :: i, n

n = len(string)
do i = 1, n
reverse_string(n-i+1:n-i+1) = string(i:i)
end do

end function reverse

end module
end module stdlib_ascii
Loading