-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathhfbtho_utilities.f90
executable file
·122 lines (115 loc) · 5.59 KB
/
hfbtho_utilities.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
!***********************************************************************
!
! Copyright (c) 2016, Lawrence Livermore National Security, LLC.
! Produced at the Lawrence Livermore National
! Laboratory.
! Written by Nicolas Schunck, [email protected]
!
! LLNL-CODE-728299 All rights reserved.
! LLNL-CODE-573953 All rights reserved.
!
! Copyright 2017, R. Navarro Perez, N. Schunck, R. Lasseri, C. Zhang,
! J. Sarich
! Copyright 2012, M.V. Stoitsov, N. Schunck, M. Kortelainen, H.A. Nam,
! N. Michel, J. Sarich, S. Wild
! Copyright 2005, M.V. Stoitsov, J. Dobaczewski, W. Nazarewicz, P.Ring
!
! This file is part of HFBTHO.
!
! HFBTHO is free software: you can redistribute it and/or modify it
! under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! HFBTHO is distributed in the hope that it will be useful, but
! WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with HFBTHO. If not, see <http://www.gnu.org/licenses/>.
!
! OUR NOTICE AND TERMS AND CONDITIONS OF THE GNU GENERAL PUBLIC
! LICENSE
!
! Our Preamble Notice
!
! A. This notice is required to be provided under our contract
! with the U.S. Department of Energy (DOE). This work was
! produced at the Lawrence Livermore National Laboratory under
! Contract No. DE-AC52-07NA27344 with the DOE.
! B. Neither the United States Government nor Lawrence Livermore
! National Security, LLC nor any of their employees, makes any
! warranty, express or implied, or assumes any liability or
! responsibility for the accuracy, completeness, or usefulness
! of any information, apparatus, product, or process disclosed,
! or represents that its use would not infringe privately-owned
! rights.
! C. Also, reference herein to any specific commercial products,
! process, or services by trade name, trademark, manufacturer
! or otherwise does not necessarily constitute or imply its
! endorsement, recommendation, or favoring by the United States
! Government or Lawrence Livermore National Security, LLC. The
! views and opinions of authors expressed herein do not
! necessarily state or reflect those of the United States
! Government or Lawrence Livermore National Security, LLC, and
! shall not be used for advertising or product endorsement
! purposes.
!
! The precise terms and conditions for copying, distribution and
! modification are contained in the file COPYING.
!
!***********************************************************************
! ==================================================================== !
! !
! BASIC UTILITIES PACKAGE !
! !
! ==================================================================== !
!----------------------------------------------------------------------
!> This module defines basic data types, constants and file units.
!----------------------------------------------------------------------
! Subroutines: - get_CPU_time(subname,is)
!----------------------------------------------------------------------
Module HFBTHO_utilities
Implicit None
Integer, Parameter, Public :: ipr=Kind(1) ! to set the precision of the DFT solver
Integer, Parameter, Public :: pr =Kind(1.0d0) ! to set the precision of the DFT solver
! I/O
Integer, Public :: lout = 6, lfile = 7
! Global numbers
Real(pr), Parameter :: zero=0.0_pr,half= 0.5_pr,one=1.0_pr,two =2.0_pr,three=3.0_pr, &
four=4.0_pr,five= 5.0_pr,six=6.0_pr,seven=7.0_pr,eight=8.0_pr, &
nine=9.0_pr,ten =10.0_pr
! Whole global numbers pp#
Real(pr), Parameter :: pp12=12.0_pr,pp16=16.0_pr,pp15=15.0_pr,pp20=20.0_pr, &
pp24=24.0_pr,pp27=27.0_pr,pp32=32.0_pr,pp64=64.0_pr, &
pp40=40.0_pr
! Fractional global numbers p#
Real(pr), Parameter :: p12=one/two, p13=one/three, p14=one/four, p23=two/three, &
p43=four/three,p32=three/two, p34=three/four,p53=five/three,&
p18=one/eight, p38=three/eight,p59=five/nine, p52=five/two, &
p54=five/four, p74=seven/four
Contains
!=======================================================================
!
!=======================================================================
Subroutine get_CPU_time(subname,is)
Implicit None
Integer, Intent(in) :: is
Character*(*), Intent(in) :: subname
Character(Len=15) :: subprint
Integer(ipr), Save :: t1,t2,countrate,countmax
!
If(is.Eq.0) Then
Call system_clock(t1,countrate,countmax)
Else
Call system_clock(t2,countrate,countmax)
Write(subprint,'(a15)') subname
Write(*,'(a,a15,a,F16.6)') ' Time in seconds -> ',subprint,':',(t2-t1)/real(countrate,kind=pr)
End If
!
End Subroutine get_CPU_time
!=======================================================================
!
!=======================================================================
End Module HFBTHO_utilities