never executed always true always false
    1 {-# LANGUAGE QuasiQuotes #-}
    2 {-# LANGUAGE TemplateHaskell #-}
    3 
    4 module OpenCV.ImgProc.ColorMaps
    5     ( ColorMap(..)
    6     , applyColorMap
    7     ) where
    8 
    9 import "base" Data.Int
   10 import "base" Data.Word
   11 import qualified "inline-c" Language.C.Inline as C
   12 import qualified "inline-c-cpp" Language.C.Inline.Cpp as C
   13 import "this" OpenCV.Core.Types
   14 import "this" OpenCV.Internal.C.Inline ( openCvCtx )
   15 import "this" OpenCV.Internal.C.Types
   16 import "this" OpenCV.Internal.Core.Types.Mat
   17 import "this" OpenCV.Internal.Exception
   18 import "this" OpenCV.TypeLevel
   19 
   20 --------------------------------------------------------------------------------
   21 
   22 C.context openCvCtx
   23 
   24 C.include "opencv2/core.hpp"
   25 C.include "opencv2/imgproc.hpp"
   26 C.using "namespace cv"
   27 
   28 #include <bindings.dsl.h>
   29 #include "opencv2/core.hpp"
   30 #include "opencv2/imgproc.hpp"
   31 
   32 #include "namespace.hpp"
   33 
   34 --------------------------------------------------------------------------------
   35 
   36 data ColorMap
   37    = ColorMapAutumn  -- ^ <<doc/generated/examples/colorMapAutumImg.png   colorMapAutumImg  >>
   38    | ColorMapBone    -- ^ <<doc/generated/examples/colorMapBoneImg.png    colorMapBoneImg   >>
   39    | ColorMapJet     -- ^ <<doc/generated/examples/colorMapJetImg.png     colorMapJetImg    >>
   40    | ColorMapWinter  -- ^ <<doc/generated/examples/colorMapWinterImg.png  colorMapWinterImg >>
   41    | ColorMapRainbow -- ^ <<doc/generated/examples/colorMapRainbowImg.png colorMapRainbowImg>>
   42    | ColorMapOcean   -- ^ <<doc/generated/examples/colorMapOceanImg.png   colorMapOceanImg  >>
   43    | ColorMapSummer  -- ^ <<doc/generated/examples/colorMapSummerImg.png  colorMapSummerImg >>
   44    | ColorMapSpring  -- ^ <<doc/generated/examples/colorMapSpringImg.png  colorMapSpringImg >>
   45    | ColorMapCool    -- ^ <<doc/generated/examples/colorMapCoolImg.png    colorMapCoolImg   >>
   46    | ColorMapHsv     -- ^ <<doc/generated/examples/colorMapHsvImg.png     colorMapHsvImg    >>
   47    | ColorMapPink    -- ^ <<doc/generated/examples/colorMapPinkImg.png    colorMapPinkImg   >>
   48    | ColorMapHot     -- ^ <<doc/generated/examples/colorMapHotImg.png     colorMapHotImg    >>
   49    | ColorMapParula  -- ^ <<doc/generated/examples/colorMapParulaImg.png  colorMapParulaImg >>
   50 
   51 #num COLORMAP_AUTUMN
   52 #num COLORMAP_BONE
   53 #num COLORMAP_JET
   54 #num COLORMAP_WINTER
   55 #num COLORMAP_RAINBOW
   56 #num COLORMAP_OCEAN
   57 #num COLORMAP_SUMMER
   58 #num COLORMAP_SPRING
   59 #num COLORMAP_COOL
   60 #num COLORMAP_HSV
   61 #num COLORMAP_PINK 
   62 #num COLORMAP_HOT 
   63 #num COLORMAP_PARULA 
   64 
   65 marshalColorMap :: ColorMap -> Int32
   66 marshalColorMap = \case
   67    ColorMapAutumn  -> c'COLORMAP_AUTUMN
   68    ColorMapBone    -> c'COLORMAP_BONE
   69    ColorMapJet     -> c'COLORMAP_JET
   70    ColorMapWinter  -> c'COLORMAP_WINTER
   71    ColorMapRainbow -> c'COLORMAP_RAINBOW
   72    ColorMapOcean   -> c'COLORMAP_OCEAN
   73    ColorMapSummer  -> c'COLORMAP_SUMMER
   74    ColorMapSpring  -> c'COLORMAP_SPRING
   75    ColorMapCool    -> c'COLORMAP_COOL
   76    ColorMapHsv     -> c'COLORMAP_HSV
   77    ColorMapPink    -> c'COLORMAP_PINK
   78    ColorMapHot     -> c'COLORMAP_HOT
   79    ColorMapParula  -> c'COLORMAP_PARULA
   80 
   81 {- | Applies a GNU Octave/MATLAB equivalent colormap on a given image
   82 
   83 The human perception isn’t built for observing fine changes in grayscale
   84 images. Human eyes are more sensitive to observing changes between colors, so
   85 you often need to recolor your grayscale images to get a clue about
   86 them. OpenCV now comes with various colormaps to enhance the visualization in
   87 your computer vision application.
   88 
   89 Example:
   90 
   91 @
   92 grayscaleImg
   93     :: forall (height :: Nat) (width :: Nat) depth
   94      . (height ~ 30, width ~ 256, depth ~ Word8)
   95     => Mat (ShapeT [height, width]) ('S 1) ('S depth)
   96 grayscaleImg = exceptError $
   97     matFromFunc
   98       (Proxy :: Proxy [height, width])
   99       (Proxy :: Proxy 1)
  100       (Proxy :: Proxy depth)
  101       grayscale
  102   where
  103     grayscale :: [Int] -> Int -> Word8
  104     grayscale [_y, x] 0 = fromIntegral x
  105     grayscale _pos _channel = error "impossible"
  106 
  107 type ColorMapImg = Mat (ShapeT [30, 256]) ('S 3) ('S Word8)
  108 
  109 mkColorMapImg :: ColorMap -> ColorMapImg
  110 mkColorMapImg cmap = exceptError $ applyColorMap cmap grayscaleImg
  111 
  112 colorMapAutumImg   :: ColorMapImg
  113 colorMapBoneImg    :: ColorMapImg
  114 colorMapJetImg     :: ColorMapImg
  115 colorMapWinterImg  :: ColorMapImg
  116 colorMapRainbowImg :: ColorMapImg
  117 colorMapOceanImg   :: ColorMapImg
  118 colorMapSummerImg  :: ColorMapImg
  119 colorMapSpringImg  :: ColorMapImg
  120 colorMapCoolImg    :: ColorMapImg
  121 colorMapHsvImg     :: ColorMapImg
  122 colorMapPinkImg    :: ColorMapImg
  123 colorMapHotImg     :: ColorMapImg
  124 colorMapParulaImg  :: ColorMapImg
  125 
  126 colorMapAutumImg   = mkColorMapImg ColorMapAutumn
  127 colorMapBoneImg    = mkColorMapImg ColorMapBone
  128 colorMapJetImg     = mkColorMapImg ColorMapJet
  129 colorMapWinterImg  = mkColorMapImg ColorMapWinter
  130 colorMapRainbowImg = mkColorMapImg ColorMapRainbow
  131 colorMapOceanImg   = mkColorMapImg ColorMapOcean
  132 colorMapSummerImg  = mkColorMapImg ColorMapSummer
  133 colorMapSpringImg  = mkColorMapImg ColorMapSpring
  134 colorMapCoolImg    = mkColorMapImg ColorMapCool
  135 colorMapHsvImg     = mkColorMapImg ColorMapHsv
  136 colorMapPinkImg    = mkColorMapImg ColorMapPink
  137 colorMapHotImg     = mkColorMapImg ColorMapHot
  138 colorMapParulaImg  = mkColorMapImg ColorMapParula
  139 @
  140 
  141 <<doc/generated/examples/grayscaleImg.png grayscaleImg>>
  142 
  143 <http://docs.opencv.org/3.0-last-rst/modules/imgproc/doc/colormaps.html#applycolormap OpenCV Sphinx doc>
  144 -}
  145 applyColorMap
  146     :: ColorMap
  147     -> Mat shape ('S 1) ('S Word8)
  148     -> CvExcept (Mat shape ('S 3) ('S Word8))
  149 applyColorMap colorMap src = unsafeWrapException $ do
  150     dst <- newEmptyMat
  151     handleCvException (pure $ unsafeCoerceMat dst) $
  152       withPtr src $ \srcPtr ->
  153       withPtr dst $ \dstPtr ->
  154         [cvExcept|
  155           cv::applyColorMap( *$(Mat * srcPtr)
  156                            , *$(Mat * dstPtr)
  157                            , $(int32_t c'colorMap)
  158                            );
  159         |]
  160   where
  161     c'colorMap = marshalColorMap colorMap