Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 3 additions & 1 deletion src/nf/nf_layer_constructors.f90
Original file line number Diff line number Diff line change
Expand Up @@ -156,7 +156,7 @@ end function conv2d

interface locally_connected

module function locally_connected2d(filters, kernel_size, activation) result(res)
module function locally_connected2d(filters, kernel_size, activation, stride) result(res)
!! 1-d locally connected network constructor
!!
!! This layer is for building 1-d locally connected network.
Expand All @@ -179,6 +179,8 @@ module function locally_connected2d(filters, kernel_size, activation) result(res
!! Width of the convolution window, commonly 3 or 5
class(activation_function), intent(in), optional :: activation
!! Activation function (default sigmoid)
integer, intent(in), optional :: stride
!! Size of the stride (default 1)
type(layer) :: res
!! Resulting layer instance
end function locally_connected2d
Expand Down
15 changes: 13 additions & 2 deletions src/nf/nf_layer_constructors_submodule.f90
Original file line number Diff line number Diff line change
Expand Up @@ -80,12 +80,14 @@ module function conv2d(filters, kernel_width, kernel_height, activation) result(

end function conv2d

module function locally_connected2d(filters, kernel_size, activation) result(res)
module function locally_connected2d(filters, kernel_size, activation, stride) result(res)
integer, intent(in) :: filters
integer, intent(in) :: kernel_size
class(activation_function), intent(in), optional :: activation
integer, intent(in), optional :: stride
type(layer) :: res

integer :: stride_tmp
class(activation_function), allocatable :: activation_tmp

res % name = 'locally_connected2d'
Expand All @@ -98,9 +100,18 @@ module function locally_connected2d(filters, kernel_size, activation) result(res

res % activation = activation_tmp % get_name()

if (present(stride)) then
stride_tmp = stride
else
stride_tmp = 1
endif

if (stride_tmp < 1) &
error stop 'stride must be >= 1 in a conv1d layer'

allocate( &
res % p, &
source=locally_connected2d_layer(filters, kernel_size, activation_tmp) &
source=locally_connected2d_layer(filters, kernel_size, activation_tmp, stride_tmp) &
)

end function locally_connected2d
Expand Down
8 changes: 7 additions & 1 deletion src/nf/nf_locally_connected2d_layer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module nf_locally_connected2d_layer
integer :: channels
integer :: kernel_size
integer :: filters
integer :: stride

real, allocatable :: biases(:,:) ! size(filters)
real, allocatable :: kernel(:,:,:,:) ! filters x channels x window x window
Expand All @@ -40,12 +41,13 @@ module nf_locally_connected2d_layer
end type locally_connected2d_layer

interface locally_connected2d_layer
module function locally_connected2d_layer_cons(filters, kernel_size, activation) &
module function locally_connected2d_layer_cons(filters, kernel_size, activation, stride) &
result(res)
!! `locally_connected2d_layer` constructor function
integer, intent(in) :: filters
integer, intent(in) :: kernel_size
class(activation_function), intent(in) :: activation
integer, intent(in) :: stride
type(locally_connected2d_layer) :: res
end function locally_connected2d_layer_cons
end interface locally_connected2d_layer
Expand Down Expand Up @@ -91,7 +93,9 @@ end function get_num_params
module subroutine get_params_ptr(self, w_ptr, b_ptr)
class(locally_connected2d_layer), intent(in), target :: self
real, pointer, intent(out) :: w_ptr(:)
!! Pointer to the kernel weights (flattened)
real, pointer, intent(out) :: b_ptr(:)
!! Pointer to the biases
end subroutine get_params_ptr

module function get_gradients(self) result(gradients)
Expand All @@ -106,7 +110,9 @@ end function get_gradients
module subroutine get_gradients_ptr(self, dw_ptr, db_ptr)
class(locally_connected2d_layer), intent(in), target :: self
real, pointer, intent(out) :: dw_ptr(:)
!! Pointer to the kernel weight gradients (flattened)
real, pointer, intent(out) :: db_ptr(:)
!! Pointer to the bias gradients
end subroutine get_gradients_ptr

end interface
Expand Down
34 changes: 18 additions & 16 deletions src/nf/nf_locally_connected2d_layer_submodule.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,16 +7,17 @@

contains

module function locally_connected2d_layer_cons(filters, kernel_size, activation) result(res)
implicit none
module function locally_connected2d_layer_cons(filters, kernel_size, activation, stride) result(res)
integer, intent(in) :: filters
integer, intent(in) :: kernel_size
class(activation_function), intent(in) :: activation
integer, intent(in) :: stride
type(locally_connected2d_layer) :: res

res % kernel_size = kernel_size
res % filters = filters
res % activation_name = activation % get_name()
res % stride = stride
allocate(res % activation, source = activation)
end function locally_connected2d_layer_cons

Expand All @@ -26,8 +27,11 @@ module subroutine init(self, input_shape)
integer, intent(in) :: input_shape(:)

self % channels = input_shape(1)
self % width = input_shape(2) - self % kernel_size + 1
self % width = (input_shape(2) - self % kernel_size) / self % stride +1

if (mod(input_shape(2) - self % kernel_size , self % stride) /= 0) self % width = self % width + 1

! Output of shape: filters x width
allocate(self % output(self % filters, self % width))
self % output = 0

Expand Down Expand Up @@ -63,10 +67,10 @@ pure module subroutine forward(self, input)
input_width = size(input, dim=2)

do j = 1, self % width
iws = j
iwe = j + self % kernel_size - 1
iws = self % stride * (j-1) + 1
iwe = min(iws + self % kernel_size - 1, input_width)
do n = 1, self % filters
self % z(n, j) = sum(self % kernel(n, j, :, :) * input(:, iws:iwe)) + self % biases(n, j)
self % z(n, j) = sum(self % kernel(n, j, :, 1:iwe-iws+1) * input(:, iws:iwe)) + self % biases(n, j)
end do
end do
self % output = self % activation % eval(self % z)
Expand All @@ -77,7 +81,7 @@ pure module subroutine backward(self, input, gradient)
class(locally_connected2d_layer), intent(in out) :: self
real, intent(in) :: input(:,:)
real, intent(in) :: gradient(:,:)
integer :: input_channels, input_width, output_width
integer :: input_channels, input_width
integer :: j, n, k
integer :: iws, iwe
real :: gdz(self % filters, self % width)
Expand All @@ -86,14 +90,13 @@ pure module subroutine backward(self, input, gradient)

input_channels = size(input, dim=1)
input_width = size(input, dim=2)
output_width = self % width

do j = 1, output_width
do j = 1, self % width
gdz(:, j) = gradient(:, j) * self % activation % eval_prime(self % z(:, j))
end do

do n = 1, self % filters
do j = 1, output_width
do j = 1, self % width
db_local(n, j) = gdz(n, j)
end do
end do
Expand All @@ -102,12 +105,12 @@ pure module subroutine backward(self, input, gradient)
self % gradient = 0.0

do n = 1, self % filters
do j = 1, output_width
iws = j
iwe = j + self % kernel_size - 1
do j = 1, self % width
iws = self % stride * (j-1) + 1
iwe = min(iws + self % kernel_size - 1, input_width)
do k = 1, self % channels
dw_local(n, j, k, :) = dw_local(n, j, k, :) + input(k, iws:iwe) * gdz(n, j)
self % gradient(k, iws:iwe) = self % gradient(k, iws:iwe) + self % kernel(n, j, k, :) * gdz(n, j)
dw_local(n, j, k, 1:iwe-iws+1) = dw_local(n, j, k, 1:iwe-iws+1) + input(k, iws:iwe) * gdz(n, j)
self % gradient(k, iws:iwe) = self % gradient(k, iws:iwe) + self % kernel(n, j, k, 1:iwe-iws+1) * gdz(n, j)
end do
end do
end do
Expand Down Expand Up @@ -144,5 +147,4 @@ module subroutine get_gradients_ptr(self, dw_ptr, db_ptr)
db_ptr(1:size(self % db)) => self % db
end subroutine get_gradients_ptr


end submodule nf_locally_connected2d_layer_submodule
25 changes: 24 additions & 1 deletion test/test_locally_connected2d_layer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ program test_locally_connected2d_layer
select type(this_layer => input_layer % p); type is(input2d_layer)
call this_layer % set(sample_input)
end select
deallocate(sample_input)

call locally_connected_1d_layer % forward(input_layer)
call locally_connected_1d_layer % get_output(output)
Expand All @@ -67,11 +68,33 @@ program test_locally_connected2d_layer
write(stderr, '(a)') 'locally_connected2d layer with zero input and sigmoid function must forward to all 0.5.. failed'
end if

! Minimal locally_connected_1d layer: 1 channel, 3x3 pixel image, stride = 3;
allocate(sample_input(1, 17))
sample_input = 0

input_layer = input(1, 17)
locally_connected_1d_layer = locally_connected(filters, kernel_size, stride = 3)
call locally_connected_1d_layer % init(input_layer)

select type(this_layer => input_layer % p); type is(input2d_layer)
call this_layer % set(sample_input)
end select
deallocate(sample_input)

call locally_connected_1d_layer % forward(input_layer)
call locally_connected_1d_layer % get_output(output)

if (.not. all(abs(output) < tolerance)) then
ok = .false.
write(stderr, '(a)') 'locally_connected2d layer with zero input and sigmoid function must forward to all 0.5.. failed'
end if

!Final
if (ok) then
print '(a)', 'test_locally_connected2d_layer: All tests passed.'
else
write(stderr, '(a)') 'test_locally_connected2d_layer: One or more tests failed.'
stop 1
end if

end program test_locally_connected2d_layer