module Web.Lightning.Plots.Force
(
ForcePlot(..)
, Visualization (..)
, forcePlot
)
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 ForcePlot =
ForcePlot { fpConn :: [[Double]]
, fpValues :: Maybe [Double]
, fpLabels :: Maybe [T.Text]
, fpColor :: Maybe [Int]
, fpGroup :: Maybe [Int]
, fpColorMap :: Maybe T.Text
, fpSize :: Maybe [Int]
, fpToolTips :: Maybe Bool
, fpZoom :: Maybe Bool
, fpBrush :: Maybe Bool
}
deriving (Show, Eq)
instance Default ForcePlot where
def = ForcePlot [[]] Nothing Nothing Nothing Nothing Nothing
Nothing (Just True) (Just True) (Just True)
instance ToJSON ForcePlot where
toJSON (ForcePlot conn vs lbs cs gs cm ss tt z b) =
omitNulls [ "links" .= getLinks conn
, "nodes" .= getNodes conn
, "values" .= vs
, "labels" .= lbs
, "color" .= cs
, "group" .= gs
, "colormap" .= cm
, "size" .= ss
, "tooltips" .= tt
, "zoom" .= z
, "brush" .= b
]
instance ValidatablePlot ForcePlot where
validatePlot (ForcePlot conn vl lbl c grp cm s tt z b) = do
conn' <- validateConn conn
c' <- validateColor c
cm' <- validateColorMap cm
s' <- validateSize s
return $ ForcePlot conn' vl lbl c' grp cm' s' tt z b
forcePlot :: Monad m => ForcePlot
-> LightningT m Visualization
forcePlot forcePlt = do
url <- ask
viz <- sendPlot "force" forcePlt R.plot
return $ viz { vizBaseUrl = Just url }