gloss-accelerate-1.8.0.0: Extras to interface Gloss and Accelerate

Safe HaskellNone

Graphics.Gloss.Accelerate.Data.Color

Contents

Description

Predefined and custom colors. Essentially equivalent to the Graphics.Gloss.Data.Color, but lifted to Accelerate types.

Synopsis

Color data type

type Color = RGBA FloatSource

An abstract color value.

We keep the type abstract so we can be sure that the components are in the required range. To make a custom color use makeColor.

data RGBA a Source

An RGBA colour value to hold the color components. All components lie in the range [0..1).

We need to parameterise by a type so that we can have both Exp (RGBA a) and RGBA (Exp a).

Constructors

RGBA a a a a 

Instances

Typeable1 RGBA 
(Lift Exp a, Elt (Plain a)) => Lift Exp (RGBA a) 
Elt a => Unlift Exp (RGBA (Exp a)) 
Eq a => Eq (RGBA a) 
(Elt a, IsNum a) => Num (Exp (RGBA a)) 
Num a => Num (RGBA a) 
Show a => Show (RGBA a) 
IsTuple (RGBA a) 
Elt a => Elt (RGBA a) 

makeColorSource

Arguments

:: Exp Float

Red component.

-> Exp Float

Green component.

-> Exp Float

Blue component.

-> Exp Float

Alpha component.

-> Exp Color 

Make a custom color. All components are clamped to the range [0..1].

makeColor8Source

Arguments

:: Exp Word8

Red component.

-> Exp Word8

Green component.

-> Exp Word8

Blue component.

-> Exp Word8

Alpha component.

-> Exp Color 

Make a custom color from 8-bit values.

rawColor :: Exp Float -> Exp Float -> Exp Float -> Exp Float -> Exp ColorSource

Make a custom color. You promise that all components are clamped to the range [0..1]

rgbaOfColor :: Exp Color -> (Exp Float, Exp Float, Exp Float, Exp Float)Source

Take the RGBA components of a color.

packRGBA :: Exp Color -> Exp Word32Source

Convert a color into a packed RGBA value.

packABGR :: Exp Color -> Exp Word32Source

Convert a colour into a packed BGRA value.

This is necessary as OpenGL reads pixel data as ABGR, rather than RGBA.

clampColor :: Exp Color -> Exp ColorSource

Clamp components of a color into the required range.

Color functions

mixColorsSource

Arguments

:: Exp Float

Ratio of first color.

-> Exp Float

Ratio of second color.

-> Exp Color

First color.

-> Exp Color

Second color.

-> Exp Color

Resulting color.

Mix two colors with the given ratios.

addColors :: Exp Color -> Exp Color -> Exp ColorSource

Add RGB components of a color component-wise, then normalise them to the highest resulting one. The alpha components are averaged.

dim :: Exp Color -> Exp ColorSource

Make a dimmer version of a color, scaling towards black.

brighten :: Exp Color -> Exp ColorSource

Make a brighter version of a color, scaling towards white.

lighten :: Exp Color -> Exp ColorSource

Lighten a color, adding white.

darken :: Exp Color -> Exp ColorSource

Darken a color, adding black.

opaque :: Exp Color -> Exp ColorSource

Make a colour completely opaque.

Pre-defined colors

greyNSource

Arguments

:: Exp Float

Range is 0 = black, to 1 = white.

-> Exp Color 

A greyness of a given magnitude.

Primary

Secondary

Tertiary