Commit 0c650a74 authored by Kai Zhang's avatar Kai Zhang

type check during serialization

parent 6ce9fdfd
name: haskell-igraph
version: 0.5.0
version: 0.6.0
synopsis: Haskell interface of the igraph library.
description: igraph<"http://igraph.org/c/"> is a library for creating
and manipulating large graphs. This package provides the Haskell
......
......@@ -42,7 +42,7 @@ module IGraph
import Conduit
import Control.Arrow ((&&&))
import Control.Monad (forM, forM_, liftM, replicateM)
import Control.Monad (forM, forM_, liftM, replicateM, when)
import Control.Monad.Primitive
import Control.Monad.ST (runST)
import Data.Conduit.Cereal
......@@ -71,6 +71,7 @@ data Graph (d :: EdgeType) v e = Graph
instance (SingI d, Serialize v, Serialize e, Hashable v, Eq v)
=> Serialize (Graph d v e) where
put gr = do
put $ fromSing (sing :: Sing d)
put $ nNodes gr
go (nodeLab gr) (nNodes gr) 0
put $ nEdges gr
......@@ -79,6 +80,9 @@ instance (SingI d, Serialize v, Serialize e, Hashable v, Eq v)
go f n i | i >= n = return ()
| otherwise = put (f i) >> go f n (i+1)
get = do
directed <- get
when (fromSing (sing :: Sing d) /= directed) $
error "Incorrect graph type"
nn <- get
nds <- replicateM nn get
ne <- get
......
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
......@@ -15,15 +16,19 @@
module IGraph.Types where
import Data.Serialize (Serialize)
import Data.Singletons.Prelude
import Data.Singletons.TH
import GHC.Generics (Generic)
$(singletons [d|
data EdgeType = D
| U
deriving (Show, Read, Eq)
deriving (Show, Read, Eq, Generic)
|])
instance Serialize EdgeType
type Node = Int
type LNode a = (Node, a)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment