function runge_antideriv ( x ) !*****************************************************************************80 ! !! runge_antideriv() evaluates the antiderivative of the Runge function. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 23 March 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real ( kind = rk8 ) x: the argument of the function. ! ! Output: ! ! real ( kind = rk8 ) runge_antideriv: the value of the antiderivative. ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) real ( kind = rk8 ) runge_antideriv real ( kind = rk8 ) x runge_antideriv = atan ( 5.0D+00 * x ) / 5.0D+00 return end function runge_deriv ( x ) !*****************************************************************************80 ! !! runge_deriv() evaluates the derivative of the Runge function. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 23 March 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real ( kind = rk8 ) x: the argument of the function. ! ! Output: ! ! real ( kind = rk8 ) runge_deriv: the value of the derivative. ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) real ( kind = rk8 ) runge_deriv real ( kind = rk8 ) x runge_deriv = - 50.0D+00 * x / ( 1.0D+00 + 25.0D+00 * x * x )**2 return end function runge_deriv2 ( x ) !*****************************************************************************80 ! !! runge_deriv2() evaluates the second derivative of the Runge function. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 23 March 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real ( kind = rk8 ) x: the argument of the function. ! ! Output: ! ! real ( kind = rk8 ) runge_deriv2, the value of the second derivative. ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) real ( kind = rk8 ) runge_deriv2 real ( kind = rk8 ) u real ( kind = rk8 ) up real ( kind = rk8 ) v real ( kind = rk8 ) vp real ( kind = rk8 ) x u = - 50.0D+00 * x up = - 50.0D+00 v = ( 1.0D+00 + 25.0D+00 * x * x )**2 vp = 2.0D+00 * ( 1.0D+00 + 25.0D+00 * x * x ) * ( 50.0D+00 * x ) runge_deriv2 = ( up * v - u * vp ) / v**2 return end function runge_fun ( x ) !*****************************************************************************80 ! !! runge_fun() evaluates the Runge function. ! ! Discussion: ! ! This function causes a breakdown for ! polynomial interpolation over equally spaced nodes in [-1,+1]. ! ! Runge originally considered the function 1/(1+x^2) over the ! interval [-5,+5]. For convenience, a rescaled version is considered ! over the interval [-1,+1]. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 23 March 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real ( kind = rk8 ) x: the argument of the function. ! ! Output: ! ! real ( kind = rk8 ) runge_fun: the value of the function. ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) real ( kind = rk8 ) runge_fun real ( kind = rk8 ) x runge_fun = 1.0D+00 / ( 1.0D+00 + 25.0D+00 * x * x ) return end function runge_power_series ( x, n ) !*****************************************************************************80 ! !! runge_power_series() evaluates a power series for the Runge function. ! ! Discussion: ! ! The Runge function considered here has the form ! f(x) = 1 / ( 1 + 25x^2 ) ! ! The power series is 1 - (5x)^2 + (5x)^4 - (5x)^6 + (5x)^8 - (5x)^10 ... ! ! The power series is only well defined in the open interval ! -1/5 < x < 1/5 ! where successive terms gradually go to zero. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 25 March 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real x: the argument of the function. ! ! integer n: the number of terms to be computed. ! ! Output: ! ! real value: the value of the function. ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) integer i integer n real ( kind = rk8 ) runge_power_series real ( kind = rk8 ) term real ( kind = rk8 ) value real ( kind = rk8 ) x value = 0.0D+00 term = 1.0D+00 do i = 1, n value = value + term term = - term * ( 5.0D+00 * x )**2 end do runge_power_series = value return end