[R] hcl()

Martin Maechler maechler at stat.math.ethz.ch
Fri Jun 24 14:26:52 CEST 2005


I have written a nice (IMO) function that lets you explore the
hcl space quite nicely, and show its calls.

hcl.wheel <-
    function(chroma = 35, lums = 0:100, hues = 1:360, asp = 1,
             p.cex = 0.6, do.label = FALSE, rev.lum = FALSE,
             fixup = TRUE)
{
    ## Purpose: show chroma "sections" of hcl() color space; see  ?hcl
    ## ----------------------------------------------------------------------
    ## Arguments: chroma: can be vector -> multiple plots are done,
    ##            lums, hues, fixup : all corresponding to hcl()'s args
    ##            rev.lum: logical indicating if luminance
    ## 			should go from outer to inner
    ## ----------------------------------------------------------------------
    ## Author: Martin Maechler, Date: 24 Jun 2005

    stopifnot(is.numeric(lums), lums >= 0, lums <= 100,
              is.numeric(hues), hues >= 0, hues <= 360,
              is.numeric(chroma), chroma >= 0, (nch <- length(chroma)) >= 1)
    if(is.unsorted(hues)) hues <- sort(hues)
    if(nch > 1) {
        op <- par(mfrow= n2mfrow(nch), mar = c(0,0,0,0))
        on.exit(par(op))
    }
    for(i.c in 1:nch) {
        plot(-1:1,-1:1, type="n", axes = FALSE, xlab="",ylab="", asp = asp)
        ## main = sprintf("hcl(h = <angle>, c = %g)", chroma[i.c]),
        text(0.4, 0.99, paste("chroma =", format(chroma[i.c])),
             adj = 0, font = 4)
        l.s <- (if(rev.lum) rev(lums) else lums) / max(lums) # <= 1
        for(ang in hues) { # could do all this using outer() instead of for()...
            a. <- ang * pi/180
            z.a <- exp(1i * a.)
            cols <- hcl(ang, c = chroma[i.c], l = lums, fixup = fixup)
            points(l.s * z.a, pch = 16, col = cols, cex = p.cex)
            ##if(do."text") : draw the 0,45,90,... angle "lines"
            if(do.label)
                text(z.a*1.05, labels = ang, col = cols[length(cols)/2],
                     srt = ang)
        }
        if(!fixup) ## show the outline
            lines(exp(1i * hues * pi/180))
   }
   invisible()
}

##-- and now a few interesting calls

hcl.wheel() # and watch it redraw when you fiddle with the graphic window
hcl.wheel(rev.lum= TRUE) # dito
hcl.wheel(do.lab = TRUE) # dito


## Now watch:
hcl.wheel(ch = c(25,35,45,55))

hcl.wheel(ch = seq(10, 90, by = 10), p.cex = 0.4)
hcl.wheel(ch = seq(10, 90, by = 10), p.cex = 0.3, fixup = FALSE)
hcl.wheel(ch = seq(10, 90, by = 10), p.cex = 0.3, rev.lum = TRUE)
x11() # new device -- in order to compare with previous :
hcl.wheel(ch = seq(10, 90, by = 10), p.cex = 0.3, rev.lum = TRUE, fixup=FALSE)

## the last two, in my eyes show that
## 1) fixup = TRUE {the default!} works quite nicely in most cases
## 2) Robin's original problem was a sample of a much larger "problem"
##    where IMO the 'fixup' algorithm ``breaks down'' and I
##    think should be improvable.

Martin Maechler, ETH Zurich


>>>>> "Robin" == Robin Hankin <r.hankin at noc.soton.ac.uk>
>>>>>     on Fri, 24 Jun 2005 11:32:49 +0100 writes:

    Robin> Professor Ripley thanks for this.

    >>>

    >>> plot(1:50,pch=16,col=hcl(h=240, c=50, l=1:50))
    >>> 
    >>> I get mostly blue, but also some red, dots.  Note that
    >>> h=240 throughout.  If 240 is blue, how come there's a
    >>> red dot there?  Or is it just my monitor?
    >>

    >>> hcl(h=240, c=50, l=1:50, fixup=F)
    >> [1] NA NA NA NA NA NA NA [8] NA NA NA NA NA NA NA [15] NA
    >> NA NA NA NA NA NA [22] NA NA NA NA NA NA NA [29] NA NA NA
    >> NA NA NA NA [36] NA NA NA "#08628E" "#126490" "#196693"
    >> "#1F6995" [43] "#246B97" "#286E9A" "#2D709C" "#31729F"
    >> "#3575A1" "#3877A4" "#3C7AA6" [50] "#3F7CA9"
    >> 
    >> You have mainly used invalid values: you cannot have high
    >> chroma and low luminance (and there are warnings to that
    >> effect on the help page).
    >> 
    >> Not sure the chosen mapping of out-of-gamut specs onto
    >> the sRGB gamut is particularly helpful, though.
    >> 


    Robin> Yes, this is what I was missing: with fixup taking
    Robin> its default value of TRUE, out-of-range combinations
    Robin> are silently mapped to real RGB values, [although the
    Robin> description of argument fixup in the manpage conveys
    Robin> this information to me only now that I have your
    Robin> example above to look at].

    Robin>   If I understand your comment, my odd-looking
    Robin> colours are a result of this mapping.

    Robin> So, how best to determine the maximum chroma for a
    Robin> given luminance and hue?




    Robin> -- Robin Hankin Uncertainty Analyst National
    Robin> Oceanography Centre, Southampton European Way,
    Robin> Southampton SO14 3ZH, UK tel 023-8059-7743

    Robin> ______________________________________________
    Robin> R-help at stat.math.ethz.ch mailing list
    Robin> https://stat.ethz.ch/mailman/listinfo/r-help PLEASE
    Robin> do read the posting guide!
    Robin> http://www.R-project.org/posting-guide.html


    Robin> !DSPAM:42bbe27a59521197013008!




More information about the R-help mailing list