19#include "../base/base_uses.f90"
25 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'space_groups_types'
28 LOGICAL :: keep_space_group = .false.
29 LOGICAL :: show_space_group = .false.
30 LOGICAL :: symlib = .false.
31 LOGICAL :: print_atoms = .false.
33 INTEGER :: istriz = -1
34 REAL(kind=
dp) :: eps_symmetry = 1.0e-4_dp
35 INTEGER :: nparticle = 0
36 INTEGER :: nparticle_sym = 0
39 INTEGER :: n_shell = 0
40 INTEGER :: n_atom_sym = 0
41 INTEGER :: n_core_sym = 0
42 INTEGER :: n_shell_sym = 0
43 INTEGER,
DIMENSION(:),
ALLOCATABLE :: atype
44 INTEGER,
DIMENSION(:, :),
ALLOCATABLE :: eqatom
45 LOGICAL,
DIMENSION(:),
ALLOCATABLE :: lop, lat
46 REAL(kind=
dp),
DIMENSION(3) :: pol = 0.0_dp
48 INTEGER :: space_group_number = 0
49 CHARACTER(len=11) :: international_symbol =
""
50 CHARACTER(len=6) :: pointgroup_symbol =
""
51 CHARACTER(len=7) :: schoenflies =
""
52 INTEGER :: n_operations = 0
53 INTEGER :: n_reduced_operations = 0
54 INTEGER :: n_operations_subset = 0
55 INTEGER,
DIMENSION(:, :, :),
ALLOCATABLE :: rotations
56 INTEGER,
DIMENSION(:, :, :),
ALLOCATABLE :: rotations_subset
57 REAL(kind=
dp),
DIMENSION(:, :),
ALLOCATABLE :: translations
76 IF (
ASSOCIATED(spgr))
THEN
78 IF (
ALLOCATED(spgr%rotations))
THEN
79 DEALLOCATE (spgr%rotations)
81 IF (
ALLOCATED(spgr%rotations_subset))
THEN
82 DEALLOCATE (spgr%rotations_subset)
84 IF (
ALLOCATED(spgr%translations))
THEN
85 DEALLOCATE (spgr%translations)
87 IF (
ALLOCATED(spgr%atype))
THEN
88 DEALLOCATE (spgr%atype)
90 IF (
ALLOCATED(spgr%eqatom))
THEN
91 DEALLOCATE (spgr%eqatom)
93 IF (
ALLOCATED(spgr%lop))
THEN
96 IF (
ALLOCATED(spgr%lat))
THEN
Handles all functions related to the CELL.
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
Defines the basic variable types.
integer, parameter, public dp
Space Group Symmetry Type Module (version 1.0, Ferbruary 12, 2021)
subroutine, public release_spgr_type(spgr)
Release the SPGR type.
Type defining parameters related to the simulation cell.