-- | A module defining some basic color tuples. The old 16 color standard plus -- a variable gray and some functions to attenuate, and fade colors. module Graphics.Rendering.Hieroglyph.Colors where import Graphics.Rendering.Hieroglyph.Primitives white = (1,1,1,1) black = (0,0,0,1) red = (1,0,0,1) green = (0,1,0,1) blue = (0,0,1,1) yellow = (1,1,0,1) violet = (1,0,1,1) cyan = (0,1,1,1) darkRed = attenuate 0.5 red darkGreen = attenuate 0.5 green darkBlue = attenuate 0.5 blue darkYellow = attenuate 0.5 yellow darkViolet = attenuate 0.5 violet darkCyan = attenuate 0.5 cyan -- | Grey. Domain of the input values is the bounded interval [0..100] pctGrey :: Double -> (Double,Double,Double,Double) pctGrey k | k >= 0 && k <= 100 = (k*0.01,k*0.01,k*0.01,k*0.01) | k < 0 = black | k > 0 = white -- | Lighten the color by a floating point amount between [0..1] unattenuate :: Double -> (Double,Double,Double,Double) -> (Double,Double,Double,Double) unattenuate by ( r, g, b, a) = ((clamp 0 1 $ (1+by)*r), (clamp 0 1 $ (1+by)*g), (clamp 0 1 $ (1+by)*b), a) -- | Darken the color by a floating point amount between [0..1] attenuate :: Double -> (Double,Double,Double,Double) -> (Double,Double,Double,Double) attenuate by (r, g, b, a) = ((clamp 0 1 $ by*r), (clamp 0 1 $ by*g), (clamp 0 1 $ by*b), a) -- | Make the color more transparent by multiplying the alpha component by a floating point amount between [0..1] fade :: Double -> (Double,Double,Double,Double) -> (Double,Double,Double,Double) fade by (r, g, b, a) = (r, g, b, (clamp 0 1 $ by*a)) -- | Make the color less transparent by multiplying the alpha component by a floating point amount between [0..1] unfade :: Double -> (Double,Double,Double,Double) -> (Double,Double,Double,Double) unfade by (r, g, b, a) = (r, g, b, (clamp 0 1 $ (1+by)*a)) -- | Mix two colors together with a ratio. mix :: Double -> (Double,Double,Double,Double) -> (Double,Double,Double,Double) -> (Double,Double,Double,Double) mix ratio ( r1, g1, b1, a1) ( r2, g2, b2, a2) = ( r', g', b', a') where r' = clamp 0 1 $ (r1+r2) * ratio g' = clamp 0 1 $ (g1+g2) * ratio b' = clamp 0 1 $ (b1+b2) * ratio a' = clamp 0 1 $ (a1+a2) * ratio clamp lo hi val = min hi (max lo val)