summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core
diff options
context:
space:
mode:
authorJasper Van der Jeugt <jaspervdj@gmail.com>2011-03-20 15:14:42 +0100
committerJasper Van der Jeugt <jaspervdj@gmail.com>2011-03-20 15:14:42 +0100
commit99233f830cead0dea265eb5ec708f781295e734e (patch)
tree23aa20037d6daebb398a2cc76f7f4893a10f8982 /src/Hakyll/Core
parent18d19e068b62025906c448a9c8a80fbe12faf77d (diff)
downloadhakyll-99233f830cead0dea265eb5ec708f781295e734e.tar.gz
Binary instance for DirectedGraph
Diffstat (limited to 'src/Hakyll/Core')
-rw-r--r--src/Hakyll/Core/DirectedGraph/Internal.hs10
1 files changed, 9 insertions, 1 deletions
diff --git a/src/Hakyll/Core/DirectedGraph/Internal.hs b/src/Hakyll/Core/DirectedGraph/Internal.hs
index 5b02ad6..70efd8e 100644
--- a/src/Hakyll/Core/DirectedGraph/Internal.hs
+++ b/src/Hakyll/Core/DirectedGraph/Internal.hs
@@ -1,18 +1,22 @@
-- | Internal structure of the DirectedGraph type. Not exported outside of the
-- library.
--
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.DirectedGraph.Internal
( Node (..)
, DirectedGraph (..)
) where
import Prelude hiding (reverse, filter)
+import Control.Applicative ((<$>), (<*>))
import Data.Monoid (Monoid, mempty, mappend)
import Data.Set (Set)
import Data.Map (Map)
import qualified Data.Map as M
import qualified Data.Set as S
+import Data.Binary (Binary, put, get)
+
-- | A node in the directed graph
--
data Node a = Node
@@ -20,6 +24,10 @@ data Node a = Node
, nodeNeighbours :: Set a -- ^ Edges starting at this node
} deriving (Show)
+instance (Binary a, Ord a) => Binary (Node a) where
+ put (Node t n) = put t >> put n
+ get = Node <$> get <*> get
+
-- | Append two nodes. Useful for joining graphs.
--
appendNodes :: Ord a => Node a -> Node a -> Node a
@@ -33,7 +41,7 @@ appendNodes (Node t1 n1) (Node t2 n2)
-- | Type used to represent a directed graph
--
newtype DirectedGraph a = DirectedGraph {unDirectedGraph :: Map a (Node a)}
- deriving (Show)
+ deriving (Show, Binary)
-- | Allow users to concatenate different graphs
--