38 atm,
bar,
bohr,
e_mass,
evolt,
femtoseconds,
joule,
kcalmol,
kelvin,
kjmol,
massunit, &
43#include "../base/base_uses.f90"
48 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
49 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'cp_units'
133 INTEGER :: n_kinds = -1
134 INTEGER,
DIMENSION(cp_unit_max_kinds):: kind_id = -1, unit_id = -1, power = -1
144 END TYPE cp_unit_p_type
151 TYPE(cp_unit_p_type),
DIMENSION(cp_ukind_max) :: units = cp_unit_p_type()
164 CHARACTER(len=*),
INTENT(in) :: string
166 CHARACTER(default_string_length) :: desc
167 CHARACTER(LEN=40) :: formatstr
168 CHARACTER(LEN=LEN(string)) :: unit_string
169 INTEGER :: i_high, i_low, i_unit, len_string, &
171 INTEGER,
DIMENSION(cp_unit_max_kinds) :: kind_id, power, unit_id
178 len_string = len(string)
181 DO WHILE (i_low < len_string)
182 IF (string(i_low:i_low) /=
' ')
EXIT
186 DO WHILE (i_high <= len_string)
187 IF (string(i_high:i_high) ==
' ' .OR. string(i_high:i_high) ==
'^' .OR. &
188 string(i_high:i_high) ==
'*' .OR. string(i_high:i_high) ==
'/')
EXIT
192 IF (i_high <= i_low .OR. i_low > len_string)
EXIT
195 cpabort(
"Maximum number of combined units exceeded")
199 unit_string = string(i_low:i_high - 1)
201 SELECT CASE (trim(unit_string))
202 CASE (
"INTERNAL_CP2K")
211 CASE (
"WAVENUMBER_E")
313 CASE (
"WAVENUMBER_T")
349 CASE (
"MN",
"MNEWTON")
359 CALL cp_abort(__location__, &
360 "au unit without specifying its kind not accepted, use "// &
361 "(au_e, au_f, au_t, au_temp, au_l, au_m, au_p, au_pot)")
363 cpabort(
"Unknown unit: "//string(i_low:i_high - 1))
365 power(i_unit) = next_power
368 DO WHILE (i_low <= len_string)
369 IF (string(i_low:i_low) /=
' ')
EXIT
373 DO WHILE (i_high <= len_string)
374 IF (string(i_high:i_high) ==
' ' .OR. string(i_high:i_high) ==
'^' .OR. &
375 string(i_high:i_high) ==
'*' .OR. string(i_high:i_high) ==
'/')
EXIT
378 IF (i_high < i_low .OR. i_low > len_string)
EXIT
380 IF (i_high <= len_string)
THEN
381 IF (string(i_low:i_high) ==
'^')
THEN
383 DO WHILE (i_low <= len_string)
384 IF (string(i_low:i_low) /=
' ')
EXIT
388 DO WHILE (i_high <= len_string)
389 SELECT CASE (string(i_high:i_high))
390 CASE (
'+',
'-',
'0',
'1',
'2',
'3',
'4',
'5',
'6',
'7',
'8',
'9')
396 IF (i_high <= i_low .OR. i_low > len_string)
THEN
397 cpabort(
"an integer number is expected after a '^'")
401 READ (string(i_low:i_high - 1), formatstr) &
403 power(i_unit) = power(i_unit)*next_power
406 DO WHILE (i_low < len_string)
407 IF (string(i_low:i_low) /=
' ')
EXIT
411 DO WHILE (i_high <= len_string)
412 IF (string(i_high:i_high) ==
' ' .OR. string(i_high:i_high) ==
'^' .OR. &
413 string(i_high:i_high) ==
'*' .OR. string(i_high:i_high) ==
'/')
EXIT
418 IF (i_low > len_string)
EXIT
420 IF (i_high <= len_string)
THEN
421 IF (string(i_low:i_high) ==
"*" .OR. string(i_low:i_high) ==
'/')
THEN
422 IF (string(i_low:i_high) ==
'/') next_power = -1
424 DO WHILE (i_low <= len_string)
425 IF (string(i_low:i_low) /=
' ')
EXIT
429 DO WHILE (i_high <= len_string)
430 IF (string(i_high:i_high) ==
' ' .OR. string(i_high:i_high) ==
'^' .OR. &
431 string(i_high:i_high) ==
'*' .OR. string(i_high:i_high) ==
'/')
EXIT
437 CALL cp_unit_create2(unit, kind_id=kind_id, unit_id=unit_id, &
452 SUBROUTINE cp_unit_create2(unit, kind_id, unit_id, power)
454 INTEGER,
DIMENSION(:),
INTENT(in) :: kind_id, unit_id
455 INTEGER,
DIMENSION(:),
INTENT(in),
OPTIONAL :: power
457 INTEGER :: i, j, max_kind, max_pos
462 unit%kind_id(1:
SIZE(kind_id)) = kind_id
464 unit%unit_id(1:
SIZE(unit_id)) = unit_id
466 IF (
PRESENT(power))
THEN
467 unit%power(1:
SIZE(power)) = power
468 unit%power(
SIZE(power) + 1:) = 0
469 DO i = 1,
SIZE(unit%power)
470 IF (unit%power(i) == 0)
THEN
476 DO i = 1,
SIZE(unit%power)
477 IF (unit%unit_id(i) /= 0)
THEN
488 DO i = 1,
SIZE(unit%kind_id)
491 max_kind = unit%kind_id(i)
494 DO j = i + 1,
SIZE(unit%kind_id)
495 IF (unit%kind_id(j) >= max_kind)
THEN
496 IF (unit%kind_id(j) /= 0 .AND. unit%kind_id(j) == max_kind .AND. &
497 unit%unit_id(j) == unit%unit_id(max_pos))
THEN
498 unit%power(max_pos) = unit%power(max_pos) + unit%power(j)
502 IF (unit%power(max_pos) == 0)
THEN
505 unit%power(max_pos) = 0
509 ELSE IF (unit%kind_id(j) > max_kind .OR. &
510 (unit%kind_id(j) == max_kind .AND. &
511 unit%unit_id(j) > unit%unit_id(max_pos)))
THEN
512 max_kind = unit%kind_id(j)
517 IF (.NOT. repeat)
EXIT
519 IF (max_kind /= 0) unit%n_kinds = unit%n_kinds + 1
521 IF (max_pos /= i)
THEN
522 unit%kind_id(max_pos) = unit%kind_id(i)
523 unit%kind_id(i) = max_kind
524 max_kind = unit%unit_id(max_pos)
525 unit%unit_id(max_pos) = unit%unit_id(i)
526 unit%unit_id(i) = max_kind
527 max_kind = unit%power(max_pos)
528 unit%power(max_pos) = unit%power(i)
529 unit%power(i) = max_kind
532 CALL cp_basic_unit_check(basic_kind=unit%kind_id(i), &
533 basic_unit=unit%unit_id(i))
535 END SUBROUTINE cp_unit_create2
557 SUBROUTINE cp_basic_unit_check(basic_kind, basic_unit)
558 INTEGER,
INTENT(in) :: basic_kind, basic_unit
560 SELECT CASE (basic_kind)
562 SELECT CASE (basic_unit)
565 cpabort(
"unknown undef unit:"//trim(
cp_to_string(basic_unit)))
568 SELECT CASE (basic_unit)
573 cpabort(
"unknown energy unit:"//trim(
cp_to_string(basic_unit)))
576 SELECT CASE (basic_unit)
580 cpabort(
"unknown length unit:"//trim(
cp_to_string(basic_unit)))
583 SELECT CASE (basic_unit)
586 cpabort(
"unknown temperature unit:"//trim(
cp_to_string(basic_unit)))
589 SELECT CASE (basic_unit)
592 cpabort(
"unknown pressure unit:"//trim(
cp_to_string(basic_unit)))
595 SELECT CASE (basic_unit)
598 cpabort(
"unknown angle unit:"//trim(
cp_to_string(basic_unit)))
601 SELECT CASE (basic_unit)
604 cpabort(
"unknown time unit:"//trim(
cp_to_string(basic_unit)))
607 SELECT CASE (basic_unit)
610 cpabort(
"unknown mass unit:"//trim(
cp_to_string(basic_unit)))
613 SELECT CASE (basic_unit)
616 cpabort(
"unknown potential unit:"//trim(
cp_to_string(basic_unit)))
619 SELECT CASE (basic_unit)
622 cpabort(
"unknown force unit:"//trim(
cp_to_string(basic_unit)))
626 CALL cp_abort(__location__, &
627 "if the kind of the unit is none also unit must be undefined,not:" &
630 cpabort(
"unknown kind of unit:"//trim(
cp_to_string(basic_kind)))
632 END SUBROUTINE cp_basic_unit_check
643 FUNCTION cp_basic_unit_to_cp2k(value, basic_kind, basic_unit, power)
RESULT(res)
644 REAL(kind=
dp),
INTENT(in) ::
value
645 INTEGER,
INTENT(in) :: basic_kind, basic_unit
646 INTEGER,
INTENT(in),
OPTIONAL :: power
652 IF (
PRESENT(power)) my_power = power
655 CALL cp_abort(__location__, &
656 "unit not yet fully specified, unit of kind "// &
659 SELECT CASE (basic_kind)
661 SELECT CASE (basic_unit)
665 cpabort(
"unknown energy unit:"//trim(
cp_to_string(basic_unit)))
668 SELECT CASE (basic_unit)
674 res =
joule**(-my_power)*
value
676 res =
kcalmol**(-my_power)*
value
678 res =
kjmol**(-my_power)*
value
680 res = (
kjmol*1.0e+3_dp)**(-my_power)*
value
682 res = 0.5_dp**my_power*
value
684 res =
evolt**(-my_power)*
value
686 res = (1.0e-3_dp*
evolt)**(-my_power)*
value
688 res =
kelvin**(-my_power)*
value
690 cpabort(
"unknown energy unit:"//trim(
cp_to_string(basic_unit)))
693 SELECT CASE (basic_unit)
697 res =
value*(1.0e10_dp*
bohr)**my_power
699 res =
value*(0.01_dp*
bohr)**my_power
701 res =
value*(10.0_dp*
bohr)**my_power
703 res =
value*
bohr**my_power
705 cpabort(
"unknown length unit:"//trim(
cp_to_string(basic_unit)))
708 SELECT CASE (basic_unit)
710 res =
kelvin**(-my_power)*
value
714 cpabort(
"unknown temperature unit:"//trim(
cp_to_string(basic_unit)))
717 SELECT CASE (basic_unit)
719 res =
bar**(-my_power)*
value
721 res =
atm**(-my_power)*
value
723 res = (1.0e-3_dp*
bar)**(-my_power)*
value
725 res =
pascal**(-my_power)*
value
727 res = (1.0e-6_dp*
pascal)**(-my_power)*
value
729 res = (1.0e-9_dp*
pascal)**(-my_power)*
value
733 cpabort(
"unknown pressure unit:"//trim(
cp_to_string(basic_unit)))
736 SELECT CASE (basic_unit)
740 res =
value*(
radians)**my_power
742 cpabort(
"unknown angle unit:"//trim(
cp_to_string(basic_unit)))
745 SELECT CASE (basic_unit)
747 res =
value*
seconds**(-my_power)
757 cpabort(
"unknown time unit:"//trim(
cp_to_string(basic_unit)))
760 SELECT CASE (basic_unit)
762 res =
e_mass**my_power*
value
768 cpabort(
"unknown mass unit:"//trim(
cp_to_string(basic_unit)))
771 SELECT CASE (basic_unit)
773 res =
evolt**(-my_power)*
value
777 cpabort(
"unknown potential unit:"//trim(
cp_to_string(basic_unit)))
780 SELECT CASE (basic_unit)
782 res =
value*
newton**(-my_power)
784 res =
value*(1.0e+3*
newton)**(-my_power)
788 cpabort(
"unknown force unit:"//trim(
cp_to_string(basic_unit)))
791 CALL cp_abort(__location__, &
792 "if the kind of the unit is none also unit must be undefined,not:" &
795 cpabort(
"unknown kind of unit:"//trim(
cp_to_string(basic_kind)))
797 END FUNCTION cp_basic_unit_to_cp2k
808 FUNCTION cp_basic_unit_desc(basic_kind, basic_unit, power, accept_undefined) &
810 INTEGER,
INTENT(in) :: basic_kind, basic_unit
811 INTEGER,
INTENT(in),
OPTIONAL :: power
812 LOGICAL,
INTENT(in),
OPTIONAL :: accept_undefined
813 CHARACTER(len=cp_unit_basic_desc_length) :: res
815 INTEGER :: a, my_power
816 LOGICAL :: my_accept_undefined
820 my_accept_undefined = .false.
821 IF (accept_undefined) my_accept_undefined = accept_undefined
822 IF (
PRESENT(power)) my_power = power
824 IF (.NOT. my_accept_undefined .AND. basic_kind ==
cp_units_none) &
825 CALL cp_abort(__location__,
"unit not yet fully specified, unit of kind "// &
828 SELECT CASE (basic_kind)
830 SELECT CASE (basic_unit)
832 res =
"internal_cp2k"
834 CALL cp_abort(__location__, &
835 "unit not yet fully specified, unit of kind "// &
839 SELECT CASE (basic_unit)
862 IF (.NOT. my_accept_undefined) &
863 CALL cp_abort(__location__, &
864 "unit not yet fully specified, unit of kind "// &
867 cpabort(
"unknown energy unit:"//trim(
cp_to_string(basic_unit)))
870 SELECT CASE (basic_unit)
883 cpabort(
"unknown length unit:"//trim(
cp_to_string(basic_unit)))
886 SELECT CASE (basic_unit)
893 IF (.NOT. my_accept_undefined) &
894 CALL cp_abort(__location__, &
895 "unit not yet fully specified, unit of kind "// &
898 cpabort(
"unknown temperature unit:"//trim(
cp_to_string(basic_unit)))
901 SELECT CASE (basic_unit)
918 IF (.NOT. my_accept_undefined) &
919 CALL cp_abort(__location__, &
920 "unit not yet fully specified, unit of kind "// &
923 cpabort(
"unknown pressure unit:"//trim(
cp_to_string(basic_unit)))
926 SELECT CASE (basic_unit)
933 IF (.NOT. my_accept_undefined) &
934 CALL cp_abort(__location__, &
935 "unit not yet fully specified, unit of kind "// &
938 cpabort(
"unknown angle unit:"//trim(
cp_to_string(basic_unit)))
941 SELECT CASE (basic_unit)
954 IF (.NOT. my_accept_undefined) &
955 CALL cp_abort(__location__, &
956 "unit not yet fully specified, unit of kind "// &
959 cpabort(
"unknown time unit:"//trim(
cp_to_string(basic_unit)))
962 SELECT CASE (basic_unit)
971 IF (.NOT. my_accept_undefined) &
972 CALL cp_abort(__location__, &
973 "unit not yet fully specified, unit of kind "// &
976 cpabort(
"unknown mass unit:"//trim(
cp_to_string(basic_unit)))
979 SELECT CASE (basic_unit)
986 IF (.NOT. my_accept_undefined) &
987 CALL cp_abort(__location__, &
988 "unit not yet fully specified, unit of kind "// &
991 cpabort(
"unknown potential unit:"//trim(
cp_to_string(basic_unit)))
994 SELECT CASE (basic_unit)
1003 IF (.NOT. my_accept_undefined) &
1004 CALL cp_abort(__location__, &
1005 "unit not yet fully specified, unit of kind "// &
1008 cpabort(
"unknown potential unit:"//trim(
cp_to_string(basic_unit)))
1011 CALL cp_abort(__location__, &
1012 "if the kind of the unit is none also unit must be undefined,not:" &
1015 cpabort(
"unknown kind of unit:"//trim(
cp_to_string(basic_kind)))
1017 IF (my_power /= 1)
THEN
1019 cpassert(len(res) - a >= 3)
1020 WRITE (res(a + 1:),
"('^',i3)") my_power
1023 END FUNCTION cp_basic_unit_desc
1038 LOGICAL,
INTENT(in),
OPTIONAL :: accept_undefined
1039 CHARACTER(len=cp_unit_desc_length) :: res
1041 INTEGER :: i, my_unit, pos
1042 LOGICAL :: check, has_defaults, my_accept_undefined
1046 my_accept_undefined = .false.
1047 IF (
PRESENT(accept_undefined)) my_accept_undefined = accept_undefined
1048 DO i = 1, unit%n_kinds
1049 cpassert(unit%kind_id(i) /= 0)
1050 cpassert(pos < len(res))
1051 my_unit = unit%unit_id(i)
1052 has_defaults = .false.
1053 IF (
PRESENT(defaults)) has_defaults =
ASSOCIATED(defaults%units(1)%unit)
1054 IF (my_unit == 0)
THEN
1055 IF (has_defaults)
THEN
1056 my_unit = defaults%units(unit%kind_id(i))%unit%unit_id(1)
1058 check = my_accept_undefined .OR. unit%kind_id(i) /= 0
1066 res(pos:) = trim(cp_basic_unit_desc(basic_kind=unit%kind_id(i), &
1067 basic_unit=my_unit, accept_undefined=my_accept_undefined, &
1068 power=unit%power(i)))
1069 pos = len_trim(res) + 1
1085 REAL(kind=
dp),
INTENT(in) ::
value
1088 INTEGER,
INTENT(in),
OPTIONAL :: power
1089 REAL(kind=
dp) :: res
1091 INTEGER :: i_unit, my_basic_unit, my_power
1094 IF (
PRESENT(power)) my_power = power
1096 DO i_unit = 1, unit%n_kinds
1097 cpassert(unit%kind_id(i_unit) > 0)
1098 my_basic_unit = unit%unit_id(i_unit)
1099 IF (my_basic_unit == 0 .AND. unit%kind_id(i_unit) /=
cp_ukind_undef)
THEN
1100 cpassert(
PRESENT(defaults))
1101 cpassert(
ASSOCIATED(defaults%units(unit%kind_id(i_unit))%unit))
1102 my_basic_unit = defaults%units(unit%kind_id(i_unit))%unit%unit_id(1)
1104 res = cp_basic_unit_to_cp2k(
value=res, basic_unit=my_basic_unit, &
1105 basic_kind=unit%kind_id(i_unit), &
1106 power=my_power*unit%power(i_unit))
1121 REAL(kind=
dp),
INTENT(in) ::
value
1124 INTEGER,
INTENT(in),
OPTIONAL :: power
1125 REAL(kind=
dp) :: res
1130 IF (
PRESENT(power)) my_power = power
1131 IF (
PRESENT(defaults))
THEN
1150 REAL(kind=
dp),
INTENT(in) ::
value
1151 CHARACTER(len=*),
INTENT(in) :: unit_str
1153 INTEGER,
INTENT(in),
OPTIONAL :: power
1154 REAL(kind=
dp) :: res
1159 IF (
PRESENT(defaults))
THEN
1179 REAL(kind=
dp),
INTENT(in) ::
value
1180 CHARACTER(len=*),
INTENT(in) :: unit_str
1182 INTEGER,
INTENT(in),
OPTIONAL :: power
1183 REAL(kind=
dp) :: res
1188 IF (
PRESENT(defaults))
THEN
1211 DO i = 1,
SIZE(ref_unit%kind_id)
1212 IF (ref_unit%kind_id(i) == unit%kind_id(i)) cycle
1229 CHARACTER(len=*),
INTENT(in) :: name
1231 CHARACTER(len=default_string_length) :: my_name
1238 NULLIFY (unit_set%units(i)%unit)
1239 ALLOCATE (unit_set%units(i)%unit)
1243 CASE (
'ATOM',
'ATOMIC',
'INTERNAL',
'CP2K')
1245 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), &
1248 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), &
1254 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_none/), &
1257 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_hartree/), &
1260 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_angstrom/), &
1263 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_k/), &
1266 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_deg/), &
1269 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_bar/), &
1272 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_fs/), &
1275 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_amu/), &
1278 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_volt/), &
1281 CALL cp_unit_create2(unit_set%units(i)%unit, kind_id=(/i/), unit_id=(/
cp_units_newton/), &
1288 cpabort(
'unknown parameter set name '//trim(name))
1303 DO i = 1,
SIZE(unit_set%units)
1305 DEALLOCATE (unit_set%units(i)%unit)
1316 INTEGER,
INTENT(IN) :: iw
1318 CALL format_units_as_xml(
"energy",
s2a(
"hartree",
"wavenumber_e",
"joule",
"kcalmol", &
1319 "kjmol",
"Ry",
"eV",
"keV",
"K_e"), iw)
1320 CALL format_units_as_xml(
"length",
s2a(
"bohr",
"m",
"pm",
"nm",
"angstrom"), iw)
1321 CALL format_units_as_xml(
"temperature",
s2a(
"K",
"au_temp"), iw)
1322 CALL format_units_as_xml(
"pressure",
s2a(
"bar",
"atm",
"kbar",
"Pa",
"MPa",
"GPa",
"au_p"), iw)
1323 CALL format_units_as_xml(
"angle",
s2a(
"rad",
"deg"), iw)
1324 CALL format_units_as_xml(
"time",
s2a(
"s",
"fs",
"ps",
"au_t",
"wavenumber_t"), iw)
1325 CALL format_units_as_xml(
"mass",
s2a(
"kg",
"amu",
"m_e"), iw)
1326 CALL format_units_as_xml(
"potential",
s2a(
"volt",
"au_pot"), iw)
1327 CALL format_units_as_xml(
"force",
s2a(
"N",
"Newton",
"mN",
"mNewton",
"au_f"), iw)
1338 SUBROUTINE format_units_as_xml(unit_kind, units_set, iw)
1339 CHARACTER(LEN=*),
INTENT(IN) :: unit_kind
1340 CHARACTER(LEN=*),
DIMENSION(:),
INTENT(IN) :: units_set
1341 INTEGER,
INTENT(IN) :: iw
1345 WRITE (iw, fmt=
'(T2,A)')
'<UNIT_KIND name="'//trim(unit_kind)//
'">'
1346 DO i = 1,
SIZE(units_set)
1347 WRITE (iw, fmt=
'(T3,A)')
'<UNIT>'//trim(units_set(i))//
'</UNIT>'
1349 WRITE (iw, fmt=
'(T3,A)')
'<UNIT>'//trim(unit_kind)//
'</UNIT>'
1350 WRITE (iw, fmt=
'(T2,A)')
'</UNIT_KIND>'
1351 END SUBROUTINE format_units_as_xml
various routines to log and control the output. The idea is that decisions about where to log should ...
integer, parameter, public cp_units_wavenum
integer, parameter, public cp_ukind_none
integer, parameter, public cp_units_fs
integer, parameter, public cp_units_kev
integer, parameter, public cp_units_m
integer, parameter, public cp_units_k
integer, parameter, public cp_ukind_potential
integer, parameter, public cp_units_mpa
integer, parameter, public cp_ukind_undef
integer, parameter, public cp_units_none
integer, parameter, public cp_units_angstrom
integer, parameter, public cp_units_volt
character(len=cp_unit_desc_length) function, public cp_unit_desc(unit, defaults, accept_undefined)
returns the "name" of the given unit
real(kind=dp) function, public cp_unit_to_cp2k1(value, unit, defaults, power)
transform a value to the internal cp2k units
integer, parameter, public cp_units_au
integer, parameter, public cp_ukind_length
integer, parameter, public cp_ukind_temperature
real(kind=dp) function, public cp_unit_from_cp2k1(value, unit, defaults, power)
converts from the internal cp2k units to the given unit
integer, parameter, public cp_units_hartree
integer, parameter, public cp_units_nm
integer, parameter, public cp_units_bar
integer, parameter, public cp_units_amu
integer, parameter, public cp_ukind_time
integer, parameter, public cp_ukind_energy
real(kind=dp) function, public cp_unit_from_cp2k(value, unit_str, defaults, power)
converts from the internal cp2k units to the given unit
subroutine, public cp_unit_create(unit, string)
creates a unit parsing a string
integer, parameter, public cp_ukind_force
integer, parameter, public cp_unit_desc_length
integer, parameter, public cp_units_kbar
integer, parameter, public cp_units_newton
integer, parameter, public cp_units_ps
integer, parameter, public cp_units_ev
integer, parameter, public cp_ukind_max
integer, parameter, public cp_units_mnewton
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
integer, parameter, public cp_units_atm
integer, parameter, public cp_units_deg
subroutine, public cp_unit_set_release(unit_set)
releases the given unit set
integer, parameter, public cp_units_ry
integer, parameter, public cp_units_kcalmol
integer, parameter, public cp_units_rad
integer, parameter, public cp_units_pa
integer, parameter, public cp_units_jmol
integer, parameter, public cp_units_joule
integer, parameter, public cp_unit_basic_desc_length
subroutine, public cp_unit_set_create(unit_set, name)
initializes the given unit set
integer, parameter, public cp_units_gpa
integer, parameter, public cp_units_bohr
subroutine, public export_units_as_xml(iw)
Exports all available units as XML.
integer, parameter, public cp_units_kjmol
integer, parameter, public cp_units_wn
integer, parameter, public cp_units_m_e
integer, parameter, public cp_units_pm
integer, parameter, public cp_units_kg
integer, parameter, public cp_ukind_mass
logical function, public cp_unit_compatible(ref_unit, unit)
returs true if the two units are compatible
elemental subroutine, public cp_unit_release(unit)
releases the given unit
integer, parameter, public cp_ukind_angle
integer, parameter, public cp_units_s
integer, parameter, public cp_unit_max_kinds
integer, parameter, public cp_ukind_pressure
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_string_length
Definition of mathematical constants and functions.
real(kind=dp), parameter, public radians
real(kind=dp), parameter, public twopi
Definition of physical constants:
real(kind=dp), parameter, public kcalmol
real(kind=dp), parameter, public femtoseconds
real(kind=dp), parameter, public atm
real(kind=dp), parameter, public joule
real(kind=dp), parameter, public kelvin
real(kind=dp), parameter, public newton
real(kind=dp), parameter, public seconds
real(kind=dp), parameter, public evolt
real(kind=dp), parameter, public e_mass
real(kind=dp), parameter, public picoseconds
real(kind=dp), parameter, public wavenumbers
real(kind=dp), parameter, public bar
real(kind=dp), parameter, public massunit
real(kind=dp), parameter, public kjmol
real(kind=dp), parameter, public pascal
real(kind=dp), parameter, public bohr
Utilities for string manipulations.
subroutine, public compress(string, full)
Eliminate multiple space characters in a string. If full is .TRUE., then all spaces are eliminated.
elemental subroutine, public uppercase(string)
Convert all lower case characters in a string to upper case.
stores the default units to be used