M_strings(3f) - [M_strings::INTRO] Fortran string module
Description
Synopsis
See Also
Examples
Author
License
The M_strings(3fm) module is a collection of Fortran procedures that supplement the built-in intrinsic string routines. Routines for parsing, tokenizing, changing case, substituting new strings for substrings, locating strings with simple wildcard expressions, removing tabs and line terminators and other string manipulations are included.M_strings__oop(3fm) is a companion module that provides an OOP interface to the M_strings module.
public entities:
use M_strings,only : split, slice, sep, delim, chomp, strtok use M_strings,only : split2020, find_field use M_strings,only : substitute, change, modif, transliterate, & & reverse, squeeze use M_strings,only : replace, join use M_strings,only : upper, lower, upper_quoted, lower_quoted use M_strings,only : rotate13, percent_encode, percent_decode use M_strings,only : encode_base64, decode_base64 use M_strings,only : adjustc, compact, nospace, indent use M_strings,only : crop, clip, unquote, quote, matching_delimiter use M_strings,only : len_white, pad, lpad, cpad, rpad, zpad, & & stretch, lenset, merge_str use M_strings,only : switch, s2c, c2s use M_strings,only : noesc, notabs, dilate, expand, visible use M_strings,only : longest_common_substring use M_strings,only : string_to_value, string_to_values, s2v, s2vs use M_strings,only : int, real, dble, nint use M_strings,only : atoi, atol, aton use M_strings,only : value_to_string, v2s, str, fmt use M_strings,only : listout, getvals use M_strings,only : glob, ends_with use M_strings,only : paragraph use M_strings,only : base, decodebase, codebase, base2 use M_strings,only : isalnum, isalpha, iscntrl, isdigit use M_strings,only : isgraph, islower, isprint, ispunct use M_strings,only : isspace, isupper, isascii, isblank, isxdigit use M_strings,only : isnumber use M_strings,only : fortran_name use M_strings,only : describe use M_strings,only : edit_distance use M_strings,only : bundle
split subroutine parses string using specified delimiter characters and stores tokens into an array sep function interface to split(3f) slice subroutine parses string using specified delimiter characters and stores beginning and ending positions in arrays delim subroutine parses string using specified delimiter characters and store tokens into an array and records beginning and end chomp function consumes input line as it returns next token in a string using specified delimiters paragraph convert a string into a paragraph strtok tokenize a string like C strtok(3c) routine
split2020 split a string using prototype of proposed standard procedure find_field parse a string into tokens
substitute subroutine non-recursively globally replaces old substring with new substring replace function non-recursively globally replaces old substring with new substring using allocatable string (version of substitute(3f) without limitation on length of output string) change subroutine non-recursively globally replaces old substring with new substring with a directive like line editor modif subroutine modifies a string with a directive like the XEDIT line editor MODIFY command transliterate replace characters found in set one with characters from set two reverse reverse character order in a string join join an array of CHARACTER variables with specified separator rotate13 apply trivial encryption algorithm ROT13 to a string percent_encode apply percent-encryption (aka. URL encryption) to characters percent_decode apply percent-decryption (aka. URL decryption) to characters encode_base64 apply base64 encoding (as defined in RFC-4648) to an array of bytes decode_base64 apply base64 decoding (as defined in RFC-4648) to an array of bytes squeeze delete adjacent duplicate characters from a string
upper function converts string to uppercase lower function converts string to miniscule upper_quoted function converts string to uppercase skipping strings quoted per Fortran rules lower_quoted function converts string to lowercase skipping strings quoted per Fortran rules
len_white find location of last non-whitespace character lenset return a string of specified length pad return a string of at least specified length zpad pad integer or string to length with zero characters on left lpad convert scalar intrinsic to a string padded on left to specified length cpad convert scalar intrinsic to a centered string of the specified length rpad convert scalar intrinsic to a string padded on right to specified length stretch return a string of at least specified length with suffix merge_str make strings of equal length and then call MERGE(3f) intrinsic
See Also: squeeze
adjustc elemental function centers text within the length of the input string compact left justify string and replace duplicate whitespace with single characters or nothing nospace function replaces whitespace with nothing indent find number of leading spaces crop function trims leading and trailing spaces and control characters clip trim leading and trailings spaces or set of characters from string
matching_delimiter find position of matching delimiter unquote remove quotes from string as if read with list-directed input quote add quotes to string as if written with list-directed output
switch switch between a string and an array of single characters s2c convert string to array of single characters and add null terminator for passing to C c2s convert null-terminated array of single characters to string for converting strings returned from C
noesc convert non-printable ASCII8 characters to a space notabs convert tabs to spaces while maintaining columns, assuming tabs are set every 8 characters dilate function to convert tabs to spaces assuming tabs are set every 8 characters expand expand escape sequences in a string visible expand escape sequences in a string to "control" and meta-control representations
string_to_value generic subroutine returns numeric value (REAL, DOUBLEPRECISION, INTEGER) from string string_to_values subroutine reads an array of numbers from a string getvals subroutine reads a relatively arbitrary number of values from a string using list-directed read s2v function returns DOUBLEPRECISION numeric value from string s2vs function returns a DOUBLEPRECISION array of numbers from a string atol function returns INTEGER(kind=int64) from a string aton changes string to numeric value str append the values of up to twenty values into a string, including user-specified separator and a CSV-style option fmt return string from generic intrinsic value using optionally specified format. value_to_string generic subroutine returns string given numeric value (REAL, DOUBLEPRECISION, INTEGER, LOGICAL ) v2s generic function returns string from numeric value (REAL, DOUBLEPRECISION, INTEGER ) listout expand a list of numbers where negative numbers denote range ends (1 -10 means 1 thru 10) isnumber determine if string represents a number
glob compares given string for match to pattern which may contain wildcard characters ends_with test whether strings ends with one of the specified suffixes
o isalnum returns .true. if character is a letter or digit o isalpha returns .true. if character is a letter and [char46]false. otherwise o iscntrl returns .true. if character is a delete character or ordinary control character o isdigit returns .true. if character is a digit (0,1,...,9) and .false. otherwise o isgraph returns .true. if character is a printable character except a space is considered non-printable o islower returns .true. if character is a miniscule letter (a-z) o isprint returns .true. if character is an ASCII printable character o ispunct returns .true. if character is a printable punctuation character o isspace returns .true. if character is a null, space, tab, carriage return, new line, vertical tab, or formfeed o isupper returns .true. if character is an uppercase letter (A-Z) o isascii returns .true. if the character is in the range char(0) to char(127) o isblank returns .true. if character is a blank character (space or horizontal tab. o isxdigit returns .true. if character is a hexadecimal digit (0-9, a-f, or A-F). fortran_name returns .true. if input string is a valid Fortran name
base convert whole number string in base [2-36] to string in alternate base [2-36] base2 convert INTEGER to a string representing a binary value codebase convert whole number string in base [2-36] to base 10 number decodebase convert whole number in base 10 to string in base [2-36]
bundle return up to twenty strings of arbitrary length as an array describe returns a string describing the name of a single character edit_distance returns a naive edit distance using the Levenshtein distance algorithm longest_common_substring function that returns the longest common substring of two strings.
The M_strings(3fm) module supplements and works in combination with the Fortran built-in intrinsics. Stand-alone Fortran lets you access the characters in a string using ranges much like they are character arrays, assignment, comparisons with standard operators, supports dynamically allocatable strings and supports concatenation using the // operator, as well as a number of intrinsic string routines:
adjustl Left adjust a string adjustr Right adjust a string index Position of a substring within a string repeat Repeated string concatenation scan Scan a string for the presence of a set of characters trim Remove trailing blank characters of a string verify Scan a string for the absence of a set of characters len It returns the length of a character string achar converts an integer into a character iachar converts a character into an integer len_trim finds length of string with trailing spaces ignored new_line Newline character selected_char_kind Choose character kind lge Lexical greater than or equal lgt Lexical greater than lle Lexical less than or equal llt Lexical less than
The M_strings__oop(3fm) module (included with the M_strings(3fm) module) provides an OOP (Object-Oriented Programming) interface to the M_strings(3fm) module.
There are additional routines in other GPF modules for working with expressions (M_calculator), time strings (M_time), random strings (M_random, M_uuid), lists (M_list), and interfacing with the C regular expression library (M_regex).
Each of the procedures includes an [example](example/) program in the corresponding man(1) page for the function.Sample program:
program demo_M_strings use M_strings,only : SPLIT, slice, sep, delim, chomp, strtok use M_strings,only : split2020, find_field use M_strings,only : substitute, change, modif, transliterate, & & reverse, squeeze use M_strings,only : REPLACE, join use M_strings,only : UPPER, LOWER, upper_quoted, lower_quoted use M_strings,only : rotate13, percent_encode, percent_decode use M_strings,only : encode_base64, decode_base64 use M_strings,only : adjustc, compact, nospace, indent use M_strings,only : crop, clip, unquote, quote, matching_delimiter use M_strings,only : len_white, pad, lpad, cpad, rpad, zpad, & & stretch, lenset, merge_str use M_strings,only : switch, s2c, c2s use M_strings,only : noesc, notabs, dilate, expand, visible use M_strings,only : longest_common_substring use M_strings,only : string_to_value, string_to_values, s2v, s2vs use M_strings,only : int, real, dble, nint use M_strings,only : atoi, atol, aton use M_strings,only : value_to_string, v2s, str, fmt use M_strings,only : listout, getvals use M_strings,only : glob, ends_with use M_strings,only : paragraph use M_strings,only : base, decodebase, codebase, base2 use M_strings,only : isalnum, isalpha, iscntrl, isdigit use M_strings,only : isgraph, islower, isprint, ispunct use M_strings,only : isspace, isupper, isascii, isblank, isxdigit use M_strings,only : isnumber use M_strings,only : fortran_name use M_strings,only : describe use M_strings,only : edit_distance use M_strings,only : bundle character(len=:),allocatable :: string character(len=:),allocatable :: array(:) ! output array of tokens character(len=*),parameter :: gen=’(*(g0))’ character(len=*),parameter :: genx=’(*("[",g0,"] ":))’ string=’abcdefghijklmnopqrstuvwxyz ABCDEFGHIJKLMNOPQRSTUVWXYZ 01234567890’ write(*,gen)string write(*,gen)upper(string) write(*,gen)lower(string) call split(string,array) write(*,genx)array write(*,gen)replace(string,’qrs’,’--RePlace--’,ignorecase=.true.) end program demo_M_stringsResults:
> abcdefghijklmnopqrstuvwxyz ABCDEFGHIJKLMNOPQRSTUVWXYZ 01234567890 > ABCDEFGHIJKLMNOPQRSTUVWXYZ ABCDEFGHIJKLMNOPQRSTUVWXYZ 01234567890 > abcdefghijklmnopqrstuvwxyz abcdefghijklmnopqrstuvwxyz 01234567890 > [abcdefghijklmnopqrstuvwxyz] [ABCDEFGHIJKLMNOPQRSTUVWXYZ] [01234567890 ] > abcdefghijklmnop--RePlace--tuvwxyz ABCDEFGHIJKLMNOP--RePlace--TUVWXYZ 01234567890
John S. Urban
Public Domain
adjustc(3f) - [M_strings:WHITESPACE] center text (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
pure function adjustc(string[,length])
character(len=*),intent(in) :: string integer,intent(in),optional :: length character(len=:),allocatable :: adjustc
Centers input text in a string of the length specified. Returns a string of length LENGTH if LENGTH is present. Otherwise returns a string of the length of the input string.
string input string to trim and center length line length to center text in, optional.
adjustc centered output string
Sample Program:
program demo_adjustc use M_strings, only : adjustc ! using length of the input string write(*,’(a)’) ’================================’ write(*,’(a)’)adjustc(’centered string ’) write(*,’(a)’)adjustc(’ centered string’) write(*,’(a)’)adjustc(’ centered string ’) ! using explicit output string length write(*,’(a)’)repeat(’=’,50) write(*,’(a)’)adjustc(’this is a centered string’,50) write(*,’(a)’)repeat(’=’,50) end program demo_adjustcExpected output
================================ centered string centered string centered string ================================================== this is a centered string ==================================================
John S. Urban
Public Domain
atoi(3f) - [M_strings:TYPE] function returns a 32-bit integer value from a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
pure elemental function atoi (string) result(val)
character(len=*),intent(in) :: string integer(kind=int32),intent(out) :: val
function atoi(3f) converts a string representing an integer value to a numeric 32-bit integer value.
str holds string assumed to represent a numeric integer value
val returned INTEGER.
Sample Program:
program demo_atoiResults:use iso_fortran_env, only: wp => int32 use M_strings, only: atoi implicit none character(len=14),allocatable :: strings(:) integer(kind=wp) :: iv integer :: i
! different strings representing whole numbers strings=[& &’+10 ’,& &’ -3 ’,& &’ ’,& ! Note: will return zero without an error message &’1 2 1 2 1 . 0 ’,& ! Note: will just read first value &’WHAT? ’] ! Note: will return zero without an error message
do i=1,size(strings) iv=atoi(strings(i)) write(*,’(*(g0,1x))’)’STRING:’,strings(i),’:VALUE:’,iv enddo
end program demo_atoi
> STRING: +10 :VALUE: 10 > STRING: -3 :VALUE: -3 > STRING: :VALUE: 0 > STRING: 1 2 1 2 1 . 0 :VALUE: 1 > STRING: WHAT? :VALUE: 0
John S. Urban
Public Domain
atol(3f) - [M_strings:TYPE] function returns a 64-bit integer value from a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
pure elemental function atol (string) result(val)
character(len=*),intent(in) :: string integer(kind=int64),intent(out) :: val
function atol(3f) converts a string representing an integer value to a numeric 64-bit integer value.
str holds string assumed to represent a numeric integer value
val returned INTEGER.
Sample Program:
program demo_atolResults:use iso_fortran_env, only: wp => int64 use M_strings, only: atol implicit none character(len=14),allocatable :: strings(:) integer(kind=wp) :: iv integer :: i
! different strings representing whole numbers strings=[& &’+10 ’,& &’ -3 ’,& &’ ’,& ! Note: will return zero without an error message &’1 2 1 2 1 . 0 ’,& ! Note: will just read first value &’WHAT? ’] ! Note: will return zero without an error message
do i=1,size(strings) iv=atol(strings(i)) write(*,’(*(g0,1x))’)’STRING:’,strings(i),’:VALUE:’,iv enddo
end program demo_atol
> STRING: +10 :VALUE: 10 > STRING: -3 :VALUE: -3 > STRING: :VALUE: 0 > STRING: 1 2 1 2 1 . 0 :VALUE: 1 > STRING: WHAT? :VALUE: 0
John S. Urban
Public Domain
aton(3f) - [M_strings:TYPE] function returns argument as a numeric value from a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
logical function aton(str,val[,msg])
character(len=*),intent(in) :: str type(TYPE(kind=KIND)),intent(out) :: val character(len=:),allocatable,intent(out) :: msg
This function converts a string to a numeric value.
str holds string assumed to represent a numeric value val returned value. May be REAL or INTEGER. msg message describing error when ATON returns .false.
aton [char46]true. if the conversion was successful, .false. otherwise
Sample Program:
program demo_atonuse M_strings, only: aton implicit none character(len=14),allocatable :: strings(:) doubleprecision :: dv integer :: iv real :: rv integer :: i
! different strings representing INTEGER, REAL, and DOUBLEPRECISION strings=[& &’ 10.345 ’,& &’+10 ’,& &’ -3 ’,& &’ -4.94e-2 ’,& &’0.1 ’,& &’12345.678910d0’,& &’ ’,& ! Note: will return zero without an error message &’1 2 1 2 1 . 0 ’,& ! Note: spaces will be ignored &’WHAT? ’] ! Note: error messages will appear, zero returned
do i=1,size(strings) write(*,’(a)’,advance=’no’)’STRING:’,strings(i) if(aton(strings(i),iv)) write(*,’(g0)’,advance=’no’)’:INTEGER ’,iv if(aton(strings(i),rv)) write(*,’(g0)’,advance=’no’)’:INTEGER ’,rv if(aton(strings(i),dv)) write(*,’(g0)’,advance=’no’)’:INTEGER ’,dv enddo
end program demo_aton
John S. Urban
Public Domain
base(3f) - [M_strings:BASE] convert whole number string in base [2-36] to string in alternate base [2-36] (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental impure logical function base(x,b,y,a)
character(len=*),intent(in) :: x character(len=*),intent(out) :: y integer,intent(in) :: b,a
Convert a numeric string from base B to base A. The function returns FALSE if B is not in the range [2..36] or if string X contains invalid characters in base B or if result Y is too big.
The letters A,B,...,Z represent 10,11,...,36 in a base > 10.
x input string representing numeric whole value b assumed base of input string y output string. Y is assumed long enough to hold the computed value. If an error occurs Y is filled with asterisks (*). a base specified for output string
Returns .TRUE. if no error occurred, else returns .FALSE. .
Sample program:
program demo_base use M_strings, only: base implicit none integer :: ba, bd, i character(len=40) :: x, y character(len=*), parameter :: input(*) = [character(len=80) :: & ’10 12345 10’, & ’2 10111 10’, & ’10 12345 20’, & ’10 abcdef 2’, & ’0 0 0’] character(len=:),allocatable :: line print *, ’Base Conversion using base(3f)’ do i = 1, size(input) line=input(i) read (line, *) bd, x, ba if (x == ’0’) exit if (base(x, bd, y, ba)) then else print *, ’Error in decoding/encoding numbers’ end if write (*, ’(a," in base ",i0," is ",a," in base ",i0)’)& & trim(x),bd,trim(y),ba end do end program demo_baseResults:
> Base Conversion using base(3f) > 12345 in base 10 is 12345 in base 10 > 10111 in base 2 is 23 in base 10 > 12345 in base 10 is 1AH5 in base 20 > Error in decoding/encoding numbers > abcdef in base 10 is **************************************** in base 2
John S. Urban
Public Domain
base2(3f) - [M_strings:BASE] convert whole number to string in base 2 (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function base2(int)
integer,intent(in) :: int character(len=:),allocatable :: base2
Convert a whole number to a string in base 2.
This is often done with the B edit descriptor and an internal WRITE() statement, but is done without calling the I/O routines, and as a function.
int input string representing numeric whole value
base2 string representing input value in base 2
Sample program:
program demo_base2 use M_strings, only : base2 implicit none write(*,’(a)’) base2(huge(0)) write(*,’(a)’) base2(0) write(*,’(a)’) base2(64) write(*,’(a)’) base2(-64) write(*,’(a)’) base2(-huge(0)-1) end program demo_base2Results:
> 1111111111111111111111111111111 > 0 > 1000000 > 11111111111111111111111111000000 > 10000000000000000000000000000000
John S. Urban
Public Domain
bundle(3f) - [M_strings:ARRAY] return up to twenty strings of arbitrary length as an array (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
function bundle(str1,str2,...str20,len) result (vec)
character(len=*),intent(in),optional :: str1, str2 ... str20 integer,intent(in),optional :: len
Given a list of up to twenty strings create a string array. The length of the variables will be the same as the maximum length of the input strings unless explicitly specified via LEN.This is an alternative to the syntax
[ CHARACTER(LEN=NN) :: str1, str2, ... ]that by default additionally calculates the minimum length required to prevent truncation.
str1,str2, ... str20 input strings to combine into a vector len length of returned array variables
Sample Program:
program demo_bundle use M_strings, only: bundle implicit none character(len=*),parameter :: fmt= "(*(’""’,a,’""’:,’,’,1x))" character(len=:),allocatable :: array(:) print fmt, bundle("one") print fmt, bundle("one","two") print fmt, bundle("one","two","three") array=bundle("one","two","three","four","five","six","seven") write(*,’(*(g0))’)’size=’,size(array),’,len=’,len(array) write(*,’("[",a,"]")’)array end program demo_bundleResults:
> "one" > "one", "two" > "one ", "two ", "three" > size=7,len=5 > [one ] > [two ] > [three] > [four ] > [five ] > [six ] > [seven]
John S. Urban
Public Domain
c2s(3f) - [M_strings:ARRAY] convert C string pointer to Fortran character string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function c2s(c_string_pointer) result(f_string)
type(c_ptr), intent(in) :: c_string_pointer character(len=:), allocatable :: f_string
Given a C pointer to a character string return a Fortran character string.
c_string_pointer C pointer to convert
f_string Fortran character variable to return
John S. Urban
Public Domain
change(3f) - [M_strings:EDITING] change old string to new string with a directive like a line editor (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
subroutine change(target_string,cmd,ierr)
character(len=*),intent(inout) :: target_string character(len=*),intent(in) :: cmd integer :: ierr
change an old substring into a new substring in a character variable like a line editor. Primarily used to create interactive utilities such as input history editors for interactive line-mode programs. The output string is assumed long enough to accommodate the change. a directive resembles a line editor directive of the form
C/old_string/new_string/where / may be any character which is not included in old_string or new_string.
a null old_string implies "beginning of string".
target_string line to be changed cmd contains instructions to change the string ierr error code.
o =-1 bad directive o =0 no changes made o >0 count of changes made
Sample program:
program demo_changeExpected outputuse M_strings, only : change implicit none character(len=132) :: line=’This is a test string to change’ integer :: ierr write(*,*)trim(line) ! change miniscule a to uppercase A call change(line,’c/a/A/’,ierr) write(*,*)trim(line) ! put string at beginning of line call change(line,’c//prefix: /’,ierr) write(*,*)trim(line) ! remove blanks call change(line,’c/ //’,ierr) write(*,*)trim(line) end program demo_change
This is a test string to change This is A test string to chAnge prefix: This is A test string to chAnge prefix:ThisisAteststringtochAnge
John S. Urban
Public Domain
chomp(3f) - [M_strings:TOKENS] Tokenize a string, consuming it one token per call (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function chomp(source_string,token[,delimiters])
character(len=*) :: source_string character(len=:),intent(out) :: token character(len=:),intent(in),optional :: delimiters integer :: chomp
The CHOMP(3f) function is used to isolate sequential tokens in a string, SOURCE_STRING. These tokens are delimited in the string by at least one of the characters in DELIMITERS. This routine consumes the source_string one token per call. It returns -1 when complete. The default delimiter list is "space,tab,carriage return,newline".
SOURCE_STRING string to tokenize DELIMITERS list of separator characters
TOKEN returned token CHOMP status flag. 0 = success, -1 = no tokens remain
Sample program:
program demo_chompsample input fileuse M_strings, only : chomp implicit none character(len=100) :: inline character(len=:),allocatable :: token character(len=*),parameter :: delimiters=’ ;,’ integer :: iostat integer :: icount integer :: itoken icount=0 do ! read lines from stdin until end-of-file or error read (unit=*,fmt="(a)",iostat=iostat) inline if(iostat /= 0)stop icount=icount+1 itoken=0 write(*,*)’INLINE ’,trim(inline) do while ( chomp(inline,token,delimiters) >= 0) itoken=itoken+1 print *, itoken,’TOKEN=[’//trim(token)//’]’ enddo enddo
end program demo_chomp
this is a test of chomp; A:B :;,C;;sample output file
> INLINE this is a test of chomp; A:B :;,C;; > 1 TOKEN=[this] > 2 TOKEN=[is] > 3 TOKEN=[a] > 4 TOKEN=[test] > 5 TOKEN=[of] > 6 TOKEN=[chomp] > 7 TOKEN=[A:B] > 8 TOKEN=[:] > 9 TOKEN=[C]
John S. Urban
Public Domain
clip(3f) - [M_strings:WHITESPACE] trim leading and trailing blanks or set of characters from a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function clip(strin,set) result (strout)
character(len=*),intent(in) :: strin character(len=*),intent(in),optional :: set character(len=:),allocatable :: strout
leading and trailing spaces or set of characters are trimmed from the input string.
strin input string to trim leading and trailing characters from set set of characters to trim. Defaults to a space.
strout clipped version of input string
Sample program:
program demo_clip use M_strings, only: clip implicit none character(len=20) :: untrimmed = ’ ABCDEFG abcdefg ’ write(*,*) ’untrimmed string=[’,untrimmed,’]’ write(*,*) ’clipped string=[’,clip(untrimmed),’]’ ! which is equivalent to write(*,*) ’clipped string=[’,trim(adjustl(untrimmed)),’]’ write(*,*)’non-space:’ write(*,*) ’[’//clip(’----single-character----’,set=’-’)//’]’ write(*,*) ’[’//clip(’ ... . .multi-character . ...’,set=’. ’)//’]’ end program demo_clipResults:
> untrimmed string=[ ABCDEFG abcdefg ] > clipped string=[ABCDEFG abcdefg] > clipped string=[ABCDEFG abcdefg] > non-space: > [single-character] > [multi-character]
John S. Urban
Public Domain
codebase(3f) - [M_strings:BASE] convert whole number in base 10 to string in base [2-36] (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
logical function codebase(in_base10,out_base,answer,uc)
integer,intent(in) :: in_base10 integer,intent(in) :: out_base character(len=*),intent(out) :: answer logical,intent(in),optional :: uc
Convert a number from base 10 to base OUT_BASE. The function returns [char46]FALSE. if OUT_BASE is not in the range [2..36] or if number IN_BASE10 is too big.The letters A,B,...,Z represent 10,11,...,36 in the base > 10.
in_base10 whole number to convert to an alternate base out_base the desired base of the output answer the input value converted to a string representing the original number IN_BASE10 in base OUT_BASE. uc returned letters are uppercase if .true., lowercase if .false.
Returns .true. if no error occurred, else returns .false. .
Sample program:
program demo_codebase use M_strings, only : codebase implicit none character(len=20) :: answer integer :: i, j logical :: ierr do j=1,100 do i=2,36 ierr=codebase(j,i,answer) write(*,*)’VALUE=’,j,’ BASE=’,i,’ ANSWER=’,answer enddo enddo end program demo_codebase
John S. Urban
Ref.: "Math matiques en Turbo-Pascal by M. Ducamp and A. Reverchon (2), Eyrolles, Paris, 1988".based on a F90 Version By J-P Moreau (www.jpmoreau.fr)
Public Domain
compact(3f) - [M_strings:WHITESPACE] converts contiguous whitespace to a single character (or nothing) (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function compact(STR,CHAR) result (OUTSTR)
character(len=*),intent(in) :: STR character(len=*),intent(in),optional :: CHAR character(len=len(str)) :: OUTSTR
COMPACT(3f) converts multiple spaces, tabs and control characters (called "whitespace") to a single character or nothing. Leading whitespace is removed.
STR input string to reduce or remove whitespace from CHAR By default the character that replaces adjacent whitespace is a space. If the optional CHAR parameter is supplied it will be used to replace the whitespace. If a null character is supplied for CHAR whitespace is removed.
OUTSTR string of same length as input string but with all contiguous whitespace reduced to a single space and leading whitespace removed
Sample Program:
program demo_compact use M_strings, only : compact implicit none ! produces ’This is a test ’ write(*,*)compact(’ This is a test ’) ! produces ’Thisisatest ’ write(*,*)compact(’ This is a test ’,char=’’) ! produces ’This:is:a:test ’ write(*,*)compact(’ This is a test ’,char=’:’) ! note CHAR is used to replace the whitespace, but if CHAR is ! in the original string it is just copied write(*,*)compact(’A AA A AAAAA’,char=’A’) ! produces (original A characters are left as-is) ’AAAAAAAAAAAA’ ! not ’A’ end program demo_compactExpected output
>This is a test >Thisisatest >This:is:a:test >AAAAAAAAAAAA
John S. Urban
Public Domain
cpad(3f) - [M_strings:LENGTH] convert to a cropped string and then centers the string to specified length (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function cpad(valuein,length) result(strout)
class*,intent(in) :: valuein(..) integer,intent(in) :: length
cpad(3f) converts a scalar value to a cropped string and then pads it with spaces to center it to at least the specified length. If the trimmed input is longer than the requested length the string is returned trimmed of leading and trailing spaces.
str The input may be scalar or a vector. the input value to return as a string, padded with spaces to center it at the the specified length if shorter than length. The input may be any intrinsic scalar which is converted to a cropped string much as if written with list-directed output. length The minimum string length to return
strout The input string center-padded to the requested length with spaces.
Sample Program:
program demo_cpad use M_strings, only : cpad implicit none write(*,’("[",a,"]")’) cpad( ’my string’, 20) write(*,’("[",a,"]")’) cpad( ’my string ’, 20) write(*,’("[",a,"]")’) cpad( ’ my string’, 20) write(*,’("[",a,"]")’) cpad( ’ my string ’, 20) write(*,’("[",a,"]")’) cpad( valuein=42 , length=7) write(*,’("[",a,"]")’) cpad( valuein=1.0/9.0 , length=20) end program demo_cpad
John S. Urban
Public Domain
crop(3f) - [M_strings:WHITESPACE] trim leading and trailing blanks and control characters from a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
See Also
Author
License
function crop(strin) result (strout)
character(len=*),intent(in) :: strin character(len=:),allocatable :: strout
Tabs are expanded assuming a stop every eight characters. All other control characters throughout the string are replaced with spaces and leading and trailing spaces are trimmed from the resulting string.This means trailing characters like linefeed and carriage returns are removed. If this is not desired, see clip(3f).
strin input string to trim leading and trailing space and control characters from
strout cropped version of input string
Sample program:
program demo_crop use M_strings, only: crop implicit none character(len=20) :: untrimmed = ’ ABCDEFG abcdefg ’ write(*,*) ’untrimmed string=[’,untrimmed,’]’ write(*,*) ’cropped string=[’,crop(untrimmed),’]’ end program demo_cropResults:
> untrimmed string=[ ABCDEFG abcdefg ] > cropped string=[ABCDEFG abcdefg]
clip(3f)
John S. Urban
Public Domain
dble(3f) - [M_strings:TYPE] overloads DBLE(3f) so it can handle character arguments (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
impure elemental function dble(string)
character(len=*) :: string integer :: dble
dble(3f) returns a DOUBLE value when given a numeric representation of a numeric value. This overloads the DBLE(3f) intrinsic so that CHARACTER arguments assumed to represent a numeric value may be input.
STRING input string to be converted to a dble value
DBLE double precision value represented by input string
Sample program:
program demo_dble use M_strings, only: dble implicit none write(*,*)dble(’100’),dble(’20.4’) write(*,*)’dble still works’,dble(20),dble(20.4) write(*,*)’elemental’,& & dble([character(len=23) :: ’10’,’20.3’,’20.5’,’20.6’]) end program demo_dbleResults:
> 100.00000000000000 20.399999999999999 > dble still works 20.000000000000000 20.399999618530273 > elemental 10.00000000000000 20.30000000000000 > 20.50000000000000 20.60000000000000
John S. Urban
Public Domain
decode_base64-(3f) - [M_strings:ENCODE] decode data from base64 encoding as defined in RFC-4648 (LICENSE:MIT)
Synopsis
Description
Options
Output
Example
See Also
function decode_base64(text,ignore_garbage) result(out)
character(len=1),intent(in) :: text(*) logical,intent(in),optional :: ignore_garbage character(len=1),allocatable :: out(:)
The data is deencoded as described for the base64-alphabet-encoding in RFC 4648.
TEXT Data to decode IGNORE_GARBAGE when decoding, ignore all characters not in the formal base64 alphabet. This option will attempt to recover from any other non-alphabet bytes in the encoded data.
OUT array of decoded characters
Sample program:
program demo_decode_base64 use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 use M_strings, only : switch, encode_base64, decode_base64 implicit none integer :: i character(len=1),parameter :: nl=new_line(’a’) character(len=1),allocatable :: textin(:), textout(:) character(len=*),parameter :: data(*)=[ & ’This is some sample data ’, & ’To encode. Should make it long ’, & ’enough to generate multiple lines ’, & ’of output so can check line wrap ’, & ’functionality as well. ’ & ] ! make a file-like byte stream by trimming lines and adding newlines textin=[(switch(trim(data(i))),new_line(’a’),i=1,size(data))] write(*,’(*(a))’)’input:’,nl,textin ! textout=encode_base64(textin,width=50) write(*,’(*(a))’)’result:’,nl, textout ! write(*,’(*(a))’)’decode result:’,nl, decode_base64(textout) ! end program demo_decode_base64Results:
> input: > This is some sample data > To encode. Should make it long > enough to generate multiple lines > of output so can check line wrap > functionality as well. > > result: > VGhpcyBpcyBzb21lIHNhbXBsZSBkYXRhClRvIGVuY29kZS4gU2 > hvdWxkIG1ha2UgaXQgbG9uZwplbm91Z2ggdG8gZ2VuZXJhdGUg > bXVsdGlwbGUgbGluZXMKb2Ygb3V0cHV0IHNvIGNhbiBjaGVjay > BsaW5lIHdyYXAKZnVuY3Rpb25hbGl0eSBhcyB3ZWxsLgo= > > decode result: > This is some sample data > To encode. Should make it long > enough to generate multiple lines > of output so can check line wrap > functionality as well. >
encode_base64(3), base64(1), uuencode(1), uudecode(1)
decodebase(3f) - [M_strings:BASE] convert whole number string in base [2-36] to base 10 number (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
logical function decodebase(string,basein,out10)
character(len=*),intent(in) :: string integer,intent(in) :: basein integer,intent(out) :: out10
Convert a numeric string representing a whole number in base BASEIN to base 10. The function returns FALSE if BASEIN is not in the range [2..36] or if string STRING contains invalid characters in base BASEIN or if result OUT10 is too big
The letters A,B,...,Z represent 10,11,...,36 in the base > 10.
string input string. It represents a whole number in the base specified by BASEIN unless BASEIN is set to zero. When BASEIN is zero STRING is assumed to be of the form BASE#VALUE where BASE represents the function normally provided by BASEIN. basein base of input string; either 0 or from 2 to 36. out10 output value in base 10
Returns .true. if no error occurred, else returns .false. .
Sample program:
program demo_decodebase use M_strings, only : codebase, decodebase implicit none integer :: bd, i, r character(len=40) :: x character(len=*), parameter :: input(*) = [character(len=80) :: & ’10 12345’, & ’2 10111’, & ’6 12345’, & ’10 abcdef’, & ’0 0’] character(len=:),allocatable :: line print *, ’Base Conversion using decodebase(3f)’ do i = 1, size(input) line=input(i) read (line, *) bd, x if (x == ’0’) exit if(.not.decodebase(x,bd,r)) then print *,’Error in decoding number.’ endif write (*, ’(a," in base ",i0," becomes ",i0," in base 10")’)& & trim(x),bd,r end do end program demo_decodebaseResults:
> Base Conversion using decodebase(3f) > 12345 in base 10 becomes 12345 in base 10 > 10111 in base 2 becomes 23 in base 10 > 12345 in base 6 becomes 1865 in base 10 > Error in decoding number. > abcdef in base 10 becomes 0 in base 10
John S. Urban
Ref.: "Math matiques en Turbo-Pascal by M. Ducamp and A. Reverchon (2), Eyrolles, Paris, 1988".based on a F90 Version By J-P Moreau (www.jpmoreau.fr)
Public Domain
delim(3f) - [M_strings:TOKENS] parse a string and store tokens into an array (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
subroutine delim(line,array,n,icount,ibegin,iterm,lgth,dlim)
character(len=*),intent(in) :: line integer,integer(in) :: n integer,intent(out) :: icount character(len=*) :: array(n) integer,intent(out) :: ibegin(n) integer,intent(out) :: iterm(n) integer,intent(out) :: lgth character(len=*) :: dlim
Given a LINE of structure " par1 par2 par3 ... parn " store each par(n) into a separate variable in ARRAY (UNLESS ARRAY(1) == ’#N#’)Also set ICOUNT to number of elements of array initialized, and return beginning and ending positions for each element in IBEGIN(N) and ITERM(N).
Return position of last non-blank character (even if more than N elements were found) in lgth
No quoting or escaping of delimiter is allowed, so the delimiter character can not be placed in a token.
No checking for more than N parameters; If any more they are ignored.
This routine originates pre-Fortran90. A version using optional parameters and allocatable arrays is on the TODO list.
LINE input string to parse into tokens ARRAY(N) array that receives tokens N size of arrays ARRAY, IBEGIN, ITERM ICOUNT number of tokens found IBEGIN(N) starting columns of tokens found ITERM(N) ending columns of tokens found LGTH position of last non-blank character in input string LINE DLIM delimiter characters
Sample program:
program demo_delimResults:use M_strings, only: delim implicit none character(len=80) :: line character(len=80) :: dlm integer,parameter :: n=80 character(len=20) :: array(n)=’ ’ integer :: ibegin(n),iterm(n) integer :: i20, icount, lgth, i10,i30 line=’ first second 10.3 words_of_stuff ’ do i20=1,4 ! change delimiter list and what is calculated or parsed if(i20 == 1)dlm=’ ’ if(i20 == 2)dlm=’o’ if(i20 == 3)dlm=’ aeiou’ ! NOTE SPACE IS FIRST if(i20 == 3)ARRAY(1)=’#N#’ ! QUIT RETURNING STRING ARRAY if(i20 == 4)line=’AAAaBBBBBBbIIIIIi J K L’
! write out a break line composed of =========== .. write(*,’(57("="))’) ! show line being parsed write(*,’(a)’)’PARSING=[’//trim(line)//’] on ’//trim(dlm) ! call parsing procedure call delim(line,array,n,icount,ibegin,iterm,lgth,dlm) write(*,*)’number of tokens found=’,icount write(*,*)’last character in column ’,lgth if(icount > 0)then if(lgth /= iterm(icount))then write(*,*)’ignored from column ’,iterm(icount)+1,’ to ’,lgth endif do i10=1,icount ! check flag to see if ARRAY() was set if(array(1) /= ’#N#’)then ! from returned array write(*,’(a,a,a)’,advance=’no’)& &’[’,array(i10)(:iterm(i10)-ibegin(i10)+1),’]’ endif enddo ! using start and end positions in IBEGIN() and ITERM() write(*,*) do i10=1,icount ! from positions in original line write(*,’(a,a,a)’,advance=’no’)& &’[’,line(ibegin(i10):iterm(i10)),’]’ enddo write(*,*) endif enddo line=’four score and seven years ago’ call delim(line,["#N#"],n,icount,ibegin,iterm,lgth,’ ’) do i30=1,icount write(*,*)ibegin(i30),iterm(i30),& & ’[’//line(ibegin(i30):iterm(i30))//’]’ enddo
end program demo_delim
> ========================================================= > PARSING=[ first second 10.3 words_of_stuff] on > number of tokens found= 4 > last character in column 34 > [first][second][10.3][words_of_stuff] > [first][second][10.3][words_of_stuff] > ========================================================= > PARSING=[ first second 10.3 words_of_stuff] on o > number of tokens found= 4 > last character in column 34 > [ first sec][nd 10.3 w][rds_][f_stuff] > [ first sec][nd 10.3 w][rds_][f_stuff] > ========================================================= > PARSING=[ first second 10.3 words_of_stuff] on aeiou > number of tokens found= 10 > last character in column 34 > > [f][rst][s][c][nd][10.3][w][rds_][f_st][ff] > ========================================================= > PARSING=[AAAaBBBBBBbIIIIIi J K L] on aeiou > number of tokens found= 5 > last character in column 24 > > [AAA][BBBBBBbIIIII][J][K][L] > 1 4 [four] > 9 13 [score] > 15 17 [and] > 21 25 [seven] > 28 32 [years] > 34 36 [ago]================================================================================
John S. Urban
Public Domain
describe(3f) - [M_strings:DESCRIBE] returns a string describing the name of a single character (LICENSE:PD)
Synopsis
Description
Examples
Author
License
function describe(ch) result (string)
character(len=1),intent(in) :: ch character(len=:),allocatable :: string
describe(3f) returns a string describing long name of a single character
Sample Program:
program demo_describe use M_strings, only : describe implicit none integer :: i do i=1,128 ! fill variable with base ASCII character set write(*,*)describe(char(i-1)) enddo end program demo_describeExpected output
ctrl-@ or ctrl-? (NUL) null ctrl-A (SOH) start of heading ctrl-B (STX) start of text ctrl-C (ETX) end of text ctrl-D (EOT) end of transmission ctrl-E (ENQ) enquiry ctrl-F (ACK) acknowledge ctrl-G (BEL) bell ctrl-H (BS) backspace ctrl-I (HT) horizontal tabulation ctrl-J (LF) line feed ctrl-K (VT) vertical tabulation ctrl-L (FF) form feed ctrl-M (CR) carriage return ctrl-N (SO) shift out ctrl-O (SI) shift in ctrl-P (DLE) data link escape ctrl-Q (DC1) device control 1 ctrl-R (DC2) device control 2 ctrl-S (DC3) device control 3 ctrl-T (DC4) device control 4 ctrl-U (NAK) negative acknowledge ctrl-V (SYN) synchronous idle ctrl-W (ETB) end of transmission block ctrl-X (CAN) cancel ctrl-Y (EM) end of medium ctrl-Z (SUB) substitute ctrl-[ (ESC) escape ctrl-\ or ctrl-@ (FS) file separator ctrl-] (GS) group separator ctrl-^ or ctrl-= (RS) record separator ctrl-_ (US) unit separator space ! exclamation point " quotation marks # number sign $ currency symbol % percent & ampersand ’ apostrophe ( left parenthesis ) right parenthesis * asterisk + plus , comma - minus . period / slash 0 zero 1 one 2 two 3 three 4 four 5 five 6 six 7 seven 8 eight 9 nine : colon ; semicolon < less than = equals > greater than ? question mark @ at sign majuscule A majuscule B majuscule C majuscule D majuscule E majuscule F majuscule G majuscule H majuscule I majuscule J majuscule K majuscule L majuscule M majuscule N majuscule O majuscule P majuscule Q majuscule R majuscule S majuscule T majuscule U majuscule V majuscule W majuscule X majuscule Y majuscule Z [ left bracket \ backslash ] right bracket ^ caret _ underscore ‘ grave accent miniscule a miniscule b miniscule c miniscule d miniscule e miniscule f miniscule g miniscule h miniscule i miniscule j miniscule k miniscule l miniscule m miniscule n miniscule o miniscule p miniscule q miniscule r miniscule s miniscule t miniscule u miniscule v miniscule w miniscule x miniscule y miniscule z { left brace | vertical line } right brace ~ tilde ctrl-? (DEL) delete
John S. Urban
Public Domain
dilate(3f) - [M_strings:NONALPHA] function to expand tab characters (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function dilate(INSTR) result(OUTSTR)
character(len=*),intent=(in) :: INSTR character(len=:),allocatable :: OUTSTR
dilate(3) converts tabs in INSTR to spaces in OUTSTR. It assumes a tab is set every 8 characters. Trailing spaces are removed.In addition, trailing carriage returns and line feeds are removed (they are usually a problem created by going to and from MSWindows).
instr Input line to remove tabs from
outstr Output string with tabs expanded.
Sample program:
program demo_dilateResults:use M_strings, only : dilate, visible implicit none character(len=:),allocatable :: in integer :: i in=’ this is my string ’ ! change spaces to tabs to make a sample input do i=1,len(in) if(in(i:i) == ’ ’)in(i:i)=char(9) enddo write(*,’("[",a,"]")’)visible(in) write(*,’("[",a,"]")’)visible(dilate(in)) end program demo_dilate
> [^I^Ithis^Iis^Imy^Istring^I^I] > [ this is my string]
John S. Urban
Public Domain
edit_distance(3f) - [M_strings:DESCRIBE] returns a naive edit distance using the Levenshtein distance algorithm (LICENSE:PD)
Synopsis
Description
Examples
Author
License
pure elemental function edit_distance(str1,str2) result (distance)
character(len=*),intent(in) :: str1, str2 integer :: distance
The Levenshtein distance function returns how many edits (deletions, insertions, transposition) are required to turn one string into another.
Sample Program:
program demo_edit_distance use M_strings, only : edit_distance write(*,*)edit_distance(’kittens’,’sitting’)==3 write(*,*)edit_distance(’geek’,’gesek’)==1 write(*,*)edit_distance(’Saturday’,’Sunday’)==3 end program demo_edit_distanceExpected output
> T > T > T
John S. Urban
Public Domain
encode_base64-(3f) - [M_strings:ENCODE] encode data using base64 encoding as defined in RFC-4648 (LICENSE:MIT)
Synopsis
Description
Options
Output
Example
See Also
function encode_base64(text,width) result(out)
character(len=1),intent(in) :: text(*) integer,intent(in),optional :: width character(len=1),allocatable :: out(:)
The data is encoded as described for the base64-alphabet-encoding in RFC 4648.
TEXT Data to encode WIDTH wrap encoded lines after specified number of characters (default 76). Use 0 to disable line wrapping
OUT array of encoded characters representing input text
Sample program:
program demo_encode_base64 use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 use M_strings, only : switch, encode_base64, decode_base64 implicit none integer :: i character(len=1),parameter :: nl=new_line(’a’) character(len=1),allocatable :: textin(:), textout(:) character(len=*),parameter :: data(*)=[ & ’This is some sample data ’, & ’To encode. Should make it long ’, & ’enough to generate multiple lines ’, & ’of output so can check line wrap ’, & ’functionality as well. ’ & ] ! make a file-like byte stream by trimming lines and adding newlines textin=[(switch(trim(data(i))),new_line(’a’),i=1,size(data))] write(*,’(*(a))’)’input:’,nl,textin ! textout=encode_base64(textin,width=50) write(*,’(*(a))’)’result:’,nl, textout ! write(*,’(*(a))’)’decode result:’,nl, decode_base64(textout) ! ! one way to encode non-byte data call other() contains subroutine other() real :: arr1(100) character(len=1),allocatable :: in(:) character(len=1),allocatable :: out(:) real,allocatable :: arr2(:) ! fill a real array with some values arr1=[(sqrt(real(i)),i=1,size(arr1))] ! use TRANSFER() to convert data to bytes in=transfer(source=arr1,mold=[’+’]) ! encode the bytes out=encode_base64(in) ! decode the bytes out=decode_base64(out) ! store the bytes back into arr1 arr2=transfer(source=out,mold=[0.0]) write(*,’(*(g0,1x))’) ’are arr1 and arr2 the same?’,all(arr1.eq.arr2) end subroutine other end program demo_encode_base64Results:
> input: > This is some sample data > To encode. Should make it long > enough to generate multiple lines > of output so can check line wrap > functionality as well. > > result: > VGhpcyBpcyBzb21lIHNhbXBsZSBkYXRhClRvIGVuY29kZS4gU2 > hvdWxkIG1ha2UgaXQgbG9uZwplbm91Z2ggdG8gZ2VuZXJhdGUg > bXVsdGlwbGUgbGluZXMKb2Ygb3V0cHV0IHNvIGNhbiBjaGVjay > BsaW5lIHdyYXAKZnVuY3Rpb25hbGl0eSBhcyB3ZWxsLgo= > > decode result: > This is some sample data > To encode. Should make it long > enough to generate multiple lines > of output so can check line wrap > functionality as well. > > are arr1 and arr2 the same? T
decode_base64(3), base64(1), uuencode(1), uudecode(1)
ends_with(3f) - [M_strings:COMPARE] test if string ends with specified suffix(es) (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
pure function ends_with(string,ending[,ignorecase])
character(len=*),intent(in) :: string character(len=*),intent(in) :: ending(..) logical,intent(in),optional :: ignorecase logical :: ends_with
ends_with(3f) tests if a string ends with any specified suffix. Differs from using index(3f) in that the input string and multiple suffices are trimmed by ends_with(3f),
STRING string to search ENDING list of separator strings. May be scalar or an array. Trailing spaces in ENDING are ignored. IGNORECASE If .true. case is ignored.
ENDS_WITH returns .TRUE. if one of the suffix match the end of STRING.
Sample program:
program demo_ends_with use M_strings, only : ends_with use, intrinsic :: iso_fortran_env, only : stdout=>output_unit implicit none character(len=:),allocatable :: line, pattern ! write(*,*)’basic usage’ write(stdout,*)ends_with(’prog.a’,’.a’), ’should be true’ write(stdout,*)ends_with(’prog.a’,’.o’), ’should be false’ write(stdout,*)ends_with(’prog.a’,[’.o’,’.i’,’.s’]) write(stdout,*)ends_with(’prog.f90’,[’.F90’,’.f90’,’.f ’,’.F ’]) ! write(*,*)’ignored case’ write(stdout,*)ends_with(’prog.F90’,[’.f90’,’.f ’],ignorecase=.true.) ! write(*,*)’trailing whitespace is ignored’ write(stdout,*)ends_with(’prog.pdf’,’.pdf’) write(stdout,*)ends_with(’prog.pdf’,’.pdf ’) write(stdout,*)ends_with(’prog.pdf ’,’.pdf ’) write(stdout,*)ends_with(’prog.pdf ’,’.pdf ’) ! write(*,*)’equivalent using index(3f)’ line= ’myfile.doc ’ pattern=’.doc ’ write(stdout,*)& &index(trim(line),trim(pattern),back=.true.)==len_trim(line)-len_trim(pattern)+1 write(stdout,*)ends_with(line,pattern) end program demo_ends_withResults:
> basic usage > T should be true > F should be false > F > T > ignored case > T > trailing whitespace is ignored > T > T > T > T > equivalent using index(3f) > T > T
John S. Urban
Public Domain
expand(3f) - [M_strings:NONALPHA] expand C-like escape sequences (LICENSE:PD)
Synopsis
Description
Examples
Author
License
function expand(line,escape) result(lineout)
character(len=*) :: line character(len=1),intent(in),optional :: escape character(len=:),allocatable :: lineout
EXPAND(3) expands sequences used to represent commonly used escape sequences or control characters. By default ...Escape sequences
\ backslash a alert (BEL) -- g is an alias for a b backspace c suppress further output e escape f form feed n new line r carriage return t horizontal tab v vertical tab oNNN byte with octal value NNN (3 digits) dNNN byte with decimal value NNN (3 digits) xHH byte with hexadecimal value HH (2 digits) -- h is an alias for xThe default escape character is the backslash, but this may be changed using the optional parameter ESCAPE.
Sample Program:
program demo_expand ! demonstrate filter to expand C-like escape sequences in input lines use M_strings, only : expand integer,parameter :: iwidth=1024 integer :: i character(len=iwidth),parameter :: input(*)=[ character(len=iwidth) :: & ’\e[H\e[2J’,& ! home cursor and clear screen on ANSI terminals ’\tABC\tabc’,& ! write some tabs in the output ’\tA\a’,& ! ring bell at end if supported ’\nONE\nTWO\nTHREE’,& ! place one word per line ’\#146;] write(*,’(a)’)(trim(expand(input(i))),i=1,size(input)) end program demo_expandResults (with nonprintable characters shown visible):
> ^[[H^[[2J > ^IABC^Iabc > ^IA^G > > ONE > TWO > THREE > \
John S. Urban
Public Domain
find_field(3f) - [M_strings:TOKENS] parse a string into tokens (LICENSE:MIT)
Synopsis
Description
Options
Examples
Author
License
Version
subroutine find_field (string, field, position, delims, delim, found)
character*(*),intent(in) :: string character*(*),intent(out) :: field integer,optional,intent(inout) :: position character*(*),optional,intent(in) :: delims character*(*),optional,intent(out) :: delim logical,optional,intent(out) :: found
Find a delimited field in a string.
Here is my equivalent, which I have used for nearly 2 decades, as you can see from the date. This does not try to mimic the C strtok (and does not have its limitations either). It is in a much more native Fortran style.
It is a little more complicated than some because it does some things that I regularly find useful. For example, it can tell the caller what trailing delimiter it found. This can be useful, for example, to distinguish between
somefield, someotherfieldversus
somefield=somevalue, someotherfieldAlso, I have a bit of special handling for blanks. All the usage information is in the argument descriptions. Note that most of the arguments are optional.
from comp.lang.fortran @ Richard Maine
STRING The string input. FIELD The returned field. Blank if no field found. POSITION On entry, the starting position for searching for the field. Default is 1 if the argument is not present. On exit, the starting position of the next field or len(string)+1 if there is no following field. DELIMS String containing the characters to be accepted as delimiters. If this includes a blank character, then leading blanks are removed from the returned field and the end delimiter may optionally be preceded by blanks. If this argument is not present, the default delimiter set is a blank. DELIM Returns the actual delimiter that terminated the field. Returns char(0) if the field was terminated by the end of the string or if no field was found. If blank is in delimiters and the field was terminated by one or more blanks, followed by a non-blank delimiter, the non-blank delimiter is returned. FOUND True if a field was found.
Sample of uses
program demo_find_field use M_strings, only : find_field implicit none character(len=256) :: string character(len=256) :: field integer :: position character(len=:),allocatable :: delims character(len=1) :: delim logical :: foundResults:delims=’[,]’ position=1 found=.true. string=’[a,b,[ccc,ddd],and more]’ write(*,’(a)’)trim(string) do call find_field(string,field,position,delims,delim,found=found) if(.not.found)exit write(*,’("<",a,">")’)trim(field) enddo write(*,’(*(g0))’)repeat(’=’,70)
position=1 found=.true. write(*,’(a)’)trim(string) do call find_field(string,field,position,’[], ’,delim,found=found) if(.not.found)exit write(*,’("<",a,">",i0,1x,a)’)trim(field),position,delim enddo write(*,’(*(g0))’)repeat(’=’,70)
end program demo_find_field
> [a,b,[ccc,ddd],and more] > <> > <a> > <b> > <> > <ccc> > <ddd> > <> > <and more> > <> > ================================================================== > [a,b,[ccc,ddd],and more] > <>2 [ > <a>4 , > <b>6 , > <>7 [ > <ccc>11 , > <ddd>15 ] > <>16 , > <and>20 > <more>257 ] > ==================================================================
Richard Maine
version 0.1.0, copyright Nov 15 1990, Richard MaineMinor editing to conform to inclusion in the string procedure module
fmt(3f) - [M_strings:TYPE] convert any intrinsic to a string using specified format (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function fmt(value,format) result(string)
class(*),intent(in),optional :: value character(len=*),intent(in),optional :: format character(len=:),allocatable :: string
FMT(3f) converts any standard intrinsic value to a string using the specified format.
value value to print the value of. May be of type INTEGER, LOGICAL, REAL, DOUBLEPRECISION, COMPLEX, or CHARACTER. format format to use to print value. It is up to the user to use an appropriate format. The format does not require being surrounded by parenthesis. If not present a default is selected similar to what would be produced with free format, with trailing zeros removed.
string A string value
Sample program:
program demo_fmt use :: M_strings, only : fmt implicit none character(len=:),allocatable :: outputResults:output=fmt(10,"’[’,i0,’]’") write(*,*)’result is ’,output
output=fmt(10.0/3.0,"’[’,g0.5,’]’") write(*,*)’result is ’,output
output=fmt(.true.,"’The final answer is [’,g0,’]’") write(*,*)’result is ’,output
end program demo_fmt
result is [10] result is [3.3333] result is The final answer is [T]
John S. Urban
Public Domain
fortran_name(3f) - [M_strings:COMPARE] test if string meets criteria for being a fortran name (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function fortran_name(line) result (lout)
character(len=*),intent(in) :: line logical :: lout
Determines if a string is an allowed Fortran name. To pass the input string must be composed of 1 to 63 ASCII characters and start with a letter and be composed entirely of alphanumeric characters [a-zA-Z0-9] and underscores.
LINE input string to test. Leading spaces are significant but trailing spaces are ignored.
LOUT a logical value indicating if the input string passed or failed the test to see if it is a valid Fortran name or not.
Sample program
program demo_fortran_name use M_strings, only : fortran_name implicit none character(len=20),parameter :: names(*)=[character(len=20) :: & & ’_name’, ’long_variable_name’, ’name_’, & & ’12L’, ’a__b__c ’, ’PropertyOfGas’, & & ’3%3’, ’$NAME’, ’ ’, & & ’Variable-name’, ’A’, ’x@x’ ] integer :: i write(*,’(i3,1x,a20,1x,l1)’)& & (i,names(i),fortran_name(names(i)),i=1,size(names)) end program demo_fortran_nameResults:
> 1 _name F > 2 long_variable_name T > 3 name_ T > 4 12L F > 5 a__b__c T > 6 PropertyOfGas T > 7 3%3 F > 8 $NAME F > 9 F > 10 Variable-name F > 11 A T > 12 x@x F
John S. Urban
Public Domain
getvals(3f) - [M_strings:TYPE] read arbitrary number of REAL values from a character variable up to size of VALUES() array (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
subroutine getvals(line,values,icount,ierr)
character(len=*),intent(in) :: line class(*),intent(out) :: values(:) integer,intent(out) :: icount integer,intent(out),optional :: ierr
GETVALS(3f) reads a relatively arbitrary number of numeric values from a character variable into a REAL array using list-directed input.NOTE: In this version null values are skipped instead of meaning to leave that value unchanged
1,,,,,,,2 / reads VALUES=[1.0,2.0]
Per list-directed rules when reading values, allowed delimiters are comma, semi-colon and space.
the slash separator can be used to add inline comments.
10.1, 20.43e-1 ; 11 / THIS IS TREATED AS A COMMENTRepeat syntax can be used up to the size of the output array. These are equivalent input lines:
4*10.0 10.0, 10.0, 10.0, 10.0
LINE A character variable containing the characters representing a list of numbers
VALUES() array holding numbers read from string. May be of type INTEGER, REAL, DOUBLEPRECISION, or CHARACTER. If CHARACTER the strings are returned as simple words instead of numeric values. ICOUNT number of defined numbers in VALUES(). If ICOUNT reaches the size of the VALUES() array parsing stops. IERR zero if no error occurred in reading numbers. Optional. If not present and an error occurs the program is terminated.
Sample program:
program demo_getvals use M_strings, only: getvals implicit none integer,parameter :: longest_line=256 character(len=longest_line) :: line real :: values(longest_line/2+1) integer :: iostat,icount,ierr INFINITE: do read(*,’(a)’,iostat=iostat) line if(iostat /= 0)exit INFINITE call getvals(line,values,icount,ierr) write(*,’(4(g0,1x))’)’VALUES=’,values(:icount) enddo INFINITE end program demo_getvalsSample input lines
10,20 30.4 1 2 3 1Expected output:3 4*2.5 8 32.3333 / comment 1 30e3;300, 30.0, 3 even 1 like this! 10 11,,,,22,,,,33
VALUES= 10.0000000 20.0000000 30.3999996 VALUES= 1.00000000 2.00000000 3.00000000 VALUES= 1.00000000 VALUES= VALUES= 3.00000000 2.50000000 2.50000000 2.50000000 2.50000000 8.00000000 VALUES= 32.3333015 VALUES= 30000.0000 300.000000 30.0000000 3.00000000 *getvals* WARNING:[even] is not a number *getvals* WARNING:[like] is not a number *getvals* WARNING:[this!] is not a number VALUES= 1.00000000 10.0000000 VALUES= 11.0000000 22.0000000 33.0000000
John S. Urban
Public Domain
glob(3f) - [M_strings:COMPARE] compare given string for match to a pattern which may contain globbing wildcard characters (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
References
License
logical function glob(string, pattern )
character(len=*),intent(in) :: string character(len=*),intent(in) :: pattern
glob(3f) compares an (entire) STRING for a match to a PATTERN which may contain basic wildcard "globbing" characters."*" matches any string. "?" matches any single character.
In this version to get a match the entire string must be described by PATTERN. Trailing whitespace is significant, so trim the input string to have trailing whitespace ignored.
Patterns like "b*ba" fail on a string like "babababa" because the first match found is not at the end of the string so ’baba’ does not match
To skip over the early matches insert an extra character at the end of the string and pattern that does not occur in the pattern. Typically a NULL is used (char(0)). So searching for b*ba\0 in babababa\0 matches the entire string.
string the input string to be tested for a match to the pattern. pattern the globbing pattern to search for. The following simple globbing options are available
o "?" matching any one character o "*" matching zero or more characters. Do NOT use adjacent asterisks. o spaces are significant and must be matched or trimmed before the comparison. o There is no escape character, so matching strings with a literal question mark and asterisk is problematic.
Example program
program demo_glob implicit none ! This main routine passes a bunch of test strings ! into the above code. In performance comparison mode, ! it does that over and over. Otherwise, it does it just ! once. Either way, it outputs a passed/failed result. ! integer :: nReps logical :: allpassed integer :: i allpassed = .true.Expected outputnReps = 10000 ! Can choose as many repetitions as you’re expecting ! in the real world. nReps = 1
do i=1,nReps ! Cases with repeating character sequences. allpassed= test("a*abab", "a*b", .true.) .and. allpassed allpassed= test("ab", "*?", .true.) .and. allpassed allpassed= test("abc", "*?", .true.) .and. allpassed allpassed= test("abcccd", "*ccd", .true.) .and. allpassed allpassed= test("bLah", "bLaH", .false.) .and. allpassed allpassed= test("mississippi", "*sip*", .true.) .and. allpassed allpassed= & & test("xxxx*zzzzzzzzy*f", "xxx*zzy*f", .true.) .and. allpassed allpassed= & & test("xxxx*zzzzzzzzy*f", "xxxx*zzy*fffff", .false.) .and. allpassed allpassed= & & test("mississipissippi", "*issip*ss*", .true.) .and. allpassed allpassed= & & test("xxxxzzzzzzzzyf", "xxxx*zzy*fffff", .false.) .and. allpassed allpassed= & & test("xxxxzzzzzzzzyf", "xxxx*zzy*f", .true.) .and. allpassed allpassed= test("xyxyxyzyxyz", "xy*z*xyz", .true.) .and. allpassed allpassed= test("xyxyxyxyz", "xy*xyz", .true.) .and. allpassed allpassed= test("mississippi", "mi*sip*", .true.) .and. allpassed allpassed= test("ababac", "*abac*", .true.) .and. allpassed allpassed= test("aaazz", "a*zz*", .true.) .and. allpassed allpassed= test("a12b12", "*12*23", .false.) .and. allpassed allpassed= test("a12b12", "a12b", .false.) .and. allpassed allpassed= test("a12b12", "*12*12*", .true.) .and. allpassed
! Additional cases where the ’*’ char appears in the tame string. allpassed= test("*", "*", .true.) .and. allpassed allpassed= test("a*r", "a*", .true.) .and. allpassed allpassed= test("a*ar", "a*aar", .false.) .and. allpassed
! More double wildcard scenarios. allpassed= test("XYXYXYZYXYz", "XY*Z*XYz", .true.) .and. allpassed allpassed= test("missisSIPpi", "*SIP*", .true.) .and. allpassed allpassed= test("mississipPI", "*issip*PI", .true.) .and. allpassed allpassed= test("xyxyxyxyz", "xy*xyz", .true.) .and. allpassed allpassed= test("miSsissippi", "mi*sip*", .true.) .and. allpassed allpassed= test("miSsissippi", "mi*Sip*", .false.) .and. allpassed allpassed= test("abAbac", "*Abac*", .true.) .and. allpassed allpassed= test("aAazz", "a*zz*", .true.) .and. allpassed allpassed= test("A12b12", "*12*23", .false.) .and. allpassed allpassed= test("a12B12", "*12*12*", .true.) .and. allpassed allpassed= test("oWn", "*oWn*", .true.) .and. allpassed
! Completely tame (no wildcards) cases. allpassed= test("bLah", "bLah", .true.) .and. allpassed
! Simple mixed wildcard tests suggested by IBMer Marlin Deckert. allpassed= test("a", "*?", .true.) .and. allpassed
! More mixed wildcard tests including coverage for false positives. allpassed= test("a", "??", .false.) .and. allpassed allpassed= test("ab", "?*?", .true.) .and. allpassed allpassed= test("ab", "*?*?*", .true.) .and. allpassed allpassed= test("abc", "?**?*?", .true.) .and. allpassed allpassed= test("abc", "?**?*&?", .false.) .and. allpassed allpassed= test("abcd", "?b*??", .true.) .and. allpassed allpassed= test("abcd", "?a*??", .false.) .and. allpassed allpassed= test("abcd", "?**?c?", .true.) .and. allpassed allpassed= test("abcd", "?**?d?", .false.) .and. allpassed allpassed= test("abcde", "?*b*?*d*?", .true.) .and. allpassed
! Single-character-match cases. allpassed= test("bLah", "bL?h", .true.) .and. allpassed allpassed= test("bLaaa", "bLa?", .false.) .and. allpassed allpassed= test("bLah", "bLa?", .true.) .and. allpassed allpassed= test("bLaH", "?Lah", .false.) .and. allpassed allpassed= test("bLaH", "?LaH", .true.) .and. allpassed
allpassed= test(’abcdefghijk’ , ’?b*’, .true.) .and. allpassed allpassed= test(’abcdefghijk’ , ’*c*’, .true.) .and. allpassed allpassed= test(’abcdefghijk’ , ’*c’, .false.) .and. allpassed allpassed= test(’abcdefghijk’ , ’*c*k’, .true.) .and. allpassed allpassed= test(’LS’ , ’?OW’, .false.) .and. allpassed allpassed= test(’teztit’ , ’tez*t*t’, .true.) .and. allpassed ! Two pattern match problems that might pose difficulties allpassed= test(’e ’ , ’*e* ’, .true.) .and. allpassed allpassed= test(’abcde ’ , ’*e *’, .true.) .and. allpassed allpassed= test(’bababa’ , ’b*ba’, .true.) .and. allpassed allpassed= test(’baaaaax’ , ’b*ax’, .true.) .and. allpassed allpassed= test(’baaaaa’ , ’b*ax’, .false.) .and. allpassed allpassed= test(’baaaaax’ , ’b*a’, .false.) .and. allpassed allpassed= test(’’ , ’b*’, .false.) .and. allpassed allpassed= test(’’ , ’*’, .true.) .and. allpassed allpassed= test(’b’ , ’’, .false.) .and. allpassed allpassed= test(’3’ , ’??’, .false.) .and. allpassed ! known flaws allpassed= test(’’ , ’’, .true.) .and. allpassed allpassed= test(’baaaaa’ , ’b*a’, .true.) .and. allpassed ! add unused character to work around allpassed= test(’’//char(0), ’’//char(0), .true.).and.allpassed allpassed= test(’baaaaa’//char(0),’b*a’//char(0),.true.).and.allpassed
! Many-wildcard scenarios. allpassed= test(& &"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa& &aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaab",& &"a*a*a*a*a*a*aa*aaa*a*a*b",& &.true.) .and. allpassed allpassed= test(& &"abababababababababababababababababababaacacacacacacac& &adaeafagahaiajakalaaaaaaaaaaaaaaaaaffafagaagggagaaaaaaaab",& &"*a*b*ba*ca*a*aa*aaa*fa*ga*b*",& &.true.) .and. allpassed allpassed= test(& &"abababababababababababababababababababaacacacacacaca& &cadaeafagahaiajakalaaaaaaaaaaaaaaaaaffafagaagggagaaaaaaaab",& &"*a*b*ba*ca*a*x*aaa*fa*ga*b*",& &.false.) .and. allpassed allpassed= test(& &"abababababababababababababababababababaacacacacacacacad& &aeafagahaiajakalaaaaaaaaaaaaaaaaaffafagaagggagaaaaaaaab",& &"*a*b*ba*ca*aaaa*fa*ga*gggg*b*",& &.false.) .and. allpassed allpassed= test(& &"abababababababababababababababababababaacacacacacacacad& &aeafagahaiajakalaaaaaaaaaaaaaaaaaffafagaagggagaaaaaaaab",& &"*a*b*ba*ca*aaaa*fa*ga*ggg*b*",& &.true.) .and. allpassed allpassed= test("aaabbaabbaab","*aabbaa*a*",.true.).and.allpassed allpassed= & test("a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*",& &"a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*", .true.) .and. allpassed allpassed= test("aaaaaaaaaaaaaaaaa",& &"*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*", .true.) .and. allpassed allpassed= test("aaaaaaaaaaaaaaaa",& &"*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*a*", .false.) .and. allpassed allpassed= test(& &"abc*abcd*abcde*abcdef*abcdefg*abcdefgh*abcdefghi*abcdefghij& &*abcdefghijk*abcdefghijkl*abcdefghijklm*abcdefghijklmn",& & "abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*abc& &*abc*abc*abc*",& &.false.) .and. allpassed allpassed= test(& &"abc*abcd*abcde*abcdef*abcdefg*abcdefgh*abcdefghi*abcdefghij& &*abcdefghijk*abcdefghijkl*abcdefghijklm*abcdefghijklmn",& &"abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*",& &.true.) .and. allpassed allpassed= test("abc*abcd*abcd*abc*abcd",& &"abc*abc*abc*abc*abc", .false.) .and. allpassed allpassed= test( "abc*abcd*abcd*abc*abcd*abcd& &*abc*abcd*abc*abc*abcd", & &"abc*abc*abc*abc*abc*abc*abc*abc*abc*abc*abcd",& &.true.) .and. allpassed allpassed= test("abc",& &"********a********b********c********", .true.) .and. allpassed allpassed=& &test("********a********b********c********", "abc",.false.)& & .and.allpassed allpassed= & &test("abc", "********a********b********b********",.false.)& & .and.allpassed allpassed= test("*abc*", "***a*b*c***", .true.) .and. allpassed
! A case-insensitive algorithm test. ! allpassed=test("mississippi", "*issip*PI", .true.) .and. allpassed enddo
if (allpassed)then write(*,’(*(g0,1x))’)"Passed",nReps else write(*,’(a)’)"Failed" endif contains ! This is a test program for wildcard matching routines. ! It can be used either to test a single routine for correctness, ! or to compare the timings of two (or more) different wildcard ! matching routines. ! function test(tame, wild, bExpectedResult) result(bPassed) use M_strings, only : glob character(len=*) :: tame character(len=*) :: wild logical :: bExpectedResult logical :: bResult logical :: bPassed bResult = .true. ! We’ll do "&=" cumulative checking. bPassed = .false. ! Assume the worst. write(*,*)repeat(’=’,79) bResult = glob(tame, wild) ! Call a wildcard matching routine.
! To assist correctness checking, output the two strings in any ! failing scenarios. if (bExpectedResult .eqv. bResult) then bPassed = .true. if(nReps == 1) write(*,*)"Passed match on ",tame," vs. ", wild else if(nReps == 1) write(*,*)"Failed match on ",tame," vs. ", wild endif
end function test end program demo_glob
John S. Urban
The article "Matching Wildcards: An Empirical Way to Tame an Algorithm" in Dr Dobb’s Journal, By Kirk J. Krauss, October 07, 2014
Public Domain
indent(3f) - [M_strings:WHITESPACE] count number of leading spaces in a string (LICENSE:PD)
Synopsis
Description
Examples
Author
License
function indent(line)
integer :: indent character(len=*),intent(in) :: line
Count number of leading spaces in a CHARACTER variable.
Sample Program:
program demo_indent ! test filter to count leading spaces in a character variable ! might want to call notabs(3f) to expand tab characters use M_strings, only : indent implicit none character(len=1024) :: in integer :: iostat READFILE: do read(*,’(A)’,iostat=iostat)in if(iostat /= 0) exit READFILE write(*,’(i3,"",a)’)indent(in),trim(in) enddo READFILE end program demo_indentResults:
> 3 a b c > 0a b c > 6 a b c
John S. Urban
Public Domain
int(3f) - [M_strings:TYPE] overloads INT(3f) so it can handle character arguments (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
impure elemental function int(string)
character(len=*) :: string integer(kind=int32) :: int
int(3f) returns an integer when given a numeric representation of a numeric value. This overloads the INT(3f) intrinsic so that CHARACTER arguments assumed to represent a numeric value may be input.
STRING input string to be converted to an INT32 integer
INT integer represented by input string
Sample program:
program demo_int use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 use M_strings, only: int implicit none character(len=*),parameter :: g=’(*(g0,1x))’ write(*,g)int(’100’),int(’20.4’) write(*,g)’intrinsic int(3f) still works’,int(20,int32) write(*,g)’elemental’,& & int([character(len=23) :: ’10’,’20.3’,’20.5’,’20.6’]) end program demo_intResults:
> 100 20 > intrinsic int(3f) still works 20 > elemental 10 20 20 20
John S. Urban
Public Domain
isalnum,isalpha,iscntrl,isdigit,isgraph,islower, isprint,ispunct,isspace,isupper, isascii,isblank,isxdigit(3f) - [M_strings:COMPARE] test membership in subsets of ASCII set (LICENSE:PD)
Synopsis
Description
Examples
Author
License
Where "FUNCNAME" is one of the function names in the group, the functions are defined by
elemental function FUNCNAME(onechar) character,intent(in) :: onechar logical :: FUNC_NAME
These elemental functions test if a character belongs to various subsets of the ASCII character set.
isalnum returns .true. if character is a letter (a-z,A-Z) or digit (0-9) isalpha returns .true. if character is a letter and [char46]false. otherwise isascii returns .true. if character is in the range char(0) to char(127) isblank returns .true. if character is a blank (space or horizontal tab). iscntrl returns .true. if character is a delete character or ordinary control character (0x7F or 0x00-0x1F). isdigit returns .true. if character is a digit (0,1,...,9) and .false. otherwise isgraph returns .true. if character is a printable ASCII character excluding space islower returns .true. if character is a miniscule letter (a-z) isprint returns .true. if character is a printable ASCII character ispunct returns .true. if character is a printable punctuation character (isgraph(c) && !isalnum(c)). isspace returns .true. if character is a null, space, tab, carriage return, new line, vertical tab, or formfeed isupper returns .true. if character is an uppercase letter (A-Z) isxdigit returns .true. if character is a hexadecimal digit (0-9, a-f, or A-F).
Sample Program:
program demo_isdigitExpected output:use M_strings, only : isdigit, isspace, switch implicit none character(len=10),allocatable :: string(:) integer :: i string=[& & ’1 2 3 4 5 ’ ,& & ’letters ’ ,& & ’1234567890’ ,& & ’both 8787 ’ ] ! if string is nothing but digits and whitespace return .true. do i=1,size(string) write(*,’(a)’,advance=’no’)’For string[’//string(i)//’]’ write(*,*) & all(isdigit(switch(string(i))) .or. & & isspace(switch(string(i)))) enddo
end program demo_isdigit
For string[1 2 3 4 5 ] T For string[letters ] F For string[1234567890] T For string[both 8787 ] F
John S. Urban
Public Domain
isalpha(3f) - [M_strings:COMPARE] returns .true. if character is a letter and .false. otherwise (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isalpha(onechar)
character,intent(in) :: onechar logical :: isalpha
isalpha(3f) returns .true. if character is a letter and [char46]false. otherwise
onechar character to test
isalpha logical value returns .true. if character is a ASCII letter or false otherwise.
Sample program
program demo_isalpha use M_strings, only : isalpha implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(40(a))’)’ISGRAPH: ’,pack( string, isalpha(string) ) end program demo_isalphaResults:
ISGRAPH: ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklm nopqrstuvwxyz
John S. Urban
Public Domain
isascii(3f) - [M_strings:COMPARE] returns .true. if the character is in the range char(0) to char(256) (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isascii(onechar)
character,intent(in) :: onechar logical :: isascii
isascii(3f) returns .true. if the character is in the range char(0) to char(127)
onechar character to test
isupper logical value returns true if character is an ASCII character.
Sample program
program demo_isascii use M_strings, only : isascii implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,255)] write(*,’(10(g0,1x))’)’ISASCII: ’, & & iachar(pack( string, isascii(string) )) end program demo_isasciiResults:
ISASCII: 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127
John S. Urban
Public Domain
isblank(3f) - [M_strings:COMPARE] returns .true. if character is a blank character (space or horizontal tab). (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isblank(onechar)
character,intent(in) :: onechar logical :: isblank
isblank(3f) returns .true. if character is a blank character (space or horizontal tab).
onechar character to test
isblank logical value returns true if character is a "blank"
( an ASCII space or horizontal tab character).
Sample program:
program demo_isblank use M_strings, only : isblank implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(*(g0,1x))’)’ISXBLANK: ’,& & iachar(pack( string, isblank(string) )) end program demo_isblankResults:
ISXBLANK: 9 32
John S. Urban
Public Domain
iscntrl(3f) - [M_strings:COMPARE] returns .true. if character is a delete character or ordinary control character (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function iscntrl(onechar)
character,intent(in) :: onechar logical :: iscntrl
iscntrl(3f) returns .true. if character is a delete character or ordinary control character
onechar character to test
iscntrl logical value returns true if character is a control character
Sample program
program demo_iscntrl use M_strings, only : iscntrl implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(20(g0,1x))’)’ISCNTRL: ’, & & iachar(pack( string, iscntrl(string) )) end program demo_iscntrlResults:
ISCNTRL: 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 127
John S. Urban
Public Domain
isdigit(3f) - [M_strings:COMPARE] returns .true. if character is a digit (0,1,...,9) and .false. otherwise (LICENSE:PD)
Synopsis
Description
Examples
Author
License
elemental function isdigit(onechar)
character,intent(in) :: onechar logical :: isdigit
isdigit(3f) returns .true. if character is a digit (0,1,...,9) and .false. otherwise
Sample Program:
program demo_isdigit use M_strings, only : isdigit, isspace, switch implicit none character(len=10),allocatable :: string(:) integer :: i string=[& & ’1 2 3 4 5 ’ ,& & ’letters ’ ,& & ’1234567890’ ,& & ’both 8787 ’ ] ! if string is nothing but digits and whitespace return .true. do i=1,size(string) write(*,’(a)’,advance=’no’)’For string[’//string(i)//’]’ write(*,*) & & all(isdigit(switch(string(i))).or.& & isspace(switch(string(i)))) enddo end program demo_isdigitExpected output:
For string[1 2 3 4 5 ] T For string[letters ] F For string[1234567890] T For string[both 8787 ] F
John S. Urban
Public Domain
isgraph(3f) - [M_strings:COMPARE] returns .true. if character is a printable character except a space is considered non-printable (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isgraph(onechar)
character,intent(in) :: onechar logical :: isgraph
isgraph(3f) returns .true. if character is a printable character except a space is considered non-printable
onechar character to test
isgraph logical value returns true if character is a printable non-space character
Sample Program:
program demo_isgraph use M_strings, only : isgraph implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(40(a))’)’ISGRAPH: ’,pack( string, isgraph(string) ) end program demo_isgraphResults:
ISGRAPH: !"#$%&’()*+,-./0123456789:;<=>?@ABCDEFG HIJKLMNOPQRSTUVWXYZ[\]^_‘abcdefghijklmno pqrstuvwxyz{|}~
John S. Urban
Public Domain
islower(3f) - [M_strings:COMPARE] returns .true. if character is a miniscule letter (a-z) (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function islower(onechar)
character,intent(in) :: onechar logical :: islower
islower(3f) returns .true. if character is a miniscule letter (a-z)
onechar character to test
islower logical value returns true if character is a lowercase ASCII character else false.
Sample program
program demo_islower use M_strings, only : islower implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(15(g0,1x))’)’ISLOWER: ’, & & iachar(pack( string, islower(string) )) write(*,’(15(g0,1x))’)’ISLOWER: ’, & & pack( string, islower(string) ) end program demo_islowerResults:
ISLOWER: 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 ISLOWER: a b c d e f g h i j k l m n o p q r s t u v w x y z
John S. Urban
Public Domain
isnumber(3f) - [M_strings:TYPE] determine if a string represents a number (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function isnumber(str,msg)
character(len=*),intent(in) :: str character(len=:),intent(out),allocatable,optional :: msg
ISNUMBER(3f) returns a value greater than zero if the string represents a number, and a number less than or equal to zero if it is a bad number. Blank characters are ignored.
str the string to evaluate as to whether it represents a numeric value or not msg An optional message describing the string
values less than 1 represent an error
isnumber the following values are returned
1 for an integer [-+]NNNNN 2 for a whole number [-+]NNNNN. 3 for a real value [-+]NNNNN.MMMM 4 for a exponential value [-+]NNNNN.MMMM[-+]LLLL [-+]NNNNN.MMMM[ed][-+]LLLL
As the example shows, you can use an internal READ(3f) along with the IOSTAT= parameter to check (and read) a string as well.
program demo_isnumber use M_strings, only : isnumber implicit none character(len=256) :: line real :: value integer :: ios1, ios2 integer :: answer character(len=256) :: message character(len=:),allocatable :: description write(*,*)’Begin entering values, one per line’ do read(*,’(a)’,iostat=ios1)line ! ! try string as number using list-directed input line=’’ read(line,*,iostat=ios2,iomsg=message) value if(ios2 == 0)then write(*,*)’VALUE=’,value elseif( is_iostat_end(ios1) ) then stop ’end of file’ else write(*,*)’ERROR:’,ios2,trim(message) endif ! ! try string using isnumber(3f) answer=isnumber(line,msg=description) if(answer > 0)then write(*,*) & & ’ for ’,trim(line),’ ’,answer,’:’,description else write(*,*) & & ’ ERROR for ’,trim(line),’ ’,answer,’:’,description endif ! enddo end program demo_isnumberExample run
> Begin entering values > ERROR: -1 End of file > ERROR for -1 :null string >10 > VALUE= 10.0000000 > for 10 1 :integer >20 > VALUE= 20.0000000 > for 20 1 :integer >20. > VALUE= 20.0000000 > for 20. 2 :whole number >30.1 > VALUE= 30.1000004 > for 30.1 3 :real number >3e1 > VALUE= 30.0000000 > for 3e1 4 :value with exponent >1-2 > VALUE= 9.99999978E-03 > for 1-2 4 :value with exponent >100.22d-4 > VALUE= 1.00220004E-02 > for 100.22d-4 4 :value with exponent >1--2 > ERROR: 5010 Bad real number in item 1 of list input > ERROR for 1--2 -5 :bad number >e > ERROR: 5010 Bad real number in item 1 of list input > ERROR for e -6 :missing leading value before exponent >e1 > ERROR: 5010 Bad real number in item 1 of list input > ERROR for e1 -6 :missing leading value before exponent >1e > ERROR: 5010 Bad real number in item 1 of list input > ERROR for 1e -3 :missing exponent >1e+ > ERROR: 5010 Bad real number in item 1 of list input > ERROR for 1e+ -4 :missing exponent after sign >1e+2.0 > ERROR: 5010 Bad real number in item 1 of list input > ERROR for 1e+2.0 -5 :bad number
John S. Urban
Public Domain
isprint(3f) - [M_strings:COMPARE] returns .true. if character is an ASCII printable character (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isprint(onechar)
character,intent(in) :: onechar logical :: isprint
isprint(3f) returns .true. if character is an ASCII printable character
onechar character to test
isprint logical value returns true if character is a printable ASCII character else false.
Sample Program:
program demo_isprint use M_strings, only : isprint implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(40(a))’)’ISPRINT: ’,pack( string, isprint(string) ) end program demo_isprintResults:
ISPRINT: !"#$%&’()*+,-./0123456789:;<=>?@ABCDEF GHIJKLMNOPQRSTUVWXYZ[\]^_‘abcdefghijklmn opqrstuvwxyz{|}~
John S. Urban
Public Domain
ispunct(3f) - [M_strings:COMPARE] returns .true. if character is a printable punctuation character (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function ispunct(onechar)
character,intent(in) :: onechar logical :: ispunct
ispunct(3f) returns .true. if character is a printable punctuation character
onechar character to test
ispunct logical value returns true if character is a printable punctuation character.
Sample program:
program demo_ispunct use M_strings, only : ispunct implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(20(g0,1x))’)’ISPUNCT: ’, & & iachar(pack( string, ispunct(string) )) write(*,’(20(g0,1x))’)’ISPUNCT: ’, & & pack( string, ispunct(string) ) end program demo_ispunctResults:
ISPUNCT: 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 58 59 60 61 62 63 64 91 92 93 94 95 96 123 124 125 126 ISPUNCT: ! " # $ % & ’ ( ) * + , - . / : ; < = > ? @ [ \ ] ^ _ ‘ { | } ~
John S. Urban
Public Domain
isspace(3f) - [M_strings:COMPARE] returns .true. if character is a null, space, tab, carriage return, new line, vertical tab, or formfeed (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isspace(onechar)
character,intent(in) :: onechar logical :: isspace
isspace(3f) returns .true. if character is a null, space, tab, carriage return, new line, vertical tab, or formfeed
onechar character to test
isspace returns true if character is ASCII white space
Sample program:
program demo_isspace use M_strings, only : isspace implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(20(g0,1x))’)’ISSPACE: ’, & & iachar(pack( string, isspace(string) )) end program demo_isspaceResults:
ISSPACE: 0 9 10 11 12 13 32
John S. Urban
Public Domain
isupper(3f) - [M_strings:COMPARE] returns .true. if character is an uppercase letter (A-Z) (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isupper(onechar)
character,intent(in) :: onechar logical :: isupper
isupper(3f) returns .true. if character is an uppercase letter (A-Z)
onechar character to test
isupper logical value returns true if character is an uppercase ASCII character else false.
Sample program:
program demo_isupper use M_strings, only : isupper implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(10(g0,1x))’)’ISUPPER: ’, & & iachar(pack( string, isupper(string) )) write(*,’(10(g0,1x))’)’ISUPPER: ’, & & pack( string, isupper(string) ) end program demo_isupperResults:
> ISUPPER: 65 66 67 68 69 70 71 72 73 > 74 75 76 77 78 79 80 81 82 83 > 84 85 86 87 88 89 90 > ISUPPER: A B C D E F G H I > J K L M N O P Q R S > T U V W X Y Z
John S. Urban
Public Domain
isxdigit(3f) - [M_strings:COMPARE] returns .true. if character is a hexadecimal digit (0-9, a-f, or A-F). (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
elemental function isxdigit(onechar)
character,intent(in) :: onechar logical :: isxdigit
isxdigit(3f) returns .true. if character is a hexadecimal digit (0-9, a-f, or A-F).
onechar character to test
isxdigit logical value returns true if character is a hexadecimal digit
Sample program
program demo_isxdigit use M_strings, only : isxdigit implicit none integer :: i character(len=1),parameter :: string(*)=[(char(i),i=0,127)] write(*,’(40(a))’)’ISXDIGIT: ’,pack( string, isxdigit(string) ) end program demo_isxdigitResults:
ISXDIGIT: 0123456789ABCDEFabcdef
John S. Urban
Public Domain
join(3f) - [M_strings:EDITING] append CHARACTER variable array into a single CHARACTER variable with specified separator (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
pure function join(str,sep,trm,left,right,start,end) result (string)
character(len=*),intent(in) :: str(:) character(len=*),intent(in),optional :: sep logical,intent(in),optional :: trm character(len=*),intent(in),optional :: right character(len=*),intent(in),optional :: left character(len=*),intent(in),optional :: start character(len=*),intent(in),optional :: end character(len=:),allocatable :: string
JOIN(3f) appends the elements of a CHARACTER array into a single CHARACTER variable, with elements 1 to N joined from left to right. By default each element is trimmed of trailing spaces and the default separator is a null string.
STR(:) array of CHARACTER variables to be joined SEP separator string to place between each variable. defaults to a null string. LEFT string to place at left of each element RIGHT string to place at right of each element START prefix string END suffix string TRM option to trim each element of STR of trailing spaces. Defaults to .TRUE.
STRING CHARACTER variable composed of all of the elements of STR() appended together with the optional separator SEP placed between the elements.
Sample program:
program demo_join use M_strings, only: join implicit none character(len=*),parameter :: w=’(/,*(g0,/,g0))’ character(len=:),allocatable :: s(:) s=[character(len=10) :: & & ’ United’, & & ’we’, & & ’stand,’, & & ’divided’, & & ’we fall.’] write(*,w) ’SIMPLE JOIN: ’,& join(s) write(*,w) ’SIMPLE JOIN WITH SEPARATOR: ’,& join(s,sep=’ ’) write(*,w) ’CUSTOM SEPARATOR: ’,& join(s,sep=’==>’) write(*,w) ’LEFT AND RIGHT AND SEPARATOR: ’,& join(s,sep=’;’,left=’[’,right=’]’) write(*,w) ’NO TRIMMING: ’,& join(s,trm=.false.) write(*,w) ’LEFT AND RIGHT: ’,& join(s,left=’[’,right=’]’) write(*,w) ’START,END AND EVERYTHING: ’,& join(s,trm=.false.,sep=’,’,start=’[’,end=’]’,left=’"’,right=’"’) write(*,w) ’TABLE’ call line() write(*,’(a)’) join(s(1:3),trm=.false.,sep=’|’,start=’|’,end=’|’) write(*,’(a)’) join([s(4:5),repeat(’ ’,len(s))],& & trm=.false.,sep=’|’,start=’|’,end=’|’) call line() contains subroutine line() integer :: i write(*,’(a)’) join([(repeat(’-’,len(s)),i=1,3)],& & sep=’#’,start=’#’,end=’#’) end subroutine line end program demo_joinResults:
> > SIMPLE JOIN: > Unitedwestand,dividedwe fall. > > SIMPLE JOIN WITH SEPARATOR: > United we stand, divided we fall. > > CUSTOM SEPARATOR: > United==>we==>stand,==>divided==>we fall. > > LEFT AND RIGHT AND SEPARATOR: > [ United];[we];[stand,];[divided];[we fall.] > > NO TRIMMING: > United we stand, divided we fall. > > LEFT AND RIGHT: > [ United][we][stand,][divided][we fall.] > > START,END AND EVERYTHING: > [" United ","we ","stand, ","divided ","we fall. "] > > TABLE > > #----------#----------#----------# > | United |we |stand, | > |divided |we fall. | | > #----------#----------#----------#
John S. Urban
Public Domain
len_white(3f) - [M_strings:LENGTH] get length of string trimmed of whitespace. (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Notes
Author
License
elemental integer function len_white(string)
character(len=*) :: string
len_white(3f) returns the position of the last character in string that is not a whitespace character. The Fortran90 intrinsic LEN_TRIM(3) should be used when trailing whitespace can be assumed to always be spaces.This procedure was heavily used in the past because ANSI FORTRAN 77 character objects are fixed length and blank padded and the LEN_TRIM(3) intrinsic did not exist. It should now be used only when whitespace characters other than blanks are likely.
string input string whose trimmed length is being calculated ignoring all trailing whitespace characters.
len_white the number of characters in the trimmed string
Sample Program:
program demo_len_whiteResults:use M_strings, only : len_white implicit none character(len=80) :: s integer :: lgth, lastnb intrinsic len
s=’ ABCDEFG abcdefg ’ lgth = len(s) lastnb = len_white(s)
write(*,*) ’total length of variable is ’,lgth write(*,*) ’trimmed length of variable is ’,lastnb write(*,*) ’trimmed string=[’,s(:lastnb),’]’
end program demo_len_white
total length of variable is 80 trimmed length of variable is 16 trimmed string=[ ABCDEFG abcdefg]
o len_white is a resource-intensive routine. Once the end of the string is found, it is probably best to keep track of it in order to avoid repeated calls to len_white. Because they might be more efficient, consider looking for vendor-supplied or system-optimized equivalents. For example:o lnblnk - Solaris f77 o len_trim - FORTRAN 90
o Some compilers seem to have trouble passing a string of variable length properly. To be safe, use something like this: subroutine message(s) character(len=*) :: s ! s is of variable length lgth=len(s) ! get total length of variable ! explicitly specify a substring instead of just variable name lastnb = len_white(s(:lgth)) write(*,*)’error:[’,s(:lastnb),’]’ end subroutine messages
John S. Urban
Public Domain
lenset(3f) - [M_strings:LENGTH] return string trimmed or padded to specified length (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function lenset(str,length) result(strout)
character(len=*) :: str character(len=length) :: strout integer,intent(in) :: length
lenset(3f) truncates a string or pads it with spaces to the specified length.
str input string length output string length
strout output string
Sample Program:
program demo_lenset use M_strings, only : lenset implicit none character(len=10) :: string=’abcdefghij’ character(len=:),allocatable :: answer answer=lenset(string,5) write(*,’("[",a,"]")’) answer answer=lenset(string,20) write(*,’("[",a,"]")’) answer end program demo_lensetExpected output:
[abcde] [abcdefghij ]
John S. Urban
Public Domain
listout(3f) - [M_strings:NUMERIC] expand a list of numbers where negative numbers denote range ends (1 -10 means 1 thru 10) (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
subroutine listout(icurve_lists,icurve_expanded,inums,ierr)
integer,intent(in) :: icurve_lists(:) integer,intent(out) :: icurve_expanded(:) integer,intent(out) :: inums integer,intent(out) :: ierr
expand a list of whole numbers where negative numbers indicate a range. So [10,-20] would be expanded to [10,11,12,13,14,15,16,17,18,19,20].
icurve_lists(:) input array
icurve_expanded(:) output array; assumed large enough to hold returned list inums number of icurve_expanded numbers on output ierr zero if no error occurred
Sample program:
program demo_listout use M_strings, only : listout implicit none integer,allocatable :: icurve_lists(:) integer :: icurve_expanded(1000) ! icurve_lists is input array integer :: inums ! icurve_expanded is output array integer :: i ! number of icurve_lists values on input, ! number of icurve_expanded numbers on output integer :: ierr icurve_lists=[1, 20, -30, 101, 100, 99, 100, -120, 222, -200] inums=size(icurve_lists) call listout(icurve_lists,icurve_expanded,inums,ierr) if(ierr == 0)then write(*,’(i0)’)(icurve_expanded(i),i=1,inums) else write(*,’(a,i0)’)’error occurred in *listout* ’,ierr write(*,’(i0)’)(icurve_expanded(i),i=1,inums) endif end program demo_listoutResults:
> 1 20 21 22 23 > 24 25 26 27 28 > 29 30 101 100 99 > 100 101 102 103 104 > 105 106 107 108 109 > 110 111 112 113 114 > 115 116 117 118 119 > 120 222 221 220 219 > 218 217 216 215 214 > 213 212 211 210 209 > 208 207 206 205 204 > 203 202 201 200
John S. Urban
Public Domain
longest_common_substring(3f) - [M_strings:COMPARE] function that returns the longest common substring of two strings.
Synopsis
Description
Options
Returns
Examples
function longest_common_substring(a,b) result(match)
character(len=*),intent(in) :: a, b character(len=:),allocatable :: match
function that returns the longest common substring of two strings.Note that substrings are consecutive characters within a string. This distinguishes them from subsequences, which is any sequence of characters within a string, even if there are extraneous characters in between them.
Hence, the longest common subsequence between "thisisatest" and "testing123testing" is "tsitest", whereas the longest common substring is just "test".
a,b strings to search for the longest common substring.
longest_common_substring the longest common substring found
Sample program
program demo_longest_common_substring use M_strings, only : longest_common_substring implicit none call compare(’testing123testingthing’,’thisis’, ’thi’) call compare(’testing’, ’sting’, ’sting’) call compare(’thisisatest_stinger’,’testing123testingthing’,’sting’) call compare(’thisisatest_stinger’, ’thisis’, ’thisis’) call compare(’thisisatest’, ’testing123testing’, ’test’) call compare(’thisisatest’, ’thisisatest’, ’thisisatest’) containsexpected outputsubroutine compare(a,b,answer) character(len=*),intent(in) :: a, b, answer character(len=:),allocatable :: match character(len=*),parameter :: g=’(*(g0))’ match=longest_common_substring(a,b) write(*,g) ’comparing "’,a,’" and "’,b,’"’ write(*,g) merge(’(PASSED) "’,’(FAILED) "’,answer == match), & & match,’"; expected "’,answer,’"’ end subroutine compare
end program demo_longest_common_substring
comparing "testing123testingthing" and "thisis" (PASSED) "thi"; expected "thi" comparing "testing" and "sting" (PASSED) "sting"; expected "sting" comparing "thisisatest_stinger" and "testing123testingthing" (PASSED) "sting"; expected "sting" comparing "thisisatest_stinger" and "thisis" (PASSED) "thisis"; expected "thisis" comparing "thisisatest" and "testing123testing" (PASSED) "test"; expected "test" comparing "thisisatest" and "thisisatest" (PASSED) "thisisatest"; expected "thisisatest"
lower(3f) - [M_strings:CASE] changes a string to lowercase over specified range (LICENSE:PD)
Synopsis
Description
Options
Returns
Trivia
Examples
Author
License
elemental pure function lower(str,begin,end) result (string)
character(*), intent(in) :: str integer,optional :: begin, end character(len(str)) :: string ! output string
lower(str) returns a copy of the ASCII input string with all characters converted to miniscule (ie. "lowercase") over the specified range, If no range is specified the entire string is converted to miniscule.
str string to convert to miniscule begin optional starting position in "str" to begin converting to miniscule. Defaults to the beginning of the string (ie. "1"). end optional ending position in "str" to stop converting to miniscule. Defaults to the end of the string (ie. "len(str)").
lower copy of the entire input string with all characters converted to miniscule over optionally specified range.
The terms "uppercase" and "lowercase" date back to the early days of the mechanical printing press. Individual metal alloy casts of each needed letter or punctuation symbol were meticulously added to a press block, by hand, before rolling out copies of a page. These metal casts were stored and organized in wooden cases. The more-often-needed miniscule letters were placed closer to hand, in the lower cases of the work bench. The less often needed, capitalized, majuscule letters, ended up in the harder to reach upper cases.
Sample program:
program demo_lower use M_strings, only: lower implicit none character(len=:),allocatable :: s s=’ ABCDEFG abcdefg ’ write(*,*) ’mixed-case input string is ....’,s write(*,*) ’lower-case output string is ...’,lower(s) end program demo_lowerExpected output
mixed-case input string is .... ABCDEFG abcdefg lower-case output string is ... abcdefg abcdefg
John S. Urban
Public Domain
lower_quoted(3f) - [M_strings:CASE] elemental function converts string to lowercase skipping strings quoted per Fortran syntax rules (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
See Also
Author
License
elemental pure function lower_quoted(str) result (string)
character(*), intent(in) :: str character(len(str)) :: string ! output string
lower_quoted(string) returns a copy of the input string with all not-quoted characters converted to lowercase, assuming ASCII character sets are being used. The quoting rules are the same as for Fortran source. Either a single or double quote starts a quoted string, and a quote character of the same type is doubled when it appears internally in the quoted string. If a double quote quotes the string single quotes may appear in the quoted string as single characters, and vice-versa for single quotes.
str string to convert to lowercase
lower copy of the input string with all unquoted characters converted to lowercase
Sample program:
program demo_lower_quoted use M_strings, only: lower_quoted implicit none character(len=:),allocatable :: s s=’ ABCDEFG abcdefg "Double-Quoted" ’’Single-Quoted’’ "with ""& & Quote" everything else’ write(*,*) ’mixed-case input string is ....’,s write(*,*) ’lower-case output string is ...’,lower_quoted(s) write(*,’(1x,a,*(a:,"+"))’) ’lower_quoted(3f) is elemental ==>’, & & lower_quoted(["abc","def","ghi"]) end program demo_lower_quotedResults:
> mixed-case input string is .... ABCDEFG abcdefg "Double-Quoted" ... ... ’Single-Quoted’ "with "" Quote" everything else > lower-case output string is ... abcdefg abcdefg "Double-Quoted" ... ... ’Single-Quoted’ "with "" Quote" everything else > lower_quoted(3f) is elemental ==>abc+def+ghi
flower(1)
John S. Urban
Public Domain
lpad(3f) - [M_strings:LENGTH] convert to a cropped string and then blank-pad on the left to requested length (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function lpad(valuein,length) result(strout)
class*,intent(in) :: valuein(..) integer,intent(in) :: length
lpad(3f) converts a scalar value to a cropped string and then pads it on the left with spaces to at least the specified length. If the trimmed input is longer than the requested length the string is returned trimmed of leading and trailing spaces.
str The input may be scalar or a vector. the input value to return as a string, padded on the left to the specified length if shorter than length. The input may be any intrinsic scalar which is converted to a cropped string much as if written with list-directed output. length The minimum string length to return
strout The input string padded to the requested length on the left with spaces.
Sample Program:
program demo_lpad use M_strings, only : lpad implicit none write(*,’("[",a,"]")’) lpad( ’my string’, 20) write(*,’("[",a,"]")’) lpad( ’my string ’, 20) write(*,’("[",a,"]")’) lpad( ’ my string’, 20) write(*,’("[",a,"]")’) lpad( ’ my string ’, 20) write(*,’("[",a,"]")’) lpad( valuein=42 , length=7) write(*,’("[",a,"]")’) lpad( valuein=1.0/9.0 , length=20) end program demo_lpadResults:
> [ my string] > [ my string] > [ my string] > [ my string] > [ 42] > [ 0.111111112]
John S. Urban
Public Domain
matching_delimiter(3f) - [M_strings:QUOTES] find position of matching delimiter (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
impure elemental subroutine matching_delimiter(str,ipos,imatch)
character(len=*),intent(in) :: str integer,intent(in) :: ipos integer,intent(out) :: imatch
Sets imatch to the position in string of the delimiter matching the delimiter in position ipos. Allowable delimiters are (), [], {}, <>.
str input string to locate delimiter position in ipos position of delimiter to find match for imatch location of matching delimiter. If no match is found, zero (0) is returned.
Sample program:
program demo_matching_delimiter use M_strings, only : matching_delimiter implicit none character(len=128) :: str integer :: imatchstr=’ a [[[[b] and ] then ] finally ]’ write(*,*)’string=’,str call matching_delimiter(str,1,imatch) write(*,*)’location=’,imatch call matching_delimiter(str,4,imatch) write(*,*)’location=’,imatch call matching_delimiter(str,5,imatch) write(*,*)’location=’,imatch call matching_delimiter(str,6,imatch) write(*,*)’location=’,imatch call matching_delimiter(str,7,imatch) write(*,*)’location=’,imatch call matching_delimiter(str,32,imatch) write(*,*)’location=’,imatch
end program demo_matching_delimiter
John S. Urban
Public Domain
merge_str(3f) - [M_strings:LENGTH] pads strings to same length and then calls MERGE(3f) (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function merge_str(str1,str2,expr) result(strout)
character(len=*),intent(in),optional :: str1 character(len=*),intent(in),optional :: str2 logical,intent(in) :: expr character(len=:),allocatable :: strout
merge_str(3f) pads the shorter of str1 and str2 to the longest length of str1 and str2 and then calls MERGE(padded_str1,padded_str2,expr). It trims trailing spaces off the result and returns the trimmed string. This makes it easier to call MERGE(3f) with strings, as MERGE(3f) requires the strings to be the same length.NOTE: STR1 and STR2 are always required even though declared optional. this is so the call "STR_MERGE(A,B,present(A))" is a valid call. The parameters STR1 and STR2 when they are optional parameters can be passed to a procedure if the options are optional on the called procedure.
STR1 string to return if the logical expression EXPR is true STR2 string to return if the logical expression EXPR is false EXPR logical expression to evaluate to determine whether to return STR1 when true, and STR2 when false.
MERGE_STR a trimmed string is returned that is otherwise the value of STR1 or STR2, depending on the logical expression EXPR.
Sample Program:
program demo_merge_str use M_strings, only : merge_str implicit none character(len=:), allocatable :: answer answer=merge_str(’first string’, & & ’second string is longer’,10 == 10) write(*,’("[",a,"]")’) answer answer=merge_str(’first string’, & & ’second string is longer’,10 /= 10) write(*,’("[",a,"]")’) answer end program demo_merge_strExpected output
[first string] [second string is longer]
John S. Urban
Public Domain
modif(3f) - [M_strings:EDITING] emulate the MODIFY command from the line editor XEDIT (LICENSE:PD)
Synopsis
Description
Examples
Author
License
subroutine modif(cline,cmod)
character(len=*) :: cline ! input string to change ! directive provides directions on changing string character(len=*) :: cmod
MODIF(3f) Modifies the line currently pointed at using a directive that acts much like a line editor directive. Primarily used to create interactive utilities such as input history editors for interactive line-mode programs.the modify directives are as follows-
Any other character replaces the character above it.
^STRING# Causes the string of characters between the ^ and the next # to be inserted before the characters pointed to by the ^. an ^ or & within the string is treated as a regular character. If the closing # is not specified, MODIF(3f) inserts the remainder of the line as if a # was specified after the last nonblank character. There are two exceptions. the combination ^# causes a # to be inserted before the character pointed to by the ^, and an ^ as the last character of the directives causes a blank to be inserted.
# (When not the first # after an ^) causes the character above it to be deleted. & Replaces the character above it with a space. (SPACE) A space below a character leaves it unchanged.
Example input/output:
THE INPUT LINE........ 10 THIS STRING TO BE MORTIFD THE DIRECTIVES LINE... ^ IS THE# D# ^IE ALTERED INPUT LINE.... 10 THIS IS THE STRING TO BE MODIFIEDSample program:
program demo_modif use M_strings, only : modif implicit none character(len=256) :: line integer :: iostat integer :: count integer :: COMMAND_LINE_LENGTH character(len=:),allocatable :: COMMAND_LINE ! get command name length call get_command_argument(0,length=count) ! get command line length call get_command(length=COMMAND_LINE_LENGTH) ! allocate string big enough to hold command line allocate(character(len=COMMAND_LINE_LENGTH+200) :: COMMAND_LINE) ! get command line as a string call get_command(command=COMMAND_LINE) ! trim leading spaces just in case COMMAND_LINE=adjustl(COMMAND_LINE) ! remove command name COMMAND_LINE=adjustl(COMMAND_LINE(COUNT+2:)) INFINITE: do read(*,’(a)’,iostat=iostat)line if(iostat /= 0)exit call modif(line,COMMAND_LINE) write(*,’(a)’)trim(line) enddo INFINITE end program demo_modif
John S. Urban
Public Domain
nint(3f) - [M_strings:TYPE] overloads NINT(3f) so it can handle character arguments (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
impure elemental function nint(string)
character(len=*) :: string integer :: nint
nint(3f) returns an integer when given a numeric representation of a numeric value. This overloads the NINT(3f) intrinsic so that CHARACTER arguments assumed to represent a numeric value may be input.
STRING input string to be converted to an integer
NINT integer represented by input string
Sample program:
program demo_nint use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64 use M_strings, only: nint implicit none character(len=*),parameter :: g=’(*(g0,1x))’ write(*,g)nint(’100’),nint(’20.4’) write(*,g)’intrinsic nint(3f) still works’,nint(20.4) write(*,g)’elemental’,& & nint([character(len=23) :: ’10’,’20.3’,’20.5’,’20.6’]) end program demo_nintResults:
> 100 20 > intrinsic nint(3f) still works 20 > elemental 10 20 21 21
John S. Urban
Public Domain
noesc(3f) - [M_strings:NONALPHA] convert non-printable characters to a space (LICENSE:PD)
Synopsis
Description
Examples
Author
License
elemental function noesc(INSTR)
character(len=*),intent(in) :: INSTR character(len=len(instr)) :: noesc
Convert non-printable characters to a space.
Sample Program:
program demo_noesccharacters and their ADE (ASCII Decimal Equivalent)use M_strings, only : noesc implicit none character(len=128) :: ascii character(len=128) :: cleared integer :: i ! fill variable with base ASCII character set do i=1,128 ascii(i:i)=char(i-1) enddo cleared=noesc(ascii) write(*,*)’characters and their ADE (ASCII Decimal Equivalent)’ call ade(ascii) write(*,*)’Cleared of non-printable characters’ call ade(cleared) write(*,*)’Cleared string:’ write(*,*)cleared contains subroutine ade(string) implicit none ! the string to print character(len=*),intent(in) :: string ! number of characters in string to print integer :: lgth ! counter used to step thru string integer :: i ! get trimmed length of input string lgth=len_trim(string(:len(string)))
! replace lower unprintable characters with spaces write(*,101)(merge(string(i:i),’ ’,& & iachar(string(i:i)) >= 32 & & .and. & & iachar(string(i:i)) <= 126) & & ,i=1,lgth)
! print ADE value of character underneath it write(*,202) (iachar(string(i:i))/100, i=1,lgth) write(*,202)(mod( iachar(string(i:i)),100)/10,i=1,lgth) write(*,202)(mod((iachar(string(i:i))),10), i=1,lgth) ! format for printing string characters 101 format(*(a1:)) ! format for printing ADE values 202 format(*(i1:)) end subroutine ade end program demo_noesc
Expected output
The string is printed with the ADE value vertically beneath. The original string has all the ADEs from 000 to 127. After NOESC(3f) is called on the string all the "non-printable" characters are replaced with a space (ADE of 032).
> !"#$%&’()*+,-./0123456789 :;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_‘abcdefghijklmnopqrstuvwxyz{|}~ >0000000000000000000000000000000000000000000000000000000000 0000000000000000000000000000000000000000001111111111111111111111111111 >00000000001111111111222222222233333333334444444444555555555566666666 667777777777888888888899999999990000000000111111111122222222 >012345678901234567890123456789012345678901234567890123456789012345678 90123456789012345678901234567890123456789012345678901234567Cleared of non-printable characters
> !"#$%&’()*+,-./0123456789 :;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_‘abcdefghijklmnopqrstuvwxyz{|}~ >0000000000000000000000000000000000000000000000000000000000 000000000000000000000000000000000000000000111111111111111111111111111 >3333333333333333333333333333333333333333444444444455555555 556666666666777777777788888888889999999999000000000011111111112222222 >2222222222222222222222222222222223456789012345678901234567 890123456789012345678901234567890123456789012345678901234567890123456Cleared string:
> !"#$%&’()*+,-./0123456789:;<=>?@ ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_‘abcdefghijklmnopqrstuvwxyz{|}~
John S. Urban
Public Domain
nospace(3f) - [M_strings:WHITESPACE] remove all whitespace from input string (LICENSE:PD)
Synopsis
Description
Examples
Author
License
function nospace(str) - remove all whitespace from input string
character(len=*),intent(in) :: str character(len=:),allocatable :: nospace
nospace(3f) removes space, tab, carriage return, new line, vertical tab, formfeed and null characters (called "whitespace"). The output is returned trimmed.
Sample program:
program demo_nospace use M_strings, only: nospace implicit none character(len=:),allocatable :: s s=’ This is a test ’ write(*,*) ’original input string is ....’,s write(*,*) ’processed output string is ...’,nospace(s) if(nospace(s) == ’Thisisatest’)then write(*,*)’nospace test passed’ else write(*,*)’nospace test error’ endif end program demo_nospaceExpected output
original input string is .... This is a test processed output string is ...Thisisatest nospace test passed
John S. Urban
Public Domain
notabs(3f) - [M_strings:NONALPHA] expand tab characters (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
See Also
Author
License
elemental impure subroutine notabs(instr,outstr,lgth)
character(len=*),intent=(in) :: INSTR character(len=*),intent=(out),optional :: OUTSTR integer,intent=(out),optional :: lgth
NOTABS(3) converts tabs in INSTR to spaces in OUTSTR while maintaining columns. It assumes a tab is set every 8 characters. Trailing spaces are removed.In addition, trailing carriage returns and line feeds are removed (they are usually a problem created by going to and from MSWindows).
What are some reasons for removing tab characters from an input line? Some Fortran compilers have problems with tabs, as tabs are not part of the Fortran character set. Some editors and printers will have problems with tabs. It is often useful to expand tabs in input files to simplify further processing such as tokenizing an input line.
instr Input line to remove tabs from
outstr Output string with tabs expanded. Assumed to be of sufficient length lgth Significant length of returned string. If greater than len(outstr) truncation has occurred.
Sample program:
program demo_notabs use M_strings, only : notabs character(len=255) :: in,out character(len=:),allocatable :: string character(len=1),parameter :: t=char(9) ! horizontal tab integer :: iostat,iout,lun call makefile(lun) ! create scratch file ! read file and expand tabs do read(lun,’(A)’,iostat=iostat)in if(iostat /= 0) exit call notabs(in,out,iout) write(*,’(a)’)out(:iout) enddo string=’one’//t//’two’//t//’three’ call notabs(string,lgth=iout) out=repeat(’ ’,iout) call notabs(string,out) write(*,*)’[’//string//’]’ contains subroutine makefile(lun) integer :: lun integer :: i character(len=80),parameter :: fakefile(*)=[character(len=80) :: & ’col1’//t//’col2’ ,& ’a’//t//’one’ ,& ’bb’//t//’two’ ,& ’ccc’//t//’three’ ,& ’dddd’//t//’four’ ,& ’’] ! create input file open(newunit=lun,status=’scratch’) write(lun,’(a)’)(trim(fakefile(i)),i=1,size(fakefile)) rewind(lun) end subroutine makefile end program demo_notabs‘‘‘
GNU/Unix commands expand(1) and unexpand(1)
John S. Urban
Public Domain
pad(3f) - [M_strings:LENGTH] return string padded to at least specified length (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
See Also
Author
License
function pad(str,length,pattern,right,clip) result(strout)
character(len=*) :: str integer,intent(in) :: length character(len=max(length,len(trim(line)))) :: strout character(len=*),intent(in),optional :: pattern logical,intent(in),optional :: right logical,intent(in),optional :: clip
pad(3f) pads a string with a pattern to at least the specified length. If the trimmed input string is longer than the requested length the trimmed string is returned.
str the input string to return trimmed, but then padded to the specified length if shorter than length length The minimum string length to return pattern optional string to use as padding. Defaults to a space. right if true pads string on the right, else on the left clip trim spaces from input string but otherwise retain length. Except for simple cases you typically would trim the input yourself.
strout The input string padded to the requested length or the trimmed input string if the input string is longer than the requested length.
Sample Program:
program demo_pad use M_strings, only : pad implicit none character(len=10) :: string=’abcdefghij’ character(len=:),allocatable :: answer integer :: i character(len=*),parameter :: g=’(*(g0))’ answer=pad(string,5) write(*,’("[",a,"]")’) answer answer=pad(string,20) write(*,’("[",a,"]")’) answer i=30 write(*,g) write(*,’(1x,a,1x,i0)’) & & pad(’CHAPTER 1 : The beginning ’,i,’.’), 1 , & & pad(’CHAPTER 2 : The end ’,i,’.’), 1234, & & pad(’APPENDIX ’,i,’.’), 1235 write(*,*) write(*,’(1x,a,i7)’) & & pad(’CHAPTER 1 : The beginning ’,i,’.’), 1 , & & pad(’CHAPTER 2 : The end ’,i,’.’), 1234, & & pad(’APPENDIX ’,i,’.’), 1235Results:write(*,g)pad(’12’,5,’0’,right=.false.)
write(*,g)pad(’12345 ’,30,’_’,right=.false.) write(*,g)pad(’12345 ’,30,’_’,right=.false.,clip=.true.) write(*,g)pad(’12345 ’,7,’_’,right=.false.) write(*,g)pad(’12345 ’,7,’_’,right=.false.,clip=.true.) write(*,g)pad(’12345 ’,6,’_’,right=.false.) write(*,g)pad(’12345 ’,6,’_’,right=.false.,clip=.true.) write(*,g)pad(’12345 ’,5,’_’,right=.false.) write(*,g)pad(’12345 ’,5,’_’,right=.false.,clip=.true.) write(*,g)pad(’12345 ’,4,’_’,right=.false.) write(*,g)pad(’12345 ’,4,’_’,right=.false.,clip=.true.) end program demo_pad
> [abcdefghij]
> [abcdefghij > > CHAPTER 1 : The beginning .... 1 > CHAPTER 2 : The end .......... 1234 > APPENDIX ..................... 1235 > > CHAPTER 1 : The beginning .... 1 > CHAPTER 2 : The end .......... 1234 > APPENDIX ..................... 1235 > 00012 > ________________________12345 > _________________________12345 > _12345 > __12345 > 12345 > _12345 > 12345 > 12345 > 12345 > 12345
adjustl(3f), adjustr(3f), repeat(3f), trim(3f), len_trim(3f), len(3f)adjustc(3f), stretch(3f), lpad(3f), rpad(3f), cpad(3f), zpad(3f), lenset(3f)
John S. Urban
Public Domain
paragraph(3f) - [M_strings:TOKENS] break a long line into a paragraph (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function paragraph(source_string,length)
character(len=*),intent(in) :: source_string integer,intent(in) :: length character(allocatable(len=length) :: paragraph(:)
paragraph(3f) breaks a long line into a simple paragraph of specified line length.Given a long string break it on spaces into an array such that no variable is longer than the specified length. Individual words longer than LENGTH will be placed in lines by themselves and the paragraph width will be increased to the length of the longest word.
SOURCE_STRING input string to break into an array of shorter strings on blank delimiters LENGTH length of lines to break the string into.
PARAGRAPH character array filled with data from source_string broken at spaces into variables of length LENGTH.
sample program
program demo_paragraph use M_strings, only : paragraph implicit none character(len=:),allocatable :: paragrph(:) character(len=*),parameter :: string= ’& &one two three four five & &six seven eight & &nine ten eleven twelve & &thirteen fourteen fifteen sixteen & &seventeen’Results:write(*,*)’LEN=’,len(string) write(*,*)’INPUT:’ write(*,*)string
paragrph=paragraph(string,40) write(*,*)’LEN=’,len(paragrph),’ SIZE=’,size(paragrph) write(*,*)’OUTPUT:’ write(*,’(a)’)paragrph
write(*,’(a)’)paragraph(string,0) write(*,’(3x,a)’)paragraph(string,47)
end program demo_paragraph
LEN= 106 INPUT: one two three four five six seven eight nine ten eleven twelve thirteen fourteen fifteen sixteen seventeen LEN= 40 SIZE= 3 OUTPUT:one two three four five six seven eight nine ten eleven twelve thirteen fourteen fifteen sixteen seventeen one two three four five six seven eight nine ten eleven twelve thirteen fourteen fifteen sixteen seventeen one two three four five six seven eight nine ten eleven twelve thirteen fourteen fifteen sixteen seventeen
John S. Urban
Public Domain
percent_decode(3f) - [M_strings:ENCODE] percent-decode strings and character arrays (LICENSE:ISC)
Synopsis
Description
Options
Returns
Examples
Author
function percent_decode(text,exit_code)
character(len=1),intent(in) :: text(:) integer,optional,intent(out) :: exit_code character(len=:),allocatable :: percent_decodeor
function percent_decode(text,exit_code)
character(len=*),intent(in) :: text integer,optional,intent(out) :: exit_code character(len=:),allocatable :: percent_decode
percent_decode(3f) percent-decodes percent-encoded strings or character arrays.
URI containing spaces or most other non-alphanumeric characters must be encoded using percent encoding (aka. URL encoding). This procedure unwinds the encryption.
The characters allowed in a URI are either reserved or unreserved (or a percent character as part of a percent-encoding). Reserved characters are those characters that sometimes have special meaning, while unreserved characters have no such meaning. Using percent-encoding, characters which otherwise would not be allowed are represented using allowed characters. The sets of reserved and unreserved characters and the circumstances under which certain reserved characters have special meaning have changed slightly with each revision of specifications that govern URIs and URI schemes.
According to RFC 3986, the characters in a URL have to be taken from a defined set of unreserved and reserved ASCII characters. Any other characters are not allowed in a URL.
The unreserved characters can be encoded, but should not be. The unreserved characters are:
> ABCDEFGHIJKLMNOPQRSTUVWXYZ > abcdefghijklmnopqrstuvwxyz > 0123456789-_.~The reserved characters have to be encoded only under certain circumstances. The reserved characters are:
> * ’ ( ) ; : @ & = + $ , / ? % # [ ]
SOURCE_STRING string or character array to decode EXIT_CODE non-zero if decoding failed
percent_decode a string holding a percent-decoded copy of the input
Sample program:
program demo_percent_decode use M_strings, only : percent_encode, percent_decode implicit none character(len=:),allocatable :: input,output character(len=*),parameter :: see=’(g0,*("""",g0,"""":))’ character(len=*),parameter :: expected=’& &%01%02%03%04%05%06%07%08%09%0A%0B%0C%0D%0E%0F%10%11%12%13%14%15%& &16%17%18%19%1A%1B%1C%1D%1E%1F%20%21%22%23%24%25%26%27%28%29%2A%2& &B%2C-.%2F0123456789%3A%3B%3C%3D%3E%3F%40ABCDEFGHIJKLMNOPQRSTUVWX& &YZ%5B%5C%5D%5E_%60abcdefghijklmnopqrstuvwxyz%7B%7C%7D~%7F%80%81%& &82%83%84%85%86%87%88%89%8A%8B%8C%8D%8E%8F%90%91%92%93%94%95%96%9& &7%98%99%9A%9B%9C%9D%9E%9F%A0%A1%A2%A3%A4%A5%A6%A7%A8%A9%AA%AB%AC& &%AD%AE%AF%B0%B1%B2%B3%B4%B5%B6%B7%B8%B9%BA%BB%BC%BD%BE%BF%C0%C1%& &C2%C3%C4%C5%C6%C7%C8%C9%CA%CB%CC%CD%CE%CF%D0%D1%D2%D3%D4%D5%D6%D& &7%D8%D9%DA%DB%DC%DD%DE%DF%E0%E1%E2%E3%E4%E5%E6%E7%E8%E9%EA%EB%EC& &%ED%EE%EF%F0%F1%F2%F3%F4%F5%F6%F7%F8%F9%FA%FB%FC%FD%FE%FF%20’ integer :: j input=’[this is a string]’ write(*,see)’INPUT=’,input output=percent_encode(input) write(*,see)’ENCODED=’,output output=percent_decode(output) write(*,see)’DECODED=’,output input=repeat(’ ’,256) do j=0,255 input(j:j)=char(j) enddo output=percent_encode(input) write(*,*)’ENCODING PASSED:’,output==expected output=percent_decode(output) write(*,*)’DECODING PASSED:’,input == output end program demo_percent_decodeResults:
> INPUT="[this is a string]" > ENCODED="%5Bthis%20is%20a%20string%5D" > DECODED="[this is a string]" > ENCODING PASSED: T > DECODING PASSED: T
o based on dm_cgi_encode.f90, Copyright (c) 2023, Philipp Engel o Modified to be more aligned with percent_encode(3f), John S. Urban, 2024
percent_encode(3f) - [M_strings:ENCODE] percent-encode strings and character arrays (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
function percent_encode(text)
character(len=1),intent(in) :: text(:) character(len=;),allocatable :: percent_encodeor
function percent_encode(text)
character(len=*),intent(in) :: text character(len=;),allocatable :: percent_encode
This function percent-encodes ASCII strings or ASCII character arrays. "Reserved" characters are encoded.
URI containing spaces or most other non-alphanumeric characters must be encoded using percent encoding (aka. URL encoding).
The characters allowed in a URI are either reserved or unreserved (or a percent character as part of a percent-encoding). Reserved characters are those characters that sometimes have special meaning, while unreserved characters have no such meaning. Using percent-encoding, characters which otherwise would not be allowed are represented using allowed characters. The sets of reserved and unreserved characters and the circumstances under which certain reserved characters have special meaning have changed slightly with each revision of specifications that govern URIs and URI schemes.
According to RFC 3986, the characters in a URL have to be taken from a defined set of unreserved and reserved ASCII characters. Any other characters are not allowed in a URL.
The unreserved characters can be encoded, but should not be. The unreserved characters are:
> ABCDEFGHIJKLMNOPQRSTUVWXYZ > abcdefghijklmnopqrstuvwxyz > 0123456789-_.~The reserved characters have to be encoded only under certain circumstances. The reserved characters are:
> * ’ ( ) ; : @ & = + $ , / ? % # [ ]
SOURCE_STRING string or character array to encode
percent_encode a string holding a percent-encoded copy of the input
Sample program:
program demo_percent_encode use M_strings, only : percent_encode use, intrinsic :: iso_fortran_env, only : stdout=>output_unit implicit none write(*,*)percent_encode(’[this is a string]’) end program demo_percent_encodeResults:
> %5Bthis%20is%20a%20string%5D
John S. Urban
quote(3f) - [M_strings:QUOTES] add quotes to string as if written with list-directed output (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function quote(str,mode,clip) result (quoted_str)
character(len=*),intent(in) :: str character(len=*),optional,intent(in) :: mode logical,optional,intent(in) :: clip character(len=:),allocatable :: quoted_str
Add quotes to a CHARACTER variable as if it was written using list-directed output. This is particularly useful for processing strings to add to CSV files.
str input string to add quotes to, using the rules of list-directed output (single quotes are replaced by two adjacent quotes) mode alternate quoting methods are supported: DOUBLE default. replace quote with double quotes ESCAPE replace quotes with backslash-quote instead of double quotes
clip default is to trim leading and trailing spaces from the string. If CLIP is .FALSE. spaces are not trimmed
quoted_str The output string, which is based on adding quotes to STR.
Sample program:
program demo_quote use M_strings, only : quote implicit none integer :: i character(len=*),parameter :: f=’(*(g0))’ character(len=:),allocatable :: str character(len=80),parameter :: data(3)=[character(len=80)::& ’test string’,& ’quote="’,& ’"word1" "word2"’] do i=1,size(data) ! the original string write(*,’(a)’)’ORIGINAL ’//trim(data(i))Results:! the string processed by quote(3f) str=quote(data(i)) write(*,’(a)’)’QUOTED ’//str
! write the string list-directed to compare the results write(*,f,advance=’no’) ’LIST DIRECTED’ ! default is often NONE or APOSTROPHE write(*,*,delim=’quote’) trim(data(i)) enddo end program demo_quote
> ORIGINAL test string > QUOTED "test string" > LIST DIRECTED "test string" > ORIGINAL quote=" > QUOTED "quote=""" > LIST DIRECTED "quote=""" > ORIGINAL "word1" "word2" > QUOTED """word1"" ""word2""" > LIST DIRECTED """word1"" ""word2"""
John S. Urban
Public Domain
real(3f) - [M_strings:TYPE] overloads REAL(3f) so it can handle character arguments (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
impure elemental function real(string)
character(len=*) :: string integer :: real
real(3f) returns a REAL value when given a numeric representation of a numeric value. This overloads the REAL(3f) intrinsic so that CHARACTER arguments assumed to represent a numeric value may be input.
STRING input string to be converted to a real value
REAL real value represented by input string
Sample program:
program demo_real use M_strings, only: real implicit none write(*,*)real(’100’),real(’20.4’) write(*,*)’real still works’,real(20) write(*,*)’elemental’,& & real([character(len=23) :: ’10’,’20.3’,’20.5’,’20.6’]) end program demo_realResults:
> 100.000000 20.3999996 > real still works 20.0000000 > elemental 10.0000000 20.2999992 20.5000000 20.6000004
John S. Urban
Public Domain
replace(3f) - [M_strings:EDITING] function replaces one substring for another in string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
syntax:
function replace(targetline,old,new,cmd,& & occurrence, & & repeat, & & ignorecase, & & ierr) result (newline) character(len=*) :: targetline character(len=*),intent(in),optional :: old character(len=*),intent(in),optional :: new character(len=*),intent(in),optional :: cmd integer,intent(in),optional :: occurrence integer,intent(in),optional :: repeat logical,intent(in),optional :: ignorecase integer,intent(out),optional :: ierr character(len=:),allocatable :: newline
Replace one substring for another in string. Either CMD or OLD and NEW must be specified.
targetline input line to be changed old old substring to replace new new substring cmd alternate way to specify old and new string, in the form c/old/new/; where "/" can be any character not in "old" or "new". occurrence if present, start changing at the Nth occurrence of the OLD string. If negative start replacing from the left end of the string. repeat number of replacements to perform. Defaults to a global replacement. ignorecase whether to ignore ASCII case or not. Defaults to .false. .
newline allocatable string returned ierr error code. If ier = -1 bad directive, >= 0 then count of changes made.
Sample Program:
program demo_replace use M_strings, only : replace implicit none character(len=:),allocatable :: lineResults:write(*,*)replace(’Xis is Xe string’,’X’,’th’) write(*,*)replace(’Xis is xe string’,’x’,’th’,ignorecase=.true.) write(*,*)replace(’Xis is xe string’,’X’,’th’,ignorecase=.false.)
! a null old substring means "at beginning of line" write(*,*) replace(’my line of text’,’’,’BEFORE:’)
! a null new string deletes occurrences of the old substring write(*,*) replace(’I wonder i ii iii’,’i’,’’)
! Examples of the use of RANGE
line=replace(’aaaaaaaaa’,’a’,’A’,occurrence=1,repeat=1) write(*,*)’replace first a with A [’//line//’]’
line=replace(’aaaaaaaaa’,’a’,’A’,occurrence=3,repeat=3) write(*,*)’replace a with A for 3rd to 5th occurrence [’//line//’]’
line=replace(’ababababa’,’a’,’’,occurrence=3,repeat=3) write(*,*)’replace a with null instances 3 to 5 [’//line//’]’
line=replace( & & ’a b ab baaa aaaa aa aa a a a aa aaaaaa’,& & ’aa’,’CCCC’,occurrence=-1,repeat=1) write(*,*)’replace lastaa with CCCC [’//line//’]’
write(*,*)replace(’myf90stuff.f90.f90’,’f90’,’for’,occurrence=-1,repeat=1) write(*,*)replace(’myf90stuff.f90.f90’,’f90’,’for’,occurrence=-2,repeat=2)
end program demo_replace
this is the string this is the string this is xe string BEFORE:my line of text I wonder replace first a with A [Aaaaaaaaa] replace a with A for 3rd to 5th occurrence [aaAAAaaaa] replace a with null instances 3 to 5 [ababbb] replace lastaa with CCCC [a b ab baaa aaaa aa aa a a a aa aaaaCCCC] myf90stuff.f90.for myforstuff.for.f90
John S. Urban
Public Domain
reverse(3f) - [M_strings:EDITING] Return a string reversed (LICENSE:PD)
Synopsis
Description
Examples
Author
License
elemental pure function reverse(str) result (string)
character(*), intent(in) :: str character(len(str)) :: string
reverse(string) returns a copy of the input string with all characters reversed from right to left.
Sample program:
program demo_reverse use M_strings, only: reverse implicit none character(len=:),allocatable :: s write(*,*)’REVERSE STRINGS:’,reverse(’Madam, I’’m Adam’) s=’abcdefghijklmnopqrstuvwxyz’ write(*,*) ’original input string is ....’,s write(*,*) ’reversed output string is ...’,reverse(s) end program demo_reverseResults:
> REVERSE STRINGS:madA m’I ,madaM > original input string is ....abcdefghijklmnopqrstuvwxyz > reversed output string is ...zyxwvutsrqponmlkjihgfedcba
John S. Urban
Public Domain
rotate13(3f) - [M_strings:ENCODE] apply trivial ROT13 encryption to a string (LICENSE:PD)
Synopsis
Description
References
Examples
Author
License
rotate13(input) result(output)
character(len=*),intent(in) :: input character(len=len(input)) :: output
ROT13 ("rotate by 13 places", sometimes hyphenated ROT-13) is a simple letter substitution cipher that replaces a letter with the 13th letter after it in the alphabet; wrapping around if necessary.The transformation can be done using a lookup table, such as the following:
Input ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz Output NOPQRSTUVWXYZABCDEFGHIJKLMnopqrstuvwxyzabcdefghijklmROT13 is used in online forums as a means of hiding spoilers, punchlines, puzzle solutions, and offensive materials from the casual glance. ROT13 has inspired a variety of letter and word games on-line, and is frequently mentioned in newsgroup conversations.
The algorithm provides virtually no cryptographic security, and is often cited as a canonical example of weak encryption.
ROT13 is a special case of the Caesar cipher which was developed in ancient Rome.
Applying ROT13 to a piece of text merely requires examining its alphabetic characters and replacing each one by the letter 13 places further along in the alphabet, wrapping back to the beginning if necessary. A becomes N, B becomes O, and so on up to M, which becomes Z, then the sequence continues at the beginning of the alphabet: N becomes A, O becomes B, and so on to Z, which becomes M. Only those letters which occur in the English alphabet are affected; numbers, symbols, whitespace, and all other characters are left unchanged.
Because there are 26 letters in the English alphabet and 26 = 2 x 13, the ROT13 function is its own inverse: so the same action can be used for encoding and decoding. In other words, two successive applications of ROT13 restore the original text (in mathematics, this is sometimes called an involution; in cryptography, a reciprocal cipher).
The use of a constant shift means that the encryption effectively has no key, and decryption requires no more knowledge than the fact that ROT13 is in use. Even without this knowledge, the algorithm is easily broken through frequency analysis.
In encrypted normal English-language text of any significant size, ROT13 is recognizable from some letter/word patterns. The words "n", "V" (capitalized only), and "gur" (ROT13 for "a", "I", and "the"), and words ending in "yl" ("ly") are examples.
Wikipedia, the free encyclopedia
Sample program
program demo_rotate13 use M_strings, only : rotate13 implicit none character(len=256) :: line integer :: iostat do read(*,’(a)’,iostat=iostat)line if(iostat /= 0)exit write(*,’(a)’)rotate13(line) enddo end program demo_rotate13Sample usage:
demo_rotate13 United we stand, divided we fall. Havgrq jr fgnaq, qvivqrq jr snyy.
John S. Urban
Public Domain
rpad(3f) - [M_strings:LENGTH] convert to a string and pad on the right to requested length (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function rpad(valuein,length) result(strout)
class*,intent(in) :: valuein(..) integer,intent(in) :: length
rpad(3f) converts a scalar intrinsic value to a string and then pads it on the right with spaces to at least the specified length. If the trimmed input string is longer than the requested length the string is returned trimmed of leading and trailing spaces.
str The input may be scalar or a vector. the input value to return as a string, padded on the left to the specified length if shorter than length. The input may be any intrinsic scalar which is converted to a cropped string much as if written with list-directed output. length The minimum string length to return
strout The input string padded to the requested length on the right with spaces.
Sample Program:
program demo_rpad use M_strings, only : rpad implicit none write(*,’("[",a,"]")’) rpad( ’my string’, 20) write(*,’("[",a,"]")’) rpad( ’my string ’, 20) write(*,’("[",a,"]")’) rpad( ’ my string’, 20) write(*,’("[",a,"]")’) rpad( ’ my string ’, 20) write(*,’("[",a,"]")’) rpad( valuein=42 , length=7) write(*,’("[",a,"]")’) rpad( valuein=1.0/9.0 , length=20) end program demo_rpadResults:
> [my string ] > [my string ] > [my string ] > [my string ] > [42 ] > [0.111111112 ]
John S. Urban
Public Domain
s2c(3f) - [M_strings:ARRAY] convert character variable to array of characters with last element set to null (LICENSE:PD)
Synopsis
Description
Examples
Author
License
pure function s2c(string) RESULT (array) character(len=*),intent=(in) :: string character(len=1),allocatable :: s2c(:)
Given a character variable convert it to an array of single-character character variables with the last element set to a null character. This is generally used to pass character variables to C procedures.
character(len=3),allocatable :: array(:)
integer :: i ! put one character into each 3-character element of array array = [(string(i:i),i=1,len(string))] ! write array with ASCII Decimal Equivalent below it except show ! unprintable characters like NULL as "XXX" write(*,g) merge(’XXX’,array,iachar(array(:)(1:1)) < 32) write(*,g) iachar(array(:)(1:1)) Sample Program:
program demo_s2c use M_strings, only : s2c implicit none character(len=*),parameter :: string="single string" character(len=*),parameter :: g= ’(1x,*("[",g3.3,"]":))’ character(len=3),allocatable :: array(:) write(*,*)’INPUT STRING ’,trim(string) ! put one character into each 3-character element of array array=s2c(string) ! write array with ASCII Decimal Equivalent below it except show ! unprintable characters like NULL as "XXX" write(*,g) merge(’XXX’,array,iachar(array(:)(1:1)) < 32) write(*,g) iachar(array(:)(1:1)) end program demo_s2cExpected output:
INPUT STRING single string [s ][i ][n ][g ][l ][e ][ ][s ][t ][r ][i ][n ][g ][XXX] [115][105][110][103][108][101][ 32][115][116][114][105][110][103][ 0]
John S. Urban
Public Domain
s2v(3f) - [M_strings:TYPE] function returns doubleprecision numeric value from a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function s2v(string[,ierr][,onerr])
character(len=*) :: string doubleprecision :: s2v integer,intent(out),optional :: ierr class(*),intent(in),optional :: onerr
This function converts a string to a DOUBLEPRECISION numeric value.The intrinsics INT(3f), REAL(3f), and DBLE(3f) are also extended to take CHARACTER variables. The KIND= keyword is not supported on the extensions.
string holds string assumed to represent a numeric value ierr If an error occurs the program is stopped if the optional parameter IERR is not present. If IERR returns a non-zero value an error occurred. onerr The value to return on error. A value of NaN is returned on error by default.
s2v numeric value read from string
Sample Program:
program demo_s2vuse M_strings, only: s2v, int, real, dble implicit none character(len=8) :: s=’ 10.345 ’ integer :: i character(len=14),allocatable :: strings(:) doubleprecision :: dv integer :: errnum
! different strings representing INTEGER, REAL, and DOUBLEPRECISION strings=[& &’ 10.345 ’,& &’+10 ’,& &’ -3 ’,& &’ -4.94e-2 ’,& &’0.1 ’,& &’12345.678910d0’,& &’ ’,& ! Note: will return zero without an error message &’1 2 1 2 1 . 0 ’,& ! Note: spaces will be ignored &’WHAT? ’] ! Note: error messages will appear, zero returned
! a numeric value is returned, ! so it can be used in numeric expression write(*,*) ’1/2 value of string is ’,s2v(s)/2.0d0 write(*,*) write(*,*)’ STRING VALUE ERROR_NUMBER’ do i=1,size(strings) ! Note: not a good idea to use s2v(3f) in a WRITE(3f) statement, ! as it does I/O when errors occur, so called on a separate line dv=s2v(strings(i),errnum) write(*,*) strings(i)//’=’,dv,errnum enddo write(*,*)"Extended intrinsics" write(*,*)’given inputs:’,s,strings(:8) write(*,*)’INT(3f):’,int(s),int(strings(:8)) write(*,*)’REAL(3f):’,real(s),real(strings(:8)) write(*,*)’DBLE(3f):’,dble(s),dble(strings(:8)) write(*,*)"That’s all folks!"
end program demo_s2v
Expected output
>1/2 value of string is 5.1725000000000003 > > STRING VALUE ERROR_NUMBER > 10.345 = 10.345000000000001 0 >+10 = 10.000000000000000 0 > -3 = -3.0000000000000000 0 > -4.94e-2 = -4.9399999999999999E-002 0 >0.1 = 0.10000000000000001 0 >12345.678910d0= 12345.678910000001 0 > = 0.0000000000000000 0 >1 2 1 2 1 . 0 = 12121.000000000000 0 >*a2d* - cannot produce number from string [WHAT?] >*a2d* - [Bad value during floating point read] >WHAT? = 0.0000000000000000 5010 >Extended intrinsics >given inputs: 10.345 10.345 +10 -3 -4.94e-2 0.1 12345.678910d0 1 2 1 2 1 . 0 >INT(3f): 10 10 10 -3 0 0 12345 0 12121 >REAL(3f): 10.3450003 10.3450003 10.0000000 -3.00000000 -4.94000018E-02 > 0.100000001 12345.6787 0.00000000 12121.0000 >DBLE(3f): 10.345000000000001 10.345000000000001 10.000000000000000 > -3.0000000000000000 -4.9399999999999999E-002 0.10000000000000001 > 12345.678910000001 0.0000000000000000 12121.000000000000 >That’s all folks!
John S. Urban
Public Domain
s2vs(3f) - [M_strings:TYPE] given a string representing numbers return a numeric array (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function s2vs(line[,delim])
character(len=*) :: line doubleprecision,allocatable :: s2vs(:)
The function S2VS(3f) takes a string representing a series of numbers and converts it to a numeric doubleprecision array. The string values may be delimited by spaces, semi-colons, and commas by default.
LINE Input string containing numbers DELIM optional list of delimiter characters. If a space is included, it should appear as the left-most character in the list. The default is " ;," (spaces, semi-colons, and commas).
S2VS doubleprecision array
Sample Program:
program demo_s2vs use M_strings, only : s2vs implicit none character(len=80) :: s=’ 10 20e3;3.45 -400.3e-2;1234; 5678 ’ real,allocatable :: values(:) integer,allocatable :: ivalues(:) integer :: iiExpected outputvalues=s2vs(s) ivalues=int(s2vs(s)) call reportit()
contains subroutine reportit() write(*,*)’S2VS:’ write(*,*)’input string.............’,& & trim(s) write(*,*)’number of values found...’,& & size(values) write(*,*)’values...................’,& & (values(ii),ii=1,size(values)) write(*,’(*(g0,1x))’)’ivalues..................’,& & (ivalues(ii),ii=1,size(values)) end subroutine reportit end program demo_s2vs
S2VS: input string............. 10 20e3;3.45 -400.3e-2;1234; 5678 number of values found... 6 values................... 10.0000000 20000.0000 3.45000005 -4.00299978 1234.00000 5678.00000ivalues.................. 10 20000 3 -4 1234 5678
John S. Urban
Public Domain
sep(3f) - [M_strings:TOKENS] function to parse string into an array using specified delimiters (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function sep(input_line,delimiters,nulls)
character(len=*),intent(in) :: input_line character(len=*),optional,intent(in) :: delimiters character(len=*),optional,intent(in) :: nulls character(len=:),allocatable :: sep(:)
sep(3f) parses a string using specified delimiter characters and store tokens into an allocatable array
INPUT_LINE Input string to tokenize DELIMITERS List of delimiter characters. The default delimiters are the "whitespace" characters (space, tab,new line, vertical tab, formfeed, carriage return, and null). You may specify an alternate set of delimiter characters. Multi-character delimiters are not supported (Each character in the DELIMITERS list is considered to be a delimiter).
Quoting of delimiter characters is not supported.
NULLS=IGNORE|RETURN|IGNOREEND Treatment of null fields. By default adjacent delimiters in the input string do not create an empty string in the output array. if NULLS=’return’ adjacent delimiters create an empty element in the output ARRAY. If NULLS=’ignoreend’ then only trailing delimiters at the right of the string are ignored. ORDER=’ASCENDING’|’DESCENDING’ by default the tokens are returned from last to first; order=’ASCENDING’ returns them from first to last (left to right).
SEP Output array of tokens
Sample program:
program demo_sep use M_strings, only: sep character(len=*),parameter :: fo=’(/,a,*(/,"[",g0,"]":,","))’ character(len=*),parameter :: line=& ’ aBcdef ghijklmnop qrstuvwxyz 1:|:2 333|333 a B cc ’ write(*,’(a)’) ’INPUT LINE:[’//LINE//’]’ write(*,fo) ’typical call:’,sep(line) write(*,fo) ’delimiters ":|":’,sep(line,’:|’) write(*,fo) ’count null fields ":|":’,sep(line,’:|’,’return’) end program demo_sepOutput
INPUT LINE:[ aBcdef ghijklmnop qrstuvwxyz 1:|:2 333|333 a B cc ]typical call: [cc ], [B ], [a ], [333|333 ], [1:|:2 ], [qrstuvwxyz], [ghijklmnop], [aBcdef ]
delimiters ":|": [333 a B cc ], [2 333 ], [ aBcdef ghijklmnop qrstuvwxyz 1]
count null fields ":|": [333 a B cc ], [2 333 ], [ ], [ ], [ aBcdef ghijklmnop qrstuvwxyz 1]
John S. Urban
Public Domain
slice(3f) - [M_strings:TOKENS] parse string into an array using specified delimiters (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
subroutine slice(input_line,ibegin,iend,delimiters,nulls)
character(len=*),intent(in) :: input_line integer,allocatable,intent(out) :: ibegin(:),iend(:) character(len=*),optional,intent(in) :: delimiters character(len=*),optional,intent(in) :: nulls
slice(3f) parses a string using specified delimiter characters and store token beginning and ending positions into allocatable arrays
INPUT_LINE Input string to tokenize IBEGIN,IEND arrays containing start and end positions of tokens. IEND(I)<IBEGIN(I) designates a null token. DELIMITERS List of delimiter characters. The default delimiters are the "whitespace" characters (space, tab,new line, vertical tab, formfeed, carriage return, and null). You may specify an alternate set of delimiter characters. Multi-character delimiters are not supported (Each character in the DELIMITERS list is considered to be a delimiter).
Quoting of delimiter characters is not supported.
NULLS= IGNORE | RETURN | IGNOREEND Treatment of null fields. By default adjacent delimiters in the input string do not create an empty string in the output array. if NULLS=’return’ adjacent delimiters create an empty element in the output ARRAY. If NULLS=’ignoreend’ then only trailing delimiters at the right of the string are ignored.
Sample program:
program demo_slice use M_strings, only: slice implicit none integer :: i character(len=*),parameter :: & & line=’ aBcdef ghijklmnop qrstuvwxyz 1:|:2 333|333 a B cc ’ integer,allocatable :: ibegin(:), iend(:) ! output arrays of positions character(len=*),parameter :: title=’(80("="),t1,a)’ write(*,*)’INPUT LINE:[’//line//’]’ ! write(*,title)’typical call: ’ call slice(line,ibegin,iend) call printme() ! write(*,title)’custom list of delimiters=":|" : ’ call slice(line,ibegin,iend,delimiters=’:|’,nulls=’ignore’) call printme() ! write(*,title)’delimiters=":|", and count null fields: ’ call slice(line,ibegin,iend,delimiters=’:|’,nulls=’return’) call printme() ! write(*,title)’default delimiters and return null fields: ’ call slice(line,ibegin,iend,delimiters=’’,nulls=’return’) call printme() contains subroutine printme() write(*,’((*(:/,3x,"[",g0,"]")))’)& & (line(ibegin(i):iend(i)),i=1,size(ibegin)) write(*,’(*(g0,1x))’)’SIZE:’,size(ibegin) end subroutine printme end program demo_sliceResults:
> INPUT LINE: > [ aBcdef ghijklmnop qrstuvwxyz 1:|:2 333|333 a B cc ] > typical call: ======================================================== > > [aBcdef] > [ghijklmnop] > [qrstuvwxyz] > [1:|:2] > [333|333] > [a] > [B] > [cc] > SIZE: 8 > custom list of delimiters=":|" : ===================================== > > [ aBcdef ghijklmnop qrstuvwxyz 1] > [2 333] > [333 a B cc ] > SIZE: 3 > delimiters=":|", and count null fields: ============================== > > [ aBcdef ghijklmnop qrstuvwxyz 1] > [] > [] > [2 333] > [333 a B cc ] > SIZE: 5 > default delimiters and return null fields: =========================== > > [] > [] > [aBcdef] > [] > [] > [ghijklmnop] > [qrstuvwxyz] > [] > [1:|:2] > [] > [] > [] > [] > [333|333] > [a] > [B] > [cc] > [] > [] > [] > SIZE: 20======================================================================
John S. Urban
Public Domain
split(3f) - [M_strings:TOKENS] parse string into an array using specified delimiters (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
subroutine split(input_line,array,delimiters,order,nulls)
character(len=*),intent(in) :: input_line character(len=:),allocatable,intent(out) :: array(:) character(len=*),optional,intent(in) :: delimiters character(len=*),optional,intent(in) :: order character(len=*),optional,intent(in) :: nulls
SPLIT(3f) parses a string using specified delimiter characters and store tokens into an allocatable array
INPUT_LINE Input string to tokenize ARRAY Output array of tokens DELIMITERS List of delimiter characters. The default delimiters are the "whitespace" characters (space, tab,new line, vertical tab, formfeed, carriage return, and null). You may specify an alternate set of delimiter characters. Multi-character delimiters are not supported (Each character in the DELIMITERS list is considered to be a delimiter).
Quoting of delimiter characters is not supported.
ORDER SEQUENTIAL|REVERSE|RIGHT Order of output array. By default ARRAY contains the tokens having parsed the INPUT_LINE from left to right. If ORDER=’RIGHT’ or ORDER=’REVERSE’ the parsing goes from right to left. (This can be accomplished with array syntax in modern Fortran, but was more useful pre-fortran90). NULLS=IGNORE|RETURN|IGNOREEND Treatment of null fields. By default adjacent delimiters in the input string do not create an empty string in the output array. if NULLS=’return’ adjacent delimiters create an empty element in the output ARRAY. If NULLS=’ignoreend’ then only trailing delimiters at the right of the string are ignored.
Sample program:
program demo_split use M_strings, only: split implicit none integer :: i character(len=*),parameter :: title=’(80("="),t1,a)’ character(len=*),parameter :: line=& ’ aBcdef ghijklmnop qrstuvwxyz 1:|:2 333|333 a B cc ’ character(len=:),allocatable :: array(:) ! output array of tokens write(*,*)’INPUT LINE:[’//line//’]’ ! write(*,title)’typical call: ’ call split(line,array) call printme() ! write(*,title)’custom delimiters=":|" : ’ call split(line,array,delimiters=’:|’,& & order=’sequential’,nulls=’ignore’) call printme() ! write(*,title)& ’delimiters=":|",reverse array order and count null fields:’ call split(line,array,delimiters=’:|’,& & order=’reverse’,nulls=’return’) call printme() ! write(*,title)& ’default delimiters, reverse array order and return null fields:’ call split(line,array,delimiters=’’,& & order=’reverse’,nulls=’return’) call printme() contains subroutine printme() write(*,’(i0," ==> ",a)’)(i,trim(array(i)),i=1,size(array)) write(*,*)’SIZE:’,size(array) end subroutine printme end program demo_splitResults:
> INPUT LINE: > [ aBcdef ghijklmnop qrstuvwxyz 1:|:2 333|333 a B cc ] > typical call: ======================================================== > 1 ==> aBcdef > 2 ==> ghijklmnop > 3 ==> qrstuvwxyz > 4 ==> 1:|:2 > 5 ==> 333|333 > 6 ==> a > 7 ==> B > 8 ==> cc > SIZE: 8 > custom delimiters=":|" : ============================================= > 1 ==> aBcdef ghijklmnop qrstuvwxyz 1 > 2 ==> 2 333 > 3 ==> 333 a B cc > SIZE: 3 > delimiters=":|",reverse array order and count null fields:============ > 1 ==> 333 a B cc > 2 ==> 2 333 > 3 ==> > 4 ==> > 5 ==> aBcdef ghijklmnop qrstuvwxyz 1 > SIZE: 5 > default delimiters, reverse array order and return null fields:======= > 1 ==> > 2 ==> > 3 ==> > 4 ==> cc > 5 ==> B > 6 ==> a > 7 ==> 333|333 > 8 ==> > 9 ==> > 10 ==> > 11 ==> > 12 ==> 1:|:2 > 13 ==> > 14 ==> qrstuvwxyz > 15 ==> ghijklmnop > 16 ==> > 17 ==> > 18 ==> aBcdef > 19 ==> > 20 ==> > SIZE: 20
John S. Urban
Public Domain
split2020(3f) - [M_strings:TOKENS] parse a string into tokens using proposed f2023 method (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
Version
TOKEN form
subroutine split2020 (string, set, tokens, separator) character(len=*),intent(in) :: string character(len=*),intent(in) :: set character(len=:),allocatable,intent(out) :: tokens(:) character(len=1),allocatable,intent(out),optional :: separator(:)BOUNDS ARRAY form
subroutine split2020 (string, set, first, last) character(len=*),intent(in) :: string character(len=*),intent(in) :: set integer,allocatable,intent(out) :: first(:) integer,allocatable,intent(out) :: last(:)STEP THROUGH BY POSITION form
subroutine split2020 (string, set, pos [, back]) character(len=*),intent(in) :: string character(len=*),intent(in) :: set integer,intent(inout) :: pos logical,intent(in),optional :: back
Parse a string into tokens. STRING, SET, TOKENS and SEPARATOR must all be of the same CHARACTER kind type parameter.
STRING string to break into tokens SET Each character in SET is a token delimiter. A sequence of zero or more characters in STRING delimited by any token delimiter, or the beginning or end of STRING, comprise a token. Thus, two consecutive token delimiters in STRING, or a token delimiter in the first or last character of STRING, indicate a token with zero length. ??? how about if null defaults to all whitespace characters
TOKENS It is allocated with the lower bound equal to one and the upper bound equal to the number of tokens in STRING, and with character length equal to the length of the longest token. The tokens in STRING are assigned by intrinsic assignment, in the order found, to the elements of TOKENS, in array element order. ???If input is null it still must be of size 1?
SEPARATOR Each element in SEPARATOR(i) is assigned the value of the ith token delimiter in STRING. It is allocated with the lower bound equal to one and the upper bound equal to one less than the number of tokens in STRING, and with character length equal to one. ???one less than? ’’ ’ ’
FIRST It is allocated with the lower bound equal to one and the upper bound equal to the number of tokens in STRING. Each element is assigned, in array element order, the starting position of each token in STRING, in the order found. If a token has zero length, the starting position is equal to one if the token is at the beginning of STRING, and one greater than the position of the preceding delimiter otherwise. LAST It is allocated with the lower bound equal to one and the upper bound equal to the number of tokens in STRING. Each element is assigned, in array element order, the ending position of each token in STRING, in the order found. If a token has zero length, the ending position is one less than the starting position. POS If BACK is present with the value .TRUE., the value If BACK is absent or is present with the value .FALSE., POS is assigned the position of the leftmost token delimiter in STRING whose position is greater than POS, or if there is no such character, it is assigned a value one greater than the length of STRING. This identifies a token with starting position one greater than the value of POS on invocation, and ending position one less than the value of POS on return.
of POS shall be in the range 0 < POS LEN (STRING)+1; otherwise it shall be in the range 0 POS LEN (STRING). If BACK is present with the value true, POS is assigned the position of the rightmost token delimiter in STRING whose position is less than POS, or if there is no such character, it is assigned the value zero. This identifies a token with ending position one less than the value of POS on invocation, and starting position one greater than the value of POS on return.
When SPLIT is invoked with a value for POS of 1 <= POS <= LEN(STRING) and STRING(POS:POS) is not a token delimiter present in SET, the token identified by SPLIT does not comprise a complete token as described in the description of the SET argument, but rather a partial token.
BACK shall be a logical scalar. It is an INTENT (IN) argument. If POS does not appear and BACK is present with the value true, STRING is scanned backwards for tokens starting from the end. If POS does not appear and BACK is absent or present with the value false, STRING is scanned forwards for tokens starting from the beginning.
Sample of uses
program demo_sort2020 use M_strings, only : split2020 implicit none character(len=*),parameter :: gen=’(*("[",g0,"]":,","))’Results:! Execution of TOKEN form block character (len=:), allocatable :: string character (len=:), allocatable :: tokens(:) character (len=*),parameter :: set = " ," string = ’first,second,third’ call split2020(string, set, tokens ) write(*,gen)tokens
! assigns the value [’first ’,’second’,’third ’ ] ! to TOKENS. endblock
! Execution of BOUNDS form
block character (len=:), allocatable :: string character (len=*),parameter :: set = " ," integer, allocatable :: first(:), last(:) string = ’first,second,,forth’ call split2020 (string, set, first, last) write(*,gen)first write(*,gen)last
! will assign the value [ 1, 7, 14, 15 ] to FIRST, ! and the value [ 5, 12, 13, 19 ] to LAST. endblock
! Execution of STEP form block character (len=:), allocatable :: string character (len=*),parameter :: set = " ," integer :: p, ibegin, iend string = " one, last example " do while (p < len(string)) ibegin = p + 1 call split2020 (string, set, p) iend=p-1 if(iend > ibegin)then print ’(t3,a,1x,i0,1x,i0)’, string (ibegin:iend),ibegin,iend endif enddo endblock end program demo_sort2020
[first ],[second],[third ] [1],[7],[14],[15] [5],[12],[13],[19] one 2 4 last 9 12 example 15 21> ??? option to skip adjacent delimiters (not return null tokens) > common with whitespace > ??? quoted strings, especially CSV both " and ’, Fortran adjacent > is insert versus other rules > ??? escape character like \\ . > ??? multi-character delimiters like \\n, \\t, > ??? regular expression separator
Milan Curcic, "milancurcic@hey.com"
version 0.1.0, copyright 2020, Milan Curcic
squeeze(3f) - [M_strings:EDITING] delete adjacent duplicate occurrences of a character from a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function squeeze(STR,CHAR) result (OUTSTR)
character(len=*),intent(in) :: STR character(len=*),intent(in),optional :: CHAR character(len=len(str)) :: OUTSTR
squeeze(3f) reduces adjacent duplicates of the specified character to a single character
STR input string in which to reduce adjacent duplicate characters to a single character CHAR The character to remove adjacent duplicates of
OUTSTR string with all contiguous adjacent occurrences of CHAR removed
Sample Program:
program demo_squeeze use M_strings, only : squeeze implicit none character(len=:),allocatable :: strings(:)strings=[ character(len=72) :: & &’’, & &’"If I were two-faced,& &would I be wearing this one?" --- Abraham Lincoln’, & &’..1111111111111111111& &111111111111111111111111111111111111111111117777888’, & &’I never give ’’em hell,& &I just tell the truth, and they think it’’s hell.’,& &’ & & --- Harry S Truman’ & &] call printme( trim(strings(1)), ’ ’ ) call printme( strings(2:4), [’-’,’7’,’.’] ) call printme( strings(5), [’ ’,’-’,’r’] ) contains impure elemental subroutine printme(str,chr) character(len=*),intent(in) :: str character(len=1),intent(in) :: chr character(len=:),allocatable :: answer write(*,’(a)’)repeat(’=’,11) write(*,’("IN: <<<",g0,">>>")’)str answer=squeeze(str,chr) write(*,’("OUT: <<<",g0,">>>")’)answer write(*,’("LENS: ",*(g0,1x))’)"from",len(str),"to",len(answer), & & "for a change of",len(str)-len(answer) write(*,’("CHAR: ",g0)’)chr end subroutine printme end program demo_squeeze
John S. Urban
Public Domain
str(3f) - [M_strings:TYPE] converts multiple values to a (CSV) string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function str( g1,g2,g3,g4,g5,g6,g7,g8,g9,g10, & & g11,g12,g13,g14,g15,g16,g17,g18,g19,g20,sep,csv)
class(*),intent(in),optional :: g1,g2,g3,g4,g5,g6,g7,g8,g9,g10 class(*),intent(in),optional :: g11,g12,g13,g14,g15,g16,g17,g18,g19,g20 character(len=*),intent(in),optional :: sep logical,intent(in),optional :: csv character(len=:),allocatable :: str
str(3f) builds a string from up to twenty scalar values.
g[1-20] optional value to print the value of after the message. May be of type INTEGER, LOGICAL, REAL, DOUBLEPRECISION, COMPLEX, or CHARACTER. sep separator between values. Defaults to a space csv write output conforming to RFC 1080 for CSV (Comma-Separated Values) files
str description to print
Sample program:
program demo_str use M_strings, only : str, quote implicit none character(len=:),allocatable :: pr character(len=:),allocatable :: frmt integer :: biggestResults:pr=str(’HUGE(3f) integers’,huge(0),& & ’and real’,huge(0.0),’and double’,huge(0.0d0)) write(*,’(a)’)pr pr=str(’real :’,& & huge(0.0),0.0,12345.6789,tiny(0.0) ) write(*,’(a)’)pr pr=str(’doubleprecision :’,& & huge(0.0d0),0.0d0,12345.6789d0,tiny(0.0d0) ) write(*,’(a)’)pr pr=str(’complex :’,& & cmplx(huge(0.0),tiny(0.0)) ) write(*,’(a)’)pr
! create a format on the fly biggest=huge(0) ! +0 for gfortran-11 bug frmt=str(’(*(i’,int(log10(real(biggest)))+0,’:,1x))’,sep=’’) write(*,*)’format=’,frmt
! compound output pr=str(10,100.0,"string",(11.0,22.0),.false.) write(*,’(a)’)pr ! a separator and also use of quote(3f) pr=str(10,100.0,quote("string"),(11.0,22.0),.false.,sep=’;’) write(*,’(a)’)pr ! CSV mode pr=str(10,100.0,"string",(11.0,22.0),.false.,csv=.true.) write(*,’(a)’)pr ! everything a vector instead of a scalar pr=str([10,20,30],["string"],[(11.0,22.0)],[.false.,.true.]) write(*,’(a)’)pr pr=str([10,20,30],["string"],[(11.0,22.0)],[.false.,.true.],sep=’|’) write(*,’(a)’)pr pr=str([10,20,30],["string"],[(11.0,22.0)],[.false.,.true.],csv=.true.) write(*,’(a)’)pr
! although it will often work, using str(3f) in an I/O statement ! is not recommended write(*,*)str(’program will now attempt to stop’)
end program demo_str
> HUGE(3f) integers 2147483647 and real 3.40282347E+38 and ... > ... double 1.7976931348623157E+308 > real : 3.40282347E+38 0.00000000 12345.6787 1.17549435E-38 > doubleprecision : 1.7976931348623157E+308 0.0000000000000000 ... > ... 12345.678900000001 2.2250738585072014E-308 > complex : (3.40282347E+38,1.17549435E-38) > format=(*(i9:,1x)) > 10 100.000000 string (11.0000000,22.0000000) F > 10;100.000000;"string";(11.0000000,22.0000000);F > 10,100.000000,"string",11.0000000,22.0000000,F > program will now attempt to stop
John S. Urban
Public Domain
stretch(3f) - [M_strings:LENGTH] return string padded to at least specified length (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function stretch(str,length,pattern,suffix) result(strout)
character(len=*),intent(in) :: str integer,intent(in) :: length character(len=*)intent(in),optional :: pattern character(len=*)intent(in),optional :: suffix character(len=:),allocatable :: strout
stretch(3f) pads a string with spaces to at least the specified length. If the trimmed input string is longer than the requested length the original string is returned trimmed of trailing spaces.
str the input string to return trimmed, but then padded to the specified length if shorter than length length The minimum string length to return pattern optional string to use as padding. Defaults to a space. suffix optional string to append to output string
strout The input string padded to the requested length or the trimmed input string if the input string is longer than the requested length.
Sample Program:
program demo_stretch use M_strings, only : stretch implicit none character(len=10) :: string=’abcdefghij’ character(len=:),allocatable :: answer integer :: i answer=stretch(string,5) write(*,’("[",a,"]")’) answer answer=stretch(string,20) write(*,’("[",a,"]")’) answer i=30 write(*,*) write(*,’(1x,a,i0)’) & & stretch(’CHAPTER 1 : The beginning ’,i,’.’), 1 ,& & stretch(’CHAPTER 2 : The end ’,i,’.’), 1234 ,& & stretch(’APPENDIX ’,i,’.’), 1235 write(*,*) write(*,’(1x,a,i7)’) & & stretch(’CHAPTER 1 : The beginning ’,i,’.’), 1 ,& & stretch(’CHAPTER 2 : The end ’,i,’.’), 1234 ,& & stretch(’APPENDIX ’,i,’.’), 1235 write(*,*) write(*,*) & & stretch(’CHAPTER 1 : The beginning ’,i,suffix=’: ’), 1 write(*,*) & & stretch(’CHAPTER 2 : The end ’,i,suffix=’: ’),1234 write(*,*) & & stretch(’APPENDIX ’,i,suffix=’: ’), 1235 end program demo_stretchResults:
[abcdefghij] [abcdefghij ]
CHAPTER 1 : The beginning ....1 CHAPTER 2 : The end ..........1234 APPENDIX .....................1235
CHAPTER 1 : The beginning .... 1 CHAPTER 2 : The end .......... 1234 APPENDIX ..................... 1235
CHAPTER 1 : The beginning : 1 CHAPTER 2 : The end : 1234 APPENDIX : 1235
John S. Urban
Public Domain
string_to_value(3f) - [M_strings:TYPE] subroutine returns numeric value from string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
subroutine string_to_value(chars,valu,ierr)
character(len=*),intent(in) :: chars ! input string integer|real|doubleprecision,intent(out) :: valu integer,intent(out) :: ierr
Returns a numeric value from a numeric character string.Works with any g-format input, including integer, real, and exponential. If the input string begins with "B", "Z", or "O" and otherwise represents a positive whole number it is assumed to be a binary, hexadecimal, or octal value. If the string contains commas they are removed. If the string is of the form NN:MMM... or NN#MMM then NN is assumed to be the base of the whole number.
If an error occurs in the READ, IOSTAT is returned in IERR and value is set to zero. if no error occurs, IERR=0.
CHARS input string to read numeric value from
VALU numeric value returned. May be INTEGER, REAL, or DOUBLEPRECISION. IERR error flag (0 == no error)
Sample Program:
program demo_string_to_value use M_strings, only: string_to_value implicit none real :: value integer :: ierr character(len=80) :: string string=’ -40.5e-2 ’ call string_to_value(string,value,ierr) write(*,*) ’value of string [’//trim(string)//’] is ’,value end program demo_string_to_value
John S. Urban
Public Domain
string_to_values(3f) - [M_strings:TYPE] read a string representing numbers into a numeric array (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
subroutine string_to_values(line,iread,values,inums,delims,ierr)
character(len=*) :: line integer :: iread real :: values(*) integer :: inums character(len=*) :: delims integer :: ierr
This routine can take a string representing a series of numbers and convert it to a numeric array and return how many numbers were found.
LINE Input string containing numbers IREAD maximum number of values to try to read from input string
VALUES real array to be filled with numbers INUMS number of values successfully read (before error occurs if one does) DELIMS delimiter character(s), usually a space. must not be a null string. If more than one character, a space must not be the last character or it will be ignored. IERR error flag (0=no error, else column number string starts at that error occurred on).
Sample Program:
program demo_string_to_values use M_strings, only : string_to_values implicit none character(len=80) :: s=’ 10 20e3;3.45 -400.3e-2;1234; 5678 ’ integer,parameter :: isz=10 real :: array(isz) integer :: inums, ierr, iiExpected outputcall string_to_values(s,10,array,inums,’ ;’,ierr) call reportit()
call string_to_values(’10;2.3;3.1416’,isz,array,inums,’ ;’,ierr) call reportit()
contains subroutine reportit() write(*,*)’string_to_values:’ write(*,*)’input string.............’,trim(s) write(*,*)’number of values found...’,inums write(*,*)’values...................’,(array(ii),ii=1,inums) end subroutine reportit end program demo_string_to_values
string_to_values: input string............. 10 20e3;3.45 -400.3e-2;1234; 5678 number of values found... 6 values................... 10.0000000 20000.0000 3.45000005 -4.00299978 1234.00000 5678.00000 string_to_values: input string............. 10 20e3;3.45 -400.3e-2;1234; 5678 number of values found... 3 values................... 10.0000000 2.29999995 3.14159989
John S. Urban
Public Domain
strtok(3f) - [M_strings:TOKENS] Tokenize a string (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function strtok(source_string,itoken,token_start,token_end,delimiters) result(strtok_status)
! returned value logical :: strtok_status ! string to tokenize character(len=*),intent(in) :: source_string ! token count since started integer,intent(inout) :: itoken ! beginning of token integer,intent(out) :: token_start ! end of token integer,intent(inout) :: token_end ! list of separator characters character(len=*),intent(in) :: delimiters
The STRTOK(3f) function is used to isolate sequential tokens in a string, SOURCE_STRING. These tokens are delimited in the string by at least one of the characters in DELIMITERS. The first time that STRTOK(3f) is called, ITOKEN should be specified as zero. Subsequent calls, wishing to obtain further tokens from the same string,This routine assumes no other calls are made to it using any other input string while it is processing an input line.
should pass back in TOKEN_END and ITOKEN until the function result returns .false.
source_string input string to parse itoken token count should be set to zero for a new string delimiters characters used to determine the end of tokens
token_start beginning position in SOURCE_STRING where token was found token_end ending position in SOURCE_STRING where token was found strtok_status
Sample program:
program demo_strtok use M_strings, only : strtok implicit none character(len=264) :: inline character(len=*),parameter :: delimiters=’ ;,’ integer :: iostat, itoken, ibegin, iend do ! read lines from stdin until end-of-file or error read (unit=*,fmt="(a)",iostat=iostat) inline if(iostat /= 0)stop ! must set ITOKEN=0 before looping on strtok(3f) ! on a new string. itoken=0 do while & &( strtok(inline,itoken,ibegin,iend,delimiters) ) print *, itoken,& & ’TOKEN=[’//(inline(ibegin:iend))//’]’,ibegin,iend enddo enddo end program demo_strtoksample input file
this is a test of strtok; A:B :;,C;;
sample output file
1 TOKEN=[this] 2 5 2 TOKEN=[is] 7 8 3 TOKEN=[a] 10 10 4 TOKEN=[test] 12 15 5 TOKEN=[of] 17 18 6 TOKEN=[strtok] 20 25 7 TOKEN=[A:B] 28 30 8 TOKEN=[:] 32 32 9 TOKEN=[C] 35 35
John S. Urban
Public Domain
substitute(3f) - [M_strings:EDITING] subroutine globally substitutes one substring for another in string (LICENSE:PD)
Synopsis
Description
Options
Examples
Author
License
impure elemental subroutine substitute(targetline,old,new,ierr,start,end)
character(len=*) :: targetline character(len=*),intent(in) :: old character(len=*),intent(in) :: new integer,intent(out),optional :: ierr integer,intent(in),optional :: start integer,intent(in),optional :: end
Globally substitute one substring for another in string.
TARGETLINE input line to be changed. Must be long enough to hold altered output. OLD substring to find and replace NEW replacement for OLD substring IERR error code. If IER = -1 bad directive, >= 0 then count of changes made. START sets the left margin to be scanned for OLD in TARGETLINE. END sets the right margin to be scanned for OLD in TARGETLINE.
Sample Program:
program demo_substitute use M_strings, only : substitute implicit none ! must be long enough to hold changed line character(len=80) :: targetlineExpected outputtargetline=’this is the input string’ write(*,*)’ORIGINAL : ’//trim(targetline)
! changes the input to ’THis is THe input string’ call substitute(targetline,’th’,’TH’) write(*,*)’th => TH : ’//trim(targetline)
! a null old substring means "at beginning of line" ! changes the input to ’BEFORE:this is the input string’ call substitute(targetline,’’,’BEFORE:’) write(*,*)’"" => BEFORE: ’//trim(targetline)
! a null new string deletes occurrences of the old substring ! changes the input to ’ths s the nput strng’ call substitute(targetline,’i’,’’) write(*,*)’i => "" : ’//trim(targetline)
end program demo_substitute
ORIGINAL : this is the input string th => TH : THis is THe input string "" => BEFORE: BEFORE:THis is THe input string i => "" : BEFORE:THs s THe nput strng
John S. Urban
Public Domain
switch(3f) - [M_strings:ARRAY] converts between CHARACTER scalar and array of single characters (LICENSE:PD)
Synopsis
Description
Examples
Author
License
pure function switch(array) result (string)
character(len=1),intent(in) :: array(:) character(len=SIZE(array)) :: stringpure function switch(string) result (array)or
character(len=*),intent(in) :: string character(len=1) :: array(len(string))
SWITCH(3f): generic function that switches CHARACTER string to an array of single characters or an array of single characters to a CHARACTER string. Useful in passing strings to C. New Fortran features may supersede these routines.
Sample program:
program demo_switch use M_strings, only : switch, isalpha, islower, nospace character(len=*),parameter :: & & dashes=’-----------------------------------’ character(len=*),parameter :: string=’This is a string’ character(len=1024) :: lineExpected output! First, examples of standard Fortran features ! returns array [F,T,T,T,T,T] write(*,*)[’A’,’=’,’=’,’=’,’=’,’=’] == ’=’ ! this would return T write(*,*)all([’=’,’=’,’=’,’=’,’=’,’=’] == ’=’) ! this would return F write(*,*)all([’A’,’=’,’=’,’=’,’=’,’=’] == ’=’)
! so to test if the string DASHES is all dashes ! using SWITCH(3f) is if(all(switch(dashes) == ’-’))then write(*,*)’DASHES is all dashes’ endif
! so to test is a string is all letters ! isalpha(3f) returns .true. only if character is a letter ! false because dashes are not a letter write(*,*) all(isalpha(switch(dashes))) ! false because of spaces write(*,*) all(isalpha(switch(string))) ! true because removed whitespace write(*,*) all(isalpha(switch(nospace(string))))
! to see if a string is all uppercase ! show the string write(*,*) string ! converted to character array write(*,’(1x,*("[",a,"]":))’) switch(string) write(*,’(*(l3))’) islower(switch(string))
! we need a string that is all letters line=nospace(string) write(*,*)’LINE=’,trim(line) ! all true except first character write(*,*) islower(switch(nospace(string))) ! should be false write(*,*) all(islower(switch(nospace(string)))) ! should be true write(*,*) all(islower(switch(nospace(string(2:)))))
end program demo_switch
> F T T T T T > T > F > DASHES is all dashes > F > F > T > This is a string > [T][h][i][s][ ][i][s][ ][a][ ][s][t][r][i][n][g] > F T T T F T T F T F T T T T T T > LINE=Thisisastring > F T T T T T T T T T T T T > F > T
John S. Urban
Public Domain
transliterate(3f) - [M_strings:EDITING] replace characters from old set with new set (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
pure function transliterate(instr,old_set,new_set) result(outstr)
character(len=*),intent(in) :: instr character(len=*),intent(in) :: old_set character(len=*),intent(in) :: new_set character(len=len(instr)) :: outstr
Translate, squeeze, and/or delete characters from the input string.
instr input string to change old_set list of letters to change in INSTR if found Each character in the input string that matches a character in the old set is replaced.
new_set list of letters to replace letters in OLD_SET with. If the new_set is the empty set the matched characters are deleted.If the new_set is shorter than the old set the last character in the new set is used to replace the remaining characters in the new set.
outstr instr with substitutions applied
Sample Program:
program demo_transliterateuse M_strings, only : transliterate implicit none character(len=80) :: STRING
STRING=’aAbBcCdDeEfFgGhHiIjJkKlLmMnNoOpPqQrRsStTuUvVwWxXyYzZ’ write(*,’(a)’) STRING
! convert a string to uppercase: write(*,*) TRANSLITERATE(STRING, & & ’abcdefghijklmnopqrstuvwxyz’,’ABCDEFGHIJKLMNOPQRSTUVWXYZ’)
! change all miniscule letters to a colon (":"): write(*,*) TRANSLITERATE(STRING, & & ’abcdefghijklmnopqrstuvwxyz’,’:’)
! delete all miniscule letters write(*,*) TRANSLITERATE(STRING, & & ’abcdefghijklmnopqrstuvwxyz’,’’)
end program demo_transliterate
Expected output
> aAbBcCdDeEfFgGhHiIjJkKlLmMnNoOpPqQrRsStTuUvVwWxXyYzZ > AABBCCDDEEFFGGHHIIJJKKLLMMNNOOPPQQRRSSTTUUVVWWXXYYZZ > :A:B:C:D:E:F:G:H:I:J:K:L:M:N:O:P:Q:R:S:T:U:V:W:X:Y:Z > ABCDEFGHIJKLMNOPQRSTUVWXYZ
John S. Urban
Public Domain
unquote(3f) - [M_strings:QUOTES] remove quotes from string as if read with list-directed input (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function unquote(quoted_str,esc) result (unquoted_str)
character(len=*),intent(in) :: quoted_str character(len=1),optional,intent(in) :: esc character(len=:),allocatable :: unquoted_str
Remove quotes from a CHARACTER variable as if it was read using list-directed input. This is particularly useful for processing tokens read from input such as CSV files.Fortran can now read using list-directed input from an internal file, which should handle quoted strings, but list-directed input does not support escape characters, which UNQUOTE(3f) does.
quoted_str input string to remove quotes from, using the rules of list-directed input (two adjacent quotes inside a quoted region are replaced by a single quote, a single quote or double quote is selected as the delimiter based on which is encountered first going from left to right, ...) esc optional character used to protect the next quote character from being processed as a quote, but simply as a plain character.
unquoted_str The output string, which is based on removing quotes from quoted_str.
Sample program:
program demo_unquote use M_strings, only : unquote implicit none character(len=128) :: quoted_str character(len=:),allocatable :: unquoted_str character(len=1),parameter :: esc=’#146; character(len=1024) :: iomsg integer :: iostat character(len=1024) :: dummy do write(*,’(a)’,advance=’no’)’Enter test string:’ read(*,’(a)’,iostat=iostat,iomsg=iomsg)quoted_str if(iostat /= 0)then write(*,*)trim(iomsg) exit endif! the original string write(*,’(a)’)’QUOTED [’//trim(quoted_str)//’]’
! the string processed by unquote(3f) unquoted_str=unquote(trim(quoted_str),esc) write(*,’(a)’)’UNQUOTED [’//unquoted_str//’]’
! read the string list-directed to compare the results read(quoted_str,*,iostat=iostat,iomsg=iomsg)dummy if(iostat /= 0)then write(*,*)trim(iomsg) else write(*,’(a)’)’LIST DIRECTED[’//trim(dummy)//’]’ endif enddo end program demo_unquote
John S. Urban
Public Domain
upper(3f) - [M_strings:CASE] changes a string to uppercase (LICENSE:PD)
Synopsis
Description
Options
Returns
Trivia
Examples
Author
License
elemental pure function upper(str,begin,end) result (string)
character(*), intent(in) :: str integer,optional,intent(in) :: begin,end character(len(str)) :: string ! output string
upper(string) returns a copy of the input string with all characters converted in the optionally specified range to uppercase, assuming ASCII character sets are being used. If no range is specified the entire string is converted to uppercase.
str string to convert to uppercase begin optional starting position in "str" to begin converting to uppercase end optional ending position in "str" to stop converting to uppercase
upper copy of the input string with all characters converted to uppercase over optionally specified range.
The terms "uppercase" and "lowercase" date back to the early days of the mechanical printing press. Individual metal alloy casts of each needed letter, or punctuation symbol, were meticulously added to a press block, by hand, before rolling out copies of a page. These metal casts were stored and organized in wooden cases. The more often needed miniscule letters were placed closer to hand, in the lower cases of the work bench. The less often needed, capitalized, majuscule letters, ended up in the harder to reach upper cases.
Sample program:
program demo_upper use M_strings, only: upper implicit none character(len=:),allocatable :: s s=’ ABCDEFG abcdefg ’ write(*,*) ’mixed-case input string is ....’,s write(*,*) ’upper-case output string is ...’,upper(s) write(*,*) ’make first character uppercase ... ’,& & upper(’this is a sentence.’,1,1) write(*,’(1x,a,*(a:,"+"))’) ’UPPER(3f) is elemental ==>’,& & upper(["abc","def","ghi"]) end program demo_upperExpected output
mixed-case input string is .... ABCDEFG abcdefg upper-case output string is ... ABCDEFG ABCDEFG make first character uppercase ... This is a sentence. UPPER(3f) is elemental ==>ABC+DEF+GHI
John S. Urban
Public Domain
upper_quoted(3f) - [M_strings:CASE] elemental function converts string to uppercase skipping strings quoted per Fortran syntax rules (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
See Also
Author
License
elemental pure function upper_quoted(str) result (string)
character(*), intent(in) :: str character(len(str)) :: string ! output string
upper_quoted(string) returns a copy of the input string with all not-quoted characters converted to uppercase, assuming ASCII character sets are being used. The quoting rules are the same as for Fortran source. Either a single or double quote starts a quoted string, and a quote character of the same type is doubled when it appears internally in the quoted string. If a double quote quotes the string single quotes may appear in the quoted string as single characters, and vice-versa for single quotes.
str string to convert to uppercase
upper copy of the input string with all unquoted characters converted to uppercase
Sample program:
program demo_upper_quoted use M_strings, only: upper_quoted implicit none character(len=:),allocatable :: s s=’ ABCDEFG abcdefg "Double-Quoted" ’’Single-Quoted’’ "with ""& & Quote" everything else’ write(*,*) ’mixed-case input string is ....’,s write(*,*) ’upper-case output string is ...’,upper_quoted(s) write(*,’(1x,a,*(a:,"+"))’) ’upper_quoted(3f) is elemental ==>’, & & upper_quoted(["abc","def","ghi"]) end program demo_upper_quotedExpected output:
mixed-case input string is .... ABCDEFG abcdefg "Double-Quoted" ... ... ’Single-Quoted’ "with "" Quote" everything else upper-case output string is ... ABCDEFG ABCDEFG "Double-Quoted" ... ... ’Single-Quoted’ "with "" Quote" EVERYTHING ELSE upper_quoted(3f) is elemental ==>ABC+DEF+GHI
flower(1)
John S. Urban
Public Domain
v2s(3f) - [M_strings:TYPE] return numeric string from a numeric value (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function v2s(value) result(outstr)
integer|real|doubleprecision|logical,intent(in ) :: value character(len=:),allocatable :: outstr character(len=*),optional,intent(in) :: fmt
v2s(3f) returns a representation of a numeric value as a string when given a numeric value of type REAL, DOUBLEPRECISION, INTEGER or LOGICAL. It creates the strings using internal WRITE() statements. Trailing zeros are removed from non-zero values, and the string is left-justified.
VALUE input value to be converted to a string FMT format can be explicitly given, but is limited to generating a string of eighty or less characters.
OUTSTR returned string representing input value,
Sample Program:
program demo_v2s use M_strings, only: v2s write(*,*) ’The value of 3.0/4.0 is [’//v2s(3.0/4.0)//’]’ write(*,*) ’The value of 1234 is [’//v2s(1234)//’]’ write(*,*) ’The value of 0d0 is [’//v2s(0d0)//’]’ write(*,*) ’The value of .false. is [’//v2s(.false.)//’]’ write(*,*) ’The value of .true. is [’//v2s(.true.)//’]’ end program demo_v2sExpected output
The value of 3.0/4.0 is [0.75] The value of 1234 is [1234] The value of 0d0 is [0] The value of .false. is [F] The value of .true. is [T]
John S. Urban
Public Domain
value_to_string(3f) - [M_strings:TYPE] return numeric string from a numeric value (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
subroutine value_to_string(value,chars[,lgth,ierr,fmt,trimz])
character(len=*) :: chars ! minimum of 23 characters required !-------- ! VALUE may be any <em>one</em> of the following types: doubleprecision,intent(in) :: value real,intent(in) :: value integer,intent(in) :: value logical,intent(in) :: value !-------- character(len=*),intent(out) :: chars integer,intent(out),optional :: lgth integer,optional :: ierr character(len=*),intent(in),optional :: fmt logical,intent(in) :: trimz
value_to_string(3f) returns a numeric representation of a numeric value in a string given a numeric value of type REAL, DOUBLEPRECISION, INTEGER or LOGICAL. It creates the string using internal writes. It then removes trailing zeros from non-zero values, and left-justifies the string.
VALUE input value to be converted to a string FMT You may specify a specific format that produces a string up to the length of CHARS; optional. TRIMZ If a format is supplied the default is not to try to trim trailing zeros. Set TRIMZ to .true. to trim zeros from a string assumed to represent a simple numeric value.
CHARS returned string representing input value, must be at least 23 characters long; or what is required by optional FMT if longer. LGTH position of last non-blank character in returned string; optional. IERR If not zero, error occurred; optional.
Sample program:
program demo_value_to_string use M_strings, only: value_to_string implicit none character(len=80) :: string integer :: lgth call value_to_string(3.0/4.0,string,lgth) write(*,*) ’The value is [’,string(:lgth),’]’Expected outputcall value_to_string(3.0/4.0,string,lgth,fmt=’’) write(*,*) ’The value is [’,string(:lgth),’]’
call value_to_string& &(3.0/4.0,string,lgth,fmt=’("THE VALUE IS ",g0)’) write(*,*) ’The value is [’,string(:lgth),’]’
call value_to_string(1234,string,lgth) write(*,*) ’The value is [’,string(:lgth),’]’
call value_to_string(1.0d0/3.0d0,string,lgth) write(*,*) ’The value is [’,string(:lgth),’]’
end program demo_value_to_string
The value is [0.75] The value is [ 0.7500000000] The value is [THE VALUE IS .750000000] The value is [1234] The value is [0.33333333333333331]
John S. Urban
Public Domain
visible(3f) - [M_strings:NONALPHA] expand a string to control and meta-control representations (LICENSE:PD)
Synopsis
Description
Examples
Bugs
Author
License
function visible(input) result(output)
character(len=*),intent(in) :: input character(len=:),allocatable :: output
visible(3f) expands characters to commonly used sequences used to represent the characters as control sequences or meta-control sequences.
Sample Program:
program demo_visible use M_strings, only : visible integer :: i do i=0,255 write(*,’(i0,1x,a)’)i,visible(char(i)) enddo end program demo_visible
The expansion is not reversible, as input sequences such as "M-" or "^a" will look like expanded sequences.
John S. Urban
Public Domain
zpad(3f) - [M_strings:LENGTH] pad a string on the left with zeros to specified length (LICENSE:PD)
Synopsis
Description
Options
Returns
Examples
Author
License
function zpad(valuein,length) result(strout)
class*,intent(in) :: valuein(..) integer,intent(in),optional :: length
zpad(3f) crops the input string (or integer, which will be converted to a string) and then pads it on the left with zeros to the specified length.Note that if the trimmed input string is already as long or longer than the requested length the trimmed original string is returned.
For strings representing unsigned numbers this is basically an alias for
strout=pad(str,length,’0’,clip=.true.,right=.false.)For integers the same is often done with internal WRITE(3f) statements such as
write(strout,’(i5.5)’)ivaluebut unlike internal I/O the function call can be used in expressions or passed as a procedure argument.
valuein The input value to left-pad. May be a scalar or vector string or integer. If the leftmost non-blank character is a sign character it is moved to the left-most position of the output. length The minimum string length to return. If not present, the length of the input parameter VALUEIN is used. If the input value VALUEIN is an integer no zero padding occurs if LENGTH is not supplied.
strout A trimmed string padded on the left with zeros to the requested length
Sample Program:
program demo_zpad use M_strings, only : zpad implicit none character(len=*),parameter :: boxed=’("[",a,"]",*(g0,1x))’ integer :: lun, i print boxed, zpad( ’111’, 5),’basic use’ print boxed, zpad( valuein=42 , length=7),’by argument name’ print boxed, zpad( ’ 34567 ’, 7),’cropped before padding’ print boxed, zpad( ’123456789’, 5),’input longer than length’ print boxed, zpad( ’ +34567 ’, 7),’starts with plus sign’ print boxed, zpad( ’ -34567 ’, 7),’starts with minus sign’ print boxed, zpad(1234),’some integers instead of strings’ print boxed, zpad(-1234) print boxed, zpad(1234,8) print boxed, zpad(-1234,8) print boxed, zpad(’’),’a null gets you nothing’ print boxed, zpad(’0’),’but blanks are used for default length’ print boxed, zpad(’0 ’) print boxed, zpad(’ ’) print *, ’input value may be an array:’ print ’("[",a,"]")’, zpad([1,10,100,1000,10000,100000],8)Results:! example usage: ! open output_00085.dat i=85 open(newunit=lun,file=’output_’//zpad(i,5)//’.dat’) close(unit=lun,status=’delete’)
end program demo_zpad
> [00111]basic use > [0000042]by argument name > [0034567]cropped before padding > [123456789]input longer than length > [+0034567]starts with plus sign > [-0034567]starts with minus sign > [1234]some integers instead of strings > [-1234] > [00001234] > [-00001234] > []a null gets you nothing > [0]but blanks are used for default length > [00000] > [00000] > input value may be an array: > [00000001] > [00000010] > [00000100] > [00001000] > [00010000] > [00100000]
John S. Urban
Public Domain
M_strings__oop(3f) - [M_strings::INTRO::OOPS] OOP Fortran string module
Synopsis
Description
See Also
Examples
Author
License
use M_strings__oop
The M_strings(3fm) module is a collection of Fortran procedures that supplement the built-in intrinsic string routines. Routines for parsing, tokenizing, changing case, substituting new strings for substrings, locating strings with simple wildcard expressions, removing tabs and line terminators and other string manipulations are included.M_strings__oop(3fm) is a companion module that provides an OOP interface to the M_strings module.
There are additional routines in other GPF modules for working with expressions (M_calculator), time strings (M_time), random strings (M_random, M_uuid), lists (M_list), and interfacing with the C regular expression library (M_regex).
Each of the procedural functions in M_strings(3fm) includes an example program in the corresponding man(1) page for the function. The object-oriented interface does not have individual man(1) pages, but is instead demonstrated using the following example program:
program demo_M_strings__oop ! ! This is an example using the object-oriented class/type model ! defined in M_strings__oop ! ! This is essentially the same functionality as the procedures ! combined with several Fortran intrinsics and overloaded operators ! use M_strings__oop,only : string, p implicit none TYPE(string) :: str1, str2, str3, str4Expected outputwrite(*,*)’Call methods of type(STRING)’
! define TYPE(STRING) with constructor str2=string(’ This is a String! ’) str4=string(’ a String ’)
write(*,101)’str2%str is ................ ’, & & str2%str ! print string member of type write(*,202)’len ........................ ’, & & str2%len() ! same as intrinsic LEN() write(*,202)’len_trim ................... ’, & & str2%len_trim() ! same as intrinsic LEN_TRIM() write(*,202)’index("is")................. ’, & & str2%index("is") ! same as intrinsic INDEX() write(*,202)’index("is",back=.T.) ....... ’, & & str2%index("is",back=.TRUE.) ! same as intrinsic INDEX() write(*,101)’upper ...................... ’, & & p(str2%upper()) ! call upper() write(*,101)’lower ...................... ’, & & p(str2%lower()) ! call lower() write(*,101)’reverse .................... ’, & & p(str2%reverse()) ! call reverse() write(*,101)’adjustl .................... ’, & & p(str2%adjustl()) ! same as intrinsic ADJUSTL() write(*,101)’adjustr .................... ’, & & p(str2%adjustr()) ! same as intrinsic ADJUSTR() write(*,101)’adjustc .................... ’, & & p(str2%adjustc()) ! center string in current string length write(*,101)’adjustc(40) ................ ’, & & p(str2%adjustc(40)) ! center string in string length of NN write(*,101)’lenset(40) ................. ’, & & p(str2%lenset(40)) ! call pad() to force minimal string length write(*,101)’trim ....................... ’, & & p(str2%trim()) ! same as intrinsic TRIM() write(*,101)’crop ....................... ’, & & p(str2%crop()) ! trim leading and trailing spaces write(*,101)’substitute("This","Here") .. ’, & & p(str2%substitute("This","Here")) ! call SUBSTITUTE() write(*,101)’compact .................... ’, & & p(str2%compact()) ! call COMPACT() write(*,101)’compact("") ................ ’, & & p(str2%compact("")) write(*,101)’compact(":") ............... ’, & & p(str2%compact(":")) ! calls M_strings procedure TRANSLITERATE() write(*,101)’transliterate("aei","VWX") . ’, & & p(str2%transliterate("aei","VWX")) write(*,101)’transliterate("aeiou"," ") . ’, & & p(str2%transliterate("aeiou"," ")) write(*,101)’transliterate("aeiou","") .. ’, & & p(str2%transliterate("aeiou","")) write(*,101)’transliterate(" aeiou","") . ’, & & p(str2%transliterate(" aeiou","")) write(*,404)’chars .................... . ’, & & str4%chars() ! call SWITCH()
str2%str=’\t\tSome tabs\t x\bX ’ write(*,101)’str2%str ................... ’,str2%str write(*,101)’expand ..................... ’, & & p(str2%expand()) str2=str2%expand() write(*,101)’notabs ..................... ’, & & p(str2%notabs()) ! calls NOTABS() write(*,101)’noesc ...................... ’, & & p(str2%noesc()) ! calls NOESC()
write(*,*)repeat(’=’,68) write(*,*)’Casting to numeric variables’ str3=string(’ 12.345678901234567e1 ’) write(*,101)’str3%str ................... ’,str3%str ! calls to M_strings procedure STRING_TO_VALUE() write(*,*)’int ....................... ’, str3%int() write(*,*)’nint ....................... ’, str3%nint() write(*,*)’real ....................... ’, str3%real() write(*,*)’dble ....................... ’, str3%dble()
write(*,*)repeat(’=’,68) write(*,*)’Matching simple globbing patterns’ str3=string(’ 12.345678901234567e1 ’) str3=string(’Four score and seven years ago’) write(*,101)’str3%str ................... ’,str3%str ! %match calls M_strings procedure GLOB write(*,*)’match("Fo*") ............... ’, str3%match("Fo*") write(*,*)’match("and") ............... ’, str3%match("and") write(*,*)’match("*and*") ............. ’, str3%match("*and*")
101 format(1x,a,"[",a,"]") 202 format(1x,a,i0) 303 format(1x,*(l3)) 404 format(1x,a,*("[",a1,"]":))
write(*,*)repeat(’=’,68) write(*,*)’OVERLOADED OPERATORS (add and subtract,return TYPE(STRING))’ str1%str=’123.456’ str2%str=’AaBbCcDdEeFfGgHhIi AaBbCcDdEeFfGgHhIi’ write(*,101)’str1%str ................... ’,str1%str write(*,101)’str2%str ................... ’,str2%str write(*,*)’str1 + str2 ................ ’,p(str1 + str2) ! a string that looks like a numeric value can have a value added write(*,*)’str1 + 20000 ............... ’,p(str1 +20000) write(*,*)’str1 - 20.0 ................ ’,p(str1 -20.0) write(*,*)’str2 - "Aa" (removes ALL) .. ’,p(str2 - ’Aa’)
write(*,*)repeat(’=’,68) write(*,*)’OVERLOADED OPERATORS (multiply,return TYPE(STRING))’ str1%str=’AaBbCcDdEeFfGgHhIi’ write(*,101)’str1%str ................... ’,str1%str write(*,*)’str1 * 2 ................... ’,p(str1 * 2)
write(*,*)repeat(’=’,68) write(*,*)’OVERLOADED OPERATORS (//,return TYPE(STRING))’ str1%str=’String one:’ str2%str=’String two:’ write(*,101)’str1%str ................... ’,str1%str write(*,101)’str2%str ................... ’,str2%str write(*,*)’str1 // str2 ................ ’,p(str1 // str2) ! numeric values are converted to strings write(*,*)’str1 // 20000 ............... ’,p(str1 // 20000) write(*,*)’str1 // 20.0 ................ ’,p(str1 // 20.0)
write(*,*)repeat(’=’,68) write(*,*)’OVERLOADED OPERATORS (logical comparisons,return logical)’ ! NOTE: comparisons are performed on the character variable members ! of the type(string) str1%str=’abcdefghij’ str2%str=’klmnopqrst’ write(*,101)’str1%str ................... ’,str1%str write(*,101)’str2%str ................... ’,str2%str write(*,*)’: EQ LT GT LE GE NE’ write(*,*)’compare str1 to str1’ write(*,303)str1 == str1 ,str1 < str1 ,str1 > str1 ,str1 <= str1 & & ,str1 >= str1 ,str1 /= str1 write(*,*)’compare str1 to str2’ write(*,303)str1 == str2 ,str1 < str2 ,str1 > str2 ,str1 <= str2 & & ,str1 >= str2 ,str1 /= str2 write(*,*)’compare str2 to str1’ write(*,303)str2 == str1 ,str2 < str1 ,str2 > str1 ,str2 <= str1 & & ,str2 >= str1 ,str2 /= str1
write(*,*)repeat(’=’,68)
end program demo_M_strings__oop
exercise the M_STRING_OOP module interface =================================================================== Call methods of type(STRING) =================================================================== str2%str is ................ [ This is a String! ] len ........................ 36 len_trim ................... 23 index("is")................. 6 index("is",back=.T.) ....... 10 upper ...................... [ THIS IS A STRING! ] lower ...................... [ this is a string! ] reverse .................... [ !gnirtS a si sihT ] adjustl .................... [This is a String! ] adjustr .................... [ This is a String!] adjustc .................... [ This is a String! ] adjustc(40) ................ [ This is a String! ] lenset(40) ................. [ This is a String! ] trim ....................... [ This is a String!] crop ....................... [This is a String!] substitute("This","Here") .. [ Here is a String! ] compact .................... [This is a String!] compact("") ................ [ThisisaString!] compact(":") ............... [This:is:a:String!] transliterate("aei","VWX") . [ ThXs Xs V StrXng! ] transliterate("aeiou"," ") . [ Th s s Str ng! ] transliterate("aeiou","") .. [ Ths s Strng! ] transliterate(" aeiou","") . [ThssStrng! ] chars .................... . [ ][a][ ][s][t][r][i][n][g][ ] =================================================================== str2%str ................... [\t\tSome tabs\t x\bX ] expand ..................... [ Some tabs x X] notabs ..................... [ Some tabs x X] noesc ...................... [ Some tabs x X] =================================================================== Casting to numeric variables str3%str ................... [ 12.345678901234567e1 ] int ....................... 123 real ....................... 123.456787 dble ....................... 123.45678901234567 =================================================================== Matching simple globbing patterns str3%str ................... [Four score and seven years ago] match("Fo*") ............... T match("and") ............... F match("*and*") ............. T ==================================================================== OVERLOADED OPERATORS (add and subtract, return TYPE(STRING)) str1%str .................. [123.456] str2%str .................. [AaBbCcDdEeFfGgHhIi AaBbCcDdEeFfGgHhIi] str1 + str2 ............... 123.456 AaBbCcDdEeFfGgHhIi AaBbCcDdEeFfGgHhIi str1 + 20000 .............. 20123.455999999998 str1 - 20.0 ............... -103.456 str2 - "Aa" (removes ALL) . BbCcDdEeFfGgHhIi BbCcDdEeFfGgHhIi =================================================================== OVERLOADED OPERATORS (multiply, return TYPE(STRING)) str1%str ................... [AaBbCcDdEeFfGgHhIi] str1 * 2 ................... AaBbCcDdEeFfGgHhIiAaBbCcDdEeFfGgHhIi =================================================================== OVERLOADED OPERATORS (//, return TYPE(STRING)) str1%str ................... [String one:] str2%str ................... [String two:] str1 // str2 ............... String one:String two: str1 // 20000 .............. String one:20000 str1 // 20.0 ............... String one:20.0 =================================================================== OVERLOADED OPERATORS (logical comparisons, return logical) str1%str ................... [abcdefghij] str2%str ................... [klmnopqrst] : EQ LT GT LE GE NE compare str1 to str1 : T F F T T F compare str1 to str2 : F T F T F T compare str2 to str1 : F F T F T T ===================================================================
John S. Urban
Public Domain