SUBROUTINE graf (start, delta, psi, npts, filename, nds, ider) USE Numeric_Kinds_Module USE FileUnits_Module USE CommonInfo_Module !----------------------------------------------------------------------- ! This routine was written by G. A. Parker ! IF you find an error or have an improvement please send a messge to ! parker@phyast.nhn.uoknor.edu !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER (len=*) :: filename INTEGER :: npts, ip, nds, nstart, ider REAL (dp) :: start, delta, psi (nds:npts) REAL (sp) :: xval, pltf !----------------------------------------------------------------------- ! outputs results for subsequent plotting. !----------------------------------------------------------------------- OPEN (unit = 39, file = TRIM(filename)) IF (nds.eq.1) THEN nstart = 1 ELSEIF (nds.eq.0) THEN nstart = - npts ELSE STOP 'graf' ENDIF DO 1 ip = nstart, npts xval = start + (ip - 1) * delta IF (ip.lt.0) THEN pltf = psi ( - ip) * ( - 1) **ider ELSE pltf = psi (ip) ENDIF WRITE (39, 2) xval, pltf 1 END DO CLOSE (unit = 39) 2 FORMAT(1x,6(1pe14.6,',')) RETURN END SUBROUTINE graf