closest_color_name Subroutine

public subroutine closest_color_name(r, g, b, closestname)

NAME

 closest_color_name(3f) - [M_pixel:COLOR] returns the closest name
 for the given RGB values.
 (LICENSE:PD)

SYNOPSIS

subroutine closest_color_name(r,g,b,closestname)

 real,intent(in)               :: r,g,b
 character(len=20),intent(out) :: closestname

DESCRIPTION

 closest_color_name() returns the closest name for the given RGB
 values. Most X11 Windows color names are supported.

OPTIONS

 R   red component, range of 0 to 100
 G   green component, range of 0 to 100
 B   blue component, range of 0 to 100

RETURNS

 CLOSESTNAME   name of color found closest to given RGB value</li>

EXAMPLE

Sample program

    program demo_closest_color_name
    use M_pixel, only : closest_color_name
    implicit none
    character(len=100) :: string ! at least 20 characters
       string=' '

       call closest_color_name(100.0,  0.0,  0.0,string)
       write(*,*)trim(string)

       call closest_color_name(  0.0,100.0,  0.0,string)
       write(*,*)trim(string)

       call closest_color_name(  0.0,  0.0,100.0,string)
       write(*,*)trim(string)

    end program demo_closest_color_name

Results:

    red
    green
    blue

AUTHOR

John S. Urban

LICENSE

Public Domain

Arguments

Type IntentOptional Attributes Name
real, intent(in) :: r
real, intent(in) :: g
real, intent(in) :: b
character(len=*), intent(out) :: closestname

Contents

Source Code


Source Code

SUBROUTINE closest_color_name(r,g,b,closestname)

! ident_72="@(#) M_pixel closest_color_name(3f) given RGB values try to find closest named color"

real,intent(in)               :: r,g,b
character(len=*),intent(out) :: closestname
real                          :: rn,gn,bn
real                          :: distance, minimum_distance
character(len=20)             :: echoname
integer                       :: i
!-----------------------------------------------------------------------------------------------------------------------------------
   minimum_distance=1000.0
   closestname='Unknown'
   INFINITE: do i=1,1000
      call color_name2rgb(i2s(i),rn,gn,bn,echoname)       ! get next color
      if(echoname.eq.'Unknown') exit INFINITE
      distance=sqrt( (r-rn)**2 + (g-gn)**2 + (b-bn)**2 )
      if(distance.lt.minimum_distance)then
         closestname=echoname
         minimum_distance=min(minimum_distance,distance)
      endif
   enddo INFINITE
end SUBROUTINE closest_color_name