You can use the char and ichar functions, for example
elemental subroutine lower_case(word)
! convert a word to lower case
character (len=*) , intent(in out) :: word
integer :: i,ic,nlen
nlen = len(word)
do i=1,nlen
ic = ichar(word(i:i))
if (ic >= 65 .and. ic < 90) word(i:i) = char(ic+32)
end do
end subroutine lower_case
The code posted at the end of this message is what I use. The StrLowCase function is used
thusly:
string = 'THIS IS A STRING'
WRITE( *, '( a )' ) StrLowCase( string )
this is a string
and the StrUpCase similarly
string = 'this is a string'
WRITE( *, '( a )' ) StrUpCase( string )
THIS IS A STRING
Both of these were obtained from:
Figure 3.5B, pg 80, "Upgrading to Fortran 90", by Cooper Redwine,
1995 Springer-Verlag, New York.
which is a good book if you can find it (even if it is about only f90 stuff). The code is
simple and probably inefficient for large amounts of text processing but it suits my needs
perfectly.
cheers,
paulv
---------------------
MODULE String_Utility
IMPLICIT NONE
PRIVATE
PUBLIC :: StrUpCase
PUBLIC :: StrLowCase
CHARACTER( * ), PRIVATE, PARAMETER :: LOWER_CASE = 'abcdefghijklmnopqrstuvwxyz'
CHARACTER( * ), PRIVATE, PARAMETER :: UPPER_CASE = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
CONTAINS
FUNCTION StrUpCase ( Input_String ) RESULT ( Output_String )
! -- Argument and result
CHARACTER( * ), INTENT( IN ) :: Input_String
CHARACTER( LEN( Input_String ) ) :: Output_String
! -- Local variables
INTEGER :: i, n
! -- Copy input string
Output_String = Input_String
! -- Loop over string elements
DO i = 1, LEN( Output_String )
! -- Find location of letter in lower case constant string
n = INDEX( LOWER_CASE, Output_String( i:i ) )
! -- If current substring is a lower case letter, make it upper case
IF ( n /= 0 ) Output_String( i:i ) = UPPER_CASE( n:n )
END DO
END FUNCTION StrUpCase
FUNCTION StrLowCase ( Input_String ) RESULT ( Output_String )
! -- Argument and result
CHARACTER( * ), INTENT( IN ) :: Input_String
CHARACTER( LEN( Input_String ) ) :: Output_String
! -- Local variables
INTEGER :: i, n
! -- Copy input string
Output_String = Input_String
! -- Loop over string elements
DO i = 1, LEN( Output_String )
! -- Find location of letter in upper case constant string
n = INDEX( UPPER_CASE, Output_String( i:i ) )
! -- If current substring is an upper case letter, make it lower case
IF ( n /= 0 ) Output_String( i:i ) = LOWER_CASE( n:n )
END DO
END FUNCTION StrLowCase
END MODULE String_Utility
--
Paul van Delst
CIMSS @ NOAA/NCEP/EMC
Shouldn't you use ACHAR and IACHAR instead of CHAR and ICHAR? That would make the values
65, 90, and 32 meaningful on (probably non-existant) platforms that use other than ASCII
by default.
cheers,
paulv
p.s. *Are* there any machines nowadays that don't use the ASCII collating sequence by
default. EBCDIC is an acronym that springs to mind (something about binary coded decimal
on IBMs...? <waving hands about in the air here>)
It doesn't _quite_ work anyway. I use ISO Latin-1 (8859-1) most of
the time and it has letters that aren't in the ranges that the above covers.
And, there are letters that have no alternate case. The German ß is
lowercase and has no corresponding uppercase symbol.
I tend to use a full translation table for upper- and lowercase conversions.
Then the actual conversion is:
word(i:i) = lower_table(ichar(word(i:i))
Where LOWER_TABLE is a CHARACTER(1) array of the same size
as the whole character set. It'll be big if I ever want to switch to UNICODE.
But by that time memory will be even cheaper. This is probably a faster
solution (some hardware even has specialized instructions to do the
translation).
--
J. Giles
"I conclude that there are two ways of constructing a software
design: One way is to make it so simple that there are obviously
no deficiencies and the other way is to make it so complicated
that there are no obvious deficiencies." -- C. A. R. Hoare
Hi, I modified the above program but get some error in the result. Can
you point out where the error is?
This is my subroutine:
subroutine lower_case(uword,lword)
character (len=*) uword,lword
integer i,ic,nlen
nlen = len_trim(uword)
do i=1,nlen
ic = ichar(uword(i:i))
if (ic >= 65 .and. ic <= 90) lword(i:i) = char(ic+32)
end do
end subroutine
There are some weird character after the converted lowercase string. I
don't know why, I use g77 compiler
As a guess, you need to set lword to uword before the loop.
Otherwise, you are only putting in the lower case
conversions, not the other characters.
Dick Hendrickson
What's 'vice visa' in fortran? MasterCard, etc., but cheek with
Aar...@hotmail.com, the CLF ass licking wonder on such trivia, or is it
the NASA rocket sceintist/engineer, big Bill what's his name? No matter.
--
You're Welcome,
Gerry T.
______
"Don't play dumb! You're not as good at it as I am!" -- Col Sam Flagg,
ICORPS dropin to the 4077th M*A*S*H
> p.s. *Are* there any machines nowadays that don't use the ASCII collating sequence by
> default.
Yes.
> --
> Paul van Delst
These are non-portable.
Best to stick to the original.
[much elided]
> > if (ic >= 65 .and. ic <= 90) lword(i:i) = char(ic+32)
> These are non-portable.
> Best to stick to the original.
I'm slightly confused by the antecedent for "the original" here, since I
don't see any "original" code alluded to anywhere upthread. Beliavsky's
shares the same non-portability, so I assume that isn't it. The comment
about non-portability is accurate (albeit... ummm... "concise" - in
contrast to my usual posting style, I suppose :-)); it is just the part
about "the original" that confuses me. Guess I'll just remain confused
on that.
One could fix the non-portability by using achar and iachar instead of
char and ichar. That will work on an EBCDIC machine as well, though
they were new to f90, which might be a problem for the OP, who is using
g77. Or one can do the job in any of several other ways, some of which
are illustrated by other posts.
(And, of course, Dick Hendrickson's bug fix is important regardless of
the character set or language version).
--
Richard Maine | Good judgment comes from experience;
email: my first.last at org.domain | experience comes from bad judgment.
org: nasa, domain: gov | -- Mark Twain
That's Paul van Delst's code, as it appears in Redwine's book.
This form is portable, and has the advantage that it is easily
extended to deal with other characters.