trainable_network_m.f90 Source File


This file depends on

sourcefile~~trainable_network_m.f90~~EfferentGraph sourcefile~trainable_network_m.f90 trainable_network_m.f90 sourcefile~input_output_pair_m.f90 input_output_pair_m.f90 sourcefile~trainable_network_m.f90->sourcefile~input_output_pair_m.f90 sourcefile~kind_parameters_m.f90 kind_parameters_m.f90 sourcefile~trainable_network_m.f90->sourcefile~kind_parameters_m.f90 sourcefile~mini_batch_m.f90 mini_batch_m.f90 sourcefile~trainable_network_m.f90->sourcefile~mini_batch_m.f90 sourcefile~neural_network_m.f90 neural_network_m.f90 sourcefile~trainable_network_m.f90->sourcefile~neural_network_m.f90 sourcefile~tensor_map_m.f90 tensor_map_m.f90 sourcefile~trainable_network_m.f90->sourcefile~tensor_map_m.f90 sourcefile~training_configuration_m.f90 training_configuration_m.f90 sourcefile~trainable_network_m.f90->sourcefile~training_configuration_m.f90 sourcefile~input_output_pair_m.f90->sourcefile~kind_parameters_m.f90 sourcefile~tensor_m.f90 tensor_m.f90 sourcefile~input_output_pair_m.f90->sourcefile~tensor_m.f90 sourcefile~mini_batch_m.f90->sourcefile~input_output_pair_m.f90 sourcefile~mini_batch_m.f90->sourcefile~kind_parameters_m.f90 sourcefile~neural_network_m.f90->sourcefile~kind_parameters_m.f90 sourcefile~neural_network_m.f90->sourcefile~mini_batch_m.f90 sourcefile~neural_network_m.f90->sourcefile~tensor_map_m.f90 sourcefile~activation_m.f90 activation_m.f90 sourcefile~neural_network_m.f90->sourcefile~activation_m.f90 sourcefile~double_precision_file_m.f90 double_precision_file_m.f90 sourcefile~neural_network_m.f90->sourcefile~double_precision_file_m.f90 sourcefile~metadata_m.f90 metadata_m.f90 sourcefile~neural_network_m.f90->sourcefile~metadata_m.f90 sourcefile~neural_network_m.f90->sourcefile~tensor_m.f90 sourcefile~tensor_map_m.f90->sourcefile~kind_parameters_m.f90 sourcefile~double_precision_string_m.f90 double_precision_string_m.f90 sourcefile~tensor_map_m.f90->sourcefile~double_precision_string_m.f90 sourcefile~tensor_map_m.f90->sourcefile~tensor_m.f90 sourcefile~training_configuration_m.f90->sourcefile~kind_parameters_m.f90 sourcefile~training_configuration_m.f90->sourcefile~activation_m.f90 sourcefile~training_configuration_m.f90->sourcefile~double_precision_file_m.f90 sourcefile~hyperparameters_m.f90 hyperparameters_m.f90 sourcefile~training_configuration_m.f90->sourcefile~hyperparameters_m.f90 sourcefile~network_configuration_m.f90 network_configuration_m.f90 sourcefile~training_configuration_m.f90->sourcefile~network_configuration_m.f90 sourcefile~tensor_names_m.f90 tensor_names_m.f90 sourcefile~training_configuration_m.f90->sourcefile~tensor_names_m.f90 sourcefile~double_precision_file_m.f90->sourcefile~double_precision_string_m.f90 sourcefile~hyperparameters_m.f90->sourcefile~kind_parameters_m.f90 sourcefile~hyperparameters_m.f90->sourcefile~double_precision_string_m.f90 sourcefile~metadata_m.f90->sourcefile~double_precision_string_m.f90 sourcefile~network_configuration_m.f90->sourcefile~double_precision_string_m.f90 sourcefile~tensor_m.f90->sourcefile~kind_parameters_m.f90

Files dependent on this one

sourcefile~~trainable_network_m.f90~~AfferentGraph sourcefile~trainable_network_m.f90 trainable_network_m.f90 sourcefile~fiats_m.f90 fiats_m.f90 sourcefile~fiats_m.f90->sourcefile~trainable_network_m.f90 sourcefile~trainable_network_s.f90 trainable_network_s.f90 sourcefile~trainable_network_s.f90->sourcefile~trainable_network_m.f90 sourcefile~concurrent-inferences.f90 concurrent-inferences.f90 sourcefile~concurrent-inferences.f90->sourcefile~fiats_m.f90 sourcefile~learn-addition.f90 learn-addition.F90 sourcefile~learn-addition.f90->sourcefile~fiats_m.f90 sourcefile~learn-exponentiation.f90 learn-exponentiation.F90 sourcefile~learn-exponentiation.f90->sourcefile~fiats_m.f90 sourcefile~learn-multiplication.f90 learn-multiplication.F90 sourcefile~learn-multiplication.f90->sourcefile~fiats_m.f90 sourcefile~learn-power-series.f90 learn-power-series.F90 sourcefile~learn-power-series.f90->sourcefile~fiats_m.f90 sourcefile~learn-saturated-mixing-ratio.f90 learn-saturated-mixing-ratio.F90 sourcefile~learn-saturated-mixing-ratio.f90->sourcefile~fiats_m.f90 sourcefile~saturated_mixing_ratio_m.f90 saturated_mixing_ratio_m.f90 sourcefile~learn-saturated-mixing-ratio.f90->sourcefile~saturated_mixing_ratio_m.f90 sourcefile~print-training-configuration.f90 print-training-configuration.F90 sourcefile~print-training-configuration.f90->sourcefile~fiats_m.f90 sourcefile~read-query-infer.f90 read-query-infer.f90 sourcefile~read-query-infer.f90->sourcefile~fiats_m.f90 sourcefile~saturated_mixing_ratio_m.f90->sourcefile~fiats_m.f90 sourcefile~train-and-write.f90 train-and-write.F90 sourcefile~train-and-write.f90->sourcefile~fiats_m.f90 sourcefile~write-read-infer.f90 write-read-infer.F90 sourcefile~write-read-infer.f90->sourcefile~fiats_m.f90

Source Code

! Copyright (c), The Regents of the University of California
! Terms of use are as specified in LICENSE.txt

module trainable_network_m
  use neural_network_m, only : neural_network_t, workspace_t
  use input_output_pair_m, only : input_output_pair_t
  use julienne_m, only : string_t
  use kind_parameters_m, only : default_real
  use mini_batch_m, only : mini_batch_t
  use training_configuration_m, only : training_configuration_t
  use tensor_map_m, only : tensor_map_t
  implicit none

  private
  public :: trainable_network_t 

  type, extends(neural_network_t) ::  trainable_network_t(m)
    integer, kind :: m = default_real
    private
    type(workspace_t), private :: workspace_
  contains
    generic :: train           => default_real_train                   
    procedure, private, non_overridable :: default_real_train
    generic ::   map_to_training_ranges => default_real_map_to_training_ranges
    procedure, private, non_overridable :: default_real_map_to_training_ranges
  end type

  interface trainable_network_t 

    pure module function default_real_network(neural_network) result(trainable_network)
      implicit none
      type(neural_network_t), intent(in) :: neural_network
      type(trainable_network_t) trainable_network
    end function 

    module function perturbed_identity_network(training_configuration, perturbation_magnitude, metadata, input_map, output_map) &
      result(trainable_network)
      implicit none
      type(training_configuration_t), intent(in) :: training_configuration
      real, intent(in) :: perturbation_magnitude
      type(string_t), intent(in) :: metadata(:)
      type(tensor_map_t) input_map, output_map
      type(trainable_network_t) trainable_network
    end function

  end interface

  interface

    pure module subroutine default_real_train(self, mini_batches_arr, cost, adam, learning_rate)
      implicit none
      class(trainable_network_t), intent(inout) :: self
      type(mini_batch_t), intent(in) :: mini_batches_arr(:)
      real, intent(out), allocatable, optional :: cost(:)
      logical, intent(in) :: adam
      real, intent(in) :: learning_rate
    end subroutine

    elemental module function default_real_map_to_training_ranges(self, input_output_pair) result(normalized_input_output_pair)
      implicit none
      class(trainable_network_t), intent(in) :: self
      type(input_output_pair_t), intent(in) :: input_output_pair
      type(input_output_pair_t) normalized_input_output_pair
    end function

  end interface

end module trainable_network_m