GCC Code Coverage Report


Directory: src/athena/
File: athena_container_layer.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__container_layer
2 !! Module containing types and interfaces for the container type
3 !!
4 !! This module contains the container layer type which is a container for an
5 !! individual layer.
6 use coreutils, only: real32
7 use athena__base_layer, only: base_layer_type
8 use athena__misc_types, only: &
9 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
10 implicit none
11
12
13 private
14
15 public :: container_layer_type
16 public :: read_layer_container
17 public :: list_of_layer_types
18 public :: allocate_list_of_layer_types
19 public :: onnx_create_layer_container
20 public :: list_of_onnx_layer_creators
21 public :: allocate_list_of_onnx_layer_creators
22 #if defined(GFORTRAN)
23 public :: container_reduction
24 #endif
25
26
27 type :: container_layer_type
28 !! Container for a layer
29 class(base_layer_type), allocatable :: layer
30 !! Layer
31 contains
32 #if defined(GFORTRAN)
33 procedure, pass(this) :: reduce => container_reduction
34 !! Reduce two layers via summation
35 final :: finalise_container_layer
36 !! Finalise the container layer
37 #endif
38 end type container_layer_type
39
40
41 #if defined(GFORTRAN)
42 interface
43 module subroutine container_reduction(this, rhs)
44 !! Reduce two layers via summation
45 class(container_layer_type), intent(inout) :: this
46 !! Present layer container
47 class(container_layer_type), intent(in) :: rhs
48 !! Input layer container
49 end subroutine
50 end interface
51 #endif
52
53
54 type :: read_layer_container
55 !! Type containing information needed to read a layer
56 character(20) :: name
57 !! Name of the layer
58 procedure(read_layer), nopass, pointer :: read_ptr => null()
59 !! Pointer to the specific layer read function
60 end type read_layer_container
61 type(read_layer_container), dimension(:), allocatable :: &
62 list_of_layer_types
63 !! List of layer names and their associated read functions
64
65 type :: onnx_create_layer_container
66 !! Type containing information needed to create a layer from ONNX
67 character(20) :: op_type
68 !! Name of the layer
69 procedure(create_from_onnx_layer), nopass, pointer :: create_ptr => null()
70 !! Pointer to the specific layer creation function from ONNX
71 end type onnx_create_layer_container
72 type(onnx_create_layer_container), dimension(:), allocatable :: &
73 list_of_onnx_layer_creators
74 !! List of layer names and their associated ONNX creation functions
75
76 interface
77 module function read_layer(unit, verbose) result(layer)
78 !! Read a layer from a file
79 integer, intent(in) :: unit
80 !! Unit number
81 integer, intent(in), optional :: verbose
82 !! Verbosity level
83 class(base_layer_type), allocatable :: layer
84 !! Instance of a layer
85 end function read_layer
86
87 module function create_from_onnx_layer( &
88 nodes, initialisers, value_info, verbose &
89 ) result(layer)
90 !! Create a layer from ONNX nodes and initialisers
91 type(onnx_node_type), intent(in) :: nodes
92 !! ONNX nodes
93 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
94 !! ONNX initialisers
95 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
96 !! ONNX value info
97 integer, intent(in), optional :: verbose
98 !! Verbosity level
99 class(base_layer_type), allocatable :: layer
100 !! Instance of a layer
101 end function create_from_onnx_layer
102 end interface
103
104 interface
105 module subroutine allocate_list_of_layer_types(addit_list)
106 !! Allocate the list of layer types
107 type(read_layer_container), dimension(:), intent(in), optional :: &
108 addit_list
109 !! Additional list of layer types
110 end subroutine allocate_list_of_layer_types
111
112 module subroutine allocate_list_of_onnx_layer_creators(addit_list)
113 !! Allocate the list of ONNX layer creation procedures
114 type(onnx_create_layer_container), dimension(:), intent(in), optional :: &
115 addit_list
116 !! Additional list of ONNX layer creation procedures
117 end subroutine allocate_list_of_onnx_layer_creators
118 end interface
119
120 interface
121 module subroutine finalise_container_layer(this)
122 !! Finalise the container layer
123 class(container_layer_type), intent(inout) :: this
124 !! Present layer container
125 end subroutine finalise_container_layer
126 end interface
127
128 end module athena__container_layer
129