GCC Code Coverage Report


Directory: src/fortran/lib/
File: mod_element_utils.f90
Date: 2025-06-15 07:27:34
Exec Total Coverage
Lines: 35 37 94.6%
Functions: 0 0 -%
Branches: 42 58 72.4%

Line Branch Exec Source
1 module raffle__element_utils
2 !! Module for storing and handling element and bond data.
3 !!
4 !! This module contains the element and bond types, and the element and bond
5 !! databases. The element and bond databases are used to store the properties
6 !! of the elements and bonds in the system, respectively.
7 !! The element and bond types are used by other modules to store the
8 !! properties relevant to an individual system.
9 use raffle__constants, only: real32
10 use raffle__io_utils, only: print_warning
11 implicit none
12
13 private
14
15 public :: element_type, element_bond_type
16 public :: element_database, element_bond_database
17
18
19 type :: element_type
20 !! Type for storing the properties of an element.
21 character(len=3) :: name
22 real(real32) :: mass = 0._real32
23 real(real32) :: charge = 0._real32
24 real(real32) :: radius = 0._real32
25 real(real32) :: energy = 0._real32
26 contains
27 procedure, pass(this) :: set => set_element
28 end type element_type
29 type(element_type), dimension(:), allocatable :: element_database
30
31
32 type :: element_bond_type
33 !! Type for storing the properties of a bond between two elements.
34 real(real32) :: radius_covalent = 0._real32
35 character(3), dimension(2) :: element
36 contains
37 procedure, pass(this) :: set => set_bond
38 end type element_bond_type
39 type(element_bond_type), dimension(:), allocatable :: element_bond_database
40
41
42 interface element_type
43 !! Constructor for the element type.
44 module function init_element_type( &
45 name, mass, charge, energy) result(element)
46 character(len=3), intent(in) :: name
47 real(real32), intent(in), optional :: mass, charge, energy
48 type(element_type) :: element
49 end function init_element_type
50 end interface element_type
51
52
53 interface element_bond_type
54 !! Constructor for the element bond type.
55 module function init_element_bond_type( &
56 elements, radius) result(bond)
57 character(len=3), dimension(2), intent(in) :: elements
58 real(real32), intent(in), optional :: radius
59 type(element_bond_type) :: bond
60 end function init_element_bond_type
61 end interface element_bond_type
62
63
64 contains
65
66 !###############################################################################
67 17 module function init_element_type(name, mass, charge, energy) result(element)
68 !! Initialise an instance of the element_type.
69 !!
70 !! This function initialises an instance of the element_type with the
71 !! provided properties.
72 implicit none
73
74 ! Arguments
75 character(len=3), intent(in) :: name
76 !! Element name.
77 real(real32), intent(in), optional :: mass, charge, energy
78 !! Element mass, charge, and energy.
79
80 type(element_type) :: element
81 !! Instance of element_type.
82
83 17 element%name = name
84 1 if(present(mass)) element%mass= mass
85
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 16 times.
17 if(present(charge)) element%charge = charge
86
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 16 times.
17 if(present(energy)) element%energy = energy
87
88
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 16 times.
34 end function init_element_type
89 !###############################################################################
90
91
92 !###############################################################################
93 20 module function init_element_bond_type(elements, radius) result(bond)
94 !! Initialise an instance of the element_bond_type.
95 !!
96 !! This function initialises an instance of the element_bond_type with the
97 !! provided properties.
98 implicit none
99
100 ! Arguments
101 character(len=3), dimension(2), intent(in) :: elements
102 !! Element names.
103 real(real32), intent(in), optional :: radius
104 !! Element radius.
105
106 type(element_bond_type) :: bond
107 !! Instance of bond_type.
108
109
2/2
✓ Branch 0 taken 40 times.
✓ Branch 1 taken 20 times.
60 bond%element = elements
110
2/2
✓ Branch 0 taken 17 times.
✓ Branch 1 taken 3 times.
20 if(present(radius)) bond%radius_covalent = radius
111
112 40 end function init_element_bond_type
113 !###############################################################################
114
115
116 !###############################################################################
117 30 subroutine set_element(this, name, in_database)
118 !! Set the element properties.
119 !!
120 !! This subroutine sets the properties of an element instance with data from
121 !! the element database.
122 !! Element properties include the mass, charge, radius, and reference energy
123 !! of the element.
124 implicit none
125
126 ! Arguments
127 class(element_type), intent(inout) :: this
128 !! Parent. Instance of element_type.
129 character(len=3), intent(in) :: name
130 !! Element name.
131 logical, intent(out), optional :: in_database
132 !! Boolean whether pair is in database.
133
134 ! Local variables
135 integer :: i
136 !! Loop index.
137 character(256) :: warn_msg
138 !! Warning message.
139
140
141
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 29 times.
30 if(present(in_database)) in_database = .false.
142
1/2
✓ Branch 0 taken 30 times.
✗ Branch 1 not taken.
30 if(allocated(element_database))then
143
1/2
✓ Branch 0 taken 50 times.
✗ Branch 1 not taken.
50 do i = 1, size(element_database)
144
4/6
✓ Branch 2 taken 50 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 50 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 30 times.
✓ Branch 7 taken 20 times.
50 if(trim(element_database(i)%name) .eq. trim(name))then
145 30 this%name = element_database(i)%name
146 30 this%mass = element_database(i)%mass
147 30 this%charge = element_database(i)%charge
148 30 this%radius = element_database(i)%radius
149 30 this%energy = element_database(i)%energy
150
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 29 times.
30 if(present(in_database)) in_database = .true.
151 30 return
152 end if
153 end do
154 end if
155
156 write(warn_msg,'("Element ",A," not found in element database")') trim(name)
157 call print_warning(warn_msg)
158
159 end subroutine set_element
160 !###############################################################################
161
162
163 !###############################################################################
164 174 subroutine set_bond(this, element_1, element_2, in_database)
165 !! Set the bond properties for a pair of elements.
166 !!
167 !! This subroutine sets the properties of a bond instance with data from
168 !! the bond database.
169 !! Bond properties include the covalent radius of the bond.
170 implicit none
171
172 ! Arguments
173 class(element_bond_type), intent(inout) :: this
174 !! Parent. Instance of element_bond_type.
175 character(len=3), intent(in) :: element_1, element_2
176 !! Element names.
177 logical, intent(out), optional :: in_database
178 !! Boolean whether pair is in database.
179
180 ! Local variables
181 integer :: i
182 !! Loop index.
183 character(256) :: warn_msg
184 !! Warning message.
185
186
187
2/2
✓ Branch 0 taken 171 times.
✓ Branch 1 taken 3 times.
174 if(present(in_database)) in_database = .false.
188
2/2
✓ Branch 0 taken 167 times.
✓ Branch 1 taken 7 times.
174 if(allocated(element_bond_database))then
189
2/2
✓ Branch 0 taken 426 times.
✓ Branch 1 taken 10 times.
436 do i = 1, size(element_bond_database)
190 if( &
191 ( &
192 trim(element_bond_database(i)%element(1)) .eq. &
193 trim(element_1) .and. &
194 ( &
195 trim(element_bond_database(i)%element(2)) .eq. &
196 trim(element_2) &
197 ) &
198
10/18
✓ Branch 8 taken 426 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 426 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 426 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 426 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 426 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 426 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 426 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 426 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 157 times.
✓ Branch 25 taken 269 times.
426 ) .or. ( &
199 trim(element_bond_database(i)%element(1)) .eq. &
200 trim(element_2) .and. &
201 ( &
202 trim(element_bond_database(i)%element(2)) .eq. &
203 trim(element_1) &
204 ) &
205 ) &
206 10 )then
207
2/2
✓ Branch 0 taken 314 times.
✓ Branch 1 taken 157 times.
471 this%element = element_bond_database(i)%element
208 157 this%radius_covalent = element_bond_database(i)%radius_covalent
209
2/2
✓ Branch 0 taken 154 times.
✓ Branch 1 taken 3 times.
157 if(present(in_database)) in_database = .true.
210 157 return
211 end if
212 end do
213 end if
214
215 write(warn_msg, &
216 '("Bond between ",A," and ",A," not found in bond database")' &
217 ) &
218
2/4
✓ Branch 3 taken 17 times.
✗ Branch 4 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
17 trim(element_1), trim(element_2)
219 17 call print_warning(warn_msg)
220
221 end subroutine set_bond
222 !###############################################################################
223
224 4 end module raffle__element_utils
225