| Copyright | (c) Marcelo Garlet Milani 2026 |
|---|---|
| License | MIT |
| Maintainer | mgmilani@pm.me |
| Stability | unstable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Nauty.Sparse6.Internal
Description
This module contains internal functions used by the Nauty.Sparse6 module. Except for test cases, you should not import this module.
Synopsis
- data AdjacencyList = AdjacencyList {}
- parse :: Text -> [Either Text AdjacencyList]
- graph :: Text -> Either Text AdjacencyList
- symmetricDifference :: AdjacencyList -> Text -> Either Text AdjacencyList
- data EncodeState = EncodeState {}
- encode :: AdjacencyList -> Text
- encodeSymmetricDifference :: Word64 -> [(Word64, Word64)] -> Text
- encodeEdgeList :: Word64 -> [(Word64, Word64)] -> Text
- encodeVertex' :: Word64 -> Int -> [Word8] -> Word8 -> Int -> ([Word8], Word8, Int)
- oneBit :: forall (m :: Type -> Type). Monad m => StateT EncodeState m ()
- zeroBit :: forall (m :: Type -> Type). Monad m => StateT EncodeState m ()
- encodeStartState :: EncodeState
- data EdgeListState = EdgeListState {}
- parseEdgeList :: Word64 -> Word64 -> StateT ByteString (Either Text) AdjacencyList
- consumeByte :: Word64 -> Word64 -> EdgeListState -> Word8 -> Int -> EdgeListState
- edgeList :: Word64 -> Word64 -> EdgeListState -> Word8 -> EdgeListState
- fromEdgeList :: Word64 -> [(Word64, Word64)] -> AdjacencyList
- toEdgeList :: AdjacencyList -> (Word64, [(Word64, Word64)])
- areAdjacent :: AdjacencyList -> Word64 -> Word64 -> Bool
Documentation
data AdjacencyList Source #
A graph represented as an adjacency list.
Constructors
| AdjacencyList | |
Instances
| Show AdjacencyList Source # | |
Defined in Nauty.Sparse6.Internal Methods showsPrec :: Int -> AdjacencyList -> ShowS # show :: AdjacencyList -> String # showList :: [AdjacencyList] -> ShowS # | |
| Eq AdjacencyList Source # | |
Defined in Nauty.Sparse6.Internal Methods (==) :: AdjacencyList -> AdjacencyList -> Bool # (/=) :: AdjacencyList -> AdjacencyList -> Bool # | |
Arguments
| :: AdjacencyList | Reference graph |
| -> Text | symmetric difference between reference graph and the resulting graph, in incremental |
| -> Either Text AdjacencyList |
Parse a graph in incremental sparse6 format.
The edges of the first graph are the symmetric difference between the edges of the second graph and the resulting graph.
data EncodeState Source #
State for encoding a graph.
Constructors
| EncodeState | |
Instances
| Show EncodeState Source # | |
Defined in Nauty.Sparse6.Internal Methods showsPrec :: Int -> EncodeState -> ShowS # show :: EncodeState -> String # showList :: [EncodeState] -> ShowS # | |
| Eq EncodeState Source # | |
Defined in Nauty.Sparse6.Internal | |
encode :: AdjacencyList -> Text Source #
Encode a graph in sparse6 format.
encodeSymmetricDifference :: Word64 -> [(Word64, Word64)] -> Text Source #
Encode a graph using the incremental sparse6 format.
The list of edges given is the symmetric difference between the current graph and the previous one in the list.
encodeVertex' :: Word64 -> Int -> [Word8] -> Word8 -> Int -> ([Word8], Word8, Int) Source #
Encode a single vertex.
oneBit :: forall (m :: Type -> Type). Monad m => StateT EncodeState m () Source #
Set next bit to one.
zeroBit :: forall (m :: Type -> Type). Monad m => StateT EncodeState m () Source #
Set next bit to zero.
encodeStartState :: EncodeState Source #
Starting state when encoding a graph.
data EdgeListState Source #
State when parsing a list of edges.
Constructors
| EdgeListState | |
Instances
| Show EdgeListState Source # | |
Defined in Nauty.Sparse6.Internal Methods showsPrec :: Int -> EdgeListState -> ShowS # show :: EdgeListState -> String # showList :: [EdgeListState] -> ShowS # | |
| Eq EdgeListState Source # | |
Defined in Nauty.Sparse6.Internal Methods (==) :: EdgeListState -> EdgeListState -> Bool # (/=) :: EdgeListState -> EdgeListState -> Bool # | |
parseEdgeList :: Word64 -> Word64 -> StateT ByteString (Either Text) AdjacencyList Source #
Parse a list of edges.
consumeByte :: Word64 -> Word64 -> EdgeListState -> Word8 -> Int -> EdgeListState Source #
Read a single byte.
edgeList :: Word64 -> Word64 -> EdgeListState -> Word8 -> EdgeListState Source #
Bytes of the list of edges.
fromEdgeList :: Word64 -> [(Word64, Word64)] -> AdjacencyList Source #
Create an adjacency matrix from a list of edges. Vertices need to be in the range from 0 to n-1.
toEdgeList :: AdjacencyList -> (Word64, [(Word64, Word64)]) Source #
The list of edges of a graph together with the number of vertices.
areAdjacent :: AdjacencyList -> Word64 -> Word64 -> Bool Source #
Whether two vertices are adjacent.