Commit 02184221 authored by Kai Zhang's avatar Kai Zhang

add Layout module

parent 4ff1d01e
......@@ -27,12 +27,14 @@ library
IGraph.Internal.Structure
IGraph.Internal.Clique
IGraph.Internal.Community
IGraph.Internal.Layout
IGraph
IGraph.Mutable
IGraph.Clique
IGraph.Structure
IGraph.Community
IGraph.Read
IGraph.Layout
-- other-modules:
-- other-extensions:
build-depends:
......@@ -42,6 +44,7 @@ library
, primitive
, unordered-containers
, hashable
, split
extra-libraries: igraph
hs-source-dirs: src
......
......@@ -7,6 +7,8 @@ import Foreign
import Foreign.C.Types
import Foreign.C.String
import System.IO.Unsafe (unsafePerformIO)
import Data.List (transpose)
import Data.List.Split (chunksOf)
#include "cbits/haskelligraph.c"
......@@ -111,6 +113,32 @@ listToStrVector xs = do
{#fun igraph_matrix_fill as ^ { `MatrixPtr', `Double' } -> `()' #}
{#fun pure igraph_matrix_e as ^ { `MatrixPtr', `Int', `Int' } -> `Double' #}
{#fun igraph_matrix_e as ^ { `MatrixPtr', `Int', `Int' } -> `Double' #}
{#fun pure igraph_matrix_set as ^ { `MatrixPtr', `Int', `Int', `Double' } -> `()' #}
{#fun igraph_matrix_set as ^ { `MatrixPtr', `Int', `Int', `Double' } -> `()' #}
{#fun igraph_matrix_copy_to as ^ { `MatrixPtr', id `Ptr CDouble' } -> `()' #}
{#fun igraph_matrix_nrow as ^ { `MatrixPtr' } -> `Int' #}
{#fun igraph_matrix_ncol as ^ { `MatrixPtr' } -> `Int' #}
listsToMatrixPtr :: [[Double]] -> IO MatrixPtr
listsToMatrixPtr xs = do
mptr <- igraphMatrixNew r c
forM_ (zip [0..] xs) $ \(i, row) ->
forM_ (zip [0..] row) $ \(j,v) ->
igraphMatrixSet mptr i j v
return mptr
where
r = length xs
c = maximum $ map length xs
matrixPtrToLists :: MatrixPtr -> IO [[Double]]
matrixPtrToLists mptr = do
r <- igraphMatrixNrow mptr
c <- igraphMatrixNcol mptr
xs <- allocaArray (r*c) $ \ptr -> do
igraphMatrixCopyTo mptr ptr
peekArray (r*c) ptr
return $ transpose $ chunksOf r $ map realToFrac xs
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Internal.Layout where
import Foreign
import Foreign.C.Types
{#import IGraph.Internal.Graph #}
{#import IGraph.Internal.Data #}
#include "igraph/igraph.h"
{#fun igraph_layout_kamada_kawai as ^ { `IGraphPtr'
, `MatrixPtr'
, `Int'
, `Double'
, `Double'
, `Double'
, `Double'
, `Bool'
, id `Ptr VectorPtr'
, id `Ptr VectorPtr'
, id `Ptr VectorPtr'
, id `Ptr VectorPtr'
} -> `Int' #}
module IGraph.Layout
( kamadaKawai
) where
import Foreign (nullPtr)
import Control.Applicative ((<$>))
import System.IO.Unsafe (unsafePerformIO)
import IGraph
import IGraph.Internal.Clique
import IGraph.Internal.Layout
import IGraph.Internal.Data
data LayoutOpt = LayoutOpt
{ _seed :: Maybe [(Double, Double)]
, _nIter :: Int
} deriving (Show)
kamadaKawai :: Graph d => LGraph d v e -> Double -> Double -> Double -> Double -> LayoutOpt -> [(Double, Double)]
kamadaKawai gr sigma initemp coolexp kkconst opt = unsafePerformIO $ do
mptr <- mat
igraphLayoutKamadaKawai (_graph gr) mptr (_nIter opt) sigma initemp coolexp kkconst useSeed nullPtr nullPtr nullPtr nullPtr
[x, y] <- matrixPtrToLists mptr
return $ zip x y
where
(useSeed, mat) = case _seed opt of
Just xs -> if length xs /= nNodes gr
then error "Seed error: incorrect size"
else (True, f xs)
_ -> (False, igraphMatrixNew 0 0)
f xs = let (x,y) = unzip xs
in listsToMatrixPtr [x,y]
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