-
Notifications
You must be signed in to change notification settings - Fork 85
/
nf_conv2d_layer.f90
120 lines (98 loc) · 3.8 KB
/
nf_conv2d_layer.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
module nf_conv2d_layer
!! This modules provides a 2-d convolutional `conv2d_layer` type.
use nf_activation, only: activation_function
use nf_base_layer, only: base_layer
implicit none
private
public :: conv2d_layer
type, extends(base_layer) :: conv2d_layer
integer :: width
integer :: height
integer :: channels
integer :: kernel_size
integer :: filters
real, allocatable :: biases(:) ! size(filters)
real, allocatable :: kernel(:,:,:,:) ! filters x channels x window x window
real, allocatable :: output(:,:,:) ! filters x output_width * output_height
real, allocatable :: z(:,:,:) ! kernel .dot. input + bias
real, allocatable :: dw(:,:,:,:) ! weight (kernel) gradients
real, allocatable :: db(:) ! bias gradients
real, allocatable :: gradient(:,:,:)
class(activation_function), allocatable :: activation
contains
procedure :: forward
procedure :: backward
procedure :: get_gradients
procedure :: get_num_params
procedure :: get_params
procedure :: init
procedure :: set_params
end type conv2d_layer
interface conv2d_layer
module function conv2d_layer_cons(filters, kernel_size, activation) &
result(res)
!! `conv2d_layer` constructor function
integer, intent(in) :: filters
integer, intent(in) :: kernel_size
class(activation_function), intent(in) :: activation
type(conv2d_layer) :: res
end function conv2d_layer_cons
end interface conv2d_layer
interface
module subroutine init(self, input_shape)
!! Initialize the layer data structures.
!!
!! This is a deferred procedure from the `base_layer` abstract type.
class(conv2d_layer), intent(in out) :: self
!! A `conv2d_layer` instance
integer, intent(in) :: input_shape(:)
!! Input layer dimensions
end subroutine init
pure module subroutine forward(self, input)
!! Apply a forward pass on the `conv2d` layer.
class(conv2d_layer), intent(in out) :: self
!! A `conv2d_layer` instance
real, intent(in) :: input(:,:,:)
!! Input data
end subroutine forward
pure module subroutine backward(self, input, gradient)
!! Apply a backward pass on the `conv2d` layer.
class(conv2d_layer), intent(in out) :: self
!! A `conv2d_layer` instance
real, intent(in) :: input(:,:,:)
!! Input data (previous layer)
real, intent(in) :: gradient(:,:,:)
!! Gradient (next layer)
end subroutine backward
pure module function get_num_params(self) result(num_params)
!! Get the number of parameters in the layer.
class(conv2d_layer), intent(in) :: self
!! A `conv2d_layer` instance
integer :: num_params
!! Number of parameters
end function get_num_params
module function get_params(self) result(params)
!! Return the parameters (weights and biases) of this layer.
!! The parameters are ordered as weights first, biases second.
class(conv2d_layer), intent(in), target :: self
!! A `conv2d_layer` instance
real, allocatable :: params(:)
!! Parameters to get
end function get_params
module function get_gradients(self) result(gradients)
!! Return the gradients of this layer.
!! The gradients are ordered as weights first, biases second.
class(conv2d_layer), intent(in), target :: self
!! A `conv2d_layer` instance
real, allocatable :: gradients(:)
!! Gradients to get
end function get_gradients
module subroutine set_params(self, params)
!! Set the parameters of the layer.
class(conv2d_layer), intent(in out) :: self
!! A `conv2d_layer` instance
real, intent(in) :: params(:)
!! Parameters to set
end subroutine set_params
end interface
end module nf_conv2d_layer