- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
PROGRAM INDICES
INTEGER, POINTER, DIMENSION(:) :: a, b
ALLOCATE(a(0:1))
a(0) = 1
a(1) = 2
b => a
WRITE(*,*) LBOUND(b,1) !__ = 0
WRITE(*,*) UBOUND(b,1) !__ = 1
WRITE(*,*)
b => a(:)
WRITE(*,*) LBOUND(b,1) !__ = 1
WRITE(*,*) UBOUND(b,1) !__ = 2
END PROGRAM INDICES
Apparently, the boundaries of indices are only kept if I do not specify (:). Though, this makes it impossible for me to work with parts of a large array (e.g. x => y(:,:,:, j)) since all the indices get shifted to start from 1. Is there any way to have a pointer to a subfield without shifting the boundaries of indices? Or do i have to allocate another array for that?
Thanks
Dino
- Balises:
- Intel® Fortran Compiler
Lien copié
- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
If you want b to point to a(ilower:iupper) such that the bounds of b also run from ilower to iupper, the statement you want is
b(ilower:)=>a(ilower:iupper)
This form of pointer was not a part of Fortran 90 or Fortran 95; it was introduced in Fortran 2003. I assume that by now it is implemented in ifort. If you have to be compatible with a Fortran compiler that doesn't implement this form of pointer assignment, there is an ugly workaround:
call my_section_assigner(b,a(jlower:jupper),jlower)
...
subroutine my_section_assigner(lhs,rhs,lower)
integer :: lower
integer,pointer :: lhs(:)
integer,target :: rhs(lower:)
lhs=>rhs
end subroutine
The subroutine dummy argument rhs is associated with (i.e., points to) the section of interest, and the subroutine interface gives it our chosen lower bound. Because the pointer assignment is now to a simple name rather than an expression, the lower bound of that name becomes the lower bound of the pointer.
-Kurt
- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
Dino,
Here is an additional example:
[fortran]
recursive subroutine CopyToYMM_1D(f, t, s)
use MOD_ALL
real, pointer :: f(:)
type(TypeYMM), pointer :: t(:)
integer :: s
integer :: i
real, pointer :: slice(:)
do i=LBOUND(f, DIM=1),UBOUND(f, DIM=1)
t(i).v(s) = f(i)
end do
slice(LBOUND(f, DIM=1):UBOUND(f, DIM=1)) => t(LBOUND(f, DIM=1))%v(s::4)
f => slice
end subroutine CopyToYMM_1D
[/fortran]
Jim Dempsey
- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
Ah, thanks a lot. This is kind of obvious, but I'm still surprised that the default behavior is to start all indices from 1.
- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
It's because you can point to an array section, including a discontiguous section. What other choice could be made there? The same rule applies to passing an array to a deferred-shape array dummy argument.
- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
And Steve could have added that arrays can be declared:
real :: foo(-123:456)
Jim Dempsey
- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
Dino R. wrote:
Ah, thanks a lot. This is kind of obvious, but I'm still surprised that the default behavior is to start all indices from 1.
To do otherwise puts a big burden on the compiler that is better suited in the hands of the programmer. Its also the reason I deal with a lot of code that resorts to [fortran]function func(u,v,w,ib,ie,jb,je,kb,ke)
integer :: ib,ie,jb,je,kb,ke
real, dimension(ib:ie) :: u
real, dimension(jb,je) :: v
real, dimension(kb:ke) :: w
[/fortran]
- Marquer comme nouveau
- Marquer
- S'abonner
- Sourdine
- S'abonner au fil RSS
- Surligner
- Imprimer
- Signaler un contenu inapproprié
Since Fortran pointers/allocatables contain information about the upper and lower limits of indices, I mainly use them to obtain summation indices. Thus if I pass a pointer, it may look like this:
SUBROUTINE (a)
INTEGER, POINTER, DIMENSION(:) :: a
INTEGER :: i
DO i = LBOUND(a,1), UBOUND(a,1)
a(i) = ...
END DO
END SUBROUTINE
On the CONTIGUOUS-attribute: I didn't specify it anywhere, but all my arrays are actually contiguous. Does it make sense to explicitly specify it everywhere? Or will the Compiler know that a pointer array, pointing at an allocated array is contiguous if i specify a contiguous range of indices?
- S'abonner au fil RSS
- Marquer le sujet comme nouveau
- Marquer le sujet comme lu
- Placer ce Sujet en tête de liste pour l'utilisateur actuel
- Marquer
- S'abonner
- Page imprimable