Commit 1ff8f16d authored by Kai Zhang's avatar Kai Zhang

add more functions

parent 22ca7495
Revision history for haskell-igraph Revision history for haskell-igraph
=================================== ===================================
v0.7.0 --
-----------
* Add more functions and tests.
* Internal interface redesign.
v0.6.0 -- 2018-05-10 v0.6.0 -- 2018-05-10
-------------------- --------------------
......
name: haskell-igraph name: haskell-igraph
version: 0.7.0-dev version: 0.7.0
synopsis: Haskell interface of the igraph library. synopsis: Haskell interface of the igraph library.
description: igraph<"http://igraph.org/c/"> is a library for creating description: igraph<"http://igraph.org/c/"> is a library for creating
and manipulating large graphs. This package provides the Haskell and manipulating large graphs. This package provides the Haskell
...@@ -40,6 +40,7 @@ library ...@@ -40,6 +40,7 @@ library
IGraph.Algorithms.Motif IGraph.Algorithms.Motif
IGraph.Algorithms.Generators IGraph.Algorithms.Generators
IGraph.Algorithms.Isomorphism IGraph.Algorithms.Isomorphism
IGraph.Algorithms.Centrality
other-modules: other-modules:
IGraph.Internal.C2HS IGraph.Internal.C2HS
......
...@@ -6,6 +6,7 @@ module IGraph.Algorithms ...@@ -6,6 +6,7 @@ module IGraph.Algorithms
, module IGraph.Algorithms.Motif , module IGraph.Algorithms.Motif
, module IGraph.Algorithms.Generators , module IGraph.Algorithms.Generators
, module IGraph.Algorithms.Isomorphism , module IGraph.Algorithms.Isomorphism
, module IGraph.Algorithms.Centrality
) where ) where
import IGraph.Algorithms.Structure import IGraph.Algorithms.Structure
...@@ -15,3 +16,4 @@ import IGraph.Algorithms.Layout ...@@ -15,3 +16,4 @@ import IGraph.Algorithms.Layout
import IGraph.Algorithms.Motif import IGraph.Algorithms.Motif
import IGraph.Algorithms.Generators import IGraph.Algorithms.Generators
import IGraph.Algorithms.Isomorphism import IGraph.Algorithms.Isomorphism
import IGraph.Algorithms.Centrality
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Algorithms.Centrality
( closeness
, betweenness
, eigenvectorCentrality
, pagerank
) where
import Control.Monad
import Data.Serialize (Serialize)
import Data.List (foldl')
import System.IO.Unsafe (unsafePerformIO)
import Data.Maybe
import Data.Singletons (SingI)
import Foreign
import Foreign.C.Types
import IGraph
{#import IGraph.Internal #}
{#import IGraph.Internal.Constants #}
#include "haskell_igraph.h"
-- | The normalized closeness centrality of a node is the average length of the
-- shortest path between the node and all other nodes in the graph.
closeness :: [Int] -- ^ vertices
-> Graph d v e
-> Maybe [Double] -- ^ optional edge weights
-> Bool -- ^ whether to normalize the results
-> [Double]
closeness nds gr ws normal = unsafePerformIO $ allocaVector $ \result ->
withVerticesList nds $ \vs -> withListMaybe ws $ \ws' -> do
igraphCloseness (_graph gr) result vs IgraphOut ws' normal
toList result
{#fun igraph_closeness as ^
{ `IGraph'
, castPtr `Ptr Vector'
, castPtr %`Ptr VertexSelector'
, `Neimode'
, castPtr `Ptr Vector'
, `Bool' } -> `CInt' void- #}
-- | Betweenness centrality
betweenness :: [Int]
-> Graph d v e
-> Maybe [Double]
-> [Double]
betweenness nds gr ws = unsafePerformIO $ allocaVector $ \result ->
withVerticesList nds $ \vs -> withListMaybe ws $ \ws' -> do
igraphBetweenness (_graph gr) result vs True ws' False
toList result
{#fun igraph_betweenness as ^
{ `IGraph'
, castPtr `Ptr Vector'
, castPtr %`Ptr VertexSelector'
, `Bool'
, castPtr `Ptr Vector'
, `Bool' } -> `CInt' void- #}
-- | Eigenvector centrality
eigenvectorCentrality :: Graph d v e
-> Maybe [Double]
-> [Double]
eigenvectorCentrality gr ws = unsafePerformIO $ allocaArpackOpt $ \arparck ->
allocaVector $ \result -> withListMaybe ws $ \ws' -> do
igraphEigenvectorCentrality (_graph gr) result nullPtr True True ws' arparck
toList result
{#fun igraph_eigenvector_centrality as ^
{ `IGraph'
, castPtr `Ptr Vector'
, id `Ptr CDouble'
, `Bool'
, `Bool'
, castPtr `Ptr Vector'
, castPtr `Ptr ArpackOpt' } -> `CInt' void- #}
-- | Google's PageRank algorithm, with option to
pagerank :: SingI d
=> Graph d v e
-> Maybe [Double] -- ^ Node weights or reset probability. If provided,
-- the personalized PageRank will be used
-> Maybe [Double] -- ^ Edge weights
-> Double -- ^ damping factor, usually around 0.85
-> [Double]
pagerank gr reset ws d
| n == 0 = []
| isJust ws && length (fromJust ws) /= m = error "incorrect length of edge weight vector"
| isJust reset && length (fromJust reset) /= n = error
"incorrect length of node weight vector"
| fmap (foldl' (+) 0) reset == Just 0 = error "sum of node weight vector must be non-zero"
| otherwise = unsafePerformIO $ alloca $ \p -> allocaVector $ \result ->
withVerticesAll $ \vs -> withListMaybe ws $ \ws' -> do
case reset of
Nothing -> igraphPagerank (_graph gr) IgraphPagerankAlgoPrpack
result p vs (isDirected gr) d ws' nullPtr
Just reset' -> withList reset' $ \reset'' -> igraphPersonalizedPagerank
(_graph gr) IgraphPagerankAlgoPrpack result p vs
(isDirected gr) d reset'' ws' nullPtr
toList result
where
n = nNodes gr
m = nEdges gr
{#fun igraph_pagerank as ^
{ `IGraph'
, `PagerankAlgo'
, castPtr `Ptr Vector'
, id `Ptr CDouble'
, castPtr %`Ptr VertexSelector'
, `Bool'
, `Double'
, castPtr `Ptr Vector'
, id `Ptr ()'
} -> `CInt' void- #}
{#fun igraph_personalized_pagerank as ^
{ `IGraph'
, `PagerankAlgo'
, castPtr `Ptr Vector'
, id `Ptr CDouble'
, castPtr %`Ptr VertexSelector'
, `Bool'
, `Double'
, castPtr `Ptr Vector'
, castPtr `Ptr Vector'
, id `Ptr ()'
} -> `CInt' void- #}
...@@ -3,11 +3,12 @@ module IGraph.Algorithms.Structure ...@@ -3,11 +3,12 @@ module IGraph.Algorithms.Structure
( -- * Shortest Path Related Functions ( -- * Shortest Path Related Functions
getShortestPath getShortestPath
, inducedSubgraph , inducedSubgraph
, isConnected
, isStronglyConnected
, decompose , decompose
, closeness , isDag
, betweenness , topSort
, eigenvectorCentrality , topSortUnsafe
, pagerank
) where ) where
import Control.Monad import Control.Monad
...@@ -21,6 +22,7 @@ import Foreign ...@@ -21,6 +22,7 @@ import Foreign
import Foreign.C.Types import Foreign.C.Types
import IGraph import IGraph
import IGraph.Internal.C2HS
{#import IGraph.Internal #} {#import IGraph.Internal #}
{#import IGraph.Internal.Constants #} {#import IGraph.Internal.Constants #}
...@@ -67,6 +69,17 @@ inducedSubgraph gr nds = unsafePerformIO $ withVerticesList nds $ \vs -> ...@@ -67,6 +69,17 @@ inducedSubgraph gr nds = unsafePerformIO $ withVerticesList nds $ \vs ->
, `SubgraphImplementation' , `SubgraphImplementation'
} -> `CInt' void- #} } -> `CInt' void- #}
-- | Decides whether the graph is weakly connected.
isConnected :: Graph d v e -> Bool
isConnected gr = igraphIsConnected (_graph gr) IgraphWeak
isStronglyConnected :: Graph 'D v e -> Bool
isStronglyConnected gr = igraphIsConnected (_graph gr) IgraphStrong
{#fun igraph_is_connected as ^
{ `IGraph'
, alloca- `Bool' peekBool*
, `Connectedness'
} -> `CInt' void- #}
-- | Decompose a graph into connected components. -- | Decompose a graph into connected components.
decompose :: (Ord v, Serialize v) decompose :: (Ord v, Serialize v)
...@@ -86,108 +99,30 @@ decompose gr = unsafePerformIO $ allocaVectorPtr $ \ptr -> do ...@@ -86,108 +99,30 @@ decompose gr = unsafePerformIO $ allocaVectorPtr $ \ptr -> do
, `Int' , `Int'
} -> `CInt' void- #} } -> `CInt' void- #}
-- | Closeness centrality
closeness :: [Int] -- ^ vertices
-> Graph d v e
-> Maybe [Double] -- ^ optional edge weights
-> Neimode
-> Bool -- ^ whether to normalize
-> [Double]
closeness nds gr ws mode normal = unsafePerformIO $ allocaVector $ \result ->
withVerticesList nds $ \vs -> withListMaybe ws $ \ws' -> do
igraphCloseness (_graph gr) result vs mode ws' normal
toList result
{#fun igraph_closeness as ^
{ `IGraph'
, castPtr `Ptr Vector'
, castPtr %`Ptr VertexSelector'
, `Neimode'
, castPtr `Ptr Vector'
, `Bool' } -> `CInt' void- #}
-- | Betweenness centrality
betweenness :: [Int]
-> Graph d v e
-> Maybe [Double]
-> [Double]
betweenness nds gr ws = unsafePerformIO $ allocaVector $ \result ->
withVerticesList nds $ \vs -> withListMaybe ws $ \ws' -> do
igraphBetweenness (_graph gr) result vs True ws' False
toList result
{#fun igraph_betweenness as ^
{ `IGraph'
, castPtr `Ptr Vector'
, castPtr %`Ptr VertexSelector'
, `Bool'
, castPtr `Ptr Vector'
, `Bool' } -> `CInt' void- #}
-- | Eigenvector centrality -- | Checks whether a graph is a directed acyclic graph (DAG) or not.
eigenvectorCentrality :: Graph d v e isDag :: Graph d v e -> Bool
-> Maybe [Double] isDag = igraphIsDag . _graph
-> [Double] {#fun pure igraph_is_dag as ^
eigenvectorCentrality gr ws = unsafePerformIO $ allocaArpackOpt $ \arparck ->
allocaVector $ \result -> withListMaybe ws $ \ws' -> do
igraphEigenvectorCentrality (_graph gr) result nullPtr True True ws' arparck
toList result
{#fun igraph_eigenvector_centrality as ^
{ `IGraph' { `IGraph'
, castPtr `Ptr Vector' , alloca- `Bool' peekBool*
, id `Ptr CDouble' } -> `CInt' void- #}
, `Bool'
, `Bool'
, castPtr `Ptr Vector'
, castPtr `Ptr ArpackOpt' } -> `CInt' void- #}
-- | Google's PageRank algorithm, with option to -- | Calculate a possible topological sorting of the graph.
pagerank :: SingI d topSort :: Graph d v e -> [Node]
=> Graph d v e topSort gr | isDag gr = topSortUnsafe gr
-> Maybe [Double] -- ^ Node weights or reset probability. If provided, | otherwise = error "the graph is not acyclic"
-- the personalized PageRank will be used
-> Maybe [Double] -- ^ Edge weights -- | Calculate a possible topological sorting of the graph. If the graph is not
-> Double -- ^ damping factor, usually around 0.85 -- acyclic (it has at least one cycle), a partial topological sort is returned.
-> [Double] topSortUnsafe :: Graph d v e -> [Node]
pagerank gr reset ws d topSortUnsafe gr = unsafePerformIO $ allocaVectorN n $ \res -> do
| n == 0 = [] igraphTopologicalSorting (_graph gr) res IgraphOut
| isJust ws && length (fromJust ws) /= m = error "incorrect length of edge weight vector" map truncate <$> toList res
| isJust reset && length (fromJust reset) /= n = error
"incorrect length of node weight vector"
| fmap (foldl' (+) 0) reset == Just 0 = error "sum of node weight vector must be non-zero"
| otherwise = unsafePerformIO $ alloca $ \p -> allocaVector $ \result ->
withVerticesAll $ \vs -> withListMaybe ws $ \ws' -> do
case reset of
Nothing -> igraphPagerank (_graph gr) IgraphPagerankAlgoPrpack
result p vs (isDirected gr) d ws' nullPtr
Just reset' -> withList reset' $ \reset'' -> igraphPersonalizedPagerank
(_graph gr) IgraphPagerankAlgoPrpack result p vs
(isDirected gr) d reset'' ws' nullPtr
toList result
where where
n = nNodes gr n = nNodes gr
m = nEdges gr {#fun igraph_topological_sorting as ^
{#fun igraph_pagerank as ^
{ `IGraph'
, `PagerankAlgo'
, castPtr `Ptr Vector'
, id `Ptr CDouble'
, castPtr %`Ptr VertexSelector'
, `Bool'
, `Double'
, castPtr `Ptr Vector'
, id `Ptr ()'
} -> `CInt' void- #}
{#fun igraph_personalized_pagerank as ^
{ `IGraph' { `IGraph'
, `PagerankAlgo'
, castPtr `Ptr Vector' , castPtr `Ptr Vector'
, id `Ptr CDouble' , `Neimode'
, castPtr %`Ptr VertexSelector'
, `Bool'
, `Double'
, castPtr `Ptr Vector'
, castPtr `Ptr Vector'
, id `Ptr ()'
} -> `CInt' void- #} } -> `CInt' void- #}
...@@ -136,3 +136,12 @@ setEdgeAttr :: (PrimMonad m, Serialize e) ...@@ -136,3 +136,12 @@ setEdgeAttr :: (PrimMonad m, Serialize e)
-> m () -> m ()
setEdgeAttr edgeId x gr = unsafePrimToPrim $ setEdgeAttr edgeId x gr = unsafePrimToPrim $
withByteString (encode x) $ igraphHaskellAttributeEASSet (_mgraph gr) edgeAttr edgeId withByteString (encode x) $ igraphHaskellAttributeEASSet (_mgraph gr) edgeAttr edgeId
{-
-- | Removes loop and/or multiple edges from the graph.
simplify :: Bool -- ^ If true, multiple edges will be removed.
-> Bool -- ^ If true, loops (self edges) will be removed.
->
-> Graph d v e -> Graph d v e
simplify delMul delLoop fun gr = do
-}
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