module Web.Lightning.Plots.Scatter3
(
Scatter3Plot(..)
, Visualization (..)
, scatter3Plot
)
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 Scatter3Plot =
Scatter3Plot { sptX :: [Double]
, sptY :: [Double]
, sptZ :: [Double]
, sptColors :: Maybe [Int]
, sptGroups :: Maybe [Int]
, sptSize :: Maybe [Int]
, sptAlpha :: Maybe [Double]
}
deriving (Show, Eq)
instance Default Scatter3Plot where
def = Scatter3Plot [] [] [] Nothing Nothing Nothing Nothing
instance ToJSON Scatter3Plot where
toJSON (Scatter3Plot xs ys zs cs gs ss as) =
omitNulls [ "points" .= getPoints3 xs ys zs
, "color" .= cs
, "group" .= gs
, "size" .= ss
, "alpha" .= as
]
instance ValidatablePlot Scatter3Plot where
validatePlot (Scatter3Plot xs ys zs c g s a) = do
(xs', ys', zs') <- validateCoordinates3 xs ys zs
c' <- validateColor c
s' <- validateSize s
a' <- validateAlpha a
return $ Scatter3Plot xs' ys' zs' c' g s' a'
scatter3Plot :: Monad m => Scatter3Plot
-> LightningT m Visualization
scatter3Plot scatter3Plt = do
url <- ask
viz <- sendPlot "scatter-3" scatter3Plt R.plot
return $ viz { vizBaseUrl = Just url }