Skip to content

Commit

Permalink
Merge branch 'fortran-lang:master' into sparse
Browse files Browse the repository at this point in the history
  • Loading branch information
jalvesz authored May 27, 2024
2 parents 23be647 + 718ac3a commit 1d9dabc
Show file tree
Hide file tree
Showing 30 changed files with 2,499 additions and 193 deletions.
1 change: 1 addition & 0 deletions doc/specs/index.md
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ This is an index/directory of the specifications (specs) for each new module/fea
- [ansi](./stdlib_ansi.html) - Terminal color and style escape sequences
- [array](./stdlib_array.html) - Procedures for index manipulation and array handling
- [ascii](./stdlib_ascii.html) - Procedures for handling ASCII characters
- [constants](./stdlib_constants.html) - Constants
- [bitsets](./stdlib_bitsets.html) - Bitset data types and procedures
- [error](./stdlib_error.html) - Catching and handling errors
- [hash](./stdlib_hash_procedures.html) - Hashing integer
Expand Down
78 changes: 78 additions & 0 deletions doc/specs/stdlib_constants.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,78 @@
---
title: constants
---

[TOC]

## Introduction


The [[stdlib_constants]] module provides mathematical constants and the most common physical constants.

**Warning**: The names of the most common physical constants are kept short as they are inside a dedicated module.
Nonetheless, in case of overlapping names, they can always be renamed as following:

```fortran
use stdlib_constants, only: clight => c
```

## Codata

The [[stdlib_codata(module)]] module defines all codata (physical) constants as derived
type. The module is automatically generated with a simple
[parser written in Python](https://github.com/MilanSkocic/codata/)
The latest codata constants were released in 2022 by the [NIST](http://physics.nist.gov/constants)
All values for the codata constants are provided as double precision reals.
The names are quite long and can be aliased with shorter names.

The derived type [[stdlib_codata_type(module):codata_constant_type(type)]] defines:

* 4 members:

* `name` (string)
* `value` (double precision real)
* `uncertainty` (double precision real)
* `unit` (string)

* 2 type-bound procedures:

* `print`: to print the values of the constant members;
* `to_real`: to get the value or the uncertainty to the desired precision.

A module level interface [[stdlib_codata_type(module):to_real(interface)]] is
available for getting the constant value or uncertainty of a constant.

## `to_real` - Get the constant value or its uncertainty.

### Status

Experimental

### Description

Convert a [[stdlib_codata_type(module):codata_constant_type(type)]] to a `real` (at least `sp`, or `dp`) scalar.
**Warning**: Some constants cannot be converted to single precision `sp` reals due to the value of the exponents.

### Syntax

`r = ` [[stdlib_codata_type(module):to_real(interface)]] `(c, mold [, uncertainty])`

### Arguments

`c`: argument has `intent(in) ` and shall be of type [[stdlib_codata_type(module):codata_constant_type(type)]].

`mold`: argument has `intent(in)` and shall be of `real` type.
**Note**: The type of the `mold` argument defines the type of the result.

`uncertainty` (optional): argument has `intent(in)` and shall be of `logical` type.
It specifies if the uncertainty needs to be returned instead of the value. Default to `.false.`.

### Return value

Returns a scalar of `real` type which is either the value or the uncertainty of a codata constant.

## Example

```fortran
{!example/constants/example_constants.f90!}
```
2 changes: 1 addition & 1 deletion doc/specs/stdlib_linalg.md
Original file line number Diff line number Diff line change
Expand Up @@ -767,7 +767,7 @@ Result vector `x` returns the approximate solution that minimizes the 2-norm \(

`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.

`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.
`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.

`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.

Expand Down
24 changes: 12 additions & 12 deletions doc/specs/stdlib_sorting.md
Original file line number Diff line number Diff line change
Expand Up @@ -25,15 +25,15 @@ module's `string_type` type.
## Overview of the module

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

### The `int_size` parameter
### The `int_index` parameter

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

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

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

`iwork` (optional): shall be a rank one integer array of kind
`int_size`, and shall have at least `size(array)/2` elements. It
`int_index`, and shall have at least `size(array)/2` elements. It
is an `intent(out)` argument. It is intended to be used as "scratch"
memory for internal record keeping. If associated with an array in
static storage, its use can significantly reduce the stack memory
Expand Down Expand Up @@ -465,8 +465,8 @@ Sorting a related rank one array:
integer, intent(inout) :: a(:)
integer(int32), intent(inout) :: b(:) ! The same size as a
integer(int32), intent(out) :: work(:)
integer(int_size), intent(out) :: index(:)
integer(int_size), intent(out) :: iwork(:)
integer(int_index), intent(out) :: index(:)
integer(int_index), intent(out) :: iwork(:)
! Find the indices to sort a
call sort_index(a, index(1:size(a)),&
work(1:size(a)/2), iwork(1:size(a)/2))
Expand All @@ -483,8 +483,8 @@ Sorting a rank 2 array based on the data in a column
integer, intent(inout) :: array(:,:)
integer(int32), intent(in) :: column
integer(int32), intent(out) :: work(:)
integer(int_size), intent(out) :: index(:)
integer(int_size), intent(out) :: iwork(:)
integer(int_index), intent(out) :: index(:)
integer(int_index), intent(out) :: iwork(:)
integer, allocatable :: dummy(:)
integer :: i
allocate(dummy(size(array, dim=1)))
Expand All @@ -508,8 +508,8 @@ Sorting an array of a derived type based on the data in one component
type(a_type), intent(inout) :: a_data(:)
integer(int32), intent(inout) :: a(:)
integer(int32), intent(out) :: work(:)
integer(int_size), intent(out) :: index(:)
integer(int_size), intent(out) :: iwork(:)
integer(int_index), intent(out) :: index(:)
integer(int_index), intent(out) :: iwork(:)
! Extract a component of `a_data`
a(1:size(a_data)) = a_data(:) % a
! Find the indices to sort the component
Expand Down
1 change: 1 addition & 0 deletions example/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ endmacro(ADD_EXAMPLE)
add_subdirectory(array)
add_subdirectory(ascii)
add_subdirectory(bitsets)
add_subdirectory(constants)
add_subdirectory(error)
add_subdirectory(hashmaps)
add_subdirectory(hash_procedures)
Expand Down
1 change: 1 addition & 0 deletions example/constants/CMakeLists.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
ADD_EXAMPLE(constants)
25 changes: 25 additions & 0 deletions example/constants/example_constants.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
program example_constants
use stdlib_constants, only: c, pi=>PI_dp
use stdlib_codata, only: alpha=>ALPHA_PARTICLE_ELECTRON_MASS_RATIO
use stdlib_codata_type, only : to_real
use stdlib_kinds, only: dp, sp

! Use most common physical constants defined as double precision reals
print *, "speed of light in vacuum= ", c

! Use of mathematical constants such as PI
print *, "PI as double precision real= ", pi

! Use codata_constant type for evaluating the value to the desired precision
print *, "Value of alpha... evaluated to double precision=", alpha%to_real(1.0_dp)
print *, "Uncertainty of alpha... evaluated to double precision=", alpha%to_real(1.0_sp, .true.)
print *, "Value of alpha... evaluated to single precision=", alpha%to_real(1.0_sp)

! Convert a codata constant to a real
print *, "Value of the alpha... evaluated to double precision=", to_real(alpha, 1.0_dp)


! Print out codata constant attributes: name, value, uncertainty and unit
call alpha%print()

end program example_constants
23 changes: 13 additions & 10 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -6,14 +6,16 @@ set(fppFiles
stdlib_bitsets.fypp
stdlib_bitsets_64.fypp
stdlib_bitsets_large.fypp
stdlib_hash_32bit.fypp
stdlib_codata_type.fypp
stdlib_constants.fypp
stdlib_hash_32bit.fypp
stdlib_hash_32bit_fnv.fypp
stdlib_hash_32bit_nm.fypp
stdlib_hash_32bit_water.fypp
stdlib_hash_64bit.fypp
stdlib_hash_64bit_fnv.fypp
stdlib_hash_64bit_pengy.fypp
stdlib_hash_64bit_spookyv2.fypp
stdlib_hash_32bit_nm.fypp
stdlib_hash_32bit_water.fypp
stdlib_hash_64bit.fypp
stdlib_hash_64bit_fnv.fypp
stdlib_hash_64bit_pengy.fypp
stdlib_hash_64bit_spookyv2.fypp
stdlib_io.fypp
stdlib_io_npy.fypp
stdlib_io_npy_load.fypp
Expand All @@ -25,9 +27,9 @@ set(fppFiles
stdlib_linalg_outer_product.fypp
stdlib_linalg_kronecker.fypp
stdlib_linalg_cross_product.fypp
stdlib_linalg_solve.fypp
stdlib_linalg_solve.fypp
stdlib_linalg_determinant.fypp
stdlib_linalg_state.fypp
stdlib_linalg_state.fypp
stdlib_optval.fypp
stdlib_selection.fypp
stdlib_sorting.fypp
Expand Down Expand Up @@ -71,7 +73,7 @@ set(fppFiles
stdlib_version.fypp
)

# Preprocessed files to contain preprocessor directives -> .F90
# Preprocessed files to contain preprocessor directives -> .F90
set(cppFiles
stdlib_linalg_constants.fypp
stdlib_linalg_blas.fypp
Expand Down Expand Up @@ -100,6 +102,7 @@ set(SRC
stdlib_ansi_operator.f90
stdlib_ansi_to_string.f90
stdlib_array.f90
stdlib_codata.f90
stdlib_error.f90
stdlib_hashmap_wrappers.f90
stdlib_hashmaps.f90
Expand Down
Loading

0 comments on commit 1d9dabc

Please sign in to comment.