Color-0.1.2: Color spaces and conversions between them

Copyright(c) Alexey Kuleshevich 2018-2019
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Graphics.Color.Adaptation.VonKries

Contents

Description

 
Synopsis

Color conversion

convert :: (ColorSpace cs' i' e', ColorSpace cs i e) => Color cs' e' -> Color cs e Source #

This function allows conversion of a color between any two color spaces. It uses a very common VonKries chromatic adaptation transform with Bradford matrix. One of more general functions convertWith or convertElevatedWith can be used for selecting another chromatic adaptation algorithm.

Since: 0.1.0

Von Kries adaptation

data VonKries Source #

Constructors

VonKries

VonKries chromatic adaptation transform matrix

>>> cat :: CAT 'VonKries Float
CAT VonKries 'VonKries Float
[ [ 0.400240, 0.707600,-0.080810 ]
, [-0.226300, 1.165320, 0.045700 ]
, [ 0.000000, 0.000000, 0.918220 ] ]
>>> icat :: ICAT 'VonKries Float
ICAT VonKries 'VonKries Float
[ [ 1.859936,-1.129382, 0.219897 ]
, [ 0.361191, 0.638812,-0.000006 ]
, [-0.000000,-0.000000, 1.089064 ] ]
Bradford

Bradford chromatic adaptation transform matrix

>>> cat :: CAT 'Bradford Float
CAT VonKries 'Bradford Float
[ [ 0.895100, 0.266400,-0.161400 ]
, [-0.750200, 1.713500, 0.036700 ]
, [ 0.038900,-0.068500, 1.029600 ] ]
>>> icat :: ICAT 'Bradford Float
ICAT VonKries 'Bradford Float
[ [ 0.986993,-0.147054, 0.159963 ]
, [ 0.432305, 0.518360, 0.049291 ]
, [-0.008529, 0.040043, 0.968487 ] ]
Fairchild

Fairchild chromatic adaptation transform matrix

>>> cat :: CAT 'Fairchild Float
CAT VonKries 'Fairchild Float
[ [ 0.856200, 0.337200,-0.193400 ]
, [-0.836000, 1.832700, 0.003300 ]
, [ 0.035700,-0.046900, 1.011200 ] ]
>>> icat :: ICAT 'Fairchild Float
ICAT VonKries 'Fairchild Float
[ [ 0.987400,-0.176825, 0.189425 ]
, [ 0.450435, 0.464933, 0.084632 ]
, [-0.013968, 0.027807, 0.986162 ] ]
CIECAM02

CIECAM02 chromatic adaptation transform matrix

>>> cat :: CAT 'CIECAM02 Float
CAT VonKries 'CIECAM02 Float
[ [ 0.732800, 0.429600,-0.162400 ]
, [-0.703600, 1.697500, 0.006100 ]
, [ 0.003000, 0.013600, 0.983400 ] ]
>>> icat :: ICAT 'CIECAM02 Float
ICAT VonKries 'CIECAM02 Float
[ [ 1.096124,-0.278869, 0.182745 ]
, [ 0.454369, 0.473533, 0.072098 ]
, [-0.009628,-0.005698, 1.015326 ] ]
Instances
(Illuminant it, Illuminant ir, Elevator e, RealFloat e) => ChromaticAdaptation (t :: VonKries) (it :: kt) (ir :: kr) e Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

Associated Types

data Adaptation t it ir e :: Type Source #

Methods

adaptColorXYZ :: Adaptation t it ir e -> Color (XYZ it) e -> Color (XYZ ir) e Source #

Eq e => Eq (Adaptation t it ir e) Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

Methods

(==) :: Adaptation t it ir e -> Adaptation t it ir e -> Bool #

(/=) :: Adaptation t it ir e -> Adaptation t it ir e -> Bool #

(Illuminant it, Illuminant ir, Elevator e) => Show (Adaptation t it ir e) Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

Methods

showsPrec :: Int -> Adaptation t it ir e -> ShowS #

show :: Adaptation t it ir e -> String #

showList :: [Adaptation t it ir e] -> ShowS #

newtype Adaptation (t :: VonKries) (it :: kt) (ir :: kr) e Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

newtype Adaptation (t :: VonKries) (it :: kt) (ir :: kr) e = AdaptationMatrix (M3x3 e)

newtype CAT (t :: k) e Source #

Chromatic adaptation transformation matrix matrix

Constructors

CAT (M3x3 e) 
Instances
Eq e => Eq (CAT t e) Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

Methods

(==) :: CAT t e -> CAT t e -> Bool #

(/=) :: CAT t e -> CAT t e -> Bool #

(Typeable t, Typeable k, Elevator e) => Show (CAT t e) Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

Methods

showsPrec :: Int -> CAT t e -> ShowS #

show :: CAT t e -> String #

showList :: [CAT t e] -> ShowS #

newtype ICAT (t :: k) e Source #

Inverse of chromatic adaptation transformation matrix

Constructors

ICAT (M3x3 e) 
Instances
Eq e => Eq (ICAT t e) Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

Methods

(==) :: ICAT t e -> ICAT t e -> Bool #

(/=) :: ICAT t e -> ICAT t e -> Bool #

(Typeable t, Typeable k, Elevator e) => Show (ICAT t e) Source # 
Instance details

Defined in Graphics.Color.Adaptation.VonKries

Methods

showsPrec :: Int -> ICAT t e -> ShowS #

show :: ICAT t e -> String #

showList :: [ICAT t e] -> ShowS #

adaptationMatrix :: forall t it ir e. (ChromaticAdaptationTransform t, ChromaticAdaptation t it ir e) => Adaptation (t :: VonKries) it ir e Source #