{-# LANGUAGE OverloadedStrings, DeriveGeneric #-} module NetSpider.GraphML.WriterSpec (main,spec) where import Data.Aeson (ToJSON(..), genericToEncoding, defaultOptions) import Data.List (sortOn) import Data.Maybe (fromJust) import Data.Text (Text) import qualified Data.Text.Lazy as TL -- import qualified Data.Text.Lazy.IO as TLIO import GHC.Generics (Generic) import NetSpider.Snapshot.Internal ( SnapshotNode(..), SnapshotLink(..) ) import NetSpider.Timestamp (fromEpochMillisecond, fromS) import Test.Hspec import NetSpider.GraphML.Writer ( writeGraphML, ToAttributes(..), AttributeValue(..), attributesFromAeson, writeGraphMLWith, defWriteOption, woptDefaultDirected ) main :: IO () main = hspec spec data Att1 = Att1 { at1Hoge :: Int, at1Foo :: Text, at1Buzz :: Bool } deriving (Show,Eq,Ord) instance ToAttributes Att1 where toAttributes a = [ ("hoge", AttrInt $ at1Hoge a), ("foo", AttrString $ at1Foo a), ("buzz", AttrBoolean $ at1Buzz a) ] data Att2 = Att2 { at2_quux :: Double, at2_huga :: Text } deriving (Show,Eq,Ord,Generic) instance ToJSON Att2 where toEncoding = genericToEncoding defaultOptions instance ToAttributes Att2 where toAttributes a = sortOn fst $ fromJust $ attributesFromAeson $ toJSON a spec :: Spec spec = do describe "writeGraphML" $ do specify "no attribute, directed and undirected mixed, node id escaped" $ do let time_with_tz = fromS "2018-09-23T08:48:52+09:00" nodes :: [SnapshotNode Text ()] nodes = [ SnapshotNode { _nodeId = "\"the root\"", _isOnBoundary = False, _nodeTimestamp = Just $ fromEpochMillisecond 100, _nodeAttributes = Just () }, SnapshotNode { _nodeId = "☃", _isOnBoundary = True, _nodeTimestamp = Nothing, _nodeAttributes = Nothing }, SnapshotNode { _nodeId = "", _isOnBoundary = False, _nodeTimestamp = Just $ time_with_tz, _nodeAttributes = Just () } ] links :: [SnapshotLink Text ()] links = [ SnapshotLink { _sourceNode = "\"the root\"", _destinationNode = "☃", _isDirected = True, _linkTimestamp = fromEpochMillisecond 100, _linkAttributes = () }, SnapshotLink { _sourceNode = "", _destinationNode = "\"the root\"", _isDirected = False, _linkTimestamp = time_with_tz, _linkAttributes = () } ] expected = mconcat $ map (<> "\n") [ "", "", "", "", "", "", "", "", "", "", "", "", "", "", " ", " 100", " 1970-01-01T00:00:00.100", " false", " ", " ", " true", " ", " ", " 1537660132000", " 2018-09-23T08:48:52.000+09:00", " 540", " false", " ", " false", " ", " ", " 100", " 1970-01-01T00:00:00.100", " ", " ", " 1537660132000", " 2018-09-23T08:48:52.000+09:00", " 540", " false", " ", " ", "", "" ] got = writeGraphML (nodes, links) -- TLIO.putStrLn got got `shouldBe` expected specify "with attributes" $ do let nodes :: [SnapshotNode Int Att1] nodes = [ SnapshotNode { _nodeId = 100, _isOnBoundary = False, _nodeTimestamp = Just $ fromEpochMillisecond 155, _nodeAttributes = Just $ Att1 { at1Hoge = 99, at1Foo = "new\nline", at1Buzz = False } }, SnapshotNode { _nodeId = 200, _isOnBoundary = False, _nodeTimestamp = Nothing, _nodeAttributes = Just $ Att1 { at1Hoge = 2099, at1Foo = "", at1Buzz = True } } ] links :: [SnapshotLink Int Att2] links = [ SnapshotLink { _sourceNode = 100, _destinationNode = 200, _isDirected = True, _linkTimestamp = fromEpochMillisecond 155, _linkAttributes = Att2 { at2_quux = 109.25, at2_huga = "HUGA" } } ] expected = mconcat $ map (<> "\n") [ "", "", "", "", "", "", "", "", "", "", "", "", "", " ", " 155", " 1970-01-01T00:00:00.155", " false", " 99", " new line", " false", " ", " ", " false", " 2099", " ", " true", " ", " ", " 155", " 1970-01-01T00:00:00.155", " HUGA", " 109.25", " ", "", "" ] got = writeGraphML (nodes, links) -- TLIO.putStrLn got got `shouldBe` expected describe "writeGraphMLWith" $ do specify "woptDefaultDirected = False" $ do let nodes :: [SnapshotNode Text ()] nodes = [ SnapshotNode { _nodeId = "n1", _isOnBoundary = False, _nodeTimestamp = Just $ fromEpochMillisecond 200, _nodeAttributes = Just () }, SnapshotNode { _nodeId = "n2", _isOnBoundary = False, _nodeTimestamp = Nothing, _nodeAttributes = Nothing } ] links :: [SnapshotLink Text ()] links = [ SnapshotLink { _sourceNode = "n1", _destinationNode = "n2", _isDirected = True, _linkTimestamp = fromEpochMillisecond 200, _linkAttributes = () } ] expected = mconcat $ map (<> "\n") [ "", "", "", "", "", "", "", "", " ", " 200", " 1970-01-01T00:00:00.200", " false", " ", " ", " false", " ", " ", " 200", " 1970-01-01T00:00:00.200", " ", "", "" ] opt = defWriteOption { woptDefaultDirected = False } got = writeGraphMLWith opt (nodes, links) got `shouldBe` expected