diff options
author | Jasper Van der Jeugt <jaspervdj@gmail.com> | 2011-03-20 17:17:39 +0100 |
---|---|---|
committer | Jasper Van der Jeugt <jaspervdj@gmail.com> | 2011-03-20 17:17:39 +0100 |
commit | 9d95ef483d5ae251a5fae3c693507746dc1a2d16 (patch) | |
tree | db95f3ac019cb3d861e00438b24da30de2b6dc7b /src/Hakyll/Core | |
parent | 92aa446041d9857e57502bc4755e7e9aeca29659 (diff) | |
download | hakyll-9d95ef483d5ae251a5fae3c693507746dc1a2d16.tar.gz |
Save dependency graph after run
Diffstat (limited to 'src/Hakyll/Core')
-rw-r--r-- | src/Hakyll/Core/DirectedGraph/Internal.hs | 7 | ||||
-rw-r--r-- | src/Hakyll/Core/Identifier.hs | 8 | ||||
-rw-r--r-- | src/Hakyll/Core/Run.hs | 12 |
3 files changed, 17 insertions, 10 deletions
diff --git a/src/Hakyll/Core/DirectedGraph/Internal.hs b/src/Hakyll/Core/DirectedGraph/Internal.hs index 70efd8e..b836d6d 100644 --- a/src/Hakyll/Core/DirectedGraph/Internal.hs +++ b/src/Hakyll/Core/DirectedGraph/Internal.hs @@ -1,7 +1,7 @@ -- | Internal structure of the DirectedGraph type. Not exported outside of the -- library. -- -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable #-} module Hakyll.Core.DirectedGraph.Internal ( Node (..) , DirectedGraph (..) @@ -16,13 +16,14 @@ import qualified Data.Map as M import qualified Data.Set as S import Data.Binary (Binary, put, get) +import Data.Typeable (Typeable) -- | A node in the directed graph -- data Node a = Node { nodeTag :: a -- ^ Tag identifying the node , nodeNeighbours :: Set a -- ^ Edges starting at this node - } deriving (Show) + } deriving (Show, Typeable) instance (Binary a, Ord a) => Binary (Node a) where put (Node t n) = put t >> put n @@ -41,7 +42,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, Binary) + deriving (Show, Binary, Typeable) -- | Allow users to concatenate different graphs -- diff --git a/src/Hakyll/Core/Identifier.hs b/src/Hakyll/Core/Identifier.hs index 16403e6..5bfe9e4 100644 --- a/src/Hakyll/Core/Identifier.hs +++ b/src/Hakyll/Core/Identifier.hs @@ -20,7 +20,7 @@ -- @posts/foo.html@. In this case, the identifier is the name of the source -- file of the page. -- -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable #-} module Hakyll.Core.Identifier ( Identifier (..) , parseIdentifier @@ -29,14 +29,16 @@ module Hakyll.Core.Identifier import Control.Arrow (second) import Data.Monoid (Monoid) +import System.FilePath (joinPath) +import Data.Binary (Binary) import GHC.Exts (IsString, fromString) -import System.FilePath (joinPath) +import Data.Typeable (Typeable) -- | An identifier used to uniquely identify a value -- newtype Identifier = Identifier {unIdentifier :: [String]} - deriving (Eq, Ord, Monoid) + deriving (Eq, Ord, Monoid, Binary, Typeable) instance Show Identifier where show = toFilePath diff --git a/src/Hakyll/Core/Run.hs b/src/Hakyll/Core/Run.hs index 1fefff8..9a5245d 100644 --- a/src/Hakyll/Core/Run.hs +++ b/src/Hakyll/Core/Run.hs @@ -1,6 +1,6 @@ -- | This is the module which binds it all together -- -{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE GeneralizedNewtypeDeriving, OverloadedStrings #-} module Hakyll.Core.Run ( run ) where @@ -10,7 +10,7 @@ import Control.Monad (filterM) import Control.Monad.Trans (liftIO) import Control.Applicative (Applicative, (<$>)) import Control.Monad.Reader (ReaderT, runReaderT, ask) -import Control.Monad.State.Strict (StateT, evalStateT, get, modify) +import Control.Monad.State.Strict (StateT, runStateT, get, modify) import Control.Arrow ((&&&)) import qualified Data.Map as M import Data.Monoid (mempty, mappend) @@ -50,9 +50,13 @@ run configuration rules = do -- Extract the reader/state reader = unRuntime $ addNewCompilers [] compilers - state' = runReaderT reader $ env logger ruleSet provider store + stateT = runReaderT reader $ env logger ruleSet provider store - evalStateT state' state + -- Run the program and fetch the resulting state + ((), state') <- runStateT stateT state + + -- We want to save the final dependency graph for the next run + storeSet store "Hakyll.Core.Run.run" "dependencies" $ hakyllGraph state' -- Flush and return flushLogger logger |