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

size of a derived type containing pointers...

63 views
Skip to first unread message

pehache-tolai

unread,
Mar 25, 2010, 3:49:21 AM3/25/10
to
Hello,

In my code I need to determine the size of various variables which are
defined as derived types.

Until now I used to use the INQUIRE() function, but it doesn't work if
the derived type contains some pointers. Is there a (not too
complicated) solution ? I don't need to know the size of the objects
pointed or allocated by the pointers, but only the size of the derived
type.

Thanks,

--
pehache

robert....@sun.com

unread,
Mar 25, 2010, 5:58:00 AM3/25/10
to


The easiest way would be to declare an array of two of them
and subtract the LOC of the second from the LOC of the first.
For example, using Oracle Solaris Fortran in 32-bit mode, the
program

PROGRAM MAIN
TYPE T
TYPE(T), POINTER :: P
END TYPE
TYPE(T) A(2)
PRINT *, LOC(A(2)) - LOC(A(1))
END

prints

4

The function LOC is a nonstandard extension, but one that
is almost always present. I showed in a previous posting
how to do the same thing using only standard features,
but some people thought that approach was too ugly to even
consider.

Bob Corbett

pehache-tolai

unread,
Mar 25, 2010, 11:25:26 AM3/25/10
to
On 25 mar, 10:58, robert.corb...@sun.com wrote:
>
> The easiest way would be to declare an array of two of them
> and subtract the LOC of the second from the LOC of the first.
> For example, using Oracle Solaris Fortran in 32-bit mode, the
> program
>
>       PROGRAM MAIN
>         TYPE T
>           TYPE(T), POINTER :: P
>         END TYPE
>         TYPE(T) A(2)
>         PRINT *, LOC(A(2)) - LOC(A(1))
>       END
>
> prints
>
>  4
>
> The function LOC is a nonstandard extension, but one that
> is almost always present.  

Thanks !

Now I remember that I already seen something like that some years
ago...

> I showed in a previous posting
> how to do the same thing using only standard features,
> but some people thought that approach was too ugly to even
> consider.
>

Probably I would have tried to equivalence a variable of the derived
type with a large enough integer array, then fill the derived type
with some values, then check until which element the integer array has
been modified. But I guess this can fail in some cases :

type my_type
real :: x
complex, pointer :: y(:)
integer :: n
end type
type(my_type) :: A
integer :: B(1000) ! B must be larger than A
equivalence (A,B)

B(:) = 0
A%x = huge(0.0)
allocate( A%y(10) )
A%n = huge(0)
size_of_my_type = size(B)
while (B(size_of_my_type) == 0 .and. size_of_my_type > 0)
size_of_my_type = size_of_my_type - 1
end while


--
pehache

Richard Maine

unread,
Mar 25, 2010, 11:59:54 AM3/25/10
to
pehache-tolai <peha...@gmail.com> wrote:

There is currently no portable standard-conforming way.

Bob mentioned the LOC function, but I think he overstates when he says
it is "almost always present." I haven't actually checked recently, but
I doubt it is present in some of the compilers I have most used. I'd
probably agree if the claim were modified to say that almost all
compilers have some similar functionality, possibly under a different
name.

One possible variant that you will probably find in most current
compilers is the f2003 C_LOC function. It does require extra trickery to
convert the results of C_LOC into integers for subtraction. One way
would be to do it in a short C function.

The equivalence trick you mentioned involves a nonstandard equivalence
that some compilers will reject.

As long as you are looking at nonstandard solutions anyway, you might
look at one that is at least slated to become standard. I think that
storage_size is in the f2008 draft. I proposed it for f2003, as a
substitute for what I considered to be anacronisms otherwise being added
to f2003, but my proposal didn't make it. (F2003 added ways to find
storage sizes, as long as you were working only with f77 types. I
considered that an anacronism. For example, you could not even get the
sizes of intrinsic types of other than default or double precision
kinds).

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain

glen herrmannsfeldt

unread,
Mar 25, 2010, 2:24:09 PM3/25/10
to
robert....@sun.com wrote:
(snip)


> The easiest way would be to declare an array of two of them
> and subtract the LOC of the second from the LOC of the first.

As I found out when I tried, though, you can't subtract
C_LOC(first) from C_LOC(second). It would be nice to
be able to do that.

-- glen

James Van Buskirk

unread,
Mar 25, 2010, 2:35:08 PM3/25/10
to
"Richard Maine" <nos...@see.signature> wrote in message
news:1jfwiq3.1154fi71vt5b5sN%nos...@see.signature...

> There is currently no portable standard-conforming way.

C:\gfortran\clf\sizetest>type sizetest1.f90
program sizetest1
use ISO_C_BINDING
implicit none
type contains_pointer
integer data
type(contains_pointer), pointer :: next
end type contains_pointer
integer, parameter :: ik1 = selected_int_kind(2)
type(contains_pointer) sp
type(contains_pointer), target :: ap(2)

! f90 way:
write(*,'(a,i0)') 'In f90: ', size(transfer(sp,(/1_ik1/)))
! f03 way:
write(*,'(a,i0)') 'In f03: ', &
transfer(C_LOC(ap(2)),1_C_INTPTR_T)- &
transfer(C_LOC(ap(1)),1_C_INTPTR_T)
! f08 way:
write(*,'(a,i0)') 'In f08: ', C_SIZEOF(sp)
end program sizetest1

C:\gfortran\clf\sizetest>gfortran -Wall sizetest1.f90 -osizetest1

C:\gfortran\clf\sizetest>sizetest1
In f90: 16
In f03: 16
In f08: 16

--
write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
6.0134700243160014d-154/),(/'x'/)); end


glen herrmannsfeldt

unread,
Mar 25, 2010, 3:46:30 PM3/25/10
to
James Van Buskirk <not_...@comcast.net> wrote:
(snip)

> ! f03 way:
> write(*,'(a,i0)') 'In f03: ', &
> transfer(C_LOC(ap(2)),1_C_INTPTR_T)- &
> transfer(C_LOC(ap(1)),1_C_INTPTR_T)

Last time this came up, I just put in 4.

It would have been nice to have C_PTRDIFF.

C_PTRDIFF(C_LOC(ap(2)),C_LOC(ap(1)))

-- glen

Richard Maine

unread,
Mar 25, 2010, 4:31:52 PM3/25/10
to
James Van Buskirk <not_...@comcast.net> wrote:

> "Richard Maine" <nos...@see.signature> wrote in message
> news:1jfwiq3.1154fi71vt5b5sN%nos...@see.signature...
>
> > There is currently no portable standard-conforming way.

> ! f90 way:


> write(*,'(a,i0)') 'In f90: ', size(transfer(sp,(/1_ik1/)))

I didn't think of that one. Figures that you would. :-) I agree it is
standard conforming. I have used size(transfer(...)) in the past for
related purposes, so I suppose I ought to have thought of it. It was a
long time ago that I was doing that. I stopped it because, in addition
to being horribly messy (not just that line, but all the other parts
involved), it tended to crash compilers of the day. I think they have
since gotten better.

> ! f03 way:
> write(*,'(a,i0)') 'In f03: ', &
> transfer(C_LOC(ap(2)),1_C_INTPTR_T)- &
> transfer(C_LOC(ap(1)),1_C_INTPTR_T)

That's not standard conforming. It is highly likely to work, but is not
standard conforming. It assumes things about the internal representation
of C_PTR. They are things quite likely to be so, but they aren't
specified in the standard. This is a plausible alternative to the option
I mentioned of using a C function to do the subtraction (which is also
probably not strictly standard conforming, but is also likely to work).

> ! f08 way:
> write(*,'(a,i0)') 'In f08: ', C_SIZEOF(sp)

Why C_SIZEOF instead of just STORAGE_SIZE, which I mentioned? C_SIZEOF
is mostly just a transformation of a special case. It is a
transformation that is often enough used to justify a special function
(at least that's my understanding of the argument for what otherwise
looks like redundant functionality).

Note that your version with C_SIZEOF is not actually conformant with the
f2008 draft because it does not meet the special-case requirements of
C_SIZEOF. In particular, sp is not interoperable.

glen herrmannsfeldt

unread,
Mar 25, 2010, 7:12:18 PM3/25/10
to
Richard Maine <nos...@see.signature> wrote:
> James Van Buskirk <not_...@comcast.net> wrote:

>> "Richard Maine" <nos...@see.signature> wrote in message
>> news:1jfwiq3.1154fi71vt5b5sN%nos...@see.signature...

>> > There is currently no portable standard-conforming way.

>> ! f90 way:
>> write(*,'(a,i0)') 'In f90: ', size(transfer(sp,(/1_ik1/)))

> I didn't think of that one. Figures that you would. :-) I agree it is
> standard conforming. I have used size(transfer(...)) in the past for
> related purposes, so I suppose I ought to have thought of it. It was a
> long time ago that I was doing that. I stopped it because, in addition
> to being horribly messy (not just that line, but all the other parts
> involved), it tended to crash compilers of the day. I think they have
> since gotten better.

"Standard conforming" is a complicated question in these cases.
In this case, it depends on the existence of the appropriate kind.
The unit for sizeof in C is the size of a char, but the main
requirement on that is that it be at least 8 bits.


>> ! f03 way:
>> write(*,'(a,i0)') 'In f03: ', &
>> transfer(C_LOC(ap(2)),1_C_INTPTR_T)- &
>> transfer(C_LOC(ap(1)),1_C_INTPTR_T)

> That's not standard conforming. It is highly likely to work, but is not
> standard conforming. It assumes things about the internal representation
> of C_PTR. They are things quite likely to be so, but they aren't
> specified in the standard. This is a plausible alternative to the option
> I mentioned of using a C function to do the subtraction (which is also
> probably not strictly standard conforming, but is also likely to work).

C only allows subtraction of pointers to different parts of the
same object, such as different elements of an array. That removes
some of the cases where this can fail. C also allows different
representation for pointers to different types. If I understand
it right, Fortran doesn't allow for that one. For example,
character pointers on word addressed machines might use other
bits to indicate the position in a word. I believe that C also
doesn't guarantee that there is such an integer type, but only says
what happens if there is such a type. It could be especially
interesting in the case of 32 bit far model IA32 code, where
pointers are 48 bits. (16 bit segment selector, 32 bit offset.)



>> ! f08 way:
>> write(*,'(a,i0)') 'In f08: ', C_SIZEOF(sp)

> Why C_SIZEOF instead of just STORAGE_SIZE, which I mentioned? C_SIZEOF
> is mostly just a transformation of a special case. It is a
> transformation that is often enough used to justify a special function
> (at least that's my understanding of the argument for what otherwise
> looks like redundant functionality).

Again, there could be some interesting cases on word addressed
machines. C has the preprocessor macro CHAR_BIT indicating
the number of bits in a (char), and so the unit for sizeof.



> Note that your version with C_SIZEOF is not actually conformant with the
> f2008 draft because it does not meet the special-case requirements of
> C_SIZEOF. In particular, sp is not interoperable.

If there is no corresponding C type, then asking for the C sizeof
something doesn't make so much sense. There are some C cases
that I wonder about. In C, character constants, such as 'x', have
type int, and so sizeof('x')==sizeof(int). (As I understand it,
that isn't true in C++.) Enumeration constants also have sizeof(int),
though the appropriate variable can have a different size. C doesn't
allow pointers to constants, which avoids some problems that would
otherwise appear in those two cases.

-- glen

Phred Phungus

unread,
Mar 25, 2010, 9:37:59 PM3/25/10
to

$ gfortran -D_GNU_SOURCE -Wall -Wextra jb1.f90 -o out
jb1.f90:19.32:

write(*,'(a,i0)') 'In f08: ', C_SIZEOF(sp)

1
Error: Function 'c_sizeof' at (1) has no IMPLICIT type
$ cat jb1.f90


program sizetest1
use ISO_C_BINDING
implicit none
type contains_pointer
integer data
type(contains_pointer), pointer :: next
end type contains_pointer
integer, parameter :: ik1 = selected_int_kind(2)
type(contains_pointer) sp
type(contains_pointer), target :: ap(2)

! f90 way:
write(*,'(a,i0)') 'In f90: ', size(transfer(sp,(/1_ik1/)))
! f03 way:
write(*,'(a,i0)') 'In f03: ', &
transfer(C_LOC(ap(2)),1_C_INTPTR_T)- &
transfer(C_LOC(ap(1)),1_C_INTPTR_T)
! f08 way:
write(*,'(a,i0)') 'In f08: ', C_SIZEOF(sp)
end program sizetest1

! gfortran -D_GNU_SOURCE -Wall -Wextra jb1.f90 -o out
$


I don't see an obvious culprit for the error.
--
fred

robert....@sun.com

unread,
Mar 25, 2010, 10:08:43 PM3/25/10
to
On Mar 25, 8:59 am, nos...@see.signature (Richard Maine) wrote:
> pehache-tolai <pehach...@gmail.com> wrote:

> There is currently no portable standard-conforming way.
>
> Bob mentioned the LOC function, but I think he overstates when he says
> it is "almost always present." I haven't actually checked recently, but
> I doubt it is present in some of the compilers I have most used. I'd
> probably agree if the claim were modified to say that almost all
> compilers have some similar functionality, possibly under a different
> name.

I would be very interested in knowing if there is a Fortran
implementation that does not provide the function LOC. LOC
is so commonly used, I would think an implementation that
did not provide it would not be viable.

Bob Corbett

Richard Maine

unread,
Mar 25, 2010, 10:19:30 PM3/25/10
to
Phred Phungus <Ph...@example.invalid> wrote:

> write(*,'(a,i0)') 'In f08: ', C_SIZEOF(sp)
> 1
> Error: Function 'c_sizeof' at (1) has no IMPLICIT type

...


> I don't see an obvious culprit for the error.

I would say that the most obvious culprit is that, as per the comment,
C_SIZEOF is an f2008 feature. Since GFortran doesn't (yet?) claim to be
even a full f2003 compiler, much less f2008, you can't necessarily count
on f2008 features.

Given that James appears to have gotten it to work with GFortran, I
posit that perhaps this function might have been fairly recently added
and that he has a newer version of GFortran than you do. While I don't
know that to be so, it seems like a good guess.

robert....@sun.com

unread,
Mar 25, 2010, 10:25:12 PM3/25/10
to


There are a couple of points that are unlikely to cause
problems, but which are, theoretically, possible problems.
The first is that the Fortran standards do not require an
implementation to use the same layout for textually
identical type definitions. The second is that an
implementation might add some padding between elements of
arrays to make address arithmetic easier. The
implementation need not provide the padding for scalar
variables and components. In practice, every implementation
of which I am aware always uses the same padding whether a
variable is a scalar or an array.

Bob Corbett

Richard Maine

unread,
Mar 25, 2010, 10:26:28 PM3/25/10
to
<robert....@sun.com> wrote:

Well, I don't maintain a list because it isn't a feature I use. I don't
use the feature because I've run into compilers that don't support it.
The F90 compiler vendor that provided the very first f90 compiler comes
to mind. That is also the vendor whose f90/f95 compilers I most often
used, so it counts as a *MAJOR* case for me - not just some obscure nit.
It wouldn't surprise me at all to find that there are others as well.
That one case was enough to keep me from using it, so, as noted, I
didn't even check others to make a list.

program bob
integer :: i
write (*,*) loc(i)
end

nagfor clf.f90
NAG Fortran Compiler Release 5.2(711)
[NAG Fortran Compiler normal termination]
Undefined symbols:
"_loc_", referenced from:
_main in clf.o

robert....@sun.com

unread,
Mar 25, 2010, 10:47:31 PM3/25/10
to
On Mar 25, 7:26 pm, nos...@see.signature (Richard Maine) wrote:

I can believe the NAGWare compiler would not support LOC.
Sun stopped purchasing a license for the NAG compiler
during the lean times, so it has been a while since I used
it. I do wonder if there is a second compiler that does not
support LOC.

Bob Corbett

glen herrmannsfeldt

unread,
Mar 26, 2010, 1:04:02 AM3/26/10
to
robert....@sun.com wrote:
(snip)


> There are a couple of points that are unlikely to cause
> problems, but which are, theoretically, possible problems.
> The first is that the Fortran standards do not require an
> implementation to use the same layout for textually
> identical type definitions. The second is that an
> implementation might add some padding between elements of
> arrays to make address arithmetic easier. The
> implementation need not provide the padding for scalar
> variables and components. In practice, every implementation
> of which I am aware always uses the same padding whether a
> variable is a scalar or an array.

C sizeof is required to including any padding needed for
an array. I believe that means that the padding is there
even for a scalar, as you need to be able to memcpy() a
scalar struct based on its sizeof.

Also, I believe that C does require the same layout for
texttually identical struct definitions. It seems that
would apply to BIND(C) structures, too.

Sizing not related to C interoperability might not
including such padding.

-- glen

glen herrmannsfeldt

unread,
Mar 26, 2010, 1:09:45 AM3/26/10
to
Richard Maine <nos...@see.signature> wrote:
(snip)


> I would say that the most obvious culprit is that, as per the comment,
> C_SIZEOF is an f2008 feature. Since GFortran doesn't (yet?) claim to be
> even a full f2003 compiler, much less f2008, you can't necessarily count
> on f2008 features.

> Given that James appears to have gotten it to work with GFortran, I
> posit that perhaps this function might have been fairly recently added
> and that he has a newer version of GFortran than you do. While I don't
> know that to be so, it seems like a good guess.

You might also want the -std=f2008 command line option.
The version I have doesn't yet allow that, but presumably
versions with Fortran 2008 features will add it.

-- glen

robert....@sun.com

unread,
Mar 26, 2010, 2:40:16 AM3/26/10
to
On Mar 25, 10:04 pm, glen herrmannsfeldt <g...@ugcs.caltech.edu>
wrote:

> C sizeof is required to including any padding needed for
> an array. I believe that means that the padding is there
> even for a scalar, as you need to be able to memcpy() a
> scalar struct based on its sizeof.
>
> Also, I believe that C does require the same layout for
> texttually identical struct definitions. It seems that
> would apply to BIND(C) structures, too.

Yes the Fortran standards require the same layout for
identical BIND(C) types and sequence types, even they
derive from different type definitions. One bit of
nastiness regarding numeric sequence types is that the
standards require them to be laid out in ways that can
violate some machines' data alignment requirements.

> Sizing not related to C interoperability might not
> including such padding.

AFAIK, no implementation has taken advantage of that
freedom, but, yes, the standard offers it. Several
implementors have threatened to reorder the fields of
a derived type to allow more efficient data packing
and/or access, but I do not think any implementor has
yet had the guts to do it. I certainly do not propose
to be the first.

Bob Corbett

Richard Maine

unread,
Mar 26, 2010, 2:57:13 AM3/26/10
to
<robert....@sun.com> wrote:

> I can believe the NAGWare compiler would not support LOC.
> Sun stopped purchasing a license for the NAG compiler
> during the lean times, so it has been a while since I used
> it. I do wonder if there is a second compiler that does not
> support LOC.

I suspect so, but as I said, the NAG compiler alone is more than enough
instance for me and I haven't kept a list.

Now that I'm retired, I have a lot more limited selection of compilers
to experiment with to make such lists. The NAG compiler would account
for 50% of the ones I have handy at the moment on this machine. Yes, the
other 50% appears to have a LOC. By my measurement, 50% is a lot less
than "almost always." Before I retired, I had a lot larger selection of
compilers that I could test, but the NAG one (well, ones) probably
accounted for more like 90% of my use.

Of course, I'm thinking only about reasonably current f90+ compilers. If
one allows older f90 compilers as well as current ones, I'd go from
suspecting so to being willing to bet on it.

And if one allows f77 compilers, then lots of them didn't have LOC,
paticularly if one looks for that exact spelling.

Richard Maine

unread,
Mar 26, 2010, 3:03:48 AM3/26/10
to
<robert....@sun.com> wrote:

> One bit of
> nastiness regarding numeric sequence types is that the
> standards require them to be laid out in ways that can
> violate some machines' data alignment requirements.

That kind of issue isn't new to numeric sequence types either. Common
has had that issue for a long time, notably with double precision, which
can end up misaligned. I recall dealing with some f77 compilers that
just could not compile valid f77 code into something that actually
worked if there were such common misalignments. Others violated the
standard's layout requirements (thus possibly breaking things) in order
to make it work. I recall SUN at least having an option to make the code
conform to the standard's layout requirements and still work, but it
gave you a prominent warning that the result would run slowly.

robert....@sun.com

unread,
Mar 26, 2010, 3:15:09 AM3/26/10
to
On Mar 25, 11:57 pm, nos...@see.signature (Richard Maine) wrote:
> <robert.corb...@sun.com> wrote:

> Now that I'm retired, I have a lot more limited selection of compilers
> to experiment with to make such lists. The NAG compiler would account
> for 50% of the ones I have handy at the moment on this machine. Yes, the
> other 50% appears to have a LOC. By my measurement, 50% is a lot less
> than "almost always." Before I retired, I had a lot larger selection of
> compilers that I could test, but the NAG one (well, ones) probably
> accounted for more like 90% of my use.

I agree that there might be another, I just cannot think
of what it might be. The compilers to which I currently
have easy access all support LOC, either as an intrinsic
(the right way) or as an external function. The external
function is undesirable for implementations that need to
work in 32- and 64-bit enviornments.

I was surprised NAGWare does not support it yet. I know
NAGWare started out requiring code to be pretty strictly
standard conforming, but they had to give ground on many
fronts already.

> Of course, I'm thinking only about reasonably current f90+ compilers. If
> one allows older f90 compilers as well as current ones, I'd go from
> suspecting so to being willing to bet on it.
>
> And if one allows f77 compilers, then lots of them didn't have LOC,
> paticularly if one looks for that exact spelling.

Yes, I can think of a few Fortran vendors in this area who
went out of business refusing to support the nonstandard
extensions their customers wanted.

Bob Corbett

robert....@sun.com

unread,
Mar 26, 2010, 3:28:42 AM3/26/10
to
On Mar 26, 12:03 am, nos...@see.signature (Richard Maine) wrote:

> <robert.corb...@sun.com> wrote:
> > One bit of
> > nastiness regarding numeric sequence types is that the
> > standards require them to be laid out in ways that can
> > violate some machines' data alignment requirements.
>
> That kind of issue isn't new to numeric sequence types either. Common
> has had that issue for a long time, notably with double precision, which
> can end up misaligned. I recall dealing with some f77 compilers that
> just could not compile valid f77 code into something that actually
> worked if there were such common misalignments. Others violated the
> standard's layout requirements (thus possibly breaking things) in order
> to make it work. I recall SUN at least having an option to make the code
> conform to the standard's layout requirements and still work, but it
> gave you a prominent warning that the result would run slowly.

Oracle Solaris Fortran and its Sun Fortran predecessors
produce the standard required layouts for both common
blocks and most numeric sequence types by default. Yes,
there are cases where it costs significant performance on
some hardware. I along with others pushed hard to have the
hardware handle misaligned accesses more efficiently when
the SPARC V9 architecture was designed (you can find the
results of that in the SPARC V9 architecture manual), but
the hardware designers chose to ignore those bits in their
implementations. Given the magnificent job the designers
of the original UltraSPARC chip did, it is hard to fault
them for what they left out.

Bob Corbett

glen herrmannsfeldt

unread,
Mar 26, 2010, 3:26:10 AM3/26/10
to
Richard Maine <nos...@see.signature> wrote:
> <robert....@sun.com> wrote:

>> One bit of
>> nastiness regarding numeric sequence types is that the
>> standards require them to be laid out in ways that can
>> violate some machines' data alignment requirements.

> That kind of issue isn't new to numeric sequence types either. Common
> has had that issue for a long time, notably with double precision, which
> can end up misaligned.

I haven't heard about this one recently, so I thought that
the standard may have changed.

> I recall dealing with some f77 compilers that
> just could not compile valid f77 code into something that actually
> worked if there were such common misalignments. Others violated the
> standard's layout requirements (thus possibly breaking things) in order
> to make it work. I recall SUN at least having an option to make the code
> conform to the standard's layout requirements and still work, but it
> gave you a prominent warning that the result would run slowly.

I used to know the OS/360 routines for that. They trap the
interrupt that occurs for a misaligned operand, copy it to
appropriately aligned memory, execute the offending instruction
with the new address, then fix up everything so that it looks
like it should. It takes many instructions to do all that.

Even more, though, the imprecise interrupt on the 360/91 didn't
allow such routines to find the operand. S/370 allows for
misaligned data, though it may still run slower.

As for newer machines, most RISC processors require data to
be appropriately aligned. IA32 does not, but does indicate
that aligned data will likely run faster.

-- glen

Phred Phungus

unread,
Mar 26, 2010, 5:14:32 AM3/26/10
to

$ gfortran -D_GNU_SOURCE -std=f2008 -Wall -Wextra jb1.f90 -o out
f951: error: unrecognized command line option "-std=f2008"
$ uname -v
#58-Ubuntu SMP Tue Dec 1 18:57:07 UTC 2009
$ which gfortran
/usr/bin/gfortran
$

Rats. I wonder how the notion of "snapshots" fits in with this.
--
fred

Paul Thomas

unread,
Mar 26, 2010, 5:34:17 AM3/26/10
to

gfortran --version

Paul

Tim Prince

unread,
Mar 26, 2010, 9:49:20 AM3/26/10
to
On 3/26/2010 12:26 AM, glen herrmannsfeldt wrote:
> Richard Maine<nos...@see.signature> wrote:
>> <robert....@sun.com> wrote:
>
>>> One bit of
>>> nastiness regarding numeric sequence types is that the
>>> standards require them to be laid out in ways that can
>>> violate some machines' data alignment requirements.
>
>> That kind of issue isn't new to numeric sequence types either. Common
>> has had that issue for a long time, notably with double precision, which
>> can end up misaligned.
>
> I haven't heard about this one recently, so I thought that
> the standard may have changed.
What's different from previous decades is the widespread availability of
CPUs with hardware fixup for mis-aligned data, and compilers which try
to fix up alignments at run time.

The machines I learned on (GE6xx/H6xxx) simply took the data from the
next lower aligned address. No address fault, but not the data you
might have expected. The machines persisted into the f77 era, but I
never saw a production f77 or C compiler.


>
> As for newer machines, most RISC processors require data to
> be appropriately aligned. IA32 does not, but does indicate
> that aligned data will likely run faster.

This will come around again next year with the introduction of hardware
support for 256-bit parallel operations.


--
Tim Prince

Tim Prince

unread,
Mar 26, 2010, 9:55:44 AM3/26/10
to

Why would any compiler have introduced LOC in recent years, when the
standard spells it c_loc() ? The question now is whether customers will
demand the warnings for non-standard usage.


--
Tim Prince

Dick Hendrickson

unread,
Mar 26, 2010, 12:08:20 PM3/26/10
to
Richard Maine wrote:
> <robert....@sun.com> wrote:
>
>> I can believe the NAGWare compiler would not support LOC.
>> Sun stopped purchasing a license for the NAG compiler
>> during the lean times, so it has been a while since I used
>> it. I do wonder if there is a second compiler that does not
>> support LOC.
>
> I suspect so, but as I said, the NAG compiler alone is more than enough
> instance for me and I haven't kept a list.
>
Did you try the -dusty (or whatever) option. At one time they had
a lot of stuff hidden.

Dick Hendrickson

Richard Maine

unread,
Mar 26, 2010, 12:55:56 PM3/26/10
to
Tim Prince <tpr...@myrealbox.com> wrote:

> On 3/26/2010 12:15 AM, robert....@sun.com wrote:
> > On Mar 25, 11:57 pm, nos...@see.signature (Richard Maine) wrote:
> >> <robert.corb...@sun.com> wrote:
> >
> >> And if one allows f77 compilers, then lots of them didn't have LOC,
> >> paticularly if one looks for that exact spelling.
> >
> > Yes, I can think of a few Fortran vendors in this area who
> > went out of business refusing to support the nonstandard
> > extensions their customers wanted.

or for unrelated reasons. I detect some circularity here in suggesting
that users can safely use LOC because almost all vendors have it and
that vendors should have it because users use it. Not that such
circularity is unheard of.

> Why would any compiler have introduced LOC in recent years, when the
> standard spells it c_loc() ? The question now is whether customers will
> demand the warnings for non-standard usage.

In any case, rather than wander farther off, I'd like to restate my main
point, which that I advise against depending on the existance of the
nonstandard LOC intrinsic, insomuch as it is not portable. There does
exist at least one major compiler vendor that does not support it. I
will not discuss the relative merits of different vendor's products in
this regard. I just note that the one demonstrated case is a significant
vendor.

In answer to Dick's question about -dusty... good thought. That's not
the kind of thing I normally associate with -dusty, but it does seem
worth checking just in case. I did so and it makes no difference.

There are the portability issues of LOC even among those vendors that do
support it. Its units of measure can vary. In fact, I think the first
machines I recall seeing it on returned a value in units of words. I'm
not sure what happens with compilers that support 64-bit addressing and
have 32-bit default integers; I suppose the "obvious" thing would be for
LOC to return a non-default integer, but that has a good chance of
breaking old codes that use it. There are reasons why the standard
didn't just adopt LOC to standardize a common existing practice and why
C_LOC deliberately makes its internals opaque.

Phred Phungus

unread,
Mar 28, 2010, 12:44:16 AM3/28/10
to
Paul Thomas wrote:

[nothing too precious in the context]

> gfortran --version

$ gfortran --version
GNU Fortran (Ubuntu 4.3.3-5ubuntu4) 4.3.3
Copyright (C) 2008 Free Software Foundation, Inc.

GNU Fortran comes with NO WARRANTY, to the extent permitted by law.
You may redistribute copies of GNU Fortran
under the terms of the GNU General Public License.
For more information about these matters, see the file named COPYING

$

This surprises me, because I thought my OS had told me before that it
was done with 4.3, but I find many such erroneous moments as a person in
his first year with linux.

So I go to the gfortran page to see what one does here to modernize.

# Download the GFortran binary
# Go into directory under which you want to put GFortran
# Unpack the package using tar xvfz gcc-trunk-x86_64.tar.gz, which
unpacks it into the directory gcc-trunk.

This sounds easy, and I'm sure it is for persons who have done it
before. The links to the latest builds did not fire for me, and so one
is left to find one thing there but is faced with many choices that look
very similar.

http://users.physik.fu-berlin.de/~tburnus/gcc-trunk/

I can't tell what's C here and what's Fortran.

Of course, I would put the binary in /usr/bin

I currently have no directory called gcc-trunk. I have one question
before I create it: they talk about a trunk over in gcc development as
well. Is the process I do here with gfortran going to conflict with the
same process, if done with gcc? Also, why isn't it called gfortran-trunk?

Thanks for your comment, and cheers,
--
fred

Phred Phungus

unread,
Mar 28, 2010, 2:27:25 AM3/28/10
to

Funny. I've seen implementations come and go now, well, at least go.

I think silverfrost might be an example. If Andy Vaught is doing as
much construction as I am, then g95 is in a state of latency.

What I don't get is that I thought that Nag was still commercially
viable. Maybe not supporting LOC is different than not supporting C_LOC?
--
fred

Richard Maine

unread,
Mar 28, 2010, 2:49:41 AM3/28/10
to
Phred Phungus <Ph...@example.invalid> wrote:

> What I don't get is that I thought that Nag was still commercially
> viable.

It is. That was sort of the point - to cite it as a counterexample to
Bob's suggestion that an implementation without LOC would not be viable.
NAG has sold f90/f95 compilers for longer than any other vendor. One can
(and people do, but I won't) debate things such as the speed of
executables, but that's not the main definition of commercial viability.
Nag does sell compilers. I'm not privy to sales information, but I know
that people make their living from its sales. That pretty much does
define commercial viability.

Phred Phungus

unread,
Mar 28, 2010, 3:48:38 AM3/28/10
to
Richard Maine wrote:
> Phred Phungus <Ph...@example.invalid> wrote:
>
>> What I don't get is that I thought that Nag was still commercially
>> viable.
>
> It is. That was sort of the point - to cite it as a counterexample to
> Bob's suggestion that an implementation without LOC would not be viable.
> NAG has sold f90/f95 compilers for longer than any other vendor. One can
> (and people do, but I won't) debate things such as the speed of
> executables, but that's not the main definition of commercial viability.
> Nag does sell compilers. I'm not privy to sales information, but I know
> that people make their living from its sales. That pretty much does
> define commercial viability.
>

Doesn't the C from MR&C work there? I've heard you talk of Malcolm as
an innovator of particular prodigousness.
--
fred

Richard Maine

unread,
Mar 28, 2010, 12:04:44 PM3/28/10
to
Phred Phungus <Ph...@example.invalid> wrote:

Yes.

robert....@sun.com

unread,
Mar 29, 2010, 8:14:35 PM3/29/10
to
On Mar 26, 9:08 am, Dick Hendrickson <dick.hendrick...@att.net> wrote:
> Richard Maine wrote:

I would be interested in knowing if NAGWare Fortran does
provide an option to accept the LOC function.

Bob Corbett

glen herrmannsfeldt

unread,
Mar 29, 2010, 8:19:14 PM3/29/10
to
robert....@sun.com wrote:
(snip)


> I would be interested in knowing if NAGWare Fortran does
> provide an option to accept the LOC function.

One could always write one in assembler. I will guess
that it is two executable instructions on most processors.

-- glen

robert....@sun.com

unread,
Mar 29, 2010, 9:46:25 PM3/29/10
to
On Mar 29, 5:19 pm, glen herrmannsfeldt <g...@ugcs.caltech.edu> wrote:

Two is probably the most common number of instructions
required. It takes one instruction (a return) for some
calling conventions on some processors.

Nonetheless, for the purpose of saying that an implementation
provides a LOC function, the ease of a user providing one of
of his own is not relevant. It might, however, explain why an
implementation that did not provide a LOC function could be
viable, even given the large number of programs that use LOC.

Bob Corbett

Richard Maine

unread,
Mar 29, 2010, 11:45:46 PM3/29/10
to
<robert....@sun.com> wrote:

> I would be interested in knowing if NAGWare Fortran does
> provide an option to accept the LOC function.

I doubt it. If so, they have hidden it pretty well. It is not in the
documentation (I just checked the latest version to make sure). The
documention does mention an option to enable some common nonstandard
intrinsics, but LOC isn't one of them. (The option is -dcfuns, which
enables some nonstandard double precision complex intrinsics).

Jim Xia

unread,
Mar 31, 2010, 12:08:14 PM3/31/10
to
> I would be very interested in knowing if there is a Fortran
> implementation that does not provide the function LOC.  LOC
> is so commonly used, I would think an implementation that
> did not provide it would not be viable.
>
> Bob Corbett


Your example (with LOC) doesn't compile with XLF. Just let you know
there are compilers think differently from yours :-)

Cheers,

Jim

robert....@sun.com

unread,
Mar 31, 2010, 10:30:07 PM3/31/10
to


Do you mean it does not compile or that it does not link?

Bob Corbett

David Thompson

unread,
Apr 7, 2010, 1:02:06 AM4/7/10
to
On Thu, 25 Mar 2010 23:12:18 +0000 (UTC), glen herrmannsfeldt
<g...@ugcs.caltech.edu> wrote:

> Richard Maine <nos...@see.signature> wrote:

> C only allows subtraction of pointers to different parts of the
> same object, such as different elements of an array. That removes

To be exact, the C standard only requires pointer subtraction within
an array, but any (single) object (such as a struct) can be treated as
an array of characters, and thus pointers within that object cast to
character pointers subtracted. The standard leaves subtraction of
pointers to/into different objects undefined: it does not require a
diagnostic, the implementation can do what it chooses, and on current
machines where subtraction of the machine addresses works fine that's
what a sane C implementor does.

> some of the cases where this can fail. C also allows different
> representation for pointers to different types. If I understand
> it right, Fortran doesn't allow for that one. For example,

Well, *Fortran* POINTERs can certainly be type-dependent; they pretty
much have to be at least rank-dependent. You presumably mean Fortran
C_PTR's, which do further constrain the C implementation to use
homogenous pointers (note 15.10 in the draft I have to hand).

> character pointers on word addressed machines might use other
> bits to indicate the position in a word. I believe that C also
> doesn't guarantee that there is such an integer type, but only says
> what happens if there is such a type. It could be especially

Namely the intptr_t and uintptr_t types, which if they exist must be
capable of losslessly preserving all data pointer values. Correct.

> interesting in the case of 32 bit far model IA32 code, where
> pointers are 48 bits. (16 bit segment selector, 32 bit offset.)

> If there is no corresponding C type, then asking for the C sizeof
> something doesn't make so much sense. There are some C cases
> that I wonder about. In C, character constants, such as 'x', have
> type int, and so sizeof('x')==sizeof(int). (As I understand it,
> that isn't true in C++.) Enumeration constants also have sizeof(int),
> though the appropriate variable can have a different size. C doesn't

More exactly, in C both characters 'x' and enum constants have the
specific type int, just like 123; in C++ they have type char or enum
type respectively. sizeof(char) is always 1 and *typically* less than
sizeof(int), but there are systems with sizeof(int)=1=sizeof(char).
sizeof(enum x) is *typically* the same as sizeof(int) but it may be
different at the compiler's choice; except in C++ which allows enum
constants to be outside (range of) int but within long in which case
*that* enum type (at least) must be wider than int.

> allow pointers to constants, which avoids some problems that would
> otherwise appear in those two cases.
>
C99 adds compound literals, which are intended mainly for aggregates
(arrays and structs) but can be used degenerately for e.g. simple
number as well. But a compound literal explicitly creates an object,
initialized by the constant(s) (or if nonstatic in a function,
optionally nonconstant(s)), which can be pointed to.

Similarly C string constants like "this" have since always actually
meant an array of char *object* initialized to the string's value,
which like any array in C is actually passed and used as a pointer.

0 new messages