ForColormap, a Fortran library for colormaps šŸŒˆ

ForColormap is a small fpm library, independent of any graphical toolkit, to convert a real value to RGB values using various colormaps. You can test it without any graphical library as the fpm run --example demo command will generate PPM files for each available colormap (see below). Any comment or help about that project are welcome (OOP, API, etc.).

I first worked on my own colormaps during my Ph.D. (at the end of the last century) but my colormaps were all built intuitively. I had read Why Should Engineers and Scientists Be Worried About Color? on the IBM Research site in 2005 but finally did not deepened the subject, until I recently reread @rgba comments about colormaps (Sept. 2022). ForColormap includes my own naive colormaps (except a few ones using code uncompatible with MIT license), the Dave Greenā€™s cubehelix colormap, and finally 62 of the Scientific Colour Maps by Fabio Crameri.

The basic usage, assuming your graphical library has a setpixelgb() function and your z values are in the [0, 2] range, is typically:

	use forcolormap
...
	type(Colormap) :: cmap
	integer  :: red, green, blue
	real(wp) :: z, x, y
...
	call cmap%set("glasgow", 0.0_wp, 2.0_wp)
...
	z = f(x,y)
	call cmap%compute_RGB(z, red, green, blue)
	call setpixelrgb(x, y, red, green, blue)

You can also create your own colormap or load one (a text file containing lines of RGB triplets separated by spaces). See the example\demo.f90 file.

P.s. I have noticed the M_color project by @urbanjost, which could probably be useful for people interested in creating new colormaps, and also the forimage project developed by @Ali for reading and writing PPM files, which could take advantage of ForColormap.

30 Likes

Life feels much more colorful now! Definetely will use it in my astrophotography program. Cheers!

3 Likes

The Cubehelix colormap seems to be a reference in that domain:

This colour scheme is now recommended in the Graphics Guide for authors from the American Astronomical Society (although, bizarrely, they decided to call it ā€˜cube-helixā€™ with a hyphen).

Nice, I was thinking that I should implement some predefined palettes for my Fortran image library (which is about to be released soon.) No need anymore. :slight_smile:

Just a remark though, many C libraries expect colormaps to be arrays of unsigned bytes. There is no such a thing in Fortran but integer(kind=1) works well, except you need a conversion function from kind=1 to normal integers to print them, and vice versa to assign values to colormaps. I can easily convert your colormaps to this format since the conversion functions are recursive. But maybe such functionality should be added in ForColormap, something like a public class function get_map_bytes, which will return self%map converted in a kind=1 integer array?

1 Like

colormap resembling the color changes in red cabbage (containing Anthocyanins) with pH
cabagge_map

integer, dimension(0:7, 3) :: my_colormap = reshape( [ & 
    198,    29,    32,   &   
    189,    21,    56,   &   
    171,    82,   150,   &   
    102,    81,   156,   &   
     38,    53,   108,   &   
      5,    65,    40,   &   
    221,   199,    44,   &   
    237,   191,    44 ], &
    shape(my_colormap), order = [2, 1] )
4 Likes

Nice work @vmagnin!

I first learned a few things about colormaps from the works of Kenneth Moreland and the choice of the default colormap in Paraview. Here are a few related blog posts:

I also like the colormaps in Matplotlib (Choosing Colormaps in Matplotlib ā€” Matplotlib 3.8.0 documentation) and the ones used in ColorBrewer. The latter are also available for gnuplot here: GitHub - aschn/gnuplot-colorbrewer: ColorBrewer color schemes for gnuplot

Here is a short Python script to export colormaps from Matplotlib. I didnā€™t do any tests yet with ForColormap, so apologies if any bugs remain. The usage should be self-explanatory:

$ ./export_mpl_cmap.py -h
usage: export_mpl_cmap [-h] [--list] [-t TABSIZE] [-o OUTPUT] [colormap]

Helper script to export matplotlib colormaps as Fortran arrays for use with ForColormap.

positional arguments:
  colormap              A valid Matplotlib colormap name.

optional arguments:
  -h, --help            show this help message and exit
  --list                List the available colormaps in Matplotlib and quit.
  -t TABSIZE, --tabsize TABSIZE
                        Size of the tab; default is 4.
  -o OUTPUT, --output OUTPUT
                        A destination file; defaults to stdout.
#!/usr/bin/env python
"""
export_mpl_cmap.py --
  Script for exporting Matplotlib colormaps as Fortran include blocks

Copyright (c) 2023 Ivan Pribec. All rights reserved.

This work is licensed under the terms of the MIT license.  
For a copy, see <https://opensource.org/licenses/MIT>.
"""
import matplotlib.pyplot as plt
import numpy as np

import matplotlib as mpl

def fortran_cmap(name,tabsize=4):
    """Exports a Matplotlib colormap as a Fortran block"""

    cmap = mpl.colormaps[name]

    header = "\tinteger, dimension(0:{N}, 1:3) :: {name} = reshape([ &\n"
    footer = "\t], shape({name}), order=[2,1] )\n"

    triplet = "{:3d},{:3d},{:3d}"

    block = header.format(N=cmap.N-1,name=name)

    for i in range(0,cmap.N,4):
        left = cmap.N - i
        line = ""
        if (left > 4):
            for k in range(4):
                (r,g,b,_) = cmap(i + k,bytes=True)
                line += "\t" + triplet.format(r,g,b) + ','
            line += " &\n"
        else:
            for k in range(left):
                (r,g,b,_) = cmap(i + k,bytes=True)
                sep = ',' if k < left-1 else ''
                line += "\t" + triplet.format(r,g,b) + sep
            line += "  &\n"
        block += line

    block += footer.format(name=name)

    return block

if __name__ == '__main__':
    
    import argparse
    import sys
    from textwrap import wrap

    parser = argparse.ArgumentParser(
        prog='export_mpl_cmap',
        description="""Helper script to export matplotlib colormaps 
        as Fortran arrays for use with ForColormap.""")

    parser.add_argument('--list',action='store_true',
        help="List the available colormaps in Matplotlib and quit.")

    parser.add_argument('-t', '--tabsize', default=4,
        help="Size of the tab; default is 4.")
    parser.add_argument('-o', '--output',
        type=argparse.FileType('w'),
        default=sys.stdout,
        help="A destination file; defaults to stdout.")

    parser.add_argument('colormap', nargs='?',
        help="A valid Matplotlib colormap name.")

    args = parser.parse_args()

    if args.list:
        print("The colormaps available are:\n")
        
        cmaps = list(filter(lambda x: not x.endswith('_r'), 
            mpl.pyplot.colormaps()))

        # Column width
        cw = len(max(cmaps,key=len)) + 3
        
        for a, b, c, d in zip(cmaps[0::4],cmaps[1::4],
            cmaps[2::4],cmaps[3::4]):

            print("  {:{cw}}{:{cw}}{:{cw}}{:{cw}}".format(a,b,c,d,cw=cw))

        print("\nAppend '_r' to the end of a colormap to obtain the reverse version.")
        print("\nFor more information visit:\n\n\t"
              "https://matplotlib.org/stable/users/explain/colors/colormaps.html\n")
    else:
        color_block = fortran_cmap(args.colormap,args.tabsize)
        with args.output as f:
            f.write(color_block)

4 Likes

Is there a synopsis which of them remain well discernible after passing a Xerox?

For one, because the interactive web site of colorbrewer has an optional toggle as photocopy safe. For two that reprinting a pdf in gray scale (example pdf_rewriter) may provide a file even more portable as an attachment of an email (e.g., sharing a paper with a colleague) than a mere reprint in color and still useful if luminance of the color map is designed well. Intrigued by talks by Nathaniel Smith and SteĢfan van der Walt about viridis (link to youtube recording on SciPy2015), Kristen Thyng about colormaps in oceanography (SciPy2015), and Damon McDougall against use of jet (SciPy2014) I once tested Kenneth Morelandā€™s color maps (GitHub repository) for a projection of f(x,y) = x**2 + y**2, for instance

altogether with color maps already available in gnuplot (including cubehelix), or provided for gnuplotting (e.g., the dreaded jet).

The synopsis equally could mark if they are colourblind safe. This may be more complex as there are multiple types of color blindness, on occasion mutually exclusive to a map equally safe if represented in gray scale.

1 Like

Depending on custom, it is a bit puzzling to see the scale with blue in the centre for that the scale on universal pH paper often runs from red (pH 1, acidic) to yellow and green (pH 7, neutral) to blue (pH well above 10, basic)

(image credit Macherey-Nagel)

However, it clearly indicates a wide range of application (e.g., the test strips in water analysis in general, e.g. nitrates, heavy metals, etc.)

2 Likes

Of course. A somewhat uncommon scale for red cabbage.
cabbage_scale

Concerning the Scientific Colour Maps collection (the great majority of colormaps I have included), this Fabio Crameriā€™s poster states:

Made by science,
made for science
āœ“ Perceptually uniform
i.e., NOT distorting the data
āœ“ Perceptually ordered
i.e., intuitively readable
āœ“ Colour-vision-deficiency friendly
i.e., NOT excluding certain readers
āœ“ Readable as black-and-white print
i.e., convenient
āœ“ Available in all major data formats
i.e., openly accessible
āœ“ Including diagnostics; peer-reviewed; citable
i.e., tested and trustworthy

People wanting to quickly learn some facts about the scientific use of colormaps can look that poster. Itā€™s a very good and concise introduction. You will find more references at the bottom of the README.md file of ForColormap.

@vmagnin , great work, thank you for your effort!

Just a couple of minor comments:

  1. In terms of API, such libraries and consumers of them can truly benefit from a proper enumeration facility in the Fortran language, otherwise ā€œmagic numbersā€ tend to proliferate in codes which is always a source of confusion and at times, error. Unfortunately proper enumeration is either decades away or more likely the language may never see one. My vision for Fortran is here, unfortunately I failed miserably from it even being considered by the committee.
  2. In your code, is there a reason why you donā€™t mark MODULE entities and your ā€œclassā€ members (derived type components) as PRIVATE by default?
1 Like

No, thanks for pointing this. Itā€™s just a residue of my development process, where everything was public at the beginning and became progressively privateā€¦ I will fix that.

Concerning enumerations, I guess you mean I could have used enums instead of a ā€œlistā€ of strings for choosing the palette. Probably I chose that way just because I was inspired by some APIs of other colormap libraries in other languagesā€¦ The only true advantage of enums I see for the user is that choosing a non-existent colormap would be detected at compile time. Here it is made at run-time.

P.s. It is your honor to have tried to participate in the standard committee. But decisions in human organizations is a complex thing and I can imagine diverging interests can kill sincere initiatives.

Probably too specific to put it in my library! But it is a good example of how to write a custom colormap.

Well, I found a similar pH scale in this paper.

1 Like

Nice work ! Gonna try it!

I will think about it.

In gtk-fortran, images are coded in pixbuffers which are defined by:

character(kind=c_char), dimension(:), pointer :: pixel

and I have typically such code:

    integer(int8) :: red, green, blue
...
    pixel(p)   = char(red)
    pixel(p+1) = char(green)
    pixel(p+2) = char(blue)

In Intel Visual Fortran (Windows only), things are different. You can use the function SETPIXELRGB_W(x,y,color) where color is an integer(4), with three bytes coding the RGB values and one byte not used. This integer(4) can be obtained with the function RGBTOINTEGER(r, g, b).

Concerning the real working precision, what is the good practice in a library?

At the time being, I have defined:

    use iso_fortran_env, only: wp=>real64

    implicit none
    private

    public :: wp

But maybe I should rather just keep the wp private and say in the documentation that the ForColormap library is expecting real64 ? And if the user donā€™t use them he will have a Error: Type mismatch in argument ā€˜zminā€™ at (1); passed REAL(4) to REAL(8) message and will understand what he should do.

Iā€™m interested in seeing the discussion on this question.

Normally, a user program would not depend on a library in order to establish the working precision of the application. The user would choose depending on the accuracy requirements of his application, of the precision of the available input data, and so on, and then he would seek the library code that matches his needs (e.g. with generic interfaces, etc.).

On the other hand, if the library supports a single program (or, say, a small set of related programs), then you might want to do the opposite, import the precision parameters from the application code into the library code, and compile the library code with those parameters.

Those are kind of the two extremes, there are in-between cases too.

Yes, I think the working precision used in the library here is not important. And it does not really impact the calling program because the main objective is just to draw bitmaps, not computing a precise value. Anyway our eye can distinguish only around 300000 colors (some says 1M).

One thing I would like to see is more cyclic color maps in the library. I used my Fortran Image Library to create two animated gifs, using the ā€œmanaguaā€ and ā€œbrocOā€ color maps, both taken from ForColormap. They are just color bars, with shifting palette and 16 ms/frame (62.5 fps). They animate more slowly here, presumably because of browser rendering:

managua (non cyclic): managua

brocO (clearly cyclic): brocO

From what I can tell, there are only five cyclic color maps in the library, namely bamO, brocO, corkO, romaO, and vikO. I am aware that Fabio Crameriā€™s paper has only a few cyclic color maps, but one can easily make more. I typically do that using the HSV color model (Hue, Saturation, Value), then convert the resulting palette to RGB. For example this code

do x=0,255
  palette(x) = ConvertToRGB( HSVColor(x, 255, 255) )
end do

makes a simple rainbow-like cyclic map: rainbow

So yes, some more cyclic color maps would be nice. They donā€™t necessarily have to be strictly scientific color maps. :slight_smile:

2 Likes

I take note @pap for future developments. We could either add more good cyclic maps (under MIT or public domain licenses) or add methods to create them.