Silverfrost Forums

Welcome to our forums

Re if / then statement

13 May 2023 12:32 (Edited: 13 May 2023 5:03) #30305

How do I check whether a character is a space, in an if / then statement?

13 May 2023 1:13 #30306

The following changes give no compiler errors, although I am not sure if the code does what you described.

There is more work to read other lines ?

program test
character(200) :: stringin
character,dimension(200) :: strgout
integer :: single_character, i

stringin = 'the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze. '
do i = 1, len(stringin)
  single_character = iachar(stringin(i:i))
  strgout(i) = achar(single_character)
  strgout(i) = stringin(i:i)        ! this should be the same as the previous 2 lines
  if (i > 40) then 
    if (strgout(i) == achar(32)) print *,'\n'    ! are these prints what you want ?
  end if
end do

!  what do you want to do with strgout ?

end program

note that both 'character(200) :: stringin' and 'character,dimension(200) :: strgout' can be used to achieve a similar outcome, with appropriate Fortran syntax, so converting from one to the other can be avoided. 'stringin' probably has easier syntax when being used. You should review intrinsic routines LEN, LEN_TRIM and TRIM when using stringin.

13 May 2023 8:01 #30307

The objective is to list strings 40 characters wide The skip back up isn't working. Please help.

program test character(200) :: strIn integer::single_character

strIn= 'the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze. '

do i = 1, len(strIn), 1
single_character = ichar(strIn(i:i))
write(*,*) achar(single_character)
if (i < 40) print *, achar(43)!skip back up

end do end program

17 May 2023 2:27 #30322

This is not the final position, but a start ?

program test
character(200) :: strIn
integer :: i,k

strIn= 'the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze. '

do i = 1, len(strIn), 40
 k = min(len(strIn),i+39)
 write(*,*) strIn( i:k )
end do
end program

You could write code to modify 'k' for the end of a 'word'

program test
character(200) :: strIn
integer :: i,k,n

strIn= 'the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze. '

 n = len_trim (strIn)
 i = 1
 do
   k = min (n,i+39)
   k = i + INDEX ( strIn(i:k+1), ' ', .true. ) - 1
   if ( k > i ) write(*,*) strIn( i:k )
   i = k+1
   if ( i > n ) exit
end do
end program

There may be more tests for loop to end or if there are very long words !

17 May 2023 9:38 #30323

Does this help? Space_loc(N) holds the location of the Nth occurrence of ichar(' ')

program test
implicit none
character(200) :: stringin
integer, dimension(200) :: space
integer, dimension(200) :: space_loc
integer i, j, counter, total

stringin = ' the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze. '

do i = 1, len(stringin), 1
  if (ichar(stringin(i:i)) .eq. ichar(' ')) then
    space(i) = 1   ! True
  else
    space(i) = 0   ! False
  end if
end do
  
total     = sum(space)
counter   = 1
space_loc = 0
j = 1
do i = 1, len_trim(stringin), 1
  if (space(i) .eq. 1) then
    space_loc(j) = counter
    j = j + 1
  end if
  counter = counter + 1
end do

! space_loc(N) gives the location of the Nth occurrence of ichar(' ')

  do i = 1, total , 1
    if (space_loc(i) .gt. 0) print*, 'ichar(' ')', i,  ' at location ', space_loc(i) 
  end do
end
17 May 2023 12:44 #30324

Re the responses to my question! I am very grateful. Thank you! Patrick.

17 May 2023 2:02 #30326

Generalising my previous post:

module string_mod
implicit none
integer, protected, allocatable :: location(:)
contains
  subroutine locatechar(instring,searchchar,number)
  character(len=*), intent(in) :: instring 
  character(len=1), intent(in) :: searchchar
  integer, intent(out)         :: number 
  integer :: a(len(instring))
  integer i, j, counter
    a      = 0
    number = 0
    do i = 1, len(instring), 1
      if (ichar(instring(i:i)) .eq. ichar(searchchar))then
        a(i)   = 1
        number = number + 1
      end if
    end do    
    if (.not. allocated(location)) then
      allocate(location(len(instring)))
    else if (allocated(location) .and. size(location) .ne. len(instring)) then
      deallocate(location)
      allocate(location(len(instring)))
    end if
    location  = 0
    counter   = 1
    j = 1
    do i = 1, len_trim(instring), 1
      if (a(i) .eq. 1) then
        location(j) = counter
        j = j + 1
      end if
      counter = counter + 1
    end do
  end subroutine locatechar
end module string_mod

program test
use string_mod
implicit none
character(200) :: stringin
character(50)  :: string2
integer  total, i
stringin = ' the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze. '
string2 = 'Casper is a fiesty terrior'
call locatechar(stringin,'a',total)
print'(/a)',      repeat('1234567890',10)
print'(a)',       repeat('         |',10)
print'(a)',       trim(stringin)
print'(a,1x,i3)', 'Occurrences of 'a' ', total
do i = 1, total , 1
    print*, ''k'', i,  ' at location ', location(i)
end do
call locatechar(string2,'r', total)
print'(/a)',      repeat('1234567890',10)
print'(a)',       repeat('         |',10)
print'(a)',       trim(string2)
print'(a,1x,i3)', 'Occurrences of 'r' ', total
  do i = 1, total , 1
 print*, ''r'', i,  ' at location ', location(i)
end do
end
Please login to reply.