GCC Code Coverage Report


Directory: src/athena/
File: athena_onnx_creators.f90
Date: 2025-12-10 07:37:07
Exec Total Coverage
Lines: 0 0 100.0%
Functions: 0 0 -%
Branches: 0 0 -%

Line Branch Exec Source
1 module athena__onnx_creators
2 !! Module containing ONNX layer creator functions
3 use coreutils, only: stop_program, icount
4 use athena__base_layer, only: base_layer_type
5 use athena__avgpool1d_layer, only: avgpool1d_layer_type
6 use athena__avgpool2d_layer, only: avgpool2d_layer_type
7 use athena__avgpool3d_layer, only: avgpool3d_layer_type
8 use athena__batchnorm1d_layer, only: batchnorm1d_layer_type
9 use athena__batchnorm2d_layer, only: batchnorm2d_layer_type
10 use athena__batchnorm3d_layer, only: batchnorm3d_layer_type
11 use athena__conv1d_layer, only: conv1d_layer_type
12 use athena__conv2d_layer, only: conv2d_layer_type
13 use athena__conv3d_layer, only: conv3d_layer_type
14 use athena__pad1d_layer, only: pad1d_layer_type
15 use athena__pad2d_layer, only: pad2d_layer_type
16 use athena__pad3d_layer, only: pad3d_layer_type
17 use athena__maxpool1d_layer, only: maxpool1d_layer_type
18 use athena__maxpool2d_layer, only: maxpool2d_layer_type
19 use athena__maxpool3d_layer, only: maxpool3d_layer_type
20
21 use athena__misc_types, only: &
22 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
23 implicit none
24
25
26 private
27
28 public :: create_from_onnx_avgpool_layer
29 public :: create_from_onnx_batchnorm_layer
30 public :: create_from_onnx_conv_layer
31 public :: create_from_onnx_maxpool_layer
32 public :: create_from_onnx_pad_layer
33
34
35
36 contains
37
38 !###############################################################################
39 function create_from_onnx_avgpool_layer( &
40 node, initialisers, value_info, verbose &
41 ) result(layer)
42 !! Build avgpool layer from attributes and return layer
43 implicit none
44
45 ! Arguments
46 type(onnx_node_type), intent(in) :: node
47 !! ONNX node information
48 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
49 !! ONNX initialiser information
50 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
51 !! ONNX value info information
52 integer, optional, intent(in) :: verbose
53 !! Verbosity level
54 class(base_layer_type), allocatable :: layer
55 !! Instance of the 2D convolutional layer
56
57 ! Local variables
58 integer :: i, dim
59 !! Loop variable and data rank
60 integer :: verbose_ = 0
61 !! Verbosity level
62
63 if(present(verbose)) verbose_ = verbose
64 dim = size(value_info(1)%dims) - 2
65
66 select case(dim)
67 case(1)
68 allocate(layer, source=avgpool1d_layer_type())
69 case(2)
70 allocate(layer, source=avgpool2d_layer_type())
71 case(3)
72 allocate(layer, source=avgpool3d_layer_type())
73 case default
74 call stop_program("create_from_onnx_avgpool_layer: " // &
75 "unsupported pooling dimension")
76 end select
77 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
78
79 end function create_from_onnx_avgpool_layer
80 !###############################################################################
81
82
83 !###############################################################################
84 function create_from_onnx_batchnorm_layer( &
85 node, initialisers, value_info, verbose &
86 ) result(layer)
87 !! Build batchnorm layer from attributes and return layer
88 implicit none
89
90 ! Arguments
91 type(onnx_node_type), intent(in) :: node
92 !! ONNX node information
93 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
94 !! ONNX initialiser information
95 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
96 !! ONNX value info information
97 integer, optional, intent(in) :: verbose
98 !! Verbosity level
99 class(base_layer_type), allocatable :: layer
100 !! Instance of the batch normalization layer
101
102 ! Local variables
103 integer :: i, dim
104 !! Loop variable and data rank
105 integer :: verbose_ = 0
106 !! Verbosity level
107
108 if(present(verbose)) verbose_ = verbose
109 dim = size(value_info(1)%dims) - 2
110
111 select case(dim)
112 case(0)
113 allocate(layer, source=batchnorm1d_layer_type())
114 case(2)
115 allocate(layer, source=batchnorm2d_layer_type())
116 case(3)
117 allocate(layer, source=batchnorm3d_layer_type())
118 case default
119 call stop_program("create_from_onnx_batchnorm_layer: " // &
120 "unsupported batchnorm dimension")
121 end select
122 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
123
124 end function create_from_onnx_batchnorm_layer
125 !###############################################################################
126
127
128 !###############################################################################
129 function create_from_onnx_conv_layer( &
130 node, initialisers, value_info, verbose &
131 ) result(layer)
132 !! Build conv layer from attributes and return layer
133 implicit none
134
135 ! Arguments
136 type(onnx_node_type), intent(in) :: node
137 !! ONNX node information
138 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
139 !! ONNX initialiser information
140 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
141 !! ONNX value info information
142 integer, optional, intent(in) :: verbose
143 !! Verbosity level
144 class(base_layer_type), allocatable :: layer
145 !! Instance of the 2D convolutional layer
146
147 ! Local variables
148 integer :: i, dim
149 !! Loop variable and data rank
150 integer :: verbose_ = 0
151 !! Verbosity level
152
153 if(present(verbose)) verbose_ = verbose
154 dim = size(value_info(1)%dims) - 2
155
156 select case(dim)
157 case(1)
158 allocate(layer, source=conv1d_layer_type())
159 case(2)
160 allocate(layer, source=conv2d_layer_type())
161 case(3)
162 allocate(layer, source=conv3d_layer_type())
163 case default
164 call stop_program("create_from_onnx_conv_layer: " // &
165 "unsupported convolution dimension")
166 end select
167 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
168
169 end function create_from_onnx_conv_layer
170 !###############################################################################
171
172
173 !###############################################################################
174 function create_from_onnx_maxpool_layer( &
175 node, initialisers, value_info, verbose &
176 ) result(layer)
177 !! Build maxpool layer from attributes and return layer
178 implicit none
179
180 ! Arguments
181 type(onnx_node_type), intent(in) :: node
182 !! ONNX node information
183 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
184 !! ONNX initialiser information
185 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
186 !! ONNX value info information
187 integer, optional, intent(in) :: verbose
188 !! Verbosity level
189 class(base_layer_type), allocatable :: layer
190 !! Instance of the 2D convolutional layer
191
192 ! Local variables
193 integer :: i, dim
194 !! Loop variable and data rank
195 integer :: verbose_ = 0
196 !! Verbosity level
197
198 if(present(verbose)) verbose_ = verbose
199 dim = size(value_info(1)%dims) - 2
200
201 select case(dim)
202 case(1)
203 allocate(layer, source=maxpool1d_layer_type())
204 case(2)
205 allocate(layer, source=maxpool2d_layer_type())
206 case(3)
207 allocate(layer, source=maxpool3d_layer_type())
208 case default
209 call stop_program("create_from_onnx_maxpool_layer: " // &
210 "unsupported pooling dimension")
211 end select
212 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
213
214 end function create_from_onnx_maxpool_layer
215 !###############################################################################
216
217
218 !###############################################################################
219 function create_from_onnx_pad_layer( &
220 node, initialisers, value_info, verbose &
221 ) result(layer)
222 !! Build pad layer from attributes and return layer
223 implicit none
224
225 ! Arguments
226 type(onnx_node_type), intent(in) :: node
227 !! ONNX node information
228 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
229 !! ONNX initialiser information
230 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
231 !! ONNX value info information
232 integer, optional, intent(in) :: verbose
233 !! Verbosity level
234 class(base_layer_type), allocatable :: layer
235 !! Instance of the pad layer
236
237 ! Local variables
238 integer :: i, dim
239 !! Loop variable and data rank
240 integer :: verbose_ = 0
241 !! Verbosity level
242
243 if(present(verbose)) verbose_ = verbose
244 dim = size(value_info(1)%dims) - 2
245
246 select case(dim)
247 case(1)
248 allocate(layer, source=pad1d_layer_type(padding=[0], method="valid"))
249 case(2)
250 allocate(layer, source=pad2d_layer_type(padding=[0], method="valid"))
251 case(3)
252 allocate(layer, source=pad3d_layer_type(padding=[0], method="valid"))
253 case default
254 call stop_program("create_from_onnx_pad_layer: " // &
255 "unsupported pad dimension")
256 end select
257 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
258
259 end function create_from_onnx_pad_layer
260 !###############################################################################
261
262 end module athena__onnx_creators
263