Commit bdaeae38 authored by Kai Zhang's avatar Kai Zhang

forget to add igraphInit

parent de2ab7cc
...@@ -42,6 +42,10 @@ module IGraph ...@@ -42,6 +42,10 @@ module IGraph
, nfilter , nfilter
, efilter , efilter
-- * Non-simple graphs: multiple and loop edges
, isSimple
, hasMultiple
) where ) where
import Conduit import Conduit
...@@ -316,3 +320,16 @@ efilter f gr = runST $ do ...@@ -316,3 +320,16 @@ efilter f gr = runST $ do
gr' <- thaw gr gr' <- thaw gr
GM.delEdges deleted gr' GM.delEdges deleted gr'
unsafeFreeze gr' unsafeFreeze gr'
-- | Decides whether the input graph is a simple graph. A graph is a simple
-- graph if it does not contain loop edges and multiple edges.
isSimple :: Graph d v e -> Bool
isSimple = unsafePerformIO . igraphIsSimple . _graph
{-# INLINE isSimple #-}
-- | Check whether the graph has at least one multiple edge. An edge is a
-- multiple edge if there is another edge with the same head and tail vertices
-- in the graph.
hasMultiple :: Graph d v e -> Bool
hasMultiple = unsafePerformIO . igraphHasMultiple . _graph
{-# INLINE hasMultiple #-}
...@@ -33,6 +33,7 @@ full :: forall d. SingI d ...@@ -33,6 +33,7 @@ full :: forall d. SingI d
-> Bool -- ^ Whether to include self-edges (loops) -> Bool -- ^ Whether to include self-edges (loops)
-> Graph d () () -> Graph d () ()
full n hasLoop = unsafePerformIO $ do full n hasLoop = unsafePerformIO $ do
igraphInit
gr <- MGraph <$> igraphFull n directed hasLoop gr <- MGraph <$> igraphFull n directed hasLoop
M.initializeNullAttribute gr M.initializeNullAttribute gr
unsafeFreeze gr unsafeFreeze gr
...@@ -49,6 +50,7 @@ full n hasLoop = unsafePerformIO $ do ...@@ -49,6 +50,7 @@ full n hasLoop = unsafePerformIO $ do
star :: Int -- ^ The number of nodes star :: Int -- ^ The number of nodes
-> Graph 'U () () -> Graph 'U () ()
star n = unsafePerformIO $ do star n = unsafePerformIO $ do
igraphInit
gr <- MGraph <$> igraphStar n IgraphStarUndirected 0 gr <- MGraph <$> igraphStar n IgraphStarUndirected 0
M.initializeNullAttribute gr M.initializeNullAttribute gr
unsafeFreeze gr unsafeFreeze gr
...@@ -87,11 +89,13 @@ erdosRenyiGame model self = do ...@@ -87,11 +89,13 @@ erdosRenyiGame model self = do
degreeSequenceGame :: [Int] -- ^ Out degree degreeSequenceGame :: [Int] -- ^ Out degree
-> [Int] -- ^ In degree -> [Int] -- ^ In degree
-> IO (Graph 'D () ()) -> IO (Graph 'D () ())
degreeSequenceGame out_deg in_deg = withList out_deg $ \out_deg' -> degreeSequenceGame out_deg in_deg = do
withList in_deg $ \in_deg' -> do igraphInit
gr <- MGraph <$> igraphDegreeSequenceGame out_deg' in_deg' IgraphDegseqSimple withList out_deg $ \out_deg' ->
M.initializeNullAttribute gr withList in_deg $ \in_deg' -> do
unsafeFreeze gr gr <- MGraph <$> igraphDegreeSequenceGame out_deg' in_deg' IgraphDegseqSimple
M.initializeNullAttribute gr
unsafeFreeze gr
{#fun igraph_degree_sequence_game as ^ {#fun igraph_degree_sequence_game as ^
{ allocaIGraph- `IGraph' addIGraphFinalizer* { allocaIGraph- `IGraph' addIGraphFinalizer*
, castPtr `Ptr Vector', castPtr `Ptr Vector', `Degseq' , castPtr `Ptr Vector', castPtr `Ptr Vector', `Degseq'
......
...@@ -14,6 +14,7 @@ import Data.Either (fromRight) ...@@ -14,6 +14,7 @@ import Data.Either (fromRight)
import Data.Hashable (Hashable) import Data.Hashable (Hashable)
import qualified Data.HashMap.Strict as M import qualified Data.HashMap.Strict as M
import Data.Serialize (Serialize, decode) import Data.Serialize (Serialize, decode)
import Data.List (foldl')
import System.IO.Unsafe (unsafePerformIO) import System.IO.Unsafe (unsafePerformIO)
import Data.Maybe import Data.Maybe
import Data.Singletons (SingI) import Data.Singletons (SingI)
...@@ -134,6 +135,9 @@ pagerank :: SingI d ...@@ -134,6 +135,9 @@ pagerank :: SingI d
pagerank gr reset ws d pagerank gr reset ws d
| n == 0 = [] | n == 0 = []
| isJust ws && length (fromJust ws) /= m = error "incorrect length of edge weight vector" | 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 -> | otherwise = unsafePerformIO $ alloca $ \p -> allocaVector $ \result ->
withVerticesAll $ \vs -> withListMaybe ws $ \ws' -> do withVerticesAll $ \vs -> withListMaybe ws $ \ws' -> do
case reset of case reset of
......
...@@ -56,6 +56,8 @@ module IGraph.Internal ...@@ -56,6 +56,8 @@ module IGraph.Internal
, addIGraphFinalizer , addIGraphFinalizer
, igraphNew , igraphNew
, igraphCreate , igraphCreate
, igraphIsSimple
, igraphHasMultiple
-- * Selector and iterator for edge and vertex -- * Selector and iterator for edge and vertex
-- ** Igraph vertex selector -- ** Igraph vertex selector
...@@ -386,6 +388,17 @@ igraphNew n directed _ = igraphNew' n directed ...@@ -386,6 +388,17 @@ igraphNew n directed _ = igraphNew' n directed
-- to the second, etc. -- to the second, etc.
} -> `CInt' void- #} } -> `CInt' void- #}
-- | A graph is a simple graph if it does not contain loop edges and multiple edges.
{#fun igraph_is_simple as ^
{ `IGraph'
, alloca- `Bool' peekBool*
} -> `CInt' void- #}
{#fun igraph_has_multiple as ^
{ `IGraph'
, alloca- `Bool' peekBool*
} -> `CInt' void- #}
{#fun igraph_to_directed as ^ {#fun igraph_to_directed as ^
{ `IGraph' -- ^ The graph object to convert. { `IGraph' -- ^ The graph object to convert.
, `ToDirected' -- ^ Specifies the details of how exactly the conversion is , `ToDirected' -- ^ Specifies the details of how exactly the conversion is
......
...@@ -4,7 +4,7 @@ module IGraph.Internal.C2HS ( ...@@ -4,7 +4,7 @@ module IGraph.Internal.C2HS (
cIntConv, cFloatConv, cToBool, cFromBool, cToEnum, cFromEnum, cIntConv, cFloatConv, cToBool, cFromBool, cToEnum, cFromEnum,
-- * Composite marshalling functions -- * Composite marshalling functions
peekIntConv, peekFloatConv, peekIntConv, peekFloatConv, peekBool
) where ) where
...@@ -64,10 +64,14 @@ cFromEnum = cIntConv . fromEnum ...@@ -64,10 +64,14 @@ cFromEnum = cIntConv . fromEnum
-- | Marshalling of numerals -- | Marshalling of numerals
-- --
{-# INLINE peekIntConv #-}
peekIntConv :: (Storable a, Integral a, Integral b) => Ptr a -> IO b peekIntConv :: (Storable a, Integral a, Integral b) => Ptr a -> IO b
peekIntConv = liftM cIntConv . peek peekIntConv = liftM cIntConv . peek
{-# INLINE peekIntConv #-}
peekBool :: (Storable a, Eq a, Num a) => Ptr a -> IO Bool
peekBool = liftM cToBool . peek
{-# INLINE peekBool #-}
{-# INLINE peekFloatConv #-}
peekFloatConv :: (Storable a, RealFloat a, RealFloat b) => Ptr a -> IO b peekFloatConv :: (Storable a, RealFloat a, RealFloat b) => Ptr a -> IO b
peekFloatConv = liftM cFloatConv . peek peekFloatConv = liftM cFloatConv . peek
{-# INLINE peekFloatConv #-}
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