Commit b9066467 authored by Kai Zhang's avatar Kai Zhang

add more functions

parent 12ba3923
......@@ -76,3 +76,8 @@ void igraph_arpack_destroy(igraph_arpack_options_t* arpack)
free(arpack);
arpack = NULL;
}
igraph_vs_t* igraph_vs_new() {
igraph_vs_t* vs = (igraph_vs_t*) malloc (sizeof (igraph_vs_t));
return vs;
}
......@@ -17,17 +17,21 @@ cabal-version: >=1.10
library
exposed-modules:
IGraph.Internal.Arpack
IGraph.Internal.Initialization
IGraph.Internal.Constants
IGraph.Internal.Arpack
IGraph.Internal.Data
IGraph.Internal.Graph
IGraph.Internal.Attribute
IGraph.Internal.Selector
IGraph.Internal.Structure
IGraph.Internal.Generator
IGraph.Internal.Clique
IGraph.Internal.Community
IGraph
IGraph.Mutable
IGraph.Clique
IGraph.Structure
IGraph.Community
IGraph.Read
-- other-modules:
......
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Internal.Constants where
import Foreign
#include "igraph/igraph.h"
#include "cbits/igraph.c"
{#enum igraph_neimode_t as IGraphNeimode {underscoreToCase} deriving (Show, Eq) #}
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Internal.Selector where
import Control.Monad
import Foreign
import Foreign.C.Types
import System.IO.Unsafe (unsafePerformIO)
{#import IGraph.Internal.Constants #}
{#import IGraph.Internal.Data #}
#include "igraph/igraph.h"
#include "cbits/igraph.c"
{#pointer *igraph_vs_t as IGraphVsPtr foreign finalizer igraph_vs_destroy newtype #}
{#fun igraph_vs_new as ^ { } -> `IGraphVsPtr' #}
{#fun igraph_vs_all as ^ { `IGraphVsPtr' } -> `Int' #}
{#fun igraph_vs_adj as ^ { `IGraphVsPtr', `Int', `IGraphNeimode' } -> `Int' #}
{#fun igraph_vs_vector as ^ { `IGraphVsPtr', `VectorPtr' } -> `Int' #}
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Internal.Structure where
import Foreign
import Foreign.C.Types
{#import IGraph.Internal.Graph #}
{#import IGraph.Internal.Selector #}
{#import IGraph.Internal.Constants #}
{#import IGraph.Internal.Data #}
{#import IGraph.Internal.Arpack #}
#include "igraph/igraph.h"
#include "cbits/igraph.c"
{#fun igraph_closeness as ^ { `IGraphPtr'
, `VectorPtr'
, %`IGraphVsPtr'
, `IGraphNeimode'
, `VectorPtr'
, `Bool' } -> `Int' #}
{#fun igraph_betweenness as ^ { `IGraphPtr'
, id `Ptr VectorPtr'
, %`IGraphVsPtr'
, `Bool'
, id `Ptr VectorPtr'
, `Bool' } -> `Int' #}
{#fun igraph_eigenvector_centrality as ^ { `IGraphPtr'
, id `Ptr VectorPtr'
, id `Ptr CDouble'
, `Bool'
, `Bool'
, id `Ptr VectorPtr'
, `ArpackOptPtr' } -> `Int' #}
module IGraph.Structure
( closeness
) where
import Control.Monad
import Foreign
import Foreign.C.Types
import System.IO.Unsafe (unsafePerformIO)
import IGraph
import IGraph.Mutable (U)
import IGraph.Internal.Data
import IGraph.Internal.Selector
import IGraph.Internal.Structure
import IGraph.Internal.Arpack
import IGraph.Internal.Constants
closeness :: [Int] -- ^ vertices
-> LGraph d v e
-> Maybe [Double] -- ^ optional edge weights
-> IGraphNeimode
-> Bool -- ^ whether to normalize
-> [Double]
closeness vs (LGraph g) ws mode normal = unsafePerformIO $ do
vsptr <- igraphVsNew
vs' <- listToVector $ map fromIntegral vs
igraphVsVector vsptr vs'
vptr <- igraphVectorNew 0
ws' <- case ws of
Just w -> listToVector w
_ -> liftM VectorPtr $ newForeignPtr_ $ castPtr nullPtr
igraphCloseness g vptr vsptr mode ws' normal
vectorPtrToList vptr
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