Skip to content

Commit 9f51efe

Browse files
committed
Merge branch 'svd' of github.com:perazz/stdlib into svd
2 parents bdffb4f + 173f1ee commit 9f51efe

40 files changed

+2823
-317
lines changed

Diff for: CHANGELOG.md

+50
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,53 @@
1+
# Version 0.6.1
2+
3+
Full release notes available at [v0.6.1] tag.
4+
5+
[v0.6.1]: https://github.com/fortran-lang/stdlib/releases/tag/v0.6.1
6+
7+
Changes to existing scripts and modules
8+
- changes in module `stdlib_linalg_lapack`
9+
- Renamed variable for compiler compliance
10+
[#812](https://github.com/fortran-lang/stdlib/pull/812)
11+
- change of the format in some example programs
12+
[#813](https://github.com/fortran-lang/stdlib/pull/813)
13+
14+
15+
# Version 0.6.0
16+
17+
Full release notes available at [v0.6.0] tag.
18+
19+
[v0.6.0]: https://github.com/fortran-lang/stdlib/releases/tag/v0.6.0
20+
21+
22+
- new script `fypp_deployment.py` to support `fpm` in combination with `fypp`
23+
files
24+
[#802](https://github.com/fortran-lang/stdlib/pull/802)
25+
26+
27+
Changes to existing scripts and modules
28+
- change in module `stdlib_hashmap_wrappers`
29+
- addition of `int32` hashmap key type
30+
[#778](https://github.com/fortran-lang/stdlib/pull/778)
31+
- changes in module `stdlib_linalg`
32+
- addition of the procedure `det` to compute determinants
33+
[#798](https://github.com/fortran-lang/stdlib/pull/798)
34+
- addition of the procedures `lstsq` and `lstsq_space`
35+
[#801](https://github.com/fortran-lang/stdlib/pull/801)
36+
[#809](https://github.com/fortran-lang/stdlib/pull/809)
37+
- addition of the procedures `solve` and `solve_lu`
38+
[#806](https://github.com/fortran-lang/stdlib/pull/806)
39+
- change in module `stdlib_linalg_blas`
40+
- addition of the documentation for `rotm` and `rotmg`
41+
[#795](https://github.com/fortran-lang/stdlib/pull/795)
42+
- use of macOS 12 in macOS CI
43+
[#807](https://github.com/fortran-lang/stdlib/pull/807)
44+
45+
46+
Changes to existing documentation
47+
- Improvement of the documentation `linalg`
48+
[#797](https://github.com/fortran-lang/stdlib/pull/797)
49+
50+
151
# Version 0.5.0
252

353
Full release notes available at [v0.5.0] tag.

Diff for: VERSION

+1-1
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
0.5.0
1+
0.6.1

Diff for: doc/specs/index.md

+1
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ This is an index/directory of the specifications (specs) for each new module/fea
1414
- [ansi](./stdlib_ansi.html) - Terminal color and style escape sequences
1515
- [array](./stdlib_array.html) - Procedures for index manipulation and array handling
1616
- [ascii](./stdlib_ascii.html) - Procedures for handling ASCII characters
17+
- [constants](./stdlib_constants.html) - Constants
1718
- [bitsets](./stdlib_bitsets.html) - Bitset data types and procedures
1819
- [error](./stdlib_error.html) - Catching and handling errors
1920
- [hash](./stdlib_hash_procedures.html) - Hashing integer

Diff for: doc/specs/stdlib_constants.md

+78
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
---
2+
title: constants
3+
---
4+
5+
[TOC]
6+
7+
## Introduction
8+
9+
10+
The [[stdlib_constants]] module provides mathematical constants and the most common physical constants.
11+
12+
**Warning**: The names of the most common physical constants are kept short as they are inside a dedicated module.
13+
Nonetheless, in case of overlapping names, they can always be renamed as following:
14+
15+
```fortran
16+
use stdlib_constants, only: clight => c
17+
```
18+
19+
## Codata
20+
21+
The [[stdlib_codata(module)]] module defines all codata (physical) constants as derived
22+
type. The module is automatically generated with a simple
23+
[parser written in Python](https://github.com/MilanSkocic/codata/)
24+
The latest codata constants were released in 2022 by the [NIST](http://physics.nist.gov/constants)
25+
All values for the codata constants are provided as double precision reals.
26+
The names are quite long and can be aliased with shorter names.
27+
28+
The derived type [[stdlib_codata_type(module):codata_constant_type(type)]] defines:
29+
30+
* 4 members:
31+
32+
* `name` (string)
33+
* `value` (double precision real)
34+
* `uncertainty` (double precision real)
35+
* `unit` (string)
36+
37+
* 2 type-bound procedures:
38+
39+
* `print`: to print the values of the constant members;
40+
* `to_real`: to get the value or the uncertainty to the desired precision.
41+
42+
A module level interface [[stdlib_codata_type(module):to_real(interface)]] is
43+
available for getting the constant value or uncertainty of a constant.
44+
45+
## `to_real` - Get the constant value or its uncertainty.
46+
47+
### Status
48+
49+
Experimental
50+
51+
### Description
52+
53+
Convert a [[stdlib_codata_type(module):codata_constant_type(type)]] to a `real` (at least `sp`, or `dp`) scalar.
54+
**Warning**: Some constants cannot be converted to single precision `sp` reals due to the value of the exponents.
55+
56+
### Syntax
57+
58+
`r = ` [[stdlib_codata_type(module):to_real(interface)]] `(c, mold [, uncertainty])`
59+
60+
### Arguments
61+
62+
`c`: argument has `intent(in) ` and shall be of type [[stdlib_codata_type(module):codata_constant_type(type)]].
63+
64+
`mold`: argument has `intent(in)` and shall be of `real` type.
65+
**Note**: The type of the `mold` argument defines the type of the result.
66+
67+
`uncertainty` (optional): argument has `intent(in)` and shall be of `logical` type.
68+
It specifies if the uncertainty needs to be returned instead of the value. Default to `.false.`.
69+
70+
### Return value
71+
72+
Returns a scalar of `real` type which is either the value or the uncertainty of a codata constant.
73+
74+
## Example
75+
76+
```fortran
77+
{!example/constants/example_constants.f90!}
78+
```

Diff for: doc/specs/stdlib_io.md

+5-1
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ Loads a rank-2 `array` from a text file.
1717

1818
### Syntax
1919

20-
`call ` [[stdlib_io(module):loadtxt(interface)]] `(filename, array [, skiprows] [, max_rows])`
20+
`call ` [[stdlib_io(module):loadtxt(interface)]] `(filename, array [, skiprows] [, max_rows] [, fmt])`
2121

2222
### Arguments
2323

@@ -29,6 +29,10 @@ Loads a rank-2 `array` from a text file.
2929

3030
`max_rows` (optional): Read `max_rows` lines of content after `skiprows` lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1.
3131

32+
`fmt` (optional): Fortran format specifier for the text read. Defaults to the write format for the data type. Setting fmt='*' will specify list directed read.
33+
34+
35+
3236
### Return value
3337

3438
Returns an allocated rank-2 `array` with the content of `filename`.

Diff for: doc/specs/stdlib_linalg.md

+1-1
Original file line numberDiff line numberDiff line change
@@ -767,7 +767,7 @@ Result vector `x` returns the approximate solution that minimizes the 2-norm \(
767767

768768
`b`: Shall be a rank-1 or rank-2 array of the same kind as `a`, containing one or more right-hand-side vector(s), each in its leading dimension. It is an `intent(in)` argument.
769769

770-
`x`: Shall be an array of same kind and rank as `b`, containing the solution(s) to the least squares system. It is an `intent(inout)` argument.
770+
`x`: Shall be an array of same kind and rank as `b`, and leading dimension of at least `n`, containing the solution(s) to the least squares system. It is an `intent(inout)` argument.
771771

772772
`real_storage` (optional): Shall be a `real` rank-1 array of the same kind `a`, providing working storage for the solver. It minimum size can be determined with a call to [[stdlib_linalg(module):lstsq_space(interface)]]. It is an `intent(inout)` argument.
773773

Diff for: doc/specs/stdlib_sorting.md

+12-12
Original file line numberDiff line numberDiff line change
@@ -25,15 +25,15 @@ module's `string_type` type.
2525
## Overview of the module
2626

2727
The module `stdlib_sorting` defines several public entities, one
28-
default integer parameter, `int_size`, and four overloaded
28+
default integer parameter, `int_index`, and four overloaded
2929
subroutines: `ORD_SORT`, `SORT`, `RADIX_SORT` and `SORT_INDEX`. The
3030
overloaded subroutines also each have several specific names for
3131
versions corresponding to different types of array arguments.
3232

33-
### The `int_size` parameter
33+
### The `int_index` parameter
3434

35-
The `int_size` parameter is used to specify the kind of integer used
36-
in indexing the various arrays. Currently the module sets `int_size`
35+
The `int_index` parameter is used to specify the kind of integer used
36+
in indexing the various arrays. Currently the module sets `int_index`
3737
to the value of `int64` from the `stdlib_kinds` module.
3838

3939
### The module subroutines
@@ -414,7 +414,7 @@ It is an `intent(inout)` argument. On input it
414414
will be an array whose sorting indices are to be determined. On return
415415
it will be the sorted array.
416416

417-
`index`: shall be a rank one integer array of kind `int_size` and of
417+
`index`: shall be a rank one integer array of kind `int_index` and of
418418
the size of `array`. It is an `intent(out)` argument. On return it
419419
shall have values that are the indices needed to sort the original
420420
array in the desired direction.
@@ -427,7 +427,7 @@ static storage, its use can significantly reduce the stack memory
427427
requirements for the code. Its contents on return are undefined.
428428

429429
`iwork` (optional): shall be a rank one integer array of kind
430-
`int_size`, and shall have at least `size(array)/2` elements. It
430+
`int_index`, and shall have at least `size(array)/2` elements. It
431431
is an `intent(out)` argument. It is intended to be used as "scratch"
432432
memory for internal record keeping. If associated with an array in
433433
static storage, its use can significantly reduce the stack memory
@@ -465,8 +465,8 @@ Sorting a related rank one array:
465465
integer, intent(inout) :: a(:)
466466
integer(int32), intent(inout) :: b(:) ! The same size as a
467467
integer(int32), intent(out) :: work(:)
468-
integer(int_size), intent(out) :: index(:)
469-
integer(int_size), intent(out) :: iwork(:)
468+
integer(int_index), intent(out) :: index(:)
469+
integer(int_index), intent(out) :: iwork(:)
470470
! Find the indices to sort a
471471
call sort_index(a, index(1:size(a)),&
472472
work(1:size(a)/2), iwork(1:size(a)/2))
@@ -483,8 +483,8 @@ Sorting a rank 2 array based on the data in a column
483483
integer, intent(inout) :: array(:,:)
484484
integer(int32), intent(in) :: column
485485
integer(int32), intent(out) :: work(:)
486-
integer(int_size), intent(out) :: index(:)
487-
integer(int_size), intent(out) :: iwork(:)
486+
integer(int_index), intent(out) :: index(:)
487+
integer(int_index), intent(out) :: iwork(:)
488488
integer, allocatable :: dummy(:)
489489
integer :: i
490490
allocate(dummy(size(array, dim=1)))
@@ -508,8 +508,8 @@ Sorting an array of a derived type based on the data in one component
508508
type(a_type), intent(inout) :: a_data(:)
509509
integer(int32), intent(inout) :: a(:)
510510
integer(int32), intent(out) :: work(:)
511-
integer(int_size), intent(out) :: index(:)
512-
integer(int_size), intent(out) :: iwork(:)
511+
integer(int_index), intent(out) :: index(:)
512+
integer(int_index), intent(out) :: iwork(:)
513513
! Extract a component of `a_data`
514514
a(1:size(a_data)) = a_data(:) % a
515515
! Find the indices to sort the component

Diff for: example/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ endmacro(ADD_EXAMPLE)
99
add_subdirectory(array)
1010
add_subdirectory(ascii)
1111
add_subdirectory(bitsets)
12+
add_subdirectory(constants)
1213
add_subdirectory(error)
1314
add_subdirectory(hashmaps)
1415
add_subdirectory(hash_procedures)

Diff for: example/constants/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
ADD_EXAMPLE(constants)

Diff for: example/constants/example_constants.f90

+25
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
program example_constants
2+
use stdlib_constants, only: c, pi=>PI_dp
3+
use stdlib_codata, only: alpha=>ALPHA_PARTICLE_ELECTRON_MASS_RATIO
4+
use stdlib_codata_type, only : to_real
5+
use stdlib_kinds, only: dp, sp
6+
7+
! Use most common physical constants defined as double precision reals
8+
print *, "speed of light in vacuum= ", c
9+
10+
! Use of mathematical constants such as PI
11+
print *, "PI as double precision real= ", pi
12+
13+
! Use codata_constant type for evaluating the value to the desired precision
14+
print *, "Value of alpha... evaluated to double precision=", alpha%to_real(1.0_dp)
15+
print *, "Uncertainty of alpha... evaluated to double precision=", alpha%to_real(1.0_sp, .true.)
16+
print *, "Value of alpha... evaluated to single precision=", alpha%to_real(1.0_sp)
17+
18+
! Convert a codata constant to a real
19+
print *, "Value of the alpha... evaluated to double precision=", to_real(alpha, 1.0_dp)
20+
21+
22+
! Print out codata constant attributes: name, value, uncertainty and unit
23+
call alpha%print()
24+
25+
end program example_constants

Diff for: example/io/example_loadtxt.f90

+3
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,7 @@ program example_loadtxt
33
implicit none
44
real, allocatable :: x(:, :)
55
call loadtxt('example.dat', x)
6+
7+
! Can also use list directed format if the default read fails.
8+
call loadtxt('example.dat', x, fmt='*')
69
end program example_loadtxt

Diff for: example/strings/example_ends_with.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_ends_with
22
use stdlib_strings, only: ends_with
33
implicit none
4-
print'(a)', ends_with("pattern", "ern") ! T
5-
print'(a)', ends_with("pattern", "pat") ! F
4+
print'(l1)', ends_with("pattern", "ern") ! T
5+
print'(l1)', ends_with("pattern", "pat") ! F
66
end program example_ends_with

Diff for: example/strings/example_starts_with.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_starts_with
22
use stdlib_strings, only: starts_with
33
implicit none
4-
print'(a)', starts_with("pattern", "pat") ! T
5-
print'(a)', starts_with("pattern", "ern") ! F
4+
print'(l1)', starts_with("pattern", "pat") ! T
5+
print'(l1)', starts_with("pattern", "ern") ! F
66
end program example_starts_with

Diff for: src/CMakeLists.txt

+12-9
Original file line numberDiff line numberDiff line change
@@ -6,14 +6,16 @@ set(fppFiles
66
stdlib_bitsets.fypp
77
stdlib_bitsets_64.fypp
88
stdlib_bitsets_large.fypp
9-
stdlib_hash_32bit.fypp
9+
stdlib_codata_type.fypp
10+
stdlib_constants.fypp
11+
stdlib_hash_32bit.fypp
1012
stdlib_hash_32bit_fnv.fypp
11-
stdlib_hash_32bit_nm.fypp
12-
stdlib_hash_32bit_water.fypp
13-
stdlib_hash_64bit.fypp
14-
stdlib_hash_64bit_fnv.fypp
15-
stdlib_hash_64bit_pengy.fypp
16-
stdlib_hash_64bit_spookyv2.fypp
13+
stdlib_hash_32bit_nm.fypp
14+
stdlib_hash_32bit_water.fypp
15+
stdlib_hash_64bit.fypp
16+
stdlib_hash_64bit_fnv.fypp
17+
stdlib_hash_64bit_pengy.fypp
18+
stdlib_hash_64bit_spookyv2.fypp
1719
stdlib_io.fypp
1820
stdlib_io_npy.fypp
1921
stdlib_io_npy_load.fypp
@@ -25,7 +27,7 @@ set(fppFiles
2527
stdlib_linalg_outer_product.fypp
2628
stdlib_linalg_kronecker.fypp
2729
stdlib_linalg_cross_product.fypp
28-
stdlib_linalg_solve.fypp
30+
stdlib_linalg_solve.fypp
2931
stdlib_linalg_determinant.fypp
3032
stdlib_linalg_state.fypp
3133
stdlib_linalg_svd.fypp
@@ -69,7 +71,7 @@ set(fppFiles
6971
stdlib_version.fypp
7072
)
7173

72-
# Preprocessed files to contain preprocessor directives -> .F90
74+
# Preprocessed files to contain preprocessor directives -> .F90
7375
set(cppFiles
7476
stdlib_linalg_constants.fypp
7577
stdlib_linalg_blas.fypp
@@ -98,6 +100,7 @@ set(SRC
98100
stdlib_ansi_operator.f90
99101
stdlib_ansi_to_string.f90
100102
stdlib_array.f90
103+
stdlib_codata.f90
101104
stdlib_error.f90
102105
stdlib_hashmap_wrappers.f90
103106
stdlib_hashmaps.f90

0 commit comments

Comments
 (0)