Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Upper-case conversion in one statement?

545 views
Skip to first unread message

Clive Page

unread,
May 7, 1999, 3:00:00 AM5/7/99
to
The recent threads here on upper/lower-case conversion using ICHAR/IACHAR
etc made me realise how unfortunate it is that Standard Fortran doesn't
have intrinsic functions to do these conversions, so we all have to write
our own.

And then I wondered if the conversion could be done in a single statement.
Here's my first attempt; it isn't very elegant (because of the need to use
TRANSFER to convert the string first into an array, and then back again)
but, well, it works. Note I define a statement function; obviously an
internal function would be equally valid. Any suggestions for improvement
would be welcome.


program test_upper
implicit none
character(len=20) :: string, up, s
up(string) = &
transfer(merge(achar(iachar(transfer(string,"x",len(string)))-32), &
transfer(string,"x",len(string)) , &
transfer(string,"x",len(string)) >= "a" .and. &
transfer(string,"x",len(string)) <= "z"), repeat("x", len(string)))
write(*,"(A)",advance='no') "Enter string: "
read(*,'(A)') s
print *,'up = ', up(s)
end program


--
Clive Page, e-mail: cgp (at) le (dot) ac (dot) uk
Dept of Physics & Astronomy,
University of Leicester.


Kelvin Hales

unread,
May 7, 1999, 3:00:00 AM5/7/99
to
In article <Pine.SGI.3.96.990507165629.26211A-100000@owl>, Clive Page wrote:
> From: Clive Page <c...@le.ac.uk>
> Newsgroups: comp.lang.fortran
> Subject: Upper-case conversion in one statement?
> Date: Fri, 7 May 1999 17:03:52 +0100

>
> The recent threads here on upper/lower-case conversion using ICHAR/IACHAR
> etc made me realise how unfortunate it is that Standard Fortran doesn't
> have intrinsic functions to do these conversions, so we all have to write
> our own.

Absolutely!

> And then I wondered if the conversion could be done in a single statement.

Its a nice idea; but:


> program test_upper
> implicit none
> character(len=20) :: string, up, s
> up(string) = &
> transfer(merge(achar(iachar(transfer(string,"x",len(string)))-32), &
> transfer(string,"x",len(string)) , &
> transfer(string,"x",len(string)) >= "a" .and. &
> transfer(string,"x",len(string)) <= "z"), repeat("x", len(string)))
> write(*,"(A)",advance='no') "Enter string: "
> read(*,'(A)') s
> print *,'up = ', up(s)
> end program

I can't get this to compile in DVF5. I get the error:

--------------------Configuration: upper - Win32 Debug--------------------
Compiling Fortran...
D:\upper\upper.f90
D:\upper\upper.f90(4) : Severe: Please report this error along with the
circumstances in which it occurred in a Software Problem Report
up(string) = &
^
[ Aborting due to internal error. ]
Error executing df.exe.

upper.obj - 1 error(s), 0 warning(s)

Kelvin B. Hales
Kelvin Hales Associates Limited - Consulting Process Control Engineers
Egham, Surrey, England, TW20 9NB
E-mail: kha...@khales.cix.co.uk
http://www.mathworks.com/connections/khace.shtml
http://www.mathworks.com/connections/mltiflsh.shtml


Herman D. Knoble

unread,
May 7, 1999, 3:00:00 AM5/7/99
to
Same Internal Compiler Error during compile with DVF6.0b, and Salford
FTN95 V1.5. Lahey LF95 V5.0f compiles and runs the program as expected.

Rather surprising I think. Would the author of this code please report it to
both Dec and Salford? If not, I'll gladly do it next week.


On Fri, 07 May 1999 18:17:36 +0100, Kelvin Hales <kha...@khales.cix.co.uk>
wrote:

-|In article <Pine.SGI.3.96.990507165629.26211A-100000@owl>, Clive Page
wrote:
-|> From: Clive Page <c...@le.ac.uk>
-|> Newsgroups: comp.lang.fortran
-|> Subject: Upper-case conversion in one statement?
-|> Date: Fri, 7 May 1999 17:03:52 +0100
-|>
-|> The recent threads here on upper/lower-case conversion using ICHAR/IACHAR
-|> etc made me realise how unfortunate it is that Standard Fortran doesn't
-|> have intrinsic functions to do these conversions, so we all have to write
-|> our own.
-|
-| Absolutely!
-|
-|> And then I wondered if the conversion could be done in a single
statement.
-|
-|Its a nice idea; but:
-|> program test_upper
-|> implicit none
-|> character(len=20) :: string, up, s
-|> up(string) = &
-|> transfer(merge(achar(iachar(transfer(string,"x",len(string)))-32), &
-|> transfer(string,"x",len(string)) , &
-|> transfer(string,"x",len(string)) >= "a" .and. &
-|> transfer(string,"x",len(string)) <= "z"), repeat("x", len(string)))
-|> write(*,"(A)",advance='no') "Enter string: "
-|> read(*,'(A)') s
-|> print *,'up = ', up(s)
-|> end program
-|
-|I can't get this to compile in DVF5. I get the error:
-|
-|--------------------Configuration: upper - Win32 Debug--------------------
-|Compiling Fortran...
-|D:\upper\upper.f90
-|D:\upper\upper.f90(4) : Severe: Please report this error along with the
-|circumstances in which it occurred in a Software Problem Report
-|up(string) = &
-|^
-|[ Aborting due to internal error. ]
-|Error executing df.exe.
-|
-|upper.obj - 1 error(s), 0 warning(s)
-|
-|Kelvin B. Hales
-|Kelvin Hales Associates Limited - Consulting Process Control Engineers
-|Egham, Surrey, England, TW20 9NB
-|E-mail: kha...@khales.cix.co.uk
-|http://www.mathworks.com/connections/khace.shtml
-|http://www.mathworks.com/connections/mltiflsh.shtml


Herman D. Knoble, research associate
mailto:h...@psu.edu
http://www.personal.psu.edu/hdk
Penn State Center for Academic Computing
214 C Computer Building
University Park, PA 16802-2101
phone: +1 (814) 865-0818
fax: +1 (814) 863-7049
Penn State Center for Academic Computing
214-C Computer Building
University Park, PA 16802-2101
phone: +1 (814) 865-0818
fax: +1 (814) 863-7049


Mirek Gruszkiewicz

unread,
May 7, 1999, 3:00:00 AM5/7/99
to
Herman D. Knoble wrote:

> Same Internal Compiler Error during compile with DVF6.0b, and Salford
> FTN95 V1.5. Lahey LF95 V5.0f compiles and runs the program as expected.

What is expected? Not an internal error for sure, however some trouble can be
expected, since DVF can be forced to confess:

Error: This transformational intrinsic function is invalid in this context;
statement functions cannot contain transformational intrinsic functions.
[TRANSFER]
transfer(achar(iachar(transfer(string,"x",len(string)))-32), &
---^

This is probably what should appear instead of the internal error.

Mirek Gruszkiewicz

bg...@my-dejanews.com

unread,
May 7, 1999, 3:00:00 AM5/7/99
to
Clive Page <c...@le.ac.uk> writes:

> The recent threads here on upper/lower-case conversion using ICHAR/IACHAR

> etc made me realise how unfortunate it is that Standard Fortran doesn't

> have intrinsic functions to do these conversions, so we all have to write

> our own.

Methinks this would be appropriate for a standard module or two.
Shall we draft a specification? Ideas could be borrowed from
the standard Ada 95 package Ada.Strings.Maps, which supports
arbitrary conversion tables, membership tests, etc.

I understand there is a mandate to include "i18n" support in the next
revision of the standard. What constitutes upper or lower case depends
on the character encoding used, hence the need to make this reasonably
flexible.

Gary Scott

unread,
May 7, 1999, 3:00:00 AM5/7/99
to
I would vote for an "ADJUSTC" (center) function companion to ADJUSTL/R as
well...

bg...@my-dejanews.com wrote:

--
Gary Scott
mailto:sco...@flash.net

mailto:webm...@fortranlib.com
http://www.fortranlib.com

Mike Prager

unread,
May 8, 1999, 3:00:00 AM5/8/99
to
It *is* a pain that Fortran does not include basic character functions
that every programmer eventually needs. Case conversion is certainly
the most basic. String parsing (a la REXX) would also be a wonderful
addition.

Mike Prager
Beaufort, NC

Kevin G. Rhoads

unread,
May 8, 1999, 3:00:00 AM5/8/99
to
0) This makes NO pretense of attempting a single statement conversion,
unless you count a SUBROUTINE invocation as a single statement.
1) This is F77 not F90 or F95 (Sorry, still learning the new constructs.)
2) I PLACE THIS IN THE PUBLIC DOMAIN (For what it is worth, probably not
much.)
3) It was a quick hack, it is ASCII specific (no EBCDIC or UNICODE).
4) I prefer * rather than C to start comment lines, So shoot me!
5) The program is trivial, the work gets done in the SUBROUTINEs
6) It was written for MS F5.1 and uses the MS extension of taking a file
from the command line
when the filename in the OPEN is blank.
program case
character*255 string
external lowercase,uppercase
*-----
open (unit=10,file=' ',status='old')
open (unit=11,file='lowrcase',status='unknown')
open (unit=12,file='upprcase',status='unknown')
9999 continue
read (10,'(A)',end=9000,err=9000) string
call lowercase(string)
write (11,*) string(1:len_trim(string))
call uppercase(string)
write (12,*) string(1:len_trim(string))
goto 9999
9000 continue
close (unit=10,status='keep',err=9001)
9001 continue
close (unit=11,status='keep',err=9002)
9002 continue
close (unit=12,status='keep',err=9003)
9003 continue
stop ' Bye!'
end
*---------------
subroutine lowercase(astring)
character*(*) astring
integer i,lenstring,iichar
character*1 achar
*-----
lenstring = len(astring)
do 1 i = 1,lenstring
achar = astring(i:i)
iichar = ichar( achar )
if ( iichar.ge.65 .and. iichar.le.90 ) then
iichar = iichar + 32
achar = char ( iichar )
astring(i:i) = achar
endif
1 continue
return
end
*---------------
subroutine uppercase(astring)
character*(*) astring
integer i,lenstring,iichar
character*1 achar
*-----
lenstring = len(astring)
do 1 i = 1,lenstring
achar = astring(i:i)
iichar = ichar( achar )
if ( iichar.ge.97 .and. iichar.le.122 ) then
iichar = iichar - 32
achar = char ( iichar )
astring(i:i) = achar
endif
1 continue
return
end
7) No claims to optimality, elegance or portability are made.
--
Kevin G. Rhoads, Ph.D. (Linearity is a convenient fiction.)
T_Rhoads@NO_SPAM.MSN.com
krhoads@NO_SPAM.cmpnetmail.com

Michel OLAGNON

unread,
May 8, 1999, 3:00:00 AM5/8/99
to

Parsing is pretty easy to do oneself with the functions of the ISO/IEC 1539-2
Varying Length Character Strings auxiliary standard to the ISO/IEC 1539-1
Fortran standard.
It's a pity that vendors don't feel committed to implement it.

Michel


--
| Michel OLAGNON email : Michel....@ifremer.fr|
| IFREMER: Institut Francais de Recherches pour l'Exploitation de la Mer|
| Centre de Brest - B.P. 70 phone : +33-2-9822 4144|
| F-29280 PLOUZANE - FRANCE fax : +33-2-9822 4650|
| http://www.ifremer.fr/ditigo/molagnon/molagnon.html |
| NOTE: http://www.ifremer.fr/isope99/ |


bg...@my-dejanews.com

unread,
May 8, 1999, 3:00:00 AM5/8/99
to
Gary Scott <sco...@flash.net> writes:

> I would vote for an "ADJUSTC" (center) function companion to ADJUSTL/R as
> well...

That one is less problematic. (It depends on the definition of a
blank, but not on differences between the various ISO 8859-* for
example.)

ELEMENTAL FUNCTION ADJUSTC (S)
CHARACTER(LEN=*), INTENT(IN) :: S
CHARACTER(LEN=LEN(S)) :: ADJUSTC

INTEGER :: ILEFT, IRIGHT, IMBALANCE

ILEFT = VERIFY (S, ' ', BACK=.FALSE.)
IF (ILEFT == 0) THEN
ADJUSTC = S
ELSE
IRIGHT = LEN (S) - VERIFY (S(ILEFT:), ' ', BACK=.TRUE.) - (ILEFT-1)
ILEFT = ILEFT - 1
IMBALANCE = (IRIGHT-ILEFT)/2
IF (IMBALANCE > 0) THEN
ADJUSTC = S(LEN(S)+1-IMBALANCE:) // S
ELSE
ADJUSTC = S(1-IMBALANCE:)
END IF
END IF
END FUNCTION ADJUSTC

What I had in mind was something more along the lines of

MODULE CHARACTER_MAPS

TYPE, PUBLIC :: MAP
PRIVATE
! Implementation-dependent, for example:
CHARACTER(LEN=1) :: TRANSLATION (0:255)
! But for double-byte character kinds it might be wiser to
! adopt a sparse representation...
END TYPE MAP

! The values below are of course implementation-dependent
TYPE(MAP), PARAMETER, PUBLIC :: UPPER_CASE_MAP_8859_1 = MAP ( &
(/ (CHAR(I),I=0,96), (CHAR(I-32),I=97,122), &
(CHAR(I),I=123,223), (CHAR(I-32),I=224,246), CHAR(247), &
(CHAR(I-32),I=248,255) /) )
TYPE(MAP), PARAMETER, PUBLIC :: LOWER_CASE_MAP_8859_1 = ...
TYPE(MAP), PARAMETER, PUBLIC :: ASCII_MAP = MAP ( &
(/ (CHAR(I),I=0,127), (CHAR(0),I=128,255) /) )
TYPE(MAP), PARAMETER, PUBLIC :: IDENTITY_MAP = MAP ( &
(/ (CHAR(I),I=0,255) /) )
! More maps should be added

ELEMENTAL FUNCTION TRANSLATION (S, M)
CHARACTER(LEN=*), INTENT(IN) :: S
TYPE(MAP), INTENT(IN) :: M
CHARACTER(LEN=LEN(S)) :: TRANSLATION
FORALL (I=1:LEN(S))
TRANSLATION(I) = M%TRANSLATION(ICHAR(S(I)))
END FORALL
END FUNCTION TRANSLATION

ELEMENTAL FUNCTION IS_IN_MAP (S, M)
CHARACTER(LEN=*), INTENT(IN) :: S
TYPE(MAP), INTENT(IN) :: M
LOGICAL :: IS_IN_MAP
IS_IN_MAP = (TRANSLATION(S,M)==S)
END FUNCTION IS_IN_MAP

SUBROUTINE SET (M, FROM, TO)
TYPE(MAP), INTENT(IN OUT) :: M
CHARACTER(LEN=*), INTENT(IN) :: FROM, TO ! No duplicates allowed in FROM
IF (LEN(TO) < LEN(FROM)) STOP 'ERROR' ! Exceptions would be nice...
FORALL (I=1:LEN(FROM))
M%TRANSLATION(ICHAR(FROM(I:I))) = TO(I:I)
END FORALL
END SUBROUTINE SET

! More?

ELEMENTAL FUNCTION IS_ASCII (S)
CHARACTER(LEN=*), INTENT(IN) :: S
LOGICAL :: IS_ASCII
IS_ASCII = IS_IN_MAP (S, ASCII_MAP)
END FUNCTION IS_ASCII

ELEMENTAL FUNCTION TO_UPPER_8859_1 (S)
CHARACTER(LEN=*), INTENT(IN) :: S
CHARACTER(LEN=LEN(S)) :: TO_UPPER
TO_UPPER = TRANSLATION (S, UPPER_CASE_MAP_8859_1)
END FUNCTION TO_UPPER_8859_1

! etc.

END MODULE CHARACTER_MAPS


James Giles

unread,
May 8, 1999, 3:00:00 AM5/8/99
to
Converting from lower- to upper- case is an inherently implementation
dependent (and KIND dependent) activity. Which characters in a
character set that *are* letters is implementation dependent. On the
PC, the letter which appears as the combined O and E does not
have the same spacing between its upper- and lower-case representation
as the bulk of the alphabet. The rest of the letters are the same as in
Latin-1 (iso-8859-1), except that, whereas latin-1 does not provide
a capital Y-umlaut, the PC does (which again is not the same distance
between cases as the bulk of the alphabet).

The fact that the conversion is widely desired and that it is inherently
implementation dependent is a pretty good argument that the operations
should be standardized. Failing that, the best you can hope for is an
implemenation dependent solution in your own code. With a properly
constructed table, the following should work:

New = Ucase_kind (ichar(C):ichar(C))

Where Ucase_kind is just a character string with the desired transformation
encoded in it : that is, all lower-case letters are replaced with upper-case,
and the string is otherwise just a list of the character set in collation order.
The same trick would be applied for converting to lower-case. You'd
have to have such a table for each KIND supported (unless you were
absolutely sure that all KINDs had letters in the same places).

This at least has the advantage that it's reasonable fast and that it requires
only one line to write a use of it. The tables would, of course, have to
be proof-read very carefully indeed.

--
J. Giles

robin

unread,
May 9, 1999, 3:00:00 AM5/9/99
to
Clive Page <c...@le.ac.uk> writes: > The recent threads here on upper/lower-case conversion using ICHAR/IACHAR
> etc made me realise how unfortunate it is that Standard Fortran doesn't
> have intrinsic functions to do these conversions, so we all have to write
> our own.
>
> And then I wondered if the conversion could be done in a single statement.

While on the trail of one-liners, let's not overlook:

UP = ACHAR (IACHAR(C) + MIN(INDEX('abcdefghijklmnopqrstuvwxyz', C), 1) * &
(IACHAR('A') - IACHAR('a') ) )

where C is a CHARACTER variable of length 1 containing the character tobe
converted to upper case. The result is stored in CHARACTER variable UP.

> Here's my first attempt; it isn't very elegant (because of the need to use
> TRANSFER to convert the string first into an array, and then back again)
> but, well, it works. Note I define a statement function; obviously an
> internal function would be equally valid. Any suggestions for improvement
> would be welcome.
>
>

> program test_upper
> implicit none
> character(len=20) :: string, up, s
> up(string) = &
> transfer(merge(achar(iachar(transfer(string,"x",len(string)))-32), &

> transfer(string,"x",len(string)) , &

> transfer(string,"x",len(string)) >= "a" .and. &

> transfer(string,"x",len(string)) <= "z"), repeat("x", len(string)))

> write(*,"(A)",advance='no') "Enter string: "

> read(*,'(A)') s


> print *,'up = ', up(s)

Jos Bergervoet

unread,
May 9, 1999, 3:00:00 AM5/9/99
to
Mike Prager <mpr...@alum.mit.edu> wrote:
> It *is* a pain that Fortran does not include basic character functions
> that every programmer eventually needs. Case conversion is certainly
> the most basic. String parsing (a la REXX) would also be a wonderful
> addition.

A more revolutionary idea: make the character type obsolescent and
introduce a better one. Why? Look:

character(len=your_choice) :: s
s = "Hello " <- does not work in Fortran (blank ignored)
s = s // "world" <- doesn't work either (forgot to use trim())
print *, s

This character type will never be pleasant to work with. Especially
the required use of trim() in all kinds of places can lead to errors
that are easily overlooked.

!-- Jos

Dan Tex1

unread,
May 10, 1999, 3:00:00 AM5/10/99
to

It may be a good point that there are "other" character types that might be
worth having in fortran. None the less... although there are all sorts of
errors that can be made using the current character type... I have not yet
found a language that is any less error prone. I personally find fortran
character data a lot easier to work with than Basic, C or C++. Fortran
character manipulation ( in its current form ) also doesn't have a steep
learning curve. And that is.... to a large degree, what fortran is all
about.

Dan :-)

Jos Bergervoet

unread,
May 10, 1999, 3:00:00 AM5/10/99
to
Dan Tex1 <dan...@aol.com> wrote:
> It may be a good point that there are "other" character types that might be
> worth having in fortran. None the less... although there are all sorts of
> errors that can be made using the current character type... I have not yet
> found a language that is any less error prone. I personally find fortran
> character data a lot easier to work with than Basic, C or C++.

That is because those languages have string types that are even more
clumsy, but that does not imply that Fortran is particularly good.
Good strings are those of Pascal (and some other languages.) Fortran
is error-prone (but just bearable) in this respect. C is a complete
disaster.

Greetings,
Jos


Richard Maine

unread,
May 10, 1999, 3:00:00 AM5/10/99
to
"James Giles" <james...@worldnet.att.net> writes:

> Converting from lower- to upper- case is an inherently implementation
> dependent (and KIND dependent) activity. Which characters in a
> character set that *are* letters is implementation dependent. On the
> PC, the letter which appears as the combined O and E does not
> have the same spacing between its upper- and lower-case representation
> as the bulk of the alphabet. The rest of the letters are the same as in
> Latin-1 (iso-8859-1), except that, whereas latin-1 does not provide
> a capital Y-umlaut, the PC does (which again is not the same distance
> between cases as the bulk of the alphabet).

Yes. I once made a request (I forget the exact context of my request
at the moment) that case conversion intrinsics be added, and the
above is pretty much the kind of reply I got to why it isn't as
trivial as I had thought. I didn't bother to pursue it any farther.
It was pretty trivial for me to throw together something adequate for
my needs. I had just figured that it was a common enough requirement
that it should be standardized instead of requiring everyone to do
their own. But when it became apparent that a viable standard version
would be less trivial than what I had envisioned, I didn't push any
farther.

Its clearly something that is doable, but seems like it actually
would require some thought to do well.

--
Richard Maine
ma...@altair.dfrc.nasa.gov

Steve Lionel

unread,
May 10, 1999, 3:00:00 AM5/10/99
to
Thanks to the folks who sent us a report saying that Clive's rather
amusing statement function makes our compiler unhappy. We'll fix the
internal compiler error.

However, as mentioned elsewhere, this code is not standard Fortran 95,
as section 12.5.4 (Statement function) prohibits transformational
intrinsics such as TRANSFER in the "body" of a statement function.

--
Send Visual Fortran support requests to vf-su...@compaq.com

Steve Lionel (mailto:Steve....@compaq.com)
Fortran Engineering
Compaq Computer Corporation, Nashua NH

Compaq Fortran web site: http://www.compaq.com/fortran

bg...@my-dejanews.com

unread,
May 10, 1999, 3:00:00 AM5/10/99
to
Jos Bergervoet <berg...@iaehv.iae.nl> writes:

> A more revolutionary idea: make the character type obsolescent

No way.

> and introduce a better one.

Done already; see ISO/IEC 1539-2:1994. Hardly my idea of revolutionary...

> This character type will never be pleasant to work with.

Some of us find it quite convenient. If I want a varying string,
either I use the standard module I just mentioned or I roll my own
TYPE BOUNDED_STRING
INTEGER :: LENGTH
CHARACTER(LEN=MAX_LENGTH) :: STRING
END TYPE BOUNDED_STRING

FUNCTION BOUNDED (STRING)
CHARACTER(LEN=*), INTENT(IN) :: STRING
TYPE(BOUNDED_STRING) :: BOUNDED
BOUNDED = BOUNDED_STRING (MIN(MAX_LENGTH,LEN(STRING)), STRING)
END FUNCTION BOUNDED

> Especially
> the required use of trim() in all kinds of places can lead to errors
> that are easily overlooked.

Not if you have a proper test suite, no.

Gerry Thomas

unread,
May 13, 1999, 3:00:00 AM5/13/99
to

Clive Page wrote in message ...

>The recent threads here on upper/lower-case conversion using ICHAR/IACHAR
>etc made me realise how unfortunate it is that Standard Fortran doesn't
>have intrinsic functions to do these conversions, so we all have to write
>our own.
>
>And then I wondered if the conversion could be done in a single statement.
[...]

If the language doesn't have it, leverage the OS. On WinNT, invoke a
CharUpper API call

--
Gerry T.

Richard Maine

unread,
May 17, 1999, 3:00:00 AM5/17/99
to
"Gerry Thomas" <gfth...@netcom.ca> writes:

> If the language doesn't have it, leverage the OS. On WinNT, invoke a
> CharUpper API call

To each his own, but I'd personally think this particular capability
does not justify such highly system-dependent code....at least if you
are just looking for the simple stuff. If you want something that
properly handles all the locale-specific cases (and if the WinNT call
does so - I have no idea whether or not it does), then I suppose it
might make sense.

If all you want is the 26 Roman letters, with no accents or other
accouterments then I personally would never consider using an OS call.
The language does trivially have support for doing such case
conversion (as demonstrated by samples posted), even if the support
doesn't take the form of an intrinsic procvedure and might actually
take more than 1 line. It would not take nearly as many lines as just
the lines of documentation that I'd consider needed to adequately
cover the system-specific code.

--
Richard Maine
ma...@altair.dfrc.nasa.gov

Gerry Thomas

unread,
May 17, 1999, 3:00:00 AM5/17/99
to
Richard Maine wrote in message ...

>"Gerry Thomas" <gfth...@netcom.ca> writes:
>
>> If the language doesn't have it, leverage the OS. On WinNT, invoke a
>> CharUpper API call
>
>To each his own, but I'd personally think this particular capability
>does not justify such highly system-dependent code....at least if you
>are just looking for the simple stuff. If you want something that
>properly handles all the locale-specific cases (and if the WinNT call
>does so - I have no idea whether or not it does), then I suppose it
>might make sense.
>

It makes sense to use Unicode on WinNT, a fully Unicode-based OS. Even COM
components running on nonWinNT OS's can avail of the WinNT API to compensate
for deficiencies in ones favorite HLL.

[...]

--
Gerry T.


ess...@ix.netcom.com

unread,
May 21, 1999, 3:00:00 AM5/21/99
to
Richard Maine wrote:
>
> If all you want is the 26 Roman letters, with no accents or other
> accouterments then I personally would never consider using an OS call.
> The language does trivially have support for doing such case...


Indeed it does, and it appears unclear why such a chatty thread on
subjects on the fringes of Fortran problem domain. Perhaps it is the
Fortran's community drifting focus that is making issues when none exist
while neglecting what really need to be improved.

In any case, here's my take from a residual spillover left from the C
type homeworks.


subroutine strcc (str)
*------------------------------------------------
* Change str chrs from upper to lower case
*------------------------------------------------
logical lne
character str*(*),ab_u*26,ab_l*26,sa,sb
data ab_u/'ABCDEFGHIJKLMNOPQRSTUVWXYZ'/,
& ab_l/'abcdefghijklmnopqrstuvwxyz'/
lne(sa,sb) = llt(sa,sb) .or. lgt(sa,sb)

do i = 1,len(str)
do j = 1,len(ab_u)
if (lne(str(i:i),ab_u(j:j))) cycle
str(i:i) = ab_l(j:j)
exit
enddo
enddo
end


It's a simple mod to convert the above into a fcn, should that be
preferable to a sub. Also, can't think of the machine where this code
wouldn't work in spite of all the commotion concerning system_dependent
solutions!?

--
Dr.B.Voh
-----------------------------------------------
Modeling * Simulation * Analysis
http://www.netcom.com/~essoft
-----------------------------------------------

0 new messages