- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi all,
I know this topic has been covered in other topics....but i cannot figure out how to implement the previously given suggestions.
here is my code trying to create an array of pointers which (so far) is a missing feature in fortran.
   program pointers
	    !
	    implicit none
	    !
	    integer i,n
	    real, target :: values(9)
   ! f is the array of pointers, contained in a structure
	    type dataptr
	        real, pointer :: f(:,:) 
	    end type
    !
	    ! define my structures:
	    type(dataptr), allocatable, dimension(:) :: dats
	    !--------------------------
 ! fill the target with some random values:
	    do i =1,9
	        values(i)=i 
	    enddo
	! allocate the pointers:
	    do i =1,3
	        allocate(dats(i)%f(i,i+1))  ! some random sizes here
	    enddo
	    
	    dats(3)%f(1,1) => values(2) !  apparently this element by element association is not allowed  <---
!------------------------------
end program pointers
I get the following error upon compilation:
error #8524: The syntax of this data pointer assignment is incorrect: either 'bound spec' or 'bound remapping' is expected in this context.
any help is welcome, thank you.
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
dats(3)%f is a pointer to an array. You can do a pointer assignment to an array. It is not an array of individual element pointers. Instead of => you may just want = to assign a value. If you really do want a second level of pointers you will have to create a new type with a pointer array component, allocate each one individually and then do the pointer assignment.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
thanks for your quick reply.
Steve Lionel (Intel) wrote:But it's declared as an array...i'm confused...
dats(3)%f is a pointer to an array.
Steve Lionel (Intel) wrote:Yes, i got it.
You can do a pointer assignment to an array. It is not an array of individual element pointers. Instead of => you may just want = to assign a value.
Steve Lionel (Intel) wrote:this is exactly what I thought i was doing with my code...I'm confused then. can you show me an example? thanks
... you will have to create a new type with a pointer array component, allocate each one individually and then do the pointer assignment.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I don't understand what you're trying to accomplish. How will you be using these pointers? You never allocated dats itself.
Here's code that works - I am not certain it does what you want, but you should get the idea.
program pointers
    !
    implicit none
    !
    integer i,n
    real, target :: values(9)
   ! f is the array of pointers, contained in a structure
    type dataptr
        real, pointer :: val
    end type
    type arrayofpointers
        type(dataptr), allocatable :: f(:,:) 
    end type
    !
    ! define my structures:
    type(arrayofpointers), allocatable, dimension(:) :: dats
    !--------------------------
 ! fill the target with some random values:
    do i =1,9
        values(i)=i 
    enddo
 ! allocate dats 
    allocate (dats(3))
! allocate the pointers:
    do i =1,3
        allocate(dats(i)%f(i,i+1))  ! some random sizes here
    enddo
    
    dats(3)%f(1,1)%val => values(2) ! 
    !------------------------------
    end program pointers
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel (Intel) wrote:attached is a picture of what i would like to do, where pointers ranks are decided at compile time, sizes of pointers and targets at runtime:
I don't understand what you're trying to accomplish. How will you be using these pointers? You never allocated dats itself.
here is your code with 2 targets (a_values and b_values).
   program pointers
    !
    implicit none
    !
    integer i,j,k, ngrids,ntot,flat_position
    integer, allocatable, dimension(:) :: nx,ny
    real, allocatable, dimension(:), target :: a_values,b_values
   
   ! f is the array of pointers, contained in a structure
    type dataptr
        real, pointer :: val
    end type
    
    type aop
        type(dataptr), allocatable :: fa(:,:) 
        type(dataptr), allocatable :: fb(:,:) 
    end type
    !
    ! define my structures:
    type(aop), allocatable, dimension(:) :: dats
    !--------------------------
    ngrids=3
    
    allocate(nx(ngrids),ny(ngrids))  
    ! allocate structures
    allocate (dats(ngrids))
    !--------------------------   
    nx=(/3, 2, 5/)
    ny=(/3, 4, 2/)  
    ! allocate the pointers:
    do k=1,ngrids
        allocate( dats(k)%fa(nx(k),ny(k)) )
        allocate( dats(k)%fb(nx(k),ny(k)) )
    enddo
    !--------------------------    
    ntot=dot_product(nx,ny)
    allocate(a_values(ntot),b_values(ntot))
    
 ! fill the target with some random values:
    do i =1,ntot
        a_values(i)=i 
        b_values(i)=i*2 
    enddo
! associate pointers
    do k=1,ngrids
        do j=1,ny(k)
            do i=1,nx(k)
                flat_position =  j + (i-1)*ny(k)
                dats(k)%fa(i,j)%val => a_values(flat_position)  
                dats(k)%fb(i,j)%val => b_values(flat_position) 
            enddo
        enddo
    enddo
 ! check if association works   
    write(*,*) dats(3)%fa(1,1)%val, 1+(1-1)*ny(3)
    write(*,*) dats(2)%fb(2,1)%val, (1+(2-1)*ny(2))*2
    write(*,*) dats(1)%fb(2,3)%val, (3+(2-1)*ny(1))*2
    
    pause
    end program pointers
Your code works just fine, but i bet there is a better way to accomplish that, right?
thanks
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Which is used more extensively by your program? The flat array or the nD arrays?
In the event of nD's, can you use a flat array of pointers?
Edit: flip the pointer and target. This would also clean up the code to access each.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
jimdempseyatthecove wrote:
Which is used more extensively by your program? The flat array or the nD arrays?
In the event of nD's, can you use a flat array of pointers?
Edit: flip the pointer and target. This would also clean up the code to access each.
Jim Dempsey
I'm not sure i got what you mean. I use ONLY the array of pointers to the flat vector. the reason for that is that the array of pointers yield the geometrical features (they map the physical space).
about the flip: how do i do that? it sounds interesting!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In your diagram, you have three multi-rank arrays (colors), referencing three sections of a flat array. If the linear addresses in the flat representations represent linear addresses within the multi-rank arrays, then you do not need any of the pointer funny business.
You can choose to either allocate the flat array and use a single nD pointer for each of the array sections, or allocate each nD array, then use three linear pointers. This assumes (requires) that your layout of the multi-dimension subscripts are chosen correctly
! pointers.f90 program pointers implicit none real, allocatable, target :: a(:,:,:), b(:,:), c(:,:) real, pointer :: pa(:), pb(:), pc(:) integer :: i,j,k real :: fill allocate(a(3,4,5),b(6,7),c(8,9)) fill = 0.0 do k=lbound(a,dim=3),ubound(a, dim=3) ! or 1,5 do j = lbound(a, dim=2),ubound(a, dim=2) ! or 1,4 do i = lbound(a, dim=1),ubound(a, dim=1) ! or 1,3 a(i,j,k) = fill fill = fill + 1.0 end do end do end do do j = lbound(b, dim=2),ubound(b, dim=2) ! or 1,7 do i = lbound(b, dim=1),ubound(b, dim=1) ! or 1,6 b(i,j) = fill fill = fill + 1.0 end do end do do j = lbound(c, dim=2),ubound(c, dim=2) ! or 1,9 do i = lbound(c, dim=1),ubound(c, dim=1) ! or 1,8 c(i,j) = fill fill = fill + 1.0 end do end do pa(1:size(a)) => a pb(1:size(b)) => b pc(1:size(c)) => c print *,a print *,pa print * print *,b print *,pb print * print *,c print *,pc print * end program pointers
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi all....shame on me: i just realized that i don't really need any pointer to do what i need to do..
Indeed i need to allocate N groups of rank(D), size(S) arrays, each group has its own S but N is known only at run time. In other words, the only feature known at compile time is the rank (D). Here is an example with D=2, N=3 (N=ngrids), and N different sizes (S).
    program pointers
    !
    implicit none
    !
    integer i,j,k, ngrids
    integer, allocatable, dimension(:) :: nx,ny
    
    type griddata
        real, allocatable :: fa(:,:) 
        real, allocatable :: fb(:,:) 
    end type
    !
    ! define my structures:
    type(griddata), allocatable, dimension(:) :: dats
    !--------------------------
    ngrids=3
    
    allocate(nx(ngrids),ny(ngrids))  
    allocate (dats(ngrids))
    !--------------------------   
    nx=(/3, 2, 5/)
    ny=(/3, 4, 2/)  
    ! allocate the pointers:
    do k=1,ngrids
        allocate( dats(k)%fa(nx(k),ny(k)) )
        allocate( dats(k)%fb(nx(k),ny(k)) )
        do j=1,ny(k)
            do i=1,nx(k) 
                dats(k)%fa(i,j)=i+j
                dats(k)%fb(i,j)=2.0*dats(k)%fa(i,j)
            enddo
        enddo
    enddo
    
    write(*,*) dats(3)%fa(2,1) 
    write(*,*) dats(2)%fa(2,1)
    write(*,*) dats(2)%fb(2,1)
    
    pause
    end program pointers
 
					
				
				
			
		
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page
