stdlib_string_class
moduleThe stdlib_string_class
provides an abstract base class (ABC) to create an
extendible string object to hold an arbitrary character sequence compatibile
with most Fortran intrinsic character procedures as well as compatibility
with the stdlib stdlib_string_type.
string_class
derived typeThe string_class
is defined as an abstract derived type representing a
sequence of characters. The internal representation of the character sequence
is decided by the class inheriting from the string_class
.
The module provides the abstract base class and overloaded function interfaces
for the respective intrinsic functions.
Implementations of the string class should import all overloaded function interfaces
and reexport them to ease usage of the string implementation.
A minimal implementation must at least provide a setter as assignment(=)
,
three getter functions (for the whole string, a specific index and a range)
as well as the length and trimmed length getter functions.
All other functionality is implemented by using the getter and setter functions in
the abstract base class, but implementations are encouraged to overwrite those with
procedures specific and optimal for their character sequence representation.
Experimental
!> Minimal implementation of a string based on the stdlib string abstract base class
module string_implementation
use stdlib_string_class, only : string_class, &
len, len_trim, trim, index, scan, verify, repeat, adjustr, adjustl, &
lgt, lge, llt, lle, char, ichar, iachar
implicit none
private
public :: my_string_type
public :: len, len_trim, trim, index, scan, verify, repeat, adjustr, adjustl
public :: lgt, lge, llt, lle, char, ichar, iachar
!> Definition of a string class implementation
type, extends(string_class) :: my_string_type
private
character(len=:), allocatable :: raw
contains
!> Assign a character sequence to a string object.
procedure :: assign_object_char
!> Returns the length of the character sequence represented by the string.
procedure :: get_len
!> Returns the length of the character sequence without trailing spaces
!> represented by the string.
procedure :: get_len_trim
!> Return the character sequence represented by the string.
procedure :: get_char
!> Return the character sequence represented by the string.
procedure :: get_char_pos
!> Return the character sequence represented by the string.
procedure :: get_char_range
end type my_string_type
!> Constructor for string class implementation
interface my_string_type
module procedure :: new_string
end interface my_string_type
contains
!> Constructor for new string instances from a scalar character value.
elemental function new_string(string) result(new)
character(len=*), intent(in), optional :: string
type(my_string_type) :: new
if (present(string)) then
new%raw = string
end if
end function new_string
!> Assign a character sequence to a string object.
elemental subroutine assign_object_char(lhs, rhs)
class(my_string_type), intent(inout) :: lhs
character(len=*), intent(in) :: rhs
lhs%raw = rhs
end subroutine assign_object_char
!> Returns the length of the character sequence represented by the string.
elemental function get_len(self) result(val)
class(my_string_type), intent(in) :: self
integer :: val
val = merge(len(self%raw), 0, allocated(self%raw))
end function get_len
!> Returns the length of the character sequence without trailing spaces
!> represented by the string.
elemental function get_len_trim(self) result(val)
class(my_string_type), intent(in) :: self
integer :: val
val = merge(len_trim(self%raw), 0, allocated(self%raw))
end function get_len_trim
!> Return the character sequence represented by the string.
pure function get_char(self) result(character_string)
class(my_string_type), intent(in) :: self
character(len=:), allocatable :: character_string
if (allocated(self%raw)) then
character_string = self%raw
else
character_string = ""
end if
end function get_char
!> Return the character sequence represented by the string.
elemental function get_char_pos(self, pos) result(character_string)
class(my_string_type), intent(in) :: self
integer, intent(in) :: pos
character(len=1) :: character_string
if (allocated(self%raw)) then
character_string = self%raw(pos:pos)
else
character_string = ""
end if
end function get_char_pos
!> Return the character sequence represented by the string.
pure function get_char_range(self, start, last) result(character_string)
class(my_string_type), intent(in) :: self
integer, intent(in) :: start
integer, intent(in) :: last
character(len=last-start+1) :: character_string
if (allocated(self%raw)) then
character_string = self%raw(start:last)
else
character_string = ""
end if
end function get_char_range
end module string_implementation
The ABC defines an assignment operations, =
, to create a string object
from a character scalar.
lhs = rhs
Experimental
Elemental, deferred subroutine, assignment(=)
.
The ABC defines an assignment operations, =
, to create a string class
from a string_type
instance.
lhs = rhs
Experimental
Elemental subroutine, assignment(=)
.
Returns the length of the string object.
res = len (string)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.
The result is a default integer scalar value.
Returns the length of the character sequence without trailing spaces represented by the string.
res = len_trim (string)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.
The result is a default integer scalar value.
Returns the character sequence hold by the string without trailing spaces
represented by a string_type
.
res = trim (string)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar string_type
value.
Left-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.
res = adjustl (string)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar string_type
value.
Right-adjust the character sequence represented by the string. The length of the character sequence remains unchanged.
res = adjustr (string)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar string_type
value.
Repeats the character sequence hold by the string by the number of specified copies.
res = repeat (string, ncopies)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.ncopies
: Integer of default type. This argument is intent(in)
.The result is a scalar string_type
value.
Return the character sequence represented by the string.
res = char (string)
Experimental
Pure function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a scalar character value.
Return the character at a certain position in the string.
res = char (string, pos)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.pos
: Integer of default type. This argument is intent(in)
.The result is a scalar character value.
Return a substring from the character sequence of the string.
res = char (string, start, last)
Experimental
Pure function.
string
: Instance of a string_type
. This argument is intent(in)
.start
: Integer of default type. This argument is intent(in)
.last
: Integer of default type. This argument is intent(in)
.The result is a scalar character value.
Character-to-integer conversion function.
Returns the code for the character in the first character position of the character sequence in the system's native character set.
res = ichar (string)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a default integer scalar value.
Code in ASCII collating sequence.
Returns the code for the ASCII character in the first character position of the character sequences represent by the string.
res = iachar (string)
Experimental
Elemental function.
string
: Instance of a string_type
. This argument is intent(in)
.The result is a default integer scalar value.
Position of a substring within a string.
Returns the position of the start of the leftmost or rightmost occurrence of string substring in string, counting from one. If substring is not present in string, zero is returned.
res = index (string, substring[, back])
Experimental
Elemental function.
string
: Either scalar character value, string type or string object.
This argument is intent(in)
.substring
: Either scalar character value, string type or string object.
This argument is intent(in)
.back
: Either absent or a scalar logical value. This argument is intent(in)
.The result is a default integer scalar value.
Scans a string for the presence any of the characters in a set of characters. If back is either absent or false, this function returns the position of the leftmost character of string that is in set. If back is true, the rightmost position is returned. If no character of set is found in string, the result is zero.
res = scan (string, set[, back])
Experimental
Elemental function.
string
: Either scalar character value, string type or string object.
This argument is intent(in)
.set
: Either scalar character value, string type or string object.
This argument is intent(in)
.back
: Either absent or a scalar logical value. This argument is intent(in)
.The result is a default integer scalar value.
Verifies that all the characters in string belong to the set of characters in set. If back is either absent or false, this function returns the position of the leftmost character of string that is not in set. If back is true, the rightmost position is returned. If all characters of string are found in set, the result is zero.
res = verify (string, set[, back])
Experimental
Elemental function.
string
: Either scalar character value, string type or string object.
This argument is intent(in)
.set
: Either scalar character value, string type or string object.
This argument is intent(in)
.back
: Either absent or a scalar logical value. This argument is intent(in)
.The result is a default integer scalar value.
Lexically compare the order of two character sequences being greater than.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic lgt
procedure.
res = lgt (lhs, rhs)
Experimental
Elemental function.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Lexically compare the order of two character sequences being less than.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic llt
procedure.
res = llt (lhs, rhs)
Experimental
Elemental function.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Lexically compare the order of two character sequences being greater than or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic lge
procedure.
res = lge (lhs, rhs)
Experimental
Elemental function.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Lexically compare the order of two character sequences being less than or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic lle
procedure.
res = lle (lhs, rhs)
Experimental
Elemental function.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Compare the order of two character sequences being greater.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic operator(>)
and operator(.gt.)
.
res = lhs > rhs
res = lhs .gt. rhs
Experimental
Elemental function, operator(>)
and operator(.gt.)
.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Compare the order of two character sequences being less.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic operator(<)
and operator(.lt.)
.
res = lhs < rhs
res = lhs .lt. rhs
Experimental
Elemental function, operator(<)
and operator(.lt.)
.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Compare the order of two character sequences being greater or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic operator(>=)
and operator(.ge.)
.
res = lhs >= rhs
res = lhs .ge. rhs
Experimental
Elemental function, operator(>=)
and operator(.ge.)
.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Compare the order of two character sequences being less or equal.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic operator(<=)
and operator(.le.)
.
res = lhs <= rhs
res = lhs .le. rhs
Experimental
Elemental function, operator(<=)
and operator(.le.)
.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Compare two character sequences for equality.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic operator(==)
and operator(.eq.)
.
res = lhs == rhs
res = lhs .eq. rhs
Experimental
Elemental function, operator(==)
and operator(.eq.)
.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Compare two character sequences for inequality.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic operator(/=)
and operator(.ne.)
.
res = lhs /= rhs
res = lhs .ne. rhs
Experimental
Elemental function, operator(/=)
and operator(.ne.)
.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is a default logical scalar value.
Concatenate two character sequences.
The left-hand side, the right-hand side or both character sequences can
be represented by a string object.
This defines five procedures overloading the intrinsic operator(//)
.
res = lhs // rhs
Experimental
Elemental function, operator(//)
.
lhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.rhs
: Either scalar character value, string type or string object.
This argument is intent(in)
.The result is an instance of string_type
.
Write the character sequence hold by the string to a connected unformatted unit. The character sequences is represented by an 64 bit signed integer record, holding the length of the following character record.
write(unit, iostat=iostat, iomsg=iomsg) string
Experimental
Unformatted user defined derived type output.
string
: Instance of the string type to read. This argument is intent(inout)
.unit
: Formatted unit for output. This argument is intent(in)
.iostat
: Status identifier to indicate success of output operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing output operation.
This argument is intent(inout)
.Write the character sequence hold by the string to a connected formatted unit.
write(unit, fmt, iostat=iostat, iomsg=iomsg) string
Experimental
Formatted user defined derived type output.
string
: Instance of the string object to read. This argument is intent(inout)
.unit
: Formatted unit for output. This argument is intent(in)
.iotype
: Type of formatted data transfer, has the value "LISTDIRECTED"
for fmt=*
,
"NAMELIST"
for namelist output or starts with "DT"
for derived type output.
This argument is intent(in)
.v_list
: Rank one array of default integer type containing the edit descriptors for
derived type output.
This argument is intent(in)
.iostat
: Status identifier to indicate success of output operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing output operation.
This argument is intent(inout)
.Read a character sequence from a connected unformatted unit into the string. The character sequences is represented by an 64 bit signed integer record, holding the length of the following character record.
On failure the state the read variable is undefined and implementation dependent.
read(unit, iostat=iostat, iomsg=iomsg) string
Experimental
Unformatted derived type input.
string
: Instance of the string object to read. This argument is intent(inout)
.unit
: Formatted unit for input. This argument is intent(in)
.iostat
: Status identifier to indicate success of input operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing input operation.
This argument is intent(inout)
.Read a character sequence from a connected formatted unit into the string. List-directed input will retrieve the complete record into the string.
On failure the state the read variable is undefined and implementation dependent.
read(unit, fmt, iostat=iostat, iomsg=iomsg) string
Experimental
Formatted derived type input.
string
: Instance of the string object to read. This argument is intent(inout)
.unit
: Formatted unit for input. This argument is intent(in)
.iotype
: Type of formatted data transfer, has the value "LISTDIRECTED"
for fmt=*
,
"NAMELIST"
for namelist input or starts with "DT"
for derived type input.
This argument is intent(in)
.v_list
: Rank one array of default integer type containing the edit descriptors for
derived type input.
This argument is intent(in)
.iostat
: Status identifier to indicate success of input operation.
This argument is intent(out)
.iomsg
: Buffer to return error message in case of failing input operation.
This argument is intent(inout)
.