opencv-extra-0.2.0.1: Haskell binding to OpenCV-3.x extra modules

Safe HaskellNone
LanguageHaskell2010

OpenCV.Extra.XPhoto.WhiteBalancer

Synopsis

Documentation

class WhiteBalancer a where Source #

Minimal complete definition

balanceWhite

Methods

balanceWhite Source #

Arguments

:: PrimMonad m 
=> a (PrimState m) 
-> Mat (S [h, w]) channels depth

The input Image.

-> m (Mat (S [h, w]) channels depth)

The output image.

Instances

WhiteBalancer (SimpleWB *) Source # 

Methods

balanceWhite :: PrimMonad m => SimpleWB * (PrimState m) -> Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth -> m (Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth) Source #

WhiteBalancer (LearningBasedWB *) Source # 

Methods

balanceWhite :: PrimMonad m => LearningBasedWB * (PrimState m) -> Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth -> m (Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth) Source #

WhiteBalancer (GrayworldWB *) Source # 

Methods

balanceWhite :: PrimMonad m => GrayworldWB * (PrimState m) -> Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth -> m (Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth) Source #

data GrayworldWB s Source #

Instances

Algorithm (GrayworldWB *) Source # 
WhiteBalancer (GrayworldWB *) Source # 

Methods

balanceWhite :: PrimMonad m => GrayworldWB * (PrimState m) -> Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth -> m (Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth) Source #

WithPtr (GrayworldWB k s) Source # 

Methods

withPtr :: GrayworldWB k s -> (Ptr (C (GrayworldWB k s)) -> IO b) -> IO b

FromPtr (GrayworldWB k s) Source # 

Methods

fromPtr :: IO (Ptr (C (GrayworldWB k s))) -> IO (GrayworldWB k s)

type C (GrayworldWB k s) Source # 
type C (GrayworldWB k s)

data LearningBasedWB s Source #

Instances

Algorithm (LearningBasedWB *) Source # 
WhiteBalancer (LearningBasedWB *) Source # 

Methods

balanceWhite :: PrimMonad m => LearningBasedWB * (PrimState m) -> Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth -> m (Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth) Source #

WithPtr (LearningBasedWB k s) Source # 

Methods

withPtr :: LearningBasedWB k s -> (Ptr (C (LearningBasedWB k s)) -> IO b) -> IO b

FromPtr (LearningBasedWB k s) Source # 

Methods

fromPtr :: IO (Ptr (C (LearningBasedWB k s))) -> IO (LearningBasedWB k s)

type C (LearningBasedWB k s) Source # 
type C (LearningBasedWB k s)

data SimpleWB s Source #

Instances

Algorithm (SimpleWB *) Source # 
WhiteBalancer (SimpleWB *) Source # 

Methods

balanceWhite :: PrimMonad m => SimpleWB * (PrimState m) -> Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth -> m (Mat (S [DS Nat] ((DS Nat ': h) ((DS Nat ': w) [DS Nat]))) channels depth) Source #

WithPtr (SimpleWB k s) Source # 

Methods

withPtr :: SimpleWB k s -> (Ptr (C (SimpleWB k s)) -> IO b) -> IO b

FromPtr (SimpleWB k s) Source # 

Methods

fromPtr :: IO (Ptr (C (SimpleWB k s))) -> IO (SimpleWB k s)

type C (SimpleWB k s) Source # 
type C (SimpleWB k s)

newGrayworldWB Source #

Arguments

:: PrimMonad m 
=> Maybe Double

A threshold of 1 means that all pixels are used to white-balance, while a threshold of 0 means no pixels are used. Lower thresholds are useful in white-balancing saturated images. Default: 0.9.

-> m (GrayworldWB (PrimState m)) 

Perform GrayworldWB a simple grayworld white balance algorithm.

Example:

grayworldWBImg
    :: forall h w h2 w2 c d
     . ( Mat (ShapeT [h, w]) ('S c) ('S d) ~ Sailboat_768x512
       , w2 ~ ((*) w 2)
       , h2 ~ ((*) h 2)
       )
    => IO (Mat ('S ['S h2, 'S w2]) ('S c) ('S d))
grayworldWBImg = do
    let
      bw :: (WhiteBalancer a) => a (PrimState IO) -> IO (Mat (ShapeT [h, w]) ('S c) ('S d))
      bw = flip balanceWhite sailboat_768x512
    balancedGrayworldWB <- bw =<< newGrayworldWB Nothing
    balancedLearningBasedWB <- bw =<< newLearningBasedWB Nothing Nothing Nothing
    balancedSimpleWB <- bw =<< newSimpleWB Nothing Nothing Nothing Nothing Nothing
    pure $ exceptError $
        withMatM
          (Proxy :: Proxy [h2, w2])
          (Proxy :: Proxy c)
          (Proxy :: Proxy d)
          black $ \imgM -> do
            matCopyToM imgM (V2 0 0) sailboat_768x512 Nothing
            matCopyToM imgM (V2 w 0) balancedGrayworldWB Nothing
            matCopyToM imgM (V2 0 h) balancedLearningBasedWB Nothing
            matCopyToM imgM (V2 w h) balancedSimpleWB Nothing
  where
    w = fromInteger $ natVal (Proxy :: Proxy w)
    h = fromInteger $ natVal (Proxy :: Proxy h)

newLearningBasedWB Source #

Arguments

:: PrimMonad m 
=> Maybe Int32

default 64, Defines the size of one dimension of a three-dimensional RGB histogram that is used internally by the algorithm. It often makes sense to increase the number of bins for images with higher bit depth (e.g. 256 bins for a 12 bit image).

-> Maybe Int32

default 255, Maximum possible value of the input image (e.g. 255 for 8 bit images, 4095 for 12 bit images)

-> Maybe Double

default 0.98, Threshold that is used to determine saturated pixels, i.e. pixels where at least one of the channels exceeds

-> m (LearningBasedWB (PrimState m)) 

newSimpleWB Source #

Arguments

:: PrimMonad m 
=> Maybe Double

Input Min (default: 0)

-> Maybe Double

Input Max (default: 255)

-> Maybe Double

Output Min (default: 0)

-> Maybe Double

Output Max (default: 255)

-> Maybe Double

Percent of top/bottom values to ignore (default: 2)

-> m (SimpleWB (PrimState m))