module Web.Lightning.Plots.Adjacency
(
AdjacencyPlot(..)
, Visualization (..)
, adjacencyPlot
)
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 AdjacencyPlot =
AdjacencyPlot { apConn :: [[Double]]
, apLabels :: Maybe [T.Text]
, apGroup :: Maybe [Int]
, apSort :: Maybe T.Text
, apNumbers :: Maybe Bool
, apSymmetric :: Maybe Bool
}
deriving (Show, Eq)
instance Default AdjacencyPlot where
def = AdjacencyPlot [[]] Nothing Nothing (Just "group") (Just False) (Just True)
instance ToJSON AdjacencyPlot where
toJSON (AdjacencyPlot conn lbs grps srt nbrs sym) =
omitNulls [ "links" .= getLinks conn
, "nodes" .= getNodes conn
, "labels" .= lbs
, "group" .= grps
, "numbers" .= nbrs
, "symmetric" .= sym
, "srt" .= srt
]
instance ValidatablePlot AdjacencyPlot where
validatePlot (AdjacencyPlot conn lbls grp srt nbrs sym) = do
conn' <- validateConn conn
return $ AdjacencyPlot conn' lbls grp srt nbrs sym
adjacencyPlot :: Monad m => AdjacencyPlot
-> LightningT m Visualization
adjacencyPlot adjPlt = do
url <- ask
viz <- sendPlot "adjacency" adjPlt R.plot
return $ viz { vizBaseUrl = Just url }