@@ -186,3 +186,95 @@ program demo_simps_weights
186186! 64.0
187187end program demo_simps_weights
188188```
189+
190+ ## ` gauss_legendre ` - Gauss-Legendre quadrature (a.k.a. Gaussian quadrature) nodes and weights
191+
192+ ### Status
193+
194+ Experimental
195+
196+ ### Description
197+
198+ Computes Gauss-Legendre quadrature (also known as simply Gaussian quadrature) nodes and weights,
199+ for any ` N ` (number of nodes).
200+ Using the nodes ` x ` and weights ` w ` , you can compute the integral of some function ` f ` as follows:
201+ ` integral = sum(f(x) * w) ` .
202+
203+ Only double precision is supported - if lower precision is required, you must do the appropriate conversion yourself.
204+ Accuracy has been validated up to N=64 by comparing computed results to tablulated values known to be accurate to machine precision
205+ (maximum difference from those values is 2 epsilon).
206+
207+ ### Syntax
208+
209+ ` subroutine [[stdlib_quadrature(module):gauss_legendre(interface)]] (x, w[, interval]) `
210+
211+ ### Arguments
212+
213+ ` x ` : Shall be a rank-one array of type ` real(real64) ` . It is an * output* argument, representing the quadrature nodes.
214+
215+ ` w ` : Shall be a rank-one array of type ` real(real64) ` , with the same dimension as ` x ` .
216+ It is an * output* argument, representing the quadrature weights.
217+
218+ ` interval ` : (Optional) Shall be a two-element array of type ` real(real64) ` .
219+ If present, the nodes and weigts are calculated for integration from ` interval(1) ` to ` interval(2) ` .
220+ If not specified, the default integral is -1 to 1.
221+
222+ ### Example
223+
224+ ``` fortran
225+ program integrate
226+ use iso_fortran_env, dp => real64
227+ implicit none
228+
229+ integer, parameter :: N = 6
230+ real(dp), dimension(N) :: x,w
231+ call gauss_legendre(x,w)
232+ print *, "integral of x**2 from -1 to 1 is", sum(x**2 * w)
233+ end program
234+ ```
235+
236+ ## ` gauss_legendre_lobatto ` - Gauss-Legendre-Lobatto quadrature nodes and weights
237+
238+ ### Status
239+
240+ Experimental
241+
242+ ### Description
243+
244+ Computes Gauss-Legendre-Lobatto quadrature nodes and weights,
245+ for any ` N ` (number of nodes).
246+ Using the nodes ` x ` and weights ` w ` , you can compute the integral of some function ` f ` as follows:
247+ ` integral = sum(f(x) * w) ` .
248+
249+ Only double precision is supported - if lower precision is required, you must do the appropriate conversion yourself.
250+ Accuracy has been validated up to N=64 by comparing computed results to tablulated values known to be accurate to machine precision
251+ (maximum difference from those values is 2 epsilon).
252+
253+ ### Syntax
254+
255+ ` subroutine [[stdlib_quadrature(module):gauss_legendre_lobatto(interface)]] (x, w[, interval]) `
256+
257+ ### Arguments
258+
259+ ` x ` : Shall be a rank-one array of type ` real(real64) ` . It is an * output* argument, representing the quadrature nodes.
260+
261+ ` w ` : Shall be a rank-one array of type ` real(real64) ` , with the same dimension as ` x ` .
262+ It is an * output* argument, representing the quadrature weights.
263+
264+ ` interval ` : (Optional) Shall be a two-element array of type ` real(real64) ` .
265+ If present, the nodes and weigts are calculated for integration from ` interval(1) ` to ` interval(2) ` .
266+ If not specified, the default integral is -1 to 1.
267+
268+ ### Example
269+
270+ ``` fortran
271+ program integrate
272+ use iso_fortran_env, dp => real64
273+ implicit none
274+
275+ integer, parameter :: N = 6
276+ real(dp), dimension(N) :: x,w
277+ call gauss_legendre_lobatto(x,w)
278+ print *, "integral of x**2 from -1 to 1 is", sum(x**2 * w)
279+ end program
280+ ```
0 commit comments