{-# LINE 1 "src/IGraph/Internal/Structure.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Internal.Structure where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.ForeignPtr as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import Foreign
import Foreign.C.Types
import IGraph.Internal.Graph
{-# LINE 7 "src/IGraph/Internal/Structure.chs" #-}
import IGraph.Internal.Selector
{-# LINE 8 "src/IGraph/Internal/Structure.chs" #-}
import IGraph.Internal.Constants
{-# LINE 9 "src/IGraph/Internal/Structure.chs" #-}
import IGraph.Internal.Data
{-# LINE 10 "src/IGraph/Internal/Structure.chs" #-}
import IGraph.Internal.Arpack
{-# LINE 11 "src/IGraph/Internal/Structure.chs" #-}
igraphInducedSubgraph :: (IGraph) -> (IGraphVs) -> (SubgraphImplementation) -> IO ((IGraph))
igraphInducedSubgraph a1 a3 a4 =
(withIGraph) a1 $ \a1' ->
C2HSImp.mallocForeignPtrBytes 160 >>= \a2'' -> C2HSImp.withForeignPtr a2'' $ \a2' ->
(withIGraphVs) a3 $ \a3' ->
let {a4' = (fromIntegral . fromEnum) a4} in
igraphInducedSubgraph'_ a1' a2' a3' a4' >>
return (IGraph a2'')
{-# LINE 18 "src/IGraph/Internal/Structure.chs" #-}
igraphCloseness :: (IGraph) -> (Vector) -> (IGraphVs) -> (Neimode) -> (Vector) -> (Bool) -> IO ((Int))
igraphCloseness a1 a2 a3 a4 a5 a6 =
(withIGraph) a1 $ \a1' ->
(withVector) a2 $ \a2' ->
(withIGraphVs) a3 $ \a3' ->
let {a4' = (fromIntegral . fromEnum) a4} in
(withVector) a5 $ \a5' ->
let {a6' = C2HSImp.fromBool a6} in
igraphCloseness'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 25 "src/IGraph/Internal/Structure.chs" #-}
igraphBetweenness :: (IGraph) -> (Vector) -> (IGraphVs) -> (Bool) -> (Vector) -> (Bool) -> IO ((Int))
igraphBetweenness a1 a2 a3 a4 a5 a6 =
(withIGraph) a1 $ \a1' ->
(withVector) a2 $ \a2' ->
(withIGraphVs) a3 $ \a3' ->
let {a4' = C2HSImp.fromBool a4} in
(withVector) a5 $ \a5' ->
let {a6' = C2HSImp.fromBool a6} in
igraphBetweenness'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 32 "src/IGraph/Internal/Structure.chs" #-}
igraphEigenvectorCentrality :: (IGraph) -> (Vector) -> (Ptr CDouble) -> (Bool) -> (Bool) -> (Vector) -> (ArpackOpt) -> IO ((Int))
igraphEigenvectorCentrality a1 a2 a3 a4 a5 a6 a7 =
(withIGraph) a1 $ \a1' ->
(withVector) a2 $ \a2' ->
let {a3' = id a3} in
let {a4' = C2HSImp.fromBool a4} in
let {a5' = C2HSImp.fromBool a5} in
(withVector) a6 $ \a6' ->
(withArpackOpt) a7 $ \a7' ->
igraphEigenvectorCentrality'_ a1' a2' a3' a4' a5' a6' a7' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 40 "src/IGraph/Internal/Structure.chs" #-}
igraphPagerank :: (IGraph) -> (PagerankAlgo) -> (Vector) -> (Ptr CDouble) -> (IGraphVs) -> (Bool) -> (Double) -> (Vector) -> (Ptr ()) -> IO ((Int))
igraphPagerank a1 a2 a3 a4 a5 a6 a7 a8 a9 =
(withIGraph) a1 $ \a1' ->
let {a2' = (fromIntegral . fromEnum) a2} in
(withVector) a3 $ \a3' ->
let {a4' = id a4} in
(withIGraphVs) a5 $ \a5' ->
let {a6' = C2HSImp.fromBool a6} in
let {a7' = realToFrac a7} in
(withVector) a8 $ \a8' ->
let {a9' = id a9} in
igraphPagerank'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 50 "src/IGraph/Internal/Structure.chs" #-}
igraphPersonalizedPagerank :: (IGraph) -> (PagerankAlgo) -> (Vector) -> (Ptr CDouble) -> (IGraphVs) -> (Bool) -> (Double) -> (Vector) -> (Vector) -> (Ptr ()) -> IO ((Int))
igraphPersonalizedPagerank a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 =
(withIGraph) a1 $ \a1' ->
let {a2' = (fromIntegral . fromEnum) a2} in
(withVector) a3 $ \a3' ->
let {a4' = id a4} in
(withIGraphVs) a5 $ \a5' ->
let {a6' = C2HSImp.fromBool a6} in
let {a7' = realToFrac a7} in
(withVector) a8 $ \a8' ->
(withVector) a9 $ \a9' ->
let {a10' = id a10} in
igraphPersonalizedPagerank'_ a1' a2' a3' a4' a5' a6' a7' a8' a9' a10' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 61 "src/IGraph/Internal/Structure.chs" #-}
foreign import ccall safe "IGraph/Internal/Structure.chs.h __c2hs_wrapped__igraph_induced_subgraph"
igraphInducedSubgraph'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr (IGraphVs)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))
foreign import ccall safe "IGraph/Internal/Structure.chs.h __c2hs_wrapped__igraph_closeness"
igraphCloseness'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr (IGraphVs)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Vector)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "IGraph/Internal/Structure.chs.h __c2hs_wrapped__igraph_betweenness"
igraphBetweenness'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr (IGraphVs)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Vector)) -> (C2HSImp.CInt -> (IO C2HSImp.CInt)))))))
foreign import ccall safe "IGraph/Internal/Structure.chs.h igraph_eigenvector_centrality"
igraphEigenvectorCentrality'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (C2HSImp.CInt -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr (ArpackOpt)) -> (IO C2HSImp.CInt))))))))
foreign import ccall safe "IGraph/Internal/Structure.chs.h __c2hs_wrapped__igraph_pagerank"
igraphPagerank'_ :: ((C2HSImp.Ptr (IGraph)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr (IGraphVs)) -> (C2HSImp.CInt -> (C2HSImp.CDouble -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt))))))))))
foreign import ccall safe "IGraph/Internal/Structure.chs.h __c2hs_wrapped__igraph_personalized_pagerank"
igraphPersonalizedPagerank'_ :: ((C2HSImp.Ptr (IGraph)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr C2HSImp.CDouble) -> ((C2HSImp.Ptr (IGraphVs)) -> (C2HSImp.CInt -> (C2HSImp.CDouble -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr (Vector)) -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))))))))