Skip to content
Open
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_conv1d_layer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module nf_conv1d_layer
integer :: channels
integer :: kernel_size
integer :: filters
integer :: stride

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

interface conv1d_layer
module function conv1d_layer_cons(filters, kernel_size, activation) &
module function conv1d_layer_cons(filters, kernel_size, activation, stride) &
result(res)
!! `conv1d_layer` constructor function
integer, intent(in) :: filters
integer, intent(in) :: kernel_size
class(activation_function), intent(in) :: activation
integer, intent(in) :: stride
type(conv1d_layer) :: res
end function conv1d_layer_cons
end interface conv1d_layer
Expand Down
26 changes: 14 additions & 12 deletions src/nf/nf_conv1d_layer_submodule.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,17 @@

contains

module function conv1d_layer_cons(filters, kernel_size, activation) result(res)
module function conv1d_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(conv1d_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 conv1d_layer_cons

Expand All @@ -25,7 +27,7 @@ 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 + 1) / self % stride

! Output of shape: filters x width
allocate(self % output(self % filters, self % width))
Expand Down Expand Up @@ -68,12 +70,12 @@ pure module subroutine forward(self, input)
do j = 1, self % width
! Compute the input window corresponding to output index j.
! In forward: center index = j + half_window, so window = indices j to j+kernel_size-1.
iws = j
iwe = j + self % kernel_size - 1
iws = self % stride * (j-1) + 1
iwe = max(iws + self % kernel_size - 1, input_width)

! For each filter, compute the convolution (inner product over channels and kernel width).
do concurrent (n = 1:self % filters)
self % z(n, j) = sum(self % kernel(n,:,:) * input(:,iws:iwe))
self % z(n, j) = sum(self % kernel(n,:,1:iwe-iws+1) * input(:,iws:iwe))
end do

! Add the bias for each filter.
Expand All @@ -92,7 +94,7 @@ pure module subroutine backward(self, input, gradient)
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

Expand All @@ -104,7 +106,6 @@ pure module subroutine backward(self, input, gradient)
! Determine dimensions.
input_channels = size(input, dim=1)
input_width = size(input, dim=2)
output_width = self % width ! Note: output_width = input_width - kernel_size + 1

!--- Compute the local gradient gdz = (dL/dy) * sigma'(z) for each output.
gdz = gradient * self % activation % eval_prime(self % z)
Expand All @@ -120,14 +121,15 @@ pure module subroutine backward(self, input, gradient)
! In the forward pass the window for output index j was:
! iws = j, iwe = j + kernel_size - 1.
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 = max(iws + self % kernel_size - 1, input_width)

do k = 1, self % channels
! Weight gradient: accumulate contribution from the input window.
dw_local(n,k,:) = dw_local(n,k,:) + input(k,iws:iwe) * gdz(n,j)
dw_local(n,k,1:iws-iwe+1) = dw_local(n,k,1:iws-iwe+1) + input(k,iws:iwe) * gdz(n,j)
! Input gradient: propagate gradient back to the input window.
self % gradient(k,iws:iwe) = self % gradient(k,iws:iwe) + self % kernel(n,k,:) * gdz(n,j)
self % gradient(k,iws:iwe) = self % gradient(k,iws:iwe) + self % kernel(n,k,1:iws-iwe+1) * gdz(n,j)
end do
end do
end do
Expand Down
4 changes: 3 additions & 1 deletion src/nf/nf_conv2d_layer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module nf_conv2d_layer
integer :: channels
integer :: kernel_size
integer :: filters
integer :: stride(2)

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

interface conv2d_layer
module function conv2d_layer_cons(filters, kernel_size, activation) &
module function conv2d_layer_cons(filters, kernel_size, activation, stride) &
result(res)
!! `conv2d_layer` constructor function
integer, intent(in) :: filters
integer, intent(in) :: kernel_size
class(activation_function), intent(in) :: activation
integer, intent(in) :: stride(:)
type(conv2d_layer) :: res
end function conv2d_layer_cons
end interface conv2d_layer
Expand Down
8 changes: 5 additions & 3 deletions src/nf/nf_conv2d_layer_submodule.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,16 +7,18 @@

contains

module function conv2d_layer_cons(filters, kernel_size, activation) result(res)
module function conv2d_layer_cons(filters, kernel_size, activation, stride) result(res)
implicit none
integer, intent(in) :: filters
integer, intent(in) :: kernel_size
class(activation_function), intent(in) :: activation
integer, intent(in) :: stride(:)
type(conv2d_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 conv2d_layer_cons
Expand All @@ -28,8 +30,8 @@ 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 % height = input_shape(3) - self % kernel_size + 1
self % width = (input_shape(2) - self % kernel_size + 1) / self % stride(1)
self % height = (input_shape(3) - self % kernel_size + 1) / self % stride(2)

! Output of shape filters x width x height
allocate(self % output(self % filters, self % width, self % height))
Expand Down
8 changes: 6 additions & 2 deletions src/nf/nf_layer_constructors.f90
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ end function input3d

interface conv

module function conv1d(filters, kernel_width, activation) result(res)
module function conv1d(filters, kernel_width, activation, stride) result(res)
!! 1-d convolutional layer constructor.
!!
!! This layer is for building 1-d convolutional network.
Expand All @@ -117,11 +117,13 @@ module function conv1d(filters, kernel_width, 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
!! Stride length of the convolution
type(layer) :: res
!! Resulting layer instance
end function conv1d

module function conv2d(filters, kernel_width, kernel_height, activation) result(res)
module function conv2d(filters, kernel_width, kernel_height, activation, stride) result(res)
!! 2-d convolutional layer constructor.
!!
!! This layer is for building 2-d convolutional network.
Expand All @@ -147,6 +149,8 @@ module function conv2d(filters, kernel_width, kernel_height, activation) result(
!! Height of the convolution window, commonly 3 or 5
class(activation_function), intent(in), optional :: activation
!! Activation function (default sigmoid)
integer, intent(in), optional :: stride(:)
!! Stride length of the convolution
type(layer) :: res
!! Resulting layer instance
end function conv2d
Expand Down
33 changes: 29 additions & 4 deletions src/nf/nf_layer_constructors_submodule.f90
Original file line number Diff line number Diff line change
Expand Up @@ -23,14 +23,19 @@

contains

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

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

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

res % name = 'conv1d'

if (present(activation)) then
Expand All @@ -41,20 +46,28 @@ module function conv1d(filters, kernel_width, activation) result(res)

res % activation = activation_tmp % get_name()

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

allocate( &
res % p, &
source=conv1d_layer(filters, kernel_width, activation_tmp) &
source=conv1d_layer(filters, kernel_width, activation_tmp, stride_tmp) &
)

end function conv1d

module function conv2d(filters, kernel_width, kernel_height, activation) result(res)
module function conv2d(filters, kernel_width, kernel_height, activation, stride) result(res)
integer, intent(in) :: filters
integer, intent(in) :: kernel_width
integer, intent(in) :: kernel_height
class(activation_function), intent(in), optional :: activation
integer, intent(in), optional :: stride(:)
type(layer) :: res

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

! Enforce kernel_width == kernel_height for now;
Expand All @@ -63,6 +76,12 @@ module function conv2d(filters, kernel_width, kernel_height, activation) result(
if (kernel_width /= kernel_height) &
error stop 'kernel_width must equal kernel_height in a conv2d layer'

if (size(stride) /= 2 ) &
error stop 'size of stride must be equal to 2 in a conv2d layer'

if (stride(1) < 1 .or. stride(2) < 1) &
error stop 'stride must be >= 1 in a conv2d layer'

res % name = 'conv2d'

if (present(activation)) then
Expand All @@ -73,9 +92,15 @@ module function conv2d(filters, kernel_width, kernel_height, activation) result(

res % activation = activation_tmp % get_name()

if (present(stride)) then
stride_tmp = stride
else
stride_tmp = [1, 1]
endif

allocate( &
res % p, &
source=conv2d_layer(filters, kernel_width, activation_tmp) &
source=conv2d_layer(filters, kernel_width, activation_tmp, stride) &
)

end function conv2d
Expand Down
Loading