Commit e4cac031 authored by Kai Zhang's avatar Kai Zhang

v0.7.0

parent 1ff8f16d
Revision history for haskell-igraph Revision history for haskell-igraph
=================================== ===================================
v0.7.0 -- v0.7.0 -- 2018-05-23
----------- --------------------
* Add more functions and tests. * Add more functions and tests.
* Internal interface redesign. * Internal interface redesign.
......
{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE DataKinds #-}
module IGraph.Algorithms.Structure module IGraph.Algorithms.Structure
( -- * Shortest Path Related Functions ( -- * Shortest Path Related Functions
getShortestPath getShortestPath
...@@ -75,7 +76,8 @@ isConnected gr = igraphIsConnected (_graph gr) IgraphWeak ...@@ -75,7 +76,8 @@ isConnected gr = igraphIsConnected (_graph gr) IgraphWeak
isStronglyConnected :: Graph 'D v e -> Bool isStronglyConnected :: Graph 'D v e -> Bool
isStronglyConnected gr = igraphIsConnected (_graph gr) IgraphStrong isStronglyConnected gr = igraphIsConnected (_graph gr) IgraphStrong
{#fun igraph_is_connected as ^
{#fun pure igraph_is_connected as ^
{ `IGraph' { `IGraph'
, alloca- `Bool' peekBool* , alloca- `Bool' peekBool*
, `Connectedness' , `Connectedness'
......
...@@ -141,7 +141,7 @@ setEdgeAttr edgeId x gr = unsafePrimToPrim $ ...@@ -141,7 +141,7 @@ setEdgeAttr edgeId x gr = unsafePrimToPrim $
-- | Removes loop and/or multiple edges from the graph. -- | Removes loop and/or multiple edges from the graph.
simplify :: Bool -- ^ If true, multiple edges will be removed. simplify :: Bool -- ^ If true, multiple edges will be removed.
-> Bool -- ^ If true, loops (self edges) will be removed. -> Bool -- ^ If true, loops (self edges) will be removed.
-> -> ([e] -> e) -- ^ Edge c
-> Graph d v e -> Graph d v e -> Graph d v e -> Graph d v e
simplify delMul delLoop fun gr = do simplify delMul delLoop fun gr = do
-} -}
...@@ -20,6 +20,7 @@ tests = testGroup "Basic tests" ...@@ -20,6 +20,7 @@ tests = testGroup "Basic tests"
[ graphCreation [ graphCreation
, graphCreationLabeled , graphCreationLabeled
, graphEdit , graphEdit
, nonSimpleGraphTest
] ]
graphCreation :: TestTree graphCreation :: TestTree
...@@ -69,3 +70,15 @@ graphEdit = testGroup "Graph editing" ...@@ -69,3 +70,15 @@ graphEdit = testGroup "Graph editing"
freeze g freeze g
getEdges gr = map getEdges gr = map
(\(a,b) -> ((nodeLab gr a, nodeLab gr b), edgeLab gr (a,b))) $ edges gr (\(a,b) -> ((nodeLab gr a, nodeLab gr b), edgeLab gr (a,b))) $ edges gr
nonSimpleGraphTest :: TestTree
nonSimpleGraphTest = testGroup "loops, multiple edges"
[ testCase "case 1" $ es @=? labEdges gr
]
where
es = [ ((0,1), 'a')
, ((1,2), 'b')
, ((1,2), 'c')
, ((0,2), 'd') ]
gr :: Graph 'U Int Char
gr = mkGraph [0,1,2] es
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment