{-# LANGUAGE RecordWildCards #-}
module Data.Graph.Sparse where
import Control.Monad.Primitive
import Control.Monad.ST
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Unboxed.Mutable as UM
import Data.Buffer
type Vertex = Int
type Edge = (Vertex, Vertex)
type EdgeWith w = (Vertex, Vertex, w)
type EdgeId = Int
data SparseGraph w = SparseGraph
{ forall w. SparseGraph w -> Int
numVerticesSG :: !Int
, forall w. SparseGraph w -> Int
numEdgesSG :: !Int
, forall w. SparseGraph w -> Vector Int
offsetSG :: !(U.Vector Int)
, forall w. SparseGraph w -> Vector Int
adjacentSG :: !(U.Vector Vertex)
, forall w. SparseGraph w -> Vector w
edgeCtxSG :: !(U.Vector w)
}
data SparseGraphBuilder s w = SparseGraphBuilder
{ forall s w. SparseGraphBuilder s w -> Int
numVerticesSGB :: !Int
, forall s w. SparseGraphBuilder s w -> Buffer s (EdgeWith w)
bufferSGB :: Buffer s (EdgeWith w)
, forall s w. SparseGraphBuilder s w -> MVector s Int
outDegSGB :: UM.MVector s Int
}
buildSparseGraph ::
(U.Unbox w) =>
Int ->
Int ->
(forall s. SparseGraphBuilder s w -> ST s ()) ->
SparseGraph w
buildSparseGraph :: forall w.
Unbox w =>
Int
-> Int
-> (forall s. SparseGraphBuilder s w -> ST s ())
-> SparseGraph w
buildSparseGraph Int
numVerticesSG Int
ubNumE forall s. SparseGraphBuilder s w -> ST s ()
run = (forall s. ST s (SparseGraph w)) -> SparseGraph w
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (SparseGraph w)) -> SparseGraph w)
-> (forall s. ST s (SparseGraph w)) -> SparseGraph w
forall a b. (a -> b) -> a -> b
$ do
bufferSGB <- Int -> ST s (Buffer (PrimState (ST s)) (EdgeWith w))
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
Int -> m (Buffer (PrimState m) a)
newBuffer Int
ubNumE
outDegSGB <- UM.replicate numVerticesSG 0
run SparseGraphBuilder{numVerticesSGB = numVerticesSG, ..}
numEdgesSG <- lengthBuffer bufferSGB
offsetSG <- U.scanl' (+) 0 <$> U.unsafeFreeze outDegSGB
moffset <- U.thaw offsetSG
madj <- UM.unsafeNew numEdgesSG
mectx <- UM.unsafeNew numEdgesSG
edges <- unsafeFreezeBuffer bufferSGB
U.forM_ edges $ \(Int
src, Int
dst, w
w) -> do
pos <- MVector (PrimState (ST s)) Int -> Int -> ST s Int
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
UM.unsafeRead MVector s Int
MVector (PrimState (ST s)) Int
moffset Int
src
UM.unsafeWrite moffset src (pos + 1)
UM.unsafeWrite madj pos dst
UM.unsafeWrite mectx pos w
adjacentSG <- U.unsafeFreeze madj
edgeCtxSG <- U.unsafeFreeze mectx
return SparseGraph{..}
{-# INLINE buildSparseGraph #-}
addDirectedEdge ::
(U.Unbox w, PrimMonad m) =>
SparseGraphBuilder (PrimState m) w ->
EdgeWith w ->
m ()
addDirectedEdge :: forall w (m :: * -> *).
(Unbox w, PrimMonad m) =>
SparseGraphBuilder (PrimState m) w -> EdgeWith w -> m ()
addDirectedEdge SparseGraphBuilder{Int
MVector (PrimState m) Int
Buffer (PrimState m) (Int, Int, w)
numVerticesSGB :: forall s w. SparseGraphBuilder s w -> Int
bufferSGB :: forall s w. SparseGraphBuilder s w -> Buffer s (EdgeWith w)
outDegSGB :: forall s w. SparseGraphBuilder s w -> MVector s Int
numVerticesSGB :: Int
bufferSGB :: Buffer (PrimState m) (Int, Int, w)
outDegSGB :: MVector (PrimState m) Int
..} (Int
src, Int
dst, w
w) = do
(Int, Int, w) -> Buffer (PrimState m) (Int, Int, w) -> m ()
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
a -> Buffer (PrimState m) a -> m ()
pushBack (Int
src, Int
dst, w
w) Buffer (PrimState m) (Int, Int, w)
bufferSGB
MVector (PrimState m) Int -> (Int -> Int) -> Int -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
UM.unsafeModify MVector (PrimState m) Int
outDegSGB (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
src
{-# INLINE addDirectedEdge #-}
addUndirectedEdge ::
(U.Unbox w, PrimMonad m) =>
SparseGraphBuilder (PrimState m) w ->
EdgeWith w ->
m ()
addUndirectedEdge :: forall w (m :: * -> *).
(Unbox w, PrimMonad m) =>
SparseGraphBuilder (PrimState m) w -> EdgeWith w -> m ()
addUndirectedEdge SparseGraphBuilder{Int
MVector (PrimState m) Int
Buffer (PrimState m) (Int, Int, w)
numVerticesSGB :: forall s w. SparseGraphBuilder s w -> Int
bufferSGB :: forall s w. SparseGraphBuilder s w -> Buffer s (EdgeWith w)
outDegSGB :: forall s w. SparseGraphBuilder s w -> MVector s Int
numVerticesSGB :: Int
bufferSGB :: Buffer (PrimState m) (Int, Int, w)
outDegSGB :: MVector (PrimState m) Int
..} (Int
src, Int
dst, w
w) = do
(Int, Int, w) -> Buffer (PrimState m) (Int, Int, w) -> m ()
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
a -> Buffer (PrimState m) a -> m ()
pushBack (Int
src, Int
dst, w
w) Buffer (PrimState m) (Int, Int, w)
bufferSGB
(Int, Int, w) -> Buffer (PrimState m) (Int, Int, w) -> m ()
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
a -> Buffer (PrimState m) a -> m ()
pushBack (Int
dst, Int
src, w
w) Buffer (PrimState m) (Int, Int, w)
bufferSGB
MVector (PrimState m) Int -> (Int -> Int) -> Int -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
UM.unsafeModify MVector (PrimState m) Int
outDegSGB (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
src
MVector (PrimState m) Int -> (Int -> Int) -> Int -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
UM.unsafeModify MVector (PrimState m) Int
outDegSGB (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
dst
{-# INLINE addUndirectedEdge #-}
addDirectedEdge_ ::
(PrimMonad m) =>
SparseGraphBuilder (PrimState m) () ->
Edge ->
m ()
addDirectedEdge_ :: forall (m :: * -> *).
PrimMonad m =>
SparseGraphBuilder (PrimState m) () -> Edge -> m ()
addDirectedEdge_ SparseGraphBuilder{Int
MVector (PrimState m) Int
Buffer (PrimState m) (Int, Int, ())
numVerticesSGB :: forall s w. SparseGraphBuilder s w -> Int
bufferSGB :: forall s w. SparseGraphBuilder s w -> Buffer s (EdgeWith w)
outDegSGB :: forall s w. SparseGraphBuilder s w -> MVector s Int
numVerticesSGB :: Int
bufferSGB :: Buffer (PrimState m) (Int, Int, ())
outDegSGB :: MVector (PrimState m) Int
..} (Int
src, Int
dst) = do
(Int, Int, ()) -> Buffer (PrimState m) (Int, Int, ()) -> m ()
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
a -> Buffer (PrimState m) a -> m ()
pushBack (Int
src, Int
dst, ()) Buffer (PrimState m) (Int, Int, ())
bufferSGB
MVector (PrimState m) Int -> (Int -> Int) -> Int -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
UM.unsafeModify MVector (PrimState m) Int
outDegSGB (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
src
{-# INLINE addDirectedEdge_ #-}
addUndirectedEdge_ ::
(PrimMonad m) =>
SparseGraphBuilder (PrimState m) () ->
Edge ->
m ()
addUndirectedEdge_ :: forall (m :: * -> *).
PrimMonad m =>
SparseGraphBuilder (PrimState m) () -> Edge -> m ()
addUndirectedEdge_ SparseGraphBuilder{Int
MVector (PrimState m) Int
Buffer (PrimState m) (Int, Int, ())
numVerticesSGB :: forall s w. SparseGraphBuilder s w -> Int
bufferSGB :: forall s w. SparseGraphBuilder s w -> Buffer s (EdgeWith w)
outDegSGB :: forall s w. SparseGraphBuilder s w -> MVector s Int
numVerticesSGB :: Int
bufferSGB :: Buffer (PrimState m) (Int, Int, ())
outDegSGB :: MVector (PrimState m) Int
..} (Int
src, Int
dst) = do
(Int, Int, ()) -> Buffer (PrimState m) (Int, Int, ()) -> m ()
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
a -> Buffer (PrimState m) a -> m ()
pushBack (Int
src, Int
dst, ()) Buffer (PrimState m) (Int, Int, ())
bufferSGB
(Int, Int, ()) -> Buffer (PrimState m) (Int, Int, ()) -> m ()
forall a (m :: * -> *).
(Unbox a, PrimMonad m) =>
a -> Buffer (PrimState m) a -> m ()
pushBack (Int
dst, Int
src, ()) Buffer (PrimState m) (Int, Int, ())
bufferSGB
MVector (PrimState m) Int -> (Int -> Int) -> Int -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
UM.unsafeModify MVector (PrimState m) Int
outDegSGB (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
src
MVector (PrimState m) Int -> (Int -> Int) -> Int -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> (a -> a) -> Int -> m ()
UM.unsafeModify MVector (PrimState m) Int
outDegSGB (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
dst
{-# INLINE addUndirectedEdge_ #-}
buildDirectedGraph ::
Int ->
Int ->
U.Vector Edge ->
SparseGraph ()
buildDirectedGraph :: Int -> Int -> Vector Edge -> SparseGraph ()
buildDirectedGraph Int
numVerticesSG Int
ubNumE Vector Edge
edges =
Int
-> Int
-> (forall s. SparseGraphBuilder s () -> ST s ())
-> SparseGraph ()
forall w.
Unbox w =>
Int
-> Int
-> (forall s. SparseGraphBuilder s w -> ST s ())
-> SparseGraph w
buildSparseGraph Int
numVerticesSG Int
ubNumE ((forall s. SparseGraphBuilder s () -> ST s ()) -> SparseGraph ())
-> (forall s. SparseGraphBuilder s () -> ST s ()) -> SparseGraph ()
forall a b. (a -> b) -> a -> b
$ \SparseGraphBuilder s ()
builder -> do
(Edge -> ST s ()) -> Vector Edge -> ST s ()
forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
(a -> m b) -> Vector a -> m ()
U.mapM_ (SparseGraphBuilder (PrimState (ST s)) () -> Edge -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
SparseGraphBuilder (PrimState m) () -> Edge -> m ()
addDirectedEdge_ SparseGraphBuilder s ()
SparseGraphBuilder (PrimState (ST s)) ()
builder) Vector Edge
edges
buildUndirectedGraph ::
Int ->
Int ->
U.Vector Edge ->
SparseGraph ()
buildUndirectedGraph :: Int -> Int -> Vector Edge -> SparseGraph ()
buildUndirectedGraph Int
numVerticesSG Int
ubNumE Vector Edge
edges =
Int
-> Int
-> (forall s. SparseGraphBuilder s () -> ST s ())
-> SparseGraph ()
forall w.
Unbox w =>
Int
-> Int
-> (forall s. SparseGraphBuilder s w -> ST s ())
-> SparseGraph w
buildSparseGraph Int
numVerticesSG (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
ubNumE) ((forall s. SparseGraphBuilder s () -> ST s ()) -> SparseGraph ())
-> (forall s. SparseGraphBuilder s () -> ST s ()) -> SparseGraph ()
forall a b. (a -> b) -> a -> b
$ \SparseGraphBuilder s ()
builder -> do
(Edge -> ST s ()) -> Vector Edge -> ST s ()
forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
(a -> m b) -> Vector a -> m ()
U.mapM_ (SparseGraphBuilder (PrimState (ST s)) () -> Edge -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
SparseGraphBuilder (PrimState m) () -> Edge -> m ()
addUndirectedEdge_ SparseGraphBuilder s ()
SparseGraphBuilder (PrimState (ST s)) ()
builder) Vector Edge
edges
buildDirectedGraphW ::
(U.Unbox w) =>
Int ->
Int ->
U.Vector (EdgeWith w) ->
SparseGraph w
buildDirectedGraphW :: forall w.
Unbox w =>
Int -> Int -> Vector (EdgeWith w) -> SparseGraph w
buildDirectedGraphW Int
numVerticesSG Int
ubNumE Vector (EdgeWith w)
edges =
Int
-> Int
-> (forall s. SparseGraphBuilder s w -> ST s ())
-> SparseGraph w
forall w.
Unbox w =>
Int
-> Int
-> (forall s. SparseGraphBuilder s w -> ST s ())
-> SparseGraph w
buildSparseGraph Int
numVerticesSG Int
ubNumE ((forall s. SparseGraphBuilder s w -> ST s ()) -> SparseGraph w)
-> (forall s. SparseGraphBuilder s w -> ST s ()) -> SparseGraph w
forall a b. (a -> b) -> a -> b
$ \SparseGraphBuilder s w
builder -> do
(EdgeWith w -> ST s ()) -> Vector (EdgeWith w) -> ST s ()
forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
(a -> m b) -> Vector a -> m ()
U.mapM_ (SparseGraphBuilder (PrimState (ST s)) w -> EdgeWith w -> ST s ()
forall w (m :: * -> *).
(Unbox w, PrimMonad m) =>
SparseGraphBuilder (PrimState m) w -> EdgeWith w -> m ()
addDirectedEdge SparseGraphBuilder s w
SparseGraphBuilder (PrimState (ST s)) w
builder) Vector (EdgeWith w)
edges
buildUndirectedGraphW ::
(U.Unbox w) =>
Int ->
Int ->
U.Vector (EdgeWith w) ->
SparseGraph w
buildUndirectedGraphW :: forall w.
Unbox w =>
Int -> Int -> Vector (EdgeWith w) -> SparseGraph w
buildUndirectedGraphW Int
numVerticesSG Int
ubNumE Vector (EdgeWith w)
edges =
Int
-> Int
-> (forall s. SparseGraphBuilder s w -> ST s ())
-> SparseGraph w
forall w.
Unbox w =>
Int
-> Int
-> (forall s. SparseGraphBuilder s w -> ST s ())
-> SparseGraph w
buildSparseGraph Int
numVerticesSG (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
ubNumE) ((forall s. SparseGraphBuilder s w -> ST s ()) -> SparseGraph w)
-> (forall s. SparseGraphBuilder s w -> ST s ()) -> SparseGraph w
forall a b. (a -> b) -> a -> b
$ \SparseGraphBuilder s w
builder -> do
(EdgeWith w -> ST s ()) -> Vector (EdgeWith w) -> ST s ()
forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
(a -> m b) -> Vector a -> m ()
U.mapM_ (SparseGraphBuilder (PrimState (ST s)) w -> EdgeWith w -> ST s ()
forall w (m :: * -> *).
(Unbox w, PrimMonad m) =>
SparseGraphBuilder (PrimState m) w -> EdgeWith w -> m ()
addUndirectedEdge SparseGraphBuilder s w
SparseGraphBuilder (PrimState (ST s)) w
builder) Vector (EdgeWith w)
edges
adj :: SparseGraph w -> Vertex -> U.Vector Vertex
adj :: forall w. SparseGraph w -> Int -> Vector Int
adj SparseGraph{Int
Vector w
Vector Int
numVerticesSG :: forall w. SparseGraph w -> Int
numEdgesSG :: forall w. SparseGraph w -> Int
offsetSG :: forall w. SparseGraph w -> Vector Int
adjacentSG :: forall w. SparseGraph w -> Vector Int
edgeCtxSG :: forall w. SparseGraph w -> Vector w
numVerticesSG :: Int
numEdgesSG :: Int
offsetSG :: Vector Int
adjacentSG :: Vector Int
edgeCtxSG :: Vector w
..} Int
v = Int -> Int -> Vector Int -> Vector Int
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.unsafeSlice Int
o (Int
o' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
o) Vector Int
adjacentSG
where
o :: Int
o = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG Int
v
o' :: Int
o' = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE adj #-}
iadj :: SparseGraph w -> Vertex -> U.Vector (EdgeId, Vertex)
iadj :: forall w. SparseGraph w -> Int -> Vector Edge
iadj SparseGraph{Int
Vector w
Vector Int
numVerticesSG :: forall w. SparseGraph w -> Int
numEdgesSG :: forall w. SparseGraph w -> Int
offsetSG :: forall w. SparseGraph w -> Vector Int
adjacentSG :: forall w. SparseGraph w -> Vector Int
edgeCtxSG :: forall w. SparseGraph w -> Vector w
numVerticesSG :: Int
numEdgesSG :: Int
offsetSG :: Vector Int
adjacentSG :: Vector Int
edgeCtxSG :: Vector w
..} Int
v = (Int -> Int -> Edge) -> Vector Int -> Vector Edge
forall a b.
(Unbox a, Unbox b) =>
(Int -> a -> b) -> Vector a -> Vector b
U.imap ((,) (Int -> Int -> Edge) -> (Int -> Int) -> Int -> Int -> Edge
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
o)) (Vector Int -> Vector Edge) -> Vector Int -> Vector Edge
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector Int -> Vector Int
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.unsafeSlice Int
o (Int
o' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
o) Vector Int
adjacentSG
where
o :: Int
o = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG Int
v
o' :: Int
o' = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE iadj #-}
adjW ::
(U.Unbox w) =>
SparseGraph w ->
Vertex ->
U.Vector (Vertex, w)
adjW :: forall w. Unbox w => SparseGraph w -> Int -> Vector (Int, w)
adjW SparseGraph{Int
Vector w
Vector Int
numVerticesSG :: forall w. SparseGraph w -> Int
numEdgesSG :: forall w. SparseGraph w -> Int
offsetSG :: forall w. SparseGraph w -> Vector Int
adjacentSG :: forall w. SparseGraph w -> Vector Int
edgeCtxSG :: forall w. SparseGraph w -> Vector w
numVerticesSG :: Int
numEdgesSG :: Int
offsetSG :: Vector Int
adjacentSG :: Vector Int
edgeCtxSG :: Vector w
..} Int
v =
Vector Int -> Vector w -> Vector (Int, w)
forall a b.
(Unbox a, Unbox b) =>
Vector a -> Vector b -> Vector (a, b)
U.zip
(Int -> Int -> Vector Int -> Vector Int
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.unsafeSlice Int
o (Int
o' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
o) Vector Int
adjacentSG)
(Int -> Int -> Vector w -> Vector w
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.unsafeSlice Int
o (Int
o' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
o) Vector w
edgeCtxSG)
where
o :: Int
o = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG Int
v
o' :: Int
o' = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE adjW #-}
iadjW ::
(U.Unbox w) =>
SparseGraph w ->
Vertex ->
U.Vector (EdgeId, Vertex, w)
iadjW :: forall w. Unbox w => SparseGraph w -> Int -> Vector (Int, Int, w)
iadjW SparseGraph{Int
Vector w
Vector Int
numVerticesSG :: forall w. SparseGraph w -> Int
numEdgesSG :: forall w. SparseGraph w -> Int
offsetSG :: forall w. SparseGraph w -> Vector Int
adjacentSG :: forall w. SparseGraph w -> Vector Int
edgeCtxSG :: forall w. SparseGraph w -> Vector w
numVerticesSG :: Int
numEdgesSG :: Int
offsetSG :: Vector Int
adjacentSG :: Vector Int
edgeCtxSG :: Vector w
..} Int
v =
(Int -> Int -> w -> (Int, Int, w))
-> Vector Int -> Vector w -> Vector (Int, Int, w)
forall a b c.
(Unbox a, Unbox b, Unbox c) =>
(Int -> a -> b -> c) -> Vector a -> Vector b -> Vector c
U.izipWith
(\Int
i Int
u w
w -> (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
o, Int
u, w
w))
(Int -> Int -> Vector Int -> Vector Int
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.unsafeSlice Int
o (Int
o' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
o) Vector Int
adjacentSG)
(Int -> Int -> Vector w -> Vector w
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
U.unsafeSlice Int
o (Int
o' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
o) Vector w
edgeCtxSG)
where
o :: Int
o = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG Int
v
o' :: Int
o' = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE iadjW #-}
outEdges :: SparseGraph w -> Vertex -> U.Vector EdgeId
outEdges :: forall w. SparseGraph w -> Int -> Vector Int
outEdges SparseGraph{Int
Vector w
Vector Int
numVerticesSG :: forall w. SparseGraph w -> Int
numEdgesSG :: forall w. SparseGraph w -> Int
offsetSG :: forall w. SparseGraph w -> Vector Int
adjacentSG :: forall w. SparseGraph w -> Vector Int
edgeCtxSG :: forall w. SparseGraph w -> Vector w
numVerticesSG :: Int
numEdgesSG :: Int
offsetSG :: Vector Int
adjacentSG :: Vector Int
edgeCtxSG :: Vector w
..} Int
v = Int -> (Int -> Int) -> Vector Int
forall a. Unbox a => Int -> (Int -> a) -> Vector a
U.generate (Int
o' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
o) (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
o)
where
o :: Int
o = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG Int
v
o' :: Int
o' = Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE outEdges #-}
outDegree :: SparseGraph w -> Vertex -> Int
outDegree :: forall w. SparseGraph w -> Int -> Int
outDegree SparseGraph{Int
Vector w
Vector Int
numVerticesSG :: forall w. SparseGraph w -> Int
numEdgesSG :: forall w. SparseGraph w -> Int
offsetSG :: forall w. SparseGraph w -> Vector Int
adjacentSG :: forall w. SparseGraph w -> Vector Int
edgeCtxSG :: forall w. SparseGraph w -> Vector w
numVerticesSG :: Int
numEdgesSG :: Int
offsetSG :: Vector Int
adjacentSG :: Vector Int
edgeCtxSG :: Vector w
..} Int
v =
Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG (Int
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Int -> Int -> Int
forall a. Num a => a -> a -> a
- Vector Int -> Int -> Int
forall a. Unbox a => Vector a -> Int -> a
U.unsafeIndex Vector Int
offsetSG Int
v
{-# INLINE outDegree #-}
outDegrees :: SparseGraph w -> U.Vector Int
outDegrees :: forall w. SparseGraph w -> Vector Int
outDegrees SparseGraph{Int
Vector w
Vector Int
numVerticesSG :: forall w. SparseGraph w -> Int
numEdgesSG :: forall w. SparseGraph w -> Int
offsetSG :: forall w. SparseGraph w -> Vector Int
adjacentSG :: forall w. SparseGraph w -> Vector Int
edgeCtxSG :: forall w. SparseGraph w -> Vector w
numVerticesSG :: Int
numEdgesSG :: Int
offsetSG :: Vector Int
adjacentSG :: Vector Int
edgeCtxSG :: Vector w
..} = (Int -> Int -> Int) -> Vector Int -> Vector Int -> Vector Int
forall a b c.
(Unbox a, Unbox b, Unbox c) =>
(a -> b -> c) -> Vector a -> Vector b -> Vector c
U.zipWith (-) (Vector Int -> Vector Int
forall a. Unbox a => Vector a -> Vector a
U.tail Vector Int
offsetSG) Vector Int
offsetSG
{-# INLINE outDegrees #-}