module Web.Lightning.Plots.ScatterStream
(
ScatterStreamPlot(..)
, Visualization (..)
, streamingScatterPlot
)
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 ScatterStreamPlot =
ScatterStreamPlot { sspX :: [Double]
, sspY :: [Double]
, sspValues :: Maybe [Double]
, sspLabels :: Maybe [T.Text]
, sspColor :: Maybe [Int]
, sspGroup :: Maybe [Int]
, sspColorMap :: Maybe T.Text
, sspSize :: Maybe [Int]
, sspXaxis :: Maybe T.Text
, sspYaxis :: Maybe T.Text
, sspToolTips :: Maybe Bool
, sspZoom :: Maybe Bool
, sspBrush :: Maybe Bool
, sspVisualization :: Maybe Visualization
}
deriving (Show)
instance Default ScatterStreamPlot where
def = ScatterStreamPlot [] [] Nothing Nothing Nothing Nothing Nothing
Nothing Nothing Nothing (Just True) (Just True) (Just True) Nothing
instance ToJSON ScatterStreamPlot where
toJSON (ScatterStreamPlot xs ys vs ls cs gs cm ss xa ya t z b _) =
omitNulls [ "points" .= getPoints xs ys
, "values" .= vs
, "labels" .= ls
, "color" .= cs
, "group" .= gs
, "colormap" .= cm
, "size" .= ss
, "xaxis" .= xa
, "yaxis" .= ya
, "tooltips" .= t
, "zoom" .= z
, "brush" .= b
]
instance ValidatablePlot ScatterStreamPlot where
validatePlot (ScatterStreamPlot xs ys v lbl c grp cm s xa ya tt z b viz) = do
(xs', ys') <- validateCoordinates xs ys
c' <- validateColor c
cm' <- validateColorMap cm
s' <- validateSize s
return $ ScatterStreamPlot xs' ys' v lbl c' grp cm' s' xa ya tt z b viz
streamingScatterPlot :: Monad m => ScatterStreamPlot
-> LightningT m Visualization
streamingScatterPlot slp = do
url <- ask
viz' <- streamPlot (sspVisualization slp) "scatter-streaming" slp R.plot
return $ viz' { vizBaseUrl = Just url }