module Numeric.Histogram ( Range
, binBounds
, histValues
, histWeightedValues
, histWithBins
) where
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as MV
import Control.Monad.ST
type Range a = (a,a)
binBounds :: RealFrac a => a -> a -> Int -> [Range a]
binBounds a b n = map (\i->(lbound i, lbound (i+1))) [0..n1]
where lbound i = a + (ba) * realToFrac i / realToFrac n
histValues :: RealFrac a => a -> a -> Int -> [a] -> V.Vector (Range a, Int)
histValues a b n = histWithBins (V.fromList $ binBounds a b n) . zip (repeat 1)
histWeightedValues :: RealFrac a => a -> a -> Int -> [(Double,a)] -> V.Vector (Range a, Double)
histWeightedValues a b n = histWithBins (V.fromList $ binBounds a b n)
histWithBins :: (Num w, RealFrac a) => V.Vector (Range a) -> [(w, a)] -> V.Vector (Range a, w)
histWithBins bins xs =
let n = V.length bins
testBin :: RealFrac a => a -> (Int, Range a) -> Bool
testBin x (i, (a,b)) =
if i == n 1
then x >= a && x <= b
else x >= a && x < b
f :: (RealFrac a, Num w)
=> V.Vector (Range a) -> MV.STVector s w -> (w, a)
-> ST s ()
f bins1 bs (w,x) =
case V.dropWhile (not . testBin x) $ V.indexed bins1 of
v | V.null v -> return ()
v | (idx,_) <- V.head v -> do
m <- MV.read bs idx
MV.write bs idx $! m+w
counts = runST $ do b <- MV.replicate n 0
mapM_ (f bins b) xs
V.freeze b
in V.zip bins counts