{-# LANGUAGE MultiParamTypeClasses, TemplateHaskell, TypeFamilies #-}
module Data.Graph.Haggle.Internal.Basic (
  Vertex(..),
  Edge(..),
  vertexId,
  edgeId,
  edgeSource,
  edgeDest
  ) where
import Control.DeepSeq
import Data.Hashable
import Data.Vector.Unboxed.Deriving (derivingUnbox)
newtype Vertex = V Int
  deriving (Vertex -> Vertex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Vertex -> Vertex -> Bool
$c/= :: Vertex -> Vertex -> Bool
== :: Vertex -> Vertex -> Bool
$c== :: Vertex -> Vertex -> Bool
Eq, Eq Vertex
Vertex -> Vertex -> Bool
Vertex -> Vertex -> Ordering
Vertex -> Vertex -> Vertex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Vertex -> Vertex -> Vertex
$cmin :: Vertex -> Vertex -> Vertex
max :: Vertex -> Vertex -> Vertex
$cmax :: Vertex -> Vertex -> Vertex
>= :: Vertex -> Vertex -> Bool
$c>= :: Vertex -> Vertex -> Bool
> :: Vertex -> Vertex -> Bool
$c> :: Vertex -> Vertex -> Bool
<= :: Vertex -> Vertex -> Bool
$c<= :: Vertex -> Vertex -> Bool
< :: Vertex -> Vertex -> Bool
$c< :: Vertex -> Vertex -> Bool
compare :: Vertex -> Vertex -> Ordering
$ccompare :: Vertex -> Vertex -> Ordering
Ord, Int -> Vertex -> ShowS
[Vertex] -> ShowS
Vertex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Vertex] -> ShowS
$cshowList :: [Vertex] -> ShowS
show :: Vertex -> String
$cshow :: Vertex -> String
showsPrec :: Int -> Vertex -> ShowS
$cshowsPrec :: Int -> Vertex -> ShowS
Show)
$(derivingUnbox "Vertex"
  [t| Vertex -> Int |]
  [| \(V i) -> i |]
  [| V |])
instance Hashable Vertex where
  hashWithSalt :: Int -> Vertex -> Int
hashWithSalt = Int -> Vertex -> Int
hashVertex
instance NFData Vertex where
  rnf :: Vertex -> ()
rnf (V Int
i) = Int
i seq :: forall a b. a -> b -> b
`seq` ()
hashVertex :: Int -> Vertex -> Int
hashVertex :: Int -> Vertex -> Int
hashVertex Int
s (V Int
i) = forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
s Int
i
{-# INLINE hashVertex #-}
data Edge = E {-# UNPACK #-}!Int {-# UNPACK #-}!Int {-# UNPACK #-}!Int
  deriving (Edge -> Edge -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Edge -> Edge -> Bool
$c/= :: Edge -> Edge -> Bool
== :: Edge -> Edge -> Bool
$c== :: Edge -> Edge -> Bool
Eq, Eq Edge
Edge -> Edge -> Bool
Edge -> Edge -> Ordering
Edge -> Edge -> Edge
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Edge -> Edge -> Edge
$cmin :: Edge -> Edge -> Edge
max :: Edge -> Edge -> Edge
$cmax :: Edge -> Edge -> Edge
>= :: Edge -> Edge -> Bool
$c>= :: Edge -> Edge -> Bool
> :: Edge -> Edge -> Bool
$c> :: Edge -> Edge -> Bool
<= :: Edge -> Edge -> Bool
$c<= :: Edge -> Edge -> Bool
< :: Edge -> Edge -> Bool
$c< :: Edge -> Edge -> Bool
compare :: Edge -> Edge -> Ordering
$ccompare :: Edge -> Edge -> Ordering
Ord, Int -> Edge -> ShowS
[Edge] -> ShowS
Edge -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Edge] -> ShowS
$cshowList :: [Edge] -> ShowS
show :: Edge -> String
$cshow :: Edge -> String
showsPrec :: Int -> Edge -> ShowS
$cshowsPrec :: Int -> Edge -> ShowS
Show)
$(derivingUnbox "Edge"
  [t| Edge -> (Int, Int, Int) |]
  [| \(E eid src dst) -> (eid, src, dst) |]
  [| \(eid, src, dst) -> E eid src dst |])
instance Hashable Edge where
  hashWithSalt :: Int -> Edge -> Int
hashWithSalt = Int -> Edge -> Int
hashEdge
instance NFData Edge where
  rnf :: Edge -> ()
rnf Edge
e = Edge
e seq :: forall a b. a -> b -> b
`seq` ()
hashEdge :: Int -> Edge -> Int
hashEdge :: Int -> Edge -> Int
hashEdge Int
s (E Int
eid Int
src Int
dst) = Int
s forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
eid forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
src forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
dst
{-# INLINE hashEdge #-}
vertexId :: Vertex -> Int
vertexId :: Vertex -> Int
vertexId (V Int
vid) = Int
vid
{-# INLINE vertexId #-}
edgeId :: Edge -> Int
edgeId :: Edge -> Int
edgeId (E Int
eid Int
_ Int
_) = Int
eid
{-# INLINE edgeId #-}
edgeSource :: Edge -> Vertex
edgeSource :: Edge -> Vertex
edgeSource (E Int
_ Int
s Int
_) = Int -> Vertex
V Int
s
{-# INLINE edgeSource #-}
edgeDest :: Edge -> Vertex
edgeDest :: Edge -> Vertex
edgeDest (E Int
_ Int
_ Int
d) = Int -> Vertex
V Int
d
{-# INLINE edgeDest #-}