SUBROUTINE Trapezoidal (npt, xpt, wht, a, b) USE Numeric_Kinds_Module USE Precision_Module USE FileUnits_Module IMPLICIT NONE INTEGER(KIND=IW_Kind) :: i, npt REAL(KIND=WP_Kind) :: xpt(npt), wht(npt), a, b, h !--------------------------------------------------------------------- ! ! purpose ! supplies the Trapezoidal abscissas and weights ! ! description of parameters ! npt-number of points desired ! xpt-resultant array containing the gauss legenedre abscissas. ! wht-resultant array containing the gauss legenedre weights !--------------------------------------------------------------------- h=(b-a)/(npt-1) DO i = 1, npt xpt(i)=a+(i-1)*h wht(i)=h ENDDO wht(1)=h/Two wht(npt)=h/Two IF(ABS(SUM(wht)-(Npt-1)*h).gt.Ten*REpsilon)THEN WRITE(Out_Unit,*)'Error in Trapezoidal weights' WRITE(Out_Unit,*)ABS(SUM(wht)) WRITE(Out_Unit,*)(Npt-1)*h !STOP 'Error in Trapezoidal' ENDIF RETURN END SUBROUTINE Trapezoidal