| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
OpenCV.Extra.XPhoto.WhiteBalancer
- class WhiteBalancer a where
- data GrayworldWB s
- data LearningBasedWB s
- data SimpleWB s
- newGrayworldWB :: PrimMonad m => Maybe Double -> m (GrayworldWB (PrimState m))
- newLearningBasedWB :: PrimMonad m => Maybe Int32 -> Maybe Int32 -> Maybe Double -> m (LearningBasedWB (PrimState m))
- newSimpleWB :: PrimMonad m => Maybe Double -> Maybe Double -> Maybe Double -> Maybe Double -> Maybe Double -> m (SimpleWB (PrimState m))
Documentation
data GrayworldWB s Source #
Instances
| Algorithm (GrayworldWB *) Source # | |
| WhiteBalancer (GrayworldWB *) Source # | |
| WithPtr (GrayworldWB k s) Source # | |
| FromPtr (GrayworldWB k s) Source # | |
| type C (GrayworldWB k s) Source # | |
data LearningBasedWB s Source #
Instances
| Algorithm (LearningBasedWB *) Source # | |
| WhiteBalancer (LearningBasedWB *) Source # | |
| WithPtr (LearningBasedWB k s) Source # | |
| FromPtr (LearningBasedWB k s) Source # | |
| type C (LearningBasedWB k s) 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)

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)) |