{- |
  This module provides 1-dimensional colour maps with
  smooth (linear) colour blending between control points.
-}

module Data.Colour.Map
    (
      -- * Utility
      range_cycle,

      -- * Simple colour range
      ColourMap, colour_map,

      -- * Repeating colour range
      FullColourMap (..), full_colour_map
    )
  where

import Data.Colour.Double

{- |
  Takes a range and a value, and returns a value inside
  the given range. If the value is already in the range,
  it is unchanged. Otherwise it \"wraps around\". For
  example, if the range is @(0, 1)@ then, in effect,
  the fractional part of the value is returned.

  Note that extremely narrow ranges may exhibit numerical
  instability.
-}
range_cycle :: (Double,Double) -> Double -> Double
range_cycle (x0,x1) x
  | x0 == x1  = error "Data.Colour.Map.range_cycle: zero-width range"
  | x0 >  x1  = range_cycle (x1,x0) x
  | otherwise =
    let
      dx = x1 - x0
      y  = x  - x0
      n  = floor (y / dx)
      z  = y - (fromIntegral n * dx)
    in z + x0

{- |
  This is the basic colour map type. It consists of a list of
  control points, each one being a parameter value and the
  colour at that parameter value. The colour at other
  parameter values is linearly interpolated between the
  control points.

  Parameter values outside the range (i.e., below the first
  point or above the last point) take the colour of the
  end control point. This means that in the degenerate
  case of a single control point, the colour is applied
  everywhere (and the parameter value is ignored).

  A map with /zero/ control points is not permitted.
-}
type ColourMap = [(Double, Colour)]

{- |
  Compute the value of a colour map at a particular
  parameter value.
-}
colour_map :: ColourMap -> Double -> Colour
colour_map [] _ = error "Data.Colour.Map.colour_map []"
colour_map ps x = cm_internal ps x

cm_internal ((x0,c0):[])         x = c0
cm_internal ((x0,c0):(x1,c1):ps) x
  | x < x0 = c0
  | x > x1 = cm_internal ((x1,c1):ps) x
  | otherwise =
    let
      dx = x1 - x0
      k  = (x - x0) / dx
    in (1-k) `cscale` c0 + k `cscale` c1

{- |
  This is a colour map with has optional repeating behaviour using
  'range_cycle' above.

  Notice that the parameter range that gets repeated need not cover
  the entire range of the underlying 'ColourMap'.
-}
data FullColourMap =
  SimpleMap                    ColourMap | -- ^ Colour map which does not repeat.
  RepeatingMap (Double,Double) ColourMap   -- ^ Colour map which repeats.

{- |
  Compute the value of a full colour map at a particular
  parameter value, similar to 'colour_map'.
-}
full_colour_map :: FullColourMap -> Double -> Colour
full_colour_map (SimpleMap      m) = colour_map m
full_colour_map (RepeatingMap r m) = colour_map m . range_cycle r