FUNCTION toupper(label) RESULT(RES)
CHARACTER(LEN=*) :: label
CHARACTER(LEN=LEN(label)) :: RES
INTEGER I,J
DO I=1,LEN(label)
J=INDEX("the quick brown fox jumps over the lazy
dog",label(I:I))
SELECT CASE(J)
CASE (0)
RES(I:I)=label(I:I)
CASE DEFAULT
RES(I:I)="THE QUICK BROWN FOX JUMPS OVER THE LAZY DOG"(J:J)
END SELECT
ENDDO
END FUNCTION toupper
Cheers,
Joost
LOWER_CASE ( WORK_LINE )
C
C This subroutine converts all upper-case characters in WORK_LINE to
C lower case.
C
IMPLICIT NONE
C
CHARACTER*(*) WORK_LINE
C
C Index of DO loop over characters in line
INTEGER I
C
DO I = 1, LEN(WORK_LINE)
IF ( (WORK_LINE(I:I).GE.'A') .AND.
A (WORK_LINE(I:I).LE.'Z') ) THEN
WORK_LINE(I:I) = CHAR(ICHAR(WORK_LINE(I:I))+32)
END IF
END DO
C
RETURN
C
END
This presumes that the program uses ASCII encoding. Though ubiquitous,
this is certainly not universal! You can make it a bit more portable
by using the ACHAR() and IACHAR() functions instead.
Another drawback is that it does not do anything for characters
outside the ASCII version of the alphabet. Like: accented letters,
letters that are not part of the Latin alphabet at all, etc...
In its generality: case conversion is not as trivial as it looks.
Regards,
Arjen
I checked with two compilers I have access to, but could not find
anything of this sort (one provides it as part of Winteracter, but
that is cheating :)) - I may have overlooked the relevant
functions/subroutines though.
Still, using such compiler-specific functions makes you depend
on that particular compiler. And do they all treat the problem
in the same way (if you go beyond the ASCII subset of characters)?
Regards,
Arjen
Back in December 2001 Richard Maine posted a standard Fortran 90
code (that he wrote in April of '92) that (was part of a larger code)
and which converted from lower to upper case:
http://groups-beta.google.com/group/comp.lang.fortran/browse_thread/thread/187feb4071ffc73c/ada5786220ed251b?q=fdas_string&rnum=1&hl=en#ada5786220ed251b
There are other codes (to convert to upper case) posted; but Richard's
code is probably the most self-documenting and most adaptable to any
character set.
This code is thus easily adaptable to convert from upper to lower case.
I think the followeing changes should do it.
1) integer, parameter :: lo_map_ascii(0:127) = &
(/ (i_do, i_do=0,64), (i_do+32, i_do=65,90), (i_do, i_do=91,127) /)
2) function lower_case (string) result(result)
3) do i = 1 , len(string)
result(i:i) = achar(lo_map_ascii(iachar(string(i:i))))
end do
return
end function lower_case
Skip Knoble
On Sat, 18 Jun 2005 07:45:22 GMT, TC <teco...@inwind.it> wrote:
-|there is the function Lowercase for the string?
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 )
CHARACTER( * ), INTENT( IN ) :: Input_String
CHARACTER( LEN( Input_String ) ) :: Output_String
INTEGER :: i, n
Output_String = Input_String
DO i = 1, LEN( Output_String )
n = INDEX( LOWER_CASE, Output_String( i:i ) )
IF ( n /= 0 ) Output_String( i:i ) = UPPER_CASE( n:n )
END DO
END FUNCTION StrUpCase
FUNCTION StrLowCase ( Input_String ) RESULT ( Output_String )
CHARACTER( * ), INTENT( IN ) :: Input_String
CHARACTER( LEN( Input_String ) ) :: Output_String
INTEGER :: i, n
Output_String = Input_String
DO i = 1, LEN( Output_String )
n = INDEX( UPPER_CASE, Output_String( i:i ) )
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
What happens to this code if the input string contains a non-ASCII
character (e.g. char(128))? As I read things, IACHAR returns a
processor dependent value (128?), and that could violate the bounds of
up_map_ascii. Given that this was written by RM, I'd be surprised if
that's' a correct reading!
--
John Appleyard - (send email to john!news@.. rather than spamtrap@..)
Polyhedron Software
Programs for Programmers - QA, Compilers, Graphics, Consultancy
********* Visit our Web site on http://www.polyhedron.co.uk/ *********
Skip
On Tue, 21 Jun 2005 11:16:13 +0100, John Appleyard <spam...@polyhedron.com> wrote:
-|Herman D. Knoble wrote:
-|> TC:
-|>
-|> Back in December 2001 Richard Maine posted a standard Fortran 90
-|> code (that he wrote in April of '92) that (was part of a larger code)
-|> and which converted from lower to upper case:
-|>
http://groups-beta.google.com/group/comp.lang.fortran/browse_thread/thread/187feb4071ffc73c/ada5786220ed251b?q=fdas_string&rnum=1&hl=en#ada5786220ed251b
-|>
-|
-|What happens to this code if the input string contains a non-ASCII
-|character (e.g. char(128))? As I read things, IACHAR returns a
-|processor dependent value (128?), and that could violate the bounds of
-|up_map_ascii. Given that this was written by RM, I'd be surprised if
-|that's' a correct reading!
Having looked at the versions in this thread and the earlier thread you
mentioned, I've now updated my utility module with the following code.
It adds a useful function (Translate) and, like the Cooper Redwine
version, doesn't depend on IACHAR and friends, which have a degree of
processor dependence. It may be a little slower than others, but string
functions are not usually time critical for me. Actually, I really
should put "the quick brown fox.." instead of "abcdef.."!
JA
!===============================================================================
function Translate(String,InTable,OutTable)
character(*),intent(in) :: String,InTable,OutTable
character(Len(String)) :: Translate
Integer :: i , p , l
Translate = String
l = min(len(InTable),len(OutTable))
do p = 1 , len(String)
i = index(InTable(1:l),String(p:p))
if ( i>0 ) Translate(p:p) = OutTable(i:i)
enddo
end function Translate
!=================================================================
function UpperCase(string)
character(*),intent(in) :: string
character(len(string)) :: UpperCase
UpperCase = Translate(string,'abcdefghijklmnopqrstuvwxyz' &
,'ABCDEFGHIJKLMNOPQRSTUVWXYZ')
end function UpperCase
!=================================================================
function LowerCase(string)
character(*),intent(in) :: string
character(len(string)) :: LowerCase
LowerCase = Translate(string,'ABCDEFGHIJKLMNOPQRSTUVWXYZ' &
,'abcdefghijklmnopqrstuvwxyz')
end function LowerCase
!=================================================================
Two orders of magnitude is not 'a little'!
For most situations, I'd think the ACHAR/IACHAR version is preferable.
That is how I usually write it. If one really wants to deal with
accented letters and such, as Arjen Markus noted, a simple table lookup
would probably be best.
> but string
> functions are not usually time critical for me. Actually, I really
> should put "the quick brown fox.." instead of "abcdef.."!
Walt
(w6ws att earthlink dott net)
> CHARACTER( * ), PRIVATE, PARAMETER :: LOWER_CASE = 'abcdefghijklmnopqrstuvwxyz'
> CHARACTER( * ), PRIVATE, PARAMETER :: UPPER_CASE = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
Alas, you have no poetry in your soul...
-- g
Oh, I dunno... there's a certain peace, harmony, and oneness with the universe one can
experience from well-defined, regular structures. :o)
cheers,
paulv
> Greg Lindahl wrote:
> > In article <d96h5g$1o7$1...@news.nems.noaa.gov>,
> > Paul Van Delst <paul.v...@noaa.gov> wrote:
> >
> >> CHARACTER( * ), PRIVATE, PARAMETER :: LOWER_CASE =
> >> 'abcdefghijklmnopqrstuvwxyz'
> >> CHARACTER( * ), PRIVATE, PARAMETER :: UPPER_CASE =
> >> 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
> >
> > Alas, you have no poetry in your soul...
>
> Oh, I dunno... there's a certain peace, harmony, and oneness with the
> universe one can
> experience from well-defined, regular structures. :o)
But shouldn't it be lower_case instead of LOWER_CASE? :-)
--
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
> But shouldn't it be lower_case instead of LOWER_CASE? :-)
Another "improvement" might be to rearrange the letters in
decreasing frequency, "etoi...z".
$.02 -Ron Shepard
That is rather language-dependent - and as I am confronted
daily with at least two natural languages, I would have to
swap the oneness with the universe mentioned elsewhere with
the manyness of human languages ...
(This brings to mind some wordplay I had almost forgotten
about - but as there is no English equivalent that I know
of, I won't attempt to explain :o)
Regards,
Arjen
> Ron Shepard wrote:
> >
> > Another "improvement" might be to rearrange the letters in
> > decreasing frequency, "etoi...z".
> >
> That is rather language-dependent - and as I am confronted
> daily with at least two natural languages,
Not to speak of computer languages. One named Fortran comes to mind. I
don't recall seeing a study of letter frequency in Fortran codes, but I
bet it isn't the same as for typical English prose. For example, that
"z" on the end there (I forget that end of the English letter frequency
scale, so I'm just assuming that the "z" does belong there as you show -
seems plausible). But I doubt that the "z" deserves such poor placement
in Fortran.