(git:374b731)
Loading...
Searching...
No Matches
space_groups_types.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 Space Group Symmetry Type Module (version 1.0, Ferbruary 12, 2021)
10!> \par History
11!> Pierre-André Cazade [pcazade] 02.2021 - University of Limerick
12!> \author Pierre-André Cazade (first version)
13! **************************************************************************************************
15
16 USE cell_types, ONLY: cell_release,&
18 USE kinds, ONLY: dp
19#include "../base/base_uses.f90"
20
21 IMPLICIT NONE
22
23 PRIVATE
24
25 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'space_groups_types'
26
28 LOGICAL :: keep_space_group = .false.
29 LOGICAL :: symlib = .false.
30 LOGICAL :: print_atoms = .false.
31 INTEGER :: iunit = -1
32 INTEGER :: istriz = -1
33 REAL(kind=dp) :: eps_symmetry = 1.0e-4_dp
34 INTEGER :: nparticle = 0
35 INTEGER :: nparticle_sym = 0
36 INTEGER :: n_atom = 0
37 INTEGER :: n_core = 0
38 INTEGER :: n_shell = 0
39 INTEGER :: n_atom_sym = 0
40 INTEGER :: n_core_sym = 0
41 INTEGER :: n_shell_sym = 0
42 INTEGER, DIMENSION(:), ALLOCATABLE :: atype
43 INTEGER, DIMENSION(:, :), ALLOCATABLE :: eqatom
44 LOGICAL, DIMENSION(:), ALLOCATABLE :: lop, lat
45 REAL(kind=dp), DIMENSION(3) :: pol = 0.0_dp
46 !SPGLIB
47 INTEGER :: space_group_number = 0
48 CHARACTER(len=11) :: international_symbol = ""
49 CHARACTER(len=6) :: pointgroup_symbol = ""
50 CHARACTER(len=7) :: schoenflies = ""
51 INTEGER :: n_operations = 0
52 INTEGER :: n_reduced_operations = 0
53 INTEGER :: n_operations_subset = 0
54 INTEGER, DIMENSION(:, :, :), ALLOCATABLE :: rotations
55 INTEGER, DIMENSION(:, :, :), ALLOCATABLE :: rotations_subset
56 REAL(kind=dp), DIMENSION(:, :), ALLOCATABLE :: translations
57 TYPE(cell_type), POINTER :: cell_ref => null()
58 END TYPE spgr_type
59
61
62CONTAINS
63
64! **************************************************************************************************
65!> \brief Release the SPGR type
66!> \param spgr The SPGR type
67!> \par History
68!> 01.2020 created [pcazade]
69!> \author Pierre-André Cazade (first version)
70! **************************************************************************************************
71 SUBROUTINE release_spgr_type(spgr)
72
73 TYPE(spgr_type), POINTER :: spgr
74
75 IF (ASSOCIATED(spgr)) THEN
76
77 IF (ALLOCATED(spgr%rotations)) THEN
78 DEALLOCATE (spgr%rotations)
79 END IF
80 IF (ALLOCATED(spgr%rotations_subset)) THEN
81 DEALLOCATE (spgr%rotations_subset)
82 END IF
83 IF (ALLOCATED(spgr%translations)) THEN
84 DEALLOCATE (spgr%translations)
85 END IF
86 IF (ALLOCATED(spgr%atype)) THEN
87 DEALLOCATE (spgr%atype)
88 END IF
89 IF (ALLOCATED(spgr%eqatom)) THEN
90 DEALLOCATE (spgr%eqatom)
91 END IF
92 IF (ALLOCATED(spgr%lop)) THEN
93 DEALLOCATE (spgr%lop)
94 END IF
95 IF (ALLOCATED(spgr%lat)) THEN
96 DEALLOCATE (spgr%lat)
97 END IF
98
99 CALL cell_release(spgr%cell_ref)
100
101 DEALLOCATE (spgr)
102 END IF
103
104 END SUBROUTINE release_spgr_type
105
106END MODULE space_groups_types
Handles all functions related to the CELL.
Definition cell_types.F:15
subroutine, public cell_release(cell)
releases the given cell (see doc/ReferenceCounting.html)
Definition cell_types.F:559
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
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.
Definition cell_types.F:55