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