Skip to content

Commit eb4079d

Browse files
committed
Now reshape2d works, maxpool still not
1 parent cf2caf6 commit eb4079d

File tree

3 files changed

+134
-145
lines changed

3 files changed

+134
-145
lines changed

src/nf/nf_layer_submodule.f90

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -87,6 +87,12 @@ pure module subroutine backward_2d(self, previous, gradient)
8787
type is(locally_connected_1d_layer)
8888
call this_layer % backward(prev_layer % output, gradient)
8989
end select
90+
91+
type is(reshape2d_layer)
92+
select type(prev_layer => previous % p)
93+
type is(input1d_layer)
94+
call this_layer % backward(prev_layer % output, gradient)
95+
end select
9096

9197
end select
9298

@@ -248,6 +254,12 @@ pure module subroutine forward(self, input)
248254
type is(flatten_layer)
249255
call this_layer % forward(prev_layer % output)
250256
end select
257+
258+
type is(reshape2d_layer)
259+
select type(prev_layer => input % p)
260+
type is(input1d_layer)
261+
call this_layer % forward(prev_layer % output)
262+
end select
251263

252264
end select
253265

src/nf/nf_locally_connected_1d_submodule.f90

Lines changed: 69 additions & 93 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,6 @@ module function locally_connected_1d_layer_cons(filters, kernel_size, activation
1818
res % filters = filters
1919
res % activation_name = activation % get_name()
2020
allocate( res % activation, source = activation )
21-
2221
end function locally_connected_1d_layer_cons
2322

2423
module subroutine init(self, input_shape)
@@ -29,16 +28,14 @@ module subroutine init(self, input_shape)
2928
self % channels = input_shape(1)
3029
self % width = input_shape(2) - self % kernel_size + 1
3130

32-
! Output of shape filters x width
31+
! Output of shape: filters x width
3332
allocate(self % output(self % filters, self % width))
3433
self % output = 0
3534

36-
! Kernel of shape filters x channels x kernel_size
35+
! Kernel of shape: filters x channels x kernel_size
3736
allocate(self % kernel(self % filters, self % channels, self % kernel_size))
38-
39-
! Initialize the kernel with random values with a normal distribution
4037
call random_normal(self % kernel)
41-
self % kernel = self % kernel / self % kernel_size ** 2
38+
self % kernel = self % kernel / real(self % kernel_size**2)
4239

4340
allocate(self % biases(self % filters))
4441
self % biases = 0
@@ -61,113 +58,93 @@ pure module subroutine forward(self, input)
6158
implicit none
6259
class(locally_connected_1d_layer), intent(in out) :: self
6360
real, intent(in) :: input(:,:)
64-
integer :: input_width, input_channels
65-
integer :: i, n, i_out
66-
integer :: iws, iwe
67-
integer :: half_window
61+
integer :: input_channels, input_width
62+
integer :: j, n
63+
integer :: iws, iwe, half_window
6864

69-
! Get input dimensions
7065
input_channels = size(input, dim=1)
7166
input_width = size(input, dim=2)
72-
73-
! For a kernel of odd size, half_window = kernel_size / 2 (integer division)
7467
half_window = self % kernel_size / 2
7568

76-
! Loop over output indices rather than input indices.
77-
do i_out = 1, self % width
78-
! Compute the corresponding center index in the input.
79-
i = i_out + half_window
80-
81-
! Define the window in the input corresponding to the filter kernel
82-
iws = i - half_window
83-
iwe = i + half_window
69+
! Loop over output positions.
70+
do j = 1, self % width
71+
! Compute the input window corresponding to output index j.
72+
! In forward: center index = j + half_window, so window = indices j to j+kernel_size-1.
73+
iws = j
74+
iwe = j + self % kernel_size - 1
8475

85-
! Compute the inner tensor product (sum of element-wise products)
86-
! for each filter across all channels and positions in the kernel.
87-
do concurrent(n = 1:self % filters)
88-
self % z(n, i_out) = sum(self % kernel(n, :, :) * input(:, iws:iwe))
76+
! For each filter, compute the convolution (inner product over channels and kernel width).
77+
do concurrent (n = 1:self % filters)
78+
self % z(n, j) = sum(self % kernel(n, :, :) * input(:, iws:iwe))
8979
end do
9080

9181
! Add the bias for each filter.
92-
self % z(:, i_out) = self % z(:, i_out) + self % biases
82+
self % z(:, j) = self % z(:, j) + self % biases
9383
end do
9484

95-
! Apply the activation function to get the final output.
85+
! Apply the activation function.
9686
self % output = self % activation % eval(self % z)
9787
end subroutine forward
9888

99-
10089
pure module subroutine backward(self, input, gradient)
10190
implicit none
10291
class(locally_connected_1d_layer), intent(in out) :: self
103-
real, intent(in) :: input(:,:) ! shape: (channels, width)
104-
real, intent(in) :: gradient(:,:) ! shape: (filters, width)
105-
106-
! Local gradient arrays:
107-
real :: db(self % filters)
108-
real :: dw(self % filters, self % channels, self % kernel_size)
109-
real :: gdz(self % filters, size(input, 2))
110-
111-
integer :: i, n, k
112-
integer :: input_channels, input_width
113-
integer :: istart, iend
114-
integer :: iws, iwe
115-
integer :: half_window
116-
117-
! Get input dimensions.
92+
! 'input' has shape: (channels, input_width)
93+
! 'gradient' (dL/dy) has shape: (filters, output_width)
94+
real, intent(in) :: input(:,:)
95+
real, intent(in) :: gradient(:,:)
96+
97+
integer :: input_channels, input_width, output_width
98+
integer :: j, n, k
99+
integer :: iws, iwe, half_window
100+
real :: gdz_val
101+
102+
! Local arrays to accumulate gradients.
103+
real :: gdz(self % filters, self % width) ! local gradient (dL/dz)
104+
real :: db_local(self % filters)
105+
real :: dw_local(self % filters, self % channels, self % kernel_size)
106+
107+
! Determine dimensions.
118108
input_channels = size(input, dim=1)
119109
input_width = size(input, dim=2)
120-
121-
! For an odd-sized kernel, half_window = kernel_size / 2.
110+
output_width = self % width ! Note: output_width = input_width - kernel_size + 1
111+
122112
half_window = self % kernel_size / 2
123-
124-
! Define the valid output range so that the full input window is available.
125-
istart = half_window + 1
126-
iend = input_width - half_window
127-
128-
!---------------------------------------------------------------------
129-
! Compute the local gradient: gdz = (dL/dy) * sigma'(z)
130-
! We assume self%z stores the pre-activation values from the forward pass.
131-
gdz = 0.0
132-
gdz(:, istart:iend) = gradient(:, istart:iend) * self % activation % eval_prime(self % z(:, istart:iend))
133-
134-
!---------------------------------------------------------------------
135-
! Compute gradient with respect to biases:
136-
! dL/db(n) = sum_{i in valid range} gdz(n, i)
137-
do concurrent (n = 1:self % filters)
138-
db(n) = sum(gdz(n, istart:iend))
113+
114+
!--- Compute the local gradient gdz = (dL/dy) * sigma'(z) for each output.
115+
do j = 1, output_width
116+
gdz(:, j) = gradient(:, j) * self % activation % eval_prime(self % z(:, j))
139117
end do
140-
141-
! Initialize weight gradient and input gradient accumulators.
142-
dw = 0.0
143-
self % gradient = 0.0 ! This array is assumed preallocated to shape (channels, width)
144-
145-
!---------------------------------------------------------------------
146-
! Accumulate gradients over valid output positions.
147-
! For each output position i, determine the corresponding input window indices.
148-
do concurrent (n = 1:self % filters, &
149-
k = 1:self % channels, &
150-
i = istart:iend)
151-
! The input window corresponding to output index i:
152-
iws = i - half_window
153-
iwe = i + half_window
154-
155-
! Weight gradient (dL/dw):
156-
! For each kernel element, the contribution is the product of the input in the window
157-
! and the local gradient at the output position i.
158-
dw(n, k, :) = dw(n, k, :) + input(k, iws:iwe) * gdz(n, i)
159-
160-
! Input gradient (dL/dx):
161-
! Distribute the effect of the output gradient back onto the input window,
162-
! weighted by the kernel weights.
163-
self % gradient(k, iws:iwe) = self % gradient(k, iws:iwe) + self % kernel(n, k, :) * gdz(n, i)
118+
119+
!--- Compute bias gradients: db(n) = sum_j gdz(n, j)
120+
do n = 1, self % filters
121+
db_local(n) = sum(gdz(n, :))
164122
end do
165-
166-
!---------------------------------------------------------------------
167-
! Accumulate the computed gradients into the layer's stored gradients.
168-
self % dw = self % dw + dw
169-
self % db = self % db + db
170-
123+
124+
!--- Initialize weight gradient and input gradient accumulators.
125+
dw_local = 0.0
126+
self % gradient = 0.0
127+
128+
!--- Accumulate gradients over each output position.
129+
! In the forward pass the window for output index j was:
130+
! iws = j, iwe = j + kernel_size - 1.
131+
do n = 1, self % filters
132+
do j = 1, output_width
133+
iws = j
134+
iwe = j + self % kernel_size - 1
135+
do k = 1, self % channels
136+
! Weight gradient: accumulate contribution from the input window.
137+
dw_local(n, k, :) = dw_local(n, k, :) + input(k, iws:iwe) * gdz(n, j)
138+
! Input gradient: propagate gradient back to the input window.
139+
self % gradient(k, iws:iwe) = self % gradient(k, iws:iwe) + self % kernel(n, k, :) * gdz(n, j)
140+
end do
141+
end do
142+
end do
143+
144+
!--- Update stored gradients.
145+
self % dw = self % dw + dw_local
146+
self % db = self % db + db_local
147+
171148
end subroutine backward
172149

173150
pure module function get_num_params(self) result(num_params)
@@ -197,11 +174,10 @@ module subroutine set_params(self, params)
197174
real, intent(in) :: params(:)
198175

199176
if (size(params) /= self % get_num_params()) then
200-
error stop 'locally_connected_1d % set_params: Number of parameters does not match'
177+
error stop 'locally_connected_1d_layer % set_params: Number of parameters does not match'
201178
end if
202179

203180
self % kernel = reshape(params(:product(shape(self % kernel))), shape(self % kernel))
204-
205181
associate(n => product(shape(self % kernel)))
206182
self % biases = params(n + 1 : n + self % filters)
207183
end associate

test/test_reshape2d_layer.f90

Lines changed: 53 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -1,54 +1,55 @@
11
program test_reshape2d_layer
22

3-
use iso_fortran_env, only: stderr => error_unit
4-
use nf, only: input, network, reshape2d_layer => reshape2d
5-
use nf_datasets, only: download_and_unpack, keras_reshape_url
6-
7-
implicit none
8-
9-
type(network) :: net
10-
real, allocatable :: sample_input(:), output(:,:)
11-
integer, parameter :: output_shape(2) = [32, 32]
12-
integer, parameter :: input_size = product(output_shape)
13-
character(*), parameter :: keras_reshape_path = 'keras_reshape.h5'
14-
logical :: file_exists
15-
logical :: ok = .true.
16-
17-
! Create the network
18-
net = network([ &
19-
input(input_size), &
20-
reshape2d_layer(output_shape) &
21-
])
22-
23-
if (.not. size(net % layers) == 2) then
24-
write(stderr, '(a)') 'the network should have 2 layers.. failed'
25-
ok = .false.
26-
end if
27-
28-
! Initialize test data
29-
allocate(sample_input(input_size))
30-
call random_number(sample_input)
31-
32-
! Propagate forward and get the output
33-
call net % forward(sample_input)
34-
call net % layers(2) % get_output(output)
35-
36-
if (.not. all(shape(output) == output_shape)) then
37-
write(stderr, '(a)') 'the reshape layer produces expected output shape.. failed'
38-
ok = .false.
39-
end if
40-
41-
if (.not. all(reshape(sample_input, output_shape) == output)) then
42-
write(stderr, '(a)') 'the reshape layer produces expected output values.. failed'
43-
ok = .false.
44-
end if
45-
46-
if (ok) then
47-
print '(a)', 'test_reshape2d_layer: All tests passed.'
48-
else
49-
write(stderr, '(a)') 'test_reshape2d_layer: One or more tests failed.'
50-
stop 1
51-
end if
52-
53-
end program test_reshape2d_layer
54-
3+
use iso_fortran_env, only: stderr => error_unit
4+
use nf, only: input, network, reshape2d_layer => reshape2d
5+
use nf_datasets, only: download_and_unpack, keras_reshape_url
6+
7+
implicit none
8+
9+
type(network) :: net
10+
real, allocatable :: sample_input(:), output(:,:)
11+
integer, parameter :: output_shape(2) = [4,4]
12+
integer, parameter :: input_size = product(output_shape)
13+
character(*), parameter :: keras_reshape_path = 'keras_reshape.h5'
14+
logical :: file_exists
15+
logical :: ok = .true.
16+
17+
! Create the network
18+
net = network([ &
19+
input(input_size), &
20+
reshape2d_layer(output_shape) &
21+
])
22+
23+
if (.not. size(net % layers) == 2) then
24+
write(stderr, '(a)') 'the network should have 2 layers.. failed'
25+
ok = .false.
26+
end if
27+
28+
! Initialize test data
29+
allocate(sample_input(input_size))
30+
call random_number(sample_input)
31+
32+
! Propagate forward and get the output
33+
call net % forward(sample_input)
34+
call net % layers(2) % get_output(output)
35+
36+
! Check shape of the output
37+
if (.not. all(shape(output) == output_shape)) then
38+
write(stderr, '(a)') 'the reshape layer produces expected output shape.. failed'
39+
ok = .false.
40+
end if
41+
42+
! Check if reshaped input matches output
43+
if (.not. all(reshape(sample_input, output_shape) == output)) then
44+
write(stderr, '(a)') 'the reshape layer produces expected output values.. failed'
45+
ok = .false.
46+
end if
47+
48+
if (ok) then
49+
print '(a)', 'test_reshape2d_layer: All tests passed.'
50+
else
51+
write(stderr, '(a)') 'test_reshape2d_layer: One or more tests failed.'
52+
stop 1
53+
end if
54+
55+
end program test_reshape2d_layer

0 commit comments

Comments
 (0)