module Web.Lightning.Plots.LineStream
(
LineStreamPlot(..)
, Visualization (..)
, streamingLinePlot
)
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 LineStreamPlot =
LineStreamPlot { lspSeries :: [[Double]]
, lspIndex :: Maybe [Int]
, lspColor :: Maybe [Int]
, lspGroup :: Maybe [Int]
, lspSize :: Maybe [Int]
, lspXAxis :: Maybe T.Text
, lspYAxis :: Maybe T.Text
, lspMaxWidth :: Maybe Int
, lspZoom :: Maybe Bool
, lspVisualization :: Maybe Visualization
}
deriving (Show)
instance Default LineStreamPlot where
def = LineStreamPlot [[]] Nothing Nothing Nothing Nothing
Nothing Nothing Nothing (Just True) Nothing
instance ToJSON LineStreamPlot where
toJSON (LineStreamPlot ss is cs gs t xa ya mw z _) =
omitNulls [ "series" .= ss
, "index" .= is
, "color" .= cs
, "group" .= gs
, "size" .= t
, "xaxis" .= xa
, "yaxis" .= ya
, "max_width" .= mw
, "zoom" .= z
]
instance ValidatablePlot LineStreamPlot where
validatePlot (LineStreamPlot ss i c g s xa ya mw z viz) = do
i' <- validateIndex i
c' <- validateColor c
s' <- validateSize s
return $ LineStreamPlot ss i' c' g s' xa ya mw z viz
streamingLinePlot :: Monad m => LineStreamPlot
-> LightningT m Visualization
streamingLinePlot slp = do
url <- ask
viz <- streamPlot (lspVisualization slp) "line-streaming" slp R.plot
return $ viz { vizBaseUrl = Just url }