Line | Branch | Exec | Source |
---|---|---|---|
1 | !!!############################################################################# | ||
2 | !!! Code written by Ned Thaddeus Taylor | ||
3 | !!! Code part of the ATHENA library - a feedforward neural network library | ||
4 | !!!############################################################################# | ||
5 | !!! module contains implementation of a 3D input layer | ||
6 | !!!############################################################################# | ||
7 | module input3d_layer | ||
8 | use constants, only: real12 | ||
9 | use base_layer, only: input_layer_type | ||
10 | implicit none | ||
11 | |||
12 | |||
13 | type, extends(input_layer_type) :: input3d_layer_type | ||
14 | real(real12), allocatable, dimension(:,:,:,:) :: output | ||
15 | contains | ||
16 | procedure, pass(this) :: get_output => get_output_input3d | ||
17 | procedure, pass(this) :: init => init_input3d | ||
18 | procedure, pass(this) :: set_batch_size => set_batch_size_input3d | ||
19 | procedure, pass(this) :: forward => forward_rank | ||
20 | procedure, pass(this) :: backward => backward_rank | ||
21 | procedure, pass(this) :: set => set_input3d | ||
22 | end type input3d_layer_type | ||
23 | |||
24 | interface input3d_layer_type | ||
25 | module function layer_setup(input_shape, batch_size) result(layer) | ||
26 | integer, dimension(:), optional, intent(in) :: input_shape | ||
27 | integer, optional, intent(in) :: batch_size | ||
28 | type(input3d_layer_type) :: layer | ||
29 | end function layer_setup | ||
30 | end interface input3d_layer_type | ||
31 | |||
32 | |||
33 | private | ||
34 | public :: input3d_layer_type | ||
35 | |||
36 | |||
37 | contains | ||
38 | |||
39 | !!!############################################################################# | ||
40 | !!! get layer outputs | ||
41 | !!!############################################################################# | ||
42 | 1 | pure subroutine get_output_input3d(this, output) | |
43 | implicit none | ||
44 | class(input3d_layer_type), intent(in) :: this | ||
45 | real(real12), allocatable, dimension(..), intent(out) :: output | ||
46 | |||
47 | select rank(output) | ||
48 | rank(1) | ||
49 | ✗ | output = reshape(this%output, [size(this%output)]) | |
50 | rank(2) | ||
51 | output = & | ||
52 | ✗ | reshape(this%output, [product(this%output_shape),this%batch_size]) | |
53 | rank(4) | ||
54 |
34/68✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 1 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 1 times.
✗ Branch 24 not taken.
✓ Branch 25 taken 1 times.
✗ Branch 27 not taken.
✓ Branch 28 taken 1 times.
✗ Branch 30 not taken.
✓ Branch 31 taken 1 times.
✗ Branch 33 not taken.
✓ Branch 34 taken 1 times.
✗ Branch 36 not taken.
✓ Branch 37 taken 1 times.
✗ Branch 39 not taken.
✓ Branch 40 taken 1 times.
✗ Branch 42 not taken.
✓ Branch 43 taken 1 times.
✗ Branch 45 not taken.
✓ Branch 46 taken 1 times.
✗ Branch 48 not taken.
✓ Branch 49 taken 1 times.
✗ Branch 50 not taken.
✗ Branch 51 not taken.
✗ Branch 52 not taken.
✗ Branch 53 not taken.
✗ Branch 54 not taken.
✗ Branch 55 not taken.
✗ Branch 56 not taken.
✗ Branch 57 not taken.
✓ Branch 58 taken 1 times.
✗ Branch 59 not taken.
✓ Branch 60 taken 1 times.
✗ Branch 61 not taken.
✓ Branch 62 taken 1 times.
✗ Branch 63 not taken.
✓ Branch 64 taken 1 times.
✗ Branch 65 not taken.
✓ Branch 66 taken 1 times.
✗ Branch 67 not taken.
✓ Branch 68 taken 1 times.
✗ Branch 69 not taken.
✓ Branch 70 taken 1 times.
✗ Branch 71 not taken.
✓ Branch 72 taken 1 times.
✗ Branch 73 not taken.
✓ Branch 74 taken 1 times.
✗ Branch 75 not taken.
✓ Branch 76 taken 1 times.
✓ Branch 77 taken 1 times.
✓ Branch 78 taken 1 times.
✓ Branch 79 taken 1 times.
✓ Branch 80 taken 3 times.
✓ Branch 81 taken 1 times.
✓ Branch 82 taken 9 times.
✓ Branch 83 taken 3 times.
|
15 | output = this%output |
55 | end select | ||
56 | |||
57 | 1 | end subroutine get_output_input3d | |
58 | !!!############################################################################# | ||
59 | |||
60 | |||
61 | !!!##########################################################################!!! | ||
62 | !!! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !!! | ||
63 | !!!##########################################################################!!! | ||
64 | |||
65 | |||
66 | !!!############################################################################# | ||
67 | !!! forward propagation assumed rank handler | ||
68 | !!! placeholder to satisfy deferred | ||
69 | !!!############################################################################# | ||
70 | ✗ | pure subroutine forward_rank(this, input) | |
71 | implicit none | ||
72 | class(input3d_layer_type), intent(inout) :: this | ||
73 | real(real12), dimension(..), intent(in) :: input | ||
74 | |||
75 | select rank(input) | ||
76 | rank(1) | ||
77 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
78 | rank(2) | ||
79 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
80 | rank(3) | ||
81 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
82 | rank(4) | ||
83 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
84 | rank(5) | ||
85 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
86 | rank(6) | ||
87 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
88 | end select | ||
89 | ✗ | end subroutine forward_rank | |
90 | !!!############################################################################# | ||
91 | |||
92 | |||
93 | !!!############################################################################# | ||
94 | !!! backward propagation assumed rank handler | ||
95 | !!! placeholder to satisfy deferred | ||
96 | !!!############################################################################# | ||
97 | ✗ | pure subroutine backward_rank(this, input, gradient) | |
98 | implicit none | ||
99 | class(input3d_layer_type), intent(inout) :: this | ||
100 | real(real12), dimension(..), intent(in) :: input | ||
101 | real(real12), dimension(..), intent(in) :: gradient | ||
102 | ✗ | return | |
103 | end subroutine backward_rank | ||
104 | !!!############################################################################# | ||
105 | |||
106 | |||
107 | !!!##########################################################################!!! | ||
108 | !!! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !!! | ||
109 | !!!##########################################################################!!! | ||
110 | |||
111 | |||
112 | !!!############################################################################# | ||
113 | !!! set up layer | ||
114 | !!!############################################################################# | ||
115 | #if defined(GFORTRAN) | ||
116 | module function layer_setup(input_shape, batch_size) result(layer) | ||
117 | implicit none | ||
118 | integer, dimension(:), optional, intent(in) :: input_shape | ||
119 | integer, optional, intent(in) :: batch_size | ||
120 | |||
121 | type(input3d_layer_type) :: layer | ||
122 | #else | ||
123 |
2/4✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 4 times.
✗ Branch 3 not taken.
|
4 | module procedure layer_setup |
124 | implicit none | ||
125 | #endif | ||
126 | |||
127 | |||
128 |
3/8✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 4 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
|
4 | layer%name = "input3d" |
129 | 4 | layer%input_rank = 3 | |
130 | !!-------------------------------------------------------------------------- | ||
131 | !! initialise batch size | ||
132 | !!-------------------------------------------------------------------------- | ||
133 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
|
4 | if(present(batch_size)) layer%batch_size = batch_size |
134 | |||
135 | |||
136 | !!-------------------------------------------------------------------------- | ||
137 | !! initialise layer shape | ||
138 | !!-------------------------------------------------------------------------- | ||
139 |
5/10✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 4 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 4 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 4 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
|
4 | if(present(input_shape)) call layer%init(input_shape=input_shape) |
140 | |||
141 | #if defined(GFORTRAN) | ||
142 | end function layer_setup | ||
143 | #else | ||
144 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
8 | end procedure layer_setup |
145 | #endif | ||
146 | !!!############################################################################# | ||
147 | |||
148 | |||
149 | !!!############################################################################# | ||
150 | !!! initialise layer | ||
151 | !!!############################################################################# | ||
152 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
4 | subroutine init_input3d(this, input_shape, batch_size, verbose) |
153 | implicit none | ||
154 | class(input3d_layer_type), intent(inout) :: this | ||
155 | integer, dimension(:), intent(in) :: input_shape | ||
156 | integer, optional, intent(in) :: batch_size | ||
157 | integer, optional, intent(in) :: verbose | ||
158 | |||
159 | integer :: verbose_ = 0 | ||
160 | |||
161 | |||
162 | !!-------------------------------------------------------------------------- | ||
163 | !! initialise optional arguments | ||
164 | !!-------------------------------------------------------------------------- | ||
165 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | if(present(verbose)) verbose_ = verbose |
166 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | if(present(batch_size)) this%batch_size = batch_size |
167 | |||
168 | |||
169 | !!-------------------------------------------------------------------------- | ||
170 | !! initialise input shape | ||
171 | !!-------------------------------------------------------------------------- | ||
172 |
4/8✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 4 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 4 times.
|
4 | if(.not.allocated(this%input_shape)) call this%set_shape(input_shape) |
173 | |||
174 |
10/20✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 4 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 4 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 4 times.
✗ Branch 14 not taken.
✗ Branch 15 not taken.
✓ Branch 16 taken 4 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 4 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 4 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 12 times.
✓ Branch 23 taken 4 times.
|
16 | this%output_shape = this%input_shape |
175 |
6/10✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 4 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 4 times.
✓ Branch 12 taken 12 times.
✓ Branch 13 taken 4 times.
|
16 | this%num_outputs = product(this%input_shape) |
176 | |||
177 | |||
178 | !!-------------------------------------------------------------------------- | ||
179 | !! initialise batch size-dependent arrays | ||
180 | !!-------------------------------------------------------------------------- | ||
181 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
|
4 | if(this%batch_size.gt.0) call this%set_batch_size(this%batch_size) |
182 | |||
183 | 4 | end subroutine init_input3d | |
184 | !!!############################################################################# | ||
185 | |||
186 | |||
187 | !!!############################################################################# | ||
188 | !!! set batch size | ||
189 | !!!############################################################################# | ||
190 | 3 | subroutine set_batch_size_input3d(this, batch_size, verbose) | |
191 | implicit none | ||
192 | class(input3d_layer_type), intent(inout) :: this | ||
193 | integer, intent(in) :: batch_size | ||
194 | integer, optional, intent(in) :: verbose | ||
195 | |||
196 | integer :: verbose_ = 0 | ||
197 | |||
198 | |||
199 | !!-------------------------------------------------------------------------- | ||
200 | !! initialise optional arguments | ||
201 | !!-------------------------------------------------------------------------- | ||
202 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
3 | if(present(verbose)) verbose_ = verbose |
203 | 3 | this%batch_size = batch_size | |
204 | |||
205 | |||
206 | !!-------------------------------------------------------------------------- | ||
207 | !! allocate arrays | ||
208 | !!-------------------------------------------------------------------------- | ||
209 |
1/2✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
|
3 | if(allocated(this%input_shape))then |
210 |
3/4✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
|
3 | if(allocated(this%output)) deallocate(this%output) |
211 | ✗ | allocate(this%output( & | |
212 | 6 | this%input_shape(1), & | |
213 | 6 | this%input_shape(2), & | |
214 | 6 | this%input_shape(3), & | |
215 |
19/38✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 3 times.
✓ Branch 6 taken 3 times.
✗ Branch 7 not taken.
✗ Branch 8 not taken.
✓ Branch 9 taken 3 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 3 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 3 times.
✓ Branch 16 taken 3 times.
✗ Branch 17 not taken.
✗ Branch 18 not taken.
✓ Branch 19 taken 3 times.
✗ Branch 20 not taken.
✓ Branch 21 taken 3 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 3 times.
✓ Branch 26 taken 3 times.
✗ Branch 27 not taken.
✗ Branch 28 not taken.
✓ Branch 29 taken 3 times.
✓ Branch 30 taken 3 times.
✗ Branch 31 not taken.
✗ Branch 32 not taken.
✓ Branch 33 taken 3 times.
✗ Branch 34 not taken.
✓ Branch 35 taken 3 times.
✗ Branch 36 not taken.
✓ Branch 37 taken 3 times.
✗ Branch 38 not taken.
✓ Branch 39 taken 3 times.
✗ Branch 41 not taken.
✓ Branch 42 taken 3 times.
✗ Branch 43 not taken.
✓ Branch 44 taken 3 times.
|
3 | this%batch_size)) |
216 | end if | ||
217 | |||
218 | 3 | end subroutine set_batch_size_input3d | |
219 | !!!############################################################################# | ||
220 | |||
221 | |||
222 | !!!##########################################################################!!! | ||
223 | !!! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !!! | ||
224 | !!!##########################################################################!!! | ||
225 | |||
226 | |||
227 | !!!############################################################################# | ||
228 | !!! set input layer values | ||
229 | !!!############################################################################# | ||
230 | 3 | pure subroutine set_input3d(this, input) | |
231 | implicit none | ||
232 | class(input3d_layer_type), intent(inout) :: this | ||
233 | real(real12), & | ||
234 | dimension(..), intent(in) :: input | ||
235 | !dimension(this%batch_size * this%num_outputs), intent(in) :: input | ||
236 | |||
237 | select rank(input) | ||
238 | rank(1) | ||
239 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
240 | rank(2) | ||
241 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
242 | rank(3) | ||
243 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
244 | rank(4) | ||
245 |
26/36✓ Branch 0 taken 12 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 12 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 12 times.
✓ Branch 8 taken 3 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 3 times.
✓ Branch 11 taken 3 times.
✓ Branch 12 taken 7 times.
✓ Branch 13 taken 3 times.
✓ Branch 14 taken 45 times.
✓ Branch 15 taken 7 times.
✓ Branch 16 taken 303 times.
✓ Branch 17 taken 45 times.
✓ Branch 18 taken 3 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 3 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 3 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 3 times.
✗ Branch 25 not taken.
✓ Branch 26 taken 3 times.
✗ Branch 27 not taken.
✗ Branch 28 not taken.
✗ Branch 29 not taken.
✓ Branch 30 taken 3 times.
✓ Branch 31 taken 3 times.
✓ Branch 32 taken 7 times.
✓ Branch 33 taken 3 times.
✓ Branch 34 taken 45 times.
✓ Branch 35 taken 7 times.
✓ Branch 36 taken 303 times.
✓ Branch 37 taken 45 times.
|
731 | this%output = reshape(input, shape=shape(this%output)) |
246 | rank(5) | ||
247 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
248 | rank(6) | ||
249 | ✗ | this%output = reshape(input, shape=shape(this%output)) | |
250 | end select | ||
251 | |||
252 | 3 | end subroutine set_input3d | |
253 | !!!############################################################################# | ||
254 | |||
255 | |||
256 |
27/75✓ Branch 0 taken 7 times.
✓ Branch 1 taken 5 times.
✓ Branch 2 taken 7 times.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 12 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 7 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 6 times.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✗ Branch 14 not taken.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✗ Branch 17 not taken.
✗ Branch 18 not taken.
✗ Branch 19 not taken.
✗ Branch 20 not taken.
✗ Branch 21 not taken.
✓ Branch 22 taken 3 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 3 times.
✗ Branch 25 not taken.
✗ Branch 26 not taken.
✓ Branch 27 taken 3 times.
✗ Branch 28 not taken.
✓ Branch 29 taken 3 times.
✗ Branch 30 not taken.
✓ Branch 31 taken 3 times.
✓ Branch 32 taken 3 times.
✗ Branch 33 not taken.
✗ Branch 34 not taken.
✗ Branch 35 not taken.
✗ Branch 36 not taken.
✗ Branch 37 not taken.
✗ Branch 38 not taken.
✗ Branch 39 not taken.
✓ Branch 40 taken 4 times.
✗ Branch 42 not taken.
✓ Branch 43 taken 4 times.
✓ Branch 45 taken 4 times.
✓ Branch 46 taken 4 times.
✗ Branch 47 not taken.
✓ Branch 48 taken 4 times.
✗ Branch 49 not taken.
✗ Branch 50 not taken.
✗ Branch 52 not taken.
✗ Branch 53 not taken.
✗ Branch 55 not taken.
✗ Branch 56 not taken.
✗ Branch 58 not taken.
✗ Branch 59 not taken.
✗ Branch 61 not taken.
✗ Branch 62 not taken.
✗ Branch 64 not taken.
✗ Branch 65 not taken.
✓ Branch 67 taken 4 times.
✗ Branch 68 not taken.
✗ Branch 69 not taken.
✓ Branch 70 taken 4 times.
✓ Branch 71 taken 4 times.
✗ Branch 72 not taken.
✗ Branch 73 not taken.
✓ Branch 74 taken 4 times.
✓ Branch 75 taken 4 times.
✗ Branch 76 not taken.
✗ Branch 77 not taken.
✓ Branch 78 taken 4 times.
✓ Branch 79 taken 4 times.
✗ Branch 80 not taken.
✓ Branch 81 taken 4 times.
✗ Branch 82 not taken.
|
34 | end module input3d_layer |
257 | !!!############################################################################# | ||
258 |