{- |
  This module exports all the main interesting parts of the various
  colour modules. It also provides functions for converting between
  'Colour' and 'Colour8'.

  It is the general intention that \"most\" work will be done with
  'Colour', with values converted to @Colour8@ only as a final step.
  However, full arithmetic on 'Colour8' is supported anyway,
  in case anybody wants to work that way. It is slightly less
  efficient and flexible, however.
-}

module Data.Colour
    (
      Colour (..),
      grey, cscale, clip, pack, unpack,
      cBlack, cWhite, cRed, cYellow, cGreen, cCyan, cBlue, cMagenta,

      Colour8 (..),
      grey8, c8scale, pack8, unpack8,
      c8Black, c8White, c8Red, c8Yellow, c8Green, c8Cyan, c8Blue, c8Magenta,

      cpromote, cdemote
    )
  where

import Data.Colour.Double
import Data.Colour.Word8
import Data.Colour.FastFloor

{- |
  Convert a 'Colour8' into a 'Colour'. Recall that
  0x00 means zero and 0xFF means one; this function will
  remap such values appropriately.
-}
cpromote :: Colour8 -> Colour
cpromote (Colour8 r g b) = Colour
  {
    red   = fromIntegral r / 0xFF,
    green = fromIntegral g / 0xFF,
    blue  = fromIntegral b / 0xFF
  }

{- |
  Convert a 'Colour' into a 'Colour8'. Any values outside
  the range 0--1 will be `wrapped' to that range. You may
  want to run 'clip' before calling this function to
  prevent this behaviour (unless you know the values can't
  be outside the permitted range). This function is the
  exact inverse of 'cpromote'; 0 is mapped to 0x00 and
  1 is mapped to 0xFF.
-}
cdemote :: Colour -> Colour8
cdemote (Colour r g b) = Colour8
  {
    red8   = fast_floor (r * 0xFF),
    green8 = fast_floor (g * 0xFF),
    blue8  = fast_floor (b * 0xFF)
  }