Line | Branch | Exec | Source |
---|---|---|---|
1 | module raffle__distribs_host | ||
2 | !! Module for handling the host distribution functions. | ||
3 | !! | ||
4 | !! This module contains the type and procedures for handling the host | ||
5 | !! distribution function. Procedures are also provided to calculate the | ||
6 | !! interface energy of the host and to set the mapping of host elements to | ||
7 | !! the element database. | ||
8 | use raffle__constants, only: real32 | ||
9 | use raffle__io_utils, only: stop_program | ||
10 | use raffle__geom_rw, only: basis_type | ||
11 | use raffle__element_utils, only: element_type | ||
12 | use raffle__distribs, only: distribs_type | ||
13 | implicit none | ||
14 | |||
15 | |||
16 | private | ||
17 | |||
18 | public :: distribs_host_type | ||
19 | |||
20 | |||
21 | type, extends(distribs_type) :: distribs_host_type | ||
22 | !! Type for host information. | ||
23 | !! | ||
24 | !! This type contains the information regarding the host structure that | ||
25 | !! will be used in the grandparent generator type. | ||
26 | logical :: defined = .false. | ||
27 | !! Boolean whether the host structure has been set. | ||
28 | real(real32) :: interface_energy = 0.0_real32 | ||
29 | !! Energy associated with the formation of the interface in the host. | ||
30 | type(basis_type) :: basis | ||
31 | !! Host structure. | ||
32 | integer, dimension(:,:), allocatable :: pair_index | ||
33 | !! Index for the 2-body distribution function. | ||
34 | integer, dimension(:), allocatable :: element_map | ||
35 | !! Mapping of host elements to distribution function elements. | ||
36 | contains | ||
37 | procedure, pass(this) :: calculate_interface_energy | ||
38 | !! Calculate the interface formation energy of the host. | ||
39 | procedure, pass(this) :: set => set_host | ||
40 | !! Set the host structure for the distribution functions. | ||
41 | procedure, pass(this) :: set_element_map => set_host_element_map | ||
42 | !! Set the mapping of host elements to distribution function elements. | ||
43 | end type distribs_host_type | ||
44 | |||
45 | |||
46 | contains | ||
47 | |||
48 | !############################################################################### | ||
49 | 9 | subroutine set_host(this, host) | |
50 | !! Set the host structure for the distribution functions. | ||
51 | !! | ||
52 | !! distribution function not needed for host | ||
53 | implicit none | ||
54 | |||
55 | ! Arguments | ||
56 | class(distribs_host_type), intent(inout) :: this | ||
57 | !! Parent. Instance of distribution functions container. | ||
58 | type(basis_type), intent(in) :: host | ||
59 | !! Host structure for the distribution functions. | ||
60 | |||
61 | ! Local variables | ||
62 | integer :: i, is, js | ||
63 | !! Loop indices. | ||
64 | |||
65 | 9 | call this%basis%copy(host) | |
66 | 9 | this%defined = .true. | |
67 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%pair_index)) deallocate(this%pair_index) |
68 |
9/18✓ Branch 0 taken 9 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 9 times.
✓ Branch 4 taken 9 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 9 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 9 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 9 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 9 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 9 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 9 times.
|
9 | allocate(this%pair_index(this%basis%nspec, this%basis%nspec)) |
69 | 9 | i = 0 | |
70 |
2/2✓ Branch 0 taken 11 times.
✓ Branch 1 taken 9 times.
|
20 | do is = 1, this%basis%nspec |
71 |
2/2✓ Branch 0 taken 14 times.
✓ Branch 1 taken 11 times.
|
34 | do js = is, this%basis%nspec, 1 |
72 | 14 | i = i + 1 | |
73 | 14 | this%pair_index(js,is) = i | |
74 | 25 | this%pair_index(is,js) = i | |
75 | end do | ||
76 | end do | ||
77 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%df_2body)) deallocate(this%df_2body) |
78 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%df_3body)) deallocate(this%df_3body) |
79 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%df_4body)) deallocate(this%df_4body) |
80 | |||
81 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%stoichiometry)) deallocate(this%stoichiometry) |
82 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%element_symbols)) deallocate(this%element_symbols) |
83 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%num_pairs)) deallocate(this%num_pairs) |
84 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%num_per_species)) deallocate(this%num_per_species) |
85 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%weight_pair)) deallocate(this%weight_pair) |
86 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
9 | if(allocated(this%weight_per_species)) deallocate(this%weight_per_species) |
87 | |||
88 | 9 | end subroutine set_host | |
89 | !############################################################################### | ||
90 | |||
91 | |||
92 | !############################################################################### | ||
93 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
4 | subroutine calculate_interface_energy(this, element_info) |
94 | !! Calculate the interface formation energy of the host. | ||
95 | implicit none | ||
96 | |||
97 | ! Arguments | ||
98 | class(distribs_host_type), intent(inout) :: this | ||
99 | !! Parent. Instance of host type. | ||
100 | type(element_type), dimension(:), intent(in) :: element_info | ||
101 | !! List of elements and properties. | ||
102 | |||
103 | ! Local variables | ||
104 | integer :: is, idx1 | ||
105 | !! Loop indices. | ||
106 | |||
107 | 4 | this%interface_energy = this%energy | |
108 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
|
8 | do is = 1, size(this%element_symbols) |
109 | idx1 = findloc( & | ||
110 | [ element_info(:)%name ], & | ||
111 | this%element_symbols(is), dim=1 & | ||
112 |
6/8✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✓ Branch 3 taken 8 times.
✓ Branch 4 taken 4 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✓ Branch 7 taken 8 times.
✓ Branch 8 taken 4 times.
|
20 | ) |
113 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | if(idx1.lt.1)then |
114 | ✗ | call stop_program( "Species not found in species list" ) | |
115 | ✗ | return | |
116 | end if | ||
117 | this%interface_energy = this%interface_energy - & | ||
118 | 4 | this%stoichiometry(is) * element_info(idx1)%energy | |
119 | end do | ||
120 | |||
121 | end subroutine calculate_interface_energy | ||
122 | !############################################################################### | ||
123 | |||
124 | |||
125 | !############################################################################### | ||
126 |
1/2✓ Branch 0 taken 18 times.
✗ Branch 1 not taken.
|
18 | subroutine set_host_element_map(this, element_info) |
127 | !! Set the host element map for the container. | ||
128 | implicit none | ||
129 | |||
130 | ! Arguments | ||
131 | class(distribs_host_type), intent(inout) :: this | ||
132 | !! Parent of the procedure. Instance of distribution functions container. | ||
133 | type(element_type), dimension(:), intent(in) :: element_info | ||
134 | !! Element information. | ||
135 | |||
136 | ! Local variables | ||
137 | integer :: is | ||
138 | !! Index of the elements in the element_info array. | ||
139 | |||
140 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 18 times.
|
18 | if(.not.this%defined)then |
141 | ✗ | call stop_program( "Host not defined" ) | |
142 | ✗ | return | |
143 | end if | ||
144 |
3/4✓ Branch 0 taken 10 times.
✓ Branch 1 taken 8 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 10 times.
|
18 | if(allocated(this%element_map)) deallocate(this%element_map) |
145 |
7/14✓ Branch 0 taken 18 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 18 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 18 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 18 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 18 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 18 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 18 times.
|
18 | allocate(this%element_map(this%basis%nspec)) |
146 |
2/2✓ Branch 0 taken 22 times.
✓ Branch 1 taken 18 times.
|
40 | do is = 1, this%basis%nspec |
147 | this%element_map(is) = findloc(& | ||
148 | [ element_info(:)%name ], & | ||
149 | this%basis%spec(is)%name, dim=1 & | ||
150 |
6/8✗ Branch 0 not taken.
✓ Branch 1 taken 22 times.
✓ Branch 3 taken 38 times.
✓ Branch 4 taken 22 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 22 times.
✓ Branch 7 taken 38 times.
✓ Branch 8 taken 22 times.
|
98 | ) |
151 | end do | ||
152 | |||
153 | end subroutine set_host_element_map | ||
154 | !############################################################################### | ||
155 | |||
156 | ✗ | end module raffle__distribs_host | |
157 |