Basic procedures for manipulating character variables#

len#

Name#

len(3) - [CHARACTER] Length of a character entity

Synopsis#

    result = len(string [,kind])
     integer(kind=KIND) function len(string,KIND)

      character(len=*),intent(in) :: string(..)
      integer,optional,intent(in) :: KIND

Characteristics#

  • string is a scalar or array character variable

  • KIND is a scalar integer constant expression.

  • the returned value is the same integer kind as the kind argument, or of the default integer kind if kind is not specified.

Description#

len(3) returns the length of a character string.

If string is an array, the length of a single element of string is returned, as all elements of an array are the same length.

Note that string need not be defined when this intrinsic is invoked, as only the length (not the content) of string is needed.

Options#

  • string

    A scalar or array string to return the length of. If it is an unallocated allocatable variable or a pointer that is not associated, its length type parameter shall not be deferred.

  • kind

    A constant indicating the kind parameter of the result.

Result#

The result has a value equal to the number of characters in STRING if it is scalar or in an element of STRING if it is an array.

Examples#

Sample program

program demo_len
implicit none

! fixed length
character(len=40) :: string
! allocatable length
character(len=:),allocatable :: astring
character(len=:),allocatable :: many_strings(:)
integer :: ii
  ! BASIC USAGE
   ii=len(string)
   write(*,*)'length =',ii

  ! ALLOCATABLE VARIABLE LENGTH CAN CHANGE
  ! the allocatable string length will be the length of RHS expression
   astring=' How long is this allocatable string? '
   write(*,*)astring, ' LEN=', len(astring)
  ! print underline
   write(*,*) repeat('=',len(astring))
  ! assign new value to astring and length changes
   astring='New allocatable string'
   write(*,*)astring, ' LEN=', len(astring)
  ! print underline
   write(*,*) repeat('=',len(astring))

  ! THE STRING LENGTH WILL BE CONSTANT FOR A FIXED-LENGTH VARIABLE
   string=' How long is this fixed string? '
   write(*,*)string,' LEN=',len(string)
   string='New fixed string '
   write(*,*)string,' LEN=',len(string)

  ! ALL STRINGS IN AN ARRAY ARE THE SAME LENGTH
  ! a scalar is returned for an array, as all values in a Fortran
  ! character array must be of the same length.
   many_strings = [ character(len=7) :: 'Tom', 'Dick', 'Harry' ]
   write(*,*)'length of ALL elements of array=',len(many_strings)

  ! NAME%LEN IS ESSENTIALLY THE SAME AS LEN(NAME)
  ! you can also query the length (and other attributes) of a string
  ! using a "type parameter inquiry" (available since fortran 2018)
   write(*,*)'length from type parameter inquiry=',string%len
  ! %len is equivalent to a call to LEN() except the kind of the integer
  ! value returned is always of default kind.

  ! LOOK AT HOW A PASSED STRING CAN BE USED ...
   call passed(' how long? ')

contains

   subroutine passed(str)
   character(len=*),intent(in)  :: str
   ! the length of str can be used in the definitions of variables
      ! you can query the length of the passed variable
      write(*,*)'length of passed value is ', LEN(str)
   end subroutine passed

end program demo_len

Results:

 >  length =          40
 >   How long is this allocatable string?  LEN=          38
 >  ======================================
 >  New allocatable string LEN=          22
 >  ======================
 >   How long is this fixed string?          LEN=          40
 >  New fixed string                         LEN=          40
 >  length of ALL elements of array=           7
 >  length from type parameter inquiry=          40
 >  length of passed value is           11

Standard#

FORTRAN 77 ; with kind argument - Fortran 2003

See Also#

len_trim(3), adjustr(3), trim(3), and adjustl(3) are related routines that allow you to deal with leading and trailing blanks.

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

new_line#

Name#

new_line(3) - [CHARACTER:INQUIRY] Newline character

Synopsis#

    result = new_line(c)
     character(len=1,kind=KIND) function new_line(c)

      character(len=1,kind=KIND),intent(in) :: c(..)

Characteristics#

  • c shall be of type character. It may be a scalar or an array.

  • the result is a character scalar of length one with the same kind type parameter as c.

Description#

new_line(3) returns the newline character.

Normally, newlines are generated with regular formatted I/O statements like WRITE() and PRINT() when each statement completes:

   print *, 'x=11'
   print *
   print *, 'y=22'
   end

produces:

   x=11

   y=22

Alternatively, a “/” descriptor in a format is used to generate a newline on the output. For example:

   write(*,'(a,1x,i0,/,a)') 'x =',11,'is the answer'
   end

produces:

   x = 11
   is the answer

Also, for formatted sequential output if more data is listed on the output statement than can be represented by the format statement a newline is generated and then the format is reused until the output list is exhausted.

   write(*,'(a,"=",i0)') 'x', 10, 'y', 20
   end

produces

   x=10
   y=20

But there are occasions, particularly when non-advancing I/O or stream I/O is being generated (which does not generate a newline at the end of each WRITE statement, as normally occurs) where it is preferable to place a newline explicitly in the output at specified points.

To do so you must make sure you are generating the correct newline character, which the techniques above do automatically.

The newline character varies between some platforms, and can even depend on the encoding (ie. which character set is being used) of the output file. In these cases selecting the correct character to output can be determined by the new_line(3) procedure.

Options#

  • c

    an arbitrary character whose kind is used to decide on the output character that represents a newline.

Result#

Case (i)

If a is default character and the character in position 10 of the ASCII collating sequence is representable in the default character set, then the result is achar(10).

This is the typical case, and just requires using “new_line(‘a’)”.

Case (ii)

If a is an ASCII character or an ISO 10646 character, then the result is char(10, kind (a)).

Case (iii)

Otherwise, the result is a processor-dependent character that represents a newline in output to files connected for formatted stream output if there is such a character.

Case (iv)

If not of the previous cases apply, the result is the blank character.

Examples#

Sample program:

program demo_new_line
implicit none
character,parameter :: nl=new_line('a')
character(len=:),allocatable :: string
real :: r
integer :: i, count

  ! basics
   ! print a string with a newline embedded in it
   string='This is record 1.'//nl//'This is record 2.'
   write(*,'(a)') string

   ! print a newline character string
   write(*,'(*(a))',advance='no') &
      nl,'This is record 1.',nl,'This is record 2.',nl

   ! output a number of words of random length as a paragraph
   ! by inserting a new_line before line exceeds 70 characters

  ! simplistic paragraph print using non-advancing I/O
   count=0
   do i=1,100

      ! make some fake word of random length
      call random_number(r)
      string=repeat('x',int(r*10)+1)

      count=count+len(string)+1
      if(count.gt.70)then
         write(*,'(a)',advance='no')nl
         count=len(string)+1
      endif
      write(*,'(1x,a)',advance='no')string
   enddo
   write(*,'(a)',advance='no')nl

end program demo_new_line

Results:

   This is record 1.
   This is record 2.

   This is record 1.
   This is record 2.
    x x xxxx xxxxxxx xxxxxxxxxx xxxxxxxxx xxxx xxxxxxxxxx xxxxxxxx
    xxxxxxxxx xxxx xxxxxxxxx x xxxxxxxxx xxxxxxxx xxxxxxxx xxxx x
    xxxxxxxxxx x x x xxxxxx xxxxxxxxxx x xxxxxxxxxx x xxxxxxx xxxxxxxxx
    xx xxxxxxxxxx xxxxxxxx x xx xxxxxxxxxx xxxxxxxx xxx xxxxxxx xxxxxx
    xxxxx xxxxxxxxx x xxxxxxxxxx xxxxxx xxxxxxxx xxxxx xxxxxxxx xxxxxxxx
    xxxxx xxx xxxxxxxx xxxxxxx xxxxxxxx xxx xxxx xxx xxxxxxxx xxxxxx
    xxxxxxx xxxxxxx xxxxx xxxxx xx xxxxxx xx xxxxxxxxxx xxxxxx x xxxx
    xxxxxx xxxxxxx x xxx xxxxx xxxxxxxxx xxx xxxxxxx x xxxxxx xxxxxxxxx
    xxxx xxxxxxxxx xxxxxxxx xxxxxxxx xxx xxxxxxx xxxxxxx xxxxxxxxxx
    xxxxxxxxxx xxxxxx xxxxx xxxx xxxxxxx xx xxxxxxxxxx xxxxxx xxxxxx
    xxxxxx xxxx xxxxx

Standard#

Fortran 2003

See also#

achar(3), char(3), iachar(3), ichar(3), selected_char_kind(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

repeat#

Name#

repeat(3) - [CHARACTER] Repeated string concatenation

Synopsis#

    result = repeat(string, ncopies)
     character(len=len(string)*ncopies) function repeat(string, ncopies)

      character(len=*),intent(in)   :: string
      integer(kind=**),intent(in)   :: ncopies

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • string is a scalar character type.

  • ncopies is a scalar integer.

  • the result is a new scalar of type character of the same kind as string

Description#

repeat(3) concatenates copies of a string.

Options#

  • string

    The input string to repeat

  • ncopies

    Number of copies to make of string, greater than or equal to zero (0).

Result#

A new string built up from ncopies copies of string.

Examples#

Sample program:

program demo_repeat
implicit none
    write(*,'(a)') repeat("^v", 35)         ! line break
    write(*,'(a)') repeat("_", 70)          ! line break
    write(*,'(a)') repeat("1234567890", 7)  ! number line
    write(*,'(a)') repeat("         |", 7)  !
end program demo_repeat

Results:

 > ^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v^v
 > ______________________________________________________________________
 > 1234567890123456789012345678901234567890123456789012345678901234567890
 >          |         |         |         |         |         |         |

Standard#

Fortran 95

See Also#

Functions that perform operations on character strings:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

#

achar#

Name#

achar(3) - [CHARACTER:CONVERSION] Returns a character in a specified position in the ASCII collating sequence

Synopsis#

    result = achar(i [,kind])
     elemental character(len=1,kind=KIND) function achar(i,KIND)

      integer(kind=**),intent(in) :: i
      integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • The character kind returned is the value of kind if present. otherwise, a single default character is returned.

Description#

achar(3) returns the character located at position i (commonly called the ADE or ASCII Decimal Equivalent) in the ASCII collating sequence.

The achar(3) function is often used for generating in-band escape sequences to control terminal attributes, as it makes it easy to print unprintable characters such as escape and tab. For example:

   write(*,'(*(a))')achar(27),'[2J'

will clear the screen on an ANSI-compatible terminal display,

Note#

The ADEs (ASCII Decimal Equivalents) for ASCII are

*-------*-------*-------*-------*-------*-------*-------*-------*
| 00 nul| 01 soh| 02 stx| 03 etx| 04 eot| 05 enq| 06 ack| 07 bel|
| 08 bs | 09 ht | 10 nl | 11 vt | 12 np | 13 cr | 14 so | 15 si |
| 16 dle| 17 dc1| 18 dc2| 19 dc3| 20 dc4| 21 nak| 22 syn| 23 etb|
| 24 can| 25 em | 26 sub| 27 esc| 28 fs | 29 gs | 30 rs | 31 us |
| 32 sp | 33  ! | 34  " | 35  # | 36  $ | 37  % | 38  & | 39  ' |
| 40  ( | 41  ) | 42  * | 43  + | 44  , | 45  - | 46  . | 47  / |
| 48  0 | 49  1 | 50  2 | 51  3 | 52  4 | 53  5 | 54  6 | 55  7 |
| 56  8 | 57  9 | 58  : | 59  ; | 60  < | 61  = | 62  > | 63  ? |
| 64  @ | 65  A | 66  B | 67  C | 68  D | 69  E | 70  F | 71  G |
| 72  H | 73  I | 74  J | 75  K | 76  L | 77  M | 78  N | 79  O |
| 80  P | 81  Q | 82  R | 83  S | 84  T | 85  U | 86  V | 87  W |
| 88  X | 89  Y | 90  Z | 91  [ | 92  \ | 93  ] | 94  ^ | 95  _ |
| 96  ` | 97  a | 98  b | 99  c |100  d |101  e |102  f |103  g |
|104  h |105  i |106  j |107  k |108  l |109  m |110  n |111  o |
|112  p |113  q |114  r |115  s |116  t |117  u |118  v |119  w |
|120  x |121  y |122  z |123  { |124  | |125  } |126  ~ |127 del|
*-------*-------*-------*-------*-------*-------*-------*-------*

Options#

  • i

    the integer value to convert to an ASCII character, in the range 0 to 127.

    achar(3) shall have the value C for any character C capable of representation as a default character.

  • kind

    a integer initialization expression indicating the kind parameter of the result.

Result#

Assuming i has a value in the range 0 <= I <= 127, the result is the character in position i of the ASCII collating sequence, provided the processor is capable of representing that character in the character kind of the result; otherwise, the result is processor dependent.

Examples#

Sample program:

program demo_achar
use,intrinsic::iso_fortran_env,only:int8,int16,int32,int64
implicit none
integer :: i
   i=65
   write(*,'("decimal     =",i0)')i
   write(*,'("character   =",a1)')achar(i)
   write(*,'("binary      =",b0)')achar(i)
   write(*,'("octal       =",o0)')achar(i)
   write(*,'("hexadecimal =",z0)')achar(i)

   write(*,'(8(i3,1x,a,1x),/)')(i,achar(i), i=32,126)

   write(*,'(a)')upper('Mixed Case')
contains
! a classic use of achar(3) is to convert the case of a string

pure elemental function upper(str) result (string)
!
!$@(#) upper(3f): function to return a trimmed uppercase-only string
!
! input string to convert to all uppercase
character(*), intent(in)      :: str
! output string that contains no miniscule letters
character(len(str))           :: string
integer                       :: i, iend
integer,parameter             :: toupper = iachar('A')-iachar('a')
   iend=len_trim(str)
   ! initialize output string to trimmed input string
   string = str(:iend)
   ! process each letter in the string
   do concurrent (i = 1:iend)
       select case (str(i:i))
       ! located miniscule letter
       case ('a':'z')
          ! change miniscule to majuscule letter
          string(i:i) = achar(iachar(str(i:i))+toupper)
       end select
   enddo
end function upper
end program demo_achar

Results:

   decimal     =65
   character   =A
   binary      =1000001
   octal       =101
   hexadecimal =41
    32    33 !  34 "  35 #  36 $  37 %  38 &  39 '

    40 (  41 )  42 *  43 +  44 ,  45 -  46 .  47 /

    48 0  49 1  50 2  51 3  52 4  53 5  54 6  55 7

    56 8  57 9  58 :  59 ;  60 <  61 =  62 >  63 ?

    64 @  65 A  66 B  67 C  68 D  69 E  70 F  71 G

    72 H  73 I  74 J  75 K  76 L  77 M  78 N  79 O

    80 P  81 Q  82 R  83 S  84 T  85 U  86 V  87 W

    88 X  89 Y  90 Z  91 [  92 \  93 ]  94 ^  95 _

    96 `  97 a  98 b  99 c 100 d 101 e 102 f 103 g

   104 h 105 i 106 j 107 k 108 l 109 m 110 n 111 o

   112 p 113 q 114 r 115 s 116 t 117 u 118 v 119 w

   120 x 121 y 122 z 123 { 124 | 125 } 126 ~
   MIXED CASE

Standard#

FORTRAN 77. KIND argument added Fortran 2003

See Also#

char(3), iachar(3), ichar(3)

Resources#

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

char#

Name#

char(3) - [CHARACTER] Generate a character from a code value

Synopsis#

    result = char(i [,kind])
     elemental character(kind=KIND) function char(i,KIND)

      integer(kind=**),intent(in) :: i
      integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • a kind designated as ** may be any supported kind for the type

  • i is an integer of any kind

  • kind is an integer initialization expression indicating the kind parameter of the result.

  • The returned value is a character with the kind specified by kind or if kind is not present, the default character kind.

Description#

Generates a character value given a numeric code representing the position i in the collating sequence associated with the specified kind kind.

Note that achar(3) is a similar function specifically for ASCII characters that is preferred when only ASCII is being processed, which is equivalent to char(i,kind=selected_char_kind(“ascii”) )

The ichar(3) function is the reverse of char(3), converting characters to their collating sequence value.

Options#

  • i

    a value in the range 0 <= I <= n-1, where n is the number of characters in the collating sequence associated with the specified kind type parameter.

    For ASCII, n is 127. The default character set may or may not allow higher values.

  • kind

    A constant integer initialization expression indicating the kind parameter of the result. If not present, the default kind is assumed.

Result#

The return value is a single character of the specified kind, determined by the position of i in the collating sequence associated with the specified kind.

Examples#

Sample program:

program demo_char
implicit none
integer, parameter :: ascii =  selected_char_kind ("ascii")
character(len=1, kind=ascii ) :: c
integer :: i
  ! basic
   i=74
   c=char(i)
   write(*,*)'ASCII character ',i,'is ',c
  !
   print *, 'a selection of ASCII characters (shows hex if not printable)'
   do i=0,127,10
      c = char(i,kind=ascii)
      select case(i)
      case(32:126)
         write(*,'(i3,1x,a)')i,c
      case(0:31,127)
         ! print hexadecimal value for unprintable characters
         write(*,'(i3,1x,z2.2)')i,c
      case default
         write(*,'(i3,1x,a,1x,a)')i,c,'non-standard ASCII'
      end select
   enddo

end program demo_char

Results:

    ASCII character           74 is J
    a selection of ASCII characters (shows hex if not printable)
     0 00
    10 0A
    20 14
    30 1E
    40 (
    50 2
    60 <
    70 F
    80 P
    90 Z
   100 d
   110 n
   120 x

Standard#

FORTRAN 77

See Also#

achar(3), iachar(3), ichar(3)

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

iachar#

Name#

iachar(3) - [CHARACTER:CONVERSION] Return integer ASCII code of a character

Synopsis#

    result = iachar(c [,kind])
     elemental integer(kind=KIND) function iachar(c,kind)

      character(len=1),intent(in) :: c
      integer(kind=**),intent(in),optional :: KIND

Characteristics#

  • c is a single character

  • The return value is of type integer and of kind KIND. If KIND is absent, the return value is of default integer kind.

NOTE:

a kind designated as ** may be any supported kind for the type

Description#

iachar(3) returns the code for the ASCII character in the first character position of C.

Options#

  • c

    A character to determine the ASCII code of.

    A common extension is to allow strings but all but the first character is then ignored.

  • kind

    A constant initialization expression indicating the kind parameter of the result.

Result#

the result is the position of the character c in the ASCII collating sequence. It is nonnegative and less than or equal to 127.

By ASCII, it is meant that c is in the collating sequence defined by the codes specified in ISO/IEC 646:1991 (International Reference Version).

The value of the result is processor dependent if c is not in the ASCII collating sequence.

The results are consistent with the lge(3), lgt(3), lle(3), and llt(3) comparison functions. For example, if lle(C, D) is true, iachar(C) <= iachar (D) is true where C and D are any two characters representable by the processor.

Examples#

Sample program:

program demo_iachar
implicit none
   ! basic usage
    ! just does a string one character long
    write(*,*)iachar('A')
    ! elemental: can do an array of letters
    write(*,*)iachar(['A','Z','a','z'])

   ! convert all characters to lowercase
    write(*,'(a)')lower('abcdefg ABCDEFG')
contains
!
pure elemental function lower(str) result (string)
! Changes a string to lowercase
character(*), intent(In)     :: str
character(len(str))          :: string
integer                      :: i
   string = str
   ! step thru each letter in the string in specified range
   do i = 1, len(str)
      select case (str(i:i))
      case ('A':'Z') ! change letter to miniscule
         string(i:i) = char(iachar(str(i:i))+32)
      case default
      end select
   end do
end function lower
!
end program demo_iachar

Results:

   65
   65          90          97         122
   abcdefg abcdefg

Standard#

Fortran 95 , with KIND argument - Fortran 2003

See Also#

achar(3), char(3), ichar(3)

See ichar(3) in particular for a discussion of converting between numerical values and formatted string representations.

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

ichar#

Name#

ichar(3) - [CHARACTER:CONVERSION] Character-to-integer code conversion function

Synopsis#

    result = ichar(c [,kind])
     elemental integer(kind=KIND) function ichar(c,KIND)

      character(len=1,kind=**),intent(in) :: c
      integer,intent(in),optional :: KIND

Characteristics#

  • c is a scalar character

  • kind is a constant integer initialization expression indicating the kind parameter of the result.

  • The return value is of type integer and of kind kind. If kind is absent, the return value is of default integer kind.

Description#

ichar(3) returns the code for the character in the system’s native character set. The correspondence between characters and their codes is not necessarily the same across different Fortran implementations. For example, a platform using EBCDIC would return different values than an ASCII platform.

See iachar(3) for specifically working with the ASCII character set.

Options#

  • c

    The input character to determine the code for. Its value shall be that of a character capable of representation in the processor.

  • kind

    indicates the kind parameter of the result. If kind is absent, the return value is of default integer kind.

Result#

The code in the system default character set for the character being queried is returned.

The result is the position of c in the processor collating sequence associated with the kind type parameter of c.

it is nonnegative and less than n, where n is the number of characters in the collating sequence.

The kind type parameter of the result shall specify an integer kind that is capable of representing n.

For any characters C and D capable of representation in the processor, C <= D is true if and only if ICHAR (C) <= ICHAR (D) is true and C == D is true if and only if ICHAR (C) == ICHAR (D) is true.

Examples#

Sample program:

program demo_ichar
implicit none

   write(*,*)ichar(['a','z','A','Z'])

end program demo_ichar

Results:

             97         122          65          90

Standard#

Fortran 95 , with KIND argument -Fortran 2003

See Also#

achar(3), char(3), iachar(3)

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

scan(3), verify(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

index#

Name#

index(3) - [CHARACTER:SEARCH] Position of a substring within a string

Synopsis#

result = index( string, substring [,back] [,kind] )
 elemental integer(kind=KIND) function index(string,substring,back,kind)

  character(len=*,kind=KIND),intent(in) :: string
  character(len=*,kind=KIND),intent(in) :: substring
  logical(kind=**),intent(in),optional :: back
  integer(kind=**),intent(in),optional :: kind

Characteristics#

  • string is a character variable of any kind

  • substring is a character variable of the same kind as string

  • back is a logical variable of any supported kind

  • KIND is a scalar integer constant expression.

Description#

index(3) returns the position of the start of the leftmost or rightmost occurrence of string substring in string, counting from one. If substring is not present in string, zero is returned.

Options#

  • string

    string to be searched for a match

  • substring

    string to attempt to locate in string

  • back

    If the back argument is present and true, the return value is the start of the rightmost occurrence rather than the leftmost.

  • kind

    if kind is present, the kind type parameter is that specified by the value of kind; otherwise the kind type parameter is that of default integer type.

Result#

The result is the starting position of the first substring substring found in string.

If the length of substring is longer than string the result is zero.

If the substring is not found the result is zero.

If back is .true. the greatest starting position is returned (that is, the position of the right-most match). Otherwise, the smallest position starting a match (ie. the left-most match) is returned.

The position returned is measured from the left with the first character of string being position one.

Otherwise, if no match is found zero is returned.

Examples#

Example program

program demo_index
implicit none
character(len=*),parameter :: str=&
   'Search this string for this expression'
   !1234567890123456789012345678901234567890
   write(*,*)&
      index(str,'this').eq.8,              &
      ! return value is counted from the left end even if BACK=.TRUE.
      index(str,'this',back=.true.).eq.24, &
      ! INDEX is case-sensitive
      index(str,'This').eq.0
end program demo_index

Expected Results:

   T T T

Standard#

FORTRAN 77 , with KIND argument Fortran 2003

See Also#

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions

scan#

Name#

scan(3) - [CHARACTER:SEARCH] Scan a string for the presence of a set of characters

Synopsis#

    result = scan( string, set, [,back] [,kind] )
     elemental integer(kind=KIND) function scan(string,set,back,kind)

      character(len=*,kind=**),intent(in) :: string
      character(len=*,kind=**),intent(in) :: set
      logical,intent(in),optional :: back
      integer,intent(in),optional :: kind

Characteristics#

  • string is a character string of any kind

  • set must be a character string with the same kind as string

  • back is a logical

  • kind is a scalar integer constant expression

  • the result is an integer with the kind specified by kind. If kind is not present the result is a default integer.

Description#

scan(3) scans a string for any of the characters in a set of characters.

If back is either absent or equals .false., this function returns the position of the leftmost character of STRING that is in set. If back equals .true., the rightmost position is returned. If no character of set is found in string, the result is zero.

Options#

  • string

    the string to be scanned

  • set

    the set of characters which will be matched

  • back

    if .true. the position of the rightmost character matched is returned, instead of the leftmost.

  • kind

    the kind of the returned value is the same as kind if present. Otherwise a default integer kind is returned.

Result#

If back is absent or is present with the value false and if string contains at least one character that is in set, the value of the result is the position of the leftmost character of string that is in set.

If back is present with the value true and if string contains at least one character that is in set, the value of the result is the position of the rightmost character of string that is in set.

The value of the result is zero if no character of STRING is in SET or if the length of STRING or SET is zero.

Examples#

Sample program:

program demo_scan
implicit none
   write(*,*) scan("fortran", "ao")          ! 2, found 'o'
   write(*,*) scan("fortran", "ao", .true.)  ! 6, found 'a'
   write(*,*) scan("fortran", "c++")         ! 0, found none
end program demo_scan

Results:

 >            2
 >            6
 >            0

Standard#

Fortran 95 , with KIND argument - Fortran 2003

See Also#

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

verify#

Name#

verify(3) - [CHARACTER:SEARCH] Position of a character in a string of characters that does not appear in a given set of characters.

Synopsis#

    result = verify(string, set [,back] [,kind] )
     elemental integer(kind=KIND) function verify(string,set,back,KIND)

      character(len=*,kind=**),intent(in) :: string
      character(len=*,kind=**),intent(in) :: set
      logical,intent(in),optional :: back
      integer,intent(in),optional :: KIND

Characteristics#

  • string and set must be of type character and have the same kind for any individual call, but that can be any supported character kind.

  • KIND must be a constant integer initialization expression and a valid kind for the integer type.

  • back shall be of type logical.

  • the kind of the returned value is the same as kind if present. Otherwise a default integer kind is returned.

Description#

verify(3) verifies that all the characters in string belong to the set of characters in set by identifying the position of the first character in the string that is not in the set.

This makes it easy to verify strings are all uppercase or lowercase, follow a basic syntax, only contain printable characters, and many of the conditions tested for with the C routines isalnum(3c), isalpha(3c), isascii(3c), isblank(3c), iscntrl(3c), isdigit(3c), isgraph(3c), islower(3c), isprint(3c), ispunct(3c), isspace(3c), isupper(3c), and isxdigit(3c); but for a string as well as an array of strings.

Options#

  • string

    The string to search in for an unmatched character.

  • set

    The set of characters that must be matched.

  • back

    The direction to look for an unmatched character. The left-most unmatched character position is returned unless back is present and .false., which causes the position of the right-most unmatched character to be returned instead of the left-most unmatched character.

  • kind

    An integer initialization expression indicating the kind parameter of the result.

Result#

If all characters of string are found in set, the result is zero.

If string is of zero length a zero (0) is always returned.

Otherwise, if an unmatched character is found The position of the first or last (if back is .false.) unmatched character in string is returned, starting with position one on the left end of the string.

Examples#

Sample program I:#

program demo_verify
implicit none
! some useful character sets
character,parameter :: &
 & int*(*)   = '1234567890', &
 & low*(*)   = 'abcdefghijklmnopqrstuvwxyz', &
 & upp*(*)   = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ', &
 & punc*(*)  = "!""#$%&'()*+,-./:;<=>?@[\]^_`{|}~", &
 & blank*(*) = ' ', &
 & tab       = char(11), &
 & prnt*(*) = int//low//upp//blank//punc

character(len=:),allocatable :: string
integer :: i
    print *, 'basics:'
    print *, VERIFY ('ABBA', 'A')                ! has the value 2.
    print *, VERIFY ('ABBA', 'A', BACK = .TRUE.) ! has the value 3.
    print *, VERIFY ('ABBA', 'AB')               ! has the value 0.

   print *,'find first non-uppercase letter'
   ! will produce the location of "d", because there is no match in UPP
   write(*,*) 'something unmatched',verify("ABCdEFG", upp)

   print *,'if everything is matched return zero'
   ! will produce 0 as all letters have a match
   write(*,*) 'everything matched',verify("ffoorrttrraann", "nartrof")

   print *,'easily categorize strings as uppercase, lowercase, ...'
   ! easy C-like functionality but does entire strings not just characters
   write(*,*)'isdigit 123?',verify("123", int) == 0
   write(*,*)'islower abc?',verify("abc", low) == 0
   write(*,*)'isalpha aBc?',verify("aBc", low//upp) == 0
   write(*,*)'isblank aBc dEf?',verify("aBc dEf", blank//tab ) /= 0
   ! check if all printable characters
   string="aB;cde,fgHI!Jklmno PQRSTU vwxyz"
   write(*,*)'isprint?',verify(string,prnt) == 0
   ! this now has a nonprintable tab character in it
   string(10:10)=char(11)
   write(*,*)'isprint?',verify(string,prnt) == 0

   print *,'VERIFY(3) is very powerful using expressions as masks'
   ! verify(3f) is often used in a logical expression
   string=" This is NOT all UPPERCASE "
   write(*,*)'all uppercase/spaces?',verify(string, blank//upp) == 0
   string=" This IS all uppercase "
   write(*,*) 'string=['//string//']'
   write(*,*)'all uppercase/spaces?',verify(string, blank//upp) == 0

  ! set and show complex string to be tested
   string='  Check this out. Let me know  '
   ! show the string being examined
   write(*,*) 'string=['//string//']'
   write(*,*) '        '//repeat(int,4) ! number line

   ! the Fortran functions returns a position just not a logical like C
   print *, 'returning a position not just a logical is useful'
   ! which can be very useful for parsing strings
   write(*,*)'first non-blank character',verify(string, blank)
   write(*,*)'last non-blank character',verify(string, blank,back=.true.)
   write(*,*)'first non-letter non-blank',verify(string,low//upp//blank)

  !VERIFY(3) is elemental so you can check an array of strings in one call
  print *, 'elemental'
   ! are strings all letters (or blanks)?
   write(*,*) 'array of strings',verify( &
   ! strings must all be same length, so force to length 10
   & [character(len=10) :: "YES","ok","000","good one","Nope!"], &
   & low//upp//blank) == 0

   ! rarer, but the set can be an array, not just the strings to test
   ! you could do ISPRINT() this (harder) way :>
   write(*,*)'isprint?',.not.all(verify("aBc", [(char(i),i=32,126)])==1)
   ! instead of this way
   write(*,*)'isprint?',verify("aBc",prnt) == 0

end program demo_verify

Results:

 >  basics:
 >            2
 >            3
 >            0
 >  find first non-uppercase letter
 >  something unmatched           4
 >  if everything is matched return zero
 >  everything matched           0
 >  easily categorize strings as uppercase, lowercase, ...
 >  isdigit 123? T
 >  islower abc? T
 >  isalpha aBc? T
 >  isblank aBc dEf? T
 >  isprint? T
 >  isprint? F
 >  VERIFY(3) is very powerful using expressions as masks
 >  all uppercase/spaces? F
 >  string=[ This IS all uppercase ]
 >  all uppercase/spaces? F
 >  string=[  Check this out. Let me know  ]
 >          1234567890123456789012345678901234567890
 >  returning a position not just a logical is useful
 >  first non-blank character           3
 >  last non-blank character          29
 >  first non-letter non-blank          17
 >  elemental
 >  array of strings T T F T F
 >  isprint? T
 >  isprint? T

Sample program II:#

Determine if strings are valid integer representations

program fortran_ints
implicit none
integer :: i
character(len=*),parameter :: ints(*)=[character(len=10) :: &
 '+1 ', &
 '3044848 ', &
 '30.40 ', &
 'September ', &
 '1 2 3', &
 '  -3000 ', &
 ' ']
   ! show the strings to test
   write(*,'("|",*(g0,"|"))') ints
   ! show if strings pass or fail the test done by isint(3f)
   write(*,'("|",*(1x,l1,8x,"|"))') isint(ints)

contains

elemental function isint(line) result (lout)
!
! determine if string is a valid integer representation
! ignoring trailing spaces and leading spaces
!
character(len=*),parameter   :: digits='0123456789'
character(len=*),intent(in)  :: line
character(len=:),allocatable :: name
logical                      :: lout
   lout=.false.
   ! make sure at least two characters long to simplify tests
   name=adjustl(line)//'  '
   ! blank string
   if( name == '' )return
   ! allow one leading sign
   if( verify(name(1:1),'+-') == 0 ) name=name(2:)
   ! was just a sign
   if( name == '' )return
   lout=verify(trim(name), digits)  == 0
end function isint

end program fortran_ints

Results:

|+1       |3044848  |30.40    |September|1 2 3    |  -3000  |         |
| T       | T       | F       | F       | F       | T       | F       |

Sample program III:#

Determine if strings represent valid Fortran symbol names

program fortran_symbol_name
implicit none
integer :: i
character(len=*),parameter :: symbols(*)=[character(len=10) :: &
 'A_ ', &
 '10 ', &
 'September ', &
 'A B', &
 '_A ', &
 ' ']

   write(*,'("|",*(g0,"|"))') symbols
   write(*,'("|",*(1x,l1,8x,"|"))') fortran_name(symbols)

contains

elemental function fortran_name(line) result (lout)
!
! determine if a string is a valid Fortran name
! ignoring trailing spaces (but not leading spaces)
!
character(len=*),parameter   :: int='0123456789'
character(len=*),parameter   :: lower='abcdefghijklmnopqrstuvwxyz'
character(len=*),parameter   :: upper='ABCDEFGHIJKLMNOPQRSTUVWXYZ'
character(len=*),parameter   :: allowed=upper//lower//int//'_'

character(len=*),intent(in)  :: line
character(len=:),allocatable :: name
logical                      :: lout
   name=trim(line)
   if(len(name).ne.0)then
      ! first character is alphameric
      lout = verify(name(1:1), lower//upper) == 0  &
       ! other characters are allowed in a symbol name
       & .and. verify(name,allowed) == 0           &
       ! allowable length
       & .and. len(name) <= 63
   else
      lout = .false.
   endif
end function fortran_name

end program fortran_symbol_name

Results:

    |A_        |10        |September |A B       |_A        |          |
    | T        | F        | T        | F        | F        | F        |

Sample program IV:#

check if string is of form NN-HHHHH

program checkform
! check if string is of form NN-HHHHH
implicit none
character(len=*),parameter :: int='1234567890'
character(len=*),parameter :: hex='abcdefABCDEF0123456789'
logical                    :: lout
character(len=80)          :: chars

   chars='32-af43d'
   lout=.true.

   ! are the first two characters integer characters?
   lout = lout.and.(verify(chars(1:2), int) == 0)

   ! is the third character a dash?
   lout = lout.and.(verify(chars(3:3), '-') == 0)

   ! is remaining string a valid representation of a hex value?
   lout = lout.and.(verify(chars(4:8), hex) == 0)

   if(lout)then
      write(*,*)trim(chars),' passed'
   else
      write(*,*)trim(chars),' failed'
   endif
end program checkform

Results:

    32-af43d passed

Sample program V:#

exploring uses of elemental functionality and dusty corners

program more_verify
implicit none
character(len=*),parameter :: &
  & int='0123456789', &
  & low='abcdefghijklmnopqrstuvwxyz', &
  & upp='ABCDEFGHIJKLMNOPQRSTUVWXYZ', &
  & blank=' '
! note character variables in an array have to be of the same length
character(len=6) :: strings(3)=["Go    ","right ","home! "]
character(len=2) :: sets(3)=["do","re","me"]

  ! elemental -- you can use arrays for both strings and for sets

   ! check each string from right to left for non-letter/non-blank
   write(*,*)'last non-letter',verify(strings,upp//low//blank,back=.true.)

   ! even BACK can be an array
   ! find last non-uppercase character in "Howdy "
   ! and first non-lowercase in "there "
   write(*,*) verify(strings(1:2),[upp,low],back=[.true.,.false.])

   ! using a null string for a set is not well defined. Avoid it
   write(*,*) 'null',verify("for tran ", "", .true.) ! 8,length of string?
   ! probably what you expected
   write(*,*) 'blank',verify("for tran ", " ", .true.) ! 7,found 'n'

   ! first character in  "Go    " not in "do",
   ! and first letter in "right " not in "ri"
   ! and first letter in "home! " not in "me"
   write(*,*) verify(strings,sets)

end program more_verify

Results:

    > last non-letter 0 0 5
    > 6 6
    > null 9
    > blank 8
    > 1 2 1

Standard#

Fortran 95 , with kind argument - Fortran 2003

See Also#

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

lge#

Name#

lge(3) - [CHARACTER:COMPARE] ASCII Lexical greater than or equal

Synopsis#

    result = lge(string_a, stringb)
     elemental logical function lge(string_a, string_b)

      character(len=*),intent(in) :: string_a
      character(len=*),intent(in) :: string_b

Characteristics#

  • string_a is default character or an ASCII character.

  • string_b is the same type and kind as string_a

  • the result is a default logical

Description#

lge(3) determines whether one string is lexically greater than or equal to another string, where the two strings are interpreted as containing ASCII character codes. If string_a and string_b are not the same length, the shorter is compared as if spaces were appended to it to form a value that has the same length as the longer.

The lexical comparison intrinsics lge(3), lgt(3), lle(3), and llt(3) differ from the corresponding intrinsic operators .ge., .gt., .le., and .lt., in that the latter use the processor’s character ordering (which is not ASCII on some targets), whereas the former always use the ASCII ordering.

Options#

  • string_a

    string to be tested

  • string_b

    string to compare to string_a

Result#

Returns .true. if string*a == string_b, and *.false._ otherwise, based on the ASCII collating sequence.

If both input arguments are null strings, .true. is always returned.

If either string contains a character not in the ASCII character set, the result is processor dependent.

Examples#

Sample program:

program demo_lge
implicit none
integer :: i
   print *,'the ASCII collating sequence for printable characters'
   write(*,'(1x,19a)')(char(i),i=32,126) ! ASCII order
   write(*,*) lge('abc','ABC')           ! [T] lowercase is > uppercase
   write(*,*) lge('abc','abc  ')         ! [T] trailing spaces
   ! If both strings are of zero length the result is true
   write(*,*) lge('','')                 ! [T]
   write(*,*) lge('','a')                ! [F] the null string is padded
   write(*,*) lge('a','')                ! [T]
   ! elemental
   write(*,*) lge('abc',['abc','123'])   ! [T T]  scalar and array
   write(*,*) lge(['cba', '123'],'abc')  ! [T F]
   write(*,*) lge(['abc','123'],['cba','123']) ! [F T]  both arrays
end program demo_lge

Results:

 >  the ASCII collating sequence for printable characters
 >   !"#$%&'()*+,-./012
 >  3456789:;<=>?@ABCDE
 >  FGHIJKLMNOPQRSTUVWX
 >  YZ[\]^_`abcdefghijk
 >  lmnopqrstuvwxyz{|}~
 >  T
 >  T
 >  T
 >  F
 >  T
 >  T T
 >  T F
 >  F T

Standard#

FORTRAN 77

See Also#

lgt(3), lle(3), llt(3)

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

scan(3), verify(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

lgt#

Name#

lgt(3) - [CHARACTER:COMPARE] ASCII Lexical greater than

Synopsis#

     result = lgt(string_a, string_b)
      elemental logical function lgt(string_a, string_b)

       character(len=*),intent(in) :: string_a
       character(len=*),intent(in) :: string_b

Characteristics#

  • string_a is default character or an ASCII character.

  • string_b is the same type and kind as string_a

  • the result is a default logical

Description#

lgt(3) determines whether one string is lexically greater than another string, where the two strings are interpreted as containing ASCII character codes. If the String a and String b are not the same length, the shorter is compared as if spaces were appended to it to form a value that has the same length as the longer.

In general, the lexical comparison intrinsics lge, lgt, lle, and llt differ from the corresponding intrinsic operators .ge., .gt., .le., and .lt., in that the latter use the processor’s character ordering (which is not ASCII on some targets), whereas the former always use the ASCII ordering.

Options#

  • string_a

    string to be tested

  • string_b

    string to compare to string_a

Result#

Returns .true. if string*a > string_b, and *.false._ otherwise, based on the ASCII ordering.

If both input arguments are null strings, .false. is returned.

If either string contains a character not in the ASCII character set, the result is processor dependent.

Examples#

Sample program:

program demo_lgt
implicit none
integer :: i
   print *,'the ASCII collating sequence for printable characters'
   write(*,'(1x,19a)')(char(i),i=32,126)

   write(*,*) lgt('abc','ABC')          ! [T] lowercase is > uppercase
   write(*,*) lgt('abc','abc  ')        ! [F] trailing spaces

   ! If both strings are of zero length the result is false.
   write(*,*) lgt('','')                ! [F]
   write(*,*) lgt('','a')               ! [F] the null string is padded
   write(*,*) lgt('a','')               ! [T]
   write(*,*) lgt('abc',['abc','123'])  ! [F T]  scalar and array
   write(*,*) lgt(['cba', '123'],'abc') ! [T F]
   write(*,*) lgt(['abc','123'],['cba','123']) ! [F F]  both arrays
end program demo_lgt

Results:

 >  the ASCII collating sequence for printable characters
 >   !"#$%&'()*+,-./012
 >  3456789:;<=>?@ABCDE
 >  FGHIJKLMNOPQRSTUVWX
 >  YZ[\]^_`abcdefghijk
 >  lmnopqrstuvwxyz{|}~
 >  T
 >  F
 >  F
 >  F
 >  T
 >  F T
 >  T F
 >  F F

Standard#

FORTRAN 77

See Also#

lge(3), lle(3), llt(3)

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

scan(3), verify(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

lle#

Name#

lle(3) - [CHARACTER:COMPARE] ASCII Lexical less than or equal

Synopsis#

     result = lle(string_a, stringb)
      elemental logical function lle(string_a, string_b)

       character(len=*),intent(in) :: string_a
       character(len=*),intent(in) :: string_b

Characteristics#

  • string_a is default character or an ASCII character.

  • string_b is the same type and kind as string_a

  • the result is a default logical

Description#

lle(3) determines whether one string is lexically less than or equal to another string, where the two strings are interpreted as containing ASCII character codes.

If string_a and string_b are not the same length, the shorter is compared as if spaces were appended to it to form a value that has the same length as the longer.

Leading spaces are significant.

In general, the lexical comparison intrinsics lge, lgt, lle, and llt differ from the corresponding intrinsic operators .ge., .gt., .le., and .lt., in that the latter use the processor’s character ordering (which is not ASCII on some targets), whereas lle(3) always uses the ASCII ordering.

Options#

  • string_a

    string to be tested

  • string_b

    string to compare to string_a

Result#

  • result Returns .true. if string_a <= string_b, and .false. otherwise, based on the ASCII collating sequence.

    If both input arguments are null strings, .true. is always returned.

    If either string contains a character not in the ASCII character set, the result is processor dependent.

Examples#

Sample program:

program demo_lle
implicit none
integer :: i
   print *,'the ASCII collating sequence for printable characters'
   write(*,'(1x,19a)')(char(i),i=32,126)
  ! basics

   print *,'case matters'
   write(*,*) lle('abc','ABC')          ! F lowercase is > uppercase

   print *,'a space is the lowest printable character'
   write(*,*) lle('abcd','abc')         ! F  d > space
   write(*,*) lle('abc','abcd')         ! T  space < d

   print *,'leading spaces matter, trailing spaces do not'
   write(*,*) lle('abc','abc  ')        ! T trailing spaces
   write(*,*) lle('abc',' abc')         ! F leading spaces are significant

   print *,'even null strings are padded and compared'
   ! If both strings are of zero length the result is true.
   write(*,*) lle('','')                ! T
   write(*,*) lle('','a')               ! T the null string is padded
   write(*,*) lle('a','')               ! F
   print *,'elemental'
   write(*,*) lle('abc',['abc','123'])  ! [T,F] scalar and array
   write(*,*) lle(['cba', '123'],'abc') ! [F,T]
   ! per the rules for elemental procedures arrays must be the same size
   write(*,*) lle(['abc','123'],['cba','123']) ! [T,T] both arrays
end program demo_lle

Results:

 >  the ASCII collating sequence for printable characters
 >   !"#$%&'()*+,-./012
 >  3456789:;<=>?@ABCDE
 >  FGHIJKLMNOPQRSTUVWX
 >  YZ[\]^_`abcdefghijk
 >  lmnopqrstuvwxyz{|}~
 >  case matters
 >  F
 >  a space is the lowest printable character
 >  F
 >  T
 >  leading spaces matter, trailing spaces do not
 >  T
 >  F
 >  even null strings are padded and compared
 >  T
 >  T
 >  F
 >  elemental
 >  T F
 >  F T
 >  T T

Standard#

FORTRAN 77

See Also#

lge(3), lgt(3), llt(3)

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

scan(3), verify(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

llt#

Name#

llt(3) - [CHARACTER:COMPARE] ASCII Lexical less than

Synopsis#

     result = llt(string_a, stringb)
      elemental logical function llt(string_a, string_b)

       character(len=*),intent(in) :: string_a
       character(len=*),intent(in) :: string_b

Characteristics#

  • string_a is default character or an ASCII character.

  • string_b is the same type and kind as string_a

  • the result is a default logical

Description#

llt(3) determines whether one string is lexically less than another string, where the two strings are interpreted as containing ASCII character codes. If the string_a and string_b are not the same length, the shorter is compared as if spaces were appended to it to form a value that has the same length as the longer.

In general, the lexical comparison intrinsics lge, lgt, lle, and llt differ from the corresponding intrinsic operators .ge., .gt., .le., and .lt., in that the latter use the processor’s character ordering (which is not ASCII on some targets), whereas the former always use the ASCII ordering.

Options#

  • string_a

    string to be tested

  • string_b

    string to compare to string_a

Result#

Returns .true. if string*a <= string_b, and *.false._ otherwise, based on the ASCII collating sequence.

If both input arguments are null strings, .false. is always returned.

If either string contains a character not in the ASCII character set, the result is processor dependent.

Examples#

Sample program:

program demo_llt
implicit none
integer :: i

   print *,'the ASCII collating sequence for printable characters'
   write(*,'(1x,19a)')(char(i),i=32,126) ! ASCII order

  ! basics
   print *,'case matters'
   write(*,*) llt('abc','ABC')           ! [F] lowercase is > uppercase
   write(*,*) llt('abc','abc  ')         ! [F] trailing spaces
   ! If both strings are of zero length the result is false.
   write(*,*) llt('','')                 ! [F]
   write(*,*) llt('','a')                ! [T] the null string is padded
   write(*,*) llt('a','')                ! [F]
   print *,'elemental'
   write(*,*) llt('abc',['abc','123'])   ! [F F]  scalar and array
   write(*,*) llt(['cba', '123'],'abc')  ! [F T]
   write(*,*) llt(['abc','123'],['cba','123']) ! [T F]  both arrays
end program demo_llt

Results:

 >  the ASCII collating sequence for printable characters
 >   !"#$%&'()*+,-./012
 >  3456789:;<=>?@ABCDE
 >  FGHIJKLMNOPQRSTUVWX
 >  YZ[\]^_`abcdefghijk
 >  lmnopqrstuvwxyz{|}~
 >  case matters
 >  F
 >  F
 >  F
 >  T
 >  F
 >  elemental
 >  F F
 >  F T
 >  T F

Standard#

FORTRAN 77

See Also#

lge(3), lgt(3), lle(3))

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

adjustl#

Name#

adjustl(3) - [CHARACTER:WHITESPACE] Left-justified a string

Synopsis#

  result = adjustl(string)
   elemental character(len=len(string),kind=KIND) function adjustl(string)

    character(len=*,kind=KIND),intent(in) :: string

Characteristics#

  • string is a character variable of any supported kind

  • The return value is a character variable of the same kind and length as string

Description#

adjustl(3) will left-justify a string by removing leading spaces. Spaces are inserted at the end of the string as needed.

Options#

  • string

    the string to left-justify

Result#

A copy of string where leading spaces are removed and the same number of spaces are inserted on the end of string.

Examples#

Sample program:

program demo_adjustl
implicit none
character(len=20) :: str = '   sample string'
character(len=:),allocatable :: astr
integer :: length

   ! basic use
    write(*,'(a,"[",a,"]")') 'original: ',str
    str=adjustl(str)
    write(*,'(a,"[",a,"]")') 'adjusted: ',str

    ! a fixed-length string can be printed
    ! trimmed using trim(3f) or len_trim(3f)
    write(*,'(a,"[",a,"]")') 'trimmed:  ',trim(str)
    length=len_trim(str)
    write(*,'(a,"[",a,"]")') 'substring:',str(:length)

    ! note an allocatable string stays the same length too
    ! and is not trimmed by just an adjustl(3f) call.
    astr='    allocatable string   '
    write(*,'(a,"[",a,"]")') 'original:',astr
    astr = adjustl(astr)
    write(*,'(a,"[",a,"]")') 'adjusted:',astr
    ! trim(3f) can be used to change the length
    astr = trim(astr)
    write(*,'(a,"[",a,"]")') 'trimmed: ',astr

end program demo_adjustl

Results:

   original: [   sample string    ]
   adjusted: [sample string       ]
   trimmed:  [sample string]
   substring:[sample string]
   original:[    allocatable string   ]
   adjusted:[allocatable string       ]
   trimmed: [allocatable string]

Standard#

Fortran 95

See Also#

adjustr(3), trim(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

adjustr#

Name#

adjustr(3) - [CHARACTER:WHITESPACE] Right-justify a string

Synopsis#

  result = adjustr(string)
   elemental character(len=len(string),kind=KIND) function adjustr(string)

    character(len=*,kind=KIND),intent(in) :: string

Characteristics#

  • string is a character variable

  • The return value is a character variable of the same kind and length as string

Description#

adjustr(3) right-justifies a string by removing trailing spaces. Spaces are inserted at the start of the string as needed to retain the original length.

Options#

  • string

    the string to right-justify

Result#

Trailing spaces are removed and the same number of spaces are inserted at the start of string.

Examples#

Sample program:

program demo_adjustr
implicit none
character(len=20) :: str
   ! print a short number line
   write(*,'(a)')repeat('1234567890',2)

  ! basic usage
   str = '  sample string '
   write(*,'(a)') str
   str = adjustr(str)
   write(*,'(a)') str

   !
   ! elemental
   !
   write(*,'(a)')repeat('1234567890',5)
   write(*,'(a)')adjustr([character(len=50) :: &
   '  first           ', &
   '     second       ', &
   '         third    ' ])
   write(*,'(a)')repeat('1234567890',5)

end program demo_adjustr

Results:

   12345678901234567890
     sample string
          sample string
   12345678901234567890123456789012345678901234567890
                                                first
                                               second
                                                third
   12345678901234567890123456789012345678901234567890

Standard#

Fortran 95

See Also#

adjustl(3), trim(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

len_trim#

Name#

len_trim(3) - [CHARACTER:WHITESPACE] Character length without trailing blank characters

Synopsis#

  result = len_trim(string [,kind])
   elemental integer(kind=KIND) function len_trim(string,KIND)

    character(len=*),intent(in) :: string
    integer(kind=KIND),intent(in),optional :: KIND

Characteristics#

  • string is of type character

  • kind is a scalar integer constant expression specifying the kind of the returned value.

  • The return value is of type integer and of kind KIND. If KIND is absent, the return value is of default integer kind.

Description#

len_trim(3) returns the length of a character string, ignoring any trailing blanks.

Options#

  • string

    The input string whose length is to be measured.

  • kind

    Indicates the kind parameter of the result.

Result#

The result equals the number of characters remaining after any trailing blanks in string are removed.

If the input argument is of zero length or all blanks the result is zero.

Examples#

Sample program

program demo_len_trim
implicit none
character(len=:),allocatable :: string
integer :: i
! basic usage
   string=" how long is this string?     "
   write(*,*) string
   write(*,*)'UNTRIMMED LENGTH=',len(string)
   write(*,*)'TRIMMED LENGTH=',len_trim(string)

   ! print string, then print substring of string
   string='xxxxx   '
   write(*,*)string,string,string
   i=len_trim(string)
   write(*,*)string(:i),string(:i),string(:i)
   !
  ! elemental example
   ELE:block
   ! an array of strings may be used
   character(len=:),allocatable :: tablet(:)
   tablet=[character(len=256) :: &
   & ' how long is this string?     ',&
   & 'and this one?']
      write(*,*)'UNTRIMMED LENGTH=  ',len(tablet)
      write(*,*)'TRIMMED LENGTH=    ',len_trim(tablet)
      write(*,*)'SUM TRIMMED LENGTH=',sum(len_trim(tablet))
   endblock ELE
   !
end program demo_len_trim

Results:

     how long is this string?
    UNTRIMMED LENGTH=          30
    TRIMMED LENGTH=          25
    xxxxx   xxxxx   xxxxx
    xxxxxxxxxxxxxxx
    UNTRIMMED LENGTH=           256
    TRIMMED LENGTH=              25          13
    SUM TRIMMED LENGTH=          38

Standard#

Fortran 95 . kind argument added with Fortran 2003.

See Also#

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

trim#

Name#

trim(3) - [CHARACTER:WHITESPACE] Remove trailing blank characters from a string

Synopsis#

    result = trim(string)
     character(len=:,kind=KIND) function trim(string)

      character(len=*,kind=KIND),intent(in) :: string

Characteristics#

  • KIND can be any kind supported for the character type.

  • The result has the same type and kind as the input argument string.

Description#

trim(3) removes trailing blank characters from a string.

Options#

  • string

    A string to trim

Result#

The result is the same as string except trailing blanks are removed.

If string is composed entirely of blanks or has zero length, the result has zero length.

Examples#

Sample program:

program demo_trim
implicit none
character(len=:), allocatable :: str, strs(:)
character(len=*),parameter :: brackets='( *("[",a,"]":,1x) )'
integer :: i

   str='   trailing    '
   print brackets, str,trim(str) ! trims it

   str='   leading'
   print brackets, str,trim(str) ! no effect

   str='            '
   print brackets, str,trim(str) ! becomes zero length
   print *,  len(str), len(trim('               '))

  ! array elements are all the same length, so you often
  ! want to print them
   strs=[character(len=10) :: "Z"," a b c","ABC",""]

   write(*,*)'untrimmed:'
   ! everything prints as ten characters; nice for neat columns
   print brackets, (strs(i), i=1,size(strs))
   print brackets, (strs(i), i=size(strs),1,-1)
   write(*,*)'trimmed:'
   ! everything prints trimmed
   print brackets, (trim(strs(i)), i=1,size(strs))
   print brackets, (trim(strs(i)), i=size(strs),1,-1)

end program demo_trim

Results:

    > [   trailing    ] [   trailing]
    > [   leading] [   leading]
    > [            ] []
    >           12           0
    >  untrimmed:
    > [Z         ] [ a b c    ] [ABC       ] [          ]
    > [          ] [ABC       ] [ a b c    ] [Z         ]
    >  trimmed:
    > [Z] [ a b c] [ABC] []
    > [] [ABC] [ a b c] [Z]

Standard#

Fortran 95

See Also#

Functions that perform operations on character strings, return lengths of arguments, and search for certain arguments:

fortran-lang intrinsic descriptions (license: MIT) @urbanjost