Safe Haskell | None |
---|---|
Language | Haskell2010 |
Predefined and custom colors.
Synopsis
- data Color
- makeColor :: Float -> Float -> Float -> Float -> Color
- makeColorI :: Int -> Int -> Int -> Int -> Color
- rgbaOfColor :: Color -> (Float, Float, Float, Float)
- mixColors :: Float -> Float -> Color -> Color -> Color
- addColors :: Color -> Color -> Color
- dim :: Color -> Color
- bright :: Color -> Color
- light :: Color -> Color
- dark :: Color -> Color
- withRed :: Float -> Color -> Color
- withGreen :: Float -> Color -> Color
- withBlue :: Float -> Color -> Color
- withAlpha :: Float -> Color -> Color
- greyN :: Float -> Color
- black :: Color
- white :: Color
- red :: Color
- green :: Color
- blue :: Color
- yellow :: Color
- cyan :: Color
- magenta :: Color
- rose :: Color
- violet :: Color
- azure :: Color
- aquamarine :: Color
- chartreuse :: Color
- orange :: Color
Color data type
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
.
Instances
Eq Color | |
Data Color | |
Defined in Graphics.Gloss.Internals.Data.Color gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Color -> c Color # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Color # dataTypeOf :: Color -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Color) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color) # gmapT :: (forall b. Data b => b -> b) -> Color -> Color # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r # gmapQ :: (forall d. Data d => d -> u) -> Color -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Color -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Color -> m Color # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Color -> m Color # | |
Num Color | |
Show Color | |
:: Float | Red component. |
-> Float | Green component. |
-> Float | Blue component. |
-> Float | Alpha component. |
-> Color |
Make a custom color. All components are clamped to the range [0..1].
makeColorI :: Int -> Int -> Int -> Int -> Color #
Make a custom color. All components are clamped to the range [0..255].
Color functions
:: Float | Proportion of first color. |
-> Float | Proportion of second color. |
-> Color | First color. |
-> Color | Second color. |
-> Color | Resulting color. |
Mix two colors with the given ratios.
addColors :: Color -> Color -> Color Source #
Add RGB components of a color component-wise, then normalise them to the highest resulting one. The alpha components are averaged.
Pre-defined colors
Primary
Secondary
Tertiary
aquamarine :: Color Source #
chartreuse :: Color Source #