module Web.Lightning.Plots.Scatter
(
ScatterPlot(..)
, Visualization (..)
, scatterPlot
)
where
import Control.Monad.Reader
import Data.Aeson
import Data.Default.Class
import qualified Data.Text as T
import qualified Web.Lightning.Routes as R
import Web.Lightning.Types.Lightning
import Web.Lightning.Types.Visualization (Visualization (..))
import Web.Lightning.Utilities
data ScatterPlot =
ScatterPlot { spX :: [Double]
, spY :: [Double]
, spValues :: Maybe [Double]
, spLabels :: Maybe [T.Text]
, spColor :: Maybe [Int]
, spGroup :: Maybe [Int]
, spColorMap :: Maybe T.Text
, spSize :: Maybe [Int]
, spAlpha :: Maybe [Double]
, spXaxis :: Maybe T.Text
, spYaxis :: Maybe T.Text
, spToolTips :: Maybe Bool
, spZoom :: Maybe Bool
, spBrush :: Maybe Bool
}
deriving (Show, Eq)
instance Default ScatterPlot where
def = ScatterPlot [] [] Nothing Nothing Nothing Nothing Nothing Nothing
Nothing Nothing Nothing (Just True) (Just True) (Just True)
instance ToJSON ScatterPlot where
toJSON (ScatterPlot xs ys vs ls cs gs cm ss as xa ya t z b) =
omitNulls [ "points" .= getPoints xs ys
, "values" .= vs
, "labels" .= ls
, "color" .= cs
, "group" .= gs
, "colormap" .= cm
, "size" .= ss
, "alpha" .= as
, "xaxis" .= xa
, "yaxis" .= ya
, "tooltips" .= t
, "zoom" .= z
, "brush" .= b
]
instance ValidatablePlot ScatterPlot where
validatePlot (ScatterPlot xs ys v lbl c grp cm s a xa ya tt z b) = do
(xs', ys') <- validateCoordinates xs ys
c' <- validateColor c
cm' <- validateColorMap cm
s' <- validateSize s
a' <- validateAlpha a
return $ ScatterPlot xs' ys' v lbl c' grp cm' s' a' xa ya tt z b
scatterPlot :: Monad m => ScatterPlot
-> LightningT m Visualization
scatterPlot scatterPlt = do
url <- ask
viz <- sendPlot "scatter" scatterPlt R.plot
return $ viz { vizBaseUrl = Just url }