Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Multiblock Plot3d Problem

Status
Not open for further replies.

minger88

Technical User
Nov 16, 2006
7
US
Hello, I have a seemingly simple problem that I cannot solve. I am trying to read in a multiblock plot3D formatted file, and given a block number, write out a single block plot3D formatted file for just that block. It seems like it should be rather easy, but I am having problems. My code is below.

I am reading in a 27 block file, and all of the blocks show up fine up to block number 10. From there, many of the blocks do not display correctly.

Code:
SUBROUTINE get_grid_data(blockid,filename,X,Y,Z,dims)

INTEGER          ,INTENT(IN)                               :: blockid
CHARACTER(LEN=20),INTENT(IN)                               :: filename
INTEGER          ,INTENT(OUT),DIMENSION(3)                 :: dims
REAL             ,INTENT(OUT),DIMENSION(:,:,:),ALLOCATABLE :: X,Y,Z

!! local variables
INTEGER                               :: i,j,k,m,nblocks,imax,jmax,kmax
INTEGER,DIMENSION(:),ALLOCATABLE      :: ni,nj,nk
REAL                                  :: mach,alpha,reyn,time
REAL,DIMENSION(:,:,:,:,:),ALLOCATABLE :: temp

OPEN(20,file=filename,form='formatted')
READ(20,*) nblocks
ALLOCATE(ni(nblocks),nj(nblocks),nk(nblocks) )
READ(20,*) (ni(m),nj(m),nk(m), m=1,nblocks)
imax = MAXVAL(ni)
jmax = MAXVAL(nj)
kmax = MAXVAL(nk)
ALLOCATE(temp(imax,jmax,kmax,3,nblocks))
DO m=1,nblocks
  READ(20,*) (((temp(i,j,k,1,m),i=1,ni(m)),j=1,nj(m)),k=1,nk(m)),&
             (((temp(i,j,k,2,m),i=1,ni(m)),j=1,nj(m)),k=1,nk(m)),&
             (((temp(i,j,k,3,m),i=1,ni(m)),j=1,nj(m)),k=1,nk(m))
END DO

dims(1) = ni(blockid)
dims(2) = nj(blockid)
dims(3) = nk(blockid)

ALLOCATE(X(ni(blockid),nj(blockid),nk(blockid)))
ALLOCATE(Y(ni(blockid),nj(blockid),nk(blockid)))
ALLOCATE(Z(ni(blockid),nj(blockid),nk(blockid)))
DO i=1,ni(blockid)
  DO j=1,nj(blockid)
    DO k=1,nj(blockid)
      X(i,j,k) = temp(i,j,k,1,blockid)
      Y(i,j,k) = temp(i,j,k,2,blockid)
      Z(i,j,k) = temp(i,j,k,3,blockid)
    END DO
  END DO
END DO

CLOSE(20)

OPEN(21,file='in_sub_tester.x',form='formatted')
write(21,*) '1'
write(21,*) ni(blockid),nj(blockid),nk(blockid)
write(21,*) x,y,z
close(21)

DEALLOCATE(ni,nj,nk,temp)

END SUBROUTINE get_grid_data
 
Is the input data OK? You're reading the data in free format. Have 2 numbers run into each other and are being read as one number?

Is there line length limit on the input? For instance, does it truncate after column 80 and your data stretches to column 255.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top