forked from modern-fortran/neural-fortran
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathnf_layer.f90
158 lines (130 loc) · 5.07 KB
/
nf_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
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
module nf_layer
!! This module provides the `layer` type that is part of the public
!! user-facing API.
use nf_base_layer, only: base_layer
use nf_optimizers, only: optimizer_base_type
implicit none
private
public :: layer
type :: layer
!! Main layer type. Use custom constructor functions from
!! nf_layer_constructors.f90 to create `layer` instances.
class(base_layer), allocatable :: p
character(:), allocatable :: name
character(:), allocatable :: activation
integer, allocatable :: layer_shape(:)
integer, allocatable :: input_layer_shape(:)
logical :: initialized = .false.
contains
procedure :: forward
procedure :: get_num_params
procedure :: get_params
procedure :: get_gradients
procedure :: set_params
procedure :: init
procedure :: print_info
! Specific subroutines for different array ranks
procedure, private :: backward_1d
procedure, private :: backward_3d
procedure, private :: get_output_1d
procedure, private :: get_output_3d
generic :: backward => backward_1d, backward_3d
generic :: get_output => get_output_1d, get_output_3d
end type layer
interface backward
pure module subroutine backward_1d(self, previous, gradient)
!! Apply a backward pass on the layer.
!! This changes the internal state of the layer.
!! This is normally called internally by the `network % backward`
!! method.
class(layer), intent(in out) :: self
!! Layer instance
class(layer), intent(in) :: previous
!! Previous layer instance
real, intent(in) :: gradient(:)
!! Array of gradient values from the next layer
end subroutine backward_1d
pure module subroutine backward_3d(self, previous, gradient)
!! Apply a backward pass on the layer.
!! This changes the internal state of the layer.
!! This is normally called internally by the `network % backward`
!! method.
class(layer), intent(in out) :: self
!! Layer instance
class(layer), intent(in) :: previous
!! Previous layer instance
real, intent(in) :: gradient(:,:,:)
!! Array of gradient values from the next layer
end subroutine backward_3d
end interface backward
interface
pure module subroutine forward(self, input)
!! Apply a forward pass on the layer.
!! This changes the internal state of the layer.
!! This is normally called internally by the `network % forward`
!! method.
class(layer), intent(in out) :: self
!! Layer instance
class(layer), intent(in) :: input
!! Input layer instance
end subroutine forward
pure module subroutine get_output_1d(self, output)
!! Returns the output values (activations) from this layer.
class(layer), intent(in) :: self
!! Layer instance
real, allocatable, intent(out) :: output(:)
!! Output values from this layer
end subroutine get_output_1d
pure module subroutine get_output_3d(self, output)
!! Returns the output values (activations) from a layer with a 3-d output
!! (e.g. input3d, conv2d)
class(layer), intent(in) :: self
!! Layer instance
real, allocatable, intent(out) :: output(:,:,:)
!! Output values from this layer
end subroutine get_output_3d
impure elemental module subroutine init(self, input)
!! Initialize the layer, using information from the input layer,
!! i.e. the layer that precedes this one.
class(layer), intent(in out) :: self
!! Layer instance
class(layer), intent(in) :: input
!! Input layer instance
end subroutine init
impure elemental module subroutine print_info(self)
!! Prints a summary information about this layer to the screen.
!! This method is called by `network % print_info` for all layers
!! on that network.
class(layer), intent(in) :: self
!! Layer instance
end subroutine print_info
elemental module function get_num_params(self) result(num_params)
!! Returns the number of parameters in this layer.
class(layer), intent(in) :: self
!! Layer instance
integer :: num_params
!! Number of parameters in this layer
end function get_num_params
pure module function get_params(self) result(params)
!! Returns the parameters of this layer.
class(layer), intent(in) :: self
!! Layer instance
real, allocatable :: params(:)
!! Parameters of this layer
end function get_params
pure module function get_gradients(self) result(gradients)
!! Returns the gradients of this layer.
class(layer), intent(in) :: self
!! Layer instance
real, allocatable :: gradients(:)
!! Gradients of this layer
end function get_gradients
module subroutine set_params(self, params)
!! Returns the parameters of this layer.
class(layer), intent(in out) :: self
!! Layer instance
real, intent(in) :: params(:)
!! Parameters of this layer
end subroutine set_params
end interface
end module nf_layer