!! DUIVP !***PURPOSE Dummy routine for DBVSUP quick check. !***LIBRARY SLATEC !***TYPE DOUBLE PRECISION (UIVP-S, DUIVP-D) !***KEYWORDS QUICK CHECK !***AUTHOR Watts, H. A., (SNLA) !***DESCRIPTION ! ! This routine is never called; it is here to prevent loaders from ! complaining about undefined externals while testing DBVSUP. ! !***ROUTINES CALLED (NONE) !***REVISION HISTORY (YYMMDD) ! 750601 DATE WRITTEN ! 890618 REVISION DATE from Version 3.2 ! 891214 Prologue converted to Version 4.0 format. (BAB) ! 920401 Variables declaration and TYPE sections added. (WRB) !***END PROLOGUE DUIVP ! .. Scalar Arguments .. subroutine DUIVP (X, Y, YP) ! .. Array Arguments .. double precision X !***FIRST EXECUTABLE STATEMENT DUIVP double precision Y(*), YP(*) STOP end !! UIVP !***PURPOSE Dummy routine for BVSUP quick check. !***LIBRARY SLATEC !***TYPE SINGLE PRECISION (UIVP-S, DUIVP-D) !***KEYWORDS QUICK CHECK !***AUTHOR Watts, H. A., (SNLA) !***DESCRIPTION ! ! This routine is never called; it is here to prevent loaders from ! complaining about undefined externals while testing BVSUP. ! !***ROUTINES CALLED (NONE) !***REVISION HISTORY (YYMMDD) ! 750601 DATE WRITTEN ! 890618 REVISION DATE from Version 3.2 ! 891214 Prologue converted to Version 4.0 format. (BAB) ! 920401 Variables declaration and TYPE sections added. (WRB) !***END PROLOGUE UIVP ! .. Scalar Arguments .. subroutine UIVP (X, Y, YP) ! .. Array Arguments .. REAL X !***FIRST EXECUTABLE STATEMENT UIVP REAL Y(*), YP(*) STOP end subroutine UIVP !! DUVEC !***PURPOSE Dummy routine for DBVSUP quick check. !***LIBRARY SLATEC !***TYPE DOUBLE PRECISION (UVEC-S, DUVEC-D) !***KEYWORDS QUICK CHECK !***AUTHOR Watts, H. A., (SNLA) !***DESCRIPTION ! ! This routine is never called; it is here to prevent loaders from ! complaining about undefined externals while testing DBVSUP. ! !***ROUTINES CALLED (NONE) !***REVISION HISTORY (YYMMDD) ! 750601 DATE WRITTEN ! 890618 REVISION DATE from Version 3.2 ! 891214 Prologue converted to Version 4.0 format. (BAB) ! 920401 Variables declaration and TYPE sections added. (WRB) !***END PROLOGUE DUVEC ! .. Scalar Arguments .. subroutine DUVEC (X, Y, YP) ! .. Array Arguments .. double precision X !***FIRST EXECUTABLE STATEMENT DUVEC double precision Y(*), YP(*) STOP end !! UVEC !***PURPOSE Dummy routine for BVSUP quick check. !***LIBRARY SLATEC !***TYPE SINGLE PRECISION (UVEC-S, DUVEC-D) !***KEYWORDS QUICK CHECK !***AUTHOR Watts, H. A., (SNLA) !***DESCRIPTION ! ! This routine is never called; it is here to prevent loaders from ! complaining about undefined externals while testing BVSUP. ! !***ROUTINES CALLED (NONE) !***REVISION HISTORY (YYMMDD) ! 750601 DATE WRITTEN ! 890618 REVISION DATE from Version 3.2 ! 891214 Prologue converted to Version 4.0 format. (BAB) ! 920401 Variables declaration and TYPE sections added. (WRB) !***END PROLOGUE UVEC ! .. Scalar Arguments .. subroutine UVEC (X, Y, YP) ! .. Array Arguments .. REAL X !***FIRST EXECUTABLE STATEMENT UVEC REAL Y(*), YP(*) STOP end !! DFMAT !***PURPOSE Subsidiary to !***LIBRARY SLATEC !***AUTHOR (UNKNOWN) !***ROUTINES CALLED (NONE) !***COMMON BLOCKS DSAVEX !***REVISION HISTORY (YYMMDD) ! ?????? DATE WRITTEN ! 891214 Prologue converted to Version 4.0 format. (BAB) !***END PROLOGUE DFMAT subroutine DFMAT (X, Y, YP) double precision X,Y,YP,XSAVE,TERM,TANX dimension Y(*),YP(*) !***FIRST EXECUTABLE STATEMENT DFMAT COMMON /DSAVEX/ XSAVE, TERM YP(1) = Y(2) if ( X == XSAVE) GO TO 10 XSAVE=X TANX= TAN(X/57.2957795130823D0) TERM= 3.0D0/TANX+2.0D0*TANX 10 YP(2) = -TERM*Y(2)-0.7D0*Y(1) return end !! FMAT !***PURPOSE Subsidiary to !***LIBRARY SLATEC !***AUTHOR (UNKNOWN) !***ROUTINES CALLED (NONE) !***COMMON BLOCKS SAVEX !***REVISION HISTORY (YYMMDD) ! ?????? DATE WRITTEN ! 891214 Prologue converted to Version 4.0 format. (BAB) !***END PROLOGUE FMAT subroutine FMAT (X, Y, YP) dimension Y(*),YP(*) !***FIRST EXECUTABLE STATEMENT FMAT COMMON /SAVEX/ XSAVE, TERM YP(1) = Y(2) if ( X == XSAVE) GO TO 10 XSAVE=X TANX=TAN(X/57.2957795130823) TERM=3.0/TANX+2.0*TANX 10 YP(2) = -TERM*Y(2)-0.7*Y(1) return end !! DGVEC !***PURPOSE Subsidiary to !***LIBRARY SLATEC !***AUTHOR (UNKNOWN) !***ROUTINES CALLED (NONE) !***REVISION HISTORY (YYMMDD) ! ?????? DATE WRITTEN ! 891214 Prologue converted to Version 4.0 format. (BAB) !***END PROLOGUE DGVEC subroutine DGVEC (X, G) double precision X,G !***FIRST EXECUTABLE STATEMENT DGVEC dimension G(*) G(1) = 0.0D0 G(2) = 1.0D0+COS(X) return end subroutine DGVEC !! GVEC !***PURPOSE Subsidiary to !***LIBRARY SLATEC !***AUTHOR (UNKNOWN) !***ROUTINES CALLED (NONE) !***REVISION HISTORY (YYMMDD) ! ?????? DATE WRITTEN ! 891214 Prologue converted to Version 4.0 format. (BAB) !***END PROLOGUE GVEC subroutine GVEC (X, G) !***FIRST EXECUTABLE STATEMENT GVEC dimension G(*) G(1) = 0.0 G(2) = 1.0+COS(X) return end subroutine GVEC