module mykinds
implicit none
integer, parameter :: ck = kind('x')
integer, parameter :: ik1 = selected_int_kind(2)
integer, parameter :: ik2 = selected_int_kind(4)
integer, parameter :: ik4 = selected_int_kind(9)
integer, parameter :: ik8 = selected_int_kind(18)
integer, parameter :: lk1 = ik1
integer, parameter :: lk2 = ik2
integer, parameter :: lk4 = ik4
integer, parameter :: lk8 = ik8
integer, parameter :: sp = selected_real_kind(6,30)
integer, parameter :: dp = selected_real_kind(15,300)
end module mykinds
module fun
use mykinds
implicit none
private
public f
interface f
module procedure f_c1, f_i1, f_i2, f_i4, f_i8
module procedure f_l1, f_l2, f_l4, f_l8
module procedure f_r4, f_r8, f_c4, f_c8
end interface f
contains
subroutine f_c1(x)
character(*,ck), intent(in) :: x
write(*,'(a,i0,a,i0,a)') 'Input was CHARACTER(',len(x), &
',',kind(x),')'
write(*,*) 'Value was "',x,'"'
end subroutine f_c1
subroutine f_i1(x)
integer(ik1), intent(in) :: x
write(*,'(a,i0,a)') 'Input was INTEGER(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_i1
subroutine f_i2(x)
integer(ik2), intent(in) :: x
write(*,'(a,i0,a)') 'Input was INTEGER(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_i2
subroutine f_i4(x)
integer(ik4), intent(in) :: x
write(*,'(a,i0,a)') 'Input was INTEGER(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_i4
subroutine f_i8(x)
integer(ik8), intent(in) :: x
write(*,'(a,i0,a)') 'Input was INTEGER(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_i8
subroutine f_l1(x)
logical(lk1), intent(in) :: x
write(*,'(a,i0,a)') 'Input was LOGICAL(',kind(x),')'
write(*,*) 'Value was ',trim(merge('.TRUE. ','.FALSE.',x))
end subroutine f_l1
subroutine f_l2(x)
logical(lk2), intent(in) :: x
write(*,'(a,i0,a)') 'Input was LOGICAL(',kind(x),')'
write(*,*) 'Value was ',trim(merge('.TRUE. ','.FALSE.',x))
end subroutine f_l2
subroutine f_l4(x)
logical(lk4), intent(in) :: x
write(*,'(a,i0,a)') 'Input was LOGICAL(',kind(x),')'
write(*,*) 'Value was ',trim(merge('.TRUE. ','.FALSE.',x))
end subroutine f_l4
subroutine f_l8(x)
logical(lk8), intent(in) :: x
write(*,'(a,i0,a)') 'Input was LOGICAL(',kind(x),')'
write(*,*) 'Value was ',trim(merge('.TRUE. ','.FALSE.',x))
end subroutine f_l8
subroutine f_r4(x)
real(sp), intent(in) :: x
write(*,'(a,i0,a)') 'Input was REAL(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_r4
subroutine f_r8(x)
real(dp), intent(in) :: x
write(*,'(a,i0,a)') 'Input was REAL(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_r8
subroutine f_c4(x)
complex(sp), intent(in) :: x
write(*,'(a,i0,a)') 'Input was COMPLEX(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_c4
subroutine f_c8(x)
complex(dp), intent(in) :: x
write(*,'(a,i0,a)') 'Input was COMPLEX(',kind(x),')'
write(*,*) 'Value was ', x
end subroutine f_c8
end module fun
program hated
use fun
implicit none
character(4) stuff
! call f(4HUGLY)
call f('xyz')
call f(1_1)
call f(1_2)
call f(1_4)
call f(1_8)
call f(.TRUE._1)
call f(.TRUE._2)
call f(.TRUE._4)
call f(.TRUE._8)
call f(1.0_4)
call f(1.0_8)
call f((1.0_4,0.0_4))
call f((1.0_8,0.0_8))
if(.NOT.((.NOT..TRUE. .AND. 2).OR.(.TRUE. .AND. 2))) then
stuff = '@#$%'
read(stuff,100)
100 format(4HUGLY)
write(*,100)
else
write(*,*) 2.0**-3*5
end if
end program hated
Now, with ifort it compiles flawlessly:
C:\gfortran\clf\xor>ifort hated.f90
Intel(R) Fortran Compiler for Intel(R) EM64T-based applications, Version 9.1
Build 20061104
Copyright (C) 1985-2006 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 8.00.40310.39
Copyright (C) Microsoft Corporation. All rights reserved.
-out:hated.exe
-subsystem:console
hated.obj
C:\gfortran\clf\xor>hated
Input was CHARACTER(3,1)
Value was "xyz"
Input was INTEGER(1)
Value was 1
Input was INTEGER(2)
Value was 1
Input was INTEGER(4)
Value was 1
Input was INTEGER(8)
Value was 1
Input was LOGICAL(1)
Value was .TRUE.
Input was LOGICAL(2)
Value was .TRUE.
Input was LOGICAL(4)
Value was .TRUE.
Input was LOGICAL(8)
Value was .TRUE.
Input was REAL(4)
Value was 1.000000
Input was REAL(8)
Value was 1.00000000000000
Input was COMPLEX(4)
Value was (1.000000,0.0000000E+00)
Input was COMPLEX(8)
Value was (1.00000000000000,0.000000000000000E+000)
@#$%
But gfortran seems to want to complain about it:
C:\gfortran\clf\xor>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran
hated.f90 -
ohated
hated.f90:127.50:
if(.NOT.((.NOT..TRUE. .AND. 2).OR.(.TRUE. .AND. 2))) then
1
Error: Operands of logical operator '.and.' at (1) are LOGICAL(4)/INTEGER(4)
This seems to me to be in conflict with
which says that GNU Fortran allows the implicit conversion between
LOGICAL and INTEGER values. Also when the if...then...else stuff
is commented out so that both blocks are executed, we get an error
At line 129 of file hated.f90
Fortran runtime error: Constant string in input format
(4HUGLY)
^
from gfortran, whereas this syntax is supposed to be allowed, e.g.
http://en.wikipedia.org/wiki/Hollerith_constant
and then when the offending READ statement is commented out,
the last two lines of output are:
UGLY
0.62500000
contradicting the ifort results. Which compiler is right?
Also if the line
call f(4HUGLY)
is commented out, both compilers refuse to accept the code, even
though e.g.
http://gcc.gnu.org/onlinedocs/gfortran/Hollerith-constants-support.html#Hollerith-constants-support
says Hollerith constants are supported in function arguments.
Perhaps a member of the group with more experience in Hollerith
constants can explain these issues with clarity.
--
write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
6.0134700243160014d-154/),(/'x'/)); end
I think this is only true for assignments, ie you can assign a logical
value to an integer lhs and the other way around. The doc needs fixing.
--
FX
> ...contradicting the ifort results. Which compiler is right?
Pretty much everything in the (elided) code is nonstandard, so the
question of which compiler is "right" is largely meaningless. I'm not
going to bother to comment on the wisdom of using such things. The code,
after all, looks a lot like an intentional exploration of the features,
which is a fine experiment to run.
I agree that it can be instructive to observe the different ways in
which different compilers handle these things, but I don't think you can
say that any of them are "right", just "different". I suppose I'm
sounding "politically correct" with that wording. So be it. :-)
> Also if the line
>
> call f(4HUGLY)
>
> is commented out, both compilers refuse to accept the code, even
> though e.g.
>
>
http://gcc.gnu.org/onlinedocs/gfortran/Hollerith-constants-support.html#
Hollerith-constants-support
>
> says Hollerith constants are supported in function arguments.
But it doesn't say anything about Holleriths in generic functions. Yes,
it makes a difference - a huge one. Of course, like everything else in
the elided code, this is nonstandard. Holleriths have never coexisted in
a standard with user generics. But even if one were to guess at
plausible extensions, I would not think that this would be on the list.
There are several things that are allowed for specific function
references, but are not allowed with generics. Of course, Hollerith
aren't on the list because of not being in the standard at all any more,
but it seems a pretty goof guess that they would be excluded from
generics anyway.
Holleriths are inherently about a type mismatch, putting character data
in a noncharacter variable (as character variables didn't exist then).
When Holleriths were in the language, a Hollerith actual argumentg could
match with any of several dummy argument types.
This doesn't fit well with the concept of generics, where type matching
is used to select the appropriate specific. I don't think you'd have any
luck at all trying to "sell" that one.
--
Richard Maine | Good judgement comes from experience;
email: last name at domain . net | experience comes from bad judgement.
domain: summertriangle | -- Mark Twain
> if(.NOT.((.NOT..TRUE. .AND. 2).OR.(.TRUE. .AND. 2))) then
> 1
> Error: Operands of logical operator '.and.' at (1) are LOGICAL(4)/INTEGER(4)
Although the Intel compiler allows this (it is an extension dating
back at least to VAX FORTRAN V1 in 1978 if not earlier), this is a
VERY bad idea. The value of .TRUE. could be anything when converted
to integer, and different compilers use different values. I know you
were just trying things, but please don't write code like this for
real. I would not encourage gfortran to pick up this extension - I'm
lobbying to have it give a warning by default in ifort. If gfortran
wants to pick it up, please make it off by default (or at least a
default warning.)
> UGLY
> 0.62500000
>
> contradicting the ifort results. Which compiler is right?
Both. Neither. You have two consecutive operators, which is non-
standard. The interpretation of this is implementation-dependent.
ifort allows this but notes that operator precedence might give you
unexpected results. In fact, an identical example is used in the
ifort documentation. Here's what it says:
---
Ordinarily, the exponentiation operator would be evaluated first in
the following example. However, because Intel Fortran allows the
combination of the exponentiation and minus operators, the
exponentiation operator is not evaluated until the minus operator is
evaluated:
A**-B*C is evaluated as A**(-(B*C))
Note that the multiplication operator is evaluated first, since it
takes precedence over the minus operator.
When consecutive operators are used with constants, the unary plus or
minus before the constant is treated the same as any other operator.
This can produce unexpected results. In the following example, the
multiplication operator is evaluated first, since it takes precedence
over the minus operator:
X/-15.0*Y is evaluated as X/-(15.0*Y)
---
So gfortran is evaluating it as (2.0**(-3))*5 and ifort as 2.0**(-
(3*5))
I can't quite understand the gfortran choice, based on normal
precedence rules, but hey, it's an extension and it can do anything it
likes.
> Also if the line
>
> call f(4HUGLY)
>
> is commented out, both compilers refuse to accept the code, even
> though e.g.
>
> http://gcc.gnu.org/onlinedocs/gfortran/Hollerith-constants-support.ht...
>
> says Hollerith constants are supported in function arguments.
> Perhaps a member of the group with more experience in Hollerith
> constants can explain these issues with clarity.
The ifort documentation says:
---
If an actual argument is a Hollerith constant (for example, 4HABCD),
the corresponding dummy argument must have a numeric data type.
---
Now, this works as long as there isn't a generic involved. If there
is, ifort fails to resolve the generic, even if there is only one
match. I'll note that in your example there are many possible
matches, so one might expect an error about an ambiguous generic.
I guess I'd call it a bug that ifort doesn't resolve Hollerith
constants in generics, but, really!
Steve
> I guess I'd call it a bug that ifort doesn't resolve Hollerith
> constants in generics, but, really!
I see that Richard and I were posting at the same time. I'm going to
go with his view that Holleriths don't participate in generic matching
if for no other reason that they don't have a type or kind.
Steve
> On Dec 19, 3:21 pm, "James Van Buskirk" <not_va...@comcast.net> wrote:
>
> > if(.NOT.((.NOT..TRUE. .AND. 2).OR.(.TRUE. .AND. 2))) then
> > 1
> > Error: Operands of logical operator '.and.' at (1) are LOGICAL(4)/INTEGER(4)
>
> Although the Intel compiler allows this (it is an extension dating
> back at least to VAX FORTRAN V1 in 1978 if not earlier), this is a
> VERY bad idea.
In addition to the reasons that Steve mentions, there is another bit of
nastiness burried in this kind of extension.
Although the standard doesn't define a "logical .and. integer"
operation, it allows the user to do so. If a compiler defines such an
operation as an extension, it can interact poorly with contradicting
user definitions.
The standard doesn't allow the user to override the standard intrinsic
operations. For example, the user can't redefine "logical .and.
logical". A compiler that implements "logical .and. integer" as an
extension would also have to allow user overriding of that in order to
be standard conforming. (Alternatively, the compiler could have a switch
to turn off the extension.) While that could be done, it introduces an
extra level of complication in that generic overrides would have
diffferent rules for standard operations as opposed to compiler
extension operations. Seems like there is good oportunity for bugs
there.
> I see that Richard and I were posting at the same time. I'm going to
> go with his view that Holleriths don't participate in generic matching
> if for no other reason that they don't have a type or kind.
C:\gfortran\clf\xor>type kindly.f90
! File: kindly.f90
! Public domain 2007 James Van Buskirk
program kindly
implicit none
write(*,*) kind(4HUGLY)
end program kindly
! End of file: kindly.f90
C:\gfortran\clf\xor>C:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran
kindly.f90
-okindly
kindly.f90:6.21:
write(*,*) kind(4HUGLY)
1
Warning: Extension: Hollerith constant at (1)
C:\gfortran\clf\xor>kindly
1
C:\gfortran\clf\xor>ifort kindly.f90
Intel(R) Fortran Compiler for Intel(R) EM64T-based applications, Version 9.1
Build 20061104
Copyright (C) 1985-2006 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 8.00.40310.39
Copyright (C) Microsoft Corporation. All rights reserved.
-out:kindly.exe
-subsystem:console
kindly.obj
C:\gfortran\clf\xor>kindly
4
> implicit none
>
> write(*,*) kind(4HUGLY)
> end program kindly
> 4
The ifort manual sayeth:
---
Hollerith constants have no intrinsic data type. In most cases, the
default integer data type is assumed.
---
What would you expect:
print *, kind(10HABCDEFGHIJ)
to display?
The description of KIND says that the argument can be of "any
intrinsic type", but Hollerith constants have no intrinsic type. I
suppose one could argue that KIND(4HABCD) should give an error, but I
can't get too heated up about that one.
To paraphrase Monty Python, "this is an issue for laying down and
avoiding..."
Steve
Does that get the c.l.f prize for the year's most entertaining typo?
You have only a few days to try and beat it :-)
-- John Harper, School of Mathematics, Statistics and Computer Science,
Victoria University, PO Box 600, Wellington 6140, New Zealand
e-mail john....@vuw.ac.nz phone (+64)(4)463 5662 fax (+64)(4)463 5045
In Excel, 2^-3*5 is evaluated to 0.625. So is it in Unix bc and R. Maybe
the same logic prevailed there.
But of course, as you say, the only right thing to do is not to use it.
--
FX
> In Excel, 2^-3*5 is evaluated to 0.625. So is it in Unix bc and R. Maybe
> the same logic prevailed there.
In Excel, what is -2.0^3 or atan2(2.0,3.0) ? I think that following
Excel's logic is a bad idea.
> But of course, as you say, the only right thing to do is not to use it.
That's why I think that run-on operators and mixed integer-logical
operations should only work if they're enabled by a switch, never as
a compiler default. These syntaxes are really mistakes I hope for
a Fortran compiler to catch before they cause any damage. Programs
can require so much nonstandard syntax that it doesn't do any good to
turn on standards checking. If ever they were intended they would
be for the most part easy to fix (well except maybe for a sum of
minterms) and if not intended you want to nail them before they
become an incomprehensible tradition.
> What would you expect:
> print *, kind(10HABCDEFGHIJ)
> to display?
I see you're getting in the Christmas spirit, Steve!
C:\gfortran\clf\xor>type wprobe.f90
program wprobe
implicit none
write(*,*) kind(4HUGLY)
write(*,*) kind(10HABCDEFGH)
write(*,*) Z'594C4755'
write(*,*) O'13123043525'
write(*,*) B'01011001010011000100011101010101'
write(*,*) 3.59370785E+15
write(*,*) 1498171221
write(*,*) 'UGLY'
write(*,*) 4HUGLY
write(*,'(z8.8)') 4HUGLY
write(*,'(o11.11)') 4HUGLY
write(*,'(b32.32)') 4HUGLY
write(*,'(i11.11)') 4HUGLY
! write(*,'(e15.7)') 4HUGLY
end program wprobe
C:\gfortran\clf\xor>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran
wprobe.f90
-owprobe
wprobe.f90:3.21:
write(*,*) kind(4HUGLY)
1
Warning: Extension: Hollerith constant at (1)
wprobe.f90:4.31:
write(*,*) kind(10HABCDEFGH)
1
Error: Syntax error in argument list at (1)
wprobe.f90:11.16:
write(*,*) 4HUGLY
1
Warning: Extension: Hollerith constant at (1)
wprobe.f90:12.23:
write(*,'(z8.8)') 4HUGLY
1
Warning: Extension: Hollerith constant at (1)
wprobe.f90:13.25:
write(*,'(o11.11)') 4HUGLY
1
Warning: Extension: Hollerith constant at (1)
wprobe.f90:14.25:
write(*,'(b32.32)') 4HUGLY
1
Warning: Extension: Hollerith constant at (1)
wprobe.f90:15.25:
write(*,'(i11.11)') 4HUGLY
1
Warning: Extension: Hollerith constant at (1)
C:\gfortran\clf\xor>wprobe
1
1
1498171221
1498171221
1498171221
3.59370785E+15
1498171221
UGLY
UGLY
594C4755
13123043525
01011001010011000100011101010101
At line 15 of file wprobe.f90 (unit = 6, file = 'stdout')
Fortran runtime error: Expected INTEGER for item 2 in formatted transfer,
got CH
ARACTER
(i11.11)
^
So clearly gfortran says TYPE = CHARACTER, KIND = 1.
C:\gfortran\clf\xor>type tprobe.f90
program tprobe
use fun
implicit none
write(*,*) kind(4HUGLY)
write(*,*) 10HABCDEFGHIJ
write(*,*) Z'594C4755'
write(*,*) O'13123043525'
write(*,*) B'01011001010011000100011101010101'
write(*,*) 3.59370785E+15
write(*,*) 1498171221
write(*,*) 'UGLY'
write(*,*) 4HUGLY
call f(transfer(Z'594C4755',4H----))
call f(transfer(O'13123043525',4H----))
call f(transfer(B'01011001010011000100011101010101',4H----))
call f(transfer(3.59370785E+15,4H----))
call f(transfer(1498171221,4H----))
call f(transfer('UGLY',4H----))
call f(transfer(4HUGLY,4H----))
write(*,*) transfer(Z'594C4755',4H----)
write(*,*) transfer(O'13123043525',4H----)
write(*,*) transfer(B'01011001010011000100011101010101',4H----)
write(*,*) transfer(3.59370785E+15,4H----)
write(*,*) transfer(1498171221,4H----)
write(*,*) transfer('UGLY',4H----)
write(*,*) transfer(4HUGLY,4H----)
write(*,'(z8.8)') 4HUGLY
write(*,'(o11.11)') 4HUGLY
write(*,'(b32.32)') 4HUGLY
! write(*,'(i11.11)') 4HUGLY
! write(*,'(e15.7)') 4HUGLY
end program tprobe
C:\gfortran\clf\xor>ifort tprobe.f90
Intel(R) Fortran Compiler for Intel(R) EM64T-based applications, Version 9.1
Build 20061104
Copyright (C) 1985-2006 Intel Corporation. All rights reserved.
Microsoft (R) Incremental Linker Version 8.00.40310.39
Copyright (C) Microsoft Corporation. All rights reserved.
-out:tprobe.exe
-subsystem:console
tprobe.obj
C:\gfortran\clf\xor>tprobe
4
ABCDEFGHIJ
1498171221
1498171221
1498171221
3.5937079E+15
1498171221
UGLY
UGLY
Input was INTEGER(4)
Value was 1498171221
Input was INTEGER(4)
Value was 1498171221
Input was INTEGER(4)
Value was 1498171221
Input was INTEGER(4)
Value was 1498171221
Input was INTEGER(4)
Value was 1498171221
Input was INTEGER(4)
Value was 1498171221
Input was INTEGER(4)
Value was 1498171221
1498171221
1498171221
1498171221
1498171221
1498171221
1498171221
1498171221
594C4755
13123043525
01011001010011000100011101010101
So we come to the conclusion the ifort has TYPE = INTEGER, KIND = 4.
> "Steve Lionel" <steve....@intel.com> wrote in message
> news:d59b9c2d-5624-4109-9358-
>
> > What would you expect:
> > print *, kind(10HABCDEFGHIJ)
> > to display?
> So clearly gfortran says TYPE = CHARACTER, KIND = 1.
...
> So we come to the conclusion the ifort has TYPE = INTEGER, KIND = 4.
I confess that I didn't actually study the code to do anything like
verify the above conclusions. And, of course, we still have the caveat
of all of this being nonstandard. Just like Hollerith has never
coexisted with user generics, it has never coexisted with the kind
intrinsic. But that being said...
I could see the character interpretation as being sort of what one might
think of such a construct today. But historically, Hollerith was
specifically for use with noncharacter variables. I might argue that the
integer interpretation is at least closer to historically consistent.
You'd be hard put to ascribe any specific type to Hollerith and have
everything work as it should, but integer probably comes as close as
anything.
So the above difference doesn't surprise me. It even fits with the Intel
compiler having a lot more investment in historical compatibility, while
gfortran is of much newer heritage.
The key difference is how the unary minus is treated. In many
languages, a numerical constant in an expression is signed, so the
minus is "welded" to the number. Not so in Fortran where the sign is
simply a unary operator treated like any other. Once you understand
this, evaluating the expression is simply a mechanical process of
following Fortran's operator precedence rules. This is also why
trying to generalize Fortran behavior from that of other languages is
dangerous. (And also likely why the standard does not allow
consecutive operators as the results can be a trap for the unwary.)
Before some of you jump on me about this, noting that the standard
defines *signed-int-literal-constant*, let me explain further.
In the definition of an expression, a *primary* can be a *constant*.
If you look at the definition of *constant* you see one of the choices
is *literal-constant* which in turn can be *int-literal-constant*.
This last is a digit string (with optional kind specifier) and is NOT
the same as *signed-int-literal-constant*.
So while signed-int-literal-constant has many uses in the language, it
does not in an expression. If you place a plus or minus before such a
constant, it's a unary operator and there are precedence and
association rules for those.
Steve
> So while signed-int-literal-constant has many uses in the language, it
> does not in an expression. If you place a plus or minus before such a
> constant, it's a unary operator and there are precedence and
> association rules for those.
In Fortran 66 signed-int-literal-constant was needed for DATA statements
which didn't allow an expression, even a constant expression.
-- glen
That's essentially the same thing as giving the sign higher precedence
than the infix add operators. That's also different from conventional
mathematical practice. Consider 10 - 5**2, mathematically
people expect that to mean the same as -5**2 + 10.
> [...] (And also likely why the standard does not allow
> consecutive operators as the results can be a trap for the unwary.)
Fortran actually does allow consecutive operators. But (loosely
stated) the operators must increase in precedence from left to
right. So, the closer you get to the operand, the higher the
operator's precedence has to be. This rule is memorable (and
used to be completely true). Now days the unary sign operators
are claimed in a normative table in the standard document to
be higher precedence than the infix operators. If you look at
the syntax rules though, it's clear that the prefix sign operators
have the *same* precendence as the infix add ops. So, an infix
addop can't be immediately followed by a prefix sign.
> Before some of you jump on me about this, noting that the standard
> defines *signed-int-literal-constant*, let me explain further.
There are only three places in the language where the sign is considered
part of the literal. They are all places where an expression is not
permitted. They could eliminate the peculiarity by adding a different
one: claim that in those three places expressions *are* allowed, but
the only operation allowed is unary signs. (The three places are:
literals in a formatted file, literal data in the DATA statement, and
the scale factor for the P edit descriptor.)
--
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
> There are only three places in the language where the sign is considered
> part of the literal.
.....
> (The three places are: literals in a formatted file, literal data in the
> DATA statement, and the scale factor for the P edit descriptor.)
I was going to qubble about Steve's "many places in the language", but
James beat me to it. I don't think of three as many. I'd also quibbble
with James about the formatted file case. That doesn't count as a
literal. Earlier versions of the language referred to it that way, but I
think that at least most usages of that terminology got expunged in an
f90 corrigendum. The thing in a formatted file has a lot of comonality
in form with a literal constant, but it also has a lot of diffferences.
If one calls it a literal constant, one needs to spend about as long
listing the differences as it would have taken to just define it
separately. I'm thinking there might have been another place that James
missed because the number three sounds familliar (not counting the
formatted file case), but it isn't occurring to me off the top of my
head. Oh, I think I just recalled. Might be as part of a literal complex
constant.
I have another approach I'd have taken to this stuff. I'd allow the sign
to be considered as part of the literal in all contexts, as long as that
still parses. (In cases like -5-3, it doesn't parse if the second minus
is part of the second literal constant, so that's an example of a case
where it wouldn't be.) I'm convinced that would actually be a quite
simple rule. I've mentioned it here before and James didn't like it as
he clearly thought it would be orders of magnitue more complicated than
I do. I still do like it, but I'm not going to argue about it.
Well, and it might be that the digit string on a STOP statement has
that property. I often forget the "complex literal" since it should be
considered an expression (a complex constructor) and should indeed
allow expressions as the operands within it. In fact, I think that all*
contexts that allow a literal should allow an expression as well - maybe
limited to being an "initialization expression" or a "specification
expression" in some cases, but an expression nevertheless. With
that rule, there would be no need of a signed-int-literal-constant
syntax definition at all.
*OK, not the integers in Format strings - making them expressions
would generally be a mess. And not the values on formatted files,
which Maine doesn't even regard as literals anyway. Maybe that's
the attitude that should be taken with respect to formats too. Evidently
the DT edit descriptor syntax also uses "signed literals", which
would be another of the list of exceptions to the general rule.