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

Kind of new to cray pointers

10 views
Skip to first unread message

James Van Buskirk

unread,
Dec 3, 2007, 1:21:44 AM12/3/07
to
I am trying to use cray pointers to work around the limitations of
certain compilers regarding procedure pointers. I read the
documentation at
http://gcc.gnu.org/onlinedocs/gfortran/Cray-pointers.html#Cray-pointers
and came up with the following example:

C:\gfortran\clf\sizes>type sizes1.f90
! sizes1.f90
program sizes1
use ISO_C_BINDING
implicit none
integer(C_INT8_T) i1(0)

type C_PTR_T
type(C_PTR) data
end type C_PTR_T
type(C_PTR_T) s_C_PTR

type F_PTR_S
integer(C_INTPTR_T), pointer :: data
end type F_PTR_S
type(F_PTR_S) s_F_PTR_S

type F_PTR_A
integer(C_INTPTR_T), pointer :: data(:)
end type F_PTR_A
type(F_PTR_A) s_F_PTR_A

interface
function fptr(x) bind(C)
use ISO_C_BINDING
implicit none

integer(C_INTPTR_T), value :: x
integer(C_INTPTR_T) fptr
end function fptr
end interface

type C_PTR_F
type(C_FUNPTR) data
end type C_PTR_F
type(C_PTR_F) s_C_PTR_F

type F_PTR_F
pointer (data, fptr)
end type F_PTR_F
type(F_PTR_F) s_F_PTR_F

integer(C_INTPTR_T) fval(*)
type F_PTR_V
pointer (data, fval)
end type F_PTR_V
type(F_PTR_V) s_F_PTR_V

integer(C_INTPTR_T) sval
type F_PTR_1
pointer (data, sval)
end type F_PTR_1
type(F_PTR_1) s_F_PTR_1

write(*,'(a,i0)') 'size(C_PTR) = ', size(transfer(s_C_PTR, i1))
write(*,'(a,i0)') 'size(C_FUNPTR) = ', size(transfer(s_C_PTR_F, i1))
write(*,'(a,i0)') 'size(pointer=>scaler) = ', size(transfer(s_F_PTR_S,
i1))
write(*,'(a,i0)') 'size(pointer=>vector) = ', size(transfer(s_F_PTR_A,
i1))
write(*,'(a,i0)') 'size(cray=>function) = ', size(transfer(s_F_PTR_F,
i1))
write(*,'(a,i0)') 'size(cray=>vector) = ', size(transfer(s_F_PTR_V, i1))
write(*,'(a,i0)') 'size(cray=>scalar) = ', size(transfer(s_F_PTR_1, i1))
end program sizes1

C:\gfortran\clf\sizes>C:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran -std=f200
3 -Wall sizes1.f90 -fcray-pointer -osizes1
sizes1.f90:38.20:

pointer (data, fptr)
1
Error: BIND(C) attribute conflicts with CRAY POINTEE attribute at (1)
sizes1.f90:44.26:

pointer (data, fval)
1
Error: Unexpected attribute declaration statement at (1)
sizes1.f90:50.26:

pointer (data, sval)
1
Error: Unexpected attribute declaration statement at (1)

The last two error statements make sense in that every instance of
type F_PTR_V or type F_PTR_1 would vie to define the address of fval
or sval respectively. Perhaps the documentation could be tidied up
a bit to reflect this. The first error, though, is a showstopper.
I was hoping to be able to use cray pointers to work around the
absence of procedure pointers, which may take a while to get
implemented because the f03 standard gives them more capabilities
than cray pointers have. It doesn't make any sense to me that
cray pointers can't point at BIND(C) procedures and the documentation
doesn't alert the programmer to this restriction. It leaves the
programmer with no syntax for directly invoking a procedure obtained
as a C_FUNPTR type.

I tried a similar example with ifort and got errors like
sizes2.f90(26) : Error: This statement is not permitted as a statement
within a
derived-type-def
pointer (data, fptr)
------^

A little better error statement but again I couldn't find anything
about this issue in ifort documentation.

--
write(*,*) transfer([3.9435632276541913d180,6.013470016999177d-154], &
['x']);end


Steve Lionel

unread,
Dec 3, 2007, 1:01:26 PM12/3/07
to
On Dec 3, 1:21 am, "James Van Buskirk" <not_va...@comcast.net> wrote:
> I am trying to use cray pointers to work around the limitations of
> certain compilers regarding procedure pointers.

Cray pointers are not allowed as components of a derived type. The
Cray-style POINTER declaration is not a type declaration, you can
think of it as similar in concept to EQUIVALENCE - it establishes a
relationship between a variable and an entity.

If you want to store integer pointers in a derived type, you will have
to declare it as an INTEGER of the size of an address (you can use
ISO_C_BINDING's C_INTPTR_T for this.) To use it, you'll then assign
the value stored in the component to a variable you have named in a
POINTER statement.

Steve

James Van Buskirk

unread,
Dec 4, 2007, 6:47:55 AM12/4/07
to
"Steve Lionel" <steve....@intel.com> wrote in message
news:8b8597ba-55bf-4ac1...@j44g2000hsj.googlegroups.com...

> Cray pointers are not allowed as components of a derived type. The
> Cray-style POINTER declaration is not a type declaration, you can
> think of it as similar in concept to EQUIVALENCE - it establishes a
> relationship between a variable and an entity.

As I said, it's possible to see this after reflection, it's just not
stated as such in the documentation. Here's another thing I have
been trying to achieve with cray pointers: from all I can tell from
reading the documentation, it seems reasonable to put the pointee in
a generic interface block (it can't be the name of a generic
interface block, it's only going to be a specific function) so that
I can change what the generic name does by pointing the pointer at
different functions. Also, of course I'm going to put the pointer
in a common block (the pointee can't be in a common block, but it's
a function anyhow) so that I can have the pointer in different threads
point to different functions because the common block will be declared
THREADPRIVATE.

C:\Program Files\Microsoft Visual Studio 8\James\clf\var_comp>type qsort.i90
! File: qsort.i90
! Public domain 2007 James Van Buskirk
recursive subroutine qsort(x,N)
integer, intent(in) :: N
type(T) x(N)
real harvest
integer ipiv
type(T) temp
integer lo
integer hi

if(N <= 1) return
call random_number(harvest)
ipiv = min(int(harvest*N+1),N)
temp = x(ipiv)
x(ipiv) = x(1)
x(1) = temp
lo = 2
hi = N
do while(lo <= hi)
do lo = lo, hi
if(.NOT. x(lo) <= x(1)) exit
end do
do hi = hi, lo, -1
if(x(hi) <= x(1)) exit
end do
if(lo < hi) then
temp = x(lo)
x(lo) = x(hi)
x(hi) = temp
lo = lo+1
hi = hi-1
end if
end do
temp = x(lo-1)
x(lo-1) = x(1)
x(1) = temp
call qsort(x(1), lo-2)
if(lo < N) call qsort(x(lo), N-lo+1)
end subroutine qsort
! End of file: qsort.i90

C:\Program Files\Microsoft Visual Studio 8\James\clf\var_comp>type
var_comp.f90
! File: var_comp.f90
! Public domain 2007 James Van Buskirk
module mytype_mod
implicit none
type mytype
integer x
real y
end type mytype
interface assignment(=)
module procedure assign_mytype
end interface assignment(=)
contains
subroutine assign_mytype(x,y)
type(mytype), intent(out) :: x
type(mytype), intent(in) :: y

x%x = y%x
x%y = y%y
end subroutine assign_mytype
end module mytype_mod

module compare_mytype_mod
use mytype_mod
implicit none
private
public operator(<=)
interface operator(<=)
function lessorequal(x,y)
import mytype
type(mytype), intent(in) :: x
type(mytype), intent(in) :: y
logical lessorequal
end function lessorequal
end interface operator(<=)

pointer(loe, lessorequal)
common /loecom/ loe
!$OMP THREADPRIVATE( /loecom/ )

public set_cmp
contains
function cmpx(x,y)
type(mytype), intent(in) :: x
type(mytype), intent(in) :: y
logical cmpx

cmpx = x%x <= y%x
end function cmpx
function cmpy(x,y)
type(mytype), intent(in) :: x
type(mytype), intent(in) :: y
logical cmpy

cmpy = x%y <= y%y
end function cmpy
subroutine set_cmp(x)
logical, intent(in) :: x

if(x) then
loe = loc(cmpx)
else
loe = loc(cmpy)
end if
end subroutine set_cmp
end module compare_mytype_mod

module mytype_qsort_mod
use mytype_mod, T => mytype
use compare_mytype_mod, only: operator(<=)
implicit none
contains
include 'qsort.i90'
end module mytype_qsort_mod

module generic_recombination
use qsort_mod, only: qsort_mytype => qsort
end module generic_recombination

program test
use mytype_mod
use compare_mytype_mod, only: set_cmp
use generic_recombination
implicit none
type(mytype) x(10)
real harvest
integer i

call random_seed()
do i = 1, size(x)
call random_number(harvest)
x(i)%x = harvest*100
call random_number(harvest)
x(i)%y = harvest
end do
write(*,*) 'Original array:'
do i = 1, size(x)
write(*,*) x(i)
end do
call set_cmp(.TRUE.)
call qsort_mytype(x,size(x))
write(*,*)
write(*,*) 'Array sorted by x:'
do i = 1, size(x)
write(*,*) x(i)
end do
call set_cmp(.FALSE.)
call qsort_mytype(x,size(x))
write(*,*)
write(*,*) 'Array sorted by y:'
do i = 1, size(x)
write(*,*) x(i)
end do
end program test
! End of file: var_comp.f90

C:\Program Files\Microsoft Visual Studio 8\James\clf\var_comp>ifort /Qopenmp
var
_comp.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.

fortcom: Fatal: There has been an internal compiler error (C0000005).
compilation aborted for var_comp.f90 (code 1)

Oooh, yummy! Runs great! I still must not understand cray pointers...

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


Richard Maine

unread,
Dec 4, 2007, 11:21:57 AM12/4/07
to
James Van Buskirk <not_...@comcast.net> wrote:

> As I said, it's possible to see this after reflection, it's just not
> stated as such in the documentation. Here's another thing I have
> been trying to achieve with cray pointers: from all I can tell from
> reading the documentation, it seems reasonable to put the pointee in

> a generic interface block...

The trouble here is that you are looking for extensions to an old
feature that was never standard or particularly portable. There weren't
any such things as interface blocks when Cray pointers were first
developed. Heck, Cray pointers in most implementations can't point at
procedures at all. I'd say that there isn't much payoff in a vendor
implementing this kind of extension. It isn't as though there is any
existing code at all that uses such an extension. There is probably a
lot bigger payoff in getting the f2003 features in place.

As for the documentation, well, of course in an ideal world I'm sure
that the documentation should be better than whatever state it is in
(that's pretty much true no matter what state it is in). But mostly, I
recommend against using Cray pointers in new code except as a last
resort interim expediency. And I double lthat disrecommendation for Cray
pointers to procedures.

I suspect you will find that the documentation of Cray pointers isn't
going to keep expanding, just as the features of them aren't going to
keep expanding. It is probably safer to assume that a Cray pointer can
*NOT* be used anywhere except where the documentation explicitly says
that it can. Otherwise, the documentation of each new feature would have
to mention that you can't use Cray pointers there (which is usually
going to be the case).

For Cray pointers in interface blocks, the syntax should pretty much
document that you can't use Cray pointers there because they don't fit
in the syntax. The only things you can have in an interface block in
f90/f95 are interface bodies and module procedure statements. Cray
pointers aren't either of those. (F2003 also allows procedure
statements, which is at least a little easier to see as potentially
fitting).

I'll not comment on the internal compiler error.

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

James Van Buskirk

unread,
Dec 4, 2007, 12:51:44 PM12/4/07
to
"Richard Maine" <nos...@see.signature> wrote in message
news:1i8l7w2.1ciwl9j13dmg4uN%nos...@see.signature...

> For Cray pointers in interface blocks, the syntax should pretty much
> document that you can't use Cray pointers there because they don't fit
> in the syntax. The only things you can have in an interface block in
> f90/f95 are interface bodies and module procedure statements. Cray
> pointers aren't either of those. (F2003 also allows procedure
> statements, which is at least a little easier to see as potentially
> fitting).

C:\gfortran\clf\alloc_cray>type alloc_cray.f90
! File: alloc_cray.f90


! Public domain 2007 James Van Buskirk

module mod1
implicit none
interface zarp
subroutine can_alloc(x)
implicit none
integer, allocatable :: x(:)
end subroutine can_alloc
end interface zarp
pointer(ptr, can_alloc)
end module mod1

module mod2
implicit none
integer N
contains
subroutine alloc_me(x)
integer, allocatable :: x(:)

allocate(x(N))
end subroutine alloc_me
subroutine dealloc_me(x)
integer, allocatable :: x(:)

deallocate(x)
end subroutine dealloc_me
end module mod2

program test
use mod1
use mod2
integer i
integer, allocatable :: x(:)

N = 10
ptr = loc(alloc_me)
call zarp(x)
x = [(2*i-1, i = 1, size(x))]


do i = 1, size(x)

write(*,'(2(a,i0))') 'x(',i,') = ',x(i)
end do
ptr = loc(dealloc_me)
write(*,*) allocated(x)
call zarp(x)
write(*,*) allocated(x)
end program test
! End of file: alloc_cray.f90

C:\gfortran\clf\alloc_cray>C:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran
-Wal
l -fcray-pointer alloc_cray.f90 -oalloc_cray

C:\gfortran\clf\alloc_cray>alloc_cray
x(1) = 1
x(2) = 3
x(3) = 5
x(4) = 7
x(5) = 9
x(6) = 11
x(7) = 13
x(8) = 15
x(9) = 17
x(10) = 19
T
F

C:\gfortran\clf\alloc_cray>ifort alloc_cray.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:alloc_cray.exe
-subsystem:console
alloc_cray.obj

C:\gfortran\clf\alloc_cray>alloc_cray
x(1) = 1
x(2) = 3
x(3) = 5
x(4) = 7
x(5) = 9
x(6) = 11
x(7) = 13
x(8) = 15
x(9) = 17
x(10) = 19
T
F

Richard Maine

unread,
Dec 4, 2007, 1:08:03 PM12/4/07
to
James Van Buskirk <not_...@comcast.net> wrote:

> "Richard Maine" <nos...@see.signature> wrote in message
> news:1i8l7w2.1ciwl9j13dmg4uN%nos...@see.signature...
>
> > For Cray pointers in interface blocks, the syntax should pretty much
> > document that you can't use Cray pointers there because they don't fit
> > in the syntax. The only things you can have in an interface block in
> > f90/f95 are interface bodies and module procedure statements. Cray
> > pointers aren't either of those. (F2003 also allows procedure
> > statements, which is at least a little easier to see as potentially
> > fitting).

> [example code]

Oh. I see... well sort of. Actually I pretty much always have trouble
reading Cray pointer code, and this is no exception; Cray pointer syntax
doesn't mesh with my intuition. But anyway, I see that what you have in
the interface block is just an ordinary interface body, so that does at
least match the syntax of an interface block.

James Van Buskirk

unread,
Dec 4, 2007, 3:18:35 PM12/4/07
to
"Richard Maine" <nos...@see.signature> wrote in message
news:1i8ld6n.1jn6gesdpj465N%nos...@see.signature...

> Oh. I see... well sort of. Actually I pretty much always have trouble
> reading Cray pointer code, and this is no exception; Cray pointer syntax
> doesn't mesh with my intuition. But anyway, I see that what you have in
> the interface block is just an ordinary interface body, so that does at
> least match the syntax of an interface block.

So do you find this more readable?

C:\g95\test>type alloc_pp.f90
! File: alloc_pp.f90


! Public domain 2007 James Van Buskirk
module mod1
implicit none

abstract interface


subroutine can_alloc(x)
implicit none
integer, allocatable :: x(:)
end subroutine can_alloc
end interface

procedure(can_alloc), pointer, save :: ptr
interface zarp
procedure ptr
end interface zarp
end module mod1

module mod2
implicit none
integer N
contains
subroutine alloc_me(x)
integer, allocatable :: x(:)

allocate(x(N))
end subroutine alloc_me
subroutine dealloc_me(x)
integer, allocatable :: x(:)

deallocate(x)
end subroutine dealloc_me
end module mod2

program test
use mod1
use mod2
integer i
integer, allocatable :: x(:)

N = 10
ptr => alloc_me


call zarp(x)
x = [(2*i-1, i = 1, size(x))]
do i = 1, size(x)
write(*,'(2(a,i0))') 'x(',i,') = ',x(i)
end do

ptr => dealloc_me


write(*,*) allocated(x)
call zarp(x)
write(*,*) allocated(x)
end program test

! End of file: alloc_pp.f90

C:\g95\test>g95 -std=f2003 -Wall alloc_pp.f90 -oalloc_pp
In file alloc_pp.f90:13

procedure ptr
1
Error: Unclassifiable statement at (1)

Richard Maine

unread,
Dec 4, 2007, 4:32:40 PM12/4/07
to
James Van Buskirk <not_...@comcast.net> wrote:

> "Richard Maine" <nos...@see.signature> wrote in message
> news:1i8ld6n.1jn6gesdpj465N%nos...@see.signature...
>
> > Oh. I see... well sort of. Actually I pretty much always have trouble
> > reading Cray pointer code, and this is no exception; Cray pointer syntax
> > doesn't mesh with my intuition. But anyway, I see that what you have in
> > the interface block is just an ordinary interface body, so that does at
> > least match the syntax of an interface block.
>
> So do you find this more readable?

[example with procedure pointers instead of Cray procedure pointers]

Yes. Mostly bcause I can tell what is pointing at what. The Cray pointer
stuff always leaves me confused about that. It strikes me as more
simillar to a funny kind of equivalence, in that I allocate space to one
name and then I reference it by some other name, with the two names
having been connected by the Cray pointer statement.

I tend to get confused about which of the two names of the Cray pointer
I use in what contexts.

In your case, both versions are a bit hard for me because the generic
just adds an extra layer of naming indirection. So even the F2003
procedure pointer version assignes the pointer target and then
references it by another name (th egeneric name). I don't see that the
generic does anything useful here. I suppose this might be an extract
from a larger sample where there were also other things in the generic.

But in the Cray pointer version has a second level of naming indirection
in addition to the generic one.

0 new messages