module Web.Lightning.Plots.Histogram
(
HistogramPlot(..)
, Visualization (..)
, histogramPlot
)
where
import Control.Monad.Reader
import Data.Aeson
import Data.Default.Class
import qualified Web.Lightning.Routes as R
import Web.Lightning.Types.Lightning
import Web.Lightning.Types.Visualization (Visualization (..))
import Web.Lightning.Utilities
data HistogramPlot =
HistogramPlot { hpValues :: [Double]
, hpBins :: Maybe [Double]
, hpZoom :: Maybe Bool
}
deriving (Show, Eq)
instance Default HistogramPlot where
def = HistogramPlot [] Nothing (Just True)
instance ToJSON HistogramPlot where
toJSON (HistogramPlot vs bs z) =
omitNulls [ "values" .= vs
, "bins" .= bs
, "zoom" .= z
]
instance ValidatablePlot HistogramPlot where
validatePlot (HistogramPlot v b z) = do
b' <- validateBin b
return $ HistogramPlot v b' z
histogramPlot :: Monad m => HistogramPlot
-> LightningT m Visualization
histogramPlot histPlt = do
url <- ask
viz <- sendPlot "histogram" histPlt R.plot
return $ viz { vizBaseUrl = Just url }