module Graphics.Image.IO.Histogram (
Histogram(..), getHistograms, getHistogram,
displayHistograms, writeHistograms
) where
import Prelude hiding (map, mapM_, zipWith)
import qualified Prelude as P (map, mapM_, zipWith)
import Control.Monad.Primitive (PrimMonad (..))
import Graphics.Image.Interface
import Graphics.Image.ColorSpace
import Graphics.Image.IO.Base (displayProgram, spawnProcess)
import Graphics.Rendering.Chart.Easy
import Graphics.Rendering.Chart.Backend.Cairo
import qualified Data.Colour as C
import qualified Data.Vector.Unboxed as V
import qualified Data.Vector.Unboxed.Mutable as MV
import Data.IORef
import Control.Concurrent (forkIO, ThreadId)
import System.Exit (ExitCode(ExitSuccess))
import System.Process (waitForProcess, showCommandForUser)
import System.IO.Temp (withSystemTempDirectory)
import System.FilePath ((</>))
data Histogram = Histogram { hBins :: V.Vector Int
, hName :: String
, hColour :: C.AlphaColour Double
}
getHistograms :: forall arr cs e . (SequentialArray arr Gray e,
SequentialArray arr cs e, Elevator e) =>
Image arr cs e
-> [Histogram]
getHistograms = P.zipWith setCh (enumFrom (toEnum 0) :: [cs]) . P.map getHistogram . toGrayImages
where setCh cs h = h { hName = show cs
, hColour = csColour cs }
getHistogram :: (SequentialArray arr Gray e, Elevator e) =>
Image arr Gray e
-> Histogram
getHistogram img = Histogram { hBins = V.modify countBins $
V.replicate
(1 + fromIntegral (maxBound :: Word8)) (0 :: Int)
, hName = show Gray
, hColour = csColour Gray } where
incBin v (toWord8 -> (PixelGray g)) = modify v (+1) $ fromIntegral g
countBins v = mapM_ (incBin v) img
writeHistograms :: FilePath -> [Histogram] -> IO ()
writeHistograms fileName hists = toFile def fileName $ do
layout_title .= "Histogram"
setColors $ P.map hColour hists
let axis = set la_nTicks 20 . set la_nLabels 14
layout_x_axis . laxis_generate .= scaledIntAxis (axis defaultIntAxis) (0, 260)
P.mapM_ plotHist hists where
plotHist h = plot (line (hName h) [V.toList $ V.imap (,) $ hBins h])
displayHistograms :: [Histogram] -> IO (Maybe ThreadId)
displayHistograms hists = do
(program, block) <- readIORef displayProgram
let displayAction = withSystemTempDirectory "hip" (displayUsing hists program)
if block
then displayAction >> return Nothing
else Just <$> forkIO displayAction
displayUsing :: [Histogram] -> String -> FilePath -> IO ()
displayUsing hists program path = do
let path' = path </> "tmp-hist.png"
writeHistograms path' hists
ph <- spawnProcess program [path']
e <- waitForProcess ph
let printExit ExitSuccess = return ()
printExit exitCode = do
putStrLn $ showCommandForUser program [path']
print exitCode
printExit e
modify :: (PrimMonad m, V.Unbox a) => MV.MVector (PrimState m) a -> (a -> a) -> Int -> m ()
modify v f idx = do
e <- MV.read v idx
MV.write v idx $ f e