You cannot select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

30 lines
738 B
Fortran

SUBROUTINE FRMNODQ(X1,Y1,X2,Y2,X3,Y3,X4,Y4,NPTS1,NPTS2)
USE BLK1MOD
! INCLUDE 'BLK1.COM'
! X1,X2,X3,X4 AND Y1,Y2,Y3,Y4 are vertices of quad
! NPTS1 and NPTS2 are the nominal number of elements on each side
! Work along first side AND backwards along second line
DO N=1,NPTS1-1
RATIO=FLOAT(N)/FLOAT(NPTS1)
X12=X1+RATIO*(X2-X1)
Y12=Y1+RATIO*(Y2-Y1)
X43=X4+RATIO*(X3-X4)
Y43=Y4+RATIO*(Y3-Y4)
! Now get interior points
DO M=1,NPTS2-1
RATIO=FLOAT(M)/FLOAT(NPTS2)
XNEW=X12+RATIO*(X43-X12)
YNEW=Y12+RATIO*(Y43-Y12)
CALL DEFNOD(XNEW,YNEW)
ENDDO
ENDDO
RETURN
END