{-# LINE 1 "src/IGraph/Motif.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Motif
( triad
, triadCensus
) where
import qualified Foreign.C.Types as C2HSImp
import Data.Hashable (Hashable)
import System.IO.Unsafe (unsafePerformIO)
import qualified Foreign.Ptr as C2HSImp
import IGraph
import IGraph.Internal
{-# LINE 13 "src/IGraph/Motif.chs" #-}
triad :: [LGraph D () ()]
triad = map make edgeList
where
edgeList =
[ []
, [(0,1)]
, [(0,1), (1,0)]
, [(1,0), (1,2)]
, [(0,1), (2,1)]
, [(0,1), (1,2)]
, [(0,1), (1,0), (2,1)]
, [(0,1), (1,0), (1,2)]
, [(0,1), (2,1), (0,2)]
, [(1,0), (2,1), (0,2)]
, [(0,1), (1,0), (0,2), (2,0)]
, [(1,0), (1,2), (0,2), (2,0)]
, [(0,1), (2,1), (0,2), (2,0)]
, [(0,1), (1,2), (0,2), (2,0)]
, [(0,1), (1,2), (2,1), (0,2), (2,0)]
, [(0,1), (1,0), (1,2), (2,1), (0,2), (2,0)]
]
make :: [(Int, Int)] -> LGraph D () ()
make xs = mkGraph (replicate 3 ()) $ zip xs $ repeat ()
triadCensus :: (Hashable v, Eq v, Read v) => LGraph d v e -> [Int]
triadCensus gr = unsafePerformIO $ do
vptr <- igraphVectorNew 0
igraphTriadCensus (_graph gr) vptr
map truncate <$> toList vptr
igraphTriadCensus :: (IGraph) -> (Vector) -> IO ()
igraphTriadCensus a1 a2 =
(withIGraph) a1 $ \a1' ->
(withVector) a2 $ \a2' ->
igraphTriadCensus'_ a1' a2' >>= \res ->
return ()
{-# LINE 67 "src/IGraph/Motif.chs" #-}
igraphMotifsRandesu :: (IGraph) -> (Vector) -> (Int) -> (Vector) -> IO ()
igraphMotifsRandesu a1 a2 a3 a4 =
(withIGraph) a1 $ \a1' ->
(withVector) a2 $ \a2' ->
let {a3' = fromIntegral a3} in
(withVector) a4 $ \a4' ->
igraphMotifsRandesu'_ a1' a2' a3' a4' >>= \res ->
return ()
{-# LINE 70 "src/IGraph/Motif.chs" #-}
foreign import ccall safe "IGraph/Motif.chs.h igraph_triad_census"
igraphTriadCensus'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr (Vector)) -> (IO C2HSImp.CInt)))
foreign import ccall safe "IGraph/Motif.chs.h igraph_motifs_randesu"
igraphMotifsRandesu'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr (Vector)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Vector)) -> (IO C2HSImp.CInt)))))