subroutine standing_wave_exact ( x, t, c, u, ut, utt, ux, uxx ) !*****************************************************************************80 ! !! standing_wave_exact() evaluates an exact solution of the 1D wave equation. ! ! Discussion: ! ! d^2u/dt^2 = c^2 d^2u/dx^2 ! u[x,t] = sin(x) * cos(c*t) ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 April 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real x, t: the position and time. ! ! real c: the wave speed. ! ! Output: ! ! real u, ut, utt, ux, uxx: the values of the exact solution, its time ! derivative, and its first and second spatial derivatives at (x,t). ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) real ( kind = rk8 ) c real ( kind = rk8 ) t real ( kind = rk8 ) u real ( kind = rk8 ) ut real ( kind = rk8 ) utt real ( kind = rk8 ) ux real ( kind = rk8 ) uxx real ( kind = rk8 ) x u = sin ( x ) * cos ( c * t ) ut = - c * sin ( x ) * sin ( c * t ) utt = - c**2 * sin ( x ) * cos ( c * t ) ux = cos ( x ) * cos ( c * t ) uxx = - sin ( x ) * cos ( c * t ) return end subroutine standing_wave_parameters ( c_in, xmin_in, xmax_in, t0_in, & tstop_in, c_out, xmin_out, xmax_out, t0_out, tstop_out ) !*****************************************************************************80 ! !! standing_wave_parameters() returns parameters for the standing wave equation. ! ! Discussion: ! ! d^2u/dt^2 = c^2 d^2u/dx^2 ! u[x,t] = sin(x) * cos(c*t) ! ! If input values are specified, this resets the default parameters. ! Otherwise, the output will be the current defaults. ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 April 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real c_in: the wave speed. ! ! real xmin_in, xmax_in: the left and right interval endpoints. ! ! real t0_in: the initial time. ! ! real tstop_in: the final time. ! ! Output: ! ! real c_out: the wave speed. ! ! real xmin_out, xmax_out: the left and right interval endpoints. ! ! real t0_out: the initial time. ! ! real tstop_out: the final time. ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) real ( kind = rk8 ), save :: c_default = 0.2D+00 real ( kind = rk8 ), optional :: c_in real ( kind = rk8 ), optional :: c_out real ( kind = rk8 ), save :: t0_default = 0.0D+00 real ( kind = rk8 ), optional :: t0_in real ( kind = rk8 ), optional :: t0_out real ( kind = rk8 ), save :: tstop_default = 5.0D+00 real ( kind = rk8 ), optional :: tstop_in real ( kind = rk8 ), optional :: tstop_out real ( kind = rk8 ), save :: xmax_default = +1.0D+00 real ( kind = rk8 ), optional :: xmax_in real ( kind = rk8 ), optional :: xmax_out real ( kind = rk8 ), save :: xmin_default = -1.0D+00 real ( kind = rk8 ), optional :: xmin_in real ( kind = rk8 ), optional :: xmin_out ! ! New values, if supplied on input, overwrite the current values. ! if ( present ( c_in ) ) then c_default = c_in end if if ( present ( xmin_in ) ) then xmin_default = xmin_in end if if ( present ( xmax_in ) ) then xmax_default = xmax_in end if if ( present ( t0_in ) ) then t0_default = t0_in end if if ( present ( tstop_in ) ) then tstop_default = tstop_in end if ! ! Return values. ! c_out = c_default xmin_out = xmin_default xmax_out = xmax_default t0_out = t0_default tstop_out = tstop_default return end subroutine standing_wave_residual ( x, t, c, r ) !*****************************************************************************80 ! !! standing_wave_residual() computes the residual of the standing wave equation. ! ! Discussion: ! ! d^2u/dt^2 = c^2 d^2u/dx^2 ! u[x,t] = sin(x) * cos(c*t) ! ! Licensing: ! ! This code is distributed under the MIT license. ! ! Modified: ! ! 05 April 2025 ! ! Author: ! ! John Burkardt ! ! Input: ! ! real X, T: the position and time where the solution is evaluated. ! ! real c: the wave speed. ! ! Output: ! ! real R: the residual at that time and position. ! implicit none integer, parameter :: rk8 = kind ( 1.0D+00 ) real ( kind = rk8 ) c real ( kind = rk8 ) r real ( kind = rk8 ) t real ( kind = rk8 ) u real ( kind = rk8 ) ut real ( kind = rk8 ) utt real ( kind = rk8 ) ux real ( kind = rk8 ) uxx real ( kind = rk8 ) x call standing_wave_exact ( x, t, c, u, ut, utt, ux, uxx ) r = utt - c**2 * uxx return end