(git:374b731)
Loading...
Searching...
No Matches
kinds.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Defines the basic variable types
10!> \note
11!> Data type definitions; tested on:
12!> - IBM AIX xlf90
13!> - SGI IRIX f90
14!> - CRAY T3E f90
15!> - DEC ALPHA f90
16!> - NAG_F90
17!> - SUN
18!> - HITACHI
19!> \par History
20!> Adapted for CP2K by JGH
21!> \author Matthias Krack
22! **************************************************************************************************
23MODULE kinds
24
25 IMPLICIT NONE
26
27 PRIVATE
32
33 INTEGER, PARAMETER :: sp = selected_real_kind(6, 30)
34 INTEGER, PARAMETER :: dp = selected_real_kind(14, 200)
35 ! we rely on this (libraries) but do not check this
36 INTEGER, PARAMETER :: dp_size = 8, &
37 int_size = bit_size(0)/8, &
38 sp_size = 4
39
40 INTEGER, PARAMETER :: real_4 = selected_real_kind(6, 30)
41 INTEGER, PARAMETER :: real_8 = selected_real_kind(14, 200)
42 INTEGER, PARAMETER :: real_4_size = 4
43 INTEGER, PARAMETER :: real_8_size = 8
44
45 INTEGER, PARAMETER :: int_1 = selected_int_kind(2)
46 INTEGER, PARAMETER :: int_1_size = bit_size(int(0, int_1))/8
47
48 INTEGER, PARAMETER :: int_2 = selected_int_kind(4)
49 INTEGER, PARAMETER :: int_2_size = bit_size(int(0, int_2))/8
50
51 INTEGER, PARAMETER :: int_4 = selected_int_kind(5)
52 INTEGER, PARAMETER :: int_4_size = bit_size(int(0, int_4))/8
53
54 INTEGER, PARAMETER :: int_8 = selected_int_kind(10)
55 INTEGER, PARAMETER :: int_8_size = bit_size(int(0, int_8))/8
56
57 INTEGER, PARAMETER :: default_string_length = 80
58 INTEGER, PARAMETER :: default_path_length = 1024
59 INTEGER, PARAMETER :: max_line_length = 2*default_path_length
60 CHARACTER(LEN=1), PARAMETER, PUBLIC :: default_blank_character(2) = (/" ", char(9)/)
61
62CONTAINS
63
64! **************************************************************************************************
65!> \brief Print informations about the used data types.
66!> \param iw ...
67!> \par History
68!> Adapted by JGH for Cp2k
69!> \author Matthias Krack
70! **************************************************************************************************
71 SUBROUTINE print_kind_info(iw)
72
73 INTEGER, INTENT(IN) :: iw
74
75 WRITE (iw, '( /, T2, A )') 'DATA TYPE INFORMATION:'
76
77 WRITE (iw, '( /,T2,A,T79,A,2(/,T2,A,T75,I6),3(/,T2,A,T67,E14.8) )') &
78 'REAL: Data type name:', 'dp', ' Kind value:', kind(0.0_dp), &
79 ' Precision:', precision(0.0_dp), &
80 ' Smallest non-negligible quantity relative to 1:', &
81 epsilon(0.0_dp), &
82 ' Smallest positive number:', tiny(0.0_dp), &
83 ' Largest representable number:', huge(0.0_dp)
84 WRITE (iw, '( /,T2,A,T79,A,2(/,T2,A,T75,I6),3(/,T2,A,T67,E14.8) )') &
85 ' Data type name:', 'sp', ' Kind value:', kind(0.0_sp), &
86 ' Precision:', precision(0.0_sp), &
87 ' Smallest non-negligible quantity relative to 1:', &
88 epsilon(0.0_sp), &
89 ' Smallest positive number:', tiny(0.0_sp), &
90 ' Largest representable number:', huge(0.0_sp)
91 WRITE (iw, '( /,T2,A,T72,A,4(/,T2,A,T61,I20) )') &
92 'INTEGER: Data type name:', '(default)', ' Kind value:', &
93 kind(0), &
94 ' Bit size:', bit_size(0), &
95 ' Largest representable number:', huge(0)
96 WRITE (iw, '( /,T2,A,T72,A,/,T2,A,T75,I6,/ )') &
97 'LOGICAL: Data type name:', '(default)', &
98 ' Kind value:', kind(.true.)
99 WRITE (iw, '( /,T2,A,T72,A,/,T2,A,T75,I6,/ )') &
100 'CHARACTER: Data type name:', '(default)', &
101 ' Kind value:', kind('C')
102
103 END SUBROUTINE print_kind_info
104
105END MODULE kinds
106
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public max_line_length
Definition kinds.F:59
character(len=1), dimension(2), parameter, public default_blank_character
Definition kinds.F:60
integer, parameter, public int_8
Definition kinds.F:54
integer, parameter, public dp_size
Definition kinds.F:36
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public int_4_size
Definition kinds.F:52
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public int_1_size
Definition kinds.F:46
integer, parameter, public sp_size
Definition kinds.F:36
integer, parameter, public real_8_size
Definition kinds.F:43
integer, parameter, public int_8_size
Definition kinds.F:55
integer, parameter, public real_4_size
Definition kinds.F:42
integer, parameter, public real_4
Definition kinds.F:40
integer, parameter, public int_2_size
Definition kinds.F:49
integer, parameter, public int_size
Definition kinds.F:36
integer, parameter, public int_1
Definition kinds.F:45
integer, parameter, public default_path_length
Definition kinds.F:58
integer, parameter, public sp
Definition kinds.F:33
integer, parameter, public real_8
Definition kinds.F:41
subroutine, public print_kind_info(iw)
Print informations about the used data types.
Definition kinds.F:72
integer, parameter, public int_4
Definition kinds.F:51