query_2lsom Subroutine

public subroutine query_2lsom(kohonen_map, input_pattern, sample_index)

Function to find the input samples associated with specific vector

Type Bound

two_level_self_organizing_map

Arguments

Type IntentOptional Attributes Name
class(two_level_self_organizing_map) :: kohonen_map

A two_level_self_organizing_map object

real(kind=wp), intent(inout), dimension(:,:) :: input_pattern

A real array

integer, allocatable :: sample_index(:)

An integer array


Calls

proc~~query_2lsom~~CallsGraph proc~query_2lsom two_level_self_organizing_map%query_2lsom none~get_prototype kohonen_prototype%get_prototype proc~query_2lsom->none~get_prototype

Variables

Type Visibility Attributes Name Initial
integer, public :: ix
integer, public :: iy
integer, public :: iz
integer, public :: ihit
integer, public :: jhit
integer, public :: khit
integer, public :: ivar1
integer, public :: ivar2
integer, public :: nvar1
integer, public :: nvar2
integer, public :: number_patterns
integer, public :: ipat
integer, public :: ierr
integer, public :: number_selected
integer, public :: i
integer, public :: pos
integer, public :: ic
integer, public :: number_samples
real(kind=wp), public, dimension(kohonen_map%parameters(1)%number_variables1, kohonen_map%parameters(1)%number_variables2) :: current_values
real(kind=wp), public, dimension(kohonen_map%parameters(1)%number_variables1, kohonen_map%parameters(1)%number_variables2) :: centers
real(kind=wp), public :: dist
real(kind=wp), public :: dist_min
integer, public, dimension(size(kohonen_map%cells_index,1)) :: position
integer, public, dimension(size(kohonen_map%cells_index,1)) :: real_position

Source Code

   subroutine query_2lsom(kohonen_map,input_pattern,sample_index) !,output_patterns)
   !========================================================================================
!!  Function to find the input samples associated with specific vector 
      class(two_level_self_organizing_map) :: kohonen_map
!! A `two_level_self_organizing_map` object
      real(kind=wp),dimension(:,:),intent(inout) :: input_pattern
!! A real array
      integer,allocatable :: sample_index(:)
!! An integer array
      integer :: ix,iy,iz,ihit,jhit,khit,ivar1,ivar2,nvar1,nvar2,number_patterns,ipat,ierr
      integer :: number_selected,i,pos,ic,number_samples
      real(kind=wp),dimension(kohonen_map%parameters(1)%number_variables1,&
      kohonen_map%parameters(1)%number_variables2) ::current_values,centers
      real(kind=wp) :: dist,dist_min
      integer,dimension(size(kohonen_map%cells_index,1)) :: position,real_position
   ! 
      do ic=1,size(kohonen_map%cluster_layer);
         !write(unit1,*) 'Cluster= ',ic
         !call kohonen_map%cluster_layer(ic)%print(unit1);
         call kohonen_map%cluster_layer(ic)%get_prototype(centers);
         !centers1(:,ic)=centers(:)
         dist_min=1.0d5;
         dist=0.0_wp;
         do ix=1,size(centers,1);
            do iy=1,size(centers,2);
               if(input_pattern(ix,iy) > 0.0_wp) then
                  dist=dist+(input_pattern(ix,iy)-centers(ix,iy))**2
               endif
            enddo
         enddo
         if(dist < dist_min) then
            dist_min=dist;
            ihit=ic;
         endif
         number_samples=kohonen_map%number_cluster_samples(ihit);
         if(number_samples .gt. 0) then
            allocate(sample_index(number_samples),stat=ierr);
            sample_index=kohonen_map%index_cluster_samples(ihit,1:number_samples);
         else 
            write(*,*) 'WARNING: Empty query'
            return
         endif
      enddo!ic
   !
   end subroutine query_2lsom