Safe Haskell | None |
---|---|
Language | Haskell2010 |
Graphics.Color.Space.CIE1976.LUV
Description
Constructors for an CIE L*u*v* color space.
pattern ColorLUVA :: e -> e -> e -> e -> Color (Alpha (LUV i)) e Source #
Constructor for LUV
with alpha channel.
CIE L*u*v* color space
Instances
(Illuminant i, Elevator e, RealFloat e) => ColorSpace (LUV i) (i :: k) e Source # | |
Defined in Graphics.Color.Space.CIE1976.LUV Methods toBaseModel :: Color (LUV i) e -> Color (BaseModel (LUV i)) e Source # fromBaseModel :: Color (BaseModel (LUV i)) e -> Color (LUV i) e Source # toBaseSpace :: Color (LUV i) e -> Color (BaseSpace (LUV i)) e Source # fromBaseSpace :: Color (BaseSpace (LUV i)) e -> Color (LUV i) e Source # luminance :: (Elevator a, RealFloat a) => Color (LUV i) e -> Color (Y i) a Source # toColorXYZ :: (Elevator a, RealFloat a) => Color (LUV i) e -> Color (XYZ i) a Source # fromColorXYZ :: (Elevator a, RealFloat a) => Color (XYZ i) a -> Color (LUV i) e Source # | |
Functor (Color (LUV i)) Source # | CIE1976 |
Applicative (Color (LUV i)) Source # | CIE1976 |
Defined in Graphics.Color.Space.CIE1976.LUV Methods pure :: a -> Color (LUV i) a # (<*>) :: Color (LUV i) (a -> b) -> Color (LUV i) a -> Color (LUV i) b # liftA2 :: (a -> b -> c) -> Color (LUV i) a -> Color (LUV i) b -> Color (LUV i) c # (*>) :: Color (LUV i) a -> Color (LUV i) b -> Color (LUV i) b # (<*) :: Color (LUV i) a -> Color (LUV i) b -> Color (LUV i) a # | |
Foldable (Color (LUV i)) Source # | CIE1976 |
Defined in Graphics.Color.Space.CIE1976.LUV Methods fold :: Monoid m => Color (LUV i) m -> m # foldMap :: Monoid m => (a -> m) -> Color (LUV i) a -> m # foldMap' :: Monoid m => (a -> m) -> Color (LUV i) a -> m # foldr :: (a -> b -> b) -> b -> Color (LUV i) a -> b # foldr' :: (a -> b -> b) -> b -> Color (LUV i) a -> b # foldl :: (b -> a -> b) -> b -> Color (LUV i) a -> b # foldl' :: (b -> a -> b) -> b -> Color (LUV i) a -> b # foldr1 :: (a -> a -> a) -> Color (LUV i) a -> a # foldl1 :: (a -> a -> a) -> Color (LUV i) a -> a # toList :: Color (LUV i) a -> [a] # null :: Color (LUV i) a -> Bool # length :: Color (LUV i) a -> Int # elem :: Eq a => a -> Color (LUV i) a -> Bool # maximum :: Ord a => Color (LUV i) a -> a # minimum :: Ord a => Color (LUV i) a -> a # | |
Traversable (Color (LUV i)) Source # | CIE1976 |
Defined in Graphics.Color.Space.CIE1976.LUV Methods traverse :: Applicative f => (a -> f b) -> Color (LUV i) a -> f (Color (LUV i) b) # sequenceA :: Applicative f => Color (LUV i) (f a) -> f (Color (LUV i) a) # mapM :: Monad m => (a -> m b) -> Color (LUV i) a -> m (Color (LUV i) b) # sequence :: Monad m => Color (LUV i) (m a) -> m (Color (LUV i) a) # | |
Eq e => Eq (Color (LUV i) e) Source # | CIE1976 |
Ord e => Ord (Color (LUV i) e) Source # | CIE1976 |
Defined in Graphics.Color.Space.CIE1976.LUV Methods compare :: Color (LUV i) e -> Color (LUV i) e -> Ordering # (<) :: Color (LUV i) e -> Color (LUV i) e -> Bool # (<=) :: Color (LUV i) e -> Color (LUV i) e -> Bool # (>) :: Color (LUV i) e -> Color (LUV i) e -> Bool # (>=) :: Color (LUV i) e -> Color (LUV i) e -> Bool # max :: Color (LUV i) e -> Color (LUV i) e -> Color (LUV i) e # min :: Color (LUV i) e -> Color (LUV i) e -> Color (LUV i) e # | |
(Illuminant i, Elevator e) => Show (Color (LUV i) e) Source # | CIE1976 |
Storable e => Storable (Color (LUV i) e) Source # | CIE1976 |
Defined in Graphics.Color.Space.CIE1976.LUV Methods sizeOf :: Color (LUV i) e -> Int # alignment :: Color (LUV i) e -> Int # peekElemOff :: Ptr (Color (LUV i) e) -> Int -> IO (Color (LUV i) e) # pokeElemOff :: Ptr (Color (LUV i) e) -> Int -> Color (LUV i) e -> IO () # peekByteOff :: Ptr b -> Int -> IO (Color (LUV i) e) # pokeByteOff :: Ptr b -> Int -> Color (LUV i) e -> IO () # | |
(Illuminant i, Elevator e) => ColorModel (LUV i) e Source # | CIE1976 |
Defined in Graphics.Color.Space.CIE1976.LUV Associated Types type Components (LUV i) e Source # Methods toComponents :: Color (LUV i) e -> Components (LUV i) e Source # fromComponents :: Components (LUV i) e -> Color (LUV i) e Source # showsColorModelName :: Proxy (Color (LUV i) e) -> ShowS Source # | |
newtype Color (LUV i) e Source # | Color in CIE L*u*v* color space |
Defined in Graphics.Color.Space.CIE1976.LUV | |
type BaseModel (LUV i) Source # | |
Defined in Graphics.Color.Space.CIE1976.LUV | |
type BaseSpace (LUV i) Source # | |
Defined in Graphics.Color.Space.CIE1976.LUV | |
type Components (LUV i) e Source # | |
Defined in Graphics.Color.Space.CIE1976.LUV |