mirror of https://gitlab.com/QEF/q-e.git
69 lines
3.1 KiB
Fortran
69 lines
3.1 KiB
Fortran
!
|
|
! Copyright (C) 2002-2004 Quantum ESPRESSO group
|
|
! This file is distributed under the terms of the
|
|
! GNU General Public License. See the file `License'
|
|
! in the root directory of the present distribution,
|
|
! or http://www.gnu.org/copyleft/gpl.txt .
|
|
!
|
|
!------------------------------------------------------------------------------!
|
|
MODULE kinds
|
|
!------------------------------------------------------------------------------!
|
|
!! kind definitions.
|
|
!
|
|
IMPLICIT NONE
|
|
SAVE
|
|
!
|
|
INTEGER, PARAMETER :: DP = selected_real_kind(14,200)
|
|
INTEGER, PARAMETER :: sgl = selected_real_kind(6,30)
|
|
INTEGER, PARAMETER :: i4b = selected_int_kind(9)
|
|
INTEGER, PARAMETER :: i8b = selected_int_kind(18)
|
|
TYPE :: offload_kind_cpu ! no offload (CPU compilation and execution)
|
|
END TYPE
|
|
TYPE :: offload_kind_acc ! CUF/OpenACC offload (NVIDIA GPU hardware and software stack)
|
|
END TYPE
|
|
TYPE :: offload_kind_omp ! OpenMP5 offload (Intel and AMD GPU hardware and software stack)
|
|
END TYPE
|
|
PRIVATE
|
|
PUBLIC :: i4b, i8b, sgl, DP, print_kind_info
|
|
PUBLIC :: offload_kind_cpu, offload_kind_acc, offload_kind_omp
|
|
!
|
|
!------------------------------------------------------------------------------!
|
|
CONTAINS
|
|
!------------------------------------------------------------------------------!
|
|
!
|
|
SUBROUTINE print_kind_info (stdout)
|
|
!--------------------------------------------------------------------------!
|
|
!! Print information about the used data types.
|
|
!
|
|
IMPLICIT NONE
|
|
INTEGER, INTENT(IN) :: stdout
|
|
!
|
|
WRITE(stdout,'(/,T2,A)') 'DATA TYPE INFORMATION:'
|
|
!
|
|
WRITE(stdout,'(/,T2,A,T78,A,2(/,T2,A,T75,I6),3(/,T2,A,T67,E14.8))') &
|
|
'REAL: Data type name:', 'DP', ' Kind value:', kind(0.0_DP), &
|
|
' Precision:', precision(0.0_DP), &
|
|
' Smallest nonnegligible quantity relative to 1:', &
|
|
epsilon(0.0_DP), ' Smallest positive number:', tiny(0.0_DP), &
|
|
' Largest representable number:', huge(0.0_DP)
|
|
WRITE(stdout,'(/,T2,A,T78,A,2(/,T2,A,T75,I6),3(/,T2,A,T67,E14.8))') &
|
|
' Data type name:', 'sgl', ' Kind value:', kind(0.0_sgl), &
|
|
' Precision:', precision(0.0_sgl), &
|
|
' Smallest nonnegligible quantity relative to 1:', &
|
|
epsilon(0.0_sgl), ' Smallest positive number:', tiny(0.0_sgl), &
|
|
' Largest representable number:', huge(0.0_sgl)
|
|
WRITE(stdout,'(/,T2,A,T72,A,4(/,T2,A,T61,I20))') &
|
|
'INTEGER: Data type name:', '(default)', ' Kind value:', &
|
|
kind(0), ' Bit size:', bit_size(0), &
|
|
' Largest representable number:', huge(0)
|
|
WRITE(stdout,'(/,T2,A,T72,A,/,T2,A,T75,I6,/)') 'LOGICAL: Data type name:', &
|
|
'(default)', ' Kind value:', kind(.TRUE.)
|
|
WRITE(stdout,'(/,T2,A,T72,A,/,T2,A,T75,I6,/)') &
|
|
'CHARACTER: Data type name:', '(default)', ' Kind value:', &
|
|
kind('C')
|
|
!
|
|
END SUBROUTINE print_kind_info
|
|
!------------------------------------------------------------------------------!
|
|
END MODULE kinds
|
|
!------------------------------------------------------------------------------!
|