We read every piece of feedback, and take your input very seriously.
To see all available qualifiers, see our documentation.
There was an error while loading. Please reload this page.
1 parent b3c3102 commit 9929cdbCopy full SHA for 9929cdb
doc/specs/index.md
@@ -15,6 +15,7 @@ This is and index/directory of the specifications (specs) for each new module/fe
15
- [bitsets](./stdlib_bitsets.html) - Bitset data types and procedures
16
- [error](./stdlib_error.html) - Catching and handling errors
17
- [IO](./stdlib_io.html) - Input/output helper & convenience
18
+ - [kinds](./stdlib_kinds.html) - Kind parameters
19
- [linalg](./stdlib_linalg.html) - Linear Algebra
20
- [logger](./stdlib_logger.html) - Runtime logging system
21
- [optval](./stdlib_optval.html) - Fallback value for optional arguments
@@ -25,10 +26,6 @@ This is and index/directory of the specifications (specs) for each new module/fe
25
26
- [string\_type](./stdlib_string_type.html) - Basic string support
27
- [strings](./stdlib_strings.html) - String handling and manipulation routines
28
-## Missing specs
29
-
30
- - [kinds](https://github.com/fortran-lang/stdlib/blob/master/src/stdlib_kinds.f90)
31
32
## Released/Stable Features & Modules
33
34
- (None yet)
doc/specs/stdlib_kinds.md
@@ -0,0 +1,59 @@
1
+---
2
+title: kinds
3
4
+
5
+# The `stdlib_kinds` module
6
7
+[TOC]
8
9
+## Introduction
10
11
+The `stdlib_kinds` module provides kind parameters for the Fortran intrinsic data types,
12
+*integer*, *logical*, *real*, and *complex*.
13
14
+## Constants provided by `stdlib_kinds`
+### `sp`
+Alias for intrinsic named constant `real32` imported from `iso_fortran_env`.
22
+### `dp`
23
24
+Alias for intrinsic named constant `real64` imported from `iso_fortran_env`.
+### `qp`
+Alias for intrinsic named constant `real128` imported from `iso_fortran_env`.
+### `int8`
+Reexported intrinsic named constant `int8` from `iso_fortran_env`.
35
36
37
+### `int16`
38
39
+Reexported intrinsic named constant `int16` from `iso_fortran_env`.
40
41
42
+### `int32`
43
44
+Reexported intrinsic named constant `int32` from `iso_fortran_env`.
45
46
47
+### `int64`
48
49
+Reexported intrinsic named constant `int64` from `iso_fortran_env`.
50
51
52
+### `lk`
53
54
+Kind parameter of the default logical data type.
55
56
57
+### `c_bool`
58
59
+Reexported intrinsic named constant `c_bool` from `iso_c_binding`.
src/common.fypp
@@ -27,6 +27,15 @@
#! Collected (kind, type) tuples for integer types
#:set INT_KINDS_TYPES = list(zip(INT_KINDS, INT_TYPES))
+#! Logical kinds to be considered during templating
+#:set LOG_KINDS = ["lk", "c_bool"]
+#! Logical types to be considered during templating
+#:set LOG_TYPES = ["logical({})".format(k) for k in LOG_KINDS]
+#! Collected (kind, type) tuples for logical types
+#:set LOG_KINDS_TYPES = list(zip(LOG_KINDS, LOG_TYPES))
#! Derived type string_type
#:set STRING_KINDS = ["string_type"]
src/stdlib_ascii.fypp
@@ -5,7 +5,7 @@
!>
!> The specification of this module is available [here](../page/specs/stdlib_ascii.html).
module stdlib_ascii
- use stdlib_kinds, only : int8, int16, int32, int64
+ use stdlib_kinds, only : int8, int16, int32, int64, lk, c_bool
implicit none
private
@@ -28,6 +28,8 @@ module stdlib_ascii
interface to_string
#:for kind in INT_KINDS
module procedure :: to_string_integer_${kind}$
+ #:endfor
+ #:for kind in LOG_KINDS
module procedure :: to_string_logical_${kind}$
#:endfor
end interface to_string
@@ -396,7 +398,7 @@ contains
396
398
end function to_string_integer_${kind}$
397
399
400
- #:for kind in INT_KINDS
401
402
!> Represent an logical of kind ${kind}$ as character sequence
403
pure function to_string_logical_${kind}$(val) result(string)
404
integer, parameter :: ik = ${kind}$
src/stdlib_kinds.f90
@@ -2,10 +2,13 @@ module stdlib_kinds
!! version: experimental
use iso_fortran_env, only: sp=>real32, dp=>real64, qp=>real128
use iso_fortran_env, only: int8, int16, int32, int64
+use iso_c_binding, only: c_bool
! If we decide later to use iso_c_binding instead of iso_fortran_env:
!use iso_c_binding, only: sp=>c_float, dp=>c_double, qp=>c_float128
!use iso_c_binding, only: int8=>c_int8_t, int16=>c_int16_t, int32=>c_int32_t, int64=>c_int64_t
-public sp, dp, qp, int8, int16, int32, int64
+public sp, dp, qp, int8, int16, int32, int64, lk, c_bool
+integer, parameter :: lk = kind(.true.)
end module stdlib_kinds
src/stdlib_string_type.fypp
@@ -15,7 +15,7 @@
module stdlib_string_type
use stdlib_ascii, only: to_lower_ => to_lower, to_upper_ => to_upper, &
& to_title_ => to_title, to_sentence_ => to_sentence, reverse_ => reverse, to_string
@@ -47,6 +47,8 @@ module stdlib_string_type
module procedure :: new_string
module procedure :: new_string_from_integer_${kind}$
module procedure :: new_string_from_logical_${kind}$
end interface string_type
@@ -373,7 +375,7 @@ contains
373
375
end function new_string_from_integer_${kind}$
374
376
377
378
379
!> Constructor for new string instances from a logical of kind ${kind}$.
380
elemental function new_string_from_logical_${kind}$(val) result(new)
381
logical(${kind}$), intent(in) :: val
src/tests/ascii/test_ascii.f90
@@ -8,7 +8,7 @@ program test_ascii
is_control, is_punctuation, is_graphical, is_printable, is_ascii, &
to_lower, to_upper, to_title, to_sentence, reverse, LF, TAB, NUL, DEL, &
to_string
@@ -676,11 +676,11 @@ subroutine test_to_string
676
write(flc, '(g0)') .false.
677
call check(to_string(.false.) == trim(flc))
678
679
- write(flc, '(g0)') .true._int8
680
- call check(to_string(.true._int8) == trim(flc))
+ write(flc, '(g0)') .true._c_bool
+ call check(to_string(.true._c_bool) == trim(flc))
681
682
- write(flc, '(g0)') .false._int64
683
- call check(to_string(.false._int64) == trim(flc))
+ write(flc, '(g0)') .false._lk
+ call check(to_string(.false._lk) == trim(flc))
684
end subroutine test_to_string
685
686
end program test_ascii
src/tests/string/test_string_assignment.f90
@@ -1,7 +1,7 @@
! SPDX-Identifier: MIT
module test_string_assignment
use stdlib_error, only : check
use stdlib_string_type, only : string_type, assignment(=), operator(==), len
@@ -52,11 +52,11 @@ subroutine test_char_value
call check(string_type(.false.) == trim(flc))
- write(flc, '(g0)') .false._int8
- call check(string_type(.false._int8) == trim(flc))
+ write(flc, '(g0)') .false._c_bool
+ call check(string_type(.false._c_bool) == trim(flc))
- write(flc, '(g0)') .true._int64
- call check(string_type(.true._int64) == trim(flc))
+ write(flc, '(g0)') .true._lk
+ call check(string_type(.true._lk) == trim(flc))
60
end subroutine test_char_value
61
62
end module test_string_assignment
0 commit comments