Skip to content

Commit f1bc676

Browse files
authored
Merge branch 'master' into zoziha/feature/format_string
2 parents f155525 + 9fb85ff commit f1bc676

20 files changed

+1356
-171
lines changed

CMakeLists.txt

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -49,9 +49,7 @@ check_fortran_source_runs("i=0; error stop i; end" f18errorstop SRC_EXT f90)
4949
check_fortran_source_compiles("real, allocatable :: array(:, :, :, :, :, :, :, :, :, :); end" f03rank SRC_EXT f90)
5050
check_fortran_source_runs("use, intrinsic :: iso_fortran_env, only : real128; real(real128) :: x; x = x+1; end" f03real128)
5151

52-
if(DEFINED CMAKE_MAXIMUM_RANK)
53-
set(CMAKE_MAXIMUM_RANK ${CMAKE_MAXIMUM_RANK})
54-
endif()
52+
option(CMAKE_MAXIMUM_RANK "Maximum array rank for generated procedures" 4)
5553

5654
# --- find preprocessor
5755
find_program(FYPP fypp)

README.md

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -127,7 +127,8 @@ Important options are
127127
- `-G Ninja` to use the Ninja backend instead of the default Make backend. Other build backends are available with a similar syntax.
128128
- `-DCMAKE_INSTALL_PREFIX` is used to provide the install location for the library.
129129
- `-DCMAKE_MAXIMUM_RANK` the maximum array rank procedures should be generated for.
130-
The default is 15 for Fortran 2003 compliant compilers, otherwise 7 for compilers not supporting Fortran 2003 completely yet.
130+
The default value is chosen as 4.
131+
The maximum is 15 for Fortran 2003 compliant compilers, otherwise 7 for compilers not supporting Fortran 2003 completely yet.
131132
The minimum required rank to compile this project is 4.
132133
Compiling with maximum rank 15 can be resource intensive and requires at least 16 GB of memory to allow parallel compilation or 4 GB memory for sequential compilation.
133134
- `-DBUILD_SHARED_LIBS` set to `on` in case you want link your application dynamically against the standard library (default: `off`).

doc/specs/stdlib_linalg.md

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -168,3 +168,41 @@ program demo_trace
168168
print *, trace(A) ! 1 + 5 + 9
169169
end program demo_trace
170170
```
171+
172+
## `outer_product` - Computes the outer product of two vectors
173+
174+
### Status
175+
176+
Experimental
177+
178+
### Description
179+
180+
Computes the outer product of two vectors
181+
182+
### Syntax
183+
184+
`d = [[stdlib_linalg(module):outer_product(interface)]](u, v)`
185+
186+
### Arguments
187+
188+
`u`: Shall be a rank-1 array
189+
190+
`v`: Shall be a rank-1 array
191+
192+
### Return value
193+
194+
Returns a rank-2 array equal to `u v^T` (where `u, v` are considered column vectors). The shape of the returned array is `[size(u), size(v)]`.
195+
196+
### Example
197+
198+
```fortran
199+
program demo_outer_product
200+
use stdlib_linalg, only: outer_product
201+
implicit none
202+
real, allocatable :: A(:,:), u(:), v(:)
203+
u = [1., 2., 3. ]
204+
v = [3., 4.]
205+
A = outer_product(u,v)
206+
!A = reshape([3., 6., 9., 4., 8., 12.], [3,2])
207+
end program demo_outer_product
208+
```

doc/specs/stdlib_quadrature.md

Lines changed: 92 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -186,3 +186,95 @@ program demo_simps_weights
186186
! 64.0
187187
end 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

Comments
 (0)