Removing whitespace in string

18,008

Solution 1

Trim will remove spaces only at the edges, not in the middle (this is common behaviour on almost all languages/libraries). If you want to remove all spaces in the string, you will have to create your own function to do this, iterating through the string.

Ex.:

program Test

implicit none

    ! Variables
    character(len=200) :: string

    ! Body of Test
    string = 'Hello World              7    9'
    print *, string
    call StripSpaces (string)
    print *, string


contains

    subroutine StripSpaces(string)
    character(len=*) :: string
    integer :: stringLen 
    integer :: last, actual

    stringLen = len (string)
    last = 1
    actual = 1

    do while (actual < stringLen)
        if (string(last:last) == ' ') then
            actual = actual + 1
            string(last:last) = string(actual:actual)
            string(actual:actual) = ' '
        else
            last = last + 1
            if (actual < last) &
                actual = last
        endif
    end do

    end subroutine

end program Test

This was tested on intel compiler, not on gfortran, but I think it will work.

Solution 2

Here's a dirty, shameful way to eliminate the spaces. This is only likely to work if a compiler lays out a length-15 string in the same order and space as it would a 15-element array of characters. While this is likely to be true, and in my recent experience is true, it is not guaranteed to be so by the standard. That aside, this approach may be good enough.

  ! declarations
  CHARACTER (len=15) :: abc = "te st tex  t"
  CHARACTER, DIMENSION(LEN(abc)) :: abc_array
  ! or CHARACTER, DIMENSION(:), ALLOCATABLE :: abc_array if your compiler supports
  ! automatic allocation

  ! transfer the string into an array of characters
  abc_array = TRANSFER(abc,abc_array)

  ! eliminate the spaces, and transfer back to the string
  abc = TRANSFER(PACK(abc_array,abc_array/=' '),abc)

  ! now all the spaces are at the end of abc so the following statement writes the 
  ! string with no spaces
  WRITE(*,*) TRIM(abc)

Use this approach at your own risk.

Solution 3

For those averse to TRANSFER perhaps a nice little recursive function would appeal. As written this depends on Fortran 2003's ability to automatically allocate character scalars, but it shouldn't be too hard to modify if your compiler doesn't support this feature yet.

  RECURSIVE FUNCTION stripper(string,ch) RESULT(stripped)
    CHARACTER(len=*), INTENT(in) :: string
    CHARACTER, INTENT(in) :: ch
    CHARACTER(:), ALLOCATABLE :: stripped

    IF (LEN(string)==1) THEN
       IF (string==ch) THEN 
          stripped = ''
       ELSE
          stripped = string
       END IF
    ELSE
       IF (string(1:1)==ch) THEN
          stripped = stripper(string(2:),ch)
       ELSE
          stripped = string(1:1)//stripper(string(2:),ch)
       END IF
    END IF
  END FUNCTION stripper

Solution 4

I was able to do this using the variable string library described here ( http://schonfelder.co.uk/is1539-2-99.htm ). The source code link is found in the introduction section of the ISO document.

Here is the code

program Console1 use ISO_VARYING_STRING implicit none

! Body of Console1
character(LEN=50) :: text = 'Hello World John Mary '
character(LEN=50) :: res

  print *, trim(text)
  ! 'Hello World John Mary'
  res = REPLACE(text,' ','', every=.TRUE.)
  print *, trim(res)
  ! 'HelloWorldJohnMary'
end program Console1
Share:
18,008
fronthem
Author by

fronthem

Updated on June 11, 2022

Comments

  • fronthem
    fronthem almost 2 years

    I have the following code:

      program main
         character (len=15) :: abc = "te st tex  t"
         print *, trim(abc)      
      end program main
    

    Which outputs:

     te st tex  t
    

    I excepted all the whitespace to be removed but it wasn't. How can I remove all the whitespace from the string?