! !################################################################## !################################################################## !###### ###### !###### SUBROUTINE WIRFRM ###### !###### ###### !###### Developed by ###### !###### Center for Analysis and Prediction of Storms ###### !###### University of Oklahoma ###### !###### ###### !################################################################## !################################################################## !SUBROUTINE wirfrm(a,nx,ist,iend,ny,jst,jend,nz,kst,kend, & 3 valiso, slab) ! !----------------------------------------------------------------------- ! ! PURPOSE: ! ! Use NCARgraphyic routinue "isosrf" to generate 3-D wirefrm-plot. ! !----------------------------------------------------------------------- ! ! AUTHOR: Ming Xue ! 3/21/1992 ! ! MODIFICATION HISTORY: ! ! 9/1/94 (Y. Lu) ! Cleaned up documentation ! !----------------------------------------------------------------------- ! ! Argument list: ! ! a 3-D array of data that defines the iso-valued surface. ! nx first dimension of a ! ist index of first i grid point to be used. ! iend index of last i grid point to be used. ! ! ny second dimension of a ! jst index of first j grid point to be used. ! jend index of last j grid point to be used. ! ! nz third dimension of a ! kst index of first k grid point to be used. ! kend index of last k grid point to be used. ! ! valiso the iso-value used to define the surface. ! slab a working space for internal storage. It is larger that ! (max(nx,ny,nz)+2)*2 ! !----------------------------------------------------------------------- ! IMPLICIT NONE INTEGER :: nx,ny,nz ! Number of grid points in 3 directions INTEGER :: ist,iend,jst,jend,kst,kend ! indexes of grid points in 3 directions INTEGER :: iflag,muvw REAL :: a(nx,ny,nz) ! 3-D array of data that defines ! the iso-valued surface REAL :: valiso ! the iso-value used to define the surface ! !----------------------------------------------------------------------- ! ! Working arrays used for the wrieframe plotting. ! !----------------------------------------------------------------------- ! REAL :: eye(3) REAL :: slab( nx+1, nx+1) ! !@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ ! ! Beginning of executable code... ! !@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@ ! muvw=MAX(nx,ny,nz)+2 !----------------------------------------------------------------------- ! ! EYE: The position of the eye in 3-D space. A tentative choice ! can be (5.0*nx, 3.5*ny, 2.0*nz) ! !----------------------------------------------------------------------- eye(1)= 1.0*nx eye(2)=-1.0*ny eye(3)= 1.5*nz ! !----------------------------------------------------------------------- ! ! IFLAG: Define the types of lines to be drawn. ! =1, lines of constant z only ! =2, lines of constant y only ! =3, lines of constant z and y. ! =4, lines of constant x only ! =5, lines of constant x and z. ! =6, lines of constant x and y. ! =7, or more, lines of constant x, y and z. ! The sign of IFLAG determines what is inside and what is outside ! the isosurface. ! IFLAG >0, values greater than valiso are assumed inside the ! surface. ! IFLAG <0, values less than valiso are assumed inside the surface. ! !----------------------------------------------------------------------- ! iflag=4 IF( valiso < 0.0) iflag = -iflag CALL xnwfrm CALL xnwpic CALL gselnt(0) CALL isosrf & (a(ist,jst,kst),nx,iend-ist+1,ny,jend-jst+1, & kend-kst+1, & eye,muvw,slab,valiso,iflag) CALL xnwfrm RETURN END SUBROUTINE wirfrm