kohonen_map_base_utilities.f90 Source File

This module defines an abstract class for kohonen maps


This file depends on

sourcefile~~kohonen_map_base_utilities.f90~~EfferentGraph sourcefile~kohonen_map_base_utilities.f90 kohonen_map_base_utilities.f90 sourcefile~kohonen_layer_parameters_utilities.f90 kohonen_layer_parameters_utilities.f90 sourcefile~kohonen_map_base_utilities.f90->sourcefile~kohonen_layer_parameters_utilities.f90 sourcefile~kohonen_pattern_utilities.f90 kohonen_pattern_utilities.f90 sourcefile~kohonen_map_base_utilities.f90->sourcefile~kohonen_pattern_utilities.f90 sourcefile~precision_utilities.f90 precision_utilities.f90 sourcefile~kohonen_map_base_utilities.f90->sourcefile~precision_utilities.f90 sourcefile~kohonen_layer_parameters_utilities.f90->sourcefile~precision_utilities.f90 sourcefile~constants_utilities.f90 constants_utilities.f90 sourcefile~kohonen_layer_parameters_utilities.f90->sourcefile~constants_utilities.f90 sourcefile~kohonen_pattern_utilities.f90->sourcefile~precision_utilities.f90 sourcefile~kohonen_pattern_utilities.f90->sourcefile~constants_utilities.f90 sourcefile~kohonen_prototype_utilities.f90 kohonen_prototype_utilities.f90 sourcefile~kohonen_pattern_utilities.f90->sourcefile~kohonen_prototype_utilities.f90 sourcefile~constants_utilities.f90->sourcefile~precision_utilities.f90 sourcefile~kohonen_prototype_utilities.f90->sourcefile~precision_utilities.f90 sourcefile~kohonen_prototype_utilities.f90->sourcefile~constants_utilities.f90 sourcefile~distance_base_utilities.f90 distance_base_utilities.f90 sourcefile~kohonen_prototype_utilities.f90->sourcefile~distance_base_utilities.f90 sourcefile~distance_base_utilities.f90->sourcefile~precision_utilities.f90

Files dependent on this one

sourcefile~~kohonen_map_base_utilities.f90~~AfferentGraph sourcefile~kohonen_map_base_utilities.f90 kohonen_map_base_utilities.f90 sourcefile~kohonen_layer_utilities.f90 kohonen_layer_utilities.f90 sourcefile~kohonen_layer_utilities.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~multilayer_self_organizing_map_utilities.f90 multilayer_self_organizing_map_utilities.f90 sourcefile~multilayer_self_organizing_map_utilities.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~self_organizing_map_utilities.f90 self_organizing_map_utilities.f90 sourcefile~self_organizing_map_utilities.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~som_predict_variables.f90 som_predict_variables.f90 sourcefile~som_predict_variables.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~som_predict_variables.f90->sourcefile~self_organizing_map_utilities.f90 sourcefile~som_train_variables.f90 som_train_variables.f90 sourcefile~som_train_variables.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~som_train_variables.f90->sourcefile~self_organizing_map_utilities.f90 sourcefile~two_level_self_organizing_map_utilities.f90 two_level_self_organizing_map_utilities.f90 sourcefile~two_level_self_organizing_map_utilities.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~two_level_som_estimate_variables.f90 two_level_som_estimate_variables.f90 sourcefile~two_level_som_estimate_variables.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~two_level_som_estimate_variables.f90->sourcefile~two_level_self_organizing_map_utilities.f90 sourcefile~two_level_som_train_variables.f90 two_level_som_train_variables.f90 sourcefile~two_level_som_train_variables.f90->sourcefile~kohonen_map_base_utilities.f90 sourcefile~two_level_som_train_variables.f90->sourcefile~two_level_self_organizing_map_utilities.f90

Source Code

!! author: Oscar Garcia-Cabrejo
!! date: 12/04/2024
!! version: 0.1
!! This module defines an abstract class for kohonen maps
module kohonen_map_base_utilities
!! This module defines an abstract class for kohonen maps
use precision_utilities, only: wp;
use kohonen_layer_parameters_utilities, only: kohonen_layer_parameters;
use kohonen_pattern_utilities, only: kohonen_pattern;
!
implicit none
!
type,abstract :: kohonen_map_base
!! Abstract Class to represent a template for a kohonen map
  contains
    procedure(kohonen_map_constructor),public,deferred :: create
    procedure(kohonen_map_destructor),public,deferred :: destroy
    procedure(kohonen_map_function1),public,deferred :: train 
    procedure(kohonen_map_function2),public,deferred :: predict
end type kohonen_map_base
!!
abstract interface
!========================================================================================
  subroutine kohonen_map_constructor(kohonen_map,training_parameters)
!========================================================================================
!! Template function for the constructor of a kohonen map
    import :: kohonen_map_base
    import :: kohonen_layer_parameters
!! Import section
    class(kohonen_map_base) :: kohonen_map
!! A `kohonen_map_base` object
    type(kohonen_layer_parameters),dimension(:) :: training_parameters
!! A `kohonen_layer_parameters` object
  end subroutine kohonen_map_constructor
!========================================================================================
  subroutine kohonen_map_destructor(kohonen_map)
!========================================================================================
!! Template function for the destructor of a kohonen map
    import :: kohonen_map_base
!! Import section
    class(kohonen_map_base) :: kohonen_map
!! A `kohonen_map_base` object
  end subroutine kohonen_map_destructor
!========================================================================================
  subroutine kohonen_map_function1(kohonen_map,input_data)
!========================================================================================
!!   Template function for the training function of a kohonen map
    import :: kohonen_map_base
    import :: kohonen_pattern
!! import section
    class(kohonen_map_base) :: kohonen_map
!! A `kohonen_map_base` object
    type(kohonen_pattern),dimension(:),intent(inout) :: input_data
!! An array of `kohonen_pottern` objects
  end subroutine kohonen_map_function1
!========================================================================================
  subroutine kohonen_map_function2(kohonen_map,input_data,map_output)
!========================================================================================
!!   Template function for the prediction function of a kohonen map
    import :: kohonen_map_base
    import :: kohonen_pattern
!! import section
    class(kohonen_map_base) :: kohonen_map
!! A `kohonen_map_base` object
    type(kohonen_pattern),dimension(:),intent(inout) :: input_data
!! An array of `kohonen_pottern` objects
    integer,dimension(:,:),intent(out) :: map_output
!! An integer array
  end subroutine kohonen_map_function2
!
end interface
!
end module kohonen_map_base_utilities